summaryrefslogtreecommitdiff
path: root/testsuite/tests/programs/andy_cherry
diff options
context:
space:
mode:
Diffstat (limited to 'testsuite/tests/programs/andy_cherry')
-rw-r--r--testsuite/tests/programs/andy_cherry/DataTypes.hs622
-rw-r--r--testsuite/tests/programs/andy_cherry/GenUtils.hs244
-rw-r--r--testsuite/tests/programs/andy_cherry/Interp.hs262
-rw-r--r--testsuite/tests/programs/andy_cherry/InterpUtils.hs371
-rw-r--r--testsuite/tests/programs/andy_cherry/Main.hs204
-rw-r--r--testsuite/tests/programs/andy_cherry/Makefile3
-rw-r--r--testsuite/tests/programs/andy_cherry/Parser.hs98
-rw-r--r--testsuite/tests/programs/andy_cherry/PrintTEX.hs182
-rw-r--r--testsuite/tests/programs/andy_cherry/andy_cherry.stdout7258
-rw-r--r--testsuite/tests/programs/andy_cherry/mygames.pgn1323
-rw-r--r--testsuite/tests/programs/andy_cherry/test.T14
11 files changed, 10581 insertions, 0 deletions
diff --git a/testsuite/tests/programs/andy_cherry/DataTypes.hs b/testsuite/tests/programs/andy_cherry/DataTypes.hs
new file mode 100644
index 0000000000..9f7c5571ba
--- /dev/null
+++ b/testsuite/tests/programs/andy_cherry/DataTypes.hs
@@ -0,0 +1,622 @@
+
+ module DataTypes where
+
+ import GenUtils
+ import Data.Array -- 1.3
+ import Data.Ix
+ import Data.Char
+ infix 1 =: -- 1.3
+ (=:) a b = (a,b)
+
+
+
+
+
+ class Presentable a where
+ userFormat :: a -> String -- in prefered display format
+
+
+
+
+
+ instance (Presentable a) => Presentable [a] where
+ userFormat xs = unlines (map userFormat xs)
+
+
+
+
+ data Piece
+ = King
+ | Queen
+ | Rook
+ | Knight
+ | Bishop
+ | Pawn deriving(Eq)
+
+ instance Presentable Piece where
+ userFormat King = "K"
+ userFormat Queen = "Q"
+ userFormat Rook = "R"
+ userFormat Knight = "N"
+ userFormat Bishop = "B"
+ userFormat Pawn = "P"
+
+
+
+
+ castleK = "O-O"
+ castleQ = "O-O-O"
+
+
+
+
+
+ data Colour = Black | White deriving (Eq)
+
+ instance Presentable Colour where
+ userFormat White = "White"
+ userFormat Black = "Black"
+
+ changeColour :: Colour -> Colour
+ changeColour White = Black
+ changeColour Black = White
+
+
+
+
+
+ type ChessRank = Int -- 1-8
+ type ChessFile = Int -- 1-8
+
+ type BoardPos = (ChessFile,ChessRank) -- ChessFile (0-7) and ChessRank (0-7)
+ type ExBoardPos = (Maybe ChessFile,Maybe ChessRank)
+
+ extendBP :: BoardPos -> ExBoardPos
+ extendBP (a,b) = (Just a,Just b)
+
+ compExBPandBP :: ExBoardPos -> BoardPos -> Bool
+ compExBPandBP (a,b) (c,d) = a `cmp` c && b `cmp` d
+ where
+ cmp Nothing _ = True
+ cmp (Just x) y = x == y
+
+ userFormatBoardPos :: BoardPos -> String
+ userFormatBoardPos (f,r) = userFormatFile f ++ userFormatRank r
+ userFormatExBoardPos :: ExBoardPos -> String
+ userFormatExBoardPos (Just f,Just r) = userFormatFile f ++ userFormatRank r
+ userFormatExBoardPos (Just f,Nothing) = userFormatFile f
+ userFormatExBoardPos (Nothing,Just r) = userFormatRank r
+ userFormatExBoardPos _ = ""
+ userFormatRank r = [toEnum (r + 48)]
+ userFormatFile f = [toEnum (f + 96)]
+
+
+
+
+
+ data MoveTok
+ = PieceTok Piece -- Q,K,R,B,N
+ | RankTok ChessRank -- 1 .. 8
+ | FileTok ChessFile -- a .. h
+ | PartCastleTok -- 0 | O | o
+ | CaptureTok -- x
+ | MoveToTok -- -
+ | QueensWith -- =
+ | CheckTok -- +
+ | MateTok -- #
+
+ charToMoveTok 'Q' = Just (PieceTok Queen)
+ charToMoveTok 'K' = Just (PieceTok King)
+ charToMoveTok 'R' = Just (PieceTok Rook)
+ charToMoveTok 'B' = Just (PieceTok Bishop)
+ charToMoveTok 'N' = Just (PieceTok Knight)
+ charToMoveTok '1' = Just (RankTok 1)
+ charToMoveTok '2' = Just (RankTok 2)
+ charToMoveTok '3' = Just (RankTok 3)
+ charToMoveTok '4' = Just (RankTok 4)
+ charToMoveTok '5' = Just (RankTok 5)
+ charToMoveTok '6' = Just (RankTok 6)
+ charToMoveTok '7' = Just (RankTok 7)
+ charToMoveTok '8' = Just (RankTok 8)
+ charToMoveTok 'a' = Just (FileTok 1)
+ charToMoveTok 'b' = Just (FileTok 2)
+ charToMoveTok 'c' = Just (FileTok 3)
+ charToMoveTok 'd' = Just (FileTok 4)
+ charToMoveTok 'e' = Just (FileTok 5)
+ charToMoveTok 'f' = Just (FileTok 6)
+ charToMoveTok 'g' = Just (FileTok 7)
+ charToMoveTok 'h' = Just (FileTok 8)
+ charToMoveTok '0' = Just (PartCastleTok)
+ charToMoveTok 'O' = Just (PartCastleTok)
+ charToMoveTok 'o' = Just (PartCastleTok)
+ charToMoveTok 'x' = Just (CaptureTok)
+ charToMoveTok '-' = Just (MoveToTok)
+ charToMoveTok '=' = Just (QueensWith)
+ charToMoveTok '+' = Just (CheckTok)
+ charToMoveTok '#' = Just (MateTok)
+ charToMoveTok _ = Nothing
+
+
+
+ data Quantum
+ = QuantumMove String -- Short Description of move
+ String -- Check or Mate (+ or #)
+ String -- !,??,?!, etc
+ Board -- Snap Shot of Board
+ | QuantumNAG Int -- !,??,?! stuff
+ | QuantumComment [String] -- { comment }
+ | QuantumResult String -- 1-0, etc (marks end of game)
+ | QuantumAnalysis [Quantum] -- ( analysis )
+ | QuantumPrintBoard -- {^D}
+
+ instance Presentable Quantum where
+ userFormat (QuantumMove mv ch ann _)
+ = mv ++ ch ++ ann
+ userFormat (QuantumNAG nag) = "$" ++ show nag
+ userFormat (QuantumComment comment)
+ = "[" ++ unwords comment ++ "]"
+ --userFormat (QuantumNumber num) = userFormat num
+ userFormat (QuantumResult str) = str
+ userFormat (QuantumAnalysis anal) =
+ "( " ++ unwords (map userFormat anal) ++ " )"
+
+
+
+ data Result = Win | Draw | Loss | Unknown
+
+ instance Presentable Result where
+ userFormat Win = "1-0"
+ userFormat Draw = "1/2-1/2"
+ userFormat Loss = "0-1"
+ userFormat Unknown = "*"
+
+ mkResult :: String -> Result
+ mkResult "1-0" = Win
+ mkResult "1/2-1/2" = Draw
+ mkResult "0-1" = Loss
+ mkResult _ = Unknown
+
+
+
+ data TagStr = TagStr String String
+
+ instance Presentable TagStr where
+ userFormat (TagStr tag str) = "[" ++ tag ++ " \"" ++ str ++ "\"]"
+
+ getTagStr :: String -> String -> [TagStr] -> String
+ getTagStr str def [] = def
+ getTagStr str def (TagStr st ans:rest)
+ | str == st = ans
+ | otherwise = getTagStr str def rest
+
+ getHeaderInfo
+ :: [TagStr]
+ -> (
+ String, -- Date
+ String, -- Site
+ Maybe Int, -- Game Number
+ Result, -- W/D/L
+ String, -- White
+ String, -- Black
+ String -- Opening
+ )
+ getHeaderInfo tags = (
+ date,
+ site,
+ gameno,
+ result,
+ white `par` whiteElo,
+ black `par` blackElo,
+ opening)
+ where
+ date = case getTagStr "Date" "?" tags of
+ [a,b,c,d,'.','?','?','.','?','?'] -> [a,b,c,d]
+ [a,b,c,d,'.',x,y,'.','?','?'] -> getMonth [x,y] ++ " " ++ [a,b,c,d]
+ def -> "?"
+ site = getTagStr "Site" "?" tags
+ gameno = case getTagStr "GameNumber" "" tags of
+ xs | all isDigit xs && not (null xs) -> Just (read xs)
+ _ -> Nothing
+ result = mkResult (getTagStr "Result" "*" tags)
+ white = cannon (getTagStr "White" "?" tags)
+ whiteElo = getTagStr "WhiteElo" "" tags
+ black = cannon (getTagStr "Black" "?" tags)
+ blackElo = getTagStr "BlackElo" "" tags
+ opening = getOpening (getTagStr "ECO" "" tags)
+
+ par xs "" = xs
+ par xs ys = xs ++ " (" ++ ys ++ ")"
+
+ getMonth "01" = "Jan"
+ getMonth "02" = "Feb"
+ getMonth "03" = "Mar"
+ getMonth "04" = "Apr"
+ getMonth "05" = "May"
+ getMonth "06" = "Jun"
+ getMonth "07" = "Jul"
+ getMonth "08" = "Aug"
+ getMonth "09" = "Sep"
+ getMonth "10" = "Oct"
+ getMonth "11" = "Nov"
+ getMonth "12" = "Dec"
+
+ cannon name = case span (/= ',') name of
+ (a,[',',' ',b]) -> b : ". " ++ a
+ (a,[',',b]) -> b : ". " ++ a
+ (a,',':' ':b) -> b ++ " " ++ a
+ (a,',':b) -> b ++ " " ++ a
+ _ -> name
+
+
+ getOpening eco@[a,b,c] | a >= 'A' && a <= 'E' && isDigit b && isDigit c
+ = getOpenName ((fromEnum a - fromEnum 'A') * 100
+ + (fromEnum b - fromEnum '0') * 10
+ + (fromEnum c - fromEnum '0')) ++ " " ++ eco
+ getOpening other = other
+
+ getOpenName :: Int -> String
+ getOpenName eco
+ | otherwise = "Foo"
+ {-
+ | eco == 000 = "Irregular Openings"
+ | eco == 001 = "Larsen Opening"
+ | eco == 002 = "From's Gambit and Bird's Open"
+ | eco == 003 = "Bird's Opening"
+ | eco == 004 = "Dutch System"
+ | eco == 005 = "Transposition to various Open"
+ | eco == 006 = "Zukertort Opening"
+ | eco >= 007 && eco <= 008
+ = "Barcza System"
+ | eco == 009 = "Reti Opening"
+ | eco == 010 = "Variations of Dutch, QI, KI"
+ | eco >= 011 && eco <= 014
+ = "Reti Opening"
+ | eco == 015 = "English counter King's Fianch"
+ | eco >= 016 && eco <= 039
+ = "English Opening"
+ | eco == 040 = "Unusual replies to 1.d4"
+ | eco == 041 = "Modern Defence counter 1.d4"
+ | eco == 042 = "Modern Defence with c2-c4"
+ | eco >= 043 && eco <= 044
+ = "Old Benoni"
+ | eco == 045 = "Queen's Pawn-Trompowski Var"
+ | eco == 046 = "Queen's Pawn Opening"
+ | eco == 047 = "Queen's Indian"
+ | eco >= 048 && eco <= 049
+ = "King's Indian"
+ | eco == 050 = "Queen's Indian"
+ | eco >= 051 && eco <= 052
+ = "Budapest Defence"
+ | eco >= 053 && eco <= 056
+ = "Old Indian Defence"
+ | eco >= 057 && eco <= 059
+ = "Volga-Benko Gambit"
+ | eco >= 060 && eco <= 079
+ = "Benoni"
+ | eco >= 080 && eco <= 099
+ = "Dutch Defence"
+ | eco == 100 = "Owen Def, Nimzowitsch Def"
+ | eco == 101 = "Center Counter"
+ | eco >= 102 && eco <= 105
+ = "Alekhine's Defence"
+ | eco == 106 = "Modern Defence"
+ | eco >= 107 && eco <= 109
+ = "Pirc Defence"
+ | eco >= 110 && eco <= 119
+ = "Caro-Kann Defence"
+ | eco >= 120 && eco <= 199
+ = "Sicilian Defence"
+ | eco >= 200 && eco <= 219
+ = "French Defence"
+ | eco == 220 = "Rare moves"
+ | eco == 221 = "Nordic Gambit"
+ | eco == 222 = "Central Gambit"
+ | eco >= 223 && eco <= 224
+ = "Bishop's Opening"
+ | eco >= 225 && eco <= 229
+ = "Vienna Game"
+ | eco == 230 = "King's Gambit Declined"
+ | eco >= 231 && eco <= 232
+ = "Falkbeer Counter Gambit"
+ | eco >= 233 && eco <= 239
+ = "King's Gambit"
+ | eco == 240 = "Latvian Gambit"
+ | eco == 241 = "Philidor Defence"
+ | eco >= 242 && eco <= 243
+ = "Russian Defence-Petrov"
+ | eco >= 244 && eco <= 245
+ = "Scotch Opening"
+ | eco >= 246 && eco <= 249
+ = "Four Knight's"
+ | eco == 250 = "Italian Opening"
+ | eco >= 251 && eco <= 252
+ = "Evans Gambit"
+ | eco >= 253 && eco <= 254
+ = "Italian Opening"
+ | eco >= 255 && eco <= 259
+ = "Two Knight's Play"
+ | eco >= 260 && eco <= 299
+ = "Ruy Lopez"
+ | eco >= 300 && eco <= 305
+ = "Queen Pawn's Opening"
+ | eco >= 306 && eco <= 307
+ = "Queen's Gambit"
+ | eco >= 308 && eco <= 309
+ = "Albins Counter Gambit"
+ | eco >= 310 && eco <= 319
+ = "Slav Defence"
+ | eco >= 320 && eco <= 329
+ = "Queen's Gambit Accepted"
+ | eco >= 330 && eco <= 369
+ = "Queen's Gambit"
+ | eco >= 370 && eco <= 399
+ = "Gruenfeld Defence"
+ | eco >= 400 && eco <= 409
+ = "Catalan"
+ | eco == 410 = "Blumenfeld Gambit"
+ | eco >= 411 && eco <= 419
+ = "Queen's Indian"
+ | eco >= 420 && eco <= 459
+ = "Nimzo Indian"
+ | eco >= 460 && eco <= 499
+ = "King's Indian"
+ -}
+
+
+
+ data MoveNumber = MoveNumber Int Colour
+ instance Presentable MoveNumber where
+ userFormat (MoveNumber n White) = show n ++ "."
+ userFormat (MoveNumber n Black) = show n ++ "..."
+
+ initMoveNumber = MoveNumber 1 White
+ incMove (MoveNumber i White) = MoveNumber i Black
+ incMove (MoveNumber i Black) = MoveNumber (i+1) White
+ decMove (MoveNumber i White) = MoveNumber (i-1) Black
+ decMove (MoveNumber i Black) = MoveNumber i White
+ getMoveColour :: MoveNumber -> Colour
+ getMoveColour (MoveNumber _ c) = c
+
+
+
+ data Token
+
+
+
+ = StringToken String
+ | AsterixToken
+ | LeftABToken -- ??
+ | RightABToken -- ??
+ | NAGToken Int -- `normal' NAGS
+ | NAGAnnToken Int String
+ -- `special' move annotating NAGS (1-6)
+ | SymbolToken String
+ | CommentToken [String] -- list of words
+ | LeftSBToken
+ | RightSBToken
+ | LeftRBToken
+ | RightRBToken
+ | IntToken Int
+ | PeriodToken
+
+
+
+ | AnalToken [Token]
+
+ instance Presentable Token where
+ userFormat (StringToken str) = show str
+ userFormat (IntToken n) = show n
+ userFormat (PeriodToken) = "."
+ userFormat (AsterixToken) = "*"
+ userFormat (LeftSBToken) = "["
+ userFormat (RightSBToken) = "]"
+ userFormat (LeftRBToken) = "("
+ userFormat (RightRBToken) = ")"
+ userFormat (LeftABToken) = "<"
+ userFormat (RightABToken) = ">"
+ userFormat (NAGToken i) = "$" ++ show i
+ userFormat (NAGAnnToken i s) = "$" ++ show i
+ userFormat (SymbolToken str) = str
+ userFormat (CommentToken str) = "{" ++ unwords str ++ "}"
+ userFormat (AnalToken toks) = "( " ++ unwords (map userFormat toks)
+ ++ " )"
+
+
+
+
+
+ data Game a = Game [TagStr] [a]
+
+ type AbsGame = Game Token
+ type RealGame = Game Quantum
+
+ instance (Presentable a) => Presentable (Game a) where
+ userFormat (Game tags toks) =
+ unlines (map userFormat tags
+ ++ formatText 78 (map userFormat toks))
+
+
+
+
+
+
+ data PlayMove
+ = PlayMove
+ Piece -- with this
+ BoardPos -- from here
+ BoardPos -- to here (possibly capturing)
+ SpecialMove
+
+ mkPlayMove p f t = PlayMove p f t NothingSpecial
+
+ data SpecialMove
+ = NothingSpecial
+ | BigPawnMove -- allows e.p. next move
+ | Queening Piece -- queen with this
+ | EnPassant -- capture e.p.
+ deriving (Eq)
+
+ instance Presentable PlayMove where
+ userFormat (PlayMove piece pos pos' sp) =
+ userFormat piece ++
+ userFormatBoardPos pos ++ "-" ++
+ userFormatBoardPos pos' ++
+ userFormat sp
+
+ instance Presentable SpecialMove where
+ userFormat (NothingSpecial) = ""
+ userFormat (BigPawnMove) = "{b.p.m.}"
+ userFormat (Queening p) = "=" ++ userFormat p
+ userFormat (EnPassant) = "e.p."
+
+ extractSrcFromPlayMove :: PlayMove -> BoardPos
+ extractSrcFromPlayMove (PlayMove _ src _ _) = src
+
+ extractDestFromPlayMove :: PlayMove -> BoardPos
+ extractDestFromPlayMove (PlayMove _ _ dest _) = dest
+
+ extractSpecialFromPlayMove :: PlayMove -> SpecialMove
+ extractSpecialFromPlayMove (PlayMove _ _ _ sp) = sp
+
+
+
+
+
+
+ data BoardSquare
+ = VacantSq
+ | WhitesSq Piece
+ | BlacksSq Piece
+
+ data SquareContent
+ = Vacant
+ | Friendly
+ | Baddy
+ | OffBoard deriving (Eq)
+
+ instance Presentable SquareContent where
+ userFormat Vacant = "."
+ userFormat Friendly = "*"
+ userFormat Baddy = "#"
+ userFormat OffBoard = "?"
+
+
+
+
+
+
+ data Board
+ = Board (Array BoardPos BoardSquare)
+ MoveNumber -- current player & and move
+ (Maybe ChessFile) -- e.p. possibilties.
+
+
+
+ displayBoard :: Colour -> Board -> [String]
+ displayBoard col (Board arr _ ep) =
+ ([cjustify 33 (userFormat (changeColour col)),""] ++
+ [
+ concat [ (case (even x,even y) of
+ (True,True) -> showSq (x `div` 2) (y `div` 2)
+ (False,False) -> "+"
+ (True,False) -> "---"
+ (False,True) -> (if x == 17 then "| " ++ show (y `div` 2) else "|"))
+ | x <- [1..17::Int]]
+ | y <- reverse [1..17::Int]] ++
+ [concat [ " " ++ [x] ++ " " | x <- "abcdefgh" ]] ++
+ ["",cjustify 33 (userFormat col),"",
+ case ep of
+ Nothing -> ""
+ Just p -> "EnPassant:" ++ userFormatFile p ])
+ where
+ make n str = take n (str ++ repeat ' ')
+ lookupPlace :: Int -> Int -> BoardSquare
+ lookupPlace x' y' = arr ! (x',y')
+
+ bold :: String -> String
+ bold str = map toLower str
+
+ showSq x y = case lookupPlace x y of
+ VacantSq -> [if_dot,if_dot,if_dot]
+ (WhitesSq p) -> (if_dot : userFormat p) ++ [if_dot]
+ (BlacksSq p) -> (if_dot : bold (userFormat p)) ++ [if_dot]
+ where
+ if_dot = if (x - y) `rem` 2 == 0 then '.' else ' '
+
+ instance Presentable Board where
+ userFormat = unlines . displayBoard White
+
+ boardSize :: (BoardPos,BoardPos)
+ boardSize = ((1,1),(8,8))
+
+
+
+
+ buildBoard :: String -> Board
+ buildBoard str = Board brd initMoveNumber Nothing
+ where
+ brd = array boardSize (zipWith (=:) allSq (mkPieces str))
+ allSq = [ (x,y) | y <- reverse [1..8::Int],x <- [1..8::Int]]
+ mkPieces :: String -> [BoardSquare]
+ mkPieces (hd:rest) | hd `elem` "KQRNBPkqrnbp" = pc : mkPieces rest
+ where
+ pc = case hd of
+ 'K' -> WhitesSq King
+ 'Q' -> WhitesSq Queen
+ 'R' -> WhitesSq Rook
+ 'N' -> WhitesSq Knight
+ 'B' -> WhitesSq Bishop
+ 'P' -> WhitesSq Pawn
+ 'k' -> BlacksSq King
+ 'q' -> BlacksSq Queen
+ 'r' -> BlacksSq Rook
+ 'n' -> BlacksSq Knight
+ 'b' -> BlacksSq Bishop
+ 'p' -> BlacksSq Pawn
+ mkPieces ('/':rest) = mkPieces rest
+ mkPieces (c:rest) | isDigit c =
+ case span isDigit rest of
+ (cs,rest') -> take (read (c:cs)) (repeat VacantSq)
+ ++ mkPieces rest'
+ mkPieces [] = []
+
+ startBoard :: Board -- the uni before the big bang.
+ startBoard = buildBoard "rnbqkbnr/pppppppp/32/PPPPPPPP/RNBQKBNR"
+
+ lookupSquare :: Colour -> BoardSquare -> SquareContent
+ lookupSquare _ VacantSq = Vacant
+ lookupSquare White (WhitesSq p) = Friendly
+ lookupSquare Black (WhitesSq p) = Baddy
+ lookupSquare White (BlacksSq p) = Baddy
+ lookupSquare Black (BlacksSq p) = Friendly
+
+ lookupBoard :: Board -> BoardPos -> SquareContent
+ lookupBoard (Board arr col _) pos =
+ if inRange boardSize pos
+ then lookupSquare (getMoveColour col) (arr ! pos)
+ else OffBoard
+
+ lookupBoardSquare :: Board -> BoardPos -> BoardSquare
+ lookupBoardSquare (Board arr _ _) pos = arr ! pos
+
+ getSquarePiece :: BoardSquare -> Maybe Piece
+ getSquarePiece VacantSq = Nothing
+ getSquarePiece (WhitesSq p) = Just p
+ getSquarePiece (BlacksSq p) = Just p
+
+ lookupBoardPiece :: Board -> BoardPos -> Maybe Piece
+ lookupBoardPiece (Board arr _ _) pos =
+ case arr ! pos of
+ VacantSq -> Nothing
+ WhitesSq piece -> Just piece
+ BlacksSq piece -> Just piece
+
+
+
+ {-# INLINE mkColBoardSq #-}
+ mkColBoardSq :: Colour -> Piece -> BoardSquare
+ mkColBoardSq White p = WhitesSq p
+ mkColBoardSq Black p = BlacksSq p
+
+ getBoardColour (Board _ mv _) = getMoveColour mv
+
diff --git a/testsuite/tests/programs/andy_cherry/GenUtils.hs b/testsuite/tests/programs/andy_cherry/GenUtils.hs
new file mode 100644
index 0000000000..3e1de07fb8
--- /dev/null
+++ b/testsuite/tests/programs/andy_cherry/GenUtils.hs
@@ -0,0 +1,244 @@
+
+
+
+
+
+
+
+
+
+module GenUtils (
+
+ trace,
+
+ assocMaybe, assocMaybeErr,
+ arrElem,
+ arrCond,
+ memoise,
+ Maybe(..),
+ MaybeErr(..),
+ mapMaybe,
+ mapMaybeFail,
+ maybeToBool,
+ maybeToObj,
+ maybeMap,
+ joinMaybe,
+ mkClosure,
+ foldb,
+
+ mapAccumL,
+
+ sortWith,
+ sort,
+ cjustify,
+ ljustify,
+ rjustify,
+ space,
+ copy,
+ combinePairs,
+ formatText ) where
+
+import Data.Array -- 1.3
+import Data.Ix -- 1.3
+
+import Debug.Trace ( trace )
+
+
+-- -------------------------------------------------------------------------
+
+-- Here are two defs that everyone seems to define ...
+-- HBC has it in one of its builtin modules
+
+#if defined(__GLASGOW_HASKELL__) || defined(__GOFER__)
+
+--in 1.3: data Maybe a = Nothing | Just a deriving (Eq,Ord,Text)
+
+#endif
+
+infix 1 =: -- 1.3
+type Assoc a b = (a,b) -- 1.3
+(=:) a b = (a,b)
+
+mapMaybe :: (a -> Maybe b) -> [a] -> [b]
+mapMaybe f [] = []
+mapMaybe f (a:r) = case f a of
+ Nothing -> mapMaybe f r
+ Just b -> b : mapMaybe f r
+
+-- This version returns nothing, if *any* one fails.
+
+mapMaybeFail f (x:xs) = case f x of
+ Just x' -> case mapMaybeFail f xs of
+ Just xs' -> Just (x':xs')
+ Nothing -> Nothing
+ Nothing -> Nothing
+mapMaybeFail f [] = Just []
+
+maybeToBool :: Maybe a -> Bool
+maybeToBool (Just _) = True
+maybeToBool _ = False
+
+maybeToObj :: Maybe a -> a
+maybeToObj (Just a) = a
+maybeToObj _ = error "Trying to extract object from a Nothing"
+
+maybeMap :: (a -> b) -> Maybe a -> Maybe b
+maybeMap f (Just a) = Just (f a)
+maybeMap f Nothing = Nothing
+
+
+joinMaybe :: (a -> a -> a) -> Maybe a -> Maybe a -> Maybe a
+joinMaybe _ Nothing Nothing = Nothing
+joinMaybe _ (Just g) Nothing = Just g
+joinMaybe _ Nothing (Just g) = Just g
+joinMaybe f (Just g) (Just h) = Just (f g h)
+
+data MaybeErr a err = Succeeded a | Failed err deriving (Eq,Show{-was:Text-})
+
+-- @mkClosure@ makes a closure, when given a comparison and iteration loop.
+-- Be careful, because if the functional always makes the object different,
+-- This will never terminate.
+
+mkClosure :: (a -> a -> Bool) -> (a -> a) -> a -> a
+mkClosure eq f = match . iterate f
+ where
+ match (a:b:c) | a `eq` b = a
+ match (_:c) = match c
+
+-- fold-binary.
+-- It combines the element of the list argument in balanced mannerism.
+
+foldb :: (a -> a -> a) -> [a] -> a
+foldb f [] = error "can't reduce an empty list using foldb"
+foldb f [x] = x
+foldb f l = foldb f (foldb' l)
+ where
+ foldb' (x:y:x':y':xs) = f (f x y) (f x' y') : foldb' xs
+ foldb' (x:y:xs) = f x y : foldb' xs
+ foldb' xs = xs
+
+-- Merge two ordered lists into one ordered list.
+
+mergeWith :: (a -> a -> Bool) -> [a] -> [a] -> [a]
+mergeWith _ [] ys = ys
+mergeWith _ xs [] = xs
+mergeWith le (x:xs) (y:ys)
+ | x `le` y = x : mergeWith le xs (y:ys)
+ | otherwise = y : mergeWith le (x:xs) ys
+
+insertWith :: (a -> a -> Bool) -> a -> [a] -> [a]
+insertWith _ x [] = [x]
+insertWith le x (y:ys)
+ | x `le` y = x:y:ys
+ | otherwise = y:insertWith le x ys
+
+-- Sorting is something almost every program needs, and this is the
+-- quickest sorting function I know of.
+
+sortWith :: (a -> a -> Bool) -> [a] -> [a]
+sortWith le [] = []
+sortWith le lst = foldb (mergeWith le) (splitList lst)
+ where
+ splitList (a1:a2:a3:a4:a5:xs) =
+ insertWith le a1
+ (insertWith le a2
+ (insertWith le a3
+ (insertWith le a4 [a5]))) : splitList xs
+ splitList [] = []
+ splitList (r:rs) = [foldr (insertWith le) [r] rs]
+
+sort :: (Ord a) => [a] -> [a]
+sort = sortWith (<=)
+
+-- Gofer-like stuff:
+
+cjustify, ljustify, rjustify :: Int -> String -> String
+cjustify n s = space halfm ++ s ++ space (m - halfm)
+ where m = n - length s
+ halfm = m `div` 2
+ljustify n s = s ++ space (max 0 (n - length s))
+rjustify n s = space (max 0 (n - length s)) ++ s
+
+space :: Int -> String
+space n = copy n ' '
+
+copy :: Int -> a -> [a] -- make list of n copies of x
+copy n x = take n xs where xs = x:xs
+
+combinePairs :: (Ord a) => [(a,b)] -> [(a,[b])]
+combinePairs xs =
+ combine [ (a,[b]) | (a,b) <- sortWith (\ (a,_) (b,_) -> a <= b) xs]
+ where
+ combine [] = []
+ combine ((a,b):(c,d):r) | a == c = combine ((a,b++d) : r)
+ combine (a:r) = a : combine r
+
+assocMaybe :: (Eq a) => [(a,b)] -> a -> Maybe b
+assocMaybe env k = case [ val | (key,val) <- env, k == key] of
+ [] -> Nothing
+ (val:vs) -> Just val
+
+assocMaybeErr :: (Eq a) => [(a,b)] -> a -> MaybeErr b String
+assocMaybeErr env k = case [ val | (key,val) <- env, k == key] of
+ [] -> Failed "assoc: "
+ (val:vs) -> Succeeded val
+
+
+deSucc (Succeeded e) = e
+
+mapAccumL :: (a -> b -> (c,a)) -> a -> [b] -> ([c],a)
+mapAccumL f s [] = ([],s)
+mapAccumL f s (b:bs) = (c:cs,s'')
+ where
+ (c,s') = f s b
+ (cs,s'') = mapAccumL f s' bs
+
+
+
+-- Now some utilties involving arrays.
+-- Here is a version of @elem@ that uses partual application
+-- to optimise lookup.
+
+arrElem :: (Ix a) => [a] -> a -> Bool
+arrElem obj = \x -> inRange size x && arr ! x
+ where
+ size = (maximum obj,minimum obj)
+ arr = listArray size [ i `elem` obj | i <- range size ]
+
+-- Here is the functional version of a multi-way conditional,
+-- again using arrays, of course. Remember @b@ can be a function !
+-- Note again the use of partiual application.
+
+arrCond :: (Ix a)
+ => (a,a) -- the bounds
+ -> [(Assoc [a] b)] -- the simple lookups
+ -> [(Assoc (a -> Bool) b)] -- the functional lookups
+ -> b -- the default
+ -> a -> b -- the (functional) result
+
+arrCond bds pairs fnPairs def = (!) arr'
+ where
+ arr' = array bds [ t =: head
+ ([ r | (p, r) <- pairs, elem t p ] ++
+ [ r | (f, r) <- fnPairs, f t ] ++
+ [ def ])
+ | t <- range bds ]
+
+memoise :: (Ix a) => (a,a) -> (a -> b) -> a -> b
+memoise bds f = (!) arr
+ where arr = array bds [ t =: f t | t <- range bds ]
+
+-- Quite neat this. Formats text to fit in a column.
+
+formatText :: Int -> [String] -> [String]
+formatText n = map unwords . cutAt n []
+ where
+ cutAt :: Int -> [String] -> [String] -> [[String]]
+ cutAt m wds [] = [reverse wds]
+ cutAt m wds (wd:rest) = if len <= m || null wds
+ then cutAt (m-(len+1)) (wd:wds) rest
+ else reverse wds : cutAt n [] (wd:rest)
+ where len = length wd
+
+
+
diff --git a/testsuite/tests/programs/andy_cherry/Interp.hs b/testsuite/tests/programs/andy_cherry/Interp.hs
new file mode 100644
index 0000000000..7d33e896cf
--- /dev/null
+++ b/testsuite/tests/programs/andy_cherry/Interp.hs
@@ -0,0 +1,262 @@
+
+
+ module Interp (runInterp) where
+
+ import GenUtils
+ import DataTypes
+ import InterpUtils
+ import Parser (pgnLexer)
+
+
+
+ runInterp :: AbsGame -> RealGame
+ runInterp (Game tags toks) = Game tags (pgnInterp toks initParState)
+
+
+
+ initParState = (FirstBoard startBoard)
+
+ type Par a = StoreBoard -> a
+ thenP :: Par a -> (a -> Par b) -> Par b
+ returnP :: a -> Par a
+
+ returnP a = \s -> a
+ thenP m k s = case m s of
+ r -> k r s
+
+ failP a = \s -> error a
+ consP q rest = \s -> q : pgnInterp rest s
+ thenP' :: Par StoreBoard -> Par a -> Par a
+ thenP' m k s = case m s of
+ r -> k r
+ newGameP :: Par a -> Par a
+ newGameP m = \ _ -> m initParState
+
+ getCurrColour :: Par Colour
+ getCurrColour =
+ getBoard `thenP` \ (Board _ (MoveNumber _ col) _) ->
+ returnP col
+
+ checkColour :: MoveNumber -> Par ()
+ checkColour (MoveNumber i col) =
+ getBoard `thenP` \ (Board _ (MoveNumber i' col') _) ->
+ if i == i' && col == col'
+ then returnP ()
+ else failP ("number mis-match: "
+ ++ userFormat (MoveNumber i col)
+ ++ " (looking for "
+ ++ userFormat (MoveNumber i' col')
+ ++ ")\n")
+
+
+
+ data StoreBoard
+ = FirstBoard Board
+ | UndoableBoard Board {- new -} Board {- back one -}
+
+ updateBoard :: Board -> Par StoreBoard
+ updateBoard brd (FirstBoard old_brd)
+ = UndoableBoard brd old_brd
+ updateBoard brd (UndoableBoard old_brd _)
+ = UndoableBoard brd old_brd
+
+ getBoard :: Par Board
+ getBoard s@(FirstBoard brd)
+ = brd
+ getBoard s@(UndoableBoard brd _)
+ = brd
+
+ undoBoard :: Par StoreBoard
+ undoBoard (FirstBoard _)
+ = error "Incorrect start to some analysis"
+ undoBoard (UndoableBoard _ old_brd)
+ = FirstBoard old_brd
+
+
+
+ pgnInterp :: [Token] -> Par [Quantum]
+ pgnInterp (IntToken n:PeriodToken:PeriodToken:PeriodToken:rest) =
+ checkColour (MoveNumber n Black) `thenP` \ () ->
+ pgnInterp rest
+ pgnInterp (IntToken n:PeriodToken:rest) =
+ checkColour (MoveNumber n White) `thenP` \ () ->
+ pgnInterp rest
+
+ pgnInterp (SymbolToken str:CommentToken (ann:rs):r)
+ | all (flip elem "!?") ann =
+ pgnInterp (SymbolToken str:pgnLexer ann ++ (CommentToken rs:r))
+
+
+
+
+ pgnInterp (CommentToken (n:tag:rest):r)
+ | head tag == '(' && take 2 (reverse tag) == ":)" && length rest > 1 =
+ getCurrColour `thenP` \ col ->
+ let
+ invert Black r = r -- because the move has *already* happend
+ invert _ "0.00" = "0.00" -- dont negate 0
+ invert _ ('-':r) = r
+ invert _ r = '-':r
+ in
+ pgnInterp (LeftRBToken:map SymbolToken (take (length rest-1) rest)
+ ++ [CommentToken ["Score:",invert col n],RightRBToken] ++ r)
+
+
+ pgnInterp (CommentToken []:rest) = pgnInterp rest
+ pgnInterp (CommentToken comm:rest) =
+ consP (QuantumComment comm) rest
+ pgnInterp (NAGToken nag:rest) =
+ consP (QuantumNAG nag) rest
+ pgnInterp (NAGAnnToken nag _:rest) =
+ consP (QuantumNAG nag) rest
+ pgnInterp (SymbolToken "0-1":rest) =
+ consP (QuantumResult "0-1") rest
+ pgnInterp (SymbolToken "1-0":rest) =
+ consP (QuantumResult "1-0") rest
+ pgnInterp (SymbolToken "1/2-1/2":rest) =
+ consP (QuantumResult "1/2-1/2") rest
+ pgnInterp (AsterixToken:rest) =
+ consP (QuantumResult "*") rest
+ pgnInterp (SymbolToken move:rest@(NAGAnnToken _ str:_)) =
+ getBoard `thenP` \ brd ->
+ parseMove move brd `thenP` \ (mv,ch,corrMv,new_brd) ->
+ updateBoard new_brd `thenP'`
+ consP (QuantumMove mv ch str new_brd) rest
+ pgnInterp (SymbolToken move:rest) =
+ getBoard `thenP` \ brd ->
+ parseMove move brd `thenP` \ (mv,ch,corrMv,new_brd) ->
+ updateBoard new_brd `thenP'`
+ consP (QuantumMove mv ch "" new_brd) rest
+ pgnInterp (LeftRBToken:rest) =
+ getAnalysis rest 0 [] `thenP` \ (anal,rest) ->
+ (undoBoard `thenP'`
+ pgnInterp anal) `thenP` \ anal' ->
+ consP (QuantumAnalysis anal') rest
+ pgnInterp [] = returnP []
+ pgnInterp toks = failP ("when reading: "
+ ++ unwords (map userFormat (take 10 toks)))
+
+
+
+ getAnalysis (t@LeftRBToken:r) n anal = getAnalysis r (n+1) (t:anal)
+ getAnalysis (t@RightRBToken:r) n anal
+ | n == (0 :: Int) = returnP (reverse anal,r)
+ | otherwise = getAnalysis r (n-1) (t:anal)
+ getAnalysis (t:r) n anal = getAnalysis r n (t:anal)
+ getAnalysis [] n anal = failP "no closing ')'"
+
+
+
+
+ parseMove :: String -> Board -> Par (String,String,String,Board)
+ parseMove move brd@(Board _ (MoveNumber _ col) _) =
+ case mapMaybeFail charToMoveTok move of
+ Nothing -> failP ("strange move:" ++ move)
+ Just mv_toks ->
+ let
+ (chs,mv_toks') = getChecks (reverse mv_toks)
+ (queen,mv_toks'') = getQueen mv_toks'
+ in
+ case parseAlgMove mv_toks'' queen brd of
+ (the_mv,new_brd) -> returnP (the_mv,chs,"$$",new_brd)
+
+
+
+ parseAlgMove
+ :: [MoveTok]
+ -> Maybe Piece
+ -> Board
+ -> (String,Board)
+ parseAlgMove [PartCastleTok,MoveToTok,PartCastleTok] Nothing
+ = findCastleKMove
+ parseAlgMove [PartCastleTok,MoveToTok,PartCastleTok,
+ MoveToTok,PartCastleTok] Nothing
+ = findCastleQMove
+
+ parseAlgMove (PieceTok King:r) Nothing = parsePieceMove r King
+ parseAlgMove (PieceTok Queen:r) Nothing = parsePieceMove r Queen
+ parseAlgMove (PieceTok Rook:r) Nothing = parsePieceMove r Rook
+ parseAlgMove (PieceTok Knight:r) Nothing = parsePieceMove r Knight
+ parseAlgMove (PieceTok Bishop:r) Nothing = parsePieceMove r Bishop
+
+
+
+ parseAlgMove [FileTok sf,RankTok sr,MoveToTok,FileTok df,RankTok dr] q =
+ findAPawnMove (extendBP (sf,sr)) (extendBP (df,dr)) q
+ parseAlgMove [FileTok sf,RankTok sr,CaptureTok,FileTok df,RankTok dr] q =
+ findAPawnMove (extendBP (sf,sr)) (extendBP (df,dr)) q
+
+
+
+ parseAlgMove [FileTok sf,RankTok sr,FileTok df,RankTok dr] q = \ brd ->
+ case lookupBoardPiece brd (sf,sr) of
+ Nothing -> error ("cant find piece at: " ++ userFormatBoardPos (sf,sr))
+ Just Pawn -> findAPawnMove (extendBP (sf,sr)) (extendBP (df,dr)) q brd
+ Just King | sf == 5 && df == 7 -> findCastleKMove brd
+ Just King | sf == 5 && df == 3 -> findCastleQMove brd
+ Just p -> findAMove p (extendBP (sf,sr)) (extendBP (df,dr)) brd
+
+ -- later !
+
+
+
+ parseAlgMove [FileTok df,RankTok dr] q =
+ findAPawnMove (Nothing,Nothing) (extendBP (df,dr)) q
+
+
+
+ parseAlgMove [FileTok sf,CaptureTok,FileTok df,RankTok dr] q =
+ findAPawnMove (Just sf,Nothing) (extendBP (df,dr)) q
+
+
+
+ parseAlgMove [FileTok sf,FileTok df] q =
+ findAPawnMove (Just sf,Nothing) (Just df,Nothing) q
+
+
+
+ parseAlgMove [FileTok sf,CaptureTok,FileTok df] q =
+ findAPawnMove (Just sf,Nothing) (Just df,Nothing) q
+ parseAlgMove _ _ = error "!>!"
+
+
+
+ parsePieceMove [FileTok df,RankTok dr] p
+ = findAMove p (Nothing,Nothing) (extendBP (df,dr))
+
+
+
+ parsePieceMove [CaptureTok,FileTok df,RankTok dr] p
+ = findAMove p (Nothing,Nothing) (extendBP (df,dr))
+
+
+
+ parsePieceMove [RankTok sr,FileTok df,RankTok dr] p
+ = findAMove p (Nothing,Just sr) (extendBP (df,dr))
+ parsePieceMove [RankTok sr,CaptureTok,FileTok df,RankTok dr] p
+ = findAMove p (Nothing,Just sr) (extendBP (df,dr))
+
+
+
+ parsePieceMove [FileTok sf,FileTok df,RankTok dr] p
+ = findAMove p (Just sf,Nothing) (extendBP (df,dr))
+ parsePieceMove [FileTok sf,CaptureTok,FileTok df,RankTok dr] p
+ = findAMove p (Just sf,Nothing) (extendBP (df,dr))
+
+
+
+ parsePieceMove [FileTok sf,RankTok sr,MoveToTok,FileTok df,RankTok dr] p
+ = findAMove p (extendBP (sf,sr)) (extendBP (df,dr))
+ parsePieceMove [FileTok sf,RankTok sr,CaptureTok,FileTok df,RankTok dr] p
+ = findAMove p (extendBP (sf,sr)) (extendBP (df,dr))
+ parsePieceMove _ p = failP ("syntax error in move:")
+
+ getChecks (CheckTok:CheckTok:r) = ("#",r)
+ getChecks (CheckTok:r) = ("+",r)
+ getChecks (MateTok:r) = ("#",r)
+ getChecks r = ("",r)
+
+ getQueen (PieceTok p:QueensWith:r) = (Just p,reverse r)
+ getQueen r = (Nothing,reverse r)
+
+
diff --git a/testsuite/tests/programs/andy_cherry/InterpUtils.hs b/testsuite/tests/programs/andy_cherry/InterpUtils.hs
new file mode 100644
index 0000000000..820163e8fd
--- /dev/null
+++ b/testsuite/tests/programs/andy_cherry/InterpUtils.hs
@@ -0,0 +1,371 @@
+
+ module InterpUtils where
+
+ import GenUtils
+ import DataTypes
+ import Data.Array -- 1.3
+
+
+
+
+
+ findCastleKMove brd = (castleK,makeACastleK brd)
+ findCastleQMove brd = (castleQ,makeACastleQ brd)
+
+ findAPawnMove
+ :: ExBoardPos
+ -> ExBoardPos
+ -> Maybe Piece
+ -> Board
+ -> (String,Board)
+
+
+
+
+
+ findAPawnMove move_src move_dest queen brd@(Board arr mv _)
+ = debug (move_txt,new_brd)
+ where
+
+ move_colour = getMoveColour mv
+
+ debug = {- trace (
+ {- userFormat brd ++ -}
+ userFormat (getMoveColour mv) ++
+ -- " (" ++ userFormat absmove ++ ")" ++
+ "\nALL :" ++ unwords (map userFormat all_moves) ++
+ "\n") -} id
+
+
+
+
+ correct_src = concat (map (getAllMovesFor brd) currPieces)
+
+ currPieces =
+ [ (Pawn,x,y) |
+ (x,y) <- start_range,
+ r <- [arr ! (x,y)],
+ lookupSquare move_colour r == Friendly,
+ (Just Pawn) <- [getSquarePiece r]]
+
+
+
+ start_range
+ = case (move_src,move_dest) of
+ ((Just f,Just r),_) -> [(f,r)]
+ ((Just f,_),_) -> [(f,r) | r <- [2..7]]
+ -- no capture !
+ (_,(Just f,_)) -> [(f,r) | r <- [2..7]]
+ _ -> error "strange pawn move:"
+
+ the_correct_move = if (length correct_move /= 1)
+ then error ("\nAmbiguous move:"
+ ++ show (unwords (map userFormat correct_move))
+ ++ ":" ++ {- userFormat absmove ++ -} "\n"
+ ++ userFormat brd)
+ else head correct_move
+
+ correct_move =
+ filter (sameQueening queen.extractSpecialFromPlayMove)
+ (filter (compExBPandBP move_dest.extractDestFromPlayMove)
+ correct_src)
+ sameQueening (Just p) (Queening p') = p == p'
+ sameQueening Nothing (Queening p') = Queen == p'
+ sameQueening _ _ = True
+
+ move_txt = createShortMove the_correct_move "" brd
+ corr_txt =
+ userFormatBoardPos
+ (extractSrcFromPlayMove the_correct_move) ++
+ userFormatBoardPos
+ (extractDestFromPlayMove the_correct_move)
+ {- queening ?? -}
+ new_brd = makeAMove brd the_correct_move
+
+
+
+
+
+ findAMove
+ :: Piece
+ -> ExBoardPos
+ -> ExBoardPos
+ -> Board
+ -> (String,Board)
+
+ findAMove move_piece move_src move_dest brd@(Board arr mv _)
+ = debug (move_txt,new_brd)
+ where
+
+
+
+ move_colour = getMoveColour mv
+
+ debug = {- trace (
+ {- userFormat brd ++ -}
+ userFormat (getMoveColour mv) ++
+ " (" ++ {- userFormat absmove ++ -} ")" ++
+ "\nALL :" ++ unwords (map userFormat all_moves) ++
+ "\nDEST :" ++ unwords (map userFormat correct_dest) ++
+ "\nSRC :" ++ unwords (map userFormat correct_move) ++
+ "\n") -} id
+
+
+
+
+
+ all_moves = allValidMoves brd move_piece (const True)
+
+
+
+ correct_dest = filter
+ (compExBPandBP move_dest.extractDestFromPlayMove)
+ all_moves
+ correct_move = filter
+ (compExBPandBP move_src.extractSrcFromPlayMove)
+ correct_dest
+ the_correct_move = if (length correct_move /= 1)
+ then error ("\nAmbiguous move:"
+ ++ show (unwords (map userFormat correct_move))
+ ++ ":" {- ++ userFormat absmove -} ++ "\n"
+ ++ userFormat brd)
+ else head correct_move
+ disamb = case move_dest of
+ (Just _,Nothing) -> "" -- fg => fxg4, no disambig.
+ _ -> disAmb
+ (extractSrcFromPlayMove the_correct_move)
+ (map (extractSrcFromPlayMove) correct_dest)
+
+ move_txt = createShortMove the_correct_move disamb brd
+ corr_txt =
+ userFormatBoardPos
+ (extractSrcFromPlayMove the_correct_move) ++
+ userFormatBoardPos
+ (extractDestFromPlayMove the_correct_move)
+ {- queening -}
+ new_brd = makeAMove brd the_correct_move
+ --partain: findAMove _ _ _ brd = error ("strange move: ")
+
+ allValidMoves :: Board -> Piece -> (ChessFile -> Bool) -> [PlayMove]
+ allValidMoves brd piece corr_file
+ = concat (map (getAllMovesFor brd) (getCurrPieces brd piece corr_file))
+
+ getCurrPieces
+ :: Board
+ -> Piece
+ -> (ChessFile -> Bool)
+ -> [(Piece,ChessFile,ChessRank)]
+ getCurrPieces (Board arr (MoveNumber _ col) _) pc corr_file =
+ [ (p,x,y) |
+ ((x,y), r) <- assocs arr,
+ lookupSquare col r == Friendly,
+ (Just p) <- [getSquarePiece r],
+ p == pc,
+ corr_file x
+ ]
+
+
+
+
+
+
+ getAllMovesFor :: Board -> (Piece,Int,Int) -> [PlayMove]
+
+
+
+ getAllMovesFor brd (Rook,x,y) =
+ [ mkPlayMove Rook (x,y) (x',y')
+ | (x',y') <- (
+ movePiece 0 1 brd x y ++
+ movePiece 0 (-1) brd x y ++
+ movePiece 1 0 brd x y ++
+ movePiece (-1) 0 brd x y) ]
+ getAllMovesFor brd (Bishop,x,y) =
+ [ mkPlayMove Bishop (x,y) (x',y')
+ | (x',y') <- (
+ movePiece 1 1 brd x y ++
+ movePiece 1 (-1) brd x y ++
+ movePiece (-1) 1 brd x y ++
+ movePiece (-1) (-1) brd x y) ]
+ getAllMovesFor brd (Queen,x,y) =
+ [ mkPlayMove Queen (x,y) (x',y')
+ | (x',y') <- (
+ movePiece 0 1 brd x y ++
+ movePiece 0 (-1) brd x y ++
+ movePiece 1 0 brd x y ++
+ movePiece (-1) 0 brd x y ++
+ movePiece 1 1 brd x y ++
+ movePiece 1 (-1) brd x y ++
+ movePiece (-1) 1 brd x y ++
+ movePiece (-1) (-1) brd x y) ]
+
+
+
+ getAllMovesFor brd (Knight,x,y) =
+ [ mkPlayMove Knight (x,y) (x',y')
+ | (xd,yd) <- concat
+ [ [(d1,d2 * 2),(d1 * 2,d2)]
+ | d1 <- [1,-1], d2 <- [1,-1]],
+ x' <- [xd + x],
+ y' <- [yd + y],
+ case lookupBoard brd (x',y') of
+ Vacant -> True
+ Friendly -> False
+ Baddy -> True
+ OffBoard -> False]
+
+ getAllMovesFor brd (King,x,y) =
+ [ mkPlayMove King (x,y) (x',y')
+ | (xd,yd) <- [(1,1),(1,0),(1,-1),(0,1),
+ (0,-1),(-1,1),(-1,0),(-1,-1)],
+ x' <- [xd + x],
+ y' <- [yd + y],
+ case lookupBoard brd (x',y') of
+ Vacant -> True
+ Friendly -> False
+ Baddy -> True
+ OffBoard -> False]
+
+
+
+
+ getAllMovesFor brd@(Board _ (MoveNumber _ col) may_ep) (Pawn,x,y)
+ = real_pawn_moves
+ where
+ pawn_moves =
+ case lookupBoard brd (x,y+del) of
+ Friendly -> []
+ Baddy -> []
+ Vacant -> (mkPlayMove Pawn (x,y) (x,y+del) :
+ if y /= sta then [] else
+ case lookupBoard brd (x,y+del*2) of
+ Friendly -> []
+ Baddy -> []
+ Vacant ->
+ [ PlayMove Pawn (x,y) (x,y+del*2) BigPawnMove])
+ left_pc = case lookupBoard brd (x-1,y+del) of
+ Baddy -> [mkPlayMove Pawn (x,y) (x-1,y+del) ]
+ _ -> []
+ right_pc = case lookupBoard brd (x+1,y+del) of
+ Baddy -> [mkPlayMove Pawn (x,y) (x+1,y+del) ]
+ _ -> []
+ all_pawn_moves = pawn_moves ++ left_pc ++ right_pc
+ real_pawn_moves = en_passant ++
+ (if y + del == qn -- if can queens
+ then concat [ let fn = PlayMove Pawn f t . Queening
+ in
+ [ fn Queen,
+ fn Rook,
+ fn Bishop,
+ fn Knight ]
+ | PlayMove _ f t _ <- all_pawn_moves ]
+ else all_pawn_moves)
+ en_passant =
+ case (y == ep,may_ep) of
+ (True,Just f) | f == x+1 || f == x-1
+ -> [PlayMove Pawn (x,y) (f,y+del) EnPassant]
+ _ -> []
+ del,sta,qn,ep :: Int
+ (del,sta,qn,ep) -- delta (direction), start, Queening and E.P. Rank
+ = case col of
+ White -> (1,2,8,5)
+ Black -> (-1,7,1,4)
+
+ movePiece xd yd brd x y =
+ case lookupBoard brd (x',y') of
+ OffBoard -> []
+ Friendly -> []
+ Baddy -> [(x',y')]
+ Vacant -> (x',y') : movePiece xd yd brd x' y'
+ where
+ x' = x + xd
+ y' = y + yd
+
+
+
+
+ makeAMove :: Board -> PlayMove -> Board
+ makeAMove board@(Board brd mv@(MoveNumber _ col) _)
+ move@(PlayMove piece pos pos' NothingSpecial) =
+ Board (brd // [ pos =: VacantSq,
+ pos' =: mkColBoardSq col piece ])
+ (incMove mv) Nothing
+ makeAMove board@(Board brd mv@(MoveNumber _ col) _)
+ move@(PlayMove piece pos@(f,_) pos' BigPawnMove) =
+ Board (brd // [ pos =: VacantSq,
+ pos' =: mkColBoardSq col piece ])
+ (incMove mv) (Just f)
+ makeAMove board@(Board brd mv@(MoveNumber _ col) _)
+ move@(PlayMove piece pos@(f,_) pos' (Queening q)) =
+ Board (brd // [ pos =: VacantSq,
+ pos' =: mkColBoardSq col q])
+ (incMove mv) (Just f)
+ makeAMove board@(Board brd mv@(MoveNumber _ col) _) -- ASSERT ?
+ move@(PlayMove piece (f,_) (f',_) EnPassant) =
+ Board (brd // [ (f,st) =: VacantSq,
+ (f',fn) =: mkColBoardSq col Pawn,
+ (f',st) =: VacantSq ])
+ (incMove mv) Nothing
+ where (st,fn) = case col of
+ White -> (5,6)
+ Black -> (4,3)
+
+ makeACastleK (Board brd mv@(MoveNumber _ White) _) =
+ Board (brd //
+ [ (5,1) =: VacantSq,
+ (6,1) =: mkColBoardSq White Rook,
+ (7,1) =: mkColBoardSq White King,
+ (8,1) =: VacantSq ]) (incMove mv) Nothing
+ makeACastleK (Board brd mv@(MoveNumber _ Black) _) =
+
+ Board (brd //
+ [ (5,8) =: VacantSq,
+ (6,8) =: mkColBoardSq Black Rook,
+ (7,8) =: mkColBoardSq Black King,
+ (8,8) =: VacantSq ]) (incMove mv) Nothing
+ makeACastleQ (Board brd mv@(MoveNumber _ White) _) =
+ Board (brd //
+ [ (5,1) =: VacantSq,
+ (4,1) =: mkColBoardSq White Rook,
+ (3,1) =: mkColBoardSq White King,
+ (1,1) =: VacantSq ]) (incMove mv) Nothing
+ makeACastleQ (Board brd mv@(MoveNumber _ Black) _) =
+ Board (brd //
+ [ (5,8) =: VacantSq,
+ (4,8) =: mkColBoardSq Black Rook,
+ (3,8) =: mkColBoardSq Black King,
+ (1,8) =: VacantSq ]) (incMove mv) Nothing
+
+ disAmb _ [_] = ""
+ disAmb (a,b) t@[(n,m),(x,y)]
+ | n == x = userFormatRank b
+ | otherwise = userFormatFile a
+ disAmb src lst = error ("PANIC: cant disambiguate: " ++ show src ++ show lst)
+
+ createShortMove :: PlayMove -> String -> Board -> String
+ createShortMove (PlayMove Pawn (f,r) dest q) "" brd =
+ (if lookupBoard brd dest == Baddy || EnPassant == q
+ then userFormatFile f ++ "x" ++ userFormatBoardPos dest
+ else userFormatBoardPos dest) ++
+ case q of
+ Queening p -> "=" ++ userFormat p
+ _ -> ""
+ createShortMove (PlayMove p _ dest _) extra brd =
+ userFormat p ++ extra ++ capt ++ userFormatBoardPos dest
+ where
+ capt = if lookupBoard brd dest == Baddy
+ then "x"
+ else ""
+
+ getEPStart :: Colour -> ChessFile
+ getEPStart White = 5
+ getEPStart Black = 4
+
+ getEPEnd :: Colour -> ChessFile
+ getEPEnd White = 6
+ getEPEnd Black = 3
+
+ getHomeRank :: Colour -> ChessRank
+ getHomeRank White = 1
+ getHomeRank Black = 8
+
diff --git a/testsuite/tests/programs/andy_cherry/Main.hs b/testsuite/tests/programs/andy_cherry/Main.hs
new file mode 100644
index 0000000000..aa4274ec59
--- /dev/null
+++ b/testsuite/tests/programs/andy_cherry/Main.hs
@@ -0,0 +1,204 @@
+
+ module Main (main) where
+
+ import GenUtils
+ import DataTypes
+ import Parser
+ import Interp
+ import PrintTEX
+
+ import System.Environment -- 1.3 (partain)
+ import Data.Char -- 1.3
+
+ --fakeArgs = "game001.txt"
+ --fakeArgs = "pca2.pgn"
+ --fakeArgs = "silly.pgn"
+ --fakeArgs = "small.pgn"
+ --fakeArgs = "sicil.pgn"
+ --fakeArgs = "badgame.pgn"
+ --fakeArgs = "mycgames.pgn"
+ fakeArgs = "rab.pgn"
+
+ version = "0.3"
+
+
+ main = do
+ [test_dir] <- getArgs
+ let (style,fn,filename) = interpArgs (words "-d tex mygames.pgn")
+ file <- readFile (test_dir ++ "/" ++filename)
+ std_in <- getContents
+ let games = pgnParser fn file -- parse relavent pgn games
+ putStr (prog style std_in games)
+
+{- OLD 1.2:
+ main =
+ getArgs abort $ \ args ->
+ --let args = (words "-d tex analgames.pgn") in
+ let (style,fn,filename) = interpArgs args in
+ readFile filename abort $ \ file ->
+ readChan stdin abort $ \ std_in ->
+ let games = pgnParser fn file -- parse relavent pgn games
+ in
+ appendChan stdout (prog style std_in games) abort done
+-}
+
+ interpArgs :: [String] -> (OutputStyle,Int -> Bool,String)
+ --interpArgs [] = (ViewGame,const True,fakeArgs)
+ interpArgs [] = interpArgs (words "-d pgn analgames.pgn")
+ interpArgs files = interpArgs' OutputPGN (const True) files
+
+ interpArgs' style fn ("-d":"pgn":xs) = interpArgs' OutputPGN fn xs
+ interpArgs' style fn ("-d":"rawpgn":xs) = interpArgs' OutputRawPGN fn xs
+ interpArgs' style fn ("-d":"play":xs) = interpArgs' ViewGame fn xs
+ interpArgs' style fn ("-d":"parser":xs) = interpArgs' OutputParser fn xs
+ interpArgs' style fn ("-d":"tex":xs) = interpArgs' OutputTEX fn xs
+ interpArgs' style fn ("-d":"head":xs) = interpArgs' OutputHeader fn xs
+ interpArgs' style fn ("-g":range:xs)
+ = interpArgs' style (changeFn (parse range)) xs
+ where
+ changeFn (Digit n:Line:Digit m:r) x = moreChangeFn r x || x >= n && x <= m
+ changeFn (Line:Digit m:r) x = moreChangeFn r x || x <= m
+ changeFn (Digit n:Line:r) x = moreChangeFn r x || x >= n
+ changeFn (Digit n:r) x = moreChangeFn r x || x == n
+ changeFn _ _ = rangeError
+ moreChangeFn [] = const False
+ moreChangeFn (Comma:r) = changeFn r
+ moreChangeFn _ = rangeError
+ parse xs@(n:_)
+ | isDigit n = case span isDigit xs of
+ (dig,rest) -> Digit (read dig) : parse rest
+ parse ('-':r) = Line : parse r
+ parse (',':r) = Comma : parse r
+ parse [] = []
+ parse _ = rangeError
+ rangeError = error ("incorrect -g option (" ++ range ++ ")\n")
+
+ interpArgs' style fn [file] = (style,fn,file)
+ interpArgs' style fn args = error ("bad args: " ++ unwords args)
+
+ data Tok
+ = Digit Int -- n
+ | Line -- -
+ | Comma -- ,
+
+ data OutputStyle
+
+ = OutputPGN -- pgn
+ | OutputRawPGN -- rawpgn
+ | OutputHeader -- header
+ | ViewGame -- play
+ | ViewGameEmacs -- emacs
+ | TwoColumn -- 2col
+ | TestGames -- test
+ | OutputTEX
+
+
+
+ | OutputParser -- simply dump out the string read in.
+ | CmpGen -- cmp 2nd and 3rd generations of output
+
+
+
+ prog :: OutputStyle -- style of action
+ -> String -- stdin (for interactive bits)
+ -> [AbsGame] -- input games
+ -> String -- result
+ prog OutputPGN _
+ = pgnPrinter True -- print out game(s)
+ . map runInterp -- interprete all games
+ prog OutputRawPGN _
+ = pgnPrinter False -- print out game(s)
+ . map runInterp -- interprete all games
+ prog OutputHeader _
+ = pgnHeadPrinter -- print out game(s) headers
+ . map runInterp -- interprete all games
+ prog OutputTEX _
+ = texPrinter -- print out game(s)
+ . map runInterp -- interprete all games
+ prog ViewGame std_in
+ = interactViewer std_in -- print out game(s)
+ . runInterp -- interprete the game
+ . head -- should check for only *one* object
+ prog OutputParser _
+ = userFormat
+
+
+
+
+
+
+
+
+
+ type PrintState = (Bool,MoveNumber)
+
+ pgnPrinter :: Bool -> [RealGame] -> String
+ pgnPrinter detail = unlines . concat . map printGame
+ where
+ printMoveNumber :: Bool -> MoveNumber -> String
+ printMoveNumber False (MoveNumber _ Black) = ""
+ printMoveNumber _ mvnum = userFormat mvnum ++ " "
+
+ printQuantums :: PrintState -> [Quantum] -> [String]
+ printQuantums ps = concat . fst . mapAccumL printQuantum ps
+
+ printQuantum :: PrintState -> Quantum -> ([String],PrintState)
+ printQuantum (pnt,mv) (QuantumMove move ch an brd) =
+ ([printMoveNumber pnt mv ++ move ++ ch],(False,incMove mv))
+ printQuantum (pnt,mv) (QuantumNAG i) =
+ if detail
+ then (["$" ++ show i],(False,mv))
+ else ([],(False,mv))
+ printQuantum (pnt,mv) (QuantumComment comms) =
+ if detail
+ then ("{" : comms ++ ["}"],(True,mv))
+ else ([],(False,mv))
+ printQuantum (pnt,mv) (QuantumAnalysis anal) =
+ if detail
+ then ("(" : printQuantums (True,decMove mv) anal ++ [")"],
+ (True,mv))
+ else ([],(False,mv))
+ printQuantum (pnt,mv) (QuantumResult str) = ([str],(True,mv))
+ printQuantum _ _ = error "PANIC: strange Quantum"
+
+ printGame :: RealGame -> [String]
+ printGame (Game tags qu) =
+ [ userFormat tag | tag <- tags] ++
+ formatText 75 (printQuantums (False,initMoveNumber) qu)
+
+
+
+ printHeadGame :: RealGame -> [String]
+ printHeadGame (Game tags qu) = [
+ rjustify 4 gameno ++ " " ++
+ take 20 (rjustify 20 white) ++ " - " ++
+ take 20 (ljustify 20 black) ++ " " ++
+ take 26 (ljustify 28 site) ++ " " ++ result ]
+ where
+ (date,site,game_no,res,white,black,opening) = getHeaderInfo tags
+ gameno = case game_no of
+ Nothing -> ""
+ Just n -> show n
+ result = userFormat res
+
+ pgnHeadPrinter :: [RealGame] -> String
+ pgnHeadPrinter = unlines . concat . map printHeadGame
+
+
+
+
+
+ interactViewer :: String -> RealGame -> String
+ interactViewer stdin (Game tags qu) = replayQ qu (lines stdin)
+
+ replayQ (QuantumMove _ _ _ brd:rest) std_in
+ = "\027[H" ++ userFormat brd ++ waitQ rest std_in
+ replayQ (_:rest) std_in = replayQ rest std_in
+ replayQ [] _ = []
+
+ waitQ game std_in = ">>" ++
+ (case std_in of
+ [] -> ""
+ (q:qs) -> replayQ game qs)
+
+
diff --git a/testsuite/tests/programs/andy_cherry/Makefile b/testsuite/tests/programs/andy_cherry/Makefile
new file mode 100644
index 0000000000..9101fbd40a
--- /dev/null
+++ b/testsuite/tests/programs/andy_cherry/Makefile
@@ -0,0 +1,3 @@
+TOP=../../..
+include $(TOP)/mk/boilerplate.mk
+include $(TOP)/mk/test.mk
diff --git a/testsuite/tests/programs/andy_cherry/Parser.hs b/testsuite/tests/programs/andy_cherry/Parser.hs
new file mode 100644
index 0000000000..6dddb64a0e
--- /dev/null
+++ b/testsuite/tests/programs/andy_cherry/Parser.hs
@@ -0,0 +1,98 @@
+
+ module Parser (pgnLexer,pgnParser) where
+
+ import GenUtils
+ import DataTypes
+ import Data.Char -- 1.3
+
+
+
+ pgnLexer :: String -> [Token]
+ pgnLexer ('.':r) = PeriodToken : pgnLexer r
+ pgnLexer ('*':r) = AsterixToken : pgnLexer r
+ pgnLexer ('[':r) = LeftSBToken : pgnLexer r
+ pgnLexer (']':r) = RightSBToken : pgnLexer r
+ pgnLexer ('(':r) = LeftRBToken : pgnLexer r
+ pgnLexer (')':r) = RightRBToken : pgnLexer r
+ pgnLexer ('<':r) = LeftABToken : pgnLexer r
+ pgnLexer ('>':r) = RightABToken : pgnLexer r
+ pgnLexer ('"':r) = readString r ""
+ pgnLexer ('{':r) = readComment r ""
+ pgnLexer ('$':r) = readNAG r ""
+ pgnLexer ('!':'?':r) = mkNAGToken 5 : pgnLexer r
+ pgnLexer ('!':'!':r) = mkNAGToken 3 : pgnLexer r
+ pgnLexer ('!':r) = mkNAGToken 1 : pgnLexer r
+ pgnLexer ('?':'?':r) = mkNAGToken 4 : pgnLexer r
+ pgnLexer ('?':'!':r) = mkNAGToken 6 : pgnLexer r
+ pgnLexer ('?':r) = mkNAGToken 2 : pgnLexer r
+ pgnLexer ('%':r) = pgnLexer (dropWhile (/= '\n') r)
+ pgnLexer (c:r)
+ | isSpace c = pgnLexer r
+ | isAlpha c || isDigit c = pgnSymbolLexer r [c]
+ | otherwise = error ("Error lexing: " ++ takeWhile (/= '\n') (c:r))
+ pgnLexer [] = []
+
+ pgnSymbolLexer (c:r) sym
+ | isAlpha c
+ || isDigit c
+ || elem c "_+#=:-/" = pgnSymbolLexer r (c:sym)
+ pgnSymbolLexer r sym
+ | all isDigit sym = IntToken (read (reverse sym)) : pgnLexer r
+ pgnSymbolLexer r sym = SymbolToken (reverse sym) : pgnLexer r
+
+ readString ('\\':'\\':r) str = readString r ('\\':str)
+ readString ('\\':'"':r) str = readString r ('"':str)
+ readString ('"':r) str = StringToken (reverse str) : pgnLexer r
+ readString (c:r) str = readString r (c:str)
+
+ readComment ('}':r) str = CommentToken (revwords str []) : pgnLexer r
+ readComment (c:r) str = readComment r (c:str)
+
+ revwords (c:r) wds
+ | isSpace c = revwords r wds
+ | otherwise = revwords' r [c] wds
+ revwords [] wds = wds
+ revwords' (c:r) wd wds
+ | isSpace c = revwords r (wd:wds)
+ | otherwise = revwords' r (c:wd) wds
+ revwords' [] wd wds = wd : wds
+
+ readNAG (c:r) str
+ | isDigit c = readNAG r (c:str)
+ readNAG r str = mkNAGToken (read (reverse str)) : pgnLexer r
+
+ mkNAGToken 1 = NAGAnnToken 1 "!"
+ mkNAGToken 2 = NAGAnnToken 2 "?"
+ mkNAGToken 3 = NAGAnnToken 3 "!!"
+ mkNAGToken 4 = NAGAnnToken 4 "??"
+ mkNAGToken 5 = NAGAnnToken 5 "!?"
+ mkNAGToken 6 = NAGAnnToken 6 "?!"
+ mkNAGToken n = NAGToken n
+
+
+
+
+ pgnParser :: (Int -> Bool) -> String -> [AbsGame]
+ pgnParser fn str =
+ [ game | (no,game) <- zip [1..] (parseTags (pgnLexer str) id),
+ fn no]
+
+ type FL a = [a] -> [a]
+
+ parseTags :: [Token] -> FL TagStr -> [AbsGame]
+ parseTags (LeftSBToken:SymbolToken sym:StringToken str:RightSBToken:rest)
+ other_tags = parseTags rest (other_tags . ((:) (TagStr sym str)))
+ parseTags toks@(LeftSBToken:_) _
+ = error ("BAD Token:" ++ unwords (map userFormat (take 10 toks)))
+ parseTags toks tags = parseToks toks id tags
+
+ parseToks :: [Token]
+ -> FL Token
+ -> FL TagStr
+ -> [AbsGame]
+ parseToks next@(LeftSBToken:_) = \ toks tags ->
+ Game (tags []) (toks []) : parseTags next id
+ parseToks (tk:r) = pushToken tk r
+ parseToks [] = \ toks tags -> [Game (tags []) (toks [])]
+
+ pushToken tok r toks = parseToks r (toks . ((:) tok))
diff --git a/testsuite/tests/programs/andy_cherry/PrintTEX.hs b/testsuite/tests/programs/andy_cherry/PrintTEX.hs
new file mode 100644
index 0000000000..d8f253f6d4
--- /dev/null
+++ b/testsuite/tests/programs/andy_cherry/PrintTEX.hs
@@ -0,0 +1,182 @@
+
+ module PrintTEX (texPrinter) where
+
+ import GenUtils
+ import DataTypes
+ import Data.Array -- 1.3
+ import Data.Char -- 1.3
+
+
+
+
+
+
+
+ splitUpQuantum :: [Quantum] -> [[Quantum]]
+ splitUpQuantum q = splitUpQuantums q []
+ where
+ splitUpQuantums [] [] = []
+ splitUpQuantums [] mvs = [reverse mvs]
+ splitUpQuantums (mv@(QuantumMove _ _ _ _):rest) mvs
+ = splitUpQuantums rest (mv:mvs)
+ splitUpQuantums (mv@(QuantumNAG _):rest) mvs
+ = splitUpQuantums rest mvs
+ splitUpQuantums (x:xs) [] = [x] : splitUpQuantums xs []
+ splitUpQuantums (x:xs) mvs
+ = [reverse mvs,[x]] ++ splitUpQuantums xs []
+
+ type TeXState =
+ (Bool, -- if Top level !
+ Board, -- current board
+ MoveNumber) -- the Current Move Number
+
+ printTeXQuantums :: TeXState -> [Quantum] -> [String]
+ printTeXQuantums ps
+ = concat . fst . mapAccumL printTeXQuantum ps . splitUpQuantum
+
+ printTeXQuantum :: TeXState -> [Quantum] -> ([String],TeXState)
+ printTeXQuantum state@(_,board,_) [QuantumComment ["\004"]] =
+ (mkTeXBoard board,state)
+ printTeXQuantum state@(_,board,_) [QuantumComment (('\004':comm):comms)] =
+ (mkTeXBoard board ++ formatText 70 (parseSquiggles (comm:comms)),state)
+ printTeXQuantum state [QuantumComment comms] =
+ (formatText 70 (parseSquiggles comms),state)
+ printTeXQuantum (pnt,brd,mv) [QuantumAnalysis anal] =
+ (printTeXQuantums (False,err,decMove mv) anal,(pnt,brd,mv))
+ where err = error "Syntax error using ^D"
+ printTeXQuantum state@(_,board,_) [QuantumResult str] =
+ (mkTeXBoard board ++ [printTeXResult (mkResult str)],state)
+ printTeXQuantum state mvs@(QuantumMove _ _ _ _:_) =
+ printTeXMoves state mvs
+ printTeXQuantum _ _ = error "PANIC: strange Quantum"
+
+
+ parseSquiggles = map parseSquiggle
+ parseSquiggle ('<':'s':'a':'w':'>':r) = "\\wbetter{}" ++ r
+ parseSquiggle ('<':'a':'w':'>':r) = "\\wupperhand{}" ++ r
+ parseSquiggle ('<':'w':'a':'w':'>':r) = "\\wdecisive{}" ++ r
+ parseSquiggle ('<':'s':'a':'b':'>':r) = "\\bbetter{}" ++ r
+ parseSquiggle ('<':'a':'b':'>':r) = "\\bupperhand{}" ++ r
+ parseSquiggle ('<':'w':'a':'b':'>':r) = "\\bdecisive{}" ++ r
+ parseSquiggle wd = wd
+
+
+ printTeXResult :: Result -> String
+ printTeXResult Win = "$1\\!-\\!0$"
+ printTeXResult Loss = "$0\\!-\\!1$"
+ printTeXResult Draw = "${1 \\over 2}\\!-\\!{1 \\over 2}$"
+ printTeXResult Unknown = "$*$"
+
+ printTeXMoves (tl,_,mv) mvs
+ = ([text],(True,brd,incMove last_mv_num))
+ where
+ aux_mvs = zip3 mvs (iterate incMove mv) (False:repeat True)
+
+ (QuantumMove _ _ _ brd,last_mv_num,_) = last aux_mvs
+ text = initText tl
+ ++ concat (fst (mapAccumL (pntMove tl) (mv,False) mvs))
+ ++ endText tl
+
+ initText False =
+ case mv of
+ MoveNumber i Black -> "|" ++ show i ++ "\\ldots~"
+ _ -> "|"
+ initText True =
+ "\\begin{center}|\n" ++
+ "{\\bf" ++
+ "\\begin{tabular}{rp{50pt}p{50pt}}\n" ++
+ case mv of
+ MoveNumber i Black -> show i ++ " & \\ldots"
+ _ -> ""
+
+ endText True = case getMoveColour last_mv_num of
+ White -> "&\\\\\n\\end{tabular}}|\n\\end{center}"
+ Black -> "\\end{tabular}}|\n\\end{center}"
+ endText False = "|"
+
+
+
+ pntMove True (mv@(MoveNumber i White),bl) move
+ = (show i ++ " & "
+ ++ printableMove move,
+ (incMove mv,True))
+ pntMove True (mv@(MoveNumber i Black),bl) move
+ = (" & " ++ printableMove move ++ "\\\\\n",
+ (incMove mv,True))
+ pntMove False (mv@(MoveNumber i White),bl) move
+ = ((if bl then "; " else "") ++ show i ++ ".~"
+ ++ printableMove move,
+ (incMove mv,True))
+ pntMove False (mv@(MoveNumber i Black),bl) move
+ = ((if bl then ", " else "") ++ printableMove move,
+ (incMove mv,True))
+
+ printableMove :: Quantum -> String
+ printableMove (QuantumMove move ch an _) = map fn move ++ rest
+ where
+ fn 'x' = '*'
+ fn 'O' = '0'
+ fn c = c
+ rest = case ch of
+ "#" -> an ++ " mate"
+ _ -> ch ++ an
+
+ mkTeXBoard :: Board -> [String]
+ mkTeXBoard (Board arr _ _) =
+ ["\n\\board"] ++
+ ["{" ++ [ fn ((x-y) `rem` 2 == 0) (arr ! (x,y)) | x <- [1..8]] ++ "}"
+ | y <- reverse [1..8]] ++
+ ["$$\\showboard$$"]
+ where
+ fn _ (WhitesSq p) = head (userFormat p)
+ fn _ (BlacksSq p) = toLower (head (userFormat p))
+ fn True VacantSq = '*'
+ fn False VacantSq = ' '
+
+ printTeXGame :: RealGame -> [String]
+ printTeXGame (Game tags qu) = [
+ "\\clearpage",
+ "\\begin{center}",
+ "\\fbox{\\fbox{\\large\\begin{tabular}{l}",
+ ("Game " ++ gameno ++ " \\hspace{.3 in} "
+ ++ date
+ ++ " \\hspace{.3 in} "
+ ++ result
+ ++ "\\\\"),
+ "\\hline" ++ (if null opening then "" else "\n" ++ opening ++ "\\\\"),
+ "\\raisebox{2.5pt}[11pt]{\\framebox[11pt]{\\rule{0pt}{4.25pt}}} "
+ ++ white ++ "\\\\",
+ "\\rule[-1pt]{11pt}{11pt} "++ black ++ "\\\\",
+ site,
+ "\\end{tabular}}}",
+ "\\end{center}"] ++
+ (printTeXQuantums (True,startBoard,initMoveNumber) qu)
+ where
+ (date,site,game_no,res,white,black,opening) = getHeaderInfo tags
+ gameno = case game_no of
+ Nothing -> ""
+ Just n -> show n
+ result = printTeXResult res
+
+ texPrinter :: [RealGame] -> String
+ texPrinter games =
+ texHeader
+ ++ (unlines(concat(map printTeXGame games)))
+ ++ texFooter
+
+ texHeader =
+ "\\documentstyle[twocolumn,a4wide,chess]{article}\n" ++
+ "\\textwidth 7.0 in\n" ++
+ "\\textheight 63\\baselineskip\n" ++
+ "\\columnsep .4 in\n" ++
+ "\\columnseprule .5 pt\n" ++
+ "\\topmargin -0.5 in\n" ++
+ "\\headheight 0 pt\n" ++
+ "\\headsep 0 pt\n" ++
+ "\\oddsidemargin -0.3 in\n" ++
+ "\\font\\sc=cmcsc10\n\\pagestyle{empty}\n" ++
+ "\\begin{document}\n\\thispagestyle{empty}\n\n"
+
+ texFooter = "\n\\end{document}\n"
+
+
diff --git a/testsuite/tests/programs/andy_cherry/andy_cherry.stdout b/testsuite/tests/programs/andy_cherry/andy_cherry.stdout
new file mode 100644
index 0000000000..ef160b0325
--- /dev/null
+++ b/testsuite/tests/programs/andy_cherry/andy_cherry.stdout
@@ -0,0 +1,7258 @@
+\documentstyle[twocolumn,a4wide,chess]{article}
+\textwidth 7.0 in
+\textheight 63\baselineskip
+\columnsep .4 in
+\columnseprule .5 pt
+\topmargin -0.5 in
+\headheight 0 pt
+\headsep 0 pt
+\oddsidemargin -0.3 in
+\font\sc=cmcsc10
+\pagestyle{empty}
+\begin{document}
+\thispagestyle{empty}
+
+\clearpage
+\begin{center}
+\fbox{\fbox{\large\begin{tabular}{l}
+Game \hspace{.3 in} Oct 1993 \hspace{.3 in} $1\!-\!0$\\
+\hline
+Foo C10\\
+\raisebox{2.5pt}[11pt]{\framebox[11pt]{\rule{0pt}{4.25pt}}} George Webb\\
+\rule[-1pt]{11pt}{11pt} Andy Gill\\
+Dunfermline Club Championship
+\end{tabular}}}
+\end{center}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+1 & Nf3 & d5\\
+2 & d4 & Nc6\\
+3 & Nc3 & Nf6\\
+\end{tabular}}|
+\end{center}
+|3\ldots~Bf5|
+is more natural.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+4 & e4?&\\
+\end{tabular}}|
+\end{center}
+|4.~Bf4|
+is better.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+4 & \ldots & e6?\\
+\end{tabular}}|
+\end{center}
+|4\ldots~d*e4; 5.~d5, e*f3; 6.~d*c6, Q*d1+; 7.~N*d1|
+and black is a clear pawn up.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+5 & e5 & Ne4\\
+\end{tabular}}|
+\end{center}
+
+\board
+{r*bqkb r}
+{ppp *ppp}
+{ *n*p* *}
+{* *pP * }
+{ * Pn* *}
+{* N *N* }
+{PPP* PPP}
+{R BQKB*R}
+$$\showboard$$
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+6 & N*e4?&\\
+\end{tabular}}|
+\end{center}
+Taking this knight looses a pawn
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+6 & \ldots & d*e4\\
+7 & Nd2 & Q*d4\\
+8 & Nc4 & Q*d1+\\
+9 & K*d1 & Bd7\\
+\end{tabular}}|
+\end{center}
+|9\ldots~Bc5; 10.~f3, e*f3; 11.~g*f3, 0-0; 12.~Bd3|
+White can get presure down the `g' file, but first needs to solve the
+problem of the Bishop on c5 guarding g8.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+10 & Bd2&\\
+\end{tabular}}|
+\end{center}
+|10.~Be3|
+is better.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+10 & \ldots & Bb4\\
+11 & c3 & Bc5\\
+12 & Ke1 & 0-0-0\\
+\end{tabular}}|
+\end{center}
+|12\ldots~b5; 13.~Ne3, B*e3; 14.~B*e3, N*e5|
+wins a pawn, but black might have problems because of queenside
+weaknesses.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+13 & g3&\\
+\end{tabular}}|
+\end{center}
+|13.~Bg5, Be7; 14.~B*e7, N*e7; 15.~Rd1|
+and white is starting to contest the `d' file.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+13 & \ldots & Rhf8\\
+14 & Bg2 & f5?\\
+\end{tabular}}|
+\end{center}
+black is throwing away a pawn.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+15 & e*f6 & g*f6\\
+\end{tabular}}|
+\end{center}
+|15\ldots~R*f6|
+gives black more piece activity.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+16 & B*e4&\\
+\end{tabular}}|
+\end{center}
+taking the weak pawn, and attacking h7.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+16 & \ldots & e5?\\
+\end{tabular}}|
+\end{center}
+|16\ldots~Rh8|
+is required to protect the weak h pawn.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+17 & B*h7&\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ *kr r *}
+{pppb* *B}
+{ *n* p *}
+{* b p * }
+{ *N* * *}
+{* P * P }
+{PP B P P}
+{R * K *R}
+$$\showboard$$
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+17 & \ldots & f5\\
+\end{tabular}}|
+\end{center}
+|17\ldots~B*f2+; 18.~K*f2, Be6; 19.~N*e5, R*d2+; 20.~Ke1, R*b2|
+winning material, and striping whites king of protection.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+18 & b4 & Be6\\
+19 & b5&\\
+\end{tabular}}|
+\end{center}
+|19.~b*c5, B*c4|
+and white has the two bishops.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+19 & \ldots & B*c4\\
+20 & b*c6 & b*c6\\
+\end{tabular}}|
+\end{center}
+|20\ldots~B*f2+; 21.~K*f2, R*d2+; 22.~Ke1, Re2+; 23.~Kd1, b*c6; 24.~h4, Rd8+|
+with a winning attack on whites exposed king.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+21 & Rb1?&\\
+\end{tabular}}|
+\end{center}
+Throws away a pawn needlessly.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+21 & \ldots & B*a2\\
+\end{tabular}}|
+\end{center}
+|21\ldots~B*f2+; 22.~K*f2, R*d2+; 23.~Ke1, R*a2|
+winning two pawns rather than one.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+22 & Rb2 & Bd5\\
+23 & Rg1 & e4\\
+\end{tabular}}|
+\end{center}
+|23\ldots~a5; 24.~h4, a4; 25.~Bh6, Bf3; 26.~Rd2, R*d2; 27.~B*d2|
+is a better plan, with a dangerous passed `a' pawn.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+24 & Bh6? & Ba3\\
+\end{tabular}}|
+\end{center}
+|24\ldots~Rf7; 25.~Bg5, R*h7; 26.~B*d8, Ba3; 27.~Rd2, K*d8|
+two bishops vs a rook, a difficult win for black.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+25 & Rb1 & Rfe8?\\
+\end{tabular}}|
+\end{center}
+another missed opertunity.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+26 & B*f5+ & Be6\\
+27 & Bg6 & Rh8\\
+28 & Be3&\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ *kr * r}
+{p p * * }
+{ *p*b*B*}
+{* * * * }
+{ * *p* *}
+{b P B P }
+{ * * P P}
+{*R* K R }
+$$\showboard$$
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+28 & \ldots & Rd3?\\
+\end{tabular}}|
+\end{center}
+|28\ldots~R*h2; 29.~B*e4, c5; 30.~Rb7, a5|
+and black has a fighting chance
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+29 & Bd4&\\
+\end{tabular}}|
+\end{center}
+|29.~B*e4, R*c3; 30.~Bd4, Rc4; 31.~B*h8, R*e4+|
+and black is lost.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+29 & \ldots & Bd5??\\
+30 & B*h8 & e3??\\
+31 & f3?&\\
+\end{tabular}}|
+\end{center}
+|31.~B*d3, e*f2+; 32.~K*f2, Bc5+; 33.~Bd4|
+and white is two rooks up.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+31 & \ldots & Rd2\\
+32 & Bf6 & Bb2\\
+33 & h4&\\
+\end{tabular}}|
+\end{center}
+|33.~Bf5+, Kb7; 34.~c4, B*c4; 35.~R*b2+, R*b2; 36.~B*b2|
+winning.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+33 & \ldots & Kb7\\
+34 & Bg5 & B*f3\\
+\end{tabular}}|
+\end{center}
+|34\ldots~Ba2; 35.~Bc2, B*b1; 36.~B*b1, Rh2; 37.~B*e3, B*c3+|
+and black is just a bishop down in a pawn race.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+35 & B*e3 & Re2+\\
+36 & Kf1 & R*e3\\
+37 & Re1??&\\
+\end{tabular}}|
+\end{center}
+giving black a chance to equalize.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+37 & \ldots & Re2??\\
+\end{tabular}}|
+\end{center}
+Returning the complement.
+|37\ldots~R*e1+; 38.~K*e1, B*c3+; 39.~Kf2, Bd4+; 40.~K*f3, B*g1|
+and White still has the edge with 2 connected passed pawns, but black
+has real chances.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+38 & R*e2&\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ * * * *}
+{pkp * * }
+{ *p* *B*}
+{* * * * }
+{ * * * P}
+{* P *bP }
+{ b *R* *}
+{* * *KR }
+$$\showboard$$
+$1\!-\!0$
+\clearpage
+\begin{center}
+\fbox{\fbox{\large\begin{tabular}{l}
+Game \hspace{.3 in} Nov 1993 \hspace{.3 in} $1\!-\!0$\\
+\hline
+Foo C65\\
+\raisebox{2.5pt}[11pt]{\framebox[11pt]{\rule{0pt}{4.25pt}}} Andy Gill\\
+\rule[-1pt]{11pt}{11pt} Barry Dunne\\
+Dunfermline Club Championship
+\end{tabular}}}
+\end{center}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+1 & e4 & e5\\
+2 & Nf3 & Nc6\\
+3 & Bb5 & Nf6\\
+4 & d3&\\
+\end{tabular}}|
+\end{center}
+|4.~0-0|
+Ruy Lopez, Berlin Defence
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+4 & \ldots & Be7\\
+\end{tabular}}|
+\end{center}
+|4\ldots~Bc5|
+is better.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+5 & 0-0&\\
+\end{tabular}}|
+\end{center}
+|5.~B*c6, d*c6; 6.~N*e5, Bd6; 7.~Nf3, 0-0; 8.~0-0, Be6|
+and white is a pawn up, but black has a lead in development.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+5 & \ldots & 0-0?\\
+\end{tabular}}|
+\end{center}
+|5\ldots~d6|
+is needed to protect e5.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+6 & Nc3&\\
+\end{tabular}}|
+\end{center}
+|6.~B*c6, d*c6; 7.~N*e5, Bd6; 8.~Nf3, Bg4; 9.~Be3|
+and white is a clean pawn up.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+6 & \ldots & b6?\\
+7 & a3 & Bb7\\
+8 & b4 & Nd4\\
+\end{tabular}}|
+\end{center}
+
+\board
+{r* q rk*}
+{pbppbppp}
+{ p * n *}
+{*B* p * }
+{ P nP* *}
+{P NP*N* }
+{ *P* PPP}
+{R BQ*RK }
+$$\showboard$$
+A bit ambitious.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+9 & N*e5&\\
+\end{tabular}}|
+\end{center}
+|9.~N*d4, e*d4; 10.~Ne2, d5; 11.~e5, Nd7|
+is whites best line.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+9 & \ldots & N*b5\\
+\end{tabular}}|
+\end{center}
+|9\ldots~d5; 10.~Bb2, d*e4; 11.~d*e4, N*e4|
+with equal chances.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+10 & N*b5 & d5\\
+11 & Bb2 & d*e4\\
+12 & d*e4&\\
+\end{tabular}}|
+\end{center}
+|12.~f3|
+is a better approach.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+12 & \ldots & Q*d1\\
+13 & Ra*d1 & Bd6\\
+\end{tabular}}|
+\end{center}
+
+\board
+{r* * rk*}
+{pbp *ppp}
+{ p b n *}
+{*N* N * }
+{ P *P* *}
+{P * * * }
+{ BP* PPP}
+{* *R*RK }
+$$\showboard$$
+|13\ldots~B*e4; 14.~Nd7, B*c2; 15.~B*f6, g*f6; 16.~Rd2|
+with a slight advantage for white.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+14 & Nf3&\\
+\end{tabular}}|
+\end{center}
+|14.~N*d6, c*d6; 15.~R*d6, B*e4; 16.~c4, Rfd8; 17.~c5, b*c5; 18.~b*c5|
+winning for white.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+14 & \ldots & B*e4\\
+\end{tabular}}|
+\end{center}
+|14\ldots~N*e4|
+is better.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+15 & N*d6 & c*d6\\
+16 & B*f6 & g*f6\\
+17 & R*d6 & B*c2\\
+\end{tabular}}|
+\end{center}
+|17\ldots~B*f3; 18.~g*f3, Rac8; 19.~Rc1, Rc3; 20.~Rd3, R*d3; 21.~c*d3|
+and whites passed pawn is a long way from queening.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+18 & R*f6&\\
+\end{tabular}}|
+\end{center}
+|18.~Nd4, Ba4; 19.~R*f6, Rfd8; 20.~Rf4, Rd7; 21.~Re4|
+a pawn up, but with chances for black, because of the powerful Bishop.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+18 & \ldots & Rfd8\\
+19 & Ne5 & Kg7\\
+\end{tabular}}|
+\end{center}
+|19\ldots~Bg6|
+is better, defending the weak pawn.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+20 & R*f7+ & Kg8\\
+21 & Rc7&\\
+\end{tabular}}|
+\end{center}
+|21.~f4, a6; 22.~g3, Rd2; 23.~Rb7, b5|
+and white should win.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+21 & \ldots & Re8\\
+\end{tabular}}|
+\end{center}
+|21\ldots~Rdc8; 22.~Rb7, Be4; 23.~Rd7, Rc2; 24.~Rfd1|
+with connected rooks for white.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+22 & Re1&\\
+\end{tabular}}|
+\end{center}
+|22.~f4|
+is better for protecting the knight.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+22 & \ldots & Rac8\\
+\end{tabular}}|
+\end{center}
+should have moved the `e' Rook.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+23 & R*a7 & Bf5\\
+\end{tabular}}|
+\end{center}
+|23\ldots~Ra8!?|
+planning to attack the weak `a' pawn.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+24 & f4 & Bg4\\
+\end{tabular}}|
+\end{center}
+|24\ldots~Rc2|
+penatraiting the 7th.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+25 & Kf2 & Rc2+\\
+26 & Kg3 & Re2\\
+27 & R*e2 & B*e2\\
+28 & Nc6?&\\
+\end{tabular}}|
+\end{center}
+where is that knight going ?
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+28 & \ldots & Re3+\\
+29 & Kf2 & Re4\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ * * *k*}
+{R * * *p}
+{ pN* * *}
+{* * * * }
+{ P *rP *}
+{P * * * }
+{ * *bKPP}
+{* * * * }
+$$\showboard$$
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+30 & f5&\\
+\end{tabular}}|
+\end{center}
+|30.~Ne7+, Kf8; 31.~Nd5, Bd3; 32.~N*b6, Re7|
+totally winning for white
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+30 & \ldots & Bg4\\
+31 & Ne7+&\\
+\end{tabular}}|
+\end{center}
+|31.~Kg3, h6; 32.~f6, Be6; 33.~Re7|
+looking very good for white.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+31 & \ldots & Kf8\\
+32 & f6 & Rf4+\\
+33 & Kg3 & Re4\\
+34 & h3&\\
+\end{tabular}}|
+\end{center}
+|34.~Nd5, Be6; 35.~N*b6, Rg4+; 36.~Kf3, Rg6; 37.~R*h7, R*f6+; 38.~Ke4|
+and with 4 connected passed white will win.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+34 & \ldots & Bh5\\
+35 & Nd5 & b5\\
+36 & R*h7 & Bg6\\
+37 & Rh4&\\
+\end{tabular}}|
+\end{center}
+|37.~Rh8+, Kf7; 38.~Rb8, Bf5; 39.~R*b5, Be6; 40.~Rb7+, Kg6; 41.~Rg7+|
+just look at whites advantage.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+37 & \ldots & R*h4\\
+38 & K*h4 & Be4\\
+39 & Nc3&\\
+\end{tabular}}|
+\end{center}
+|39.~Ne3, Kf7; 40.~Kg5, Bc6; 41.~g4, Be4; 42.~h4, Bd3; 43.~h5|
+winning.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+39 & \ldots & Bc6\\
+\end{tabular}}|
+\end{center}
+|39\ldots~B*g2; 40.~N*b5, Kf7; 41.~Kg5, B*h3; 42.~Nd6+, Kg8; 43.~a4, Kh7|
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+40 & g4 & Kf7\\
+41 & g5&\\
+\end{tabular}}|
+\end{center}
+|41.~Kg5, Kg8; 42.~h4, Bd7; 43.~h5, Kf7; 44.~Ne4, Kg8; 45.~Nd6|
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+41 & \ldots & Kg6\\
+42 & Kg4? & Bd7+\\
+43 & Kf4 & B*h3\\
+44 & N*b5 & Bd7\\
+\end{tabular}}|
+\end{center}
+|44\ldots~Kf7; 45.~Nd6+, Ke6; 46.~f7, Ke7; 47.~g6, Kf8; 48.~a4, Kg7|
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+45 & a4 & Bc6\\
+46 & Nc3 & Bd7\\
+47 & b5&\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ * * * *}
+{* *b* * }
+{ * * Pk*}
+{*P* * P }
+{P* * K *}
+{* N * * }
+{ * * * *}
+{* * * * }
+$$\showboard$$
+$1\!-\!0$
+\clearpage
+\begin{center}
+\fbox{\fbox{\large\begin{tabular}{l}
+Game \hspace{.3 in} Nov 1993 \hspace{.3 in} $0\!-\!1$\\
+\hline
+Foo C65\\
+\raisebox{2.5pt}[11pt]{\framebox[11pt]{\rule{0pt}{4.25pt}}} Andy Gill\\
+\rule[-1pt]{11pt}{11pt} Rab Brown\\
+Dunfermline Club Championship
+\end{tabular}}}
+\end{center}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+1 & e4 & e5\\
+2 & Nf3 & Nc6\\
+3 & Bb5 & Bc5\\
+4 & 0-0 & Nf6\\
+5 & Nc3 & d6\\
+6 & a3 & Ng4?\\
+7 & Qe1&\\
+\end{tabular}}|
+\end{center}
+|7.~h3|
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+7 & \ldots & 0-0\\
+\end{tabular}}|
+\end{center}
+
+\board
+{r*bq rk*}
+{ppp *ppp}
+{ *np * *}
+{*Bb p * }
+{ * *P*n*}
+{P N *N* }
+{ PPP PPP}
+{R B QRK }
+$$\showboard$$
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+8 & B*c6 & b*c6\\
+9 & b4 & Ba6\\
+10 & b*c5 & B*f1\\
+11 & K*f1&\\
+\end{tabular}}|
+\end{center}
+|11.~Q*f1, Qd7; 12.~Bb2, d*c5; 13.~d3, Rfb8; 14.~Rb1|
+clearly winning for white.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+11 & \ldots & Qf6\\
+\end{tabular}}|
+\end{center}
+
+\board
+{r* * rk*}
+{p p *ppp}
+{ *pp q *}
+{* P p * }
+{ * *P*n*}
+{P N *N* }
+{ *PP PPP}
+{R B QK* }
+$$\showboard$$
+|11\ldots~Rb8; 12.~Qe2, Qd7; 13.~Qa6, Ra8; 14.~h3, Nf6; 15.~d4, e*d4|
+is a better plan.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+12 & d3 & Qg6\\
+13 & Rb1&\\
+\end{tabular}}|
+\end{center}
+|13.~h3, Nh6|
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+13 & \ldots & Qh5\\
+14 & Rb7&\\
+\end{tabular}}|
+\end{center}
+|14.~h3, Nf6; 15.~Rb7, Rfc8; 16.~Bg5, Qg6; 17.~Qe3, Ne8|
+and white has a commanding lead.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+14 & \ldots & N*h2+\\
+15 & N*h2 & Q*h2\\
+16 & R*c7 & Qh1+\\
+17 & Ke2 & Q*g2\\
+18 & R*c6&\\
+\end{tabular}}|
+\end{center}
+|18.~c*d6, Rfc8; 19.~R*c8+, R*c8; 20.~Be3, Rd8; 21.~Bc5, h5|
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+18 & \ldots & d*c5\\
+\end{tabular}}|
+\end{center}
+|18\ldots~Qg4+; 19.~f3, Qg2+; 20.~Qf2, Q*f2+; 21.~K*f2, Rfc8; 22.~Nd5, R*c6; 23.~Ne7+|
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+19 & R*c5 & f5\\
+20 & Be3 & Qg4+\\
+21 & f3 & Qg2+\\
+22 & Qf2 & Qh1\\
+23 & R*e5 & Qa1\\
+\end{tabular}}|
+\end{center}
+
+\board
+{r* * rk*}
+{p * * pp}
+{ * * * *}
+{* * Rp* }
+{ * *P* *}
+{P NPBP* }
+{ *P*KQ *}
+{q * * * }
+$$\showboard$$
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+24 & Bc5?&\\
+\end{tabular}}|
+\end{center}
+|24.~Qe1, Qb2; 25.~Qd2, Q*a3; 26.~Bc5, Qa5; 27.~e*f5|
+white has the advantage.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+24 & \ldots & Q*c3\\
+25 & R*f5&\\
+\end{tabular}}|
+\end{center}
+|25.~B*f8, Q*c2+; 26.~Kf1, Q*d3+; 27.~Qe2, Qb1+; 28.~Qe1, Q*e1+; 29.~K*e1|
+now black has only a slight advantage.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+25 & \ldots & Q*c2+\\
+\end{tabular}}|
+\end{center}
+|25\ldots~R*f5; 26.~e*f5, Q*c2+; 27.~Kf1, Q*d3+; 28.~Kg2, Rd8; 29.~f4|
+and black has a clear lead.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+26 & Ke3 & Q*f2+\\
+27 & K*f2 & R*f5\\
+28 & e*f5 & Rc8\\
+29 & d4 & a6\\
+30 & a4 & Kf7\\
+31 & Ke3&\\
+\end{tabular}}|
+\end{center}
+|31.~Kg3, Kf6; 32.~Kf4, g5+; 33.~f*g6, h*g6; 34.~a5, g5+; 35.~Kg4|
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+31 & \ldots & h5\\
+\end{tabular}}|
+\end{center}
+|31\ldots~Kf6; 32.~Kf4, Rd8; 33.~a5, Rd5; 34.~Ke4, R*f5|
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+32 & Kf4 & h4\\
+33 & Kg4 & Rh8\\
+34 & d5 & h3\\
+35 & Bd6 & g6\\
+\end{tabular}}|
+\end{center}
+|35\ldots~h2; 36.~B*h2, R*h2; 37.~Kf4, Rh4+; 38.~Ke5, R*a4; 39.~d6, Rc4|
+totaly won for black.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+36 & f*g6+ & K*g6\\
+37 & Bh2 & Kf6\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ * * * r}
+{* * * * }
+{p* * k *}
+{* *P* * }
+{P* * *K*}
+{* * *P*p}
+{ * * * B}
+{* * * * }
+$$\showboard$$
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+38 & f4&\\
+\end{tabular}}|
+\end{center}
+|38.~a5, Ke7; 39.~Kf5, Rh5+; 40.~Ke4, Rh4+; 41.~f4, Kd6; 42.~Kd4|
+holding the position.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+38 & \ldots & Ke7\\
+39 & f5 & a5\\
+\end{tabular}}|
+\end{center}
+|39\ldots~Kf6|
+is needed.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+40 & d6+ & Kd7\\
+\end{tabular}}|
+\end{center}
+|40\ldots~Kf6|
+is still needed.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+41 & Kg5 & Rb8\\
+\end{tabular}}|
+\end{center}
+|41\ldots~Ke8|
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+42 & f6 & Rb2\\
+\end{tabular}}|
+\end{center}
+|42\ldots~Ke6; 43.~Kg4, Rb4+; 44.~K*h3, R*a4; 45.~d7, K*d7; 46.~Be5|
+but black should still win.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+43 & Kg6&\\
+\end{tabular}}|
+\end{center}
+|43.~f7, Rg2+; 44.~Kh6, Rf2; 45.~Kg7, Rg2+; 46.~Kh7, Rf2; 47.~Kg7|
+white has equalised!
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+43 & \ldots & Rf2\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ * * * *}
+{* *k* * }
+{ * P PK*}
+{p * * * }
+{P* * * *}
+{* * * *p}
+{ * * r B}
+{* * * * }
+$$\showboard$$
+$0\!-\!1$
+\clearpage
+\begin{center}
+\fbox{\fbox{\large\begin{tabular}{l}
+Game \hspace{.3 in} Nov 1993 \hspace{.3 in} $0\!-\!1$\\
+\hline
+Foo C60\\
+\raisebox{2.5pt}[11pt]{\framebox[11pt]{\rule{0pt}{4.25pt}}} Andy Gill\\
+\rule[-1pt]{11pt}{11pt} Ian Kennedy\\
+Dunfermline C vs Stirling B
+\end{tabular}}}
+\end{center}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+1 & e4 & e5\\
+2 & Nf3 & Nc6\\
+3 & Bb5 & Bd6\\
+4 & 0-0 & a6\\
+5 & Ba4 & b5\\
+6 & Bb3 & Bb7\\
+7 & d3 & Nf6\\
+\end{tabular}}|
+\end{center}
+|7\ldots~Na5; 8.~Nbd2, f6; 9.~a4, N*b3; 10.~N*b3, Bb4; 11.~a*b5, a*b5|
+with equality.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+8 & Nc3&\\
+\end{tabular}}|
+\end{center}
+|8.~a4, b4; 9.~Nbd2, Bc5; 10.~Nc4, d6|
+\wbetter{}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+8 & \ldots & 0-0\\
+\end{tabular}}|
+\end{center}
+|8\ldots~Na5; 9.~Bd2, N*b3; 10.~a*b3, 0-0; 11.~Bg5, Rb8|
+=
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+9 & Be3 & Na5\\
+\end{tabular}}|
+\end{center}
+
+\board
+{r* q rk*}
+{*bpp*ppp}
+{p* b n *}
+{np* p * }
+{ * *P* *}
+{*BNPBN* }
+{PPP* PPP}
+{R *Q*RK }
+$$\showboard$$
+|9\ldots~Be7; 10.~a3, Ng4; 11.~Bd2|
+\wbetter{}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+10 & Bd5?!&\\
+\end{tabular}}|
+\end{center}
+where is that bishop going.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+10 & \ldots & b4\\
+\end{tabular}}|
+\end{center}
+|10\ldots~c6; 11.~Bb3, Bc7; 12.~Bg5, N*b3; 13.~B*f6, Q*f6; 14.~a*b3|
+\bbetter{}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+11 & B*b7 & N*b7\\
+12 & Nd5&\\
+\end{tabular}}|
+\end{center}
+|12.~Ne2, Ng4; 13.~Bd2, f5; 14.~e*f5, R*f5; 15.~Ng3, Rf6|
+\wbetter{}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+12 & \ldots & c6\\
+\end{tabular}}|
+\end{center}
+|12\ldots~N*d5; 13.~e*d5, f6; 14.~c3, b*c3; 15.~b*c3, Be7; 16.~d4, d6|
+\bbetter{}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+13 & N*f6+&\\
+\end{tabular}}|
+\end{center}
+|13.~Bb6, Qc8; 14.~N*f6+, g*f6; 15.~d4, Bc7; 16.~B*c7, Q*c7|
+\wbetter{} and the black king is exposed.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+13 & \ldots & Q*f6\\
+14 & Bb6?!&\\
+\end{tabular}}|
+\end{center}
+strange move.
+|14.~Qd2, Be7; 15.~c3, a5; 16.~a3, b*a3; 17.~b*a3|
+\wbetter{} with the plan ofs owning the `b' file.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+14 & \ldots & Bc5\\
+\end{tabular}}|
+\end{center}
+|14\ldots~Be7|
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+15 & Bc7&\\
+\end{tabular}}|
+\end{center}
+|15.~N*e5|
+but black can easly win back the pawn.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+15 & \ldots & Rac8?\\
+\end{tabular}}|
+\end{center}
+|15\ldots~d6; 16.~d4, e*d4; 17.~e5, Qe7; 18.~e*d6, N*d6; 19.~B*d6, Q*d6|
+\bupperhand{}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+16 & B*e5 & Qg6\\
+17 & d4&\\
+\end{tabular}}|
+\end{center}
+|17.~Bg3, Rfe8; 18.~Ne5, Qf6; 19.~N*d7, Q*b2; 20.~Re1|
+\wupperhand{} white should now try use his center pawns to push home
+his advantage.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+17 & \ldots & Bd6\\
+18 & B*d6&\\
+\end{tabular}}|
+\end{center}
+this is to early, leaving myself underdeveloped.
+|18.~Re1, f6; 19.~B*d6, N*d6; 20.~Qd3|
+\wupperhand{}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+18 & \ldots & N*d6\\
+19 & Ne5&\\
+\end{tabular}}|
+\end{center}
+|19.~e5, Nc4; 20.~b3, Na3; 21.~Rc1, d6; 22.~Re1|
+\wupperhand{}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+19 & \ldots & Q*e4\\
+20 & N*d7 & Rfe8\\
+21 & Nc5 & Qg6?\\
+\end{tabular}}|
+\end{center}
+|21\ldots~Qe2; 22.~Re1, Qc4; 23.~Qd2, Rcd8; 24.~Rad1, a5|
+\wupperhand{} white is a clear pawn up.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+22 & N*a6 & Nf5\\
+23 & N*b4&\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ *r*r*k*}
+{* * *ppp}
+{ *p* *q*}
+{* * *n* }
+{ N P * *}
+{* * * * }
+{PPP* PPP}
+{R *Q*RK }
+$$\showboard$$
+ white should now win the endgame quite comfortably.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+23 & \ldots & Nh4\\
+\end{tabular}}|
+\end{center}
+|23\ldots~Rcd8; 24.~c3, c5; 25.~Nc2, c*d4; 26.~N*d4, Qf6; 27.~Qf3, N*d4|
+\wupperhand{} though still two clear pawns up.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+24 & g3&\\
+\end{tabular}}|
+\end{center}
+forced.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+24 & \ldots & c5\\
+25 & d*c5 & R*c5\\
+\end{tabular}}|
+\end{center}
+|25\ldots~Qe4; 26.~g*h4, Q*b4; 27.~a4, Q*h4; 28.~Qd5, Re2|
+\wupperhand{}, but whites king is dangerously exposed, and the `a'
+rook is not (yet) part of the game.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+26 & a4&\\
+\end{tabular}}|
+\end{center}
+crap plan! Its just too slow.
+|26.~Nd3, Rf5; 27.~f4, Rd5; 28.~a4, Qb6+; 29.~Rf2, Nf5|
+\wdecisive{} black will never stop 3 connected passed pawns!
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+26 & \ldots & f5\\
+27 & Nd5 & Rd8??\\
+\end{tabular}}|
+\end{center}
+|27\ldots~Qd6; 28.~Nf4, Q*d1; 29.~Rf*d1, Nf3+; 30.~Kg2, Ne5|
+\wdecisive{}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+28 & Ne7+! & Kf7\\
+29 & Q*d8 & Qg5\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ * Q * *}
+{* * Nkpp}
+{ * * * *}
+{* r *pq }
+{P* * * n}
+{* * * P }
+{ PP* P P}
+{R * *RK }
+$$\showboard$$
+|29\ldots~Nf3+; 30.~Kg2|
+is an idea.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+30 & a5&\\
+\end{tabular}}|
+\end{center}
+this plan is still to slow.
+|30.~Qg8+, K*e7; 31.~Rfe1+, Kd6; 32.~Qf8+, Kc6; 33.~Qc8+, Kb6; 34.~Re6+, Rc6; 35.~Q*c6+, Ka7; 36.~Qb6+, Ka8; 37.~Re8+, Qd8; 38.~R*d8 mate|
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+30 & \ldots & f4\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ * Q * *}
+{* * Nkpp}
+{ * * * *}
+{P r * q }
+{ * * p n}
+{* * * P }
+{ PP* P P}
+{R * *RK }
+$$\showboard$$
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+31 & f3??&\\
+\end{tabular}}|
+\end{center}
+|31.~Nc6, Nf3+; 32.~Kg2, f*g3; 33.~Qd7+, Kf8; 34.~Qc8+, Kf7; 35.~f*g3|
+\wdecisive{} but there are still some hairy tactics.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+31 & \ldots & f*g3\\
+32 & h*g3??&\\
+\end{tabular}}|
+\end{center}
+|32.~Qg8+, K*e7; 33.~Rfe1+, Re5; 34.~R*e5+, Q*e5; 35.~h3, N*f3+; 36.~Kg2|
+and white can still win!
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+32 & \ldots & Q*g3+\\
+33 & Kh1 & Qg2 mate\\
+\end{tabular}}|
+\end{center}
+painfull!
+
+\board
+{ * Q * *}
+{* * Nkpp}
+{ * * * *}
+{P r * * }
+{ * * * n}
+{* * *P* }
+{ PP* *q*}
+{R * *R*K}
+$$\showboard$$
+$0\!-\!1$
+\clearpage
+\begin{center}
+\fbox{\fbox{\large\begin{tabular}{l}
+Game \hspace{.3 in} Nov 1993 \hspace{.3 in} $1\!-\!0$\\
+\hline
+Foo C41\\
+\raisebox{2.5pt}[11pt]{\framebox[11pt]{\rule{0pt}{4.25pt}}} Andy Gill\\
+\rule[-1pt]{11pt}{11pt} Neil Langham\\
+Dunfermline Club Championship
+\end{tabular}}}
+\end{center}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+1 & e4 & e5\\
+2 & Nf3 & d6\\
+3 & Nc3 & Nf6\\
+4 & Bc4 & h6\\
+\end{tabular}}|
+\end{center}
+|4\ldots~Bg4; 5.~d3, Nc6; 6.~h3, Bh5; 7.~0-0, B*f3; 8.~Q*f3|
+=
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+5 & 0-0 & Bd7\\
+6 & d3 & Nc6\\
+7 & Bd2&\\
+\end{tabular}}|
+\end{center}
+|7.~Be3, Be7; 8.~Nd5, 0-0; 9.~h3, N*d5; 10.~B*d5, Bf6|
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+7 & \ldots & Na5\\
+\end{tabular}}|
+\end{center}
+
+\board
+{r* qkb r}
+{pppb*pp }
+{ * p n p}
+{n * p * }
+{ *B*P* *}
+{* NP*N* }
+{PPPB PPP}
+{R *Q*RK }
+$$\showboard$$
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+8 & b4&\\
+\end{tabular}}|
+\end{center}
+|8.~Bd5, Bg4; 9.~a3, c6; 10.~Ba2, d5; 11.~Be3, d*e4; 12.~N*e4|
+but black is having the freer game
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+8 & \ldots & N*c4\\
+9 & d*c4 & Be6\\
+\end{tabular}}|
+\end{center}
+|9\ldots~Be7; 10.~Qe2, 0-0; 11.~Rfd1, Be6; 12.~c5, c6; 13.~c*d6, Q*d6|
+\bbetter{}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+10 & Nd5? & N*e4\\
+11 & Qe2&\\
+\end{tabular}}|
+\end{center}
+|11.~Re1, N*d2; 12.~Q*d2, c6; 13.~Ne3, Be7; 14.~Rad1, 0-0|
+\bupperhand{}, with white a pawn and position down.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+11 & \ldots & N*d2\\
+12 & N*d2&\\
+\end{tabular}}|
+\end{center}
+|12.~Q*d2|
+is better.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+12 & \ldots & Qg5??\\
+\end{tabular}}|
+\end{center}
+
+\board
+{r* *kb r}
+{ppp *pp }
+{ * pb* p}
+{* *Np q }
+{ PP* * *}
+{* * * * }
+{P*PNQPPP}
+{R * *RK }
+$$\showboard$$
+|12\ldots~g6; 13.~Ne3, f5; 14.~c5, d*c5; 15.~b*c5, c6|
+\bupperhand{}, ready for a pawn charge on white's king.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+13 & N*c7+ & Ke7\\
+\end{tabular}}|
+\end{center}
+|13\ldots~Kd7|
+is better, stoping the future escape of the white knight.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+14 & N*a8 & Bh3\\
+\end{tabular}}|
+\end{center}
+going for the cheapo.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+15 & f4! & Qg6\\
+16 & Nc7&\\
+\end{tabular}}|
+\end{center}
+|16.~f*e5, Kd8; 17.~Qe4, Be6; 18.~Q*g6, f*g6|
+is the best line Fritz2 found.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+16 & \ldots & Kd7\\
+17 & Nd5 & Bg4\\
+18 & Qf2 & f6\\
+\end{tabular}}|
+\end{center}
+|18\ldots~Q*c2; 19.~Ne3, Qg6; 20.~f*e5, Be6; 21.~Nf3|
+rather cheeky, but still a rook down.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+19 & Ne3 & Ke6?\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ * * b r}
+{pp* * p }
+{ * pkpqp}
+{* * p * }
+{ PP* Pb*}
+{* * N * }
+{P*PN QPP}
+{R * *RK }
+$$\showboard$$
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+20 & f5+ & B*f5\\
+21 & Q*f5+&\\
+\end{tabular}}|
+\end{center}
+|21.~N*f5, Qg5; 22.~h4, Qg4|
+actually wins more material, but with this level of inequality, you
+want to swap of queens.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+21 & \ldots & Q*f5\\
+22 & N*f5 & g6\\
+23 & Ng3&\\
+\end{tabular}}|
+\end{center}
+At this point the score sheet goes wrong, but the game was won by now
+anyway!
+
+\board
+{ * * b r}
+{pp* * * }
+{ * pkppp}
+{* * p * }
+{ PP* * *}
+{* * * N }
+{P*PN *PP}
+{R * *RK }
+$$\showboard$$
+$1\!-\!0$
+\clearpage
+\begin{center}
+\fbox{\fbox{\large\begin{tabular}{l}
+Game \hspace{.3 in} Nov 1993 \hspace{.3 in} $1\!-\!0$\\
+\hline
+\raisebox{2.5pt}[11pt]{\framebox[11pt]{\rule{0pt}{4.25pt}}} Andy Gill\\
+\rule[-1pt]{11pt}{11pt} Dennis Duncan\\
+Dunfermline Club Championship
+\end{tabular}}}
+\end{center}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+1 & e4 & e5\\
+2 & Nf3 & d6\\
+3 & Bc4 & Bg4\\
+4 & 0-0 & Nf6\\
+5 & Nc3&\\
+\end{tabular}}|
+\end{center}
+|5.~d3, Nc6; 6.~Be3, d5; 7.~e*d5, N*d5; 8.~Nbd2, N*e3; 9.~f*e3|
+=
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+5 & \ldots & c6\\
+\end{tabular}}|
+\end{center}
+|5\ldots~Nc6; 6.~Bb5, Qd7; 7.~h3, B*f3; 8.~Q*f3, 0-0-0|
+=
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+6 & Bb3 & d5\\
+7 & d3&\\
+\end{tabular}}|
+\end{center}
+|7.~e*d5, c*d5; 8.~Re1, e4; 9.~d3, B*f3|
+=
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+7 & \ldots & b5\\
+\end{tabular}}|
+\end{center}
+|7\ldots~d*e4; 8.~d*e4, Q*d1; 9.~R*d1, B*f3|
+\bbetter{}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+8 & h3&\\
+\end{tabular}}|
+\end{center}
+
+\board
+{rn qkb r}
+{p * *ppp}
+{ *p* n *}
+{*p*pp * }
+{ * *P*b*}
+{*BNP*N*P}
+{PPP* PP*}
+{R BQ*RK }
+$$\showboard$$
+|8.~e*d5, b4; 9.~Ne4, c*d5; 10.~N*f6+, g*f6; 11.~d4, e*d4; 12.~Q*d4|
+\wupperhand{}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+8 & \ldots & Bc8\\
+\end{tabular}}|
+\end{center}
+|8\ldots~B*f3; 9.~Q*f3, d4; 10.~Ne2, Nbd7; 11.~Bg5, Be7|
+\wbetter{}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+9 & N*e5&\\
+\end{tabular}}|
+\end{center}
+|9.~e*d5, N*d5; 10.~N*e5, Be6; 11.~N*d5|
+\wupperhand{}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+9 & \ldots & Qc7\\
+\end{tabular}}|
+\end{center}
+|9\ldots~Bd6; 10.~Nf3, d*e4; 11.~N*e4, N*e4; 12.~Re1, B*h3; 13.~R*e4+, Be6|
+\wupperhand{}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+10 & Nf3 & Nh5\\
+\end{tabular}}|
+\end{center}
+|10\ldots~Be6; 11.~Nd4, d*e4; 12.~B*e6|
+\wupperhand{}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+11 & e*d5 & c5\\
+12 & N*b5&\\
+\end{tabular}}|
+\end{center}
+|12.~Re1+!, Be7; 13.~N*b5, Qb6; 14.~d6, Q*b5; 15.~R*e7+, Kd8; 16.~B*f7|
+\wdecisive{}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+12 & \ldots & Qb6\\
+\end{tabular}}|
+\end{center}
+|12\ldots~Qb7; 13.~Re1+, Kd8; 14.~Ne5, Nf6; 15.~Bg5, Bf5; 16.~B*f6+, g*f6|
+\wdecisive{}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+13 & Ba4&\\
+\end{tabular}}|
+\end{center}
+|13.~Re1+, Kd8; 14.~Ne5, Q*b5; 15.~N*f7+, Kc7; 16.~N*h8, Nf6; 17.~Bf4+|
+\wdecisive{}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+13 & \ldots & Bd7\\
+14 & Qe2+ & Be7\\
+\end{tabular}}|
+\end{center}
+
+\board
+{rn *k* r}
+{p *bbppp}
+{ q * * *}
+{*NpP* *n}
+{B* * * *}
+{* *P*N*P}
+{PPP*QPP*}
+{R B *RK }
+$$\showboard$$
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+15 & d4&\\
+\end{tabular}}|
+\end{center}
+|15.~d6, 0-0; 16.~d*e7, Re8; 17.~d4, c*d4; 18.~Nf*d4|
+\wdecisive{}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+15 & \ldots & B*b5\\
+16 & B*b5+ & Nd7\\
+\end{tabular}}|
+\end{center}
+|16\ldots~Kf8; 17.~Re1, Qd6; 18.~Nh4, Qf6; 19.~Q*h5|
+\wdecisive{}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+17 & B*d7+ & K*d7\\
+18 & Ne5+ & Ke8\\
+19 & d*c5&\\
+\end{tabular}}|
+\end{center}
+|19.~Nc6, Qc7; 20.~Re1, c*d4; 21.~c4, Nf6|
+\wdecisive{}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+19 & \ldots & Q*c5\\
+20 & Rd1&\\
+\end{tabular}}|
+\end{center}
+|20.~d6, Q*d6; 21.~Qf3, Rc8; 22.~N*f7, Qf6; 23.~Q*f6, N*f6; 24.~N*h8|
+\wdecisive{}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+20 & \ldots & Ng3\\
+21 & Qe3&\\
+\end{tabular}}|
+\end{center}
+|21.~Qg4, Q*c2; 22.~Rd2, Qf5; 23.~Q*g3, Bf6|
+\wdecisive{}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+21 & \ldots & Nf5\\
+22 & Q*c5&\\
+\end{tabular}}|
+\end{center}
+|22.~Qf3, Nd6; 23.~c4, Bf6; 24.~Re1, B*e5; 25.~R*e5+, Kf8|
+\wdecisive{}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+22 & \ldots & B*c5\\
+\end{tabular}}|
+\end{center}
+
+\board
+{r* *k* r}
+{p * *ppp}
+{ * * * *}
+{* bPNn* }
+{ * * * *}
+{* * * *P}
+{PPP* PP*}
+{R BR* K }
+$$\showboard$$
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+23 & Be3?&\\
+\end{tabular}}|
+\end{center}
+|23.~Re1, Ne7; 24.~c4, f6; 25.~Nd3, Bd4|
+\wdecisive{}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+23 & \ldots & N*e3\\
+\end{tabular}}|
+\end{center}
+|23\ldots~B*e3; 24.~f*e3, N*e3; 25.~Rd2, Rc8; 26.~Re2, N*d5; 27.~Ng6+, Kd7|
+Blacks best line
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+24 & f*e3 & B*e3+\\
+25 & Kf1 & Bf4\\
+26 & Re1&\\
+\end{tabular}}|
+\end{center}
+|26.~Nd3, Bd6; 27.~c4, Rc8; 28.~b3|
+\wdecisive{}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+26 & \ldots & f6\\
+\end{tabular}}|
+\end{center}
+
+\board
+{r* *k* r}
+{p * * pp}
+{ * * p *}
+{* *PN * }
+{ * * b *}
+{* * * *P}
+{PPP* *P*}
+{R * RK* }
+$$\showboard$$
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+27 & Ng6+ & Kf7\\
+28 & N*f4 & Rhe8\\
+29 & R*e8&\\
+\end{tabular}}|
+\end{center}
+|29.~c4, Rac8; 30.~b3, h6; 31.~Kf2, R*e1; 32.~R*e1, Rc5|
+\wdecisive{}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+29 & \ldots & R*e8\\
+30 & d6&\\
+\end{tabular}}|
+\end{center}
+|30.~Kf2, Re5; 31.~Rd1, g5; 32.~Ne2|
+\wdecisive{}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+30 & \ldots & Rd8\\
+31 & Rd1 & g6\\
+32 & Nd5&\\
+\end{tabular}}|
+\end{center}
+|32.~c4, g5; 33.~Ne2, Ke6; 34.~Nd4+, Kd7; 35.~c5, h6|
+\wdecisive{},5.25
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+32 & \ldots & R*d6\\
+33 & c4&\\
+\end{tabular}}|
+\end{center}
+|33.~Ke2, Ke6; 34.~c4, Rc6; 35.~Kd3, f5; 36.~b3|
+\wdecisive{},4.53
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+33 & \ldots & f5\\
+34 & Ke1&\\
+\end{tabular}}|
+\end{center}
+|34.~b3|
+\wdecisive{},4.22
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+34 & \ldots & Ra6\\
+35 & a3 & f4??\\
+\end{tabular}}|
+\end{center}
+Simply throws away a pawn.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+36 & c5&\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ * * * *}
+{p * *k*p}
+{r* * *p*}
+{* PN* * }
+{ * * p *}
+{P * * *P}
+{ P * *P*}
+{* *RK * }
+$$\showboard$$
+ why not take the pawn?
+|36.~N*f4, h6; 37.~g3, g5; 38.~Nd5, Re6+; 39.~Kd2, Re4|
+\wdecisive{},5.06 looks good to me.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+36 & \ldots & Ke6?\\
+37 & Nc7+&\\
+\end{tabular}}|
+\end{center}
+Black resigns
+
+\board
+{ * * * *}
+{p N * *p}
+{r* *k*p*}
+{* P * * }
+{ * * p *}
+{P * * *P}
+{ P * *P*}
+{* *RK * }
+$$\showboard$$
+$1\!-\!0$
+\clearpage
+\begin{center}
+\fbox{\fbox{\large\begin{tabular}{l}
+Game \hspace{.3 in} Nov 1993 \hspace{.3 in} $1\!-\!0$\\
+\hline
+Foo C70\\
+\raisebox{2.5pt}[11pt]{\framebox[11pt]{\rule{0pt}{4.25pt}}} Andy Gill\\
+\rule[-1pt]{11pt}{11pt} Adam Rintoul\\
+Dunfermline Club Championship
+\end{tabular}}}
+\end{center}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+1 & e4 & e5\\
+2 & Nf3 & Nc6\\
+3 & Bb5 & a6\\
+4 & Ba4 & b5\\
+5 & Bb3 & Nf6\\
+6 & d3 & Bc5\\
+\end{tabular}}|
+\end{center}
+|6\ldots~Bb7; 7.~0-0, d5; 8.~e*d5, N*d5; 9.~Bg5, Be7; 10.~B*e7, Nd*e7|
+=
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+7 & Be3?&\\
+\end{tabular}}|
+\end{center}
+
+\board
+{r*bqk* r}
+{* pp*ppp}
+{p*n* n *}
+{*pb p * }
+{ * *P* *}
+{*B*PBN* }
+{PPP* PPP}
+{RN*QK *R}
+$$\showboard$$
+|7.~Nc3|
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+7 & \ldots & B*e3\\
+8 & f*e3 & 0-0\\
+9 & 0-0 & d6\\
+10 & Nbd2&\\
+\end{tabular}}|
+\end{center}
+|10.~a3, Bb7; 11.~Nc3, Rb8; 12.~Nd5, a5|
+\bbetter{},0.13
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+10 & \ldots & Bg4\\
+11 & d4?&\\
+\end{tabular}}|
+\end{center}
+|11.~a4, Rb8; 12.~a*b5, a*b5; 13.~h3, Bh5; 14.~Qe2, Nd7|
+\bbetter{},-0.22
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+11 & \ldots & B*f3\\
+\end{tabular}}|
+\end{center}
+|11\ldots~e*d4; 12.~Qe1, d*e3; 13.~Q*e3, Na5; 14.~Nd4, c6; 15.~c3, N*b3|
+\bupperhand{} a pawn up.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+12 & N*f3 & N*e4??\\
+\end{tabular}}|
+\end{center}
+
+\board
+{r* q rk*}
+{* p *ppp}
+{p*np * *}
+{*p* p * }
+{ * Pn* *}
+{*B* PN* }
+{PPP* *PP}
+{R *Q*RK }
+$$\showboard$$
+|12\ldots~Qe8; 13.~d5, Na5; 14.~Qd3, N*b3; 15.~a*b3, c6; 16.~Rad1|
+\bupperhand{}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+13 & Bd5 & Qd7\\
+\end{tabular}}|
+\end{center}
+|13\ldots~Ng5; 14.~B*c6, N*f3+; 15.~B*f3, Rb8; 16.~d*e5, d*e5; 17.~a3|
+\wdecisive{}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+14 & B*e4 & f5\\
+15 & Bd5+ & Kh8\\
+16 & Ng5 & e*d4\\
+17 & Qh5&\\
+\end{tabular}}|
+\end{center}
+
+\board
+{r* * r k}
+{* pq* pp}
+{p*np * *}
+{*p*B*pNQ}
+{ * p * *}
+{* * P * }
+{PPP* *PP}
+{R * *RK }
+$$\showboard$$
+|17.~N*h7, Rfb8; 18.~Ng5, g6; 19.~Qf3, Ne5; 20.~Qh3+, Kg7; 21.~B*a8|
+\wdecisive{},4.44
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+17 & \ldots & h6?\\
+\end{tabular}}|
+\end{center}
+|17\ldots~g6; 18.~B*c6, g*h5; 19.~B*d7, d*e3; 20.~R*f5, R*f5; 21.~B*f5|
+\wdecisive{},4.90
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+18 & e*d4&\\
+\end{tabular}}|
+\end{center}
+|18.~Qg6, Qe8; 19.~Qh7 mate|
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+18 & \ldots & Rae8\\
+\end{tabular}}|
+\end{center}
+|18\ldots~Rf6; 19.~Rae1, Raf8; 20.~Ne6, Re8; 21.~Qf3|
+\wdecisive{},2.66
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+19 & Rae1 & R*e1\\
+20 & R*e1 & Nd8\\
+21 & Qg6&\\
+\end{tabular}}|
+\end{center}
+I finally find the two move mate!
+
+\board
+{ * n r k}
+{* pq* p }
+{p* p *Qp}
+{*p*B*pN }
+{ * P * *}
+{* * * * }
+{PPP* *PP}
+{* * R K }
+$$\showboard$$
+$1\!-\!0$
+\clearpage
+\begin{center}
+\fbox{\fbox{\large\begin{tabular}{l}
+Game \hspace{.3 in} Nov 1993 \hspace{.3 in} $1\!-\!0$\\
+\hline
+Foo C30\\
+\raisebox{2.5pt}[11pt]{\framebox[11pt]{\rule{0pt}{4.25pt}}} Ian Robertson (2150)\\
+\rule[-1pt]{11pt}{11pt} Andy Gill\\
+Dunfermline Club Championship
+\end{tabular}}}
+\end{center}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+1 & e4 & e5\\
+2 & f4 & d6\\
+3 & Nf3 & Nc6\\
+\end{tabular}}|
+\end{center}
+|3\ldots~e*f4|
+Just take the pawn, and then follow the main line KG.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+4 & Bb5 & Bd7\\
+5 & 0-0 & Nf6\\
+6 & Nc3 & Be7\\
+\end{tabular}}|
+\end{center}
+|6\ldots~a6; 7.~Ba4, e*f4; 8.~d3, b5; 9.~Bb3, b4|
+Who knows?
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+7 & d3&\\
+\end{tabular}}|
+\end{center}
+
+\board
+{r* qk* r}
+{pppbbppp}
+{ *np n *}
+{*B* p * }
+{ * *PP *}
+{* NP*N* }
+{PPP* *PP}
+{R BQ*RK }
+$$\showboard$$
+ At this point white is winning.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+7 & \ldots & 0-0\\
+8 & Kh1!&\\
+\end{tabular}}|
+\end{center}
+A clever waiting move, to avoid temp gaining checks.
+|8.~Ne2|
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+8 & \ldots & Nd4?\\
+\end{tabular}}|
+\end{center}
+losses a pawn
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+9 & B*d7 & Q*d7\\
+\end{tabular}}|
+\end{center}
+|9\ldots~N*f3; 10.~Bh3, Nd4; 11.~Be3, c5; 12.~f*e5, d*e5|
+\wbetter{}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+10 & f*e5 & N*f3??\\
+\end{tabular}}|
+\end{center}
+
+\board
+{r* * rk*}
+{pppqbppp}
+{ * p n *}
+{* * P * }
+{ * *P* *}
+{* NP*n* }
+{PPP* *PP}
+{R BQ*R*K}
+$$\showboard$$
+ Losses the piece.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+11 & e*f6 & B*f6\\
+12 & Q*f3 & b5?\\
+\end{tabular}}|
+\end{center}
+what is this for?
+|12\ldots~Rae8|
+Planning taking control over the very white center.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+13 & Nd5&\\
+\end{tabular}}|
+\end{center}
+
+\board
+{r* * rk*}
+{p pq*ppp}
+{ * p b *}
+{*p*N* * }
+{ * *P* *}
+{* *P*Q* }
+{PPP* *PP}
+{R B *R*K}
+$$\showboard$$
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+13 & \ldots & Qd8??\\
+\end{tabular}}|
+\end{center}
+Losses another pawn, as well as weakening the kingside, and allowing
+exchange of queens.
+|13\ldots~Bd8|
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+14 & N*f6+ & Q*f6\\
+15 & Q*f6 & g*f6\\
+16 & R*f6 & Kg7\\
+17 & Bg5&\\
+\end{tabular}}|
+\end{center}
+Black is just out of good moves.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+17 & \ldots & Rae8?\\
+\end{tabular}}|
+\end{center}
+Blocking in the f rook, allowing the skew.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+18 & Raf1 & d5?\\
+\end{tabular}}|
+\end{center}
+again lack of vision
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+19 & Bh6+ & Kg8\\
+20 & e*d5 & Rd8\\
+21 & B*f8 & R*f8\\
+22 & Rc6&\\
+\end{tabular}}|
+\end{center}
+Planning an invasion of the 7th. Textbook play.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+22 & \ldots & Rd8\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ * r *k*}
+{p p *p*p}
+{ *R* * *}
+{*p*P* * }
+{ * * * *}
+{* *P* * }
+{PPP* *PP}
+{* * *R*K}
+$$\showboard$$
+ Planing to remove the dangerous white pawn, but missing the connected
+rooks that arrive on the 7th.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+23 & R*c7 & R*d5\\
+24 & Rf*f7 & Rd8\\
+\end{tabular}}|
+\end{center}
+Silly, blocking the kings escape, athough its over anyway. I should
+have tried for at least one cheapo.
+|24\ldots~Re5|
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+25 & R*h7 & Rf8??\\
+\end{tabular}}|
+\end{center}
+Again just missing the action.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+26 & Rcg7 mate&\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ * * rk*}
+{p * * RR}
+{ * * * *}
+{*p* * * }
+{ * * * *}
+{* *P* * }
+{PPP* *PP}
+{* * * *K}
+$$\showboard$$
+$1\!-\!0$
+\clearpage
+\begin{center}
+\fbox{\fbox{\large\begin{tabular}{l}
+Game \hspace{.3 in} Dec 1993 \hspace{.3 in} $1\!-\!0$\\
+\hline
+Foo B10\\
+\raisebox{2.5pt}[11pt]{\framebox[11pt]{\rule{0pt}{4.25pt}}} Andy Gill\\
+\rule[-1pt]{11pt}{11pt} Bob Colquhoun\\
+Dunfermline Club Knockout
+\end{tabular}}}
+\end{center}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+1 & e4 & c6\\
+2 & Nf3 & d5\\
+3 & e*d5 & c*d5\\
+4 & c4&\\
+\end{tabular}}|
+\end{center}
+|4.~d4|
+Score: 0.06
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+4 & \ldots & Nf6\\
+\end{tabular}}|
+\end{center}
+|4\ldots~d4; 5.~b3, Nc6; 6.~Bb2, Nf6; 7.~Na3, e5|
+Score: -0.03
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+5 & c*d5&\\
+\end{tabular}}|
+\end{center}
+|5.~d4, e6; 6.~c*d5, N*d5; 7.~Nbd2, Bd6; 8.~Bc4|
+Score: 0.13
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+5 & \ldots & N*d5\\
+6 & Bc4 & e6\\
+\end{tabular}}|
+\end{center}
+|6\ldots~Nb6; 7.~Bb3, Nc6; 8.~d4, Bf5; 9.~Bg5, Be4|
+Score: 0.00
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+7 & 0-0 & Nc6\\
+8 & d4 & a6\\
+\end{tabular}}|
+\end{center}
+|8\ldots~Bb4; 9.~Bd2, B*d2; 10.~Nb*d2, Nf4; 11.~Nb3, 0-0|
+Score: -0.16
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+9 & Re1&\\
+\end{tabular}}|
+\end{center}
+|9.~Nc3|
+Score: -0.09
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+9 & \ldots & b5\\
+\end{tabular}}|
+\end{center}
+|9\ldots~Be7; 10.~Nc3, 0-0; 11.~Qd3, Qd7; 12.~N*d5|
+Score: -0.03
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+10 & B*d5 & Q*d5\\
+11 & Nc3 & Qf5\\
+\end{tabular}}|
+\end{center}
+|11\ldots~Qd8; 12.~d5, Ne7; 13.~d6, Nf5; 14.~Qd5, Bd7|
+Score: 0.41
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+12 & d5 & Nd8\\
+\end{tabular}}|
+\end{center}
+|12\ldots~Nb4; 13.~d6, Nd3; 14.~Re4, N*c1; 15.~R*c1, Rb8|
+Score: 0.34
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+13 & d*e6&\\
+\end{tabular}}|
+\end{center}
+|13.~d6, Nb7; 14.~Ne4, Nc5; 15.~Nd4|
+Score: 0.34
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+13 & \ldots & B*e6\\
+14 & Qd5&\\
+\end{tabular}}|
+\end{center}
+|14.~Nd5, Rc8; 15.~Nd4, Qg6; 16.~Bf4, Bc5; 17.~Nc7, Kf8; 18.~N*a6|
+Score: 0.75
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+14 & \ldots & Q*d5\\
+15 & N*d5 & Bd6\\
+16 & Bg5&\\
+\end{tabular}}|
+\end{center}
+|16.~Nd4, Rb8; 17.~Bf4, B*f4; 18.~N*f4, Rb6; 19.~Nd*e6, N*e6; 20.~N*e6|
+Score: 0.00
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+16 & \ldots & 0-0\\
+\end{tabular}}|
+\end{center}
+|16\ldots~h6; 17.~Bd2, 0-0; 18.~Bf4|
+Score: -0.25
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+17 & Rad1 & Nc6\\
+\end{tabular}}|
+\end{center}
+|17\ldots~Nb7; 18.~Be7, B*e7|
+Score: 0.00
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+18 & Nd4&\\
+\end{tabular}}|
+\end{center}
+|18.~Nb6, Bb4; 19.~R*e6, f*e6; 20.~N*a8, R*a8|
+Score: 0.16
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+18 & \ldots & B*d5\\
+\end{tabular}}|
+\end{center}
+|18\ldots~N*d4; 19.~R*d4, h6; 20.~Ne7, Kh7; 21.~R*d6, h*g5; 22.~Nd5|
+Score: -0.25
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+19 & N*c6 & B*h2+\\
+\end{tabular}}|
+\end{center}
+|19\ldots~Rfe8; 20.~R*e8, R*e8; 21.~h3, Re6; 22.~Nd4, Re4|
+Score: -0.13
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+20 & K*h2 & B*c6\\
+21 & Rd6 & Rfe8\\
+\end{tabular}}|
+\end{center}
+|21\ldots~Rac8|
+Score: -0.44
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+22 & R*e8+&\\
+\end{tabular}}|
+\end{center}
+|22.~Rc1, Be4; 23.~Rc7, h6; 24.~Be3, Kf8|
+Score: -0.41
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+22 & \ldots & B*e8\\
+23 & a3&\\
+\end{tabular}}|
+\end{center}
+|23.~Be3, h6; 24.~b3, Kh7; 25.~a3, g6; 26.~Bd4|
+Score: -0.78
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+23 & \ldots & a5\\
+\end{tabular}}|
+\end{center}
+|23\ldots~h6; 24.~Be3, Kh7; 25.~b3, f6; 26.~Bd4, Bf7; 27.~b4|
+Score: -0.88
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+24 & Kg3&\\
+\end{tabular}}|
+\end{center}
+|24.~b3, h6; 25.~Rd8, R*d8; 26.~B*d8, a4; 27.~b*a4, b*a4|
+Score: -0.81
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+24 & \ldots & a4\\
+\end{tabular}}|
+\end{center}
+|24\ldots~h6|
+Score: -0.91
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+25 & Bc1&\\
+\end{tabular}}|
+\end{center}
+|25.~Kh4, h6; 26.~Be3, Kh7; 27.~Bd4, Rc8; 28.~g3, Bc6|
+Score: -1.03
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+25 & \ldots & Rc8\\
+\end{tabular}}|
+\end{center}
+|25\ldots~h6; 26.~Be3, Kh7; 27.~Kh4, Rc8; 28.~Bd4, Bc6; 29.~f3|
+Score: -1.09
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+26 & Bd2&\\
+\end{tabular}}|
+\end{center}
+|26.~Be3, h6; 27.~Kh4, Kh7; 28.~Bd4, Bc6; 29.~f3|
+Score: -1.13
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+26 & \ldots & Rc4\\
+\end{tabular}}|
+\end{center}
+|26\ldots~Bc6; 27.~Be3, h6; 28.~f3, Kh7|
+Score: -1.16
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+27 & Rd8 & Re4\\
+28 & Bb4&\\
+\end{tabular}}|
+\end{center}
+|28.~f4|
+Score: -0.88
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+28 & \ldots & f6\\
+\end{tabular}}|
+\end{center}
+|28\ldots~h6; 29.~Kf3, Re6; 30.~Kg4, Kh7; 31.~f4, Re4; 32.~g3|
+Score: -1.13
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+29 & f4&\\
+\end{tabular}}|
+\end{center}
+|29.~Kf3, Re6; 30.~Kg4, Kf7; 31.~Kh4, Re2; 32.~Rd2|
+Score: -0.91
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+29 & \ldots & Kf7\\
+30 & Kf3&\\
+\end{tabular}}|
+\end{center}
+|30.~Rc8, Kg6; 31.~Kf3|
+Score: -1.16
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+30 & \ldots & Bc6\\
+31 & Rc8&\\
+\end{tabular}}|
+\end{center}
+|31.~Kg3, Re2; 32.~Rd2, R*d2; 33.~B*d2, Ke6; 34.~Be3|
+Score: -1.25
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+31 & \ldots & R*b4+\\
+32 & R*c6 & R*b2\\
+33 & g4&\\
+\end{tabular}}|
+\end{center}
+|33.~Rb6|
+Score: -2.06
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+33 & \ldots & Rb3+\\
+34 & Ke4 & R*a3\\
+35 & Rc7+&\\
+\end{tabular}}|
+\end{center}
+|35.~f5, h6; 36.~Rc7, Kg8; 37.~Rb7, Rb3; 38.~Rd7, Rb4; 39.~Kf3|
+Score: -3.28
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+35 & \ldots & Kg6\\
+36 & Rb7&\\
+\end{tabular}}|
+\end{center}
+|36.~f5, Kh6; 37.~Rc2, Rb3; 38.~g5, Kh5; 39.~g*f6, g*f6; 40.~Rh2|
+Score: -3.34
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+36 & \ldots & Rb3\\
+37 & f5+&\\
+\end{tabular}}|
+\end{center}
+|37.~Kd4|
+Score: -3.44
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+37 & \ldots & Kh6\\
+38 & g5+&\\
+\end{tabular}}|
+\end{center}
+|38.~Kd4, a3; 39.~Ra7, b4; 40.~Kc4, Rb2; 41.~Rb7, Rc2|
+Score: -3.59
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+38 & \ldots & f*g5\\
+39 & Rb6+ & Kh5\\
+40 & Rb7 & Rb4+\\
+\end{tabular}}|
+\end{center}
+|40\ldots~Kg4; 41.~R*g7, Rb4; 42.~Ke5, Rf4; 43.~f6, h5; 44.~Ra7, h4|
+Score: -4.09
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+41 & Ke5 & Rf4\\
+\end{tabular}}|
+\end{center}
+|41\ldots~Kg4; 42.~R*g7, Rf4; 43.~f6, h5; 44.~Ra7, Rf5; 45.~Ke6, h4|
+Score: -4.22
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+42 & R*b5 & Kg4\\
+43 & Ke6 & R*f5\\
+\end{tabular}}|
+\end{center}
+|43\ldots~h5; 44.~Re5, h4; 45.~Re1, a3; 46.~Ra1, Rf3; 47.~Rg1, Kh5|
+Score: -3.94
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+44 & R*f5&\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ * * * *}
+{* * * pp}
+{ * *K* *}
+{* * *Rp }
+{p* * *k*}
+{* * * * }
+{ * * * *}
+{* * * * }
+$$\showboard$$
+$1\!-\!0$
+\clearpage
+\begin{center}
+\fbox{\fbox{\large\begin{tabular}{l}
+Game \hspace{.3 in} Dec 1993 \hspace{.3 in} $0\!-\!1$\\
+\hline
+\raisebox{2.5pt}[11pt]{\framebox[11pt]{\rule{0pt}{4.25pt}}} Andy Gill\\
+\rule[-1pt]{11pt}{11pt} George Petrie\\
+Dunfermline Club Championship
+\end{tabular}}}
+\end{center}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+1 & e4 & c5\\
+2 & Nf3 & Nc6\\
+3 & Bc4 & d6\\
+\end{tabular}}|
+\end{center}
+|3\ldots~e6; 4.~Nc3, Nge7; 5.~d3, d5; 6.~Bb3, d4; 7.~Ne2, e5|
+Score: 0.09
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+4 & 0-0&\\
+\end{tabular}}|
+\end{center}
+|4.~c3|
+Score: 0.03
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+4 & \ldots & e6\\
+\end{tabular}}|
+\end{center}
+|4\ldots~g6; 5.~d4, c*d4; 6.~N*d4, Bg7; 7.~Be3, N*d4; 8.~B*d4, Nf6|
+Score: -0.16
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+5 & d3&\\
+\end{tabular}}|
+\end{center}
+|5.~Bb5, Nf6; 6.~d3, Bd7; 7.~Nc3, Be7; 8.~Bg5, 0-0|
+Score: 0.00
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+5 & \ldots & Be7\\
+\end{tabular}}|
+\end{center}
+|5\ldots~d5; 6.~Bb5, Nf6; 7.~Ne5, Bd7; 8.~N*d7, Q*d7; 9.~Bg5|
+Score: 0.03
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+6 & Nc3 & Bd7\\
+\end{tabular}}|
+\end{center}
+|6\ldots~Bf6|
+Score: 0.00
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+7 & Bf4&\\
+\end{tabular}}|
+\end{center}
+|7.~Re1, Nf6; 8.~Be3, 0-0; 9.~a3, Rc8; 10.~Bf4, Nd4; 11.~N*d4|
+Score: 0.06
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+7 & \ldots & a6\\
+\end{tabular}}|
+\end{center}
+|7\ldots~Na5; 8.~Nd2, N*c4; 9.~N*c4, e5; 10.~Bg3, Be6; 11.~Ne3|
+Score: -0.06
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+8 & d4&\\
+\end{tabular}}|
+\end{center}
+|8.~a3, Nf6; 9.~Re1, 0-0; 10.~Be3, e5; 11.~Nd5, Be6; 12.~N*e7|
+Score: 0.06
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+8 & \ldots & c*d4\\
+9 & Ne2 & e5\\
+\end{tabular}}|
+\end{center}
+|9\ldots~Na5|
+Score: -0.94
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+10 & Bg3 & Nf6\\
+11 & Bd5&\\
+\end{tabular}}|
+\end{center}
+|11.~c3, N*e4; 12.~c*d4, 0-0; 13.~Bd5, N*g3|
+Score: -0.97
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+11 & \ldots & 0-0\\
+\end{tabular}}|
+\end{center}
+|11\ldots~Nb4; 12.~c3, Nb*d5; 13.~e*d5, d3; 14.~Nc1, e4; 15.~Nd2|
+Score: -1.16
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+12 & c4&\\
+\end{tabular}}|
+\end{center}
+|12.~c3, d*c3; 13.~N*c3, b6; 14.~a3, Qc7; 15.~b3, Be6; 16.~B*e6|
+Score: -0.63
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+12 & \ldots & Qb6\\
+\end{tabular}}|
+\end{center}
+|12\ldots~Bg4; 13.~Qb3, Qc7; 14.~Rac1, Rac8; 15.~Qd3, b6|
+Score: -1.13
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+13 & Qd2&\\
+\end{tabular}}|
+\end{center}
+|13.~b3, Bg4; 14.~Nc1, Rac8; 15.~Nd3, Nh5; 16.~a3, N*g3; 17.~f*g3|
+Score: -1.22
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+13 & \ldots & Rac8\\
+\end{tabular}}|
+\end{center}
+|13\ldots~Nb4; 14.~b3, Bg4; 15.~Rfd1, Nb*d5|
+Score: -1.22
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+14 & Bh4&\\
+\end{tabular}}|
+\end{center}
+|14.~Rac1|
+Score: -1.25
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+14 & \ldots & Nb4\\
+\end{tabular}}|
+\end{center}
+|14\ldots~Bg4; 15.~Bg3, Nb4; 16.~b3, Nb*d5; 17.~e*d5, B*f3; 18.~g*f3|
+Score: -1.53
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+15 & Ne*d4&\\
+\end{tabular}}|
+\end{center}
+|15.~B*f6, B*f6; 16.~h3, N*d5; 17.~c*d5|
+Score: -1.44
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+15 & \ldots & Nb*d5\\
+\end{tabular}}|
+\end{center}
+|15\ldots~e*d4; 16.~b3, Bg4; 17.~Qf4, Nd3|
+Score: -3.34
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+16 & B*f6&\\
+\end{tabular}}|
+\end{center}
+|16.~e*d5, e*d4; 17.~Rfe1, Bd8; 18.~b3, Ng4; 19.~B*d8, Rf*d8; 20.~N*d4|
+Score: -1.94
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+16 & \ldots & N*f6\\
+17 & Ne2&\\
+\end{tabular}}|
+\end{center}
+|17.~Nf5, B*f5; 18.~e*f5, R*c4; 19.~b3, Ne4; 20.~Qd5, Rb4|
+Score: -4.75
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+17 & \ldots & R*c4\\
+18 & b3&\\
+\end{tabular}}|
+\end{center}
+|18.~Nc3, Rb4; 19.~b3, N*e4; 20.~N*e4, R*e4; 21.~Rfd1|
+Score: -5.13
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+18 & \ldots & R*e4\\
+19 & Nc3&\\
+\end{tabular}}|
+\end{center}
+|19.~Ng3, Rb4; 20.~Rfe1, Bg4; 21.~Qd3, Rf4; 22.~Qe3, Q*e3; 23.~f*e3|
+Score: -5.38
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+19 & \ldots & Rg4\\
+\end{tabular}}|
+\end{center}
+|19\ldots~Rf4; 20.~Qe3, Qc7|
+Score: -5.34
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+20 & Qd1&\\
+\end{tabular}}|
+\end{center}
+|20.~Rae1|
+Score: -5.41
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+20 & \ldots & Bc6\\
+21 & Na4&\\
+\end{tabular}}|
+\end{center}
+|21.~Rc1, Rf4; 22.~Re1, B*f3; 23.~g*f3, Re8; 24.~a3|
+Score: -5.66
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+21 & \ldots & Qb4\\
+\end{tabular}}|
+\end{center}
+|21\ldots~B*a4; 22.~b*a4, Qa5; 23.~Qb3, Rb4; 24.~Qc2, R*a4; 25.~Rfc1|
+Score: -5.94
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+22 & Rc1&\\
+\end{tabular}}|
+\end{center}
+|22.~h3, Rf4; 23.~Nb2, B*f3; 24.~g*f3, Rd4; 25.~Nd3, Qc3|
+Score: -5.81
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+22 & \ldots & R*g2+\\
+23 & K*g2 & Qg4+\\
+24 & Kh1 & B*f3+\\
+25 & Q*f3 & Q*f3+\\
+26 & Kg1 & Nh5\\
+\end{tabular}}|
+\end{center}
+|26\ldots~Nd5; 27.~Rc4, b5; 28.~Rfc1, b*c4; 29.~R*c4, Bf6|
+Score: -14.53
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+27 & Rc3 & Qd5\\
+\end{tabular}}|
+\end{center}
+|27\ldots~Qg4; 28.~Kh1, b5; 29.~Rg1, Qd4; 30.~Rh3, Nf4; 31.~Rhg3, b*a4|
+Score: -12.00
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+28 & Nb6&\\
+\end{tabular}}|
+\end{center}
+|28.~h3, Nf4; 29.~Rg3, Ne2; 30.~Kh2, N*g3; 31.~K*g3, Qd3; 32.~Kg2|
+Score: -11.94
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+28 & \ldots & Qd4\\
+29 & Rfc1&\\
+\end{tabular}}|
+\end{center}
+|29.~Na4, b5; 30.~h3, Nf4; 31.~Kh2, b*a4; 32.~Rc7, Re8|
+Score: -12.97
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+29 & \ldots & Q*b6\\
+30 & Rc8&\\
+\end{tabular}}|
+\end{center}
+|30.~R1c2, d5; 31.~h3, Qg6; 32.~Kh2, Nf4; 33.~f3, b6|
+Score: -13.97
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+30 & \ldots & Nf4\\
+31 & R1c7&\\
+\end{tabular}}|
+\end{center}
+|31.~R8c3, Ne2; 32.~Kf1, N*c1; 33.~R*c1, d5; 34.~h3, Bc5; 35.~f3|
+Score: -15.63
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+31 & \ldots & Bh4\\
+\end{tabular}}|
+\end{center}
+|31\ldots~Nh3; 32.~Kh1, Q*f2; 33.~Rc4, d5; 34.~Rc3, Qg1|
+Score: -#4
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+32 & Rc2&\\
+\end{tabular}}|
+\end{center}
+|32.~R*f8, K*f8; 33.~Rc8, Ke7; 34.~Rc2, Qd4; 35.~h3, B*f2; 36.~Kh2|
+Score: -18.41
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+32 & \ldots & Nd3\\
+\end{tabular}}|
+\end{center}
+|32\ldots~B*f2; 33.~Kf1, Qe3; 34.~R*f8, K*f8; 35.~Rc8, Ke7; 36.~Rc7, Kd8|
+Score: -19.53
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+33 & R*f8+&\\
+\end{tabular}}|
+\end{center}
+|33.~Kf1, B*f2; 34.~R*f8, K*f8; 35.~Rc8, Ke7; 36.~Rg8, Bg3; 37.~Ke2|
+Score: -14.78
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+33 & \ldots & K*f8\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ * * k *}
+{*p* *ppp}
+{pq p * *}
+{* * p * }
+{ * * * b}
+{*P*n* * }
+{P*R* P P}
+{* * * K }
+$$\showboard$$
+$0\!-\!1$
+\clearpage
+\begin{center}
+\fbox{\fbox{\large\begin{tabular}{l}
+Game \hspace{.3 in} Dec 1993 \hspace{.3 in} $0\!-\!1$\\
+\hline
+\raisebox{2.5pt}[11pt]{\framebox[11pt]{\rule{0pt}{4.25pt}}} Andy Gill\\
+\rule[-1pt]{11pt}{11pt} Peter Horne\\
+Dunfermline Club Championship
+\end{tabular}}}
+\end{center}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+1 & e4 & e6\\
+2 & Nf3 & Nc6\\
+3 & Bb5 & a6\\
+\end{tabular}}|
+\end{center}
+|3\ldots~d5; 4.~d3, d*e4; 5.~B*c6, b*c6; 6.~d*e4, Q*d1; 7.~K*d1|
+Score: 0.19
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+4 & Ba4&\\
+\end{tabular}}|
+\end{center}
+|4.~B*c6, d*c6; 5.~0-0, Nf6; 6.~Re1, Be7; 7.~d4, c5; 8.~e5|
+Score: 0.22
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+4 & \ldots & b5\\
+5 & Bb3 & Bb7\\
+\end{tabular}}|
+\end{center}
+|5\ldots~Na5; 6.~d3, N*b3; 7.~a*b3, Bb7; 8.~0-0, Bc5; 9.~Nc3|
+Score: -0.13
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+6 & d4&\\
+\end{tabular}}|
+\end{center}
+|6.~c3, Nf6; 7.~d3, Be7; 8.~Be3, 0-0; 9.~Nbd2, d5|
+Score: -0.09
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+6 & \ldots & Na5\\
+7 & Nbd2&\\
+\end{tabular}}|
+\end{center}
+|7.~e5, N*b3; 8.~a*b3, c5; 9.~Bg5, f6; 10.~Be3, c*d4; 11.~B*d4|
+Score: -0.38
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+7 & \ldots & Nf6\\
+\end{tabular}}|
+\end{center}
+|7\ldots~N*b3; 8.~a*b3, c5; 9.~0-0, d5; 10.~e*d5, B*d5|
+Score: -0.41
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+8 & e5 & Nd5\\
+\end{tabular}}|
+\end{center}
+|8\ldots~N*b3; 9.~N*b3, Ne4; 10.~0-0, Be7; 11.~c3, 0-0; 12.~Be3, d5|
+Score: -0.19
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+9 & 0-0 & d6\\
+\end{tabular}}|
+\end{center}
+|9\ldots~Nf4|
+Score: -0.09
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+10 & a4&\\
+\end{tabular}}|
+\end{center}
+|10.~B*d5, B*d5; 11.~a4, d*e5; 12.~a*b5, c5; 13.~b*a6, e*d4|
+Score: 0.09
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+10 & \ldots & b4\\
+\end{tabular}}|
+\end{center}
+|10\ldots~d*e5; 11.~B*d5, Q*d5; 12.~d*e5, c5; 13.~a*b5, a*b5; 14.~b3|
+Score: 0.06
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+11 & Nc4&\\
+\end{tabular}}|
+\end{center}
+|11.~B*d5, B*d5; 12.~c3, d*e5; 13.~N*e5, Bd6; 14.~c*b4, B*b4; 15.~Ndf3|
+Score: 0.03
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+11 & \ldots & N*b3\\
+12 & c*b3 & a5\\
+\end{tabular}}|
+\end{center}
+|12\ldots~Rb8; 13.~Qc2, Be7; 14.~Na5, c5; 15.~e*d6, Q*d6; 16.~N*b7, R*b7|
+Score: -0.34
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+13 & Qe2&\\
+\end{tabular}}|
+\end{center}
+|13.~Bg5, Be7; 14.~B*e7, Q*e7; 15.~Re1, d*e5|
+Score: -0.56
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+13 & \ldots & f6\\
+\end{tabular}}|
+\end{center}
+|13\ldots~Be7; 14.~Rd1, 0-0; 15.~Be3, d*e5; 16.~d*e5|
+Score: -0.63
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+14 & e*d6&\\
+\end{tabular}}|
+\end{center}
+|14.~e*f6, Bc8; 15.~f7, K*f7; 16.~Ng5, Ke7; 17.~Ne4, Qd7; 18.~Bg5|
+Score: 0.47
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+14 & \ldots & c*d6\\
+\end{tabular}}|
+\end{center}
+|14\ldots~B*d6; 15.~Q*e6, Be7; 16.~Bd2, Ra6; 17.~Qf5, c5; 18.~d*c5, B*c5|
+Score: 0.03
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+15 & Q*e6+ & Qe7\\
+\end{tabular}}|
+\end{center}
+|15\ldots~Be7; 16.~Re1, Ra6; 17.~Nh4, Nc7; 18.~Q*e7, Q*e7; 19.~R*e7, K*e7|
+Score: 0.72
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+16 & Qh3&\\
+\end{tabular}}|
+\end{center}
+|16.~N*d6, Kd8; 17.~Q*e7, B*e7; 18.~N*b7, Kc8; 19.~Nc5, Re8; 20.~Re1|
+Score: 4.66
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+16 & \ldots & Qf7\\
+\end{tabular}}|
+\end{center}
+|16\ldots~Qc7; 17.~Re1, Be7; 18.~Qe6, Ra6; 19.~Bd2, Qc8; 20.~Q*c8, B*c8|
+Score: 0.97
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+17 & Re1+ & Kd8\\
+18 & Bd2 & Qg6\\
+\end{tabular}}|
+\end{center}
+|18\ldots~g6|
+Score: 0.97
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+19 & Re2&\\
+\end{tabular}}|
+\end{center}
+|19.~Rac1, Ra6; 20.~Ne3, N*e3; 21.~B*e3, d5; 22.~Bf4, Bd6|
+Score: 0.88
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+19 & \ldots & Be7\\
+\end{tabular}}|
+\end{center}
+|19\ldots~Ra6; 20.~Rae1, Be7; 21.~Qe6, Re8; 22.~Ne3, N*e3; 23.~B*e3, B*f3|
+Score: 0.88
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+20 & Rae1&\\
+\end{tabular}}|
+\end{center}
+|20.~Nh4, Qh5; 21.~Rae1, Bc8; 22.~Qg3, Qg4; 23.~Bf4, N*f4; 24.~Q*g4|
+Score: 1.06
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+20 & \ldots & Re8\\
+\end{tabular}}|
+\end{center}
+|20\ldots~Bc8; 21.~Qh4, Bb7; 22.~Bf4, Ba6; 23.~Qg3|
+Score: 0.91
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+21 & Nh4&\\
+\end{tabular}}|
+\end{center}
+|21.~N*d6, Bc8; 22.~Nh4, Qh5; 23.~Qg3, Rg8; 24.~Nf3, Bg4|
+Score: 2.06
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+21 & \ldots & Qh5\\
+22 & Nf5&\\
+\end{tabular}}|
+\end{center}
+|22.~N*d6, Ba6; 23.~Re6, Bc8; 24.~g4, B*e6; 25.~R*e6, Nf4; 26.~B*f4|
+Score: 3.06
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+22 & \ldots & Q*h3\\
+23 & g*h3 & g6\\
+\end{tabular}}|
+\end{center}
+|23\ldots~Bc6; 24.~N*g7, Rg8; 25.~Bh6, Bd7; 26.~Nb6|
+Score: 1.53
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+24 & Nc*d6&\\
+\end{tabular}}|
+\end{center}
+|24.~Nf*d6, Bc6; 25.~N*e8, K*e8; 26.~Re6, Bd7; 27.~Nd6, Kd8; 28.~Nf7|
+Score: 3.41
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+24 & \ldots & g*f5\\
+25 & N*e8&\\
+\end{tabular}}|
+\end{center}
+|25.~N*b7, Kd7; 26.~Nc5, B*c5; 27.~d*c5, R*e2|
+Score: 1.66
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+25 & \ldots & K*e8\\
+26 & Bh6&\\
+\end{tabular}}|
+\end{center}
+|26.~f3, Kd7; 27.~Kf2, Rg8; 28.~Rd1, Bd6; 29.~Kf1, Bc6|
+Score: -0.16
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+26 & \ldots & Kf7\\
+\end{tabular}}|
+\end{center}
+|26\ldots~Kd7; 27.~f3, Rg8; 28.~Kf2, Bd6; 29.~Rg1, Rg6; 30.~R*g6, h*g6|
+Score: -0.47
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+27 & Bf4&\\
+\end{tabular}}|
+\end{center}
+|27.~f3, Rg8; 28.~Kf2, Bd6; 29.~Rg1, Rg6; 30.~R*g6, h*g6; 31.~Ke1|
+Score: -0.41
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+27 & \ldots & Rg8+\\
+28 & Kf1 & Ba6\\
+29 & Bd2 & Bd6\\
+30 & f3&\\
+\end{tabular}}|
+\end{center}
+|30.~Rc1, B*h2; 31.~f3, Bg1; 32.~Rc4, B*c4; 33.~b*c4, B*d4; 34.~Rg2|
+Score: -3.00
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+30 & \ldots & B*h2\\
+31 & Kf2&\\
+\end{tabular}}|
+\end{center}
+|31.~Rc1, Bg1; 32.~Rc4, B*c4; 33.~b*c4, B*d4; 34.~Re1, Ne7|
+Score: -3.13
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+31 & \ldots & Bg3+\\
+32 & Kf1 & B*e1\\
+33 & B*e1&\\
+\end{tabular}}|
+\end{center}
+|33.~K*e1, Rg1; 34.~Kf2, Rb1; 35.~Re1, R*b2; 36.~Rd1, Nc3; 37.~Ke1|
+Score: -4.84
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+33 & \ldots & Ne3+\\
+\end{tabular}}|
+\end{center}
+|33\ldots~Re8; 34.~Bg3, R*e2; 35.~Kg1, R*b2; 36.~Bd6, R*b3|
+Score: -8.31
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+34 & Kf2 & f4\\
+\end{tabular}}|
+\end{center}
+|34\ldots~Nd1; 35.~Kf1, Re8; 36.~Kg1, B*e2; 37.~f4, Rd8; 38.~Kg2, R*d4|
+Score: -7.81
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+35 & R*e3 & f*e3+\\
+36 & K*e3 & Re8+\\
+37 & Kd2 & Re2+\\
+38 & Kd1 & R*b2\\
+39 & d5&\\
+\end{tabular}}|
+\end{center}
+|39.~f4, R*b3; 40.~h4, Rd3; 41.~Kc1, R*d4; 42.~Bg3, Rd3; 43.~Bf2|
+Score: -6.09
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+39 & \ldots & R*b3\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ * * * *}
+{* * *k*p}
+{b* * p *}
+{p *P* * }
+{Pp * * *}
+{*r* *P*P}
+{ * * * *}
+{* *KB * }
+$$\showboard$$
+$0\!-\!1$
+\clearpage
+\begin{center}
+\fbox{\fbox{\large\begin{tabular}{l}
+Game \hspace{.3 in} Jan 1994 \hspace{.3 in} $1\!-\!0$\\
+\hline
+\raisebox{2.5pt}[11pt]{\framebox[11pt]{\rule{0pt}{4.25pt}}} Andy Gill\\
+\rule[-1pt]{11pt}{11pt} Brian Easton\\
+Dunfermline Club Championship
+\end{tabular}}}
+\end{center}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+1 & e4 & Nf6\\
+2 & Nc3 & e6\\
+3 & d4 & d5\\
+4 & e5 & Ne4\\
+5 & N*e4 & d*e4\\
+6 & Bc4 & Nc6\\
+7 & Be3 & Bb4+\\
+8 & c3 & Be7\\
+9 & Ne2 & Bg5\\
+10 & Qd2 & Na5\\
+11 & B*g5 & N*c4\\
+12 & Qf4 & Qd5\\
+13 & b3 & Nb2\\
+14 & 0-0 & b6\\
+15 & Ng3 & Ba6\\
+16 & c4 & Nd3\\
+17 & Q*e4 & Q*e4\\
+18 & N*e4 & Bb7\\
+19 & f3 & 0-0\\
+20 & Nf2 & f6\\
+21 & e*f6 & g*f6\\
+22 & Bh6 & Rf7\\
+23 & N*d3 & Rd8\\
+24 & Nf4 & Re7\\
+25 & Rfe1 & Kf7\\
+26 & Rad1 & e5\\
+27 & d*e5 & R*d1\\
+28 & R*d1 & f*e5\\
+29 & Nd5 & Rd7\\
+30 & f4 & e4\\
+31 & f5 & c6\\
+32 & Nc3 & c5\\
+33 & R*d7+ & Kf6\\
+34 & R*b7 & K*f5\\
+35 & R*h7 & Kg6\\
+36 & Rh8&\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ * * * R}
+{p * * * }
+{ p * *kB}
+{* p * * }
+{ *P*p* *}
+{*PN * * }
+{P* * *PP}
+{* * * K }
+$$\showboard$$
+$1\!-\!0$
+\clearpage
+\begin{center}
+\fbox{\fbox{\large\begin{tabular}{l}
+Game \hspace{.3 in} Jan 1994 \hspace{.3 in} $1\!-\!0$\\
+\hline
+\raisebox{2.5pt}[11pt]{\framebox[11pt]{\rule{0pt}{4.25pt}}} George Plant\\
+\rule[-1pt]{11pt}{11pt} Andy Gill\\
+Wester-Hailes Congress
+\end{tabular}}}
+\end{center}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+1 & e4 & e5\\
+2 & Nf3 & Nc6\\
+3 & Bb5 & a6\\
+4 & Ba4 & Nf6\\
+5 & d4 & b5\\
+6 & Bb3 & d6\\
+7 & Ng5 & Qd7\\
+8 & B*f7+ & Kd8\\
+9 & d5 & Nb4\\
+10 & c3 & N*e4\\
+11 & Be6 & Qe8\\
+12 & c*b4 & N*g5\\
+13 & B*g5+ & Be7\\
+14 & B*e7+ & Q*e7\\
+15 & B*c8 & R*c8\\
+16 & 0-0 & c6\\
+17 & d*c6 & R*c6\\
+18 & Re1 & h5\\
+19 & Nc3 & Rc4\\
+20 & a3 & g5\\
+21 & Nd5 & Qg7\\
+22 & Ne3 & Rc7\\
+23 & Nf5 & Qf6\\
+24 & Q*d6+ & Q*d6\\
+25 & N*d6 & Re7\\
+26 & R*e5 & R*e5\\
+27 & Nf7+ & Ke7\\
+28 & N*e5 & Rc8\\
+29 & Nd3 & Kd6\\
+30 & Kf1 & h4\\
+31 & h3 & Kd5\\
+32 & Ne1 & Ke4\\
+33 & Nf3 & Kf4\\
+34 & Nd4 & Re8\\
+35 & Re1 & R*e1+\\
+36 & K*e1 & Ke5\\
+37 & Nc2 & Ke4\\
+38 & Ke2 & Kf4\\
+39 & Kd3 & Ke5\\
+40 & Ne3 & Kf4\\
+41 & Nd5+ & Kf5\\
+42 & Nc7&\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ * * * *}
+{* N * * }
+{p* * * *}
+{*p* *kp }
+{ P * * p}
+{P *K* *P}
+{ P * PP*}
+{* * * * }
+$$\showboard$$
+$1\!-\!0$
+\clearpage
+\begin{center}
+\fbox{\fbox{\large\begin{tabular}{l}
+Game \hspace{.3 in} Jan 1994 \hspace{.3 in} $1\!-\!0$\\
+\hline
+\raisebox{2.5pt}[11pt]{\framebox[11pt]{\rule{0pt}{4.25pt}}} Andy Gill\\
+\rule[-1pt]{11pt}{11pt} C. McIntee\\
+Wester-Hailes Congress
+\end{tabular}}}
+\end{center}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+1 & e4 & c5\\
+2 & Nf3 & Nc6\\
+3 & Be2 & Nf6\\
+4 & Nc3 & e6\\
+5 & 0-0 & d5\\
+6 & e*d5 & N*d5\\
+7 & N*d5 & Q*d5\\
+8 & c4 & Qd8\\
+9 & Re1 & h5\\
+10 & b3 & f6\\
+11 & Bb2 & h4\\
+12 & h3 & Qc7\\
+13 & d4 & Qf4\\
+14 & d5 & e*d5\\
+15 & c*d5 & Nd8\\
+16 & Bb5+ & Kf7\\
+17 & Qc1 & Qd6\\
+18 & Qe3 & Be7\\
+19 & Qe4 & g5\\
+20 & Bd3 & Ke8\\
+21 & Qg6+ & Kd7\\
+22 & Bb5+ & Kc7\\
+23 & Ne5 & Q*d5\\
+24 & Rad1 & Qg8\\
+25 & Bc4 & Ne6\\
+26 & Q*g8 & R*g8\\
+27 & B*e6 & B*e6\\
+28 & Nf3 & Rad8\\
+29 & R*d8 & R*d8\\
+30 & R*e6 & Rd1+\\
+31 & Kh2 & Bd6+\\
+32 & g3 & f5\\
+33 & Be5 & h*g3+\\
+34 & f*g3 & B*e5\\
+35 & R*e5 & Ra1\\
+36 & R*c5+ & Kb6\\
+37 & Rc2 & g4\\
+38 & h*g4 & f*g4\\
+39 & Ne5 & Kb5\\
+40 & N*g4 & a5\\
+41 & Ne3 & Re1\\
+42 & Nc4 & Re6\\
+43 & g4 & Rh6+\\
+44 & Kg3 & Rg6\\
+45 & Rg2 & a4\\
+46 & Ne5 & Rg5\\
+47 & b*a4+ & K*a4\\
+48 & Kf4 & Rg7\\
+49 & g5 & b5\\
+50 & g6 & b4\\
+51 & Kf5 & Ka3\\
+52 & Kf6 & Rg8\\
+53 & g7&\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ * * *r*}
+{* * * P }
+{ * * K *}
+{* * N * }
+{ p * * *}
+{k * * * }
+{P* * *R*}
+{* * * * }
+$$\showboard$$
+$1\!-\!0$
+\clearpage
+\begin{center}
+\fbox{\fbox{\large\begin{tabular}{l}
+Game \hspace{.3 in} Jan 1994 \hspace{.3 in} $1\!-\!0$\\
+\hline
+\raisebox{2.5pt}[11pt]{\framebox[11pt]{\rule{0pt}{4.25pt}}} F. Robertson\\
+\rule[-1pt]{11pt}{11pt} Andy Gill\\
+Wester-Hailes Congress
+\end{tabular}}}
+\end{center}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+1 & d4 & d5\\
+2 & Nf3 & e6\\
+3 & Bf4 & Be7\\
+4 & e3 & Nf6\\
+5 & Bd3 & b6\\
+6 & 0-0 & 0-0\\
+7 & Re1 & Bb7\\
+8 & Nbd2 & c5\\
+9 & c3 & Nc6\\
+10 & Ne5 & Rc8\\
+11 & Ndf3 & c4\\
+12 & Bc2 & b5\\
+13 & b3 & Qa5\\
+14 & b4 & Qd8\\
+15 & a4 & a6\\
+16 & a*b5 & a*b5\\
+17 & N*c6 & B*c6\\
+18 & Ne5 & Bb7\\
+19 & Ra5 & Qe8\\
+20 & Ra7 & Ba8\\
+21 & Ng4 & Bc6\\
+22 & Be5 & Qd8\\
+23 & Qf3 & Ra8\\
+24 & R*a8 & B*a8\\
+25 & N*f6+ & B*f6\\
+26 & e4 & B*e5\\
+27 & d*e5 & d*e4\\
+28 & B*e4 & B*e4\\
+29 & Q*e4 & Qd3\\
+30 & Q*d3 & c*d3\\
+31 & Rd1 & Rd8\\
+32 & f4 & f5\\
+33 & Kf2 & Kf8\\
+34 & Ke3 & Ke7\\
+35 & R*d3 & R*d3+\\
+36 & K*d3 & Kd7\\
+37 & h3 & g6\\
+38 & Kd4 & Kc6\\
+39 & g3 & Kb6\\
+40 & g4 & Kc6\\
+41 & c4 & Kb6\\
+42 & c5+ & Kc6\\
+43 & Ke3 & Kc7\\
+44 & Ke2 & Kc6\\
+45 & Kf3 & Kd5\\
+46 & g*f5 & g*f5\\
+47 & h4 & Kc4\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ * * * *}
+{* * * *p}
+{ * *p* *}
+{*pP Pp* }
+{ Pk* P P}
+{* * *K* }
+{ * * * *}
+{* * * * }
+$$\showboard$$
+$1\!-\!0$
+\clearpage
+\begin{center}
+\fbox{\fbox{\large\begin{tabular}{l}
+Game \hspace{.3 in} Jan 1994 \hspace{.3 in} $0\!-\!1$\\
+\hline
+\raisebox{2.5pt}[11pt]{\framebox[11pt]{\rule{0pt}{4.25pt}}} Andy Gill\\
+\rule[-1pt]{11pt}{11pt} A. McKerrow\\
+Wester-Hailes Congress
+\end{tabular}}}
+\end{center}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+1 & e4 & e5\\
+2 & Nf3 & Nc6\\
+3 & Bb5 & a6\\
+4 & Ba4 & Nf6\\
+5 & 0-0 & Be7\\
+6 & Nc3 & b5\\
+7 & Bb3 & 0-0\\
+8 & a3 & d6\\
+9 & Re1 & Rb8\\
+10 & d3 & Bg4\\
+11 & h3 & Bh5\\
+12 & Nd5 & N*d5\\
+13 & e*d5 & Nd4\\
+14 & g4 & N*f3+\\
+15 & Q*f3 & Bg6\\
+16 & a4 & b4\\
+17 & a5 & Qc8\\
+18 & Ba4 & f5\\
+19 & g*f5 & R*f5\\
+20 & Qg4 & Bh5\\
+21 & Qc4 & Rf6\\
+22 & Bg5 & Rg6\\
+23 & f4 & h6\\
+24 & R*e5 & d*e5\\
+25 & d6+ & Qe6\\
+26 & Q*e6+ & R*e6\\
+27 & Bb3 & h*g5\\
+28 & d*e7 & Bf7\\
+29 & f*g5 & Rg6\\
+30 & Rf1 & B*b3\\
+31 & c*b3 & R*g5+\\
+32 & Kh2 & Re8\\
+33 & h4 & Rg4\\
+34 & Kh3 & Rf4\\
+35 & R*f4 & e*f4\\
+36 & Kg4 & R*e7\\
+37 & K*f4 & Rd7\\
+38 & Ke4 & Rd6\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ * * *k*}
+{* p * p }
+{p* r * *}
+{P * * * }
+{ p *K* P}
+{*P*P* * }
+{ P * * *}
+{* * * * }
+$$\showboard$$
+$0\!-\!1$
+\clearpage
+\begin{center}
+\fbox{\fbox{\large\begin{tabular}{l}
+Game \hspace{.3 in} Jan 1994 \hspace{.3 in} $1\!-\!0$\\
+\hline
+\raisebox{2.5pt}[11pt]{\framebox[11pt]{\rule{0pt}{4.25pt}}} S. McCluskey\\
+\rule[-1pt]{11pt}{11pt} Andy Gill\\
+Wester-Hailes Congress
+\end{tabular}}}
+\end{center}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+1 & e4 & e5\\
+2 & Nf3 & Nc6\\
+3 & Bb5 & a6\\
+4 & B*c6 & d*c6\\
+5 & d3 & Bd6\\
+6 & 0-0 & Bg4\\
+7 & h3 & Bh5\\
+8 & Be3 & Qe7\\
+9 & Nc3 & Nf6\\
+10 & Re1 & 0-0-0\\
+11 & Nb1 & Bb4\\
+12 & c3 & Ba5\\
+13 & b4 & Bb6\\
+14 & a3 & N*e4\\
+15 & B*b6 & B*f3\\
+16 & Q*f3 & Ng5\\
+17 & Qe3 & c*b6\\
+18 & d4 & Rhe8\\
+19 & h4 & Ne6\\
+20 & g3 & e*d4\\
+21 & c*d4 & R*d4\\
+22 & Nc3 & c5\\
+23 & Rac1 & Red8\\
+24 & b*c5 & b*c5\\
+25 & Ne4 & R8d7\\
+26 & N*c5 & Rc7\\
+27 & N*e6 & Q*e6\\
+28 & Q*d4 & R*c1\\
+29 & R*c1+ & Kb8\\
+30 & Q*g7&\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ k * * *}
+{*p* *pQp}
+{p* *q* *}
+{* * * * }
+{ * * * P}
+{P * * P }
+{ * * P *}
+{* R * K }
+$$\showboard$$
+$1\!-\!0$
+\clearpage
+\begin{center}
+\fbox{\fbox{\large\begin{tabular}{l}
+Game \hspace{.3 in} Jan 1994 \hspace{.3 in} $1\!-\!0$\\
+\hline
+\raisebox{2.5pt}[11pt]{\framebox[11pt]{\rule{0pt}{4.25pt}}} Andy Gill\\
+\rule[-1pt]{11pt}{11pt} Rab Brown\\
+Dunferline Club Knockout
+\end{tabular}}}
+\end{center}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+1 & e4 & e5\\
+2 & Nf3 & d6\\
+3 & d4 & Nc6\\
+4 & d*e5 & N*e5\\
+5 & N*e5 & d*e5\\
+6 & Q*d8+ & K*d8\\
+7 & Bc4 & Bb4+\\
+8 & Nc3 & B*c3+\\
+9 & b*c3 & Be6\\
+10 & B*e6 & f*e6\\
+11 & 0-0 & Nf6\\
+12 & Bb2 & N*e4\\
+13 & c4 & Nd2\\
+14 & Rfd1 & Ke7\\
+15 & R*d2 & c5\\
+16 & B*e5 & Rhg8\\
+17 & Rad1 & g5\\
+18 & Rd7+ & Ke8\\
+19 & R*b7 & g4\\
+20 & R*h7 & Rd8\\
+21 & R*d8+ & K*d8\\
+22 & Rh8 & R*h8\\
+23 & B*h8 & Kd7\\
+24 & f3 & g*f3\\
+25 & g*f3 & Ke7\\
+26 & Be5 & Kd7\\
+27 & Kg2 & Ke7\\
+28 & Kg3 & Kf7\\
+29 & Bd6 & Kf6\\
+30 & B*c5 & a5\\
+31 & Kf4 & e5+\\
+32 & Ke4 & Ke6\\
+33 & f4 & a4\\
+34 & f*e5 & a3\\
+35 & B*a3 & Kd7\\
+36 & Kd5 & Ke8\\
+37 & Ke6 & Kd8\\
+38 & Kf7 & Kd7\\
+39 & e6+ & Kc6\\
+40 & e7 & Kc7\\
+41 & e8=Q & Kb7\\
+42 & Qe6 & Kc7\\
+43 & Qd6+ & Kb7\\
+44 & Ke7 & Ka7\\
+45 & Qb4 & Ka8\\
+46 & Kd7 & Ka7\\
+47 & Kc7 & Ka6\\
+48 & Qb6 mate&\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ * * * *}
+{* K * * }
+{kQ * * *}
+{* * * * }
+{ *P* * *}
+{B * * * }
+{P*P* * P}
+{* * * * }
+$$\showboard$$
+$1\!-\!0$
+\clearpage
+\begin{center}
+\fbox{\fbox{\large\begin{tabular}{l}
+Game \hspace{.3 in} Jan 1994 \hspace{.3 in} $0\!-\!1$\\
+\hline
+\raisebox{2.5pt}[11pt]{\framebox[11pt]{\rule{0pt}{4.25pt}}} Andy Gill\\
+\rule[-1pt]{11pt}{11pt} Dick Patterson\\
+Dunfermline C vs Grangemouth B
+\end{tabular}}}
+\end{center}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+1 & e4 & c5\\
+2 & Nf3 & Nc6\\
+3 & Be2 & e6\\
+4 & b3 & a6\\
+5 & 0-0 & b5\\
+6 & Bb2 & Nf6\\
+7 & e5 & Nd5\\
+8 & d4 & Bb7\\
+9 & c4 & Nf4\\
+10 & c*b5 & N*e2+\\
+11 & Q*e2 & a*b5\\
+12 & Re1 & c*d4\\
+13 & N*d4 & N*d4\\
+14 & B*d4 & Qg5\\
+15 & g3 & Rc8\\
+16 & f4 & Qg6\\
+17 & Q*b5 & Bc6\\
+18 & Qe2 & Be7\\
+19 & a4 & 0-0\\
+20 & a5 & f6\\
+21 & e*f6 & B*f6\\
+22 & B*f6 & R*f6\\
+23 & b4 & R*f4\\
+24 & Qd2 & Rf3\\
+25 & Rf1 & R*f1+\\
+26 & K*f1 & Qf5+\\
+27 & Qf4 & Qd3+\\
+28 & Ke1 & Rf8\\
+29 & Q*f8+ & K*f8\\
+30 & a6 & Qd4\\
+31 & Ke2 & Q*a1\\
+32 & Nd2 & Q*a6+\\
+33 & Ke3 & Qa3+\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ * * k *}
+{* *p* pp}
+{ *b*p* *}
+{* * * * }
+{ P * * *}
+{q * K P }
+{ * N * P}
+{* * * * }
+$$\showboard$$
+$0\!-\!1$
+\clearpage
+\begin{center}
+\fbox{\fbox{\large\begin{tabular}{l}
+Game \hspace{.3 in} Jan 1994 \hspace{.3 in} $1\!-\!0$\\
+\hline
+\raisebox{2.5pt}[11pt]{\framebox[11pt]{\rule{0pt}{4.25pt}}} Ian Mitchell (1660)\\
+\rule[-1pt]{11pt}{11pt} Andy Gill\\
+Dunfermline Club Championship
+\end{tabular}}}
+\end{center}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+1 & e4 & e5\\
+2 & f4 & e*f4\\
+3 & Nf3 & Nc6\\
+4 & d4 & Nf6\\
+5 & Bd3 & d5\\
+6 & e5 & Ne4\\
+7 & 0-0 & g5\\
+8 & c3 & Qe7\\
+9 & Nfd2 & Bf5\\
+10 & Qe2 & N*d2\\
+11 & N*d2 & B*d3\\
+12 & Q*d3 & 0-0-0\\
+13 & a4 & Rg8\\
+14 & a5 & a6\\
+15 & b4 & h6\\
+16 & b5 & Nb8\\
+17 & Nb3 & a*b5\\
+18 & Q*b5 & Qd7\\
+19 & Qd3 & f6\\
+20 & e*f6 & Bd6\\
+21 & Bd2 & Qg4\\
+22 & a6 & N*a6\\
+23 & R*a6 & b*a6\\
+24 & Q*a6+ & Kd7\\
+25 & Qb5+ & Ke6\\
+26 & c4 & f3\\
+27 & R*f3 & Rb8\\
+28 & Q*d5+ & Kd7\\
+29 & Nc5+ & Kd8\\
+30 & Q*g8+&\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ r k *Q*}
+{* p * * }
+{ * b P p}
+{* N * p }
+{ *PP *q*}
+{* * *R* }
+{ * B *PP}
+{* * * K }
+$$\showboard$$
+$1\!-\!0$
+\clearpage
+\begin{center}
+\fbox{\fbox{\large\begin{tabular}{l}
+Game \hspace{.3 in} Feb 1994 \hspace{.3 in} $0\!-\!1$\\
+\hline
+\raisebox{2.5pt}[11pt]{\framebox[11pt]{\rule{0pt}{4.25pt}}} Andy Gill\\
+\rule[-1pt]{11pt}{11pt} Paul Burtwistle\\
+Dunfermline Club Championship
+\end{tabular}}}
+\end{center}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+1 & e4 & c5\\
+2 & Nf3 & e6\\
+3 & Be2 & Nc6\\
+4 & 0-0 & Nf6\\
+5 & Nc3 & d5\\
+6 & e5 & Nd7\\
+7 & Re1 & Nd*e5\\
+8 & N*e5 & N*e5\\
+9 & Bb5+ & Nc6\\
+10 & d4 & a6\\
+11 & B*c6+ & b*c6\\
+12 & Be3 & c*d4\\
+13 & B*d4 & c5\\
+14 & Be5 & Bb7\\
+15 & Qd2 & f6\\
+16 & Bc7 & Q*c7\\
+17 & R*e6+ & Kf7\\
+18 & Rae1 & d4\\
+19 & Nd1 & Bd6\\
+20 & f4 & Rhe8\\
+21 & f5 & Bd5\\
+22 & R*e8 & R*e8\\
+23 & c3 & R*e1+\\
+24 & Q*e1 & B*h2+\\
+25 & Kh1 & Be5\\
+26 & c*d4 & c*d4\\
+27 & Qe2 & Qc4\\
+28 & Qh5+ & Kf8\\
+29 & Kg1 & Qc2\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ * * k *}
+{* * * pp}
+{p* * p *}
+{* *bbP*Q}
+{ * p * *}
+{* * * * }
+{PPq* *P*}
+{* *N* K }
+$$\showboard$$
+$0\!-\!1$
+\clearpage
+\begin{center}
+\fbox{\fbox{\large\begin{tabular}{l}
+Game \hspace{.3 in} Feb 1994 \hspace{.3 in} $0\!-\!1$\\
+\hline
+\raisebox{2.5pt}[11pt]{\framebox[11pt]{\rule{0pt}{4.25pt}}} Andy Gill\\
+\rule[-1pt]{11pt}{11pt} Jim O'Neill (1875)\\
+Dunfermline Club Knockout
+\end{tabular}}}
+\end{center}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+1 & e4 & c5\\
+2 & Nf3 & d6\\
+3 & d4 & c*d4\\
+4 & N*d4 & Nf6\\
+5 & Bd3 & a6\\
+6 & 0-0 & e5\\
+7 & Nf3 & Bg4\\
+8 & Nc3 & Nbd7\\
+9 & Re1 & Rc8\\
+10 & Be3 & b5\\
+11 & Nd5 & N*d5\\
+12 & e*d5 & Nf6\\
+13 & Bg5 & Be7\\
+14 & B*f6 & B*f6\\
+15 & Be4 & 0-0\\
+16 & c3 & Bh4\\
+17 & Qc2 & f5\\
+18 & N*h4 & Q*h4\\
+19 & g3 & Qh5\\
+20 & Bg2 & Rf6\\
+21 & f3 & B*f3\\
+22 & B*f3 & Q*f3\\
+23 & Rad1 & f4\\
+24 & g*f4 & Rg6+\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ *r* *k*}
+{* * * pp}
+{p* p *r*}
+{*p*Pp * }
+{ * * P *}
+{* P *q* }
+{PPQ* * P}
+{* *RR K }
+$$\showboard$$
+$0\!-\!1$
+\clearpage
+\begin{center}
+\fbox{\fbox{\large\begin{tabular}{l}
+Game \hspace{.3 in} Feb 1994 \hspace{.3 in} $1\!-\!0$\\
+\hline
+\raisebox{2.5pt}[11pt]{\framebox[11pt]{\rule{0pt}{4.25pt}}} Andy Gill\\
+\rule[-1pt]{11pt}{11pt} Bill Bell\\
+Dunfermline Club Championship
+\end{tabular}}}
+\end{center}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+1 & e4 & e6\\
+2 & d4 & d5\\
+3 & Nf3 & d*e4\\
+4 & Nfd2 & Q*d4\\
+5 & c3 & Qd5\\
+6 & Be2 & e3\\
+7 & Nf3 & Q*d1+\\
+8 & B*d1 & e*f2+\\
+9 & K*f2 & Nc6\\
+10 & Be3 & Bd7\\
+11 & Re1 & h6\\
+12 & Nbd2 & 0-0-0\\
+13 & Ba4 & Kb8\\
+14 & Rad1 & Bd6\\
+15 & b4 & a6\\
+16 & Nc4 & Be7\\
+17 & Nfe5 & Be8\\
+18 & R*d8+ & B*d8\\
+19 & B*c6 & B*c6\\
+20 & N*f7 & Rh7\\
+21 & N*d8 & Bd5\\
+22 & Nd2 & g5\\
+23 & Rd1 & Kc8\\
+24 & Nb3 & Rd7\\
+25 & N*b7 & B*b7\\
+26 & R*d7 & K*d7\\
+27 & Nc5+ & Kc6\\
+28 & N*e6 & Nf6\\
+29 & Nd8+ & Kd7\\
+30 & N*b7 & Ne4+\\
+31 & Kf3 & N*c3\\
+32 & Nc5+ & Kc6\\
+33 & N*a6 & N*a2\\
+34 & Bd2 & Kb6\\
+35 & Nc5 & Kc6\\
+36 & Nd3 & Kb5\\
+37 & Ke4 & Kc4\\
+38 & g3 & Kb3\\
+39 & h4 & g*h4\\
+40 & g*h4 & Nc3+\\
+41 & B*c3 & K*c3\\
+42 & h5 & Kc4\\
+43 & Ne5+ & K*b4\\
+44 & Kd5 & c5\\
+45 & Nd3+ & Kb5\\
+46 & N*c5 & Kb6\\
+47 & Ne6 & Kb7\\
+48 & Nf8 & Kc7\\
+49 & Ke6 & Kd8\\
+50 & Kf7 & Kc8\\
+51 & Kg6 & Kd8\\
+52 & K*h6 & Ke8\\
+53 & Kg7&\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ * *kN *}
+{* * * K }
+{ * * * *}
+{* * * *P}
+{ * * * *}
+{* * * * }
+{ * * * *}
+{* * * * }
+$$\showboard$$
+$1\!-\!0$
+\clearpage
+\begin{center}
+\fbox{\fbox{\large\begin{tabular}{l}
+Game \hspace{.3 in} Feb 1994 \hspace{.3 in} $1\!-\!0$\\
+\hline
+\raisebox{2.5pt}[11pt]{\framebox[11pt]{\rule{0pt}{4.25pt}}} John MacArthur (1725)\\
+\rule[-1pt]{11pt}{11pt} Andy Gill\\
+Dunfermline Club Championship
+\end{tabular}}}
+\end{center}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+1 & d4 & e6\\
+2 & Nf3 & Nf6\\
+3 & c4 & d5\\
+4 & Nc3 & Nc6\\
+5 & e3 & Be7\\
+6 & Be2 & 0-0\\
+7 & 0-0 & Qd6\\
+8 & c5 & Qd7\\
+9 & Ne5 & N*e5\\
+10 & d*e5 & Ne4\\
+11 & N*e4 & d*e4\\
+12 & Qc2 & Qc6\\
+13 & b4 & Rd8\\
+14 & Bb2 & a5\\
+15 & a3 & a*b4\\
+16 & a*b4 & R*a1\\
+17 & R*a1 & b6\\
+18 & Bd4 & b*c5\\
+19 & b*c5 & Bb7\\
+20 & Ra5 & Ra8\\
+21 & Bb5 & Qd5\\
+22 & Qa4 & R*a5\\
+23 & Q*a5 & B*c5\\
+24 & Q*c7 & Bf8\\
+25 & Be8 & h6\\
+26 & Q*f7+ & Kh7\\
+27 & Q*f8 & Bc6\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ * *BQ *}
+{* * * pk}
+{ *b*p* p}
+{* *qP * }
+{ * Bp* *}
+{* * P * }
+{ * * PPP}
+{* * * K }
+$$\showboard$$
+$1\!-\!0$
+\clearpage
+\begin{center}
+\fbox{\fbox{\large\begin{tabular}{l}
+Game \hspace{.3 in} Feb 1994 \hspace{.3 in} $1\!-\!0$\\
+\hline
+\raisebox{2.5pt}[11pt]{\framebox[11pt]{\rule{0pt}{4.25pt}}} Ian Sneddon (1685)\\
+\rule[-1pt]{11pt}{11pt} Andy Gill\\
+Dunfermline Club Championship
+\end{tabular}}}
+\end{center}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+1 & c4 & e5\\
+2 & Nc3 & Nf6\\
+3 & Nf3 & Nc6\\
+4 & g3 & d5\\
+5 & c*d5 & N*d5\\
+6 & Bg2 & Be6\\
+7 & 0-0 & Bb4\\
+8 & Ne4 & Qd7\\
+9 & d4 & e*d4\\
+10 & N*d4 & 0-0-0\\
+11 & N*e6 & Q*e6\\
+12 & Qc2 & h6\\
+13 & Rd1 & f5\\
+14 & Nc5 & B*c5\\
+15 & Q*c5 & Nde7\\
+16 & Be3 & R*d1+\\
+17 & R*d1 & Rd8\\
+18 & R*d8+ & K*d8\\
+19 & b3 & a6\\
+20 & Qc3 & Qe5\\
+21 & Q*e5 & N*e5\\
+22 & B*b7 & N7c6\\
+23 & Bf4 & Na5\\
+24 & B*e5 & N*b7\\
+25 & B*g7 & h5\\
+26 & Kg2 & Nd6\\
+27 & f3 & Ne8\\
+28 & Be5 & c6\\
+29 & Kh3 & Ke7\\
+30 & Kh4 & Nf6\\
+31 & B*f6+ & K*f6\\
+32 & K*h5 & c5\\
+33 & g4 & f4\\
+34 & g5+ & Kg7\\
+35 & Kg4&\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ * * * *}
+{* * * k }
+{p* * * *}
+{* p * P }
+{ * * pK*}
+{*P* *P* }
+{P* *P* P}
+{* * * * }
+$$\showboard$$
+$1\!-\!0$
+\clearpage
+\begin{center}
+\fbox{\fbox{\large\begin{tabular}{l}
+Game \hspace{.3 in} Mar 1994 \hspace{.3 in} $0\!-\!1$\\
+\hline
+Foo B70\\
+\raisebox{2.5pt}[11pt]{\framebox[11pt]{\rule{0pt}{4.25pt}}} Andy Gill\\
+\rule[-1pt]{11pt}{11pt} Paul Connally\\
+Dunfermline Club Championship
+\end{tabular}}}
+\end{center}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+1 & e4 & c5\\
+2 & Nf3 & d6\\
+3 & d4 & c*d4\\
+4 & N*d4 & g6\\
+5 & Nc3 & Nf6\\
+6 & Bd3 & Bg7\\
+7 & 0-0 & 0-0\\
+8 & f4 & Nc6\\
+9 & N*c6 & b*c6\\
+10 & Kh1 & Rb8\\
+11 & Qe1 & Ng4\\
+12 & h3 & Nf6\\
+13 & b3 & e5\\
+14 & f*e5 & Nh5\\
+15 & Bb2 & d*e5\\
+16 & Rf3 & a5\\
+17 & g4 & Nf4\\
+18 & Rd1 & Qg5\\
+19 & Bc1 & B*g4\\
+20 & B*f4 & B*f3+\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ r * rk*}
+{* * *pbp}
+{ *p* *p*}
+{p * p q }
+{ * *PB *}
+{*PNB*b*P}
+{P*P* * *}
+{* *RQ *K}
+$$\showboard$$
+$0\!-\!1$
+\clearpage
+\begin{center}
+\fbox{\fbox{\large\begin{tabular}{l}
+Game \hspace{.3 in} Mar 1994 \hspace{.3 in} ${1 \over 2}\!-\!{1 \over 2}$\\
+\hline
+\raisebox{2.5pt}[11pt]{\framebox[11pt]{\rule{0pt}{4.25pt}}} Tom Hunt\\
+\rule[-1pt]{11pt}{11pt} Andy Gill\\
+Glenrothes Congress
+\end{tabular}}}
+\end{center}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+1 & Nf3 & Nc6\\
+2 & g3 & e5\\
+3 & Nc3 & d5\\
+4 & d3 & Be6\\
+5 & Bg2 & Qd7\\
+6 & Ng5 & d4\\
+7 & Nce4 & Bf5\\
+8 & a3 & Be7\\
+9 & 0-0 & B*g5\\
+10 & N*g5 & f6\\
+11 & Ne4 & Bh3\\
+12 & Nc5 & Qc8\\
+13 & B*h3 & Q*h3\\
+14 & N*b7 & Rb8\\
+15 & Nc5 & h5\\
+16 & e4 & g5\\
+17 & Qf3 & g4\\
+18 & Qf5 & Kf7\\
+19 & Bg5 & Nce7\\
+20 & Qe6+ & Kg6\\
+21 & f4 & e*f4\\
+22 & R*f4 & K*g5\\
+23 & Raf1 & h4\\
+24 & Qf7 & h*g3\\
+25 & Ne6+ & Kh4\\
+26 & h*g3+ & Q*g3+\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ r * *nr}
+{p p nQ* }
+{ * *Np *}
+{* * * * }
+{ * pPRpk}
+{P *P* q }
+{ PP* * *}
+{* * *RK }
+$$\showboard$$
+${1 \over 2}\!-\!{1 \over 2}$
+\clearpage
+\begin{center}
+\fbox{\fbox{\large\begin{tabular}{l}
+Game \hspace{.3 in} Mar 1994 \hspace{.3 in} $1\!-\!0$\\
+\hline
+\raisebox{2.5pt}[11pt]{\framebox[11pt]{\rule{0pt}{4.25pt}}} Andy Gill\\
+\rule[-1pt]{11pt}{11pt} Dan Husband\\
+Glenrothes Congress
+\end{tabular}}}
+\end{center}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+1 & e4 & c5\\
+2 & Nf3 & Nc6\\
+3 & d4 & N*d4\\
+4 & N*d4 & c*d4\\
+5 & Q*d4 & e6\\
+6 & Nc3 & Qb6\\
+7 & Q*b6 & a*b6\\
+8 & Bb5 & Bc5\\
+9 & 0-0 & Nf6\\
+10 & Be3 & 0-0\\
+11 & Rfe1 & d6\\
+12 & a4 & Bd7\\
+13 & Bg5 & Bc6\\
+14 & B*f6 & g*f6\\
+15 & Rad1 & Kh8\\
+16 & Rd3 & Rad8\\
+17 & Rh3 & Rg8\\
+18 & Bd3 & Rg7\\
+19 & Nb5 & B*b5\\
+20 & a*b5 & Rdg8\\
+21 & Rg3 & R*g3\\
+22 & h*g3 & h6\\
+23 & Kf1 & Kg7\\
+24 & c3 & d5\\
+25 & e*d5 & e*d5\\
+26 & Ra1 & d4\\
+27 & Ra7 & d*c3\\
+28 & b*c3 & Rd8\\
+29 & Be4 & Rd1+\\
+30 & Ke2 & Rc1\\
+31 & R*b7 & R*c3\\
+32 & Kf1 & Rb3\\
+33 & R*f7+ & Kh8\\
+34 & R*f6 & R*b5\\
+35 & R*h6+ & Kg7\\
+36 & Rg6+ & Kh7\\
+37 & R*b6+&\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ * * * *}
+{* * * *k}
+{ R * * *}
+{*rb * * }
+{ * *B* *}
+{* * * P }
+{ * * PP*}
+{* * *K* }
+$$\showboard$$
+$1\!-\!0$
+\clearpage
+\begin{center}
+\fbox{\fbox{\large\begin{tabular}{l}
+Game \hspace{.3 in} Mar 1994 \hspace{.3 in} ${1 \over 2}\!-\!{1 \over 2}$\\
+\hline
+\raisebox{2.5pt}[11pt]{\framebox[11pt]{\rule{0pt}{4.25pt}}} Keith Chance\\
+\rule[-1pt]{11pt}{11pt} Andy Gill\\
+Glenrothes Congress
+\end{tabular}}}
+\end{center}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+1 & Nf3 & Nc6\\
+2 & e4 & e5\\
+3 & d4 & e*d4\\
+4 & N*d4 & d6\\
+5 & N*c6 & b*c6\\
+6 & Bd3 & Bb7\\
+7 & 0-0 & Nf6\\
+8 & Re1 & Be7\\
+9 & e5 & d*e5\\
+10 & R*e5 & 0-0\\
+11 & h3 & Re8\\
+12 & Re1 & Qd7\\
+13 & Bg5 & Rad8\\
+14 & B*f6 & B*f6\\
+15 & R*e8+ & Q*e8\\
+16 & Nc3 & Ba6\\
+17 & Qe1 & Q*e1+\\
+18 & R*e1 & B*d3\\
+19 & c*d3 & g6\\
+20 & Rd1 & Rb8\\
+21 & Ne4 & B*b2\\
+22 & Rb1 & a5\\
+23 & Nc3 & Rb4\\
+24 & Nd1 & Ba3\\
+25 & R*b4 & B*b4\\
+26 & Kf1 & f5\\
+27 & Nb2 & Kf7\\
+28 & Nc4 & Ke6\\
+29 & Ke2 & Kd5\\
+30 & a3 & Bc5\\
+31 & N*a5 & B*a3\\
+32 & Nc4 & Bc5\\
+33 & f3 & h5\\
+34 & g4 & h*g4\\
+35 & h*g4 & f*g4\\
+36 & f*g4 & Ke6\\
+37 & Kf3 & Bd6\\
+38 & Ke4 & g5\\
+39 & Na5 & c5\\
+40 & Nc4 & Bf4\\
+41 & Na5 & Bd2\\
+42 & Nc4 & Bb4\\
+43 & Ne5 & Bd2\\
+44 & Nf3 & Bc1\\
+45 & Ne5 & Bf4\\
+46 & Ng6 & Bg3\\
+47 & Nf8+ & Kd6\\
+48 & Nh7 & Bf4\\
+49 & Kf5 & Kd5\\
+50 & N*g5 & B*g5\\
+51 & K*g5 & Kd4\\
+52 & Kf5 & K*d3\\
+53 & g5 & c4\\
+54 & g6 & c3\\
+55 & g7 & c2\\
+56 & g8=Q & c1=Q\\
+57 & Qd5+ & Ke2\\
+58 & Qg2+ & Kd1\\
+59 & Qg1+&\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ * * * *}
+{* p * * }
+{ * * * *}
+{* * *K* }
+{ * * * *}
+{* * * * }
+{ * * * *}
+{* qk* Q }
+$$\showboard$$
+${1 \over 2}\!-\!{1 \over 2}$
+\clearpage
+\begin{center}
+\fbox{\fbox{\large\begin{tabular}{l}
+Game \hspace{.3 in} Mar 1994 \hspace{.3 in} ${1 \over 2}\!-\!{1 \over 2}$\\
+\hline
+\raisebox{2.5pt}[11pt]{\framebox[11pt]{\rule{0pt}{4.25pt}}} Andy Gill\\
+\rule[-1pt]{11pt}{11pt} Jim King\\
+Glenrothes Congress
+\end{tabular}}}
+\end{center}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+1 & e4 & c5\\
+2 & Nf3 & Nc6\\
+3 & d4 & c*d4\\
+4 & N*d4 & d6\\
+5 & Bb5 & Qc7\\
+6 & 0-0 & a6\\
+7 & Ba4 & b5\\
+8 & Bb3 & Nf6\\
+9 & Re1 & e6\\
+10 & Bg5 & Be7\\
+11 & c3 & 0-0\\
+12 & Nd2 & Bb7\\
+13 & Qe2 & Rfe8\\
+14 & Rac1 & d5\\
+15 & Bc2 & Rac8\\
+16 & e5 & Nd7\\
+17 & B*e7 & R*e7\\
+18 & N2f3 & h6\\
+19 & Qd3 & g6\\
+20 & Qe3 & Kg7\\
+21 & Nh4 & Nc*e5\\
+22 & b3 & Q*c3\\
+23 & Q*c3 & R*c3\\
+24 & Bb1 & b4\\
+25 & R*c3 & b*c3\\
+26 & Rc1 & g5\\
+27 & Nhf3 & N*f3+\\
+28 & N*f3 & g4\\
+29 & Nd4 & e5\\
+30 & Nf5+ & Kf6\\
+31 & N*e7 & K*e7\\
+32 & R*c3 & Kd6\\
+33 & h3 & Nf6\\
+34 & h*g4 & N*g4\\
+35 & Bf5 & Nf6\\
+36 & Bc8 & d4\\
+37 & Rc4 & Bd5\\
+38 & Rc2 & a5\\
+39 & f3 & Nh5\\
+40 & Ba6 & Nf4\\
+41 & Rd2 & f6\\
+42 & Bd3 & Bc6\\
+43 & Kf2 & h5\\
+44 & g3 & Ne6\\
+45 & a4 & Be8\\
+46 & Bb5 & Bg6\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ * * * *}
+{* * * * }
+{ * knpb*}
+{pB* p *p}
+{P* p * *}
+{*P* *PP }
+{ * R K *}
+{* * * * }
+$$\showboard$$
+${1 \over 2}\!-\!{1 \over 2}$
+\clearpage
+\begin{center}
+\fbox{\fbox{\large\begin{tabular}{l}
+Game \hspace{.3 in} Mar 1994 \hspace{.3 in} $1\!-\!0$\\
+\hline
+\raisebox{2.5pt}[11pt]{\framebox[11pt]{\rule{0pt}{4.25pt}}} R. Gourley\\
+\rule[-1pt]{11pt}{11pt} Andy Gill\\
+Glenrothes Congress
+\end{tabular}}}
+\end{center}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+1 & Nf3 & Nc6\\
+2 & d4 & e6\\
+3 & c4 & d5\\
+4 & Nc3 & Bb4\\
+5 & e3 & Nf6\\
+6 & Bd2 & 0-0\\
+7 & Ne5 & N*e5\\
+8 & d*e5 & Ne4\\
+9 & N*e4 & d*e4\\
+10 & B*b4 & c5\\
+11 & B*c5 & Qa5+\\
+12 & b4 & Rd8\\
+13 & b*a5 & R*d1+\\
+14 & R*d1 & h6\\
+15 & Rd8+ & Kh7\\
+16 & Be7 & b6\\
+17 & a*b6 & a*b6\\
+\end{tabular}}|
+\end{center}
+
+\board
+{r*bR * *}
+{* * Bppk}
+{ p *p* p}
+{* * P * }
+{ *P*p* *}
+{* * P * }
+{P* * PPP}
+{* * KB*R}
+$$\showboard$$
+$1\!-\!0$
+\clearpage
+\begin{center}
+\fbox{\fbox{\large\begin{tabular}{l}
+Game \hspace{.3 in} Mar 1994 \hspace{.3 in} $1\!-\!0$\\
+\hline
+\raisebox{2.5pt}[11pt]{\framebox[11pt]{\rule{0pt}{4.25pt}}} Andy Gill\\
+\rule[-1pt]{11pt}{11pt} Grant Glynis\\
+Dunfermline Club Championship
+\end{tabular}}}
+\end{center}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+1 & e4 & c5\\
+2 & Nf3 & d6\\
+3 & d4 & c*d4\\
+4 & N*d4 & Nf6\\
+5 & Nc3 & a6\\
+6 & Bc4 & Nc6\\
+7 & N*c6 & b*c6\\
+8 & Be3 & e6\\
+9 & 0-0 & Be7\\
+10 & Bb3 & 0-0\\
+11 & Qe2 & Bb7\\
+12 & Rad1 & Qc7\\
+13 & f4 & e5\\
+14 & Kh1 & Rfd8\\
+15 & Qf3 & Qc8\\
+16 & f*e5 & d*e5\\
+17 & Qg3 & R*d1\\
+18 & N*d1 & Qg4\\
+19 & Q*e5 & Q*e4\\
+20 & Q*e4 & N*e4\\
+21 & R*f7 & Nd6\\
+22 & R*e7+ & Kh8\\
+23 & Re5 & Rf8\\
+24 & Kg1 & h6\\
+25 & Bc5 & Rf6\\
+26 & c3 & a5\\
+27 & g3 & Ba6\\
+28 & Bc2 & g5\\
+29 & Bd4 & Kg8\\
+30 & R*a5 & Rf1+\\
+31 & Kg2 & Rf8\\
+32 & R*a6 & Nc4\\
+33 & R*c6 & Na5\\
+34 & R*h6 & Rf7\\
+35 & Rh8 mate&\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ * * *kR}
+{* * *r* }
+{ * * * *}
+{n * * p }
+{ * B * *}
+{* P * P }
+{PPB* *KP}
+{* *N* * }
+$$\showboard$$
+$1\!-\!0$
+\clearpage
+\begin{center}
+\fbox{\fbox{\large\begin{tabular}{l}
+Game \hspace{.3 in} Mar 1994 \hspace{.3 in} $0\!-\!1$\\
+\hline
+Foo B20\\
+\raisebox{2.5pt}[11pt]{\framebox[11pt]{\rule{0pt}{4.25pt}}} Alistair Welshman\\
+\rule[-1pt]{11pt}{11pt} Andy Gill\\
+Dunfermline Club Championship
+\end{tabular}}}
+\end{center}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+1 & e4 & c5\\
+2 & Bc4 & d6\\
+3 & Nc3 & Nf6\\
+4 & Nf3 & e6\\
+5 & 0-0 & Be7\\
+6 & d3 & 0-0\\
+7 & Bg5 & Nc6\\
+8 & B*f6 & B*f6\\
+9 & Bb5 & Bd7\\
+10 & B*c6 & B*c6\\
+11 & Qe2 & Re8\\
+12 & Rae1 & B*c3\\
+13 & b*c3 & Qa5\\
+14 & e5 & d5\\
+15 & d4 & Bb5\\
+16 & Qe3 & B*f1\\
+17 & R*f1 & c*d4\\
+18 & Q*d4 & Rac8\\
+19 & Qb4 & Q*b4\\
+20 & c*b4 & R*c2\\
+21 & Ra1 & Rec8\\
+22 & Kf1 & Rc1+\\
+23 & R*c1 & R*c1+\\
+24 & Ke2 & Rc2+\\
+25 & Nd2 & R*a2\\
+26 & g4 & Rb2\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ * * *k*}
+{pp* *ppp}
+{ * *p* *}
+{* *pP * }
+{ P * *P*}
+{* * * * }
+{ r NKP P}
+{* * * * }
+$$\showboard$$
+$0\!-\!1$
+\clearpage
+\begin{center}
+\fbox{\fbox{\large\begin{tabular}{l}
+Game \hspace{.3 in} Mar 1994 \hspace{.3 in} $1\!-\!0$\\
+\hline
+Foo C02\\
+\raisebox{2.5pt}[11pt]{\framebox[11pt]{\rule{0pt}{4.25pt}}} Robin Taylor (1610)\\
+\rule[-1pt]{11pt}{11pt} Andy Gill\\
+Dunfermline Club Championship
+\end{tabular}}}
+\end{center}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+1 & d4 & e6\\
+2 & e4 & d5\\
+3 & e5 & c5\\
+4 & c3 & Nc6\\
+5 & Nf3 & Bd7\\
+6 & Bf4 & c*d4\\
+7 & c*d4 & Bb4+\\
+8 & Bd2 & B*d2+\\
+9 & Q*d2 & Nge7\\
+10 & Nc3 & a6\\
+11 & a3 & Qc7\\
+12 & Bd3 & 0-0-0\\
+13 & 0-0 & Rdf8\\
+14 & b4 & f6\\
+15 & b5 & N*d4\\
+16 & N*d4 & Q*e5\\
+17 & b*a6 & Q*d4\\
+18 & a*b7+ & Kb8\\
+19 & Ne2 & Qa7\\
+20 & Qb4 & Nf5\\
+21 & B*f5 & e*f5\\
+22 & Qd6+ & K*b7\\
+23 & Rab1+ & Kc8\\
+24 & Rfc1+ & Kd8\\
+25 & Rb8+ & Q*b8\\
+26 & Q*b8+ & Ke7\\
+27 & Qb4+ & Kf7\\
+28 & f4 & Rc8\\
+29 & R*c8 & R*c8\\
+30 & Qd6 & Be6\\
+31 & Nd4 & Rc1+\\
+32 & Kf2 & Rd1\\
+33 & Q*e6+ & Kf8\\
+34 & N*f5 & Rd2+\\
+35 & Ke3&\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ * * k *}
+{* * * pp}
+{ * *Qp *}
+{* *p*N* }
+{ * * P *}
+{P * K * }
+{ * r *PP}
+{* * * * }
+$$\showboard$$
+$1\!-\!0$
+\clearpage
+\begin{center}
+\fbox{\fbox{\large\begin{tabular}{l}
+Game \hspace{.3 in} Mar 1994 \hspace{.3 in} $1\!-\!0$\\
+\hline
+Foo B92\\
+\raisebox{2.5pt}[11pt]{\framebox[11pt]{\rule{0pt}{4.25pt}}} Steve Smith (1745)\\
+\rule[-1pt]{11pt}{11pt} Andy Gill\\
+Dunfermline C vs Stirling A
+\end{tabular}}}
+\end{center}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+1 & e4 & c5\\
+2 & Nf3 & d6\\
+3 & d4 & c*d4\\
+4 & N*d4 & Nf6\\
+5 & Nc3 & a6\\
+6 & Be2 & e5\\
+7 & Nb3 & Be7\\
+8 & 0-0 & 0-0\\
+9 & a4 & Be6\\
+10 & f4 & B*b3\\
+11 & c*b3 & Nc6\\
+12 & Be3 & Qd7\\
+13 & Bc4 & Rad8\\
+14 & f5 & Kh8\\
+15 & Qf3 & Nb4\\
+16 & Rfd1 & Nc2\\
+17 & Rac1 & N*e3\\
+18 & Q*e3 & Qc6\\
+19 & Nd5 & N*d5\\
+20 & B*d5 & Qd7\\
+21 & Qb6 & Rb8\\
+22 & Rc7 & Bd8\\
+23 & R*d7 & B*b6+\\
+24 & Kf1 & f6\\
+25 & B*b7 & Bd4\\
+26 & Rc1 & B*b2\\
+27 & Rcc7 & Rg8\\
+28 & B*a6 & h5\\
+29 & Bc4 & Rgc8\\
+30 & R*g7 & R*c7\\
+31 & R*c7 & Bd4\\
+32 & Rf7 & Rg8\\
+33 & R*f6 & Rg4\\
+34 & Bd5 & Rf4+\\
+35 & Ke1 & Bc3+\\
+36 & Ke2 & Bd4\\
+37 & Rh6+ & Kg7\\
+38 & R*h5 & Rf2+\\
+39 & Kd3 & R*g2\\
+40 & Kc4 & Bg1\\
+41 & h4 & Rc2+\\
+42 & Kd3 & Rg2\\
+43 & Rg5+ & R*g5\\
+44 & h*g5 & Bb6\\
+45 & Kc4 & Bd8\\
+46 & f6+ & Kg6\\
+47 & f7 & Be7\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ * * * *}
+{* * bP* }
+{ * p *k*}
+{* *Bp P }
+{P*K*P* *}
+{*P* * * }
+{ * * * *}
+{* * * * }
+$$\showboard$$
+$1\!-\!0$
+\clearpage
+\begin{center}
+\fbox{\fbox{\large\begin{tabular}{l}
+Game \hspace{.3 in} Apr 1994 \hspace{.3 in} $0\!-\!1$\\
+\hline
+Foo C10\\
+\raisebox{2.5pt}[11pt]{\framebox[11pt]{\rule{0pt}{4.25pt}}} Andy Gill\\
+\rule[-1pt]{11pt}{11pt} Phillips Bill\\
+Dunfermline Club Championship
+\end{tabular}}}
+\end{center}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+1 & e4 & e6\\
+2 & d4 & d5\\
+3 & Nc3 & c5\\
+4 & e5 & Nc6\\
+5 & Nf3 & Qb6\\
+6 & Bb5 & Bd7\\
+7 & B*c6 & B*c6\\
+8 & 0-0 & Ne7\\
+9 & d*c5 & Q*c5\\
+10 & Be3 & Qa5\\
+11 & Qd3 & Nf5\\
+12 & Nd4 & N*e3\\
+13 & N*c6 & b*c6\\
+14 & Q*e3 & Bc5\\
+15 & Qd3 & 0-0\\
+16 & a3 & Qc7\\
+17 & b4 & Bb6\\
+18 & Rfe1 & a6\\
+19 & Na4 & Rfb8\\
+20 & N*b6 & R*b6\\
+21 & c4 & d*c4\\
+22 & Q*c4 & Rb5\\
+23 & Qe4 & Rd5\\
+24 & Rad1 & Rad8\\
+25 & R*d5 & c*d5\\
+26 & Qd4 & Rc8\\
+27 & f4 & g6\\
+28 & Re3 & h5\\
+29 & Kf2 & Qc2+\\
+30 & Kf3 & Rc4\\
+31 & Qd3 & Qc1\\
+32 & Qe2 & d4\\
+33 & Rd3 & Rc3\\
+34 & Ke4 & R*a3\\
+35 & R*a3 & Q*a3\\
+36 & Qc4 & Qe3 mate\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ * * *k*}
+{* * *p* }
+{p* *p*p*}
+{* * P *p}
+{ PQpKP *}
+{* * q * }
+{ * * *PP}
+{* * * * }
+$$\showboard$$
+$0\!-\!1$
+\clearpage
+\begin{center}
+\fbox{\fbox{\large\begin{tabular}{l}
+Game \hspace{.3 in} Apr 1994 \hspace{.3 in} $0\!-\!1$\\
+\hline
+Foo C97\\
+\raisebox{2.5pt}[11pt]{\framebox[11pt]{\rule{0pt}{4.25pt}}} Andy Gill\\
+\rule[-1pt]{11pt}{11pt} Andrew Watt\\
+Edinburgh Congress
+\end{tabular}}}
+\end{center}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+1 & e4 & e5\\
+2 & Nf3 & Nc6\\
+3 & Bb5 & a6\\
+4 & Ba4 & Nf6\\
+5 & 0-0 & Be7\\
+6 & Re1 & b5\\
+7 & Bb3 & d6\\
+8 & c3 & 0-0\\
+9 & h3 & Na5\\
+10 & Bc2 & c5\\
+11 & d4 & Qc7\\
+12 & b4 & c*b4\\
+13 & c*b4 & Nc4\\
+14 & Nbd2 & Bb7\\
+15 & N*c4 & Q*c4\\
+16 & d*e5 & d*e5\\
+17 & a3 & Rac8\\
+18 & Bd3 & Qc3\\
+19 & Bg5 & Rfd8\\
+20 & Re3 & B*e4\\
+21 & Rc1 & Q*c1\\
+22 & Q*c1 & R*c1+\\
+23 & Re1 & R*e1+\\
+24 & N*e1 & B*d3\\
+25 & Nf3 & Be4\\
+26 & N*e5 & Rd1+\\
+27 & Kh2 & Bd6\\
+28 & f4 & h6\\
+29 & Bh4 & g5\\
+30 & Bg3 & B*e5\\
+31 & f*e5 & Nh5\\
+32 & e6 & N*g3\\
+33 & e7 & Nf1+\\
+34 & Kg1 & Bc6\\
+35 & Kf2 & f6\\
+36 & Ke2 & Ra1\\
+37 & Kd3 & Kf7\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ * * * *}
+{* * Pk* }
+{p*b* p p}
+{*p* * p }
+{ P * * *}
+{P *K* *P}
+{ * * *P*}
+{r * *n* }
+$$\showboard$$
+$0\!-\!1$
+\clearpage
+\begin{center}
+\fbox{\fbox{\large\begin{tabular}{l}
+Game \hspace{.3 in} Apr 1994 \hspace{.3 in} $0\!-\!1$\\
+\hline
+Foo B50\\
+\raisebox{2.5pt}[11pt]{\framebox[11pt]{\rule{0pt}{4.25pt}}} Jake Milne\\
+\rule[-1pt]{11pt}{11pt} Andy Gill\\
+Edinburgh Congress
+\end{tabular}}}
+\end{center}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+1 & e4 & c5\\
+2 & Nf3 & d6\\
+3 & Bc4 & e6\\
+4 & d3 & Nf6\\
+5 & a3 & Nc6\\
+6 & Nc3 & Be7\\
+7 & 0-0 & 0-0\\
+8 & Be3 & b6\\
+9 & h3 & Bb7\\
+10 & Ne2 & d5\\
+11 & e*d5 & e*d5\\
+12 & Ba2 & Re8\\
+13 & c3 & Qc7\\
+14 & Bf4 & Bd6\\
+15 & B*d6 & Q*d6\\
+16 & d4 & c*d4\\
+17 & Ne*d4 & N*d4\\
+18 & N*d4 & Rad8\\
+19 & Qd2 & Ba6\\
+20 & Qg5 & Re5\\
+21 & Nf5 & R*f5\\
+22 & Q*f5 & B*f1\\
+23 & R*f1 & g6\\
+24 & Qf3 & Kg7\\
+25 & Rd1 & Qe5\\
+26 & g3 & a5\\
+27 & Kg2 & h5\\
+28 & h4 & Rd6\\
+29 & Bb1 & d4\\
+30 & Qd3 & Qd5+\\
+31 & Qf3 & Qb3\\
+32 & Qe2 & Qd5+\\
+33 & f3 & Qe6\\
+34 & Q*e6 & R*e6\\
+35 & Be4 & d*c3\\
+36 & b*c3 & N*e4\\
+37 & f*e4 & R*e4\\
+38 & Rd6 & Re2+\\
+39 & Kf3 & Rb2\\
+40 & Rd3 & a4\\
+41 & Ke4 & f5+\\
+42 & Kd5 & Re2\\
+43 & c4 & Re8\\
+44 & Kc6 & Rc8+\\
+45 & K*b6 & R*c4\\
+46 & Kb5 & Rg4\\
+47 & Rd7+ & Kf6\\
+48 & Ra7 & f4\\
+49 & g*f4 & R*f4\\
+50 & R*a4 & R*a4\\
+51 & K*a4 & g5\\
+52 & h*g5+ & K*g5\\
+53 & Kb5 & h4\\
+54 & a4 & h3\\
+55 & a5 & h2\\
+56 & a6 & h1=Q\\
+57 & Kb6 & Qb1+\\
+58 & Ka7 & Kf5\\
+59 & Ka8 & Qe4+\\
+60 & Kb8 & Qe8+\\
+61 & Kb7 & Qd7+\\
+62 & Kb6 & Qd8+\\
+63 & Kb7 & Qd5+\\
+64 & Kb6 & Qa8\\
+65 & Ka5 & Ke5\\
+66 & Kb6 & Kd5\\
+67 & Ka5 & Kc5\\
+68 & Ka4 & Q*a6+\\
+69 & Kb3 & Qc4+\\
+70 & Ka3 & Qb5\\
+71 & Ka2 & Kc4\\
+72 & Ka1 & Kc3\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ * * * *}
+{* * * * }
+{ * * * *}
+{*q* * * }
+{ * * * *}
+{* k * * }
+{ * * * *}
+{K * * * }
+$$\showboard$$
+$0\!-\!1$
+\clearpage
+\begin{center}
+\fbox{\fbox{\large\begin{tabular}{l}
+Game \hspace{.3 in} Apr 1994 \hspace{.3 in} $0\!-\!1$\\
+\hline
+Foo C54\\
+\raisebox{2.5pt}[11pt]{\framebox[11pt]{\rule{0pt}{4.25pt}}} Andy Gill\\
+\rule[-1pt]{11pt}{11pt} John Bourke\\
+Edinburgh Congress
+\end{tabular}}}
+\end{center}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+1 & e4 & e5\\
+2 & Nf3 & Nc6\\
+3 & Bc4 & Bc5\\
+4 & c3 & Nf6\\
+5 & d4 & e*d4\\
+6 & c*d4 & Bb4+\\
+7 & Bd2 & N*e4\\
+8 & B*b4 & N*b4\\
+9 & B*f7+ & K*f7\\
+10 & Qb3+ & d5\\
+11 & Q*b4 & Re8\\
+12 & 0-0 & Kg8\\
+13 & Nc3 & b6\\
+14 & Rfe1 & Bf5\\
+15 & Qb3 & c6\\
+16 & Rac1 & Qd6\\
+17 & Re3 & N*c3\\
+18 & Q*c3 & R*e3\\
+19 & Q*e3 & Rc8\\
+20 & Re1 & h6\\
+21 & Qe7 & Q*e7\\
+22 & R*e7 & a5\\
+23 & Rb7 & b5\\
+24 & Ne5 & c5\\
+25 & R*b5 & c*d4\\
+26 & f4 & Be4\\
+27 & R*a5 & Rc1+\\
+28 & Kf2 & Rc2+\\
+29 & Kg3 & R*g2+\\
+30 & Kh3 & R*b2\\
+31 & Ra3 & Rd2\\
+32 & Kg3 & Rg2+\\
+33 & Kh3 & Rd2\\
+34 & Kg3 & d3\\
+35 & Nf3 & Rb2\\
+36 & h4 & d2\\
+37 & N*d2 & R*d2\\
+38 & Kg4 & Rd3\\
+39 & R*d3 & B*d3\\
+40 & Kf3 & Bc4\\
+41 & a4 & Kf7\\
+42 & Ke3 & Ke6\\
+43 & Kd4 & Kf5\\
+44 & a5 & K*f4\\
+45 & a6 & B*a6\\
+46 & K*d5 & Kg4\\
+47 & Ke6 & K*h4\\
+48 & Kf7 & g5\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ * * * *}
+{* * *K* }
+{b* * * p}
+{* * * p }
+{ * * * k}
+{* * * * }
+{ * * * *}
+{* * * * }
+$$\showboard$$
+$0\!-\!1$
+\clearpage
+\begin{center}
+\fbox{\fbox{\large\begin{tabular}{l}
+Game \hspace{.3 in} Apr 1994 \hspace{.3 in} $1\!-\!0$\\
+\hline
+Foo C70\\
+\raisebox{2.5pt}[11pt]{\framebox[11pt]{\rule{0pt}{4.25pt}}} Andy Gill\\
+\rule[-1pt]{11pt}{11pt} David King\\
+Edinburgh Congress
+\end{tabular}}}
+\end{center}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+1 & e4 & e5\\
+2 & Nf3 & Nc6\\
+3 & Bb5 & a6\\
+4 & Ba4 & b5\\
+5 & Bb3 & Bc5\\
+6 & 0-0 & Nge7\\
+7 & c3 & d6\\
+8 & d4 & e*d4\\
+9 & c*d4 & Ba7\\
+10 & Be3 & Na5\\
+11 & Bc2 & 0-0\\
+12 & Nbd2 & f5\\
+13 & Bg5 & Qe8\\
+14 & Re1 & h6\\
+15 & B*e7 & Q*e7\\
+16 & e*f5 & Qf6\\
+17 & Be4 & Bb7\\
+18 & B*b7 & N*b7\\
+19 & Qb3+ & Kh8\\
+20 & Qd5 & Rab8\\
+21 & Rac1 & Bb6\\
+22 & g4 & Nd8\\
+23 & Ne4 & Qf7\\
+24 & Q*f7 & R*f7\\
+25 & h3&\\
+\end{tabular}}|
+\end{center}
+At this point the score sheet goes wrong. Black eventually looses on
+time!
+
+\board
+{ r n * k}
+{* p *rp }
+{pb p * p}
+{*p* *P* }
+{ * PN*P*}
+{* * *N*P}
+{PP * P *}
+{* R R K }
+$$\showboard$$
+$1\!-\!0$
+\clearpage
+\begin{center}
+\fbox{\fbox{\large\begin{tabular}{l}
+Game \hspace{.3 in} Apr 1994 \hspace{.3 in} $1\!-\!0$\\
+\hline
+Foo D20\\
+\raisebox{2.5pt}[11pt]{\framebox[11pt]{\rule{0pt}{4.25pt}}} C. Tait\\
+\rule[-1pt]{11pt}{11pt} Andy Gill\\
+Edinburgh Congress
+\end{tabular}}}
+\end{center}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+1 & d4 & d5\\
+2 & c4 & d*c4\\
+3 & e4 & c6\\
+4 & B*c4 & e6\\
+\end{tabular}}|
+\end{center}
+|4\ldots~Nf6; 5.~Nc3, e5; 6.~Be3, e*d4; 7.~B*d4, Bd6; 8.~f3|
+Score: 0.22
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+5 & Nf3 & Bb4+\\
+\end{tabular}}|
+\end{center}
+|5\ldots~Nf6; 6.~Qe2, Bb4; 7.~Bd2, Qb6; 8.~Nc3, 0-0; 9.~0-0, Nbd7|
+Score: 0.25
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+6 & Bd2 & B*d2+\\
+7 & Q*d2&\\
+\end{tabular}}|
+\end{center}
+|7.~Nb*d2, Nf6; 8.~0-0, 0-0; 9.~Rc1, Nbd7; 10.~Qe2, c5; 11.~Bd3|
+Score: 0.41
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+7 & \ldots & Nf6\\
+8 & Nc3 & 0-0\\
+\end{tabular}}|
+\end{center}
+|8\ldots~Nbd7; 9.~0-0, 0-0; 10.~Rad1, Qe7; 11.~Rfe1, e5|
+Score: 0.38
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+9 & 0-0 & b6\\
+10 & e5&\\
+\end{tabular}}|
+\end{center}
+|10.~Rac1, Bb7; 11.~Rfd1, c5; 12.~d*c5, Q*d2; 13.~R*d2, b*c5|
+Score: 0.28
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+10 & \ldots & Nfd7\\
+\end{tabular}}|
+\end{center}
+|10\ldots~Nd5; 11.~Rfd1, Ba6; 12.~B*a6, N*a6; 13.~Rac1, Nac7; 14.~N*d5, c*d5|
+Score: 0.28
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+11 & Rfd1 & Ba6\\
+\end{tabular}}|
+\end{center}
+|11\ldots~Bb7; 12.~Ne4, c5; 13.~d5, b5; 14.~B*b5, B*d5; 15.~Qe3, Qe7|
+Score: 0.34
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+12 & Bb3&\\
+\end{tabular}}|
+\end{center}
+|12.~B*a6, N*a6; 13.~Rac1, Qe7; 14.~Ne4, c5; 15.~Qe2, Nb4; 16.~d*c5|
+Score: 0.34
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+12 & \ldots & Re8\\
+\end{tabular}}|
+\end{center}
+|12\ldots~h6; 13.~Rac1, Qe7; 14.~Ne4, Rd8; 15.~Nd6, Nf6; 16.~Qe3|
+Score: 0.31
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+13 & Ne4 & c5\\
+\end{tabular}}|
+\end{center}
+|13\ldots~h6; 14.~Nd6, Re7; 15.~Rac1, c5; 16.~Bc2, Nc6; 17.~Be4, Qc7|
+Score: 0.44
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+14 & Nd6&\\
+\end{tabular}}|
+\end{center}
+|14.~d*c5, Bb7; 15.~Qe3, Re7; 16.~Nd6, Bc6; 17.~Ne4, b*c5; 18.~N*c5|
+Score: 1.25
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+14 & \ldots & Rf8\\
+\end{tabular}}|
+\end{center}
+|14\ldots~Re7; 15.~N*f7, R*f7; 16.~B*e6, c*d4; 17.~Bd5, Nc6; 18.~B*c6|
+Score: 0.44
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+15 & d5 & b5\\
+\end{tabular}}|
+\end{center}
+|15\ldots~Qe7; 16.~N*f7, c4; 17.~d*e6, N*e5; 18.~N3*e5, c*b3; 19.~Qd5|
+Score: 1.06
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+16 & d*e6 & f*e6\\
+\end{tabular}}|
+\end{center}
+|16\ldots~c4; 17.~N*f7, Qb6; 18.~e*d7, N*d7; 19.~Q*d7, R*f7; 20.~Qd5|
+Score: 3.75
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+17 & B*e6+ & Kh8\\
+18 & Nf7+&\\
+\end{tabular}}|
+\end{center}
+|18.~Qd5, Qe7; 19.~Nf7, R*f7; 20.~B*f7, h6|
+Score: 4.56
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+18 & \ldots & R*f7\\
+19 & B*f7 & Nc6\\
+\end{tabular}}|
+\end{center}
+|19\ldots~Bb7; 20.~Ng5, h6; 21.~Bd5|
+Score: 3.03
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+20 & e6&\\
+\end{tabular}}|
+\end{center}
+|20.~Q*d7, Nd4; 21.~Qg4, Qe7; 22.~N*d4, Q*f7; 23.~e6, Qf6|
+Score: 5.84
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+20 & \ldots & Qe7\\
+\end{tabular}}|
+\end{center}
+|20\ldots~Nf6; 21.~Rac1, c4; 22.~b3, Q*d2; 23.~R*d2, Rd8; 24.~R*d8, N*d8|
+Score: 3.06
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+21 & Q*d7 & Bc8\\
+\end{tabular}}|
+\end{center}
+|21\ldots~Bb7; 22.~Q*e7, N*e7; 23.~Rd7, B*f3; 24.~g*f3, Nc6; 25.~e7, N*e7|
+Score: 7.41
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+22 & Q*c6&\\
+\end{tabular}}|
+\end{center}
+|22.~Q*e7, B*e6; 23.~Q*e6, Nd4; 24.~N*d4, c*d4; 25.~R*d4, a6|
+Score: 17.72
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+22 & \ldots & Rb8\\
+\end{tabular}}|
+\end{center}
+|22\ldots~Bb7; 23.~Qd7, Q*d7; 24.~e*d7, Rd8; 25.~Re1, g6; 26.~Re8, Kg7|
+Score: 10.66
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+23 & Qe8+&\\
+\end{tabular}}|
+\end{center}
+|23.~Q*c5, B*e6; 24.~Q*e7, B*f7; 25.~Q*a7, Rf8; 26.~Q*f7, Rc8|
+Score: 18.22
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+23 & \ldots & Q*e8\\
+24 & B*e8 & Bb7\\
+\end{tabular}}|
+\end{center}
+|24\ldots~B*e6; 25.~Bd7, Bg8; 26.~Ne5, g6; 27.~Rac1, c4; 28.~a4, b*a4|
+Score: 7.88
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+25 & Bf7&\\
+\end{tabular}}|
+\end{center}
+|25.~B*b5, B*f3; 26.~g*f3, Kg8; 27.~e7, Kf7; 28.~Rd8, K*e7; 29.~R*b8|
+Score: 12.03
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+25 & \ldots & Bc6\\
+\end{tabular}}|
+\end{center}
+|25\ldots~g5; 26.~e7, Kg7; 27.~Rd8, Bc6; 28.~R*b8, K*f7; 29.~Ne5, K*e7|
+Score: 12.03
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+26 & Rd2&\\
+\end{tabular}}|
+\end{center}
+|26.~Ne5, B*g2; 27.~e7, g6; 28.~K*g2|
+Score: 15.75
+
+\board
+{ r * * k}
+{p * *Bpp}
+{ *b*P* *}
+{*pp * * }
+{ * * * *}
+{* * *N* }
+{PP R PPP}
+{R * * K }
+$$\showboard$$
+$1\!-\!0$
+\clearpage
+\begin{center}
+\fbox{\fbox{\large\begin{tabular}{l}
+Game \hspace{.3 in} Apr 1994 \hspace{.3 in} $1\!-\!0$\\
+\hline
+Foo B50\\
+\raisebox{2.5pt}[11pt]{\framebox[11pt]{\rule{0pt}{4.25pt}}} J. Comrie\\
+\rule[-1pt]{11pt}{11pt} Andy Gill\\
+Dunfermline C vs Alloa
+\end{tabular}}}
+\end{center}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+1 & e4 & c5\\
+2 & Nf3 & d6\\
+3 & Bc4 & e6\\
+4 & Nc3 & Be7\\
+5 & d4 & c*d4\\
+6 & Q*d4 & Nf6\\
+7 & e5 & d*e5\\
+8 & Q*d8+ & B*d8\\
+9 & N*e5 & 0-0\\
+10 & 0-0 & Nbd7\\
+11 & N*d7 & B*d7\\
+12 & Be3 & a6\\
+13 & a4 & Ba5\\
+14 & Ne2 & Bc6\\
+15 & Nd4 & Nd5\\
+16 & N*c6 & b*c6\\
+17 & B*d5 & c*d5\\
+18 & c3 & Rab8\\
+19 & b4 & Bc7\\
+20 & Rfd1 & Rfd8\\
+21 & Rac1 & Bb6\\
+22 & Kf1 & B*e3\\
+23 & f*e3 & f5\\
+24 & Rc2 & g5\\
+25 & Kf2 & Kf7\\
+26 & Kf3 & Rdc8\\
+27 & g4 & R*b4\\
+28 & g*f5 & Kf6\\
+29 & f*e6 & K*e6\\
+30 & Rd4 & R*d4\\
+31 & e*d4 & Rf8+\\
+32 & Kg4 & h6\\
+33 & Re2+ & Kd6\\
+34 & Rb2 & Rc8\\
+35 & Kh5 & R*c3\\
+36 & Rb6+ & Rc6\\
+37 & R*c6+ & K*c6\\
+38 & K*h6 & g4\\
+39 & Kg5 & Kd6\\
+40 & K*g4 & Ke6\\
+41 & Kg5 & Ke7\\
+42 & h4 & Kf7\\
+43 & h5 & Kg7\\
+44 & Kf5&\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ * * * *}
+{* * * k }
+{p* * * *}
+{* *p*K*P}
+{P* P * *}
+{* * * * }
+{ * * * *}
+{* * * * }
+$$\showboard$$
+$1\!-\!0$
+\clearpage
+\begin{center}
+\fbox{\fbox{\large\begin{tabular}{l}
+Game \hspace{.3 in} Apr 1994 \hspace{.3 in} $1\!-\!0$\\
+\hline
+Foo C65\\
+\raisebox{2.5pt}[11pt]{\framebox[11pt]{\rule{0pt}{4.25pt}}} Andy Gill\\
+\rule[-1pt]{11pt}{11pt} Scott Hunter\\
+Dunfermline Club Championship
+\end{tabular}}}
+\end{center}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+1 & e4 & e5\\
+2 & Nf3 & Nc6\\
+3 & Bb5 & Nf6\\
+4 & d3 & Bc5\\
+5 & 0-0 & 0-0\\
+6 & Re1 & d5\\
+7 & Be3 & B*e3\\
+8 & e*d5 & Q*d5\\
+9 & B*c6 & Q*c6\\
+10 & R*e3 & e4\\
+11 & d*e4 & N*e4\\
+12 & Nc3 & N*c3\\
+13 & R*c3 & Qd6\\
+14 & Q*d6 & c*d6\\
+15 & Rd1 & Re8\\
+16 & R*d6 & g5\\
+17 & g4 & B*g4\\
+18 & N*g5 & Re1+\\
+19 & Kg2 & Rae8\\
+20 & Rg3 & f5\\
+21 & h3 & Be2\\
+22 & Nf3+ & Kf7\\
+23 & N*e1 & f4\\
+24 & Rf3 & B*f3+\\
+25 & N*f3 & Re2\\
+26 & Rd7+ & Kf8\\
+27 & R*b7 & R*c2\\
+28 & R*a7 & R*b2\\
+29 & Ra4 & Kf7\\
+30 & R*f4+ & Kg6\\
+31 & a4 & h5\\
+32 & h4 & Ra2\\
+33 & Kg3 & Ra3\\
+34 & Rc4 & Rd3\\
+35 & Kf4 & Rd5\\
+36 & Ne5+ & Kf6\\
+37 & Re4 & Ra5\\
+38 & Nd7+ & Kg6\\
+39 & f3 & Rf5+\\
+40 & Ke3&\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ * * * *}
+{* *N* * }
+{ * * *k*}
+{* * *r*p}
+{P* *R* P}
+{* * KP* }
+{ * * * *}
+{* * * * }
+$$\showboard$$
+$1\!-\!0$
+\clearpage
+\begin{center}
+\fbox{\fbox{\large\begin{tabular}{l}
+Game \hspace{.3 in} May 1994 \hspace{.3 in} $1\!-\!0$\\
+\hline
+Foo B20\\
+\raisebox{2.5pt}[11pt]{\framebox[11pt]{\rule{0pt}{4.25pt}}} James Hepburn\\
+\rule[-1pt]{11pt}{11pt} Andy Gill\\
+Under 1500 Final
+\end{tabular}}}
+\end{center}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+1 & e4 & c5\\
+2 & Bc4 & d6\\
+3 & d3 & e6\\
+4 & Nc3 & Nf6\\
+5 & Nf3 & a6\\
+6 & Bd2 & Nc6\\
+7 & 0-0 & Be7\\
+8 & Re1 & 0-0\\
+9 & a3 & e5\\
+10 & h3 & b5\\
+11 & Bb3 & Bb7\\
+12 & Nd5 & N*d5\\
+13 & B*d5 & Qd7\\
+14 & c3 & Na5\\
+15 & b4 & B*d5\\
+16 & e*d5 & Nb7\\
+17 & Re4 & f5\\
+18 & Re2 & c*b4\\
+19 & a*b4 & Bf6\\
+20 & Qb3 & a5\\
+21 & Rae1 & a*b4\\
+22 & c*b4 & Rfe8\\
+23 & Bg5 & B*g5\\
+24 & N*g5 & Nd8\\
+25 & f4 & Nf7\\
+26 & N*f7 & Q*f7\\
+27 & f*e5 & d*e5\\
+28 & R*e5 & R*e5\\
+29 & R*e5 & Ra1+\\
+30 & Kh2 & g5\\
+31 & d4 & Kg7\\
+32 & Qd3 & Qd7\\
+33 & R*f5 & Qd6+\\
+34 & Re5 & Q*b4\\
+35 & R*g5+ & Kf7\\
+36 & Q*h7+ & Kf6\\
+37 & Qh6+ & Ke7\\
+38 & Rg7+ & Kd8\\
+39 & Qh8+&\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ * k * Q}
+{* * * R }
+{ * * * *}
+{*p*P* * }
+{ q P * *}
+{* * * *P}
+{ * * *PK}
+{r * * * }
+$$\showboard$$
+$1\!-\!0$
+\clearpage
+\begin{center}
+\fbox{\fbox{\large\begin{tabular}{l}
+Game \hspace{.3 in} May 1994 \hspace{.3 in} $1\!-\!0$\\
+\hline
+Foo D02\\
+\raisebox{2.5pt}[11pt]{\framebox[11pt]{\rule{0pt}{4.25pt}}} D. Heron (1790)\\
+\rule[-1pt]{11pt}{11pt} Andy Gill\\
+East of Scotland Championship
+\end{tabular}}}
+\end{center}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+1 & Nf3 & Nc6\\
+2 & d4 & d5\\
+3 & Bf4 & Bf5\\
+4 & e3 & a6\\
+5 & c4 & e6\\
+6 & Nc3 & Nf6\\
+7 & a3 & Qd7\\
+8 & b4 & Bd6\\
+9 & B*d6 & Q*d6\\
+10 & Be2 & 0-0\\
+11 & 0-0 & Ne4\\
+12 & N*e4 & B*e4\\
+13 & Nd2 & Bg6\\
+14 & Qb3 & Ne7\\
+15 & c5 & Qd7\\
+16 & a4 & c6\\
+17 & b5 & Nf5\\
+18 & Ra3 & Rfe8\\
+19 & Qb2 & Kh8\\
+20 & Rb3 & Nh6\\
+21 & b*c6 & b*c6\\
+22 & Rb7 & Qc8\\
+23 & Nf3 & Rb8\\
+24 & B*a6 & R*b7\\
+25 & Q*b7 & Q*b7\\
+26 & B*b7 & f6\\
+27 & B*c6 & Rb8\\
+28 & Bb5 & Bc2\\
+29 & Rc1 & Be4\\
+30 & Nd2 & Bg6\\
+31 & Nb1 & Ng8\\
+32 & Nc3 & Ne7\\
+33 & a5 & Nc8\\
+34 & Bd7 & Bf5\\
+35 & N*d5 & e*d5\\
+36 & B*f5 & Ne7\\
+37 & Bd3 & Nc6\\
+38 & Rb1 & R*b1+\\
+39 & B*b1 & N*a5\\
+40 & Ba2&\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ * * * k}
+{* * * pp}
+{ * * p *}
+{n Pp* * }
+{ * P * *}
+{* * P * }
+{B* * PPP}
+{* * * K }
+$$\showboard$$
+$1\!-\!0$
+\clearpage
+\begin{center}
+\fbox{\fbox{\large\begin{tabular}{l}
+Game \hspace{.3 in} May 1994 \hspace{.3 in} ${1 \over 2}\!-\!{1 \over 2}$\\
+\hline
+Foo A15\\
+\raisebox{2.5pt}[11pt]{\framebox[11pt]{\rule{0pt}{4.25pt}}} Andy Gill\\
+\rule[-1pt]{11pt}{11pt} W. Falconer\\
+East of Scotland Chalengers
+\end{tabular}}}
+\end{center}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+1 & c4 & Nf6\\
+2 & d3 & e6\\
+3 & Nf3 & d5\\
+4 & c*d5 & N*d5\\
+5 & a3 & Bd6\\
+6 & e3 & Nc6\\
+7 & Nbd2 & 0-0\\
+8 & Nc4 & Bd7\\
+9 & Be2 & b5\\
+10 & N*d6 & c*d6\\
+11 & 0-0 & Rc8\\
+12 & Bd2 & Qb6\\
+13 & Qb3 & Ne5\\
+14 & Rac1 & a6\\
+15 & Rc2 & R*c2\\
+16 & Q*c2 & Rc8\\
+17 & Qb1 & N*f3+\\
+18 & B*f3 & Bc6\\
+19 & Rc1 & Qd8\\
+20 & B*d5 & B*d5\\
+21 & Ba5 & Qd7\\
+22 & R*c8+ & Q*c8\\
+23 & Bb4 & Qc6\\
+24 & f3 & Bb3\\
+25 & Qe1 & Qc2\\
+26 & Qc3 & Q*c3\\
+27 & B*c3 & d5\\
+28 & Kf2 & f6\\
+29 & d4&\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ * * *k*}
+{* * * pp}
+{p* *pp *}
+{*p*p* * }
+{ * P * *}
+{PbB PP* }
+{ P * KPP}
+{* * * * }
+$$\showboard$$
+${1 \over 2}\!-\!{1 \over 2}$
+\clearpage
+\begin{center}
+\fbox{\fbox{\large\begin{tabular}{l}
+Game \hspace{.3 in} May 1994 \hspace{.3 in} $0\!-\!1$\\
+\hline
+Foo A20\\
+\raisebox{2.5pt}[11pt]{\framebox[11pt]{\rule{0pt}{4.25pt}}} Andy Gill\\
+\rule[-1pt]{11pt}{11pt} Walter Pearson (1650)\\
+East of Scotland Chalengers
+\end{tabular}}}
+\end{center}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+1 & c4 & e5\\
+2 & d3 & Ne7\\
+3 & Nf3 & d6\\
+4 & e3 & g6\\
+5 & Be2 & Bg7\\
+6 & 0-0 & 0-0\\
+7 & Nbd2 & Nd7\\
+8 & Nb3 & b6\\
+9 & d4 & e*d4\\
+10 & Nf*d4 & Bb7\\
+\end{tabular}}|
+\end{center}
+
+\board
+{r* q rk*}
+{pbpnnpbp}
+{ p p *p*}
+{* * * * }
+{ *PN * *}
+{*N* P * }
+{PP *BPPP}
+{R BQ*RK }
+$$\showboard$$
+$0\!-\!1$
+\clearpage
+\begin{center}
+\fbox{\fbox{\large\begin{tabular}{l}
+Game \hspace{.3 in} May 1994 \hspace{.3 in} $1\!-\!0$\\
+\hline
+Foo D61\\
+\raisebox{2.5pt}[11pt]{\framebox[11pt]{\rule{0pt}{4.25pt}}} Douglas Heatlie (1650)\\
+\rule[-1pt]{11pt}{11pt} Andy Gill\\
+East of Scotland Chalengers
+\end{tabular}}}
+\end{center}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+1 & d4 & e6\\
+2 & c4 & d5\\
+3 & Nc3 & Nf6\\
+4 & Bg5 & Be7\\
+5 & e3 & Nbd7\\
+6 & Qc2 & 0-0\\
+7 & Nf3 & Re8\\
+8 & h4 & Nb6\\
+9 & b3 & d*c4\\
+10 & b*c4 & Bd7\\
+11 & Bd3 & g6\\
+12 & B*f6 & B*f6\\
+13 & h5 & B*d4\\
+14 & e*d4 & Qf6\\
+15 & h*g6 & f*g6\\
+16 & Ne4 & Qg7\\
+17 & Nc5 & Bc6\\
+18 & Ne5 & Nd5\\
+19 & c*d5 & e*d5\\
+20 & 0-0-0 & R*e5\\
+21 & d*e5 & Q*e5\\
+22 & g3 & Qg5+\\
+23 & Qd2 & Qe5\\
+24 & Nb3 & Ba4\\
+25 & Qh6 & Qc3+\\
+26 & Bc2 & B*b3\\
+27 & Q*h7+ & Kf8\\
+28 & Qh8+&\\
+\end{tabular}}|
+\end{center}
+
+\board
+{r* * k Q}
+{ppp * * }
+{ * * *p*}
+{* *p* * }
+{ * * * *}
+{*bq * P }
+{P*B* P *}
+{* KR* *R}
+$$\showboard$$
+$1\!-\!0$
+\clearpage
+\begin{center}
+\fbox{\fbox{\large\begin{tabular}{l}
+Game \hspace{.3 in} Jul 1994 \hspace{.3 in} $1\!-\!0$\\
+\hline
+Foo B50\\
+\raisebox{2.5pt}[11pt]{\framebox[11pt]{\rule{0pt}{4.25pt}}} Graham Mill\\
+\rule[-1pt]{11pt}{11pt} Andy Gill\\
+Scottish Chess Minor
+\end{tabular}}}
+\end{center}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+1 & e4 & c5\\
+2 & Nf3 & d6\\
+3 & Bc4&\\
+\end{tabular}}|
+\end{center}
+This is an unusual way of opening, but is common at the Minor level.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+3 & \ldots & e6\\
+4 & Nc3 & Nf6\\
+5 & d3&\\
+\end{tabular}}|
+\end{center}
+|5.~0-0|
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+5 & \ldots & Nc6\\
+\end{tabular}}|
+\end{center}
+|5\ldots~d5; 6.~Bb3, d*e4; 7.~N*e4, N*e4; 8.~d*e4, Q*d1+; 9.~K*d1|
+=
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+6 & Bf4&\\
+\end{tabular}}|
+\end{center}
+|6.~0-0, Be7|
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+6 & \ldots & a6\\
+7 & 0-0 & Be7\\
+\end{tabular}}|
+\end{center}
+|7\ldots~Na5; 8.~Bb3, N*b3; 9.~a*b3, Be7; 10.~Re1, 0-0; 11.~Qd2|
+\bbetter{}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+8 & Re1 & 0-0\\
+\end{tabular}}|
+\end{center}
+
+\board
+{r*bq rk*}
+{*p* bppp}
+{p*nppn *}
+{* p * * }
+{ *B*PB *}
+{* NP*N* }
+{PPP* PPP}
+{R *QR K }
+$$\showboard$$
+ I often find this sort of position when playing the sicilian, where
+white has the e file, pushes his pawn, and gains a winning advantage.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+9 & e5 & d*e5\\
+10 & N*e5 & Bd7\\
+\end{tabular}}|
+\end{center}
+|10\ldots~N*e5|
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+11 & Ne4&\\
+\end{tabular}}|
+\end{center}
+|11.~Bb3|
+\wbetter{}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+11 & \ldots & N*e5\\
+12 & B*e5 & Bc6\\
+\end{tabular}}|
+\end{center}
+
+\board
+{r* q rk*}
+{*p* bppp}
+{p*b*pn *}
+{* p B * }
+{ *B*N* *}
+{* *P* * }
+{PPP* PPP}
+{R *QR K }
+$$\showboard$$
+|12\ldots~N*e4; 13.~d*e4, b5; 14.~Bb3, Bc6; 15.~Qh5, Re8|
+=
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+13 & B*f6&\\
+\end{tabular}}|
+\end{center}
+|13.~Qf3, N*e4; 14.~d*e4, b6; 15.~Rad1, Qe8|
+\wbetter{}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+13 & \ldots & B*e4??\\
+\end{tabular}}|
+\end{center}
+|13\ldots~B*f6; 14.~N*f6+, Q*f6; 15.~c3, b6; 16.~Qe2|
+\bbetter{}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+14 & B*e7 & Q*e7\\
+15 & R*e4 & Rac8\\
+16 & f4&\\
+\end{tabular}}|
+\end{center}
+|16.~a4, Qf6; 17.~c3, Rfd8; 18.~Qe2, h6; 19.~Re1|
+\wdecisive{}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+16 & \ldots & b5\\
+17 & Bb3 & Rc6\\
+\end{tabular}}|
+\end{center}
+|17\ldots~a5|
+and I might be able to stir up a queenside pawn charge.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+18 & c4&\\
+\end{tabular}}|
+\end{center}
+|18.~a4|
+striking at the ambushing pawns.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+18 & \ldots & Rd8\\
+\end{tabular}}|
+\end{center}
+|18\ldots~Rd6; 19.~c*b5, a*b5; 20.~a4, c4|
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+19 & Qe2&\\
+\end{tabular}}|
+\end{center}
+|19.~c*b5, a*b5; 20.~a4, b*a4; 21.~Ra*a4, Rcd6; 22.~d4, c*d4; 23.~Re*d4|
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+19 & \ldots & Rd4\\
+\end{tabular}}|
+\end{center}
+|19\ldots~b4|
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+20 & R*d4&\\
+\end{tabular}}|
+\end{center}
+|20.~c*b5, a*b5; 21.~a4, b*a4; 22.~R*a4, Rd8; 23.~d4, c*d4; 24.~Re*d4|
+All variations just win for white.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+20 & \ldots & c*d4\\
+21 & Re1&\\
+\end{tabular}}|
+\end{center}
+|21.~c*b5|
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+21 & \ldots & Rc5\\
+22 & Qe4&\\
+\end{tabular}}|
+\end{center}
+|22.~Qf2, b*c4; 23.~B*c4, Qd6|
+Blacks score is rapidly going down.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+22 & \ldots & Rh5\\
+\end{tabular}}|
+\end{center}
+|22\ldots~Qd7; 23.~Qa8+, Qc8; 24.~Q*c8+, R*c8; 25.~g3, b*c4; 26.~d*c4|
+a passed pawn for white! Blacks passed pawn will not live long.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+23 & g4&\\
+\end{tabular}}|
+\end{center}
+|23.~f5, Rh6; 24.~c*b5, a*b5|
+Totally won for white.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+23 & \ldots & Rh4\\
+24 & Qa8+ & Qf8\\
+25 & Q*f8+ & K*f8\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ * * k *}
+{* * *ppp}
+{p* *p* *}
+{*p* * * }
+{ *Pp PPr}
+{*B*P* * }
+{PP * * P}
+{* * R K }
+$$\showboard$$
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+26 & h3?&\\
+\end{tabular}}|
+\end{center}
+|26.~Bd1, Rh3; 27.~Be2, Ke7; 28.~Kg2, Re3; 29.~h3, Kd6|
+Just a piece up.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+26 & \ldots & R*h3\\
+27 & Bc2 & Rg3+\\
+28 & Kf2 & R*g4\\
+29 & Kf3 & h5\\
+\end{tabular}}|
+\end{center}
+|29\ldots~Rh4; 30.~Kg3, Rh6; 31.~Re4, Rg6+; 32.~Kh3, Rh6+; 33.~Kg2|
+And black has drawing chances.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+30 & Re4&\\
+\end{tabular}}|
+\end{center}
+|30.~Re5, g6; 31.~Re4, Rh4; 32.~R*d4, g5|
+Black is only a pawn or so down.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+30 & \ldots & Ke7\\
+31 & R*d4&\\
+\end{tabular}}|
+\end{center}
+|31.~c*b5, a*b5; 32.~Re5, g6; 33.~R*b5, Kd6; 34.~Ke4|
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+31 & \ldots & e5\\
+\end{tabular}}|
+\end{center}
+|31\ldots~g5; 32.~c*b5, a*b5; 33.~a4, e5; 34.~Re4, R*f4+; 35.~R*f4, e*f4|
+Blacks is a `pawn` down, with 3 connected passed pawns. Not so bad,
+but still winning for white.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+32 & Re4 & R*f4+\\
+33 & R*f4 & e*f4\\
+34 & K*f4 & Kf6\\
+35 & c5 & Ke7\\
+36 & b4 & f6\\
+37 & d4 & g5+\\
+38 & Kg3 & h4+\\
+39 & Kg4 & Ke6\\
+40 & c6 & Kd6\\
+41 & d5 & Kc7\\
+42 & Be4 & Kd6\\
+43 & Bg2 & Kc7\\
+44 & Bh3 & Kd6\\
+45 & Kf5 & Kc7\\
+46 & K*f6 & Kb6\\
+47 & K*g5&\\
+\end{tabular}}|
+\end{center}
+I finally resigned here.
+
+\board
+{ * * * *}
+{* * * * }
+{pkP* * *}
+{*p*P* K }
+{ P * * p}
+{* * * *B}
+{P* * * *}
+{* * * * }
+$$\showboard$$
+$1\!-\!0$
+\clearpage
+\begin{center}
+\fbox{\fbox{\large\begin{tabular}{l}
+Game \hspace{.3 in} Jul 1994 \hspace{.3 in} $1\!-\!0$\\
+\hline
+Foo C67\\
+\raisebox{2.5pt}[11pt]{\framebox[11pt]{\rule{0pt}{4.25pt}}} Andy Gill\\
+\rule[-1pt]{11pt}{11pt} A. McMonigle\\
+Scottish Chess Minor
+\end{tabular}}}
+\end{center}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+1 & e4 & e5\\
+2 & Nf3 & Nc6\\
+3 & Bb5 & Nf6\\
+4 & 0-0 & N*e4\\
+\end{tabular}}|
+\end{center}
+
+\board
+{r*bqkb r}
+{pppp*ppp}
+{ *n* * *}
+{*B* p * }
+{ * *n* *}
+{* * *N* }
+{PPPP PPP}
+{RNBQ*RK }
+$$\showboard$$
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+5 & Re1&\\
+\end{tabular}}|
+\end{center}
+|5.~d4, Be7; 6.~d*e5, 0-0; 7.~Be3, a6|
+and white has the edge.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+5 & \ldots & d5\\
+\end{tabular}}|
+\end{center}
+|5\ldots~Nd6; 6.~B*c6, d*c6; 7.~N*e5, Be6; 8.~Nc3, Be7; 9.~Kh1|
+\wbetter{}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+6 & N*e5&\\
+\end{tabular}}|
+\end{center}
+|6.~d3|
+is a killer move.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+6 & \ldots & Qf6\\
+7 & Nf3&\\
+\end{tabular}}|
+\end{center}
+|7.~N*c6, b*c6; 8.~Qf3, Qg6; 9.~Bd3, Bf5; 10.~B*e4|
+\wbetter{}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+7 & \ldots & Be7\\
+8 & d3! & Nd6\\
+\end{tabular}}|
+\end{center}
+
+\board
+{r*b*k* r}
+{ppp bppp}
+{ *nn q *}
+{*B*p* * }
+{ * * * *}
+{* *P*N* }
+{PPP* PPP}
+{RNBQR K }
+$$\showboard$$
+|8\ldots~N*f2; 9.~K*f2, Bg4; 10.~Nbd2, 0-0; 11.~B*c6, b*c6|
+\wupperhand{}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+9 & B*c6+&\\
+\end{tabular}}|
+\end{center}
+|9.~Bg5, Q*b2; 10.~B*c6+, b*c6; 11.~R*e7+, Kf8; 12.~Nbd2, h6|
+White is a couple of pawns up, but the tactices are hairy!
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+9 & \ldots & b*c6\\
+10 & c3 & 0-0\\
+\end{tabular}}|
+\end{center}
+
+\board
+{r*b* rk*}
+{p p bppp}
+{ *pn q *}
+{* *p* * }
+{ * * * *}
+{* PP*N* }
+{PP * PPP}
+{RNBQR K }
+$$\showboard$$
+|10\ldots~h6; 11.~Be3, Nf5; 12.~Bf4, Rb8; 13.~Be5, Qg6|
+\wbetter{}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+11 & Bg5 & Qg6\\
+\end{tabular}}|
+\end{center}
+|11\ldots~Q*f3; 12.~Q*f3, B*g5; 13.~b3, Bb7; 14.~Qg3, Bf6|
+Is blacks best line.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+12 & B*e7 & Re8\\
+13 & B*d6 & R*e1+\\
+14 & Q*e1 & Q*d6\\
+15 & Qe8+ & Qf8\\
+16 & Q*f8+&\\
+\end{tabular}}|
+\end{center}
+|16.~Q*c6, Rb8; 17.~Q*c7, R*b2; 18.~Q*a7, Bf5; 19.~Qd4, Qb8; 20.~Nfd2|
+\wdecisive{} The proper continuation, and well winning for white.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+16 & \ldots & K*f8\\
+17 & Ne5&\\
+\end{tabular}}|
+\end{center}
+|17.~h3|
+Still a \wdecisive{}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+17 & \ldots & Bf5\\
+\end{tabular}}|
+\end{center}
+|17\ldots~c5; 18.~h3, f6; 19.~Nf3|
+and white moving the knight was a waste of two tempi.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+19 & \ldots & Rb8\\
+20 & b3 & Bf5\\
+\end{tabular}}|
+\end{center}
+\wdecisive{}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+18 & d4&\\
+\end{tabular}}|
+\end{center}
+|18.~Nd2, Re8; 19.~Ndf3, c5; 20.~g4, f6; 21.~Kg2, f*e5; 22.~g*f5|
+\wdecisive{}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+18 & \ldots & Re8\\
+19 & Nd2 & Re6\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ * * k *}
+{p p *ppp}
+{ *p*r* *}
+{* *pNb* }
+{ * P * *}
+{* P * * }
+{PP N PPP}
+{R * * K }
+$$\showboard$$
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+20 & Re1&\\
+\end{tabular}}|
+\end{center}
+|20.~g4, B*g4; 21.~N*g4, Rg6; 22.~h3, h5; 23.~f3, h*g4; 24.~h*g4|
+\wdecisive{} what a cou.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+20 & \ldots & f6\\
+21 & Nd7+ & Ke7\\
+22 & R*e6+ & B*e6\\
+23 & Nc5 & Bf5\\
+24 & f3&\\
+\end{tabular}}|
+\end{center}
+|24.~h3, h6; 25.~Kh2, Kd6; 26.~Nb7+, Ke7; 27.~g4, Bd3|
+\wdecisive{}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+24 & \ldots & Bc8\\
+25 & g4&\\
+\end{tabular}}|
+\end{center}
+|25.~Kf2, Kd6; 26.~f4, g6; 27.~Kf3, h6; 28.~g3, f5|
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+25 & \ldots & Kf7\\
+26 & Kg2&\\
+\end{tabular}}|
+\end{center}
+|26.~Kf2, Ke7; 27.~Ke3, Kd6; 28.~Kd3, h6; 29.~c4, d*c4+; 30.~N*c4+|
+\wdecisive{} with a plan
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+26 & \ldots & f5\\
+27 & Kg3 & Kg6\\
+28 & Nd3&\\
+\end{tabular}}|
+\end{center}
+|28.~g*f5+, B*f5; 29.~Na6, Kf6; 30.~h3, h6; 31.~N*c7|
+Attacking the weak backwards pawn.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+28 & \ldots & f*g4\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ *b* * *}
+{p p * pp}
+{ *p* *k*}
+{* *p* * }
+{ * P *p*}
+{* PN*PK }
+{PP N * P}
+{* * * * }
+$$\showboard$$
+|28\ldots~Kf6; 29.~g*f5, K*f5; 30.~Ne5, Bb7|
+Score: 3.19
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+29 & Ne5+ & Kf6\\
+30 & N*c6 & a6\\
+31 & f*g4 & g5\\
+32 & h4&\\
+\end{tabular}}|
+\end{center}
+|32.~Nb3, Bb7; 33.~Nb8, h6; 34.~Nc5, Bc8; 35.~b4, Kg6; 36.~Nb*a6|
+Successfully ganing up on the `a` pawn.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+32 & \ldots & g*h4+\\
+33 & K*h4 & Bd7\\
+34 & g5+&\\
+\end{tabular}}|
+\end{center}
+|34.~Nb4, c6; 35.~N*a6, h6; 36.~Kh5, Kg7|
+Totally won.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+34 & \ldots & Kg7\\
+35 & Ne5&\\
+\end{tabular}}|
+\end{center}
+|35.~Nb4, c6; 36.~N*a6, h6; 37.~Nc5, Bf5; 38.~a4, Kg6; 39.~g*h6|
+And either the 'a' or 'b' pawn will queen.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+35 & \ldots & Be8\\
+36 & Nb3 & Bg6\\
+\end{tabular}}|
+\end{center}
+At this point black resigned.
+
+\board
+{ * * * *}
+{* p * kp}
+{p* * *b*}
+{* *pN P }
+{ * P * K}
+{*NP * * }
+{PP * * *}
+{* * * * }
+$$\showboard$$
+$1\!-\!0$
+\clearpage
+\begin{center}
+\fbox{\fbox{\large\begin{tabular}{l}
+Game \hspace{.3 in} Jul 1994 \hspace{.3 in} $1\!-\!0$\\
+\hline
+Foo B86\\
+\raisebox{2.5pt}[11pt]{\framebox[11pt]{\rule{0pt}{4.25pt}}} Brian Swanson\\
+\rule[-1pt]{11pt}{11pt} Andy Gill\\
+Scottish Chess Minor
+\end{tabular}}}
+\end{center}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+1 & e4 & c5\\
+2 & Nf3 & d6\\
+3 & d4 & c*d4\\
+4 & N*d4 & Nf6\\
+5 & Nc3 & a6\\
+6 & Bc4 & e6\\
+\end{tabular}}|
+\end{center}
+|6\ldots~e5; 7.~Nf3, Qc7; 8.~Bd5, Bg4; 9.~0-0, N*d5; 10.~N*d5|
+Is another line of the Sicilian.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+7 & Bg5&\\
+\end{tabular}}|
+\end{center}
+|7.~0-0, Qc7; 8.~Qd3, e5; 9.~Nf3, Bg4; 10.~Bg5|
+\wbetter{},0.25
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+7 & \ldots & Be7\\
+8 & f4 & b5\\
+\end{tabular}}|
+\end{center}
+
+\board
+{rnbqk* r}
+{* * bppp}
+{p* ppn *}
+{*p* * B }
+{ *BNPP *}
+{* N * * }
+{PPP* *PP}
+{R *QK *R}
+$$\showboard$$
+|8\ldots~d5; 9.~B*f6, B*f6; 10.~e*d5, Qc7; 11.~Be2, Q*f4|
+\bupperhand{}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+9 & Bd3?&\\
+\end{tabular}}|
+\end{center}
+|9.~Bb3, h6; 10.~B*f6, B*f6; 11.~0-0, B*d4+; 12.~Q*d4|
+\bbetter{}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+9 & \ldots & Bb7\\
+10 & b4&\\
+\end{tabular}}|
+\end{center}
+|10.~Qf3, Qb6; 11.~Nde2, d5|
+=
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+10 & \ldots & Nc6\\
+11 & Nf3?&\\
+\end{tabular}}|
+\end{center}
+|11.~N*c6, B*c6; 12.~0-0, d5; 13.~e*d5, N*d5; 14.~B*e7, Q*e7|
+\bbetter{}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+11 & \ldots & N*b4\\
+12 & Qe2 & 0-0\\
+13 & 0-0&\\
+\end{tabular}}|
+\end{center}
+|13.~a3, Qc7; 14.~Qd2|
+\bupperhand{},by a pawn or so.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+13 & \ldots & Rc8\\
+\end{tabular}}|
+\end{center}
+|13\ldots~Qc7; 14.~Qd2, d5; 15.~B*f6, B*f6|
+\bupperhand{}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+14 & Nd1 & d5\\
+15 & e*d5&\\
+\end{tabular}}|
+\end{center}
+|15.~e5, Ne4; 16.~B*e7, Q*e7; 17.~B*e4, d*e4; 18.~Nd4|
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+15 & \ldots & B*d5\\
+16 & Ne3&\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ *rq rk*}
+{* * bppp}
+{p* *pn *}
+{*p*b* B }
+{ n * P *}
+{* *BNN* }
+{P*P*Q*PP}
+{R * *RK }
+$$\showboard$$
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+16 & \ldots & Bc5\\
+\end{tabular}}|
+\end{center}
+|16\ldots~B*a2; 17.~Rad1, N*d3; 18.~c*d3, Nd5|
+\bdecisive{},2+ pawns up, but getting a bit tactical.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+17 & Kh1 & B*e3\\
+18 & Q*e3 & N*c2\\
+19 & B*c2 & R*c2\\
+20 & a4 & Ra2\\
+\end{tabular}}|
+\end{center}
+|20\ldots~h6|
+\bdecisive{}, just winning.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+21 & R*a2 & B*a2\\
+22 & a*b5&\\
+\end{tabular}}|
+\end{center}
+|22.~Ra1, Bd5; 23.~a*b5, a*b5; 24.~Rb1, Ng4|
+\bdecisive{}, to or so pawns up.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+22 & \ldots & Bc4\\
+\end{tabular}}|
+\end{center}
+|22\ldots~a*b5; 23.~Ra1, Bd5; 24.~Ra7, h6|
+\bupperhand{}, even with the rook on blacks 2nd. This rook should be
+able to get to 'b' pawn, though.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+23 & Rc1 & B*b5\\
+24 & Ne5&\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ * q rk*}
+{* * *ppp}
+{p* *pn *}
+{*b* N B }
+{ * * P *}
+{* * Q * }
+{ * * *PP}
+{* R * *K}
+$$\showboard$$
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+24 & \ldots & Nd5?\\
+\end{tabular}}|
+\end{center}
+A bit wild.
+|24\ldots~h6; 25.~B*f6, Q*f6; 26.~Rc7, a5; 27.~Qc5, Be2; 28.~Q*a5, Q*f4|
+\bdecisive{}, almost three pawns up, and threating the forced queen
+exchage on f1.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+25 & Qg3&\\
+\end{tabular}}|
+\end{center}
+Alarms bells !!!, the bishop is going to h6. Remember.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+25 & \ldots & f6\\
+\end{tabular}}|
+\end{center}
+I though I was going to win a piece for a pawn.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+26 & Bh6 & g6??\\
+\end{tabular}}|
+\end{center}
+|26\ldots~Qe7; 27.~Nc6, Qc7; 28.~Rc2, Ba4; 29.~Rc4, Nb6|
+Black still leads (two pawns up), but the tactics are hairy.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+27 & B*f8?&\\
+\end{tabular}}|
+\end{center}
+|27.~N*g6, Kf7; 28.~N*f8, Ke8; 29.~N*e6, Qd7; 30.~Re1|
+\wdecisive{},5.47
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+27 & \ldots & f*e5\\
+\end{tabular}}|
+\end{center}
+|27\ldots~K*f8; 28.~Qh4, a5; 29.~g3, a4|
+\bbetter{}, but critically depending on the weak a pawn.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+28 & Bh6 & e*f4\\
+29 & Qe1&\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ * q *k*}
+{* * * *p}
+{p* *p*pB}
+{*b*n* * }
+{ * * p *}
+{* * * * }
+{ * * *PP}
+{* R Q *K}
+$$\showboard$$
+|29.~B*f4, N*f4; 30.~Q*f4, a5; 31.~h3, g5; 32.~Qe5|
+\wupperhand{}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+29 & \ldots & g5??\\
+\end{tabular}}|
+\end{center}
+My major blunder.
+|29\ldots~Kf7; 30.~g3, f3; 31.~Qf2, Qf6|
+\bupperhand{}, but tricky.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+30 & Q*e6+ & Kh8\\
+31 & Rc8&\\
+\end{tabular}}|
+\end{center}
+Mate is in a couple of moves.
+
+\board
+{ *Rq * k}
+{* * * *p}
+{p* *Q* B}
+{*b*n* p }
+{ * * p *}
+{* * * * }
+{ * * *PP}
+{* * * *K}
+$$\showboard$$
+$1\!-\!0$
+\clearpage
+\begin{center}
+\fbox{\fbox{\large\begin{tabular}{l}
+Game \hspace{.3 in} Jul 1994 \hspace{.3 in} $1\!-\!0$\\
+\hline
+Foo B54\\
+\raisebox{2.5pt}[11pt]{\framebox[11pt]{\rule{0pt}{4.25pt}}} Andy Gill\\
+\rule[-1pt]{11pt}{11pt} Brian Thomson\\
+Scottish Chess Minor
+\end{tabular}}}
+\end{center}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+1 & e4 & c5\\
+2 & Nf3 & d6\\
+3 & d4 & c*d4\\
+4 & N*d4 & Nc6\\
+5 & Bb5 & Bd7\\
+6 & Nc3&\\
+\end{tabular}}|
+\end{center}
+|6.~N*c6|
+Score: 0.06
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+6 & \ldots & Nf6\\
+\end{tabular}}|
+\end{center}
+|6\ldots~N*d4; 7.~Q*d4, B*b5; 8.~N*b5, Qa5; 9.~Nc3, e5; 10.~Qd5, Qc7|
+Score: -0.03
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+7 & Bg5 & h6\\
+\end{tabular}}|
+\end{center}
+|7\ldots~N*d4; 8.~B*d7, N*d7; 9.~Q*d4, e5; 10.~Qd2, Be7; 11.~Be3|
+Score: -0.03
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+8 & Bh4&\\
+\end{tabular}}|
+\end{center}
+|8.~B*f6, e*f6; 9.~f4, N*d4; 10.~B*d7, Q*d7; 11.~Q*d4, Be7|
+Score: 0.16
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+8 & \ldots & Qb6\\
+\end{tabular}}|
+\end{center}
+|8\ldots~g5; 9.~Bg3, N*d4; 10.~Q*d4, Bg7; 11.~0-0, 0-0|
+Score: -0.22
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+9 & N*c6&\\
+\end{tabular}}|
+\end{center}
+|9.~B*f6, g*f6; 10.~B*c6, b*c6; 11.~Na4, Qa5; 12.~c3, Bg7|
+Score: 0.06
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+9 & \ldots & b*c6\\
+10 & B*f6&\\
+\end{tabular}}|
+\end{center}
+|10.~Bd3, Q*b2; 11.~B*f6, e*f6; 12.~Na4, Qd4; 13.~c3|
+Score: -1.03
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+10 & \ldots & e*f6\\
+11 & Ba4&\\
+\end{tabular}}|
+\end{center}
+|11.~Bd3, Q*b2; 12.~Na4, Qa3; 13.~c3, Be6; 14.~Qc2, 0-0-0|
+Score: -1.31
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+11 & \ldots & Qc7\\
+\end{tabular}}|
+\end{center}
+|11\ldots~Q*b2; 12.~Kd2, Qb6; 13.~Qf3, Be6; 14.~e5, Qd4|
+Score: -1.44
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+12 & 0-0 & Be7\\
+13 & Re1&\\
+\end{tabular}}|
+\end{center}
+|13.~Rb1, 0-0; 14.~Qd3, Be6; 15.~f4, f5|
+Score: -0.09
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+13 & \ldots & 0-0\\
+14 & Qd4&\\
+\end{tabular}}|
+\end{center}
+|14.~Bb3|
+Score: -0.09
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+14 & \ldots & Be6\\
+\end{tabular}}|
+\end{center}
+|14\ldots~Rab8; 15.~b3, Be6; 16.~Rad1, Rb6; 17.~f4, Re8|
+Score: -0.16
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+15 & Nd1&\\
+\end{tabular}}|
+\end{center}
+|15.~f4, Rab8; 16.~Bb3, f5; 17.~e5, B*b3; 18.~a*b3|
+Score: -0.16
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+15 & \ldots & Qa5\\
+\end{tabular}}|
+\end{center}
+|15\ldots~Rab8; 16.~Qc3, Rb6; 17.~Ne3, Qb7; 18.~f4|
+Score: -0.09
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+16 & Nc3 & Qc7\\
+\end{tabular}}|
+\end{center}
+|16\ldots~Rab8; 17.~b3, Qc7; 18.~Rad1, Rfe8; 19.~f4, Rb6|
+Score: -0.13
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+17 & Ne2&\\
+\end{tabular}}|
+\end{center}
+|17.~Nd1|
+Score: 0.00
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+17 & \ldots & Rab8\\
+\end{tabular}}|
+\end{center}
+|17\ldots~Rfb8; 18.~Nf4, Rb6; 19.~N*e6, f*e6; 20.~Bb3, d5; 21.~e*d5, c*d5|
+Score: -0.06
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+18 & b3&\\
+\end{tabular}}|
+\end{center}
+|18.~Nf4|
+Score: -0.13
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+18 & \ldots & a5\\
+\end{tabular}}|
+\end{center}
+|18\ldots~f5; 19.~Rad1, f*e4; 20.~Q*e4, Bd5; 21.~Qd4|
+Score: -0.41
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+19 & Nf4&\\
+\end{tabular}}|
+\end{center}
+|19.~Qc3, c5; 20.~Nd4, Rb7; 21.~Nc6, Ra8; 22.~Rad1|
+Score: 0.06
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+19 & \ldots & Bd7\\
+\end{tabular}}|
+\end{center}
+|19\ldots~Rfc8; 20.~c4, Rd8; 21.~f3, Rd7|
+Score: 0.00
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+20 & Qd2&\\
+\end{tabular}}|
+\end{center}
+|20.~Qc3, Rb7; 21.~a3, Re8; 22.~Nd3, Reb8; 23.~f4|
+Score: -0.09
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+20 & \ldots & g5\\
+\end{tabular}}|
+\end{center}
+|20\ldots~Rfe8|
+Score: -0.09
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+21 & Nh5&\\
+\end{tabular}}|
+\end{center}
+|21.~Ne2, Rb7; 22.~Nd4, Re8; 23.~Qc3, c5; 24.~B*d7, Q*d7|
+Score: 0.13
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+21 & \ldots & Qb6\\
+\end{tabular}}|
+\end{center}
+|21\ldots~Bg4; 22.~Ng3, Rfe8; 23.~c4, Bf8; 24.~f3, Be6|
+Score: 0.13
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+22 & Qc3 & Qd8\\
+23 & Rad1&\\
+\end{tabular}}|
+\end{center}
+|23.~a3, Rc8; 24.~Ng3, Re8; 25.~Rad1, Bg4; 26.~B*c6, B*d1; 27.~R*d1|
+Score: 0.31
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+23 & \ldots & Bg4\\
+24 & Ng3 & B*d1\\
+25 & R*d1 & c5\\
+26 & Nh5&\\
+\end{tabular}}|
+\end{center}
+|26.~Nf5, h5; 27.~a3, Rb7; 28.~Qd3, Rb6; 29.~Qd2|
+Score: -0.06
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+26 & \ldots & Kh8\\
+\end{tabular}}|
+\end{center}
+|26\ldots~Rb4; 27.~Ng3, Qa8; 28.~a3, Rb6|
+Score: -0.75
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+27 & Rd3&\\
+\end{tabular}}|
+\end{center}
+|27.~Ng3, Rg8; 28.~Nf5, Bf8; 29.~Qd2, Qc7|
+Score: -0.34
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+27 & \ldots & Rg8\\
+\end{tabular}}|
+\end{center}
+|27\ldots~Rb4; 28.~Ng3, c4; 29.~Rd5, c*b3; 30.~c*b3, Qb6; 31.~Bc6|
+Score: -0.88
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+28 & Rf3&\\
+\end{tabular}}|
+\end{center}
+|28.~Ng3, Rg6; 29.~Nf5, Rb4; 30.~Bc6, Qc7; 31.~a3, Rb6|
+Score: -0.81
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+28 & \ldots & Rg6\\
+\end{tabular}}|
+\end{center}
+|28\ldots~d5; 29.~e*d5, Q*d5; 30.~Re3, Qd1; 31.~Re1, Qd8; 32.~Ng3|
+Score: -1.00
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+29 & Bc6&\\
+\end{tabular}}|
+\end{center}
+|29.~Rd3, Rb4; 30.~f3, c4; 31.~Re3, c*b3; 32.~c*b3|
+Score: -0.97
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+29 & \ldots & Kg8\\
+30 & Bd5&\\
+\end{tabular}}|
+\end{center}
+|30.~Ng3, Qc7; 31.~Nf5, Bf8; 32.~Bd5, Bg7; 33.~Rd3, Bh8|
+Score: -1.00
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+30 & \ldots & a4\\
+31 & Qc4 & Qe8\\
+32 & Qd3&\\
+\end{tabular}}|
+\end{center}
+|32.~Qc3, a*b3; 33.~c*b3, Qd8; 34.~a4, Rb6; 35.~Rd3|
+Score: -0.78
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+32 & \ldots & Rb4\\
+\end{tabular}}|
+\end{center}
+|32\ldots~Qb5; 33.~Ng3, a*b3; 34.~Nf5, Bf8|
+Score: -0.97
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+33 & e5&\\
+\end{tabular}}|
+\end{center}
+|33.~c3, Rb6; 34.~e5, Kf8; 35.~N*f6|
+Score: -0.25
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+33 & \ldots & d*e5\\
+\end{tabular}}|
+\end{center}
+|33\ldots~Kh8; 34.~c3, Rh4; 35.~e*f6, Bd8; 36.~Re3, Qd7|
+Score: -0.22
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+34 & Q*g6+&\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ * *q*k*}
+{* * bp* }
+{ * * pQp}
+{* pBp pN}
+{pr * * *}
+{*P* *R* }
+{P*P* PPP}
+{* * * K }
+$$\showboard$$
+$1\!-\!0$
+\clearpage
+\begin{center}
+\fbox{\fbox{\large\begin{tabular}{l}
+Game \hspace{.3 in} Jul 1994 \hspace{.3 in} ${1 \over 2}\!-\!{1 \over 2}$\\
+\hline
+Foo B50\\
+\raisebox{2.5pt}[11pt]{\framebox[11pt]{\rule{0pt}{4.25pt}}} M. Navmann\\
+\rule[-1pt]{11pt}{11pt} Andy Gill\\
+Scottish Chess Minor
+\end{tabular}}}
+\end{center}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+1 & e4 & c5\\
+2 & Nf3 & d6\\
+3 & Bc4 & e6\\
+\end{tabular}}|
+\end{center}
+|3\ldots~Nc6|
+Score: 0.00
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+4 & Nc3 & a6\\
+\end{tabular}}|
+\end{center}
+|4\ldots~Nf6; 5.~d3, d5; 6.~Bb3, d*e4; 7.~N*e4, N*e4; 8.~d*e4, Q*d1|
+Score: 0.00
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+5 & a4&\\
+\end{tabular}}|
+\end{center}
+|5.~d3, Nc6; 6.~Bf4, Na5; 7.~e5, d5; 8.~Bg5, Ne7|
+Score: 0.09
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+5 & \ldots & Nf6\\
+6 & d3&\\
+\end{tabular}}|
+\end{center}
+|6.~d4|
+Score: 0.06
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+6 & \ldots & Be7\\
+\end{tabular}}|
+\end{center}
+|6\ldots~d5; 7.~Ba2, d*e4; 8.~N*e4, N*e4; 9.~d*e4, Q*d1; 10.~K*d1|
+Score: 0.09
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+7 & b3&\\
+\end{tabular}}|
+\end{center}
+|7.~Bg5, h6; 8.~Bh4, d5; 9.~e*d5, N*d5; 10.~N*d5, e*d5|
+Score: 0.16
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+7 & \ldots & 0-0\\
+\end{tabular}}|
+\end{center}
+|7\ldots~d5; 8.~e*d5, e*d5; 9.~N*d5, N*d5; 10.~0-0, 0-0|
+Score: -1.59
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+8 & d4&\\
+\end{tabular}}|
+\end{center}
+|8.~Qe2, Nc6; 9.~0-0, d5; 10.~e*d5, e*d5|
+Score: 0.06
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+8 & \ldots & c*d4\\
+\end{tabular}}|
+\end{center}
+|8\ldots~d5; 9.~e*d5, e*d5; 10.~Bd3, b6; 11.~0-0, Nc6|
+Score: -0.09
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+9 & N*d4&\\
+\end{tabular}}|
+\end{center}
+|9.~Q*d4|
+Score: -0.09
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+9 & \ldots & d5\\
+\end{tabular}}|
+\end{center}
+|9\ldots~Qa5; 10.~Qd2, b5; 11.~Bd3, e5; 12.~Nf3, Bg4|
+Score: -0.16
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+10 & e*d5 & e*d5\\
+11 & Bd3 & Re8\\
+\end{tabular}}|
+\end{center}
+|11\ldots~Nc6; 12.~Nce2, N*d4; 13.~N*d4, Bb4; 14.~Bd2, Qa5; 15.~Ne2, B*d2|
+Score: -0.22
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+12 & 0-0 & Bb4\\
+\end{tabular}}|
+\end{center}
+|12\ldots~Nc6; 13.~Nce2, Bg4; 14.~f3, Bc5; 15.~c3|
+Score: -0.03
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+13 & Bd2&\\
+\end{tabular}}|
+\end{center}
+|13.~Nce2, Nc6; 14.~Bb2, Bg4; 15.~f3, N*d4; 16.~N*d4|
+Score: 0.00
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+13 & \ldots & Qa5\\
+\end{tabular}}|
+\end{center}
+|13\ldots~b6|
+Score: -0.09
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+14 & Nb1 & Kh8\\
+\end{tabular}}|
+\end{center}
+|14\ldots~Nc6; 15.~B*b4, N*b4; 16.~Re1, Bg4; 17.~Be2, Rad8|
+Score: -0.09
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+15 & B*b4 & Q*b4\\
+16 & c3 & Qe7\\
+\end{tabular}}|
+\end{center}
+|16\ldots~Qc5; 17.~Re1, R*e1; 18.~Q*e1, Nc6; 19.~Nf5, b6|
+Score: 0.09
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+17 & Nd2&\\
+\end{tabular}}|
+\end{center}
+|17.~Ra2, Qc7; 18.~Re2, R*e2; 19.~Q*e2, Nc6; 20.~Rd1, N*d4; 21.~c*d4|
+Score: 0.09
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+17 & \ldots & Bg4\\
+\end{tabular}}|
+\end{center}
+|17\ldots~Qc5; 18.~Qc2, Nc6; 19.~N2f3, N*d4; 20.~N*d4, Ne4|
+Score: 0.00
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+18 & Qc1&\\
+\end{tabular}}|
+\end{center}
+|18.~N2f3, Qc7; 19.~Qd2, Nc6; 20.~Rfe1, Rad8; 21.~R*e8, R*e8|
+Score: 0.00
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+18 & \ldots & Nc6\\
+19 & N*c6&\\
+\end{tabular}}|
+\end{center}
+|19.~Re1, Ne5; 20.~Qc2, Qc7; 21.~c4, N*d3; 22.~Q*d3|
+Score: 0.03
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+19 & \ldots & b*c6\\
+20 & Re1 & Qd7\\
+\end{tabular}}|
+\end{center}
+|20\ldots~Qb7; 21.~Qc2, Rad8; 22.~h3, Bh5; 23.~c4, R*e1; 24.~R*e1|
+Score: 0.03
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+21 & R*e8+ & Q*e8\\
+22 & Qe1&\\
+\end{tabular}}|
+\end{center}
+|22.~Qc2, c5; 23.~h3, Bh5; 24.~b4, c4; 25.~Bf5|
+Score: 0.03
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+22 & \ldots & a5\\
+\end{tabular}}|
+\end{center}
+|22\ldots~Qd7|
+Score: 0.09
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+23 & h3 & Bd7\\
+\end{tabular}}|
+\end{center}
+|23\ldots~Bh5; 24.~g4, Bg6; 25.~B*g6, h*g6; 26.~Rd1, Rd8; 27.~Q*e8, N*e8|
+Score: 0.19
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+24 & Nf3&\\
+\end{tabular}}|
+\end{center}
+|24.~Rd1, Rb8; 25.~c4, h6; 26.~Q*e8, R*e8; 27.~c*d5, c*d5|
+Score: 0.16
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+24 & \ldots & Q*e1+\\
+\end{tabular}}|
+\end{center}
+|24\ldots~Rb8; 25.~Bc2, c5; 26.~c4, Q*e1; 27.~R*e1, d4|
+Score: 0.16
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+25 & R*e1 & Re8\\
+\end{tabular}}|
+\end{center}
+|25\ldots~Rb8; 26.~Bc2, g6; 27.~Re7, Kg7; 28.~Ne5, Be8|
+Score: 0.44
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+26 & R*e8+&\\
+\end{tabular}}|
+\end{center}
+|26.~Ne5|
+Score: 0.53
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+26 & \ldots & B*e8\\
+27 & c4&\\
+\end{tabular}}|
+\end{center}
+|27.~g3|
+Score: 0.28
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+27 & \ldots & h6\\
+\end{tabular}}|
+\end{center}
+|27\ldots~g6; 28.~g3, Kg7; 29.~Kg2, h6; 30.~Ne5, d4; 31.~f4, c5|
+Score: 0.13
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+28 & Kf1&\\
+\end{tabular}}|
+\end{center}
+|28.~g3, g6; 29.~Ne5, Kg7; 30.~Kg2, d4; 31.~Kf3, c5|
+Score: 0.25
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+28 & \ldots & g6\\
+29 & Ke2&\\
+\end{tabular}}|
+\end{center}
+|29.~c*d5|
+Score: 0.31
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+29 & \ldots & Kg7\\
+30 & Ke3&\\
+\end{tabular}}|
+\end{center}
+|30.~Ne5|
+Score: 0.31
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+30 & \ldots & Nd7\\
+\end{tabular}}|
+\end{center}
+|30\ldots~c5; 31.~Ne5, d4; 32.~Kd2, Bd7; 33.~N*d7, N*d7; 34.~Be4, Ne5|
+Score: 0.09
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+31 & Kd4&\\
+\end{tabular}}|
+\end{center}
+|31.~c*d5, c*d5; 32.~Kd4, Nf6; 33.~Ne5, Kf8; 34.~g3, Kg7; 35.~f4|
+Score: 0.59
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+31 & \ldots & d*c4\\
+32 & B*c4&\\
+\end{tabular}}|
+\end{center}
+|32.~K*c4, f5; 33.~Kc3, Bf7; 34.~g3, Nc5; 35.~Bc2, Bd5|
+Score: 0.16
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+32 & \ldots & Kf6\\
+\end{tabular}}|
+\end{center}
+|32\ldots~f5; 33.~Ke3, Bf7; 34.~B*f7, K*f7; 35.~Kf4, Ke6; 36.~Nd4, Kd5|
+Score: -0.03
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+33 & Bd3&\\
+\end{tabular}}|
+\end{center}
+|33.~Nd2, Nb6; 34.~Ne4, Ke7; 35.~Bd3, f5; 36.~Nc5, Bf7|
+Score: 0.22
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+33 & \ldots & Ke6\\
+34 & Kc4&\\
+\end{tabular}}|
+\end{center}
+|34.~Ke3, Nb6; 35.~Nd4, Kd6; 36.~Kf3, Ke5; 37.~Ne2, f5|
+Score: 0.09
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+34 & \ldots & f6\\
+\end{tabular}}|
+\end{center}
+|34\ldots~f5; 35.~g4, f*g4; 36.~h*g4, Ne5; 37.~N*e5, K*e5; 38.~Kc3|
+Score: -0.13
+
+\board
+{ * *b* *}
+{* *n* * }
+{ *p*kppp}
+{p * * * }
+{P*K* * *}
+{*P*B*N*P}
+{ * * PP*}
+{* * * * }
+$$\showboard$$
+${1 \over 2}\!-\!{1 \over 2}$
+\clearpage
+\begin{center}
+\fbox{\fbox{\large\begin{tabular}{l}
+Game \hspace{.3 in} Sep 1994 \hspace{.3 in} $1\!-\!0$\\
+\hline
+Foo B01\\
+\raisebox{2.5pt}[11pt]{\framebox[11pt]{\rule{0pt}{4.25pt}}} Andy Gill\\
+\rule[-1pt]{11pt}{11pt} Stewart McKay\\
+Grangemouth Congress
+\end{tabular}}}
+\end{center}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+1 & e4 & d5\\
+2 & e*d5 & Nf6\\
+3 & Bb5+ & Bd7\\
+4 & B*d7+ & Q*d7\\
+5 & Nf3 & N*d5\\
+6 & 0-0 & Nc6\\
+7 & Re1 & e6\\
+8 & d3 & g6\\
+9 & Bg5 & Bg7\\
+10 & c3 & Nf6\\
+11 & d4 & h6\\
+12 & B*f6 & B*f6\\
+13 & d5 & Rd8\\
+14 & Qd2 & Q*d5\\
+15 & Qf4 & Bg7\\
+16 & Q*c7 & 0-0\\
+17 & Qf4 & g5\\
+18 & Qd2 & Qf5\\
+19 & Qe3 & Rd3\\
+20 & Qe4 & Q*e4\\
+21 & R*e4 & Rd1+\\
+22 & Re1 & Rfd8\\
+23 & h3 & Ne5\\
+24 & Na3 & N*f3+\\
+25 & g*f3 & R1d3\\
+26 & Kg2 & a6\\
+27 & Rac1 & b5\\
+28 & Re2 & Bf8\\
+29 & Nc2 & Bc5\\
+30 & Ne1 & Rd2\\
+31 & R*d2 & R*d2\\
+32 & Rc2 & Rd1\\
+33 & Kf1 & Be7\\
+34 & a3 & Bf6\\
+35 & Ke2 & Rd5\\
+36 & Nd3 & Rd8\\
+37 & Kd2 & Rc8\\
+38 & Ke3 & Bg7\\
+39 & f4 & Bf6\\
+40 & Ne5 & Rc5\\
+41 & Nd7 & g*f4+\\
+42 & K*f4 & Bg5+\\
+43 & Ke4 & f5+\\
+44 & Kf3 & Rd5\\
+45 & Nb8 & Rd6\\
+46 & c4 & b*c4\\
+47 & R*c4 & Rb6\\
+48 & Rb4 & Rd6\\
+49 & Ra4 & Rb6\\
+50 & N*a6 & R*b2\\
+51 & Nc7 & Rb3+\\
+52 & Kg2 & Be7\\
+53 & N*e6 & R*a3\\
+54 & R*a3 & B*a3\\
+55 & Kg3 & Kf7\\
+56 & Nd4 & Kg6\\
+57 & Kf4 & Kh5\\
+58 & N*f5&\\
+\end{tabular}}|
+\end{center}
+And White won by queening the f pawn.
+
+\board
+{ * * * *}
+{* * * * }
+{ * * * p}
+{* * *N*k}
+{ * * K *}
+{b * * *P}
+{ * * P *}
+{* * * * }
+$$\showboard$$
+$1\!-\!0$
+\clearpage
+\begin{center}
+\fbox{\fbox{\large\begin{tabular}{l}
+Game \hspace{.3 in} Sep 1994 \hspace{.3 in} $0\!-\!1$\\
+\hline
+Foo D02\\
+\raisebox{2.5pt}[11pt]{\framebox[11pt]{\rule{0pt}{4.25pt}}} Harward Shaughan\\
+\rule[-1pt]{11pt}{11pt} Andy Gill\\
+Grangemouth Minor Congress
+\end{tabular}}}
+\end{center}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+1 & d4 & e6\\
+2 & Bf4 & d5\\
+3 & Nf3 & Nf6\\
+4 & Nbd2 & c5\\
+5 & e3 & a6\\
+6 & c4 & Nc6\\
+7 & Ne5 & c*d4\\
+8 & N*c6 & b*c6\\
+9 & e*d4 & Qb6\\
+10 & c*d5 & c*d5\\
+11 & Qc2 & Bd7\\
+12 & Be3 & Bb4\\
+13 & a3 & B*d2+\\
+14 & Q*d2 & 0-0\\
+15 & Bd3 & Rfc8\\
+16 & 0-0 & Bb5\\
+17 & b3 & Rc6\\
+18 & f3 & Rac8\\
+19 & Rfc1 & B*d3\\
+20 & R*c6 & R*c6\\
+21 & Q*d3 & Qc7\\
+22 & Bd2 & h6\\
+23 & Rb1 & Nh5\\
+24 & b4 & Nf4\\
+25 & B*f4 & Q*f4\\
+26 & b5 & Rc1+\\
+27 & R*c1 & Q*c1+\\
+28 & Kf2 & Qb2+\\
+29 & Kg3 & Q*b5\\
+30 & Q*b5 & a*b5\\
+31 & Kf2 & Kf8\\
+32 & Ke3 & Ke7\\
+33 & Kd3 & Kd6\\
+34 & f4 & f6\\
+35 & h4 & e5\\
+36 & d*e5+ & f*e5\\
+37 & f5 & e4+\\
+38 & Kd4 & Ke7\\
+39 & g4 & Kf6\\
+40 & Ke3 & g6\\
+41 & g5+ & h*g5\\
+42 & h*g5+ & K*f5\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ * * * *}
+{* * * * }
+{ * * *p*}
+{*p*p*kP }
+{ * *p* *}
+{P * K * }
+{ * * * *}
+{* * * * }
+$$\showboard$$
+$0\!-\!1$
+\clearpage
+\begin{center}
+\fbox{\fbox{\large\begin{tabular}{l}
+Game \hspace{.3 in} Sep 1994 \hspace{.3 in} $1\!-\!0$\\
+\hline
+Foo C65\\
+\raisebox{2.5pt}[11pt]{\framebox[11pt]{\rule{0pt}{4.25pt}}} Andy Gill\\
+\rule[-1pt]{11pt}{11pt} Lindsay Ridland\\
+Grangemouth Minor Congress
+\end{tabular}}}
+\end{center}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+1 & e4 & e5\\
+2 & Nf3 & Nc6\\
+3 & Bb5 & Nf6\\
+4 & 0-0 & Bc5\\
+5 & Re1 & a6\\
+\end{tabular}}|
+\end{center}
+|5\ldots~Ng4; 6.~Re2, 0-0; 7.~d3, Nd4; 8.~N*d4, B*d4; 9.~Nd2|
+\wbetter{},0.13 but a bit messy for white.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+6 & Ba4&\\
+\end{tabular}}|
+\end{center}
+|6.~B*c6, d*c6; 7.~h3, Qe7; 8.~d3, 0-0; 9.~Bg5, h6; 10.~Bh4|
+=, taking the exchange way out.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+6 & \ldots & b5\\
+7 & Bb3 & d6\\
+\end{tabular}}|
+\end{center}
+
+\board
+{r*bqk* r}
+{* p *ppp}
+{p*np n *}
+{*pb p * }
+{ * *P* *}
+{*B* *N* }
+{PPPP PPP}
+{RNBQR K }
+$$\showboard$$
+ We have now reached a main line of the Ruy Lopez.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+8 & c3&\\
+\end{tabular}}|
+\end{center}
+|8.~a4, Ng4; 9.~Re2, Bb7; 10.~a*b5, a*b5|
+=, and very like Game 7 of the Short-Kasparov WC, where Kasparov as
+white scored a decisive victory.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+8 & \ldots & Bg4\\
+9 & d3 & h6\\
+10 & Be3 & 0-0\\
+\end{tabular}}|
+\end{center}
+|10\ldots~B*e3; 11.~R*e3, 0-0; 12.~a4, b4; 13.~h3, Bh5; 14.~Nbd2, Rb8|
+=
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+11 & B*c5 & d*c5\\
+12 & Bc2 & Qd7\\
+13 & Nbd2&\\
+\end{tabular}}|
+\end{center}
+|13.~h3, Bh5; 14.~Nbd2, Rfd8; 15.~Nb3, Qd6; 16.~Qe2, Rab8; 17.~Red1|
+Fritz is deperate to put h3, but I dont see why.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+13 & \ldots & Nh5\\
+\end{tabular}}|
+\end{center}
+
+\board
+{r* * rk*}
+{* pq*pp }
+{p*n* * p}
+{*pp p *n}
+{ * *P*b*}
+{* PP*N* }
+{PPBN PPP}
+{R *QR K }
+$$\showboard$$
+|13\ldots~Rad8|
+is an idea.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+14 & Nb3&\\
+\end{tabular}}|
+\end{center}
+|14.~h3|
+\wbetter{},0.33 I now agree with this, because the knight block the h5
+retreat square.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+14 & \ldots & Nf4?\\
+\end{tabular}}|
+\end{center}
+|14\ldots~Qd6; 15.~h3, Be6; 16.~Ng5, B*b3; 17.~a*b3, Nf4; 18.~Nf3|
+\bbetter{}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+15 & N*c5 & Qc8\\
+\end{tabular}}|
+\end{center}
+|15\ldots~Qe7; 16.~Nb3, Rfd8; 17.~h3, Be6; 18.~d4, Qf6; 19.~Rc1, e*d4|
+=
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+16 & Re3&\\
+\end{tabular}}|
+\end{center}
+|16.~b4|
+White is just a pawn up.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+16 & \ldots & Rd8\\
+17 & Qd2 & Rd6\\
+\end{tabular}}|
+\end{center}
+|17\ldots~B*f3!; 18.~R*f3, Qg4; 19.~R*f4, e*f4; 20.~h3, Qh4; 21.~d4|
+and black has equalised!
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+18 & Bd1&\\
+\end{tabular}}|
+\end{center}
+
+\board
+{r*q* *k*}
+{* p *pp }
+{p*nr * p}
+{*pN p * }
+{ * *Pnb*}
+{* PPRN* }
+{PP Q PPP}
+{R *B* K }
+$$\showboard$$
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+18 & \ldots & N*g2??\\
+\end{tabular}}|
+\end{center}
+Throws away a piece for a very temp. inititive.
+|18\ldots~Rb8; 19.~d4, e*d4; 20.~c*d4, Ne6; 21.~N*e6, Q*e6|
+and white is starting to push home his advantage.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+19 & K*g2 & Bh3+\\
+20 & Kh1 & Qg4\\
+\end{tabular}}|
+\end{center}
+|20\ldots~Rg6|
+is another idea, but the whole plan is conceptually flawed.
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+21 & Ne1 & Qg5\\
+22 & Qe2 & Be6\\
+23 & Rg3 & Qf6\\
+24 & N*e6&\\
+\end{tabular}}|
+\end{center}
+
+\board
+{r* * *k*}
+{* p *pp }
+{p*nrNq p}
+{*p* p * }
+{ * *P* *}
+{* PP* R }
+{PP *QP P}
+{R *BN *K}
+$$\showboard$$
+|24.~Nf3, Ne7; 25.~N*e6, Q*e6; 26.~Bb3, Qf6; 27.~Rag1|
+\wdecisive{}
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+24 & \ldots & R*e6\\
+\end{tabular}}|
+\end{center}
+|24\ldots~Q*e6; 25.~Bb3, Qe7; 26.~Bd5, Rad8; 27.~Nf3, R8d7; 28.~Rd1|
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+25 & Qf3&\\
+\end{tabular}}|
+\end{center}
+Crude plan of exchanging queens to avoid `acidents`.
+|25.~Bb3|
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+25 & \ldots & Qe7\\
+26 & Bb3 & Rf6\\
+27 & Qe3&\\
+\end{tabular}}|
+\end{center}
+|27.~Qg2|
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+27 & \ldots & Rd8\\
+28 & Nc2 & Kh7\\
+29 & Rag1 & g6\\
+30 & Rf3&\\
+\end{tabular}}|
+\end{center}
+
+\board
+{ * r * *}
+{* p qp*k}
+{p*n* rpp}
+{*p* p * }
+{ * *P* *}
+{*BPPQR* }
+{PPN* P P}
+{* * * RK}
+$$\showboard$$
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+30 & \ldots & R*f3\\
+\end{tabular}}|
+\end{center}
+|30\ldots~Rfd6??; 31.~R*f7+|
+Trying to avoid the exchance, but black loses his Queen! Black
+actually moved his rook to d6, but before letting it go, spotted the
+danger, and then took the exchange. Shame...
+\begin{center}|
+{\bf\begin{tabular}{rp{50pt}p{50pt}}
+31 & Q*f3 & Rd7\\
+32 & Ne3 & h5?\\
+33 & Nd5!&\\
+\end{tabular}}|
+\end{center}
+At least winning the exchange. Black resigned here.
+
+\board
+{ * * * *}
+{* prqp*k}
+{p*n* *p*}
+{*p*Np *p}
+{ * *P* *}
+{*BPP*Q* }
+{PP * P P}
+{* * * RK}
+$$\showboard$$
+$1\!-\!0$
+
+\end{document}
diff --git a/testsuite/tests/programs/andy_cherry/mygames.pgn b/testsuite/tests/programs/andy_cherry/mygames.pgn
new file mode 100644
index 0000000000..3d2e46fa1b
--- /dev/null
+++ b/testsuite/tests/programs/andy_cherry/mygames.pgn
@@ -0,0 +1,1323 @@
+% --------------
+% Season 93/94
+% --------------
+
+[Site "Dunfermline Club Championship"]
+[Date "1993.10.??"]
+[Round "1"]
+[White "Webb, George"]
+[Black "Gill, Andy"]
+[Result "1-0"]
+[ECO "C10"]
+
+1. Nf3 d5 2. d4 Nc6 3. Nc3 Nf6 (3... Bf5 {is more natural.}) 4. e4? (
+4. Bf4 {is better.}) 4... e6? (4... dxe4 5. d5 exf3 6. dxc6 Qxd1+ 7.
+Nxd1 {and black is a clear pawn up.}) 5. e5 Ne4 {} 6. Nxe4? { Taking
+this knight looses a pawn} 6... dxe4 7. Nd2 Qxd4 8. Nc4 Qxd1+ 9. Kxd1
+Bd7 (9... Bc5 10. f3 exf3 11. gxf3 O-O 12. Bd3 {White can get presure
+down the `g' file, but first needs to solve the problem of the Bishop on
+c5 guarding g8.}) 10. Bd2 (10. Be3 {is better.}) 10... Bb4 11. c3 Bc5 12.
+Ke1 O-O-O (12... b5 13. Ne3 Bxe3 14. Bxe3 Nxe5 {wins a pawn, but black
+might have problems because of queenside weaknesses.}) 13. g3 (13. Bg5
+Be7 14. Bxe7 Nxe7 15. Rd1 {and white is starting to contest the `d'
+file.}) 13... Rhf8 14. Bg2 f5? {black is throwing away a pawn.} 15.
+exf6 gxf6 (15... Rxf6 {gives black more piece activity.}) 16. Bxe4 {
+taking the weak pawn, and attacking h7.} 16... e5? (16... Rh8 {is
+required to protect the weak h pawn.}) 17. Bxh7 {} 17... f5 (17... Bxf2+
+18. Kxf2 Be6 19. Nxe5 Rxd2+ 20. Ke1 Rxb2 {winning material, and striping
+whites king of protection.}) 18. b4 Be6 19. b5 (19. bxc5 Bxc4 {and white
+has the two bishops.}) 19... Bxc4 20. bxc6 bxc6 (20... Bxf2+ 21. Kxf2
+Rxd2+ 22. Ke1 Re2+ 23. Kd1 bxc6 24. h4 Rd8+ {with a winning attack on
+whites exposed king.}) 21. Rb1? {Throws away a pawn needlessly.} 21...
+Bxa2 (21... Bxf2+ 22. Kxf2 Rxd2+ 23. Ke1 Rxa2 {winning two pawns rather
+than one.}) 22. Rb2 Bd5 23. Rg1 e4 (23... a5 24. h4 a4 25. Bh6 Bf3 26.
+Rd2 Rxd2 27. Bxd2 {is a better plan, with a dangerous passed `a' pawn.})
+24. Bh6? 24... Ba3 (24... Rf7 25. Bg5 Rxh7 26. Bxd8 Ba3 27. Rd2 Kxd8 {
+two bishops vs a rook, a difficult win for black.}) 25. Rb1 Rfe8? {
+another missed opertunity.} 26. Bxf5+ Be6 27. Bg6 Rh8 28. Be3 {}
+28... Rd3? (28... Rxh2 29. Bxe4 c5 30. Rb7 a5 {and black has a
+fighting chance}) 29. Bd4 (29. Bxe4 Rxc3 30. Bd4 Rc4 31. Bxh8 Rxe4+ {and
+black is lost.}) 29... Bd5?? 30. Bxh8 e3?? 31. f3? (31. Bxd3
+exf2+ 32. Kxf2 Bc5+ 33. Bd4 {and white is two rooks up.}) 31... Rd2 32.
+Bf6 Bb2 33. h4 (33. Bf5+ Kb7 34. c4 Bxc4 35. Rxb2+ Rxb2 36. Bxb2 {
+winning.}) 33... Kb7 34. Bg5 Bxf3 (34... Ba2 35. Bc2 Bxb1 36. Bxb1 Rh2
+37. Bxe3 Bxc3+ {and black is just a bishop down in a pawn race.}) 35.
+Bxe3 Re2+ 36. Kf1 Rxe3 37. Re1?? {giving black a chance to equalize.}
+37... Re2?? {Returning the complement.} (37... Rxe1+ 38. Kxe1 Bxc3+
+39. Kf2 Bd4+ 40. Kxf3 Bxg1 {and White still has the edge with 2
+connected passed pawns, but black has real chances.}) 38. Rxe2 1-0
+
+
+[Site "Dunfermline Club Championship"]
+[Date "1993.11.??"]
+[Round "2"]
+[White "Gill, Andy"]
+[Black "Dunne, Barry"]
+[Result "1-0"]
+[ECO "C65"]
+
+1. e4 e5 2. Nf3 Nc6 3. Bb5 Nf6 4. d3 (4. O-O {Ruy Lopez, Berlin Defence})
+4... Be7 (4... Bc5 {is better.}) 5. O-O (5. Bxc6 dxc6 6. Nxe5 Bd6 7. Nf3
+O-O 8. O-O Be6 {and white is a pawn up, but black has a lead in
+development.}) 5... O-O $2 (5... d6 {is needed to protect e5.}) 6. Nc3 (6.
+Bxc6 dxc6 7. Nxe5 Bd6 8. Nf3 Bg4 9. Be3 {and white is a clean pawn up.})
+6... b6 $2 7. a3 Bb7 8. b4 Nd4 {A bit ambitious.} 9. Nxe5 (9. Nxd4 exd4
+10. Ne2 d5 11. e5 Nd7 {is whites best line.}) 9... Nxb5 (9... d5 10. Bb2
+dxe4 11. dxe4 Nxe4 {with equal chances.}) 10. Nxb5 d5 11. Bb2 dxe4 12.
+dxe4 (12. f3 {is a better approach.}) 12... Qxd1 13. Raxd1 Bd6 {} (13...
+Bxe4 14. Nd7 Bxc2 15. Bxf6 gxf6 16. Rd2 {with a slight advantage for
+white.}) 14. Nf3 (14. Nxd6 cxd6 15. Rxd6 Bxe4 16. c4 Rfd8 17. c5 bxc5
+18. bxc5 {winning for white.}) 14... Bxe4 (14... Nxe4 {is better.}) 15.
+Nxd6 cxd6 16. Bxf6 gxf6 17. Rxd6 Bxc2 (17... Bxf3 18. gxf3 Rac8 19. Rc1
+Rc3 20. Rd3 Rxd3 21. cxd3 {and whites passed pawn is a long way from
+queening.}) 18. Rxf6 (18. Nd4 Ba4 19. Rxf6 Rfd8 20. Rf4 Rd7 21. Re4 {a
+pawn up, but with chances for black, because of the powerful Bishop.})
+18... Rfd8 19. Ne5 Kg7 (19... Bg6 {is better, defending the weak pawn.})
+20. Rxf7+ Kg8 21. Rc7 (21. f4 a6 22. g3 Rd2 23. Rb7 b5 {and white should
+win.}) 21... Re8 (21... Rdc8 22. Rb7 Be4 23. Rd7 Rc2 24. Rfd1 {with
+connected rooks for white.}) 22. Re1 (22. f4 {is better for protecting the
+knight.}) 22... Rac8 {should have moved the `e' Rook.} 23. Rxa7 Bf5 (
+23... Ra8 $5 {planning to attack the weak `a' pawn.}) 24. f4 Bg4 (24...
+Rc2 {penatraiting the 7th.}) 25. Kf2 Rc2+ 26. Kg3 Re2 27. Rxe2 Bxe2 28.
+Nc6 $2 {where is that knight going ?} 28... Re3+ 29. Kf2 Re4 {} 30. f5 (
+30. Ne7+ Kf8 31. Nd5 Bd3 32. Nxb6 Re7 {totally winning for white})
+30... Bg4 31. Ne7+ (31. Kg3 h6 32. f6 Be6 33. Re7 {looking very good for
+white.}) 31... Kf8 32. f6 Rf4+ 33. Kg3 Re4 34. h3 (34. Nd5 Be6 35. Nxb6
+Rg4+ 36. Kf3 Rg6 37. Rxh7 Rxf6+ 38. Ke4 {and with 4 connected passed
+white will win.}) 34... Bh5 35. Nd5 b5 36. Rxh7 Bg6 37. Rh4 (37. Rh8+ Kf7
+38. Rb8 Bf5 39. Rxb5 Be6 40. Rb7+ Kg6 41. Rg7+ {just look at whites
+advantage.}) 37... Rxh4 38. Kxh4 Be4 39. Nc3 (39. Ne3 Kf7 40. Kg5 Bc6
+41. g4 Be4 42. h4 Bd3 43. h5 {winning.}) 39... Bc6 (39... Bxg2 40. Nxb5
+Kf7 41. Kg5 Bxh3 42. Nd6+ Kg8 43. a4 Kh7) 40. g4 Kf7 41. g5 (41. Kg5 Kg8
+42. h4 Bd7 43. h5 Kf7 44. Ne4 Kg8 45. Nd6) 41... Kg6 42. Kg4? 42...
+Bd7+ 43. Kf4 Bxh3 44. Nxb5 Bd7 (44... Kf7 45. Nd6+ Ke6 46. f7 Ke7 47. g6
+Kf8 48. a4 Kg7) 45. a4 Bc6 46. Nc3 Bd7 47. b5 1-0
+
+[Site "Dunfermline Club Championship"]
+[Date "1993.11.??"]
+[Round "3"]
+[White "Gill, Andy"]
+[Black "Brown, Rab"]
+[Result "0-1"]
+[ECO "C65"]
+
+1. e4 e5 2. Nf3 Nc6 3. Bb5 Bc5 4. O-O Nf6 5. Nc3 d6 6. a3 Ng4? 7.
+Qe1 (7. h3) 7... O-O {} 8. Bxc6 bxc6 9. b4 Ba6 10. bxc5 Bxf1 11. Kxf1 (
+11. Qxf1 Qd7 12. Bb2 dxc5 13. d3 Rfb8 14. Rb1 {clearly winning for
+white.}) 11... Qf6 {} (11... Rb8 12. Qe2 Qd7 13. Qa6 Ra8 14. h3 Nf6 15.
+d4 exd4 {is a better plan.}) 12. d3 Qg6 13. Rb1 (13. h3 Nh6) 13... Qh5
+14. Rb7 (14. h3 Nf6 15. Rb7 Rfc8 16. Bg5 Qg6 17. Qe3 Ne8 {and white has a
+commanding lead.}) 14... Nxh2+ 15. Nxh2 Qxh2 16. Rxc7 Qh1+ 17. Ke2 Qxg2
+18. Rxc6 (18. cxd6 Rfc8 19. Rxc8+ Rxc8 20. Be3 Rd8 21. Bc5 h5) 18... dxc5 (
+18... Qg4+ 19. f3 Qg2+ 20. Qf2 Qxf2+ 21. Kxf2 Rfc8 22. Nd5 Rxc6 23.
+Ne7+) 19. Rxc5 f5 20. Be3 Qg4+ 21. f3 Qg2+ 22. Qf2 Qh1 23. Rxe5 Qa1 {}
+24. Bc5? (24. Qe1 Qb2 25. Qd2 Qxa3 26. Bc5 Qa5 27. exf5 {white has the
+advantage.}) 24... Qxc3 25. Rxf5 (25. Bxf8 Qxc2+ 26. Kf1 Qxd3+ 27. Qe2
+Qb1+ 28. Qe1 Qxe1+ 29. Kxe1 {now black has only a slight advantage.})
+25... Qxc2+ (25... Rxf5 26. exf5 Qxc2+ 27. Kf1 Qxd3+ 28. Kg2 Rd8 29. f4 {
+and black has a clear lead.}) 26. Ke3 Qxf2+ 27. Kxf2 Rxf5 28. exf5 Rc8
+29. d4 a6 30. a4 Kf7 31. Ke3 (31. Kg3 Kf6 32. Kf4 g5+ 33. fxg6 hxg6 34.
+a5 g5+ 35. Kg4) 31... h5 (31... Kf6 32. Kf4 Rd8 33. a5 Rd5 34. Ke4 Rxf5)
+32. Kf4 h4 33. Kg4 Rh8 34. d5 h3 35. Bd6 g6 (35... h2 36. Bxh2 Rxh2 37.
+Kf4 Rh4+ 38. Ke5 Rxa4 39. d6 Rc4 {totaly won for black.}) 36. fxg6+ Kxg6
+37. Bh2 Kf6 {} 38. f4 (38. a5 Ke7 39. Kf5 Rh5+ 40. Ke4 Rh4+ 41. f4 Kd6
+42. Kd4 {holding the position.}) 38... Ke7 39. f5 a5 (39... Kf6 {is
+needed.}) 40. d6+ Kd7 (40... Kf6 {is still needed.}) 41. Kg5 Rb8 (41... Ke8)
+42. f6 Rb2 (42... Ke6 43. Kg4 Rb4+ 44. Kxh3 Rxa4 45. d7 Kxd7 46. Be5 {
+but black should still win.}) 43. Kg6 (43. f7 Rg2+ 44. Kh6 Rf2 45. Kg7
+Rg2+ 46. Kh7 Rf2 47. Kg7 {white has equalised!}) 43... Rf2 0-1
+
+[Site "Dunfermline C vs Stirling B"]
+[Date "1993.11.??"]
+[Round "4"]
+[White "Gill, Andy"]
+[Black "Kennedy, Ian"]
+[Result "0-1"]
+[ECO "C60"]
+
+1. e4 e5 2. Nf3 Nc6 3. Bb5 Bd6 4. O-O a6 5. Ba4 b5 6. Bb3 Bb7 7. d3 Nf6 (
+7... Na5 8. Nbd2 f6 9. a4 Nxb3 10. Nxb3 Bb4 11. axb5 axb5 {with
+equality.}) 8. Nc3 (8. a4 b4 9. Nbd2 Bc5 10. Nc4 d6 {<saw>}) 8... O-O (
+8... Na5 9. Bd2 Nxb3 10. axb3 O-O 11. Bg5 Rb8 {=}) 9. Be3 Na5 {} (9...
+Be7 10. a3 Ng4 11. Bd2 {<saw>}) 10. Bd5?! {where is that bishop going.}
+10... b4 (10... c6 11. Bb3 Bc7 12. Bg5 Nxb3 13. Bxf6 Qxf6 14. axb3 {
+<sab>}) 11. Bxb7 Nxb7 12. Nd5 (12. Ne2 Ng4 13. Bd2 f5 14. exf5 Rxf5 15.
+Ng3 Rf6 {<saw>}) 12... c6 (12... Nxd5 13. exd5 f6 14. c3 bxc3 15. bxc3
+Be7 16. d4 d6 {<sab>}) 13. Nxf6+ (13. Bb6 Qc8 14. Nxf6+ gxf6 15. d4 Bc7
+16. Bxc7 Qxc7 {<saw> and the black king is exposed.}) 13... Qxf6 14. Bb6 {
+?! strange move.} (14. Qd2 Be7 15. c3 a5 16. a3 bxa3 17. bxa3 {<saw> with
+the plan ofs owning the `b' file.}) 14... Bc5 (14... Be7) 15. Bc7 (15. Nxe5 {
+but black can easly win back the pawn.}) 15... Rac8? (15... d6 16. d4
+exd4 17. e5 Qe7 18. exd6 Nxd6 19. Bxd6 Qxd6 {<ab>}) 16. Bxe5 Qg6 17. d4 (
+17. Bg3 Rfe8 18. Ne5 Qf6 19. Nxd7 Qxb2 20. Re1 {<aw> white should now
+try use his center pawns to push home his advantage.}) 17... Bd6 18.
+Bxd6 {this is to early, leaving myself underdeveloped.} (18. Re1 f6 19.
+Bxd6 Nxd6 20. Qd3 {<aw>}) 18... Nxd6 19. Ne5 (19. e5 Nc4 20. b3 Na3 21.
+Rc1 d6 22. Re1 {<aw>}) 19... Qxe4 20. Nxd7 Rfe8 21. Nc5 Qg6? (21...
+Qe2 22. Re1 Qc4 23. Qd2 Rcd8 24. Rad1 a5 {<aw> white is a clear pawn up.})
+22. Nxa6 Nf5 23. Nxb4 { white should now win the endgame quite
+comfortably.} 23... Nh4 (23... Rcd8 24. c3 c5 25. Nc2 cxd4 26. Nxd4 Qf6
+27. Qf3 Nxd4 {<aw> though still two clear pawns up.}) 24. g3 {forced.}
+24... c5 25. dxc5 Rxc5 (25... Qe4 26. gxh4 Qxb4 27. a4 Qxh4 28. Qd5 Re2 {
+<aw>, but whites king is dangerously exposed, and the `a' rook is not
+(yet) part of the game.}) 26. a4 {crap plan! Its just too slow.} (26. Nd3
+Rf5 27. f4 Rd5 28. a4 Qb6+ 29. Rf2 Nf5 {<waw> black will never stop 3
+connected passed pawns!}) 26... f5 27. Nd5 Rd8?? (27... Qd6 28. Nf4
+Qxd1 29. Rfxd1 Nf3+ 30. Kg2 Ne5 {<waw>}) 28. Ne7+! 28... Kf7 29. Qxd8
+Qg5 {} (29... Nf3+ 30. Kg2 {is an idea.}) 30. a5 {this plan is still to
+slow.} (30. Qg8+ Kxe7 31. Rfe1+ Kd6 32. Qf8+ Kc6 33. Qc8+ Kb6 34. Re6+
+Rc6 35. Qxc6+ Ka7 36. Qb6+ Ka8 37. Re8+ Qd8 38. Rxd8#) 30... f4 {} 31.
+f3?? (31. Nc6 Nf3+ 32. Kg2 fxg3 33. Qd7+ Kf8 34. Qc8+ Kf7 35. fxg3 {
+<waw> but there are still some hairy tactics.}) 31... fxg3 32. hxg3?? (
+32. Qg8+ Kxe7 33. Rfe1+ Re5 34. Rxe5+ Qxe5 35. h3 Nxf3+ 36. Kg2 {and
+white can still win!}) 32... Qxg3+ 33. Kh1 Qg2# {painfull!} 0-1
+
+[Site "Dunfermline Club Championship"]
+[Date "1993.11.??"]
+[Round "5"]
+[White "Gill, Andy"]
+[Black "Langham, Neil"]
+[Result "1-0"]
+[ECO "C41"]
+
+1. e4 e5 2. Nf3 d6 3. Nc3 Nf6 4. Bc4 h6 ( 4... Bg4 5. d3 Nc6 6. h3 Bh5 7. O-O
+Bxf3 8. Qxf3 { = } ) 5. O-O Bd7 6. d3 Nc6 7. Bd2 ( 7. Be3 Be7 8. Nd5 O-O 9. h3
+Nxd5 10. Bxd5 Bf6 ) 7... Na5 {  } 8. b4 ( 8. Bd5 Bg4 9. a3 c6 10. Ba2 d5
+11. Be3 dxe4 12. Nxe4 { but black is having the freer game } ) 8... Nxc4
+9. dxc4 Be6 ( 9... Be7 10. Qe2 O-O 11. Rfd1 Be6 12. c5 c6 13. cxd6 Qxd6 { <sab>
+} ) 10. Nd5 $2 Nxe4 11. Qe2 ( 11. Re1 Nxd2 12. Qxd2 c6 13. Ne3 Be7 14. Rad1 O-O
+{ <ab>, with white a pawn and position down. } ) 11... Nxd2 12. Nxd2 ( 12. Qxd2
+{ is better. } ) 12... Qg5 $4 {  } ( 12... g6 13. Ne3 f5 14. c5 dxc5 15. bxc5
+c6 { <ab>, ready for a pawn charge on white's king. } ) 13. Nxc7+ Ke7 (
+13... Kd7 { is better, stoping the future escape of the white knight. } )
+14. Nxa8 Bh3 { going for the cheapo. } 15. f4 $1 Qg6 16. Nc7 ( 16. fxe5 Kd8
+17. Qe4 Be6 18. Qxg6 fxg6 { is the best line Fritz2 found. } ) 16... Kd7
+17. Nd5 Bg4 18. Qf2 f6 ( 18... Qxc2 19. Ne3 Qg6 20. fxe5 Be6 21. Nf3 { rather
+cheeky, but still a rook down. } ) 19. Ne3 Ke6 $2 {  } 20. f5+ Bxf5 21. Qxf5+
+( 21. Nxf5 Qg5 22. h4 Qg4 { actually wins more material, but with this level of
+inequality, you want to swap of queens. } ) 21... Qxf5 22. Nxf5 g6 23. Ng3 { At
+this point the score sheet goes wrong, but the game was won by now anyway! }
+1-0
+
+[Site "Dunfermline Club Championship"]
+[Date "1993.11.??"]
+[Round "6"]
+[White "Gill, Andy"]
+[Black "Duncan, Dennis"]
+[Result "1-0"]
+
+1. e4 e5 2. Nf3 d6 3. Bc4 Bg4 4. O-O Nf6 5. Nc3 ( 5. d3 Nc6 6. Be3 d5 7. exd5
+Nxd5 8. Nbd2 Nxe3 9. fxe3 { = } ) 5... c6 ( 5... Nc6 6. Bb5 Qd7 7. h3 Bxf3
+8. Qxf3 O-O-O { = } ) 6. Bb3 d5 7. d3 ( 7. exd5 cxd5 8. Re1 e4 9. d3 Bxf3 { = }
+) 7... b5 ( 7... dxe4 8. dxe4 Qxd1 9. Rxd1 Bxf3 { <sab> } ) 8. h3 {  } (
+8. exd5 b4 9. Ne4 cxd5 10. Nxf6+ gxf6 11. d4 exd4 12. Qxd4 { <aw> } ) 8... Bc8
+( 8... Bxf3 9. Qxf3 d4 10. Ne2 Nbd7 11. Bg5 Be7 { <saw> } ) 9. Nxe5 ( 9. exd5
+Nxd5 10. Nxe5 Be6 11. Nxd5 { <aw> } ) 9... Qc7 ( 9... Bd6 10. Nf3 dxe4 11. Nxe4
+Nxe4 12. Re1 Bxh3 13. Rxe4+ Be6 { <aw> } ) 10. Nf3 Nh5 ( 10... Be6 11. Nd4 dxe4
+12. Bxe6 { <aw> } ) 11. exd5 c5 12. Nxb5 ( 12. Re1+ $1 Be7 13. Nxb5 Qb6 14. d6
+Qxb5 15. Rxe7+ Kd8 16. Bxf7 { <waw> } ) 12... Qb6 ( 12... Qb7 13. Re1+ Kd8
+14. Ne5 Nf6 15. Bg5 Bf5 16. Bxf6+ gxf6 { <waw> } ) 13. Ba4 ( 13. Re1+ Kd8
+14. Ne5 Qxb5 15. Nxf7+ Kc7 16. Nxh8 Nf6 17. Bf4+ { <waw> } ) 13... Bd7 14. Qe2+
+Be7 {  } 15. d4 ( 15. d6 O-O 16. dxe7 Re8 17. d4 cxd4 18. Nfxd4 { <waw> } )
+15... Bxb5 16. Bxb5+ Nd7 ( 16... Kf8 17. Re1 Qd6 18. Nh4 Qf6 19. Qxh5 { <waw> }
+) 17. Bxd7+ Kxd7 18. Ne5+ Ke8 19. dxc5 ( 19. Nc6 Qc7 20. Re1 cxd4 21. c4 Nf6 {
+<waw> } ) 19... Qxc5 20. Rd1 ( 20. d6 Qxd6 21. Qf3 Rc8 22. Nxf7 Qf6 23. Qxf6
+Nxf6 24. Nxh8 { <waw> } ) 20... Ng3 21. Qe3 ( 21. Qg4 Qxc2 22. Rd2 Qf5 23. Qxg3
+Bf6 { <waw> } ) 21... Nf5 22. Qxc5 ( 22. Qf3 Nd6 23. c4 Bf6 24. Re1 Bxe5
+25. Rxe5+ Kf8 { <waw> } ) 22... Bxc5 {  } 23. Be3 $2 ( 23. Re1 Ne7 24. c4 f6
+25. Nd3 Bd4 { <waw> } ) 23... Nxe3 ( 23... Bxe3 24. fxe3 Nxe3 25. Rd2 Rc8
+26. Re2 Nxd5 27. Ng6+ Kd7 { Blacks best line } ) 24. fxe3 Bxe3+ 25. Kf1 Bf4
+26. Re1 ( 26. Nd3 Bd6 27. c4 Rc8 28. b3 { <waw> } ) 26... f6 {  } 27. Ng6+ Kf7
+28. Nxf4 Rhe8 29. Rxe8 ( 29. c4 Rac8 30. b3 h6 31. Kf2 Rxe1 32. Rxe1 Rc5 {
+<waw> } ) 29... Rxe8 30. d6 ( 30. Kf2 Re5 31. Rd1 g5 32. Ne2 { <waw> } )
+30... Rd8 31. Rd1 g6 32. Nd5 ( 32. c4 g5 33. Ne2 Ke6 34. Nd4+ Kd7 35. c5 h6 {
+<waw>,5.25 } ) 32... Rxd6 33. c4 ( 33. Ke2 Ke6 34. c4 Rc6 35. Kd3 f5 36. b3 {
+<waw>,4.53 } ) 33... f5 34. Ke1 ( 34. b3 { <waw>,4.22 } ) 34... Ra6 35. a3 f4
+$4 { Simply throws away a pawn. } 36. c5 {  why not take the pawn? } (
+36. Nxf4 h6 37. g3 g5 38. Nd5 Re6+ 39. Kd2 Re4 { <waw>,5.06 looks good to me. }
+) 36... Ke6 $2 37. Nc7+ { Black resigns } 1-0
+
+[Site "Dunfermline Club Championship"]
+[Date "1993.11.??"]
+[Round "7"]
+[White "Gill, Andy"]
+[Black "Rintoul, Adam"]
+[Result "1-0"]
+[ECO "C70"]
+1. e4 e5 2. Nf3 Nc6 3. Bb5 a6 4. Ba4 b5 5. Bb3 Nf6 6. d3 Bc5 ( 6... Bb7 7. O-O
+d5 8. exd5 Nxd5 9. Bg5 Be7 10. Bxe7 Ndxe7 { = } ) 7. Be3 $2 {  } ( 7. Nc3 )
+7... Bxe3 8. fxe3 O-O 9. O-O d6 10. Nbd2 ( 10. a3 Bb7 11. Nc3 Rb8 12. Nd5 a5 {
+<sab>,0.13 } ) 10... Bg4 11. d4 $2 ( 11. a4 Rb8 12. axb5 axb5 13. h3 Bh5
+14. Qe2 Nd7 { <sab>,-0.22 } ) 11... Bxf3 ( 11... exd4 12. Qe1 dxe3 13. Qxe3 Na5
+14. Nd4 c6 15. c3 Nxb3 { <ab> a pawn up. } ) 12. Nxf3 Nxe4 $4 {  } ( 12... Qe8
+13. d5 Na5 14. Qd3 Nxb3 15. axb3 c6 16. Rad1 { <ab> } ) 13. Bd5 Qd7 ( 13... Ng5
+14. Bxc6 Nxf3+ 15. Bxf3 Rb8 16. dxe5 dxe5 17. a3 { <waw> } ) 14. Bxe4 f5
+15. Bd5+ Kh8 16. Ng5 exd4 17. Qh5 {  } ( 17. Nxh7 Rfb8 18. Ng5 g6 19. Qf3 Ne5
+20. Qh3+ Kg7 21. Bxa8 { <waw>,4.44 } ) 17... h6 $2 ( 17... g6 18. Bxc6 gxh5
+19. Bxd7 dxe3 20. Rxf5 Rxf5 21. Bxf5 { <waw>,4.90 } ) 18. exd4 ( 18. Qg6 Qe8
+19. Qh7# ) 18... Rae8 ( 18... Rf6 19. Rae1 Raf8 20. Ne6 Re8 21. Qf3 {
+<waw>,2.66 } ) 19. Rae1 Rxe1 20. Rxe1 Nd8 21. Qg6 { I finally find the two move
+mate! } 1-0
+
+[Site "Dunfermline Club Championship"]
+[Date "1993.11.??"]
+[Round "8"]
+[White "Robertson, Ian"]
+[Black "Gill, Andy"]
+[Result "1-0"]
+[ECO "C30"]
+[WhiteElo "2150"]
+
+1. e4 e5 2. f4 d6 3. Nf3 Nc6 (3... exf4 {Just take the pawn, and then
+follow the main line KG.}) 4. Bb5 Bd7 5. O-O Nf6 6. Nc3 Be7 (6... a6 7.
+Ba4 exf4 8. d3 b5 9. Bb3 b4 {Who knows?}) 7. d3 { At this point white is
+winning.} 7... O-O 8. Kh1 {! A clever waiting move, to avoid temp
+gaining checks.} (8. Ne2) 8... Nd4 {? losses a pawn} 9. Bxd7 Qxd7 (9...
+Nxf3 10. Bh3 Nd4 11. Be3 c5 12. fxe5 dxe5 {<saw>}) 10. fxe5 Nxf3 {?? 
+Losses the piece.} 11. exf6 Bxf6 12. Qxf3 b5 {? what is this for?} (
+12... Rae8 {Planning taking control over the very white center.}) 13.
+Nd5 {} 13... Qd8 {?? Losses another pawn, as well as weakening the
+kingside, and allowing exchange of queens.} (13... Bd8) 14. Nxf6+ Qxf6
+15. Qxf6 gxf6 16. Rxf6 Kg7 17. Bg5 {Black is just out of good moves.}
+17... Rae8 {? Blocking in the f rook, allowing the skew.} 18. Raf1 d5 {
+? again lack of vision} 19. Bh6+ Kg8 20. exd5 Rd8 21. Bxf8 Rxf8 22. Rc6 {
+Planning an invasion of the 7th. Textbook play.} 22... Rd8 { Planing to
+remove the dangerous white pawn, but missing the connected rooks that
+arrive on the 7th.} 23. Rxc7 Rxd5 24. Rfxf7 Rd8 {Silly, blocking the
+kings escape, athough its over anyway. I should have tried for at least
+one cheapo.} (24... Re5) 25. Rxh7 Rf8 {?? Again just missing the action.}
+26. Rcg7# 1-0
+
+[Site "Dunfermline Club Knockout"]
+[Date "1993.12.??"]
+[Round "9"]
+[White "Gill, Andy"]
+[Black "Colquhoun, Bob"]
+[Result "1-0"]
+[ECO "B10"]
+
+1. e4 c6 2. Nf3 d5 3. exd5 cxd5 4. c4 ( 4. d4 { Score: 0.06 } ) 4... Nf6 (
+4... d4 5. b3 Nc6 6. Bb2 Nf6 7. Na3 e5 { Score: -0.03 } ) 5. cxd5 ( 5. d4 e6
+6. cxd5 Nxd5 7. Nbd2 Bd6 8. Bc4 { Score: 0.13 } ) 5... Nxd5 6. Bc4 e6 (
+6... Nb6 7. Bb3 Nc6 8. d4 Bf5 9. Bg5 Be4 { Score: 0.00 } ) 7. O-O Nc6 8. d4 a6
+( 8... Bb4 9. Bd2 Bxd2 10. Nbxd2 Nf4 11. Nb3 O-O { Score: -0.16 } ) 9. Re1 (
+9. Nc3 { Score: -0.09 } ) 9... b5 ( 9... Be7 10. Nc3 O-O 11. Qd3 Qd7 12. Nxd5 {
+Score: -0.03 } ) 10. Bxd5 Qxd5 11. Nc3 Qf5 ( 11... Qd8 12. d5 Ne7 13. d6 Nf5
+14. Qd5 Bd7 { Score: 0.41 } ) 12. d5 Nd8 ( 12... Nb4 13. d6 Nd3 14. Re4 Nxc1
+15. Rxc1 Rb8 { Score: 0.34 } ) 13. dxe6 ( 13. d6 Nb7 14. Ne4 Nc5 15. Nd4 {
+Score: 0.34 } ) 13... Bxe6 14. Qd5 ( 14. Nd5 Rc8 15. Nd4 Qg6 16. Bf4 Bc5
+17. Nc7 Kf8 18. Nxa6 { Score: 0.75 } ) 14... Qxd5 15. Nxd5 Bd6 16. Bg5 (
+16. Nd4 Rb8 17. Bf4 Bxf4 18. Nxf4 Rb6 19. Ndxe6 Nxe6 20. Nxe6 { Score: 0.00 } )
+16... O-O ( 16... h6 17. Bd2 O-O 18. Bf4 { Score: -0.25 } ) 17. Rad1 Nc6 (
+17... Nb7 18. Be7 Bxe7 { Score: 0.00 } ) 18. Nd4 ( 18. Nb6 Bb4 19. Rxe6 fxe6
+20. Nxa8 Rxa8 { Score: 0.16 } ) 18... Bxd5 ( 18... Nxd4 19. Rxd4 h6 20. Ne7 Kh7
+21. Rxd6 hxg5 22. Nd5 { Score: -0.25 } ) 19. Nxc6 Bxh2+ ( 19... Rfe8 20. Rxe8
+Rxe8 21. h3 Re6 22. Nd4 Re4 { Score: -0.13 } ) 20. Kxh2 Bxc6 21. Rd6 Rfe8 (
+21... Rac8 { Score: -0.44 } ) 22. Rxe8+ ( 22. Rc1 Be4 23. Rc7 h6 24. Be3 Kf8 {
+Score: -0.41 } ) 22... Bxe8 23. a3 ( 23. Be3 h6 24. b3 Kh7 25. a3 g6 26. Bd4 {
+Score: -0.78 } ) 23... a5 ( 23... h6 24. Be3 Kh7 25. b3 f6 26. Bd4 Bf7 27. b4 {
+Score: -0.88 } ) 24. Kg3 ( 24. b3 h6 25. Rd8 Rxd8 26. Bxd8 a4 27. bxa4 bxa4 {
+Score: -0.81 } ) 24... a4 ( 24... h6 { Score: -0.91 } ) 25. Bc1 ( 25. Kh4 h6
+26. Be3 Kh7 27. Bd4 Rc8 28. g3 Bc6 { Score: -1.03 } ) 25... Rc8 ( 25... h6
+26. Be3 Kh7 27. Kh4 Rc8 28. Bd4 Bc6 29. f3 { Score: -1.09 } ) 26. Bd2 ( 26. Be3
+h6 27. Kh4 Kh7 28. Bd4 Bc6 29. f3 { Score: -1.13 } ) 26... Rc4 ( 26... Bc6
+27. Be3 h6 28. f3 Kh7 { Score: -1.16 } ) 27. Rd8 Re4 28. Bb4 ( 28. f4 { Score:
+-0.88 } ) 28... f6 ( 28... h6 29. Kf3 Re6 30. Kg4 Kh7 31. f4 Re4 32. g3 {
+Score: -1.13 } ) 29. f4 ( 29. Kf3 Re6 30. Kg4 Kf7 31. Kh4 Re2 32. Rd2 { Score:
+-0.91 } ) 29... Kf7 30. Kf3 ( 30. Rc8 Kg6 31. Kf3 { Score: -1.16 } ) 30... Bc6
+31. Rc8 ( 31. Kg3 Re2 32. Rd2 Rxd2 33. Bxd2 Ke6 34. Be3 { Score: -1.25 } )
+31... Rxb4+ 32. Rxc6 Rxb2 33. g4 ( 33. Rb6 { Score: -2.06 } ) 33... Rb3+
+34. Ke4 Rxa3 35. Rc7+ ( 35. f5 h6 36. Rc7 Kg8 37. Rb7 Rb3 38. Rd7 Rb4 39. Kf3 {
+Score: -3.28 } ) 35... Kg6 36. Rb7 ( 36. f5 Kh6 37. Rc2 Rb3 38. g5 Kh5 39. gxf6
+gxf6 40. Rh2 { Score: -3.34 } ) 36... Rb3 37. f5+ ( 37. Kd4 { Score: -3.44 } )
+37... Kh6 38. g5+ ( 38. Kd4 a3 39. Ra7 b4 40. Kc4 Rb2 41. Rb7 Rc2 { Score:
+-3.59 } ) 38... fxg5 39. Rb6+ Kh5 40. Rb7 Rb4+ ( 40... Kg4 41. Rxg7 Rb4 42. Ke5
+Rf4 43. f6 h5 44. Ra7 h4 { Score: -4.09 } ) 41. Ke5 Rf4 ( 41... Kg4 42. Rxg7
+Rf4 43. f6 h5 44. Ra7 Rf5 45. Ke6 h4 { Score: -4.22 } ) 42. Rxb5 Kg4 43. Ke6
+Rxf5 ( 43... h5 44. Re5 h4 45. Re1 a3 46. Ra1 Rf3 47. Rg1 Kh5 { Score: -3.94 }
+) 44. Rxf5 1-0
+
+
+[Site "Dunfermline Club Championship"]
+[Date "1993.12.??"]
+[Round "10"]
+[White "Gill, Andy"]
+[Black "Petrie, George"]
+[Result "0-1"]
+
+1. e4 c5 2. Nf3 Nc6 3. Bc4 d6 ( 3... e6 4. Nc3 Nge7 5. d3 d5 6. Bb3 d4 7. Ne2
+e5 { Score: 0.09 } ) 4. O-O ( 4. c3 { Score: 0.03 } ) 4... e6 ( 4... g6 5. d4
+cxd4 6. Nxd4 Bg7 7. Be3 Nxd4 8. Bxd4 Nf6 { Score: -0.16 } ) 5. d3 ( 5. Bb5 Nf6
+6. d3 Bd7 7. Nc3 Be7 8. Bg5 O-O { Score: 0.00 } ) 5... Be7 ( 5... d5 6. Bb5 Nf6
+7. Ne5 Bd7 8. Nxd7 Qxd7 9. Bg5 { Score: 0.03 } ) 6. Nc3 Bd7 ( 6... Bf6 { Score:
+0.00 } ) 7. Bf4 ( 7. Re1 Nf6 8. Be3 O-O 9. a3 Rc8 10. Bf4 Nd4 11. Nxd4 { Score:
+0.06 } ) 7... a6 ( 7... Na5 8. Nd2 Nxc4 9. Nxc4 e5 10. Bg3 Be6 11. Ne3 { Score:
+-0.06 } ) 8. d4 ( 8. a3 Nf6 9. Re1 O-O 10. Be3 e5 11. Nd5 Be6 12. Nxe7 { Score:
+0.06 } ) 8... cxd4 9. Ne2 e5 ( 9... Na5 { Score: -0.94 } ) 10. Bg3 Nf6 11. Bd5
+( 11. c3 Nxe4 12. cxd4 O-O 13. Bd5 Nxg3 { Score: -0.97 } ) 11... O-O (
+11... Nb4 12. c3 Nbxd5 13. exd5 d3 14. Nc1 e4 15. Nd2 { Score: -1.16 } ) 12. c4
+( 12. c3 dxc3 13. Nxc3 b6 14. a3 Qc7 15. b3 Be6 16. Bxe6 { Score: -0.63 } )
+12... Qb6 ( 12... Bg4 13. Qb3 Qc7 14. Rac1 Rac8 15. Qd3 b6 { Score: -1.13 } )
+13. Qd2 ( 13. b3 Bg4 14. Nc1 Rac8 15. Nd3 Nh5 16. a3 Nxg3 17. fxg3 { Score:
+-1.22 } ) 13... Rac8 ( 13... Nb4 14. b3 Bg4 15. Rfd1 Nbxd5 { Score: -1.22 } )
+14. Bh4 ( 14. Rac1 { Score: -1.25 } ) 14... Nb4 ( 14... Bg4 15. Bg3 Nb4 16. b3
+Nbxd5 17. exd5 Bxf3 18. gxf3 { Score: -1.53 } ) 15. Nexd4 ( 15. Bxf6 Bxf6
+16. h3 Nxd5 17. cxd5 { Score: -1.44 } ) 15... Nbxd5 ( 15... exd4 16. b3 Bg4
+17. Qf4 Nd3 { Score: -3.34 } ) 16. Bxf6 ( 16. exd5 exd4 17. Rfe1 Bd8 18. b3 Ng4
+19. Bxd8 Rfxd8 20. Nxd4 { Score: -1.94 } ) 16... Nxf6 17. Ne2 ( 17. Nf5 Bxf5
+18. exf5 Rxc4 19. b3 Ne4 20. Qd5 Rb4 { Score: -4.75 } ) 17... Rxc4 18. b3 (
+18. Nc3 Rb4 19. b3 Nxe4 20. Nxe4 Rxe4 21. Rfd1 { Score: -5.13 } ) 18... Rxe4
+19. Nc3 ( 19. Ng3 Rb4 20. Rfe1 Bg4 21. Qd3 Rf4 22. Qe3 Qxe3 23. fxe3 { Score:
+-5.38 } ) 19... Rg4 ( 19... Rf4 20. Qe3 Qc7 { Score: -5.34 } ) 20. Qd1 (
+20. Rae1 { Score: -5.41 } ) 20... Bc6 21. Na4 ( 21. Rc1 Rf4 22. Re1 Bxf3
+23. gxf3 Re8 24. a3 { Score: -5.66 } ) 21... Qb4 ( 21... Bxa4 22. bxa4 Qa5
+23. Qb3 Rb4 24. Qc2 Rxa4 25. Rfc1 { Score: -5.94 } ) 22. Rc1 ( 22. h3 Rf4
+23. Nb2 Bxf3 24. gxf3 Rd4 25. Nd3 Qc3 { Score: -5.81 } ) 22... Rxg2+ 23. Kxg2
+Qg4+ 24. Kh1 Bxf3+ 25. Qxf3 Qxf3+ 26. Kg1 Nh5 ( 26... Nd5 27. Rc4 b5 28. Rfc1
+bxc4 29. Rxc4 Bf6 { Score: -14.53 } ) 27. Rc3 Qd5 ( 27... Qg4 28. Kh1 b5
+29. Rg1 Qd4 30. Rh3 Nf4 31. Rhg3 bxa4 { Score: -12.00 } ) 28. Nb6 ( 28. h3 Nf4
+29. Rg3 Ne2 30. Kh2 Nxg3 31. Kxg3 Qd3 32. Kg2 { Score: -11.94 } ) 28... Qd4
+29. Rfc1 ( 29. Na4 b5 30. h3 Nf4 31. Kh2 bxa4 32. Rc7 Re8 { Score: -12.97 } )
+29... Qxb6 30. Rc8 ( 30. R1c2 d5 31. h3 Qg6 32. Kh2 Nf4 33. f3 b6 { Score:
+-13.97 } ) 30... Nf4 31. R1c7 ( 31. R8c3 Ne2 32. Kf1 Nxc1 33. Rxc1 d5 34. h3
+Bc5 35. f3 { Score: -15.63 } ) 31... Bh4 ( 31... Nh3 32. Kh1 Qxf2 33. Rc4 d5
+34. Rc3 Qg1 { Score: -#4 } ) 32. Rc2 ( 32. Rxf8 Kxf8 33. Rc8 Ke7 34. Rc2 Qd4
+35. h3 Bxf2 36. Kh2 { Score: -18.41 } ) 32... Nd3 ( 32... Bxf2 33. Kf1 Qe3
+34. Rxf8 Kxf8 35. Rc8 Ke7 36. Rc7 Kd8 { Score: -19.53 } ) 33. Rxf8+ ( 33. Kf1
+Bxf2 34. Rxf8 Kxf8 35. Rc8 Ke7 36. Rg8 Bg3 37. Ke2 { Score: -14.78 } )
+33... Kxf8 0-1
+
+[Site "Dunfermline Club Championship"]
+[Date "1993.12.??"]
+[Round "11"]
+[White "Gill, Andy"]
+[Black "Horne, Peter"]
+[Result "0-1"]
+
+1. e4 e6 2. Nf3 Nc6 3. Bb5 a6 ( 3... d5 4. d3 dxe4 5. Bxc6 bxc6 6. dxe4 Qxd1
+7. Kxd1 { Score: 0.19 } ) 4. Ba4 ( 4. Bxc6 dxc6 5. O-O Nf6 6. Re1 Be7 7. d4 c5
+8. e5 { Score: 0.22 } ) 4... b5 5. Bb3 Bb7 ( 5... Na5 6. d3 Nxb3 7. axb3 Bb7
+8. O-O Bc5 9. Nc3 { Score: -0.13 } ) 6. d4 ( 6. c3 Nf6 7. d3 Be7 8. Be3 O-O
+9. Nbd2 d5 { Score: -0.09 } ) 6... Na5 7. Nbd2 ( 7. e5 Nxb3 8. axb3 c5 9. Bg5
+f6 10. Be3 cxd4 11. Bxd4 { Score: -0.38 } ) 7... Nf6 ( 7... Nxb3 8. axb3 c5
+9. O-O d5 10. exd5 Bxd5 { Score: -0.41 } ) 8. e5 Nd5 ( 8... Nxb3 9. Nxb3 Ne4
+10. O-O Be7 11. c3 O-O 12. Be3 d5 { Score: -0.19 } ) 9. O-O d6 ( 9... Nf4 {
+Score: -0.09 } ) 10. a4 ( 10. Bxd5 Bxd5 11. a4 dxe5 12. axb5 c5 13. bxa6 exd4 {
+Score: 0.09 } ) 10... b4 ( 10... dxe5 11. Bxd5 Qxd5 12. dxe5 c5 13. axb5 axb5
+14. b3 { Score: 0.06 } ) 11. Nc4 ( 11. Bxd5 Bxd5 12. c3 dxe5 13. Nxe5 Bd6
+14. cxb4 Bxb4 15. Ndf3 { Score: 0.03 } ) 11... Nxb3 12. cxb3 a5 ( 12... Rb8
+13. Qc2 Be7 14. Na5 c5 15. exd6 Qxd6 16. Nxb7 Rxb7 { Score: -0.34 } ) 13. Qe2 (
+13. Bg5 Be7 14. Bxe7 Qxe7 15. Re1 dxe5 { Score: -0.56 } ) 13... f6 ( 13... Be7
+14. Rd1 O-O 15. Be3 dxe5 16. dxe5 { Score: -0.63 } ) 14. exd6 ( 14. exf6 Bc8
+15. f7 Kxf7 16. Ng5 Ke7 17. Ne4 Qd7 18. Bg5 { Score: 0.47 } ) 14... cxd6 (
+14... Bxd6 15. Qxe6 Be7 16. Bd2 Ra6 17. Qf5 c5 18. dxc5 Bxc5 { Score: 0.03 } )
+15. Qxe6+ Qe7 ( 15... Be7 16. Re1 Ra6 17. Nh4 Nc7 18. Qxe7 Qxe7 19. Rxe7 Kxe7 {
+Score: 0.72 } ) 16. Qh3 ( 16. Nxd6 Kd8 17. Qxe7 Bxe7 18. Nxb7 Kc8 19. Nc5 Re8
+20. Re1 { Score: 4.66 } ) 16... Qf7 ( 16... Qc7 17. Re1 Be7 18. Qe6 Ra6 19. Bd2
+Qc8 20. Qxc8 Bxc8 { Score: 0.97 } ) 17. Re1+ Kd8 18. Bd2 Qg6 ( 18... g6 {
+Score: 0.97 } ) 19. Re2 ( 19. Rac1 Ra6 20. Ne3 Nxe3 21. Bxe3 d5 22. Bf4 Bd6 {
+Score: 0.88 } ) 19... Be7 ( 19... Ra6 20. Rae1 Be7 21. Qe6 Re8 22. Ne3 Nxe3
+23. Bxe3 Bxf3 { Score: 0.88 } ) 20. Rae1 ( 20. Nh4 Qh5 21. Rae1 Bc8 22. Qg3 Qg4
+23. Bf4 Nxf4 24. Qxg4 { Score: 1.06 } ) 20... Re8 ( 20... Bc8 21. Qh4 Bb7
+22. Bf4 Ba6 23. Qg3 { Score: 0.91 } ) 21. Nh4 ( 21. Nxd6 Bc8 22. Nh4 Qh5
+23. Qg3 Rg8 24. Nf3 Bg4 { Score: 2.06 } ) 21... Qh5 22. Nf5 ( 22. Nxd6 Ba6
+23. Re6 Bc8 24. g4 Bxe6 25. Rxe6 Nf4 26. Bxf4 { Score: 3.06 } ) 22... Qxh3
+23. gxh3 g6 ( 23... Bc6 24. Nxg7 Rg8 25. Bh6 Bd7 26. Nb6 { Score: 1.53 } )
+24. Ncxd6 ( 24. Nfxd6 Bc6 25. Nxe8 Kxe8 26. Re6 Bd7 27. Nd6 Kd8 28. Nf7 {
+Score: 3.41 } ) 24... gxf5 25. Nxe8 ( 25. Nxb7 Kd7 26. Nc5 Bxc5 27. dxc5 Rxe2 {
+Score: 1.66 } ) 25... Kxe8 26. Bh6 ( 26. f3 Kd7 27. Kf2 Rg8 28. Rd1 Bd6 29. Kf1
+Bc6 { Score: -0.16 } ) 26... Kf7 ( 26... Kd7 27. f3 Rg8 28. Kf2 Bd6 29. Rg1 Rg6
+30. Rxg6 hxg6 { Score: -0.47 } ) 27. Bf4 ( 27. f3 Rg8 28. Kf2 Bd6 29. Rg1 Rg6
+30. Rxg6 hxg6 31. Ke1 { Score: -0.41 } ) 27... Rg8+ 28. Kf1 Ba6 29. Bd2 Bd6
+30. f3 ( 30. Rc1 Bxh2 31. f3 Bg1 32. Rc4 Bxc4 33. bxc4 Bxd4 34. Rg2 { Score:
+-3.00 } ) 30... Bxh2 31. Kf2 ( 31. Rc1 Bg1 32. Rc4 Bxc4 33. bxc4 Bxd4 34. Re1
+Ne7 { Score: -3.13 } ) 31... Bg3+ 32. Kf1 Bxe1 33. Bxe1 ( 33. Kxe1 Rg1 34. Kf2
+Rb1 35. Re1 Rxb2 36. Rd1 Nc3 37. Ke1 { Score: -4.84 } ) 33... Ne3+ ( 33... Re8
+34. Bg3 Rxe2 35. Kg1 Rxb2 36. Bd6 Rxb3 { Score: -8.31 } ) 34. Kf2 f4 (
+34... Nd1 35. Kf1 Re8 36. Kg1 Bxe2 37. f4 Rd8 38. Kg2 Rxd4 { Score: -7.81 } )
+35. Rxe3 fxe3+ 36. Kxe3 Re8+ 37. Kd2 Re2+ 38. Kd1 Rxb2 39. d5 ( 39. f4 Rxb3
+40. h4 Rd3 41. Kc1 Rxd4 42. Bg3 Rd3 43. Bf2 { Score: -6.09 } ) 39... Rxb3 0-1
+
+[Site "Dunfermline Club Championship"]
+[Date "1994.01.??"]
+[Round "12"]
+[White "Gill, Andy"]
+[Black "Easton, Brian"]
+[Result "1-0"]
+
+1. e4 Nf6 2. Nc3 e6 3. d4 d5 4. e5 Ne4 5. Nxe4 dxe4 6. Bc4 Nc6 7. Be3
+Bb4+ 8. c3 Be7 9. Ne2 Bg5 10. Qd2 Na5 11. Bxg5 Nxc4 12. Qf4 Qd5 13. b3
+Nb2 14. O-O b6 15. Ng3 Ba6 16. c4 Nd3 17. Qxe4 Qxe4 18. Nxe4 Bb7 19. f3
+O-O 20. Nf2 f6 21. exf6 gxf6 22. Bh6 Rf7 23. Nxd3 Rd8 24. Nf4 Re7 25.
+Rfe1 Kf7 26. Rad1 e5 27. dxe5 Rxd1 28. Rxd1 fxe5 29. Nd5 Rd7 30. f4 e4
+31. f5 c6 32. Nc3 c5 33. Rxd7+ Kf6 34. Rxb7 Kxf5 35. Rxh7 Kg6 36. Rh8
+1-0
+
+[Site "Wester-Hailes Congress"]
+[Date "1994.01.??"]
+[Round "13"]
+[White "Plant, George"]
+[Black "Gill, Andy"]
+[Result "1-0"]
+
+1. e4 e5 2. Nf3 Nc6 3. Bb5 a6 4. Ba4 Nf6 5. d4 b5 6. Bb3 d6 7. Ng5 Qd7
+8. Bxf7+ Kd8 9. d5 Nb4 10. c3 Nxe4 11. Be6 Qe8 12. cxb4 Nxg5 13. Bxg5+
+Be7 14. Bxe7+ Qxe7 15. Bxc8 Rxc8 16. O-O c6 17. dxc6 Rxc6 18. Re1 h5
+19. Nc3 Rc4 20. a3 g5 21. Nd5 Qg7 22. Ne3 Rc7 23. Nf5 Qf6 24. Qxd6+
+Qxd6 25. Nxd6 Re7 26. Rxe5 Rxe5 27. Nf7+ Ke7 28. Nxe5 Rc8 29. Nd3 Kd6
+30. Kf1 h4 31. h3 Kd5 32. Ne1 Ke4 33. Nf3 Kf4 34. Nd4 Re8 35. Re1 Rxe1+
+36. Kxe1 Ke5 37. Nc2 Ke4 38. Ke2 Kf4 39. Kd3 Ke5 40. Ne3 Kf4 41. Nd5+
+Kf5 42. Nc7 1-0
+
+[Site "Wester-Hailes Congress"]
+[Date "1994.01.??"]
+[Round "14"]
+[White "Gill, Andy"]
+[Black "McIntee, C."]
+[Result "1-0"]
+
+1. e4 c5 2. Nf3 Nc6 3. Be2 Nf6 4. Nc3 e6 5. O-O d5 6. exd5 Nxd5 7. Nxd5
+Qxd5 8. c4 Qd8 9. Re1 h5 10. b3 f6 11. Bb2 h4 12. h3 Qc7 13. d4 Qf4
+14. d5 exd5 15. cxd5 Nd8 16. Bb5+ Kf7 17. Qc1 Qd6 18. Qe3 Be7 19. Qe4
+g5 20. Bd3 Ke8 21. Qg6+ Kd7 22. Bb5+ Kc7 23. Ne5 Qxd5 24. Rad1 Qg8 25.
+Bc4 Ne6 26. Qxg8 Rxg8 27. Bxe6 Bxe6 28. Nf3 Rad8 29. Rxd8 Rxd8 30. Rxe6
+Rd1+ 31. Kh2 Bd6+ 32. g3 f5 33. Be5 hxg3+ 34. fxg3 Bxe5 35. Rxe5 Ra1
+36. Rxc5+ Kb6 37. Rc2 g4 38. hxg4 fxg4 39. Ne5 Kb5 40. Nxg4 a5 41. Ne3
+Re1 42. Nc4 Re6 43. g4 Rh6+ 44. Kg3 Rg6 45. Rg2 a4 46. Ne5 Rg5 47.
+bxa4+ Kxa4 48. Kf4 Rg7 49. g5 b5 50. g6 b4 51. Kf5 Ka3 52. Kf6 Rg8 53.
+g7 1-0
+
+[Site "Wester-Hailes Congress"]
+[Date "1994.01.??"]
+[Round "15"]
+[White "Robertson, F."]
+[Black "Gill, Andy"]
+[Result "1-0"]
+
+1. d4 d5 2. Nf3 e6 3. Bf4 Be7 4. e3 Nf6 5. Bd3 b6 6. O-O O-O 7. Re1 Bb7
+8. Nbd2 c5 9. c3 Nc6 10. Ne5 Rc8 11. Ndf3 c4 12. Bc2 b5 13. b3 Qa5 14.
+b4 Qd8 15. a4 a6 16. axb5 axb5 17. Nxc6 Bxc6 18. Ne5 Bb7 19. Ra5 Qe8
+20. Ra7 Ba8 21. Ng4 Bc6 22. Be5 Qd8 23. Qf3 Ra8 24. Rxa8 Bxa8 25. Nxf6+
+Bxf6 26. e4 Bxe5 27. dxe5 dxe4 28. Bxe4 Bxe4 29. Qxe4 Qd3 30. Qxd3 cxd3
+31. Rd1 Rd8 32. f4 f5 33. Kf2 Kf8 34. Ke3 Ke7 35. Rxd3 Rxd3+ 36. Kxd3
+Kd7 37. h3 g6 38. Kd4 Kc6 39. g3 Kb6 40. g4 Kc6 41. c4 Kb6 42. c5+ Kc6
+43. Ke3 Kc7 44. Ke2 Kc6 45. Kf3 Kd5 46. gxf5 gxf5 47. h4 Kc4 1-0
+
+[Site "Wester-Hailes Congress"]
+[Date "1994.01.??"]
+[Round "16"]
+[White "Gill, Andy"]
+[Black "McKerrow, A."]
+[Result "0-1"]
+
+1. e4 e5 2. Nf3 Nc6 3. Bb5 a6 4. Ba4 Nf6 5. O-O Be7 6. Nc3 b5 7. Bb3
+O-O 8. a3 d6 9. Re1 Rb8 10. d3 Bg4 11. h3 Bh5 12. Nd5 Nxd5 13. exd5 Nd4
+14. g4 Nxf3+ 15. Qxf3 Bg6 16. a4 b4 17. a5 Qc8 18. Ba4 f5 19. gxf5 Rxf5
+20. Qg4 Bh5 21. Qc4 Rf6 22. Bg5 Rg6 23. f4 h6 24. Rxe5 dxe5 25. d6+ Qe6
+26. Qxe6+ Rxe6 27. Bb3 hxg5 28. dxe7 Bf7 29. fxg5 Rg6 30. Rf1 Bxb3 31.
+cxb3 Rxg5+ 32. Kh2 Re8 33. h4 Rg4 34. Kh3 Rf4 35. Rxf4 exf4 36. Kg4
+Rxe7 37. Kxf4 Rd7 38. Ke4 Rd6 0-1
+
+[Site "Wester-Hailes Congress"]
+[Date "1994.01.??"]
+[Round "17"]
+[White "McCluskey, S."]
+[Black "Gill, Andy"]
+[Result "1-0"]
+
+1. e4 e5 2. Nf3 Nc6 3. Bb5 a6 4. Bxc6 dxc6 5. d3 Bd6 6. O-O Bg4 7. h3
+Bh5 8. Be3 Qe7 9. Nc3 Nf6 10. Re1 O-O-O 11. Nb1 Bb4 12. c3 Ba5 13. b4
+Bb6 14. a3 Nxe4 15. Bxb6 Bxf3 16. Qxf3 Ng5 17. Qe3 cxb6 18. d4 Rhe8
+19. h4 Ne6 20. g3 exd4 21. cxd4 Rxd4 22. Nc3 c5 23. Rac1 Red8 24. bxc5
+bxc5 25. Ne4 R8d7 26. Nxc5 Rc7 27. Nxe6 Qxe6 28. Qxd4 Rxc1 29. Rxc1+
+Kb8 30. Qxg7 1-0
+
+[Site "Dunferline Club Knockout"]
+[Date "1994.01.??"]
+[Round "18"]
+[White "Gill, Andy"]
+[Black "Brown, Rab"]
+[Result "1-0"]
+
+1. e4 e5 2. Nf3 d6 3. d4 Nc6 4. dxe5 Nxe5 5. Nxe5 dxe5 6. Qxd8+ Kxd8
+7. Bc4 Bb4+ 8. Nc3 Bxc3+ 9. bxc3 Be6 10. Bxe6 fxe6 11. O-O Nf6 12. Bb2
+Nxe4 13. c4 Nd2 14. Rfd1 Ke7 15. Rxd2 c5 16. Bxe5 Rhg8 17. Rad1 g5 18.
+Rd7+ Ke8 19. Rxb7 g4 20. Rxh7 Rd8 21. Rxd8+ Kxd8 22. Rh8 Rxh8 23. Bxh8
+Kd7 24. f3 gxf3 25. gxf3 Ke7 26. Be5 Kd7 27. Kg2 Ke7 28. Kg3 Kf7 29.
+Bd6 Kf6 30. Bxc5 a5 31. Kf4 e5+ 32. Ke4 Ke6 33. f4 a4 34. fxe5 a3 35.
+Bxa3 Kd7 36. Kd5 Ke8 37. Ke6 Kd8 38. Kf7 Kd7 39. e6+ Kc6 40. e7 Kc7
+41. e8=Q Kb7 42. Qe6 Kc7 43. Qd6+ Kb7 44. Ke7 Ka7 45. Qb4 Ka8 46. Kd7
+Ka7 47. Kc7 Ka6 48. Qb6# 1-0
+
+[Site "Dunfermline C vs Grangemouth B"]
+[Date "1994.01.??"]
+[Round "19"]
+[White "Gill, Andy"]
+[Black "Patterson, Dick"]
+[Result "0-1"]
+
+1. e4 c5 2. Nf3 Nc6 3. Be2 e6 4. b3 a6 5. O-O b5 6. Bb2 Nf6 7. e5 Nd5
+8. d4 Bb7 9. c4 Nf4 10. cxb5 Nxe2+ 11. Qxe2 axb5 12. Re1 cxd4 13. Nxd4
+Nxd4 14. Bxd4 Qg5 15. g3 Rc8 16. f4 Qg6 17. Qxb5 Bc6 18. Qe2 Be7 19. a4
+O-O 20. a5 f6 21. exf6 Bxf6 22. Bxf6 Rxf6 23. b4 Rxf4 24. Qd2 Rf3 25.
+Rf1 Rxf1+ 26. Kxf1 Qf5+ 27. Qf4 Qd3+ 28. Ke1 Rf8 29. Qxf8+ Kxf8 30. a6
+Qd4 31. Ke2 Qxa1 32. Nd2 Qxa6+ 33. Ke3 Qa3+ 0-1
+
+[Site "Dunfermline Club Championship"]
+[Date "1994.01.??"]
+[Round "20"]
+[White "Mitchell, Ian"]
+[Black "Gill, Andy"]
+[Result "1-0"]
+[WhiteElo "1660"]
+
+1. e4 e5 2. f4 exf4 3. Nf3 Nc6 4. d4 Nf6 5. Bd3 d5 6. e5 Ne4 7. O-O g5
+8. c3 Qe7 9. Nfd2 Bf5 10. Qe2 Nxd2 11. Nxd2 Bxd3 12. Qxd3 O-O-O 13. a4
+Rg8 14. a5 a6 15. b4 h6 16. b5 Nb8 17. Nb3 axb5 18. Qxb5 Qd7 19. Qd3 f6
+20. exf6 Bd6 21. Bd2 Qg4 22. a6 Nxa6 23. Rxa6 bxa6 24. Qxa6+ Kd7 25.
+Qb5+ Ke6 26. c4 f3 27. Rxf3 Rb8 28. Qxd5+ Kd7 29. Nc5+ Kd8 30. Qxg8+
+1-0
+
+[Site "Dunfermline Club Championship"]
+[Date "1994.02.??"]
+[Round "21"]
+[White "Gill, Andy"]
+[Black "Burtwistle, Paul"]
+[Result "0-1"]
+
+1. e4 c5 2. Nf3 e6 3. Be2 Nc6 4. O-O Nf6 5. Nc3 d5 6. e5 Nd7 7. Re1
+Ndxe5 8. Nxe5 Nxe5 9. Bb5+ Nc6 10. d4 a6 11. Bxc6+ bxc6 12. Be3 cxd4
+13. Bxd4 c5 14. Be5 Bb7 15. Qd2 f6 16. Bc7 Qxc7 17. Rxe6+ Kf7 18. Rae1
+d4 19. Nd1 Bd6 20. f4 Rhe8 21. f5 Bd5 22. Rxe8 Rxe8 23. c3 Rxe1+ 24.
+Qxe1 Bxh2+ 25. Kh1 Be5 26. cxd4 cxd4 27. Qe2 Qc4 28. Qh5+ Kf8 29. Kg1
+Qc2 0-1
+
+[Site "Dunfermline Club Knockout"]
+[Date "1994.02.??"]
+[Round "22"]
+[White "Gill, Andy"]
+[Black "O'Neill, Jim"]
+[Result "0-1"]
+[BlackElo "1875"]
+
+1. e4 c5 2. Nf3 d6 3. d4 cxd4 4. Nxd4 Nf6 5. Bd3 a6 6. O-O e5 7. Nf3
+Bg4 8. Nc3 Nbd7 9. Re1 Rc8 10. Be3 b5 11. Nd5 Nxd5 12. exd5 Nf6 13. Bg5
+Be7 14. Bxf6 Bxf6 15. Be4 O-O 16. c3 Bh4 17. Qc2 f5 18. Nxh4 Qxh4 19.
+g3 Qh5 20. Bg2 Rf6 21. f3 Bxf3 22. Bxf3 Qxf3 23. Rad1 f4 24. gxf4 Rg6+
+0-1
+
+[Site "Dunfermline Club Championship"]
+[Date "1994.02.??"]
+[Round "23"]
+[White "Gill, Andy"]
+[Black "Bell, Bill"]
+[Result "1-0"]
+
+1. e4 e6 2. d4 d5 3. Nf3 dxe4 4. Nfd2 Qxd4 5. c3 Qd5 6. Be2 e3 7. Nf3
+Qxd1+ 8. Bxd1 exf2+ 9. Kxf2 Nc6 10. Be3 Bd7 11. Re1 h6 12. Nbd2 O-O-O
+13. Ba4 Kb8 14. Rad1 Bd6 15. b4 a6 16. Nc4 Be7 17. Nfe5 Be8 18. Rxd8+
+Bxd8 19. Bxc6 Bxc6 20. Nxf7 Rh7 21. Nxd8 Bd5 22. Nd2 g5 23. Rd1 Kc8
+24. Nb3 Rd7 25. Nxb7 Bxb7 26. Rxd7 Kxd7 27. Nc5+ Kc6 28. Nxe6 Nf6 29.
+Nd8+ Kd7 30. Nxb7 Ne4+ 31. Kf3 Nxc3 32. Nc5+ Kc6 33. Nxa6 Nxa2 34. Bd2
+Kb6 35. Nc5 Kc6 36. Nd3 Kb5 37. Ke4 Kc4 38. g3 Kb3 39. h4 gxh4 40. gxh4
+Nc3+ 41. Bxc3 Kxc3 42. h5 Kc4 43. Ne5+ Kxb4 44. Kd5 c5 45. Nd3+ Kb5
+46. Nxc5 Kb6 47. Ne6 Kb7 48. Nf8 Kc7 49. Ke6 Kd8 50. Kf7 Kc8 51. Kg6
+Kd8 52. Kxh6 Ke8 53. Kg7 1-0
+
+[Site "Dunfermline Club Championship"]
+[Date "1994.02.??"]
+[Round "24"]
+[White "MacArthur, John"]
+[Black "Gill, Andy"]
+[Result "1-0"]
+[WhiteElo "1725"]
+
+1. d4 e6 2. Nf3 Nf6 3. c4 d5 4. Nc3 Nc6 5. e3 Be7 6. Be2 O-O 7. O-O Qd6
+8. c5 Qd7 9. Ne5 Nxe5 10. dxe5 Ne4 11. Nxe4 dxe4 12. Qc2 Qc6 13. b4 Rd8
+14. Bb2 a5 15. a3 axb4 16. axb4 Rxa1 17. Rxa1 b6 18. Bd4 bxc5 19. bxc5
+Bb7 20. Ra5 Ra8 21. Bb5 Qd5 22. Qa4 Rxa5 23. Qxa5 Bxc5 24. Qxc7 Bf8
+25. Be8 h6 26. Qxf7+ Kh7 27. Qxf8 Bc6 1-0
+
+[Site "Dunfermline Club Championship"]
+[Date "1994.02.??"]
+[Round "25"]
+[White "Sneddon, Ian"]
+[Black "Gill, Andy"]
+[Result "1-0"]
+[WhiteElo "1685"]
+
+1. c4 e5 2. Nc3 Nf6 3. Nf3 Nc6 4. g3 d5 5. cxd5 Nxd5 6. Bg2 Be6 7. O-O
+Bb4 8. Ne4 Qd7 9. d4 exd4 10. Nxd4 O-O-O 11. Nxe6 Qxe6 12. Qc2 h6 13.
+Rd1 f5 14. Nc5 Bxc5 15. Qxc5 Nde7 16. Be3 Rxd1+ 17. Rxd1 Rd8 18. Rxd8+
+Kxd8 19. b3 a6 20. Qc3 Qe5 21. Qxe5 Nxe5 22. Bxb7 N7c6 23. Bf4 Na5 24.
+Bxe5 Nxb7 25. Bxg7 h5 26. Kg2 Nd6 27. f3 Ne8 28. Be5 c6 29. Kh3 Ke7
+30. Kh4 Nf6 31. Bxf6+ Kxf6 32. Kxh5 c5 33. g4 f4 34. g5+ Kg7 35. Kg4
+1-0
+
+[Site "Dunfermline Club Championship"]
+[Date "1994.03.??"]
+[Round "26"]
+[White "Gill, Andy"]
+[Black "Connally, Paul"]
+[Result "0-1"]
+[ECO "B70"]
+
+1. e4 c5 2. Nf3 d6 3. d4 cxd4 4. Nxd4 g6 5. Nc3 Nf6 6. Bd3 Bg7 7. O-O
+O-O 8. f4 Nc6 9. Nxc6 bxc6 10. Kh1 Rb8 11. Qe1 Ng4 12. h3 Nf6 13. b3 e5
+14. fxe5 Nh5 15. Bb2 dxe5 16. Rf3 a5 17. g4 Nf4 18. Rd1 Qg5 19. Bc1
+Bxg4 20. Bxf4 Bxf3+ 0-1
+
+[Site "Glenrothes Congress"]
+[Date "1994.03.??"]
+[Round "27"]
+[White "Hunt, Tom"]
+[Black "Gill, Andy"]
+[Result "1/2-1/2"]
+
+1. Nf3 Nc6 2. g3 e5 3. Nc3 d5 4. d3 Be6 5. Bg2 Qd7 6. Ng5 d4 7. Nce4
+Bf5 8. a3 Be7 9. O-O Bxg5 10. Nxg5 f6 11. Ne4 Bh3 12. Nc5 Qc8 13. Bxh3
+Qxh3 14. Nxb7 Rb8 15. Nc5 h5 16. e4 g5 17. Qf3 g4 18. Qf5 Kf7 19. Bg5
+Nce7 20. Qe6+ Kg6 21. f4 exf4 22. Rxf4 Kxg5 23. Raf1 h4 24. Qf7 hxg3
+25. Ne6+ Kh4 26. hxg3+ Qxg3+ 1/2-1/2
+
+[Site "Glenrothes Congress"]
+[Date "1994.03.??"]
+[Round "28"]
+[White "Gill, Andy"]
+[Black "Husband, Dan"]
+[Result "1-0"]
+
+1. e4 c5 2. Nf3 Nc6 3. d4 Nxd4 4. Nxd4 cxd4 5. Qxd4 e6 6. Nc3 Qb6 7.
+Qxb6 axb6 8. Bb5 Bc5 9. O-O Nf6 10. Be3 O-O 11. Rfe1 d6 12. a4 Bd7 13.
+Bg5 Bc6 14. Bxf6 gxf6 15. Rad1 Kh8 16. Rd3 Rad8 17. Rh3 Rg8 18. Bd3 Rg7
+19. Nb5 Bxb5 20. axb5 Rdg8 21. Rg3 Rxg3 22. hxg3 h6 23. Kf1 Kg7 24. c3
+d5 25. exd5 exd5 26. Ra1 d4 27. Ra7 dxc3 28. bxc3 Rd8 29. Be4 Rd1+ 30.
+Ke2 Rc1 31. Rxb7 Rxc3 32. Kf1 Rb3 33. Rxf7+ Kh8 34. Rxf6 Rxb5 35. Rxh6+
+Kg7 36. Rg6+ Kh7 37. Rxb6+ 1-0
+
+[Site "Glenrothes Congress"]
+[Date "1994.03.??"]
+[Round "29"]
+[White "Chance, Keith"]
+[Black "Gill, Andy"]
+[Result "1/2-1/2"]
+
+1. Nf3 Nc6 2. e4 e5 3. d4 exd4 4. Nxd4 d6 5. Nxc6 bxc6 6. Bd3 Bb7 7.
+O-O Nf6 8. Re1 Be7 9. e5 dxe5 10. Rxe5 O-O 11. h3 Re8 12. Re1 Qd7 13.
+Bg5 Rad8 14. Bxf6 Bxf6 15. Rxe8+ Qxe8 16. Nc3 Ba6 17. Qe1 Qxe1+ 18.
+Rxe1 Bxd3 19. cxd3 g6 20. Rd1 Rb8 21. Ne4 Bxb2 22. Rb1 a5 23. Nc3 Rb4
+24. Nd1 Ba3 25. Rxb4 Bxb4 26. Kf1 f5 27. Nb2 Kf7 28. Nc4 Ke6 29. Ke2
+Kd5 30. a3 Bc5 31. Nxa5 Bxa3 32. Nc4 Bc5 33. f3 h5 34. g4 hxg4 35. hxg4
+fxg4 36. fxg4 Ke6 37. Kf3 Bd6 38. Ke4 g5 39. Na5 c5 40. Nc4 Bf4 41. Na5
+Bd2 42. Nc4 Bb4 43. Ne5 Bd2 44. Nf3 Bc1 45. Ne5 Bf4 46. Ng6 Bg3 47.
+Nf8+ Kd6 48. Nh7 Bf4 49. Kf5 Kd5 50. Nxg5 Bxg5 51. Kxg5 Kd4 52. Kf5
+Kxd3 53. g5 c4 54. g6 c3 55. g7 c2 56. g8=Q c1=Q 57. Qd5+ Ke2 58. Qg2+
+Kd1 59. Qg1+ 1/2-1/2
+
+[Site "Glenrothes Congress"]
+[Date "1994.03.??"]
+[Round "30"]
+[White "Gill, Andy"]
+[Black "King, Jim"]
+[Result "1/2-1/2"]
+
+1. e4 c5 2. Nf3 Nc6 3. d4 cxd4 4. Nxd4 d6 5. Bb5 Qc7 6. O-O a6 7. Ba4
+b5 8. Bb3 Nf6 9. Re1 e6 10. Bg5 Be7 11. c3 O-O 12. Nd2 Bb7 13. Qe2 Rfe8
+14. Rac1 d5 15. Bc2 Rac8 16. e5 Nd7 17. Bxe7 Rxe7 18. N2f3 h6 19. Qd3
+g6 20. Qe3 Kg7 21. Nh4 Ncxe5 22. b3 Qxc3 23. Qxc3 Rxc3 24. Bb1 b4 25.
+Rxc3 bxc3 26. Rc1 g5 27. Nhf3 Nxf3+ 28. Nxf3 g4 29. Nd4 e5 30. Nf5+ Kf6
+31. Nxe7 Kxe7 32. Rxc3 Kd6 33. h3 Nf6 34. hxg4 Nxg4 35. Bf5 Nf6 36. Bc8
+d4 37. Rc4 Bd5 38. Rc2 a5 39. f3 Nh5 40. Ba6 Nf4 41. Rd2 f6 42. Bd3 Bc6
+43. Kf2 h5 44. g3 Ne6 45. a4 Be8 46. Bb5 Bg6 1/2-1/2
+
+[Site "Glenrothes Congress"]
+[Date "1994.03.??"]
+[Round "31"]
+[White "Gourley, R."]
+[Black "Gill, Andy"]
+[Result "1-0"]
+
+1. Nf3 Nc6 2. d4 e6 3. c4 d5 4. Nc3 Bb4 5. e3 Nf6 6. Bd2 O-O 7. Ne5
+Nxe5 8. dxe5 Ne4 9. Nxe4 dxe4 10. Bxb4 c5 11. Bxc5 Qa5+ 12. b4 Rd8 13.
+bxa5 Rxd1+ 14. Rxd1 h6 15. Rd8+ Kh7 16. Be7 b6 17. axb6 axb6 1-0
+
+[Site "Dunfermline Club Championship"]
+[Date "1994.03.??"]
+[Round "32"]
+[White "Gill, Andy"]
+[Black "Glynis, Grant"]
+[Result "1-0"]
+
+1. e4 c5 2. Nf3 d6 3. d4 cxd4 4. Nxd4 Nf6 5. Nc3 a6 6. Bc4 Nc6 7. Nxc6
+bxc6 8. Be3 e6 9. O-O Be7 10. Bb3 O-O 11. Qe2 Bb7 12. Rad1 Qc7 13. f4
+e5 14. Kh1 Rfd8 15. Qf3 Qc8 16. fxe5 dxe5 17. Qg3 Rxd1 18. Nxd1 Qg4
+19. Qxe5 Qxe4 20. Qxe4 Nxe4 21. Rxf7 Nd6 22. Rxe7+ Kh8 23. Re5 Rf8 24.
+Kg1 h6 25. Bc5 Rf6 26. c3 a5 27. g3 Ba6 28. Bc2 g5 29. Bd4 Kg8 30. Rxa5
+Rf1+ 31. Kg2 Rf8 32. Rxa6 Nc4 33. Rxc6 Na5 34. Rxh6 Rf7 35. Rh8# 1-0
+
+[Site "Dunfermline Club Championship"]
+[Date "1994.03.??"]
+[Round "33"]
+[White "Welshman, Alistair"]
+[Black "Gill, Andy"]
+[Result "0-1"]
+[ECO "B20"]
+
+1. e4 c5 2. Bc4 d6 3. Nc3 Nf6 4. Nf3 e6 5. O-O Be7 6. d3 O-O 7. Bg5 Nc6
+8. Bxf6 Bxf6 9. Bb5 Bd7 10. Bxc6 Bxc6 11. Qe2 Re8 12. Rae1 Bxc3 13.
+bxc3 Qa5 14. e5 d5 15. d4 Bb5 16. Qe3 Bxf1 17. Rxf1 cxd4 18. Qxd4 Rac8
+19. Qb4 Qxb4 20. cxb4 Rxc2 21. Ra1 Rec8 22. Kf1 Rc1+ 23. Rxc1 Rxc1+
+24. Ke2 Rc2+ 25. Nd2 Rxa2 26. g4 Rb2 0-1
+
+[Site "Dunfermline Club Championship"]
+[Date "1994.03.??"]
+[Round "34"]
+[White "Taylor, Robin"]
+[Black "Gill, Andy"]
+[Result "1-0"]
+[ECO "C02"]
+[WhiteElo "1610"]
+
+1. d4 e6 2. e4 d5 3. e5 c5 4. c3 Nc6 5. Nf3 Bd7 6. Bf4 cxd4 7. cxd4
+Bb4+ 8. Bd2 Bxd2+ 9. Qxd2 Nge7 10. Nc3 a6 11. a3 Qc7 12. Bd3 O-O-O 13.
+O-O Rdf8 14. b4 f6 15. b5 Nxd4 16. Nxd4 Qxe5 17. bxa6 Qxd4 18. axb7+
+Kb8 19. Ne2 Qa7 20. Qb4 Nf5 21. Bxf5 exf5 22. Qd6+ Kxb7 23. Rab1+ Kc8
+24. Rfc1+ Kd8 25. Rb8+ Qxb8 26. Qxb8+ Ke7 27. Qb4+ Kf7 28. f4 Rc8 29.
+Rxc8 Rxc8 30. Qd6 Be6 31. Nd4 Rc1+ 32. Kf2 Rd1 33. Qxe6+ Kf8 34. Nxf5
+Rd2+ 35. Ke3 1-0
+
+[Site "Dunfermline C vs Stirling A"]
+[Date "1994.03.??"]
+[Round "35"]
+[White "Smith, Steve"]
+[Black "Gill, Andy"]
+[Result "1-0"]
+[ECO "B92"]
+[WhiteElo "1745"]
+
+1. e4 c5 2. Nf3 d6 3. d4 cxd4 4. Nxd4 Nf6 5. Nc3 a6 6. Be2 e5 7. Nb3
+Be7 8. O-O O-O 9. a4 Be6 10. f4 Bxb3 11. cxb3 Nc6 12. Be3 Qd7 13. Bc4
+Rad8 14. f5 Kh8 15. Qf3 Nb4 16. Rfd1 Nc2 17. Rac1 Nxe3 18. Qxe3 Qc6
+19. Nd5 Nxd5 20. Bxd5 Qd7 21. Qb6 Rb8 22. Rc7 Bd8 23. Rxd7 Bxb6+ 24.
+Kf1 f6 25. Bxb7 Bd4 26. Rc1 Bxb2 27. Rcc7 Rg8 28. Bxa6 h5 29. Bc4 Rgc8
+30. Rxg7 Rxc7 31. Rxc7 Bd4 32. Rf7 Rg8 33. Rxf6 Rg4 34. Bd5 Rf4+ 35.
+Ke1 Bc3+ 36. Ke2 Bd4 37. Rh6+ Kg7 38. Rxh5 Rf2+ 39. Kd3 Rxg2 40. Kc4
+Bg1 41. h4 Rc2+ 42. Kd3 Rg2 43. Rg5+ Rxg5 44. hxg5 Bb6 45. Kc4 Bd8 46.
+f6+ Kg6 47. f7 Be7 1-0
+
+[Site "Dunfermline Club Championship"]
+[Date "1994.04.??"]
+[Round "36"]
+[White "Gill, Andy"]
+[Black "Bill, Phillips"]
+[Result "0-1"]
+[ECO "C10"]
+
+1. e4 e6 2. d4 d5 3. Nc3 c5 4. e5 Nc6 5. Nf3 Qb6 6. Bb5 Bd7 7. Bxc6
+Bxc6 8. O-O Ne7 9. dxc5 Qxc5 10. Be3 Qa5 11. Qd3 Nf5 12. Nd4 Nxe3 13.
+Nxc6 bxc6 14. Qxe3 Bc5 15. Qd3 O-O 16. a3 Qc7 17. b4 Bb6 18. Rfe1 a6
+19. Na4 Rfb8 20. Nxb6 Rxb6 21. c4 dxc4 22. Qxc4 Rb5 23. Qe4 Rd5 24.
+Rad1 Rad8 25. Rxd5 cxd5 26. Qd4 Rc8 27. f4 g6 28. Re3 h5 29. Kf2 Qc2+
+30. Kf3 Rc4 31. Qd3 Qc1 32. Qe2 d4 33. Rd3 Rc3 34. Ke4 Rxa3 35. Rxa3
+Qxa3 36. Qc4 Qe3# 0-1
+
+[Site "Edinburgh Congress"]
+[Date "1994.04.??"]
+[Round "37"]
+[White "Gill, Andy"]
+[Black "Watt, Andrew"]
+[Result "0-1"]
+[ECO "C97"]
+
+1. e4 e5 2. Nf3 Nc6 3. Bb5 a6 4. Ba4 Nf6 5. O-O Be7 6. Re1 b5 7. Bb3 d6
+8. c3 O-O 9. h3 Na5 10. Bc2 c5 11. d4 Qc7 12. b4 cxb4 13. cxb4 Nc4 14.
+Nbd2 Bb7 15. Nxc4 Qxc4 16. dxe5 dxe5 17. a3 Rac8 18. Bd3 Qc3 19. Bg5
+Rfd8 20. Re3 Bxe4 21. Rc1 Qxc1 22. Qxc1 Rxc1+ 23. Re1 Rxe1+ 24. Nxe1
+Bxd3 25. Nf3 Be4 26. Nxe5 Rd1+ 27. Kh2 Bd6 28. f4 h6 29. Bh4 g5 30. Bg3
+Bxe5 31. fxe5 Nh5 32. e6 Nxg3 33. e7 Nf1+ 34. Kg1 Bc6 35. Kf2 f6 36.
+Ke2 Ra1 37. Kd3 Kf7 0-1
+
+[Site "Edinburgh Congress"]
+[Date "1994.04.??"]
+[Round "38"]
+[White "Milne, Jake"]
+[Black "Gill, Andy"]
+[Result "0-1"]
+[ECO "B50"]
+
+1. e4 c5 2. Nf3 d6 3. Bc4 e6 4. d3 Nf6 5. a3 Nc6 6. Nc3 Be7 7. O-O O-O
+8. Be3 b6 9. h3 Bb7 10. Ne2 d5 11. exd5 exd5 12. Ba2 Re8 13. c3 Qc7
+14. Bf4 Bd6 15. Bxd6 Qxd6 16. d4 cxd4 17. Nexd4 Nxd4 18. Nxd4 Rad8 19.
+Qd2 Ba6 20. Qg5 Re5 21. Nf5 Rxf5 22. Qxf5 Bxf1 23. Rxf1 g6 24. Qf3 Kg7
+25. Rd1 Qe5 26. g3 a5 27. Kg2 h5 28. h4 Rd6 29. Bb1 d4 30. Qd3 Qd5+
+31. Qf3 Qb3 32. Qe2 Qd5+ 33. f3 Qe6 34. Qxe6 Rxe6 35. Be4 dxc3 36. bxc3
+Nxe4 37. fxe4 Rxe4 38. Rd6 Re2+ 39. Kf3 Rb2 40. Rd3 a4 41. Ke4 f5+ 42.
+Kd5 Re2 43. c4 Re8 44. Kc6 Rc8+ 45. Kxb6 Rxc4 46. Kb5 Rg4 47. Rd7+ Kf6
+48. Ra7 f4 49. gxf4 Rxf4 50. Rxa4 Rxa4 51. Kxa4 g5 52. hxg5+ Kxg5 53.
+Kb5 h4 54. a4 h3 55. a5 h2 56. a6 h1=Q 57. Kb6 Qb1+ 58. Ka7 Kf5 59. Ka8
+Qe4+ 60. Kb8 Qe8+ 61. Kb7 Qd7+ 62. Kb6 Qd8+ 63. Kb7 Qd5+ 64. Kb6 Qa8
+65. Ka5 Ke5 66. Kb6 Kd5 67. Ka5 Kc5 68. Ka4 Qxa6+ 69. Kb3 Qc4+ 70. Ka3
+Qb5 71. Ka2 Kc4 72. Ka1 Kc3 0-1
+
+[Site "Edinburgh Congress"]
+[Date "1994.04.??"]
+[Round "39"]
+[White "Gill, Andy"]
+[Black "Bourke, John"]
+[Result "0-1"]
+[ECO "C54"]
+
+1. e4 e5 2. Nf3 Nc6 3. Bc4 Bc5 4. c3 Nf6 5. d4 exd4 6. cxd4 Bb4+ 7. Bd2
+Nxe4 8. Bxb4 Nxb4 9. Bxf7+ Kxf7 10. Qb3+ d5 11. Qxb4 Re8 12. O-O Kg8
+13. Nc3 b6 14. Rfe1 Bf5 15. Qb3 c6 16. Rac1 Qd6 17. Re3 Nxc3 18. Qxc3
+Rxe3 19. Qxe3 Rc8 20. Re1 h6 21. Qe7 Qxe7 22. Rxe7 a5 23. Rb7 b5 24.
+Ne5 c5 25. Rxb5 cxd4 26. f4 Be4 27. Rxa5 Rc1+ 28. Kf2 Rc2+ 29. Kg3
+Rxg2+ 30. Kh3 Rxb2 31. Ra3 Rd2 32. Kg3 Rg2+ 33. Kh3 Rd2 34. Kg3 d3 35.
+Nf3 Rb2 36. h4 d2 37. Nxd2 Rxd2 38. Kg4 Rd3 39. Rxd3 Bxd3 40. Kf3 Bc4
+41. a4 Kf7 42. Ke3 Ke6 43. Kd4 Kf5 44. a5 Kxf4 45. a6 Bxa6 46. Kxd5 Kg4
+47. Ke6 Kxh4 48. Kf7 g5 0-1
+
+[Site "Edinburgh Congress"]
+[Date "1994.04.??"]
+[Round "40"]
+[White "Gill, Andy"]
+[Black "King, David"]
+[Result "1-0"]
+[ECO "C70"]
+
+1. e4 e5 2. Nf3 Nc6 3. Bb5 a6 4. Ba4 b5 5. Bb3 Bc5 6. O-O Nge7 7. c3 d6
+8. d4 exd4 9. cxd4 Ba7 10. Be3 Na5 11. Bc2 O-O 12. Nbd2 f5 13. Bg5 Qe8
+14. Re1 h6 15. Bxe7 Qxe7 16. exf5 Qf6 17. Be4 Bb7 18. Bxb7 Nxb7 19.
+Qb3+ Kh8 20. Qd5 Rab8 21. Rac1 Bb6 22. g4 Nd8 23. Ne4 Qf7 24. Qxf7 Rxf7
+25. h3 {At this point the score sheet goes wrong. Black eventually
+looses on time!} 1-0
+
+[Site "Edinburgh Congress"]
+[Date "1994.04.??"]
+[Round "41"]
+[White "Tait, C."]
+[Black "Gill, Andy"]
+[Result "1-0"]
+[ECO "D20"]
+
+1. d4 d5 2. c4 dxc4 3. e4 c6 4. Bxc4 e6 ( 4... Nf6 5. Nc3 e5 6. Be3 exd4
+7. Bxd4 Bd6 8. f3 { Score: 0.22 } ) 5. Nf3 Bb4+ ( 5... Nf6 6. Qe2 Bb4 7. Bd2
+Qb6 8. Nc3 O-O 9. O-O Nbd7 { Score: 0.25 } ) 6. Bd2 Bxd2+ 7. Qxd2 ( 7. Nbxd2
+Nf6 8. O-O O-O 9. Rc1 Nbd7 10. Qe2 c5 11. Bd3 { Score: 0.41 } ) 7... Nf6 8. Nc3
+O-O ( 8... Nbd7 9. O-O O-O 10. Rad1 Qe7 11. Rfe1 e5 { Score: 0.38 } ) 9. O-O b6
+10. e5 ( 10. Rac1 Bb7 11. Rfd1 c5 12. dxc5 Qxd2 13. Rxd2 bxc5 { Score: 0.28 } )
+10... Nfd7 ( 10... Nd5 11. Rfd1 Ba6 12. Bxa6 Nxa6 13. Rac1 Nac7 14. Nxd5 cxd5 {
+Score: 0.28 } ) 11. Rfd1 Ba6 ( 11... Bb7 12. Ne4 c5 13. d5 b5 14. Bxb5 Bxd5
+15. Qe3 Qe7 { Score: 0.34 } ) 12. Bb3 ( 12. Bxa6 Nxa6 13. Rac1 Qe7 14. Ne4 c5
+15. Qe2 Nb4 16. dxc5 { Score: 0.34 } ) 12... Re8 ( 12... h6 13. Rac1 Qe7
+14. Ne4 Rd8 15. Nd6 Nf6 16. Qe3 { Score: 0.31 } ) 13. Ne4 c5 ( 13... h6 14. Nd6
+Re7 15. Rac1 c5 16. Bc2 Nc6 17. Be4 Qc7 { Score: 0.44 } ) 14. Nd6 ( 14. dxc5
+Bb7 15. Qe3 Re7 16. Nd6 Bc6 17. Ne4 bxc5 18. Nxc5 { Score: 1.25 } ) 14... Rf8 (
+14... Re7 15. Nxf7 Rxf7 16. Bxe6 cxd4 17. Bd5 Nc6 18. Bxc6 { Score: 0.44 } )
+15. d5 b5 ( 15... Qe7 16. Nxf7 c4 17. dxe6 Nxe5 18. N3xe5 cxb3 19. Qd5 { Score:
+1.06 } ) 16. dxe6 fxe6 ( 16... c4 17. Nxf7 Qb6 18. exd7 Nxd7 19. Qxd7 Rxf7
+20. Qd5 { Score: 3.75 } ) 17. Bxe6+ Kh8 18. Nf7+ ( 18. Qd5 Qe7 19. Nf7 Rxf7
+20. Bxf7 h6 { Score: 4.56 } ) 18... Rxf7 19. Bxf7 Nc6 ( 19... Bb7 20. Ng5 h6
+21. Bd5 { Score: 3.03 } ) 20. e6 ( 20. Qxd7 Nd4 21. Qg4 Qe7 22. Nxd4 Qxf7
+23. e6 Qf6 { Score: 5.84 } ) 20... Qe7 ( 20... Nf6 21. Rac1 c4 22. b3 Qxd2
+23. Rxd2 Rd8 24. Rxd8 Nxd8 { Score: 3.06 } ) 21. Qxd7 Bc8 ( 21... Bb7 22. Qxe7
+Nxe7 23. Rd7 Bxf3 24. gxf3 Nc6 25. e7 Nxe7 { Score: 7.41 } ) 22. Qxc6 (
+22. Qxe7 Bxe6 23. Qxe6 Nd4 24. Nxd4 cxd4 25. Rxd4 a6 { Score: 17.72 } )
+22... Rb8 ( 22... Bb7 23. Qd7 Qxd7 24. exd7 Rd8 25. Re1 g6 26. Re8 Kg7 { Score:
+10.66 } ) 23. Qe8+ ( 23. Qxc5 Bxe6 24. Qxe7 Bxf7 25. Qxa7 Rf8 26. Qxf7 Rc8 {
+Score: 18.22 } ) 23... Qxe8 24. Bxe8 Bb7 ( 24... Bxe6 25. Bd7 Bg8 26. Ne5 g6
+27. Rac1 c4 28. a4 bxa4 { Score: 7.88 } ) 25. Bf7 ( 25. Bxb5 Bxf3 26. gxf3 Kg8
+27. e7 Kf7 28. Rd8 Kxe7 29. Rxb8 { Score: 12.03 } ) 25... Bc6 ( 25... g5 26. e7
+Kg7 27. Rd8 Bc6 28. Rxb8 Kxf7 29. Ne5 Kxe7 { Score: 12.03 } ) 26. Rd2 ( 26. Ne5
+Bxg2 27. e7 g6 28. Kxg2 { Score: 15.75 } ) 1-0
+
+[Site "Dunfermline C vs Alloa"]
+[Date "1994.04.??"]
+[Round "42"]
+[White "Comrie, J."]
+[Black "Gill, Andy"]
+[Result "1-0"]
+[ECO "B50"]
+
+1. e4 c5 2. Nf3 d6 3. Bc4 e6 4. Nc3 Be7 5. d4 cxd4 6. Qxd4 Nf6 7. e5
+dxe5 8. Qxd8+ Bxd8 9. Nxe5 O-O 10. O-O Nbd7 11. Nxd7 Bxd7 12. Be3 a6
+13. a4 Ba5 14. Ne2 Bc6 15. Nd4 Nd5 16. Nxc6 bxc6 17. Bxd5 cxd5 18. c3
+Rab8 19. b4 Bc7 20. Rfd1 Rfd8 21. Rac1 Bb6 22. Kf1 Bxe3 23. fxe3 f5
+24. Rc2 g5 25. Kf2 Kf7 26. Kf3 Rdc8 27. g4 Rxb4 28. gxf5 Kf6 29. fxe6
+Kxe6 30. Rd4 Rxd4 31. exd4 Rf8+ 32. Kg4 h6 33. Re2+ Kd6 34. Rb2 Rc8
+35. Kh5 Rxc3 36. Rb6+ Rc6 37. Rxc6+ Kxc6 38. Kxh6 g4 39. Kg5 Kd6 40.
+Kxg4 Ke6 41. Kg5 Ke7 42. h4 Kf7 43. h5 Kg7 44. Kf5 1-0
+
+[Site "Dunfermline Club Championship"]
+[Date "1994.04.??"]
+[Round "43"]
+[White "Gill, Andy"]
+[Black "Hunter, Scott"]
+[Result "1-0"]
+[ECO "C65"]
+
+1. e4 e5 2. Nf3 Nc6 3. Bb5 Nf6 4. d3 Bc5 5. O-O O-O 6. Re1 d5 7. Be3
+Bxe3 8. exd5 Qxd5 9. Bxc6 Qxc6 10. Rxe3 e4 11. dxe4 Nxe4 12. Nc3 Nxc3
+13. Rxc3 Qd6 14. Qxd6 cxd6 15. Rd1 Re8 16. Rxd6 g5 17. g4 Bxg4 18. Nxg5
+Re1+ 19. Kg2 Rae8 20. Rg3 f5 21. h3 Be2 22. Nf3+ Kf7 23. Nxe1 f4 24.
+Rf3 Bxf3+ 25. Nxf3 Re2 26. Rd7+ Kf8 27. Rxb7 Rxc2 28. Rxa7 Rxb2 29. Ra4
+Kf7 30. Rxf4+ Kg6 31. a4 h5 32. h4 Ra2 33. Kg3 Ra3 34. Rc4 Rd3 35. Kf4
+Rd5 36. Ne5+ Kf6 37. Re4 Ra5 38. Nd7+ Kg6 39. f3 Rf5+ 40. Ke3 1-0
+
+[Site "Under 1500 Final"]
+[Date "1994.05.??"]
+[Round "44"]
+[White "Hepburn, James"]
+[Black "Gill, Andy"]
+[Result "1-0"]
+[ECO "B20"]
+
+1. e4 c5 2. Bc4 d6 3. d3 e6 4. Nc3 Nf6 5. Nf3 a6 6. Bd2 Nc6 7. O-O Be7
+8. Re1 O-O 9. a3 e5 10. h3 b5 11. Bb3 Bb7 12. Nd5 Nxd5 13. Bxd5 Qd7
+14. c3 Na5 15. b4 Bxd5 16. exd5 Nb7 17. Re4 f5 18. Re2 cxb4 19. axb4
+Bf6 20. Qb3 a5 21. Rae1 axb4 22. cxb4 Rfe8 23. Bg5 Bxg5 24. Nxg5 Nd8
+25. f4 Nf7 26. Nxf7 Qxf7 27. fxe5 dxe5 28. Rxe5 Rxe5 29. Rxe5 Ra1+ 30.
+Kh2 g5 31. d4 Kg7 32. Qd3 Qd7 33. Rxf5 Qd6+ 34. Re5 Qxb4 35. Rxg5+ Kf7
+36. Qxh7+ Kf6 37. Qh6+ Ke7 38. Rg7+ Kd8 39. Qh8+ 1-0
+
+
+[Site "East of Scotland Championship"]
+[Date "1994.05.??"]
+[Round "45"]
+[White "Heron, D."]
+[Black "Gill, Andy"]
+[Result "1-0"]
+[ECO "D02"]
+[WhiteElo "1790"]
+
+1. Nf3 Nc6 2. d4 d5 3. Bf4 Bf5 4. e3 a6 5. c4 e6 6. Nc3 Nf6 7. a3 Qd7
+8. b4 Bd6 9. Bxd6 Qxd6 10. Be2 O-O 11. O-O Ne4 12. Nxe4 Bxe4 13. Nd2
+Bg6 14. Qb3 Ne7 15. c5 Qd7 16. a4 c6 17. b5 Nf5 18. Ra3 Rfe8 19. Qb2
+Kh8 20. Rb3 Nh6 21. bxc6 bxc6 22. Rb7 Qc8 23. Nf3 Rb8 24. Bxa6 Rxb7
+25. Qxb7 Qxb7 26. Bxb7 f6 27. Bxc6 Rb8 28. Bb5 Bc2 29. Rc1 Be4 30. Nd2
+Bg6 31. Nb1 Ng8 32. Nc3 Ne7 33. a5 Nc8 34. Bd7 Bf5 35. Nxd5 exd5 36.
+Bxf5 Ne7 37. Bd3 Nc6 38. Rb1 Rxb1+ 39. Bxb1 Nxa5 40. Ba2 1-0
+
+[Site "East of Scotland Chalengers"]
+[Date "1994.05.??"]
+[Round "46"]
+[White "Gill, Andy"]
+[Black "Falconer, W."]
+[Result "1/2-1/2"]
+[ECO "A15"]
+
+1. c4 Nf6 2. d3 e6 3. Nf3 d5 4. cxd5 Nxd5 5. a3 Bd6 6. e3 Nc6 7. Nbd2
+O-O 8. Nc4 Bd7 9. Be2 b5 10. Nxd6 cxd6 11. O-O Rc8 12. Bd2 Qb6 13. Qb3
+Ne5 14. Rac1 a6 15. Rc2 Rxc2 16. Qxc2 Rc8 17. Qb1 Nxf3+ 18. Bxf3 Bc6
+19. Rc1 Qd8 20. Bxd5 Bxd5 21. Ba5 Qd7 22. Rxc8+ Qxc8 23. Bb4 Qc6 24. f3
+Bb3 25. Qe1 Qc2 26. Qc3 Qxc3 27. Bxc3 d5 28. Kf2 f6 29. d4 1/2-1/2
+
+
+
+[Site "East of Scotland Chalengers"]
+[Date "1994.05.??"]
+[Round "47"]
+[White "Gill, Andy"]
+[Black "Pearson, Walter"]
+[Result "0-1"]
+[ECO "A20"]
+[BlackElo "1650"]
+
+1. c4 e5 2. d3 Ne7 3. Nf3 d6 4. e3 g6 5. Be2 Bg7 6. O-O O-O 7. Nbd2 Nd7
+8. Nb3 b6 9. d4 exd4 10. Nfxd4 Bb7 0-1
+
+[Site "East of Scotland Chalengers"]
+[Date "1994.05.??"]
+[Round "48"]
+[White "Heatlie, Douglas"]
+[Black "Gill, Andy"]
+[Result "1-0"]
+[ECO "D61"]
+[WhiteElo "1650"]
+
+1. d4 e6 2. c4 d5 3. Nc3 Nf6 4. Bg5 Be7 5. e3 Nbd7 6. Qc2 O-O 7. Nf3
+Re8 8. h4 Nb6 9. b3 dxc4 10. bxc4 Bd7 11. Bd3 g6 12. Bxf6 Bxf6 13. h5
+Bxd4 14. exd4 Qf6 15. hxg6 fxg6 16. Ne4 Qg7 17. Nc5 Bc6 18. Ne5 Nd5
+19. cxd5 exd5 20. O-O-O Rxe5 21. dxe5 Qxe5 22. g3 Qg5+ 23. Qd2 Qe5 24.
+Nb3 Ba4 25. Qh6 Qc3+ 26. Bc2 Bxb3 27. Qxh7+ Kf8 28. Qh8+ 1-0
+
+[Site "Scottish Chess Minor"]
+[Date "1994.07.??"]
+[Round "49"]
+[White "Mill, Graham"]
+[Black "Gill, Andy"]
+[Result "1-0"]
+[ECO "B50"]
+
+1. e4 c5 2. Nf3 d6 3. Bc4 { This is an unusual way of opening, but is common at
+the Minor level. } 3... e6 4. Nc3 Nf6 5. d3 ( 5. O-O ) 5... Nc6 ( 5... d5
+6. Bb3 dxe4 7. Nxe4 Nxe4 8. dxe4 Qxd1+ 9. Kxd1 { = } ) 6. Bf4 ( 6. O-O Be7 )
+6... a6 7. O-O Be7 ( 7... Na5 8. Bb3 Nxb3 9. axb3 Be7 10. Re1 O-O 11. Qd2 {
+<sab> } ) 8. Re1 O-O {  I often find this sort of position when playing the
+sicilian, where white has the e file, pushes his pawn, and gains a winning
+advantage. } 9. e5 dxe5 10. Nxe5 Bd7 ( 10... Nxe5 ) 11. Ne4 ( 11. Bb3 { <saw> }
+) 11... Nxe5 12. Bxe5 Bc6 {  } ( 12... Nxe4 13. dxe4 b5 14. Bb3 Bc6 15. Qh5
+Re8 { = } ) 13. Bxf6 ( 13. Qf3 Nxe4 14. dxe4 b6 15. Rad1 Qe8 { <saw> } )
+13... Bxe4 $4 ( 13... Bxf6 14. Nxf6+ Qxf6 15. c3 b6 16. Qe2 { <sab> } )
+14. Bxe7 Qxe7 15. Rxe4 Rac8 16. f4 ( 16. a4 Qf6 17. c3 Rfd8 18. Qe2 h6 19. Re1
+{ <waw> } ) 16... b5 17. Bb3 Rc6 ( 17... a5 { and I might be able to stir up a
+queenside pawn charge. } ) 18. c4 ( 18. a4 { striking at the ambushing pawns. }
+) 18... Rd8 ( 18... Rd6 19. cxb5 axb5 20. a4 c4 ) 19. Qe2 ( 19. cxb5 axb5
+20. a4 bxa4 21. Raxa4 Rcd6 22. d4 cxd4 23. Rexd4 ) 19... Rd4 ( 19... b4 )
+20. Rxd4 ( 20. cxb5 axb5 21. a4 bxa4 22. Rxa4 Rd8 23. d4 cxd4 24. Rexd4 { All
+variations just win for white. } ) 20... cxd4 21. Re1 ( 21. cxb5 ) 21... Rc5
+22. Qe4 ( 22. Qf2 bxc4 23. Bxc4 Qd6 { Blacks score is rapidly going down. } )
+22... Rh5 ( 22... Qd7 23. Qa8+ Qc8 24. Qxc8+ Rxc8 25. g3 bxc4 26. dxc4 { a
+passed pawn for white! Blacks passed pawn will not live long. } ) 23. g4 (
+23. f5 Rh6 24. cxb5 axb5 { Totally won for white. } ) 23... Rh4 24. Qa8+ Qf8
+25. Qxf8+ Kxf8 {  } 26. h3 $2 ( 26. Bd1 Rh3 27. Be2 Ke7 28. Kg2 Re3 29. h3 Kd6
+{ Just a piece up. } ) 26... Rxh3 27. Bc2 Rg3+ 28. Kf2 Rxg4 29. Kf3 h5 (
+29... Rh4 30. Kg3 Rh6 31. Re4 Rg6+ 32. Kh3 Rh6+ 33. Kg2 { And black has drawing
+chances. } ) 30. Re4 ( 30. Re5 g6 31. Re4 Rh4 32. Rxd4 g5 { Black is only a
+pawn or so down. } ) 30... Ke7 31. Rxd4 ( 31. cxb5 axb5 32. Re5 g6 33. Rxb5 Kd6
+34. Ke4 ) 31... e5 ( 31... g5 32. cxb5 axb5 33. a4 e5 34. Re4 Rxf4+ 35. Rxf4
+exf4 { Blacks is a `pawn` down, with 3 connected passed pawns. Not so bad, but
+still winning for white. } ) 32. Re4 Rxf4+ 33. Rxf4 exf4 34. Kxf4 Kf6 35. c5
+Ke7 36. b4 f6 37. d4 g5+ 38. Kg3 h4+ 39. Kg4 Ke6 40. c6 Kd6 41. d5 Kc7 42. Be4
+Kd6 43. Bg2 Kc7 44. Bh3 Kd6 45. Kf5 Kc7 46. Kxf6 Kb6 47. Kxg5 { I finally
+resigned here. } 1-0
+
+[Site "Scottish Chess Minor"]
+[Date "1994.07.??"]
+[Round "50"]
+[White "Gill, Andy"]
+[Black "McMonigle, A."]
+[Result "1-0"]
+[ECO "C67"]
+
+1. e4 e5 2. Nf3 Nc6 3. Bb5 Nf6 4. O-O Nxe4 {  } 5. Re1 ( 5. d4 Be7 6. dxe5 O-O
+7. Be3 a6 { and white has the edge. } ) 5... d5 ( 5... Nd6 6. Bxc6 dxc6 7. Nxe5
+Be6 8. Nc3 Be7 9. Kh1 { <saw> } ) 6. Nxe5 ( 6. d3 { is a killer move. } )
+6... Qf6 7. Nf3 ( 7. Nxc6 bxc6 8. Qf3 Qg6 9. Bd3 Bf5 10. Bxe4 { <saw> } )
+7... Be7 8. d3 $1 Nd6 {  } ( 8... Nxf2 9. Kxf2 Bg4 10. Nbd2 O-O 11. Bxc6 bxc6
+{ <aw> } ) 9. Bxc6+ ( 9. Bg5 Qxb2 10. Bxc6+ bxc6 11. Rxe7+ Kf8 12. Nbd2 h6 {
+White is a couple of pawns up, but the tactices are hairy! } ) 9... bxc6 10. c3
+O-O {  } ( 10... h6 11. Be3 Nf5 12. Bf4 Rb8 13. Be5 Qg6 { <saw> } ) 11. Bg5
+Qg6 ( 11... Qxf3 12. Qxf3 Bxg5 13. b3 Bb7 14. Qg3 Bf6 { Is blacks best line. }
+) 12. Bxe7 Re8 13. Bxd6 Rxe1+ 14. Qxe1 Qxd6 15. Qe8+ Qf8 16. Qxf8+ ( 16. Qxc6
+Rb8 17. Qxc7 Rxb2 18. Qxa7 Bf5 19. Qd4 Qb8 20. Nfd2 { <waw> The proper
+continuation, and well winning for white. } ) 16... Kxf8 17. Ne5 ( 17. h3 {
+Still a <waw> } ) 17... Bf5 ( 17... c5 18. h3 f6 19. Nf3 { and white moving the
+knight was a waste of two tempi. } 19... Rb8 20. b3 Bf5 { <waw> } ) 18. d4 (
+18. Nd2 Re8 19. Ndf3 c5 20. g4 f6 21. Kg2 fxe5 22. gxf5 { <waw> } ) 18... Re8
+19. Nd2 Re6 {  } 20. Re1 ( 20. g4 Bxg4 21. Nxg4 Rg6 22. h3 h5 23. f3 hxg4
+24. hxg4 { <waw> what a cou. } ) 20... f6 21. Nd7+ Ke7 22. Rxe6+ Bxe6 23. Nc5
+Bf5 24. f3 ( 24. h3 h6 25. Kh2 Kd6 26. Nb7+ Ke7 27. g4 Bd3 { <waw> } )
+24... Bc8 25. g4 ( 25. Kf2 Kd6 26. f4 g6 27. Kf3 h6 28. g3 f5 ) 25... Kf7
+26. Kg2 ( 26. Kf2 Ke7 27. Ke3 Kd6 28. Kd3 h6 29. c4 dxc4+ 30. Nxc4+ { <waw>
+with a plan } ) 26... f5 27. Kg3 Kg6 28. Nd3 ( 28. gxf5+ Bxf5 29. Na6 Kf6
+30. h3 h6 31. Nxc7 { Attacking the weak backwards pawn. } ) 28... fxg4 {  } (
+28... Kf6 29. gxf5 Kxf5 30. Ne5 Bb7 { Score: 3.19 } ) 29. Ne5+ Kf6 30. Nxc6 a6
+31. fxg4 g5 32. h4 ( 32. Nb3 Bb7 33. Nb8 h6 34. Nc5 Bc8 35. b4 Kg6 36. Nbxa6 {
+Successfully ganing up on the `a` pawn. } ) 32... gxh4+ 33. Kxh4 Bd7 34. g5+ (
+34. Nb4 c6 35. Nxa6 h6 36. Kh5 Kg7 { Totally won. } ) 34... Kg7 35. Ne5 (
+35. Nb4 c6 36. Nxa6 h6 37. Nc5 Bf5 38. a4 Kg6 39. gxh6 { And either the 'a' or
+'b' pawn will queen. } ) 35... Be8 36. Nb3 Bg6 { At this point black resigned.
+} 1-0
+
+[Site "Scottish Chess Minor"]
+[Date "1994.07.??"]
+[Round "51"]
+[White "Swanson, Brian"]
+[Black "Gill, Andy"]
+[Result "1-0"]
+[ECO "B86"]
+1. e4 c5 2. Nf3 d6 3. d4 cxd4 4. Nxd4 Nf6 5. Nc3 a6 6. Bc4 e6 ( 6... e5 7. Nf3
+Qc7 8. Bd5 Bg4 9. O-O Nxd5 10. Nxd5 { Is another line of the Sicilian. } )
+7. Bg5 ( 7. O-O Qc7 8. Qd3 e5 9. Nf3 Bg4 10. Bg5 { <saw>,0.25 } ) 7... Be7
+8. f4 b5 {  } ( 8... d5 9. Bxf6 Bxf6 10. exd5 Qc7 11. Be2 Qxf4 { <ab> } )
+9. Bd3 $2 ( 9. Bb3 h6 10. Bxf6 Bxf6 11. O-O Bxd4+ 12. Qxd4 { <sab> } ) 9... Bb7
+10. b4 ( 10. Qf3 Qb6 11. Nde2 d5 { = } ) 10... Nc6 11. Nf3 $2 ( 11. Nxc6 Bxc6
+12. O-O d5 13. exd5 Nxd5 14. Bxe7 Qxe7 { <sab> } ) 11... Nxb4 12. Qe2 O-O
+13. O-O ( 13. a3 Qc7 14. Qd2 { <ab>,by a pawn or so. } ) 13... Rc8 ( 13... Qc7
+14. Qd2 d5 15. Bxf6 Bxf6 { <ab> } ) 14. Nd1 d5 15. exd5 ( 15. e5 Ne4 16. Bxe7
+Qxe7 17. Bxe4 dxe4 18. Nd4 ) 15... Bxd5 16. Ne3 {  } 16... Bc5 ( 16... Bxa2
+17. Rad1 Nxd3 18. cxd3 Nd5 { <wab>,2+ pawns up, but getting a bit tactical. } )
+17. Kh1 Bxe3 18. Qxe3 Nxc2 19. Bxc2 Rxc2 20. a4 Ra2 ( 20... h6 { <wab>, just
+winning. } ) 21. Rxa2 Bxa2 22. axb5 ( 22. Ra1 Bd5 23. axb5 axb5 24. Rb1 Ng4 {
+<wab>, to or so pawns up. } ) 22... Bc4 ( 22... axb5 23. Ra1 Bd5 24. Ra7 h6 {
+<ab>, even with the rook on blacks 2nd. This rook should be able to get to 'b'
+pawn, though. } ) 23. Rc1 Bxb5 24. Ne5 {  } 24... Nd5 $2 { A bit wild. } (
+24... h6 25. Bxf6 Qxf6 26. Rc7 a5 27. Qc5 Be2 28. Qxa5 Qxf4 { <wab>, almost
+three pawns up, and threating the forced queen exchage on f1. } ) 25. Qg3 {
+Alarms bells !!!, the bishop is going to h6. Remember. } 25... f6 { I though I
+was going to win a piece for a pawn. } 26. Bh6 g6 $4 ( 26... Qe7 27. Nc6 Qc7
+28. Rc2 Ba4 29. Rc4 Nb6 { Black still leads (two pawns up), but the tactics are
+hairy. } ) 27. Bxf8 $2 ( 27. Nxg6 Kf7 28. Nxf8 Ke8 29. Nxe6 Qd7 30. Re1 {
+<waw>,5.47 } ) 27... fxe5 ( 27... Kxf8 28. Qh4 a5 29. g3 a4 { <sab>, but
+critically depending on the weak a pawn. } ) 28. Bh6 exf4 29. Qe1 {  } (
+29. Bxf4 Nxf4 30. Qxf4 a5 31. h3 g5 32. Qe5 { <aw> } ) 29... g5 $4 { My major
+blunder. } ( 29... Kf7 30. g3 f3 31. Qf2 Qf6 { <ab>, but tricky. } ) 30. Qxe6+
+Kh8 31. Rc8 { Mate is in a couple of moves. } 1-0
+
+[Site "Scottish Chess Minor"]
+[Date "1994.07.??"]
+[Round "52"]
+[White "Gill, Andy"]
+[Black "Thomson, Brian"]
+[Result "1-0"]
+[ECO "B54"]
+
+1. e4 c5 2. Nf3 d6 3. d4 cxd4 4. Nxd4 Nc6 5. Bb5 Bd7 6. Nc3 ( 6. Nxc6 { Score:
+0.06 } ) 6... Nf6 ( 6... Nxd4 7. Qxd4 Bxb5 8. Nxb5 Qa5 9. Nc3 e5 10. Qd5 Qc7 {
+Score: -0.03 } ) 7. Bg5 h6 ( 7... Nxd4 8. Bxd7 Nxd7 9. Qxd4 e5 10. Qd2 Be7
+11. Be3 { Score: -0.03 } ) 8. Bh4 ( 8. Bxf6 exf6 9. f4 Nxd4 10. Bxd7 Qxd7
+11. Qxd4 Be7 { Score: 0.16 } ) 8... Qb6 ( 8... g5 9. Bg3 Nxd4 10. Qxd4 Bg7
+11. O-O O-O { Score: -0.22 } ) 9. Nxc6 ( 9. Bxf6 gxf6 10. Bxc6 bxc6 11. Na4 Qa5
+12. c3 Bg7 { Score: 0.06 } ) 9... bxc6 10. Bxf6 ( 10. Bd3 Qxb2 11. Bxf6 exf6
+12. Na4 Qd4 13. c3 { Score: -1.03 } ) 10... exf6 11. Ba4 ( 11. Bd3 Qxb2 12. Na4
+Qa3 13. c3 Be6 14. Qc2 O-O-O { Score: -1.31 } ) 11... Qc7 ( 11... Qxb2 12. Kd2
+Qb6 13. Qf3 Be6 14. e5 Qd4 { Score: -1.44 } ) 12. O-O Be7 13. Re1 ( 13. Rb1 O-O
+14. Qd3 Be6 15. f4 f5 { Score: -0.09 } ) 13... O-O 14. Qd4 ( 14. Bb3 { Score:
+-0.09 } ) 14... Be6 ( 14... Rab8 15. b3 Be6 16. Rad1 Rb6 17. f4 Re8 { Score:
+-0.16 } ) 15. Nd1 ( 15. f4 Rab8 16. Bb3 f5 17. e5 Bxb3 18. axb3 { Score: -0.16
+} ) 15... Qa5 ( 15... Rab8 16. Qc3 Rb6 17. Ne3 Qb7 18. f4 { Score: -0.09 } )
+16. Nc3 Qc7 ( 16... Rab8 17. b3 Qc7 18. Rad1 Rfe8 19. f4 Rb6 { Score: -0.13 } )
+17. Ne2 ( 17. Nd1 { Score: 0.00 } ) 17... Rab8 ( 17... Rfb8 18. Nf4 Rb6
+19. Nxe6 fxe6 20. Bb3 d5 21. exd5 cxd5 { Score: -0.06 } ) 18. b3 ( 18. Nf4 {
+Score: -0.13 } ) 18... a5 ( 18... f5 19. Rad1 fxe4 20. Qxe4 Bd5 21. Qd4 {
+Score: -0.41 } ) 19. Nf4 ( 19. Qc3 c5 20. Nd4 Rb7 21. Nc6 Ra8 22. Rad1 { Score:
+0.06 } ) 19... Bd7 ( 19... Rfc8 20. c4 Rd8 21. f3 Rd7 { Score: 0.00 } ) 20. Qd2
+( 20. Qc3 Rb7 21. a3 Re8 22. Nd3 Reb8 23. f4 { Score: -0.09 } ) 20... g5 (
+20... Rfe8 { Score: -0.09 } ) 21. Nh5 ( 21. Ne2 Rb7 22. Nd4 Re8 23. Qc3 c5
+24. Bxd7 Qxd7 { Score: 0.13 } ) 21... Qb6 ( 21... Bg4 22. Ng3 Rfe8 23. c4 Bf8
+24. f3 Be6 { Score: 0.13 } ) 22. Qc3 Qd8 23. Rad1 ( 23. a3 Rc8 24. Ng3 Re8
+25. Rad1 Bg4 26. Bxc6 Bxd1 27. Rxd1 { Score: 0.31 } ) 23... Bg4 24. Ng3 Bxd1
+25. Rxd1 c5 26. Nh5 ( 26. Nf5 h5 27. a3 Rb7 28. Qd3 Rb6 29. Qd2 { Score: -0.06
+} ) 26... Kh8 ( 26... Rb4 27. Ng3 Qa8 28. a3 Rb6 { Score: -0.75 } ) 27. Rd3 (
+27. Ng3 Rg8 28. Nf5 Bf8 29. Qd2 Qc7 { Score: -0.34 } ) 27... Rg8 ( 27... Rb4
+28. Ng3 c4 29. Rd5 cxb3 30. cxb3 Qb6 31. Bc6 { Score: -0.88 } ) 28. Rf3 (
+28. Ng3 Rg6 29. Nf5 Rb4 30. Bc6 Qc7 31. a3 Rb6 { Score: -0.81 } ) 28... Rg6 (
+28... d5 29. exd5 Qxd5 30. Re3 Qd1 31. Re1 Qd8 32. Ng3 { Score: -1.00 } )
+29. Bc6 ( 29. Rd3 Rb4 30. f3 c4 31. Re3 cxb3 32. cxb3 { Score: -0.97 } )
+29... Kg8 30. Bd5 ( 30. Ng3 Qc7 31. Nf5 Bf8 32. Bd5 Bg7 33. Rd3 Bh8 { Score:
+-1.00 } ) 30... a4 31. Qc4 Qe8 32. Qd3 ( 32. Qc3 axb3 33. cxb3 Qd8 34. a4 Rb6
+35. Rd3 { Score: -0.78 } ) 32... Rb4 ( 32... Qb5 33. Ng3 axb3 34. Nf5 Bf8 {
+Score: -0.97 } ) 33. e5 ( 33. c3 Rb6 34. e5 Kf8 35. Nxf6 { Score: -0.25 } )
+33... dxe5 ( 33... Kh8 34. c3 Rh4 35. exf6 Bd8 36. Re3 Qd7 { Score: -0.22 } )
+34. Qxg6+ 1-0
+
+[Site "Scottish Chess Minor"]
+[Date "1994.07.??"]
+[Round "53"]
+[White "Navmann, M."]
+[Black "Gill, Andy"]
+[Result "1/2-1/2"]
+[ECO "B50"]
+
+1. e4 c5 2. Nf3 d6 3. Bc4 e6 ( 3... Nc6 { Score: 0.00 } ) 4. Nc3 a6 ( 4... Nf6
+5. d3 d5 6. Bb3 dxe4 7. Nxe4 Nxe4 8. dxe4 Qxd1 { Score: 0.00 } ) 5. a4 ( 5. d3
+Nc6 6. Bf4 Na5 7. e5 d5 8. Bg5 Ne7 { Score: 0.09 } ) 5... Nf6 6. d3 ( 6. d4 {
+Score: 0.06 } ) 6... Be7 ( 6... d5 7. Ba2 dxe4 8. Nxe4 Nxe4 9. dxe4 Qxd1
+10. Kxd1 { Score: 0.09 } ) 7. b3 ( 7. Bg5 h6 8. Bh4 d5 9. exd5 Nxd5 10. Nxd5
+exd5 { Score: 0.16 } ) 7... O-O ( 7... d5 8. exd5 exd5 9. Nxd5 Nxd5 10. O-O O-O
+{ Score: -1.59 } ) 8. d4 ( 8. Qe2 Nc6 9. O-O d5 10. exd5 exd5 { Score: 0.06 } )
+8... cxd4 ( 8... d5 9. exd5 exd5 10. Bd3 b6 11. O-O Nc6 { Score: -0.09 } )
+9. Nxd4 ( 9. Qxd4 { Score: -0.09 } ) 9... d5 ( 9... Qa5 10. Qd2 b5 11. Bd3 e5
+12. Nf3 Bg4 { Score: -0.16 } ) 10. exd5 exd5 11. Bd3 Re8 ( 11... Nc6 12. Nce2
+Nxd4 13. Nxd4 Bb4 14. Bd2 Qa5 15. Ne2 Bxd2 { Score: -0.22 } ) 12. O-O Bb4 (
+12... Nc6 13. Nce2 Bg4 14. f3 Bc5 15. c3 { Score: -0.03 } ) 13. Bd2 ( 13. Nce2
+Nc6 14. Bb2 Bg4 15. f3 Nxd4 16. Nxd4 { Score: 0.00 } ) 13... Qa5 ( 13... b6 {
+Score: -0.09 } ) 14. Nb1 Kh8 ( 14... Nc6 15. Bxb4 Nxb4 16. Re1 Bg4 17. Be2 Rad8
+{ Score: -0.09 } ) 15. Bxb4 Qxb4 16. c3 Qe7 ( 16... Qc5 17. Re1 Rxe1 18. Qxe1
+Nc6 19. Nf5 b6 { Score: 0.09 } ) 17. Nd2 ( 17. Ra2 Qc7 18. Re2 Rxe2 19. Qxe2
+Nc6 20. Rd1 Nxd4 21. cxd4 { Score: 0.09 } ) 17... Bg4 ( 17... Qc5 18. Qc2 Nc6
+19. N2f3 Nxd4 20. Nxd4 Ne4 { Score: 0.00 } ) 18. Qc1 ( 18. N2f3 Qc7 19. Qd2 Nc6
+20. Rfe1 Rad8 21. Rxe8 Rxe8 { Score: 0.00 } ) 18... Nc6 19. Nxc6 ( 19. Re1 Ne5
+20. Qc2 Qc7 21. c4 Nxd3 22. Qxd3 { Score: 0.03 } ) 19... bxc6 20. Re1 Qd7 (
+20... Qb7 21. Qc2 Rad8 22. h3 Bh5 23. c4 Rxe1 24. Rxe1 { Score: 0.03 } )
+21. Rxe8+ Qxe8 22. Qe1 ( 22. Qc2 c5 23. h3 Bh5 24. b4 c4 25. Bf5 { Score: 0.03
+} ) 22... a5 ( 22... Qd7 { Score: 0.09 } ) 23. h3 Bd7 ( 23... Bh5 24. g4 Bg6
+25. Bxg6 hxg6 26. Rd1 Rd8 27. Qxe8 Nxe8 { Score: 0.19 } ) 24. Nf3 ( 24. Rd1 Rb8
+25. c4 h6 26. Qxe8 Rxe8 27. cxd5 cxd5 { Score: 0.16 } ) 24... Qxe1+ ( 24... Rb8
+25. Bc2 c5 26. c4 Qxe1 27. Rxe1 d4 { Score: 0.16 } ) 25. Rxe1 Re8 ( 25... Rb8
+26. Bc2 g6 27. Re7 Kg7 28. Ne5 Be8 { Score: 0.44 } ) 26. Rxe8+ ( 26. Ne5 {
+Score: 0.53 } ) 26... Bxe8 27. c4 ( 27. g3 { Score: 0.28 } ) 27... h6 (
+27... g6 28. g3 Kg7 29. Kg2 h6 30. Ne5 d4 31. f4 c5 { Score: 0.13 } ) 28. Kf1 (
+28. g3 g6 29. Ne5 Kg7 30. Kg2 d4 31. Kf3 c5 { Score: 0.25 } ) 28... g6 29. Ke2
+( 29. cxd5 { Score: 0.31 } ) 29... Kg7 30. Ke3 ( 30. Ne5 { Score: 0.31 } )
+30... Nd7 ( 30... c5 31. Ne5 d4 32. Kd2 Bd7 33. Nxd7 Nxd7 34. Be4 Ne5 { Score:
+0.09 } ) 31. Kd4 ( 31. cxd5 cxd5 32. Kd4 Nf6 33. Ne5 Kf8 34. g3 Kg7 35. f4 {
+Score: 0.59 } ) 31... dxc4 32. Bxc4 ( 32. Kxc4 f5 33. Kc3 Bf7 34. g3 Nc5
+35. Bc2 Bd5 { Score: 0.16 } ) 32... Kf6 ( 32... f5 33. Ke3 Bf7 34. Bxf7 Kxf7
+35. Kf4 Ke6 36. Nd4 Kd5 { Score: -0.03 } ) 33. Bd3 ( 33. Nd2 Nb6 34. Ne4 Ke7
+35. Bd3 f5 36. Nc5 Bf7 { Score: 0.22 } ) 33... Ke6 34. Kc4 ( 34. Ke3 Nb6
+35. Nd4 Kd6 36. Kf3 Ke5 37. Ne2 f5 { Score: 0.09 } ) 34... f6 ( 34... f5 35. g4
+fxg4 36. hxg4 Ne5 37. Nxe5 Kxe5 38. Kc3 { Score: -0.13 } ) 1/2-1/2
+
+[Site "Grangemouth Congress"]
+[Date "1994.09.??"]
+[Round "54"]
+[White "Gill, Andy"]
+[Black "McKay, Stewart"]
+[Result "1-0"]
+[ECO "B01"]
+1. e4 d5 2. exd5 Nf6 3. Bb5+ Bd7 4. Bxd7+ Qxd7 5. Nf3 Nxd5
+6. O-O Nc6 7. Re1 e6 8. d3 g6 9. Bg5 Bg7 10. c3 Nf6 11. d4 h6 12. Bxf6 Bxf6
+13. d5 Rd8 14. Qd2 Qxd5 15. Qf4 Bg7 16. Qxc7 O-O 17. Qf4 g5 18. Qd2 Qf5 19. Qe3
+Rd3 20. Qe4 Qxe4 21. Rxe4 Rd1+ 22. Re1 Rfd8 23. h3 Ne5 24. Na3 Nxf3+ 25. gxf3
+R1d3 26. Kg2 a6 27. Rac1 b5 28. Re2 Bf8 29. Nc2 Bc5 30. Ne1 Rd2 31. Rxd2 Rxd2
+32. Rc2 Rd1 33. Kf1 Be7 34. a3 Bf6 35. Ke2 Rd5 36. Nd3 Rd8 37. Kd2 Rc8 38. Ke3
+Bg7 39. f4 Bf6 40. Ne5 Rc5 41. Nd7 gxf4+ 42. Kxf4 Bg5+ 43. Ke4 f5+ 44. Kf3 Rd5
+45. Nb8 Rd6 46. c4 bxc4 47. Rxc4 Rb6 48. Rb4 Rd6 49. Ra4 Rb6 50. Nxa6 Rxb2
+51. Nc7 Rb3+ 52. Kg2 Be7 53. Nxe6 Rxa3 54. Rxa3 Bxa3 55. Kg3 Kf7 56. Nd4 Kg6
+57. Kf4 Kh5 58. Nxf5 { And White won by queening the f pawn. } 1-0
+
+[Site "Grangemouth Minor Congress"]
+[Date "1994.09.??"]
+[Round "55"]
+[White "Shaughan, Harward"]
+[Black "Gill, Andy"]
+[Result "0-1"]
+[ECO "D02"]
+1. d4 e6 2. Bf4 d5 3. Nf3 Nf6 4. Nbd2 c5 5. e3 a6 6. c4 Nc6 7. Ne5 cxd4 8. Nxc6
+bxc6 9. exd4 Qb6 10. cxd5 cxd5 11. Qc2 Bd7 12. Be3 Bb4 13. a3 Bxd2+ 14. Qxd2
+O-O 15. Bd3 Rfc8 16. O-O Bb5 17. b3 Rc6 18. f3 Rac8 19. Rfc1 Bxd3 20. Rxc6 Rxc6
+21. Qxd3 Qc7 22. Bd2 h6 23. Rb1 Nh5 24. b4 Nf4 25. Bxf4 Qxf4 26. b5 Rc1+
+27. Rxc1 Qxc1+ 28. Kf2 Qb2+ 29. Kg3 Qxb5 30. Qxb5 axb5 31. Kf2 Kf8 32. Ke3 Ke7
+33. Kd3 Kd6 34. f4 f6 35. h4 e5 36. dxe5+ fxe5 37. f5 e4+ 38. Kd4 Ke7 39. g4
+Kf6 40. Ke3 g6 41. g5+ hxg5 42. hxg5+ Kxf5 0-1
+
+[Site "Grangemouth Minor Congress"]
+[Date "1994.09.??"]
+[Round "56"]
+[White "Gill, Andy"]
+[Black "Ridland, Lindsay"]
+[Result "1-0"]
+[ECO "C65"]
+1. e4 e5 2. Nf3 Nc6 3. Bb5 Nf6 4. O-O Bc5 5. Re1 a6 (5... Ng4 6. Re2 O-O
+7. d3 Nd4 8. Nxd4 Bxd4 9. Nd2 {<saw>,0.13 but a bit messy for white.})
+6. Ba4 (6. Bxc6 dxc6 7. h3 Qe7 8. d3 O-O 9. Bg5 h6 10. Bh4 {=, taking the
+exchange way out.}) 6... b5 7. Bb3 d6 { We have now reached a main line
+of the Ruy Lopez.} 8. c3 (8. a4 Ng4 9. Re2 Bb7 10. axb5 axb5 {=, and very
+like Game 7 of the Short-Kasparov WC, where Kasparov as white scored a
+decisive victory.}) 8... Bg4 9. d3 h6 10. Be3 O-O (10... Bxe3 11. Rxe3
+O-O 12. a4 b4 13. h3 Bh5 14. Nbd2 Rb8 {=}) 11. Bxc5 dxc5 12. Bc2 Qd7
+13. Nbd2 (13. h3 Bh5 14. Nbd2 Rfd8 15. Nb3 Qd6 16. Qe2 Rab8 17. Red1 {
+Fritz is deperate to put h3, but I dont see why.}) 13... Nh5 {} (13...
+Rad8 {is an idea.}) 14. Nb3 (14. h3 {<saw>,0.33 I now agree with this,
+because the knight block the h5 retreat square.}) 14... Nf4 {?} (14...
+Qd6 15. h3 Be6 16. Ng5 Bxb3 17. axb3 Nf4 18. Nf3 {<sab>}) 15. Nxc5 Qc8 (
+15... Qe7 16. Nb3 Rfd8 17. h3 Be6 18. d4 Qf6 19. Rc1 exd4 {=}) 16. Re3 (
+16. b4 {White is just a pawn up.}) 16... Rd8 17. Qd2 Rd6 (17... Bxf3 {!}
+18. Rxf3 Qg4 19. Rxf4 exf4 20. h3 Qh4 21. d4 {and black has equalised!})
+18. Bd1 {} 18... Nxg2 {?? Throws away a piece for a very temp.
+inititive.} (18... Rb8 19. d4 exd4 20. cxd4 Ne6 21. Nxe6 Qxe6 {and white
+is starting to push home his advantage.}) 19. Kxg2 Bh3+ 20. Kh1 Qg4 (
+20... Rg6 {is another idea, but the whole plan is conceptually flawed.})
+21. Ne1 Qg5 22. Qe2 Be6 23. Rg3 Qf6 24. Nxe6 {} (24. Nf3 Ne7 25. Nxe6
+Qxe6 26. Bb3 Qf6 27. Rag1 {<waw>}) 24... Rxe6 (24... Qxe6 25. Bb3 Qe7
+26. Bd5 Rad8 27. Nf3 R8d7 28. Rd1) 25. Qf3 {Crude plan of exchanging
+queens to avoid `acidents`.} (25. Bb3) 25... Qe7 26. Bb3 Rf6 27. Qe3 (27.
+Qg2) 27... Rd8 28. Nc2 Kh7 29. Rag1 g6 30. Rf3 {} 30... Rxf3 (30... Rfd6 {
+??} 31. Rxf7+ {Trying to avoid the exchance, but black loses his Queen!
+Black actually moved his rook to d6, but before letting it go, spotted
+the danger, and then took the exchange. Shame...}) 31. Qxf3 Rd7 32. Ne3
+h5 {?} 33. Nd5 {! At least winning the exchange. Black resigned here.}
+1-0
+
diff --git a/testsuite/tests/programs/andy_cherry/test.T b/testsuite/tests/programs/andy_cherry/test.T
new file mode 100644
index 0000000000..4d14ee306e
--- /dev/null
+++ b/testsuite/tests/programs/andy_cherry/test.T
@@ -0,0 +1,14 @@
+
+test('andy_cherry',
+ [skip_if_fast,
+ extra_clean(['DataTypes.hi', 'DataTypes.o',
+ 'GenUtils.hi', 'GenUtils.o',
+ 'Interp.hi', 'Interp.o',
+ 'InterpUtils.hi', 'InterpUtils.o',
+ 'Main.hi', 'Main.o',
+ 'Parser.hi', 'Parser.o',
+ 'PrintTEX.hi', 'PrintTEX.o']),
+ extra_run_opts('.')],
+ multimod_compile_and_run,
+ ['Main', '-cpp'])
+