Zilog Z80 CPU Assembler Syntax Microprocessor and Interface II Eko Henfri B Mnemonic - 1 ADC ADD WITH CARRY ADD ADD AND LOGICAL AND BIT BIT TEST CALL CALL SUB ROUTINE CCF COMPLEMENT CARRY FLAG CP COMPARE CPD COMPARE AND DECREMENT CPDR COMPARE DECREMENT AND REPEAT CPI COMPARE AND INCREMENT CPIR COMPARE INCREMENT AND REPEAT CPL COMPLEMENT ACCUMULATOR DAA DECIMAL ADJUST ACCUMULATOR DEC DECREMENT DI DISABLE INTERRUPTS Mnemonic - 2 DJNZ DEC JUMP NON-ZERO EI ENABLE INTERRUPTS EX EXCHANGE REGISTER PAIR EXX EXCHANGE ALTERNATE REGISTERS HALT HALT, WAIT FOR INTERRUPT OR RESET IM INTERRUPT MODE 0 1 2 IN INPUT FROM PORT INC INCREMENT IND INPUT, DEC HL, DEC B INDR INPUT, DEC HL, DEC B, REPEAT IF B>0 INI INPUT, INC HL, DEC B INIR INPUT, INC HL, DEC B, REPEAT IF B>0 JP JUMP JR JUMP RELATIVE LD LOAD DATA TO/FROM REGISTERS/MEMORY Mnemonic - 3 LDD LOAD DECREMENT LDDR LOAD DECREMENT AND REPEAT LDI LOAD AND INCREMENT LDIR LOAD INCREMENT AND REPEAT NEG NEGATE ACCUMULATOR 2'S COMPLEMENT NOP NO OPERATION OR -- OTDR OUTPUT, DEC HL, DEC B, REPEAT IF B>0 OTIR OUTPUT, INC HL, DEC B, REPEAT IF B>0 OUT OUTPUT TO PORT OUTD OUTPUT, DEC HL, DEC B OUTI OUTPUT, INC HL, DEC B POP POP FROM STACK PUSH PUSH INTO STACK RES RESET BIT Mnemonic - 4 RET RETURN FROM SUB ROUTINE RETI RETURN FROM INTERRUPT RETN RETURN FROM NON MASKABEL INTERRUPT RL ROTATE LEFT register RLA ROTATE LEFT ACUMULATOR RLC ROTATE LEFT THROUGH CARRY register RLCA ROTATE LEFT THROUGH CARRY ACCUMULATUR RLD ROTATE LEFT DIGIT RR ROTATE RIGHT register RRA ROTATE RIGHT ACCUMULATOR RRC ROTATE RIGHT CIRCULAR register RRCA ROTATE RIGHT CIRCULAR ACCUMULATOR RRD ROTATE RIGHT DIGIT RST RESTART SBC SUBTRACT WITH CARRY Mnemonic - 5 SCF SET CARRY FLAG SET SET BIT SLA SHIFT LEFT ARITHMETIC register SRA SHIFT RIGHT ARITHMETIC register SRL SHIFT RIGHT LOGICAL register SUB SUBTRACTION XOR EXCLUSIVE OR Instruction Summary - 1 Mnemonic SZHPNC Description Notes ADC A,s ***V0* Add with Carry A=A+s+CY ADC HL,ss **?V0* Add with Carry HL=HL+ss+CY ADD A,s ***V0* Add A=A+s ADD HL,ss --?-0* Add HL=HL+ss ADD IX,pp --?-0* Add IX=IX+pp ADD IY,rr --?-0* Add IY=IY+rr AND s ***P00 Logical AND A=A&s BIT b,m ?*1?0- Test Bit m&{2^b} CALL cc,nn ------ Conditional Call If cc CALL CALL nn ------ Unconditional Call -[SP]=PC,PC=nn CCF --?-0* Complement Carry Flag CY=~CY CP s ***V1* Compare A-s CPD ****1- Compare and Decrement A-[HL],HL=HL-1,BC=BC-1 CPDR ****1- Compare, Dec., Repeat CPD till A=[HL]or BC=0 CPI ****1- Compare and Increment A-[HL],HL=HL+1,BC=BC-1 CPIR ****1- Compare, Inc., Repeat CPI till A=[HL]or BC=0 CPL --1-1- Complement A=~A Instruction Summary - 2 Mnemonic SZHPNC Description Notes DAA ***P-* Decimal Adjust Acc. A=BCD format DEC s ***V1- Decrement s=s-1 DEC xx ------ Decrement xx=xx-1 DEC ss ------ Decrement ss=ss-1 DI ------ Disable Interrupts DJNZ e ------ Dec., Jump Non-Zero EI ------ Enable Interrupts EX [SP],HL ------ Exchange [SP]<->HL EX [SP],xx ------ Exchange [SP]<->xx EX AF,AF' ------ Exchange AF<->AF' EX DE,HL ------ Exchange DE<->HL EXX ------ Exchange qq<->qq' HALT ------ Halt IM n ------ Interrupt Mode IN A,[n] ------ Input A=[n] IN r,[C] ***P0- Input r=[C] INC r ***V0- Increment r=r+1 B=B-1 till B=0 (except AF) (n=0,1,2) Instruction Summary - 3 Mnemonic SZHPNC Description Notes INC [HL] ***V0- Increment [HL]=[HL]+1 INC xx ------ Increment xx=xx+1 INC [xx+d] ***V0- Increment [xx+d]=[xx+d]+1 INC ss ------ Increment ss=ss+1 IND ?*??1- Input and Decrement [HL]=[C],HL=HL-1,B=B-1 INDR ?1??1- Input, Dec., Repeat IND till B=0 INI ?*??1- Input and Increment [HL]=[C],HL=HL+1,B=B-1 INIR ?1??1- Input, Inc., Repeat INI till B=0 JP [HL] ------ Unconditional Jump PC=[HL] JP [xx] ------ Unconditional Jump PC=[xx] JP nn ------ Unconditional Jump PC=nn JP cc,nn ------ Conditional Jump If cc JP JR e ------ Unconditional Jump PC=PC+e JR cc,e ------ Conditional Jump If cc JR(cc=C,NC,NZ,Z) LD dst,src ------ Load dst=src LD A,i **0*0- Load A=i LDD --0*0- Load and Decrement [DE]=[HL],HL=HL-1,# (i=I,R) Instruction Summary - 4 Mnemonic SZHPNC Description Notes LDDR --000- Load, Dec., Repeat LDD till BC=0 LDI --0*0- Load and Increment [DE]=[HL],HL=HL+1,# LDIR --000- Load, Inc., Repeat LDI till BC=0 NEG ***V1* Negate A=-A NOP ------ No Operation OR s ***P00 Logical inclusive OR A=Avs OTDR ?1??1- Output, Dec., Repeat OUTD till B=0 OTIR ?1??1- Output, Inc., Repeat OUTI till B=0 OUT [C],r ------ Output [C]=r OUT [n],A ------ Output [n]=A OUTD ?*??1- Output and Decrement [C]=[HL],HL=HL-1,B=B-1 OUTI ?*??1- Output and Increment [C]=[HL],HL=HL+1,B=B-1 POP xx ------ Pop xx=[SP]+ POP qq ------ Pop qq=[SP]+ PUSH xx ------ Push -[SP]=xx PUSH qq ------ Push -[SP]=qq RES b,m ------ Reset bit m=m&{~2^b} Instruction Summary - 5 Mnemonic SZHPNC Description Notes RET ------ Return PC=[SP]+ RET cc ------ Conditional Return If cc RET RETI ------ Return from Interrupt PC=[SP]+ RETN ------ Return from NMI PC=[SP]+ RL m **0P0* Rotate Left m={CY,m}<- RLA --0-0* Rotate Left Acc. A={CY,A}<- RLC m **0P0* Rotate Left Circular m=m<- RLCA --0-0* Rotate Left Circular A=A<- RLD **0P0- Rotate Left 4 bits {A,[HL]}={A,[HL]}<- ## RR m **0P0* Rotate Right m=->{CY,m} RRA --0-0* Rotate Right Acc. A=->{CY,A} RRC m **0P0* Rotate Right Circular m=->m RRCA --0-0* Rotate Right Circular A=->A RRD **0P0- Rotate Right 4 bits {A,[HL]}=->{A,[HL]} ## RST p ------ Restart SBC A,s ***V1* Subtract with Carry A=A-s-CY SBC HL,ss **?V1* Subtract with Carry HL=HL-ss-CY (p=0H,8H,10H,...,38H) Instruction Summary - 6 Mnemonic SZHPNC SCF -1 Description Notes Set Carry Flag CY=1 SET b,m ------ Set bit m=mv{2^b} SLA m **0P0* Shift Left Arithmetic m=m*2 SRA m **0P0* Shift Right Arith. m=m/2 SRL m **0P0* Shift Right Logical m=->{0,m,CY} SUB s ***V1* Subtract A=A-s XOR s ***P00 Logical Exclusive OR A=Axs Note (Flag Bits) F * 0 1 ? Flag unaffected Affected Reset Set unknown S S Sign flag (Bit 7) Z HC P/V N CY Z Zero flag (Bit 6) H Half Carry flag (Bit 4) Parity/Overflow flag (Bit 2, V=overflow) P N Add/Subtract flag (Bit 1) C Carry flag (Bit 0) Note (Data Adressing) n Immediate addressing nn Immediate extended addressing e Relative addressing (PC=PC+2+offset) [nn] Extended addressing [xx+d] Indexed addressing r Register addressing [rr] Register indirect addressing Implied addressing b Bit addressing p Modified page zero addressing (see RST) Note (Data Definition) DEFB n(,...) Define Byte(s) DEFB 'str'(,...) Define Byte ASCII string(s) DEFS nn Define Storage Block DEFW nn(,...) Define Word(s) Note (Registers) A B C D E Registers (8-bit) AF BC DE HL Register pairs (16-bit) F Flag register (8-bit) I Interrupt page address register (8-bit) IX IY Index registers (16-bit) PC Program Counter register (16-bit) R Memory Refresh register SP Stack Pointer register (16-bit) Note (Data and Registers) b One bit (0 to 7) cc Condition (C,M,NC,NZ,P,PE,PO,Z) d One-byte expression (-128 to +127) dst Destination s, ss, [BC], [DE], [HL], [nn] e One-byte expression (-126 to +129) m Any register r, [HL] or [xx+d] n One-byte expression (0 to 255) nn Two-byte expression (0 to 65535) pp Register pair BC, DE, IX or SP qq Register pair AF, BC, DE or HL qq' Alternative register pair AF, BC, DE or HL r Register A, B, C, D, E, H or L rr Register pair BC, DE, IY or SP s Any register r, value n, [HL] or [xx+d] src Source s, ss, [BC], [DE], [HL], nn, [nn] ss Register pair BC, DE, HL or SP xx Index register IX or IY Additional Note + - * / ^ Add/subtract/multiply/divide/exponent & ~ v x Logical AND/NOT/inclusive OR/exclusive OR <- -> Rotate left/right [] Indirect addressing [ ]+ -[ ] Indirect addressing auto-increment/decrement {} Combination of operands # Also BC=BC-1,DE=DE-1 ## Only lower 4 bits of accumulator A used LD Instruction The first thing you will want to do is to load a value into a register. This is done with the LD instruction. Here are some examples: ld a,0 ; loads the value0 into register a ld b,2 ; loads the value 2 into register b ld de,257 ; loads the value 257 into register de ;(same as loading 1 into d and 1 into e) ld d,$0A ; NOTE $8A represents a HEX number, ; %00100100 represents a BIN number, ; 52 just a decimal number. ; this loads $0A into d, $0A is the same as 10 ld a,d ; loads the current value of d into a (in this case 10) NOTE: An 8-bit regiser can only hold the values from 0-255 (%00000000%11111111),but a 16 bit register can hold the values 0-65535. The register HL, is primarily used for ADDRESSING, This means it usually points to another memory location. The video Memory is located at $FC00, so to have hl "point" to the video memory you use the command: ld hl,$FC00 ;loads the value $FC00 into register hl Now, to copy a value into the memory location that HL is pointing to, we do something called indirect addressing. ld a,%10101010 ld (hl),a ld a,(hl) ;loads thevalue %10101010 into reg. a ;loads the value %10101010 into the ;memory location that hl "points" to ;the value of HL is $fc00 therefore ;the value %10101010 is loaded into ;memory location $fc00, which happens ;to be the video memory :) ;IT DOES NOT CHANGE THE VALUE OF HL!! ;similiarly this loads the value at ;mem location $fc00 into the reg. a ADD/SUB The next thing to learn, is how to add and subtract from a register. To do this we use the instructions ADD and SUB. add add add add a,## hl,ss (where ss = bc,de,hl, or sp) ix,pp (where pp = bc,de,ix, or sp) iy,rr (where rr = bc,de,iy, or sp) These are the only ways that ADD can be used. ex: ld a,8 add a,10 ld hl,$FC00 ld bc,$00BB add hl,FCBB ;a=8 ;a=a+10 a=18 ;hl = $FC00 ;bc = $00BB ;hl=hl+bc hl = $fcbb ADD In order to add anything to the other registers, you must do it indIrectly:] ld b,8 ld a,b add a,5 ld b,a ;or ld bc,46 ld h,b ld l,c ld bc,52 add hl,bc ld b,h ld c,l ;b=8 ;a=b ;a='b+5' ;b='b+5' ;bc=46 ;you can't do'ld hl,bc' ; ; ;hl = bc+52 ;. ;bc =bc+52 SUB Now you know how to add, what about subtracting? sub ## ; a=a-## That's it! you can only SUB from a (the accumulator), therefore all other subtractions must be made indirectly. Here are some examples: ld a,16 sub 5 ld b,65 ld a,b sub 6 ld b,a ;a=16 ;a=a-5, a=11 ;b=65 ;a=65 ;a=65-6, a=59 ;b=59 ADD and SUB let you add or subtract any number, however if you only want to add or subtract the value 1 then you can use INC/DEC INC/DEC inc inc dec dec r ss r ss ;(where r=a,b,c,d,e,h,orl) ;(where ss=bc,de,hl, or sp) These are the ony cases we will use. Here are some examples: ld a,5 inc a ld b,a dec b ld bc,568 inc bc inc bc ;a=5 ;a=a+1, a=6 ;b=a, b=6 ;b=b-1, b=5 ;bc=568 ;bc=bc+1, bc=569 ;bc=bc+1, bc=570 PUSH To add an item to the stack we use the PUSH instruction. You can only PUSH the following registers: AF, BC, DE, HL, IX, IY Here are some examples: push af ;adds the valuestored in AF to the stack push bc ;adds the value storedin BC to the stack NOTE: The register still contains the value it had before being PUSHED It is very important that you DON'T exit the program before POPPING, all PUSHED values. POP To remove anitem from the stack we use the POP instruction. You can only POP to the following registers: AF, BC, DE, HL Here are some examples: pop af pop bc ;stores the value on the top of the ;stack in AF (removes that value from the stack) ;stores the value on the top of the ;stack in BC (removes that value from the stack) LABELS Labels area way to define a certain area in the program. To define labels, you must first enter the name of the label then a ":". Here are some examples: loop: ; this is a label ld a,5 push af ;just somestuff push bc inc a anotherlabel: ; this is another label NOTE: Labels cannotbe indented! JR The ASM code is always processed sequently, one instruction after the next. However, if you want to skip to a certain part of the code, or go back and repeat a previous portion you must jump there. There are 2 different ways to JUMP to another part of code. JR, and JP. There are a few differences that are discussed later, but they are VERY IMPORTANT! To jump to a certain part of code you must enter JR LABELNAME. Here are some examples: ld a,1 MyLabel: inc a jr MyLabel ;a=1 ;LABEL ;a=a+1 ;jump to LABEL NOTE: This code willcause an infinite loop. The code between 'MyLabel' and 'jr MyLabel‘ will be repeated over and over. JP The ASM code is always processed sequently, one instruction after the next. However, if you want to skip to a certain part of the code, or back to a previous portion you must jump there. There are 2 different ways to JUMP to another part of code. JR, and JP. There are a few differences that are discussed later, but they're VERY IMPORTANT! To jump to a certain part of code you must enter JP LABELNAME. Here are some examples: ld a,1 ;a=1 MyLabel: ;LABEL inc a ;a=a+1 jp MyLabel ;jump to LABEL In order to make jumps ONLY IF certain requirements are met, we use the following conditionals: C NC Z NZ M P PE PO (Carry) (No Carry) (Zero) (Not Zero) (Minus) (Positive) (Parity Even) (Parity Odd) You can already see some differences between JR and JP. JP allows the use of 4 more conditions! These conditions are based on how the F register is set. Remember it is the FLAG register. Here're some examples: ld a,5 ;a=5 Loop: ;MyLOOP Label dec a ;a=a-1 jp p,Loop ;if A is positive then jumpto Loop. ;(When the value of A changes F is ALWAYS updated) This loop will execute 6 times (a=5,4,3,2,1,0. DIFFERENCES BETWEEN JR/JP The Main difference between the 2 types of jumps (jr, jp) is the JR is a RELETIVE jump. When translated into machine code it essential says 'jump this many bytes forward/backward', for this reason, it has a limited range. If you plan on jumping further then the range allowed by JR you MUST use JP. JP is an ABSOLUTE jump. When translated into machine code it basicallysays 'jump to this location'. The advantage of JR over JP is bothsize and speed in the final compiled program. Another difference, which we have already seenis that JP allows you to use more conditions. JR does not support P, M, PO, or PE. DJNZ DJNZ is a very helpful instruction. It combines the [DEC -> JP nz, label] sequence used so often in loops. ld b,15 ;b=15, the number of times for the loop to execute Loop: ; all the cool loop stuff inside of here djnz Loop ;b=b-1, jump is b is NotZero NOTE: DJNZ always uses the register B. It decrements B, checks if B is nz, if so then jumps to the label. If the value of B is changed inside your loop code remember to use PUSH/POP so your values is not destroyed. ld a,0 ld b,15 Loop: push bc ;adds it to the stack ld b,4 ;b=4 add a,b ;a=a+b, a=a+4 pop bc ;gets our value of Bback! djnz Loop CP CP simply sets the FLAG register (F) based on the subtraction (A-s) CP S (where S = A,F,B,C,D,E,H,L,#,(hl),(iy+#),or (ix+#)) IF... THEN... ELSE To achieve an IF... THEN... ELSE statement(s) you must use a CP call followed by a JR, JP, or any other instruction that has conditionals (ret, call, ...) Here are some examples: ld b,5 ld a,5 ;b=5 ;a=5 cp b ;set flags based on (a-b) jr z,AequalsB ;if a=b -> a-b=0,therefore ;if the Zero flag is set JUMP to AequalsB : . AequalsB: ; : . You can also string them together like this: ld b,6 ;. ld c,5 ;. ld a,5 ;Set the init values cp jr cp jr jr b ;IF a=b z,AB ;THEN goto AB c ;IF a=c z,AC ;THEN goto AC NONE ;ELSE goto NONE (if it didn'tjump one of the other ; times then it must be an ELSE, NOTE:no conditia ; listed. Just a straight 'jr NONE') : . AB:: . AC: : . NONE: GREATER THAN, and LESS THAN: Compare A and B for =, < and > LD B, 7 LD A, 5 CP B ; Flags = status(A-B) JP Z, A_Equal_To_B ; IF(a-b)=0 THEN a=b JP NC, A_Greater_Than_B ; IF(a-b)>0 THEN a>b JP C, A_Lower_Than_B ; IF(a-b)<0 THEN a<b A_Greater_Than_B: (...) JP end_compare A_Lower_Than_B: (...) JP end_compare A_Equal_To_B: (...) end_compare: RET CALL Call allows you to jump to a different location in the ASM program, while saving where it was, so it can return to that location later. CALL cc,LABEL (where cc=c,nc,z,nz,p,m,pe,orpo) If the condition cc is true then it jumps to the label. CC is OPTIONAL. call _clrLCD call z,_clrLCD ; calls the ROM function to clear the LCD ; only calls the function if the Zeroflag is set RET RET, returns power back to where the last CALL statement was made, or back the TI/OS-SHELL, if no CALLs where made. It's actually similar to the stack, but it's easier to explain it this way. RET cc (where cc=c,nc,z,nz,p,m,pe,or po) If cc is true then the ret is executed. CC is OPTIONAL FUNCTIONS Putting the CALL and RET commands together you are given a powerful way to modulate your programs. You can create functions that perform certain tasks and even accept input and produce output. ld a,5 call Add3 ld c,b : . Add3: ld b,a inc b inc b inc b ret ; calls our function Add3which adds 3 to the reg. A ; and stores the new value in B ; NOW b=a+3, or 8 ; c=b, c=8 ;b=a ; ; ;b=a+3 ;returns control to next line after CALL was made.