Apple /// Disk /// Floppy Disk Formatter Driver 1.30 Source Code Listing

Size: px
Start display at page:

Download "Apple /// Disk /// Floppy Disk Formatter Driver 1.30 Source Code Listing"

Transcription

1 Apple /// Computer Technical Information Apple /// Disk /// Floppy Disk Formatter Driver 1.30 Source Code Listing Created by David T. Craig 06 January / 19

2 ; # PROJECT : Apple /// SOS DISK /// Formatter Device Driver 1.30 (6502 Assembly Source Code) ; # FILE NAME: FMTDX.TEXT NOPATCHLIST NOMACROLIST ; ; SOS DISK /// Formatter Device Driver ; (C) Copyright 1980, 1981 by Apple Computer Inc ; Revisions: 11-SEP-81 V1.10 Modify Devtype and Subtype to ; reflect new conventions. Activate all formatters ; 19-AUG-82 V1.21 Include DSPEED checks and max /RRA82237/ ; retries on WTRACK16. R. Auricchio. Changes marked by /RRA82237/ ; '/RRA82237'. /RRA82237/ ; 15-SEP-82 V1.22 Fix WTRACK16/VTRACK code so /RRA82258/ ; it doesn't write 128 nybbles prior to sector 0 on a /RRA82258/ ; retry. This caused 'too fast' error if several tries /RRA82258/ ; were done: since 128-nibble seam is so large, VTRACK /RRA82258/ ; thinks NSYNC is too large, and decrements it. The end/rra82258/ ; result is NSYNC getting too small. Also changed VTRACK/RRA82258/ ; retries to 2 rotations MAX. R. Auricchio. /RRA82258/ ; Changes marked by '/RRA82258'. /RRA82258/ ; 06-DEC-82 V1.23 Fix VTRACK code to verify that /RRA82340/ ; the gap between sectors 15 & 0 (the "seam") is large /RRA82340/ ; enough. R. Auricchio. Changes marked by '/RRA82340'. /RRA82340/ ; 04-Jan-82 V1.30 Installed comment field and set/hgl83004/ ; the configuration block length to 0. H. Lehtman. /HGL83004/ ; Deleted absolute assembly code. /HGL83004/ ; Added code to support D_CONTROL 0 by returning rather /HGL83004/ ; than generating an error. /HGL83004/ ; Changes marked by /HGL /HGL83004/ ; Error codes returned: $00 : good completion ; $27 : Unable to format (usually bad media) ; $28 : Write-Protected ; $33 : Drive too SLOW /RRA82237/ ; $34 : Drive too FAST /RRA82237/ ; DEVTYPE.EQU 011 ;Disk Formatter SUBTYPE.EQU 01 ;For Disk /// APPLE.EQU RELEASE.EQU 1300 ; /HGL83301/ DEVBLKS.EQU 280. ;NUMBER OF BLKS ON VOLUME ; MAXTRKRETRY.EQU 3. ;MAX RETRIES PER TRACK /RRA82237/ MAXSECTRETRY.EQU 16. ;MAX RETRIES TO READ SECTORS /RRA82258/ ; ; AVERAGE CORRECT SYNC VALUE HAS BEEN MEASURED AS FOLLOWS /RRA82237/ ; GOODSYNC.EQU 22. ;CORRECT VALUE /RRA82237/ DELTAS.EQU 3. ; /RRA82237/ DELTAF.EQU 3. ;DSPEED IS DELTA*16/2 /RRA82237/ MINSYNC.EQU GOODSYNC-DELTAF ; /RRA82237/ MAXSYNC.EQU GOODSYNC+DELTAS ; /RRA82237/ PAGE ; ; ; The macro SWITCH performs an N way branch based on a switch index. The ; maximum value of the switch index is 127 with bounds checking provided ; as an option. The macro uses the A and Y registers and alters the C, ; Z, and N flags of the status register, but the X register is unchanged ; ; SWITCH [index], [bounds], adrs_table, [*] ; ; index This is the variable that is to be used as the switch index ; If omitted, the value in the accumulator is used ; ; bounds This is the maximum allowable value for index. If index ; exceeds this value, the carry bit will be set and execution ; will continue following the macro. If bounds is omitted, / 19

3 ; no bounds checking will be performed ; ; adrs_table This is a table of addresses (low byte first) used by the ; switch. The first entry corresponds to index zero ; ; * If an asterisk is supplied as the fourth parameter, the ; macro will push the switch address but will not exit to ; it; execution will continue following the macro. The ; program may then load registers or set the status before ; exiting to the switch address ; ; ; MACRO SWITCH IF "%1" <> "" ;If PARM1 is present, LDA %1 ; Load A with switch index ENDC IF "%2" <> "" ;If PARM2 is present, CMP #%2+1 ; Perform bounds checking BCS $010 ; on switch index ENDC ASL A TAY LDA %3+1,Y ;Get switch address from table PHA ; and push onto stack LDA %3,Y PHA IF "%4" <> "*" ;If PARM4 is omitted, RTS ; Exit to code ENDC ;Otherwise, drop through $010.ENDM PAGE ; SOS Global Data & Subroutines SYSERR.EQU ; SOS Error Codes XCTLCODE.EQU 21 ;Invalid control/status code XCTLPARM.EQU 22 ;Invalid control/status parm XNOTOPEN.EQU 23 ;Device not open XNOTAVAIL.EQU 24 ;Device not available XBADOP.EQU 26 ;Invalid operation for device XIOERR.EQU 27 ;I/O err, cannot format XWPROT.EQU 2B ;Write Protected XDEVSPEC.EQU 30 ;Device-specific error /RRA82237/ ; Miscellaneous Equates TRUE.EQU FALSE.EQU ; ; SOS Device Driver Interface ; SOSINT.EQU 0C REQCODE.EQU SOSINT+0 ;SOS request code UNITNUM.EQU SOSINT+1 ;REQUESTED UNIT NUMBER CTLSTAT.EQU SOSINT+2 ;Control/status code CSLIST.EQU SOSINT+3 ;Control/status list pointer PROC FMTDISK ; ; Device Identification Blocks: The first one is here so that the SOS ; loader correctly pagealigns us. The other three (for.d2..4) are ; at the end of the module, so they don't affect the alignment ; WORD 0FFFF ; /HGL83004/ WORD 53. ;LENGTH OF COMMENT /HGL83004/ ASCII "(C) Apple Computer, " ; /HGL83004/" ASCII "Disk /// Formatter Driver." ; /HGL83004/" DIBD1.WORD DIBD2 ;Link to next device handler WORD FMTMAIN ;Entry point address / 19

4 BYTE 6 ;Length of device name ASCII ".FMTD1 " BYTE 0C0 ;Active, page-aligned BYTE 00,00 ;Slot & Unit numbers BYTE DEVTYPE BYTE SUBTYPE BYTE WORD DEVBLKS ;block count WORD APPLE WORD RELEASE WORD 0 ; /HGL83004/ DCB_MINSYNC.BYTE MINSYNC ; /RRA82237/ DCB_MAXSYNC.BYTE MAXSYNC ; /RRA82237/ DCB_TRKRETRY.BYTE MAXTRKRETRY ; /RRA82237/ DCB_SECTRETRY.BYTE MAXSECTRETRY ; /RRA82258/ TITLE "DRIVER GLOBAL EQUATES/DATA" INCLUDE FMTDATA.TEXT ;DATA INCLUDE FMTREAD.TEXT ;READ DATA INCLUDE FMTWRADDR.TEXT ;WRITE ADDRESS INCLUDE FMTFORMAT.TEXT ;FORMATTER CODE INCLUDE FMTWTRACK.TEXT ;WTRACK16/VTRACK /RRA82258/ TITLE "FORMATTER MAINLINE" PAGE ; ; FMTDISK3-- Main entry point ; FMTMAIN.EQU * SWITCH REQCODE, 8, REQSTSW BADREQ LDA #XBADOP ;Invalid request code JSR SYSERR REQSTSW.EQU * ;FMTDISK3 request switch WORD BADREQ-1 ;0 - READ WORD BADREQ-1 ;1 - WRITE WORD FMTSTATUS-1 ;2 - DSTATUS WORD FMTCTRL-1 ;3 - DCNTRL WORD BADREQ-1 ;4 - INVALID WORD BADREQ-1 ;5 - INVALID WORD BADREQ-1 ;6 - OPEN WORD BADREQ-1 ;7 - CLOSE WORD FMTINIT-1 ;8 - INIT PAGE ; ; FMTDISK3 -- Control Request ; FMTCTRL.EQU * LDA CTLSTAT ;get control code CMP #0 ;reset must be supported /HGL82004/ BNE $005 ; for Pascal. /HGL82004/ RTS ;nop if reset call /HGL82004/ $005 CMP #0FE ;is it our special one? /HGL82004/ BEQ $020 ;=>yes LDA #XCTLCODE ;bad control code $010 JSR SYSERR ; Make sure the FORMATTER code likes everything: $020 JSR FMTSTARTUP ;OK TO GO? CMP #0 ;WELL? BNE $010 ;=>NOPE ; SET UP CONTROL-LIST PARMS: LDA CSLIST ;copy the address of STA USERBUF ; the caller's buffer LDA CSLIST STA USERBUF LDA 1400+CSLIST+1 ;lest we forget the STA USERBUF+2 ; extend value LDX UNITNUM ;GET DRIVE TO BE FORMATTED / 19

5 INX ;MAKE RELATIVE TO ONE ; FORMAT THE DISKETTE: JSR DSKFORM ;** FORMAT IT ** ; EXIT PATH: CMP #0 ;CHECK RETURN CODE BNE $030 ;=>AN ERROR RTS ;ALL'S WELL $030 CMP #2 ;IS IT WPROT? BNE $040 ;=>NO, MUST BE IOERR LDA #XWPROT ;YES JSR SYSERR $040 CMP #1 ;IS IT I/O ERR? /RRA82237/ BNE $050 ;->NOPE /RRA82237/ LDA #XIOERR ;I/O ERROR JSR SYSERR $050 CLC ;SLOW/FAST IS /RRA82237/ ADC #XDEVSPEC ; SPECIFIC /RRA82237/ JSR SYSERR ; /RRA82237/ BADDRIVE.EQU * ;INVALID DRIVE REQUESTED LDA #XCTLPARM JSR SYSERR PAGE ; ; FMTDISK3 -- Status Request ; FMTSTATUS.EQU * LDA CTLSTAT CMP #0FE ;IS IT OUR SPECIAL ONE? BEQ $010 ;=>YES LDA #XCTLCODE ;ILLEGAL CODE, BOZO! JSR SYSERR $010 LDY # LDA #0FF ;WE HAVE NO BITMAP PREFERENCE STA (CSLIST),Y ; FOR BITMAP-STARTBLOCK FIELD INY STA (CSLIST),Y RTS PAGE ; ; FMTINIT -- Initialization Request ; FMTINIT.EQU * CLC RTS TITLE "The other DIBs" PAGE DIBD2.WORD DIBD3 ;Link to next device handler WORD FMTMAIN ;Entry point address BYTE 6 ;Length of device name ASCII ".FMTD2 " BYTE 080 ;Active BYTE 00,01 ;Slot & Unit numbers BYTE DEVTYPE BYTE SUBTYPE BYTE WORD DEVBLKS ;block count WORD APPLE WORD RELEASE WORD 0 ;NO DCB DIBD3.WORD DIBD4 ;Link to next device handler WORD FMTMAIN ;Entry point address BYTE 6 ;Length of device name ASCII ".FMTD3 " BYTE 080 ;Active BYTE 00,02 ;Slot & Unit numbers / 19

6 BYTE DEVTYPE BYTE SUBTYPE BYTE WORD DEVBLKS ;block count WORD APPLE WORD RELEASE WORD 0 ;NO DCB DIBD4.WORD 0000 ;Link to next device handler WORD FMTMAIN ;Entry point address BYTE 6 ;Length of device name ASCII ".FMTD4 " BYTE 080 ;Active BYTE 00,03 ;Slot & Unit numbers BYTE DEVTYPE BYTE SUBTYPE BYTE WORD DEVBLKS ;block count WORD APPLE WORD RELEASE WORD 0 ;NO DCB END ; # END OF FILE: FMTDX.TEXT ; # LINES : 341 ; # CHARACTERS : ; # Formatter : Assembly Language Reformatter (06 January 1998) ; # Author : David T. Craig @compuserve.com -- Santa Fe, New Mexico USA / 19

7 ; # PROJECT : Apple /// SOS DISK /// Formatter Device Driver 1.30 (6502 Assembly Source Code) ; # FILE NAME: FMTDATA.TEXT PAGE ; GLOBAL DATA AREAS: USERBUF.BLOCK 3 ;SECTOR BUF POINTER TITLE "FORMATTER LOCAL EQUATES/DATA" PAGE ; FORMATTER LOCAL DATA AREAS: E_REG.EQU 0FFDF IBSLOT.EQU 81 ;SLOT IMASK.EQU IBSLOT+0A CURTRK.EQU IBSLOT+0B ;CURRENT TRACK INTRTRY.EQU IBSLOT+0E RETRYCNT.EQU IBSLOT BUF.EQU IBSLOT+1A ;DATA BUFFER FOR PRE/POSTNIB CKSUM.EQU IBSLOT+15 ;CHECKSUM BYTE CSSTV.EQU IBSLOT+16 ;FOUR BYTES, SECT.EQU CSSTV TRACK.EQU CSSTV ; CHECKSUM,SECTOR,TRACK,VOLUME TRKN.EQU IBSLOT+1D MONTIME.EQU CSSTV+2 ;MOTOR-ON TIME ; ; Zeropage Usage: ; AA.EQU 0D0 ;TIMING CONSTANT TRK.EQU 0D1 ;FORMATTER TRACK NSECT.EQU 0D2 ;FORMATTER SECTOR NVOL.EQU 0D3 ;FORMATTER VOLUME NSYNC.EQU 0D4 ;NUMBER SELFSYNC NYBBLES IDX.EQU 0D5 ;NBUF INDEX/COUNT FOR READ TRKRETRY.EQU 0D6 ;NO. RETRIES FOR WTRACK PAGE ;************************ ; * ; HARDWARE ADDRESSES * ; * ;************************ MOTOROFF.EQU 0C MOTORON.EQU 0C Q6L.EQU 0C08C Q6H.EQU 0C08D Q7L.EQU 0C08E Q7H.EQU 0C08F ;************************ ; * ; ROM ROUTINE ADDRESSES * ; * ;************************ RDADR16.EQU 0F1B9 ;READ ADDRESS WRITE16.EQU 0F216 ;WRITE DATA PRENIB16.EQU 0F2C4 ;PRENIBBLIZE FOR WRITE SEEK.EQU 0F400 ;SEEK MSWAIT.EQU 0F456 ;TIME DELAYER DNIBL.EQU 0F300 ;DNIBL TABLE ADDR PAGE ; ; Zeropage Savearea: This area is used to save the SOS ZeroPage ; area $80..$9F, which is used exclusively by the ROM Core ; Routines. These locations are clobbered by the Formatter ; during its operation, and are then restored ; ZEROSAVE.BLOCK 32. ;SAVEAREA FOR $1800 PAGE XTNDSAVE.BLOCK 32. ;SAVEAREA FOR $1400 PAGE E_SAVE.BLOCK 1 ;SAVED CALLER ENVIRONMENT P_SAVE.BLOCK 1 ;SAVED CALLER STATUS ; DiskDrive Select Addresses ;.D1.D2.D3.D ; SEL1.BYTE 000,0D0,0D5,0D5,0D SEL2.BYTE 000,0D2,0D1,0D0,0D / 19

8 SEL3.BYTE 000,0D4,0D2,0D3,0D FOUND.BLOCK 16. ;'SECTOR FOUND' TABLE. ; # END OF FILE: FMTDATA.TEXT ; # LINES : 79 ; # CHARACTERS : 4060 ; # Formatter : Assembly Language Reformatter (06 January 1998) ; # Author : David T. Craig @compuserve.com -- Santa Fe, New Mexico USA / 19

9 ; # PROJECT : Apple /// SOS DISK /// Formatter Device Driver 1.30 (6502 Assembly Source Code) ; # FILE NAME: FMTREAD.TEXT TITLE "16-SECTOR READ" PAGE ;************************* ; * ; READ SUBROUTINE * ; (16-SECTOR FORMAT) * ; * ;************************* ; READS 6-BIT NIBLS * ; (00ABCDEF) INTO * ; NBUF1 AND NBUF2 * ; CONVERTING 7-BIT * ; NIBLS TO 6-BIT * ; VIA 'DNIBL' TABLE * ; * ; FIRST READS NBUF2 * ; HIGH TO LOW, * ; THEN READS NBUF1 * ; LOW TO HIGH. * ; * ; ---- ON ENTRY ---- * ; * ; X-REG: SLOTNUM * ; TIMES $10. * ; * ; READ MODE (Q6L, Q7L) * ; * ; ---- ON EXIT * ; * ; CARRY SET IF ERROR. * ; * ; IF NO ERROR: * ; A-REG HOLDS $AA. * ; X-REG UNCHANGED. * ; Y-REG HOLDS $00. * ; CARRY CLEAR. * ; * ; NBUF1 AND NBUF2 * ; HOLD 6-BIT NIBLS * ; (00ABCDEF) * ; * ; USES TEMP 'IDX'. * ; * ; ---- CAUTION * ; * ; OBSERVE * ; 'NO PAGE CROSS' * ; WARNINGS ON * ; SOME BRANCHES!! * ; * ; ---- ASSUMES ---- * ; * ; 1 USEC CYCLE TIME * ; * ;************************* READ16 LDY #020 ;'MUST FIND' COUNT RSYNC DEY ;IF CAN'T FIND MARKS BEQ RDERR ;THEN EXIT WITH CARRY SET RD1 LDA Q6L,X ;READ NIBL BPL RD1 ;**; NO PAGE CROSS! *** RSYNC1 EOR #0D5 ;DATA MARK 1? BNE RSYNC ;LOOP IF NOT NOP ;DELAY BETWEEN NIBLS RD2 LDA Q6L,X BPL RD2 ;**; NO PAGE CROSS! *** CMP #0AA ;DATA MARK 2? BNE RSYNC1 ;(IF NOT, IS IT DM1?) LDY #056 ;INIT NBUF2 INDEX ; (ADDED NIBL DELAY) RD3 LDA Q6L,X BPL RD3 ;**; NO PAGE CROSS! *** CMP #0AD ;DATA MARK 3? BNE RSYNC1 ;(IF NOT, IS IT DM1?) ; (CARRY SET IF DM3!) LDA #0 ;INIT CHECKSUM RDATA1 DEY / 19

10 STY IDX RD4 LDY Q6L,X BPL RD4 ;**; NO PAGE CROSS! *** RDNIBL1 EOR DNIBL,Y ;XOR 6-BIT NIBL LDY IDX ; NOTE: The storing of the Nybble into the NBUF has been deleted so that ; the formatter doesn't have to prenibblize the data pattern again ; STA NBUF2,Y ;STORE IN NBUF2 PAGE BNE RDATA1 ;TAKEN IF Y-REG NONZERO RDATA2 STY IDX RD5 LDY Q6L,X BPL RD5 ;**; NO PAGE CROSS! *** RDNIBL2 EOR DNIBL,Y ;XOR 6-BIT NIBL LDY IDX ; NOTE: The storing of the Nybble into the NBUF has been deleted so that ; the formatter doesn't have to prenibblize the data pattern again ; STA NBUF1,Y ;STORE IN NBUF1 PAGE INY BNE RDATA RD6 LDY Q6L,X ;READ 7-BIT CSUM NIBL BPL RD6 ;**; NO PAGE CROSS! *** RDNIBL3 CMP DNIBL,Y ;IF LAST NBUF1 NIBL NOT BNE RDERR ;EQUAL CHKSUM NIBL THEN ERR RD7 LDA Q6L,X BPL RD7 ;**; NO PAGE CROSS! *** CMP #0DE ;FIRST BIT SLIP MARK? BNE RDERR ;(ERR IF NOT) NOP ;DELAY BETWEEN NIBLS RD8 LDA Q6L,X BPL RD8 ;**; NO PAGE CROSS! *** CMP #0AA ;SECOND BIT SLIP MARK? BEQ RDEXIT ;(DONE IF IT IS) RDERR SEC ;INDICATE 'ERROR EXIT' RTS ;RETURN FROM READ16 OR RDADR RDEXIT CLC RTS ; # END OF FILE: FMTREAD.TEXT ; # LINES : 118 ; # CHARACTERS : 5863 ; # Formatter : Assembly Language Reformatter (06 January 1998) ; # Author : David T. Craig @compuserve.com -- Santa Fe, New Mexico USA / 19

11 ; # PROJECT : Apple /// SOS DISK /// Formatter Device Driver 1.30 (6502 Assembly Source Code) ; # FILE NAME: FMTWRADDR.TEXT TITLE "16-SECTOR WRITE ADDRESS" PAGE ;******************************* ; * ; WRITE ADR FIELD SUBROUTINE * ; (16-SECTOR FORMAT) * ; WRITES SPECIFIED NUMBER OF * ; 40-USEC (10-BIT) SELF-SYNC * ; NIBLS, ADR FIELDS 16-SECTOR * ; START MARKS ($D5,$AA,$96), * ; BODY (VOLUME, TRACK, SECTOR,* ; CHECKSUM), END FIELD MARKS, * ; AND THE WRITE TURN-OFF NIBL.* ; * ;******************************* ; * ; ON ENTRY * ; * ; THE LOCATIONS VOLUME, TRK, * ; AND NSECT MUST CONTAIN THE * ; DESIRED VOLUME, TRACK, AND * ; SECTOR VALUES DESIRED. * ; * ; THE PROPER DRIVE MUST BE * ; ENABLED AND UP TO SPEED IN * ; READ MODE (Q7L, Q6L). * ; * ; X-REG CONTAINS SLOTNUM * ; TIMES 16. * ; * ; Y-REG CONTAINS NUMBER OF * ; SELF-SYNC NIBLS DESIRED * ; MINUS 1. * ; (0 FOR 256 NIBLS) * ; * ;******************************* ; * ; REQUIRES * ; * ; 1 USEC CYCLE * ; * ;******************************* ; * ; CAUTION * ; * ; MOST OF THIS CODE IS TIME * ; CRITICAL. OBSERVE ALL * ; 'NO PAGE CROSS!' WARNINGS * ; ON BRANCHES. * ; * ;******************************* WADR16 SEC ;ANTICIPATE WR PROT ERR LDA Q6H,X ;INTO 'WR PROT SENSE' MODE LDA Q7L,X ;SENSE IT (NEG=PROTECTED) BMI WADRTS ;ERR EXIT IF PROTECTED LDA #0FF ;SELF-SYNC NIBL STA Q7H,X ;WRITE FIRST NIBL CMP Q6L,X ;(4) BACK TO WRITE MODE PHA ;(3) FOR DELAY PLA ;(4) WSYNC1 JSR WADRTS1 ;(12) FOR 40-USEC NIBLS JSR WADRTS1 ;(12) STA Q6H,X ;(5) WRITE NIBL CMP Q6L,X ;(4) (BACK TO WRITE MODE) NOP ;(2) FOR DELAY DEY ;(2) NEXT OF 'N' NIBLS BNE WSYNC1 ;(3) **; NO PAGE CROSS! *** LDA #0D5 ;(2) ADR MARK JSR WNIBLB2 ;(15,9,6) WRITE IT LDA #0AA ;(2) ADR MARK JSR WNIBLB2 ;(15,9,6) WRITE IT LDA #096 ;(2) 16-SECTOR ADR MARK JSR WNIBLB2 ;(15,9,6) WRITE IT LDA NVOL ;(3) JSR WBYTE ;(14,9,6) WRITE NVOL (ODD, THEN EVEN, BITS.) / 19

12 LDA TRK ;(3) WRITE TRACK NUMBER JSR WBYTE ;(14,9,6) ODD, THEN EVEN, BITS) LDA NSECT ;(3) WRITE SECTOR NUMBER JSR WBYTE ;(14,9,6) (ODD, THEN EVEN, BITS) LDA NVOL ;(3) EOR TRK ;(3) FORM ADR FIELD CHECKSUM EOR NSECT ;(3) PHA ;(3) SAVE FOR EVEN BITS LSR A ;(2) ALIGHN ODD BITS ORA AA ;(3) SET CLOCK BITS ; (PRECISE TIMING, 32 CYCLES PER NIBL) STA Q6H,X ;(5) WRITE CHECKSUM ODD BITS LDA Q6L,X ;(4) BACK TO WRITE MODE PLA ;(4) RECOVER FOR EVEN BITS ORA #0AA ;(2) SET CLOCK BITS JSR WNIBLA ;(17,9,6) WRITE THEM LDA #0DE ;(2) END MARK JSR WNIBLB2 ;(15,9,6) WRITE IT LDA #0AA ;(2) END MARK JSR WNIBLB2 ;(15,9,6) WRITE IT LDA #0EB ;(2) END MARK JSR WNIBLB2 ;(15,9,6) 'WRITE TURN-OFF' CLC ;INDICATE NO WR PROT ERR WADRTS LDA Q7L,X ;OUT OF WRITE MODE LDA Q6L,X ;TO READ MODE WADRTS1 RTS ;RETURN WBYTE PHA ;(3) PRESERVE FOR EVEN BITS LSR A ;(2) ALIGN ODD BITS ORA AA ;(3) SET CLOCK BITS STA Q6H,X ;(5) WRITE NIBL CMP Q6L,X ;(4) PLA ;(4) RECOVER FOR EVEN BITS NOP ;(2) NOP ;(2) FOR DELAY NOP ;(2) ORA #0AA ;(2) SET CLOCK BITS WNIBLA NOP ;(2) (17,9,6) ENTRY WNIBLB2 NOP ;(2) (15,9,6) ENTRY PHA ;(3) FOR PLA ;(4) DELAY WRNIBL STA Q6H,X ;(5) WRITE NIBL CMP Q6L,X ;(4) RTS ;(6) RETURN. ; # END OF FILE: FMTWRADDR.TEXT ; # LINES : 118 ; # CHARACTERS : 7495 ; # Formatter : Assembly Language Reformatter (06 January 1998) ; # Author : David T. Craig @compuserve.com -- Santa Fe, New Mexico USA / 19

13 ; # PROJECT : Apple /// SOS DISK /// Formatter Device Driver 1.30 (6502 Assembly Source Code) ; # FILE NAME: FMTFORMAT.TEXT TITLE "16-SECTOR FORMATTER" ; ; THIS IS THE 'SEEK' ROUTINE ; SEEKS TRACK 'N' IN SLOT #X/$ ; DOES NOT CARE WHETHER ON DRIVE 0 OR 1 OR N ; MYSEEK ASL A ASL CURTRK ;SEEK IS IN HALFTRACKS STA TRKN ;SAVE DESTINATION TRACK(*2) TXA ;TXY ROUTINE LSR A LSR A LSR A LSR A TAY LDA TRKN ;AND WHERE I'M GOING TO JSR SEEK ;GO THERE! LSR CURTRK ;DIVIDE BACK DOWN RTS PAGE ;************************************************ ; * ; FORMATTER INITIALIZATION SUBROUTINE * ; * ; This subroutine is called by the * ; driver during OPEN; it will perform * ; all necessary startup initialization * ; prior to opening the FORMATTER driver. * ; * ; INPUT : none * ; OUTPUT: NONE * /RRA82237/ ; * ;************************************************ ; for 1.1 release: nothing to do since Rev0 ROM not supported /RRA82237/ FMTSTARTUP.EQU * LDA #0 ;GOOD RTS PAGE ;************************************************** ; * ; FORMATTER SUBROUTINE * ; * ; INPUT: X = DRIVE TO BE FORMATTED (1..4) * ; 'USERBUF' POINTER INITIALIZED. * ; * ; OUTPUT: AC = RETURN CODE AS FOLLOWS: * ; 0 : GOOD COMPLETION * ; 1 : UNABLE TO FORMAT * ; 2 : WRITE-PROTECTED * ; 3 : DRIVE TOO SLOW * /RRA82237/ ; 4 : DRIVE TOO FAST * /RRA82237/ ; * ;************************************************** DSKFORM.EQU * ; SELECT THE CORRECT DRIVE: LDY SEL1,X ;GET FIRST SELECT LDA 0C000,Y ;SELECT # LDY SEL2,X ;GET SECOND SELECT LDA 0C000,Y ;SELECT # LDY SEL3,X ;GET THIRD SELECT LDA 0C000,Y ;SELECT # CPX #1 ;INTERNAL (.D1)? BNE $030 ;=>NO, IT'S EXTERNAL LDA 0C0EA ;SELECT INTERNAL JMP $ $030 LDA 0C0EB ;SELECT EXTERNAL ; SET UP THE ENVIRONMENT: $032 LDA E_REG / 19

14 STA E_SAVE ;SAVE CALLER ENV ORA #83 ;1 MHz, ROM enabled ; AND #0FF-10 ;inhibit the RESET STA E_REG PHP ;SAVE CALLER INHIBITS PLA STA P_SAVE ; SAVE THE ROM'S ZEROPAGE AREA: LDX #31. ;INDEX $035 LDA 1480,X ;SAVE EXTEND STA XTNDSAVE,X LDA 80,X STA ZEROSAVE,X DEX BPL $ ; START THE MOTOR: LDX #060 ;ALL APPLE-III DRIVES ARE STX IBSLOT LDA MOTORON,X ;IN SLOT ; PRENIBBLIZE THE DATA BUFFER PRIOR TO WRITING (WHILE MOTORING-UP): ; Note: PRENIB16 returns to us in 1 MHz mode LDA E_REG ;SET 2 MHz MODE FOR AND #7F ; FASTER STA E_REG ; PRENIB OPERATION LDA USERBUF ;SET DATA ADDRESS STA BUF ; TO POINT TO LDA USERBUF+1 ; THE CALLER'S STA BUF+1 ; BUFFER LDA USERBUF+2 ;ALSO SET XTND BYTE STA 1400+BUF JSR PRENIB16 ;PRENIB THE BUFFER! LDA #0D7 ;ALMOST 1 SECOND STA MONTIME ; RECALIBRATE THE HEAD WHILE THE MOTOR COMES UP TO SPEED: LDA #80. ;FAKING TRACK 80 FORCES RECAL STA CURTRK LDA #0 ;WE WANNA GO TO ZEEEEERO! JSR MYSEEK ;HONNNNNNNNK! WAITUP LDA MONTIME+1 ;MOTOR UP TO SPEED? BEQ $040 ;=>YES JSR MSWAIT ;NO, WAIT FOR A BIT JMP WAITUP ; INITIALIZE THINGS: $040 SEI ;NO IRQ DURING FORMATTING LDA #0 ;SET INTERRUPT RETRIES STA INTRTRY ; TO ZERO (NONE OCCURRED) LDA #80 ;SET INHIBIT INDICATOR STA IMASK ; TO SAY 'NO ENABLE,PLEASE' LDA #1 ;RANDY SAYS ALL SARA DISKETTES WILL BE VOLUME STA NVOL ;FOR FORMATTER LDA #0AA ;SET Z-PAG LOC TO $AA FOR STA AA ;TIME DEPENDENT REFERENCES LDA DCB_MAXSYNC ; /RRA82237/ CLC ;USE LARGER VALUE /RRA82237/ ADC #2 ; TO START OFF /RRA82237/ STA NSYNC ;BEGINNING SELF-SYNC NIBLS LDA #0 ;START ON TRACK ZERO STA TRK FORMTRK LDA TRK LDX # JSR MYSEEK ;GOTO NEXT TRACK ; See if the diskette is Write-Protected: LDX # / 19

15 LDA Q6H,X ;SENSE WRITEPROT MODE LDA Q7L,X TAY ;SAVE RESULT LDA Q7L,X ;BACK INTO LDA Q6L,X ; READ MODE TYA BPL $010 ;IT'S OK LDA # JMP FORMDONE ;FLAG WRITE PROTECT $010 JSR WT16 ;WRITE AND VERIFY TRACK. /RRA82237/ BCC $020 ;=>NO ERROR ; BEFORE SAYING IT'S BAD MEDIA, SEE IF THE DRIVE'S WAY TOO FAST: /RRA82237/ LDA #1 ;ASSUME BAD MEDIA /RRA82237/ LDY NSYNC ;GET IT /RRA82237/ CPY DCB_MINSYNC ;GAPS TOO SMALL? /RRA82237/ BCS $015 ;GAPS OK: BAD MEDIA /RRA82237/ LDA #4 ;"DRIVE TOO FAST" /RRA82237/ $015 JMP FORMDONE ; THE MEDIA FORMATTED OK...BUT THE DRIVE MIGHT STILL BE TOO SLOW OR TOO FAST $020 LDY NSYNC ;GET IT /RRA82237/ CPY DCB_MINSYNC ;GAPS TOO SMALL? /RRA82237/ BCS $025 ;GAPS LARGE ENOUGH /RRA82237/ LDA #4 ;"DRIVE TOO FAST" /RRA82237/ JMP FORMDONE ; /RRA82237/ $025 CPY DCB_MAXSYNC ;GAPS TOO LARGE? /RRA82237/ BCC $030 ;->OK /RRA82237/ LDA #3 ;"DRIVE TOO SLOW" /RRA82237/ JMP FORMDONE ; /RRA82237/ $030 LDA DCB_SECTRETRY ;SECTOR RETRIES /RRA82258/ STA RETRYCNT ; TO FIND SECTOR FINDS0.EQU * DEC RETRYCNT ;DONE RETRIES? BNE $010 ;=>NO, KEEP RETRYING LDA #1 ;'UNABLE TO FORMAT' ERROR JMP FORMDONE $010 LDX # JSR RDADR16 ;READ ADR FIELD BCS FINDS0 ;RETRY IF ERR LDA SECT ;CHECK SECTOR THAT WAS READ BNE FINDS0 ;CONTINUE SEARCHING IF NOT SECT LDX # JSR READ16 ;NOW READ DATA FIELD BCS FINDS0 ;CONTINUE SEARCH IF ERR ; (NOW POSITIONED PROPERLY FOR NEXT TRACK) INC TRK ;INCREMENT TRACK NUMBER LDA TRK CMP #35. ;CONTINUE IF LESS THAN BCC FORMTRK LDA #0 ;GOOD COMPLETION FORMDONE PHA ;SAVE RETURN CODE LDX # LDA MOTOROFF,X ;TURN MOTOR OFF LDA # JSR MYSEEK ;RESTORE HEAD TO TRACK ; RESTORE THE ROM'S ZEROPAGE AREA: LDX #31. ;INDEX $035 LDA XTNDSAVE,X ;RESTORE EXTEND STA 1480,X LDA ZEROSAVE,X STA 80,X DEX BPL $ ; Restore the caller's Environment: LDA P_SAVE ;RESTORE PHA ; INHIBITS PLP LDA E_SAVE ;RESTORE STA E_REG ; ENVIRONMENT / 19

16 PLA ;RESTORE RETURN CODE RTS ; AND RETURN. ; # END OF FILE: FMTFORMAT.TEXT ; # LINES : 239 ; # CHARACTERS : ; # Formatter : Assembly Language Reformatter (06 January 1998) ; # Author : David T. Craig @compuserve.com -- Santa Fe, New Mexico USA / 19

17 ; # PROJECT : Apple /// SOS DISK /// Formatter Device Driver 1.30 (6502 Assembly Source Code) ; # FILE NAME: FMTWTRACK.TEXT ;***************************** ; * ; WRITE TRACK SUBROUTINE * ; * ;***************************** ; ; WE HAVE A COUNTER, TRKRETRY, WHICH PREVENTS WTRACK16 FROM RETRYING /RRA82237/ ; FOREVER. THE EXTENSIVE RETRIES CAUSED THE TRACK TO PRECESS ON /RRA82237/ ; SUCCESSIVE WRITES, POSSIBLY ALLOWING A DAMAGED SPOT ON THE MEDIA TO/RRA82237/ ; BE 'SLID' INTO AN INTERSECTOR GAP. SUBSEQUENT DATA WRITES COULD /RRA82237/ ; THEN ENCOUNTER THE DAMAGED AREA. /RRA82237/ ; WT16.EQU * ;/RRA82237/ LDA DCB_TRKRETRY ;MAX RETRIES TO DO THE TRACK /RRA82237/ STA TRKRETRY ; TO PREVENT TOO MUCH TRYING /RRA82237/ ; On the first attempt, deliberately write too large a seam. This ; ensures that ALL of the track is erased WTRETRY.EQU * ; /RRA82258/ LDY #128. ;128 NIBS PRIOR SECTOR LDA #0 ;start at sector 0 /RRA82258/ STA NSECT ; /RRA82258/ JMP WSECT0 ; TO INSURE NO BLANK SPOT BETW 15 & WSECT LDY NSYNC ;CURRENT NUM OF GAP SELF-SYNC NIBLS WSECT0.EQU * LDX # JSR WADR16 ;WRITE GAP AND ADR FIELD BCC $010 ;=>GOOD, NOT WRITE-PROTECTED JMP WEXIT2 ;ERR IF WRITE PROTECTED $010 LDX # JSR WRITE16 ;WRITE SECTOR FROM NBUF1, NBUF BCC $020 ;=>OK JMP WEXIT2 ;ERR IF WRITE PROTECTED $020 INC NSECT ;NEXT OF 16 SECTORS LDA NSECT CMP # BCC WSECT ;CONTINUE IF NOT DONE PAGE ;**************************** ; * ; VERIFY ROUTINE * ; * ; VERIFIES THAT THE FIRST * ; SECTOR ENCOUNTERED IS * ; SECTOR 0, AND THAT ALL * ; 16 SECTORS ARE READABLE * ; WITH MINIMAL RETRIES. * ; (2 REVOLUTIONS MAXIMUM) * ; * ; IF FIRST SECTOR IS NOT * ; SECTOR 0 THEN THE * ; CURRENT NUMBER OF SELF- * ; SYNC NIBLS IS DECR'D BY * ; 1. THEN SECTOR * ; 15 IS LOCATED SO AS TO * ; POSITION THE NEW TRACK * ; REWRITE. * ; * ; IF UNABLE TO READ ANY * ; SECTOR THEN THE ENTIRE * ; TRACK IS REWRITTEN. * ; * ;**************************** PAGE LDY #16.-1 ;sect0 is special /RRA82258/ STY NSECT ;SET 16 BYTES OF LDA DCB_SECTRETRY ;SECTOR FOUND TABLE STA RETRYCNT ;TO SOMETHING NONNEGATIVE CLRFOUND STA FOUND,Y DEY BPL CLRFOUND ; Delay for 40uSec per NSYNC byte, to ensure that the gap between /RRA82340/ ; sector 15 & sector 0 is large enough. /RRA82340/ / 19

18 LDA NSYNC ;get current count /RRA82340/ SEC ;two already past and /RRA82340/ SBC #5 ; five for sync'ing /RRA82340/ TAY ; /RRA82340/ S0DELAY.EQU * ; /RRA82340/ JSR WEXIT2 ;(12) /RRA82340/ JSR WEXIT2 ;(12) /RRA82340/ PHA ;(3) /RRA82340/ PLA ;(4) /RRA82340/ NOP ;(2) /RRA82340/ NOP ;(2) /RRA82340/ DEY ;(2) /RRA82340/ BNE S0DELAY ;(3) /RRA82340/ ; See if we have a sector-zero here: LDX # JSR RDADR16 ;READ NEXT ADDRESS FIELD BCS REWRITE ;ERR, LOCATE SECT 15 AND REWRITE TRK LDA SECT ;WAS IT SECTOR 0? BEQ VDATA ;YES, NOW VERIFY DATA FIELD ; NO SECTOR 0? THEN SYNC GAPS ARE TOO LARGE. SHRINK 'EM DEC NSYNC LDA NSYNC CMP DCB_MINSYNC ;IF TOO SMALL, UNRECOVERABLE /RRA82237/ BCS REWRITE ;OK, REWRITE AFTER DATA FLD SEC ;DRIVE EXTREMELY FAST /RRA82237/ RTS ; (CALLER WILL CHECK NSYNC) /RRA82237/ ; Make sure we can read the track we just wrote VSECT LDX # JSR RDADR16 ;READ AN ADDRESS FIELD BCS VERR1 ;RETRY IF ERR VDATA LDX # JSR READ16 ;READ DATA FIELD BCS VERR1 ;=>it's bad... /RRA82258/ LDY SECT ;THIS IS SECTOR READ LDA FOUND,Y ;ALREADY FOUND? BMI VERR1 ;YES, IGNORE IT LDA #0FF STA FOUND,Y ;INDICATE THIS SECT NOW FOUND DEC NSECT ;FOUND 16 SECTORS? BPL VSECT ;NO, LOOK FOR NEXT ; REMOVED 'BLIND DECREMENT' OF NSYNC ON TRACKS /RRA82237/ WEXIT1 CLC ;INDICATE NO ERROR RTS ;RETURN VERR1 DEC RETRYCNT ;NEXT OF 48 SECTOR TRIES BNE VSECT ;(KEEP TRYING) ; We can't get a good verify...maybe we should rewrite the track DEC TRKRETRY ;MORE RETRIES? /RRA82237/ BNE REWRITE ;->YES, TRY AGAIN /RRA82237/ SEC ;UNABLE TO WRITE & VERIFY /RRA82237/ RTS ; /RRA82237/ ; Read Sector 15 data to position for track retry REWRITE.EQU * ; /RRA82258/ LDA DCB_SECTRETRY ;MAX RETRIES /RRA82258/ ASL A ; *2 for good find /RRA82258/ STA RETRYCNT ; /RRA82258/ S15LOC LDX # JSR RDADR16 ;READ ADDRESS FIELD BCS NOTS15 ;ERR, TRY UP TO 128 TIMES LDA SECT ;SECTOR THAT WAS READ CMP #15. ; SECTOR 15? BEQ PASS15 ;YES, GO FOR IT. /RRA82258/ NOTS15 DEC RETRYCNT BNE S15LOC ;TRY FOR SECT 15 AGAIN SEC ;SET CARRY TO INDICATE VERIFY ERR WEXIT2 RTS ;AND RETURN TO FORMATTER / 19

19 ; Delay to let most of sector 15's data pass by, then go back and /RRA82258/ ; rewrite the track (including the 128-nibbles of seam). This assures/rra82258/ ; that we will rewrite the track entirely, and that sector 0 will be /RRA82258/ ; aligned at roughly the same place as it was on the prior try. /RRA82258/ PASS15.EQU * ; /RRA82258/ LDX # ;LET MOST GO BY /RRA82258/ VFYDELAY.EQU * ; /RRA82258/ JSR WEXIT2 ;(12) /RRA82258/ JSR WEXIT2 ;(12) /RRA82258/ BIT 0 ;( 3) /RRA82258/ DEX ;( 2) /RRA82258/ BNE VFYDELAY ;( 3) /RRA82258/ JMP WTRETRY ;WRITE TRACK FROM HERE IF NO ERR. ; # END OF FILE: FMTWTRACK.TEXT ; # LINES : 172 ; # CHARACTERS : ; # Formatter : Assembly Language Reformatter (06 January 1998) ; # Author : David T. Craig @compuserve.com -- Santa Fe, New Mexico USA ### / 19

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

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

; Once Initialized, monitor character in calls to CN05 ; set carry for input, to be tested CN35 C SEC

; Once Initialized, monitor character in calls to CN05 ; set carry for input, to be tested CN35 C SEC // // Serialcode.s // 256 Byte Prom P8 and 512 Byte PROM P9A (second version) for Apple II Serial Card // P9A differs from P9 by adding RTS/ACK software flow control to output and // by removing batch

More information

COSC 243. Assembly Language Techniques. Lecture 9. COSC 243 (Computer Architecture)

COSC 243. Assembly Language Techniques. Lecture 9. COSC 243 (Computer Architecture) COSC 243 Assembly Language Techniques 1 Overview This Lecture Source Handouts Next Lectures Memory and Storage Systems 2 Parameter Passing In a high level language we don t worry about the number of parameters

More information

Regarding the change of names mentioned in the document, such as Mitsubishi Electric and Mitsubishi XX, to Renesas Technology Corp.

Regarding the change of names mentioned in the document, such as Mitsubishi Electric and Mitsubishi XX, to Renesas Technology Corp. To all our customers Regarding the change of names mentioned in the document, such as Mitsubishi Electric and Mitsubishi XX, to Renesas Technology Corp. The semiconductor operations of Hitachi and Mitsubishi

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

A Technical Overview of Commodore Copy Protection. Glenn Holmer ( ShadowM ) World of Commodore Expo, 12/01/2007

A Technical Overview of Commodore Copy Protection. Glenn Holmer ( ShadowM )   World of Commodore Expo, 12/01/2007 A Technical Overview of Commodore Copy Protection Glenn Holmer ( ShadowM ) www.lyonlabs.org/commodore/c64.html World of Commodore Expo, 12/01/2007 Why Talk About This? These skills were a black art to

More information

Apple /// Business BASIC Peek/Poke Invokable Module Information

Apple /// Business BASIC Peek/Poke Invokable Module Information APPLE /// COMPUTER INFORMATION Apple /// Business BASIC Peek/Poke Invokable Module Information Source Dr. John Jeppson SOFTALK magazine -- August 1982 -- pages 38-48 Compiled By David T Craig -- December

More information

Code Secrets of Wolfenstein 3D IIGS. Eric Shepherd

Code Secrets of Wolfenstein 3D IIGS. Eric Shepherd Code Secrets of Wolfenstein 3D IIGS Eric Shepherd Fast Screen Refresh with PEI Slamming Or, Dirty Tricks with the Direct Page IIGS Features We Can Abuse Super high-resolution graphics shadowing Bank $01

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

NAM M6800 DISK-BUG DS VER 3.5 OPT PAG

NAM M6800 DISK-BUG DS VER 3.5 OPT PAG NAM M6800 DISK-BUG DS VER 3.5 OPT PAG Floppy Disk Controller Debug Monitor Written 27 Aug 1980 Michael Holley Record of modifications 18 OCT 1981 Disk routines DC-1 23 JAN 1982 Command Table 8 MAY 1982

More information

DAN64: an AVR based 8-bit Microcomputer

DAN64: an AVR based 8-bit Microcomputer DAN64: an AVR based 8-bit Microcomputer Juan J. Martínez jjm@usebox.net Manual for V.R - May 0, 06 Features Composite video black and white output, 56 x 9 resolution, x 4 characters (8 x 8 pixels font,

More information

Call A.P.P.L.E. TOME OF COPY PROTECTION

Call A.P.P.L.E. TOME OF COPY PROTECTION Call A.P.P.L.E. World s Largest Apple User Group Since 1978 www.callapple.org TOME OF COPY PROTECTION Technical Errata for First Printing Compiled August 2018 Changes are Bold Page 20 Half Tracks * BE5A:

More information

Example Programs for 6502 Microprocessor Kit

Example Programs for 6502 Microprocessor Kit Example Programs for 6502 Microprocessor Kit 0001 0000 0002 0000 GPIO1.EQU $8000 0003 0000 0004 0000 0005 0200.ORG $200 0006 0200 0007 0200 A5 00 LDA $0 0008 0202 8D 00 80 STA $GPIO1 0009 0205 00 BRK 0010

More information

Quicksort (for 16-bit Elements)

Quicksort (for 16-bit Elements) 2017-09-21 17:30 1/9 Quicksort (for 16-bit Elements) Quicksort (for 16-bit Elements) by Vladimir Lidovski aka litwr, 13 Aug 2016 (with help of BigEd) It is well known that the best, the fastest sort routine

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

COMPUTE! ISSUE 36 / MAY 1983 / PAGE 244

COMPUTE! ISSUE 36 / MAY 1983 / PAGE 244 Versatile Data Acquisition with VIC Doug Homer and Stan Klein COMPUTE! ISSUE 36 / MAY 1983 / PAGE 244 This simple method of adjusting the VIC's internal jiffy dock can slow it down to match your timing

More information

Programming Book for 6809 Microprocessor Kit

Programming Book for 6809 Microprocessor Kit Programming Book for 6809 Microprocessor Kit Wichit Sirichote, wichit.sirichote@gmail.com Image By Konstantin Lanzet - CPU collection Konstantin Lanzet, CC BY-SA 3.0, Rev1.2 March 2018 1 Contents Lab 1

More information

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

:31 1/9 RLE Toolkit for CC65 v 1.0

:31 1/9 RLE Toolkit for CC65 v 1.0 2017-09-21 17:31 1/9 RLE Toolkit for CC65 v 1.0 RLE Toolkit for CC65 v 1.0 By MagerValp. The homepage and sources to this Toolkit is available here. Check that page for potential updates to this code.

More information

JBit E1 (1) Subroutines. Preface. Usage. Tables. Program Layout

JBit E1 (1) Subroutines. Preface. Usage. Tables. Program Layout JBit E1 (1) Preface, Usage, Program Layout, Subroutines, Tables Preface JBit E1 (1) The E1 series will show you how to write a complete application with JBit. While the application is trivial by today

More information

BINARY LOAD AND PUNCH

BINARY LOAD AND PUNCH BINARY LOAD AND PUNCH To easily decrease the amount of time it takes to load a long tape (Cassette or paper) a BINARY formatting technique can be used instead of the conventional ASCII format used by the

More information

User Manual for KRUSADER. Ken s Rather Useless Symbolic Assembly Development Environment for the Replica 1 or is that Reasonably Useful? You decide!

User Manual for KRUSADER. Ken s Rather Useless Symbolic Assembly Development Environment for the Replica 1 or is that Reasonably Useful? You decide! User Manual for KRUSADER Ken s Rather Useless Symbolic Assembly Development Environment for the Replica 1 or is that Reasonably Useful? You decide! Ken Wessen ken.wessen@gmail.com Version 1.3 December

More information

1 Introduction Forth, the Language Why Forth? Comparing to other Forths Stack Checking... 5

1 Introduction Forth, the Language Why Forth? Comparing to other Forths Stack Checking... 5 1 Contents 1 Introduction 4 1.1 Forth, the Language......................... 4 1.1.1 Why Forth?.......................... 4 1.1.2 Comparing to other Forths................. 4 1.1.3 Stack Checking........................

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

Content. 1. General informations 2. direct addressing 3. indirect addressing 4. Examples including informations

Content. 1. General informations 2. direct addressing 3. indirect addressing 4. Examples including informations IV. Addressing Modi Content 1. General informations 2. direct addressing 3. indirect addressing 4. Examples including informations 1. General Informations Address range for data and program : the 65xx

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

8085 INSTRUCTION SET INSTRUCTION DETAILS

8085 INSTRUCTION SET INSTRUCTION DETAILS 8085 INSTRUCTION SET INSTRUCTION DETAILS DATA TRANSFER INSTRUCTIONS MOV Rd, Rs Copy from source to destination This instruction copies the contents of the source register Rs into the destination register

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

INSTRUCTION SET OF 8085

INSTRUCTION SET OF 8085 INSTRUCTION SET OF 8085 Instruction Set of 8085 An instruction is a binary pattern designed inside a microprocessor to perform a specific function. The entire group of instructions that a microprocessor

More information

Instruction Set Instruction set of 8085 can be classified in following groups: Data Transfer Instructions These instructions can perform data transfer operations between Registers of 8085 e.g. MOV 8085

More information

User s Guide. pico Viewer v.1.01

User s Guide. pico Viewer v.1.01 User s Guide pico Viewer 6502 v.1.01 ii User s Guide Copyright Notice This documentation and the software described herein are copyrighted with all rights reserved. Under the copyright laws, neither this

More information

(2) Explain the addressing mode of OR What do you mean by addressing mode? Explain diff. addressing mode for 8085 with examples.

(2) Explain the addressing mode of OR What do you mean by addressing mode? Explain diff. addressing mode for 8085 with examples. (1) Explain instruction format and Opcode format of 8085 μp with example. OR With help of examples, explain the formation of opcodes of 8085 OR What is an instruction? List type of instruction based on

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

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

G65SC802 G65SC816. Microcircuits. CMOS 8-Bit/16-Bit Microprocessor Family ADVANCE INFORMATION. Features. General Description. Features (G65SC802 Only)

G65SC802 G65SC816. Microcircuits. CMOS 8-Bit/16-Bit Microprocessor Family ADVANCE INFORMATION. Features. General Description. Features (G65SC802 Only) G65SC802 G65SC816 Microcircuits CMOS 8-Bit/16-Bit Microprocessor Family Features Advanced CMOS design for low power consumption and increased noise immunity Emulation mode for total software compatibility

More information

MC68705P3 Bootstrap ROM

MC68705P3 Bootstrap ROM MC68705P3 Bootstrap ROM ;This is a listing of the Bootstrap ROM which resides in Motorola's MC68705P3 single chip ;micros. Its sole purpose is to program its own EPROM by copying the data from an external

More information

ARM Assembly Language. Programming

ARM Assembly Language. Programming Outline: ARM Assembly Language the ARM instruction set writing simple programs examples Programming hands-on: writing simple ARM assembly programs 2005 PEVE IT Unit ARM System Design ARM assembly language

More information

Assembly Language Programming of 8085

Assembly Language Programming of 8085 Assembly Language Programming of 8085 1. Introduction A microprocessor executes instructions given by the user Instructions should be in a language known to the microprocessor Microprocessor understands

More information

OSIAC Read OSIAC 5362 posted on the course website

OSIAC Read OSIAC 5362 posted on the course website OSIAC 5362 Read OSIAC 5362 posted on the course website The Basic Structure of Control Unit m CLK Run/Inhibit Control Step Counter m Preset (to any new state) Reset IR Decoder/Encoder (combinational logic)

More information

SwiftLink-232 Application Notes (revised)

SwiftLink-232 Application Notes (revised) SwiftLink-232 Application Notes (revised) Introduction The SwiftLink-232 ACIA cartridge replaces the Commodore Kernal RS-232 routines with a hardware chip. The chip handles all the bit-level processing

More information

CPU08RM/AD REV 3 8M68HC08M. CPU08 Central Processor Unit. Reference Manual

CPU08RM/AD REV 3 8M68HC08M. CPU08 Central Processor Unit. Reference Manual CPU08RM/AD REV 3 68HC08M6 HC08M68HC 8M68HC08M CPU08 Central Processor Unit Reference Manual blank CPU08 Central Processor Unit Reference Manual Motorola reserves the right to make changes without further

More information

AN1287. MC68HC708LN56 LCD Utilities. Introduction. LCD Hardware General Information

AN1287. MC68HC708LN56 LCD Utilities. Introduction. LCD Hardware General Information Order this document by /D MC68HC708LN56 LCD Utilities By Rick Cramer CSIC Product Engineering Austin, Texas Introduction LCD Hardware General Information A set of software utilities that causes the LCD

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

NMOS 6510 Unintended Opcodes

NMOS 6510 Unintended Opcodes NMOS 6510 Unintended Opcodes no more secrets (v0.92-24/12/17) (w) 2013-2017 groepaz/solution, all rights reversed Contents Preface...I Scope of this Document...I Intended Audience...I License...I What

More information

Assembly Language Programming of 8085

Assembly Language Programming of 8085 Assembly Language Programming of 8085 Topics 1. Introduction 2. Programming model of 8085 3. Instruction set of 8085 4. Example Programs 5. Addressing modes of 8085 6. Instruction & Data Formats of 8085

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

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

; export symbols XDEF Entry ; export 'Entry' symbol ABSENTRY Entry ; for assembly entry point

; export symbols XDEF Entry ; export 'Entry' symbol ABSENTRY Entry ; for assembly entry point **************************************************************** * This program for CMPEN 472, Flash Memory Writing * * By Kyusun Choi, ID=0000 * * Date: 11/15/2017 * * Freescale CodeWarrior, for the HCS12C128

More information

ELECTRICAL ENGINEERING

ELECTRICAL ENGINEERING Serial : 1. JP_EE_Microprocessor_130618 CLASS TEST Delhi Noida Bhopal Hyderabad Jaipur Lucknow Indore Pune Bhubaneswar Kolkata Patna Web: E-mail: info@madeeasy.in Ph: 011-45124612 ELECTRICAL ENGINEERING

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

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

MAHALAKSHMI ENGINEERING COLLEGE TIRUCHIRAPALLI

MAHALAKSHMI ENGINEERING COLLEGE TIRUCHIRAPALLI MAHALAKSHMI ENGINEERING COLLEGE TIRUCHIRAPALLI-621213. QUESTION BANK DEPARTMENT: EEE SUB CODE: EE2324 YR/ SEM:III/ VI SUB NAME: MICROPROCESSORS & MICROCONTROLLERS UNIT 2- PROGRAMMING OF 8085 MICROPROCESSORS

More information

Altirra Hardware Reference Manual 05/17/17 Edition Avery Lee

Altirra Hardware Reference Manual 05/17/17 Edition Avery Lee Altirra Hardware Reference Manual 05/17/17 Edition Avery Lee Table of Contents 1.1. Introduction... 7 1.2. What's new in this edition... 8 1.3. Conventions in this manual... 11 1.4. Basic characteristics...

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

A T T E N T I O N. Know Your Computer and Be Sure You Are Using the Correct Software

A T T E N T I O N. Know Your Computer and Be Sure You Are Using the Correct Software A T T E N T I O N Know Your Computer and Be Sure You Are Using the Correct Software SWTPC has offered, or is now offering, three types of 6809 computers. In order to make SWTPC supplied software work correctly

More information

AN1239. HC05 MCU Keypad Decoding Techniques Using the MC68HC705J1A. Introduction

AN1239. HC05 MCU Keypad Decoding Techniques Using the MC68HC705J1A. Introduction Order this document by /D Rev. 1.0 HC05 MCU Keypad Decoding Techniques Using the MC68HC705J1A By David Yoder CSIC Applications Introduction This application note demonstrates the use of a matrix keypad

More information

Aug.3, W65C816S 8/16 bit Microprocessor

Aug.3, W65C816S 8/16 bit Microprocessor Aug., 9 WC8S 8/ bit Microprocessor WDC reserves the right to make changes at any time without notice in order to improve design and supply the best possible product. Information contained herein is provided

More information

W65C816S 8/16 bit Microprocessor

W65C816S 8/16 bit Microprocessor November 9, 8 WC8S 8/ bit Microprocessor WDC reserves the right to make changes at any time without notice in order to improve design and supply the best possible product. Information contained herein

More information

Free for personal use but you must have written permission to reproduce

Free for personal use but you must have written permission to reproduce www.commodore.ca www.commodore.ca Commodore Business Machines, Inc. 901 California Avenue Palo Alto, California 94304, USA Commodore/MOS Valley Forge Corporate Center 950 Rittenhouse Road Norristown, Pennsylvania

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

EE319 K Lecture 7. Address mode review Assembler, Debugging Psuedo ops 16 bit timer finite state machines. University of Texas ECE

EE319 K Lecture 7. Address mode review Assembler, Debugging Psuedo ops 16 bit timer finite state machines. University of Texas ECE EE319 K Lecture 7 Address mode review Assembler, Debugging Psuedo ops 16 bit timer finite state machines University of Texas ECE Texas and execution A $24 EEPROM $F800 $F801 $86 $F802 $24 $F803 }ldaa #36

More information

AN1742. Programming the 68HC705J1A In-Circuit By Chris Falk CSG Product Engineering Austin, Texas. Introduction. Overview

AN1742. Programming the 68HC705J1A In-Circuit By Chris Falk CSG Product Engineering Austin, Texas. Introduction. Overview Order this document by /D Programming the 68HC705J1A In-Circuit By Chris Falk CSG Product Engineering Austin, Texas Introduction Overview This application note describes how a user can program the 68HC705J1A

More information

MC68705U3 Bootstrap ROM

MC68705U3 Bootstrap ROM MC68705U3 Bootstrap ROM ;This is a listing of the Bootstrap ROM which resides in Motorola's MC68705U3 single chip ;micros. Its sole purpose is to program its own EPROM by copying the data from an external

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

Introduction to Assembly Language Programming (Instruction Set) 1/18/2011 1

Introduction to Assembly Language Programming (Instruction Set) 1/18/2011 1 Introduction to Assembly Language Programming (Instruction Set) 1/18/2011 1 High Level Language Compiler Assembly Language Assembler Machine Code Microprocessor Hardware 1/18/2011 2 8085A Instruction Set

More information

EXPERIMENT NO. 1 THE MKT 8085 MICROPROCESSOR TRAINER

EXPERIMENT NO. 1 THE MKT 8085 MICROPROCESSOR TRAINER OBJECT: EXPERIMENT NO. 1 THE MKT 8085 MICROPROCESSOR TRAINER To understand the structure and operating instruction of the microprocessor trainer. INTRODUCTION: The MKT 8085 is a single-board microcomputer,

More information

Lecture #2 January 30, 2004 The 6502 Architecture

Lecture #2 January 30, 2004 The 6502 Architecture Lecture #2 January 30, 2004 The 6502 Architecture In order to understand the more modern computer architectures, it is helpful to examine an older but quite successful processor architecture, the MOS-6502.

More information

Decoding bitstreams for fun and profit

Decoding bitstreams for fun and profit 2018-12-01 11:25 1/13 Decoding bitstreams for fun and profit Decoding bitstreams for fun and profit by lft This article describes a technique for extracting bitfields from a long sequence of bytes stored

More information

; export symbols ; export 'Entry' symbol. ; include derivative specific macros PORTA EQU $0000 PORTB EQU $0001 DDRA EQU $0002 DDRB EQU $0003

; export symbols ; export 'Entry' symbol. ; include derivative specific macros PORTA EQU $0000 PORTB EQU $0001 DDRA EQU $0002 DDRB EQU $0003 ******************************************************* * This program for CSE472, Flash Memory Writing * * By Kyusun Choi, ID=0000 * * Date: 11/14/2009 * * Freescale CodeWarrior, for the MC9S12C32 Program

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

H8/300L Series Programming Manual

H8/300L Series Programming Manual H8/300L Series Programming Manual Notice When using this document, keep the following in mind: 1. This document may, wholly or partially, be subject to change without notice. 2. All rights are reserved:

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

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

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

Appendix A: The ISA of a Small 8-bit Processor

Appendix A: The ISA of a Small 8-bit Processor Computer Architecture in VHDL 1 Appendix A: The ISA of a Small 8-bit Processor Introduction to Small8 An Instruction Set Processor (ISP) is characterized by its instruction set, address modes (means to

More information

Architecture & Instruction set of 8085 Microprocessor and 8051 Micro Controller

Architecture & Instruction set of 8085 Microprocessor and 8051 Micro Controller of 8085 microprocessor 8085 is pronounced as "eighty-eighty-five" microprocessor. It is an 8-bit microprocessor designed by Intel in 1977 using NMOS technology. It has the following configuration 8-bit

More information

Assembler Manual THE COMMODORE PET ASSEMBLER DEVELOPMENT SYSTEM

Assembler Manual THE COMMODORE PET ASSEMBLER DEVELOPMENT SYSTEM THE COMMODORE PET ASSEMBLER DEVELOPMENT SYSTEM Copyright 1979, Commodore Business Machines Professional Computer Division 1200 Wilson Drive West Chester, PA 19380 COPYRIGHT This software product is copyrighted

More information

SWTPC 6800/CT-1024/AC-30 Cassette Tape

SWTPC 6800/CT-1024/AC-30 Cassette Tape SWTPC 6800/CT-1024/AC-30 Cassette Tape Diagnostic Programs These two diagnostic programs have been written to generate and verify respectively cassette tapes generated on the SWTPC 6800 Computer System

More information

Grundlagen Microcontroller Processor Core. Günther Gridling Bettina Weiss

Grundlagen Microcontroller Processor Core. Günther Gridling Bettina Weiss Grundlagen Microcontroller Processor Core Günther Gridling Bettina Weiss 1 Processor Core Architecture Instruction Set Lecture Overview 2 Processor Core Architecture Computes things > ALU (Arithmetic Logic

More information

Programming. A. Assembly Language Programming. A.1 Machine Code. Machine Code Example: Motorola ADD

Programming. A. Assembly Language Programming. A.1 Machine Code. Machine Code Example: Motorola ADD A. Assembly Language Programming Programming of a computer system: Machine code direct execution Assembly language tool: assembler High level programming language tool: interpreter tool: compiler Programming

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

NET3001. Advanced Assembly

NET3001. Advanced Assembly NET3001 Advanced Assembly Arrays and Indexing supposed we have an array of 16 bytes at 0x0800.0100 write a program that determines if the array contains the byte '0x12' set r0=1 if the byte is found plan:

More information

EE319K Exam 1 Summer 2014 Page 1. Exam 1. Date: July 9, Printed Name:

EE319K Exam 1 Summer 2014 Page 1. Exam 1. Date: July 9, Printed Name: EE319K Exam 1 Summer 2014 Page 1 Exam 1 Date: July 9, 2014 UT EID: Printed Name: Last, First Your signature is your promise that you have not cheated and will not cheat on this exam, nor will you help

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

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

NMOS 6510 Unintended Opcodes

NMOS 6510 Unintended Opcodes NMOS 6510 Unintended Opcodes no more secrets (Christmas release, 24/12/14) (w) 2013-2014 groepaz/hitmen, all rights reversed Contents Preface...I Scope of this Document...I Intended Audience...I What you

More information

Its Assembly language programming

Its Assembly language programming 8085 Architecture & Its Assembly language programming Dr A Sahu Dept of Computer Science & Engineering IIT Guwahati 8085 Era and Features 8085 Outline Block diagram (Data Path) Bus Structure Register Structure

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

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

Hi Hsiao-Lung Chan, Ph.D. Dept Electrical Engineering Chang Gung University, Taiwan

Hi Hsiao-Lung Chan, Ph.D. Dept Electrical Engineering Chang Gung University, Taiwan ARM Programmers Model Hi Hsiao-Lung Chan, Ph.D. Dept Electrical Engineering Chang Gung University, Taiwan chanhl@maili.cgu.edu.twcgu Current program status register (CPSR) Prog Model 2 Data processing

More information

Note that none of the above MAY be a VALID ANSWER.

Note that none of the above MAY be a VALID ANSWER. ECE 270 Learning Outcome 4-1 - Practice Exam / Solution OUTCOME #4: An ability to design and implement computer logic circuits. Multiple Choice select the single most appropriate response for each question.

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

M0100. SOLOS (tm) /CUTER (tm) USER'S MANUAL Hollis Street P. O. Box 5260 Emeryville, CA San Mateo, CA (415) (415)

M0100. SOLOS (tm) /CUTER (tm) USER'S MANUAL Hollis Street P. O. Box 5260 Emeryville, CA San Mateo, CA (415) (415) M0100 SOLOS (tm) /CUTER (tm) USER'S MANUAL PROCESSOR TECHNOLOGY CORP. SOFTWARE TECHNOLOGY CORP. 6200 Hollis Street P. O. Box 5260 Emeryville, CA 94608 San Mateo, CA 94402 (415) 652-8080 (415) 349-8080

More information

PERIPHERAL INTERFACING Rev. 1.0

PERIPHERAL INTERFACING Rev. 1.0 This work is licensed under the Creative Commons Attribution-NonCommercial-Share Alike 2.5 India License. To view a copy of this license, visit http://creativecommons.org/licenses/by-nc-sa/2.5/in/deed.en

More information

Floating Point Routines for the 6502 by Roy Rankin and Steve Wozniak

Floating Point Routines for the 6502 by Roy Rankin and Steve Wozniak http://www.6502.org/source/floats/wozfp1.txt 31 October 2004 TABLE OF CONTENTS Floating Point Routines for the 6502 by Roy Rankin and Steve Wozniak Originally published in the August 1976 issue of Dr.

More information

ARM Instruction Set Architecture. Jin-Soo Kim Computer Systems Laboratory Sungkyunkwan University

ARM Instruction Set Architecture. Jin-Soo Kim Computer Systems Laboratory Sungkyunkwan University ARM Instruction Set Architecture Jin-Soo Kim (jinsookim@skku.edu) Computer Systems Laboratory Sungkyunkwan University http://csl.skku.edu Condition Field (1) Most ARM instructions can be conditionally

More information

PROGRAM CONTROL UNIT (PCU)

PROGRAM CONTROL UNIT (PCU) nc. SECTION 5 PROGRAM CONTROL UNIT (PCU) MOTOROLA PROGRAM CONTROL UNIT (PCU) 5-1 nc. SECTION CONTENTS 5.1 INTRODUCTION........................................ 5-3 5.2 PROGRAM COUNTER (PC)...............................

More information

The PC's keyboard. PC Keyboard Theory. Quality Information in one Place...

The PC's keyboard. PC Keyboard Theory. Quality Information in one Place... Interfacing the PC / Beyond Logic Quality Information in one Place... Parallel Ports Serial Ports Interrupts AT Keyboard Ports USB The PC's keyboard. Why would you want to interface the Keyboard? The IBM

More information