DataMuseum.dk

Presents historical artifacts from the history of:

RegneCentralen RC850

This is an automatic "excavation" of a thematic subset of
artifacts from Datamuseum.dk's BitArchive.

See our Wiki for more about RegneCentralen RC850

Excavated with: AutoArchaeologist - Free & Open Source Software.


top - metrics - download

⟦9bc39d7be⟧ TextFile

    Length: 24576 (0x6000)
    Types: TextFile
    Names: »CONDR.MAC«

Derivation

└─⟦9f46c4107⟧ Bits:30005988 Sources for TurboDOS ver. 1.30 device drivers
    └─⟦this⟧ »CONDR.MAC« 

TextFile

.Z80
TITLE	CONSOLE DRIVER FOR RC855 (WITH MEMORY BANKING)
SUBTTL	ASE GmbH, Altenstadt, vers.: 29.11.83
;
	INCLUDE	CONDINIT.MAC
	.LIST
;
	CSEG
;
CONDR@::XOR	A		;set console driver busy LED
	OUT	(0),A		;
	LD	A,E		;get requested function
	CP	0		;status test ?
	JP	Z,CNST		;
;	CP	10		;fast console output ?
;	JP	Z,CNDOUT	;
;	CP	2		;standart console output ?
;	JP	Z,CRTOUT	;
	LD	HL,MUXSPH	;else, lock driver
	CALL	WAIT##		;
	CALL	SELDRV		;call driver
	PUSH	AF		;save return code
	PUSH	BC		;
	LD	HL,MUXSPH	;unlock driver
	CALL	SIGNAL##	;
	LD	A,1		;clear busy bit
	OUT	(0),A		;
	POP	BC		;restore return code
	POP	AF		;
	RET			;done
;
;
;
SELDRV:	LD	A,E		; test function code
	CP	10		;fast console output ?
	JP	Z,CNDOUT	;
	CP	1		;
	JP	Z,CONIN1	;
	CP	2		;
	JP	Z,CRTOUT	;
	CP	8		;
	JP	Z,STATL1	;
	CP	9		;
	JP	Z,STATL2	;
	RET			;
;
;
;
STATL1:
		LD	HL,KBXSPH	; get interlock semaphore address
		CALL	WAIT		; wait if driver is already in use
CRTMAP:		LD	A,(ECURX)	;get X-address
		ADD	A,32		;
		LD	(SECURX),A	;save X-address
		LD	A,(ECURY)	;get Y-address
		ADD	A,32		;
		LD	(SECURY),A	;save Y-address
		LD	C,06H		;start cursor pos. in line 25
		CALL	CRTOUT		;
		LD	C,56		;
		CALL	CRTOUT		;
		LD	C,32		;
		CALL	CRTOUT		;
;
		LD	HL,(ECRPOS)	;
		ADD	HL,HL		; function gaddr: integer
		LD	DE,(ELGPOS)	; begin
		ADD	HL,DE		;   gaddr = (HL * 2 + logpos) mod 4096
		LD	A,H		;	+ address(picture)
		AND	00001111B	;
		LD	H,A		;
		LD	DE,EPICT	;
		ADD	HL,DE		; HL = address
		LD	DE,SAVE25	; DE = save address
		LD	BC,160		; BC = loop count
		LDIR			; move data
;
		CALL	ERALIN		;
		LD	C,236		;set light and blink
		CALL	CRTOUT		;
		RET			;done
;
STATL2:
		LD	C,128		;reset light and blink
		CALL	CRTOUT		;
		LD	C,0DH		;CR funktion
		CALL	CRTOUT		;
		CALL	ERALIN		;
;
		LD	HL,(ECRPOS)	;
		ADD	HL,HL		; function gaddr: integer
		LD	DE,(ELGPOS)	; begin
		ADD	HL,DE		;   gaddr = (HL * 2 + logpos) mod 4096
		LD	A,H		;	+ address(picture)
		AND	00001111B	;
		LD	H,A		;
		LD	DE,EPICT	;
		ADD	HL,DE		; HL = address
		EX	DE,HL		; DE = address
		LD	HL,SAVE25	; HL = save address
		LD	BC,160		; BC = loop count
		LDIR			; move data

		LD	C,06		;
		CALL	CRTOUT		;
		LD	A,(SECURX)	;set X and Y to old value
		LD	C,A		;
		CALL	CRTOUT		;
		LD	A,(SECURY)	;
		LD	C,A		;
		CALL	CRTOUT		;
;
CRTMA1:		LD	HL,KBXSPH	; get interlock semaphor address
		CALL	SIGNAL		; signal driver no longer in use
		RET			;done
;
	PAGE
;			
;	console output routine for function call 10
;
CRTOUT::
CNDOUT:	CALL	CONOUT		; no, character to crt
	LD	A,0FFH		; return without dispatching
	OUT	(0),A		;clear driver busy LED
	RET			;
;
CONOUT: LD	A,(CURMDE)	;test for coursor addresseing
	CP	6		;X coordinate ?
	JP	Z,XADDR		;
	CP	7		;Y coordinate ?
	JP	Z,YADDR		;
	BIT	7,C		; startattribute
	JP	NZ,SETATR
	LD	A,C		;
	CP	32		;
	JP	M,CNTCHR	; ctrl-character <32
	LD	HL,CONVTB##	;get conversion table bottom
	LD	B,0		;
	ADD	HL,BC		;compute offset
	LD	C,(HL)		; C = converted ASCII-value
	LD	HL,(ECRPOS)	; procedure entry writechar(C: char)
	CALL	EGADDR		; procedure entry writechar-index
	LD	A,(ECRATR)	; begin (* A = HL, C = BC *)
	LD	B,A		;
	DI			;
	IN	A,(SELDSP)	;
	LD	(HL),C		; (A = integer; C = char)
	INC	HL		;   picture(getaddr) = C
	LD	(HL),B		;   picture(getaddr+1) = curatr
	IN	A,(DESDSP)	;
	EI			;
	CALL	EFWDCR		;   writechar-index(cursorpos,C)
	LD	BC,(ECRPOS)	;   forwaed-cursor
	CALL	ESTPOS		;   setposition(curpos)
	RET			;done
;
;
;
SETATR:	LD	A,C		; A = char.
	SLA	A		; shift 1 left (bit 9,10,11,12,13,14,15)
	LD	(ECRATR),A	; save attribute
	RET			;
;
;
;
CNTCHR:		CP	5		; back tab
		JP	Z,BACKSP	; back space cursor
		CP	6		; cursor addressing start
		JP	Z,STCURM	;
		CP	7		; bell-character
		JP	Z,AUDIO		;
		C▶d0◀	8		▶bb◀ backspace
		J▶d0◀	Z,BACKS▶d0◀	;
		CP	9		; tab
		JP	Z,CFORW		;
		CP	10		; nl
		JP	Z,ENWLIN	;
		CP	12		; formfeed
		JP	Z,ECLCRT	;
		CP	13		; cr
		JP	Z,CRRET		;
		CP	14		; stop roll
		JP	Z,STPROL	;
		CP	15		; start roll
		JP	Z,SRTROL	;
		CP	18H		; forward cursor
		JP	Z,CURFW		;
		CP	1AH		; cusor up
		JP	Z,CURUP		;
		CP	1DH		; cursor home
		JP	Z,CURHME	;
		CP	30		; erase to end of line
		JP	Z,ERALIN	;
		CP	31		; erase to end of screen
		JP	Z,ERAEOS	;
		RET			;
;
STPROL:		LD	BC,23		; set max line to 24 (0 - 23)
		LD	(VMXLIN),BC	;
		RET			; done
;
SRTROL:		LD	BC,24		; set max line to 25 (0 - 24)
		LD	(VMXLIN),BC	;
		RET			; done
;
;	set coursor - function 6
;	next 2 characters must be the XY address
;
STCURM:	LD	(CURMDE),A	;set coursor flag to none zero
	RET			;done
;
XADDR:	LD	A,C		;get X address
	LD	B,32		;get offset
	SUB	B		;A contains X address
	LD	(SAVEX),A	;save address
	LD	A,7		;set entry value for Y address
	LD	(CURMDE),A	;
	RET			;done
;
YADDR:	LD	A,C		;get Y address
	LD	BC,32		;get offset
	SUB	C		;A contains Y address
	LD	C,A		;BC contains Y address
	LD	HL,(SAVEX)	;HL contains X address
	XOR	A		;clear set coursor flag
	LD	(CURMDE),A	;
	JP	ESTCUR		;set coursor and exit
;
;	backspace coursor - function 8
;
BACKSP:	LD	HL,ECURX	; line number
	LD	B,(HL)		;
	LD	HL,ECURY	;
	LD	A,(HL)		;
	OR	B		; if y-coordinate = x-coordinate = 0 then nothing
	RET	Z		;
	LD	A,(HL)		; position
	CP	0		;
	JR	NZ,LAB1		;
	DEC	B		; lineno0 = lineno0 - 1
	LD	(HL),COPLN		;
	LD	A,B		;
	LD	(ECURX),A	; lineno
LAB1:	DEC	(HL)		;
	LD	HL,(ECRPOS)	;
	DEC	HL		;
	LD	(ECRPOS),HL	; cursorpos: = cursorpos - 1
	LD	BC,(ECRPOS)	;
	JP	ESTPOS		;
;
;	carrige return - function 13
;
CRRET:	LD	HL,ECURX	; row = row
	LD	L,(HL)		;
	LD	H,0		;
	LD	BC,0		; column = 0
	JP	ESTCUR		;set coursor and exit
;
;	coursor forward - function 24
;
CURFW:	CALL	EFWDCR		; forward cursor
	LD	BC,(ECRPOS)	;
	JP	ESTPOS		;
;
;
;
ERALIN:	LD	HL,(ECRPOS)	; erase to end of line
	CALL	EGADDR		; 
	LD	A,(ECURY)	;
	LD	B,A		;
	LD	A,COPLN		;
	SUB	B		;
	LD	B,A		;
;
; erase no. of pos. given by reg. B, address by reg. HL
;
ERA:	DI			;disable interupt if display
	IN	A,(SELDSP)	;memory is selected
	LD	D,BLANK		;set character and
	LD	E,NOATRB	;video attribute
ERA1:	SET	4,H		;make sure, selected address id x'Exxx
	SET	5,H		;
	SET	6,H		;
	SET	7,H		;
	LD	(HL),D		;display location set to blank
	INC	HL		;
	LD	(HL),E		;attributes cleared
	INC	HL		;
	DJNZ	ERA1		;loop till B = 0
	IN	A,(DESDSP)	;
	EI			;
	RET			;done
;
;
;
ERAEOS:	CALL	ERALIN		; erase to end of screen; 1. current line
	LD	A,(ECURX)	; get current line
	INC	A		; increment to next line
	LD	C,A		; save line no.
	LD	A,25		; A = no. of lines
	SUB	C		; A = no. of lines to erase
	RET	Z		; if A = 0 then finish
	LD	C,A		; save
ERARST:	LD	B,COPLN		; no. of char
	CALL	ERA		; erase current line
	DEC	C		; no. of lines - 1
	JR	NZ,ERARST	;
	RET			;
;
;	autio circiut on (bell) function 7
;
AUDIO:	LD	HL,INPSPH	;lock driver
	CALL	WAIT##		;
	LD	A,(LBYTE2)	; fetch lamp byte 2
	OR	00001000B	; set byte 3 autio
	LD	(SAVEPL),A	;
	CALL	SENDKB		;issue command
	LD	HL,6		;set bell sound time
	CALL	DELAY##		;
	LD	A,(LBYTE2)	;reset audio bit
	RES	3,A		;
	LD	(SAVEPL),A	;
	CALL	SENDKB		;issue command
	LD	HL,INPSPH	;unlock driver
	CALL	SIGNAL##	;
	RET			;done
;
; tabulation
;
CFORW:	CALL	EFWDCR		; forward cursor 1 pos
	CALL	EFWDCR		;
	CALL	EFWDCR		;
	CALL	EFWDCR		;
	LD	BC,(ECRPOS)	;
	JP	ESTPOS		;
;
; cursor 1 line up
;
CURUP:	LD	A,(ECURX)	;
	CP	0		;
	RET	Z		; if line = 0 then return
	LD	HL,(ECRPOS)	;
	LD	BC,COPLN	;
	XOR	A		;clear carry flag
	SBC	HL,BC		; position:= position - 80
	LD	(ECRPOS),HL	;
	LD	BC,(ECRPOS)	;
	LD	HL,ECURX	;
	DEC	(HL)		; line no.:=line no. - 1
	JP	ESTPOS		;
;
; cursor home (pos. 0,0)
;
CURHME:	LD	BC,0		;
	LD	(ECRPOS),BC	; cursor pos. = 0
	XOR	A		;
	LD	(ECURX),A	;
	LD	(ECURY),A	; line no. = 0; column = 0
	JP	ESTPOS		;
;
;	forme feed - function 12
;
ECLCRT:		LD	HL,EPICT  	; procedure entry clear display
		LD	C,LNPSC  	; begin
ECLCR1:		LD	B,COPLN		;   picture(1) = 0
		CALL	ERA		;
		DEC	C		; 
		JR	NZ,ECLCR1	;  
		LD	B,95		;   clear the rest of crt
		CALL	ERA		;
		LD	BC,0		;   clear bc
		LD	(ECRPOS),BC	;   cursorpos = 0
		LD	(ELGPOS),BC	;   logpos = 0
		XOR	A		;
		LD	(ECURX),A	;   cursorx = 0
		LD	(ECURY),A	;   cursoey = 0
		LD	(ECRATR),A	;   curatr = 0
		CALL	ESTPOS		;   setpos(cursorpos)
		JP	ESTBSE		; end
;
;	new line - function 10
;
ENWLIN:		LD	A,(ECURX)	; procedure entry newline
		LD	BC,(VMXLIN)	; begin
		CP	C		;
		JR	Z,LROLL		;   if cursorx <> maxlin then
		INC	A		;   begin
		LD	(ECURX),A	;	cursorx = cursorx + 1
		LD	HL,(ECRPOS)	;
		LD	BC,COPLN	;
		ADD	HL,BC		;	cursorpos = cursorpos + 80
		LD	(ECRPOS),HL	;
		LD	B,H		;	setpos(cursorpos)
		LD	C,L		;
		JP	ESTPOS		;done
;
LROLL:		CP	23		; max line = 23 (inhibit roll) ?
		JP	Z,LROLL1	; yes, continue
	LD	HL,EPICT	;	repeat
	LD	DE,(ELGPOS)	;get current display address
	ADD	HL,DE		;add it to base address
	LD	B,COPLN		;get columns per line
	CALL	ERA		;erase new line
	LD	(ELGPOS),HL	;set new base (* refresh address *)
	CALL	ESTBSE		;
	LD	BC,(ECRPOS)	;
	JP	ESTPOS		;   setpos(cursorpos)
;
LROLL1:	XOR	A		; set all counter to line 0
	LD	BC,0		;
	LD	(ECRPOS),BC	;
	LD	(ELGPOS),BC	;
	LD	(ECURX),BC	;
	LD	HL,(ECURX)	;
	LD	BC,(ECURY)	;
	JP	ESTCUR		;
;
;
;
ESTBSE:	DI
	LD	DE,(ELGPOS)	; procedure entry set-base
	SRL	D		;   help = logpos div 2
	RR	E		;
	LD	A,(CRT60)	; is it a 50Hz or 60Hz crt ?
	CP	0FFH		;
	JR	NZ,ESTBS1	; no, continue
	SRL	D		;
	RR	E		;
ESTBS1:	LD	C,DSPLDA	;
	LD	A,12		;
	OUT	(DSPLSE),A	; out(displ-sel,12)
	OUT	(C),D		; out(displ-data,highbyte(help))
	INC	A		;
	OUT	(DSPLSE),A	; out(displ-select,13)
	OUT	(C),E		; out(displ-data,lowbyte(help))
	EI
	RET			;
;
;
;
EFWDCR:	LD	HL,ECURY	; procedure entry forward cursor
	LD	A,(HL)		; begin
	CP	79		;   if cursory <> 79 then
	JR	Z,LFW001	;   begin
	INC	(HL)		;	cursory = cursory + 1
	LD	HL,(ECRPOS)	;
	INC	HL		;	cursorpos = cursorpos + 1
	LD	(ECRPOS),HL	; end
	RET			; else
;
EWRTLN:	LD	HL,ECURY	; procedure entry writel
;
LFW001:	LD	B,0		; begin
	LD	C,(HL)		;   help = cursory
	LD	(HL),B		;   cursory = 0
	LD	HL,(ECRPOS)	;
	OR	A		;
	SBC	HL,BC		;   cursorpos = cursorpos - help
	LD	(ECRPOS),HL	;   newline
	JP	ENWLIN		; end
;
;
;
EGADDR:		ADD	HL,HL		; function gaddr: integer
PGADR1:		LD	DE,(ELGPOS)	; begin
		ADD	HL,DE		;   gaddr = (HL * 2 + logpos) mod 4096
MD4096:		LD	A,H		;	+ address(picture)
		AND	00001111B	;
		LD	H,A		;
		LD	DE,EPICT	;
		ADD	HL,DE		;
		RET			; end
;
;
;
ESTCUR:	LD	A,L		; procedure entry set-cursor-position(R,C:byte)
	LD	(ECURX),A	; begin (* R = HL, C = BC *)
	LD	A,C		;   cursorx = R
	LD	(ECURY),A	;   cursory = C
	ADD	HL,HL		;   R = 2 * R
	ADD	HL,HL		;   R = 2 * R (* 4 *)
	ADD	HL,HL		;   R = 2 * R (* 8 *)
	ADD	HL,HL		;   R = 2 * R (* 16 *)
	LD	D,H		;
	LD	E,L		;   help = R; (* 10 * initial-R *)
	ADD	HL,HL		;   R = 2 * R (* 32 *)
	ADD	HL,HL		;   R = 2 * R (* 64 *)
	ADD	HL,DE		;   R = R + help (* (64+16)*initial-R *)
	ADD	HL,BC		;   R = R + C  (* R*80+C *)
	LD	(ECRPOS),HL	;   cursorpos = R
	LD	B,H		;   setpos(cursorpos)
	LD	C,L		;
					; procedure entry set-position
					; (position: integer)
; position = BC				; begin
;
ESTPOS:	LD	HL,(ELGPOS)	;
	SRL	H		;   pos = position + logpos div 2
	RR	L		;
	ADD	HL,BC		;
	LD	A,(CRT60)	; 50Hz or 60Hz crt ?
	CP	0FFH		;
	JR	NZ,ESTPO1	; no, continue
	SRL	H		;
	RR	L		;
	LD	A,0		;
	RR	A		;
	OUT	(22H),A		;
ESTPO1:	LD	A,14		;
	OUT	(DSPLSE),A	;	out(displ-sel,14)
	LD	A,H		;
	OUT	(DSPLDA),A	;	out(displ-data,highbyte(pos))
	LD	A,15		;
	OUT	(DSPLSE),A	;	out(displ-sel,15)
	LD	A,L		;
	OUT	(DSPLDA),A	;	out(displ-data-lowbyte(pos))
	RET			; end
;
;******************** end of display *******************
;********************   routines     *******************
;
	SUBTTL	CONIN DRIVER
	PAGE
;
;***************************** KEXBOARD DRIVER ********************************
;*****************************    ROUTINES     ********************************
;
;
;
;******************   CONST   *****************
; sample the status of the console
; A = 0FFH  if a character is ready to be read
; A =  00H  if no character is ready
;
CNST:
 	LD	DE,(KBICNT)	; get input buffer count
	OR	E		; input buffer count=0 ? (A = 0)
	JR	NZ,CNST1	;
	LD	A,1		;clear busy bit
	OUT	(0),A		;
	XOR	A		;
	RET			;done
;
CNST1:	LD	HL,(KBOPTR)	;get output counter pointer
	LD	A,(HL)		; get character from buffer
		LD	C,A		;
		CALL	CHKCS		;
		JR	Z,FUKKEY	;funktion key
		LD	A,C		;
		LD	(SAVECH),A	;
		CALL	CONV		;
		CP	0FFH		; character <1 or <31
		JR	Z,FUKKEY	;
		LD	C,A		;character to C	
	LD	A,1		;clear busy bit
	OUT	(0),A		;
		LD	A,0FFH		;
		RET			;
;
FUKKEY:		CALL	UPDPNT		;
	LD	A,1		;clear busy bit
	OUT	(0),A		;
		XOR	A		; A = 0
		RET			; done
;
; *** CHECKCS ***
; checks for control and shift keys, and update the relevant mode
;
CHKCS:		CP	SHRE		;
		JP	Z,RLSSH		; RELEASE SHIFT KEY
		CP	SHPR1		;
		JP 	Z,PRSSH		; PRESS SHIFT KEY
		CP	SHPR2		;
		JP	Z,PRSSH		; 
		CP	CTRLPR		;
		JP	Z,PRSCTL	; PRESS CTRL KEY
		CP	CTRLRE		;
		JP	Z,RLSCTL	; RELEASE CTRL KEY
		CP	ALPLCK		;
		JP	Z,LOCKA		; set or clear lamp-alpha lock
		RET			;
;
RLSSH:		LD	A,96		; A = LOWER CASE
		LD	(SHMODE),A	;
		RET			; 
PRSSH:		LD	A,64		; A = UPPER CASE
		LD	(SHMODE),A	;
		RET			;
PRSCTL:		LD	A,1		;
		LD	(CTLMDE),A	;
		RET			;
RLSCTL:		LD	A,0		;
		LD	(CTLMDE),A	;
		RET			;
;
;
;********************	CONIN	**********************
;
;read next console character into register a and set
;the parity bit to zero.
;if no character is ready, dispach until a character is typed
;
CONIN1::
		LD	DE,(KBICNT)	; get input count
		LD	A,D		;
		OR	E		; input buffer count=0 ?
		JR	NZ,SIN		; if not, continue
;
WAITFI:		LD	HL,KBESPH	; get event semaphore
		CALL	WAIT		; wait for event to occur
;
		JR	CONIN1		;
SIN:
		LD	HL,(KBOPTR)	; get output pointer
		LD	A,(HL)		; get character from buffer
		LD	C,A		;
		CALL	CHKCS		;
		JR	Z,NOASCC	;funktion key
		LD	A,C		;
		LD	(SAVECH),A	;
		CALL	CONV		;
		CP	0FFH		; character <1 or <31
		JR	Z,NOASCC	;
		PUSH	AF		; save character
		CALL	UPDPNT
		POP	AF		; restore character
		RET			; done
;
NOASCC:
		CALL	UPDPNT
		JP	CONIN1
;
UPDPNT:
		DI
		LD	HL,(KBICNT)	; get input count
		DEC	HL		; decrement serial input count
		LD	(KBICNT),HL	; update serial input count
		LD	HL,(KBOPTR)	; get output pointer
;		LD	A,(HL)		; get character from buffer
		INC	HL		; increment output pointer
		EX	DE,HL		; serial output pointer to de-reg.
		LD	HL,(KYBBUF)	; get serial input buffer address
		LD	BC,(KYBBSZ)	; get serial input buffer size
		DEC	BC		; decrement input buffer size
		ADD	HL,BC		; calc last input buffer address
		SBC	HL,DE		; buffer wrap-around ?
		JR	NC,NWAO		; if not, continue
		LD	DE,(KYBBUF)	; get input buffer address
NWAO:
		LD	(KBOPTR),DE	; update output pointer
		EI			;
		RET			; done
;
;
;*** CONV procedure
; the procedure converts the value of the key pressed
; to an ASCII character, the value returned depends upen the SHIFT and 
; CTRL modes (keys)
;
CONV:		LD	HL,HDWCNV	; hardware to logical conversion
		LD	DE,(SAVECH)	; relative address in conv. taple
		ADD	HL,DE		; 
		LD	A,(HL)		; logical key - value
		LD	(SAVECH),A	;
		LD	HL,CONVTB	; startaddress of conv. table
		LD	DE,128		;
		ADD	HL,DE		; start address of lawer case conv. table
		LD	A,(SHMODE)	;
		CP	96		; mode 96=lower case
		JR	Z,CONV1		;
		LD	DE,141		;
		ADD	HL,DE		; startaddress of upper case conv. table
CONV1:		LD	DE,(SAVECH)	; relative address in conv. table
		ADD	HL,DE		;
		LD	A,(HL)		; ASCII key-value
		LD	(SAVECH),A	; save ASCII char.
;
; check ctrl mode, if pressed then convert to ctrl-ASCII code
;
		LD	A,(CTLMDE)	;
		CP	0		;
		LD	A,(SAVECH)	; fetch current code
		JP	Z,CHLOCK	; check if lower case and return if ctrl mode = 0
;
; ctrl - mode = 1
;
		CP	12		; if char. = ctrl-clear then reset system
		JP	Z,RESET		;
		LD	A,(SHMODE)	; A = 64 or 96
		LD	B,A		;
		LD	A,(SAVECH)	;
		SUB	B		; A = A - (if lawer c. then 96 else 64)
		LD	(SAVECH),A	;
		CP	1		;
		JP	M,CHERR		;
		CP	32		;
		JP	P,CHERR		; if A < 1 or 31 < ? then error 
		RET			;
;
; ctrl error char < 1 or < 31 char
;
CHERR:		LD	A,0FFH		; dummy value
		RET			;
;
; *** if alpa lock is on then convert lower case to upper case
;
CHLOCK:		LD	HL,LBYTE2	; lamp byte no. 2
		BIT	0,(HL)		; check bit 0, lamp 12
		RET	Z		; return if bit 0 = 0 - ie. lamp not on
		LD	HL,ALFLOW	; alfalow value
		CP	(HL)		; if char. < ALFALOW or char. > ALFAHIGH then return
		RET	M		;
		INC	HL		; ALFAHIGH value
		CP	(HL)		; 
		RET	P		;
		SUB	32		;else char = char - 32 (upper case)
		RET			;
;
LOCKA:
		PUSH	AF
		LD	HL,LBYTE2	;
		LD	B,00000001B	; lamp 12
		CALL	SETLP2		;
		POP	AF		;
		RET			; done
;
;***  procedure SETLAMP  ***
; HL = lambyte SETLAMP 
;
SETLP2:
		LD	A,(HL)		; lamp byte
		AND	B		; select relevant lamp
		LD	A,(HL)		;
		JR	NZ,CLRLP2	;
		OR	B		;
		JR	OUTLP2		;
CLRLP2:		LD	C,A		;
		LD	A,B		;
		CPL			;
		LD	B,A		;
		LD	A,C		;
		AND	B		;
OUTLP2:		LD	(HL),A		;
		LD	HL,LBYTE2	; lampbyte (lock key)
		LD	A,(HL)		;
;
		LD	(SAVEPL),A	; save character
;
SENDKB:	IN	A,(KBCOMM)	; get sio status
	BIT	2,A		;transmit buffer empty ?
	JR	NZ,SENDK1	;continue if empty
	LD	HL,0		;else wait for it
	CALL	DELAY##		;
	JR	SENDKB		;
;
SENDK1:	LD	A,(SAVEPL)	;get the character
	OUT	(KBDATA),A	;and issue it to keyboard
	RET			; done
;
;
; RESET: reset system load from diskette
;
RESET:		DI			; disable interrupt
		LD	A,18H		;
		OUT	(00AH),A	;
		OUT	(00BH),A	;
		OUT	(032H),A	;
		OUT	(033H),A	;
		LD	A,3		;
		OUT	(0FDH),A	;
		OUT	(00CH),A	;
		OUT	(00DH),A	;
		OUT	(00EH),A	;
		OUT	(00FH),A	;
		LD	A,4		;
		OUT	(02CH),A	;
		OUT	(018H),A	;
		NOP			;
		JP	0000H		; enable autoload
;
;******************** end of keyboard ********************
;********************     routines    ********************
;
PINTP1:	PUSH	AF		;save register
	LD	A,DMARD		;restart display DMA
	OUT	(DMAMDE),A	;
	XOR	A		;A = 0
	OUT	(DMAKCK),A	;select display RAM, set DRQ for DMA
	POP	AF		;restore register
PINTP2:	EI			; this lable used during init.
	RETI
;
;
; *** KEYBOARD INTERRUPT ROUTINE ***
;
KBRISR::	DI
		LD	(INTSP),SP
		LD	SP,INTSTK
		PUSH	AF		;SAVE PSW
		PUSH	BC		;
		PUSH	DE		;
		PUSH	HL		;
		CALL	S0I		;check for input
		POP	HL		;restor register
		POP	DE		;
		POP	BC		;
		POP	AF		;
		LD	SP,(INTSP)	;
		EI			;return from interrupt
		RETI			;
;
S0I:		IN	A,(KBCOMM)	;
		BIT	0,A		; receive char. available ?
		RET	Z		;if not, done
		IN	A,(KBDATA)	; get data byte
		LD	C,A		;
		LD	HL,(KYBBSZ)	;get input buffer size
		LD	DE,(KBICNT)	;get input count
		INC	DE		;increment input count
		OR	A		;clear carry flag
		SBC	HL,DE		;input buffer full ?
		RET	C		;if so, done
		LD	(KBICNT),DE	;else, update input count
		LD	HL,(KYBPTR)	;get input pointer
		LD	(HL),C		;store input character in buffer
		INC	HL		;increment input pointer
		EX	DE,HL		;input buffer pointer to de-reg.
		LD	HL,(KYBBSZ)	;get input buffer size
		DEC	HL		;decrement input buffer size
		LD	BC,(KYBBUF)	;get input buffer address
		ADD	HL,BC		;calc last input buffer address
		SBC	HL,DE		;buffer wrap-around ?
		JR	NC,ISNWAO	;if not, continue
		LD	DE,(KYBBUF)	;get input buffer address
ISNWAO:		LD	(KYBPTR),DE	;update input pointer
		LD	HL,KBESPH	;GET SEMAPHOR
		LD	A,(HL)		;get semaphore count
		OR	A		;semaphore count=0 ?
		RET	Z		;if so, done
	CALL	SIGNAL##	;signal that event has occured
	RET			;done
;
KBTISR:
KBXISR:	RETI
;
	SUBTTL	COMMON MEMORY FOR INIT,CONIN,CONOUT
	PAGE
	DSEG
;
; MUTUAL-EXCLUSION INTERLOCK AND EVENT SEMAPHOR
;
INPSPH:
		DW	1		;mutual-exclusion interlock semaphor
		DW	INPSPH+2	;semaphor list forward pointer
		DW	INPSPH+2	;semaphor list backward pointer
;
MUXSPH:
		DW	1		;mutual-exclusion interlock semaphor
		DW	MUXSPH+2	;semaphor list forward pointer
		DW	MUXSPH+2	;semaphor list backward pointer
;
KBXSPH:
		DW	1		;mutual-exclusion interlock semaphor
		DW	KBXSPH+2	;semaphor list forward pointer
		DW	KBXSPH+2	;semaphor list backward pointer
;
KBESPH:
		DW	0		;semaphor count
		DW	KBESPH+2	;semaphor list forward pointer
		DW	KBESPH+2	;semaphor list backward pointer
;
TRXSPH:
		DW	1		;mutual-exclusion interlock semaphor
		DW	TRXSPH+2	;semaphor list forward pointer
		DW	TRXSPH+2	;semaphor list backward pointer
;
TRESPH:
		DW	0		;semaphor count
		DW	TRESPH+2	;semaphor list forward pointer
		DW	TRESPH+2	;semaphor list backward pointer
;
STPCRT::
		DW	1		;mutual-exclusion interlock semaphor
		DW	STPCRT+2	;semaphor list forward pointer
		DW	STPCRT+2	;semaphor list backward pointer
;
ELGPOS:		DS	2		;logpos: integer
VMXLIN:		DS	2		;maxlin: integer (last line)
ECRPOS:		DS	2		;cursorpos: integer
 					;curx and cury must folow each other
CURPRE::	DB	0C0H		; cursor presentation (block blink)
					; bit 6 and 7
ECURX:		DS	1		;   cursorx, (line no.)
ECURY:		DS	1		;   cursory, (line pos. no.)
SECURX:		DB	0		;
SECURY:		DB	0		;
ECRATR:		DS	1		;   current-attribute: byte
;
KYBBSZ::	DW	64		; input buffer size
KYBBUF:		DW	0		; input buffer address
KYBPTR:		DW	0		; input pointer
KBOPTR:		DW	0		; output pointer
KBICNT:		DW	0		; input count
KBOCHR:		DB	0		; output character
;
; misc. memory area
;
SHMODE:		DB	96		; contains current shift mode
CTLMDE:		DB	0		; contains current ctrl mode
SAVECH:		DW	0		;     -       -    key val. or ASCII
OUTCHR:		DW	0		;     -	      _    output character
SAVEIS:		DW	0		;     -    character (atten. test)
SAVEPL:		DB	0		;     -       -    in poll routine
ISRCHR:		DB	0		;     -       -    after interrupt
CURMDE:		DB	0		; cursor mode
SAVEX:		DW	0		; save x-coordinate
;
RDVAL:		DB	0FFH		; value read from keyboard
ALFLOW:		DB	0		; alfa-low value
ALFHGH:		DB	0		; alfa-high value
;
RTCCNT:		DB	1		;1 sec counter
DSPCNT:		DB	1		;start display counter (CRT-DMA)
DSPFLG:		DB	0		;display flag
DMACPL:		DB	0		;dma-complete-flag
ASYN::		DB	0		;async/sync mode on comm chanel
					;00H = async / 20H = sync
KYBLOK::	DB	0		;keyboard lock (bit 6)
POLFLG:		DB	0		;keyboard poll flag
CRT60::		DB	0		;50Hz or 60Hz CRT; 0=50Hz/0FF=60Hz
;
;
; save area for lamp bytes
;
LBYTE0:		DB	00000000B	; lamp no. 0-5, byte code 00 (bit 6+7)
LBYTE1:		DB	01000000B	; lamp no. 6-11, byte code 01 (bit 6+7)
LBYTE2:		DB	10000000B	; lamp no. 12-14,byte code 10 (bit 6+7)
					; bit 3 - audio circuit, 4+5 not used
;
; value of double keys
;
DKEYS:		DB	240Q, 263Q	; reset all d-keys - dummy value
		DB	240Q, 263Q	; shift 1 press - release
		DB	306Q, 263Q	; shift 2
		DB	200Q, 264Q	; ctrl
;
SAVE25:		DS	160		; svae area for line 25
;
;
;********** KEYBOARD CONVERSION TABLES **********
;
; hardware to logical conversion tables
;
HDWCNV:		DB	 1 , 2 , 3 , 4	;
		DB	 5 , 6 , 7 , 8	;
		DB	 9 ,0AH,0BH,0CH	;
		DB	10H,11H,12H,13H	;
		DB	14H,15H,16H, 0	;
		DB	 0 , 0 , 0 , 0	;
		DB	 0 , 0 , 0 , 0	;
		DB	 0 , 0 , 0 , 0	;
		DB	17H,18H,19H,1AH	;
		DB	1BH,1CH,1DH,1EH	;
		DB	1FH,20H,21H,22H	;
		DB	26H,27H,28H,29H	;
		DB	2AH,2BH,2CH, 0	;
		DB	 0 , 0 , 0 , 0	;
		DB	 0 , 0 , 0 , 0	;
		DB	 0 , 0 , 0 , 0	;
		DB	2DH,2EH,2FH,30H	;
		DB	31H,32H,33H,34H	;
		DB	35H,36H,37H,38H	;
		DB	3CH,3DH,3EH,3FH	;
		DB	40H,41H,42H, 0	;
		DB	 0 , 0 , 0 , 0	;
		DB	 0 , 0 , 0 , 0	;
		DB	 0 , 0 , 0 , 0	;
		DB	43H,44H,45H,46H	;
		DB	47H,48H,49H,4AH	;
		DB	4BH,4CH,4DH,4EH	;
		DB	 0 , 0 , 0 , 0	;
		DB	 0 , 0 , 0 , 0	;
		DB	 0 , 0 , 0 , 0	;
		DB	 0 , 0 , 0 , 0	;
		DB	 0 , 0 , 0 , 0	;
		DB	 0 , 0 ,59H,5AH	;
		DB	5BH,5CH,5DH,5EH	;
		DB	5FH,60H,61H,62H	;
		DB	66H,67H,68H,69H	;
		DB	6AH,6BH,6CH, 0	;
		DB	 0 , 0 , 0 , 0	;
		DB	 0 , 0 , 0 , 0	;
		DB	 0 , 0 , 0 , 0	;
		DB	 0 ,6DH,6EH,6FH	;
		DB	70H,71H,72H,73H	;
		DB	74H,75H,76H,77H	;
		DB	78H,79H,7AH,7BH	;
		DB	7CH,7DH,7EH, 0	;
		DB	 0 , 0 , 0 , 0	;
		DB	 0 , 0 , 0 , 0	;
		DB	 0 , 0 , 0 , 0	;
		DB	7FH,80H,81H,82H	;
		DB	85H, 0 , 0 ,65H	;
		DB	64H,63H,83H,84H	;
		DB	86H,87H,88H,89H	;
		DB	8AH,8BH,8CH, 0	;
		DB	 0 , 0 , 0 , 0	;
		DB	 0 , 0 , 0 , 0	;
		DB	 0 , 0 , 0 , 0	;
		DB	51H,50H,4FH,3BH	;
		DB	3AH,39H,25H,24H	;
		DB	23H,0FH,0EH,0DH	;
		DB	52H,53H,54H,55H	;
		DB	56H,57H,58H, 0	;
		DB	 0 , 0 , 0 , 0	;
		DB	 0 , 0 , 0 , 0	;
		DB	 0 , 0 , 0 , 0	;
;
;
;
	END
«eof»