EXERCISE CORRECTIONS
NUMBER 2
1) Exercise number 1
-------------
Here are the listings of the 2 macro instructions 'SAVE' and 'RESTORE'
that allow to respectively save and restore the 68000's registers.
I will skip the details, it was enough to use the MOVEM instruction.
The registers will be saved in the system stack by pre-decrement mode
and restored by post-increment mode. That's all ...
TEXT
SAVE MACRO
movem.l d0-d7/a0-a6,-(sp)
ENDM
RESTORE MACRO
movem.l (sp)+,d0-d7/a0-a6
ENDM
END
2) Exercise number 2
-------------
Here is the listing of the HEXA macro, that allows to display the content
of its parameter in hexadecimal.
First we need to successively reach the 8 half-bytes making up
the L-M passed as parameter (1 hex digit = 4 bits).
To do this we use the rotation instruction ROL and place it in
a loop. (LSR also worked...)
We will then mask the 4 least significant bits with AND.L #%1111,dn
to keep only the half-byte to be processed.
The most difficult comes then:
It's now necessary to display the value of this hex digit coded by 4 bits
on screen.
If the digit is <$A (which means <10) this digit will be between 0 and 9.
By adding $30 to the value of this digit we will get the ascii code
of the digit. (Because the ascii code of '0' is $30: that of '1' is thus
$30+1=$31 etc...)
If the hex digit to be displayed is >9 this digit will be a letter from the
alphabet (from A to F).
By adding $37+$A to the value of this digit we will get the ascii code
of the digit to display. (Because the ascii code of 'A' is $37+$A: that of 'B'
is thus $37+$B=$42 etc...)
It's then enough to display with CCONOUT the ascii code obtained and
to repeat the operation with all the half-bytes of the parameter.
NB: We use the macros SAVE and RESTORE in our HEXA macro to
-- be able to use all the registers without modifying their content at
the end of the macro.
Please note that I'm using LABELS in the HEXA macro.
Hence the macro can only be used once in a listing because
the assembler cannot distinguish between two identical labels and at
each call of a macro, it is fully rewritten...
You can, however, put the macro in a subroutine to
be able to call it multiple times...
TEXT
HEXA MACRO $\1 ;macro with 1 parameter
SAVE ;we save the registers so as not
;to lose their content
move.l \1,d1 ;we put the parameter in d1
moveq #0,d2 ;initializes the number of shifts
SHIFT addi.b #4,d2 ;we add 4 to the number of shifts
cmpi.b #36,d2 ;if d2=36=32+4 we finished the 32
beq END ;rotations, in this case -> END
move.l d1,d3 ;otherwise we put d1 in d3 and
rol.l d2,d3 ;do a rotation of 4 bits
andi.l #%1111,d3 ;and we mask these 4 bits as only
;they must be processed.
; d3 therefore contains the value to be displayed: 0 to 9 or A to F. (because a
; hex digit is coded by 4 bits (see introduction) )
cmpi.b #9,d3
bgt HEX ;if d3 >9, go to HEX because we will
;need to display a letter and no longer a
;number...
DECIMAL addi.b #$30,d3 ;d3=d3+$30 because the ASCII value of 0 is $30
;For example, if d3 is worth 1, we represent it
;by the ascii character $30+1=$31='1', if it
;is 5, by the ascii code $30+5=$35='5', and so
;on for all hex digits <9
CCONOUT d3 ;edition of the content of d3
jmp SHIFT ;we re-shift the parameter and continue with
;the next 4 bits in SHIFT
HEX addi.b #$37,d3 ;d3=d3+$37 for the hex numbers represented
;by the letters because the ASCII value of A is
;$37+$A. So for exp. if d3 is worth $B, we re-
;present it by the ascii code $37+$B=$42='B'...
CCONOUT d3 ;we display the letter (from A to F)
jmp SHIFT ;we re-shift the parameter and continue with
;the next 4 bits in SHIFT
END RESTORE ;when we are done with all the 32 bits,
;we restore the stacked registers
ENDM
END
3) Exercise number 3
-------------
Here is the correction of the 'BINARY' macro.
To reach the 32 bits of the parameter and to display them on the screen,
we use the instruction LSL.L #1, parameter in a loop and depending on
the value of the shift out bit, we display a '1' (active bit) or a '0' (extinguished
bit).
The corresponding conditional branch instruction can for example be
bCC (Which tests if the C bit of the CCR is zero: LSL copies the shifted out
bit into the C bit of the CCR)
To display the '1' or the '0', we use the CCONOUT #'1' or
CCONOUT #'0' macro.
NB:Same remarks as for the HEXA macro concerning the use of labels
-- in the 'BINARY' macro.
TEXT
BINARY MACRO $\1 ;MACRO with 1 parameter
SAVE ;registers saved
move.L \1,d1 ;the parameter in d1
move #31,d3 ;loop counter for shifts
LOOK move #'0',d0 ;d0 contains the ascii code of 0
lsl.l #1,d1 ;shift of one bit of d1: Copy of the bit into
;the C code of the CCR
bcc ZERO ;if the bit is zero (C=0): go to 'zero'
move #'1',d0 ;otherwise d0 contains the ascii code of '1'
ZERO CCONOUT d0 ;we display the content of d0 (0 or 1)
dbf d3,LOOK ;we continue with the other 31 bits
RESTORE ;we restore the registers
ENDM ;done...
END
4) Exercise number 4:
--------------
Here is the listing of the program that formats a floppy disk.
It was simply necessary to properly use the FLOPFMT function of the Gemdos
and put it in a loop to be able to vary the number of the track to format.
To ask for execution confirmation from the program's user,
we display an alert message with PRINTLINE, we wait for him to press
a keyboard key (with 'WAIT') and we test the ascii code of
the selected key. (value which returns in d0)
If this key is 'F' we format the floppy, otherwise we exit the program
with the TERM macro (TERM function of the Gemdos).
If an error occurs during formatting (d0 negative after FLOPFMT),
we display the error code in DECIMAL.
We will first need to make the digit to process positive with NEG dn.
The digit to process (the error code) will thus be a positive number
and less than 100 (see the Gemdos error codes).
We perform a division by 10 of this digit to get the tens digit
with DIVU #10,dn.
The quotient returns in the low weight word of dn: it's the tens digit, we display it
by adding $30 to obtain an ascii code (with CCONOUT).
The remainder is in the high weight word of dn: It represents the
units digit of the error code. We SWAP dn and also display it.
When the formatting is finished, we display a message indicating that
everything is OK.
Remark:
---------
BE CAREFUL, our program will format the disk correctly, but if
you look at the disk information using the 'INFORMATION' option of the GEM desktop, it will indicate that there
remain 0 bytes free even though there are also 0 used...
This is explained by the fact that we haven't initialized the
BOOT SECTOR of the floppy: It will therefore not be writable because
it contains all the necessary information for disk operations...
NB: Those who don't have PROFIMAT and who want (must!) set
-- the buffer for FLOPFMT to an EVEN address should not write
the DIRECTIVE: 'ALIGN.W' in the BSS area.
For METACOMCO, there is an equivalent DIRECTIVE: CNOP 0,2
For DEVPAC ST: it's the EVEN directive.
The others will assemble the listing and if it doesn't work, it's because
the buffer for FLOPFMT is not at an even address.
It will then be sufficient to reserve 1 BYTE just in front of the buffer: it
will thus move from an odd address to an even address (odd+1).
TEXT
INCLUDE "INIT_TOS.L"
INCLUDE "MACROS.L"
SETBLOCK
PRINTLINE ATTENTION ;the alert message
WAIT ;waiting for a key:ascii code in d0
CMPI.B #'F',d0 ;d0='F' ?
BEQ FORMAT ;if so, FORMAT
CMPI.B #'f',d0 ;d0='f' ?
BEQ FORMAT ;if so, FORMAT
TERM ;otherwise exit
FORMAT SUPER ;SUPERVISOR mode
clr.l d0
LOOP movem.l d0,-(sp) ;we save just d0
move.w #$e5e5,-(sp) ;virgin
move.l #$87654321,-(sp) ;magic word
move.w #1,-(sp) ;interleave
move.w #0,-(sp) ;side
move.w d0,-(sp) ;d0=different tracks
move.w #9,-(sp) ;number of sectors per track
move.w #0,-(sp) ;drive A
clr.l -(sp) ;L-M=0
pea BUFFER ;buffer address
move.w #$a,-(sp) ;Flopfmt
trap #14
add.l #26,sp ;update SP
tst d0
bmi ERROR ;If d0 is negative: error
movem.l (sp)+,d0 ;we restore d0
addi.b #1,d0 ;we increment the track number
cmpi.b #80,d0 ;have we the 80 tracks ?
bne LOOP
PRINTLINE OK ;no problem, OK
CONTINUE WAIT ;waiting for a key
USER ;we return to USER mode
TERM ;-> exit
ERROR move d0,d5 ;we save d0 in d5 because d0 will be modified
PRINTLINE PROBLEM
neg d5 ;d5 becomes positive
; DECIMAL display of d5
divu #10,d5 ;tens digit in the low word of d5
add #$30,d5 ;digit=ascii code
CCONOUT d5 ;we display it
swap d5 ;low word of d5=remainder of division=digit
;units of d5
add #$30,d5 ;digit=ascii code
CCONOUT d5 ;we display it
jmp CONTINUE ;--> end
DATA
ATTENTION DC.B 27,'E','DANGER! This program FORMATS the floppy disk,'
DC.B ' insert a BLANK disk then',10,13,'press'
DC.B ' [F] to FORMAT the floppy disk...'
DC.B ' (Or another key to EXIT!)',7,0
OK DC.B 27,'E','No error: OK...',0
PROBLEM DC.B 27,'E',7,'ERROR code:-',0
BSS
DS.B 20000 ;buffer upstream of the new STACK
PILE DS.B 1 ;formatting requires a lot of space...
ALIGN.W ;SPECIFIC to PROFIMAT !!!!!
BUFFER DS.B 10000 ;buffer for formatting (EVEN address)
SAUV_SP DS.L 1 ;buffer for SUPER and USER
END
5) Exercise number 5
-------------
Here is the program that replays the sounds created with PRO SOUND DESIGNER.
The program will wait until a key is pressed on the keyboard then it
tests it (Macro 'WAIT' from gemdos, return of the code and the scancode in
d0).
Function keys have no ascii code but all have a
SCANCOD that differentiates them.
If the low byte of d0 contains an ascii code (d0.w different
from 0), we exit the program because it means we have pressed a key other
than one of the 10 function keys.
You then had to find the different scancodes of function keys
to be able to use them here.
For that, you just had to write the following program,
TEXT
INCLUDE "MACROS.L"
AA WAIT ;waiting for a key
SWAP d0 ;low weight byte of d0 = scancode
and.l #$FF,d0 ;we keep only the low byte of
;this word (which is the SCANCODE)
HEXA d0 ;display in HEXA the scancode
WAIT ;waiting for a key
CCONOUT #27
CCONOUT #'E' ;we clear the screen
jmp AA ;and we start again
END
then to assemble it, to execute it and to press on the function keys to note their SCANCODES.
The rest of the program must identify the different scancodes of
the function keys and play a sound.
To test the values of the scancode of the pressed key, we compare
the value of the scancode entered with the values of the 10 scancodes of the function keys that we have placed in the DATA area.
At the same time, we vary the value of an 'an' address register
which points to the different sound addresses.
If a scancode is identified, we play the sound pointed by 'an' by
providing it as a parameter to the macro 'DOSOUND', otherwise we increment
address registers (mode (an)+) pointing to the DATAs that represent
the scancodes and sound addresses.
If no scancode is finally recognized, we restart the keyboard test from
the beginning of the program.
The data defining the sounds are in the file
PROSOUND.DAT, just include it in the DATA zone in the listing.
NB:I'm modifying the value of a SYSTEM VARIABLE in this listing (with
-- move.b #0,$484) this with the purpose of stopping the 'BEEP' that is
heard when pressing a key in order not to disturb
the replayed sound.
I will soon talk about the SYSTEM VARIABLES...
TEXT
INCLUDE "INIT_TOS.L"
INCLUDE "MACROS.L"
SETBLOCK
SUPER ;SUPERVISOR mode
PRINTLINE message ;text
move.b #0,$484 ;system variable (putting
;0 removes repetition and
;beep of the keys)
TEST WAIT ;waiting for a key
;:CODE in d0
tst.b d0 ;if ascii code different from
bne STP ;0, then SToP, otherwise
swap d0 ;low word d0
;becomes the SCANCODE
lea FUNCT,a0 ;a0=address of SCANCODES
lea VECTOR,a1 ;a1=address of sound
;address of VECTOR
SONGS cmp.b (a0)+,d0 ;compare SCANCODE of the
;pressed key (d0) to
;those in the table DC.B .
move.l (a1)+,a5 ;Puts the address pointed by
;a1 in a5
beq SOUND ;if CMP=yes, go play the
;sound pointed by a5
addq.b #1,d1 ;otherwise add 1 to d1
cmpi.b #9,d1 ;d1=9 ?
beq TEST ;then no more scancodes
;and we return to 'TEST'
jmp SONGS ;otherwise we increment a0
;and a1
SOUND DOSOUND a5 ;Dosound the sound pointed by
;a5
jmp TEST ;then we return to 'TEST'
STP USER ;USER mode
TERM ;we exit
DATA
MESSAGE DC.B 27,'E','Here are some PRO SOUND DESIGNER sounds'
DC.B ', press the Function keys:'
DC.B '(Or another key to exit)',7,0
VECTOR DC.L sound0,sound1,sound2,sound3,sound4,sound5
DC.L sound6,sound7,sound8,sound9
;addresses of the 10 sounds.
FUNCT DC.B $3B