|
DataMuseum.dkPresents historical artifacts from the history of: CP/M |
This is an automatic "excavation" of a thematic subset of
See our Wiki for more about CP/M Excavated with: AutoArchaeologist - Free & Open Source Software. |
top - metrics - download
Length: 16512 (0x4080) Types: TextFile Names: »EGENSUB.MAC«
└─⟦77f87173f⟧ Bits:30005981/disk3.imd Turn Key Data Entry System/Datenerfassungspaket - Vers. 1.90 └─⟦this⟧ »EGENSUB.MAC«
;************************************************* ;* * ;* MODULE : EGENSUB.MAC (RC-700) * ;* DATE : 01.02.82 * ;* BY : ASE GmbH , 6472 Altenstadt * ;* VERSION: 1.90 * ;* * ;************************************************* ; ; THIS ROUTINE CONTAINS MOST OF THE GENERAL SUBROUTINES USED THROUGH- ; THE PACKAGE. THIS VERSION IS USED IN ALL MODES EXCEPT 'FORMAT' ; 'FORMAT-UPDATE' MODES. ; PUBLIC GENSUB ; GENSUB: ; ; ; NAME : CONBTA ; FUNCTION : translates a 16-bit binary number ; to a 6-digit ascii character string. ; CALLING SEQUENCE : HL = contains the 16-bit binary number ; (IX) = points to A 6-byte buffer ; CALL CONBTA ; RETURNED VALUES : IX = points to buffer + 5 ; ERROR CONDITIONS : none ; PUBLIC CONBTA ; ; CONBTA: ld iy,p10tab ;power of ten table loop0: xor a ;set digit cnt = 0 ld e,(iy) ; ld d,(iy+1) ; loop1: and a ;clear carry sbc hl,de ;subtract power of ten jp c,jump1 ;go if done inc a ;bump digit count jp loop1 ; jump1: add hl,de ;restore to positive add a,30h ;add ascii offset ld (ix),a ;store digit count inc ix ; inc iy ; inc iy ;point to next power of 10 ld (save),a ld a,e cp 1 ld e,a ld a,(save) jp nz,loop0 ret ; ; save: ds 1 ; p10tab: dw 2710h dw 3e8h dw 64h dw 0ah dw 1h ; ; NAME : INBUFF ; FUNCTION : routine initializes a buffer with ; a given character. ; CALLING SEQUENCE : A = character to be used ; (BC) = buffer start address ; (HL) = buffer length (# bytes) ; CALL INBUFF ; PUBLIC INBUFF ; INBUFF: ld de,0h and a ; ex de,hl ; sbc hl,de ;check for zero-length ret z ;ret if zero ex de,hl ; ld de,-1 ;set de to -1 add hl,de ;-1 the buffer length ILOOP: ld (bc),a ;store the byte inc bc ;bump the pointer add hl,de ;-1 the buffer length jp c,ILOOP ;jump if not last byte ret ; ; ; ; ; NAME : DSPMSG ; FUNCTION : routine will display a message in the ; of line 25 on the crt.the caller must ; supply a legal message number.this ; routine takes the message from MSGTAB. ; setting bit 8 in the message number will ; prevent blinking and inverted display. ; the location PREMSG contains the previous ; message number which can be used to restore ; the previous message number by setting ; the a-reg to FF before calling this rout. ; CALLING SEQUENCE : A = message number (currently 0-39) ; (mess. num.without blinking 128-167) ; CALL DSPMSG ; ; ; ; MASTAD equ 0ff98h ;start of message area in ln 25 ext MSGTAB ;start message table ; PUBLIC DSPMSG PUBLIC PREMSG ; DSPMSG: ld de,MASTAD ; ld hl,MSGTAB ; cp 0ffh ; jp nz,DSPMS1 ; ld a,(PREMSG) ; DSPMS1: ld c,a ; ld (PREMSG),a ;save message ld a,c ; ld (savea),a ;save the a-reg res 7,a ;reset the non-blinking bit LOOP: cp 0 jp z,TSTBLK ; ld bc,32 ; add hl,bc ;build up the dec a ;table address by adding jp LOOP ;the 32-byte offset until done TSTBLK: ld a,(savea) ; ld b,a ; ld a,0 ; ld (savea),a ;zero savea ld a,b ;restore a bit 7,a ;test for non-blinking jp nz,MOVE ;jump for non-blinking ld a,1 ; ld (savea),a ;set the blinking marker ld a,90h ; ld (de),a ;set to blinking inc de ; MOVE: ld bc,32 ;set byte count ldir ;and move it ld a,(savea) ;test if blinking bit 0,a ;was set jp z,DDONE ;jump if not inc de ; ld a,80h ; ld (de),a ;set the stop blinking character DDONE: ret ; ; SAVEA: ds 1 ;save a-reg PREMSG: ds 1 ;previous message number ; ; ; ; NAME ; ASXDEC ; FUNCTION : routine will translate up to 5 ; ascci decimal's to a 16-bit binary value ; CALLING SEQUENCE: (DGTCNT) = must contain number of digits ; (no more the five).register IX must point ; to the first of the digits. ; CALL ASXDEC ; RETURNED VALUES : reg. HL contains 16-bit value.IX will be ; counted up according to the number of digits. ; PUBLIC ASXDEC PUBLIC DGTCNT ; DGTCNT: ds 1 ; ; ASXDEC: ld hl,DGTCNT ; ld b,(hl) ;load ld c,0h ;number of digits ld hl,0h ; AXDCLP: add hl,hl ;result x2 push hl ; add hl,hl ;x4 add hl,hl ;x8 pop de ; add hl,de ;x10 ld a,(ix) ;get next ascci character sub 30h ;convert to 0-9 ld e,a ; ld d,0h ; add hl,de ;merge in result inc ix ;bump the pointer djnz AXDCLP ;loop if not last digit ret ;ret to caller ; ; ;the following are subs used for cursor movement and buffer pointer ;control ext INTFLG ;int-flag ext UBFADD ;start of user buffer address ext SOFUBA ;start of field in user buffer ext MLNFLG ;message line flag ext GENFSB ;check for FSB's ext CBFADD ;crt buffer base address ext FBFADD ;format buffer base address ext SOFFBA ;start of field in format buffer ext DEMODE ;binary mode ext FRMLNG ;format length ext VFPCTR ;var.pos.counter ext ENTFLG ;if set: entry-mode and entry phase ext SOFCBA ;start of field in crt buffer ext CFLAG ;call flag ; CURPOS equ 0ffcch ;start position of cursor ctr in ln.25 CURLNG equ 4 ;display-length of cursor ctr in lne. 25 CRTSZE equ 1920 ;size of user-portion on crt (line 1-24) ERACRT equ 0ch ;crt erase control character CCTRL equ 06h ;cursor start sequence control character SPACE equ 20h ;space charcter LNELNG equ 50h ;current line length (80 positions) ESCCHR equ 1bh ;escape character (used as reset) CLRCHR equ ERACRT ;clear key CHRBWD equ 08h ;character backward key ENDCRT equ 0ff7fh ;last position of crt-user-area BELL equ 07h ;bell,audible alarm DHXB equ 0ffbbh ;display area for hex entry (2bytes) CR equ 0dh ;carriage return PRM equ 7fh ;prime character (printer) CTRLU equ 15h ;ctrl/U display lower half of FSB CTRLF equ 06h ;control/f (write format) HMECRS equ 1dh ;home cursor control character ; PUBLIC CHRRD PUBLIC ALLINC PUBLIC CLRCUR PUBLIC INTCRT PUBLIC INCCRS PUBLIC MOVCUR PUBLIC CURWRK PUBLIC INCCRS ; ; ; ;the following will set the cursor count to 1 (CLRCUR) or increment ;the count by 1 (MOVCUR). ; CLRCUR: ld c,HMECRS ;home the call co ;cursor ld hl,1 ;put count to 1 MOVCUR: ld ix,CURWRK ;get the ascci call CONBTA ;for the cursorcount ld hl,CURWRK + 1 ;and move ld de,CURPOS ;the cursorcnt ld bc,CURLNG ;to (currently 4 pos.) ldir ;line 25 ret ; ; CURWRK: ds 6 ; CHRRD: call ci ;preliminary read routine ret ; ;the following will xlate the german umlaut characters and ;other keys to direct keyboard code. this routine will have to be ;modified if other code-sets are used. ; ;hl-reg must contain point to the crt-buffer ;c-reg must contain the character to be xlated ; PUBLIC CHRCNV ; CHRCNV: ld a,c ; cp 7bh ;lower ae jp nz,CHRCN1 ;go if not ld a,96 ; ld (hl),a ;write xlated char to crt-buffer ret ; CHRCN1: cp 7ch ;lower oe jp nz,CHRCN2 ; ld a,126 ; ld (hl),a ; ret ; CHRCN2: cp 7dh ; jp nz,CHRCN3 ;lower ue ld a,64 ; ld (hl),a ; ret ; CHRCN3: cp 7eh ; jp nz,CHRCN4 ;double s ld a,17 ; ld (hl),a ; ret ; CHRCN4: cp 5bh ;upper AE jp nz,CHRCN5 ; ld a,6 ; ld (hl),a ; ret ; CHRCN5: cp 5ch ; jp nz,CHRCN6 ; ld a,14 ; ld (hl),a ; ret ; CHRCN6: cp 5dh ; jp nz,CHRCN7 ; ld a,00 ; ld (hl),a ; ret ; CHRCN7: cp 40h ;paragraph jp nz,CHRCN8 ; ld a,19 ; ld (hl),a ; ret ; CHRCN8: cp 60h ;hyphen jp nz,CHRCN9 ; ld a,22 ; ld (hl),a ; ret ; CHRCN9: ld (hl),c ; ret ; ; ; ;the following will increment the buffer pointers depending on ;the mode. ; ALLINC: and a ;clear carry ld bc,ENDCRT ; ld hl,(SOFCBA) ;is crt full? sbc hl,bc ; ret z ;yes dont increment ld hl,(SOFFBA) ;increment inc hl ;the format ld (SOFFBA),hl ;buffer address ; ld a,(ENTFLG) ; cp 0ffh ;is the entry-flag set? jp z,NONFR1 ;yes ld bc,(UBFADD) ;inc the ld hl,(VFPCTR) ; add hl,bc ;user buffer pointer ld (SOFUBA),hl ; ; ALLIN1: ld hl,(SOFCBA) ;inc the inc hl ;crt ld (SOFCBA),hl ;buffer address ; ld a,(INTFLG) ; cp 0ffh ;is the int-flag set? call nz,INCCRS ;no inc the cursor ret ; NONFR1: ld hl,(SOFUBA) ;inc the inc hl ;user buffer ld (SOFUBA),hl ;directly jp ALLIN1 ;join the routine again ; ; ;the following will calculate the X-Y cursor position coordinates ;from the current states of the buffer pointers. ; INCCRS: and a ;clear the carry ld de,(CBFADD) ;calculate offset ld hl,(SOFCBA) ; sbc hl,de ;into crt buffer xor a ;clear a ld de,lnelng ;load the line length constant INCLP: and a ;clear carry sbc hl,de ; jp c,INCDN ;found number of lines inc a ;inc up line count jp INCLP ;keep going INCDN: add hl,de ;restore hl to positive ld (YCORD),a ; ld a,l ; ld (XCORD),a ; ; ;XCORD contains now the column count (X) ;YCORD contains now the line count (Y) ;the following will physically position the cursor ; ld c,CCTRL ;send cursor call co ;control character ld a,(XCORD) ; add a,32 ;get col. + 32 ld c,a ; call co ;and send it ld a,(YCORD) ; add a,32 ; ld c,a ;get line + 32 call co ;and send it. ; ;cursor should be positioned now ;the following will set the cursor count depending on the ;current mode. ; ld a,(DEMODE) ; cp 03h ;format mode ? jp z,UPCFRM ;yes bypass cp 04h ;format update ? jp nz,NONFRM ;nonformatting mode! UPCFRM: ld hl,(SOFCBA) ;get the ld de,(CBFADD) ;crt offset and a ;clear the carry sbc hl,de ; inc hl ; UPCC: ld a,(MLNFLG) ; cp 0ffh ;is msg.line flag set? jp z,MLFRST ;yes. call MOVCUR ;update the cursor count ret ; NONFRM: ld hl,(SOFUBA) ;use user buffer for cursor ld de,(UBFADD) ;counting on non-formatting and a ; sbc hl,de ;mode's inc hl ; jp UPCC ; ; MLFRST: ld a,0h ; ld (MLNFLG),a ; ret ; ; ; ; ;the following will clear and initialize the screen. ; INTCRT: push hl ; ld hl,INTCR1 ; ld (hl),a ; push bc ; ld c,ERACRT ;clear the CRT call co ; ld bc,(CBFADD) ; ld (SOFCBA),bc ; ld a,SPACE ; ld hl,2000 ; call INBUFF ; ld c,1dh ;home the cursor call co ; ld c,CCTRL ;fake the blanking call co ; ld c,33 ;by sending call co ;a space ld c,57 ; call co ;the ld c,SPACE ;last position -1 call co ;in the crt ld hl,(CBFADD) ; ld de,1921 ; add hl,de ; ld a,20h ; ld (hl),a ; ld hl,INTCR1 ; ld a,(hl) ; pop bc ; pop hl ; ret ; ; INTCR1: ds 1 ; XCORD: db 00h ; YCORD: db 00h ; ; ; ;the following allows standard entries to the following bios ;facillities : WBOOT,CONST,CONIN,CONOUT,LIST ; PUBLIC BOOT PUBLIC CONST PUBLIC co PUBLIC ci PUBLIC LIST ; ext BIOSBS ; BOOT: ld hl,(BIOSBS) ld de,3 ; jp GOBIOS ; CONST: ld hl,(BIOSBS) ; ld de,6 ; jp GOBIOS ; co: ld hl,(BIOSBS) ; ld de,12 ; jp GOBIOS ; ci: ld hl,(BIOSBS) ; ld de,9 ; jp GOBIOS ; LIST: ld hl,(BIOSBS) ; ld de,15 ; GOBIOS: add hl,de ; jp (hl) ; ; ;programm goes of to bios and will return direct from there ; ; ; ;the following will add 2 bcd-strings of 16 digits (8 bytes) each. ;if the result exceeds the 8 byte capacity , the overflow-flag ; (OVFFLG) will be set. the routine works as follows: ; STR2 plus STR1 = STR2 ; ; NAME: ADD ; CALLING SEQUENCE: STR1 = operand 2 ; STR2 = operand 1 ; CALL ADD PUBLIC ADD ; ADD: ld a,00h ; ld (STR3),a ; ld (STR4),a ; ld (STR5),a ; ld (STR6),a ; LD A,(BCDCNT) ; LD B,A ; ld a,00h ; ld (NEGFLG),a ; ld de,STR2 ; ld hl,STR1 ; AND A ; DECAD: LD A,(de) ; ADC A,(hl) ; DAA ; LD (de),A ; INC DE ; INC HL ; DEC B ; JP NZ,DECAD ; jp c,ADD1 ; ENDADD: ret ; ; ADD1: ld a,0ffh ; ld (NEGFLG),a ;set overflow flag jp ENDADD ; ; ;the following will subtract two bcd-strings of 16 digits (8 bytes) ;length. if the result is negativ the NEGFLG will be set to ff, ;otherwise it will be zero. ;the routine works in the following fashion: STR2 minus STR1 = STR2 . ; ; NAME: SUB ; CALLING SEQUENCE: STR1 = operand 2 ; STR2 = operand 1 ; CALL SUB PUBLIC SUB PUBLIC NEGFLG PUBLIC STR1 PUBLIC STR2 ; ext OPFLG ; SUB: ld a,00h ; ld (NEGFLG),a ; ld (PSFLG),a ; ld a,09h ; ld (STR3),a ; ld a,90h ; ld (STR5),a ; ld a,(STR6) ; or 90h ; ld (STR6),a ; ld a,01h ; ld (STR4),a ; ld a,(BCDCNT) ; ld b,a ; SUB1: ld hl,STR1 ; ld de,STR2 ; AND A ; DECSUB: LD A,(DE) ; SBC A,(HL) ; DAA ; LD (DE),A ; INC DE ; INC HL ; DEC B ; JP NZ,DECSUB ; jp c,SUB2 ; SUB3: jp ENDSUB ; ; SUB2: ld a,(PSFLG) ; cp 0ffh ;pass flag set? jp z,SUB3 ;yes. ld hl,STR2 ; ld de,STR1 ; ld bc,8 ; ldir ; ld a,00h ; ld bc,STR2 ; ld hl,08 ; call INBUFF ; ld a,0ffh ; ld (NEGFLG),a ; ld (PSFLG),a ;set pass-flag. ld b,9 ; jp SUB1 ; ; ;the following checks for an all-zero result after a negativ-subtract ;(i.e.after the second pass) and resets the negativ-flag. ; ENDSUB: ld a,(PSFLG) ; cp 0ffh ; ret z ; ld b,7h ; ld hl,STR2 ; SUB5: ld a,(hl) ; cp 00h ; ret nz ;found a nonzero digit. inc hl ; dec b ; jp nz,SUB5 ;loop for next digit ld b,(hl) ; ld a,0fh ; and b ; and a ; ret nz ; ld a,(OPFLG) ; cp 00h ; jp z,SUB4 ; cp 02h ; ret nz ; SUB4: ld a,0ffh ; ld (NEGFLG),a ; ret ; ; BCDCNT: db 08 ; STR2: ds 07 ; STR5: db 90h ; STR4: db 01h ; STR1: ds 07 ; STR6: db 90h ; STR3: db 09h ; NEGFLG: db 00h ; PSFLG: db 00h ; ; ; ; NAME: BCDAXB ; FUNCTION: to convert a string of x ascii decimal ; characters to a string of bcd-halfbytes. ; CALLING SEQUENCE: reg IX contains pointer to ; last position of ascii string. ; reg HL contains pointer to start of bcd-string. ; reg B contains number of digits to be converted ; CALL BCDAXB ; PUBLIC BCDAXB ; BCDAXB: ld a,00h ; cp b ;zero digits to do? jp z,BCDEND ;yes BCDAX4: ld a,(ix) ;get character call BCDAX2 ;check decimal range cp 0ffh ;non-decimal? jp z,BCDAX4 ;yes sub 30h ;convert to bcd rrd ;rotate to hl dec b ; jp m,BCDEND ;go if started with 0 digits to convert jp nz,BCDAX1 ;go if more to convert rrd ; jp BCDEND ;conversion complete BCDAX1: ld a,(ix-1) ;get next character call BCDAX2 ;check decimal range cp 0ffh ;non-decimal? jp z,BCDAX1 ;yes. sub 30h ; rrd ;rotate to hl dec ix ;bump ascci pointer dec ix ; inc hl ;bump bcd-pointer dec b ;dec counter jp m,BCDEND ; jp nz,BCDAX4 ; BCDEND: ret ;all done! ; ; ;the following checks decimal range and if it is not decimal ;sets the a-reg to ffh which prevents the character from being ;converted. ; BCDAX2: ld c,a ;save a to c ld a,2fh ; and a ; sub c ; jp p,BCDAX3 ;not decimal, < 30h ld a,39h ; cpl ; add a,c ; jp p,BCDAX3 ;not decimal, > 39h ld a,c ; ret ;within decimal range BCDAX3: ld a,0ffh ; dec ix ;bump ascii pointer dec b ;dec digit ctr ret ; ; ; NAME: BXBCDA ; FUNCTION:to convert a string of x bcd-digits ; to a string of ascii decimals. ; CALLING SEQUENCE: reg IX as above ; reg HL and B also as above (under BCDAXB) ; CALL BXBCDA ; PUBLIC BXBCDA ; BXBCDA: xor a ; rrd ; add a,30h ; ld (ix),a ; dec b ; ld a,b ; cp 00h ; jp z,BXBEND ; xor a ; rrd ; add a,30h ; ld (ix-1),a ; dec ix ; dec ix ; inc hl ; dec b ; jp nz,BXBCDA ; BXBEND: ld a,90h ; ld (STR5),a ; ld (STR6),a ; ld a,01h ; ld (STR4),a ; ld a,09h ; ld (STR3),a ; ld a,00h ; ld bc,STR2 ; ld hl,7 ; call INBUFF ; ld a,00h ; ld bc,STR1 ; ld hl,7 ; call INBUFF ; ret ; ; ;the following will be the multiplication routine. ; PUBLIC MUL ; MUL: ret ; ; end ; «eof»