[comp.sys.handhelds] Reversi assembly sources

grue@batserver.cs.uq.oz.au (Frobozz) (12/21/90)

hiya,
	I've decided to post my current version of the assembly code portions
of my just released reversi program.  I will note that the comments are
slightly out of date and are in some places less than meaningfull (and I
haven't got round to re-doing them).  This will be most noticable in the
header comment of the MVGEN routine which has undergone quite a few minor
alterations during its lifetime.

	These sources are written for assembly using sass and might
suffer compatibility problems when used with other assemblers.

	Any non-profit, non-commercial usage of these routines is permitted
so long as they remain intact.  Any other usage requires my permission.


							Pauli
seeya

Paul Dale               | Internet/CSnet:            grue@batserver.cs.uq.oz.au
Dept of Computer Science| Bitnet:       grue%batserver.cs.uq.oz.au@uunet.uu.net
Uni of Qld              | JANET:           grue%batserver.cs.uq.oz.au@uk.ac.ukc
Australia, 4072         | EAN:                          grue@batserver.cs.uq.oz
                        | UUCP:           uunet!munnari!batserver.cs.uq.oz!grue
f4e6g4Qh4++             | JUNET:                     grue@batserver.cs.uq.oz.au



MVGEN:
;
; Routine written by Paul Dale November 1990
;   Copyright 1990 all rights reserved.
;
; Given a position in a reversi game (in SOS) produce a new
;   position (on TOS) that corresponds to the old position
;   after anoth move has been made.  Thus succesive calls
;   to this routine (without altering the stack) will cause
;   all the moves from the position (in SOS) to be made.  When
;   all legal moves have been done, the machine returns a five
;   nibble zero value at the start of SOS.  This routine requires
;   two strings of 112 characters or long at the top of the stack
;   it does not make any checks it assumes that they are present.
;   It also modifies the strings in situ.  Both of these are
;   potentially major problems, they have both been left in
;   in order to increase the speed of the program.  If a deep
;   minimax search is being performed then the time to copy each
;   of the positions would probably be longer than the time
;   required for the routine to run to completion.  Also, it
;   would be possible to play some rather nasty tricks moving
;   the stack pointer up and down the stack and making calls
;   to the move generation routine.  This would provide a major
;   speed increase in a deep search.  Initially, the program is
;   only going to make a single ply search so these considerations
;   are quite unwarranted (in the future this statement will
;   hopefully be false, i.e. a proper search will have be written)
;   Since the computer will move first (with respect to this
;   routine), the code has been written so that it will run more
;   quickly when the computer has the move.  In a more general,
;   deeper search this may still provide an advantage (whenever
;   an odd number of ply are searched).  Reconstructing the move
;   in a human readable form might prove interesting...  Also,
;   the search routine is designed to run faster when we are at
;   a terminal node (if there is a choice).  This is beacuse most
;   of the nodes that are going to be searched are terminal.
; One possible way to improve this routine would be to unroll the
;   important loops.  The initial copy could be done inline and
;   the piece run-follower could also be inlined (since runs can
;   only be 6 long and still be flippable).  The actual move
;   search shouldn't be inlined since the move subtable might be
;   subject to re-ordering (and it is 60 long, unrolling the thing
;   60 times is really stupid, but faster ;-)  Another interesting
;   thing might be to inline the code fo do_move (eight times only)
;   this would save a level of the stack and might speed things.
;   Again, I feel that this is not going to be worthwhile.
;
;
; The format of the board description string is as follows:
;
; 5     nibbles indicating the position in the move subtable
;       we're up to as an offset from the start.
; 1     nibble indicating the colour to move
; 5     nibbles padding, currently unused. (move made??)
; 91    nibbles that contain the board itself (1 nibble per
;       square.  A 9 by 10 grid with an extra square:
;       ##########
;       #........       Here # is an illegal border square
;       #........       and . is a vacant square
;       #........       X and O are player pieces
;       #...OX...
;       #...XO...       Start from the bottom left corner and
;       #........       work left to right up the page.
;       #........
;       #........
;       #########
; 122   nibbles that contain the move subtable.  Each byte
;       holds the offset from the start of the structure to
;       the appropriate square to move to.  This whole thing
;       is null terminated and shrinks as the game proceeds.
;       Hopefully this will provide an initial gross ordering
;       of the moves for the search.
;
; The initial position is thus:
;   66000 1 00000   start 0x00  initial info
;   888888888       start 0x0b  board structure itself
;   800000000       start 0x14
;   800000000       start 0x1d
;   800000000       start 0x26
;   80001f000       start 0x2f
;   8000f1000       start 0x38
;   800000000       start 0x41
;   800000000       start 0x4a
;   800000000       start 0x53
;   8888888888      start 0x5c  end of board, start of move table
;   51 c1 45 b5     start 0x66  corners
;   71 a1 72 e2 24 94 65 95     edge 2 away from corner
;   81 91 03 73 93 04 75 85     middle edge
;   12 22 13 63 a3 f3 e4 f4     middle one row/col in
;   02 32 82 d2 34 84 d4 05     knight move from corner
;   61 b1 e1 52 b4 25 55 a5     one away from corner
;   92 c2 44 74                 corners of middle 16 squares
;   a2 b2 23 53 b3 e3 54 64     rest of edge of middle 16
;   f1 42 c4 15                 the X squares
;   00                          Terminator
;   
;
; Internally, the pieces are stored as the follow nibbles:
;   0   Empty square
;   1   Human piece
;   f   Computer piece  NB: negation of computer code gives human
;   8   Border square
;
; On entry, it is assumed that the usual RPL things apply
;   later, this routine will likely be integrated into the
;   move evalulator and this assumption would be false.
;
; This routine makes use of the following registers:
;   d0, d1, a, b, c, d
;   r2, r3
;   p is used but it will be zero on exit (no matter what)
;   Also, bit 2 of ST is set if the human is moving and
;   bit 1 of ST is set if a valid move has been found (on exit)
;   bit 11 of ST is used to indicate that this is the bottom ply
;   to be searched, this means that the move generator doesn't
;   have to perform all updates of the board string that it usually
;   does.  (Set means this is the terminal ply).
;
;   Three levels of stack are used:
;       one for the CPU hardware flags (register st) and
;       one for internal subroutine usage and
;       one by the RPL calling routine.
;   If this were to be linked into a larger machine code block,
;   it would be possible to save the stack level for st and the
;   one for the RPL caller if this code was inlined.
;
; The registers are used for:
;   r0 returns the result from these routines
;   r2 holds a pointer to the body of SOS (after header stuff)
;   r3 holds a pointer to the body of TOS
;   d is used to hold the offset into the move sub-table
;
; Define some useful rom routines.  The first set are for
;   the 48sx and the second for the 28s.
;
; These are indicated in the source file by comments:
; INLINE CONSTANT
;
;save_regs      =   0x0679b ; Save RPL registers HP48sx
;restore_regs   =   0x067d2 ; Restore them HP48sx
;push_si        =   0x06537 ; Push R0 as sint, restore regs HP48sx
;pop_si         =   0x06641 ; Pop sint into A HP48sx
;
;save_regs      =   0x05081 ; Save RPL registers HP28s
;restore_regs   =   0x050b8 ; Restore them HP28s
;push_si        =   0x0???? ; Push R0 as sint, restore regs HP28s
;pop_si         =   0x04f27 ; Pop sint into A HP28s
;

mvgen_entry:
; before we save any registers, we are going to fudge with d1 so
; it appears that we've poped our args from the stack!
    add.a   10, d1          ; two args!
    inc.a   d
    inc.a   d               ; pop the args properly
    call.a  0x0679b         ; save regs INLINE CONSTANT
    sub.a   10, d1          ; put them back

    clr.a   c               ; going to clear all the flags...
    swap.x  c, st           ; grab the system flags
    push.a  c               ; and save 'em
;   clrb    11, st          ; not bottom ply of search
    call.3  minimax         ; do the real work

    pop.a   c               ; grab the system flags and
    move.x  c, st           ; restore 'em to their former glory

    call.a  0x06537         ; push R0 on stack and restore regs INLINE CONSTANT
    move.a  @d0,a           ; \
    add.a   5,d0            ;  > return to RPL
    jump    @a              ; /


;-----------------------------------------------------------------
; SUBROUTINE do_move: try to make a move in a given direction
;-----------------------------------------------------------------
;
; This is the one that really does all the work.  It expects
;   a direction of travel in c.a and it will attempt to flip
;   oponent disks in that direction.  If it succeeds in making
;   a flip, it should set a flag to indicate this.  It is free
;   to destroy the c register in any way whatsoever.  The
;   starting position should be in register d0 on entry and
;   should remain unchanged throughout this operation.  Register
;   d should also remain unchanged.  There is a trade off between
;   speed and register usage in the subroutine.  I wanted it to
;   run as fast as possible, but I couldn't accept using all the
;   registers.  Particularly, I did not desire to use any more
;   of the temporary Rn registers or levels of the stack.  If
;   this is only called from RPL these restrictions are silly.
;   However, I was/am intending to integrate this routines into
;   another (larger) machine code program.
;
do_move:
    move.a  c, b            ; save the offset somewhere safe
    swap.a  a, d0           ; grab the initial square
    move.a  a, d0           ; and store it back for safety
    add.a   b, a            ; adjust by the offset
    move.a  a, d1           ; prepare to examine that square
    move.1  @d1, c
    brbc    2, st, computer_move

human_move:
    inc.a   c               ; test for computer's piece
    brz.p   c, cont_move    ; it is we may have a move...
    ret                     ; nope, give up looking

computer_move:
    dec.a   c               ; check for human piece
    retnz.p c               ; nope, give up

;
; The first square has been check as the ememy piece, from here
;   we run along in that direction until we locate a square of
;   a different kind to the one we just located.  If this
;   different square is one of our pieces, then the move is
;   a valid one and we can flip all the pieces in teh middle
;   as if the move had been made.
;
cont_move:
    add.a   b, a            ; look at next sqaure in direction
    move.a  a, d1
    move.1  @d1, c          ; get the square value
    retz.p  c               ; empty square - no good
    move.p1 8, a
    reteq.p c, a            ; off board square - no good
    swap.a  a, d1           ; restore the pointer for next iter
    brbc    2, st, c_move

h_move:
    inc.a   c               ; is it a computer piece?
    brz.p   c, cont_move    ; yep, keep following run
    dec.a   c               ; restore to initial value
    jump.3  valid_move      ; no, it must be a human piece

c_move:
    dec.a   c
    brz.p   c, cont_move
    inc.a   c

;
; Getting here implies that the move is a plausable one, we
;   must run backwards along the run and flip them all.  A
;   flag is also set to indicate that the move is valid.
;
valid_move:
    setb    1, st           ; this move is valid, so set flag
    neg.a   b               ; we're going the other way this time

valid_loop:
    add.a   b, a            ; backtrack one square
    move.a  a, d1
    move.1  @d1, a
    retz.p  a               ; back to the initial square??
    move.1  c, @d1          ; my piece goes there
    swap.a  a, d1
    jump.3  valid_loop      ; keep going until the empty square


;-----------------------------------------------------------------
; PROCEDURE minimax: Perform a minimax search.
;-----------------------------------------------------------------
;
; Minimax performs an alpha beta search to a depth given by TOS.
;   On entry there should be n+1 distinct copies of the board
;   on the stack (where n=TOS).  The top-most one is the one that
;   contains the initial position, the rest may contain anything
;   at all.  This routine returns the best move at the first ply
;   in register r0 (?).
; At present the search depth is limited to one move only.  And we
;   only perform a max search!
; Register r0 contains the best top-level move, r1 contains the
;   current max value.
;
minimax:                    ; first setup registers r2, r3
    swap.a  c, d1           ; grab the TOS string and save it
    move.a  c, d1
    move.a  c, d0
    add.a   5, d1           ; point at SOS

    move.a  @d0, a          ; de-ref it and keep raw ptr
    move.a  a, d0
    add.a   10, d0          ; skip the header
    swap.a  c, d0
    move.w  c, r3           ; save TOS pointer
    
    move.a  @d1, a
    move.a  a, d1
    add.a   10, d1
    swap.a  c, d1
    move.w  c, r2           ; and the SOS pointer

;
; Here is the main body of the maximise search
;
    call.3  mvgen_main      ; generate the next move

;
; now r2, r3 point at SOS, TOS respectively, C holds the move
;   sub-table offset or zero if no move was possible.  d0 points
;   to the square moved to.
;
    brz.a   c, must_pass    ; no moves available means we pass

    call.3  eval_pos        ; find a static value for the position
best_move:
    move.w  b, a            ; grab the evaluation
    move.w  a, r1           ; current best move
    swap.a  a, d0
    move.w  a, r0           ; it is the best so far

next_mv:                    ; figure out the next move
    call.3  mvgen_main      ; perform the next move
    brz.a   c, mm_exit      ; finished the search
    call.3  eval_pos        ; score the position
    move.w  r1, a           ; get the current score
    brge.w  a, b, next_mv   ; continue with the next move unless...
    jump.3  best_move       ; update best move found so far

must_pass:                  ; the only available move is to pass
    clr.a   c
    move.w  c, r0           ; return the zero move
    ret

; We've got a 'best' move and must return the offset of the move
mm_exit:
    move.w  r0, a           ; get the 'best' move
    move.w  r3, c           ; get the start posn
    neg.a   c               ; The assembler's sub.a ops are broken!!
    add.a   c, a            ; work out the offset
    move.w  a, r0           ; return the offset
    ret


;-----------------------------------------------------------------
; SUBROUTINE mvgen_main: try to find a move for the given player
;-----------------------------------------------------------------
;
; The subroutine does all the real work.  The stuff above is just
;   an interface to the RPL caller.  The final production version
;   will not include the above.  This routine will return a zero
;   value in the C register if no (more) moves we found.  Register
;   d0 will contain the exact memory location of the square that
;   was just played into if a move was made.  It will contain
;   garbage otherwise.
;
mvgen_main:                 ; The main routine itself
    move.w  r2, c
    move.a  c, d0           ; point at TOS
    move.w  r3, c
    move.a  c, d1           ; point at SOS

;
; Here d0, d1 point at the raw strings.  We must now copy
;   d0 into d1 and then make the move.  The first few nibbles
;   of the string are special.  We've extract the colour info
;   and change the colour for the copied string.  We also get
;   the move offset stuff.
;
    move.w  @d0, c          ; copy the first 16 nibbles
    move.a  c, d            ; save the move index for later
    move.1  5, p            ; point at the colour nibble
    move.p1 0xf, a          ; compare value
;   clrb    2, st           ; assume computer moving
    breq.p  c, a, mvg_skp1  ; skip player move code
    setb    2, st           ; player's move

mvg_skp1:                   ; we now know who is moving
    move.1  6, p            ; assume we're doing a partial copy
    brbs    11, st, mvg_sht ; the short copy (for terminal nodes)
;
; Here goes the long copy code, for non-terminal nodes of the
;   search tree.  We have to change the colour of the player to
;   move.  Increase the loop count so the move table gets copied
;   and reset the move table index.
;
    move.1  5, p            ; point back at the colour nibble
    neg.p   c               ; change colour of the player to move
    move.1  0, p            ; restore p to its normal state
    move.p5 0x00066, c      ; reset the move table index
    move.1  13, p           ; loop counter for full copy

mvg_sht:
    move.w  c, @d1          ; write the first word back

copy_loop:                  ; The strings are 14*16 nibbles
    add.a   16, d0          ; long.  This copies SOS into TOS
    add.a   16, d1          ; Could unroll the loop for
    move.w  @d0, a          ; greater speed (which shouldn't
    move.w  a, @d1          ; be necessary yet)
    dec.1   p
    brne.1  p, 0, copy_loop ; keep doing it...

; P must now be zero again

;
; Here, TOS is basicly the same as SOS.  The move colour is
;   slightly different, but that is correct.  Now, we have
;   to run through the move list (starting at the offset)
;   looking for the next move to make.  If the null terminator
;   is found then we've got to return without making a move.
;
; Register usage:
;   d0 points to the interior of the string
;   r3 is TOS (start of body of string)
;   r2 is SOS (start of body of string)
;   d is the move offset
;
; This is the place to come when the previous move has been
;   rejected as a dud.
;
next_square:
    move.w  r3, c           ; grab TOS
    add.a   d, c            ; square in board store
    inc.a   d
    inc.a   d               ; increment offset pointer

    move.a  c, d0
    clr.a   a               ; need full 20 bits for add later
    move.b  @d0, a          ; get the new offset
    brz.b   a, done_all_m   ; we've looked at all moves :-{

    move.w  r3, c           ; grab TOS again
    add.a   c, a            ; calc position
    move.a  a, d0
    move.p  @d0, c          ; get the piece at that square
;
; If the square is occupied, don't consider it any further.
;   It might be possible to dynamically update the move list
;   while the program is playing.  This is likely to be a messy
;   job since the ordering is quite important.
;
    brnz.p  c, next_square  ; check if square is empty...

;
; Here is where we've got to do the difficult work.  We've got
;   to verify if the suggested move is in fact legal and if
;   it is, we've got to make the move (in TOS) and return
;   normally.
;
; The constants to add for each move direction are:
;     8  9  10
;    -1  .   1
;   -10 -9  -8
;
; Bit 1 of the hardware status register is used to keep track
;   of the validity of the move.  If it is set then the move
;   is good.  If it is clear, the move is bad.
;   Register d0 still points at the initial square considered
;   for the move (a is a duplicate of this info -- not used).
;
    clrb    1, st           ; assume the move is a dud

    clr.a   c
    dec.a   c               ; left = -1
    call.3  do_move

    clr.a   c
    move.p1 8, c            ; up left = 8
    call.3  do_move

    clr.a   c
    move.p1 9, c            ; up = 9
    call.3  do_move

    clr.a   c
    move.p1 10, c           ; up right = 10
    call.3  do_move

    clr.a   c
    inc.a   c               ; right = 1
    call.3  do_move

    move.p5 0xffff8, c      ; down right = -8
    call.3  do_move

    move.p5 0xffff7, c      ; down = -9
    call.3  do_move

    move.p5 0xffff6, c      ; down left = -10
    call.3  do_move

;
; By now, we've checked all moves from the given square and know
;   if the move was good or not (by checking bit 1 of ST).
;   If the move is bad, we've got to backtrack and try the next
;   potential move.  If it was good we can return now.  It
;   would be more usual to expect a dud move, so that is
;   checked for first.
;
    brbc    1, st, next_square
    jump.3  good_move       ; clean up and return

; When the null terminator for a string is encountered, we
;   set the move offset (in SOS) to zero and exit normally).
;
done_all_m:
    clr.a   c
    jump.3  set_move_offset ; & leave gracefully

;
; Come here if the move that was considered has turned out to
;   be a legal move.  All we've got to do is update the move
;   index in SOS and return from the current position.  We must
;   also put a piece at the necessary location in TOS (as if
;   we've made the given move).  d0 points at the square where
;   we just moved to.
;
good_move:
    move.p1 0xf, c          ; assume computer piece = -1
    brbc    2, st, pce_good ; depending upon colour
    move.p1 1, c            ; human piece = 1

pce_good:
    move.1  c, @d0          ; put the piece onto the board
    move.a  d, c            ; get offset into move table and...

set_move_offset:
    move.w  r2, a           ; and pointer to SOS body
    move.a  a, d1
    move.a  c, @d1          ; write the value
    ret                     ; go back to the caller of this
                            ; wonderous function


;-----------------------------------------------------------------
; eval_pos: Evalulate a given position using a simple eval func
;-----------------------------------------------------------------
;
; Evalulate the current position using a static evaluation function
;   Currently, this function is a simple piece differential one.
;   i.e. Count +1 for a computer piece, -1 for a human one and
;   0 for an empty square (code==0) or a border one (code=8)
;
;   We return the score for the position in register B.w and we are
;   free to use any registers we want except d0 which should remain
;   unchanged after calling this routine.  The current routine uses:
;   A for getting each square from the board
;   B to hold the partial evaluation
;   C for constants for testing against
;   D for the loop counter
;   d1 as a pointer into the board table
; The routine also assumes that the pointer to the current
;   position is in register r3 (which it should be since the
;   move_gen routine leaves it there).  No usage is made of the
;   fact that r2 points to the previous position.
;   (These registers may be destroyed if desired).
;
eval_pos:
    move.w  r3, a           ; get pointer to TOS
    move.a  a, d1           ; point at what we desire
    add.a   11, d1          ; get to the board itself
    add.a   10, d1          ; skip initial bit of board
    clr.a   c
    move.p2 72, c           ; set 64 in C.a
    move.a  c, d            ; save it in d
    move.p2 64, c
    clr.w   b               ; zero the entire register
    move.a  c, b            ; score from 0 to 128

eval_lp:
    move.1  @d1, a
    move.p1 0xf, c          ; computer piece
    brne.p  c, a, eval_sk1

    inc.a   b

eval_lp_end:
    add.a   1, d1
    dec.a   d
    brnz.a  d, eval_lp
    ret

eval_sk1:
    move.p1 1, c            ; human piece
    brne.p  c, a, eval_lp_end
    dec.a   b
    jump.3  eval_lp_end



========================================================================

PUTN:
;
; This routine will put either a 1 or a -1 into the string
;   (third on stack) at the position specified by SOS.  The
;   value to be put is in TOS.  The string is updated in situ
;   and the other args are popped from the stack before
;   returning.
;
; These are indicated in the source file by comments:
; INLINE CONSTANT
;
;save_regs      =   0x0679b ; Save RPL registers HP48sx
;restore_regs   =   0x067d2 ; Restore them HP48sx
;push_si        =   0x06537 ; Push R0 as sint, restore regs HP48sx
;pop_si         =   0x06641 ; Pop sint into A HP48sx
;real_1         =   0x2a2c9 ; Real 1 (start of HP48sx rom real table)
;
;save_regs      =   0x05081 ; Save RPL registers HP28s
;restore_regs   =   0x050b8 ; Restore them HP28s
;push_si        =   0x0???? ; Push R0 as sint, restore regs HP28s
;pop_si         =   0x04f27 ; Pop sint into A HP28s
;real_1         =   0x112c9 ; Real 1 (start of HP28s rom real table)
;
    move.a  @d1, c          ; get TOS == value
    move.w  c, r0           ; chace it for later on
    add.a   5, d1           ; pop stack
    inc.a   d               ; inc free memory
    call.a  0x06641         ; pop si, get offset in A.a INLINE
    swap.a  c, d1           ; save this register for later
    push.a  c
    move.a  c, d1           ; put it back also
    move.a  @d1, c          ; address of string
    add.a   a, c            ; adjust by the offset
    move.a  c, d1           ; into an address register
    add.a   10, d1          ; adjust for header
    move.w  r0, a           ; get the value back again
    move.p5 0x2a2c9, c      ; check if it is 1 INLINE
    breq.a  c, a, gtone     ; yep, it was a real 1
    move.p1 15, c           ; -1
    jump.3  common

gtone:
    move.p1 1, c            ; 1

common:
    move.1  c, @d1          ; put the thing into the string
    pop.a   c
    move.a  c, d1           ; restore for RPL
    move.a  @d0, a          ; \
    add.a   5, d0           ;  > return to RPL
    jump.a  @a              ; /



========================================================================


GETN:

;
; This routine, get the nth nibble from SOS where n is the
;   short int in TOS.  The 10 nibbles of header are skipped.
;   The nibble is returned as a real 0, 1, -1, or 8 only.  The
;   string is left on the stack unchanged.  (this code will
;   prob also work for 0..9 correctly!).
;
; These are indicated in the source file by comments:
; INLINE CONSTANT
;
;save_regs      =   0x0679b ; Save RPL registers HP48sx
;restore_regs   =   0x067d2 ; Restore them HP48sx
;push_si        =   0x06537 ; Push R0 as sint, restore regs HP48sx
;pop_si         =   0x06641 ; Pop sint into A HP48sx
;real_0         =   0x2a2b4 ; Real 0 (start of HP48sx rom real table)
;
;save_regs      =   0x05081 ; Save RPL registers HP28s
;restore_regs   =   0x050b8 ; Restore them HP28s
;push_si        =   0x0???? ; Push R0 as sint, restore regs HP28s
;pop_si         =   0x04f27 ; Pop sint into A HP28s
;real_0         =   0x112b4 ; Real 0 (start of HP28s rom real table)
;
    swap.a  c, d1           ; get TOS
    push.a  c               ; save it
    move.a  c, d1           ; and restore everything
    call.a  0x06641         ; pop TOS into A.a INLINE
    move.a  @d1, c          ; get the string address
    add.a   a, c            ; adjust by the desired offset
    move.a  c, d1           ; into a pointer register
    add.a   10, d1          ; past the header
    clr.a   a
    move.1  @d1, a          ; get the nibble into A.a
    move.p1 15, c           ; check if it is -1
    breq.p  c, a, m1        ; it is...
    move.a  a, c            ; save it for later
    add.a   a, a            ; *2
    add.a   a, a            ; *4
    add.a   a, c            ; *5 in C
    add.a   a, a            ; *8
    add.a   a, a            ; *16
    add.a   c, a            ; *21 in A (== sizeof(real))

common:
    move.p5 0x2a2b4, c      ; INLINE start of rom real table
    add.a   c, a            ; index correctly
    pop.a   c               ; get the old d1
    move.a  c, d1
    move.a  a, @d1          ; push the real value
    dec.a   d               ; less space remains

    move.a  @d0, a          ; \
    add.a   5, d0           ;  > return to RPL
    jump.a  @a              ; /
m1: clr.a   a
    move.p2 0xd2, a         ; offset for the -1 real in table
    jump.3  common          ; fix things up



========================================================================


CHKMV:

;
; This function takes a string representing the board position
;   in level 2 and a short integer in level 1 that is the player's
;   move.  It checks to see if the move suggested is legal and
;   returns a real zero on the stack if it is.  A real one is
;   returned if the move is a dud.
;
; Define some useful rom routines.  The first set are for
;   the 48sx and the second for the 28s.
;
; These are indicated in the source file by comments:
; INLINE CONSTANT
;
;save_regs      =   0x0679b ; Save RPL registers HP48sx
;restore_regs   =   0x067d2 ; Restore them HP48sx
;push_si        =   0x06537 ; Push R0 as sint, restore regs HP48sx
;pop_si         =   0x06641 ; Pop sint into A HP48sx
;real_0         =   0x2a2b4 ; Real zero in rom HP48sx
;real_1         =   0x2a2c9 ; Real one in rom HP48sx
;
;save_regs      =   0x05081 ; Save RPL registers HP28s
;restore_regs   =   0x050b8 ; Restore them HP28s
;push_si        =   0x0???? ; Push R0 as sint, restore regs HP28s
;pop_si         =   0x04f27 ; Pop sint into A HP28s
;real_0         =   0x112b4 ; Real zero in rom HP28s
;real_1         =   0x112c9 ; Real one in rom HP28s
;
mvchk_entry:
    call.a  0x06641         ; Pop short integer into register A INLINE
    call.a  0x0679b         ; Save RPL registers INLINE

    clr.a   c               ; going to clear all the flags...
    swap.x  c, st           ; grab the system flags
    push.a  c               ; and save 'em

    move.a  @d1, c          ; get the board position
    move.a  c, d1           ; find out the colour on move
;   add.a   10, d1          ; skip the header
;   add.a   5, d1           ; to the move colour nibble
    add.a   15, d1          ; to the colour nibble

    add.a   a, c            ; adjust by the move position
    move.a  c, d0
    add.a   10, d0          ; adjust for the header

    move.1  @d1, c          ; get the colour nibble
    inc.p   c
    brz.p   c, got_mover    ; computer moving?
    setb    2, st           ; set player moving flag
got_mover:

    brnz.a  a, check_normal

;
; The player wants to pass, so we've got to try to generate
;   every move and if any of them is legal, the player cannot
;   pass.  d0 contains a pointer to the start of the board.
;
check_pass:
    add.a   11, d0          ; at start of logical board
    add.a   10, d0          ; to real start of board
    clr.a   c
    move.p2 72, c
    move.a  c, d            ; cache the loop counter

;
; Run thought the board check for legal moves
;
cp_loop:
    move.1  @d0, c          ; load the square
    brnz.p  c, cp_next      ; next iteration for full squares
    call.3  check_move      ; is the move good?
    brbs    1, st, ret_bad  ; good move means no pass!

cp_next:
    add.a   1, d0           ; to next square
    dec.a   d               ; check for end of search
    brnz.a  d, cp_loop      ; keep going for all moves
    jump.3  ret_good        ; pass is alright

;
; Check if the move pointed to by d0 is legal.
;
check_normal:
    move.1  @d0, c          ; check that the suggested square is
    brnz.p  c, ret_bad      ; really empty!
    call.3  check_move      ; check if the move is valid
    brbc    1, st, ret_bad  ; nope, it is a dud
                            ; good moves fall through
;
; Now see if we can possibly make a move!
;

ret_good:
    move.p5 0x2a2c9, c      ; get real one address INLINE
    jump.3  ret_common

ret_bad:
    move.p5 0x2a2b4, c      ; get real zero INLINE

ret_common:
    move.a  c, a            ; save the value
    call.a  0x067d2         ; restore RPL regs INLINE
    move.a  a, @d1          ; replace TOS with our result

    pop.a   c               ; grab the system flags and
    move.x  c, st           ; restore 'em to their former glory

    move.a  @d0,a           ; \
    add.a   5,d0            ;  > return to RPL
    jump    @a              ; /

;
; Given a square, check if ANY move is legal and if so, set
;   flag 1.  (see code from mvgen.s for comments).  Set bit 1
;   if the move is good
;
check_move:
    clr.a   c
    dec.a   c               ; left = -1
    call.3  do_move

    clr.a   c
    move.p1 8, c            ; up left = 8
    call.3  do_move

    clr.a   c
    move.p1 9, c            ; up = 9
    call.3  do_move

    clr.a   c
    move.p1 10, c           ; up right = 10
    call.3  do_move

    clr.a   c
    inc.a   c               ; right = 1
    call.3  do_move

    move.p5 0xffff8, c      ; down right = -8
    call.3  do_move

    move.p5 0xffff7, c      ; down = -9
    call.3  do_move

    move.p5 0xffff6, c      ; down left = -10
;   call.3  do_move
;   ret
;   jump.3  do_move         ; optimised a little

;
; try to perform the move, see mvgen.s for more details...
;   removed the code to actually make the move.
;
do_move:
    move.a  c, b            ; save the offset somewhere safe
    swap.a  a, d0           ; grab the initial square
    move.a  a, d0           ; and store it back for safety
    add.a   b, a            ; adjust by the offset
    move.a  a, d1           ; prepare to examine that square
    move.1  @d1, c
    brbc    2, st, computer_move

human_move:
    inc.a   c               ; test for computer's piece
    brz.p   c, cont_move    ; it is we may have a move...
    ret                     ; nope, give up looking

computer_move:
    dec.a   c               ; check for human piece
    retnz.p c               ; nope, give up

cont_move:
    add.a   b, a            ; look at next sqaure in direction
    move.a  a, d1
    move.1  @d1, c          ; get the square value
    retz.p  c               ; empty square - no good
    move.p1 8, a
    reteq.p c, a            ; off board square - no good
    swap.a  a, d1           ; restore the pointer for next iter
    brbc    2, st, c_move

h_move:
    inc.a   c               ; is it a computer piece?
    brz.p   c, cont_move    ; yep, keep following run
    dec.a   c               ; restore to initial value
    jump.3  valid_move      ; no, it must be a human piece

c_move:
    dec.a   c
    brz.p   c, cont_move
    inc.a   c

valid_move:
    setb    1, st           ; this move is valid, so set flag
    ret                     ; don't bother making the move, just return
--