* COMPILER CONSTANTS * ***********************************************************************************

Size: px
Start display at page:

Download "* COMPILER CONSTANTS * ***********************************************************************************"

Transcription

1 Copyright 2005 by Aaron Enes Adam Cardi Matt Wagner ASSEMBLY LANGUAGE CODE FOR THE TEETERING BUFFALO OR THE SELF BALANCING ROBOT OR THE REMOTE CONTROL SEGWAY COMPILER CONSTANTS PROG EQU $E000 CONST EQU $1040 STACK EQU $0047 TCNT EQU $100E TOC5 EQU $101E TOC3 EQU $101A PORTA EQU $1000 PORTD EQU $1008 DDRD EQU $1009 TIC3 EQU $1014 TCTL1 EQU $1020 TCTL2 EQU $1021 TMSK1 EQU $1022 TFLG1 EQU $1023 TMSK2 EQU $1024 TFLG2 EQU $1025 PACTL EQU $1026 ADCTL EQU $1030 OPTION EQU $1039 LED_ON EQU $80 LED_OFF EQU $00 SWITCH EQU $02 OC5_VEC EQU $FFE0 OC3_VEC EQU $FFE4 IC3_VEC EQU $FFEA RST_VEC EQU $FFFE OC5_ISR EQU $F000 OC3_ISR EQU $F100 IC3_ISR EQU $F200 ACCEL EQU $1031 ACCEL_F EQU $1034 GYRO EQU $1032 GYRO_F EQU $1033 PROGRAM SPACE SPACE FOR DYNAMIC PROGRAM VARIABLES START OF USER STACK HC11 REGISTERS USED TO TURN AND OFF AN INDICATOR LED FOR DEBUGGINS USED TO MONITOR RESET SWITCH THESE ARE THE VECTOR LOCATIONS FOR THE OC5,3 INTERUPTS SET THESE ACCORDING TO ROMON ENABLED/DISABLED INTERRUPT SERVICE ROUTINE (ISR) FOR OC5 ISR FOR OC3 ISR FOR IC3 EQUATES FOR ACCEL AND GYRO INPUTS. ACCEL TRIGGERS INT REGION _F DESIGNATES THE MORE FILTERED INPUTS DIR EQU $1008 LOCATION OF OUTPUT PORT USED FOR SETTING MOTOR DIRECTIONS REV_L EQU % USED TO CLEAR DIR BITS TO CHANGE DIRECTION REV_R EQU % FORW_L EQU % USED TO SET DIR BITS TO CHANGE DIRECTION FORW_R EQU % HERE ARE THE COMPILER EQUATES USED FOR CONSTANTS THAT AFFECT BALANCING AND PROGRAM OPERATION PERIOD EQU $05FA PERIOD OF PWM SIGNAL IN CLOCK CYCLES. (SET FOR 1KHZ) AINT_NULL EQU $3000 NULL VALUE OF ACCELEROMETER INTEGRATION THRESH EQU $FF 06 USED TO IMPLEMENT THE 2 GAIN REGIONS

2 RSET_ERROR EQU $09 THRESHOLD FOR INTEGRATION AND RAMPUP/DOWN ACC_GAIN EQU $0006 GAIN FOR ACCEL GYR_GAIN EQU $0002 GAIN FOR GYRO GYR_FGAIN EQU $0005 GAIN FOR GYRO_F AINTGAIN EQU $0009 USING FDIV, SO INCREASE TO DECREASE EFFECTIVE GAIN DUTY_MAX EQU $F0 DUTY_MIN EQU $05 MAXIMUM AND MINIMUM ALLOWABLE DUTY CYCLES OUTSIDE THIS RANGE THE OC INTERRUPTS OCCUR TOO OFTEN TURN_G EQU $0012 TURNING GAIN, USING FDIV DELTA EQU $08 INT_MAX EQU $3300 INT_MIN EQU $2D00 PWMTH EQU $0007 STEP SIZE FOR RAMPING UP AND RAMPING DOWN THE ACCEL INT MAX AND MIN ALLOWED FOR ACCEL INT MAX ALLOWED CHANGE OF DUTY CYCLE. USED FOR DIGITAL SMOOTHING STEER_NULL EQU $0BF2 VALUE OF T.I.C. WHEN X-MITTER INPUT IS NULL P_TIMEMIN EQU $0830 MAX AND MIN ALLOWED VALUES FOR T.I.C. P_TIMEMAX EQU $0F50 USED TO FILTER OUT ERRONEOUS STEERING SIGNAL INPUTS MEMORY SPACE FOR DYNAMIC PROGRAM VARIABLES ORG CONST OC3_HIGH RMB 2 OC3_LOW RMB 2 OC5_HIGH RMB 2 OC5_LOW RMB 2 DUTY1 RMB 1 DUTY2 RMB 1 STORES THE HIGH AND LOW TIMES FOR THE DUTY CYCLE CALCULATIONS DUTY CYCLE FOR EACH MOTOR FLOATING POINT VARIABLES MANT1 RMB 2 OP1 EXP1 RMB 1 MANT2 RMB 2 OP2 EXP2 RMB 1 TEMP1 RMB 2 used by routines TEMP2 RMB 2 Y RMB 2 substitute Y register QUOT RMB 2 used by FDIV SENSOR VARIABLES FOR CALCULATIONS GYRO_VAL RMB 2 ACCEL_VAL RMB 2 GYRO_NULL RMB 2 ACCEL_NULL RMB 2 GYRO_FNULL RMB 2 A_GAIN RMB 2 G_GAIN RMB 2 GNULL_CALC RMB 2 ANULL_CALC RMB 2 PWM RMB 2 PWM_L RMB 2 PWM_R RMB 2 PREVDTY1 RMB 1 PREVDTY2 RMB 1 PWM1 RMB 2 PWM2 RMB 2 MANTISSA RMB 2

3 EXPONENT RMB 1 MANT_L RMB 2 MANT_R RMB 2 ABS_ACCEL RMB 1 ABS_GYRO RMB 1 ACC_INT RMB 2 1 BYTE DEVIATION OF ACCEL AND GYRO FROM NULL NUMERICAL INTEGRATION OF ACCEL GINT_TEMP RMB 2 GINTN_TEMP RMB 2 AINT_TEMP RMB 2 AINTN_TEMP RMB 2 GYRO_TEMP RMB 2 GYRON_TEMP RMB 2 MODE RMB 1 VARIABLE TO TEST STATE OF STEERING PWM INPUT T_0 RMB 2 TIME OF RISING EDGE OF STEERING INPUT T_1 RMB 2 TIME OF FALLING EDGE OF STEERING INPUT P_TIME RMB 2 STORES PULSE LENGTH OF STEERING INPUT END CONFIGURE EEPROM VECTORS CONFIGURE OC5 ORG #OC5_VEC FDB $F000 END CONFIGURE OC3 ORG #OC3_VEC FDB $F100 END CONFIGURE IC3 ORG #IC3_VEC FDB $F200 END CONFIGURE RESET ORG #RST_VEC FDB $E000 END PROGRAM SPACE ORG PROG CONFIGURATION SETTINGS CONFIGURE A/D REGISTER LDS #STACK LOAD STACK INTO RAM LDAA #$90 ADPU = 1; DLY = 1 STAA OPTION LDAA #$30 SCAN = 1; MULT = 1 STAA ADCTL LDX #$FFFF AD_SET NOP DEX CPX #$00 BNE AD_SET DELAY BEFORE LOADING FIRST VALUE TO ALLOW ADC TO SETTLE CONFIGURE LED

4 LDAA #LED_ON STAA PACTL CONFIGURE MASKS AND FLAGS FOR OC5 AND OC3 LDAA #% CONFIGURES OC5/3 TO GO HIGH ON SUCCESSFUL COMAPRE STAA TCTL1 LDAA #% STAA TCTL2 LDAA #% STAA TFLG1 STAA TMSK1 LDD #$0000 STD TOC3 STD TOC5 SETS IC3 ON PA1 TO CAPTURE ON RISING EDGE CONFIGURE MASKS AND FLAGS FLAG OC5/3 MASK OC5/3 LOAD INITIAL COMPARE TO OC3 AND OC5 CONFIGURE DDRD LDAA #% DIRECTION FOR PWM CONTROLLER. PD3: DIR1, PD4: DIR2 STAA DDRD SET GAIN FOR ACCEL AND GYRO LDD #ACC_GAIN STD A_GAIN LDD #GYR_GAIN STD G_GAIN LDD #GINTGAIN STD GINT_GAIN MISC. SETUP STEPS LDD #AINT_NULL STD ACC_INT LDAA #$FF STAA PREVDTY1 STAA PREVDTY2 INITIALIZE ACCEL INTEGRAL INITIALIZE PREVIOUS DUTY CYCLES LDD #$3000 STD PWM1 LDAA #$00 STAA MODE IF MODE=00, NEXT IC WILL TRIGGER ON RISING CONFIGURE OUTSIDE OF MAIN LOOP LDD #STEER_NULL STD P_TIME CLI JMP RESET RESET NULL GYRO/ACCEL VALUES RESET LDAA #LED_ON STAA PORTA LDD #AINT_NULL STD ACC_INT CLRA LDAB ACCEL NO WEIGHT: 78, WEIGHT: 6E STD ACCEL_NULL CLRA LDAB GYRO STD GYRO_NULL LDAB GYRO_F STD GYRO_FNULL

5 LDAB ACCEL_F #$95 STD ANULL_CALC LDAA #LED_OFF STAA PORTA MAIN PROGRAM LOOP LOOP NOP LDAA PORTA BITA #SWITCH BNE RESET CHECK IF RESET PRESSED CALC DEVIATIONS FROM NULL LDAB ACCEL_NULL+1 CMPB ACCEL BMI SUBT_2 SUBB ACCEL STAB ABS_ACCEL BRA NEXT_ SUBT_2 LDAB ACCEL SUBB ACCEL_NULL+1 STAB ABS_ACCEL NEXT_ LDAB GYRO_NULL+1 CMPB GYRO BMI SUBT_1 SUBB GYRO STAB ABS_GYRO BRA DONE_ABS SUBT_1 LDAB GYRO SUBB GYRO_NULL+1 STAB ABS_GYRO DONE_ABS NOP LOAD CURRENT A/D VALUES CLRA LDAB ABS_GYRO CMPB #THRESH BMI SLOWVAL STAY_FAST CLRA LDAB ACCEL_F STD ACCEL_VAL LDAB GYRO STD GYRO_VAL LDD #GYR_GAIN STD G_GAIN LDD #GINTGAIN STD GINT_GAIN LDD #ACC_GAIN STD A_GAIN LDD GYRO_NULL STD GNULL_CALC

6 SLOWVAL CLRA BRA FASTVAL LDAB ACCEL_F STD ACCEL_VAL LDAB GYRO_F STD GYRO_VAL LDD #GYR_FGAIN STD G_GAIN LDD #GINTGAIN STD GINT_GAIN LDD #ACC_GAIN STD A_GAIN LDD GYRO_FNULL STD GNULL_CALC FASTVAL NOP INTEGRATE ACCEL, RESET DRIFT WHEN ALLOWED LDAA ABS_ACCEL ONLY INTEGRATE WHEN OUTSIDE OF THRESHOLD CMPA #RSET_ERROR BMI RAMP LDAA #LED_OFF STAA PORTA BRA INTEGRATE RAMP LDAA #LED_ON STAA PORTA LDD #AINT_NULL CPD ACC_INT BMI RAMPDOWN LDD ACC_INT ADDD #DELTA STD ACC_INT CPD #$2FE0 BMI MINMAX LDD #AINT_NULL STD ACC_INT BRA MINMAX THE RAMPING PROVIDES A WAY OF DAMPING THE INTEGRAL TERM RAMPDOWN LDD ACC_INT SUBD #DELTA STD ACC_INT CPD #$3020 BPL MINMAX LDD #AINT_NULL STD ACC_INT BRA MINMAX INTEGRATE CLRA LDAB ACCEL ADDD ACC_INT SUBD ACCEL_NULL STD ACC_INT MINMAX LDD ACC_INT CPD #INT_MAX BMI OKHIGH LDD #INT_MAX STD ACC_INT PERFORM INTEGRATION TEST FOR MIN/ MAX VALS

7 OKHIGH LDD ACC_INT CPD #INT_MIN BPL NO_INT LDD #INT_MIN STD ACC_INT NO_INT NOP END OF INTEGRATION COMPUTE PWM WITH (ACCEL-ACCEL_NULL)A_GAIN + (GYRO-GYRO_NULL)GYRO_GAIN LDD GYRO_VAL JSR INTFLOAT1 GYRO () GYRO_GAIN, STORE IN GYRO_TEMP LDD G_GAIN JSR FMUL JSR FLOATINT1 STD GYRO_TEMP LDD GNULL_CALC JSR INTFLOAT1 GYRO_NULL () GYRO_GAIN, STORE IN GYRON_TEMP LDD G_GAIN JSR FMUL JSR FLOATINT1 STD GYRON_TEMP LDD #AINT_NULL JSR INTFLOAT1 (ACCINTNULL-ACCINT)/ACCINTGAIN LDD #AINTGAIN JSR FDIV JSR FLOATINT1 STD AINTN_TEMP LDD ACC_INT JSR INTFLOAT1 LDD #AINTGAIN JSR FDIV JSR FLOATINT1 STD AINT_TEMP LDD ANULL_CALC JSR INTFLOAT1 (ACCEL-ACCEL_NULL)(A_GAIN) LDD ACCEL_VAL JSR FSUB LDD A_GAIN JSR FMUL LDD GYRO_TEMP NOW ADD GYRO AND INT TEMP TERMS

8 JSR FADD LDD GYRON_TEMP JSR FSUB LDD AINT_TEMP JSR FSUB LDD AINTN_TEMP JSR FADD JMP CONT59 SMOOTHING OF PWM SIGNAL TO PREVENT JITTERING LDD MANT1 STD MANTISSA LDD PWM1 STD PWM2 LDD #AINT_NULL JSR FADD JSR FLOATINT1 STD PWM STD PWM1 CPD PWM2 BEQ CONT57 BLS DECREASE LDD PWM1 SUBD PWM2 CPD #PWMTH BMI CONT58 BEQ CONT58 LDD PWM2 ADDD #PWMTH STD PWM1 BRA CONT57 DECREASE LDD PWM2 SUBD PWM1 CPD #PWMTH BMI CONT58 BEQ CONT58 LDD PWM2 SUBD #PWMTH STD PWM1 CONT57 LDD PWM1 JSR INTFLOAT1 LDD #$3000 JSR FSUB CONT58 LDD PWM JSR INTFLOAT1 LDD #$3000 JSR FSUB END SMOOTHING

9 MODIFICATION OF PWM FOR STEERING CONT59 NOP LDD MANT1 STD MANTISSA LDAA EXP1 STAA EXPONENT LEFT MOTOR LDD P_TIME JSR INTFLOAT1 LDD #STEER_NULL JSR FSUB LDD #TURN_G JSR FDIV LDD MANTISSA STD MANT2 LDD EXPONENT STD EXP2 JSR FADD LDD MANT1 STD MANT_L JSR FLOATINT1 STD PWM_L LDD P_TIME JSR INTFLOAT1 LDD #STEER_NULL RIGHT MOTOR JSR FSUB LDD #TURN_G JSR FDIV LDD MANTISSA STD MANT2 LDD EXPONENT STD EXP2 JSR FSUB LDD MANT1 STD MANT_R JSR FLOATINT1 STD PWM_R SET DIRECTION PINS BY CHECKING THE SIGN OF THE PWM CALCULATIONS ST_RDIR LDD MANT_L BITA #% BEQ POSI_L LDX #DIR BCLR $0,X #REV_L BRA UME

10 POSI_L NOP LDAA DIR ORAA #FORW_L STAA DIR UME LDD MANT_R BITA #% BEQ POSI_R LDX #DIR BCLR $0,X #REV_R BRA CONT867 POSI_R NOP LDAA DIR ORAA #FORW_R STAA DIR CONT867 NOP CHECK FOR FLOATING POINT OVERFLOW ABOVE FF LEFT MOTOR LDD PWM_L CMPA #$00 BEQ OVER_OK LDAB #DUTY_MAX STAB DUTY1 CHECK FOR OVERFLOW INTO ACC. A LOAD MAX DUTY IF OVERFLOW DETECTED OVER_OK STAB DUTY1 RIGHT MOTOR LDD PWM_R CMPA #$00 BEQ OVER_ROK LDAB #DUTY_MAX STAB DUTY2 CHECK FOR OVERFLOW INTO ACC. A LOAD MAX DUTY IF OVERFLOW DETECTED OVER_ROK STAB DUTY2 CHECK IF DUTY IS WITHIN DUTY_MIN AND DUTY_MAX LDAA DUTY1 CMPA #DUTY_MIN BLS D1_LESS CMPA #DUTY_MAX BHS D1_MORE BRA D1_OK D1_LESS LDAA #DUTY_MIN STAA DUTY1 BRA D1_OK D1_MORE LDAA #DUTY_MAX STAA DUTY1 D1_OK LDAA DUTY2 CMPA #DUTY_MIN BLS D2_LESS CMPA #DUTY_MAX BHS D2_MORE BRA D2_OK D2_LESS LDAA #DUTY_MIN STAA DUTY2 BRA D2_OK D2_MORE LDAA #DUTY_MAX

11 D2_OK NOP STAA DUTY2 CONVERT DUTY CYCLE TO HIGH/LOW TIME MOTOR 1 / OC5 LDAA DUTY1 LOAD DUTY CYCLE FROM 00(MIN) TO FF(MAX) LDB #$06 SCALING FACTOR FOR 1hZ CYCLE TIME MUL HIGH TIME IS IN D STD OC5_HIGH STORE HIGH TIME LDD #PERIOD PERIOD OF PWM SIGNAL SUBD OC5_HIGH STD OC5_LOW STORE LOW TIME MOTOR 2 / OC3 LDAA DUTY2 LOAD DUTY CYCLE FROM 00(MIN) TO FF(MAX) LDB #$06 MUL STD OC3_HIGH STORE HIGH TIME LDD #PERIOD SUBD OC3_HIGH STD OC3_LOW SCALING FACTOR FOR 1hZ CYCLE TIME HIGH TIME IS IN D STORE LOW TIME JMP LOOP RETURN TO TOP OF PROGRAM FLOATING POINT PACKAGE BELOW INTERUPT SERVICE ROUTINES AT BOTTOM OF CODE Floating Point Package 22/1/86 written by R.Soja, Motorola; modified for MC6801 by Tom Rogers All floating point routines use two, 3-byte operands located in RAM at OP1,OP2 Each is organised as: 7 bit exponent + 1 sign bit (2's complement) 15 bit mantissa + 1 sign bit (15 bit positive notation) Sign bit is always is always MSBit Routines implemented: 1. Addition MAD (FADD) OP1+OP2 2. Subtraction MSB (FSUB) OP1-OP2 3. Division MDV (FDIV) OP1/OP2 4. Multiplication MML (FMUL) OP1OP2 On exit from routine, OP1 contains result, OP2 is destroyed Two conversion routines are included: FLOATINT1 converts FP number in OP1 to unsigned integer in ACCD INTFLOAT1 converts unsigned integer in ACCD to FP number in OP1 An integer rounding subroutine (ROUND) is also included. INTFLOAT2 PUTS ACCD INTO OP2 FLOATINT2 PUTS OP2 INTO ACCD Note that NO ORG staements are included, as this package is intended to be appended as a subroutine package to a main calling program. RAM variables: FP routines: MAD EQU OP1 + OP2 => OP1

12 FADD EQU BSR ALIGN BVS FADDEX LDAA MANT1 ANDA #$80 JSR XGDX LDAA MANT1 EORA MANT2 BMI SUBMANT BSR GETABS ADDD MANT2 BPL FADD1 INC EXP1 BVC FADD2 DEC EXP1 LDD #$7FFF BRA FADD1 FADD2 LSRD FADD1 STX MANT2 STD MANT1 JSR NORM FADDEX SUBMANT BSR GETABS SUBD MANT2 BSR CONVFP BRA FADD1 GETABS LDAA MANT2 ANDA #$7F STAA MANT2 LDD MANT1 ANDA #$7F If exponent difference too great, return. Put sign bit of mantissa 1 in X reg. If signs are same then add positive parts of mantissas. if MSBit of result set, then result has overflowed, so increment exponent, while limiting value to upper bound. Save sign bit and result, prior to normalising it. Return to calling program segment. If signs are different, then subtract positive parts of mantissas. Change 2s compl result to floating point format and store result (X contains corrected sign bit) Clear sign bits in MANT2 and MANT1 in ACCD MSB EQU OP1 - OP2 => OP1 FSUB EQU LDAA MANT2 ADDA #$80 Negate sign of mantissa 2 STAA MANT2 BRA FADD ALIGN CLRA LDAB EXP1 SUBB EXP2 BPL POS BVS ALIGNEX NEGB JSR XGDX LDD MANT1 BSR ALIGN1 STD MANT1 LDAA EXP2 and perform addition If EXP1<EXP2 then If exponent difference within range, get absolute value of difference into X. This will be the # of bits to shift. Update result exponent STAA EXP1 POS BVC POS1 If exp diff too great then LDD MANT2 STD MANT1 LDAA EXP2 STAA EXP1 SEV copy OP2 to OP1 restore flag for calling routine and return. POS1 JSR XGDX Move number of bits to shift into X reg CPX #0 If no shift required BEQ ALIGNEX then return LDD MANT2 BSR ALIGN1 else align mantissa 2 with mantissa 1 STD MANT2 ALIGNEX ALIGN1 BMI ALIGN3 ALIGN2 LSRD (Result exponent stays the same). If sign bit is clear then align ACCD

13 DEX BNE ALIGN2 ALIGN3 ANDA #$7F BSR ALIGN2 ORAA #$80 CONVFP EQU JSR XGDX STX MANT2 ADDA MANT2 ANDA #$80 JSR XGDX TSTA BPL CONVFPEX COMA NEGB BCS CONVFPEX else remove sign bit before aligning. Restore sign bit and return Put result in X, sign bit in ACCD Store 2s compl result. Correct sign bit and mask it. Restore result to ACCD, corrected sign to X Update CC reg Only convert negative numbers 1s complement hi byte Convert lo byte to 2s complement. INCA Convert hi byte to 2s complement if ACCB=0 CONVFPEX NORM EQU!ACCD = unsigned value to be normalised.!mant2= sign bit of value. BEQ NORMEX Zero cannot be normalised! NORM1 DEC EXP1 BVS NORM2 Terminate on underflow (i.e. EXP1 < $80) LSLD BPL NORM1 LSRD NORM2 INC EXP1 NORMEX ORAA MANT2 NORM3 CMPA #$80 BNE NORMEX1 CMPB #$00 BNE NORMEX1 CLRA NORMEX1 STD MANT1 Wait until MSB set Clear sign bit and adjust exponent Update sign bit and remove sign from -0 mantissa. Store normalised result. MDV EQU OP1 / OP2 => OP1 FDIV EQU LDD MANT2 BEQ MAXRES Trap divide by 0 LDAA MANT1 EORA MANT2 BMI FDIV1 CLR Y CLR Y+1 BRA FDIV2 FDIV1 LDX #$8000 STX Y FDIV2 LDAB EXP1 SUBB EXP2 BVC FDIV3 If signs are same then result sign is positive ( Y has result sign.) else result sign is negative. If V bit set then its an under/overflow, so STAA MANT1! update result sign BCC MINRES! If C bit clear then force result to min limit BRA MAXRES! else force result to max limit, retaining sign FDIV3 STAB EXP1 Save result exponent LDX #16 Initialize shift counter JSR GETABS +ive part of MANT1 in D, +ive part of MANT2 in it COMPARE SUBD MANT2 Dividend minus divisor BCS RESTORE Borrow so need to restore dividend SEC else no borrow so set carry BRA SHIFT and go shift into quotient. RESTORE ADDD MANT2 Add divisor back to dividend CLC prep to shift a 0 SHIFT ROL QUOT+1 Shift 0 or 1 into quotient ROL QUOT LSLD Shift dividend left DEX All division done?

14 BNE COMPARE not yet LDD QUOT else done so get quotient BPL FDIV4 If quot sign bit already clear, wrap up LSRD else open up sign bit INC EXP1 adjusting exponent. FDIV4 ADDD Y Update sign bit BRA NORM3 Ck. for -0, store result and return MAXRES STAA TEMP1 Store A. LDAA MANT1 Maximise MSbyte of mantissa, retaining sign. ORAA #$7F STAA MANT1 LDAA TEMP1 Restore A. LDD #$FF7F Maximise LSbyte of mantissa, and exponent. STD MANT1+1 MINRES CLRA Result = 0 CLRB STD MANT1 CLR EXP1 MML EQU OP1 OP2 => OP1 FMUL EQU LDAB EXP1 First, add exponents. ADDB EXP2 BVC FMUL1 If V bit is set then its an under/overflow, so STAA MANT1! update result sign BCS MINRES! If C bit set then force result to min limit BRA MAXRES! else force result to max limit, retaining sign FMUL1 STAB EXP1 Store result exponent. LDAA MANT1 Evaluate result sign, and EORA MANT2 put it in X reg JSR XGDX STAA TEMP1 Store A. LDAA MANT1 Make both operands positive ANDA #$7F STAA MANT1 LDAA MANT2 ANDA #$7F STAA MANT2 LDAA TEMP1 Restore A. BSR CONVFPI Convert MANT1,MANT2 to unsigned integer format!and return with result sign + MANT1 in Y reg LDAA MANT1 multiply MSbytes of mantissas. LDAB MANT2 MUL JSR XGDX Save 1st partial result in X LDAA MANT1+1 Cross multiply. LDAB MANT2 MUL ADCA #0 Round up and TAB CLRA restore weighting of partial result (in ACCD) STX MANT1 Add 1st and 2nd partial results ADDD MANT1 JSR XGDX Store updated partial result. STD TEMP1 Store D. LDD Y Restore MANT1 STD MANT1 LDD TEMP1 Restore D. LDAA MANT1 Cross multiply again. LDAB MANT2+1 MUL ADCA #0 Round up again. TAB CLRA Correctly weighted 3rd partial result now in ACCD STX MANT1 so add it to stored partial result. ADDD MANT1 BSR CONVIFP Convert integer in ACCD to FP format,and store.

15 Multiplication of LS bytes is unnecessary, as the result will always overflow if both non-zero. Return to calling program. CONVFPI EQU Enter with +ive MANT1,MANT2: result sign in X reg LSL MANT1+1 De-normalise both operands. ROL MANT1 LSL MANT2+1 ROL MANT2 LDD MANT1 CPX #0 Add result sign bit to ACCD BPL FPI1 ORAB #1 FPI1 JSR XGDY and save result sign+operand 1 in Y. CONVIFP EQU LDX #0 STX MANT2 STD MANT1 Temporarily store result. JSR XGDY Move result sign bit LSRD ROR MANT2 to MANT2 before LDD MANT1 LSRD JSR NORM normalising result mantissa. IFP2 Return with result stored in MANT1. FLOATINT1 EQU CLRB LDAA EXP1 If exponent <= 0 BGT FLTINT1 then clear ACCD and return. CLRA FLTINT1 CLRA else LSL MANT1+1 adjust mantissa, destroying sign bit ROL MANT1 FLTINT2 LSL MANT1+1 then move mantissa into ACCD ROL MANT1 ROLB ROLA DEC EXP1 BNE FLTINT2 until exponent = 0 ROUND TST MANT1 Call IMMEDIATELY after FLOATINT if to be used. BPL ROUNDEX MANT1 has "leftover precision." ASL MANT1 If MSB of MANT1 is set, fraction >=.5 BPL ROUNDEX If next MSB set, fraction >=.75 ADDD #1 so increment D & return ROUNDEX else just return. INTFLOAT1 EQU On entry, unsigned integer in ACCD LDX #0 Initialise result mantissa STX MANT1 CLR EXP1 and exponent. INTFLT1 LSRD Move integer to F.P. mantissa ROR MANT1 ROR MANT1+1 INC EXP1 adjusting exponent with every shift. CMPA #0 BNE INTFLT1 CMPB #0 BNE INTFLT1 When no more bits in ACCD ROR MANT1 clear sign bit as integer was always >=0 ROR MANT1+1 XGDX STD TEMP1 Store D STX TEMP2 and X. LDD TEMP2 Load D with X

16 LDX TEMP1 and X with D. XGDXEX XGDY STD TEMP1 D in TEMP1 LDD Y Move Y STD TEMP2 to TEMP2. LDD TEMP1 Move D/TEMP1 STD Y to Y. LDD TEMP2 Put Y into D. XGDYEX INTFLOAT2 EQU On entry, unsigned integer in ACCD LDX #0 Initialise result mantissa STX MANT2 CLR EXP2 and exponent. INTFLT2 LSRD ROR MANT2 ROR MANT2+1 INC EXP2 CMPA #0 BNE INTFLT2 CMPB #0 FLOATINT2 EQU CLRB Move integer to F.P. mantissa adjusting exponent with every shift. BNE INTFLT2 When no more bits in ACCD ROR MANT2 clear sign bit as integer was always >=0 ROR MANT2+1 LDAA EXP2 If exponent <= 0 BGT FLTINT12 then clear ACCD and return. CLRA FLTINT12 CLRA else LSL MANT2+1 ROL MANT2 FLTINT22 LSL MANT2+1 adjust mantissa, destroying sign bit then move mantissa into ACCD ROL MANT2 ROLB ROLA DEC EXP2 BNE FLTINT22 until exponent = 0 END END OF FLOATING POINT ROUTINES BELOW ARE THE INTERRUPT SERVICE ROUTINES OC5 INTERRUPT SERVICE SUBROUTINE FOR MOTOR 1 ORG OC5_ISR OC5 INTERRUPT SERVICE SUBROUTINE LDAA #% BITA TCTL1 BEQ LOW LDD TCNT ADDD OC5_HIGH STD TOC5 BRA HIGH TEST FOR CURRENT STATE OF PWM (HIGH OR LOW) LOAD CURRENT VAL OF COMPARE, ADD HIGH TIME LOW LDD TCNT LOAD CURRENT VAL OF COMPARE, ADD LOW TIME ADDD OC5_LOW STD TOC5

17 HIGH LDAA TCTL1 EORA #% STAA TCTL1 LDX #TFLG1 BCLR $0,X #% INVERT HIGH/LOW BIT OF OC5 RESET OC5 FLAG RTI END OC3 INTERRUPT SERVICE SUBROUTINE FOR MOTOR 2 ORG OC3_ISR LDAA #% BITA TCTL1 BEQ LOW2 LDD TCNT ADDD OC3_HIGH STD TOC3 BRA HIGH2 LOW2 LDD TCNT ADDD OC3_LOW STD TOC3 HIGH2 LDAA TCTL1 EORA #% STAA TCTL1 LDX #TFLG1 BCLR $0,X #% TEST FOR CURRENT STATE (HIGH OR LOW LOAD CURRENT VAL OF COMPARE, ADD HIGH TIME LOAD CURRENT VAL OF COMPARE, ADD LOW TIME INVERT HIGH/LOW BIT OF OC3 RESET FLAG RTI END IC3 SERVICE ROUTINE. USED TO DECODE PULSE WIDTH FROM RC RECEIVER ORG IC3_ISR LDAA MODE CMPA #$00 BEQ R_EDGE LDD TIC3 SUBD T_0 BPL DONE LDD #$FFFF SUBD T_0 ADDD TIC3 DONE CPD #P_TIMEMIN BPL MAXSTR LDD #STEER_NULL BRA SET MAXSTR CPD #P_TIMEMAX BMI SET LDD #STEER_NULL CHECK STATE OF INPUT SIGNAL BRANCH IF RISING EDGE DO THIS IF FALLING EDGE IF P_TIME < P_TIMEMIN, THEN DONOT CHANGE P_TIME CHECK IF STEERING IS WITHING ALLOWED RANGE SET STD P_TIME LDAA MODE DECA STAA MODE LDAA #% STAA TCTL2 NEXT TIME ISR IS CALLED THE PULSE WILL BE A RISING EDGE. SETS IC3 ON PA1 TO CAPTURE ON RISING EDGE

18 LDX #TFLG1 BCLR $0,X #% CLEAR IC3 FLAG RTI R_EDGE LDD TIC3 STD T_0 LDAA MODE INCA STAA MODE LDAA #% STAA TCTL2 STORE TIME OF INPUT CAPTURE EVENT NEXT TIME ISR IS CALLED THE PULSE WILL BE A FALLING EDGE SETS IC3 ON PA2 TO CAPTURE ON FALLING EDGE LDX #TFLG1 BCLR $0,X #% CLEAR IC3 FLAG RTI END

Table 1: Mnemonics Operations Dictionary. Add Accumulators Add B to Y. Add with carry to B. Add Memory to B. Add 16-bit to D And B with Memory

Table 1: Mnemonics Operations Dictionary. Add Accumulators Add B to Y. Add with carry to B. Add Memory to B. Add 16-bit to D And B with Memory Table 1: Mnemonics s Dictionary ABA ABX ABY ADCA ADCB ADDA ADDB ADDD ANDA ANDB ASL ASLA ASLB ASLD ASR ASRA ASRB BCC BCLR BCS BEQ BGE BGT BHI BHS BITA BITB BLE BLO BLS BLT Add Accumulators Add B to X Add

More information

Programming the Motorola MC68HC11 Microcontroller

Programming the Motorola MC68HC11 Microcontroller Programming the Motorola MC68HC11 Microcontroller COMMON PROGRAM INSTRUCTIONS WITH EXAMPLES aba Add register B to register A Similar commands are abx aby aba add the value in register B to the value in

More information

The Motorola 68HC11 Instruc5on Set

The Motorola 68HC11 Instruc5on Set The Motorola 68HC11 Instruc5on Set Some Defini5ons A, B * accumulators A and B D * double accumulator (A + B) IX, IY * index registers X and Y SP * stack pointer M * some memory loca5on opr * an operand

More information

C SC 230 Computer Architecture and Assembly Language April 2000 Exam Sample Solutions

C SC 230 Computer Architecture and Assembly Language April 2000 Exam Sample Solutions C SC 230 Computer Architecture and Assembly Language April 2000 Exam Sample Solutions 1. (12 marks) Circle the correct answer for each of the following: The 8-bit two's complement representation of -15

More information

Ryerson University Department of Electrical and Computer Engineering ELE 538 Microprocessor Systems Final Examination December 8, 2003

Ryerson University Department of Electrical and Computer Engineering ELE 538 Microprocessor Systems Final Examination December 8, 2003 Ryerson University Department of Electrical and Computer Engineering ELE 538 Microprocessor Systems Final Examination December 8, 23 Name: Student Number: Time limit: 3 hours Section: Examiners: K Clowes,

More information

EE 3170 Microcontroller Applications

EE 3170 Microcontroller Applications Q. 3.9 of HW3 EE 37 Microcontroller Applications (a) (c) (b) (d) Midterm Review: Miller Chapter -3 -The Stuff That Might Be On the Exam D67 (e) (g) (h) CEC23 (i) (f) (j) (k) (l) (m) EE37/CC/Lecture-Review

More information

Lecture 6 Assembly Programming: Branch & Iteration

Lecture 6 Assembly Programming: Branch & Iteration CPE 390: Microprocessor Systems Spring 2018 Lecture 6 Assembly Programming: Branch & Iteration Bryan Ackland Department of Electrical and Computer Engineering Stevens Institute of Technology Hoboken, NJ

More information

EE4390 Microprocessors

EE4390 Microprocessors EE4390 Microprocessors Lesson 6,7 Instruction Set, Branch Instructions, Assembler Directives Revised: Aug 1, 2003 1 68HC12 Instruction Set An instruction set is defined as a set of instructions that a

More information

2) [ 2 marks] Both of the following statements cause the value $0300 to be stored in location $1000, but at different times. Explain the difference.

2) [ 2 marks] Both of the following statements cause the value $0300 to be stored in location $1000, but at different times. Explain the difference. 1) [ 9 marks] Write a sequence of directives for an HCS12 assembly language program that performs all of these tasks, in this order: a) Define an array called Measurements starting from memory location

More information

Timing Generation and Measurements

Timing Generation and Measurements Timing Generation and Measurements Lab #7 Robert McManus & Junsang Cho April 2, 2004 Timing Generation and Measurements 1. Objective To gain experience using input capture to measure pulse width. To gain

More information

Addressing Mode Description Addressing Mode Source Format Abbrev. Description

Addressing Mode Description Addressing Mode Source Format Abbrev. Description Addressing Mode Description Addressing Mode Source Format Abbrev. Description Inherent INST (no operands) INH Operands (if any) are in CPU registers Immediate INST #opr8i or INST #opr16i IMM Operand is

More information

ECE331 Handout 3- ASM Instructions, Address Modes and Directives

ECE331 Handout 3- ASM Instructions, Address Modes and Directives ECE331 Handout 3- ASM Instructions, Address Modes and Directives ASM Instructions Functional Instruction Groups Data Transfer/Manipulation Arithmetic Logic & Bit Operations Data Test Branch Function Call

More information

Chapter 2: HCS12 Assembly Programming. EE383: Introduction to Embedded Systems University of Kentucky. Samir Rawashdeh

Chapter 2: HCS12 Assembly Programming. EE383: Introduction to Embedded Systems University of Kentucky. Samir Rawashdeh Chapter 2: HCS12 Assembly Programming EE383: Introduction to Embedded Systems University of Kentucky Samir Rawashdeh With slides based on material by H. Huang Delmar Cengage Learning 1 Three Sections of

More information

SECTION 6 CENTRAL PROCESSING UNIT

SECTION 6 CENTRAL PROCESSING UNIT SECTION 6 CENTRAL PROCESSING UNIT This section discusses the M68HC11 central processing unit (CPU), which is responsible for executing all software instructions in their programmed sequence. The M68HC11

More information

Coe538 Final Study Guide 2016 (Questions & Answers)

Coe538 Final Study Guide 2016 (Questions & Answers) Coe538 Study Guide 1 of 8 Coe538 Final Study Guide 2016 (Questions & Answers) This version contains questions AND answers. This study guide is meant to help you review coe538 and prepare for the final.

More information

ECE/CE 3720: Embedded System Design

ECE/CE 3720: Embedded System Design Basic Components of Input Capture Slide 1 ECE/CE 3720: Embedded System Design Chris J. Myers Lecture 12: Input Capture Slide 3 Basic Principles of Input Capture Basic Principles of Input Capture (cont)

More information

Introduction to Mechatronics. Fall Instructor: Professor Charles Ume. Interrupts and Resets

Introduction to Mechatronics. Fall Instructor: Professor Charles Ume. Interrupts and Resets ME645 Introduction to Mechatronics Fall 24 Instructor: Professor Charles Ume Interrupts and Resets Reason for Interrupts You might want instructions executed immediately after internal request and/or request

More information

Lecture 7 Assembly Programming: Shift & Logical

Lecture 7 Assembly Programming: Shift & Logical CPE 390: Microprocessor Systems Fall 2017 Lecture 7 Assembly Programming: Shift & Logical Bryan Ackland Department of Electrical and Computer Engineering Stevens Institute of Technology Hoboken, NJ 07030

More information

Capstone Design Course. Lecture-2: The Timer

Capstone Design Course. Lecture-2: The Timer Capstone Design Course Lecture-2: The Timer By Syed Masud Mahmud, Ph.D. Copyright 2002 by Syed Masud Mahmud 1 The Timer The 68HC11 has a 16-Bit Free Running Timer. The count value of the timer is available

More information

instruction 1 Fri Oct 13 13:05:

instruction 1 Fri Oct 13 13:05: instruction Fri Oct :0:0. Introduction SECTION INSTRUCTION SET This section describes the aressing modes and instruction types.. Aressing Modes The CPU uses eight aressing modes for flexibility in accessing

More information

AN Kbyte Addressing with the M68HC11. Overview

AN Kbyte Addressing with the M68HC11. Overview Order this document by /D 128-Kbyte Addressing with the M68HC11 By Ross Mitchell MCU Applications Engineering Freescale Ltd. East Kilbride, Scotland Overview The maximum direct addressing capability of

More information

Chapter 2 HCS12 Assembly Language

Chapter 2 HCS12 Assembly Language Chapter 2 HCS12 Assembly Language ECE 3120 Dr. Mohamed Mahmoud http://iweb.tntech.edu/mmahmoud/ mmahmoud@tntech.edu Outline 2.1 Assembly language program structure 2.2 Data transfer instructions 2.3 Arithmetic

More information

ECET Chapter 2, Part 3 of 3

ECET Chapter 2, Part 3 of 3 ECET 310-001 Chapter 2, Part 3 of 3 W. Barnes, 9/2006, rev d. 10/07 Ref. Huang, Han-Way, The HCS12/9S12: An Introduction to Software and Hardware Interfacing, Thomson/Delmar. In This Set of Slides: 1.

More information

0b) [2] Can you name 2 people form technical support services (stockroom)?

0b) [2] Can you name 2 people form technical support services (stockroom)? ECE 372 1 st Midterm ECE 372 Midterm Exam Fall 2004 In this exam only pencil/pen are allowed. Please write your name on the front page. If you unstaple the papers write your name on the loose papers also.

More information

Disassembly of an HC12 Program It is sometimes useful to be able to convert HC12 op codes into mnemonics. For example, consider the hex code:

Disassembly of an HC12 Program It is sometimes useful to be able to convert HC12 op codes into mnemonics. For example, consider the hex code: Disassembly of an HC12 Program It is sometimes useful to be able to convert HC12 op codes into mnemonics. For example, consider the hex code: ADDR DATA ---- ------------------------------------------------------

More information

COE538 Lecture Notes Week 3 (Week of Sept 17, 2012)

COE538 Lecture Notes Week 3 (Week of Sept 17, 2012) COE538 Lecture Notes: Week 3 1 of 11 COE538 Lecture Notes Week 3 (Week of Sept 17, 2012) Announcements My lecture sections should now be on Blackboard. I've also created a discussion forum (and anonymous

More information

ELECTRICAL AND COMPUTER ENGINEERING DEPARTMENT, OAKLAND UNIVERSITY ECE-470/570: Microprocessor-Based System Design Fall 2014.

ELECTRICAL AND COMPUTER ENGINEERING DEPARTMENT, OAKLAND UNIVERSITY ECE-470/570: Microprocessor-Based System Design Fall 2014. c 2 =1 c 1 =1 c 0 =0 c 2 =1 c 1 =1 c 0 =0 c 4 =0 c 3 =0 c 2 =0 c 1 =0 c 0 =0 c 2 =0 c 1 =0 c 0 =1 c 2 =0 c 1 =0 c 0 =0 ELECTRICAL AND COMPUTER ENGINEERING DEPARTMENT, OAKLAND UNIVERSITY Notes - Unit 4

More information

Reading Assignment. 68HC12 Instruction Set. M68HC12 Instruction Set Categories. Some Tips. Endianness (Byte Order) Load and Store Instructions

Reading Assignment. 68HC12 Instruction Set. M68HC12 Instruction Set Categories. Some Tips. Endianness (Byte Order) Load and Store Instructions Reading Assignment EEL 4744C: Microprocessor Applications Lecture 5 68HC12 Instruction Set Software and Hardware Engineering (Old version) Chapter 4 Or Software and Hardware Engineering (New version) Chapter

More information

Disassembly of MC9S12 op codes Decimal, Hexadecimal and Binary Numbers

Disassembly of MC9S12 op codes Decimal, Hexadecimal and Binary Numbers Disassembly of MC9S12 op codes Decimal, Hexadecimal and Binary Numbers o How to disassemble an MC9S12 instruction sequence o Binary numbers are a code and represent what the programmer intends for the

More information

Disassembly of MC9S12 op codes Decimal, Hexadecimal and Binary Numbers

Disassembly of MC9S12 op codes Decimal, Hexadecimal and Binary Numbers Disassembly of MC9S12 op codes Decimal, Hexadecimal and Binary Numbers o How to disassemble an MC9S12 instruction sequence o Binary numbers are a code and represent what the programmer intends for the

More information

Administrivia. ECE/CS 5780/6780: Embedded System Design. Assembly Language Syntax. Assembly Language Development Process

Administrivia. ECE/CS 5780/6780: Embedded System Design. Assembly Language Syntax. Assembly Language Development Process Administrivia ECE/CS 5780/6780: Embedded System Design Scott R. Little Lecture 3: Assembly Language Programming 2 versions of CodeWarrior are on the lab machines. You should use the 4.5 version (CW for

More information

ECE/CS 5780/6780: Embedded System Design

ECE/CS 5780/6780: Embedded System Design ECE/CS 5780/6780: Embedded System Design Scott R. Little Lecture 3: Assembly Language Programming Scott R. Little (Lecture 3: Assembly) ECE/CS 5780/6780 1 / 59 Administrivia 2 versions of CodeWarrior are

More information

ECE 3120 Computer Systems Arithmetic Programming

ECE 3120 Computer Systems Arithmetic Programming ECE 3120 Computer Systems Arithmetic Programming Manjeera Jeedigunta http://blogs.cae.tntech.edu/msjeedigun21 Email: msjeedigun21@tntech.edu Tel: 931-372-6181, Prescott Hall 120 Today: Multiplication and

More information

HC11 Instruction Set

HC11 Instruction Set HC11 Instruction Set Instruction classes 1. Accumulator and Memory 2. Stack and Index Register 3. Condition Code Register 4. Program control instructions CMPE12 Summer 2009 19-2 1 Accumulator and memory

More information

MC9S12 Assembler Directives A Summary of MC9S12 Instructions Disassembly of MC9S12 op codes. Summary of HCS12 addressing modes ADDRESSING MODES

MC9S12 Assembler Directives A Summary of MC9S12 Instructions Disassembly of MC9S12 op codes. Summary of HCS12 addressing modes ADDRESSING MODES MC9S12 Assembler Directives A Summary of MC9S12 Instructions Disassembly of MC9S12 op codes o Review of Addressing Modes o Which branch instruction to use (signed vs unsigned) o Using X and Y registers

More information

EE319K Fall 2007 Quiz 1A Page 1. (5) Question 2. What will be the value of the carry (C) bit after executing the following? ldab #210 subb #60

EE319K Fall 2007 Quiz 1A Page 1. (5) Question 2. What will be the value of the carry (C) bit after executing the following? ldab #210 subb #60 EE319K Fall 2007 Quiz 1A Page 1 First: Last: This is a closed book exam. You must put your answers on this piece of paper only. You have 50 minutes, so allocate your time accordingly. Please read the entire

More information

Lecture 9 Subroutines

Lecture 9 Subroutines CPE 390: Microprocessor Systems Spring 2018 Lecture 9 Subroutines Bryan Ackland Department of Electrical and Computer Engineering Stevens Institute of Technology Hoboken, NJ 07030 Adapted from HCS12/9S12

More information

Assembly Language Development Process. ECE/CS 5780/6780: Embedded System Design. Assembly Language Listing. Assembly Language Syntax

Assembly Language Development Process. ECE/CS 5780/6780: Embedded System Design. Assembly Language Listing. Assembly Language Syntax Assembly Language Development Process ECE/CS 5780/6780: Embedded System Design Chris J. Myers Lecture 3: Assembly Language Programming Chris J. Myers (Lecture 3: Assembly Language) ECE/CS 5780/6780: Embedded

More information

Department of Computer Science and Engineering

Department of Computer Science and Engineering Department of Computer Science and Engineering Instruction Set Overview This is a complete overview of the instruction set for the Motorola MC9S12DT256 microprocessor. Some of the groups are irrelevant

More information

538 Lecture Notes Week 3

538 Lecture Notes Week 3 538 Lecture Notes Week 3 (Sept. 16, 2013) 1/18 538 Lecture Notes Week 3 Answers to last week's questions 1 Write code so that the least significant bit of Accumulator A is cleared, the most significant

More information

68HC11 Opera,ng Modes

68HC11 Opera,ng Modes 68HC11 Opera,ng Modes Modes Single- Chip Expanded Mul,plexed Special Bootstrap Special Test Minimal Circuit Layout: Single Chip Timing Diagrams Timing Laboratory 2 Debrief Exercise 1: Serial TX Generally

More information

COSC 243. Instruction Sets And Addressing Modes. Lecture 7&8 Instruction Sets and Addressing Modes. COSC 243 (Computer Architecture)

COSC 243. Instruction Sets And Addressing Modes. Lecture 7&8 Instruction Sets and Addressing Modes. COSC 243 (Computer Architecture) COSC 243 Instruction Sets And Addressing Modes 1 Overview This Lecture Source Chapters 12 & 13 (10 th editition) Textbook uses x86 and ARM (we use 6502) Next 2 Lectures Assembly language programming 2

More information

UNIVERSITY OF MANITOBA DEPARTMENT OF ELECTRICAL AND COMPUTER ENGINEERING. Term Test #2 Solution ECE 3610 MICROPROCESSING SYSTEMS

UNIVERSITY OF MANITOBA DEPARTMENT OF ELECTRICAL AND COMPUTER ENGINEERING. Term Test #2 Solution ECE 3610 MICROPROCESSING SYSTEMS ECE 3610 Test 2 Solution 1 of 7 PRINT LAST NAME: STUDENT NUMBER PRINT FIRST NAME: UNIVERSITY OF MANITOBA DEPARTMENT OF ELECTRICAL AND COMPUTER ENGINEERING DATE: Feb. 28, 11; TIME: 6:00-8:00 P.M. Term Test

More information

EE319 K Lecture 3. Introduction to the 9S12 Lab 1 Discussion Using the TExaS simulator. University of Texas ECE

EE319 K Lecture 3. Introduction to the 9S12 Lab 1 Discussion Using the TExaS simulator. University of Texas ECE EE319 K Lecture 3 Introduction to the 9S12 Lab 1 Discussion Using the TExaS simulator University of Texas ECE Introduction (von Neumann architecture) processor Bus Memory Mapped I/O System Input Devices

More information

EE 3170 Microcontroller Applications

EE 3170 Microcontroller Applications EE 37 Microcontroller Applications Lecture 8: Instruction Subset & Machine Language: A Brief Tour of the 68HC Instruction Set - Miller 2.4 & 5.2-5.3 & Appendix A Based on slides for ECE37 by Profs. Davis,

More information

EE319K Final Fall 2005 Solution C. (3) Question 1. (3) Question 2. short function(const short in){ return in+5; } const

EE319K Final Fall 2005 Solution C. (3) Question 1. (3) Question 2. short function(const short in){ return in+5; } const EE319K Final Fall 2005 Solution C. Jonathan Valvano (3) Question 1. Consider a matrix with 4 rows and 6 columns, stored in column-major zero-index format. Each element is 16 bits. Which equation correctly

More information

Menu. Programming Models for the Atmel XMEGA Architecture (and others devices) Assembly Programming Addressing Modes for the XMEGA Instruction Set

Menu. Programming Models for the Atmel XMEGA Architecture (and others devices) Assembly Programming Addressing Modes for the XMEGA Instruction Set Menu Programming Models for the Atmel XMEGA Architecture (and others devices) Assembly Programming Addressing Modes for the XMEGA Instruction Set Look into my... See examples on web-site: doc8331, doc0856

More information

2. Arithmetic Instructions addition, subtraction, multiplication, divison (HCS12 Core Users Guide, Sections 4.3.4, and ).

2. Arithmetic Instructions addition, subtraction, multiplication, divison (HCS12 Core Users Guide, Sections 4.3.4, and ). AS12 Assembler Directives A Summary of 9S12 instructions Disassembly of 9S12 op codes Huang Section 1.8, Chapter 2 MC9S12 V1.5 Core User Guide Version 1.2, Section 12 o A labels is a name assigned the

More information

EE 3170 Microcontroller Applications

EE 3170 Microcontroller Applications Lecture Overview EE 3170 Microcontroller Applications Lecture 7 : Instruction Subset & Machine Language: Conditions & Branches in Motorola 68HC11 - Miller 2.2 & 2.3 & 2.4 Based on slides for ECE3170 by

More information

MIGRATING TO THE 68HC12 IN C

MIGRATING TO THE 68HC12 IN C MIGRATING TO THE 68HC12 IN C by Jean-Pierre Lavandier (Cosmic Software) and Greg Viot (Motorola) INTRODUCTION An important design goal of the 68HC12 was to maintain software compatibility with the 68HC11

More information

EE319K Fall 2003 Quiz 1 Page 1

EE319K Fall 2003 Quiz 1 Page 1 EE319K Fall 2003 Quiz 1 Page 1 First: Last: This is a closed book exam. You must put your answers on this piece of paper only. You have 50 minutes, so allocate your time accordingly. Please read the entire

More information

EE319K Fall 2006 Quiz 1 Page 1

EE319K Fall 2006 Quiz 1 Page 1 EE319K Fall 2006 Quiz 1 Page 1 First: Last: This is a closed book exam. You must put your answers on this piece of paper only. You have 50 minutes, so allocate your time accordingly. Please read the entire

More information

ME 6405 Introduction to Mechatronics

ME 6405 Introduction to Mechatronics ME 6405 Introduction to Mechatronics Fall 2005 Instructor: Professor Charles Ume LECTURE 9 Homework 1 Solution 1. Write an assembly language program to clear the usable internal RAM in the M68HC11E9. Solution:

More information

Introduction to Microcontrollers

Introduction to Microcontrollers Motorola M68HC11 Specs Assembly Programming Language BUFFALO Topics of Discussion Microcontrollers M68HC11 Package & Pinouts Accumulators Index Registers Special Registers Memory Map I/O Registers Instruction

More information

538 Lecture Notes Week 5

538 Lecture Notes Week 5 538 Lecture Notes Week 5 (Sept. 30, 2013) 1/15 538 Lecture Notes Week 5 Answers to last week's questions 1. With the diagram shown for a port (single bit), what happens if the Direction Register is read?

More information

ME4447/6405. Microprocessor Control of Manufacturing Systems and Introduction to Mechatronics. Instructor: Professor Charles Ume LECTURE 7

ME4447/6405. Microprocessor Control of Manufacturing Systems and Introduction to Mechatronics. Instructor: Professor Charles Ume LECTURE 7 ME4447/6405 Microprocessor Control of Manufacturing Systems and Introduction to Mechatronics Instructor: Professor Charles Ume LECTURE 7 Reading Assignments Reading assignments for this week and next

More information

ECE 367 -Experiment #1 Fall 2012

ECE 367 -Experiment #1 Fall 2012 Due at the beginning of lab during week 3 (9/1/2012) Introduction ECE 367 -Experiment #1 Fall 2012 The goal of this experiment is the acquaint you with the Technological Arts nanocore12 microcontroller

More information

EE319K Fall 2005 Quiz 1A Page 1

EE319K Fall 2005 Quiz 1A Page 1 EE319K Fall 2005 Quiz 1A Page 1 First: Last: This is a closed book exam. You must put your answers on this piece of paper only. You have 50 minutes, so allocate your time accordingly. Please read the entire

More information

Condition Code Register. Microcomputer Architecture and Interfacing Colorado School of Mines Professor William Hoff

Condition Code Register. Microcomputer Architecture and Interfacing Colorado School of Mines Professor William Hoff Condition Code Register 1 Topics Condition code register Addition and subtraction instructions Conditional branches 2 Condition Code Register Condition code bits are automatically set by some instructions

More information

538 Lecture Notes Week 5

538 Lecture Notes Week 5 538 Lecture Notes Week 5 (October 4, 2017) 1/18 538 Lecture Notes Week 5 Announements Midterm: Tuesday, October 25 Answers to last week's questions 1. With the diagram shown for a port (single bit), what

More information

Using the stack and the stack pointer

Using the stack and the stack pointer Using the stack and the stack pointer o The Stack and Stack Pointer o The stack is a memory area for temporary storage o The stack pointer points to the last byte in the stack o Some instructions which

More information

EE 5340/7340 Motorola 68HC11 Microcontroler Lecture 1. Carlos E. Davila, Electrical Engineering Dept. Southern Methodist University

EE 5340/7340 Motorola 68HC11 Microcontroler Lecture 1. Carlos E. Davila, Electrical Engineering Dept. Southern Methodist University EE 5340/7340 Motorola 68HC11 Microcontroler Lecture 1 Carlos E. Davila, Electrical Engineering Dept. Southern Methodist University What is Assembly Language? Assembly language is a programming language

More information

Introduction to Microcontroller. Systems. Embedded system. Assembler or C? Datatypes 2. Datatypes 1

Introduction to Microcontroller. Systems. Embedded system. Assembler or C? Datatypes 2. Datatypes 1 Introduction to Microcontroller Sven Knutsson 031-772 57 27 svenk@chl.chalmers.se www.chl.chalmers.se/~svenk/it_university 1 2 Embedded system Assembler or C? Real time Size Price Power consumption User

More information

Decimal, Hexadecimal and Binary Numbers Writing an assembly language program

Decimal, Hexadecimal and Binary Numbers Writing an assembly language program Decimal, Hexadecimal and Binary Numbers Writing an assembly language program o Disassembly of MC9S12 op codes o Use flow charts to lay out structure of program o Use common flow structures if-then if-then-else

More information

538 Lecture Notes Week 3

538 Lecture Notes Week 3 538 Lecture Notes Week 3 (Sept. 20, 2017) 1/24 538 Lecture Notes Week 3 Answers to last week's questions 1 Write code so that the least significant bit of Accumulator A is cleared, the most significant

More information

68HC11 PROGRAMMER'S MODEL

68HC11 PROGRAMMER'S MODEL 8H11 PROGRMMER'S MODEL s (,, and D) s and are general-purpose 8-bit accumulators used to hold operands and results of arithmetic calculations or data manipulations. Some instructions treat the combination

More information

1 Execution of main program is suspended. 2 All registers are pushed onto the stack. 3 The ISR, or background thread, is executed.

1 Execution of main program is suspended. 2 All registers are pushed onto the stack. 3 The ISR, or background thread, is executed. Introduction ECE/CS 5780/6780: Embedded System Design Chris J. Myers Lecture 7: Interrupt Synchronization Interrupts provide guarantee on response time. Interrupts allow response to rare but important

More information

Wed. Sept 6 Announcements

Wed. Sept 6 Announcements Wed. Sept 6 Announcements HW 3 / Lab 3 posted [1.C]-1 Endianness Problem: Memory is byte addressed. Sometimes you want to access multi-byte values (16-bit, 32-bits etc.) X is 2-bytes Addr Memory Value

More information

Cross Assembly and Program Development

Cross Assembly and Program Development Cross Assembly and ENGG4640/3640; Fall 2004; Prepared by Radu Muresan 1 Introduction Text Editor Program Ex. DOS, Notepad, Word saved as ASCII Source Code Assembler or Cross-Assembler Object Code Machine

More information

HC 11 Instructions! From Alex Hollowayʼs notes with! many thanks!

HC 11 Instructions! From Alex Hollowayʼs notes with! many thanks! HC 11 Instructions! From Alex Hollowayʼs notes with! many thanks! Instruction Classes! Accumulator and Memory! Stack and Index Register! Condition Code Register! Program Control! Accumulator and memory

More information

The 6502 Instruction Set

The 6502 Instruction Set The 6502 Instruction Set Load and Store Group LDA Load Accumulator N,Z LDX Load X Register N,Z LDY Load Y Register N,Z STA Store Accumulator STX Store X Register STY Store Y Register Arithmetic Group ADC

More information

538 Lecture Notes Week 2

538 Lecture Notes Week 2 538 Lecture Notes Week 2 (Sept. 13, 2017) 1/15 Announcements 538 Lecture Notes Week 2 Labs begin this week. Lab 1 is a one-week lab. Lab 2 (starting next week) is a two-week lab. 1 Answers to last week's

More information

Motorola 6809 and Hitachi 6309 Programmer s Reference

Motorola 6809 and Hitachi 6309 Programmer s Reference Motorola 6809 and Hitachi 6309 Programmer s Reference 2009 by Darren Atkinson A note about cycle counts The MPU cycle counts listed throughout this document will sometimes show two different values separated

More information

Interrupts. Interrupts Resets Low Power Modes. Resets Low Power Modes

Interrupts. Interrupts Resets Low Power Modes. Resets Low Power Modes Interrupts Resets Low Power Modes Drop everything and get your priorities straight! Alan Claghorn Chris Golder Raja Shah Outline Interrupts Why use interrupts? Types of interrupts Interrupt Flow Priorities

More information

Introduction to Embedded Microcomputer Systems Lecture 8.1. Computers in the future may weigh no more than 1.5 tons Popular Science, 1949

Introduction to Embedded Microcomputer Systems Lecture 8.1. Computers in the future may weigh no more than 1.5 tons Popular Science, 1949 Introduction to Embedded Microcomputer Systems Lecture 8.1 Computers in the future may weigh no more than 1.5 tons Popular Science, 1949 Recap Debugging: Monitor, dump TExaS Real 9S12DG Overview Addition

More information

Caution: Make sure to follow the wiring diagram (last pages) as shown.

Caution: Make sure to follow the wiring diagram (last pages) as shown. GP2D120 Distance sensor application using 9S12C32 Hardwares: - SchoolBoard or - NC12SSIM using J8 connections - SFR04 - NC12DX This application will use PAD2/AN02 to measure the voltage from a GP2D120

More information

ECE 372 Microcontroller Design Assembly Programming Arrays. ECE 372 Microcontroller Design Assembly Programming Arrays

ECE 372 Microcontroller Design Assembly Programming Arrays. ECE 372 Microcontroller Design Assembly Programming Arrays Assembly Programming Arrays Assembly Programming Arrays Array For Loop Example: unsigned short a[]; for(j=; j

More information

Lecture #3 Microcontroller Instruction Set Embedded System Engineering Philip Koopman Wednesday, 20-Jan-2015

Lecture #3 Microcontroller Instruction Set Embedded System Engineering Philip Koopman Wednesday, 20-Jan-2015 Lecture #3 Microcontroller Instruction Set 18-348 Embedded System Engineering Philip Koopman Wednesday, 20-Jan-2015 Electrical& Computer ENGINEERING Copyright 2006-2015, Philip Koopman, All Rights Reserved

More information

PROGRAMMING THE MICROCONTROLLER

PROGRAMMING THE MICROCONTROLLER PROGRAMMING THE MICROCONTROLLER ASSEMBLY LANGUAGE Assembly language is of higher level than machine language and hence easier to use. An assembly language code consists of a) Program statement lines b)

More information

(5) Question 7. Simplified memory cycles (you may or may not need all 5 entries) R/W Addr Data

(5) Question 7. Simplified memory cycles (you may or may not need all 5 entries) R/W Addr Data EE319K Fall 2003 Quiz 3 Page 1 First: Middle Initial: Last: This is a closed book exam. You must put your answers on this piece of paper only. You have 50 minutes, so allocate your time accordingly. Please

More information

Exam 2 E2-1 Fall Name: Exam 2

Exam 2 E2-1 Fall Name: Exam 2 Exam 2 E2-1 Fall 2002 1. Short Answer [10 pts] Exam 2 a.[2 pts] Briefly describe what each of the following instructions do so that it is clear what the differences between them are: STAA -2,X STAA 2,-X

More information

Module 1-G. Marcos and Structured Programming

Module 1-G. Marcos and Structured Programming Module 1-G Marcos and Structured Programming 1 Learning Outcome #1 An ability to program a microcontroller to perform various tasks How? A. Architecture and Programming Model B. Instruction Set Overview

More information

1. Memory Mapped Systems 2. Adding Unsigned Numbers

1. Memory Mapped Systems 2. Adding Unsigned Numbers 1 Memory Mapped Systems 2 Adding Unsigned Numbers 1 1 Memory Mapped Systems Our system uses a memory space Address bus is 16-bit locations Data bus is 8-bit 2 Adding Unsigned Numbers 2 Our system uses

More information

History of the Microprocessor. ECE/CS 5780/6780: Embedded System Design. Microcontrollers. First Microprocessors. MC9S12C32 Block Diagram

History of the Microprocessor. ECE/CS 5780/6780: Embedded System Design. Microcontrollers. First Microprocessors. MC9S12C32 Block Diagram History of the Microprocessor ECE/CS 5780/6780: Embedded System Design Chris J. Myers Lecture 1: 68HC12 In 1968, Bob Noyce and Gordon Moore left Fairchild Semiconductor and formed Integrated Electronics

More information

Introduction to Microcontrollers II

Introduction to Microcontrollers II Introduction to Microcontrollers II brset, brclr Indexed Addressing Example µp Laboratory #2 BUFFALO Assembling Code EECE 143 Digital Design Project Purpose: To allow students to design their own digital

More information

Exam 2 E2-1 Fall Name: Exam 2

Exam 2 E2-1 Fall Name: Exam 2 Exam 2 E2-1 Fall 2004 1. Short Answer [20 pts] Exam 2 a. [4 points] Show the contents of registers A, B, SP, and X after the following code executes: lds #$a00 ldab #$23 A = ldaa #$87 ldx #$2543 B = pshd

More information

TEMPERATURE SENSOR. Revision Class. Instructor / Professor LICENSE

TEMPERATURE SENSOR. Revision Class. Instructor / Professor LICENSE CME-11E9 EVBU LAB EXPERIMENT TEMPERATURE SENSOR Revision 04.02.11 Class Instructor / Professor LICENSE You may use, copy, modify and distribute this document freely as long as you include this license

More information

Fri. Aug 25 Announcements

Fri. Aug 25 Announcements Fri. Aug 25 Announcements HW 1 / Lab 1 next week Tools and fundamentals of instructions Remember no in-lab quiz but HWs still marked Slides online Complete class for last year This year s slides available

More information

A. CPU INSTRUCTION SET SUMMARY

A. CPU INSTRUCTION SET SUMMARY A. CPU INSTRUCTION SET SUMMARY This appendix summarizes the CPU instruction set. Table A-1 is a matrix of CPU instructions and addressing modes arranged by operation code. Table A-2 lists the CPU instruction

More information

INSTRUCTION SET AND EXECUTION

INSTRUCTION SET AND EXECUTION SECTION 6 INSTRUCTION SET AND EXECUTION Fetch F1 F2 F3 F3e F4 F5 F6 Decode D1 D2 D3 D3e D4 D5 Execute E1 E2 E3 E3e E4 Instruction Cycle: 1 2 3 4 5 6 7 MOTOROLA INSTRUCTION SET AND EXECUTION 6-1 SECTION

More information

Exam I Review February 2017

Exam I Review February 2017 Exam I Review February 2017 Binary Number Representations Conversion of binary to hexadecimal and decimal. Convert binary number 1000 1101 to hexadecimal: Make groups of 4 bits to convert to hexadecimal,

More information

III. Flags of the Processor Staus Register

III. Flags of the Processor Staus Register III. Flags of the Processor Staus Register INHALT 1. Meaning 2. Application 2.1 Shifts 2.2 Branches 2.3 Addition and Subtraction 2.4 Comparisons in magnitude 1. Meaning processor status register Overflow

More information

Freescale Semiconductor, Inc.

Freescale Semiconductor, Inc. Order this document by /D Software I 2 C Communications By Brad Bierschenk MMD Applications Engineering Austin, Texas Introduction I 2 C Overview The I 2 C (inter-integrated circuit) protocol is a 2-wire

More information

HC11 Instruction Set Architecture

HC11 Instruction Set Architecture HC11 Instruction Set Architecture High-level HC11 architecture Interrupt logic MEMORY Timer and counter M8601 CPU core Serial I/O A/D converter Port A Port B Port C Port D Port E CMPE12 Summer 2009 16-2

More information

EE 308 Spring A software delay. To enter a software delay, put in a nested loop, just like in assembly.

EE 308 Spring A software delay. To enter a software delay, put in a nested loop, just like in assembly. More on Programming the 9S12 in C Huang Sections 5.2 through 5.4 Introduction to the MC9S12 Hardware Subsystems Huang Sections 8.2-8.6 ECT_16B8C Block User Guide A summary of MC9S12 hardware subsystems

More information

HC11 Instruction Set Architecture

HC11 Instruction Set Architecture HC11 Instruction Set Architecture Summer 2008 High-level HC11 architecture Interrupt logic MEMORY Timer and counter M8601 CPU core Serial I/O A/D converter Port A Port B Port C Port D Port E CMPE12 Summer

More information

Exam 1 Feb. 23, 25, 27?

Exam 1 Feb. 23, 25, 27? Exam 1 Feb. 23, 25, 27? You will be able to use all of the Motorola data manuals on the exam. No calculators will be allowed for the exam. Numbers Decimal to Hex (signed and unsigned) Hex to Decimal (signed

More information

ECE/CE 3720: Embedded System Design

ECE/CE 3720: Embedded System Design Sequence of Events During Interrupt 1. Hardwere needs service (busy-to-done) transition. 2. Flag is set in one of the I/O status registers. (a) Interrupting event sets the flag (ex., STAF=1). Slide 1 ECE/CE

More information

ECE 3610 MICROPROCESSING SYSTEMS AN ENCRYPTED ASCII CODE DECODER

ECE 3610 MICROPROCESSING SYSTEMS AN ENCRYPTED ASCII CODE DECODER ECE 3610 MICROPROCESSIG SYSTEMS A ECRYPTED ASCII CODE DECODER 1 PROBLEM SPECIFICATIO Design a microprocessing system to decode messages which are encrypted. Each byte of the message is an encrypted ASCII

More information