SlideShare a Scribd company logo
EE312                          Embedded Microcontrollers                   TUE / THU 9:00AM
Final Lab                                                                       Spring 2009




                                          EE 312

                              Embedded Microcontrollers

                                Final Lab Assignment




        “Modular programming with the MC68HC11, using loops,

subroutines, branching, terminal I/O, Buffalo Monitor I/O, LEDs,

              LCDs, sounds, buttons, and ASCII conversion.”



                                By:   Loren K. Schwappach

                               Student Number:       06B7050651




                                 Date Due:    May 18, 2009

                              Date Completed:    May 16, 2009



Professor:   Pamela Hoffman           Page 1 of 81            Colorado Technical University
EE312                         Embedded Microcontrollers                TUE / THU 9:00AM
 Final Lab                                                                   Spring 2009


    1. Purpose:
         This program will cover many of the possibilities offered by the

 MC68HC11, FOX-11 board.       It will use the buffalo monitor and terminal I/O

 addresses to get/send information to a monitor and LCD.          This lab will

 demonstrate sound, buttons, LEDs, basic math operations, and finally how

 to convert ASCII user input into numerical values for a small math

 computation game.




    2. Future project ideas for students:
  I.     Use the keypad for setting variable speed of the LED racetrack.

II.      Create a module that would get/convert/store several larger ASCII (0-

         9) numerals into Hex at a separate memory location and reconvert for

         terminal & LCD output.

III.     Develop song for intro using Buffalo monitor test.asm demo

IV.      Have credits at the end scroll and repeat over the LCD, by

         incrementing the X location in a loop and calling the LCD display

         subroutine until the end of the string +16.




 Professor:   Pamela Hoffman         Page 2 of 81          Colorado Technical University
EE312                         Embedded Microcontrollers                TUE / THU 9:00AM
  Final Lab                                                                   Spring 2009


     3. Instructions and Directives:


I.        LOAD:   Places a specified value or memory location(s) into a register

  for temporary storage manipulation.         It can be used to load values /

  address in 8 bit accumulators A or B, or the 16 bit registers, double

  accumulator D (Uses A and B), the stack pointer, or either index register

  X or Y.




  Figure 4.1:     Load instructions



  Professor:   Pamela Hoffman         Page 3 of 81          Colorado Technical University
EE312                           Embedded Microcontrollers                TUE / THU 9:00AM
   Final Lab                                                                     Spring 2009


II.        ADD:    Performs arithmetic addition operation(s) upon registers. Very

   powerful!




   Figure 4.2:       Add instructions




   Professor:     Pamela Hoffman         Page 4 of 81          Colorado Technical University
EE312                           Embedded Microcontrollers                TUE / THU 9:00AM
    Final Lab                                                                     Spring 2009


III.        SUB:    Performs arithmetic subtraction operation(s) upon registers.

    Also very powerful!




    Figure 4.3:       Subtraction instructions




    Professor:     Pamela Hoffman         Page 5 of 81          Colorado Technical University
EE312                         Embedded Microcontrollers                TUE / THU 9:00AM
   Final Lab                                                                   Spring 2009


IV.        STORE:   Stores contents of register into memory location(s).

   Destination must be a valid storable memory location.         Also if register is

   16 bit register, storage will consume two blocks of memory.




   Figure 4.4:      Store instruction




   Professor:   Pamela Hoffman          Page 6 of 81         Colorado Technical University
EE312                           Embedded Microcontrollers                  TUE / THU 9:00AM
   Final Lab                                                                       Spring 2009


 V.        MUL:    Multiplies an 8-bit unsigned value in A by an 8-bit unsigned

   value in B to obtain a 16-bit unsigned result in D (thus writes over A and

   B).     Uses inherent addressing.

   Example:

   Start:         ORG   $9000      ; directive, sets program start

                                   ; location.     Use go 9000

                  LDAA #10         ; load accum. A with decimal 10

                  LDAB #25         ; load accum. B with decimal 25

                  MUL              ; multiplies A*B stores decimal

                                   ; value 250 in D

                  STD    $8000     ; stores D at location $8000 and

                                   ; $8001

                  END              ; housekeeping directive tells

                                   ; program to halt.



VI.        DIV:    There are two division instructions IDIV and FDIV.

           IDIV performs unsigned integer division of the 16 bit numerator in D

   by the 16 bit denominator in X.           For the result, the quotient is placed in

   X and the remainder is placed in D.           If denominator is 0 the quotient is

   set to $FFFF, the remainder is indeterminate and the CCR C flag is set=1.

   IDIV uses inherent addressing.



   Example:


   Professor:     Pamela Hoffman         Page 7 of 81            Colorado Technical University
EE312                           Embedded Microcontrollers                   TUE / THU 9:00AM
    Final Lab                                                                        Spring 2009


    LDD     #4     ; Loads D with decimal value 4

    LDX     #2     ; Loads X with decimal value 2

    IDIV           ; (4/2)=2 w/ r=0 so X=2, D=0



            FDIV performs unsigned fractional division of the 16 bit numerator in

    D by the 16 bit denominator in X.           For the result, the quotient is placed

    in X and the remainder is placed in D.            If the denominator is 0 or in the

    case of overflow the quotient is set to $FFFF and remainder is

    indeterminate and CCR C flag is set=1.               The radix point is to the left of

    bit 15 for the quotient.         FDIV uses inherent addressing.



    Example:

    LDD     #2     ; 4 is loaded in D (numerator)

    LDX     #3     ; 3 is loaded in X (denominator)

    FDIV           ; quotient in X, remainder in D



VII.        DAA:    Decimal Adjust Accumulator A, used for BCD addition.           Checks

    CCR C (Carry) flag, upper half byte of Accumulator A, initial H (Half

    Carry) flag, lower byte of Accumulator A and uses conditions to add a set

    amount to Accumulator A and finally resets C flag.              This ensures correct

    BCD addition.        Use inherent addressing.



    Example:


    Professor:     Pamela Hoffman         Page 8 of 81             Colorado Technical University
EE312                           Embedded Microcontrollers                TUE / THU 9:00AM
     Final Lab                                                                     Spring 2009


     LDA     #$04         ; Load BCD 00100100, decimal value 04

     ADDA #$16            ; Load BCD 00010110, decimal value 16

     DAA                  ; Checks A, and CCR and then adds $06 to A

                          ; A now correctly holds hex $20 BCD value

                          ; 00100000



VIII.        Exchange Registers:       There are two instructions that perform register

     exchanges.       XGDX (exchange double accumulator D with index register X) and

     XGDY (exchange double accumulator D with index register Y), both use

     inherent addressing.



     Example (Assume X = 8020 and Y = 8040 prior to execution):

     LDD     #$8000       ; Load D w/ hex value 8000

     XGDX                 ; D now holds $8020, X now holds 8000

     XGDY                 ; D now holds $8040, Y now holds 8020

     Note:     Another way of exchanging register is with the load and store

     instructions already covered.




     Professor:     Pamela Hoffman         Page 9 of 81          Colorado Technical University
EE312                         Embedded Microcontrollers                TUE / THU 9:00AM
   Final Lab                                                                   Spring 2009


IX.        Compare / Test Instruction:      Used to compare or test registers /

   locations and set CCR flags, while leaving compared accumulator contents

   intact.      Very powerful!   Used to control branch instructions and

   interrupts.      Often used in loop control.




   Figure 4.5 Compare and Test Instructions




   Professor:   Pamela Hoffman         Page 10 of 81         Colorado Technical University
EE312                         Embedded Microcontrollers                 TUE / THU 9:00AM
  Final Lab                                                                    Spring 2009


X.        Branch / Jump / Return Instructions:

  Branch, Jump, and Return instructions tell the program to go somewhere

  else or return from somewhere, normally depending upon CCR flag and the

  use of the stack.



  Branch instructions (Essential for modular programming and loops):

          The following are branch instructions that if the conditions are met

  (CCR) the program branches to relative address specified (relative

  addresses are offsets from current address limited to -128 to 127 bytes)

  so is very limited to the location it can branch to...) Refer to a text on

  Boolean algebra if you do not understand AND, OR, XOR operations



  Instr.       ; Meaning                          ; Branches if

  BRA <rel> ; branch (unconditional)              ; Always

  BCC <rel> ; carry clear                         ; C = 0

  BCS <rel> ; carry set                           ; C = 1

  BLO <rel> ; lower (unsigned)                    ; C = 1

  BHS <rel> ; higher or same (unsigned)           ; C = 0

  BEQ <rel> ; equal to 0                          ; Z = 1

  BNE <rel> ; not equal to 0                      ; Z = 0

  BPL <rel> ; plus (signed)                       ; N = 0

  BMI <rel> ; minus (signed)                      ; N = 1

  BVS <rel> ; overflow bit set                    ; V = 1


  Professor:   Pamela Hoffman         Page 11 of 81          Colorado Technical University
EE312                         Embedded Microcontrollers                   TUE / THU 9:00AM
Final Lab                                                                      Spring 2009


BVC <rel> ; overflow bit clear                  ; V = 0

BGE <rel> ; greater or = to 0 (signed)          ; (N XOR V) = 0

BGT <rel> ; greater than 0 (signed)             ; (Z + (N XOR V)) = 0

BHI <rel> ; higher or same (unsigned)           ; (C + Z) = 0

BLE <rel> ; less than or = 0                    ; (Z + (N XOR V)) = 1

BLS <rel> ; lower or same (unsigned)            ; (C + Z) = 1

BLT <rel> ; less than 0 (signed)                ; (N XOR V) = 1

BCLR <operand>           ; clear bits           ; M AND M’

        <msk>

BRCLR <operand>          ; if bits clear        ; M AND (PC+2) = 0

         <msk><rel>

BSET <operand>           ; set bits             ; M + M AND M

        <msk>

BRSET <operand>          ; if bits set          ; M AND (PC+2) = 1

        <msk><rel>




Professor:   Pamela Hoffman         Page 12 of 81            Colorado Technical University
EE312                         Embedded Microcontrollers                    TUE / THU 9:00AM
Final Lab                                                                       Spring 2009


Jump Instructions:

JMP <operand>      ; Jumps to instruction stored at effective address given in

operand.     JMP uses extended or indexed addressing.



JSR <operand>      ; Jumps to subroutine specified by operand.          JSR uses

direct, extended, or indexed addressing.            Note:   This allows for the

creation of modular programming (functions).              JSR increments the program

counter (PC) by two or three depending upon addressing used and pushes the

PC onto the stack so you can return where you left off using RTS (Return

from Sub Routine) instruction.



Return Instructions:

        There are two return instructions RTS (Return from Sub Routine) and

RTI (Return from interrupt).



RTS     ; Uses inherent addressing and is used to return out the called

subroutine back to the caller subroutine.            This is accomplished by

incrementing the stack pointer and loading the address contained back into

the program counter.



RTI     ; Users inherent addressing and is used to restore A, B, X, Y, CCR,

and PC states by pulling them from the stack, also may or may not set CCR

X flag.


Professor:   Pamela Hoffman         Page 13 of 81             Colorado Technical University
EE312                         Embedded Microcontrollers                TUE / THU 9:00AM
    Final Lab                                                                   Spring 2009


 XI.        Decrement / Increment Instructions (Often used in loops):

    DEC <operand>      ; decrements value at location by 1, value - 1

    DECA               ; decrements A by 1, A = A - 1

    DECB               ; decrements B by 1, B = B - 1

    DEX                ; decrements X by 1, X = X - 1

    DEY                ; decrements Y by 1, Y = Y - 1

    DES                ; decrements SP by 1, SP = SP - 1



    INC <operand>      ; increments value at location by 1, value + 1

    INCA               ; increments A by 1, A = A + 1

    INCB               ; increments B by 1, B = B + 1

    INX                ; increments X by 1, X = X + 1

    INY                ; increments Y by 1, Y = Y + 1

    INS                ; increments SP by 1, SP = SP + 1



XII.        Rotate & Shift (Logical & Arithmetic) Instructions:




    Professor:   Pamela Hoffman         Page 14 of 81         Colorado Technical University
EE312                         Embedded Microcontrollers                TUE / THU 9:00AM
Final Lab                                                                   Spring 2009




Figure 4.6:     Rotate and Shift Instructions




Professor:   Pamela Hoffman         Page 15 of 81         Colorado Technical University
EE312                           Embedded Microcontrollers                TUE / THU 9:00AM
     Final Lab                                                                     Spring 2009


XIII.        PUSH / PULL & Transfer Instructions:

     Push and pull instructions manipulate the stack which is discussed in

     detail in Section 8.          They are extremely valuable instructions and assist

     in searching, accessing, and manipulating strings and arrays as well as

     preserving register values for modular programming.




     Figure 4.7:     Push and Pull instructions



     Transfer Instructions:

     Professor:   Pamela Hoffman           Page 16 of 81         Colorado Technical University
EE312                         Embedded Microcontrollers                TUE / THU 9:00AM
    Final Lab                                                                   Spring 2009


    Transfer instructions are used to manipulate the stack pointer (SP), and

    thus can be used to quickly navigate the stack.




    Figure 4.8:     Transfer Instructions



XIV.        Clear Instruction & variable initialization:

    Clear “CLR” instructions do just what they suggest; they replace the

    contents of a memory location or register with zeros.         This is often used

    for variable initialization.




    Figure 4.9:     Clear Instructions



    Professor:   Pamela Hoffman         Page 17 of 81         Colorado Technical University
EE312                         Embedded Microcontrollers                TUE / THU 9:00AM
   Final Lab                                                                   Spring 2009


XV.        Other Important Instructions:

   Logic Instructions

   ANDA <operand> ; AND A with memory (Immediate, Direct, Extended,                or

                      Indirect Addressing)

   ANDB <operand> ; AND B with memory (Immediate, Direct, Extended,                or

                      Indirect Addressing)

   BITA <operand> ; Bit tests A with memory (A AND M) and sets CCR

                      (Immediate, Direct, Extended, or Indirect

                      Addressing)

   BITB <operand> ; Bit tests B with memory (B AND M) and sets CCR

                      (Immediate, Direct, Extended, or Indirect

                      Addressing)

   COM <operand> ; Get value at operand and take ones complement or

                      invert bits (extended or indirect addressing)

   COMA               ; Take ones comp. of A store in A, invert bits

   COMB               ; Take ones comp. of B store in B, invert bits

   EORA <operand> ; XOR with value in memory w/ A store in A

                      (Immediate, extended, direct, indirect)

   EORB <operand> ; XOR with value in memory w/ B store in B

                      (Immediate, extended, direct, indirect)




   Professor:   Pamela Hoffman         Page 18 of 81         Colorado Technical University
EE312                         Embedded Microcontrollers                TUE / THU 9:00AM
Final Lab                                                                   Spring 2009


NEG <operand>      ; 2’s complement of memory store in memory

                   (Extended or Indirect)

NEGA               ; 2’s complement of A store in A

NEGB               ; 2’s complement of B store in B

ORAA <operand> ; OR A with memory store in A

ORAB <operand> ; OR B with memory store in B




Other Useful Instructions (Note: Several used for interrupts)

CLV                ; lear overflow flag, V=0

NOP                ; No operation, takes up clock cycles for nothing

SEC                ; Set carry, C=1

SEI                ; Set interrupt mask, I=1

SEV                ; Set overflow flag, V=1

STOP               ; Stop internal clock

SWI                ; Software interrupt

TAP                ; Transfer A to CCR

TPA                ; Transfer CCR to A

WAI                ; Wait for interrupt




Professor:   Pamela Hoffman         Page 19 of 81         Colorado Technical University
EE312                            Embedded Microcontrollers                 TUE / THU 9:00AM
    Final Lab                                                                       Spring 2009


XVI.        Directives:

            Directives are commands to the assembler that define data and

    symbols, setting assembly conditions, and specifying output format.

    Directives do not produce code but perform housekeeping activities for the

    assembler.

            ORG <address>     ; Sets value of location counter to address specified

            RMB <#>           ; Reserves memory byte(s), number given by #

            DCB               ; Defines constant block, reserves area in memory and

                              initializes each byte to the same constant.

            FCB <......>      ; Forms constant byte(s) w/ value set by operand

            FDB <......>      ; Forms 2 bytes for each argument

            FCC <......>      ; Forms constant character(s), forms ASCII string, use

                              “This is my String” format.

            BSZ <#>           ; Reserves a number of bytes specified starting at

                              location counter and initializes each/all value(s) to

                              $00.

            FILL <Value1, Value2>          ; Reserves # of bytes (Value1) and fills

                                           each with Value2 starting at address given

                                           by location counter.

            END               ; Indicates the END of a program.




    Professor:    Pamela Hoffman           Page 20 of 81          Colorado Technical University
EE312                         Embedded Microcontrollers                TUE / THU 9:00AM
Final Lab                                                                   Spring 2009


   4. Understanding and Using the program:
        This begin this lab copy/paste/save/assemble/load the program and

start the program at memory location $9000 with the “go $9000” command.

$9000 is where I begin to store all of the program code for this lab.

        Once the program begins the first thing that is accomplished is to

load the stack pointer at $C800.         This should always be in the first few

lines of code for any program that plans on making use of the stack, as

all modular programs should.

        I also use the equate directive extensively, which helps in keeping

port locations, terminal/Buffalo monitor I/O routines, ASCII values, and

delay loop variables easy to remember.

        I also declared/formed area for the storage of my user input ASCII

values and filled the first 16 blocks with ASCII whitespace and a

terminating EOT so that the terminal display routine and Buffalo monitor

LCD routine could correctly handle/display the correct information when

called.      These string locations as well as other temp variable locations

begin at locations $8000 in memory for easy referencing.

        As with the above, I also formed/reserved storage for all of the

strings, ensuring all strings were 16 characters and ending in a ASCII EOT

for later referencing.        All output strings begin at memory location $A000.

This sort of memory assignment/separation is important for T/S code and

ensures that you don’t have problems where pieces of code override one

another.

Professor:   Pamela Hoffman         Page 21 of 81         Colorado Technical University
EE312                           Embedded Microcontrollers                    TUE / THU 9:00AM
Final Lab                                                                         Spring 2009


        Next, after beginning the program and loading the stack I immediately

call a jump statement that sends the program to my main_func subroutine,

which if you are reading the code right now is at the very bottom.                  Just

like in C or C++ this seemed a logical place for placing the subroutine

that would call all other subroutines.

        Once in main_func subroutine I begin calling all of the following

other subroutines but before I go into them let me explain something about

them all.     To ensure that I can contain each subroutines variables and

register components intact I make extensive use of the stack pull and push

instructions.      This allows each subroutine to keep a form of temporary

register storage and prevents a register value in one subroutine from

interfering with another subroutines values.                If I plan on passing a

register from one subroutine to the next over and over I skip this

push/pull which allows the two to use each other’s register values.

        The first subroutine called is LCD_init which initializes the Buffalo

monitor LCD for use.          Next I call Clear LEDs which sets the value $00 in

port B and clears the LEDs.          Next, I call Disp_LCD_clear which clears the

LCDs with whitespace.          I then call Disp_welcome to display my initial

program welcome message.

        Next, Flash_LEDs_osc displays an oscillating (middle to left/right,

left/right to middle) LED pattern using a delay routine and specifies

values of Port B to flash the LEDs and make a beep when the LEDs touch

(like a hospital heart monitor), a simple but dramatic effect.

Professor:   Pamela Hoffman           Page 22 of 81             Colorado Technical University
EE312                         Embedded Microcontrollers                    TUE / THU 9:00AM
Final Lab                                                                       Spring 2009


        Next I call Disp_q_name to tell the user I would like their name.              I

then call Get_name to get the users name and store it at an assigned

memory location.      I also prevent the users input from storing more than 16

characters so that the name displays correctly on the LCD.               I then call

Display_name to display their results to screen.

        Finally I call Display_press_btn, which tells the user to press one

of three buttons and the I call Check_buttons which selectively calls for

four other subroutines, one which checks for a button being pressed, and

if pressed calls one of the other three subroutines depending upon which

button was pressed.       Depending upon the button pressed the program will do

one of the following...

        The first button will flash the intro LED pulse pattern ten times.

The second run a looping colorful racetrack LED pattern using the

breadboard and LEDs (Note: If you want to do this on your breadboard you

will need to use the PB0-PB7 outputs as highs to your breadboard LEDs and

use the ground as a low for your breadboard.              I also ensured that the

delay subroutines used a temporary delay value that although I didn’t use

the user could expand upon the program and build a module to increase or

decrease the speed at which the racetrack LEDs flashed (I leave this up to

the user).

        The third button will run a simple math program to get two numbers

(0-4) from the user, it then converts the numbers into their actual hex

value representations for computation, reconverts the result into ASCII

Professor:   Pamela Hoffman         Page 23 of 81             Colorado Technical University
EE312                         Embedded Microcontrollers                    TUE / THU 9:00AM
Final Lab                                                                       Spring 2009


stores and displays on the terminal and LCD.              I had plans to make this

perform larger computations but would have needed to create a larger

module in order to handle large user ASCII strings into hex values

conversion for multi-precision addition (Remember each ASCII numeral

entered is two bytes (representing 10 possibilities 0-9) where the actual

hex only needs one and represents 16 possibilities (decimal 0-15 or 0-F).

To simplify the program I used validation routines that ensured the user

could only enter a value between 0 and 4 (Because max values 4+4=8 which

simplifies ASCII conversion +/- $30).

        Once the user is done with the choices I used a loop for the

Check_buttons routine which caused the loop to exit after a certain period

of inactive time (30 seconds).

        Then Display_credits and Display_exit_world is called to display

goodbye messages to the user.

        Finally the program exits Main_Func and returns to the top where the

registers are cleared and the program terminates.




Professor:   Pamela Hoffman         Page 24 of 81             Colorado Technical University
EE312                                   Embedded Microcontrollers                           TUE / THU 9:00AM
Final Lab                                                                                        Spring 2009


* Assembly Code!

* Final Project, Version 1

* Coded by: Loren K. R. Schwappach

* Coded on: 13 June 09




* Completed in Requirements for:

* EE312, Embedded Microcontrollers

* Instructor: Professor Pamella Hoffman




* Program description: This program will cover many of the possibilities

* offered by the MC68HC11, FOX-11 board.    It will use the buffalo monitor

* and I/O addresses to get/send information to a monitor and LCD.   It will

* demonstrate sound, buttons, LEDs, and how to control output to a bread board.

* it also demonstrates how to convert ASCII user input into numerical values

* for a small math computation.




* Future ideas (if time permitted..)

* #1 Use the keypad for setting variable speed of racetrack

* #2 Create a module the would get/convert/store large ASCII numerals to Hex

*   And then retrieve/convert/store these values in ASCII for display

* #3 Develop song for intro..

* #4 Have credits scroll and repeat over LCD by inc X in loop and increasing init string size




* ------------------------

* References

* ------------------------

* Define addresses for LCD output

LCD_init                 EQU    $FF70   ; Address to initialize the LCD

LCD_write_top            EQU    $FF73   ; Address to write to LCD top

LCD_write_bottom         EQU    $FF76   ; Address to write to LCD bottom




Professor:      Pamela Hoffman                Page 25 of 81                    Colorado Technical University
EE312                                    Embedded Microcontrollers                               TUE / THU 9:00AM
Final Lab                                                                                             Spring 2009


* Define addresses/values for terminal I/O

Output_disp_text        EQU      $FFC7    ; Outputs all ASCII stored at loc in X until EOT

Input_get_char          EQU      $FFCD    ; Gets ASCII character from keyboard -> stores in A

Output_disp_CR          EQU      $FFC4     ; Outputs ASCII character return and line feed

CR                      EQU      $0D      ; ASCII CR, (enter key)

EOT                     EQU      $04      ; ASCII EOT, (End Of Transmission)




* Define port I/O addresses

Port_A           EQU    $1000    ; Port A Address

Port_B           EQU    $1404    ; Port B Address

Port_C           EQU    $1403    ; Port C Address




* Delay loop times

Hundred_ms       EQU     16700       ; Loop iterations for 100ms delay

Ten_ms           EQU    1670     ; Loop iterations for 10ms delay

One_ms           EQU    167      ; Loop iterations for 1ms delay

Var_ms           EQU     2505        ; Loop iterations for variable delay (15ms)




* Other important values

* Store Program at {$9000 - $9FFF}, Store Stack at {$C800 - $C000}

Program_loc      EQU    $9000    ; Begin program here w/ go 9000 command

Stack_loc        EQU    $C800    ; Set aside location for stack, used extensively




* ------------------------

* Variable Storage Locations {$8000 - $8FFF}

* ------------------------

Username         EQU     $8000       ; Location to reference later for ASCII name storage

                 ORG    $8000    ; Set location to $8000

                 FILL   16, $20 ; Fill 16 blocks from $8000 to $8010 with $20 "ASCII space"

                                 ;     Note on above: value $20 used so LCDs display correctly

                 FCB    EOT      ; Form Constant Block at $8011 with ASCII EOT



Professor:       Pamela Hoffman                  Page 26 of 81                     Colorado Technical University
EE312                                   Embedded Microcontrollers                                TUE / THU 9:00AM
Final Lab                                                                                             Spring 2009




Result         EQU     $8020       ; Location to reference later for ASCII math result storage

               ORG    $8020    ; Set location to $8020

               FILL   16, $20 ; Fill 16 blocks from $8020 to $8030 with $20 "ASCII space"

                               ;     Note on above: value $20 used so LCDs display correctly

               FCB    EOT      ; Form Constant Block at $8031 with ASCII EOT




Value1         RMB        1        ; Reserve Memory Block at $8032 for math fun value 1

value2         RMB        1        ; Reserve Memory Block at $8033 for math fun value 2




* ------------------------

* String Output Locations {$A000 - $AFFF}

* ------------------------

               ORG    $A000                     ; Set location for storage of string

Clear_LCD      FCC    "                   "     ; Form Constant Character for LCD "16 character" display

               FCB    EOT                       ; Form Constant Block at location above + 17 for output to monitor

               ORG    $A020                     ; Set location for storage of string

Welcome1       FCC    " Welcome to my     "     ; Form Constant Character for LCD "16 character" display

               FCB    EOT                       ; Form Constant Block at location above + 17 for output to monitor

               ORG    $A040                     ; Set location for storage of string

Welcome2       FCC    "EE312 FOX11 Demo"        ; Form Constant Character for LCD "16 character" display

               FCB    EOT                       ; Form Constant Block at location above + 17 for output to monitor

               ORG    $A060                     ; Set location for storage of string

Question_Name1 FCC    " Please enter,     "     ; Form Constant Character for LCD "16 character" display

               FCB    EOT                       ; Form Constant Block at location above + 17 for output to monitor

               ORG    $A080                     ; Set location for storage of string

Question_Name2 FCC    " Your name...      "     ; Form Constant Character for LCD "16 character" display

               FCB    EOT                       ; Form Constant Block at location above + 17 for output to monitor

               ORG    $A0A0                     ; Set location for storage of string

Warning1       FCC    " !Max 15 char!     "     ; Form Constant Character for LCD "16 character" display

               FCB    EOT                       ; Form Constant Block at location above + 17 for output to monitor



Professor:    Pamela Hoffman                   Page 27 of 81                   Colorado Technical University
EE312                              Embedded Microcontrollers                              TUE / THU 9:00AM
Final Lab                                                                                       Spring 2009


              ORG    $A0C0                 ; Set location for storage of string

Question_Name3 FCC   "Enter name -here"    ; Form Constant Character for LCD "16 character" display

              FCB    EOT                   ; Form Constant Block at location above + 17 for output to monitor

              ORG    $A0E0                 ; Set location for storage of string

Response_Name1 FCC   "**** Hello **** "    ; Form Constant Character for LCD "16 character" display

              FCB    EOT                   ; Form Constant Block at location above + 17 for output to monitor




              ORG    $A100                 ; Set location for storage of string

Press_Btn1    FCC    " Press a Button "    ; Form Constant Character for LCD "16 character" display

              FCB    EOT                   ; Form Constant Block at location above + 17 for output to monitor

              ORG    $A120                 ; Set location for storage of string

Press_Btn2    FCC    "PA0, PC1, or PC0"    ; Form Constant Character for LCD "16 character" display

              FCB    EOT                   ; Form Constant Block at location above + 17 for output to monitor

              ORG    $A140                 ; Set location for storage of string

Warning2      FCC    "20s left to exit"    ; Form Constant Character for LCD "16 character" display

              FCB    EOT                   ; Form Constant Block at location above + 17 for output to monitor

              ORG    $A160                 ; Set location for storage of string

Warning3      FCC    "10s left to exit"    ; Form Constant Character for LCD "16 character" display

              FCB    EOT                   ; Form Constant Block at location above + 17 for output to monitor




              ORG    $A180                 ; Set location for storage of string

MathA_1       FCC    " Time for some   "   ; Form Constant Character for LCD "16 character" display

              FCB    EOT                   ; Form Constant Block at location above + 17 for output to monitor

              ORG    $A1A0                 ; Set location for storage of string

MathA_2       FCC    "Simple math fun "    ; Form Constant Character for LCD "16 character" display

              FCB    EOT                   ; Form Constant Block at location above + 17 for output to monitor

              ORG    $A1C0                 ; Set location for storage of string

MathB_1       FCC    " Give me two #s "    ; Form Constant Character for LCD "16 character" display

              FCB    EOT                   ; Form Constant Block at location above + 17 for output to monitor

              ORG    $A1E0                 ; Set location for storage of string

MathB_2       FCC    "1 dig.= {0 to 4}"    ; Form Constant Character for LCD "16 character" display



Professor:    Pamela Hoffman               Page 28 of 81                  Colorado Technical University
EE312                                 Embedded Microcontrollers                            TUE / THU 9:00AM
Final Lab                                                                                          Spring 2009


               FCB    EOT                   ; Form Constant Block at location above + 17 for output to monitor

               ORG    $A200                 ; Set location for storage of string

MathC_1        FCC    "ENT 1st Number: "    ; Form Constant Character for LCD "16 character" display

               FCB    EOT                   ; Form Constant Block at location above + 17 for output to monitor

               ORG    $A220                 ; Set location for storage of string

MathD_1        FCC    "ENT 2nd Number: "    ; Form Constant Character for LCD "16 character" display

               FCB    EOT                   ; Form Constant Block at location above + 17 for output to monitor

               ORG    $A240                 ; Set location for storage of string

MathE_1        FCC    "The Result is.. "    ; Form Constant Character for LCD "16 character" display

               FCB    EOT                   ; Form Constant Block at location above + 17 for output to monitor




               ORG    $A260                 ; Set location for storage of string

Credits1       FCC    "Created by..     "   ; Form Constant Character for LCD "16 character" display

               FCB    EOT                   ; Form Constant Block at location above + 17 for output to monitor

               ORG    $A280                 ; Set location for storage of string

Credits2       FCC    "Loren Schwappach"    ; Form Constant Character for LCD "16 character" display

               FCB    EOT                   ; Form Constant Block at location above + 17 for output to monitor




               ORG    $A2A0                 ; Set location for storage of string

Exit_World1    FCC    "Exiting EE312Lab"    ; Form Constant Character for LCD "16 character" display

               FCB    EOT                   ; Form Constant Block at location above + 17 for output to monitor

               ORG    $A2C0                 ; Set location for storage of string

Exit_World2    FCC    "Press reset btn "    ; Form Constant Character for LCD "16 character" display

               FCB    EOT                   ; Form Constant Block at location above + 17 for output to monitor

* ------------------------

* Call program and set Stack location

* ------------------------

Start          ORG    Program_loc           ; Set location counter for program storage { Program starts at
$9000 }

               LDS    #Stack_loc            ; Loads begining storage location for stack at $C800

               JSR    Main_func             ; Jumps over all subroutines below to main subroutine at bottom of
page



Professor:    Pamela Hoffman                Page 29 of 81                  Colorado Technical University
EE312                                Embedded Microcontrollers                            TUE / THU 9:00AM
Final Lab                                                                                         Spring 2009


                 JSR     Clear_reg         ; Jump to subroutine clear registers

Terminate        END                       ; Ends Program




* ------------------------

* Subroutines

* ------------------------

* Clear Registers

Clear_reg        LDAA    #$00              ; Load Accum. A w/ 0

                 LDAB    #$00              ; Load Accum. B w/ 0

                 LDX     #$0000            ; Load Index Reg X w/ 0

                 LDY     #$0000            ; Load Index Reg Y w/ 0

                 RTS                       ; Return to Subroutine which called this




* Delay Subroutines

Delay            DEX                       ; Decrement X {Take up some time.. clock cycles}

                 INX                       ; Increment X {Take up some time.. clock cycles}

                 DEX                       ; Decrement X, initial X value provided by routine that called this

                 BNE     Delay             ; Branch if not equal to 0 to Delay.. loop until X=0

                 RTS                       ; Return to Subroutine which called this




Delay_1ms      PSHX                        ; Push X onto stack, prevents loss of data stored in X during
subroutine use

                 LDX     #One_ms           ; Load X with value referenced by EQU above

                 BSR     Delay             ; With retrieved X value obtained branch to delay to take up
indicated time

               PULX                        ; Pull X value stored in stack to X, restores data stored in X
before subroutine call

                 RTS                       ; Return to Subroutine which called this




Delay_10ms     PSHX                        ; Push X onto stack, prevents loss of data stored in X during
subroutine use

                 LDX     #Ten_ms           ; Load X with value referenced by EQU above




Professor:       Pamela Hoffman            Page 30 of 81                  Colorado Technical University
EE312                                  Embedded Microcontrollers                             TUE / THU 9:00AM
Final Lab                                                                                           Spring 2009


                 BSR     Delay                ; With retrieved X value obtained branch to delay to take up
indicated time

               PULX                           ; Pull X value stored in stack to X, restores data stored in X
before subroutine call

                 RTS                          ; Return to Subroutine which called this




Delay_100ms    PSHX                           ; Push X onto stack, prevents loss of data stored in X during
subroutine use

                 LDX     #Hundred_ms          ; Load X with value referenced by EQU above

                 BSR     Delay                ; With retrieved X value obtained branch to delay to take up
indicated time

               PULX                           ; Pull X value stored in stack to X, restores data stored in X
before subroutine call

                 RTS                          ; Return to Subroutine which called this




Delay_Var_ms   PSHX                           ; Push X onto stack, prevents loss of data stored in X during
subroutine use

                 LDX     #Var_ms              ; Load X with value referenced by EQU above

                 BSR     Delay                ; With retrieved X value obtained branch to delay to take up
indicated time

               PULX                           ; Pull X value stored in stack to X, restores data stored in X
before subroutine call

                 RTS                          ; Return to Subroutine which called this




* Clear LEDs

Clear_LEDs       PSHA                         ; Push A onto stack, prevents loss of data stored in A during
subroutine use

                 LDAA    #0                   ; Load Accum A w/ value 0 {All LEDs out}

                 STAA    Port_B               ; Stores value at Port_B {All LEDs out}

               PULA                           ; Pull A value stored in stack to A, restores data stored in A
before subroutine call

                 RTS                          ; Return to Subroutine which called this




* Create beep sound at 25 pulses

Beep_once        PSHX                  ; Push X onto stack, prevents loss of data stored in X during subroutine
use




Professor:       Pamela Hoffman              Page 31 of 81                   Colorado Technical University
EE312                                  Embedded Microcontrollers                               TUE / THU 9:00AM
Final Lab                                                                                           Spring 2009


                 PSHY                  ; Push Y onto stack, prevents loss of data stored in Y during subroutine
use

                 PSHA                  ; Push A onto stack, prevents loss of data stored in A during subroutine
use

                 LDX     #25           ; Load X w/ value 25 {controls beep loops, pulses}

Beep_once_loop LDAA      #$20          ; Load A w/ value $20 {Determines sound/tone of beep}

                 STAA    Port_A        ; Stores A in Port_A {Makes beep sound}

                 JSR     Delay_1ms     ; Takes up some time

                 LDAA    #$00          ; Loads A w/ value 0

                 STAA    Port_A        ; Stores A in Port_A {Clears beep sound}

                 JSR     Delay_1ms     ; Takes up some time

                 DEX                   ; Decrements X

                 CPX     #0            ; Compares X w/ value 0

                 BNE     Beep_once_loop ; Branches, loops.. if X does not equal 0

               PULA                    ; Pull A value stored in stack to A, restores data stored in A before
subroutine call

               PULY                    ; Pull Y value stored in stack to Y, restores data stored in Y before
subroutine call

               PULX                    ; Pull X value stored in stack to X, restores data stored in X before
subroutine call

                 RTS                   ; Return to Subroutine which called this




* Display race track, "LEDs circle around bread board"

*     If I had more time I had plans to allow user input

*     determine speed (Delay_Var_ms)




Racetrack_sim    PSHA                  ; Push A onto stack, prevents loss of data stored in A during subroutine
use

                 PSHX                  ; Push X onto stack, prevents loss of data stored in X during subroutine
use

                 JSR    Clear_LEDs     ; Clear LEDs

                 LDX    #10            ; Load X w/ value {determines number of loops}

Race_loop        LDAA    #$01          ; Loads A w/ value, determines what LED will light

                 STAA    Port_B        ; Stores A at port B, lights LEDs indicated by value {0 off 1 on, for 8
LEDs}



Professor:      Pamela Hoffman                Page 32 of 81                   Colorado Technical University
EE312                              Embedded Microcontrollers                              TUE / THU 9:00AM
Final Lab                                                                                       Spring 2009


             JSR    Beep_once      ; Beep

             JSR    Delay_Var_ms   ; Takes up some time

             LDAA   #$02           ; Loads A w/ value, determines what LED will light

             STAA   Port_B         ; Stores A at port B, lights LEDs indicated by value {0 off 1 on, for 8
LEDs}

             JSR    Beep_once      ; Beep

             JSR    Delay_Var_ms   ; Takes up some time

             LDAA   #$04           ; Loads A w/ value, determines what LED will light

             STAA   Port_B         ; Stores A at port B, lights LEDs indicated by value {0 off 1 on, for 8
LEDs}

             JSR    Beep_once      ; Beep

             JSR    Delay_Var_ms   ; Takes up some time

             LDAA   #$08           ; Loads A w/ value, determines what LED will light

             STAA   Port_B         ; Stores A at port B, lights LEDs indicated by value {0 off 1 on, for 8
LEDs}

             JSR    Beep_once      ; Beep

             JSR    Delay_Var_ms   ; Takes up some time

             LDAA   #$10           ; Loads A w/ value, determines what LED will light

             STAA   Port_B         ; Stores A at port B, lights LEDs indicated by value {0 off 1 on, for 8
LEDs}

             JSR    Beep_once      ; Beep

             JSR    Delay_Var_ms   ; Takes up some time

             LDAA   #$20           ; Loads A w/ value, determines what LED will light

             STAA   Port_B         ; Stores A at port B, lights LEDs indicated by value {0 off 1 on, for 8
LEDs}

             JSR    Beep_once      ; Beep

             JSR    Delay_Var_ms   ; Takes up some time

             LDAA   #$40           ; Loads A w/ value, determines what LED will light

             STAA   Port_B         ; Stores A at port B, lights LEDs indicated by value {0 off 1 on, for 8
LEDs}

             JSR    Beep_once      ; Beep

             JSR    Delay_Var_ms   ; Takes up some time

             LDAA   #$80           ; Loads A w/ value, determines what LED will light




Professor:   Pamela Hoffman                 Page 33 of 81                Colorado Technical University
EE312                                     Embedded Microcontrollers                              TUE / THU 9:00AM
Final Lab                                                                                              Spring 2009


               STAA     Port_B            ; Stores A at port B, lights LEDs indicated by value {0 off 1 on, for 8
LEDs}

               JSR      Beep_once         ; Beep

               JSR      Delay_Var_ms      ; Takes up some time

               DEX                        ; Decrement X by 1

               CPX      #0                ; Compare X to 0

               BEQ      Exit_race_loop ; Branches out of loop if X = 0

               JMP      Race_loop         ; Loop if X does not equal 0

Exit_race_loop JSR      Clear_LEDs        ; Clear LEDs

               PULX                       ; Pull X value stored in stack to X, restores data stored in X before
subroutine call

               PULA                       ; Pull A value stored in stack to A, restores data stored in A before
subroutine call

               RTS                        ; Return to Subroutine which called this




* Flash LEDs in a pulse pattern

Flash_LEDs_osc        PSHA                               ; Push A onto stack, prevents loss of data stored in A
during subroutine use

                        PSHX                             ; Push X onto stack, prevents loss of data stored in X
during subroutine use

                        JSR      Clear_LEDs              ; Clear LEDs

                        LDX      #10                     ; Load X w/ value used for # of loops

LED_loop_osc            LDAA     #$18                    ; Loads A w/ value, determines what LED will light

                        STAA     Port_B                  ; Stores A at port B, lights LEDs indicated by value {0 off
1 on, for 8 LEDs}

                        JSR      Beep_once               ; beep when LEDs touch

                        JSR      Delay_100ms             ; Takes up some time

                        LDAA     #$24                    ; Loads A w/ value, determines what LED will light

                        STAA     Port_B                  ; Stores A at port B, lights LEDs indicated by value {0 off
1 on, for 8 LEDs}

                        JSR      Delay_100ms             ; Takes up some time

                        LDAA     #$42                    ; Loads A w/ value, determines what LED will light

                        STAA     Port_B                  ; Stores A at port B, lights LEDs indicated by value {0 off
1 on, for 8 LEDs}

                        JSR      Delay_100ms             ; Takes up some time



Professor:     Pamela Hoffman                      Page 34 of 81                  Colorado Technical University
EE312                                  Embedded Microcontrollers                            TUE / THU 9:00AM
Final Lab                                                                                         Spring 2009


                      LDAA    #$81                  ; Loads A w/ value, determines what LED will light

                      STAA    Port_B                ; Stores A at port B, lights LEDs indicated by value {0 off
1 on, for 8 LEDs}

                      JSR     Delay_100ms           ; Takes up some time

                      LDAA    #$42                  ; Loads A w/ value, determines what LED will light

                      STAA    Port_B                ; Stores A at port B, lights LEDs indicated by value {0 off
1 on, for 8 LEDs}

                      JSR     Delay_100ms           ; Takes up some time

                      LDAA    #$24                  ; Loads A w/ value, determines what LED will light

                      STAA    Port_B                ; Stores A at port B, lights LEDs indicated by value {0 off
1 on, for 8 LEDs}

                      JSR     Delay_100ms           ; Takes up some time

                      DEX                           ; Decrement X by 1

                      BNE     LED_loop_osc          ; Loop if X does not equal 0

Exit_LED_loop_osc     LDAA    #$18                  ; Loads A w/ value, determines what LED will light

                      STAA    Port_B                ; Stores A at port B, lights LEDs indicated by value {0 off
1 on, for 8 LEDs}

                      JSR     Delay_100ms           ; Takes up some time

                      JSR     Clear_LEDs            ; Clear LEDs

                       PULX                         ; Pull X value stored in stack to X, restores data stored
in X before subroutine call

                       PULA                         ; Pull A value stored in stack to A, restores data stored
in A before subroutine call

                      RTS                           ; Return to Subroutine which called this




* Read buttons PA0, PC1, and PC0

Read_button    LDAA   Port_C ; Load A w/ value at Port C

               COMA           ; Invert bits in A

               ANDA    #$03   ; AND A w/ value $03, lowest 2 bits only

               LDAB    Port_A ; Load B w/ value at Port A

               COMB           ; Invert bits in B

               ANDB    #$01   ; AND B w/ value $01, lowest bit only

               ASLB           ; Arithmatic Shift Left Accum B

               ASLB           ; Arithmatic Shift Left Accum B



Professor:    Pamela Hoffman                 Page 35 of 81                 Colorado Technical University
EE312                                    Embedded Microcontrollers                            TUE / THU 9:00AM
Final Lab                                                                                           Spring 2009


                 ABA            ; Add B to A store in A

                 RTS            ; Return to Subroutine which called this




* Subroutines which run depending upon user input {btn press}

*   Note: Had to create these Check buttons because BNE

*   is limited to how far it can branch to..

Run_math       PSHA                            ; Push A onto stack, prevents loss of data stored in A during
subroutine use

                 PSHX                          ; Push X onto stack, prevents loss of data stored in X during
subroutine use

                 JSR     Add_numbers           ; Jump to Sub Routine

                 JSR     Display_press_btn     ; Jump to Sub Routine

               PULX                            ; Pull X value stored in stack to X, restores data stored in X
before subroutine call

               PULA                            ; Pull A value stored in stack to A, restores data stored in A
before subroutine call

                 JMP     Check_buttons         ; Jump back to Check_buttons




Run_race       PSHA                            ; Push A onto stack, prevents loss of data stored in A during
subroutine use

                 PSHX                          ; Push X onto stack, prevents loss of data stored in X during
subroutine use

                 JSR     Racetrack_sim         ; Jump to Sub Routine

               PULX                            ; Pull X value stored in stack to X, restores data stored in X
before subroutine call

               PULA                            ; Pull A value stored in stack to A, restores data stored in A
before subroutine call

                 JMP     Check_buttons         ; Jump back to Check_buttons




Run_LEDs       PSHA                            ; Push A onto stack, prevents loss of data stored in A during
subroutine use

                 PSHX                          ; Push X onto stack, prevents loss of data stored in X during
subroutine use

                 JSR     Flash_LEDs_osc        ; Jump to Sub Routine

               PULX                            ; Pull X value stored in stack to X, restores data stored in X
before subroutine call




Professor:       Pamela Hoffman                Page 36 of 81                  Colorado Technical University
EE312                                    Embedded Microcontrollers                                 TUE / THU 9:00AM
Final Lab                                                                                                 Spring 2009


               PULA                               ; Pull A value stored in stack to A, restores data stored in A
before subroutine call

                JMP      Check_buttons            ; Jump back to Check_buttons




* Check buttons PA0, PC1, and PC0 and do something

Check_buttons            LDX    #12                      ; Load X w/ value used for determining when loop should end

                         LDY    #4000                    ; Load Y w/ value used for determining when loop should end

Check_buttons_loop       BSR    Read_button              ; Branch to Sub Routine to read button

                         STAA   Port_B                   ; Stores read button result in A

                         BITA   #$01                     ; Is PC0 pressed?

                         BNE    Run_LEDs                 ; Then run LEDs, If A does not equal 0

                         BITA   #$02                     ; Is PC1 pressed?

                         BNE    Run_race                 ; Then run LED racetrack, If A does not equal 0

                         BITA   #$04                     ; Is PA0 pressed?

                         BNE    Run_math                 ; Then run math program, If A does not equal 0

                         DEY                             ; Decrement Y by 1

                         CPX    #10                      ; Compare X to value

                         BEQ    Disp_t_warning0                 ; If X = value branch to location given

                         CPX    #8                       ; Compare X to value

                         BEQ    Disp_t_warning1                 ; If X = value branch to location given

                         CPX    #4                       ; Compare X to value

                         BEQ    Disp_t_warning2                 ; If X = value branch to location given

                         CPX    #0                       ; Compare X to value

                         BEQ    Check_buttons_done       ; If X = value branch to location given

                         CPY    #0                       ; Compare Y to value

                         BEQ    Decrement_X              ; If X = value branch to location given

                         JMP    Check_buttons_loop       ; Loop if X does not equal 0

Decrement_X              DEX                             ; Decrement X

                         JMP    Check_buttons_loop       ; Jump back to loop

Check_buttons_done       RTS                             ; Return to Subroutine which called this




Professor:      Pamela Hoffman                 Page 37 of 81                     Colorado Technical University
EE312                                 Embedded Microcontrollers                               TUE / THU 9:00AM
Final Lab                                                                                           Spring 2009


* Display time warnings

* Display clear screen..

Disp_t_warning0       PSHX                     ; Push X onto stack, prevents loss of data stored in X during
subroutine use

               LDX    #Clear_LCD      ; Load Clear LCD string location in X

               JSR    LCD_write_top   ; Display 16 Character string at loc X on top LCD

               PULX                   ; Pull X value stored in stack to X, restores data stored in X before
subroutine call

               JMP    Decrement_X     ; Jump to location




* Display 20s left warning..

Disp_t_warning1       PSHX                     ; Push X onto stack, prevents loss of data stored in X during
subroutine use

               LDX    #Warning2       ; Load X w/ location of string

               JSR    LCD_write_top   ; Display 16 Character string at loc X on top LCD

               JSR     Beep_once      ; Beep

               PULX                   ; Pull X value stored in stack to X, restores data stored in X before
subroutine call

               JMP    Decrement_X     ; Jump to location




* Display 10s left warning..

Disp_t_warning2       PSHX                     ; Push X onto stack, prevents loss of data stored in X during
subroutine use

               LDX    #Warning3       ; Load X w/ location of string

               JSR    LCD_write_top   ; Display 16 Character string at loc X on top LCD

               JSR     Beep_once      ; Beep

               PULX                   ; Pull X value stored in stack to X, restores data stored in X before
subroutine call

               JMP    Decrement_X     ; Jump to location




* Display 15 max char warning..

Disp_char_warning     PSHX                            ; Push X onto stack, prevents loss of data stored in X
during subroutine use

                      LDX      #Warning1              ; Load X w/ location of string




Professor:    Pamela Hoffman                   Page 38 of 81                  Colorado Technical University
EE312                                    Embedded Microcontrollers                                 TUE / THU 9:00AM
Final Lab                                                                                                  Spring 2009


                         JSR       LCD_write_top           ; Display 16 Character string at loc X on top LCD

                         LDX       #Warning1               ; Load X w/ location of string

                       JSR         Output_disp_text        ; Jump to Sub Routine that outputs all ASCII starting at X
and ending when ASCII CR

                         JSR       Output_disp_CR          ; Jump to Sub Routine that outputs ASCII CR followed by a
line feed

                         JSR       Beep_once               ; Beep

                       PULX                                ; Pull X value stored in stack to X, restores data stored
in X before subroutine call

                         RTS                               ; Return to Subroutine which called this




* Pause for Carraige Return key

Pause_return   PSHA                       ; Push A onto stack, prevents loss of data stored in A during subroutine
use

CR_loop        JSR       Input_get_char ; Jump to Sub Routine that gets a single ASCII character from keyboard and
stores in A

               CMPA      #CR              ; Compares A with ASCII CR

               BEQ       Out_CR_loop      ; Branch out of loop if equal

               JMP       CR_loop          ; If not equal.. stay in loop

Out_CR_loop    PULA                       ; Pull A value stored in stack to A, restores data stored in A before
subroutine call

               RTS                        ; Return to Subroutine which called this




* Clear LCD

Disp_LCD_clear PSHX                                 ; Push X onto stack, prevents loss of data stored in X during
subroutine use

               LDX       #Clear_LCD                 ; Load X w/ location of string

               JSR       LCD_write_top              ; Display 16 Character string at loc X on top LCD

               LDX       #Clear_LCD                 ; Load X w/ location of string

               JSR       LCD_write_bottom           ; Display 16 Character string at loc X on bottom LCD

               PULX                                 ; Pull X value stored in stack to X, restores data stored in X
before subroutine call

               RTS                                  ; Return to Subroutine which called this




* Display Welcome & Pause for CR Key



Professor:     Pamela Hoffman                       Page 39 of 81                    Colorado Technical University
EE312                                     Embedded Microcontrollers                            TUE / THU 9:00AM
Final Lab                                                                                              Spring 2009


Disp_welcome   PSHX                             ; Push X onto stack, prevents loss of data stored in X during
subroutine use

               LDX       #Welcome1              ; Load X w/ location of string

               JSR       LCD_write_top          ; Display 16 Character string at loc X on top LCD

               LDX       #Welcome2              ; Load X w/ location of string

               JSR       LCD_write_bottom       ; Display 16 Character string at loc X on bottom LCD

               LDX       #Welcome1              ; Load X w/ location of string

               JSR       Output_disp_text       ; Jump to Sub Routine that outputs all ASCII starting at X and
ending when ASCII CR

               LDX       #Welcome2              ; Load X w/ location of string

               JSR       Output_disp_text       ; Jump to Sub Routine that outputs all ASCII starting at X and
ending when ASCII CR

               JSR       Output_disp_CR         ; Jump to Sub Routine that outputs ASCII CR followed by a line feed

               JSR       Pause_return           ; Jump to Sub Routine that pauses until user presses enter key.. CR

               PULX                             ; Pull X value stored in stack to X, restores data stored in X
before subroutine call

               RTS                              ; Return to Subroutine which called this




* Display Question_Name & Pause for CR Key

Disp_q_name    PSHX                             ; Push X onto stack, prevents loss of data stored in X during
subroutine use

               LDX       #Question_Name1               ; Load X w/ location of string

               JSR       LCD_write_top          ; Display 16 Character string at loc X on top LCD

               LDX       #Question_Name2               ; Load X w/ location of string

               JSR       LCD_write_bottom       ; Display 16 Character string at loc X on bottom LCD

               LDX       #Question_Name1               ; Load X w/ location of string

               JSR       Output_disp_text       ; Jump to Sub Routine that outputs all ASCII starting at X and
ending when ASCII CR

               LDX       #Question_Name2               ; Load X w/ location of string

               JSR       Output_disp_text       ; Jump to Sub Routine that outputs all ASCII starting at X and
ending when ASCII CR

               JSR       Output_disp_CR         ; Jump to Sub Routine that outputs ASCII CR followed by a line feed

               JSR       Pause_return           ; Jump to Sub Routine that pauses until user presses enter key.. CR

               JSR       Disp_LCD_clear         ; Jump to Sub Routine to clear LCDs




Professor:    Pamela Hoffman                    Page 40 of 81                    Colorado Technical University
EE312                                     Embedded Microcontrollers                            TUE / THU 9:00AM
Final Lab                                                                                              Spring 2009


               JSR       Disp_char_warning      ; Jump to Sub Routine

               JSR       Pause_return           ; Jump to Sub Routine that pauses until user presses enter key.. CR

               PULX                             ; Pull X value stored in stack to X, restores data stored in X
before subroutine call

               RTS                              ; Return to Subroutine which called this




* Displays Name

Display_name   PSHX                             ; Push X onto stack, prevents loss of data stored in X during
subroutine use

               LDX       #Response_Name1               ; Load X w/ location of string

               JSR       LCD_write_top          ; Display 16 Character string at loc X on top LCD

               LDX       #Username              ; Load X w/ location of string

               JSR       LCD_write_bottom       ; Display 16 Character string at loc X on bottom LCD

               JSR       Output_disp_CR         ; Jump to Sub Routine that outputs ASCII CR followed by a line feed

               LDX       #Response_Name1               ; Load X w/ location of string

               JSR       Output_disp_text       ; Jump to Sub Routine that outputs all ASCII starting at X and
ending when ASCII CR

               LDX       #Username              ; Load X w/ location of string

               JSR       Output_disp_text       ; Jump to Sub Routine that outputs all ASCII starting at X and
ending when ASCII CR

               JSR       Output_disp_CR         ; Jump to Sub Routine that outputs ASCII CR followed by a line feed

               JSR       Pause_return           ; Jump to Sub Routine that pauses until user presses enter key.. CR

               JSR       Disp_LCD_clear         ; Jump to Sub Routine to clear LCDs

               PULX                             ; Pull X value stored in stack to X, restores data stored in X
before subroutine call

               RTS                              ; Return to Subroutine which called this




* Displays Press a Button

Display_press_btn     PSHX                             ; Push X onto stack, prevents loss of data stored in X
during subroutine use

                         LDX    #Press_Btn1            ; Load X w/ location of string

                         JSR    LCD_write_top          ; Display 16 Character string at loc X on top LCD

                         LDX    #Press_Btn2            ; Load X w/ location of string

                         JSR    LCD_write_bottom       ; Display 16 Character string at loc X on bottom LCD



Professor:    Pamela Hoffman                    Page 41 of 81                    Colorado Technical University
EE312                                Embedded Microcontrollers                               TUE / THU 9:00AM
Final Lab                                                                                          Spring 2009


                      JSR     Output_disp_CR         ; Jump to Sub Routine that outputs ASCII CR followed by a
line feed

                      LDX     #Press_Btn1            ; Load X w/ location of string

                       JSR    Output_disp_text       ; Jump to Sub Routine that outputs all ASCII starting at X
and ending when ASCII CR

                      LDX     #Press_Btn2            ; Load X w/ location of string

                       JSR    Output_disp_text       ; Jump to Sub Routine that outputs all ASCII starting at X
and ending when ASCII CR

                      JSR     Output_disp_CR         ; Jump to Sub Routine that outputs ASCII CR followed by a
line feed

                      PULX                           ; Pull X value stored in stack to X, restores data stored
in X before subroutine call

                      RTS                            ; Return to Subroutine which called this




* Displays Credits

Display_credits               PSHX                          ; Push X onto stack, prevents loss of data stored in
X during subroutine use

                      LDX     #Credits1              ; Load X w/ location of string

                      JSR     LCD_write_top          ; Display 16 Character string at loc X on top LCD

                      LDX     #Credits2              ; Load X w/ location of string

                      JSR     LCD_write_bottom       ; Display 16 Character string at loc X on bottom LCD

                      JSR     Output_disp_CR         ; Jump to Sub Routine that outputs ASCII CR followed by a
line feed

                      LDX     #Credits1              ; Load X w/ location of string

                       JSR    Output_disp_text       ; Jump to Sub Routine that outputs all ASCII starting at X
and ending when ASCII CR

                      LDX     #Credits2              ; Load X w/ location of string

                       JSR    Output_disp_text       ; Jump to Sub Routine that outputs all ASCII starting at X
and ending when ASCII CR

                      JSR     Output_disp_CR         ; Jump to Sub Routine that outputs ASCII CR followed by a
line feed

                      JSR     Pause_return           ; Jump to Sub Routine that pauses until user presses enter
key.. CR

                       PULX                          ; Pull X value stored in stack to X, restores data stored
in X before subroutine call

                      RTS                            ; Return to Subroutine which called this




Professor:     Pamela Hoffman                  Page 42 of 81                Colorado Technical University
EE312                                   Embedded Microcontrollers                                 TUE / THU 9:00AM
Final Lab                                                                                               Spring 2009


* Displays Final Output

Display_exit_world    PSHX                                ; Push X onto stack, prevents loss of data stored in X
during subroutine use

                        LDX     #Exit_World1              ; Load X w/ location of string

                        JSR     LCD_write_top             ; Display 16 Character string at loc X on top LCD

                        LDX     #Exit_World2              ; Load X w/ location of string

                        JSR     LCD_write_bottom          ; Display 16 Character string at loc X on bottom LCD

                        JSR     Output_disp_CR            ; Jump to Sub Routine that outputs ASCII CR followed by a
line feed

                        LDX     #Exit_World1              ; Load X w/ location of string

                      JSR        Output_disp_text         ; Jump to Sub Routine that outputs all ASCII starting at X
and ending when ASCII CR

                        LDX     #Exit_World2              ; Load X w/ location of string

                       JSR       Output_disp_text         ; Jump to Sub Routine that outputs all ASCII starting at X
and ending when ASCII CR

                        JSR     Output_disp_CR            ; Jump to Sub Routine that outputs ASCII CR followed by a
line feed

                        JSR     Pause_return              ; Jump to Sub Routine that pauses until user presses enter
key.. CR

                       PULX                               ; Pull X value stored in stack to X, restores data stored
in X before subroutine call

                        RTS                               ; Return to Subroutine which called this




* Loop to get & math numbers..

Add_numbers    PSHX                              ; Push X onto stack, prevents loss of data stored in X during
subroutine use

                 PSHY                            ; Push Y onto stack, prevents loss of data stored in Y during
subroutine use

                 PSHA                            ; Push A onto stack, prevents loss of data stored in A during
subroutine use

                 PSHB                            ; Push B onto stack, prevents loss of data stored in B during
subroutine use

Add_nmbrs_loop   JSR      Beep_once              ; Beep

                 LDX    #MathA_1                 ; Load X w/ location of string

                 JSR    LCD_write_top            ; Display 16 Character string at loc X on top LCD

                 LDX    #MathA_2                 ; Load X w/ location of string




Professor:       Pamela Hoffman                  Page 43 of 81                    Colorado Technical University
EE312                                   Embedded Microcontrollers                            TUE / THU 9:00AM
Final Lab                                                                                            Spring 2009


               JSR     LCD_write_bottom       ; Display 16 Character string at loc X on bottom LCD

               LDX     #MathA_1               ; Load X w/ location of string

               JSR     Output_disp_text       ; Jump to Sub Routine that outputs all ASCII starting at X and
ending when ASCII CR

               LDX     #MathA_2               ; Load X w/ location of string

               JSR     Output_disp_text       ; Jump to Sub Routine that outputs all ASCII starting at X and
ending when ASCII CR

               JSR     Output_disp_CR         ; Jump to Sub Routine that outputs ASCII CR followed by a line feed

               JSR     Pause_return           ; Jump to Sub Routine that pauses until user presses enter key.. CR

               JSR     Beep_once              ; Beep

               LDX     #MathB_1               ; Load X w/ location of string

               JSR     LCD_write_top          ; Display 16 Character string at loc X on top LCD

               LDX     #MathB_2               ; Load X w/ location of string

               JSR     LCD_write_bottom       ; Display 16 Character string at loc X on bottom LCD

               LDX     #MathB_1               ; Load X w/ location of string

               JSR     Output_disp_text       ; Jump to Sub Routine that outputs all ASCII starting at X and
ending when ASCII CR

               LDX     #MathB_2               ; Load X w/ location of string

               JSR     Output_disp_text       ; Jump to Sub Routine that outputs all ASCII starting at X and
ending when ASCII CR

Get_value1     JSR     Output_disp_CR         ; Jump to Sub Routine that outputs ASCII CR followed by a line feed

               JSR     Pause_return           ; Jump to Sub Routine that pauses until user presses enter key.. CR

               JSR     Beep_once              ; Beep

               LDX     #MathC_1               ; Load X w/ location of string

               JSR     LCD_write_top          ; Display 16 Character string at loc X on top LCD

               LDX     #MathC_1               ; Load X w/ location of string

               JSR     Output_disp_text       ; Jump to Sub Routine that outputs all ASCII starting at X and
ending when ASCII CR

               JSR     Output_disp_CR         ; Jump to Sub Routine that outputs ASCII CR followed by a line feed

               JSR     Input_get_char         ; Jump to Sub Routine that gets a single ASCII character from
keyboard and stores in A

               CMPA    #$2F                   ; Compare A w/ value {ASCII value before ASCII 0}

               BLS     Get_value1             ; Branch if lower or same (Used to ensure only an ASCII 0-4 are
entered)




Professor:    Pamela Hoffman                  Page 44 of 81                    Colorado Technical University
EE312                                    Embedded Microcontrollers                            TUE / THU 9:00AM
Final Lab                                                                                             Spring 2009


                 CMPA   #$35                   ; Compare A w/ value {ASCII value after ASCII 4}

                 BHS    Get_value1             ; Branch if higher or same (Used to ensure only an ASCII 0-4 are
entered)

                 SUBA   #$30                   ; Subtracts $30 from value to convert ASCII (0 to 4) to actual hex
value

                 STAA   Value1                 ; Stores A at location

Get_value2       JSR    Output_disp_CR         ; Jump to Sub Routine that outputs ASCII CR followed by a line feed

                 JSR    Pause_return           ; Jump to Sub Routine that pauses until user presses enter key.. CR

                 JSR    Beep_once              ; Beep

                 LDX    #MathD_1               ; Load X w/ location of string

                 JSR    LCD_write_top          ; Display 16 Character string at loc X on bottom LCD

                 LDX    #MathD_1               ; Load X w/ location of string

               JSR      Output_disp_text       ; Jump to Sub Routine that outputs all ASCII starting at X and
ending when ASCII CR

                 JSR    Output_disp_CR         ; Jump to Sub Routine that outputs ASCII CR followed by a line feed

               JSR     Input_get_char          ; Jump to Sub Routine that gets a single ASCII character from
keyboard and stores in A

                 CMPA   #$2F                   ; Compare A w/ value {ASCII value before ASCII 0}

                 BLS    Get_value2             ; Branch if lower or same (Used to ensure only an ASCII 0-4 are
entered)

                 CMPA   #$35                   ; Compare A w/ value {ASCII value after ASCII 4}

                 BHS    Get_value2             ; Branch if higher or same (Used to ensure only an ASCII 0-4 are
entered)

                 SUBA   #$30                   ; Subtracts $30 from value to convert ASCII (0 to 4) to actual hex
value

                 STAA   value2                 ; Stores A at location

Add_values       LDAA   Value1                 ; Loads A w/ value at location given

                 ADDA   value2                 ; Adds A to value at location stores in A

                 ADDA   #$30                   ; Adds $30 to A -> converts Hex value (0-8) into ASCII (0-8)

                 STAA   Result                 ; Stores A in Result String

Result_section   JSR    Output_disp_CR         ; Jump to Sub Routine that outputs ASCII CR followed by a line feed

                 JSR    Output_disp_CR         ; Jump to Sub Routine that outputs ASCII CR followed by a line feed

                 JSR    Beep_once              ; Beep

                 LDX    #MathE_1               ; Load X w/ location of string




Professor:       Pamela Hoffman                Page 45 of 81                    Colorado Technical University
EE312                                     Embedded Microcontrollers                             TUE / THU 9:00AM
Final Lab                                                                                              Spring 2009


                 JSR     LCD_write_top          ; Display 16 Character string at loc X on top LCD

                 LDX     #MathE_1               ; Load X w/ location of string

               JSR       Output_disp_text       ; Jump to Sub Routine that outputs all ASCII starting at X and
ending when ASCII CR

                 LDX     #Result                ; Load X w/ location of string

                 JSR     LCD_write_bottom       ; Display 16 Character string at loc X on bottom LCD

                 LDX     #Result                ; Load X w/ location of string

               JSR       Output_disp_text       ; Jump to Sub Routine that outputs all ASCII starting at X and
ending when ASCII CR

                 JSR     Output_disp_CR         ; Jump to Sub Routine that outputs ASCII CR followed by a line feed

                 JSR     Pause_return           ; Jump to Sub Routine that pauses until user presses enter key.. CR

                 JSR     Beep_once              ; Beep

Close_add              PULB                              ; Pull B value stored in stack to B, restores data stored
in B before subroutine call

               PULA                             ; Pull A value stored in stack to A, restores data stored in A
before subroutine call

               PULY                             ; Pull Y value stored in stack to Y, restores data stored in Y
before subroutine call

               PULX                             ; Pull X value stored in stack to X, restores data stored in X
before subroutine call

                 RTS                            ; Return to Subroutine which called this




* Loop to get & store name..

Get_name       PSHX                             ; Push X onto stack, prevents loss of data stored in X during
subroutine use

                 PSHY                           ; Push Y onto stack, prevents loss of data stored in Y during
subroutine use

                 PSHA                           ; Push A onto stack, prevents loss of data stored in A during
subroutine use

                 LDX     #Question_Name3                 ; Load X w/ location of string

                 JSR     LCD_write_top          ; Display 16 Character string at loc X on top LCD

                 LDX     #Question_Name3                 ; Load X w/ location of string

               JSR       Output_disp_text       ; Jump to Sub Routine that outputs all ASCII starting at X and
ending when ASCII CR

                 JSR     Output_disp_CR         ; Jump to Sub Routine that outputs ASCII CR followed by a line feed

                 JSR     Output_disp_CR         ; Jump to Sub Routine that outputs ASCII CR followed by a line feed



Professor:       Pamela Hoffman                 Page 46 of 81                    Colorado Technical University
EE312                                     Embedded Microcontrollers                              TUE / THU 9:00AM
Final Lab                                                                                             Spring 2009


                LDX      #Username              ; Load X w/ location of string

                LDY      #0                     ; Load Y w/ location of string

Get_name_loop   CPY      #15                    ; Compares Y w/ value 15 {Prevents user from inputing too many
strings}

                BEQ      Close_Get_name         ; Braches if Equal to location outside of loop

               JSR     Input_get_char           ; Jump to Sub Routine that gets a single ASCII character from
keyboard and stores in A

                CMPA     #CR                    ; Compare A w/ ASCII CR

                BEQ      Close_Get_name         ; Braches if Equal to location outside of loop

                CMPA     #$1F                   ; Compare A w/ illegal character (Not 0-9, or A-Z, or a-z)

                BLS      Get_name_loop          ; Branch Lower or Same.. loops for new character if illegal
encountered

                CMPA     #$7F                   ; Compare A w/ illegal character (Not 0-9, or A-Z, or a-z)

                BHS      Get_name_loop          ; Branch Higher or Same.. loops for new character if illegal
encountered

                STAA     0,X                    ; Store A at location in X

                INY                             ; Increment Y {Used to count # of characters}

                INX                             ; Increment X

                BRA      Get_name_loop          ; Branch

Close_Get_name PULA                             ; Pull A value stored in stack to A, restores data stored in A
before subroutine call

               PULY                             ; Pull Y value stored in stack to Y, restores data stored in Y
before subroutine call

               PULX                             ; Pull X value stored in stack to X, restores data stored in X
before subroutine call

                RTS                             ; Return to Subroutine which called this




* ------------------------

* Start Main_func program

* ------------------------

Main_func       JSR      LCD_init               ; Initialize LCD

                JSR      Clear_LEDs             ; Clear LEDs

                JSR      Disp_LCD_clear         ; Clear LCDs

                JSR      Disp_welcome           ; Jump to Subroutine to displays welcome




Professor:      Pamela Hoffman                  Page 47 of 81                    Colorado Technical University
EE312                              Embedded Microcontrollers                               TUE / THU 9:00AM
Final Lab                                                                                        Spring 2009


             JSR   Flash_LEDs_osc        ; Jump to Subroutine to flash leds in a pulse pattern

             JSR   Disp_q_name           ; Jump to Subroutine to display question on LCD

             JSR   Get_name              ; Jump to Subroutine to get users name

             JSR    Display_name         ; Jump to Subroutine to display users name

             JSR   Display_press_btn     ; Jump to Subroutine to display statement on LCD

             JSR   Check_buttons         ; Jump to Subroutine to check buttons and do something

             JSR   Display_credits              ; Jump to Subroutine to display credits

             JSR   Display_exit_world    ; Jump to Subroutine to display exit world

             RTS                         ; Return to Subroutine which called this




Note: LAB Output:
     Because most of the program uses the LCDs and LEDs, it would be
pointless and disappointing to be limited to the output I could capture
using terminal screenshots. Therefore, please copy/paste/assemble/load/
and run the code above if you wish to see the program in action. You can
also use the trace “t” command to trace the changes to the PC, SP, and
registers, although be warned (The trace program will lose functionality
as soon as it enters the terminal I/O and Buffalo Monitor I/O subroutines.
Remember you can also log terminal output to file! I used this trick with
preceding loabs.


RE: Optimizing Code:
     I noticed a few areas where I could have removed some compare
instructions since the CCR was already set, I also noticed I could have
used the ROLA and RORA instructions in a loop for the racetrack module
which would have shortened the LED modules a bit.




Professor:   Pamela Hoffman              Page 48 of 81                  Colorado Technical University
EE312                         Embedded Microcontrollers                TUE / THU 9:00AM
Final Lab                                                                   Spring 2009




Professor:   Pamela Hoffman         Page 49 of 81         Colorado Technical University
EE312                         Embedded Microcontrollers                TUE / THU 9:00AM
Final Lab                                                                   Spring 2009




Professor:   Pamela Hoffman         Page 50 of 81         Colorado Technical University
EE312                         Embedded Microcontrollers                TUE / THU 9:00AM
Final Lab                                                                   Spring 2009




Professor:   Pamela Hoffman         Page 51 of 81         Colorado Technical University
EE312                         Embedded Microcontrollers                TUE / THU 9:00AM
Final Lab                                                                   Spring 2009




Professor:   Pamela Hoffman         Page 52 of 81         Colorado Technical University
EE312                         Embedded Microcontrollers                TUE / THU 9:00AM
Final Lab                                                                   Spring 2009




Professor:   Pamela Hoffman         Page 53 of 81         Colorado Technical University
EE312                         Embedded Microcontrollers                TUE / THU 9:00AM
Final Lab                                                                   Spring 2009




Professor:   Pamela Hoffman         Page 54 of 81         Colorado Technical University
EE312                         Embedded Microcontrollers                TUE / THU 9:00AM
Final Lab                                                                   Spring 2009




Professor:   Pamela Hoffman         Page 55 of 81         Colorado Technical University
EE312                         Embedded Microcontrollers                TUE / THU 9:00AM
Final Lab                                                                   Spring 2009




Professor:   Pamela Hoffman         Page 56 of 81         Colorado Technical University
EE312                         Embedded Microcontrollers                TUE / THU 9:00AM
Final Lab                                                                   Spring 2009




Professor:   Pamela Hoffman         Page 57 of 81         Colorado Technical University
EE312                         Embedded Microcontrollers                TUE / THU 9:00AM
Final Lab                                                                   Spring 2009




Professor:   Pamela Hoffman         Page 58 of 81         Colorado Technical University
EE312                         Embedded Microcontrollers                TUE / THU 9:00AM
Final Lab                                                                   Spring 2009




Professor:   Pamela Hoffman         Page 59 of 81         Colorado Technical University
EE312                         Embedded Microcontrollers                TUE / THU 9:00AM
Final Lab                                                                   Spring 2009




Professor:   Pamela Hoffman         Page 60 of 81         Colorado Technical University
EE312                         Embedded Microcontrollers                TUE / THU 9:00AM
Final Lab                                                                   Spring 2009




Professor:   Pamela Hoffman         Page 61 of 81         Colorado Technical University
EE312                         Embedded Microcontrollers                TUE / THU 9:00AM
Final Lab                                                                   Spring 2009




Professor:   Pamela Hoffman         Page 62 of 81         Colorado Technical University
EE312                         Embedded Microcontrollers                TUE / THU 9:00AM
Final Lab                                                                   Spring 2009




Professor:   Pamela Hoffman         Page 63 of 81         Colorado Technical University
EE312                         Embedded Microcontrollers                TUE / THU 9:00AM
Final Lab                                                                   Spring 2009




Professor:   Pamela Hoffman         Page 64 of 81         Colorado Technical University
EE312                         Embedded Microcontrollers                TUE / THU 9:00AM
Final Lab                                                                   Spring 2009




Professor:   Pamela Hoffman         Page 65 of 81         Colorado Technical University
EE312                         Embedded Microcontrollers                TUE / THU 9:00AM
Final Lab                                                                   Spring 2009




Professor:   Pamela Hoffman         Page 66 of 81         Colorado Technical University
EE312                         Embedded Microcontrollers                TUE / THU 9:00AM
Final Lab                                                                   Spring 2009




Professor:   Pamela Hoffman         Page 67 of 81         Colorado Technical University
EE312                         Embedded Microcontrollers                TUE / THU 9:00AM
Final Lab                                                                   Spring 2009




Professor:   Pamela Hoffman         Page 68 of 81         Colorado Technical University
EE312                         Embedded Microcontrollers                TUE / THU 9:00AM
Final Lab                                                                   Spring 2009




Professor:   Pamela Hoffman         Page 69 of 81         Colorado Technical University
EE312                         Embedded Microcontrollers                TUE / THU 9:00AM
Final Lab                                                                   Spring 2009




Professor:   Pamela Hoffman         Page 70 of 81         Colorado Technical University
EE312                         Embedded Microcontrollers                TUE / THU 9:00AM
Final Lab                                                                   Spring 2009




Professor:   Pamela Hoffman         Page 71 of 81         Colorado Technical University
EE312                         Embedded Microcontrollers                TUE / THU 9:00AM
Final Lab                                                                   Spring 2009




Professor:   Pamela Hoffman         Page 72 of 81         Colorado Technical University
EE312                         Embedded Microcontrollers                TUE / THU 9:00AM
Final Lab                                                                   Spring 2009




Professor:   Pamela Hoffman         Page 73 of 81         Colorado Technical University
EE312                         Embedded Microcontrollers                TUE / THU 9:00AM
Final Lab                                                                   Spring 2009




Professor:   Pamela Hoffman         Page 74 of 81         Colorado Technical University
EE312                         Embedded Microcontrollers                TUE / THU 9:00AM
Final Lab                                                                   Spring 2009




Professor:   Pamela Hoffman         Page 75 of 81         Colorado Technical University
EE312                         Embedded Microcontrollers                TUE / THU 9:00AM
Final Lab                                                                   Spring 2009




Professor:   Pamela Hoffman         Page 76 of 81         Colorado Technical University
EE312                         Embedded Microcontrollers                TUE / THU 9:00AM
Final Lab                                                                   Spring 2009




Professor:   Pamela Hoffman         Page 77 of 81         Colorado Technical University
EE312                         Embedded Microcontrollers                TUE / THU 9:00AM
Final Lab                                                                   Spring 2009




Professor:   Pamela Hoffman         Page 78 of 81         Colorado Technical University
EE312 Embedded Microcontrollers Lab
EE312 Embedded Microcontrollers Lab
EE312 Embedded Microcontrollers Lab

More Related Content

What's hot

Vlsi lab manual exp:1
Vlsi lab manual exp:1Vlsi lab manual exp:1
Vlsi lab manual exp:1
komala vani
 
Itc Theater09 Sep1420 P Redits Done
Itc Theater09 Sep1420 P Redits DoneItc Theater09 Sep1420 P Redits Done
Itc Theater09 Sep1420 P Redits Done
ra3197
 
13986149 c-pgming-for-embedded-systems
13986149 c-pgming-for-embedded-systems13986149 c-pgming-for-embedded-systems
13986149 c-pgming-for-embedded-systems
PRADEEP
 
7-Segment Display
7-Segment Display7-Segment Display
7-Segment Display
May Ann Mas
 
20081114 Friday Food iLabt Bart Joris
20081114 Friday Food iLabt Bart Joris20081114 Friday Food iLabt Bart Joris
20081114 Friday Food iLabt Bart Joris
imec.archive
 
DickeyS_presentation_2015_3_26_2_1
DickeyS_presentation_2015_3_26_2_1DickeyS_presentation_2015_3_26_2_1
DickeyS_presentation_2015_3_26_2_1
Sergey Dickey
 

What's hot (20)

DSP_Assign_1
DSP_Assign_1DSP_Assign_1
DSP_Assign_1
 
Lab9500
Lab9500Lab9500
Lab9500
 
FPGA/Reconfigurable computing (HPRC)
FPGA/Reconfigurable computing (HPRC)FPGA/Reconfigurable computing (HPRC)
FPGA/Reconfigurable computing (HPRC)
 
Intro2 Robotic With Pic18
Intro2 Robotic With Pic18Intro2 Robotic With Pic18
Intro2 Robotic With Pic18
 
Vlsi lab manual exp:1
Vlsi lab manual exp:1Vlsi lab manual exp:1
Vlsi lab manual exp:1
 
e CAD lab manual
e CAD lab manuale CAD lab manual
e CAD lab manual
 
VLSI & E-CAD Lab Manual
VLSI & E-CAD Lab ManualVLSI & E-CAD Lab Manual
VLSI & E-CAD Lab Manual
 
101495802 ee2258-lm-1
101495802 ee2258-lm-1101495802 ee2258-lm-1
101495802 ee2258-lm-1
 
Verilog lab mauual
Verilog lab mauualVerilog lab mauual
Verilog lab mauual
 
Itc Theater09 Sep1420 P Redits Done
Itc Theater09 Sep1420 P Redits DoneItc Theater09 Sep1420 P Redits Done
Itc Theater09 Sep1420 P Redits Done
 
13986149 c-pgming-for-embedded-systems
13986149 c-pgming-for-embedded-systems13986149 c-pgming-for-embedded-systems
13986149 c-pgming-for-embedded-systems
 
VLSI lab manual
VLSI lab manualVLSI lab manual
VLSI lab manual
 
7-Segment Display
7-Segment Display7-Segment Display
7-Segment Display
 
20081114 Friday Food iLabt Bart Joris
20081114 Friday Food iLabt Bart Joris20081114 Friday Food iLabt Bart Joris
20081114 Friday Food iLabt Bart Joris
 
DickeyS_presentation_2015_3_26_2_1
DickeyS_presentation_2015_3_26_2_1DickeyS_presentation_2015_3_26_2_1
DickeyS_presentation_2015_3_26_2_1
 
FPGA Implementation of Mixed Radix CORDIC FFT
FPGA Implementation of Mixed Radix CORDIC FFTFPGA Implementation of Mixed Radix CORDIC FFT
FPGA Implementation of Mixed Radix CORDIC FFT
 
branch ins 8051
branch ins 8051branch ins 8051
branch ins 8051
 
Embedded System Microcontroller Interactive Course using BASCOM-AVR - Lecture...
Embedded System Microcontroller Interactive Course using BASCOM-AVR - Lecture...Embedded System Microcontroller Interactive Course using BASCOM-AVR - Lecture...
Embedded System Microcontroller Interactive Course using BASCOM-AVR - Lecture...
 
Online test program generator for RISC-V processors
Online test program generator for RISC-V processorsOnline test program generator for RISC-V processors
Online test program generator for RISC-V processors
 
Digital system design lab manual
Digital system design lab manualDigital system design lab manual
Digital system design lab manual
 

Similar to EE312 Embedded Microcontrollers Lab

Xcs 234 microprocessors
Xcs 234 microprocessorsXcs 234 microprocessors
Xcs 234 microprocessors
sweta suman
 
Basic programming of 8085
Basic programming of 8085 Basic programming of 8085
Basic programming of 8085
vijaydeepakg
 

Similar to EE312 Embedded Microcontrollers Lab (20)

Switch Control and Time Delay - Keypad
Switch Control and Time Delay - KeypadSwitch Control and Time Delay - Keypad
Switch Control and Time Delay - Keypad
 
microp-8085 74 instructions for mct-A :P
microp-8085 74 instructions for mct-A :Pmicrop-8085 74 instructions for mct-A :P
microp-8085 74 instructions for mct-A :P
 
8085 Paper Presentation slides,ppt,microprocessor 8085 ,guide, instruction set
8085 Paper Presentation slides,ppt,microprocessor 8085 ,guide, instruction set8085 Paper Presentation slides,ppt,microprocessor 8085 ,guide, instruction set
8085 Paper Presentation slides,ppt,microprocessor 8085 ,guide, instruction set
 
microp-8085 74 instructions for mct-A :P-2
microp-8085 74 instructions for mct-A :P-2microp-8085 74 instructions for mct-A :P-2
microp-8085 74 instructions for mct-A :P-2
 
Introduction to 8085 & it's description(includes basic lab experiments)
Introduction to 8085 & it's description(includes basic lab experiments)Introduction to 8085 & it's description(includes basic lab experiments)
Introduction to 8085 & it's description(includes basic lab experiments)
 
Xcs 234 microprocessors
Xcs 234 microprocessorsXcs 234 microprocessors
Xcs 234 microprocessors
 
MPMC LAB MANUAL EEE
MPMC LAB MANUAL EEEMPMC LAB MANUAL EEE
MPMC LAB MANUAL EEE
 
Introduction to 8085 by adi ppt
Introduction to 8085 by adi pptIntroduction to 8085 by adi ppt
Introduction to 8085 by adi ppt
 
Basic programming of 8085
Basic programming of 8085 Basic programming of 8085
Basic programming of 8085
 
Microprocessor Lab Manual by Er. Swapnil V. Kaware
Microprocessor Lab Manual by Er. Swapnil V. KawareMicroprocessor Lab Manual by Er. Swapnil V. Kaware
Microprocessor Lab Manual by Er. Swapnil V. Kaware
 
8085 Architecture
8085 Architecture8085 Architecture
8085 Architecture
 
Unit 2 Instruction set.pdf
Unit 2 Instruction set.pdfUnit 2 Instruction set.pdf
Unit 2 Instruction set.pdf
 
Lec04
Lec04Lec04
Lec04
 
Lec04
Lec04Lec04
Lec04
 
Qb microprocessors
Qb microprocessorsQb microprocessors
Qb microprocessors
 
Drdo 2008-cse-paper
Drdo 2008-cse-paperDrdo 2008-cse-paper
Drdo 2008-cse-paper
 
Ec6504 microprocessor and microcontroller
Ec6504 microprocessor and microcontrollerEc6504 microprocessor and microcontroller
Ec6504 microprocessor and microcontroller
 
Microcontrollers 80 Marks Sample Question Paper
Microcontrollers   80 Marks Sample Question PaperMicrocontrollers   80 Marks Sample Question Paper
Microcontrollers 80 Marks Sample Question Paper
 
Microcontrollers 80 Marks Sample Question Paper
Microcontrollers   80 Marks Sample Question PaperMicrocontrollers   80 Marks Sample Question Paper
Microcontrollers 80 Marks Sample Question Paper
 
8085 instruction set
8085 instruction set8085 instruction set
8085 instruction set
 

More from Loren Schwappach

Ee325 cmos design lab 5 report - loren k schwappach
Ee325 cmos design   lab 5 report - loren k schwappachEe325 cmos design   lab 5 report - loren k schwappach
Ee325 cmos design lab 5 report - loren k schwappach
Loren Schwappach
 
Ee325 cmos design lab 4 report - loren k schwappach
Ee325 cmos design   lab 4 report - loren k schwappachEe325 cmos design   lab 4 report - loren k schwappach
Ee325 cmos design lab 4 report - loren k schwappach
Loren Schwappach
 
Ee325 cmos design lab 3 report - loren k schwappach
Ee325 cmos design   lab 3 report - loren k schwappachEe325 cmos design   lab 3 report - loren k schwappach
Ee325 cmos design lab 3 report - loren k schwappach
Loren Schwappach
 
Loren k. schwappach ee331 - lab 4
Loren k. schwappach   ee331 - lab 4Loren k. schwappach   ee331 - lab 4
Loren k. schwappach ee331 - lab 4
Loren Schwappach
 
Loren k. schwappach ee331 - lab 3
Loren k. schwappach   ee331 - lab 3Loren k. schwappach   ee331 - lab 3
Loren k. schwappach ee331 - lab 3
Loren Schwappach
 
Ee343 signals and systems - lab 2 - loren schwappach
Ee343   signals and systems - lab 2 - loren schwappachEe343   signals and systems - lab 2 - loren schwappach
Ee343 signals and systems - lab 2 - loren schwappach
Loren Schwappach
 
Ee343 signals and systems - lab 1 - loren schwappach
Ee343   signals and systems - lab 1 - loren schwappachEe343   signals and systems - lab 1 - loren schwappach
Ee343 signals and systems - lab 1 - loren schwappach
Loren Schwappach
 
Ee 352 lab 1 (tutorial) - schwappach - 15 oct 09
Ee 352   lab 1 (tutorial) - schwappach - 15 oct 09Ee 352   lab 1 (tutorial) - schwappach - 15 oct 09
Ee 352 lab 1 (tutorial) - schwappach - 15 oct 09
Loren Schwappach
 
EE375 Electronics 1: lab 3
EE375   Electronics 1: lab 3EE375   Electronics 1: lab 3
EE375 Electronics 1: lab 3
Loren Schwappach
 
EE375 Electronics 1: lab 1
EE375   Electronics 1: lab 1EE375   Electronics 1: lab 1
EE375 Electronics 1: lab 1
Loren Schwappach
 
Ee395 lab 2 - loren - victor - taylor
Ee395   lab 2 - loren - victor - taylorEe395   lab 2 - loren - victor - taylor
Ee395 lab 2 - loren - victor - taylor
Loren Schwappach
 
Ee395 lab 1 - bjt - loren - victor - taylor
Ee395   lab 1 - bjt - loren - victor - taylorEe395   lab 1 - bjt - loren - victor - taylor
Ee395 lab 1 - bjt - loren - victor - taylor
Loren Schwappach
 
5 ee415 - adv electronics - presentation - schwappach
5   ee415 - adv electronics - presentation - schwappach5   ee415 - adv electronics - presentation - schwappach
5 ee415 - adv electronics - presentation - schwappach
Loren Schwappach
 
4 ee414 - adv electroncs - lab 3 - loren schwappach
4   ee414 - adv electroncs - lab 3 - loren schwappach4   ee414 - adv electroncs - lab 3 - loren schwappach
4 ee414 - adv electroncs - lab 3 - loren schwappach
Loren Schwappach
 
3 ee414 - adv electroncs - lab 2 - loren schwappach
3   ee414 - adv electroncs - lab 2 - loren schwappach3   ee414 - adv electroncs - lab 2 - loren schwappach
3 ee414 - adv electroncs - lab 2 - loren schwappach
Loren Schwappach
 
2 ee414 - adv electroncs - lab 1 - loren schwappach
2   ee414 - adv electroncs - lab 1 - loren schwappach2   ee414 - adv electroncs - lab 1 - loren schwappach
2 ee414 - adv electroncs - lab 1 - loren schwappach
Loren Schwappach
 
Ee443 phase locked loop - presentation - schwappach and brandy
Ee443   phase locked loop - presentation - schwappach and brandyEe443   phase locked loop - presentation - schwappach and brandy
Ee443 phase locked loop - presentation - schwappach and brandy
Loren Schwappach
 
Ee443 phase locked loop - paper - schwappach and brandy
Ee443   phase locked loop - paper - schwappach and brandyEe443   phase locked loop - paper - schwappach and brandy
Ee443 phase locked loop - paper - schwappach and brandy
Loren Schwappach
 

More from Loren Schwappach (20)

Ubuntu OS Presentation
Ubuntu OS PresentationUbuntu OS Presentation
Ubuntu OS Presentation
 
Ee325 cmos design lab 5 report - loren k schwappach
Ee325 cmos design   lab 5 report - loren k schwappachEe325 cmos design   lab 5 report - loren k schwappach
Ee325 cmos design lab 5 report - loren k schwappach
 
Ee325 cmos design lab 4 report - loren k schwappach
Ee325 cmos design   lab 4 report - loren k schwappachEe325 cmos design   lab 4 report - loren k schwappach
Ee325 cmos design lab 4 report - loren k schwappach
 
Ee325 cmos design lab 3 report - loren k schwappach
Ee325 cmos design   lab 3 report - loren k schwappachEe325 cmos design   lab 3 report - loren k schwappach
Ee325 cmos design lab 3 report - loren k schwappach
 
Loren k. schwappach ee331 - lab 4
Loren k. schwappach   ee331 - lab 4Loren k. schwappach   ee331 - lab 4
Loren k. schwappach ee331 - lab 4
 
Loren k. schwappach ee331 - lab 3
Loren k. schwappach   ee331 - lab 3Loren k. schwappach   ee331 - lab 3
Loren k. schwappach ee331 - lab 3
 
Ee343 signals and systems - lab 2 - loren schwappach
Ee343   signals and systems - lab 2 - loren schwappachEe343   signals and systems - lab 2 - loren schwappach
Ee343 signals and systems - lab 2 - loren schwappach
 
Ee343 signals and systems - lab 1 - loren schwappach
Ee343   signals and systems - lab 1 - loren schwappachEe343   signals and systems - lab 1 - loren schwappach
Ee343 signals and systems - lab 1 - loren schwappach
 
Ee 352 lab 1 (tutorial) - schwappach - 15 oct 09
Ee 352   lab 1 (tutorial) - schwappach - 15 oct 09Ee 352   lab 1 (tutorial) - schwappach - 15 oct 09
Ee 352 lab 1 (tutorial) - schwappach - 15 oct 09
 
EE375 Electronics 1: lab 3
EE375   Electronics 1: lab 3EE375   Electronics 1: lab 3
EE375 Electronics 1: lab 3
 
EE375 Electronics 1: lab 1
EE375   Electronics 1: lab 1EE375   Electronics 1: lab 1
EE375 Electronics 1: lab 1
 
Ee395 lab 2 - loren - victor - taylor
Ee395   lab 2 - loren - victor - taylorEe395   lab 2 - loren - victor - taylor
Ee395 lab 2 - loren - victor - taylor
 
Ee395 lab 1 - bjt - loren - victor - taylor
Ee395   lab 1 - bjt - loren - victor - taylorEe395   lab 1 - bjt - loren - victor - taylor
Ee395 lab 1 - bjt - loren - victor - taylor
 
5 ee415 - adv electronics - presentation - schwappach
5   ee415 - adv electronics - presentation - schwappach5   ee415 - adv electronics - presentation - schwappach
5 ee415 - adv electronics - presentation - schwappach
 
4 ee414 - adv electroncs - lab 3 - loren schwappach
4   ee414 - adv electroncs - lab 3 - loren schwappach4   ee414 - adv electroncs - lab 3 - loren schwappach
4 ee414 - adv electroncs - lab 3 - loren schwappach
 
3 ee414 - adv electroncs - lab 2 - loren schwappach
3   ee414 - adv electroncs - lab 2 - loren schwappach3   ee414 - adv electroncs - lab 2 - loren schwappach
3 ee414 - adv electroncs - lab 2 - loren schwappach
 
2 ee414 - adv electroncs - lab 1 - loren schwappach
2   ee414 - adv electroncs - lab 1 - loren schwappach2   ee414 - adv electroncs - lab 1 - loren schwappach
2 ee414 - adv electroncs - lab 1 - loren schwappach
 
Ee443 phase locked loop - presentation - schwappach and brandy
Ee443   phase locked loop - presentation - schwappach and brandyEe443   phase locked loop - presentation - schwappach and brandy
Ee443 phase locked loop - presentation - schwappach and brandy
 
Ee443 phase locked loop - paper - schwappach and brandy
Ee443   phase locked loop - paper - schwappach and brandyEe443   phase locked loop - paper - schwappach and brandy
Ee443 phase locked loop - paper - schwappach and brandy
 
EE443 - Communications 1 - Lab 3 - Loren Schwappach.pdf
EE443 - Communications 1 - Lab 3 - Loren Schwappach.pdfEE443 - Communications 1 - Lab 3 - Loren Schwappach.pdf
EE443 - Communications 1 - Lab 3 - Loren Schwappach.pdf
 

Recently uploaded

Search and Society: Reimagining Information Access for Radical Futures
Search and Society: Reimagining Information Access for Radical FuturesSearch and Society: Reimagining Information Access for Radical Futures
Search and Society: Reimagining Information Access for Radical Futures
Bhaskar Mitra
 

Recently uploaded (20)

Empowering NextGen Mobility via Large Action Model Infrastructure (LAMI): pav...
Empowering NextGen Mobility via Large Action Model Infrastructure (LAMI): pav...Empowering NextGen Mobility via Large Action Model Infrastructure (LAMI): pav...
Empowering NextGen Mobility via Large Action Model Infrastructure (LAMI): pav...
 
IoT Analytics Company Presentation May 2024
IoT Analytics Company Presentation May 2024IoT Analytics Company Presentation May 2024
IoT Analytics Company Presentation May 2024
 
Demystifying gRPC in .Net by John Staveley
Demystifying gRPC in .Net by John StaveleyDemystifying gRPC in .Net by John Staveley
Demystifying gRPC in .Net by John Staveley
 
Unpacking Value Delivery - Agile Oxford Meetup - May 2024.pptx
Unpacking Value Delivery - Agile Oxford Meetup - May 2024.pptxUnpacking Value Delivery - Agile Oxford Meetup - May 2024.pptx
Unpacking Value Delivery - Agile Oxford Meetup - May 2024.pptx
 
In-Depth Performance Testing Guide for IT Professionals
In-Depth Performance Testing Guide for IT ProfessionalsIn-Depth Performance Testing Guide for IT Professionals
In-Depth Performance Testing Guide for IT Professionals
 
How world-class product teams are winning in the AI era by CEO and Founder, P...
How world-class product teams are winning in the AI era by CEO and Founder, P...How world-class product teams are winning in the AI era by CEO and Founder, P...
How world-class product teams are winning in the AI era by CEO and Founder, P...
 
Software Delivery At the Speed of AI: Inflectra Invests In AI-Powered Quality
Software Delivery At the Speed of AI: Inflectra Invests In AI-Powered QualitySoftware Delivery At the Speed of AI: Inflectra Invests In AI-Powered Quality
Software Delivery At the Speed of AI: Inflectra Invests In AI-Powered Quality
 
When stars align: studies in data quality, knowledge graphs, and machine lear...
When stars align: studies in data quality, knowledge graphs, and machine lear...When stars align: studies in data quality, knowledge graphs, and machine lear...
When stars align: studies in data quality, knowledge graphs, and machine lear...
 
Kubernetes & AI - Beauty and the Beast !?! @KCD Istanbul 2024
Kubernetes & AI - Beauty and the Beast !?! @KCD Istanbul 2024Kubernetes & AI - Beauty and the Beast !?! @KCD Istanbul 2024
Kubernetes & AI - Beauty and the Beast !?! @KCD Istanbul 2024
 
De-mystifying Zero to One: Design Informed Techniques for Greenfield Innovati...
De-mystifying Zero to One: Design Informed Techniques for Greenfield Innovati...De-mystifying Zero to One: Design Informed Techniques for Greenfield Innovati...
De-mystifying Zero to One: Design Informed Techniques for Greenfield Innovati...
 
AI for Every Business: Unlocking Your Product's Universal Potential by VP of ...
AI for Every Business: Unlocking Your Product's Universal Potential by VP of ...AI for Every Business: Unlocking Your Product's Universal Potential by VP of ...
AI for Every Business: Unlocking Your Product's Universal Potential by VP of ...
 
Bits & Pixels using AI for Good.........
Bits & Pixels using AI for Good.........Bits & Pixels using AI for Good.........
Bits & Pixels using AI for Good.........
 
GenAISummit 2024 May 28 Sri Ambati Keynote: AGI Belongs to The Community in O...
GenAISummit 2024 May 28 Sri Ambati Keynote: AGI Belongs to The Community in O...GenAISummit 2024 May 28 Sri Ambati Keynote: AGI Belongs to The Community in O...
GenAISummit 2024 May 28 Sri Ambati Keynote: AGI Belongs to The Community in O...
 
FIDO Alliance Osaka Seminar: FIDO Security Aspects.pdf
FIDO Alliance Osaka Seminar: FIDO Security Aspects.pdfFIDO Alliance Osaka Seminar: FIDO Security Aspects.pdf
FIDO Alliance Osaka Seminar: FIDO Security Aspects.pdf
 
JMeter webinar - integration with InfluxDB and Grafana
JMeter webinar - integration with InfluxDB and GrafanaJMeter webinar - integration with InfluxDB and Grafana
JMeter webinar - integration with InfluxDB and Grafana
 
Neuro-symbolic is not enough, we need neuro-*semantic*
Neuro-symbolic is not enough, we need neuro-*semantic*Neuro-symbolic is not enough, we need neuro-*semantic*
Neuro-symbolic is not enough, we need neuro-*semantic*
 
Smart TV Buyer Insights Survey 2024 by 91mobiles.pdf
Smart TV Buyer Insights Survey 2024 by 91mobiles.pdfSmart TV Buyer Insights Survey 2024 by 91mobiles.pdf
Smart TV Buyer Insights Survey 2024 by 91mobiles.pdf
 
Speed Wins: From Kafka to APIs in Minutes
Speed Wins: From Kafka to APIs in MinutesSpeed Wins: From Kafka to APIs in Minutes
Speed Wins: From Kafka to APIs in Minutes
 
Search and Society: Reimagining Information Access for Radical Futures
Search and Society: Reimagining Information Access for Radical FuturesSearch and Society: Reimagining Information Access for Radical Futures
Search and Society: Reimagining Information Access for Radical Futures
 
Builder.ai Founder Sachin Dev Duggal's Strategic Approach to Create an Innova...
Builder.ai Founder Sachin Dev Duggal's Strategic Approach to Create an Innova...Builder.ai Founder Sachin Dev Duggal's Strategic Approach to Create an Innova...
Builder.ai Founder Sachin Dev Duggal's Strategic Approach to Create an Innova...
 

EE312 Embedded Microcontrollers Lab

  • 1. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 EE 312 Embedded Microcontrollers Final Lab Assignment “Modular programming with the MC68HC11, using loops, subroutines, branching, terminal I/O, Buffalo Monitor I/O, LEDs, LCDs, sounds, buttons, and ASCII conversion.” By: Loren K. Schwappach Student Number: 06B7050651 Date Due: May 18, 2009 Date Completed: May 16, 2009 Professor: Pamela Hoffman Page 1 of 81 Colorado Technical University
  • 2. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 1. Purpose: This program will cover many of the possibilities offered by the MC68HC11, FOX-11 board. It will use the buffalo monitor and terminal I/O addresses to get/send information to a monitor and LCD. This lab will demonstrate sound, buttons, LEDs, basic math operations, and finally how to convert ASCII user input into numerical values for a small math computation game. 2. Future project ideas for students: I. Use the keypad for setting variable speed of the LED racetrack. II. Create a module that would get/convert/store several larger ASCII (0- 9) numerals into Hex at a separate memory location and reconvert for terminal & LCD output. III. Develop song for intro using Buffalo monitor test.asm demo IV. Have credits at the end scroll and repeat over the LCD, by incrementing the X location in a loop and calling the LCD display subroutine until the end of the string +16. Professor: Pamela Hoffman Page 2 of 81 Colorado Technical University
  • 3. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 3. Instructions and Directives: I. LOAD: Places a specified value or memory location(s) into a register for temporary storage manipulation. It can be used to load values / address in 8 bit accumulators A or B, or the 16 bit registers, double accumulator D (Uses A and B), the stack pointer, or either index register X or Y. Figure 4.1: Load instructions Professor: Pamela Hoffman Page 3 of 81 Colorado Technical University
  • 4. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 II. ADD: Performs arithmetic addition operation(s) upon registers. Very powerful! Figure 4.2: Add instructions Professor: Pamela Hoffman Page 4 of 81 Colorado Technical University
  • 5. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 III. SUB: Performs arithmetic subtraction operation(s) upon registers. Also very powerful! Figure 4.3: Subtraction instructions Professor: Pamela Hoffman Page 5 of 81 Colorado Technical University
  • 6. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 IV. STORE: Stores contents of register into memory location(s). Destination must be a valid storable memory location. Also if register is 16 bit register, storage will consume two blocks of memory. Figure 4.4: Store instruction Professor: Pamela Hoffman Page 6 of 81 Colorado Technical University
  • 7. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 V. MUL: Multiplies an 8-bit unsigned value in A by an 8-bit unsigned value in B to obtain a 16-bit unsigned result in D (thus writes over A and B). Uses inherent addressing. Example: Start: ORG $9000 ; directive, sets program start ; location. Use go 9000 LDAA #10 ; load accum. A with decimal 10 LDAB #25 ; load accum. B with decimal 25 MUL ; multiplies A*B stores decimal ; value 250 in D STD $8000 ; stores D at location $8000 and ; $8001 END ; housekeeping directive tells ; program to halt. VI. DIV: There are two division instructions IDIV and FDIV. IDIV performs unsigned integer division of the 16 bit numerator in D by the 16 bit denominator in X. For the result, the quotient is placed in X and the remainder is placed in D. If denominator is 0 the quotient is set to $FFFF, the remainder is indeterminate and the CCR C flag is set=1. IDIV uses inherent addressing. Example: Professor: Pamela Hoffman Page 7 of 81 Colorado Technical University
  • 8. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 LDD #4 ; Loads D with decimal value 4 LDX #2 ; Loads X with decimal value 2 IDIV ; (4/2)=2 w/ r=0 so X=2, D=0 FDIV performs unsigned fractional division of the 16 bit numerator in D by the 16 bit denominator in X. For the result, the quotient is placed in X and the remainder is placed in D. If the denominator is 0 or in the case of overflow the quotient is set to $FFFF and remainder is indeterminate and CCR C flag is set=1. The radix point is to the left of bit 15 for the quotient. FDIV uses inherent addressing. Example: LDD #2 ; 4 is loaded in D (numerator) LDX #3 ; 3 is loaded in X (denominator) FDIV ; quotient in X, remainder in D VII. DAA: Decimal Adjust Accumulator A, used for BCD addition. Checks CCR C (Carry) flag, upper half byte of Accumulator A, initial H (Half Carry) flag, lower byte of Accumulator A and uses conditions to add a set amount to Accumulator A and finally resets C flag. This ensures correct BCD addition. Use inherent addressing. Example: Professor: Pamela Hoffman Page 8 of 81 Colorado Technical University
  • 9. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 LDA #$04 ; Load BCD 00100100, decimal value 04 ADDA #$16 ; Load BCD 00010110, decimal value 16 DAA ; Checks A, and CCR and then adds $06 to A ; A now correctly holds hex $20 BCD value ; 00100000 VIII. Exchange Registers: There are two instructions that perform register exchanges. XGDX (exchange double accumulator D with index register X) and XGDY (exchange double accumulator D with index register Y), both use inherent addressing. Example (Assume X = 8020 and Y = 8040 prior to execution): LDD #$8000 ; Load D w/ hex value 8000 XGDX ; D now holds $8020, X now holds 8000 XGDY ; D now holds $8040, Y now holds 8020 Note: Another way of exchanging register is with the load and store instructions already covered. Professor: Pamela Hoffman Page 9 of 81 Colorado Technical University
  • 10. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 IX. Compare / Test Instruction: Used to compare or test registers / locations and set CCR flags, while leaving compared accumulator contents intact. Very powerful! Used to control branch instructions and interrupts. Often used in loop control. Figure 4.5 Compare and Test Instructions Professor: Pamela Hoffman Page 10 of 81 Colorado Technical University
  • 11. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 X. Branch / Jump / Return Instructions: Branch, Jump, and Return instructions tell the program to go somewhere else or return from somewhere, normally depending upon CCR flag and the use of the stack. Branch instructions (Essential for modular programming and loops): The following are branch instructions that if the conditions are met (CCR) the program branches to relative address specified (relative addresses are offsets from current address limited to -128 to 127 bytes) so is very limited to the location it can branch to...) Refer to a text on Boolean algebra if you do not understand AND, OR, XOR operations Instr. ; Meaning ; Branches if BRA <rel> ; branch (unconditional) ; Always BCC <rel> ; carry clear ; C = 0 BCS <rel> ; carry set ; C = 1 BLO <rel> ; lower (unsigned) ; C = 1 BHS <rel> ; higher or same (unsigned) ; C = 0 BEQ <rel> ; equal to 0 ; Z = 1 BNE <rel> ; not equal to 0 ; Z = 0 BPL <rel> ; plus (signed) ; N = 0 BMI <rel> ; minus (signed) ; N = 1 BVS <rel> ; overflow bit set ; V = 1 Professor: Pamela Hoffman Page 11 of 81 Colorado Technical University
  • 12. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 BVC <rel> ; overflow bit clear ; V = 0 BGE <rel> ; greater or = to 0 (signed) ; (N XOR V) = 0 BGT <rel> ; greater than 0 (signed) ; (Z + (N XOR V)) = 0 BHI <rel> ; higher or same (unsigned) ; (C + Z) = 0 BLE <rel> ; less than or = 0 ; (Z + (N XOR V)) = 1 BLS <rel> ; lower or same (unsigned) ; (C + Z) = 1 BLT <rel> ; less than 0 (signed) ; (N XOR V) = 1 BCLR <operand> ; clear bits ; M AND M’ <msk> BRCLR <operand> ; if bits clear ; M AND (PC+2) = 0 <msk><rel> BSET <operand> ; set bits ; M + M AND M <msk> BRSET <operand> ; if bits set ; M AND (PC+2) = 1 <msk><rel> Professor: Pamela Hoffman Page 12 of 81 Colorado Technical University
  • 13. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 Jump Instructions: JMP <operand> ; Jumps to instruction stored at effective address given in operand. JMP uses extended or indexed addressing. JSR <operand> ; Jumps to subroutine specified by operand. JSR uses direct, extended, or indexed addressing. Note: This allows for the creation of modular programming (functions). JSR increments the program counter (PC) by two or three depending upon addressing used and pushes the PC onto the stack so you can return where you left off using RTS (Return from Sub Routine) instruction. Return Instructions: There are two return instructions RTS (Return from Sub Routine) and RTI (Return from interrupt). RTS ; Uses inherent addressing and is used to return out the called subroutine back to the caller subroutine. This is accomplished by incrementing the stack pointer and loading the address contained back into the program counter. RTI ; Users inherent addressing and is used to restore A, B, X, Y, CCR, and PC states by pulling them from the stack, also may or may not set CCR X flag. Professor: Pamela Hoffman Page 13 of 81 Colorado Technical University
  • 14. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 XI. Decrement / Increment Instructions (Often used in loops): DEC <operand> ; decrements value at location by 1, value - 1 DECA ; decrements A by 1, A = A - 1 DECB ; decrements B by 1, B = B - 1 DEX ; decrements X by 1, X = X - 1 DEY ; decrements Y by 1, Y = Y - 1 DES ; decrements SP by 1, SP = SP - 1 INC <operand> ; increments value at location by 1, value + 1 INCA ; increments A by 1, A = A + 1 INCB ; increments B by 1, B = B + 1 INX ; increments X by 1, X = X + 1 INY ; increments Y by 1, Y = Y + 1 INS ; increments SP by 1, SP = SP + 1 XII. Rotate & Shift (Logical & Arithmetic) Instructions: Professor: Pamela Hoffman Page 14 of 81 Colorado Technical University
  • 15. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 Figure 4.6: Rotate and Shift Instructions Professor: Pamela Hoffman Page 15 of 81 Colorado Technical University
  • 16. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 XIII. PUSH / PULL & Transfer Instructions: Push and pull instructions manipulate the stack which is discussed in detail in Section 8. They are extremely valuable instructions and assist in searching, accessing, and manipulating strings and arrays as well as preserving register values for modular programming. Figure 4.7: Push and Pull instructions Transfer Instructions: Professor: Pamela Hoffman Page 16 of 81 Colorado Technical University
  • 17. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 Transfer instructions are used to manipulate the stack pointer (SP), and thus can be used to quickly navigate the stack. Figure 4.8: Transfer Instructions XIV. Clear Instruction & variable initialization: Clear “CLR” instructions do just what they suggest; they replace the contents of a memory location or register with zeros. This is often used for variable initialization. Figure 4.9: Clear Instructions Professor: Pamela Hoffman Page 17 of 81 Colorado Technical University
  • 18. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 XV. Other Important Instructions: Logic Instructions ANDA <operand> ; AND A with memory (Immediate, Direct, Extended, or Indirect Addressing) ANDB <operand> ; AND B with memory (Immediate, Direct, Extended, or Indirect Addressing) BITA <operand> ; Bit tests A with memory (A AND M) and sets CCR (Immediate, Direct, Extended, or Indirect Addressing) BITB <operand> ; Bit tests B with memory (B AND M) and sets CCR (Immediate, Direct, Extended, or Indirect Addressing) COM <operand> ; Get value at operand and take ones complement or invert bits (extended or indirect addressing) COMA ; Take ones comp. of A store in A, invert bits COMB ; Take ones comp. of B store in B, invert bits EORA <operand> ; XOR with value in memory w/ A store in A (Immediate, extended, direct, indirect) EORB <operand> ; XOR with value in memory w/ B store in B (Immediate, extended, direct, indirect) Professor: Pamela Hoffman Page 18 of 81 Colorado Technical University
  • 19. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 NEG <operand> ; 2’s complement of memory store in memory (Extended or Indirect) NEGA ; 2’s complement of A store in A NEGB ; 2’s complement of B store in B ORAA <operand> ; OR A with memory store in A ORAB <operand> ; OR B with memory store in B Other Useful Instructions (Note: Several used for interrupts) CLV ; lear overflow flag, V=0 NOP ; No operation, takes up clock cycles for nothing SEC ; Set carry, C=1 SEI ; Set interrupt mask, I=1 SEV ; Set overflow flag, V=1 STOP ; Stop internal clock SWI ; Software interrupt TAP ; Transfer A to CCR TPA ; Transfer CCR to A WAI ; Wait for interrupt Professor: Pamela Hoffman Page 19 of 81 Colorado Technical University
  • 20. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 XVI. Directives: Directives are commands to the assembler that define data and symbols, setting assembly conditions, and specifying output format. Directives do not produce code but perform housekeeping activities for the assembler. ORG <address> ; Sets value of location counter to address specified RMB <#> ; Reserves memory byte(s), number given by # DCB ; Defines constant block, reserves area in memory and initializes each byte to the same constant. FCB <......> ; Forms constant byte(s) w/ value set by operand FDB <......> ; Forms 2 bytes for each argument FCC <......> ; Forms constant character(s), forms ASCII string, use “This is my String” format. BSZ <#> ; Reserves a number of bytes specified starting at location counter and initializes each/all value(s) to $00. FILL <Value1, Value2> ; Reserves # of bytes (Value1) and fills each with Value2 starting at address given by location counter. END ; Indicates the END of a program. Professor: Pamela Hoffman Page 20 of 81 Colorado Technical University
  • 21. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 4. Understanding and Using the program: This begin this lab copy/paste/save/assemble/load the program and start the program at memory location $9000 with the “go $9000” command. $9000 is where I begin to store all of the program code for this lab. Once the program begins the first thing that is accomplished is to load the stack pointer at $C800. This should always be in the first few lines of code for any program that plans on making use of the stack, as all modular programs should. I also use the equate directive extensively, which helps in keeping port locations, terminal/Buffalo monitor I/O routines, ASCII values, and delay loop variables easy to remember. I also declared/formed area for the storage of my user input ASCII values and filled the first 16 blocks with ASCII whitespace and a terminating EOT so that the terminal display routine and Buffalo monitor LCD routine could correctly handle/display the correct information when called. These string locations as well as other temp variable locations begin at locations $8000 in memory for easy referencing. As with the above, I also formed/reserved storage for all of the strings, ensuring all strings were 16 characters and ending in a ASCII EOT for later referencing. All output strings begin at memory location $A000. This sort of memory assignment/separation is important for T/S code and ensures that you don’t have problems where pieces of code override one another. Professor: Pamela Hoffman Page 21 of 81 Colorado Technical University
  • 22. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 Next, after beginning the program and loading the stack I immediately call a jump statement that sends the program to my main_func subroutine, which if you are reading the code right now is at the very bottom. Just like in C or C++ this seemed a logical place for placing the subroutine that would call all other subroutines. Once in main_func subroutine I begin calling all of the following other subroutines but before I go into them let me explain something about them all. To ensure that I can contain each subroutines variables and register components intact I make extensive use of the stack pull and push instructions. This allows each subroutine to keep a form of temporary register storage and prevents a register value in one subroutine from interfering with another subroutines values. If I plan on passing a register from one subroutine to the next over and over I skip this push/pull which allows the two to use each other’s register values. The first subroutine called is LCD_init which initializes the Buffalo monitor LCD for use. Next I call Clear LEDs which sets the value $00 in port B and clears the LEDs. Next, I call Disp_LCD_clear which clears the LCDs with whitespace. I then call Disp_welcome to display my initial program welcome message. Next, Flash_LEDs_osc displays an oscillating (middle to left/right, left/right to middle) LED pattern using a delay routine and specifies values of Port B to flash the LEDs and make a beep when the LEDs touch (like a hospital heart monitor), a simple but dramatic effect. Professor: Pamela Hoffman Page 22 of 81 Colorado Technical University
  • 23. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 Next I call Disp_q_name to tell the user I would like their name. I then call Get_name to get the users name and store it at an assigned memory location. I also prevent the users input from storing more than 16 characters so that the name displays correctly on the LCD. I then call Display_name to display their results to screen. Finally I call Display_press_btn, which tells the user to press one of three buttons and the I call Check_buttons which selectively calls for four other subroutines, one which checks for a button being pressed, and if pressed calls one of the other three subroutines depending upon which button was pressed. Depending upon the button pressed the program will do one of the following... The first button will flash the intro LED pulse pattern ten times. The second run a looping colorful racetrack LED pattern using the breadboard and LEDs (Note: If you want to do this on your breadboard you will need to use the PB0-PB7 outputs as highs to your breadboard LEDs and use the ground as a low for your breadboard. I also ensured that the delay subroutines used a temporary delay value that although I didn’t use the user could expand upon the program and build a module to increase or decrease the speed at which the racetrack LEDs flashed (I leave this up to the user). The third button will run a simple math program to get two numbers (0-4) from the user, it then converts the numbers into their actual hex value representations for computation, reconverts the result into ASCII Professor: Pamela Hoffman Page 23 of 81 Colorado Technical University
  • 24. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 stores and displays on the terminal and LCD. I had plans to make this perform larger computations but would have needed to create a larger module in order to handle large user ASCII strings into hex values conversion for multi-precision addition (Remember each ASCII numeral entered is two bytes (representing 10 possibilities 0-9) where the actual hex only needs one and represents 16 possibilities (decimal 0-15 or 0-F). To simplify the program I used validation routines that ensured the user could only enter a value between 0 and 4 (Because max values 4+4=8 which simplifies ASCII conversion +/- $30). Once the user is done with the choices I used a loop for the Check_buttons routine which caused the loop to exit after a certain period of inactive time (30 seconds). Then Display_credits and Display_exit_world is called to display goodbye messages to the user. Finally the program exits Main_Func and returns to the top where the registers are cleared and the program terminates. Professor: Pamela Hoffman Page 24 of 81 Colorado Technical University
  • 25. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 * Assembly Code! * Final Project, Version 1 * Coded by: Loren K. R. Schwappach * Coded on: 13 June 09 * Completed in Requirements for: * EE312, Embedded Microcontrollers * Instructor: Professor Pamella Hoffman * Program description: This program will cover many of the possibilities * offered by the MC68HC11, FOX-11 board. It will use the buffalo monitor * and I/O addresses to get/send information to a monitor and LCD. It will * demonstrate sound, buttons, LEDs, and how to control output to a bread board. * it also demonstrates how to convert ASCII user input into numerical values * for a small math computation. * Future ideas (if time permitted..) * #1 Use the keypad for setting variable speed of racetrack * #2 Create a module the would get/convert/store large ASCII numerals to Hex * And then retrieve/convert/store these values in ASCII for display * #3 Develop song for intro.. * #4 Have credits scroll and repeat over LCD by inc X in loop and increasing init string size * ------------------------ * References * ------------------------ * Define addresses for LCD output LCD_init EQU $FF70 ; Address to initialize the LCD LCD_write_top EQU $FF73 ; Address to write to LCD top LCD_write_bottom EQU $FF76 ; Address to write to LCD bottom Professor: Pamela Hoffman Page 25 of 81 Colorado Technical University
  • 26. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 * Define addresses/values for terminal I/O Output_disp_text EQU $FFC7 ; Outputs all ASCII stored at loc in X until EOT Input_get_char EQU $FFCD ; Gets ASCII character from keyboard -> stores in A Output_disp_CR EQU $FFC4 ; Outputs ASCII character return and line feed CR EQU $0D ; ASCII CR, (enter key) EOT EQU $04 ; ASCII EOT, (End Of Transmission) * Define port I/O addresses Port_A EQU $1000 ; Port A Address Port_B EQU $1404 ; Port B Address Port_C EQU $1403 ; Port C Address * Delay loop times Hundred_ms EQU 16700 ; Loop iterations for 100ms delay Ten_ms EQU 1670 ; Loop iterations for 10ms delay One_ms EQU 167 ; Loop iterations for 1ms delay Var_ms EQU 2505 ; Loop iterations for variable delay (15ms) * Other important values * Store Program at {$9000 - $9FFF}, Store Stack at {$C800 - $C000} Program_loc EQU $9000 ; Begin program here w/ go 9000 command Stack_loc EQU $C800 ; Set aside location for stack, used extensively * ------------------------ * Variable Storage Locations {$8000 - $8FFF} * ------------------------ Username EQU $8000 ; Location to reference later for ASCII name storage ORG $8000 ; Set location to $8000 FILL 16, $20 ; Fill 16 blocks from $8000 to $8010 with $20 "ASCII space" ; Note on above: value $20 used so LCDs display correctly FCB EOT ; Form Constant Block at $8011 with ASCII EOT Professor: Pamela Hoffman Page 26 of 81 Colorado Technical University
  • 27. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 Result EQU $8020 ; Location to reference later for ASCII math result storage ORG $8020 ; Set location to $8020 FILL 16, $20 ; Fill 16 blocks from $8020 to $8030 with $20 "ASCII space" ; Note on above: value $20 used so LCDs display correctly FCB EOT ; Form Constant Block at $8031 with ASCII EOT Value1 RMB 1 ; Reserve Memory Block at $8032 for math fun value 1 value2 RMB 1 ; Reserve Memory Block at $8033 for math fun value 2 * ------------------------ * String Output Locations {$A000 - $AFFF} * ------------------------ ORG $A000 ; Set location for storage of string Clear_LCD FCC " " ; Form Constant Character for LCD "16 character" display FCB EOT ; Form Constant Block at location above + 17 for output to monitor ORG $A020 ; Set location for storage of string Welcome1 FCC " Welcome to my " ; Form Constant Character for LCD "16 character" display FCB EOT ; Form Constant Block at location above + 17 for output to monitor ORG $A040 ; Set location for storage of string Welcome2 FCC "EE312 FOX11 Demo" ; Form Constant Character for LCD "16 character" display FCB EOT ; Form Constant Block at location above + 17 for output to monitor ORG $A060 ; Set location for storage of string Question_Name1 FCC " Please enter, " ; Form Constant Character for LCD "16 character" display FCB EOT ; Form Constant Block at location above + 17 for output to monitor ORG $A080 ; Set location for storage of string Question_Name2 FCC " Your name... " ; Form Constant Character for LCD "16 character" display FCB EOT ; Form Constant Block at location above + 17 for output to monitor ORG $A0A0 ; Set location for storage of string Warning1 FCC " !Max 15 char! " ; Form Constant Character for LCD "16 character" display FCB EOT ; Form Constant Block at location above + 17 for output to monitor Professor: Pamela Hoffman Page 27 of 81 Colorado Technical University
  • 28. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 ORG $A0C0 ; Set location for storage of string Question_Name3 FCC "Enter name -here" ; Form Constant Character for LCD "16 character" display FCB EOT ; Form Constant Block at location above + 17 for output to monitor ORG $A0E0 ; Set location for storage of string Response_Name1 FCC "**** Hello **** " ; Form Constant Character for LCD "16 character" display FCB EOT ; Form Constant Block at location above + 17 for output to monitor ORG $A100 ; Set location for storage of string Press_Btn1 FCC " Press a Button " ; Form Constant Character for LCD "16 character" display FCB EOT ; Form Constant Block at location above + 17 for output to monitor ORG $A120 ; Set location for storage of string Press_Btn2 FCC "PA0, PC1, or PC0" ; Form Constant Character for LCD "16 character" display FCB EOT ; Form Constant Block at location above + 17 for output to monitor ORG $A140 ; Set location for storage of string Warning2 FCC "20s left to exit" ; Form Constant Character for LCD "16 character" display FCB EOT ; Form Constant Block at location above + 17 for output to monitor ORG $A160 ; Set location for storage of string Warning3 FCC "10s left to exit" ; Form Constant Character for LCD "16 character" display FCB EOT ; Form Constant Block at location above + 17 for output to monitor ORG $A180 ; Set location for storage of string MathA_1 FCC " Time for some " ; Form Constant Character for LCD "16 character" display FCB EOT ; Form Constant Block at location above + 17 for output to monitor ORG $A1A0 ; Set location for storage of string MathA_2 FCC "Simple math fun " ; Form Constant Character for LCD "16 character" display FCB EOT ; Form Constant Block at location above + 17 for output to monitor ORG $A1C0 ; Set location for storage of string MathB_1 FCC " Give me two #s " ; Form Constant Character for LCD "16 character" display FCB EOT ; Form Constant Block at location above + 17 for output to monitor ORG $A1E0 ; Set location for storage of string MathB_2 FCC "1 dig.= {0 to 4}" ; Form Constant Character for LCD "16 character" display Professor: Pamela Hoffman Page 28 of 81 Colorado Technical University
  • 29. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 FCB EOT ; Form Constant Block at location above + 17 for output to monitor ORG $A200 ; Set location for storage of string MathC_1 FCC "ENT 1st Number: " ; Form Constant Character for LCD "16 character" display FCB EOT ; Form Constant Block at location above + 17 for output to monitor ORG $A220 ; Set location for storage of string MathD_1 FCC "ENT 2nd Number: " ; Form Constant Character for LCD "16 character" display FCB EOT ; Form Constant Block at location above + 17 for output to monitor ORG $A240 ; Set location for storage of string MathE_1 FCC "The Result is.. " ; Form Constant Character for LCD "16 character" display FCB EOT ; Form Constant Block at location above + 17 for output to monitor ORG $A260 ; Set location for storage of string Credits1 FCC "Created by.. " ; Form Constant Character for LCD "16 character" display FCB EOT ; Form Constant Block at location above + 17 for output to monitor ORG $A280 ; Set location for storage of string Credits2 FCC "Loren Schwappach" ; Form Constant Character for LCD "16 character" display FCB EOT ; Form Constant Block at location above + 17 for output to monitor ORG $A2A0 ; Set location for storage of string Exit_World1 FCC "Exiting EE312Lab" ; Form Constant Character for LCD "16 character" display FCB EOT ; Form Constant Block at location above + 17 for output to monitor ORG $A2C0 ; Set location for storage of string Exit_World2 FCC "Press reset btn " ; Form Constant Character for LCD "16 character" display FCB EOT ; Form Constant Block at location above + 17 for output to monitor * ------------------------ * Call program and set Stack location * ------------------------ Start ORG Program_loc ; Set location counter for program storage { Program starts at $9000 } LDS #Stack_loc ; Loads begining storage location for stack at $C800 JSR Main_func ; Jumps over all subroutines below to main subroutine at bottom of page Professor: Pamela Hoffman Page 29 of 81 Colorado Technical University
  • 30. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 JSR Clear_reg ; Jump to subroutine clear registers Terminate END ; Ends Program * ------------------------ * Subroutines * ------------------------ * Clear Registers Clear_reg LDAA #$00 ; Load Accum. A w/ 0 LDAB #$00 ; Load Accum. B w/ 0 LDX #$0000 ; Load Index Reg X w/ 0 LDY #$0000 ; Load Index Reg Y w/ 0 RTS ; Return to Subroutine which called this * Delay Subroutines Delay DEX ; Decrement X {Take up some time.. clock cycles} INX ; Increment X {Take up some time.. clock cycles} DEX ; Decrement X, initial X value provided by routine that called this BNE Delay ; Branch if not equal to 0 to Delay.. loop until X=0 RTS ; Return to Subroutine which called this Delay_1ms PSHX ; Push X onto stack, prevents loss of data stored in X during subroutine use LDX #One_ms ; Load X with value referenced by EQU above BSR Delay ; With retrieved X value obtained branch to delay to take up indicated time PULX ; Pull X value stored in stack to X, restores data stored in X before subroutine call RTS ; Return to Subroutine which called this Delay_10ms PSHX ; Push X onto stack, prevents loss of data stored in X during subroutine use LDX #Ten_ms ; Load X with value referenced by EQU above Professor: Pamela Hoffman Page 30 of 81 Colorado Technical University
  • 31. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 BSR Delay ; With retrieved X value obtained branch to delay to take up indicated time PULX ; Pull X value stored in stack to X, restores data stored in X before subroutine call RTS ; Return to Subroutine which called this Delay_100ms PSHX ; Push X onto stack, prevents loss of data stored in X during subroutine use LDX #Hundred_ms ; Load X with value referenced by EQU above BSR Delay ; With retrieved X value obtained branch to delay to take up indicated time PULX ; Pull X value stored in stack to X, restores data stored in X before subroutine call RTS ; Return to Subroutine which called this Delay_Var_ms PSHX ; Push X onto stack, prevents loss of data stored in X during subroutine use LDX #Var_ms ; Load X with value referenced by EQU above BSR Delay ; With retrieved X value obtained branch to delay to take up indicated time PULX ; Pull X value stored in stack to X, restores data stored in X before subroutine call RTS ; Return to Subroutine which called this * Clear LEDs Clear_LEDs PSHA ; Push A onto stack, prevents loss of data stored in A during subroutine use LDAA #0 ; Load Accum A w/ value 0 {All LEDs out} STAA Port_B ; Stores value at Port_B {All LEDs out} PULA ; Pull A value stored in stack to A, restores data stored in A before subroutine call RTS ; Return to Subroutine which called this * Create beep sound at 25 pulses Beep_once PSHX ; Push X onto stack, prevents loss of data stored in X during subroutine use Professor: Pamela Hoffman Page 31 of 81 Colorado Technical University
  • 32. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 PSHY ; Push Y onto stack, prevents loss of data stored in Y during subroutine use PSHA ; Push A onto stack, prevents loss of data stored in A during subroutine use LDX #25 ; Load X w/ value 25 {controls beep loops, pulses} Beep_once_loop LDAA #$20 ; Load A w/ value $20 {Determines sound/tone of beep} STAA Port_A ; Stores A in Port_A {Makes beep sound} JSR Delay_1ms ; Takes up some time LDAA #$00 ; Loads A w/ value 0 STAA Port_A ; Stores A in Port_A {Clears beep sound} JSR Delay_1ms ; Takes up some time DEX ; Decrements X CPX #0 ; Compares X w/ value 0 BNE Beep_once_loop ; Branches, loops.. if X does not equal 0 PULA ; Pull A value stored in stack to A, restores data stored in A before subroutine call PULY ; Pull Y value stored in stack to Y, restores data stored in Y before subroutine call PULX ; Pull X value stored in stack to X, restores data stored in X before subroutine call RTS ; Return to Subroutine which called this * Display race track, "LEDs circle around bread board" * If I had more time I had plans to allow user input * determine speed (Delay_Var_ms) Racetrack_sim PSHA ; Push A onto stack, prevents loss of data stored in A during subroutine use PSHX ; Push X onto stack, prevents loss of data stored in X during subroutine use JSR Clear_LEDs ; Clear LEDs LDX #10 ; Load X w/ value {determines number of loops} Race_loop LDAA #$01 ; Loads A w/ value, determines what LED will light STAA Port_B ; Stores A at port B, lights LEDs indicated by value {0 off 1 on, for 8 LEDs} Professor: Pamela Hoffman Page 32 of 81 Colorado Technical University
  • 33. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 JSR Beep_once ; Beep JSR Delay_Var_ms ; Takes up some time LDAA #$02 ; Loads A w/ value, determines what LED will light STAA Port_B ; Stores A at port B, lights LEDs indicated by value {0 off 1 on, for 8 LEDs} JSR Beep_once ; Beep JSR Delay_Var_ms ; Takes up some time LDAA #$04 ; Loads A w/ value, determines what LED will light STAA Port_B ; Stores A at port B, lights LEDs indicated by value {0 off 1 on, for 8 LEDs} JSR Beep_once ; Beep JSR Delay_Var_ms ; Takes up some time LDAA #$08 ; Loads A w/ value, determines what LED will light STAA Port_B ; Stores A at port B, lights LEDs indicated by value {0 off 1 on, for 8 LEDs} JSR Beep_once ; Beep JSR Delay_Var_ms ; Takes up some time LDAA #$10 ; Loads A w/ value, determines what LED will light STAA Port_B ; Stores A at port B, lights LEDs indicated by value {0 off 1 on, for 8 LEDs} JSR Beep_once ; Beep JSR Delay_Var_ms ; Takes up some time LDAA #$20 ; Loads A w/ value, determines what LED will light STAA Port_B ; Stores A at port B, lights LEDs indicated by value {0 off 1 on, for 8 LEDs} JSR Beep_once ; Beep JSR Delay_Var_ms ; Takes up some time LDAA #$40 ; Loads A w/ value, determines what LED will light STAA Port_B ; Stores A at port B, lights LEDs indicated by value {0 off 1 on, for 8 LEDs} JSR Beep_once ; Beep JSR Delay_Var_ms ; Takes up some time LDAA #$80 ; Loads A w/ value, determines what LED will light Professor: Pamela Hoffman Page 33 of 81 Colorado Technical University
  • 34. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 STAA Port_B ; Stores A at port B, lights LEDs indicated by value {0 off 1 on, for 8 LEDs} JSR Beep_once ; Beep JSR Delay_Var_ms ; Takes up some time DEX ; Decrement X by 1 CPX #0 ; Compare X to 0 BEQ Exit_race_loop ; Branches out of loop if X = 0 JMP Race_loop ; Loop if X does not equal 0 Exit_race_loop JSR Clear_LEDs ; Clear LEDs PULX ; Pull X value stored in stack to X, restores data stored in X before subroutine call PULA ; Pull A value stored in stack to A, restores data stored in A before subroutine call RTS ; Return to Subroutine which called this * Flash LEDs in a pulse pattern Flash_LEDs_osc PSHA ; Push A onto stack, prevents loss of data stored in A during subroutine use PSHX ; Push X onto stack, prevents loss of data stored in X during subroutine use JSR Clear_LEDs ; Clear LEDs LDX #10 ; Load X w/ value used for # of loops LED_loop_osc LDAA #$18 ; Loads A w/ value, determines what LED will light STAA Port_B ; Stores A at port B, lights LEDs indicated by value {0 off 1 on, for 8 LEDs} JSR Beep_once ; beep when LEDs touch JSR Delay_100ms ; Takes up some time LDAA #$24 ; Loads A w/ value, determines what LED will light STAA Port_B ; Stores A at port B, lights LEDs indicated by value {0 off 1 on, for 8 LEDs} JSR Delay_100ms ; Takes up some time LDAA #$42 ; Loads A w/ value, determines what LED will light STAA Port_B ; Stores A at port B, lights LEDs indicated by value {0 off 1 on, for 8 LEDs} JSR Delay_100ms ; Takes up some time Professor: Pamela Hoffman Page 34 of 81 Colorado Technical University
  • 35. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 LDAA #$81 ; Loads A w/ value, determines what LED will light STAA Port_B ; Stores A at port B, lights LEDs indicated by value {0 off 1 on, for 8 LEDs} JSR Delay_100ms ; Takes up some time LDAA #$42 ; Loads A w/ value, determines what LED will light STAA Port_B ; Stores A at port B, lights LEDs indicated by value {0 off 1 on, for 8 LEDs} JSR Delay_100ms ; Takes up some time LDAA #$24 ; Loads A w/ value, determines what LED will light STAA Port_B ; Stores A at port B, lights LEDs indicated by value {0 off 1 on, for 8 LEDs} JSR Delay_100ms ; Takes up some time DEX ; Decrement X by 1 BNE LED_loop_osc ; Loop if X does not equal 0 Exit_LED_loop_osc LDAA #$18 ; Loads A w/ value, determines what LED will light STAA Port_B ; Stores A at port B, lights LEDs indicated by value {0 off 1 on, for 8 LEDs} JSR Delay_100ms ; Takes up some time JSR Clear_LEDs ; Clear LEDs PULX ; Pull X value stored in stack to X, restores data stored in X before subroutine call PULA ; Pull A value stored in stack to A, restores data stored in A before subroutine call RTS ; Return to Subroutine which called this * Read buttons PA0, PC1, and PC0 Read_button LDAA Port_C ; Load A w/ value at Port C COMA ; Invert bits in A ANDA #$03 ; AND A w/ value $03, lowest 2 bits only LDAB Port_A ; Load B w/ value at Port A COMB ; Invert bits in B ANDB #$01 ; AND B w/ value $01, lowest bit only ASLB ; Arithmatic Shift Left Accum B ASLB ; Arithmatic Shift Left Accum B Professor: Pamela Hoffman Page 35 of 81 Colorado Technical University
  • 36. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 ABA ; Add B to A store in A RTS ; Return to Subroutine which called this * Subroutines which run depending upon user input {btn press} * Note: Had to create these Check buttons because BNE * is limited to how far it can branch to.. Run_math PSHA ; Push A onto stack, prevents loss of data stored in A during subroutine use PSHX ; Push X onto stack, prevents loss of data stored in X during subroutine use JSR Add_numbers ; Jump to Sub Routine JSR Display_press_btn ; Jump to Sub Routine PULX ; Pull X value stored in stack to X, restores data stored in X before subroutine call PULA ; Pull A value stored in stack to A, restores data stored in A before subroutine call JMP Check_buttons ; Jump back to Check_buttons Run_race PSHA ; Push A onto stack, prevents loss of data stored in A during subroutine use PSHX ; Push X onto stack, prevents loss of data stored in X during subroutine use JSR Racetrack_sim ; Jump to Sub Routine PULX ; Pull X value stored in stack to X, restores data stored in X before subroutine call PULA ; Pull A value stored in stack to A, restores data stored in A before subroutine call JMP Check_buttons ; Jump back to Check_buttons Run_LEDs PSHA ; Push A onto stack, prevents loss of data stored in A during subroutine use PSHX ; Push X onto stack, prevents loss of data stored in X during subroutine use JSR Flash_LEDs_osc ; Jump to Sub Routine PULX ; Pull X value stored in stack to X, restores data stored in X before subroutine call Professor: Pamela Hoffman Page 36 of 81 Colorado Technical University
  • 37. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 PULA ; Pull A value stored in stack to A, restores data stored in A before subroutine call JMP Check_buttons ; Jump back to Check_buttons * Check buttons PA0, PC1, and PC0 and do something Check_buttons LDX #12 ; Load X w/ value used for determining when loop should end LDY #4000 ; Load Y w/ value used for determining when loop should end Check_buttons_loop BSR Read_button ; Branch to Sub Routine to read button STAA Port_B ; Stores read button result in A BITA #$01 ; Is PC0 pressed? BNE Run_LEDs ; Then run LEDs, If A does not equal 0 BITA #$02 ; Is PC1 pressed? BNE Run_race ; Then run LED racetrack, If A does not equal 0 BITA #$04 ; Is PA0 pressed? BNE Run_math ; Then run math program, If A does not equal 0 DEY ; Decrement Y by 1 CPX #10 ; Compare X to value BEQ Disp_t_warning0 ; If X = value branch to location given CPX #8 ; Compare X to value BEQ Disp_t_warning1 ; If X = value branch to location given CPX #4 ; Compare X to value BEQ Disp_t_warning2 ; If X = value branch to location given CPX #0 ; Compare X to value BEQ Check_buttons_done ; If X = value branch to location given CPY #0 ; Compare Y to value BEQ Decrement_X ; If X = value branch to location given JMP Check_buttons_loop ; Loop if X does not equal 0 Decrement_X DEX ; Decrement X JMP Check_buttons_loop ; Jump back to loop Check_buttons_done RTS ; Return to Subroutine which called this Professor: Pamela Hoffman Page 37 of 81 Colorado Technical University
  • 38. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 * Display time warnings * Display clear screen.. Disp_t_warning0 PSHX ; Push X onto stack, prevents loss of data stored in X during subroutine use LDX #Clear_LCD ; Load Clear LCD string location in X JSR LCD_write_top ; Display 16 Character string at loc X on top LCD PULX ; Pull X value stored in stack to X, restores data stored in X before subroutine call JMP Decrement_X ; Jump to location * Display 20s left warning.. Disp_t_warning1 PSHX ; Push X onto stack, prevents loss of data stored in X during subroutine use LDX #Warning2 ; Load X w/ location of string JSR LCD_write_top ; Display 16 Character string at loc X on top LCD JSR Beep_once ; Beep PULX ; Pull X value stored in stack to X, restores data stored in X before subroutine call JMP Decrement_X ; Jump to location * Display 10s left warning.. Disp_t_warning2 PSHX ; Push X onto stack, prevents loss of data stored in X during subroutine use LDX #Warning3 ; Load X w/ location of string JSR LCD_write_top ; Display 16 Character string at loc X on top LCD JSR Beep_once ; Beep PULX ; Pull X value stored in stack to X, restores data stored in X before subroutine call JMP Decrement_X ; Jump to location * Display 15 max char warning.. Disp_char_warning PSHX ; Push X onto stack, prevents loss of data stored in X during subroutine use LDX #Warning1 ; Load X w/ location of string Professor: Pamela Hoffman Page 38 of 81 Colorado Technical University
  • 39. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 JSR LCD_write_top ; Display 16 Character string at loc X on top LCD LDX #Warning1 ; Load X w/ location of string JSR Output_disp_text ; Jump to Sub Routine that outputs all ASCII starting at X and ending when ASCII CR JSR Output_disp_CR ; Jump to Sub Routine that outputs ASCII CR followed by a line feed JSR Beep_once ; Beep PULX ; Pull X value stored in stack to X, restores data stored in X before subroutine call RTS ; Return to Subroutine which called this * Pause for Carraige Return key Pause_return PSHA ; Push A onto stack, prevents loss of data stored in A during subroutine use CR_loop JSR Input_get_char ; Jump to Sub Routine that gets a single ASCII character from keyboard and stores in A CMPA #CR ; Compares A with ASCII CR BEQ Out_CR_loop ; Branch out of loop if equal JMP CR_loop ; If not equal.. stay in loop Out_CR_loop PULA ; Pull A value stored in stack to A, restores data stored in A before subroutine call RTS ; Return to Subroutine which called this * Clear LCD Disp_LCD_clear PSHX ; Push X onto stack, prevents loss of data stored in X during subroutine use LDX #Clear_LCD ; Load X w/ location of string JSR LCD_write_top ; Display 16 Character string at loc X on top LCD LDX #Clear_LCD ; Load X w/ location of string JSR LCD_write_bottom ; Display 16 Character string at loc X on bottom LCD PULX ; Pull X value stored in stack to X, restores data stored in X before subroutine call RTS ; Return to Subroutine which called this * Display Welcome & Pause for CR Key Professor: Pamela Hoffman Page 39 of 81 Colorado Technical University
  • 40. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 Disp_welcome PSHX ; Push X onto stack, prevents loss of data stored in X during subroutine use LDX #Welcome1 ; Load X w/ location of string JSR LCD_write_top ; Display 16 Character string at loc X on top LCD LDX #Welcome2 ; Load X w/ location of string JSR LCD_write_bottom ; Display 16 Character string at loc X on bottom LCD LDX #Welcome1 ; Load X w/ location of string JSR Output_disp_text ; Jump to Sub Routine that outputs all ASCII starting at X and ending when ASCII CR LDX #Welcome2 ; Load X w/ location of string JSR Output_disp_text ; Jump to Sub Routine that outputs all ASCII starting at X and ending when ASCII CR JSR Output_disp_CR ; Jump to Sub Routine that outputs ASCII CR followed by a line feed JSR Pause_return ; Jump to Sub Routine that pauses until user presses enter key.. CR PULX ; Pull X value stored in stack to X, restores data stored in X before subroutine call RTS ; Return to Subroutine which called this * Display Question_Name & Pause for CR Key Disp_q_name PSHX ; Push X onto stack, prevents loss of data stored in X during subroutine use LDX #Question_Name1 ; Load X w/ location of string JSR LCD_write_top ; Display 16 Character string at loc X on top LCD LDX #Question_Name2 ; Load X w/ location of string JSR LCD_write_bottom ; Display 16 Character string at loc X on bottom LCD LDX #Question_Name1 ; Load X w/ location of string JSR Output_disp_text ; Jump to Sub Routine that outputs all ASCII starting at X and ending when ASCII CR LDX #Question_Name2 ; Load X w/ location of string JSR Output_disp_text ; Jump to Sub Routine that outputs all ASCII starting at X and ending when ASCII CR JSR Output_disp_CR ; Jump to Sub Routine that outputs ASCII CR followed by a line feed JSR Pause_return ; Jump to Sub Routine that pauses until user presses enter key.. CR JSR Disp_LCD_clear ; Jump to Sub Routine to clear LCDs Professor: Pamela Hoffman Page 40 of 81 Colorado Technical University
  • 41. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 JSR Disp_char_warning ; Jump to Sub Routine JSR Pause_return ; Jump to Sub Routine that pauses until user presses enter key.. CR PULX ; Pull X value stored in stack to X, restores data stored in X before subroutine call RTS ; Return to Subroutine which called this * Displays Name Display_name PSHX ; Push X onto stack, prevents loss of data stored in X during subroutine use LDX #Response_Name1 ; Load X w/ location of string JSR LCD_write_top ; Display 16 Character string at loc X on top LCD LDX #Username ; Load X w/ location of string JSR LCD_write_bottom ; Display 16 Character string at loc X on bottom LCD JSR Output_disp_CR ; Jump to Sub Routine that outputs ASCII CR followed by a line feed LDX #Response_Name1 ; Load X w/ location of string JSR Output_disp_text ; Jump to Sub Routine that outputs all ASCII starting at X and ending when ASCII CR LDX #Username ; Load X w/ location of string JSR Output_disp_text ; Jump to Sub Routine that outputs all ASCII starting at X and ending when ASCII CR JSR Output_disp_CR ; Jump to Sub Routine that outputs ASCII CR followed by a line feed JSR Pause_return ; Jump to Sub Routine that pauses until user presses enter key.. CR JSR Disp_LCD_clear ; Jump to Sub Routine to clear LCDs PULX ; Pull X value stored in stack to X, restores data stored in X before subroutine call RTS ; Return to Subroutine which called this * Displays Press a Button Display_press_btn PSHX ; Push X onto stack, prevents loss of data stored in X during subroutine use LDX #Press_Btn1 ; Load X w/ location of string JSR LCD_write_top ; Display 16 Character string at loc X on top LCD LDX #Press_Btn2 ; Load X w/ location of string JSR LCD_write_bottom ; Display 16 Character string at loc X on bottom LCD Professor: Pamela Hoffman Page 41 of 81 Colorado Technical University
  • 42. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 JSR Output_disp_CR ; Jump to Sub Routine that outputs ASCII CR followed by a line feed LDX #Press_Btn1 ; Load X w/ location of string JSR Output_disp_text ; Jump to Sub Routine that outputs all ASCII starting at X and ending when ASCII CR LDX #Press_Btn2 ; Load X w/ location of string JSR Output_disp_text ; Jump to Sub Routine that outputs all ASCII starting at X and ending when ASCII CR JSR Output_disp_CR ; Jump to Sub Routine that outputs ASCII CR followed by a line feed PULX ; Pull X value stored in stack to X, restores data stored in X before subroutine call RTS ; Return to Subroutine which called this * Displays Credits Display_credits PSHX ; Push X onto stack, prevents loss of data stored in X during subroutine use LDX #Credits1 ; Load X w/ location of string JSR LCD_write_top ; Display 16 Character string at loc X on top LCD LDX #Credits2 ; Load X w/ location of string JSR LCD_write_bottom ; Display 16 Character string at loc X on bottom LCD JSR Output_disp_CR ; Jump to Sub Routine that outputs ASCII CR followed by a line feed LDX #Credits1 ; Load X w/ location of string JSR Output_disp_text ; Jump to Sub Routine that outputs all ASCII starting at X and ending when ASCII CR LDX #Credits2 ; Load X w/ location of string JSR Output_disp_text ; Jump to Sub Routine that outputs all ASCII starting at X and ending when ASCII CR JSR Output_disp_CR ; Jump to Sub Routine that outputs ASCII CR followed by a line feed JSR Pause_return ; Jump to Sub Routine that pauses until user presses enter key.. CR PULX ; Pull X value stored in stack to X, restores data stored in X before subroutine call RTS ; Return to Subroutine which called this Professor: Pamela Hoffman Page 42 of 81 Colorado Technical University
  • 43. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 * Displays Final Output Display_exit_world PSHX ; Push X onto stack, prevents loss of data stored in X during subroutine use LDX #Exit_World1 ; Load X w/ location of string JSR LCD_write_top ; Display 16 Character string at loc X on top LCD LDX #Exit_World2 ; Load X w/ location of string JSR LCD_write_bottom ; Display 16 Character string at loc X on bottom LCD JSR Output_disp_CR ; Jump to Sub Routine that outputs ASCII CR followed by a line feed LDX #Exit_World1 ; Load X w/ location of string JSR Output_disp_text ; Jump to Sub Routine that outputs all ASCII starting at X and ending when ASCII CR LDX #Exit_World2 ; Load X w/ location of string JSR Output_disp_text ; Jump to Sub Routine that outputs all ASCII starting at X and ending when ASCII CR JSR Output_disp_CR ; Jump to Sub Routine that outputs ASCII CR followed by a line feed JSR Pause_return ; Jump to Sub Routine that pauses until user presses enter key.. CR PULX ; Pull X value stored in stack to X, restores data stored in X before subroutine call RTS ; Return to Subroutine which called this * Loop to get & math numbers.. Add_numbers PSHX ; Push X onto stack, prevents loss of data stored in X during subroutine use PSHY ; Push Y onto stack, prevents loss of data stored in Y during subroutine use PSHA ; Push A onto stack, prevents loss of data stored in A during subroutine use PSHB ; Push B onto stack, prevents loss of data stored in B during subroutine use Add_nmbrs_loop JSR Beep_once ; Beep LDX #MathA_1 ; Load X w/ location of string JSR LCD_write_top ; Display 16 Character string at loc X on top LCD LDX #MathA_2 ; Load X w/ location of string Professor: Pamela Hoffman Page 43 of 81 Colorado Technical University
  • 44. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 JSR LCD_write_bottom ; Display 16 Character string at loc X on bottom LCD LDX #MathA_1 ; Load X w/ location of string JSR Output_disp_text ; Jump to Sub Routine that outputs all ASCII starting at X and ending when ASCII CR LDX #MathA_2 ; Load X w/ location of string JSR Output_disp_text ; Jump to Sub Routine that outputs all ASCII starting at X and ending when ASCII CR JSR Output_disp_CR ; Jump to Sub Routine that outputs ASCII CR followed by a line feed JSR Pause_return ; Jump to Sub Routine that pauses until user presses enter key.. CR JSR Beep_once ; Beep LDX #MathB_1 ; Load X w/ location of string JSR LCD_write_top ; Display 16 Character string at loc X on top LCD LDX #MathB_2 ; Load X w/ location of string JSR LCD_write_bottom ; Display 16 Character string at loc X on bottom LCD LDX #MathB_1 ; Load X w/ location of string JSR Output_disp_text ; Jump to Sub Routine that outputs all ASCII starting at X and ending when ASCII CR LDX #MathB_2 ; Load X w/ location of string JSR Output_disp_text ; Jump to Sub Routine that outputs all ASCII starting at X and ending when ASCII CR Get_value1 JSR Output_disp_CR ; Jump to Sub Routine that outputs ASCII CR followed by a line feed JSR Pause_return ; Jump to Sub Routine that pauses until user presses enter key.. CR JSR Beep_once ; Beep LDX #MathC_1 ; Load X w/ location of string JSR LCD_write_top ; Display 16 Character string at loc X on top LCD LDX #MathC_1 ; Load X w/ location of string JSR Output_disp_text ; Jump to Sub Routine that outputs all ASCII starting at X and ending when ASCII CR JSR Output_disp_CR ; Jump to Sub Routine that outputs ASCII CR followed by a line feed JSR Input_get_char ; Jump to Sub Routine that gets a single ASCII character from keyboard and stores in A CMPA #$2F ; Compare A w/ value {ASCII value before ASCII 0} BLS Get_value1 ; Branch if lower or same (Used to ensure only an ASCII 0-4 are entered) Professor: Pamela Hoffman Page 44 of 81 Colorado Technical University
  • 45. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 CMPA #$35 ; Compare A w/ value {ASCII value after ASCII 4} BHS Get_value1 ; Branch if higher or same (Used to ensure only an ASCII 0-4 are entered) SUBA #$30 ; Subtracts $30 from value to convert ASCII (0 to 4) to actual hex value STAA Value1 ; Stores A at location Get_value2 JSR Output_disp_CR ; Jump to Sub Routine that outputs ASCII CR followed by a line feed JSR Pause_return ; Jump to Sub Routine that pauses until user presses enter key.. CR JSR Beep_once ; Beep LDX #MathD_1 ; Load X w/ location of string JSR LCD_write_top ; Display 16 Character string at loc X on bottom LCD LDX #MathD_1 ; Load X w/ location of string JSR Output_disp_text ; Jump to Sub Routine that outputs all ASCII starting at X and ending when ASCII CR JSR Output_disp_CR ; Jump to Sub Routine that outputs ASCII CR followed by a line feed JSR Input_get_char ; Jump to Sub Routine that gets a single ASCII character from keyboard and stores in A CMPA #$2F ; Compare A w/ value {ASCII value before ASCII 0} BLS Get_value2 ; Branch if lower or same (Used to ensure only an ASCII 0-4 are entered) CMPA #$35 ; Compare A w/ value {ASCII value after ASCII 4} BHS Get_value2 ; Branch if higher or same (Used to ensure only an ASCII 0-4 are entered) SUBA #$30 ; Subtracts $30 from value to convert ASCII (0 to 4) to actual hex value STAA value2 ; Stores A at location Add_values LDAA Value1 ; Loads A w/ value at location given ADDA value2 ; Adds A to value at location stores in A ADDA #$30 ; Adds $30 to A -> converts Hex value (0-8) into ASCII (0-8) STAA Result ; Stores A in Result String Result_section JSR Output_disp_CR ; Jump to Sub Routine that outputs ASCII CR followed by a line feed JSR Output_disp_CR ; Jump to Sub Routine that outputs ASCII CR followed by a line feed JSR Beep_once ; Beep LDX #MathE_1 ; Load X w/ location of string Professor: Pamela Hoffman Page 45 of 81 Colorado Technical University
  • 46. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 JSR LCD_write_top ; Display 16 Character string at loc X on top LCD LDX #MathE_1 ; Load X w/ location of string JSR Output_disp_text ; Jump to Sub Routine that outputs all ASCII starting at X and ending when ASCII CR LDX #Result ; Load X w/ location of string JSR LCD_write_bottom ; Display 16 Character string at loc X on bottom LCD LDX #Result ; Load X w/ location of string JSR Output_disp_text ; Jump to Sub Routine that outputs all ASCII starting at X and ending when ASCII CR JSR Output_disp_CR ; Jump to Sub Routine that outputs ASCII CR followed by a line feed JSR Pause_return ; Jump to Sub Routine that pauses until user presses enter key.. CR JSR Beep_once ; Beep Close_add PULB ; Pull B value stored in stack to B, restores data stored in B before subroutine call PULA ; Pull A value stored in stack to A, restores data stored in A before subroutine call PULY ; Pull Y value stored in stack to Y, restores data stored in Y before subroutine call PULX ; Pull X value stored in stack to X, restores data stored in X before subroutine call RTS ; Return to Subroutine which called this * Loop to get & store name.. Get_name PSHX ; Push X onto stack, prevents loss of data stored in X during subroutine use PSHY ; Push Y onto stack, prevents loss of data stored in Y during subroutine use PSHA ; Push A onto stack, prevents loss of data stored in A during subroutine use LDX #Question_Name3 ; Load X w/ location of string JSR LCD_write_top ; Display 16 Character string at loc X on top LCD LDX #Question_Name3 ; Load X w/ location of string JSR Output_disp_text ; Jump to Sub Routine that outputs all ASCII starting at X and ending when ASCII CR JSR Output_disp_CR ; Jump to Sub Routine that outputs ASCII CR followed by a line feed JSR Output_disp_CR ; Jump to Sub Routine that outputs ASCII CR followed by a line feed Professor: Pamela Hoffman Page 46 of 81 Colorado Technical University
  • 47. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 LDX #Username ; Load X w/ location of string LDY #0 ; Load Y w/ location of string Get_name_loop CPY #15 ; Compares Y w/ value 15 {Prevents user from inputing too many strings} BEQ Close_Get_name ; Braches if Equal to location outside of loop JSR Input_get_char ; Jump to Sub Routine that gets a single ASCII character from keyboard and stores in A CMPA #CR ; Compare A w/ ASCII CR BEQ Close_Get_name ; Braches if Equal to location outside of loop CMPA #$1F ; Compare A w/ illegal character (Not 0-9, or A-Z, or a-z) BLS Get_name_loop ; Branch Lower or Same.. loops for new character if illegal encountered CMPA #$7F ; Compare A w/ illegal character (Not 0-9, or A-Z, or a-z) BHS Get_name_loop ; Branch Higher or Same.. loops for new character if illegal encountered STAA 0,X ; Store A at location in X INY ; Increment Y {Used to count # of characters} INX ; Increment X BRA Get_name_loop ; Branch Close_Get_name PULA ; Pull A value stored in stack to A, restores data stored in A before subroutine call PULY ; Pull Y value stored in stack to Y, restores data stored in Y before subroutine call PULX ; Pull X value stored in stack to X, restores data stored in X before subroutine call RTS ; Return to Subroutine which called this * ------------------------ * Start Main_func program * ------------------------ Main_func JSR LCD_init ; Initialize LCD JSR Clear_LEDs ; Clear LEDs JSR Disp_LCD_clear ; Clear LCDs JSR Disp_welcome ; Jump to Subroutine to displays welcome Professor: Pamela Hoffman Page 47 of 81 Colorado Technical University
  • 48. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 JSR Flash_LEDs_osc ; Jump to Subroutine to flash leds in a pulse pattern JSR Disp_q_name ; Jump to Subroutine to display question on LCD JSR Get_name ; Jump to Subroutine to get users name JSR Display_name ; Jump to Subroutine to display users name JSR Display_press_btn ; Jump to Subroutine to display statement on LCD JSR Check_buttons ; Jump to Subroutine to check buttons and do something JSR Display_credits ; Jump to Subroutine to display credits JSR Display_exit_world ; Jump to Subroutine to display exit world RTS ; Return to Subroutine which called this Note: LAB Output: Because most of the program uses the LCDs and LEDs, it would be pointless and disappointing to be limited to the output I could capture using terminal screenshots. Therefore, please copy/paste/assemble/load/ and run the code above if you wish to see the program in action. You can also use the trace “t” command to trace the changes to the PC, SP, and registers, although be warned (The trace program will lose functionality as soon as it enters the terminal I/O and Buffalo Monitor I/O subroutines. Remember you can also log terminal output to file! I used this trick with preceding loabs. RE: Optimizing Code: I noticed a few areas where I could have removed some compare instructions since the CCR was already set, I also noticed I could have used the ROLA and RORA instructions in a loop for the racetrack module which would have shortened the LED modules a bit. Professor: Pamela Hoffman Page 48 of 81 Colorado Technical University
  • 49. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 Professor: Pamela Hoffman Page 49 of 81 Colorado Technical University
  • 50. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 Professor: Pamela Hoffman Page 50 of 81 Colorado Technical University
  • 51. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 Professor: Pamela Hoffman Page 51 of 81 Colorado Technical University
  • 52. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 Professor: Pamela Hoffman Page 52 of 81 Colorado Technical University
  • 53. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 Professor: Pamela Hoffman Page 53 of 81 Colorado Technical University
  • 54. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 Professor: Pamela Hoffman Page 54 of 81 Colorado Technical University
  • 55. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 Professor: Pamela Hoffman Page 55 of 81 Colorado Technical University
  • 56. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 Professor: Pamela Hoffman Page 56 of 81 Colorado Technical University
  • 57. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 Professor: Pamela Hoffman Page 57 of 81 Colorado Technical University
  • 58. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 Professor: Pamela Hoffman Page 58 of 81 Colorado Technical University
  • 59. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 Professor: Pamela Hoffman Page 59 of 81 Colorado Technical University
  • 60. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 Professor: Pamela Hoffman Page 60 of 81 Colorado Technical University
  • 61. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 Professor: Pamela Hoffman Page 61 of 81 Colorado Technical University
  • 62. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 Professor: Pamela Hoffman Page 62 of 81 Colorado Technical University
  • 63. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 Professor: Pamela Hoffman Page 63 of 81 Colorado Technical University
  • 64. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 Professor: Pamela Hoffman Page 64 of 81 Colorado Technical University
  • 65. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 Professor: Pamela Hoffman Page 65 of 81 Colorado Technical University
  • 66. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 Professor: Pamela Hoffman Page 66 of 81 Colorado Technical University
  • 67. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 Professor: Pamela Hoffman Page 67 of 81 Colorado Technical University
  • 68. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 Professor: Pamela Hoffman Page 68 of 81 Colorado Technical University
  • 69. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 Professor: Pamela Hoffman Page 69 of 81 Colorado Technical University
  • 70. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 Professor: Pamela Hoffman Page 70 of 81 Colorado Technical University
  • 71. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 Professor: Pamela Hoffman Page 71 of 81 Colorado Technical University
  • 72. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 Professor: Pamela Hoffman Page 72 of 81 Colorado Technical University
  • 73. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 Professor: Pamela Hoffman Page 73 of 81 Colorado Technical University
  • 74. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 Professor: Pamela Hoffman Page 74 of 81 Colorado Technical University
  • 75. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 Professor: Pamela Hoffman Page 75 of 81 Colorado Technical University
  • 76. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 Professor: Pamela Hoffman Page 76 of 81 Colorado Technical University
  • 77. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 Professor: Pamela Hoffman Page 77 of 81 Colorado Technical University
  • 78. EE312 Embedded Microcontrollers TUE / THU 9:00AM Final Lab Spring 2009 Professor: Pamela Hoffman Page 78 of 81 Colorado Technical University