Assembly language statements are terminated by a colon (:) or end of line (<RET>). When terminated by a colon, it is necessary to leave a space between the colon and a preceding segment register name otherwise it may be misinterpreted as a segment override. See the Segment Override sub-section for details.
In the example shown later under the heading The assembly process, two labels are defined and used. Labels have the same rules as standard BBC BASIC variable names; they should start with a letter and not start with a keyword.
Note that although the run-time assembler will allow you to use an array element as a label, this is not valid BBC BASIC syntax and it is not accepted by the compiler (cruncher). You can use a structure member as a label, so long as it starts with a letter.
[;start assembly language program etc MOV EAX,ECX ;In-line comment : POP EBX ;start add JNZ loop ;Go back if not finished : RET ;Return etc ;end assembly language program:]
Note that since BBC BASIC for Windows is a 32-bit program, and the assembler will normally be used to generate 32-bit code in a 'flat' address space, the segment size is 2^32 bytes (4 Gbytes!). You are therefore most unlikely to want to perform inter-segment jumps or calls.
Short jump JMPS or JMP SHORT Far call CALLF or CALL FAR Far jump JMPF or JMP FAR Far return RETF
Conditional jumps are assumed to be short (8-bit displacement). Near conditional jumps (32-bit displacement) must be explicitly specified by adding the NEAR prefix, for example:
Note that the LOOP and JECXZ instructions (and their variants) can use only 8-bit displacements. You must ensure that the destination is within range.JZ NEAR dest JNC NEAR label
will load the EAX register with the contents of memory location 'store'. However,MOV EAX,[store]
will load the EAX register with the 32 bit value of BASIC variable 'store', i.e. the address of the memory location.MOV EAX,store
Compare memory - byte CMPSB Compare memory - word CMPSW Compare memory - double-word CMPSD Compare AL (byte) SCASB Compare AX (word) SCASW Compare EAX (double-word) SCASD Load from memory - byte LODSB Load from memory - word LODSW Load from memory - double-word LODSD Store to memory - byte STOSB Store to memory - word STOSW Store to memory - double-word STOSD Move byte MOVSB Move word MOVSW Move double-word MOVSD
will load the EAX register with the contents of the address 'data' in the code segment. Since BBC BASIC for Windows is a 32-bit program and the assembler will normally be used to generate 32-bit code in a 'flat' address space, segment overrides will very rarely be required.MOV EAX,CS:[data]
When assembly language statements are separated by colons, it is necessary to leave a space between the colon and a preceding segment register name. If the space is missing, the assembler will misinterpret the colon as a segment override. For example,
will give rise to an error, butPUSH CS:MOV EAX,0
will be accepted.PUSH CS :MOV EAX,0
If this operator is omitted, BBC BASIC for Windows and BBC BASIC for SDL 2.0 will issue a 'Size needed' error message (error code 2).INC BYTE PTR [EBX] MOV WORD PTR [count],0 ADD DWORD [ESI],offset
LOOP label LOOPW label LOOPD label
are accepted, but[bp+di], [bp+si], [bx+di], [bx+si]
are not.[di+bp], [si+bp], [di+bx], [si+bx]
This restriction does not apply to the 32-bit memory operands. For example, all the following are accepted:
[eax+2*ecx], [edx+ebx*4], [eax*3], [ebp+esi]
Where 'index' is an index or base register such as 'ebx', 'ebp+esi', etc, and 'offset' is a numeric expression.[index]+offset [index+offset] offset[index]
In addition to dword (or dword ptr) the data-size modifiers qword (or qword ptr) and tbyte may also be specified. These refer to a 64-bit (double float or long long integer) or 80-bit (temporary float or 18-digit BCD) data size respectively. The only instructions which can take a tbyte operand are fbld, fbstp, fld and fstp.
Be careful if you use DB, DW or DD to define locations in which to store variable data rather than constants. On some modern processors writing data to a memory location in close proximity to the code can dramatically reduce execution speed (this is to support self-modifying code). If speed is important ensure that any data storage locations to which you write frequently are at least 2 Kbytes away from the code accessing them.
will set two consecutive bytes of memory to 15 and 9 (decimal). The address of the first byte will be stored in the variable 'data'..data DB 15 DB 9
will load the string 'This is a test message' followed by a carriage-return into memory. The address of the start of the message is loaded into the variable 'string'. This is equivalent to the following program segment:JMPS continue; jump round the data .string DB "This is a test message" DB &D .continue; and continue the process
JMPS continue; jump round the data .string; leave assembly and load the string ] $P%="This is a test message" REM starting at P% P%=P%+LEN($P%)+1 REM adjust P% to next free byte [ OPT opt%; reset OPT .continue; and continue the program
will have the same result as the Byte constant example above..data DW &90F
will have the same result as,.data DD &90F0D10
.data DB 16 .data DB &10 DB 13 or DB &D DB 15 DB &F DB 9 DB &9
aaa | aad | aam | aas |
adc | add | and | bound |
bsf | bsr | bswap | bt |
btc | btr | bts | call |
cbw | cdq | clc | cld |
cli | cmc | cmp | cmpsb |
cmpsd | cmpsw | cmpxchg | cpuid |
cwd | cwde | daa | das |
dec | div | enter | hlt |
idiv | imul | in | inc |
insb | insd | insw | int |
into | invd | invlpg | iret |
iretd | jae | ja | jbe |
jb | jc | je | jge |
jg | jle | jl | jmp |
jnae | jna | jnbe | jnb |
jnc | jne | jnge | jng |
jnle | jnl | jno | jnp |
jns | jnz | jo | jpe |
jpo | jp | js | jz |
lahf | lds | lea | leave |
les | lfs | lgs | lock |
lodsb | lodsd | lodsw | loop |
loope | loopne | loopnz | loopz |
loopd | looped | loopned | loopnzd |
loopzd | loopw | loopew | loopnew |
loopnzw | loopzw | lss | mov |
movsb | movsd | movsw | movsx |
movzx | mul | neg | nop |
not | or | out | outsb |
outsd | outsw | pop | popa |
popad | popf | popfd | push |
pusha | pushad | pushf | pushfd |
rcl | rcr | rdtsc | rep |
repe | repne | repnz | repz |
ret | retf | retn | rol |
ror | sahf | sal | sar |
sbb | scasb | scasd | scasw |
setae | seta | setbe | setb |
setc | sete | setge | setg |
setle | setl | setnae | setna |
setnbe | setnb | setnc | setne |
setnge | setng | setnle | setnl |
setno | setnp | setns | setnz |
seto | setpe | setpo | setp |
sets | setz | shl | shld |
shr | shrd | stc | std |
sti | stosb | stosd | stosw |
sub | test | wait | wbinvd |
xadd | xchg | xlat | xor |
f2xm1 | fabs | fadd | faddp |
fbld | fbstp | fchs | fclex |
fcom | fcomi | fcomip | fcomp |
fcompp | fcos | fdecstp | fdiv |
fdivp | fdivr | fdivrp | ffree |
fiadd | ficom | ficomp | fidiv |
fidivr | fild | fimul | fincstp |
finit | fist | fistp | fisub |
fisubr | fld | fld1 | fldl2e |
fldl2t | fldlg2 | fldln2 | fldpi |
fldz | fldcw | fldenv | fmul |
fmulp | fnclex | fninit | fnop |
fnsave | fnstcw | fnstenv | fnstsw |
fpatn | fprem | fprem1 | fptan |
frndint | frstor | fsave | fscale |
fsin | fsincos | fsqrt | fst |
fstp | fstcw | fstenv | fstsw |
fsub | fsubp | fsubr | fsubrp |
ftst | fucom | fucomp | fucomi |
fucomip | fucompp | fxam | fxch |
fxtract | fyl2x | fyl2xp1 |
emms | maskmovq | movd | movntq |
movq | packssdw | packsswb | packuswb |
paddb | paddw | paddd | paddsb |
paddsw | paddusb | paddusw | pand |
pandn | pavgb | pavgw | pcmpeqb |
pcmpeqw | pcmpeqd | pcmpgtb | pcmpgtw |
pcmpgtd | pextrw | pinsrw | pmaddwd |
pmaxsw | pmaxub | pminsw | pminub |
pmovmskb | pmulhuw | pmulhw | pmullw |
por | psadbw | pshufw | psllw |
pslld | psllq | psraw | psrad |
psrlw | psrld | psrlq | psubb |
psubw | psubd | psubsb | psubsw |
psubusb | psubusw | punpckhbw | punpckhwd |
punpckhdq | punpcklbw | punpcklwd | punpckldq |
pxor |
Note that pavgb, pavgw, pextrw, pinsrw, pmaxsw, pmaxub, pminsw, pminub, pmovmskb, pmulhuw, psadbw and pshufw are not strictly speaking MMX opcodes, as they were added with the Streaming SIMD Extensions (SSE). However since they operate on the integer MMX registers they logically extend the MMX instruction set.
All strings are CR-terminated. In the case of 'oskey' the carry flag is cleared if no key was pressed within the timeout period. In the case of 'osbget' the carry flag is cleared if at end-of-file.CALL "osbget" ; Read byte from file to AL, EBX contains channel number CALL "osbput" ; Write byte from AL to file, EBX contains channel number CALL "osrdch" ; Read keyboard character to AL CALL "osasci" ; Write AL to the VDU drivers (plus LF if CR) CALL "osnewl" ; Write LF,CR CALL "oswrch" ; Write AL to the VDU drivers CALL "osword" ; Read character dot pattern, EDX addresses buffer CALL "osbyte" ; Read character at cursor position to AL CALL "oscli" ; Various OS commands, EDX addresses string CALL "oskey" ; Equivalent to INKEY, EAX contains timeout value CALL "osline" ; Read a line from the console, EDX addresses buffer (DL=0) CALL "osshut" ; Close a file, EBX = channel number CALL "getptr" ; Read file pointer, EBX = channel number, result in EDX:EAX CALL "setptr" ; Set file pointer, EBX = channel number, EDX:EAX = value CALL "getext" ; Read file length, EBX = channel number, result in EDX:EAX CALL "setext" ; Set file length, EBX = channel number, EDX:EAX = value CALL "osopen" ; Open a file, EDX addresses filename, AL = 0 (read), ; 1 (create) or 2 (update), channel number returned in EAX
Note that you should ensure that the direction flag is cleared before calling any of these routines. If in doubt, add a CLD instruction.
The following assembly-language program would clear the screen (text viewport):
.clrscn CLD MOV AL,12 ; VDU 12 is CLS CALL "oswrch" RET
When passing multiple parameters you must be careful to push them in 'reverse order' so they end up in the correct sequence on the stack. So for example:.beep push 48 ; Put the parameter on the stack call "MessageBeep" ret
would become in assembly language:SYS "SetWindowPos", @hwnd%, 0, xpos%, ypos%, 0, 0, 5
Note that you should ensure that the direction flag is cleared before calling any API function. If in doubt, add a CLD instruction.push 5 push 0 push 0 push ypos% push xpos% push 0 push @hwnd% call "SetWindowPos"
P% and O% are initialised to zero. Using the assembler without first setting P% or O%, as appropriate, is liable to crash BBC BASIC.
will reserve 21 bytes of code (byte 0 to byte 20) and load the variable 'code%' with the start address of the reserved area. You can then set P% (or O%) to the start of that area.DIM code% 20 : REM Note the absence of brackets
The example below reserves an area of memory 100 bytes long, sets P% to the first byte of the reserved area and sets L% to the end of the reserved area (as is required when bit 3 of OPT is set):
size% = 100 DIM code% size%-1 FOR opt% = 8 TO 10 STEP 2 PROCassemble(opt%, code%, code%+size%) NEXT opt% ... DEF PROCassemble(opt%, P%, L%) [OPT opt% ... ] ENDPROC
This allocates 2 Kbytes of memory for the code. The use of the variable code% twice is not a mistake, it ensures an accurate alignment of the address on a 2K 'boundary'. If there is insufficient room for the code, you can increase the size in multiples of 2 Kbytes (e.g. size% = 4096 will allocate 4 Kbytes).size% = 2048 DIM code% NOTEND AND 2047, code% size%-1
It is safe to incorporate items of data within your code using the DB, DD and DW pseudo-ops, but only if the data is constant (read-only). Writable data should be stored outside the block of memory containing the code. One way of guaranteeing that is as follows:
The code and data will then occupy separate 2 Kbyte blocks.[OPT opt% .data1 DB 0 : DB 0 .data2 DW 0 .data4 DD 0 ] P% = (P% + 2047) AND -2048 [OPT opt% .codestart
In the example below, a large amount of memory is initially reserved. To begin with, a single pass is made through the assembly code and the length needed for the code is stored in S%. After a CLEAR, the correct amount of memory is reserved and a further two passes of the assembly code are performed as usual. Your program should not, of course, subsequently try to use variables set before the CLEAR statement. If you use a similar structure to the example and place the program lines which initiate the assembly function at the start of your program, you can place your assembly code anywhere you like and still avoid this problem.
DIM code% HIMEM-END-2048 S% = FNassemble(0, code%, 0) - code% CLEAR size% = S% DIM code% NOTEND AND 2047, code% size%-1 S% = FNassemble(8, code%, code%+size%) S% = FNassemble(10, code%, code%+size%) - - - Put the rest of your program here. - - - DEF FNassemble(opt%, P%, L%) [OPT opt% - - - Assembler code. - - - ] = P%
will cause the assembler to issue an error if the code size exceeds 100 bytes.DIM P% 99, L% -1 [OPT 8
OPT value Limit check Code stored at Errors reported Listing generated 0 No P% No No 1 No P% No Yes 2 No P% Yes No 3 No P% Yes Yes 4 No O% No No 5 No O% No Yes 6 No O% Yes No 7 No O% Yes Yes 8 Yes P% No No 9 Yes P% No Yes 10 Yes P% Yes No 11 Yes P% Yes Yes 12 Yes O% No No 13 Yes O% No Yes 14 Yes O% Yes No 15 Yes O% Yes Yes
This is the first pass through the assembly process (note that the 'JMP fred' instruction jumps to itself):10 DIM code 12 20 FOR opt=1 TO 3 STEP 2 30 P%=code 40 [OPT opt 50 .jim JMP fred 60 DW &2345 70 .fred JMP jim 80 ] 90 NEXT
This is the second pass through the assembly process (note that the 'JMP fred' instruction now jumps to the correct address):RUN 030A18A9 OPT opt 030A18A9 E9 FB FF FF FF .jim JMP fred 030A18AE 45 23 DW &2345 030A18B0 E9 F4 FF FF FF .fred JMP jim
Generally, if labels have been used, you must make two passes through the assembly language code to resolve forward references. This can be done using a FOR...NEXT loop. Normally, the first pass should be with OPT 0 (or OPT 4, 8, 12) and the second pass with OPT 2 (or 6, 10, 14). If you want a listing, use OPT 3 (or 7, 11, 15) for the second pass. During the first pass, a table of variables giving the address of the labels is built. Labels which have not yet been included in the table (forward references) will generate the address of the current op-code. The correct address will be generated during the second pass.030A18A9 OPT opt 030A18A9 E9 02 00 00 00 .jim JMP fred 030A18AE 45 23 DW &2345 030A18B0 E9 F4 FF FF FF .fred JMP jim
DIM code 200 FOR pass=0 TO 3 STEP 3 [OPT pass .start - - - - - - code - - - - - - :] : IF flag [OPT pass: - code for routine 1 -:] IF NOT flag [OPT pass: - code for routine 2 - :] : [OPT pass .more_code - - - - - - code - - - - - -:] NEXT
It is possible to suppress the listing of the code in a macro by forcing bit 0 of OPT to zero for the duration of the macro code. This can most easily be done by ANDing the value passed to OPT with 14. This is illustrated in PROC_screen and PROC_aux in the example below.
The use of a function call to incorporate the code provides a neat way of incorporating the macro within the program and allows parameters to be passed to it. The function should return the original value of OPT.DIM code 200 op_flag=TRUE FOR pass=0 TO 3 STEP 3 [OPT pass .start - - - - - - code - - - - - - : OPT FN_select(op_flag); Include code depending on op_flag : - - - - - - code - - - - - -:] NEXT END : : REM Include code depending on value of op_flag : DEF FN_select(op_flag) IF op_flag PROC_screen ELSE PROC_aux =pass REM Return original value of OPT. This is a REM bit artificial, but necessary to insert REM some BASIC code in the assembly code. : DEF PROC_screen [OPT pass AND 14 ...code... ] ENDPROC : DEF PROC_aux [OPT pass AND 14 ...code... ] ENDPROC
CONTENTS |
CONTINUE |