CS222 Lecture: Program Control Instructions;                    8/13/91
                                                        revised 9/1/00

Need: Transparency of VAX branch instructions + handout
      MIPS Instruction set transparency
      Handout of translation patterns control structures
      Handout on VAX and MIPS branches

Introduction
------------

   A. In HLL's such as Pascal, we typically have a number of constructs for
      altering the order of program execution within a procedure - e.g.

                if .. then .. else
                case .. of
                while .. do
                for .. do
                repeat .. until
                goto ..

   B. In machine language, we basically have only one, which is the equivalent 
      of
                if .. then goto ..
        or      goto ..

      These are called BRANCH or JUMP instructions.

   C. On the VAX, the branch instructions use a special operand format that
      is different from all other instructions.  Most use a one-byte 
      DISPLACEMENT specifier that is treated as a signed integer to be added
      to the program counter (PC) if the branch is taken.

      1. If the displacement is 00..7F, the branch is forward in the program;
         if it is 80 .. FF, the branch is backward.

      2. The PC value at this point is always the address of the first byte of
         the NEXT INSTRUCTION IN SEQUENCE after the branch instruction.

      Examples:         03 11           (Branch with displacement of 3)
                        51 50 D0        (MOVL R0, R1)
                        
                        The branch would cause the MOVL to be skipped and the
                        instruction just after it to be done

                        51 50 D0        (MOVL R0, R1)
                        FB 11           (Branch with displacement of -5)
        
                        The branch would cause the MOVL to be executed again
                        (and again, and again ..)

   D. The VAX has both CONDITIONAL and UNCONDITIONAL branch instructions.

      1. The examples above used the unconditional branch instruction BRB
         (Branch with Byte displacement), whose op-code is 11.

      2. The conditional branches rely on the condition code bits in the
         processor-status word (PSW) that are set by the previous non-branch
         instruction.

         Example: BEQU (Branch if equal - unsigned) will branch if the Z flag is
                  set, indicating that the result of the last instruction that 
                  affects flags was equal to zero.  Otherwise, control will
                  simply pass to the next instruction in sequence, as with 
                  other instructions.

I. Conditional Branches and The VAX Condition Codes
-  ----------- -------- --- --- --- --------- -----

   A. As we have noted earlier, the VAX PSW contains 4 bits called CONDITION
      CODES that are affected by most data movement or arithmetic instructions.

      1. The condition codes are NOT altered by branch instructions.

      2. Their setting is always determined by the result actually stored by 
         an arithmetic instruction; thus, in the case of overflow, they may
         not accurately reflect the true result of the operation.

         Example: If we add 40000000 to 40000000 (two positive numbers) we
                  get 80000000 (a negative number) - i.e. overflow occurs.
                  The condition codes will say that the result of the operation
                  was negative, even though it shouldn't have been.

   B. The 4 condition code bits are

      1. The N bit is set if the result of the last operation was negative.

      2. The Z bit is set if the result of the last operation was zero.

      3. The V bit is set if the last arithmetic operation resulted in signed 
         overflow.  (This often implies that the N bit is the opposite of what
         it should be - i.e. two negative numbers being added to produce a
         positive result would leave N = 0, but would also set V.)    It is
         cleared by most data movement operations.

      4. The C bit is set if there was carry/borrow out of the leftmost bit
         on an ADD or SUB type instruction.  It is cleared by certain other
         arithmetic instructions and left unaffected by most other instructions.

   C. Some of the VAX conditional branch instructions test a single condition
      code bit - e.g. branch if equal test to see if the Z bit is set.

   D. Others test a combination of bits - e.g. the branch if greater 
      instruction tests the Z and N bits, and branches iff both are zero.
  
II. The CMP and TST Instructions
--  --- --- --- --- ------------

   A. As noted above, the condition codes are set by most data movement
      and arithmetic instructions.

      Example: Following        MOV X,Y

               A conditional branch instruction would reflect the value of X -
               e.g. BEQL would branch if X were equal to zero.

   B. There are several special instructions which are used only to set the
      condition codes.

      1. Often, a conditional branch instruction will be immediately 
         preceeded by a compare instruction, whose purpose is to compare two
         operands (without altering either) and set the flags accordingly.
         As typical, this instruction comes in several variants:

         CMPB   91      (Two operands.  Compare first to second.)
         CMPW   B1
         CMPL   D1
         
         This is used in translating constructs like if X > Y

      2. Another useful instruction is the test instruction, which compares
         a value to 0.

         TSTB   95      (One operand.  Compare to zero.)
         TSTW   B5
         TSTL   D5

         This is used in translating constructs like if X > 0

      3. However, a conditional branch can also be used after most data
         movement and arithmetic instructions, because these set the condition
         codes on the basis of comparing the result of the operation to zero.
         Thus, the CMP and TST instructions are NOT needed to branch based on
         the result of an arithmetic operation.

         Example:       if X * Y - Z > 0

                        Would NOT require a CMP or TST

III. The VAX Branch Instructions
---  --- --- ------ ------------

   A. Unconditional

      1. BRB            11      Unconditional branch (byte offset)

         Note: Branch range is limited to -128 .. +127 bytes from beginning
               of next instruction.

      2. BRW            31      Unconditional branch (word offset)

         Note: Branch range is limited to -32768 .. +32767 bytes from beginning
               of next instruction.

   B. Conditional

      1. All of these use a byte offset only (-128 .. +127 byte range.)

      2. Many of the conditional branch instructions come in two versions,
         depending on whether the last operation is to be interpreted as
         working on unsigned numbers or a signed numbers.

         Example: Suppose we compare 80000000 (hex) to 40000000 (hex).  Is
                  80000000 > 40000000?

                  - If both are taken as unsigned numbers, then the answer is
                    clearly yes.

                  - If both are taken as signed numbers, then the answer is no,
                    because 80000000 is negative and 40000000 is positive.

         When SIGNED numbers are subtracted or compared, the N flag reflects
         their relative order.  When UNSIGNED numbers are subtracted or
         compared, the C flag (borrow out) reflects their relative order.
         
      3. The following are the branch instructions that will be most useful
         to us for now.  In each case, the signed version is listed first.

         TRANSPARENCY: Table of conditional branch instructions

         BEQL / BEQU    13      Branch if two items compared were equal, or
                                result of a data movement or arithmetic 
                                operation was = 0.  Note that these are two
                                names for the same instruction, since zero has
                                the same meaning regardless of whether it is
                                interpreted as signed or unigned.

         BNEQ / BNEQU   12      Branch if two items compared were not equal,
                                or result <> 0. (Ditto)

         BGTR / BGTRU   14/1A   Branch if first item compared > second, or
                                result > 0.

         BGEQ / BGEQU   18/1E   Branch if first item compared >= second, or
                                result >= 0.

         BLSS / BLSSU   19/1F   Branch if first item compared < second, or
                                result < 0.

         BLEQ / BLEQU   15/1B   Branch if first item compared <= second, or
                                result <= 0.

         BVS            1D      Branch if the last instruction resulted in
                                arithmetic overflow

         BVC            1C      Branch if the last instruction did NOT result
                                in arithmetic overflow

         BCS            1F      Branch if the last instruction resulted in
                                arithmetic carry or borrow

         BCC            1E      Branch if the last instruction did not result
                                in arithmetic carry or borrow

   C. The JMP instruction

      1. One limitation of the branch instructions is that their range is
         limited by the byte offset (or word in the case of BRW.)

      2. The JMP instruction is an unconditional branch instruction that uses
         the standard VAX addressing modes - thus it can reach any location
         in memory.  In each case, the target is the operand ADDRESS computed
         in the normal way.

         a. Example:    JMP @#1000      - take next instruction from 1000

         b. Example     JMP R0          - Illegal!!  (R0 has no address)

      3. Some HLL constructs must be translated circuitously because of the
         limited range of the branch instructions.

         Example:       if x > 0 then
                            y := x

                        Test x
                        BLEQ    SKIP
                        MOVL    Y, X
                SKIP:

        But:            if x > 0 then
                           -- many statements - requiring more than 127 bytes

                        Test x
                        BGTR    SKIP1
                        BRW     SKIP2
                SKIP1:  series of statements
                SKIP2:

        Or:             if x > 0 then
                           -- many statements - requiring more than 32767 bytes

                        Test x
                        BGTR    SKIP1
                        JMP     SKIP2
                SKIP1:  series of statements
                SKIP2:

IV. Some examples:
--  ---- ---------

   A. A program to compare two signed integers found in R0 and R1, and put the 
      bigger of the two in R2, leaving R0 and R1 unchanged.

        D1      CMPL
        50      R0
        51      R1

        18      BGEQ
        05      (+5) o-----------
                                |
        D0      MOVL            |
        51      R1              |
        52      R2              |
                                |
        11      BRB             |
        03      (+3) o----------|--------
                                |       |
        D0      MOVL <-----------       |
        50      R0                      |
        51      R2                      |
                     <-------------------

   B. A program to compute the integer square root of the unsigned integer in
      R0 by trial and error, leaving the result in R1.  (Note: if R0 is not a
      perfect square then the result will be ceiling of the true value.)  R2
      will be used as a scratch pad.

        D4      CLRL
        51      R1

        D0      MOVL    <----------------
        51      R1                      |
        52      R2                      |
                                        |
        C4      MULL2                   |
        52      R2                      |
        52      R2                      |
                                        |
        D1      CMPL                    |
        52      R2                      |
        50      R0                      |
                                        |
        1E      BGEQU                   |
        04      (+4) o------------------|--------
                                        |       |
        D6      INCL                    |       |
        51      R1                      |       |
                                        |       |
        11      BRB                     |       |
        F1      (-15) o------------------       |
                        <------------------------
`
        DEMO USING DEBUGGER

   C. HANDOUT: Translation patterns for various control structures

   D. HANDOUT: Branch patterns - VAX column

V. Subroutines
-  -----------

   A. As you know from the study of Pascal, breaking up a program into smaller 
      modules using procedures is crucial to being able to write large programs 
      correctly.

   B. The VAX has two mechanisms for modularizing programs: SUBROUTINES and
      PROCEDURES.

      1. The subroutine mechanism is used for routines that don't have
         formal parameters, or for which the parameters are passed through
         registers.

         Example: The IO routines used in previous demos

      2. The procedure mechanism is used for routines that need parameter
         lists, and is also the normal mechanism used when one module needs to
         call a routines in another module (including run-time library
         routines.)

      3. We will learn about the subroutine mechanism now and the procedure
         mechanism later in the course.

   C. The subroutine instructions: BSBB, BSBW, JSB, RSB

      3. The VAX has three instructions for calling a subroutine: BSBB, BSBW,
         and JSB.  These differ in how the address of the called routine
         is specified:

         a. BSBB - relative to calling point - byte offset - analogous to BRB.
            (Op-code = 10)

         b. BSBW - relative to calling point - word offset - analogous to BRW.
            (Op-code = 30)

         c. JSB - any address mode - analogous to JMP.
            (Op-code = 16)

         d. Each instruction does two things:

            i. Push the address of the NEXT instruction on the hardware stack
               (a longword).

           ii. Go to the starting address of the subroutine.

            Example: Suppose location 1000 contains a BSBB to 1070

                        6E 10   1000

                     Following execution of this instruction, the PC would
                     contain 00001070 and the top location on the stack would
                     hold 00001002

      4. The RSB instruction is used to return from a subroutine.  It pops
         a longword from the stack and transfers control to that address.
         (Op-code = 05)

VI. Some Additional Program Control Instructions     (SKIP IF INSUFFICIENT TIME)
--  ---- ---------- ------- ------- ------------

   A. Looping instructions.

      1. As the above examples illustrate, it is easily possible to write
         a program containing loops using the conditional branch instructions.

      2. However, the VAX instruction set includes some special instructions
         to facilitate COUNTER-CONTROLLED loops (e.g. Pascal for loops)

         a. AOBLEQ, AOBLSS can be used to translate Pascal for .. to loops

            i. Each takes three operands - a limit (longword), an index
               (longword), and a branch address (byte offset).

           ii. In each case, the index operand is incremented, and the
               result is compared to the limit.  If the result is <=
               the limit (AOBLEQ) or < the limit (AOBLSS), a branch is
               taken to the branch address.  Otherwise, control goes on
               to the next instruction.

            Example: Pascal:            for i := 1 to 10 do
                                            ...

                     MACRO:             MOVL    #1, I
                                LOOP:   Body of loop
                                        ...
                                        AOBLEQ  #10, I, LOOP

            Example: BASIC:             FOR I = 1 STEP 2 TO 10
                                            ...

                     MACRO:     Can't be done by AOBxxx.  Must be done by
                                ACBx - to be discussed below

         b. SOBGEQ, SOBGTR can be used to translate Pascal for .. downto
            loops (in some cases.)

            i. Each takes two operands - an index (longword), and a branch 
               address (byte offset).

           ii. In each case, the index operand is decremented, and the
               result is compared to zero.  (There is no limit operand in
               the instruction.)  If the result is >= 0 (SOBGEQ) or
               > 0 (SOBGTR), a branch is taken to the branch address.  
               Otherwise, control goes on to the next instruction.

            Example: Pascal:            for i := 10 downto 0 do
                                            ...

                     MACRO:             MOVL    #10, I
                                LOOP:   Body of loop
                                        ...
                                        SOBGEQ  I, LOOP

            Example: Pascal:            for i := 10 downto 1 do
                                            ...

                     MACRO:             MOVL    #10, I
                                LOOP:   Body of loop
                                        ...
                                        SOBGTR  I, LOOP

            Example: Pascal:            for i := 10 downto 5 do

                     MACRO:     Can't be done using SOBxxx - must be done
                                by ACBx

         c. The instructions we have just learned work for the special case
            of loops whose step is +/- 1 and whose limit (in the case of a
            step of -1) is either 0 or 1.  For more general counter-controlled
            loops, we must use ACBB, ACBW, ACBL, ACBF etc.

            i. Each takes four operands - a limit, and amount to add, an index,
               and a branch address (WORD offset).  (The data type of the first
               three operands is determined by which version of the instruction
               is used.)

           ii. In each case, the amount to add (which can be positive or 
               negative) is added to the index operand, and the
               result is compared to the limit.  If the index is <= the limit
               (for positive amount to add) or >= the limit (for negative
               amount to add), a branch is taken to the branch address.  
               Otherwise, control goes on to the next instruction.

            Example: BASIC:             FOR X := 1.0 TO 0.1 STEP -0.1

                     MACRO:             MOVF    #1.0, X
                                LOOP:   Body of loop
                                        ...
                                        ACBF    #0.1, #-0.1, X, LOOP

   B. The CASE instruction

      1. One very unusual instruction on the VAX is the CASE instruction,
         which is designed to support the case construct in languages like
         Pascal.

      2. The CASE instruction comes in three variants: CASEB, CASEW, and CASEL.
         In each case the instruction has three operands (of the specified
         type) - a selector, a base, and an upper limit.  These are
         followed by a series of WORD branch displacements.

         Example:       Pascal:         var i: -1 .. 1;
                                        ...

                                        case i of

                                          -1:   ...

                                           0:   ...

                                           1:   ...

                                        end

                        MACRO:          CASEB   I, #-1, #2
                                        ; Note 2 because base is subtracted from
                                        ; selector before limit comparison is 
                                        ;done
                                DISPL:  .WORD   MONE_CODE - DISPL
                                        .WORD   ZERO_CODE - DISPL
                                        .WORD   ONE_CODE - DISPL
                                        ...     Code for out of range error
                                        BRW     CASE_END
                        MONE_CODE:      ...     Code for -1
                                        BRW     CASE_END
                        ZERO_CODE:      ...     Code for 0
                                        BRW     CASE_END
                        ONE_CODE:       ...     Code for 1
                        CASE_END:

VII. Bit-Oriented Branches
---  ------------ --------

   A. BBS, BBC p, b, target - branch if a specified bit is set (1) or clear (0)

      Example: test console terminal ready bit

                1$: BBC         #7, @#MYTTY_CSR, 1$
                    MOVB        R0, @#MYTTY_DATA

   B. In VMS, the low order bit of a word is of special interest (e.g. in
      status codes from system services an odd value (low order bit = 1) 
      indicates success).   Therefore, there are special versions of
      this instruction for this bit: 

                BLBS s, target = BBS #0, s, target
                BLBC s, target = BBC #0, s, target

      Example: an integer is odd iff its low bit is 1 - therefore

        if odd(x) then          BLBC x ------
            something           something   |
                                      <------

VIII. MIPS Program-Control Instructions
----  ---- --------------- ------------

   A. Unconditional - Two variants:

      1. j address      - Destination address is contained in instruction

      2. jr register    - Destination address is contained in register

   B. Conditional

      1. The VAX and MIPS architectures take a quite different approach to 
         conditional branches.

         a. The VAX makes use of condition codes, which are always set by a
            previous computational instruction.

         b. The MIPS conditional branch instructions perform a comparison
            between two registers, and then take/don't take the branch
            conditioned on the result.  There are only two such instructions:

            i. beq - branch if the two registers are equal
        
           ii. bne - branch if the two registers are not equal

            Note that the mnemonics are identical to two VAX conditional branch
            instructions - but the meanings are quite different! 

         c. Examples:

            VAX:        CMP     R1, R2
                        BEQL    FOO

            MIPS:       beq     $1, $2, foo

            
            VAX:        TST     R1
                        BNEQ    FOO

            MIPS:       bne     $1, $0, foo

            Note that, in the above cases, the MIPS program is shorter.  (Also, 
            the branch range is much greater - the MIPS instruction has a 16
            bit branch offset; the VAX instruction has only 8 bits).

      2. How does MIPS handle testing for less than, greater than, etc?  By
         using auxillary instructions that set a register to 1 or 0 based on
         comparison of two other values.

            slt  - compare two registers
            slti - compare a register to an immediate value
            sltu - same as slt, but unsigned
            sltiu- same as slti, but unsigned

         a. Example:

           VAX:         CMP     R1, R2
                        BLSSU   FOO

           MIPS:        sltu    $12, $1, $2
                        bne     $12, $0, foo

                        (sltu sets $12 to 1 if $1 < $2; bne ... branches if
                         $12 is not equal to 0)

         b. With only a set if less than, how do we handle other orders?

            ASK

            x < y       slt(u)  temp, x, y
                        bne     temp, target

            x > y       slt(u)  temp, y, x
                        bne     temp, target

            x <= y      slt(u)  temp, y, x
                        beq     temp, target    (x <= y <=> not y < x)

            x >= y      slt(u)  temp, x, y
                        beq     temp, target    (x >= y <=> not x < y) 

      3. How does MIPS handle carry and overflow testing?

         a. There is no provision for dealing with carry.

         b. Overflow results is handled by means of an exception - for this 
            reason, some arithmetic operations have two versions, one which 
            produces an exception on overflow and the other of which ignores
            this. (This is the basic difference between add and addu, sub and 
            subu.  The "unsigned" versions perform the same computation, but
            ignore overflow).

   D. Subroutine
        
      a. The MIPS instruction for calling a subroutine is jal - jump and link -
         which places the return address in a specified register (as opposed
         to pushing it on a stack.)

      b. The return from subroutine operation is done by using jr, specifying
         the same register.  

      By convention, register $31 is used for this purpose.

   E. HANDOUT - Go over MIPS column in branches handout

Copyright ©2000 - Russell C. Bjork