diff --git a/ISIS PLM/ASM.COM b/ISIS PLM/ASM.COM new file mode 100644 index 0000000..a63e5ae Binary files /dev/null and b/ISIS PLM/ASM.COM differ diff --git a/ISIS PLM/ASM80 b/ISIS PLM/ASM80 new file mode 100644 index 0000000..f73cd02 Binary files /dev/null and b/ISIS PLM/ASM80 differ diff --git a/ISIS PLM/BDOS.MAC b/ISIS PLM/BDOS.MAC new file mode 100644 index 0000000..352d8de --- /dev/null +++ b/ISIS PLM/BDOS.MAC @@ -0,0 +1,2776 @@ + title 'Bdos Interface, Bdos, Version 2.2 Feb, 1980' + + .Z80 + aseg + org 100h + maclib MEMCFG.LIB ; define configuration parameters + .phase bdosph +bios equ biosph + +;***************************************************************** +;***************************************************************** +;** ** +;** B a s i c D i s k O p e r a t i n g S y s t e m ** +;** I n t e r f a c e M o d u l e ** +;** ** +;***************************************************************** +;***************************************************************** + +; Copyright (c) 1978, 1979, 1980 +; Digital Research +; Box 579, Pacific Grove +; California + + +; 20 january 1980 + +ssize equ 24 ;24 level stack + +; low memory locations +reboot equ 0000h ;reboot system +ioloc equ 0003h ;i/o byte location +bdosa equ 0006h ;address field of jp BDOS + +; bios access constants +bootf defl bios+3*0 ;cold boot function +wbootf defl bios+3*1 ;warm boot function +constf defl bios+3*2 ;console status function +coninf defl bios+3*3 ;console input function +conoutf defl bios+3*4 ;console output function +listf defl bios+3*5 ;list output function +punchf defl bios+3*6 ;punch output function +readerf defl bios+3*7 ;reader input function +homef defl bios+3*8 ;disk home function +seldskf defl bios+3*9 ;select disk function +settrkf defl bios+3*10 ;set track function +setsecf defl bios+3*11 ;set sector function +setdmaf defl bios+3*12 ;set dma function +readf defl bios+3*13 ;read disk function +writef defl bios+3*14 ;write disk function +liststf defl bios+3*15 ;list status function +sectran defl bios+3*16 ;sector translate + +; equates for non graphic characters +ctlc equ 03h ;control c +ctle equ 05h ;physical eol +ctlh equ 08h ;backspace +ctlp equ 10h ;prnt toggle +ctlr equ 12h ;repeat line +ctls equ 13h ;stop/start screen +ctlu equ 15h ;line delete +ctlx equ 18h ;=ctl-u +ctlz equ 1ah ;end of file +rubout equ 7fh ;char delete +tab equ 09h ;tab char +cr equ 0dh ;carriage return +lf equ 0ah ;line feed +ctl equ 5eh ;up arrow + + db 0,0,0,0,0,0 + +; enter here from the user's program with function number in c, +; and information address in d,e + jp bdose ;past parameter block + +; ************************************************ +; *** relative locations 0009 - 000e *** +; ************************************************ +pererr: dw persub ;permanent error subroutine +selerr: dw selsub ;select error subroutine +roderr: dw rodsub ;ro disk error subroutine +roferr: dw rofsub ;ro file error subroutine + + +bdose: ex de,hl ;arrive here from user programs + ld (info),hl + ex de,hl ;info=DE, DE=info + ld a,e + ld (linfo),a ;linfo = low(info) - don't equ + ld hl,0 + ld (aret),hl ;return value defaults to 0000 + ;save user's stack pointer, set to local stack + add hl,sp + ld (entsp),hl ;entsp = stackptr + ld sp,lstack ;local stack setup + xor a + ld (fcbdsk),a + ld (resel),a ;fcbdsk,resel=false + ld hl,goback ;return here after all functions + push hl ;jmp goback equivalent to ret + ld a,c + cp nfuncs + ret nc ;skip if invalid # + ld c,e ;possible output character to C + ld hl,functab + ld e,a + ld d,0 ;DE=func, HL=.ciotab + add hl,de + add hl,de + ld e,(hl) + inc hl + ld d,(hl) ;DE=functab(func) + ld hl,(info) ;info in DE for later xchg + ex de,hl + jp (hl) ;dispatched + +; dispatch table for functions +functab: + dw wbootf, func1, func2, func3 + dw punchf, listf, func6, func7 + dw func8, func9, func10,func11 +diskf equ ($-functab)/2 ;disk funcs + dw func12,func13,func14,func15 + dw func16,func17,func18,func19 + dw func20,func21,func22,func23 + dw func24,func25,func26,func27 + dw func28,func29,func30,func31 + dw func32,func33,func34,func35 + dw func36,func37,func38,func39 + dw func40 +nfuncs equ ($-functab)/2 + + +; error subroutines +persub: ld hl,permsg ;report permanent error + call errflg ;to report the error + cp ctlc + jp z,reboot ;reboot if response is ctlc + ret ;and ignore the error + +selsub: ld hl,selmsg ;report select error + jp wait$err ;wait console before boot + +rodsub: ld hl,rodmsg ;report write to read/only disk + jp wait$err ;wait console + +rofsub: ;report read/only file + ld hl,rofmsg ;drop through to wait for console + +wait$err: ;wait for response before boot + call errflg + jp reboot + +; error messages +dskmsg: db 'Bdos Err On ' +dskerr: db ' : $' ;filled in by errflg +permsg: db 'Bad Sector$' +selmsg: db 'Select$' +rofmsg: db 'File ' +rodmsg: db 'R/O$' + + +errflg: push hl ;report error to console, message address in HL + call crlf ;stack mssg address, new line + ld a,(curdsk) + add a,'A' + ld (dskerr),a ;current disk name + ld bc,dskmsg + call print ;the error message + pop bc + call print ;error mssage tail +; jp conin ;to get the input character + ;(drop through to conin) +; ret + + +; console handlers +conin: ld hl,kbchar ;read console character to A + ld a,(hl) + ld (hl),0 + or a + ret nz + ;no previous keyboard character ready + jp coninf ;get character externally +; ret +conech: call conin ;read character with echo + call echoc + ret c ;echo character? + ;character must be echoed before return + push af + ld c,a + call tabout + pop af + ret ;with character in A + +echoc: ;echo character if graphic + cp cr ;cr, lf, tab, or backspace + ret z ;carriage return? + cp lf + ret z ;line feed? + cp tab + ret z ;tab? + cp ctlh + ret z ;backspace? + cp ' ' + ret ;carry set if not graphic + +conbrk: ;check for character ready + ld a,(kbchar) + or a + jp nz,conb1 ;skip if active kbchar + ;no active kbchar, check external break + call constf + and 1 + ret z ;return if no char ready + ;character ready, read it + call coninf ;to A + cp ctls + jp nz,conb0 ;check stop screen function + ;found ctls, read next character + call coninf ;to A + cp ctlc + jp z,reboot ;ctlc implies re-boot + ;not a reboot, act as if nothing has happened + xor a + ret ;with zero in accumulator +conb0: + ;character in accum, save it + ld (kbchar),a +conb1: + ;return with true set in accumulator + ld a,1 + ret + +conout: ;compute character position/write console char from C + ;compcol = true if computing column position + ld a,(compcol) + or a + jp nz,compout + ;write the character, then compute the column + ;write console character from C + push bc + call conbrk ;check for screen stop function + pop bc + push bc ;recall/save character + call conoutf ;externally, to console + pop bc + push bc ;recall/save character + ;may be copying to the list device + ld a,(listcp) + or a + call nz,listf ;to printer, if so + pop bc ;recall the character +compout: + ld a,c ;recall the character + ;and compute column position + ld hl,column ;A = char, HL = .column + cp rubout + ret z ;no column change if nulls + inc (hl) ;column = column + 1 + cp ' ' + ret nc ;return if graphic + ;not graphic, reset column position + dec (hl) ;column = column - 1 + ld a,(hl) + or a + ret z ;return if at zero + ;not at zero, may be backspace or end line + ld a,c ;character back to A + cp ctlh + jp nz,notbacksp + ;backspace character + dec (hl) ;column = column - 1 + ret + +notbacksp: ;not a backspace character, eol? + cp lf + ret nz ;return if not + ;end of line, column = 0 + ld (hl),0 ;column = 0 + ret + +ctlout: ;send C character with possible preceding up-arrow + ld a,c + call echoc ;cy if not graphic (or special case) + jp nc,tabout ;skip if graphic, tab, cr, lf, or ctlh + ;send preceding up arrow + push af + ld c,ctl + call conout ;up arrow + pop af + or 40h ;becomes graphic letter + ld c,a ;ready to print + ;(drop through to tabout) + +tabout: ;expand tabs to console + ld a,c + cp tab + jp nz,conout ;direct to conout if not + ;tab encountered, move to next tab position +tab0: ld c,' ' + call conout ;another blank + ld a,(column) + and 111b ;column mod 8 = 0 ? + jp nz,tab0 ;back for another if not + ret + +backup: ;back-up one screen position + call pctlh + ld c,' ' + call conoutf +; (drop through to pctlh) +pctlh: ;send ctlh to console without affecting column count + ld c,ctlh + jp conoutf +; ret +crlfp: ;print #, cr, lf for ctlx, ctlu, ctlr functions + ;then move to strtcol (starting column) + ld c,'#' + call conout + call crlf ;column = 0, move to position strtcol +crlfp0: ld a,(column) + ld hl,strtcol + cp (hl) + ret nc ;stop when column reaches strtcol + ld c,' ' + call conout ;print blank + jp crlfp0 + +crlf: ld c,cr ;carriage return line feed sequence + call conout + ld c,lf + jp conout +; ret +print: ld a,(bc) ;print message until M(BC) = '$' + cp '$' + ret z ;stop on $ + ;more to print + inc bc + push bc + ld c,a ;char to C + call tabout ;another character printed + pop bc + jp print + +read: ;read to info address (max length, current length, buffer) + ld a,(column) + ld (strtcol),a ;save start for ctl-x, ctl-h + ld hl,(info) + ld c,(hl) + inc hl + push hl + ld b,0 + ;B = current buffer length, + ;C = maximum buffer length, + ;HL= next to fill - 1 +readnx: ;read next character, BC, HL active + push bc + push hl ;blen, cmax, HL saved +readn0: call conin ;next char in A + and 7fh ;mask parity bit + pop hl + pop bc ;reactivate counters + cp cr + jp z,readen ;end of line? + cp lf + jp z,readen ;also end of line + cp ctlh + jp nz,noth ;backspace? + ;do we have any characters to back over? + ld a,b + or a + jp z,readnx + ;characters remain in buffer, backup one + dec b ;remove one character + ld a,(column) + ld (compcol),a ;col > 0 + ;compcol > 0 marks repeat as length compute + jp linelen ;uses same code as repeat + +noth: ;not a backspace + cp rubout + jp nz,notrub ;rubout char? + ;rubout encountered, rubout if possible + ld a,b + or a + jp z,readnx ;skip if len=0 + ;buffer has characters, resend last char + ld a,(hl) + dec b + dec hl ;A = last char + ;blen=blen-1, next to fill - 1 decremented + jp rdech1 ;act like this is an echo + +notrub: ;not a rubout character, check end line + cp ctle + jp nz,note ;physical end line? + ;yes, save active counters and force eol + push bc + push hl + call crlf + xor a + ld (strtcol),a ;start position = 00 + jp readn0 ;for another character + +note: ;not end of line, list toggle? + cp ctlp + jp nz,notp ;skip if not ctlp + ;list toggle - change parity + push hl ;save next to fill - 1 + ld hl,listcp ;HL=.listcp flag + ld a,1 + sub (hl) ;True-listcp + ld (hl),a ;listcp = not listcp + pop hl + jp readnx ;for another char + +notp: ;not a ctlp, line delete? + cp ctlx + jp nz,notx + pop hl ;discard start position + ;loop while column > strtcol +backx: ld a,(strtcol) + ld hl,column + cp (hl) + jp nc,read ;start again + dec (hl) ;column = column - 1 + call backup ;one position + jp backx + +notx: ;not a control x, control u? + ;not control-X, control-U? + cp ctlu + jp nz,notu ;skip if not + ;delete line (ctlu) + call crlfp ;physical eol + pop hl ;discard starting position + jp read ;to start all over + +notu: ;not line delete, repeat line? + cp ctlr + jp nz,notr +linelen: ;repeat line, or compute line len (ctlh) + ;if compcol > 0 + push bc + call crlfp ;save line length + pop bc + pop hl + push hl + push bc + ;bcur, cmax active, beginning buff at HL +rep0: ld a,b + or a + jp z,rep1 ;count len to 00 + inc hl + ld c,(hl) ;next to print + dec b + push bc + push hl ;count length down + call ctlout ;character echoed + pop hl + pop bc ;recall remaining count + jp rep0 ;for the next character + +rep1: ;end of repeat, recall lengths + ;original BC still remains pushed + push hl ;save next to fill + ld a,(compcol) + or a ;>0 if computing length + jp z,readn0 ;for another char if so + ;column position computed for ctlh + ld hl,column + sub (hl) ;diff > 0 + ld (compcol),a ;count down below + ;move back compcol-column spaces +backsp: ;move back one more space + call backup ;one space + ld hl,compcol + dec (hl) + jp nz,backsp + jp readn0 ;for next character + +notr: ;not a ctlr, place into buffer +rdecho: inc hl + ld (hl),a ;character filled to mem + inc b ;blen = blen + 1 +rdech1: ;look for a random control character + push bc + push hl ;active values saved + ld c,a ;ready to print + call ctlout ;may be up-arrow C + pop hl + pop bc + ld a,(hl) ;recall char + cp ctlc ;set flags for reboot test + ld a,b ;move length to A + jp nz,notc ;skip if not a control c + cp 1 ;control C, must be length 1 + jp z,reboot ;reboot if blen = 1 + ;length not one, so skip reboot +notc: ;not reboot, are we at end of buffer? + cp c + jp c,readnx ;go for another if not +readen: ;end of read operation, store blen + pop hl + ld (hl),b ;M(current len) = B + ld c,cr + jp conout ;return carriage +; ret +func1: ;return console character with echo + call conech + jp sta$ret + +func2 equ tabout + ;write console character with tab expansion + +func3: ;return reader character + call readerf + jp sta$ret + +;func4: equated to punchf + ;write punch character + +;func5: equated to listf + ;write list character + ;write to list device + +func6: ;direct console i/o - read if 0ffh + ld a,c + inc a + jp z,dirinp ;0ffh => 00h, means input mode + inc a + jp z,constf ;0feH in C for status + ;direct output function + jp conoutf + +dirinp: call constf ;status check + or a + jp z,retmon ;skip, return 00 if not ready + ;character is ready, get it + call coninf ;to A + jp sta$ret + +func7: ;return io byte + ld a,(ioloc) + jp sta$ret + +func8: ;set i/o byte + ld hl,ioloc + ld (hl),c + ret ;jmp goback + +func9: ;write line until $ encountered + ex de,hl ;was lhld info + ld c,l + ld b,h ;BC=string address + jp print ;out to console + +func10 equ read + ;read a buffered console line + +func11: ;check console status + call conbrk + ;(drop through to sta$ret) +sta$ret: ;store the A register to aret + ld (aret),a +func$ret: + ret ;jmp goback (pop stack for non cp/m functions) + +setlret1: ;set lret = 1 + ld a,1 + jp sta$ret + + + +; data areas + +compcol: + db 0 ;true if computing column position +strtcol: + db 0 ;starting column position after read +column: db 0 ;column position +listcp: db 0 ;listing toggle +kbchar: db 0 ;initial key char = 00 +entsp: ds 2 ;entry stack pointer + ds ssize*2 ;stack size +lstack: +; end of Basic I/O System + +;***************************************************************** +;***************************************************************** + +; common values shared between bdosi and bdos +usrcode: + db 0 ;current user number +curdsk: db 0 ;current disk number +info: ds 2 ;information address +aret: ds 2 ;address value to return +lret equ aret ;low(aret) + +;***************************************************************** +;***************************************************************** +;** ** +;** B a s i c D i s k O p e r a t i n g S y s t e m ** +;** ** +;***************************************************************** +;***************************************************************** + +dvers equ 22h ;version 2.2 +; module addresses + +; literal constants +true equ 0ffh ;constant true +false equ 000h ;constant false +enddir equ 0ffffh ;end of directory +byte equ 1 ;number of bytes for "byte" type +word equ 2 ;number of bytes for "word" type + +; fixed addresses in low memory +tfcb equ 005ch ;default fcb location +tbuff equ 0080h ;default buffer location + +; fixed addresses referenced in bios module are +; pererr (0009), selerr (000c), roderr (000f) + +; error message handlers + +;per$error: ;report permanent error to user +; ld hl,pererr +; jp goerr + +;rod$error: ;report read/only disk error +; ld hl,roderr +; jp goerr + +;rof$error: ;report read/only file error +; ld hl,roferr +; jp goerr + +sel$error: ;report select error + ld hl,selerr + + +goerr: ;HL = .errorhandler, call subroutine + ld e,(hl) + inc hl + ld d,(hl) ;address of routine in DE + ex de,hl + jp (hl) ;to subroutine + + + +; local subroutines for bios interface + +move: ;move data length of length C from source DE to + ;destination given by HL + inc c ;in case it is zero +move0: dec c + ret z ;more to move + ld a,(de) + ld (hl),a ;one byte moved + inc de + inc hl ;to next byte + jp move0 + +selectdisk: ;select the disk drive given by curdsk, and fill + ;the base addresses curtrka - alloca, then fill + ;the values of the disk parameter block + ld a,(curdsk) + ld c,a ;current disk# to c + ;lsb of e = 0 if not yet logged - in + call seldskf ;HL filled by call + ;HL = 0000 if error, otherwise disk headers + ld a,h + or l + ret z ;return with 0000 in HL and z flag + ;disk header block address in hl + ld e,(hl) + inc hl + ld d,(hl) + inc hl ;DE=.tran + ld (cdrmaxa),hl + inc hl + inc hl ;.cdrmax + ld (curtrka),hl + inc hl + inc hl ;HL=.currec + ld (curreca),hl + inc hl + inc hl ;HL=.buffa + ;DE still contains .tran + ex de,hl + ld (tranv),hl ;.tran vector + ld hl,buffa ;DE= source for move, HL=dest + ld c,addlist + call move ;addlist filled + ;now fill the disk parameter block + ld hl,(dpbaddr) + ex de,hl ;DE is source + ld hl,sectpt ;HL is destination + ld c,dpblist + call move ;data filled + ;now set single/double map mode + ld hl,(maxall) ;largest allocation number + ld a,h ;00 indicates < 255 + ld hl,single + ld (hl),true ;assume a=00 + or a + jp z,retselect + ;high order of maxall not zero, use double dm + ld (hl),false +retselect: + ld a,true + or a + ret ;select disk function ok + +home: ;move to home position, then offset to start of dir + call homef ;move to track 00, sector 00 reference + ;lxi h,offset ;mov c,m ;inx h ;mov b,m ;call settrkf + ;first directory position selected + xor a ;constant zero to accumulator + ld hl,(curtrka) + ld (hl),a + inc hl + ld (hl),a ;curtrk=0000 + ld hl,(curreca) + ld (hl),a + inc hl + ld (hl),a ;currec=0000 + ;curtrk, currec both set to 0000 + ret + +rdbuff: ;read buffer and check condition + call readf ;current drive, track, sector, dma + jp diocomp ;check for i/o errors + +wrbuff: ;write buffer and check condition + ;write type (wrtype) is in register C + ;wrtype = 0 => normal write operation + ;wrtype = 1 => directory write operation + ;wrtype = 2 => start of new block + call writef ;current drive, track, sector, dma +diocomp: ;check for disk errors + or a + ret z + ld hl,pererr + jp goerr + +seek$dir: ;seek the record containing the current dir entry + ld hl,(dcnt) ;directory counter to HL + ld c,dskshf + call hlrotr ;value to HL + ld (arecord),hl + ld (drec),hl ;ready for seek +; jp seek +; ret + + +seek: ;seek the track given by arecord (actual record) + ;local equates for registers + ;load the registers from memory + ld hl,arecord + ld c,(hl) + inc hl + ld b,(hl) + ld hl,(curreca) + ld e,(hl) + inc hl + ld d,(hl) + ld hl,(curtrka) + ld a,(hl) + inc hl + ld h,(hl) + ld l,a + ;loop while arecord < currec +seek0: ld a,c + sub e + ld a,b + sbc a,d + jp nc,seek1 ;skip if arecord >= currec + ;currec = currec - sectpt + push hl + ld hl,(sectpt) + ld a,e + sub l + ld e,a + ld a,d + sbc a,h + ld d,a + pop hl + ;curtrk = curtrk - 1 + dec hl + jp seek0 ;for another try + +seek1: ;look while arecord >= (t:=currec + sectpt) + push hl + ld hl,(sectpt) + add hl,de ;HL = currec+sectpt + jp c,seek2 ;can be > FFFFH + ld a,c + sub l + ld a,b + sbc a,h + jp c,seek2 ;skip if t > arecord + ;currec = t + ex de,hl + ;curtrk = curtrk + 1 + pop hl + inc hl + jp seek1 ;for another try + +seek2: pop hl + ;arrive here with updated values in each register + push bc + push de + push hl ;to stack for later + ;stack contains (lowest) BC=arecord, DE=currec, HL=curtrk + ex de,hl + ld hl,(offset) + add hl,de ;HL = curtrk+offset + ld b,h + ld c,l + call settrkf ;track set up + ;note that BC - curtrk is difference to move in bios + pop de ;recall curtrk + ld hl,(curtrka) + ld (hl),e + inc hl + ld (hl),d ;curtrk updated + ;now compute sector as arecord-currec + pop de ;recall currec + ld hl,(curreca) + ld (hl),e + inc hl + ld (hl),d + pop bc ;BC=arecord, DE=currec + ld a,c + sub e + ld c,a + ld a,b + sbc a,d + ld b,a + ld hl,(tranv) + ex de,hl ;BC=sector#, DE=.tran + call sectran ;HL = tran(sector) + ld c,l + ld b,h ;BC = tran(sector) + jp setsecf ;sector selected +; ret + +; file control block (fcb) constants +empty equ 0e5h ;empty directory entry +lstrec equ 127 ;last record# in extent +recsiz equ 128 ;record size +fcblen equ 32 ;file control block size +dirrec equ recsiz/fcblen ;directory elts / record +dskshf equ 2 ;log2(dirrec) +dskmsk equ dirrec-1 +fcbshf equ 5 ;log2(fcblen) + +extnum equ 12 ;extent number field +maxext equ 31 ;largest extent number +ubytes equ 13 ;unfilled bytes field +modnum equ 14 ;data module number +maxmod equ 15 ;largest module number +fwfmsk equ 80h ;file write flag is high order modnum +namlen equ 15 ;name length +reccnt equ 15 ;record count field +dskmap equ 16 ;disk map field +lstfcb equ fcblen-1 +nxtrec equ fcblen +ranrec equ nxtrec+1 ;random record field (2 bytes) + +; reserved file indicators +rofile equ 9 ;high order of first type char +invis equ 10 ;invisible file in dir command +; equ 11 ;reserved + +; utility functions for file access + +dm$position: ;compute disk map position for vrecord to HL + ld hl,blkshf + ld c,(hl) ;shift count to C + ld a,(vrecord) ;current virtual record to A +dmpos0: or a + rra + dec c + jp nz,dmpos0 + ;A = shr(vrecord,blkshf) = vrecord/2**(sect/block) + ld b,a ;save it for later addition + ld a,8 + sub (hl) ;8-blkshf to accumulator + ld c,a ;extent shift count in register c + ld a,(extval) ;extent value ani extmsk +dmpos1: + ;blkshf = 3,4,5,6,7, C=5,4,3,2,1 + ;shift is 4,3,2,1,0 + dec c + jp z,dmpos2 + or a + rla + jp dmpos1 + +dmpos2: ;arrive here with A = shl(ext and extmsk,7-blkshf) + add a,b ;add the previous shr(vrecord,blkshf) value + ;A is one of the following values, depending upon alloc + ;bks blkshf + ;1k 3 v/8 + extval * 16 + ;2k 4 v/16+ extval * 8 + ;4k 5 v/32+ extval * 4 + ;8k 6 v/64+ extval * 2 + ;16k 7 v/128+extval * 1 + ret ;with dm$position in A + +getdm: ;return disk map value from position given by BC + ld hl,(info) ;base address of file control block + ld de,dskmap + add hl,de ;HL =.diskmap + add hl,bc ;index by a single byte value + ld a,(single) ;single byte/map entry? + or a + jp z,getdmd ;get disk map single byte + ld l,(hl) + ld h,0 + ret ;with HL=00bb +getdmd: + add hl,bc ;HL=.fcb(dm+i*2) + ;double precision value returned + ld e,(hl) + inc hl + ld d,(hl) + ex de,hl + ret + +index: ;compute disk block number from current fcb + call dm$position ;0...15 in register A + ld c,a + ld b,0 + call getdm ;value to HL + ld (arecord),hl + ret + +allocated: ;called following index to see if block allocated + ld hl,(arecord) + ld a,l + or h + ret + +atran: ;compute actual record address, assuming index called + ld a,(blkshf) ;shift count to reg A + ld hl,(arecord) +atran0: add hl,hl + dec a + jp nz,atran0 ;shl(arecord,blkshf) + ld (arecord1),hl ;save shifted block # + ld a,(blkmsk) + ld c,a ;mask value to C + ld a,(vrecord) + and c ;masked value in A + or l + ld l,a ;to HL + ld (arecord),hl ;arecord=HL or (vrecord and blkmsk) + ret + +getexta: ;get current extent field address to A + ld hl,(info) + ld de,extnum + add hl,de ;HL=.fcb(extnum) + ret + +getfcba: ;compute reccnt and nxtrec addresses for get/setfcb + ld hl,(info) + ld de,reccnt + add hl,de + ex de,hl ;DE=.fcb(reccnt) + ld hl,nxtrec-reccnt + add hl,de ;HL=.fcb(nxtrec) + ret + +getfcb: ;set variables from currently addressed fcb + call getfcba ;addresses in DE, HL + ld a,(hl) + ld (vrecord),a ;vrecord=fcb(nxtrec) + ex de,hl + ld a,(hl) + ld (rcount),a ;rcount=fcb(reccnt) + call getexta ;HL=.fcb(extnum) + ld a,(extmsk) ;extent mask to a + and (hl) ;fcb(extnum) and extmsk + ld (extval),a + ret + +setfcb: ;place values back into current fcb + call getfcba ;addresses to DE, HL + ld a,(seqio) + cp 02 + jp nz,setfcb1 + xor a ;check ranfill +setfcb1: + ld c,a ;=1 if sequential i/o + ld a,(vrecord) + add a,c + ld (hl),a ;fcb(nxtrec)=vrecord+seqio + ex de,hl + ld a,(rcount) + ld (hl),a ;fcb(reccnt)=rcount + ret + +hlrotr: ;hl rotate right by amount C + inc c ;in case zero +hlrotr0: + dec c + ret z ;return when zero + ld a,h + or a + rra + ld h,a ;high byte + ld a,l + rra + ld l,a ;low byte + jp hlrotr0 + +compute$cs: ;compute checksum for current directory buffer + ld c,recsiz ;size of directory buffer + ld hl,(buffa) ;current directory buffer + xor a ;clear checksum value +computecs0: + add a,(hl) + inc hl + dec c ;cs=cs+buff(recsiz-C) + jp nz,computecs0 + ret ;with checksum in A + +hlrotl: ;rotate the mask in HL by amount in C + inc c ;may be zero +hlrotl0: + dec c + ret z ;return if zero + add hl,hl + jp hlrotl0 + +set$cdisk: ;set a "1" value in curdsk position of BC + push bc ;save input parameter + ld a,(curdsk) + ld c,a ;ready parameter for shift + ld hl,1 ;number to shift + call hlrotl ;HL = mask to integrate + pop bc ;original mask + ld a,c + or l + ld l,a + ld a,b + or h + ld h,a ;HL = mask or rol(1,curdsk) + ret + +nowrite: ;return true if dir checksum difference occurred + ld hl,(rodsk) + ld a,(curdsk) + ld c,a + call hlrotr + ld a,l + and 1b + ret ;non zero if nowrite + +set$ro: ;set current disk to read only + ld hl,rodsk + ld c,(hl) + inc hl + ld b,(hl) + call set$cdisk ;sets bit to 1 + ld (rodsk),hl + ;high water mark in directory goes to max + ld hl,(dirmax) + inc hl + ex de,hl ;DE = directory max + ld hl,(cdrmaxa) ;HL = .cdrmax + ld (hl),e + inc hl + ld (hl),d ;cdrmax = dirmax + ret + +check$rodir: ;check current directory element for read/only status + call getdptra ;address of element + +check$rofile: ;check current buff(dptr) or fcb(0) for r/o status + ld de,rofile + add hl,de ;offset to ro bit + ld a,(hl) + rla + ret nc ;return if not set + ld hl,roferr + jp goerr +; jp rof$error ;exit to read only disk message + + +check$write: ;check for write protected disk + call nowrite + ret z ;ok to write if not rodsk + ld hl,roderr + jp goerr +; jp rod$error ;read only disk error + +getdptra: ;compute the address of a directory element at + ;positon dptr in the buffer + ld hl,(buffa) + ld a,(dptr) +addh: ;HL = HL + A + add a,l + ld l,a + ret nc + ;overflow to H + inc h + ret + + +getmodnum: ;compute the address of the module number + ;bring module number to accumulator + ;(high order bit is fwf (file write flag) + ld hl,(info) + ld de,modnum + add hl,de ;HL=.fcb(modnum) + ld a,(hl) + ret ;A=fcb(modnum) + +clrmodnum: ;clear the module number field for user open/make + call getmodnum + ld (hl),0 ;fcb(modnum)=0 + ret + +setfwf: call getmodnum ;HL=.fcb(modnum), A=fcb(modnum) + ;set fwf (file write flag) to "1" + or fwfmsk + ld (hl),a ;fcb(modnum)=fcb(modnum) or 80h + ;also returns non zero in accumulator + ret + + +compcdr: ;return cy if cdrmax > dcnt + ld hl,(dcnt) + ex de,hl ;DE = directory counter + ld hl,(cdrmaxa) ;HL=.cdrmax + ld a,e + sub (hl) ;low(dcnt) - low(cdrmax) + inc hl ;HL = .cdrmax+1 + ld a,d + sbc a,(hl) ;hig(dcnt) - hig(cdrmax) + ;condition dcnt - cdrmax produces cy if cdrmax>dcnt + ret + +setcdr: ;if not (cdrmax > dcnt) then cdrmax = dcnt+1 + call compcdr + ret c ;return if cdrmax > dcnt + ;otherwise, HL = .cdrmax+1, DE = dcnt + inc de + ld (hl),d + dec hl + ld (hl),e + ret + +subdh: ;compute HL = DE - HL + ld a,e + sub l + ld l,a + ld a,d + sbc a,h + ld h,a + ret + +newchecksum: + ld c,true ;drop through to compute new checksum +checksum: ;compute current checksum record and update the + ;directory element if C=true, or check for = if not + ;drec < chksiz? + ld hl,(drec) + ex de,hl + ld hl,(chksiz) + call subdh ;DE-HL + ret nc ;skip checksum if past checksum vector size + ;drec < chksiz, so continue + push bc ;save init flag + call compute$cs ;check sum value to A + ld hl,(checka) ;address of check sum vector + ex de,hl + ld hl,(drec) ;value of drec + add hl,de ;HL = .check(drec) + pop bc ;recall true=0ffh or false=00 to C + inc c ;0ffh produces zero flag + jp z,initial$cs + ;not initializing, compare + cp (hl) ;compute$cs=check(drec)? + ret z ;no message if ok + ;checksum error, are we beyond + ;the end of the disk? + call compcdr + ret nc ;no message if so + call set$ro ;read/only disk set + ret + +initial$cs: ;initializing the checksum + ld (hl),a + ret + + +wrdir: ;write the current directory entry, set checksum + call newchecksum ;initialize entry + call setdir ;directory dma + ld c,1 ;indicates a write directory operation + call wrbuff ;write the buffer + jp setdata ;to data dma address +; ret +rd$dir: ;read a directory entry into the directory buffer + call setdir ;directory dma + call rdbuff ;directory record loaded + ;jmp setdata to data dma address +; ret +setdata: ;set data dma address + ld hl,dmaad + jp setdma ;to complete the call + +setdir: ;set directory dma address + ld hl,buffa ;jmp setdma to complete call + +setdma: ;HL=.dma address to set (i.e., buffa or dmaad) + ld c,(hl) + inc hl + ld b,(hl) ;parameter ready + jp setdmaf + +dir$to$user: ;copy the directory entry to the user buffer + ;after call to search or searchn by user code + ld hl,(buffa) + ex de,hl ;source is directory buffer + ld hl,(dmaad) ;destination is user dma address + ld c,recsiz ;copy entire record + jp move +; ret + +end$of$dir: ;return zero flag if at end of directory, non zero + ;if not at end (end of dir if dcnt = 0ffffh) + ld hl,dcnt + ld a,(hl) ;may be 0ffh + inc hl + cp (hl) ;low(dcnt) = high(dcnt)? + ret nz ;non zero returned if different + ;high and low the same, = 0ffh? + inc a ;0ffh becomes 00 if so + ret + +set$end$dir: ;set dcnt to the end of the directory + ld hl,enddir + ld (dcnt),hl + ret + +read$dir: ;read next directory entry, with C=true if initializing + ld hl,(dirmax) + ex de,hl ;in preparation for subtract + ld hl,(dcnt) + inc hl + ld (dcnt),hl ;dcnt=dcnt+1 + ;continue while dirmax >= dcnt (dirmax-dcnt no cy) + call subdh ;DE-HL + jp nc,read$dir0 + ;yes, set dcnt to end of directory + jp set$end$dir +; ret + +read$dir0: ;not at end of directory, seek next element + ;initialization flag is in C + ld a,(dcnt) + and dskmsk ;low(dcnt) and dskmsk + ld b,fcbshf ;to multiply by fcb size +read$dir1: + add a,a + dec b + jp nz,read$dir1 + ;A = (low(dcnt) and dskmsk) shl fcbshf + ld (dptr),a ;ready for next dir operation + or a + ret nz ;return if not a new record + push bc ;save initialization flag C + call seek$dir ;seek proper record + call rd$dir ;read the directory record + pop bc ;recall initialization flag + jp checksum ;checksum the directory elt +; ret + + +getallocbit: ;given allocation vector position BC, return with byte + ;containing BC shifted so that the least significant + ;bit is in the low order accumulator position. HL is + ;the address of the byte for possible replacement in + ;memory upon return, and D contains the number of shifts + ;required to place the returned value back into position + ld a,c + and 111b + inc a + ld e,a + ld d,a + ;d and e both contain the number of bit positions to shift + ld a,c + rrca + rrca + rrca + and 11111b + ld c,a ;C shr 3 to C + ld a,b + add a,a + add a,a + add a,a + add a,a + add a,a ;B shl 5 + or c + ld c,a ;bbbccccc to C + ld a,b + rrca + rrca + rrca + and 11111b + ld b,a ;BC shr 3 to BC + ld hl,(alloca) ;base address of allocation vector + add hl,bc + ld a,(hl) ;byte to A, hl = .alloc(BC shr 3) + ;now move the bit to the low order position of A +rotl: rlca + dec e + jp nz,rotl + ret + + +set$alloc$bit: ;BC is the bit position of ALLOC to set or reset. The + ;value of the bit is in register E. + push de + call getallocbit ;shifted val A, count in D + and 11111110b ;mask low bit to zero (may be set) + pop bc + or c ;low bit of C is masked into A +; jp rotr ;to rotate back into proper position +; ret +rotr: + ;byte value from ALLOC is in register A, with shift count + ;in register C (to place bit back into position), and + ;target ALLOC position in registers HL, rotate and replace + rrca + dec d + jp nz,rotr ;back into position + ld (hl),a ;back to ALLOC + ret + +scandm: ;scan the disk map addressed by dptr for non-zero + ;entries, the allocation vector entry corresponding + ;to a non-zero entry is set to the value of C (0,1) + call getdptra ;HL = buffa + dptr + ;HL addresses the beginning of the directory entry + ld de,dskmap + add hl,de ;hl now addresses the disk map + push bc ;save the 0/1 bit to set + ld c,fcblen-dskmap+1;size of single byte disk map + 1 +scandm0: ;loop once for each disk map entry + pop de ;recall bit parity + dec c + ret z ;all done scanning? + ;no, get next entry for scan + push de ;replace bit parity + ld a,(single) + or a + jp z,scandm1 + ;single byte scan operation + push bc ;save counter + push hl ;save map address + ld c,(hl) + ld b,0 ;BC=block# + jp scandm2 + +scandm1: ;double byte scan operation + dec c ;count for double byte + push bc ;save counter + ld c,(hl) + inc hl + ld b,(hl) ;BC=block# + push hl ;save map address +scandm2: ;arrive here with BC=block#, E=0/1 + ld a,c + or b ;skip if = 0000 + jp z,scanm3 + ld hl,(maxall) ;check invalid index + ld a,l + sub c + ld a,h + sbc a,b ;maxall - block# + call nc,set$alloc$bit + ;bit set to 0/1 +scanm3: pop hl + inc hl ;to next bit position + pop bc ;recall counter + jp scandm0 ;for another item + +initialize: ;initialize the current disk + ;lret = false ;set to true if $ file exists + ;compute the length of the allocation vector - 2 + ld hl,(maxall) + ld c,3 ;perform maxall/8 + ;number of bytes in alloc vector is (maxall/8)+1 + call hlrotr + inc hl ;HL = maxall/8+1 + ld b,h + ld c,l ;count down BC til zero + ld hl,(alloca) ;base of allocation vector + ;fill the allocation vector with zeros +initial0: + ld (hl),0 + inc hl ;alloc(i)=0 + dec bc ;count length down + ld a,b + or c + jp nz,initial0 + ;set the reserved space for the directory + ld hl,(dirblk) + ex de,hl + ld hl,(alloca) ;HL=.alloc() + ld (hl),e + inc hl + ld (hl),d ;sets reserved directory blks + ;allocation vector initialized, home disk + call home + ;cdrmax = 3 (scans at least one directory record) + ld hl,(cdrmaxa) + ld (hl),3 + inc hl + ld (hl),0 + ;cdrmax = 0000 + call set$end$dir ;dcnt = enddir + ;read directory entries and check for allocated storage +initial2: + ld c,true + call read$dir + call end$of$dir + ret z ;return if end of directory + ;not end of directory, valid entry? + call getdptra ;HL = buffa + dptr + ld a,empty + cp (hl) + jp z,initial2 ;go get another item + ;not empty, user code the same? + ld a,(usrcode) + cp (hl) + jp nz,pdollar + ;same user code, check for '$' submit + inc hl + ld a,(hl) ;first character + sub '$' ;dollar file? + jp nz,pdollar + ;dollar file found, mark in lret + dec a + ld (lret),a ;lret = 255 +pdollar: ;now scan the disk map for allocated blocks + ld c,1 ;set to allocated + call scandm + call setcdr ;set cdrmax to dcnt + jp initial2 ;for another entry + +copy$dirloc: ;copy directory location to lret following + ;delete, rename, ... ops + ld a,(dirloc) + jp sta$ret +; ret + +compext: ;compare extent# in A with that in C, return nonzero + ;if they do not match + push bc ;save C's original value + push af + ld a,(extmsk) + cpl + ld b,a + ;B has negated form of extent mask + ld a,c + and b + ld c,a ;low bits removed from C + pop af + and b ;low bits removed from A + sub c + and maxext ;set flags + pop bc ;restore original values + ret + +search: ;search for directory element of length C at info + ld a,0ffh + ld (dirloc),a ;changed if actually found + ld hl,searchl + ld (hl),c ;searchl = C + ld hl,(info) + ld (searcha),hl ;searcha = info + call set$end$dir ;dcnt = enddir + call home ;to start at the beginning + ;(drop through to searchn) + +searchn: ;search for the next directory element, assuming + ;a previous call on search which sets searcha and + ;searchl + ld c,false + call read$dir ;read next dir element + call end$of$dir + jp z,search$fin ;skip to end if so + ;not end of directory, scan for match + ld hl,(searcha) + ex de,hl ;DE=beginning of user fcb + ld a,(de) ;first character + cp empty ;keep scanning if empty + jp z,searchnext + ;not empty, may be end of logical directory + push de ;save search address + call compcdr ;past logical end? + pop de ;recall address + jp nc,search$fin ;artificial stop +searchnext: + call getdptra ;HL = buffa+dptr + ld a,(searchl) + ld c,a ;length of search to c + ld b,0 ;b counts up, c counts down +searchloop: + ld a,c + or a + jp z,endsearch + ld a,(de) + cp '?' + jp z,searchok ;? matches all + ;scan next character if not ubytes + ld a,b + cp ubytes + jp z,searchok + ;not the ubytes field, extent field? + cp extnum ;may be extent field + ld a,(de) ;fcb character + jp z,searchext ;skip to search extent + sub (hl) + and 7fh ;mask-out flags/extent modulus + jp nz,searchn ;skip if not matched + jp searchok ;matched character + +searchext: ;A has fcb character + ;attempt an extent # match + push bc ;save counters + ld c,(hl) ;directory character to c + call compext ;compare user/dir char + pop bc ;recall counters + jp nz,searchn ;skip if no match +searchok: ;current character matches + inc de + inc hl + inc b + dec c + jp searchloop + +endsearch: ;entire name matches, return dir position + ld a,(dcnt) + and dskmsk + ld (lret),a + ;lret = low(dcnt) and 11b + ld hl,dirloc + ld a,(hl) + rla + ret nc ;dirloc=0ffh? + ;yes, change it to 0 to mark as found + xor a + ld (hl),a ;dirloc=0 + ret + +search$fin: ;end of directory, or empty name + call set$end$dir ;may be artifical end + ld a,255 + jp sta$ret + +delete: ;delete the currently addressed file + call check$write ;write protected? + ld c,extnum + call search ;search through file type +delete0: + ;loop while directory matches + call end$of$dir + ret z ;stop if end + ;set each non zero disk map entry to 0 + ;in the allocation vector + ;may be r/o file + call check$rodir ;ro disk error if found + call getdptra ;HL=.buff(dptr) + ld (hl),empty + ld c,0 + call scandm ;alloc elts set to 0 + call wrdir ;write the directory + call searchn ;to next element + jp delete0 ;for another record + +get$block: ;given allocation vector position BC, find the zero bit + ;closest to this position by searching left and right. + ;if found, set the bit to one and return the bit position + ;in hl. if not found (i.e., we pass 0 on the left, or + ;maxall on the right), return 0000 in hl + ld d,b + ld e,c ;copy of starting position to de +lefttst: + ld a,c + or b + jp z,righttst ;skip if left=0000 + ;left not at position zero, bit zero? + dec bc + push de + push bc ;left,right pushed + call getallocbit + rra + jp nc,retblock ;return block number if zero + ;bit is one, so try the right + pop bc + pop de ;left, right restored +righttst: + ld hl,(maxall) ;value of maximum allocation# + ld a,e + sub l + ld a,d + sbc a,h ;right=maxall? + jp nc,retblock0 ;return block 0000 if so + inc de + push bc + push de ;left, right pushed + ld b,d + ld c,e ;ready right for call + call getallocbit + rra + jp nc,retblock ;return block number if zero + pop de + pop bc ;restore left and right pointers + jp lefttst ;for another attempt +retblock: + rla + inc a ;bit back into position and set to 1 + ;d contains the number of shifts required to reposition + call rotr ;move bit back to position and store + pop hl + pop de ;HL returned value, DE discarded + ret + +retblock0: ;cannot find an available bit, return 0000 + ld a,c + or b + jp nz,lefttst ;also at beginning + ld hl,0000h + ret + +copy$fcb: ;copy the entire file control block + ld c,0 + ld e,fcblen ;start at 0, to fcblen-1 +; jp copy$dir + +copy$dir: ;copy fcb information starting at C for E bytes + ;into the currently addressed directory entry + push de ;save length for later + ld b,0 ;double index to BC + ld hl,(info) ;HL = source for data + add hl,bc + ex de,hl ;DE=.fcb(C), source for copy + call getdptra ;HL=.buff(dptr), destination + pop bc ;DE=source, HL=dest, C=length + call move ;data moved +seek$copy: ;enter from close to seek and copy current element + call seek$dir ;to the directory element + jp wrdir ;write the directory element +; ret +rename: ;rename the file described by the first half of + ;the currently addressed file control block. the + ;new name is contained in the last half of the + ;currently addressed file conrol block. the file + ;name and type are changed, but the reel number + ;is ignored. the user number is identical + call check$write ;may be write protected + ;search up to the extent field + ld c,extnum + call search + ;copy position 0 + ld hl,(info) + ld a,(hl) ;HL=.fcb(0), A=fcb(0) + ld de,dskmap + add hl,de ;HL=.fcb(dskmap) + ld (hl),a ;fcb(dskmap)=fcb(0) + ;assume the same disk drive for new named file +rename0: + call end$of$dir + ret z ;stop at end of dir + ;not end of directory, rename next element + call check$rodir ;may be read-only file + ld c,dskmap + ld e,extnum + call copy$dir + ;element renamed, move to next + call searchn + jp rename0 + +indicators: ;set file indicators for current fcb + ld c,extnum + call search ;through file type +indic0: call end$of$dir + ret z ;stop at end of dir + ;not end of directory, continue to change + ld c,0 + ld e,extnum ;copy name + call copy$dir + call searchn + jp indic0 + +open: ;search for the directory entry, copy to fcb + ld c,namlen + call search + call end$of$dir + ret z ;return with lret=255 if end + ;not end of directory, copy fcb information +open$copy: ;(referenced below to copy fcb info) + call getexta + ld a,(hl) + push af + push hl ;save extent# + call getdptra + ex de,hl ;DE = .buff(dptr) + ld hl,(info) ;HL=.fcb(0) + ld c,nxtrec ;length of move operation + push de ;save .buff(dptr) + call move ;from .buff(dptr) to .fcb(0) + ;note that entire fcb is copied, including indicators + call setfwf ;sets file write flag + pop de + ld hl,extnum + add hl,de ;HL=.buff(dptr+extnum) + ld c,(hl) ;C = directory extent number + ld hl,reccnt + add hl,de ;HL=.buff(dptr+reccnt) + ld b,(hl) ;B holds directory record count + pop hl + pop af + ld (hl),a ;restore extent number + ;HL = .user extent#, B = dir rec cnt, C = dir extent# + ;if user ext < dir ext then user := 128 records + ;if user ext = dir ext then user := dir records + ;if user ext > dir ext then user := 0 records + ld a,c + cp (hl) + ld a,b ;ready dir reccnt + jp z,open$rcnt ;if same, user gets dir reccnt + ld a,0 + jp c,open$rcnt ;user is larger + ld a,128 ;directory is larger +open$rcnt: ;A has record count to fill + ld hl,(info) + ld de,reccnt + add hl,de + ld (hl),a + ret + +mergezero: ;HL = .fcb1(i), DE = .fcb2(i), + ;if fcb1(i) = 0 then fcb1(i) := fcb2(i) + ld a,(hl) + inc hl + or (hl) + dec hl + ret nz ;return if = 0000 + ld a,(de) + ld (hl),a + inc de + inc hl ;low byte copied + ld a,(de) + ld (hl),a + dec de + dec hl ;back to input form + ret + +close: ;locate the directory element and re-write it + xor a + ld (lret),a + ld (dcnt),a + ld (dcnt+1),a + call nowrite + ret nz ;skip close if r/o disk + ;check file write flag - 0 indicates written + call getmodnum ;fcb(modnum) in A + and fwfmsk + ret nz ;return if bit remains set + ld c,namlen + call search ;locate file + call end$of$dir + ret z ;return if not found + ;merge the disk map at info with that at buff(dptr) + ld bc,dskmap + call getdptra + add hl,bc + ex de,hl ;DE is .buff(dptr+16) + ld hl,(info) + add hl,bc ;DE=.buff(dptr+16), HL=.fcb(16) + ld c,fcblen-dskmap;length of single byte dm +merge0: ld a,(single) + or a + jp z,merged ;skip to double + ;this is a single byte map + ;if fcb(i) = 0 then fcb(i) = buff(i) + ;if buff(i) = 0 then buff(i) = fcb(i) + ;if fcb(i) <> buff(i) then error + ld a,(hl) + or a + ld a,(de) + jp nz,fcbnzero + ;fcb(i) = 0 + ld (hl),a ;fcb(i) = buff(i) +fcbnzero: + or a + jp nz,buffnzero + ;buff(i) = 0 + ld a,(hl) + ld (de),a ;buff(i)=fcb(i) +buffnzero: + cp (hl) + jp nz,mergerr ;fcb(i) = buff(i)? + jp dmset ;if merge ok + +merged: ;this is a double byte merge operation + call mergezero ;buff = fcb if buff 0000 + ex de,hl + call mergezero + ex de,hl ;fcb = buff if fcb 0000 + ;they should be identical at this point + ld a,(de) + cp (hl) + jp nz,mergerr ;low same? + inc de + inc hl ;to high byte + ld a,(de) + cp (hl) + jp nz,mergerr ;high same? + ;merge operation ok for this pair + dec c ;extra count for double byte +dmset: inc de + inc hl ;to next byte position + dec c + jp nz,merge0 ;for more + ;end of disk map merge, check record count + ;DE = .buff(dptr)+32, HL = .fcb(32) + ld bc,-(fcblen-extnum) + add hl,bc + ex de,hl + add hl,bc + ;DE = .fcb(extnum), HL = .buff(dptr+extnum) + ld a,(de) ;current user extent number + ;if fcb(ext) >= buff(fcb) then + ;buff(ext) := fcb(ext), buff(rec) := fcb(rec) + cp (hl) + jp c,endmerge + ;fcb extent number >= dir extent number + ld (hl),a ;buff(ext) = fcb(ext) + ;update directory record count field + ld bc,reccnt-extnum + add hl,bc + ex de,hl + add hl,bc + ;DE=.buff(reccnt), HL=.fcb(reccnt) + ld a,(hl) + ld (de),a ;buff(reccnt)=fcb(reccnt) +endmerge: + ld a,true + ld (fcb$copied),a ;mark as copied + jp seek$copy ;ok to "wrdir" here - 1.4 compat + ; ret + +mergerr: ;elements did not merge correctly + ld hl,lret + dec (hl) ;=255 non zero flag set + ret + +make: ;create a new file by creating a directory entry + ;then opening the file + call check$write ;may be write protected + ld hl,(info) + push hl ;save fcb address, look for e5 + ld hl,efcb + ld (info),hl ;info = .empty + ld c,1 + call search ;length 1 match on empty entry + call end$of$dir ;zero flag set if no space + pop hl ;recall info address + ld (info),hl ;in case we return here + ret z ;return with error condition 255 if not found + ex de,hl ;DE = info address + ;clear the remainder of the fcb + ld hl,namlen + add hl,de ;HL=.fcb(namlen) + ld c,fcblen-namlen ;number of bytes to fill + xor a ;clear accumulator to 00 for fill +make0: ld (hl),a + inc hl + dec c + jp nz,make0 + ld hl,ubytes + add hl,de ;HL = .fcb(ubytes) + ld (hl),a ;fcb(ubytes) = 0 + call setcdr ;may have extended the directory + ;now copy entry to the directory + call copy$fcb + ;and set the file write flag to "1" + jp setfwf +; ret + +open$reel: ;close the current extent, and open the next one + ;if possible. RMF is true if in read mode + xor a + ld (fcb$copied),a ;set true if actually copied + call close ;close current extent + ;lret remains at enddir if we cannot open the next ext + call end$of$dir + ret z ;return if end + ;increment extent number + ld hl,(info) + ld bc,extnum + add hl,bc ;HL=.fcb(extnum) + ld a,(hl) + inc a + and maxext + ld (hl),a ;fcb(extnum)=++1 + jp z,open$mod ;move to next module if zero + ;may be in the same extent group + ld b,a + ld a,(extmsk) + and b + ;if result is zero, then not in the same group + ld hl,fcb$copied ;true if the fcb was copied to directory + and (hl) ;produces a 00 in accumulator if not written + jp z,open$reel0 ;go to next physical extent + ;result is non zero, so we must be in same logical ext + jp open$reel1 ;to copy fcb information +open$mod: ;extent number overflow, go to next module + ld bc,modnum-extnum + add hl,bc ;HL=.fcb(modnum) + inc (hl) ;fcb(modnum)=++1 + ;module number incremented, check for overflow + ld a,(hl) + and maxmod ;mask high order bits + jp z,open$r$err ;cannot overflow to zero + ;otherwise, ok to continue with new module +open$reel0: + ld c,namlen + call search ;next extent found? + call end$of$dir + jp nz,open$reel1 + ;end of file encountered + ld a,(rmf) + inc a ;0ffh becomes 00 if read + jp z,open$r$err ;sets lret = 1 + ;try to extend the current file + call make + ;cannot be end of directory + call end$of$dir + jp z,open$r$err ;with lret = 1 + jp open$reel2 + +open$reel1: ;not end of file, open + call open$copy +open$reel2: + call getfcb ;set parameters + xor a + jp sta$ret ;lret = 0 +; ret ;with lret = 0 + +open$r$err: ;cannot move to next extent of this file + call setlret1 ;lret = 1 + jp setfwf ;ensure that it will not be closed +; ret + +seqdiskread: ;sequential disk read operation + ld a,1 + ld (seqio),a + ;drop through to diskread + +diskread: ;(may enter from seqdiskread) + ld a,true + ld (rmf),a ;read mode flag = true (open$reel) + ;read the next record from the current fcb + call getfcb ;sets parameters for the read + ld a,(vrecord) + ld hl,rcount + cp (hl) ;vrecord-rcount + ;skip if rcount > vrecord + jp c,recordok + ;not enough records in the extent + ;record count must be 128 to continue + cp 128 ;vrecord = 128? + jp nz,diskeof ;skip if vrecord<>128 + call open$reel ;go to next extent if so + xor a + ld (vrecord),a ;vrecord=00 + ;now check for open ok + ld a,(lret) + or a + jp nz,diskeof ;stop at eof +recordok: ;arrive with fcb addressing a record to read + call index + ;error 2 if reading unwritten data + ;(returns 1 to be compatible with 1.4) + call allocated ;arecord=0000? + jp z,diskeof + ;record has been allocated, read it + call atran ;arecord now a disk address + call seek ;to proper track,sector + call rdbuff ;to dma address + jp setfcb ;replace parameter +; ret + +diskeof: + jp setlret1 ;lret = 1 +; ret + +seqdiskwrite: ;sequential disk write + ld a,1 + ld (seqio),a + ;drop through to diskwrite + +diskwrite: ;(may enter here from seqdiskwrite above) + ld a,false + ld (rmf),a ;read mode flag + ;write record to currently selected file + call check$write ;in case write protected + ld hl,(info) ;HL = .fcb(0) + call check$rofile ;may be a read-only file + call getfcb ;to set local parameters + ld a,(vrecord) + cp lstrec+1 ;vrecord-128 + ;skip if vrecord > lstrec + ;vrecord = 128, cannot open next extent + jp nc,setlret1 ;lret=1 +diskwr0: ;can write the next record, so continue + call index + call allocated + ld c,0 ;marked as normal write operation for wrbuff + jp nz,diskwr1 + ;not allocated + ;the argument to getblock is the starting + ;position for the disk search, and should be + ;the last allocated block for this file, or + ;the value 0 if no space has been allocated + call dm$position + ld (dminx),a ;save for later + ld bc,0000h ;may use block zero + or a + jp z,nopblock ;skip if no previous block + ;previous block exists at A + ld c,a + dec bc ;previous block # in BC + call getdm ;previous block # to HL + ld b,h + ld c,l ;BC=prev block# +nopblock: ;BC = 0000, or previous block # + call get$block ;block # to HL + ;arrive here with block# or zero + ld a,l + or h + jp nz,blockok + ;cannot find a block to allocate + ld a,2 + jp sta$ret ;lret=2 + +blockok: ;allocated block number is in HL + ld (arecord),hl + ex de,hl ;block number to DE + ld hl,(info) + ld bc,dskmap + add hl,bc ;HL=.fcb(dskmap) + ld a,(single) + or a ;set flags for single byte dm + ld a,(dminx) ;recall dm index + jp z,allocwd ;skip if allocating word + ;allocating a byte value + call addh + ld (hl),e ;single byte alloc + jp diskwru ;to continue + +allocwd: ;allocate a word value + ld c,a + ld b,0 ;double(dminx) + add hl,bc + add hl,bc ;HL=.fcb(dminx*2) + ld (hl),e + inc hl + ld (hl),d ;double wd +diskwru: ;disk write to previously unallocated block + ld c,2 ;marked as unallocated write +diskwr1: ;continue the write operation of no allocation error + ;C = 0 if normal write, 2 if to prev unalloc block + ld a,(lret) + or a + ret nz ;stop if non zero returned value + push bc ;save write flag + call atran ;arecord set + ld a,(seqio) + dec a + dec a + jp nz,diskwr11 + pop bc + push bc + ld a,c + dec a + dec a + jp nz,diskwr11 ;old allocation + push hl ;arecord in hl ret from atran + ld hl,(buffa) + ld d,a ;zero buffa & fill +fill0: ld (hl),a + inc hl + inc d + jp p,fill0 + call setdir + ld hl,(arecord1) + ld c,2 +fill1: ld (arecord),hl + push bc + call seek + pop bc + call wrbuff ;write fill record + ld hl,(arecord) ;restore last record + ld c,0 ;change allocate flag + ld a,(blkmsk) + ld b,a + and l + cp b + inc hl + jp nz,fill1 ;cont until cluster is zeroed + pop hl + ld (arecord),hl + call setdata +diskwr11: + call seek ;to proper file position + pop bc + push bc ;restore/save write flag (C=2 if new block) + call wrbuff ;written to disk + pop bc ;C = 2 if a new block was allocated, 0 if not + ;increment record count if rcount<=vrecord + ld a,(vrecord) + ld hl,rcount + cp (hl) ;vrecord-rcount + jp c,diskwr2 + ;rcount <= vrecord + ld (hl),a + inc (hl) ;rcount = vrecord+1 + ld c,2 ;mark as record count incremented +diskwr2: ;A has vrecord, C=2 if new block or new record# + dec c + dec c + jp nz,noupdate + push af ;save vrecord value + call getmodnum ;HL=.fcb(modnum), A=fcb(modnum) + ;reset the file write flag to mark as written fcb + and (not fwfmsk) and 0ffh;bit reset + ld (hl),a ;fcb(modnum) = fcb(modnum) and 7fh + pop af ;restore vrecord +noupdate: ;check for end of extent, if found attempt to open + ;next extent in preparation for next write + cp lstrec ;vrecord=lstrec? + jp nz,diskwr3 ;skip if not + ;may be random access write, if so we are done + ;change next + ld a,(seqio) + cp 1 + jp nz,diskwr3 ;skip next extent open op + ;update current fcb before going to next extent + call setfcb + call open$reel ;rmf=false + ;vrecord remains at lstrec causing eof if + ;no more directory space is available + ld hl,lret + ld a,(hl) + or a + jp nz,nospace + ;space available, set vrecord=255 + dec a + ld (vrecord),a ;goes to 00 next time +nospace: + ld (hl),0 ;lret = 00 for returned value +diskwr3: + jp setfcb ;replace parameters +; ret + +rseek: ;random access seek operation, C=0ffh if read mode + ;fcb is assumed to address an active file control block + ;(modnum has been set to 1100$0000b if previous bad seek) + xor a + ld (seqio),a ;marked as random access operation +rseek1: push bc ;save r/w flag + ld hl,(info) + ex de,hl ;DE will hold base of fcb + ld hl,ranrec + add hl,de ;HL=.fcb(ranrec) + ld a,(hl) + and 7fh + push af ;record number + ld a,(hl) + rla ;cy=lsb of extent# + inc hl + ld a,(hl) + rla + and 11111b ;A=ext# + ld c,a ;C holds extent number, record stacked + ld a,(hl) + rra + rra + rra + rra + and 1111b ;mod# + ld b,a ;B holds module#, C holds ext# + pop af ;recall sought record # + ;check to insure that high byte of ran rec = 00 + inc hl + ld l,(hl) ;l=high byte (must be 00) + inc l + dec l + ld l,6 ;zero flag, l=6 + ;produce error 6, seek past physical eod + jp nz,seekerr + ;otherwise, high byte = 0, A = sought record + ld hl,nxtrec + add hl,de ;HL = .fcb(nxtrec) + ld (hl),a ;sought rec# stored away + ;arrive here with B=mod#, C=ext#, DE=.fcb, rec stored + ;the r/w flag is still stacked. compare fcb values + ld hl,extnum + add hl,de + ld a,c ;A=seek ext# + sub (hl) + jp nz,ranclose ;tests for = extents + ;extents match, check mod# + ld hl,modnum + add hl,de + ld a,b ;B=seek mod# + ;could be overflow at eof, producing module# + ;of 90H or 10H, so compare all but fwf + sub (hl) + and 7fh + jp z,seekok ;same? +ranclose: + push bc + push de ;save seek mod#,ext#, .fcb + call close ;current extent closed + pop de + pop bc ;recall parameters and fill + ld l,3 ;cannot close error #3 + ld a,(lret) + inc a + jp z,badseek + ld hl,extnum + add hl,de + ld (hl),c ;fcb(extnum)=ext# + ld hl,modnum + add hl,de + ld (hl),b ;fcb(modnum)=mod# + call open ;is the file present? + ld a,(lret) + inc a + jp nz,seekok ;open successful? + ;cannot open the file, read mode? + pop bc ;r/w flag to c (=0ffh if read) + push bc ;everyone expects this item stacked + ld l,4 ;seek to unwritten extent #4 + inc c ;becomes 00 if read operation + jp z,badseek ;skip to error if read operation + ;write operation, make new extent + call make + ld l,5 ;cannot create new extent #5 + ld a,(lret) + inc a + jp z,badseek ;no dir space + ;file make operation successful +seekok: + pop bc ;discard r/w flag + xor a + jp sta$ret ;with zero set +badseek: ;fcb no longer contains a valid fcb, mark + ;with 1100$000b in modnum field so that it + ;appears as overflow with file write flag set + push hl ;save error flag + call getmodnum ;HL = .modnum + ld (hl),11000000b + pop hl ;and drop through +seekerr: + pop bc ;discard r/w flag + ld a,l + ld (lret),a ;lret=#, nonzero + ;setfwf returns non-zero accumulator for err + jp setfwf ;flag set, so subsequent close ok +; ret + +randiskread: ;random disk read operation + ld c,true ;marked as read operation + call rseek + call z,diskread ;if seek successful + ret + +randiskwrite: ;random disk write operation + ld c,false ;marked as write operation + call rseek + call z,diskwrite ;if seek successful + ret + +compute$rr: ;compute random record position for getfilesize/setrandom + ex de,hl + add hl,de + ;DE=.buf(dptr) or .fcb(0), HL = .f(nxtrec/reccnt) + ld c,(hl) + ld b,0 ;BC = 0000 0000 ?rrr rrrr + ld hl,extnum + add hl,de + ld a,(hl) + rrca + and 80h ;A=e000 0000 + add a,c + ld c,a + ld a,0 + adc a,b + ld b,a + ;BC = 0000 000? errrr rrrr + ld a,(hl) + rrca + and 0fh + add a,b + ld b,a + ;BC = 000? eeee errrr rrrr + ld hl,modnum + add hl,de + ld a,(hl) ;A=XXX? mmmm + add a,a + add a,a + add a,a + add a,a ;cy=? A=mmmm 0000 + push af + add a,b + ld b,a + ;cy=?, BC = mmmm eeee errr rrrr + push af ;possible second carry + pop hl ;cy = lsb of L + ld a,l ;cy = lsb of A + pop hl ;cy = lsb of L + or l ;cy/cy = lsb of A + and 1 ;A = 0000 000? possible carry-out + ret + +getfilesize: ;compute logical file size for current fcb + ld c,extnum + call search + ;zero the receiving ranrec field + ld hl,(info) + ld de,ranrec + add hl,de + push hl ;save position + ld (hl),d + inc hl + ld (hl),d + inc hl + ld (hl),d ;=00 00 00 +getsize: + call end$of$dir + jp z,setsize + ;current fcb addressed by dptr + call getdptra + ld de,reccnt ;ready for compute size + call compute$rr + ;A=0000 000? BC = mmmm eeee errr rrrr + ;compare with memory, larger? + pop hl + push hl ;recall, replace .fcb(ranrec) + ld e,a ;save cy + ld a,c + sub (hl) + inc hl ;ls byte + ld a,b + sbc a,(hl) + inc hl ;middle byte + ld a,e + sbc a,(hl) ;carry if .fcb(ranrec) > directory + jp c,getnextsize ;for another try + ;fcb is less or equal, fill from directory + ld (hl),e + dec hl + ld (hl),b + dec hl + ld (hl),c +getnextsize: + call searchn + jp getsize + +setsize: + pop hl ;discard .fcb(ranrec) + ret + +setrandom: ;set random record from the current file control block + ld hl,(info) + ld de,nxtrec ;ready params for computesize + call compute$rr ;DE=info, A=cy, BC=mmmm eeee errr rrrr + ld hl,ranrec + add hl,de ;HL = .fcb(ranrec) + ld (hl),c + inc hl + ld (hl),b + inc hl + ld (hl),a ;to ranrec + ret + +select: ;select disk info for subsequent input or output ops + ld hl,(dlog) + ld a,(curdsk) + ld c,a + call hlrotr + push hl + ex de,hl ;save it for test below, send to seldsk + call selectdisk + pop hl ;recall dlog vector + call z,sel$error ;returns true if select ok + ;is the disk logged in? + ld a,l + rra + ret c ;return if bit is set + ;disk not logged in, set bit and initialize + ld hl,(dlog) + ld c,l + ld b,h ;call ready + call set$cdisk + ld (dlog),hl ;dlog=set$cdisk(dlog) + jp initialize +; ret + +curselect: + ld a,(linfo) + ld hl,curdsk + cp (hl) + ret z ;skip if linfo=curdsk + ld (hl),a ;curdsk=info + jp select +; ret + +reselect: ;check current fcb to see if reselection necessary + ld a,true + ld (resel),a ;mark possible reselect + ld hl,(info) + ld a,(hl) ;drive select code + and 11111b ;non zero is auto drive select + dec a ;drive code normalized to 0..30, or 255 + ld (linfo),a ;save drive code + cp 30 + jp nc,noselect + ;auto select function, save curdsk + ld a,(curdsk) + ld (olddsk),a ;olddsk=curdsk + ld a,(hl) + ld (fcbdsk),a ;save drive code + and 11100000b + ld (hl),a ;preserve hi bits + call curselect +noselect: ;set user code + ld a,(usrcode) ;0...31 + ld hl,(info) + or (hl) + ld (hl),a + ret + +; individual function handlers +func12: ;return version number + ld a,dvers + jp sta$ret ;lret = dvers (high = 00) +; ret +; jp goback + +func13: ;reset disk system - initialize to disk 0 + ld hl,0 + ld (rodsk),hl + ld (dlog),hl + xor a + ld (curdsk),a ;note that usrcode remains unchanged + ld hl,tbuff + ld (dmaad),hl ;dmaad = tbuff + call setdata ;to data dma address + jp select +; ret +; jp goback + +func14 equ curselect ;select disk info +; ret +; jp goback + +func15: ;open file + call clrmodnum ;clear the module number + call reselect + jp open +; ret +; jp goback + +func16: ;close file + call reselect + jp close +; ret +; jp goback + +func17: ;search for first occurrence of a file + ld c,0 ;length assuming '?' true + ex de,hl ;was lhld info + ld a,(hl) + cp '?' ;no reselect if ? + jp z,qselect ;skip reselect if so + ;normal search + call getexta + ld a,(hl) + cp '?' ; + call nz,clrmodnum ;module number zeroed + call reselect + ld c,namlen +qselect: + call search + jp dir$to$user ;copy directory entry to user +; ret +; jp goback + +func18: ;search for next occurrence of a file name + ld hl,(searcha) + ld (info),hl + call reselect + call searchn + jp dir$to$user ;copy directory entry to user +; ret +; jp goback + +func19: ;delete a file + call reselect + call delete + jp copy$dirloc +; ret +; jp goback + +func20: ;read a file + call reselect + jp seqdiskread +; jp goback + +func21: ;write a file + call reselect + jp seqdiskwrite +; jp goback + +func22: ;make a file + call clrmodnum + call reselect + jp make +; ret +; jp goback + +func23: ;rename a file + call reselect + call rename + jp copy$dirloc +; ret +; jp goback + +func24: ;return the login vector + ld hl,(dlog) + jp sthl$ret +; ret +; jp goback + +func25: ;return selected disk number + ld a,(curdsk) + jp sta$ret +; ret +; jp goback + +func26: ;set the subsequent dma address to info + ex de,hl ;was lhld info + ld (dmaad),hl ;dmaad = info + jp setdata ;to data dma address +; ret +; jp goback + +func27: ;return the login vector address + ld hl,(alloca) + jp sthl$ret +; ret +; jp goback + +func28 equ set$ro + ;write protect current disk +; ret +; jp goback + +func29: ;return r/o bit vector + ld hl,(rodsk) + jp sthl$ret +; ret +; jp goback + +func30: ;set file indicators + call reselect + call indicators + jp copy$dirloc ;lret=dirloc +; ret +; jp goback + +func31: ;return address of disk parameter block + ld hl,(dpbaddr) +sthl$ret: + ld (aret),hl + ret +; jp goback + +func32: ;set user code + ld a,(linfo) + cp 0ffh + jp nz,setusrcode + ;interrogate user code instead + ld a,(usrcode) + jp sta$ret ;lret=usrcode +; ret +; jp goback + +setusrcode: + and 1fh + ld (usrcode),a + ret +; jp goback + +func33: ;random disk read operation + call reselect + jp randiskread ;to perform the disk read +; ret +; jp goback + +func34: ;random disk write operation + call reselect + jp randiskwrite ;to perform the disk write +; ret +; jp goback + +func35: ;return file size (0-65536) + call reselect + jp getfilesize +; ret +; jp goback + +func36 equ setrandom ;set random record +; ret +; jp goback + +func37: ld hl,(info) + ld a,l + cpl + ld e,a + ld a,h + cpl + ld hl,(dlog) + and h + ld d,a + ld a,l + and e + ld e,a + ld hl,(rodsk) + ex de,hl + ld (dlog),hl + ld a,l + and e + ld l,a + ld a,h + and d + ld h,a + ld (rodsk),hl + ret + +goback: ;arrive here at end of processing to return to user + ld a,(resel) + or a + jp z,retmon + ;reselection may have taken place + ld hl,(info) + ld (hl),0 ;fcb(0)=0 + ld a,(fcbdsk) + or a + jp z,retmon + ;restore disk number + ld (hl),a ;fcb(0)=fcbdsk + ld a,(olddsk) + ld (linfo),a + call curselect + +; return from the disk monitor +retmon: ld hl,(entsp) + ld sp,hl ;user stack restored + ld hl,(aret) + ld a,l + ld b,h ;BA = HL = aret + ret + +func38 equ func$ret +func39 equ func$ret +func40: ;random disk write with zero fill of unallocated block + call reselect + ld a,2 + ld (seqio),a + ld c,false + call rseek1 + call z,diskwrite ;if seek successful + ret + +; data areas + +; initialized data +efcb: db empty ;0e5=available dir entry +rodsk: dw 0 ;read only disk vector +dlog: dw 0 ;logged-in disks +dmaad: dw tbuff ;initial dma address + +; curtrka - alloca are set upon disk select +; (data must be adjacent, do not insert variables) +; (address of translate vector, not used) +cdrmaxa: + ds word ;pointer to cur dir max value +curtrka: + ds word ;current track address +curreca: + ds word ;current record address +buffa: ds word ;pointer to directory dma address +dpbaddr: + ds word ;current disk parameter block address +checka: ds word ;current checksum vector address +alloca: ds word ;current allocation vector address +addlist equ $-buffa ;address list size + +; sectpt - offset obtained from disk parm block at dpbaddr +; (data must be adjacent, do not insert variables) +sectpt: ds word ;sectors per track +blkshf: ds byte ;block shift factor +blkmsk: ds byte ;block mask +extmsk: ds byte ;extent mask +maxall: ds word ;maximum allocation number +dirmax: ds word ;largest directory number +dirblk: ds word ;reserved allocation bits for directory +chksiz: ds word ;size of checksum vector +offset: ds word ;offset tracks at beginning +dpblist equ $-sectpt ;size of area + +; local variables +tranv: ds word ;address of translate vector +fcb$copied: + ds byte ;set true if copy$fcb called +rmf: ds byte ;read mode flag for open$reel +dirloc: ds byte ;directory flag in rename, etc. +seqio: ds byte ;1 if sequential i/o +linfo: ds byte ;low(info) +dminx: ds byte ;local for diskwrite +searchl: + ds byte ;search length +searcha: + ds word ;search address +tinfo: ds word ;temp for info in "make" +single: ds byte ;set true if single byte allocation map +resel: ds byte ;reselection flag +olddsk: ds byte ;disk on entry to bdos +fcbdsk: ds byte ;disk named in fcb +rcount: ds byte ;record count in current fcb +extval: ds byte ;extent number and extmsk +vrecord: + ds word ;current virtual record +arecord: + ds word ;current actual record +arecord1: + ds word ;current actual block# * blkmsk + +; local variables for directory access +dptr: ds byte ;directory pointer 0,1,2,3 +dcnt: ds word ;directory counter 0,1,...,dirmax +drec: ds word ;directory record 0,1,...,dirmax/4 + +;bios equ ($ and 0ff00h)+100h;next module + + end + \ No newline at end of file diff --git a/ISIS PLM/BOOT.COM b/ISIS PLM/BOOT.COM new file mode 100644 index 0000000..d8df1e1 Binary files /dev/null and b/ISIS PLM/BOOT.COM differ diff --git a/ISIS PLM/BOOT.MAC b/ISIS PLM/BOOT.MAC new file mode 100644 index 0000000..c8c6221 --- /dev/null +++ b/ISIS PLM/BOOT.MAC @@ -0,0 +1,13 @@ + .Z80 + aseg + +boot equ 0ff00h + + org 100h + + jp boot + +ds 17fh-$ + + end + \ No newline at end of file diff --git a/ISIS PLM/BOOTGEN.COM b/ISIS PLM/BOOTGEN.COM new file mode 100644 index 0000000..26892e6 Binary files /dev/null and b/ISIS PLM/BOOTGEN.COM differ diff --git a/ISIS PLM/CBIOSX.MAC b/ISIS PLM/CBIOSX.MAC new file mode 100644 index 0000000..a81d0e0 --- /dev/null +++ b/ISIS PLM/CBIOSX.MAC @@ -0,0 +1,1333 @@ +; ALTAIR 8800 BIOS with 8800 disk drives - 256 files each +; +; +; 07-Jan-2007, P. Schorn, disk configuration for PLM +; 05-Nov-2006, P. Schorn, configurable initial command after booting +; 14-Oct-2006, P. Schorn, made patching and Z80 check configurable +; 09-Oct-2002, P. Schorn, added support for simulated hard disk +; 01-Oct-2002, P. Schorn, changed computation for memory configuration (proposed +; by Scott LaBombard) +; 28-Apr-2002, P. Schorn, updated for new boot ROM +; 15-Apr-2002, P. Schorn, code clean up and simplification +; sanity check of (cdisk) to avoid loop on "Select" error +; 03-Apr-2002, P. Schorn, added CCP patches to allow SUBMIT +; on non-A boot drive as well +; moved lower case patch into BIOS +; 01-Apr-2002, P. Schorn, fixed bug in 'gotoit' +; 31-Mar-2002, P. Schorn, added BDOS patch to reboot in case of +; Bad Sector message and ^C typed +; 29-Mar-2002, P. Schorn, added symbol at end +; warm boot now uses the correct drive +; 23-Mar-2002, P. Schorn, added some CEO patches to BDOS + +false equ 0 +true equ not false + +initCmd equ false ; if true then cold boot invokes a command +sleepol equ true ; if true then sleep a bit while status polling + ; Note: requires SIMH + + .8080 +jpopcod equ (jmp) ; jp op-code +jpzopcd equ (jz) ; jp z op-code + + .Z80 + aseg + org 100h + maclib MEMCFG.LIB ; define configuration parameters + .phase biosph +ccp equ ccpph ; ccp start address +bdos equ bdosph + 6 ; bdos start address +bios equ biosph ; bios start address + +; default values in case configuration parameters are left undefined + ifndef nhdisks +nhdisks equ 0 + endif + + ifndef needZ80 +needZ80 equ false + endif + + ifndef patchOS +patchOS equ false + endif + +wbotloc equ 0000h ; warm boot location +bdosloc equ 0005h ; BDOS entry location +bioserr equ 1 ; 1 indicates BIOS error +cdisk equ 0004h ; current disk location +ndisks equ 8 ; total number of Altair disks +tracks equ 254 ; number of tracks for regular drives +track1 equ tracks+1 ; indicator for unknown track position +asecsiz equ 137 ; sector size Altair +csecsiz equ 0080h ; sector size CP/M +rom equ 0ff00h ; address of Altair bootstrap loader in ROM +bootdr1 equ rom+0037h ; taken from dskboot (offset unitnooffset1) +bootdr2 equ rom+00b4h ; taken from dskboot (offset unitnooffset2) + +; Address Mode Function +; ------- ---- -------- +; selout Out Selects and enables controller and drive +; statin In Indicates status of drive and controller +; dskcon Out Controls disk function +; secpos In Indicates current sector position of disk +; dskwrit Out Write data +; dskread In Read data + +selout equ 8 ; port to select and enable controller and drive (OUT) +; +---+---+---+---+---+---+---+---+ +; | C | X | X | X | Device | +; +---+---+---+---+---+---+---+---+ +; +; C = If this bit is 1, the disk controller selected by 'device' is +; cleared. If the bit is zero, 'device' is selected as the +; device being controlled by subsequent I/O operations. +; X = not used +; Device = value zero thru 15, selects drive to be controlled. + +statin equ 8 ; port indicating status of drive and controller (IN) +; +---+---+---+---+---+---+---+---+ +; | R | Z | I | X | X | H | M | W | +; +---+---+---+---+---+---+---+---+ +; +; W - When 0, write circuit ready to write another byte. +; M - When 0, head movement is allowed +; H - When 0, indicates head is loaded for read/write +; X - not used (will be 0) +; I - When 0, indicates interrupts enabled (not used this simulator) +; Z - When 0, indicates head is on track 0 +; R - When 0, indicates that read circuit has new byte to read + +dskcon equ 9 ; port to control disc function (OUT) +; +---+---+---+---+---+---+---+---+ +; | W | C | D | E | U | H | O | I | +; +---+---+---+---+---+---+---+---+ +; +; I - When 1, steps head IN one track +; O - When 1, steps head OUT one track +; H - When 1, loads head to drive surface +; U - When 1, unloads head +; E - Enables interrupts (ignored by this simulator) +; D - Disables interrupts (ignored by this simulator) +; C - When 1 lowers head current (ignored by this simulator) +; W - When 1, starts Write Enable sequence: +; W bit on device 'statin' (see above) will go 1 and data will be read from +; port 'dskread' until 137 bytes have been read by the controller from +; that port. The W bit will go off then, and the sector data will be written +; to disk. Before you do this, you must have stepped the track to the desired +; number, and waited until the right sector number is presented on +; device 'secpos', then set this bit. + +secpos equ 9 ; port to indicate current sector position of disk (IN) +; As the sectors pass by the read head, they are counted and the +; number of the current one is available in this register. +; +; +---+---+---+---+---+---+---+---+ +; | X | X | Sector Number | T | +; +---+---+---+---+---+---+---+---+ +; +; X = Not used +; Sector number = binary of the sector number currently under the head, 0-31. +; T = Sector True, is a 1 when the sector is positioned to read or write. + +dskwrit equ 10 ; port to write data (OUT) +dskread equ 10 ; port to read data (IN) + +; All I/O is via programmed I/O. Each device has a status port +; and a data port. A write to the status port can select +; some options for the device although the simulator only +; recognizes the reset command (0x03). +; A read of the status port gets the port status: +; +; +---+---+---+---+---+---+---+---+ +; | X | X | X | X | X | X | O | I | +; +---+---+---+---+---+---+---+---+ +; +; I - A 1 in this bit position means a character has been received +; on the data port and is ready to be read. +; O - A 1 in this bit means the port is ready to receive a character +; on the data port and transmit it out over the serial line. +; +; A read to the data port gets the buffered character, a write +; to the data port writes the character to the device. +constat equ 16 ; sio port 1 status port +condata equ 17 ; sio port 1 data port +punstat equ 18 ; sio port 2 status port +pundata equ 19 ; sio port 2 data port + +; masks for disk controller (statin) +mhm equ 02h ; head movement mask +mtzero equ 40h ; head on track zero mask +mall equ 0ffh ; everything ok mask + +; commands for disk controller (dskcon) +cstepin equ 01h ; step in command +cstepot equ 02h ; step out command +cload equ 04h ; load head to drive surface command +cuload equ 08h ; unload head from drive surface command +cwrseq equ 80h ; 'start write enable sequence' command + +; masks for SIO controller (constat, punstat) +mout equ 02h ; output allowed mask + +; commands for SIO controller (constat, punstat) +creset equ 3 ; reset command + + if nhdisks gt 0 +; constants for hard disk port +hdskReset equ 1 ; command to reset controller +hdskRead equ 2 ; read command +hdskWrite equ 3 ; write command +hdskport equ 0fdh ; control port for simulated hard disk +firstSector equ 17 ; first sector to load +firstTrack equ 0 ; from this track +firstDiskAddr equ 256*firstTrack+firstSector +sectors equ (ccplen+bdoslen)/csecsiz + endif + +dirent equ 255 ; number of directory entries +restrk equ 6 ; reserved tracks +dsm06 equ 1efh ; maximum data block number for disks 0 to 6 +dsm07 equ 254 ; maximum data block number for disk 7 +spt equ 32 ; sectors per track +sptmask equ spt-1 ; mask corresponding to 'spt' +cks equ (dirent+1)/4 +cr equ 13 ; Carriage Return +lf equ 10 ; Line Feed + + jp boot ; cold start +wboote: jp wboot ; warm start (reboot) + jp const ; console status + jp conin ; console input + jp conout ; console output + jp list ; list character out + jp punch ; punch character out + jp reader ; read character in + jp home ; move disk head to home + jp seldsk ; select disk drive + jp settrk ; set track number + jp setsec ; set sector number + jp setdma ; set disk memory read/write address + jp read ; read sector + jp write ; write sector + jp listst ; list dev status test + jp sectrn ; sector translate + +; The BOOT entry point gets control from the cold start loader and is +; responsible for basic system initialization, including sending a sign-on +; message, which can be omitted in the first version. If the IOBYTE function +; is implemented, it must be set at this point. The various system parameters +; that are set by the WBOOT entry point must be initialized, and control is +; transferred to the CCP at 3400 + b for further processing. Note that +; register C must be set to zero to select drive A. +boot: ld sp,chk02 + ld a,(bootdr1) ; load current disk with boot drive + ld (cdisk),a + ld de,msg1 ; print welcome message + call msg + + if needZ80 +entcpm: xor a + dec a + jp po,ent2 ; all eight bits set means parity even for 8080, po is Z80 + ld de,msg2 ; got an 8080 which is no good + call msg ; warn user + halt ; wait for processor to be changed + jp entcpm ; and try again +ent2 equ $ + else +entcpm equ $ + endif + + ld a,jpopcod ; jp instruction code + ld (wbotloc),a ; store at entry to warm boot + ld hl,wboote ; get jump location + ld (wbotloc+1),hl ; and store it after jp instruction + ld (bdosloc),a ; jp instruction code for entry to BDOS + ld hl,bdos ; get jump location + ld (bdosloc+1),hl ; and store it after jp instruction + + if patchOS +; begin patch CCP and BDOS + ld b,low ((patche-patchs) shr 2) ; number of entries in patch table + ld hl,patchs ; start of patch table +patch1: ld e,(hl) ; is lower byte of address for jp instruction + inc hl ; point to upper byte + ld d,(hl) ; points to address for jp instruction + inc hl ; points to lower byte of source jp address + ld a,jpopcod ; jp op code + ld (de),a ; store jp op-code to appropriate location + inc de ; points to lower byte of destination jp address + ld a,(hl) ; get lower byte of address + ld (de),a ; store it + inc hl ; point to upper byte source jp address + inc de ; point to upper byte destination jp address + ld a,(hl) ; get upper byte of address + ld (de),a ; store it + inc hl ; point to next table pair + dec b ; entry done + jp nz,patch1 ; if more to do + +; patch bdos to perform a ROM reboot in case of Bad Sector error +; is detected and user has typed ^C. This is to make sure that one +; can recover from errors due to non-existing drives. + ld hl,rom + ld (bdos+009ch),hl ; at bdos+9bh we now have jp z,rom instead of jp z,0 + +; patch ccp to look on ipl drive if file not found + ld a,jpzopcd ; replace jp opcode with jp z opcode + ld (ccp+06dbh),a ; plug into ccp at intercept point + + ld hl,lctabs + ld c,low ((lctabe-lctabs) / 3) ; number of table entries +;precondition: points to table with structure (byte length, word address)* +;at 'address' starts a character string of length 'length' which is to be translated to +;lower case +tolc: ld b,(hl) ; points to length byte + inc hl ; points to lower byte of address + ld e,(hl) ; E := lower byte of address + inc hl ; points to upper byte of address + ld d,(hl) ; D := upper byte of address + inc hl ; points to next length byte + ex de,hl +tolc1: ld a,(hl) ; get character to be transformed + cp 'A' + jp c,tolc2 ; next character if less than 'A' + cp 'Z'+1 + jp nc,tolc2 ; next character if greater than 'Z' + add a,'a'-'A' ; to lower case + ld (hl),a ; store back +tolc2: inc hl ; point to next character + dec b ; count down length + jp nz,tolc1 ; repeat if necessary + ex de,hl ; points to next length byte + dec c ; update number of table entries processed + jp nz,tolc ; if not equal to zero, continue +;end patch CCP and BDOS + endif + + + if initCmd + ld de,ccp+7 ; destination in CCP + ld hl,cmdBeg ; command length, command, 0 +movCmd: ld a,(hl) ; get byte + ld (de),a ; store at destination + or a ; check byte + jp z,doneMv ; zero byte is the last, done + inc hl ; next source + inc de ; next destination + jp movCmd ; repeat +doneMv: ld (cmdBeg),a ; execute only once + endif + + ld a,creset ; reset command + out (constat),a ; reset console device + out (punstat),a ; and list/punch device + ld bc,0080h + call setdma + ld a,(cdisk) ; get current disk + cp ndisks+nhdisks ; does it exist? + jp c,ent1 ; yes, proceed + ld a,(bootdr1) ; get boot drive + ld (cdisk),a ; and make it current disk +ent1: ld c,a ; inform CCP + ei + jp ccp + + if initCmd +cmdBeg: db cmdEnd-cmdBeg-2,'DO INITMAKE',0 +cmdEnd equ $ + endif + + + if patchOS +; DD40 3A E3EF ld a,(cdisk) +; DD43 B7 or a +; DD44 3E 00 ld a,0 +; DD46 C4 DCBD call nz,select +; DD49 11 E3AC ld de,subfcb +;DD43: jp ccpp1 +ccpp1: ld e,a ; := current disk + ld a,(bootdr1) ; := boot drive + cp e ; compare boot drive with current disk + jp ccp+0146h ; a select of boot drive occurs iff current disk <> boot drive + +; DD7D 3A E3EF ld a,(cdisk) +; DD80 B7 or a +; DD81 C4 DCBD call nz,select +; DD84 21 DC08 ld hl,combuf +;DD7D: jp ccpp2 +ccpp2: ld a,(bootdr1) ; := boot drive + ld e,a ; := boot drive + ld a,(ccp+07efh) ; := current disk + cp e ; compare boot drive with current disk + jp ccp+0181h ; a select of current disk occurs iff current disk <> boot drive + +; DDE3 36 00 ld (hl),0 ;submit flag is set to false +; DDE5 AF xor a +; DDE6 CD DCBD call select ;on drive a to erase file +; DDE9 11 E3AC ld de,subfcb +;DDE3: jp ccpp3 +ccpp3: ld (hl),0 ; patched over + ld a,(bootdr1) ; := boot drive + jp ccp+01e6h ; go select boot drive + +; patch bdos to change the drive selected by +; BDOS Function 13 (Reset Disk System). +f13pat: ld a,(bootdr1) ; get boot drive + ld (bdos+033ch),a ; store into curdsk (BDOS) + jp bdos+0c8ah + +; patch ccp to look on ipl drive if file not found +ccpat: ld hl,ccp+07f0h ; look at drive spec in command + or (hl) ; zero means default was taken + jp nz,ccp+076bh ; if nonzero don't change it + ld a,(bootdr1) ; take boot drive and increment it since + inc a ; for a FCB A=1, B=2, ... + ld (hl),a ; modify command line + ld de,ccp+07d6h ; setup for retry + jp ccp+06cdh ; go retry command + +; patch ccp to show current user number in prompt +propat: call ccp+0113h ; get current user no + or a + jp z,prono ; do not show it if it's 0 + cp 10 ; see if 1 or 2 digits + jp nc,pro2 + add a,'0' +pro1: call ccp+008ch ; output a character +prono: ld a,'>' ; prompt character + call ccp+008ch ; output it + jp ccp+0395h ; resume ! +pro2: add a,'0' - 10 + push af + ld a,'1' + call ccp+008ch + pop af + jp pro1 + +; patch bdos to look at user 0 if file not found in current user # +pubpat: ld a,b ; get char count + or a ; looking at first byte? + jp nz,pubno ; no, skipit + ld a,(de) ; get user # from directory + cp 0e5h ; active dir entry? + jp z,pubno ; no + ld a,(hl) ; get user# from dir entry + or a ; is it user # 0? + jp z,bdos+0776h ; yes, force char match regardless +pubno: ld a,b + cp 13 + jp bdos+075bh + endif + +; print the message pointed to by and terminated by '$' to the console +; leaves unchanged +msg: ld a,(de) ; get character + cp '$' ; is is the terminating character? + ret z ; yes, we are done + ld c,a ; 'conout' expects the character in + call conout ; disply it on console + inc de ; point to next character + jp msg ; and repeat + +; The WBOOT entry point gets control when a warm start occurs. A warm +; start is performed whenever a user program branches to location 0000H, or +; when the CPU is reset from the front panel. The CP/M system must be +; loaded from the first two tracks of drive A up to, but not including, the +; BIOS, or CBIOS, if the user has completed the patch. System parameters +; must be initialized as follows: +; location 0,1,2 Set to JMP WBOOT for warm starts +; (000H: JMP 4A03H + b) +; location 3 Set initial value of IOBYTE, if implemented in the +; CBIOS +; location 4 High nibble = current user no; low nibble current +; drive +; location 5,6,7 Set to JMP BDOS, which is the primary entry point +; to CP/M for transient programs. (0005H: JMP 3C06H + b) +; Upon completion of the initialization, the WBOOT program must branch to the +; CCP at 3400H + b to restart the system. Upon entry to the CCP, register C +; is set to the drive to select after system initialization. The WBOOT +; routine should read location 4 in memory, verify that is a legal drive, and +; pass it to the CCP in register C. +wboot: ld sp,chk02 + ld a,(bootdr1) ; make sure that ccp and bdos are loaded from correct disk + + if nhdisks gt 0 + cp ndisks + jp c,altdsk + ld b,32 ; reset hard disk controller + ld a,hdskReset ; by issuing the reset command 32 times +rhdsk: out (hdskPort),a + dec b + jp nz,rhdsk ; post condition is := 0 + ld de,firstDiskAddr ; := 0 (Track), := 8 (Sector) + ld hl,ccp ; DMA address + ld c,sectors ; is loop counter +again: ld a,hdskRead + out (hdskport),a ; send read command to hard disk port + ld a,(bootdr1) ; in real life take disk number from boot ROM + sub ndisks ; correct for Altair disks + out (hdskport),a ; send drive to boot from to hard disk port + ld a,e + out (hdskport),a ; send sector + ld a,d + out (hdskport),a ; send lower byte of track + xor a + out (hdskport),a ; send higher byte of track which is always 0 + ld a,l + out (hdskport),a ; send lower byte of DMA address + ld a,h + out (hdskport),a ; send upper byte of DMA address + in a,(hdskport) ; perform operation and get result + or a + jp z,cont ; continue if no error + halt ; halt otherwise +cont: ld a,c ; save in + ld c,csecsiz ; is now 128 since always zero + add hl,bc ; get next DMA address + ld c,a ; restore from + dec c ; decrement loop counter + jp z,entcpm + inc e ; Sector := Sector + 2 + inc e + ld a,e + cp spt ; is new Sector equal to 32 + jp z,switch ; yes, need to go to odd sectors + cp spt+1 ; is new Sector equal to 33 + jp nz,again ; no, proceed with read + ld e,0 ; Sector := 0 + inc d ; Track := Track + 1 + jp again ; proceed with read +switch: ld e,1 ; Sector := 1 + jp again ; proceed with read +altdsk equ $ + endif + + out (selout),a ; select it + ld a,cload ; load head command + out (dskcon),a ; load head to drive surface + call dhome ; position disk head on track zero + ld de,ccp ; destination load address + ld b,17 ; first sector to read on track zero +nextsc: push bc ; save current sector to read, is undefined + push de ; save current destination load address + call seclp2 ; position to sector in + call blread ; read the sector + pop de ; restore current destination load address, is destination + ld hl,altbuf+3 ; ignore first three byte of buffer, is source + call ldir ; has been set by 'blread' + pop bc ; is current sector, is undefined + ld hl,bios ; when reaches this address we are done + ld a,d + cp h + jp nz,decide + ld a,e + cp l +decide: jp nc,gotoit ; jump if everything loaded + inc b ; compute next sector number + inc b + ld a,b + cp spt ; compare new sector number with sectors per track + jp c,nextsc ; continue if less + ld b,1 ; otherwise prepare for odd numbered sectors + jp z,nextsc ; if old sector number was equal to sectors per track + call whmove ; loop until head movement is allowed + ld a,cstepin ; step in one track command + out (dskcon),a ; step in one track + ld b,0 ; start with even sectors + jp nextsc +gotoit: ld a,(bootdr2) ; clear disk controller of correct disk + out (selout),a ; do it + ld hl,ontrk0 ; start address of table for current track positions + ld b,ndisks ; number of disks +resett: ld (hl),track1 ; reset entry for disk + inc hl ; point to next entry + dec b ; decrement counter for disks to go + jp nz,resett ; jump if not yet done + jp entcpm + +; You should sample the status of the currently assigned console device and +; return 0FFH in register A if a character is ready to read and 00H in register +; A if no console characters are ready. +; +; console in/out routines - use sio port 1 +; +const: in a,(constat) ; get console status + rra ; I bit into carry + ld a,0 ; prepare no character available + ret nc ; I bit clear means no character, done + dec a ; character available, result is 0ffh + ret ; done + +; The next console character is read into register A, and the parity bit is set, +; high-order bit, to zero. If no console character is ready, wait until a +; character is typed before returning. + if sleepol + +conin: in a,(constat) ; get console status + rra ; I bit into carry + jp c,getchr ; get character + ld a,27 ; otherwise sleep for SIMHSleep microseconds + out (0feh),a ; execute command + jp conin ; try again +getchr: in a,(condata) ; read character + and 7fh ; clear bit 8 + ret + + else + +conin: in a,(constat) ; get console status + rra ; I bit into carry + jp nc,conin ; jump back if no character available + in a,(condata) ; read character + and 7fh ; clear bit 8 + ret + + endif + +; The character is sent from register C to the console output device. The +; character is in ASCII, with high-order parity bit set to zero. You might +; want to include a time-out on a line-feed or carriage return, if the console +; device requires some time interval at the end of the line (such as a TI Silent +; 700 terminal). You can filter out control characters that cause the console +; device to react in a strange way (CTRL-Z causes the Lear-Siegler terminal +; to clear the screen, for example). +conout: in a,(constat) ; get console status + and mout ; mask output bit + jp z,conout ; jump back if not ready for output + ld a,c ; prepare character for output + out (condata),a ; do it + ret + +; +; reader/punch routines use sio port 2 +; +; The character is sent from register C to the currently assigned listing +; device. The character is in ASCII with zero parity bit. +list: ; list aliased to punch +; The character is sent from register C to the currently assigned punch +; device. The character is in ASCII with zero parity. +punch: in a,(punstat) ; get punch status + and mout ; mask output bit + jp z,punch ; jump back if not ready for output + ld a,c ; prepare character for output + out (pundata),a ; do it + ret + +; The next character is read from the currently assigned reader device into +; register A with zero parity (high-order bit must be zero); an end-of-file +; condition is reported by returning an ASCII CTRL-Z(1AH). +reader: in a,(punstat) ; get reader status + rra ; I bit into carry + jp nc,reader ; jump back if no character available + in a,(pundata) ; read character + ret + +; The disk drive given by register C is selected for further operations, where +; register C contains 0 for drive A, 1 for drive B, and so on up to 15 for +; drive P (the standard CP/M distribution version supports four drives). On +; each disk select, SELDSK must return in HL the base address of a 16-byte +; area, called the Disk Parameter Header, described in Section 6.10. For +; standard floppy disk drives, the contents of the header and associated +; tables do not change; thus, the program segment included in the sample +; CBIOS performs this operation automatically. +; If there is an attempt to select a nonexistent drive, SELDSK returns HL = +; 0000H as an error indicator. Although SELDSK must return the header +; address on each call, it is advisable to postpone the physical disk select +; operation until an I/O function (seek, read, or write) is actually performed, +; because disk selects often occur without ultimately performing any disk +; I/O, , and many controllers unload the head of the current disk before +; selecting the new drive. This causes an excessive amount of noise and disk +; wear. The least significant bit of register E is zero if this is the first +; occurrence of the drive select since the last cold or warm start. +seldsk: ld hl,0 ; select disk number + ld a,c + ld (diskno),a + cp ndisks+nhdisks ; number of disk drives + ret nc ; error - disk number too high + ld l,a ; := disk number + ld h,0 + add hl,hl ; disk number * 2 + add hl,hl ; disk number * 4 + add hl,hl ; disk number * 8 + add hl,hl ; disk number * 16 + ld de,dpbase ; dpbase entries have size of 16 bytes + add hl,de ; = 16 * disknumber + dpbase + ret + +; The disk head of the currently selected disk (initially disk A) is moved to +; the track 00 position. If the controller allows access to the track 0 flag +; from the drive, the head is stepped until the track 0 flag is detected. If the +; controller does not support this feature, the HOME call is translated into a +; call to SETTRK with a parameter of 0. +home: ld bc,0 ; move to track 00 + ; fall into settrk + +; Register BC contains the track number for subsequent disk accesses on the +; currently selected drive. The sector number in BC is the same as the +; number returned from the SECTRAN entry point. You can choose to seek +; the selected track at this time or delay the seek until the next read or write +; actually occurs. Register BC can take on values in the range 0-76 +; corresponding to valid track numbers for standard floppy disk drives and +; 0-65535 for nonstandard disk subsystems. +settrk: ld l,c ; save track + ld h,b + ld (track),hl + ret + +; Register BC contains the sector number, 1 through 26, for subsequent disk +; accesses on the currently selected drive. The sector number in BC is the +; same as the number returned from the SECTRAN entry point. You can +; choose to send this information to the controller at this point or delay +; sector selection until a read or write operation occurs. +setsec: ld a,c ; set sector + ld (sector),a + ret + +; Logical-to-physical sector translation is performed to improve the overall +; response of CP/M. Standard CP/M systems are shipped with a skew factor +; of 6, where six physical sectors are skipped between each logical read +; operation. This skew factor allows enough time between sectors for most +; programs to load their buffers without missing the next sector. In particular +; computer systems that use fast processors, memory, and disk subsystems, +; the skew factor might be changed to improve overall response. However, +; the user should maintain a single-density IBM-compatible version of CP/M +; for information transfer into and out of the computer system, using a skew +; factor of 6. +; In general, SECTRAN receives a logical sector number relative to zero in +; BC and a translate table address in DE. The sector number is used as an +; index into the translate table, with the resulting physical sector number in +; HL. For standard systems, the table and indexing code is provided in the +; CBIOS and need not be changed. +sectrn: + if nhdisks gt 0 + ld l,c ; := BC, prepration for = 0 + ld h,b ; load upper byte + inc hl ; rebase to one + ld a,e ; get lower byte of translate table address + or d ; or with upper byte + ret z ; if equal to zero, no translation necessary + endif + ex de,hl ; := translate table address + add hl,bc ; add sector number + ld l,(hl) ; get pointed to byte + ld h,0 ; set upper byte to zero + ret ; done + +; Register BC contains the DMA (Disk Memory Access) address for +; subsequent read or write operations. For example, if B = 00H and C = 80H +; when SETDMA is called, all subsequent read operations read their data +; into 80H through 0FFH and all subsequent write operations get their data +; from 80H through 0FFH, until the next call to SETDMA occurs. The initial +; DMA address is assumed to be 80H. The controller need not actually +; support Direct Memory Access. If, for example, all data transfers are +; through I/O ports, the CBIOS that is constructed uses the 128byte area +; starting at the selected DMA address for the memory buffer during the +; subsequent read or write operations. +setdma: ld l,c ; set dma address + ld h,b + ld (dmaad),hl + ret + +; +; altair disk read/write drivers +; +; Assuming the drive has been selected, the track has been set, and +; the DMA address has been specified, the READ subroutine attempts to +; read eone sector based upon these parameters and returns the following +; error codes in register A: +; +; 0 no errors occurred +; +; 1 nonrecoverable error condition occurred +; +; Currently, CP/M responds only to a zero or nonzero value as the return +; code. That is, if the value in register A is 0, CP/M assumes that the disk +; operation was completed properly. IF an error occurs the CBIOS should +; attempt at least 10 retries to see if the error is recoverable. When an error +; is reported the BDOS prints the message BDOS ERR ON x: BAD +; SECTOR. The operator then has the option of pressing a carriage return to +; ignore the error, or CTRL-C to abort. + if nhdisks gt 0 +read: ld a,(diskno) ; get disk number + cp ndisks ; compare with number of Altair disks + jp c,aread ; carry means we got an Altair disk + ld a,hdskRead ; otherwise perform hard disk read + jp shdpar ; send hard disk parameters +aread equ $ + else +read equ $ + endif + call poshed ; select disk 'diskno' and position disk head to 'track' + call secget ; position head to desired sector + di + call blread + ld a,cuload ; unload head command + out (dskcon),a ; do it + ei + ld de,altbuf+3 ; address of sector just read + ld hl,(dmaad) ; destination address + ex de,hl ; prepare for ldir + call ldir ; move + +; You return the ready status of the list device used by the DESPOOL +; program to improve console response during its operation. The value 00 is +; returned in A if the list device is not ready to accept a character and 0FFH +; if a character can be sent to the printer. A 00 value should be returned if +; LIST status is not implemented. +listst: xor a ; := 0 means no error + ret + +; Data is written from the currently selected DMA address to the currently +; selected drive, track, and sector. For floppy disks, the data should be +; marked as nondeleted data to maintain compatibility with other CP/M +; systems. The error codes given in the READ command are returned in +; register A, with error recovery attempts as described above. + if nhdisks gt 0 +write: ld a,(diskno) ; get disk number + cp ndisks ; compare with number of Altair disks + jp c,awrite ; carry means we got an Altair disk + ld a,hdskWrite ; otherwise perform hard disk write +shdpar: out (hdskPort),a ; send command + ld a,(diskno) ; get disk number + sub ndisks ; rebase + out (hdskPort),a ; send rebased disk number + ld a,(sector) ; get sector + dec a ; rebase to 0 + out (hdskPort),a ; send rebased sector number + ld a,(track) ; get lower byte of track + out (hdskPort),a ; send lower byte of track + ld a,(track+1) ; get upper byte of track + out (hdskPort),a ; send upper byte of track + ld a,(dmaad) ; get lower byte DMA address + out (hdskPort),a ; send lower byte of DMA address + ld a,(dmaad+1) ; get upper byte of DMA address + out (hdskPort),a ; send upper byte of DMA address + in a,(hdskPort) ; perform command and get result + ret +awrite equ $ + else +write equ $ + endif + call poshed ; select desired disk and position to desired track + call secget ; position head to desired sector + ld hl,(dmaad) ; source of sector is in 'dmaad' + ld de,altbuf+3 ; destination inside local buffer + ld bc,csecsiz ; sector size is 128 + call ldir ; block move + ld a,cwrseq ; command for 'start write enable sequence' + out (dskcon),a ; do it + di + ld hl,altbuf ; point to first byte in local buffer + ld b,asecsiz+1 ; number of bytes to write (additional byte triggers 'real' write) +wready: in a,(statin) ; get status + rra ; get bit for ready for write + jp c,wready ; loop until ready for write + ld a,(hl) ; byte to write + out (dskwrit),a ; write byte + inc hl ; point to next byte + dec b ; decrement counter of bytes + jp nz,wready ; jp if not done + ld a,cuload ; unload head command + out (dskcon),a ; do it + ei + xor a ; := 0 means no error + ret + +; Postcondition: 'altbuf' contains 'asecsiz' many bytes, is set to 'csecsiz' +blread: ld hl,altbuf ; address of sector buffer + ld e,asecsiz ; number of bytes to read +blrd1: in a,(statin) ; get disk status + or a ; set sign of byte + jp m,blrd1 ; loop until disk has new byte to read + in a,(dskread) ; read byte of sector + ld (hl),a ; store into buffer + inc hl ; point to next position in buffer + dec e ; decrement size counter + jp nz,blrd1 ; if not zero, we need to continue + ld bc,csecsiz ; sector size in preparation for call to 'ldir' + ret + +; position disk on track zero, == 0 at the end +dhome: in a,(statin) ; position disk to track 0 + and mtzero ; mask for 'head is on track zero' + ret z ; track zero reached, done + call whmove ; loop until head movement is allowed + ld a,cstepot ; command for 'step head out one track' + out (dskcon),a ; do it + jp dhome ; try again + +; Select disk 'diskno' and position disk head to 'track' +poshed: call calcd ; position altair disk head + ld a,d ; select disk , cur track in + out (selout),a ; select disk + in a,(statin) ; get status of selected drive + cp mall ; ok? + jp z,selerr ; no! + ld a,b ; := track of selected disk + cp track1 ; compare with non-existing track + jp nz,alseek ; if a regular track, proceed to seek + call dhome ; position disk to track 0 + ld b,a ; := 0 (current track) +;Input: location 'track' contains desired track +; contains current track +;Output: desired track is reached and stored in track array +alseek: ld a,(track) ; seek to 'track' (cur track in b) + ld e,a ; := desired track + ld a,b ; := current track + sub e ; := current track - desired track + ret z ; we are already at desired track + ld e,a ; e is the number of "step in" or "step out" + jp c,stpin ; current track < desired track + ld c,cstepot ; command for step head out one track + jp aseek ; perform steps +stpin: ld c,cstepin ; command for step head in one track + cpl ; := ~(current track - desired track) + inc a ; := desired track - current track (positive) + ld e,a ; is positive number of tracks to move +aseek: call whmove ; loop until head movement is allowed + ld a,c ; get command (step in or step out) + out (dskcon),a ; perform it + dec e ; next iteration + jp nz,aseek ; loop if not done + call calcd ; get pointer to 'track' of 'diskno' + ld a,(track) ; this is the current track + ld (hl),a ; update 'track' of 'diskno' + ret +selerr: pop hl ; discard return address + ld a,bioserr ; := 1 means error + ret + +; loop until head movement is allowed +whmove: in a,(statin) ; get status + and mhm ; mask for 'head movement allowed' + jp nz,whmove ; loop until movement allowed + ret + +; Input: - implicit input is location 'diskno' +; Output: contains the current track of 'diskno' +; , and contain 'diskno' +; points to 'track' of 'diskno' +calcd: ld a,(diskno) ; get 'diskno' + ld e,a ; := 'diskno' + ld hl,ontrk0 + ld d,0 + add hl,de ; points to 'track' of 'diskno' + ld b,(hl) ; := 'track' of 'diskno' + ld d,e ; := 'diskno' + ret + +; Input: 'sector' contains desired sector number +; Output: head is positioned at desired sector +secget: ld a,cload ; command to load head to drive surface + out (dskcon),a ; do it + ld a,(sector) ; := desired sector + dec a ; adjust to range 0..(spt-1) + ld b,a ; := adjusted, desired sector + cp spt ; compare with sectors per track + jp c,seclp2 ; desired sector is less than total sectors per track, ok + ld de,secmsg ; prepare error message + call msg ; print it + halt ; not much we can do +seclp2: in a,(secpos) ; get sector position + rra ; rotate T bit into carry + jp c,seclp2 ; loop until sector is positioned to read or write + and sptmask ; now contains the sector under the head + cp b ; compare with desired sector + jp nz,seclp2 ; repeat if not equal + ret + +; Move bytes from start address to destination . +; This is equivalent to the Z80 instruction 'LDIR'. +; This subroutine dynamically determines the processor. +ldir: xor a ; := 0 + dec a ; := 1111'1111b + jp pe,ldir1 ; on an 8080 this means parity is even + ldir ; otherwise we have a Z80 + ret +ldir1: ld a,(hl) ; get byte from source + ld (de),a ; put byte to destination + inc hl ; point to next source address + inc de ; point to next destination address + dec bc ; decrement number of bytes to move + ld a,c ; := ( or ) + or b + jp nz,ldir1 ; not zero, move again + ret + + if patchOS +lctabs: db 9 ; (R)EAD ERROR + dw ccp+03e0h ; DFE0 + db 6 ; (N)O FILE + dw ccp+03f1h ; DFF1 + db 2 ; (A)LL + dw ccp+0553h ; E153 + db 7 ; (N)O SPACE + dw ccp+0608h ; E208 + db 10 ; (F)ILE EXISTS + dw ccp+0683h ; E283 + db 7 ; (B)AD LOAD + dw ccp+077bh ; E37B +lctabe equ $ + +patchs: dw ccp+0143h, ccpp1 ; DD43: jp ccpp1 + dw ccp+017dh, ccpp2 ; DD7D: jp ccpp2 + dw ccp+01e3h, ccpp3 ; DDE3: jp ccpp3 + dw ccp+0392h, propat + dw ccp+06dbh, ccpat + dw bdos+0c86h, f13pat + dw bdos+0758h, pubpat +patche equ $ + endif + +; In general, each disk drive has an associated (16-byte) disk parameter +; header that contains information about the disk drive and provides a +; scratch pad area for certain BDOS operations. The format of the disk +; parameter header for each drive is shown below, where each element is a +; word (16-bit) value. +; +; DISK PARAMETER HEADER +; +-------+------+------+------+----------+-------+-------+-------+ +; | XLT | 0000 | 0000 | 0000 |DIRBUF| DPB | CSV | ALV | +; +------+------+------+-------+----------+-------+-------+-------+ +; 16B 16B 16B 16B 16B 16B 16B 16B +; +; XLT Address of the logical-to-physical translation vector, if used +; for this particular drive, or the value 0000H if no sector translation +; takes place (that is, the physical and logical sector numbers are the +; same). Disk drives with identical sector skew factors share the same +; translate tables. +; +; 0000 Scratch pad values for use within the BDOS, initial value is +; unimportant. DIRBUF Address of a 128-byte scratch pad area for directory +; operations within BDOS. All DPHs address the same scratch pad area. +; +; DPB Address of a disk parameter block for this drive. Drives +; withidentical disk characteristics address the same disk parameter block. +; +; CSV Address of a scratch pad area used for software check for +; changed disks. This address is different for each DPH. +; +; ALV Address of a scratch pad area used by the BDOS to keep disk +; storage allocation information. This address is different for each DPH. +; +; Given n disk drives, the DPHs are arranged in a table whose first row of 16 +; bytes corresponds to drive 0, with the last row corresponding to drive n-1. +; In the following figure the label DPBASE defines the base address of the +; DPH table. +; +; DPBASE: +; 00 XLT00 0000 0000 0000 DIRBUF DBP00 CSV00 ALV00 +; 01 XLT01 0000 0000 0000 DIRBUF DBP01 CSV01 ALV01 +; (and so on through) +; n-1 XLTn-1 0000 0000 0000 DIRBUF DBPn-1 CSVn-1 ALVn-1 + +; +; The translation vectors, XLT00 through XLTn-1, are located elsewhere in the +; BIOS, and simply correspond one-for-one with the logical sector numbers +; zero through the sector count 1. The Disk Parameter Block (DPB) for each +; drive is more complex. As shown below, particular DPB, that is addressed by +; one or more DPHS, takes the general form: +; +; +---+---+---+---+---+---+---+---+---+---+ +; |SPT|BSH|BLM|EXM|DSM|DRM|AL0|AL1|CKS|OFF| +; +---+---+---+---+---+---+---+---+---+---+ +; 16B 8B 8B 8B 16B 16B 8B 8B 16B 16B +; +; where each is a byte or word value, as shown by the 8b or 16b indicator +; below the field. +; +; The following field abbreviations are used in the figure above: +; SPT is the total number of sectors per track. +; BSH is the data allocation block shift factor, determined by +; the data block allocation size. +; BLM is the data allocation block mask (2[BSH-1]). +; EXM is the extent mask, determined by the data block +; allocation size and the number of disk blocks. +; DSM determines the total storage capacity of the disk drive. +; DRM determines the total number of directory entries that +; can be stored on this drive. +; AL0, AL1 determine reserved directory blocks. +; CKS is the size of the directory check vector. +; +; OFF is the number of reserved tracks at the beginning of the +; (logical) disk. +; +; The values of BSH and BLM determine the data allocation size BLS, which is +; not an entry in the DPB. Given that the designer has selected a value for +; BLS, the values of BSH and BLM are shown in the following table. +; +; BLS BSH BLM +; 1,024 3 7 +; 2,048 4 15 +; 4,096 5 31 +; 8,192 6 63 +; 16,384 7 127 +; +; where all values are in decimal. The value of EXM depends upon both the BLS +; and whether the DSM value is less than 256 or greater than 255, as shown in +; the table below. +; +; EXM values +; BLS DSM<256 DSM>255 +; 1,024 0 N/A +; 2,048 1 0 +; 4,096 3 1 +; 8,192 7 3 +; 16,384 15 7 +; +; The value of DSM is the maximum data block number supported by this +; particular drive, measured in BLS units. The product (DSM + 1) is the total +; number of bytes held by the drive and must be within the capacity of the +; physical disk, not counting the reserved operating system tracks. +; +; The DRM entry is the one less than the total number of directory entries +; that can take on a 16-bit value. The values of AL0 and AL1, however, are +; determined by DRM. The values AL0 and AL1 can together be considered a +; string of 16-bits, as shown below. +; +; |--------- AL0 ---------|-------- AL1 ----------| +; 00 01 02 03 04 05 06 07 08 09 10 11 12 13 14 15 +; +; Position 00 corresponds to the high-order bit of the byte labeled AL0 and +; 15 corresponds to the low-order bit of the byte labeled AL1. Each bit +; position reserves a data block for number of directory entries, thus +; allowing a total of 16 data blocks to be assigned for directory entries +; (bits are assigned starting at 00 and filled to the right until position +; 15). Each directory entry occupies 32 bytes, resulting in the following +; tabulation: +; +; BLS Directory Entries +; 1,024 32 times # bits +; 2,048 64 times # bits +; 4,096 128 times # bits +; 8,192 256 times # bits +; 16,384 512 times # bits +; +; Thus, if DRM = 127 (128 directory entries) and BLS = 1024, there are 32 +; directory entries per block, requiring 4 reserved blocks. In this case, the +; 4 high-order bits of AL0 are set, resulting in the values AL0 = 0F0H and +; AL1 = 00H. +; +; The CKS value is determined as follows: if the disk drive media is +; removable, then CKS = (DRM + 1)/4, where DRM is the last directory entry +; number. If the media are fixed, then set CKS = 0 (no directory records are +; checked in this case). +; +; Finally, the OFF field determines the number of tracks that are skipped at +; the beginning of the physical disk. This value is automatically added +; whenever SETTRK is called and can be used as a mechanism for skipping +; reserved operating system tracks or for partitioning a large disk into +; smaller segmented sections. +; +; To complete the discussion of the DPB, several DPHs can address the same +; DPB if their drive characteristics are identical. Further, the DPB can be +; dynamically changed when a new drive is addressed by simply changing the +; pointer in the DPH; because the BDOS copies the DPB values to a local area +; whenever the SELDSK function is invoked. +; +; Returning back to DPH for a particular drive, the two address values CSV +; and ALV remain. Both addresses reference an area of uninitialized memory +; following the BIOS. The areas must be unique for each drive, and the size +; of each area is determined by the values in the DPB. +; +; The size of the area addressed by CSV is CKS bytes, which is sufficient to +; hold the directory check information for this particular drive. If CKS = +; (DRM + 1)/4, you must reserve (DRM + 1)/4 bytes for directory check use. If +; CKS = 0, no storage is reserved. +; +; The size of the area addressed by ALV is determined by the maximum number +; of data blocks allowed for this particular disk and is computed as (DSM/8) +; + 1. + +; +; diskette drives +; +dpbase equ $ + dw atrans,0,0,0,dirbf,mits2,chk00,all00 + dw atrans,0,0,0,dirbf,mits,chk01,all01 + dw atrans,0,0,0,dirbf,mits,chk02,all02 + dw atrans,0,0,0,dirbf,mits,chk03,all03 + dw atrans,0,0,0,dirbf,mits2,chk04,all04 + dw atrans,0,0,0,dirbf,mits2,chk05,all05 + dw atrans,0,0,0,dirbf,mits2,chk06,all06 + dw atrans,0,0,0,dirbf,mits,chk07,all07 + + if nhdisks gt 0 +defdw macro ?value + dw all0&?value + endm + +defdp macro ?number + local ?hdi +?hdi defl 8 + rept ?number + dw 0,0,0,0,dirbf,simhd,0 + defdw %?hdi +?hdi defl ?hdi+1 + endm + endm + + defdp nhdisks + +simhd: dw spt ; SPT, sectors per track + db 5 ; BSH, data allocation block shift factor, for BLS=4,096 + db 31 ; BLM, data allocation block mask, for BLS=4,096 + db 1 ; extent mask for BLS=4,096 and DSM>255 + dw 2047-restrk ; DSM, maximum data block number + dw 1023 ; DRM, number of directory entries - 1 + db 0ffh,0 ; AL0, AL1, 8 blocks reserved to hold all entries + ; (number of directory entries)*32 = (number of reserved blocks)*(block size BLS) + ; 1024 * 32 = 8 * 4096 + dw 0 ; CKS, set 0 since hard disk is fixed + dw restrk ; OFF, number of tracks skipped at beginning of disk + endif + +; copylib (default) format +mits: dw spt ; spt, sectors per track + db 3 ; allocation block shift factor, bsh + db 7 ; data allocation block mask, blm, allocation size (bls) = 1024 + db 0 ; extent mask + dw dsm07 ; dsm, maximum data block number + dw dirent ; drm, number of directory entries - 1 + db 0ffh,0 ; al0, al1, 8 blocks reserved to hold all entries + ; 256 * 32 = 8 * 1024 + ; (drm+1) * 32 = (number of bits in al0 and al1) * bls + dw cks ; cks = (drm + 1)/4 + dw restrk ; off, number of tracks skipped at beginning of disk + +mits2: dw spt ; spt, sectors per track + db 4 ; allocation block shift factor, bsh + db 15 ; data allocation block mask, blm, allocation size (bls) = 2048 + db 0 ; extent mask + dw dsm06 ; dsm, maximum data block number + dw dirent ; drm, number of directory entries - 1 + db 0f0h,0 ; al0, al1, 4 blocks reserved to hold all entries + ; 256 * 32 = 4 * 2048 + ; (drm+1) * 32 = (number of bits in al0 and al1) * bls + dw cks ; cks = (drm + 1)/4 + dw restrk ; off, number of tracks skipped at beginning of disk + +; speedball (copylib) skewtable +atrans: db 01,18,03,20,05,22,07,24 + db 09,26,11,28,13,30,15,32 + db 17,02,19,04,21,06,23,08 + db 25,10,27,12,29,14,31,16 +msg1: db cr, lf + db '0' + (msize/10) + db '0' + (msize MOD 10) + db 'K CP/M Version 2.2 (SIMH ALTAIR 8800, BIOS V1.26 for PLM, ' + + if nhdisks gt 0 + db '0' + nhdisks + db ' HD, ' + endif + + db '07-Jan-07)' + db cr, lf, '$' + + if needZ80 +msg2: db cr, lf, '8080 CPU detected. Need Z80.', cr, lf, '$' + endif + +secmsg: db cr, lf, 'Cannot find sector in register ', cr, lf, '$' + +; position disk drive head +ontrk0: db track1 ; current track# drive 0 (logical 1) + db track1 ; current track# drive 1 (logical 2) + db track1 ; current track# drive 2 (logical 3) + db track1 ; current track# drive 3 (logical 4) + db track1 ; current track# drive 4 (logical 5) + db track1 ; current track# drive 5 (logical 6) + db track1 ; current track# drive 6 (logical 7) + db track1 ; current track# drive 7 (logical 8) + +diskno: db 0 +sector: db 0 +track: dw 0 +dmaad: dw 0 + +; begin scratch area for bdos +dirbf: ds 128 ; directory work space +all00: ds ((dsm06+1)/8)+1 +all01: ds ((dsm06+1)/8)+1 +all02: ds ((dsm06+1)/8)+1 +all03: ds ((dsm06+1)/8)+1 +all04: ds ((dsm06+1)/8)+1 +all05: ds ((dsm06+1)/8)+1 +all06: ds ((dsm06+1)/8)+1 +all07: ds ((dsm07+1)/8)+1 + + if nhdisks gt 0 + +deflab macro ?value +all0&?value equ $ + endm + +defall macro ?number + local ?hdi +?hdi defl 8 + rept ?number + deflab %?hdi + ds 256 +?hdi defl ?hdi+1 + endm + endm + + defall nhdisks + endif + +chk00: ds cks +chk01: ds cks +chk02: ds cks +chk03: ds cks +chk04: ds cks +chk05: ds cks +chk06: ds cks +chk07: ds cks +altbuf: ds asecsiz+1 + +biosend equ $ +biossiz equ biosend-bios + +; fill remainder with 0 + +fillmod equ biossiz AND 00ffh + if fillmod gt 0 +fillsiz equ 100h-fillmod + ds fillsiz + endif + + if2 +padjust macro ?newsiz + .printx /Adjust bioslen in MEMCFG.LIB to ?newsiz/ + endm + +psize macro ?val1,?val2,?val3,?val4 + .printx /BIOS extends from ?val1 to ?val2 (Size ?val3, bioslen = ?val4)/ + endm + +psave macro ?value + .printx /SAVE ?value CPMBOOT.COM/ + endm + + .radix 16 + psize %bios,%biosend,%biossiz,%bioslen + if biossiz gt bioslen + padjust %(100h*((biossiz + 0ffh) / 100h)) + endif + .radix 10 + if biosend gt 0ff00h + .printx /Warning: BIOS extends into Altair ROM/ + endif + + psave %(9+(ccplen + bdoslen + bioslen) / 100h) + + endif + + .dephase + + end + \ No newline at end of file diff --git a/ISIS PLM/CC.SUB b/ISIS PLM/CC.SUB new file mode 100644 index 0000000..0edaa15 --- /dev/null +++ b/ISIS PLM/CC.SUB @@ -0,0 +1,13 @@ +attach b 4 +b:seteof $1.plm +b:is14 +ERA $1.MOD +era $1 +era $1.obj +:f1:PLM80 $1.PLM debug PAGEWIDTH(80) $2 +:f1:link $1.obj,:f1:x0100,:f1:plm80.lib to $1.mod +:f1:locate $1.mod code(0100H) stacksize(100) map print($1.tra) +:f1:cpm +attach b 1 +e:objcpm $1 + \ No newline at end of file diff --git a/ISIS PLM/CCP.MAC b/ISIS PLM/CCP.MAC new file mode 100644 index 0000000..3c1bed1 --- /dev/null +++ b/ISIS PLM/CCP.MAC @@ -0,0 +1,1206 @@ + title 'console command processor (CCP), ver 2.0' + + .Z80 + aseg + org 100h + maclib MEMCFG.LIB ; define configuration parameters + .phase ccpph ; CCPLOC not needed, we use ccpph instead + +; assembly language version of the CP/M console command processor +; +; version 2.2 February, 1980 + +; Copyright (c) 1976, 1977, 1978, 1979, 1980 +; Digital Research +; Box 579, Pacific Grove, +; California, 93950 + +bdosl equ bdosph ;bdos location +tran equ 100h +tranm equ $ +ccploc equ $ + +; ******************************************************** +; * Base of CCP contains the following code/data * +; * ccp: jmp ccpstart (start with command) * +; * jmp ccpclear (start, clear command) * +; * ccp+6 127 (max command length) * +; * ccp+7 comlen (command length = 00) * +; * ccp+8 ' ... ' (16 blanks) * +; ******************************************************** +; * Normal entry is at ccp, where the command line given * +; * at ccp+8 is executed automatically (normally a null * +; * command with comlen = 00). An initializing program * +; * can be automatically loaded by storing the command * +; * at ccp+8, with the command length at ccp+7. In this * +; * case, the ccp executes the command before prompting * +; * the console for input. Note that the command is exe-* +; * cuted on both warm and cold starts. When the command* +; * line is initialized, a jump to "jmp ccpclear" dis- * +; * ables the automatic command execution. * +; ******************************************************** + + jp ccpstart ;start ccp with possible initial command + jp ccpclear ;clear the command buffer +maxlen: db 127 ;max buffer length +comlen: db 0 ;command length (filled in by dos) + +; (command executed initially if comlen non zero) +combuf: db ' ' ;8 character fill + db ' ' ;8 character fill + db 'COPYRIGHT (C) 1979, DIGITAL RESEARCH '; 38 + ds 128-($-combuf) +; total buffer length is 128 characters + +comaddr: + dw combuf ;address of next to char to scan +staddr: ds 2 ;starting address of current fillfcb request + +diska equ 0004h ;disk address for current disk +bdos equ 0005h ;primary bdos entry point +buff equ 0080h ;default buffer +fcb equ 005ch ;default file control block + +rcharf equ 1 ;read character function +pcharf equ 2 ;print character function +pbuff equ 9 ;print buffer function +rbuff equ 10 ;read buffer function +breakf equ 11 ;break key function +liftf equ 12 ;lift head function (no operation) +initf equ 13 ;initialize bdos function +self equ 14 ;select disk function +openf equ 15 ;open file function +closef equ 16 ;close file function +searf equ 17 ;search for file function +searnf equ 18 ;search for next file function +delf equ 19 ;delete file function +dreadf equ 20 ;disk read function +dwritf equ 21 ;disk write function +makef equ 22 ;file make function +renf equ 23 ;rename file function +logf equ 24 ;return login vector +cself equ 25 ;return currently selected drive number +dmaf equ 26 ;set dma address +userf equ 32 ;set user number + +; special fcb flags +rofile equ 9 ;read only file +sysfile equ 10 ;system file flag + +; special characters +cr equ 13 ;carriage return +lf equ 10 ;line feed +la equ 5fh ;left arrow +eofile equ 1ah ;end of file + +; utility procedures +printchar: + ld e,a + ld c,pcharf + jp bdos + +printbc: ;print character, but save b,c registers + push bc + call printchar + pop bc + ret + +crlf: ld a,cr + call printbc + ld a,lf + jp printbc + +blank: ld a,' ' + jp printbc + +print: ;print string starting at b,c until next 00 entry + push bc + call crlf + pop hl ;now print the string +prin0: ld a,(hl) + or a + ret z ;stop on 00 + inc hl + push hl ;ready for next + call printchar + pop hl ;character printed + jp prin0 ;for another character + +initialize: + ld c,initf + jp bdos + +select: ld e,a + ld c,self + jp bdos + +bdos$inr: + call bdos + ld (dcnt),a + inc a + ret + +open: ;open the file given by d,e + ld c,openf + jp bdos$inr + +openc: ;open comfcb + xor a + ld (comrec),a ;clear next record to read + ld de,comfcb + jp open + +close: ;close the file given by d,e + ld c,closef + jp bdos$inr + +search: ;search for the file given by d,e + ld c,searf + jp bdos$inr + +searchn: ;search for the next occurrence of the file given by d,e + ld c,searnf + jp bdos$inr + +searchcom: ;search for comfcb file + ld de,comfcb + jp search + +delete: ;delete the file given by d,e + ld c,delf + jp bdos + +bdos$cond: + call bdos + or a + ret + +diskread: ;read the next record from the file given by d,e + ld c,dreadf + jp bdos$cond + +diskreadc: ;read the comfcb file + ld de,comfcb + jp diskread + +diskwrite: ;write the next record to the file given by d,e + ld c,dwritf + jp bdos$cond + +make: ;create the file given by d,e + ld c,makef + jp bdos$inr + +renam: ;rename the file given by d,e + ld c,renf + jp bdos + +getuser: ;return current user code in a + ld e,0ffh ;drop through to setuser + +setuser: + ld c,userf + jp bdos ;sets user number + +saveuser: ;save user#/disk# before possible ^c or transient + call getuser ;code to a + add a,a + add a,a + add a,a + add a,a ;rot left + ld hl,cdisk + or (hl) ;4b=user, 4b=disk + ld (diska),a ;stored away in memory for later + ret + +setdiska: + ld a,(cdisk) + ld (diska),a ;user/disk + ret + +translate: ;translate character in register A to upper case + cp 61h + ret c ;return if below lower case a + cp 7bh + ret nc ;return if above lower case z + and 5fh + ret ;translated to upper case + +readcom: ;read the next command into the command buffer + ;check for submit file + ld a,(submit) + or a + jp z,nosub + ;scanning a submit file + ;change drives to open and read the file + ld a,(cdisk) + or a + ld a,0 + call nz,select + ;have to open again in case xsub present + ld de,subfcb + call open + jp z,nosub ;skip if no sub + ld a,(subrc) + dec a ;read last record(s) first + ld (subcr),a ;current record to read + ld de,subfcb + call diskread ;end of file if last record + jp nz,nosub + ;disk read is ok, transfer to combuf + ld de,comlen + ld hl,buff + ld b,128 + call move0 + ;line is transferred, close the file with a + ;deleted record + ld hl,submod + ld (hl),0 ;clear fwflag + inc hl + dec (hl) ;one less record + ld de,subfcb + call close + jp z,nosub + ;close went ok, return to original drive + ld a,(cdisk) + or a + call nz,select + ;print to the 00 + ld hl,combuf + call prin0 + call break$key + jp z,noread + call del$sub + jp ccp ;break key depressed + +nosub: ;no submit file + call del$sub + ;translate to upper case, store zero at end + call saveuser ;user # save in case control c + ld c,rbuff + ld de,maxlen + call bdos + call setdiska ;no control c, so restore diska +noread: ;enter here from submit file + ;set the last character to zero for later scans + ld hl,comlen + ld b,(hl) ;length is in b +readcom0: + inc hl + ld a,b + or a ;end of scan? + jp z,readcom1 + ld a,(hl) ;get character and translate + call translate + ld (hl),a + dec b + jp readcom0 + +readcom1: ;end of scan, h,l address end of command + ld (hl),a ;store a zero + ld hl,combuf + ld (comaddr),hl ;ready to scan to zero + ret + +break$key: ;check for a character ready at the console + ld c,breakf + call bdos + or a + ret z + ld c,rcharf + call bdos ;character cleared + or a + ret + +cselect: ;get the currently selected drive number to reg-A + ld c,cself + jp bdos + +setdmabuff: ;set default buffer dma address + ld de,buff ;(drop through) + +setdma: ;set dma address to d,e + ld c,dmaf + jp bdos + +del$sub: ;delete the submit file, and set submit flag to false + ld hl,submit + ld a,(hl) + or a + ret z ;return if no sub file + ld (hl),0 ;submit flag is set to false + xor a + call select ;on drive a to erase file + ld de,subfcb + call delete + ld a,(cdisk) + jp select ;back to original drive + +serialize: ;check serialization + ld de,serial + ld hl,bdosl + ld b,6 ;check six bytes +ser0: ld a,(de) + cp (hl) + jp nz,badserial + inc de + inc hl + dec b + jp nz,ser0 + ret ;serial number is ok + +comerr: ;error in command string starting at position + ;'staddr' and ending with first delimiter + call crlf ;space to next line + ld hl,(staddr) ;h,l address first to print +comerr0: ;print characters until blank or zero + ld a,(hl) + cp ' ' + jp z,comerr1 ; not blank + or a + jp z,comerr1 ; not zero, so print it + push hl + call printchar + pop hl + inc hl + jp comerr0 ; for another character +comerr1: ;print question mark,and delete sub file + ld a,'?' + call printchar + call crlf + call del$sub + jp ccp ;restart with next command + + ; fcb scan and fill subroutine (entry is at fillfcb below) + ;fill the comfcb, indexed by A (0 or 16) + ;subroutines +delim: ;look for a delimiter + ld a,(de) + or a + ret z ;not the last element + cp ' ' + jp c,comerr ;non graphic + ret z ;treat blank as delimiter + cp '=' + ret z + cp la + ret z ;left arrow + cp '.' + ret z + cp ':' + ret z + cp ';' + ret z + cp '<' + ret z + cp '>' + ret z + ret ;delimiter not found + +deblank: ;deblank the input line + ld a,(de) + or a + ret z ;treat end of line as blank + cp ' ' + ret nz + inc de + jp deblank + +addh: ;add a to h,l + add a,l + ld l,a + ret nc + inc h + ret + +fillfcb0: ;equivalent to fillfcb(0) + ld a,0 + +fillfcb: + ld hl,comfcb + call addh + push hl + push hl ;fcb rescanned at end + xor a + ld (sdisk),a ;clear selected disk (in case A:...) + ld hl,(comaddr) + ex de,hl ;command address in d,e + call deblank ;to first non-blank character + ex de,hl + ld (staddr),hl ;in case of errors + ex de,hl + pop hl ;d,e has command, h,l has fcb address + ;look for preceding file name A: B: ... + ld a,(de) + or a + jp z,setcur0 ;use current disk if empty command + sbc a,'A'-1 + ld b,a ;disk name held in b if : follows + inc de + ld a,(de) + cp ':' + jp z,setdsk ;set disk name if : + +setcur: ;set current disk + dec de ;back to first character of command +setcur0: + ld a,(cdisk) + ld (hl),a + jp setname + +setdsk: ;set disk to name in register b + ld a,b + ld (sdisk),a ;mark as disk selected + ld (hl),b + inc de ;past the : + +setname: ;set the file name field + ld b,8 ;file name length (max) +setnam0: call delim + jp z,padname ;not a delimiter + inc hl + cp '*' + jp nz,setnam1 ;must be ?'s + ld (hl),'?' + jp setnam2 ;to dec count + +setnam1: + ld (hl),a ;store character to fcb + inc de +setnam2: + dec b ;count down length + jp nz,setnam0 + + ;end of name, truncate remainder +trname: call delim + jp z,setty ;set type field if delimiter + inc de + jp trname + +padname: + inc hl + ld (hl),' ' + dec b + jp nz,padname + +setty: ;set the type field + ld b,3 + cp '.' + jp nz,padty ;skip the type field if no . + inc de ;past the ., to the file type field +setty0: ;set the field from the command buffer + call delim + jp z,padty + inc hl + cp '*' + jp nz,setty1 + ld (hl),'?' ;since * specified + jp setty2 + +setty1: ;not a *, so copy to type field + ld (hl),a + inc de +setty2: ;decrement count and go again + dec b + jp nz,setty0 + + ;end of type field, truncate +trtyp: ;truncate type field + call delim + jp z,efill + inc de + jp trtyp + +padty: ;pad the type field with blanks + inc hl + ld (hl),' ' + dec b + jp nz,padty + +efill: ;end of the filename/filetype fill, save command address + ;fill the remaining fields for the fcb + ld b,3 +efill0: inc hl + ld (hl),0 + dec b + jp nz,efill0 + ex de,hl + ld (comaddr),hl ;set new starting point + + ;recover the start address of the fcb and count ?'s + pop hl + ld bc,11 ;b=0, c=8+3 +scnq: inc hl + ld a,(hl) + cp '?' + jp nz,scnq0 + ;? found, count it in b + inc b +scnq0: dec c + jp nz,scnq + ;number of ?'s in c, move to a and return with flags set + ld a,b + or a + ret + +intvec: ;intrinsic function names (all are four characters) + db 'DIR ' + db 'ERA ' + db 'TYPE' + db 'SAVE' + db 'REN ' + db 'USER' +intlen equ ($-intvec)/4 ;intrinsic function length +serial: db 0,0,0,0,0,0 + + +intrinsic: ;look for intrinsic functions (comfcb has been filled) + ld hl,intvec + ld c,0 ;c counts intrinsics as scanned +intrin0: + ld a,c + cp intlen ;done with scan? + ret nc + ;no, more to scan + ld de,comfcb+1 ;beginning of name + ld b,4 ;length of match is in b +intrin1: + ld a,(de) + cp (hl) ;match? + jp nz,intrin2 ;skip if no match + inc de + inc hl + dec b + jp nz,intrin1 ;loop while matching + ;complete match on name, check for blank in fcb + ld a,(de) + cp ' ' + jp nz,intrin3 ;otherwise matched + ld a,c + ret ;with intrinsic number in a + +intrin2: ;mismatch, move to end of intrinsic + inc hl + dec b + jp nz,intrin2 + +intrin3: ;try next intrinsic + inc c ;to next intrinsic number + jp intrin0 ;for another round + +ccpclear: ;clear the command buffer + xor a + ld (comlen),a + ;drop through to start ccp +ccpstart: ;enter here from boot loader + ld sp,stack + push bc ;save initial disk number + ;(high order 4bits=user code, low 4bits=disk#) + ld a,c + rra + rra + rra + rra + and 0fh ;user code + ld e,a + call setuser ;user code selected + ;initialize for this user, get $ flag + call initialize ;0ffh in accum if $ file present + ld (submit),a ;submit flag set if $ file present + pop bc ;recall user code and disk number + ld a,c + and 0fh ;disk number in accumulator + ld (cdisk),a ;clears user code nibble + call select ;proper disk is selected, now check sub files + ;check for initial command + ld a,(comlen) + or a + jp nz,ccp0 ;assume typed already + +ccp: ;enter here on each command or error condition + ld sp,stack + call crlf ;print d> prompt, where d is disk name + call cselect ;get current disk number + add a,'A' + call printchar + ld a,'>' + call printchar + call readcom ;command buffer filled +ccp0: ;(enter here from initialization with command full) + ld de,buff + call setdma ;default dma address at buff + call cselect + ld (cdisk),a ;current disk number saved + call fillfcb0 ;command fcb filled + call nz,comerr ;the name cannot be an ambiguous reference + ld a,(sdisk) + or a + jp nz,userfunc + ;check for an intrinsic function + call intrinsic + ld hl,jmptab ;index is in the accumulator + ld e,a + ld d,0 + add hl,de + add hl,de ;index in d,e + ld a,(hl) + inc hl + ld h,(hl) + ld l,a + jp (hl) + ;pc changes to the proper intrinsic or user function +jmptab: dw direct ;directory search + dw erase ;file erase + dw type ;type file + dw save ;save memory image + dw rename ;file rename + dw user ;user number + dw userfunc ;user-defined function +badserial: + ld hl,76f3h ;'di hlt' instructions. [di or (hlt shl 8)] + ld (ccploc),hl + ld hl,ccploc + jp (hl) + + + ;utility subroutines for intrinsic handlers +readerr: ;print the read error message + ld bc,rdmsg + jp print +rdmsg: db 'READ ERROR',0 + +nofile: ;print no file message + ld bc,nofmsg + jp print +nofmsg: db 'NO FILE',0 + +getnumber: ;read a number from the command line + call fillfcb0 ;should be number + ld a,(sdisk) + or a + jp nz,comerr ;cannot be prefixed + ;convert the byte value in comfcb to binary + ld hl,comfcb+1 + ld bc,11 ;(b=0, c=11) + ;value accumulated in b, c counts name length to zero +conv0: ld a,(hl) + cp ' ' + jp z,conv1 + ;more to scan, convert char to binary and add + inc hl + sub '0' + cp 10 + jp nc,comerr ;valid? + ld d,a ;save value + ld a,b ;mult by 10 + and 11100000b + jp nz,comerr + ld a,b ;recover value + rlca + rlca + rlca ;*8 + add a,b + jp c,comerr + add a,b + jp c,comerr ;*8+*2 = *10 + add a,d + jp c,comerr ;+digit + ld b,a + dec c + jp nz,conv0 ;for another digit + ret +conv1: ;end of digits, check for all blanks + ld a,(hl) + cp ' ' + jp nz,comerr ;blanks? + inc hl + dec c + jp nz,conv1 + ld a,b ;recover value + ret + +movename: ;move 3 characters from h,l to d,e addresses + ld b,3 +move0: ld a,(hl) + ld (de),a + inc hl + inc de + dec b + jp nz,move0 + ret + +addhcf: ;buff + a + c to h,l followed by fetch + ld hl,buff + add a,c + call addh + ld a,(hl) + ret + +setdisk: ;change disks for this command, if requested + xor a + ld (comfcb),a ;clear disk name from fcb + ld a,(sdisk) + or a + ret z ;no action if not specified + dec a + ld hl,cdisk + cp (hl) + ret z ;already selected + jp select + +resetdisk: ;return to original disk after command + ld a,(sdisk) + or a + ret z ;no action if not selected + dec a + ld hl,cdisk + cp (hl) + ret z ;same disk + ld a,(cdisk) + jp select + + ;individual intrinsics follow +direct: ;directory search + call fillfcb0 ;comfcb gets file name + call setdisk ;change disk drives if requested + ld hl,comfcb+1 + ld a,(hl) ;may be empty request + cp ' ' + jp nz,dir1 ;skip fill of ??? if not blank + ;set comfcb to all ??? for current disk + ld b,11 ;length of fill ????????.??? +dir0: ld (hl),'?' + inc hl + dec b + jp nz,dir0 + ;not a blank request, must be in comfcb +dir1: ld e,0 + push de ;E counts directory entries + call searchcom ;first one has been found + call z,nofile ;not found message +dir2: jp z,endir + ;found, but may be system file + ld a,(dcnt) ;get the location of the element + rrca + rrca + rrca + and 1100000b + ld c,a + ;c contains base index into buff for dir entry + ld a,sysfile + call addhcf ;value to A + rla + jp c,dir6 ;skip if system file + ;c holds index into buffer + ;another fcb found, new line? + pop de + ld a,e + inc e + push de + ;e=0,1,2,3,...new line if mod 4 = 0 + and 11b + push af ;and save the test + jp nz,dirhdr0 ;header on current line + call crlf + push bc + call cselect + pop bc + ;current disk in A + add a,'A' + call printbc + ld a,':' + call printbc + jp dirhdr1 ;skip current line hdr +dirhdr0: + call blank ;after last one + ld a,':' + call printbc +dirhdr1: + call blank + ;compute position of name in buffer + ld b,1 ;start with first character of name +dir3: ld a,b + call addhcf ;buff+a+c fetched + and 7fh ;mask flags + ;may delete trailing blanks + cp ' ' + jp nz,dir4 ;check for blank type + pop af + push af ;may be 3rd item + cp 3 + jp nz,dirb ;place blank at end if not + ld a,9 + call addhcf ;first char of type + and 7fh + cp ' ' + jp z,dir5 + ;not a blank in the file type field +dirb: ld a,' ' ;restore trailing filename chr +dir4: + call printbc ;char printed + inc b + ld a,b + cp 12 + jp nc,dir5 + ;check for break between names + cp 9 + jp nz,dir3 ;for another char + ;print a blank between names + call blank + jp dir3 + +dir5: ;end of current entry + pop af ;discard the directory counter (mod 4) +dir6: call break$key ;check for interrupt at keyboard + jp nz,endir ;abort directory search + call searchn + jp dir2 ;for another entry +endir: ;end of directory scan + pop de ;discard directory counter + jp retcom + + +erase: call fillfcb0 ;cannot be all ???'s + cp 11 + jp nz,erasefile + ;erasing all of the disk + ld bc,ermsg + call print + call readcom + ld hl,comlen + dec (hl) + jp nz,ccp ;bad input + inc hl + ld a,(hl) + cp 'Y' + jp nz,ccp + ;ok, erase the entire diskette + inc hl + ld (comaddr),hl ;otherwise error at retcom +erasefile: + call setdisk + ld de,comfcb + call delete + inc a ;255 returned if not found + call z,nofile ;no file message if so + jp retcom + +ermsg: db 'ALL (Y/N)?',0 + +type: call fillfcb0 + jp nz,comerr ;don't allow ?'s in file name + call setdisk + call openc ;open the file + jp z,typerr ;zero flag indicates not found + ;file opened, read 'til eof + call crlf + ld hl,bptr + ld (hl),255 ;read first buffer +type0: ;loop on bptr + ld hl,bptr + ld a,(hl) + cp 128 ;end buffer + jp c,type1 + push hl ;carry if 0,1,...,127 + ;read another buffer full + call diskreadc + pop hl ;recover address of bptr + jp nz,typeof ;hard end of file + xor a + ld (hl),a ;bptr = 0 +type1: ;read character at bptr and print + inc (hl) ;bptr = bptr + 1 + ld hl,buff + call addh ;h,l addresses char + ld a,(hl) + cp eofile + jp z,retcom + call printchar + call break$key + jp nz,retcom ;abort if break + jp type0 ;for another character + +typeof: ;end of file, check for errors + dec a + jp z,retcom + call readerr +typerr: call resetdisk + jp comerr + +save: call getnumber ; value to register a + push af ;save it for later + ;should be followed by a file to save the memory image + call fillfcb0 + jp nz,comerr ;cannot be ambiguous + call setdisk ;may be a disk change + ld de,comfcb + push de + call delete ;existing file removed + pop de + call make ;create a new file on disk + jp z,saverr ;no directory space + xor a + ld (comrec),a ; clear next record field + pop af ;#pages to write is in a, change to #sectors + ld l,a + ld h,0 + add hl,hl + ld de,tran ;h,l is sector count, d,e is load address +save0: ;check for sector count zero + ld a,h + or l + jp z,save1 ;may be completed + dec hl ;sector count = sector count - 1 + push hl ;save it for next time around + ld hl,128 + add hl,de + push hl ;next dma address saved + call setdma ;current dma address set + ld de,comfcb + call diskwrite + pop de + pop hl ;dma address, sector count + jp nz,saverr ;may be disk full case + jp save0 ;for another sector + +save1: ;end of dump, close the file + ld de,comfcb + call close + inc a ; 255 becomes 00 if error + jp nz,retsave ;for another command +saverr: ;must be full or read only disk + ld bc,fullmsg + call print +retsave: ;reset dma buffer + call setdmabuff + jp retcom + +fullmsg: + db 'NO SPACE',0 + +rename: ;rename a file on a specific disk + call fillfcb0 + jp nz,comerr ;must be unambiguous + ld a,(sdisk) + push af ;save for later compare + call setdisk ;disk selected + call searchcom ;is new name already there? + jp nz,renerr3 + ;file doesn't exist, move to second half of fcb + ld hl,comfcb + ld de,comfcb+16 + ld b,16 + call move0 + ;check for = or left arrow + ld hl,(comaddr) + ex de,hl + call deblank + cp '=' + jp z,ren1 ;ok if = + cp la + jp nz,renerr2 +ren1: ex de,hl + inc hl + ld (comaddr),hl ;past delimiter + ;proper delimiter found + call fillfcb0 + jp nz,renerr2 + ;check for drive conflict + pop af + ld b,a ;previous drive number + ld hl,sdisk + ld a,(hl) + or a + jp z,ren2 + ;drive name was specified. same one? + cp b + ld (hl),b + jp nz,renerr2 +ren2: ld (hl),b ;store the name in case drives switched + xor a + ld (comfcb),a + call searchcom ;is old file there? + jp z,renerr1 + + ;everything is ok, rename the file + ld de,comfcb + call renam + jp retcom + +renerr1: ; no file on disk + call nofile + jp retcom +renerr2: ; ambigous reference/name conflict + call resetdisk + jp comerr +renerr3: ; file already exists + ld bc,renmsg + call print + jp retcom +renmsg: db 'FILE EXISTS',0 + +user: ;set user number + call getnumber ; leaves the value in the accumulator + cp 16 + jp nc,comerr ; must be between 0 and 15 + ld e,a ;save for setuser call + ld a,(comfcb+1) + cp ' ' + jp z,comerr + call setuser ;new user number set + jp endcom + +userfunc: + call serialize ;check serialization + ;load user function and set up for execution + ld a,(comfcb+1) + cp ' ' + jp nz,user0 + ;no file name, but may be disk switch + ld a,(sdisk) + or a + jp z,endcom ;no disk name if 0 + dec a + ld (cdisk),a + call setdiska ;set user/disk + call select + jp endcom +user0: ;file name is present + ld de,comfcb+9 + ld a,(de) + cp ' ' + jp nz,comerr ;type ' ' + push de + call setdisk + pop de + ld hl,comtype ;.com + call movename ;file type is set to .com + call openc + jp z,userer + ;file opened properly, read it into memory + ld hl,tran ;transient program base +load0: push hl ;save dma address + ex de,hl + call setdma + ld de,comfcb + call diskread + jp nz,load1 + ;sector loaded, set new dma address and compare + pop hl + ld de,128 + add hl,de + ld de,tranm ;has the load overflowed? + ld a,l + sub e + ld a,h + sbc a,d + jp nc,loaderr + jp load0 ;for another sector + +load1: pop hl + dec a + jp nz,loaderr ;end file is 1 + call resetdisk ;back to original disk + call fillfcb0 + ld hl,sdisk + push hl + ld a,(hl) + ld (comfcb),a ;drive number set + ld a,16 + call fillfcb ;move entire fcb to memory + pop hl + ld a,(hl) + ld (comfcb+16),a + xor a + ld (comrec),a ;record number set to zero + ld de,fcb + ld hl,comfcb + ld b,33 + call move0 + ;move command line to buff + ld hl,combuf +bmove0: ld a,(hl) + or a + jp z,bmove1 + cp ' ' + jp z,bmove1 + inc hl + jp bmove0 ;for another scan + ;first blank position found +bmove1: ld b,0 + ld de,buff+1 + ;ready for the move +bmove2: ld a,(hl) + ld (de),a + or a + jp z,bmove3 + ;more to move + inc b + inc hl + inc de + jp bmove2 +bmove3: ;b has character count + ld a,b + ld (buff),a + call crlf + ;now go to the loaded program + call setdmabuff ;default dma + call saveuser ;user code saved + ;low memory diska contains user code + call tran ;gone to the loaded program + ld sp,stack ;may come back here + call setdiska + call select + jp ccp + +userer: ;arrive here on command error + call resetdisk + jp comerr + +loaderr: ;cannot load the program + ld bc,loadmsg + call print + jp retcom +loadmsg: + db 'BAD LOAD',0 +comtype: + db 'COM' ;for com files + + +retcom: ;reset disk before end of command check + call resetdisk + +endcom: ;end of intrinsic command + call fillfcb0 ;to check for garbage at end of line + ld a,(comfcb+1) + sub ' ' + ld hl,sdisk + or (hl) + ;0 in accumulator if no disk selected, and blank fcb + jp nz,comerr + jp ccp + +; data areas + ds 16 ;8 level stack +stack: + +; 'submit' file control block +submit: db 0 ;00 if no submit file, ff if submitting +subfcb: db 0,'$$$ ' ;file name is $$$ + db 'SUB',0,0 ;file type is sub +submod: db 0 ;module number +subrc: ds 1 ;record count filed + ds 16 ;disk map +subcr: ds 1 ;current record to read + +; command file control block +comfcb: ds 32 ;fields filled in later +comrec: ds 1 ;current record to read/write +dcnt: ds 1 ;disk directory count (used for error codes) +cdisk: ds 1 ;current disk +sdisk: ds 1 ;selected disk for current operation + ;none=0, a=1, b=2 ... +bptr: ds 1 ;buffer pointer + + end ccploc + \ No newline at end of file diff --git a/ISIS PLM/CFGCCP.LIB b/ISIS PLM/CFGCCP.LIB new file mode 100644 index 0000000..3a3875b --- /dev/null +++ b/ISIS PLM/CFGCCP.LIB @@ -0,0 +1,21 @@ +msize equ 64 ; adjust per installed system memory + +; configuration parameters for BIOS +bioslen equ 0d00h ; adjust as bios changes are made (if necessary) +nhdisks equ 2 ; total number of hard disks (set to 0 + ; if no hard disks desired) +needZ80 equ 0 ; 0 = 8080 is ok, 1 = Z80 is needed +patchOS equ 1 ; 0 = do not patch CCP and BODS + ; 1 = patch orignal CCP and original BDOS + +; common definitions and derived values - no change should be necessary below +ccplen equ 0800h ; cp/m constant +bdoslen equ 0e00h ; cp/m constant + +; cp/m image size (rounded up to next 1k boundary) +cpmlen equ (ccplen + bdoslen + bioslen + 03ffh) / 0400h + +ccpph equ (msize - cpmlen) * 1024 ; ccp start address +bdosph equ ccpph + ccplen ; bdos start address +biosph equ ccpph + ccplen + bdoslen ; bios start address + \ No newline at end of file diff --git a/ISIS PLM/COMMON.LIT b/ISIS PLM/COMMON.LIT new file mode 100644 index 0000000..9060ef7 --- /dev/null +++ b/ISIS PLM/COMMON.LIT @@ -0,0 +1,30 @@ +$nolist +/* + Common Literals +*/ + + declare true literally '0FFFFH'; + declare false literally '0'; + declare forever literally 'while true'; + declare boolean literally 'byte'; + + declare enter$region literally + 'disable'; + + exitr: + procedure external; + end exitr; + + declare exit$region literally + 'call exitr'; + + declare restarts literally + '0C7C7H,0C7C7H,0C7C7H,0C7C7H, + 0C7C7H,0C7C7H,0C7C7H,0C7C7H, + 0C7C7H,0C7C7H,0C7C7H,0C7C7H, + 0C7C7H,0C7C7H,0C7C7H,0C7C7H, + 0C7C7H,0C7C7H,0C7C7H,0C7C7H, + 0C7C7H,0C7C7H,0C7C7H'; + +$list + \ No newline at end of file diff --git a/ISIS PLM/CONV86 b/ISIS PLM/CONV86 new file mode 100644 index 0000000..5e29fa1 Binary files /dev/null and b/ISIS PLM/CONV86 differ diff --git a/ISIS PLM/COPY.COM b/ISIS PLM/COPY.COM new file mode 100644 index 0000000..99239f0 Binary files /dev/null and b/ISIS PLM/COPY.COM differ diff --git a/ISIS PLM/CPM b/ISIS PLM/CPM new file mode 100644 index 0000000..97d93d6 Binary files /dev/null and b/ISIS PLM/CPM differ diff --git a/ISIS PLM/CPU.COM b/ISIS PLM/CPU.COM new file mode 100644 index 0000000..a2dcd3c Binary files /dev/null and b/ISIS PLM/CPU.COM differ diff --git a/ISIS PLM/CPU.MAC b/ISIS PLM/CPU.MAC new file mode 100644 index 0000000..d9bd096 --- /dev/null +++ b/ISIS PLM/CPU.MAC @@ -0,0 +1,67 @@ + .Z80 + aseg + +simhport equ 0feh +setz80cpu equ 19 +set8080cpu equ 20 +printstringcmd equ 09h +bdos equ 0005h +cr equ 13 +lf equ 10 +eof equ 1ah +cmdline equ 80h + + org 100h + + jp start + +usage: db 'Usage: CPU (Z[80] | 8[080]) [v]',cr,lf + db ' sets CPU to desired type and optionally prints a confirmation.' + db cr,lf,'$',eof ; stop accidental TYPE command here +mdz80: db 'Z80 detected.', cr,lf,'$' +md8080: db '8080 detected.', cr,lf,'$' +mz80: db 'CPU set to Z80.', cr,lf,'$' +m8080: db 'CPU set to 8080.', cr,lf,'$' + +start: ld a,(cmdline) ; get number of characters on command line + ld b,a ; store also in + or a ; no parameters? + jp z,showus ; yes, show usage + dec a ; or just one character? + jp z,showus ; yes, show usage + ld a,(cmdline+2) ; get first character (cmdline+1) is ' ' + cp 'Z' ; check for Z80 + jp z,sz80 ; Z80 is desired + cp '8' ; check for 8080 + jp nz,showus ; neither, show usage + ld a,set8080cpu ; 8080 is desired, prepare command + ld de,m8080 ; and optional confirmation message for 8080 + jp doset ; perform CPU set operation + +sz80: ld a,setz80cpu ; Z80 is desired, prepare command + ld de,mz80 ; and optional confirmation message for Z80 +doset: out (simhport),a ; set CPU + ld hl,cmdline+1 ; start of command line +find: ld a,(hl) ; get character + cp 'V' ; is it 'V' (for verbose)? + jp z,print ; yes, print message + inc hl ; point to next character + dec b ; decrement counter of characters in command line + ret z ; done + jp find + +showus: xor a ; determine which CPU currently in use + dec a + ld de,md8080 ; prepare for 8080 + jp pe,detmsg ; all eight bits set means parity even for 8080 + ld de,mdz80 ; not so on Z80 +detmsg: call print ; print CPU type + ld de,usage ; show usage +print: ld c,printstringcmd ; print command for CP/M + jp bdos ; execute it and return to CP/M + +last equ $ + ds 200h - last ; make sure to fill with zeros via M80 /M option + + end + \ No newline at end of file diff --git a/ISIS PLM/CREF80.COM b/ISIS PLM/CREF80.COM new file mode 100644 index 0000000..e136ec1 Binary files /dev/null and b/ISIS PLM/CREF80.COM differ diff --git a/ISIS PLM/DDT.COM b/ISIS PLM/DDT.COM new file mode 100644 index 0000000..2dee690 Binary files /dev/null and b/ISIS PLM/DDT.COM differ diff --git a/ISIS PLM/DDTZ.COM b/ISIS PLM/DDTZ.COM new file mode 100644 index 0000000..2eafb5d Binary files /dev/null and b/ISIS PLM/DDTZ.COM differ diff --git a/ISIS PLM/DIF.COM b/ISIS PLM/DIF.COM new file mode 100644 index 0000000..71cb48f Binary files /dev/null and b/ISIS PLM/DIF.COM differ diff --git a/ISIS PLM/DO.COM b/ISIS PLM/DO.COM new file mode 100644 index 0000000..8d2b6f0 Binary files /dev/null and b/ISIS PLM/DO.COM differ diff --git a/ISIS PLM/DPGOS.LIT b/ISIS PLM/DPGOS.LIT new file mode 100644 index 0000000..dd8dfc9 --- /dev/null +++ b/ISIS PLM/DPGOS.LIT @@ -0,0 +1,25 @@ +$nolist + + declare + ostod literally '0000h', + osrlr literally '0005h', + osdlr literally '0007h', + osdrl literally '0009h', + osplr literally '000bh', + osslr literally '000dh', + osqlr literally '000fh', + osthrdrt literally '0011h', + osnmbcns literally '0013h', + oscnsatt literally '0014h', + oscnsque literally '0034h', + osnmbflags literally '0054h', + ossysfla literally '0055h', + osnmbsegs literally '0095h', + osmsegtbl literally '0096h', + ospdtbl literally '00b6h', + osnmblst literally '0256h', + oslstatt literally '0257h', + oslstque literally '0277h'; + +$list + \ No newline at end of file diff --git a/ISIS PLM/DSKBOOT.MAC b/ISIS PLM/DSKBOOT.MAC new file mode 100644 index 0000000..02ccbae --- /dev/null +++ b/ISIS PLM/DSKBOOT.MAC @@ -0,0 +1,208 @@ +; modified cold boot routine to be put into ROM + +; The sectors of a track are read in the following order: +; first even sectors, then odd sectors in ascending order +; 0,2,4,6,8,10,12,14,16,18,20,22,24,26,28,30, +; 1,3,5,7,9,11,13,15,17,19,21,23,25,27,29,31 +; T0[S8 - S31], T1, T2, T3, T4, T5[S0 - S23] +; 28 + 32+ 32+ 32+ 32+ 28 = 184 sectors = 23552 byte (5C00) +; loads sectors to 0 .. 5bff and jumps to 0 when done + + .Z80 + aseg + +cold equ 05c00h ; starting address of loader after relocation +rom equ 0ff00h + +; Address Mode Function +; ------- ---- -------- +; selout Out Selects and enables controller and drive +; statin In Indicates status of drive and controller +; dskcon Out Controls disk function +; secpos In Indicates current sector position of disk +; dskwrit Out Write data +; dskread In Read data + +selout equ 8 ; port to select and enable controller and drive (OUT) +; +---+---+---+---+---+---+---+---+ +; | C | X | X | X | Device | +; +---+---+---+---+---+---+---+---+ +; +; C = If this bit is 1, the disk controller selected by 'device' is +; cleared. If the bit is zero, 'device' is selected as the +; device being controlled by subsequent I/O operations. +; X = not used +; Device = value zero thru 15, selects drive to be controlled. + +statin equ 8 ; port indicating status of drive and controller (IN) +; +---+---+---+---+---+---+---+---+ +; | R | Z | I | X | X | H | M | W | +; +---+---+---+---+---+---+---+---+ +; +; W - When 0, write circuit ready to write another byte. +; M - When 0, head movement is allowed +; H - When 0, indicates head is loaded for read/write +; X - not used (will be 0) +; I - When 0, indicates interrupts enabled (not used this simulator) +; Z - When 0, indicates head is on track 0 +; R - When 0, indicates that read circuit has new byte to read + +dskcon equ 9 ; port to control disc function (OUT) +; +---+---+---+---+---+---+---+---+ +; | W | C | D | E | U | H | O | I | +; +---+---+---+---+---+---+---+---+ +; +; I - When 1, steps head IN one track +; O - When 1, steps head OUT one track +; H - When 1, loads head to drive surface +; U - When 1, unloads head +; E - Enables interrupts (ignored by this simulator) +; D - Disables interrupts (ignored by this simulator) +; C - When 1 lowers head current (ignored by this simulator) +; W - When 1, starts Write Enable sequence: +; W bit on device 'statin' (see above) will go 1 and data will be read from +; port 'dskread' until 137 bytes have been read by the controller from +; that port. The W bit will go off then, and the sector data will be written +; to disk. Before you do this, you must have stepped the track to the desired +; number, and waited until the right sector number is presented on +; device 'secpos', then set this bit. + +secpos equ 9 ; port to indicate current sector position of disk (IN) +; As the sectors pass by the read head, they are counted and the +; number of the current one is available in this register. +; +; +---+---+---+---+---+---+---+---+ +; | X | X | Sector Number | T | +; +---+---+---+---+---+---+---+---+ +; +; X = Not used +; Sector number = binary of the sector number currently under the head, 0-31. +; T = Sector True, is a 1 when the sector is positioned to read or write. + +dskread equ 10 ; port to read data (IN) + +spt equ 32 ; sectors per track +secsiz equ 128 ; physical sector size +bootorg equ 0000 ; jump to this address after loading +simhport equ 0feh ; SIMH port +simhreset equ 14 ; SIMH reset command +stoptimer equ 22 ; SIMH stop timer interrupt +setbankselect equ 12 ; SIMH command to set memory bank +hasbankedmemory equ 18 ; SIMH command to check for banked memory +unitnooffset1 equ (selds0+1-cold)+(dest-rom) +unitnooffset2 equ (gotoit+1-cold)+(dest-rom) + +seldsk equ selds0+1 ; address to select disk +resdsk equ gotoit+1 ; address to reset disk + + org 100h + .phase rom + di + ld b,128 ; sending SIMHRESET 128 times guarantees reset + ld a,simhreset ; reset command +reset: out (simhport),a ; reset SIMH interface + dec b + jp nz,reset ; again + ld a,stoptimer ; stop timer interrupts command + out (simhport),a ; send it + ld a,hasbankedmemory ; check for banked memory support + out (simhport),a ; send command + in a,(simhport) ; receive result + or a ; check for <> 0 + jp z,move1 ; no banked memory support detected + ld a,setbankselect ; next command is select bank + out (simhport),a ; send it + xor a ; bank for boot is 0 + out (simhport),a ; reset bank to 0 +move1: ld hl,cold + ld de,dest + ld c,altbuf - cold +move2: ld a,(de) + ld (hl),a + inc de + inc hl + dec c + jp nz,move2 + jp cold +dest equ $ + .dephase + + .phase cold + ld sp,stack +selds0: ld a,0 ; the address of <0> is "unitNoOffset1" + out (selout),a ; select it + ld a,4 ; load head command + out (dskcon),a ; load head to drive surface + jp cktk0 +back1: in a,(statin) + and 2 ; head movement mask + jp nz,back1 ; loop until head movement is allowed + ld a,2 ; step out command + out (dskcon),a ; step head out one track +cktk0: in a,(statin) + and 40h ; head on track zero mask + jp nz,back1 ; loop until head is on track zero + ld de,bootorg ; destination load address + ld b,8 ; first sector to read on track zero +nextsc: push bc ; save current sector to read, is undefined + push de ; save current destination load address + ld de,8086h ; := 80h, := 86h + ld hl,altbuf ; address of sector buffer +findsc: in a,(secpos) + rra + jp c,findsc ; loop until sector is positioned to read or write + and (spt-1) ; now contains the sector under the head + cp b ; compare with desired sector + jp nz,findsc ; loop until done +readsc: in a,(statin) ; get disk status + or a ; set sign of byte + jp m,readsc ; loop until disk has new byte to read + in a,(dskread) ; read byte of sector + ld (hl),a ; store into buffer + inc hl ; point to next position in buffer + dec e ; decrement byte counter + jp nz,readsc ; repeat if byte counter not yet zero +donesc: pop de ; restore current destination load address, is destination + ld hl,altbuf+3 ; ignore first three byte of buffer, is source + ld b,secsiz ; 128 bytes in a sector +ldir: ld a,(hl) ; get byte from source + ld (de),a ; put byte to destination + inc hl ; point to next source address + inc de ; point to next destination address + dec b ; decrement number of bytes to move + jp nz,ldir ; not zero, move again + pop bc ; is current sector, is undefined + ld hl,cold ; when reaches this address we are done + ld a,d + cp h + jp nz,decide + ld a,e + cp l +decide: jp nc,gotoit ; jump if everything loaded + inc b ; compute next sector number + inc b + ld a,b + cp spt ; compare new sector number with sectors per track + jp c,nextsc ; continue if less + ld b,1 ; otherwise prepare for odd numbered sectors + jp z,nextsc ; if old sector number was equal to sectors per track +stepin: in a,(statin) + and 2 ; head movement mask + jp nz,stepin ; loop until head movement is allowed + ld a,1 ; step in one track command + out (dskcon),a ; step in one track + ld b,0 ; start with even sectors + jp nextsc +gotoit: ld a,80h ; the address of <80H> is "unitNoOffset2" + out (selout),a + ei + jp bootorg + +altbuf: ds 137 + ds 16 + +stack: + .dephase + + end + \ No newline at end of file diff --git a/ISIS PLM/DUMP.COM b/ISIS PLM/DUMP.COM new file mode 100644 index 0000000..c02b6bb Binary files /dev/null and b/ISIS PLM/DUMP.COM differ diff --git a/ISIS PLM/ED.COM b/ISIS PLM/ED.COM new file mode 100644 index 0000000..a0f0f54 Binary files /dev/null and b/ISIS PLM/ED.COM differ diff --git a/ISIS PLM/FCB.LIT b/ISIS PLM/FCB.LIT new file mode 100644 index 0000000..d028294 --- /dev/null +++ b/ISIS PLM/FCB.LIT @@ -0,0 +1,20 @@ +$nolist +/* + FCB Literals +*/ + + declare fcb$descriptor literally + 'structure ( + et byte, + fn (8) byte, + ft (3) byte, + ex byte, + nu address, + rc byte, + dm (16) byte, + nr byte, + r0r1 address, + r2 byte )'; + +$list + \ No newline at end of file diff --git a/ISIS PLM/FIXEOF.COM b/ISIS PLM/FIXEOF.COM new file mode 100644 index 0000000..3526d51 Binary files /dev/null and b/ISIS PLM/FIXEOF.COM differ diff --git a/ISIS PLM/FIXEOF.MAC b/ISIS PLM/FIXEOF.MAC new file mode 100644 index 0000000..ca8ccfc --- /dev/null +++ b/ISIS PLM/FIXEOF.MAC @@ -0,0 +1,120 @@ +; +; This program fixes the EOF problem of the ISIS PL/M-80 compiler +; version 3.1 under CP/M. The compiler ignors EOF in text files +; and then throws error messages about illegal characters after the +; final END statement. +; The problem is avoided by filling the last record of a text file +; with CR characters, including the EOF. Don't use on origial sources, +; only on temporary copies for the building process. +; +; September 2006, Udo Munk +; +; BDOS function +; +WARM EQU 0 ;warm start +BDOS EQU 5 ;BDOS call +PRINT EQU 9 ;print string to console +FOPEN EQU 15 ;file open +FCLOSE EQU 16 ;file close +SETDMA EQU 26 ;set DMA buffer +READR EQU 33 ;read record +WRITER EQU 34 ;write record +SEEK EQU 35 ;find last record of file +; +; default FCB and I/O buffer +; +FCB EQU 5CH +BUF EQU 80H +; +; character constants +; +CR EQU 0DH ;carriage return +LF EQU 0AH ;linefeed +EOF EQU 1AH ;EOF (ctl-z) +; + .Z80 + ASEG + ORG 0100H +; +; set stack +; + LD SP,STACK +; +; try to open file +; + LD C,FOPEN + LD DE,FCB + CALL BDOS + CP 0FFH + JP NZ,OPENED + LD C,PRINT + LD DE,OERR + CALL BDOS + JP WARM +; +; file open, seek to end of file +; +OPENED: + LD C,SEEK + LD DE,FCB + CALL BDOS +; +; decrement record by one and read last record +; + LD A,(FCB+33) + DEC A + LD (FCB+33),A + CP 0FFH + JP NZ,READ + LD A,(FCB+34) + DEC A + LD (FCB+34),A +READ: + LD C,SETDMA + LD DE,BUF + CALL BDOS + LD C,READR + LD DE,FCB + CALL BDOS +; +; find EOF in the last record +; + LD A,EOF + LD HL,BUF + LD BC,128 + CPIR +; +; fill rest of the record including EOF with CR's +; + DEC HL + INC BC +FILL: + LD A,CR + LD (HL),A + INC HL + DEC BC + LD A,B + OR C + JP NZ,FILL +; +; write record and close file +; + LD C,WRITER + LD DE,FCB + CALL BDOS + LD C,FCLOSE + LD DE,FCB + CALL BDOS +; +; done +; + JP WARM +; +; data +; +OERR: + DEFM CR,LF,'can''t open file',CR,LF,'$' + DEFS 20 ;stack +STACK: +; + END ;of program diff --git a/ISIS PLM/FLAG.LIT b/ISIS PLM/FLAG.LIT new file mode 100644 index 0000000..3a48603 --- /dev/null +++ b/ISIS PLM/FLAG.LIT @@ -0,0 +1,9 @@ +$nolist +/* + Flag Literals +*/ + + declare nmbflags literally '16'; + +$list + \ No newline at end of file diff --git a/ISIS PLM/FORMAT.COM b/ISIS PLM/FORMAT.COM new file mode 100644 index 0000000..c02f74d Binary files /dev/null and b/ISIS PLM/FORMAT.COM differ diff --git a/ISIS PLM/GENHEX.COM b/ISIS PLM/GENHEX.COM new file mode 100644 index 0000000..8314d35 Binary files /dev/null and b/ISIS PLM/GENHEX.COM differ diff --git a/ISIS PLM/GENMOD.COM b/ISIS PLM/GENMOD.COM new file mode 100644 index 0000000..017afd6 Binary files /dev/null and b/ISIS PLM/GENMOD.COM differ diff --git a/ISIS PLM/GO.COM b/ISIS PLM/GO.COM new file mode 100644 index 0000000..e69de29 diff --git a/ISIS PLM/HALT.COM b/ISIS PLM/HALT.COM new file mode 100644 index 0000000..5139f32 Binary files /dev/null and b/ISIS PLM/HALT.COM differ diff --git a/ISIS PLM/HDIR.COM b/ISIS PLM/HDIR.COM new file mode 100644 index 0000000..b630224 Binary files /dev/null and b/ISIS PLM/HDIR.COM differ diff --git a/ISIS PLM/HDSKBOOT.MAC b/ISIS PLM/HDSKBOOT.MAC new file mode 100644 index 0000000..5a65d19 --- /dev/null +++ b/ISIS PLM/HDSKBOOT.MAC @@ -0,0 +1 @@ + .Z80 aseg ; The sectors of a track are read in the following order: ; first even sectors, then odd sectors in ascending order ; 0,2,4,6,8,10,12,14,16,18,20,22,24,26,28,30, ; 1,3,5,7,9,11,13,15,17,19,21,23,25,27,29,31 ; T0[S8 - S31], T1, T2, T3, T4, T5[S0 - S23] ; 28 + 32+ 32+ 32+ 32+ 28 = 184 sectors = 23552 byte (5C00) ; loads sectors to 0 .. 5bff and jumps to 0 when done true equ 0ffffh false equ not true hdskReset equ 1 ; command to reset controller hdskRead equ 2 ; read command hdskport equ 0fdh ; control port for simulated hard disk simhreset equ 14 ; SIMH reset command stoptimer equ 22 ; SIMH stop timer interrupt setbankselect equ 12 ; SIMH command to set memory bank hasbankedmemory equ 18 ; SIMH command to check for banked memory simhport equ 0feh ; SIMH port bootorg equ 0000 ; jump to this address after loading bootstart equ 5c00h ; boot code resides here bootSize equ bootend - bootstart rom equ 0ff00h ; address of Altair bootstrap loader in ROM sectorsPerTrack equ 32 sectorLength equ 128 firstSector equ 8 ; first sector to load firstTrack equ 0 ; from this track firstDiskAddr equ 256*firstTrack+firstSector lastSector equ 23 ; last sector to load lastTrack equ 5 ; from this track ; items to be checked resp. configured bootdr1 equ rom+0037h ; taken from dskboot (offset unitnooffset1) ndisks equ 8 ; number of Altair (floppy) disks includeTestCode equ false sectpos macro sector,var ;; compute index of sector in assign to var if (sector and 1) eq 0 ;; sector is even var equ (sector shr 1) ;; index is sector/2 else ;; sector is odd var equ (sectorsPerTrack shr 1)+(sector shr 1) ;; index has offset endif endm if lastTrack gt (firstTrack+1) ; get number of complete tracks fullTrk equ lastTrack-firstTrack-1 ; are there any? else fullTrk equ 0 ; no endif sectpos firstSector,fpos sectpos lastSector,lpos sectors equ sectorsPerTrack-fpos+sectorsPerTrack*fullTrk+lpos+1 org 100h if includeTestCode ; for testing purposes ld hl,bootstart ; this is where boot code should reside ld de,dest ; here is boot code currently ld c,bootSize ; length of boot code move: ld a,(de) ; get byte from source ld (hl),a ; put byte to destination inc de ; next source address inc hl ; next destination address dec c ; decrement loop counter jp nz,move ; continue if not done jp bootstart ; otherwise jump to boot code dest equ $ endif .phase bootstart di ld b,128 ; sending SIMHRESET 128 times guarantees reset ld a,simhreset ; reset command reset1: out (simhport),a ; reset SIMH interface dec b jp nz,reset1 ; again ld a,stoptimer ; stop timer interrupts command out (simhport),a ; send it ld a,hasbankedmemory ; check for banked memory support out (simhport),a ; send command in a,(simhport) ; receive result or a ; check for <> 0 jp z,reset2 ; no banked memory support detected ld a,setbankselect ; next command is select bank out (simhport),a ; send it xor a ; bank for boot is 0 out (simhport),a ; reset bank to 0 reset2: ld b,32 ; reset hard disk controller ld a,hdskReset ; by issuing the reset command 32 times reset3: out (hdskPort),a dec b jp nz,reset3 ; post condition is := 0 ld de,firstDiskAddr ; := 0 (Track), := 8 (Sector) ld hl,bootorg ; DMA address ld c,sectors ; is loop counter again: ld a,hdskRead out (hdskport),a ; send read command to hard disk port if includeTestCode ; for testing purposes ld a,0 ; always use disk 0 else ld a,(bootdr1) ; in real life take disk number from boot ROM sub ndisks ; correct for Altair disks endif out (hdskport),a ; send drive to boot from to hard disk port ld a,e out (hdskport),a ; send sector ld a,d out (hdskport),a ; send lower byte of track xor a out (hdskport),a ; send higher byte of track which is always 0 ld a,l out (hdskport),a ; send lower byte of DMA address ld a,h out (hdskport),a ; send upper byte of DMA address in a,(hdskport) ; perform operation and get result or a jp z,cont1 ; continue if no error halt ; halt otherwise cont1: ld a,c ; save in ld c,sectorLength ; is now 128 since always zero add hl,bc ; get next DMA address ld c,a ; restore from dec c ; decrement loop counter jp nz,cont2 ei jp bootorg ; done, jump to loaded code cont2: inc e ; Sector := Sector + 2 inc e ld a,e cp sectorsPerTrack ; is new Sector equal to 32 jp z,switch ; yes, need to go to odd sectors cp sectorsPerTrack+1 ; is new Sector equal to 33 jp nz,again ; no, proceed with read ld e,0 ; Sector := 0 inc d ; Track := Track + 1 jp again ; proceed with read switch: ld e,1 ; Sector := 1 jp again ; proceed with read bootend equ $ .dephase end  \ No newline at end of file diff --git a/ISIS PLM/HEXOBJ b/ISIS PLM/HEXOBJ new file mode 100644 index 0000000..c7ce009 Binary files /dev/null and b/ISIS PLM/HEXOBJ differ diff --git a/ISIS PLM/IS14.COM b/ISIS PLM/IS14.COM new file mode 100644 index 0000000..bc78d4a Binary files /dev/null and b/ISIS PLM/IS14.COM differ diff --git a/ISIS PLM/ISIS.COM b/ISIS PLM/ISIS.COM new file mode 100644 index 0000000..bc78d4a Binary files /dev/null and b/ISIS PLM/ISIS.COM differ diff --git a/ISIS PLM/ISX.COM b/ISIS PLM/ISX.COM new file mode 100644 index 0000000..bc78d4a Binary files /dev/null and b/ISIS PLM/ISX.COM differ diff --git a/ISIS PLM/IXREF b/ISIS PLM/IXREF new file mode 100644 index 0000000..9d8c249 Binary files /dev/null and b/ISIS PLM/IXREF differ diff --git a/ISIS PLM/L80.COM b/ISIS PLM/L80.COM new file mode 100644 index 0000000..264e3b5 Binary files /dev/null and b/ISIS PLM/L80.COM differ diff --git a/ISIS PLM/LIB b/ISIS PLM/LIB new file mode 100644 index 0000000..02c7eb4 Binary files /dev/null and b/ISIS PLM/LIB differ diff --git a/ISIS PLM/LIB80.COM b/ISIS PLM/LIB80.COM new file mode 100644 index 0000000..81b1d22 Binary files /dev/null and b/ISIS PLM/LIB80.COM differ diff --git a/ISIS PLM/LINK b/ISIS PLM/LINK new file mode 100644 index 0000000..5d75497 Binary files /dev/null and b/ISIS PLM/LINK differ diff --git a/ISIS PLM/LINK.OVL b/ISIS PLM/LINK.OVL new file mode 100644 index 0000000..34b6445 Binary files /dev/null and b/ISIS PLM/LINK.OVL differ diff --git a/ISIS PLM/LOAD.COM b/ISIS PLM/LOAD.COM new file mode 100644 index 0000000..b9601e0 Binary files /dev/null and b/ISIS PLM/LOAD.COM differ diff --git a/ISIS PLM/LOCATE b/ISIS PLM/LOCATE new file mode 100644 index 0000000..76f3e90 Binary files /dev/null and b/ISIS PLM/LOCATE differ diff --git a/ISIS PLM/LS.COM b/ISIS PLM/LS.COM new file mode 100644 index 0000000..413bcec Binary files /dev/null and b/ISIS PLM/LS.COM differ diff --git a/ISIS PLM/LU.COM b/ISIS PLM/LU.COM new file mode 100644 index 0000000..80be217 Binary files /dev/null and b/ISIS PLM/LU.COM differ diff --git a/ISIS PLM/M80.COM b/ISIS PLM/M80.COM new file mode 100644 index 0000000..d546065 Binary files /dev/null and b/ISIS PLM/M80.COM differ diff --git a/ISIS PLM/MAC.COM b/ISIS PLM/MAC.COM new file mode 100644 index 0000000..f49e835 Binary files /dev/null and b/ISIS PLM/MAC.COM differ diff --git a/ISIS PLM/MAKEPIP.SUB b/ISIS PLM/MAKEPIP.SUB new file mode 100644 index 0000000..94256f5 --- /dev/null +++ b/ISIS PLM/MAKEPIP.SUB @@ -0,0 +1,14 @@ +; must use "submit makepip" to execute, "do makepip" will fail +pip d:trint.src=a:os5trint.src +pip d:=a:pip.plm +fixeof d:pip.plm +isx +:f1:plm80 :f3:pip.plm +:f2:asm80 :f3:trint.src +:f1:cpm +isx +:f1:link :f3:pip.obj,:f3:trint.obj,:f1:x0100,:f1:plm80.lib to :f3:pip.mod +:f1:locate :f3:pip.mod code(0100H) stacksize(100) +:f1:cpm +objcpm d:pip + \ No newline at end of file diff --git a/ISIS PLM/MC.SUB b/ISIS PLM/MC.SUB new file mode 100644 index 0000000..6c3b12e --- /dev/null +++ b/ISIS PLM/MC.SUB @@ -0,0 +1,5 @@ +; compile an assembler program +A:M80 =$1/M +A:L80 $1,$1/N/E +ERA $1.REL + \ No newline at end of file diff --git a/ISIS PLM/MCC.SUB b/ISIS PLM/MCC.SUB new file mode 100644 index 0000000..8cf9073 --- /dev/null +++ b/ISIS PLM/MCC.SUB @@ -0,0 +1,6 @@ +; read and compile an assembler program +A:R $1.MAC +A:M80 =$1/M +A:L80 $1,$1/N/E +ERA $1.REL + \ No newline at end of file diff --git a/ISIS PLM/MCCL.SUB b/ISIS PLM/MCCL.SUB new file mode 100644 index 0000000..aae2261 --- /dev/null +++ b/ISIS PLM/MCCL.SUB @@ -0,0 +1,8 @@ +; read and compile an assembler program +R $1.MAC +M80 $1,$1=$1/M +L80 $1,$1/N/E +ERA $1.REL +W $1.PRN +ERA $1.PRN + \ No newline at end of file diff --git a/ISIS PLM/MEMMGR.LIT b/ISIS PLM/MEMMGR.LIT new file mode 100644 index 0000000..dba5769 --- /dev/null +++ b/ISIS PLM/MEMMGR.LIT @@ -0,0 +1,15 @@ +$nolist +/* + Memmgr Literals +*/ + + declare allocated literally '80H'; + + declare memory$descriptor literally + 'structure (base byte, + size byte, + attrib byte, + bank byte)'; + +$list + \ No newline at end of file diff --git a/ISIS PLM/MONX b/ISIS PLM/MONX new file mode 100644 index 0000000..8a13460 Binary files /dev/null and b/ISIS PLM/MONX differ diff --git a/ISIS PLM/MOVER.MAC b/ISIS PLM/MOVER.MAC new file mode 100644 index 0000000..dc96a5d --- /dev/null +++ b/ISIS PLM/MOVER.MAC @@ -0,0 +1,26 @@ + .Z80 + aseg + maclib MEMCFG.LIB ; define configuration parameters + org 100h + +cpmsiz equ ccplen + bdoslen + bioslen +cpmsrc equ 00A00h + +start: ld hl,cpmsrc + ld de,ccpph + ld bc,cpmsiz +again: ld a,(hl) + ld (de),a + inc hl + inc de + dec bc + ld a,c + or b + jp nz,again + jp biosph + +movend equ $ + ds 0200h-movend ; fill remainder with zeroes + + end start + \ No newline at end of file diff --git a/ISIS PLM/OBJCPM.COM b/ISIS PLM/OBJCPM.COM new file mode 100644 index 0000000..6e8fd45 Binary files /dev/null and b/ISIS PLM/OBJCPM.COM differ diff --git a/ISIS PLM/OBJHEX b/ISIS PLM/OBJHEX new file mode 100644 index 0000000..68b5b0b Binary files /dev/null and b/ISIS PLM/OBJHEX differ diff --git a/ISIS PLM/OS5TRINT.SRC b/ISIS PLM/OS5TRINT.SRC new file mode 100644 index 0000000..72de2ac --- /dev/null +++ b/ISIS PLM/OS5TRINT.SRC @@ -0,0 +1,15 @@ +; PIP INTERFACE TO BDOS (CAN BE USED FOR OTHER TRANSIENTS) + PUBLIC BOOT,IOBYTE,BDISK,BDOS,MON1,MON2,MON3 + PUBLIC MAXB,FCB,BUFF +BOOT EQU 0000H ;WARM START +IOBYTE EQU 0003H ;IO BYTE +BDISK EQU 0004H ;BOOT DISK # +BDOS EQU 0005H ;BDOS ENTRY +MON1 EQU 0005H ;BDOS ENTRY +MON2 EQU 0005H ;BDOS ENTRY +MON3 EQU 0005H ;BDOS ENTRY +MAXB EQU 0006H ;MAX MEM BASE +FCB EQU 005CH ;DEFAULT FCB +BUFF EQU 0080H ;DEFAULT BUFFER + END + \ No newline at end of file diff --git a/ISIS PLM/PIP b/ISIS PLM/PIP new file mode 100644 index 0000000..8eb676e Binary files /dev/null and b/ISIS PLM/PIP differ diff --git a/ISIS PLM/PIP.COM b/ISIS PLM/PIP.COM new file mode 100644 index 0000000..b875047 Binary files /dev/null and b/ISIS PLM/PIP.COM differ diff --git a/ISIS PLM/PIP.LIN b/ISIS PLM/PIP.LIN new file mode 100644 index 0000000..87c5d1d --- /dev/null +++ b/ISIS PLM/PIP.LIN @@ -0,0 +1,4 @@ +0000 PIP# +0000 X0100# + + \ No newline at end of file diff --git a/ISIS PLM/PIP.LST b/ISIS PLM/PIP.LST new file mode 100644 index 0000000..fdf1b98 --- /dev/null +++ b/ISIS PLM/PIP.LST @@ -0,0 +1,1700 @@ + PL/M-80 COMPILER PAGE 1 + + +ISIS-II PL/M-80 V3.1 COMPILATION OF MODULE PIPMOD +OBJECT MODULE PLACED IN :F3:PIP.OBJ +COMPILER INVOKED BY: :F1:PLM80 :F3:PIP.PLM + + + + 1 PIPMOD: + DO; + /* P E R I P H E R A L I N T E R C H A N G E P R O G R A M + + COPYRIGHT (C) 1976, 1977, 1978, 1979, 1980 + DIGITAL RESEARCH + BOX 579 + PACIFIC GROVE, CA + 93950 + */ + + 2 1 DECLARE + CPMVERSION LITERALLY '0020H'; /* REQUIRED FOR OPERATION */ + + 3 1 DECLARE + IOBYTE BYTE EXTERNAL, /* IOBYTE AT 0003H */ + MAXB ADDRESS EXTERNAL, /* ADDR FIELD OF JMP BDOS */ + FCB (33) BYTE EXTERNAL, /* DEFAULT FILE CONTROL BLOCK */ + BUFF(128)BYTE EXTERNAL; /* DEFAULT BUFFER */ + + 4 1 DECLARE + ENDFILE LITERALLY '1AH', /* END OF FILE MARK */ + JMP LITERALLY '0C3H', /* 8080 JUMP INSTRUCTION */ + RET LITERALLY '0C9H'; /* 8080 RETURN */ + + /* THE FIRST PORTION OF THE PIP PROGRAM 'FAKES' THE PAGE ONE + (100H - 1FFH) SECTION OF PIP WHICH CONTAINS A JUMP TO PIPENTRY, AND + SPACE FOR CUSTOM I/O DRIVERS (WHICH CAN BE 'PATCHED' USING DDT) IN THE + REMAINING PAGE ONE AREA. THE PIP PROGRAM ACTUALLY STARTS AT 200H */ + + 5 1 DECLARE JUMP BYTE DATA(JMP); /* JMP INSTRUCTION TO */ + /* JMP .PIPENTRY-3 WHERE THE LXI SP,STACK ACTUALLY OCCURS */ + 6 1 DECLARE JADR ADDRESS DATA(.PIPENTRY-3); /* START OF PIP */ + 7 1 DECLARE INPSUB(3) BYTE DATA(RET,0,0); /* INP: RET NOP NOP */ + 8 1 DECLARE OUTSUB(3) BYTE DATA(RET,0,0); /* OUT: RET NOP NOP */ + 9 1 DECLARE INPDATA BYTE DATA(ENDFILE); /* RETURNED DATA */ + /* NOTE: PAGE 1 AT 100H CONTAINS THE FOLLOWING + 100H: JMP PIPENTRY ;TO START THE PIP PROGRAM + 103H: RET ;INP: DEFAULTS TO EMPTY INPUT (DATA 1AH AT 109H) + 104H: NOP + 105H: NOP + 106H: RET ;OUT: DEFAULTS TO EMPTY OUTPUT + 107H: NOP + 108H: NOP + 109H: 1AH=ENDFILE ;DATA FROM INP: FUNCTION IS STORED HERE ON + ;RETURN FROM THE INP: ENTRY POINT + 10AH: - 1FFH ;SPACE RESERVED FOR SPECIAL PURPOSE + ; DRIVERS - IF INCLUDED, THEN REPLACE 103H AND 106H BY JMP'S + ; TO THE PROPER LOCATIONS WITHIN THE RESERVED AREA. + ; ALSO, RETURN DATA FROM INP: ENTRY POINT AT 109H. + ; THESE DRIVERS ARE MOST EASILY INSERTED WITH THE DDT PROGRAM + PL/M-80 COMPILER PAGE 2 + + + ; UNDER CP/M + */ + + 10 1 DECLARE /* 16 BYTE MESSAGE */ + FREEMEMORY LITERALLY '''(INP:/OUT:SPACE)''', + /* 256 BYTE AREA FOR INP: OUT: PATCHING */ + RESERVED(*) BYTE DATA(0,0,0,0,0,0, + FREEMEMORY, FREEMEMORY, FREEMEMORY, + FREEMEMORY, FREEMEMORY, FREEMEMORY, FREEMEMORY, + FREEMEMORY, FREEMEMORY, FREEMEMORY, FREEMEMORY, + FREEMEMORY, FREEMEMORY, FREEMEMORY, FREEMEMORY); + + + + + 11 1 DECLARE COPYRIGHT(*) BYTE DATA ( + ' COPYRIGHT (C) 1979, DIGITAL RESEARCH, PIP VERS 1.5'); + + 12 1 DECLARE INPLOC ADDRESS DATA (.INPSUB); /* ADDRESS OF INP: DEVICE */ + 13 1 DECLARE OUTLOC ADDRESS DATA (.OUTSUB); /* ADDRESS OF OUT: DEVICE */ + + 14 1 OUT: PROCEDURE(B); + 15 2 DECLARE B BYTE; + /* SEND B TO OUT: DEVICE */ + 16 2 CALL OUTLOC; + 17 2 END OUT; + + 18 1 INP: PROCEDURE BYTE; + 19 2 CALL INPLOC; + 20 2 RETURN INPDATA; + 21 2 END INP; + + + 22 1 TIMEOUT: PROCEDURE; + /* WAIT FOR 50 MSEC */ + 23 2 CALL TIME(250); CALL TIME(250); + 25 2 END TIMEOUT; + + /* LITERAL DECLARATIONS */ + 26 1 DECLARE + LIT LITERALLY 'LITERALLY', + LPP LIT '60', /* LINES PER PAGE */ + TAB LIT '09H', /* HORIZONTAL TAB */ + FF LIT '0CH', /* FORM FEED */ + LA LIT '05FH', /* LEFT ARROW */ + LB LIT '05BH', /* LEFT BRACKET */ + RB LIT '05DH', /* RIGHT BRACKET */ + XOFF LIT '13H', /* TRANSMIT BUFFER FUNCTION */ + + RDR LIT '5', + LST LIT '10', + PUNP LIT '15', /* POSITION OF 'PUN' + 1 */ + CONP LIT '19', /* CONSOLE */ + NULP LIT '19', /* NUL: BEFORE INCREMENT */ + EOFP LIT '20', /* EOF: BEFORE INCREMENT */ + HSRDR LIT 'RDR', /* READER DEVICES */ + PRNT LIT '10', /* PRINTER */ + PL/M-80 COMPILER PAGE 3 + + + + + FSIZE LIT '33', + FRSIZE LIT '36', /* SIZE OF RANDOM FCB */ + NSIZE LIT '8', + FNSIZE LIT '11', + MDISK LIT '1', + FNAM LIT '8', + FEXT LIT '9', + FEXTL LIT '3', + ROFILE LITERALLY '9', /* READ ONLY FILE FIELD */ + SYSFILE LITERALLY '10', /* SYSTEM FILE FIELD */ + FREEL LIT '12', /* REEL NUMBER FIELD OF FCB */ + + HBUFS LIT '80', /* "HEX" BUFFER SIZE */ + + ERR LIT '0', + SPECL LIT '1', + FILE LIT '2', + PERIPH LIT '3', + DISKNAME LIT '4'; + + 27 1 DECLARE + COLUMN BYTE, /* COLUMN COUNT FOR PRINTER TABS */ + LINENO BYTE, /* LINE WITHIN PAGE */ + AMBIG BYTE, /* SET FOR AMBIGUOUS FILE REFS */ + PARSET BYTE, /* TRUE IF PARAMETERS PRESENT */ + FEEDBASE BYTE, /* USED TO FEED SEARCH CHARACTERS */ + FEEDLEN BYTE, /* LENGTH OF FEED STRING */ + MATCHLEN BYTE, /* USED IN MATCHING STRINGS */ + QUITLEN BYTE, /* USED TO TERMINATE QUIT COMMAND */ + NBUF BYTE, /* NUM BUFFERS-1 IN SBUFF AND DBUFF */ + CDISK BYTE, /* CURRENT DISK */ + BUFFER LITERALLY 'BUFF', /* DEFAULT BUFFER */ + SEARFCB LITERALLY 'FCB', /* SEARCH FCB IN MULTI COPY */ + MEMSIZE LITERALLY 'MAXB', /* MEMORY SIZE */ + SBLEN ADDRESS, /* SOURCE BUFFER LENGTH */ + DBLEN ADDRESS, /* DEST BUFFER LENGTH */ + SBASE ADDRESS, /* SOURCE BUFFER BASE */ + /* THE VECTORS DBUFF AND SBUFF ARE DECLARED WITH DIMENSION + 1024, BUT ACTUALLY VARY WITH THE FREE MEMORY SIZE */ + DBUFF(1024) BYTE AT (.MEMORY), /* DESTINATION BUFFER */ + SBUFF BASED SBASE (1024) BYTE, /* SOURCE BUFFER */ + SDISK BYTE, /* SOURCE DISK */ + (SCOM, DHEX) BYTE, /* SOURCE IS 'COM' FILE IF TRUE */ + /* DEST IS 'HEX' FILE IF TRUE */ + SOURCE (FSIZE) BYTE, /* SOURCE FCB */ + SFUB BYTE AT(.SOURCE(13)), /* UNFILLED BYTES FIELD */ + DEST (FRSIZE) BYTE, /* DESTINATION FCB */ + DESTR ADDRESS AT(.DEST(33)), /* RANDOM RECORD POSITION */ + DESTO BYTE AT(.DEST(35)), /* RANDOM OVERFLOW BYTE */ + DFUB BYTE AT (.DEST(13)), /* UNFILLED BYTES FIELD */ + DDISK BYTE, /* DESTINATION DISK */ + HBUFF(HBUFS) BYTE, /* HEX FILE BUFFER */ + HSOURCE BYTE, /* NEXT HEX SOURCE CHARACTER */ + + NSOURCE ADDRESS, /* NEXT SOURCE CHARACTER */ + PL/M-80 COMPILER PAGE 4 + + + HARDEOF ADDRESS, /* SET TO NSOURCE ON REAL EOF */ + NDEST ADDRESS; /* NEXT DESTINATION CHARACTER */ + + 28 1 DECLARE + /* SUBMIT FILE CONTROL BLOCK FOR ERROR DELETE */ + SUBFCB (*) BYTE DATA (0,'$$$ SUB',0,0,0); + + 29 1 DECLARE + PDEST BYTE, /* DESTINATION DEVICE */ + PSOURCE BYTE; /* CURRENT SOURCE DEVICE */ + + 30 1 DECLARE + MULTCOM BYTE, /* FALSE IF PROCESSING ONE LINE */ + PUTNUM BYTE, /* SET WHEN READY FOR NEXT LINE NUM */ + CONCNT BYTE, /* COUNTER FOR CONSOLE READY CHECK */ + CHAR BYTE, /* LAST CHARACTER SCANNED */ + TYPE BYTE, /* TYPE OF CHARACTER SCANNED */ + FLEN BYTE; /* FILE NAME LENGTH */ + + 31 1 MON1: PROCEDURE(F,A) EXTERNAL; + 32 2 DECLARE F BYTE, + A ADDRESS; + 33 2 END MON1; + + 34 1 MON2: PROCEDURE(F,A) BYTE EXTERNAL; + 35 2 DECLARE F BYTE, + A ADDRESS; + 36 2 END MON2; + + 37 1 MON3: PROCEDURE(F,A) ADDRESS EXTERNAL; + 38 2 DECLARE F BYTE, + A ADDRESS; + 39 2 END MON3; + + 40 1 BOOT: PROCEDURE EXTERNAL; + /* SYSTEM REBOOT */ + 41 2 END BOOT; + + 42 1 READRDR: PROCEDURE BYTE; + /* READ CURRENT READER DEVICE */ + 43 2 RETURN MON2(3,0); + 44 2 END READRDR; + + 45 1 READCHAR: PROCEDURE BYTE; + /* READ CONSOLE CHARACTER */ + 46 2 RETURN MON2(1,0); + 47 2 END READCHAR; + + 48 1 DECLARE + TRUE LITERALLY '1', + FALSE LITERALLY '0', + FOREVER LITERALLY 'WHILE TRUE', + CR LITERALLY '13', + LF LITERALLY '10', + WHAT LITERALLY '63'; + + 49 1 PRINTCHAR: PROCEDURE(CHAR); + PL/M-80 COMPILER PAGE 5 + + + 50 2 DECLARE CHAR BYTE; + 51 2 CALL MON1(2,CHAR AND 7FH); + 52 2 END PRINTCHAR; + + 53 1 CRLF: PROCEDURE; + 54 2 CALL PRINTCHAR(CR); + 55 2 CALL PRINTCHAR(LF); + 56 2 END CRLF; + + 57 1 PRINT: PROCEDURE(A); + 58 2 DECLARE A ADDRESS; + /* PRINT THE STRING STARTING AT ADDRESS A UNTIL THE + NEXT DOLLAR SIGN IS ENCOUNTERED */ + 59 2 CALL CRLF; + 60 2 CALL MON1(9,A); + 61 2 END PRINT; + + 62 1 DECLARE DCNT BYTE; + + 63 1 VERSION: PROCEDURE ADDRESS; + 64 2 RETURN MON3(12,0); /* VERSION NUMBER */ + 65 2 END VERSION; + + 66 1 INITIALIZE: PROCEDURE; + 67 2 CALL MON1(13,0); + 68 2 END INITIALIZE; + + 69 1 SELECT: PROCEDURE(D); + 70 2 DECLARE D BYTE; + 71 2 CALL MON1(14,D); + 72 2 END SELECT; + + 73 1 OPEN: PROCEDURE(FCB); + 74 2 DECLARE FCB ADDRESS; + 75 2 DCNT = MON2(15,FCB); + 76 2 END OPEN; + + 77 1 CLOSE: PROCEDURE(FCB); + 78 2 DECLARE FCB ADDRESS; + 79 2 DCNT = MON2(16,FCB); + 80 2 END CLOSE; + + 81 1 SEARCH: PROCEDURE(FCB); + 82 2 DECLARE FCB ADDRESS; + 83 2 DCNT = MON2(17,FCB); + 84 2 END SEARCH; + + 85 1 SEARCHN: PROCEDURE; + 86 2 DCNT = MON2(18,0); + 87 2 END SEARCHN; + + 88 1 DELETE: PROCEDURE(FCB); + 89 2 DECLARE FCB ADDRESS; + 90 2 CALL MON1(19,FCB); + 91 2 END DELETE; + + 92 1 DISKREAD: PROCEDURE(FCB) BYTE; + PL/M-80 COMPILER PAGE 6 + + + 93 2 DECLARE FCB ADDRESS; + 94 2 RETURN MON2(20,FCB); + 95 2 END DISKREAD; + + 96 1 DISKWRITE: PROCEDURE(FCB) BYTE; + 97 2 DECLARE FCB ADDRESS; + 98 2 RETURN MON2(21,FCB); + 99 2 END DISKWRITE; + + 100 1 MAKE: PROCEDURE(FCB); + 101 2 DECLARE FCB ADDRESS; + 102 2 DCNT = MON2(22,FCB); + 103 2 END MAKE; + + 104 1 RENAME: PROCEDURE(FCB); + 105 2 DECLARE FCB ADDRESS; + 106 2 CALL MON1(23,FCB); + 107 2 END RENAME; + + 108 1 DECLARE + CUSER BYTE, /* CURRENT USER NUMBER */ + SUSER BYTE; /* SOURCE USER NUMBER ('G' PARAMETER) */ + + 109 1 SETIND: PROCEDURE(FCB); + 110 2 DECLARE FCB ADDRESS; + 111 2 CALL MON1(30,FCB); + 112 2 END SETIND; + + 113 1 GETUSER: PROCEDURE BYTE; + 114 2 RETURN MON2(32,0FFH); + 115 2 END GETUSER; + + 116 1 SETUSER: PROCEDURE(USER); + 117 2 DECLARE USER BYTE; + 118 2 CALL MON1(32,USER); + 119 2 END SETUSER; + + 120 1 SETCUSER: PROCEDURE; + 121 2 CALL SETUSER(CUSER); + 122 2 END SETCUSER; + + 123 1 SETSUSER: PROCEDURE; + 124 2 CALL SETUSER(SUSER); + 125 2 END SETSUSER; + + 126 1 READ$RANDOM: PROCEDURE(FCB) BYTE; + 127 2 DECLARE FCB ADDRESS; + 128 2 RETURN MON2(33,FCB); + 129 2 END READ$RANDOM; + + 130 1 WRITE$RANDOM: PROCEDURE(FCB) BYTE; + 131 2 DECLARE FCB ADDRESS; + 132 2 RETURN MON2(34,FCB); + 133 2 END WRITE$RANDOM; + + 134 1 SET$RANDOM: PROCEDURE(FCB); + 135 2 DECLARE FCB ADDRESS; + PL/M-80 COMPILER PAGE 7 + + + /* SET RANDOM RECORD POSITION */ + 136 2 CALL MON1(36,FCB); + 137 2 END SET$RANDOM; + + 138 1 DECLARE CBUFF(130) BYTE, /* COMMAND BUFFER */ + MAXLEN BYTE AT (.CBUFF(0)), /* MAX BUFFER LENGTH */ + COMLEN BYTE AT (.CBUFF(1)), /* CURRENT LENGTH */ + COMBUFF (128) BYTE AT (.CBUFF(2)); /* COMMAND BUFFER CONTENTS */ + 139 1 DECLARE (TCBP,CBP) BYTE; /* TEMP CBP, COMMAND BUFFER POINTER */ + + 140 1 READCOM: PROCEDURE; + /* READ INTO COMMAND BUFFER */ + 141 2 MAXLEN = 128; + 142 2 CALL MON1(10,.MAXLEN); + 143 2 END READCOM; + + 144 1 DECLARE MCBP BYTE; + + 145 1 CONBRK: PROCEDURE BYTE; + /* CHECK CONSOLE CHARACTER READY */ + 146 2 RETURN MON2(11,0); + 147 2 END CONBRK; + + 148 1 DECLARE /* CONTROL TOGGLE VECTOR */ + CONT(26) BYTE, /* ONE FOR EACH ALPHABETIC */ + /* 00 01 02 03 04 05 06 07 08 09 10 11 12 13 + A B C D E F G H I J K L M N + 14 15 16 17 18 19 20 21 22 23 24 25 + O P Q R S T U V W X Y Z */ + BLOCK BYTE AT(.CONT(1)), /* BLOCK MODE TRANSFER */ + DELET BYTE AT(.CONT(3)), /* DELETE CHARACTERS */ + ECHO BYTE AT(.CONT(4)), /* ECHO CONSOLE CHARACTERS */ + FORMF BYTE AT(.CONT(5)), /* FORM FILTER */ + GETU BYTE AT(.CONT(6)), /* GET FILE, USER # */ + HEXT BYTE AT(.CONT(7)), /* HEX FILE TRANSFER */ + IGNOR BYTE AT(.CONT(8)), /* IGNORE :00 RECORD ON FILE */ + LOWER BYTE AT(.CONT(11)), /* TRANSLATE TO LOWER CASE */ + NUMB BYTE AT(.CONT(13)), /* NUMBER OUTPUT LINES */ + OBJ BYTE AT(.CONT(14)), /* OBJECT FILE TRANSFER */ + PAGCNT BYTE AT(.CONT(15)), /* PAGE LENGTH */ + QUITS BYTE AT(.CONT(16)), /* QUIT COPY */ + RSYS BYTE AT(.CONT(17)), /* READ SYSTEM FILES */ + STARTS BYTE AT(.CONT(18)), /* START COPY */ + TABS BYTE AT(.CONT(19)), /* TAB SET */ + UPPER BYTE AT(.CONT(20)), /* UPPER CASE TRANSLATE */ + VERIF BYTE AT(.CONT(21)), /* VERIFY EQUAL FILES ONLY */ + WRROF BYTE AT(.CONT(22)), /* WRITE TO R/O FILE */ + ZEROP BYTE AT(.CONT(25)); /* ZERO PARITY ON INPUT */ + + 149 1 SETDMA: PROCEDURE(A); + 150 2 DECLARE A ADDRESS; + 151 2 CALL MON1(26,A); + 152 2 END SETDMA; + + /* INTELLEC 8 INTEL/ICOM READER INPUT */ + + 153 1 INTIN: PROCEDURE BYTE; + PL/M-80 COMPILER PAGE 8 + + + /* READ THE INTEL / ICOM READER */ + 154 2 DECLARE PTRI LITERALLY '3', /* DATA */ + PTRS LITERALLY '1', /* STATUS */ + PTRC LITERALLY '1', /* COMMAND */ + PTRG LITERALLY '0CH', /* GO */ + PTRN LITERALLY '08H'; /* STOP */ + + /* STROBE THE READER */ + 155 2 OUTPUT(PTRC) = PTRG; + 156 2 OUTPUT(PTRC) = PTRN; + 157 2 DO WHILE NOT ROL(INPUT(PTRS),3); /* NOT READY */ + 158 3 END; + /* DATA READY */ + 159 2 RETURN INPUT(PTRI) AND 7FH; + 160 2 END INTIN; + + + 161 1 DECLARE ZEROSUP BYTE, /* ZERO SUPPRESSION */ + (C3,C2,C1) BYTE; /* LINE COUNT ON PRINTER */ + + 162 1 ERROR: PROCEDURE(A); + 163 2 DECLARE A ADDRESS, I BYTE; + 164 2 CALL SETCUSER; + 165 2 CALL PRINT(A); CALL PRINTCHAR(':'); CALL PRINTCHAR(' '); + 168 2 DO I = TCBP TO CBP; + 169 3 IF I < COMLEN THEN CALL PRINTCHAR(COMBUFF(I)); + 171 3 END; + /* ZERO THE COMLEN IN CASE THIS IS A SINGLE COMMAND */ + 172 2 COMLEN = 0; + /* DELETE ANY $$$.SUB FILES IN CASE BATCH PROCESSING */ + /* DELETE SUB FILE ONLY IF PRESENT (MAY BE R/O DISK) */ + 173 2 CALL SEARCH(.SUBFCB); + 174 2 IF DCNT <> 255 THEN CALL DELETE(.SUBFCB); + 176 2 CALL CRLF; + 177 2 GO TO RETRY; + 178 2 END ERROR; + + 179 1 MOVE: PROCEDURE(S,D,N); + 180 2 DECLARE (S,D) ADDRESS, N BYTE; + 181 2 DECLARE A BASED S BYTE, B BASED D BYTE; + 182 2 DO WHILE (N:=N-1) <> 255; + 183 3 B = A; S = S+1; D = D+1; + 186 3 END; + 187 2 END MOVE; + + + 188 1 FILLSOURCE: PROCEDURE; + /* FILL THE SOURCE BUFFERS */ + 189 2 DECLARE (I,J) BYTE; + 190 2 NSOURCE = 0; + 191 2 CALL SELECT(SDISK); + 192 2 CALL SETSUSER; /* SOURCE USER NUMBER SET */ + 193 2 DO I = 0 TO NBUF; + /* SET DMA ADDRESS TO NEXT BUFFER POSIITION */ + 194 3 CALL SETDMA(.SBUFF(NSOURCE)); + 195 3 IF (J := DISKREAD(.SOURCE)) <> 0 THEN + 196 3 DO; IF J <> 1 THEN + PL/M-80 COMPILER PAGE 9 + + + 198 4 CALL ERROR(.('DISK READ ERROR$')); + /* END - OF - FILE */ + 199 4 HARDEOF = NSOURCE; /* SET HARD END-OF-FILE */ + 200 4 SBUFF(NSOURCE) = ENDFILE; I = NBUF; + 202 4 END; ELSE + 203 3 NSOURCE = NSOURCE + 128; + 204 3 END; + 205 2 NSOURCE = 0; + 206 2 CALL SETCUSER; /* BACK TO CURRENT USER NUMBER */ + 207 2 END FILLSOURCE; + + + 208 1 WRITEDEST: PROCEDURE; + /* WRITE OUTPUT BUFFERS UP TO BUT NOT INCLUDING POSITION + NDEST - THE LOW ORDER 7 BITS OF NDEST ARE ZERO */ + 209 2 DECLARE (I, J, N) BYTE; + 210 2 DECLARE DMA ADDRESS; + 211 2 DECLARE DATAOK BYTE; + 212 2 IF (N := LOW(SHR(NDEST,7)) - 1) = 255 THEN RETURN ; + 214 2 NDEST = 0; + 215 2 CALL SELECT(DDISK); + 216 2 CALL SETRANDOM(.DEST); /* SET BASE RECORD FOR VERIFY */ + 217 2 DO I = 0 TO N; + /* SET DMA ADDRESS TO NEXT BUFFER */ + 218 3 DMA = .DBUFF(NDEST); + 219 3 CALL SETDMA(DMA); + 220 3 IF DISKWRITE(.DEST) <> 0 THEN + 221 3 CALL ERROR(.('DISK WRITE ERROR$')); + 222 3 NDEST = NDEST + 128; + 223 3 END; + 224 2 IF VERIF THEN /* VERIFY DATA WRITTEN OK */ + 225 2 DO; + 226 3 NDEST = 0; + 227 3 CALL SETDMA(.BUFF); /* FOR COMPARE */ + 228 3 DO I = 0 TO N; + 229 4 DATAOK = READRANDOM(.DEST) = 0; + 230 4 DESTR = DESTR + 1; /* NEXT RANDOM READ */ + 231 4 J = 0; + /* PERFORM COMPARISON */ + 232 4 DO WHILE DATAOK AND J < 80H; + 233 5 DATAOK = BUFFER(J) = DBUFF(NDEST+J); + 234 5 J = J + 1; + 235 5 END; + 236 4 NDEST = NDEST + 128; + 237 4 IF NOT DATAOK THEN + 238 4 CALL ERROR(.('VERIFY ERROR$')); + 239 4 END; + 240 3 DATAOK = DISKWRITE(.DEST); + /* NOW READY TO CONTINUE THE WRITE OPERATION */ + 241 3 END; + 242 2 NDEST = 0; + 243 2 END WRITEDEST; + + 244 1 PUTDCHAR: PROCEDURE(B); + 245 2 DECLARE (B,IOB) BYTE; + /* WRITE BYTE B TO THE DESTINATION DEVICE GIVEN BY PDEST */ + 246 2 IF B >= ' ' THEN + PL/M-80 COMPILER PAGE 10 + + + 247 2 DO; COLUMN = COLUMN + 1; + 249 3 IF DELET > 0 THEN /* MAY BE PAST RIGHT SIDE */ + 250 3 DO; IF COLUMN > DELET THEN RETURN; + 253 4 END; + 254 3 END; + 255 2 IOB = IOBYTE; /* IN CASE IT IS ALTERED */ + 256 2 DO CASE PDEST; + /* CASE 0 IS THE DESTINATION FILE */ + 257 3 DO; + 258 4 IF NDEST >= DBLEN THEN CALL WRITEDEST; + 260 4 DBUFF(NDEST) = B; + 261 4 NDEST = NDEST+1; + 262 4 END; + /* CASE 1 IS ARD (ADDMASTER) */ + 263 3 GO TO NOTDEST; + /* CASE 2 IS IRD (INTEL/ICOM) */ + 264 3 GO TO NOTDEST; + /* CASE 3 IS PTR */ + 265 3 GO TO NOTDEST; + /* CASE 4 IS UR1 */ + 266 3 GO TO NOTDEST; + /* CASE 5 IS UR2 */ + 267 3 GO TO NOTDEST; + /* CASE 6 IS RDR */ + 268 3 NOTDEST: + CALL ERROR(.('NOT A CHARACTER SINK$')); + /* CASE 7 IS OUT */ + 269 3 CALL OUT(B); + /* CASE 8 IS LPT */ + 270 3 DO; IOBYTE = 1000$0000B; GO TO LSTL; + 273 4 END; + /* CASE 9 IS UL1 */ + 274 3 DO; IOBYTE = 1100$0000B; GO TO LSTL; + 277 4 END; + /* CASE 10 IS PRN (TABS EXPANDED, LINES LISTED, CHANGED TO LST) */ + 278 3 DO; IOBYTE = 1000$0000B; GO TO LSTL; + 281 4 END; + /* CASE 11 IS LST */ + 282 3 LSTL: + CALL MON1(5,B); + /* CASE 12 IS PTP */ + 283 3 DO; IOBYTE = 0001$0000B; GO TO PUNL; + 286 4 END; + /* CASE 13 IS UP1 */ + 287 3 DO; IOBYTE = 0010$0000B; GO TO PUNL; + 290 4 END; + /* CASE 14 IS UP2 */ + 291 3 DO; IOBYTE = 0011$0000B; GO TO PUNL; + 294 4 END; + /* CASE 15 IS PUN */ + 295 3 PUNL: + CALL MON1(4,B); + /* CASE 16 IS TTY */ + 296 3 DO; IOBYTE = 0; GO TO CONL; + 299 4 END; + /* CASE 17 IS CRT */ + 300 3 DO; IOBYTE = 1; GO TO CONL; + PL/M-80 COMPILER PAGE 11 + + + 303 4 END; + /* CASE 18 IS UC1 */ + 304 3 DO; IOBYTE = 11B; GO TO CONL; + 307 4 END; + /* CASE 19 IS CON */ + 308 3 CONL: + CALL MON1(2,B); + 309 3 END; + 310 2 IOBYTE = IOB; + 311 2 END PUTDCHAR; + + 312 1 PUTDESTC: PROCEDURE(B); + 313 2 DECLARE (B,I) BYTE; + /* WRITE DESTINATION CHARACTER, TAB EXPANSION */ + 314 2 IF B <> TAB THEN CALL PUTDCHAR(B); ELSE + 316 2 IF TABS = 0 THEN CALL PUTDCHAR(B); ELSE + /* B IS TAB CHAR, TABS > 0 */ + 318 2 DO; I = COLUMN; + 320 3 DO WHILE I >= TABS; + 321 4 I = I - TABS; + 322 4 END; + 323 3 I = TABS - I; + 324 3 DO WHILE I > 0; + 325 4 I = I - 1; + 326 4 CALL PUTDCHAR(' '); + 327 4 END; + 328 3 END; + 329 2 IF B = CR THEN COLUMN = 0; + 331 2 END PUTDESTC; + + 332 1 PRINT1: PROCEDURE(B); + 333 2 DECLARE B BYTE; + 334 2 IF (ZEROSUP := ZEROSUP AND B = 0) THEN CALL PUTDESTC(' '); ELSE + 336 2 CALL PUTDESTC('0'+B); + 337 2 END PRINT1; + + 338 1 PRINTDIG: PROCEDURE(D); + 339 2 DECLARE D BYTE; + 340 2 CALL PRINT1(SHR(D,4)); CALL PRINT1(D AND 1111B); + 342 2 END PRINTDIG; + + 343 1 NEWLINE: PROCEDURE; + 344 2 DECLARE ONE BYTE; + 345 2 ONE = 1; + 346 2 ZEROSUP = NUMB = 1; + 347 2 C1 = DEC(C1+ONE); C2 = DEC(C2 PLUS 0); C3 = DEC(C3 PLUS 0); + 350 2 CALL PRINTDIG(C3); CALL PRINTDIG(C2); CALL PRINTDIG(C1); + 353 2 IF NUMB = 1 THEN /* USUALLY PRINTER OUTPUT */ + 354 2 DO; CALL PUTDESTC(':'); CALL PUTDESTC(' '); + 357 3 END; ELSE + 358 2 CALL PUTDESTC(TAB); + 359 2 END NEWLINE; + + 360 1 CLEARBUFF: PROCEDURE; + /* CLEAR OUTPUT BUFFER IN BLOCK MODE TRANSMISION */ + 361 2 DECLARE NA ADDRESS; + 362 2 DECLARE I BYTE; + PL/M-80 COMPILER PAGE 12 + + + 363 2 I = LOW(NDEST) AND 7FH; /* REMAINING PARTIAL BUFFER LENGTH */ + 364 2 NA = NDEST AND 0FF80H; /* START OF SEGMENT NOT WRITTEN */ + 365 2 CALL WRITEDEST; /* CLEARS BUFFERS */ + 366 2 CALL MOVE(.DBUFF(NA),.DBUFF,I); + /* DATA MOVED TO BEGINNING OF BUFFER */ + 367 2 NDEST = I; + 368 2 END CLEARBUFF; + + 369 1 PUTDEST: PROCEDURE(B); + 370 2 DECLARE (I,B) BYTE; + /* WRITE DESTINATION CHARACTER, CHECK TABS AND LINES */ + 371 2 IF FORMF THEN /* SKIP FORM FEEDS */ + 372 2 DO; IF B = FF THEN RETURN; + 375 3 END; + 376 2 IF PUTNUM THEN /* END OF LINE OR START OF FILE */ + 377 2 DO; + 378 3 IF B <> FF THEN /* NOT FORM FEED */ + 379 3 DO; + 380 4 IF (I:=PAGCNT) <> 0 THEN /* PAGE EJECT */ + 381 4 DO; IF I=1 THEN I=LPP; + 384 5 IF (LINENO := LINENO + 1) >= I THEN + 385 5 DO; LINENO = 0; /* NEW PAGE */ + 387 6 CALL PUTDESTC(FF); + 388 6 END; + 389 5 END; + 390 4 IF NUMB > 0 THEN + 391 4 CALL NEWLINE; + 392 4 PUTNUM = FALSE; + 393 4 END; + 394 3 END; + 395 2 IF BLOCK THEN /* BLOCK MODE TRANSFER */ + 396 2 DO; + 397 3 IF B = XOFF AND PDEST = 0 THEN + 398 3 DO; CALL CLEARBUFF; /* BUFFERS WRITTEN */ + 400 4 RETURN; /* DON'T PASS THE X-OFF */ + 401 4 END; + 402 3 END; + 403 2 IF B = FF THEN LINENO = 0; + 405 2 CALL PUTDESTC(B); + 406 2 IF B = LF THEN PUTNUM = TRUE; + 408 2 END PUTDEST; + + + 409 1 UTRAN: PROCEDURE(B) BYTE; + 410 2 DECLARE B BYTE; + /* TRANSLATE ALPHA TO UPPER CASE */ + 411 2 IF B >= 110$0001B AND B <= 111$1010B THEN /* LOWER CASE */ + 412 2 B = B AND 101$1111B; /* TO UPPER CASE */ + 413 2 RETURN B; + 414 2 END UTRAN; + + 415 1 LTRAN: PROCEDURE(B) BYTE; + 416 2 DECLARE B BYTE; + /* TRANSLATE TO LOWER CASE ALPHA */ + 417 2 IF B >= 'A' AND B <= 'Z' THEN B = B OR 10$0000B; /* TO LOWER */ + 419 2 RETURN B; + 420 2 END LTRAN; + PL/M-80 COMPILER PAGE 13 + + + + 421 1 GETSOURCEC: PROCEDURE BYTE; + /* READ NEXT SOURCE CHARACTER */ + 422 2 DECLARE (IOB,B,CONCHK) BYTE; + + 423 2 IF PSOURCE - 1 <= RDR THEN /* 1 ... RDR+1 */ + 424 2 DO; IF (BLOCK OR HEXT) AND CONBRK THEN + 426 3 DO; + 427 4 IF READCHAR = ENDFILE THEN RETURN ENDFILE; + 429 4 CALL PRINT(.('READER STOPPING',CR,LF,'$')); + 430 4 RETURN XOFF; + 431 4 END; + 432 3 END; + 433 2 CONCHK = TRUE; /* CONSOLE STATUS CHECK BELOW */ + 434 2 IOB = IOBYTE; /* SAVE IT IN CASE IT IS ALTERED */ + 435 2 DO CASE PSOURCE; + /* CASE 0 IS SOURCE FILE */ + 436 3 DO; IF NSOURCE >= SBLEN THEN CALL FILLSOURCE; + 439 4 B = SBUFF(NSOURCE); + 440 4 NSOURCE = NSOURCE + 1; + 441 4 END; + /* CASE 1 IS INP */ + 442 3 B = INP; + /* CASE 2 IS IRD (INTEL/ICOM) */ + 443 3 B = INTIN; + /* CASE 3 IS PTR */ + 444 3 DO; IOBYTE = 0000$0100B; GO TO RDRL; + 447 4 END; + /* CASE 4 IS UR1 */ + 448 3 DO; IOBYTE = 0000$1000B; GO TO RDRL; + 451 4 END; + /* CASE 5 IS UR2 */ + 452 3 DO; IOBYTE = 0000$1100B; GO TO RDRL; + 455 4 END; + /* CASE 6 IS RDR */ + 456 3 RDRL: + B = MON2(3,0) AND 7FH; + /* CASE 7 IS OUT */ + 457 3 GO TO NOTSOURCE; + /* CASE 8 IS LPT */ + 458 3 GO TO NOTSOURCE; + /* CASE 9 IS UL1 */ + 459 3 GO TO NOTSOURCE; + /* CASE 10 IS PRN */ + 460 3 GO TO NOTSOURCE; + /* CASE 11 IS LST */ + 461 3 GO TO NOTSOURCE; + /* CASE 12 IS PTP */ + 462 3 GO TO NOTSOURCE; + /* CASE 13 IS UP1 */ + 463 3 GO TO NOTSOURCE; + /* CASE 14 IS UP2 */ + 464 3 GO TO NOTSOURCE; + /* CASE 15 IS PUN */ + 465 3 NOTSOURCE: + DO; CALL ERROR(.('NOT A CHARACTER SOURCE$')); + 467 4 END; + PL/M-80 COMPILER PAGE 14 + + + /* CASE 16 IS TTY */ + 468 3 DO; IOBYTE = 0; GO TO CONL; + 471 4 END; + /* CASE 17 IS CRT */ + 472 3 DO; IOBYTE = 01B; GO TO CONL; + 475 4 END; + /* CASE 18 IS UC1 */ + 476 3 DO; IOBYTE = 11B; GO TO CONL; + 479 4 END; + /* CASE 19 IS CON */ + 480 3 CONL: + DO; CONCHK = FALSE; /* DON'T CHECK CONSOLE STATUS */ + 482 4 B = MON2(1,0); + 483 4 END; + 484 3 END; /* OF CASES */ + 485 2 IOBYTE = IOB; /* RESTORE IOBYTE */ + 486 2 IF ECHO THEN /* COPY TO CONSOLE DEVICE */ + 487 2 DO; IOB = PDEST; PDEST = CONP; CALL PUTDEST(B); + 491 3 PDEST = IOB; + 492 3 END; + 493 2 IF CONCHK THEN /* TEST FOR CONSOLE CHAR READY */ + 494 2 DO; + 495 3 IF SCOM THEN /* SOURCE IS A COM FILE */ + 496 3 CONCHK = (CONCNT := CONCNT + 1) = 0; ELSE /* ASCII */ + 497 3 CONCHK = B = LF; + 498 3 IF CONCHK THEN + 499 3 DO; IF CONBRK THEN + 501 4 DO; + 502 5 IF READCHAR = ENDFILE THEN RETURN ENDFILE; + 504 5 CALL ERROR(.('ABORTED$')); + 505 5 END; + 506 4 END; + 507 3 END; + 508 2 IF ZEROP THEN B = B AND 7FH; + 510 2 IF UPPER THEN RETURN UTRAN(B); + 512 2 IF LOWER THEN RETURN LTRAN(B); + 514 2 RETURN B; + 515 2 END GETSOURCEC; + + 516 1 GETSOURCE: PROCEDURE BYTE; + /* GET NEXT SOURCE CHARACTER */ + 517 2 DECLARE CHAR BYTE; + 518 2 MATCH: PROCEDURE(B) BYTE; + /* MATCH START AND QUIT STRINGS */ + 519 3 DECLARE (B,C) BYTE; + 520 3 IF (C:=COMBUFF(B:=(B+MATCHLEN))) = ENDFILE THEN /* END MATCH */ + 521 3 DO; COMBUFF(B) = CHAR; /* SAVE CURRENT CHARACTER */ + 523 4 RETURN TRUE; + 524 4 END; + 525 3 IF C = CHAR THEN MATCHLEN = MATCHLEN + 1; ELSE + 527 3 MATCHLEN = 0; /* NO MATCH */ + 528 3 RETURN FALSE; + 529 3 END MATCH; + 530 2 IF QUITLEN > 0 THEN + 531 2 DO; IF (QUITLEN := QUITLEN - 1) = 1 THEN RETURN LF; + 534 3 RETURN ENDFILE; /* TERMINATED WITH CR,LF,ENDFILE */ + 535 3 END; + PL/M-80 COMPILER PAGE 15 + + + 536 2 DO FOREVER; /* LOOKING FOR START */ + 537 3 IF FEEDLEN > 0 THEN /* GET SEARCH CHARACTERS */ + 538 3 DO; FEEDLEN = FEEDLEN - 1; + 540 4 CHAR = COMBUFF(FEEDBASE); + 541 4 FEEDBASE = FEEDBASE + 1; + 542 4 RETURN CHAR; + 543 4 END; + 544 3 IF (CHAR := GETSOURCEC) = ENDFILE THEN RETURN ENDFILE; + 546 3 IF STARTS > 0 THEN /* LOOKING FOR START STRING */ + 547 3 DO; IF MATCH(STARTS) THEN + 549 4 DO; FEEDBASE = STARTS; STARTS = 0; + 552 5 FEEDLEN = MATCHLEN + 1; + 553 5 END; /* OTHERWISE NO MATCH, SKIP CHARACTER */ + 554 4 END; ELSE + 555 3 IF QUITS > 0 THEN /* PASS CHARACTERS TIL MATCH */ + 556 3 DO; IF MATCH(QUITS) THEN + 558 4 DO; QUITS = 0; QUITLEN = 2; + /* SUBSEQUENTLY RETURN CR, LF, ENDFILE */ + 561 5 RETURN CR; + 562 5 END; + 563 4 RETURN CHAR; + 564 4 END; ELSE + 565 3 RETURN CHAR; + 566 3 END; /* OF DO FOREVER */ + 567 2 END GETSOURCE; + + 568 1 DECLARE DISK BYTE; /* SELECTED DISK */ + + 569 1 GNC: PROCEDURE BYTE; + 570 2 IF (CBP := CBP + 1) >= COMLEN THEN RETURN CR; + 572 2 RETURN UTRAN(COMBUFF(CBP)); + 573 2 END GNC; + + 574 1 DEBLANK: PROCEDURE; + 575 2 DO WHILE (CHAR := GNC) = ' '; + 576 3 END; + 577 2 END DEBLANK; + + 578 1 SCAN: PROCEDURE(FCBA); + 579 2 DECLARE FCBA ADDRESS, /* ADDRESS OF FCB TO FILL */ + FCB BASED FCBA (FSIZE) BYTE; /* FCB TEMPLATE */ + 580 2 DECLARE (I,J,K) BYTE; /* TEMP COUNTERS */ + + /* SCAN LOOKS FOR THE NEXT DELIMITER, DEVICE NAME, OR FILE NAME. + THE VALUE OF CBP MUST BE 255 UPON ENTRY THE FIRST TIME */ + + 581 2 DELIMITER: PROCEDURE(C) BYTE; + 582 3 DECLARE (I,C) BYTE; + 583 3 DECLARE DEL(*) BYTE DATA + (' =.:,<>',CR,LA,LB,RB); + 584 3 DO I = 0 TO LAST(DEL); + 585 4 IF C = DEL(I) THEN RETURN TRUE; + 587 4 END; + 588 3 RETURN FALSE; + 589 3 END DELIMITER; + + 590 2 PUTCHAR: PROCEDURE; + PL/M-80 COMPILER PAGE 16 + + + 591 3 FCB(FLEN:=FLEN+1) = CHAR; + 592 3 IF CHAR = WHAT THEN AMBIG = TRUE; /* CONTAINS AMBIGUOUS REF */ + 594 3 END PUTCHAR; + + 595 2 FILLQ: PROCEDURE(LEN); + /* FILL CURRENT NAME OR TYPE WITH QUESTION MARKS */ + 596 3 DECLARE LEN BYTE; + 597 3 CHAR = WHAT; /* QUESTION MARK */ + 598 3 DO WHILE FLEN < LEN; + 599 4 CALL PUTCHAR; + 600 4 END; + 601 3 END FILLQ; + + 602 2 GETFCB: PROCEDURE(I) BYTE; + 603 3 DECLARE I BYTE; + 604 3 RETURN FCB(I); + 605 3 END GETFCB; + + 606 2 SCANPAR: PROCEDURE; + 607 3 DECLARE (I,J) BYTE; + /* SCAN OPTIONAL PARAMETERS */ + 608 3 PARSET = TRUE; + 609 3 SUSER = CUSER; /* SOURCE USER := CURRENT USER */ + 610 3 CHAR = GNC; /* SCAN PAST BRACKET */ + 611 3 DO WHILE NOT(CHAR = CR OR CHAR = RB); + 612 4 IF (I := CHAR - 'A') > 25 THEN /* NOT ALPHA */ + 613 4 DO; IF CHAR = ' ' THEN CHAR = GNC; ELSE + 616 5 CALL ERROR(.('BAD PARAMETER$')); + 617 5 END; ELSE + 618 4 DO; /* SCAN PARAMETER VALUE */ + 619 5 IF CHAR = 'S' OR CHAR = 'Q' THEN + 620 5 DO; /* START OR QUIT COMMAND */ + 621 6 J = CBP + 1; /* START OF STRING */ + 622 6 DO WHILE NOT ((CHAR := GNC) = ENDFILE OR CHAR = CR); + 623 7 END; + 624 6 CHAR=GNC; + 625 6 END; ELSE + 626 5 IF (J := (CHAR := GNC) - '0') > 9 THEN J = 1; + ELSE + 628 5 DO WHILE (K := (CHAR := GNC) - '0') <= 9; + 629 6 J = J * 10 + K; + 630 6 END; + 631 5 CONT(I) = J; + 632 5 IF I = 6 THEN /* SET SOURCE USER */ + 633 5 DO; + 634 6 IF J > 31 THEN + 635 6 CALL ERROR(.('INVALID USER NUMBER$')); + 636 6 SUSER = J; + 637 6 END; + 638 5 END; + 639 4 END; + 640 3 CHAR = GNC; + 641 3 END SCANPAR; + + 642 2 CHKSET: PROCEDURE; + 643 3 IF CHAR = LA THEN CHAR = '='; + 645 3 END CHKSET; + PL/M-80 COMPILER PAGE 17 + + + + /* INITIALIZE FILE CONTROL BLOCK TO EMPTY */ + 646 2 AMBIG = FALSE; TYPE = ERR; CHAR = ' '; FLEN = 0; + 650 2 DO WHILE FLEN < FSIZE-1; + 651 3 IF FLEN = FNSIZE THEN CHAR = 0; + 653 3 CALL PUTCHAR; + 654 3 END; + + /* DEBLANK COMMAND BUFFER */ + 655 2 CALL DEBLANK; + + /* SAVE STARTING POSITION OF SCAN FOR DIAGNOSTICS */ + 656 2 TCBP = CBP; + + /* MAY BE A SEPARATOR */ + 657 2 IF DELIMITER(CHAR) THEN + 658 2 DO; CALL CHKSET; + 660 3 TYPE = SPECL; RETURN; + 662 3 END; + + /* CHECK PERIPHERALS AND DISK FILES */ + 663 2 DISK = 0; + /* CLEAR PARAMETERS */ + 664 2 DO I = 0 TO 25; CONT(I) = 0; + 666 3 END; + 667 2 PARSET = FALSE; + 668 2 FEEDLEN,MATCHLEN,QUITLEN = 0; + /* SCAN NEXT NAME */ + 669 2 DO FOREVER; + 670 3 FLEN = 0; + 671 3 DO WHILE NOT DELIMITER(CHAR); + 672 4 IF FLEN >= NSIZE THEN /* ERROR, FILE NAME TOO LONG */ + 673 4 RETURN; + 674 4 IF CHAR = '*' THEN CALL FILLQ(NSIZE); ELSE CALL PUTCHAR; + 677 4 CHAR = GNC; + 678 4 END; + + /* CHECK FOR DISK NAME OR DEVICE NAME */ + 679 3 IF CHAR = ':' THEN + 680 3 DO; IF DISK <> 0 THEN RETURN; /* ALREADY SET */ + 683 4 IF FLEN = 1 THEN + /* MAY BE DISK NAME A ... Z */ + 684 4 DO; + 685 5 IF (DISK := GETFCB(1) - 'A' + 1) > 26 THEN + 686 5 /* ERROR, INVALID DISK NAME */ RETURN; + 687 5 CALL DEBLANK; /* MAY BE DISK NAME ONLY */ + 688 5 IF DELIMITER(CHAR) THEN + 689 5 DO; IF CHAR = LB THEN + 691 6 CALL SCANPAR; + 692 6 CBP = CBP - 1; + 693 6 TYPE = DISKNAME; + 694 6 RETURN; + 695 6 END; + 696 5 END; ELSE + + /* MAY BE A THREE CHARACTER DEVICE NAME */ + 697 4 IF FLEN <> 3 THEN /* ERROR, CANNOT BE DEVICE NAME */ + PL/M-80 COMPILER PAGE 18 + + + 698 4 RETURN; ELSE + + /* LOOK FOR DEVICE NAME */ + 699 4 DO; DECLARE (I,J,K) BYTE, M LITERALLY '20', + IO(*) BYTE DATA + ('INPIRDPTRUR1UR2RDROUTLPTUL1PRNLST', + 'PTPUP1UP2PUNTTYCRTUC1CONNULEOF',0); + /* NOTE THAT ALL READER-LIKE DEVICES MUST BE + PLACED BEFORE 'RDR', AND ALL LISTING-LIKE DEVICES + MUST APPEAR BELOW LST, BUT ABOVE RDR. THE LITERAL + DECLARATIONS FOR RDR, LST, AND PUNP MUST INDICATE + THE POSITIONS OF THESE DEVICES IN THE LIST */ + 701 5 J = 255; + 702 5 DO K = 0 TO M; + 703 6 I = 0; + 704 6 DO WHILE ((I:=I+1) <= 3) AND + IO(J+I) = GETFCB(I); + 705 7 END; + 706 6 IF I = 4 THEN /* COMPLETE MATCH */ + 707 6 DO; TYPE = PERIPH; + /* SCAN PARAMETERS */ + 709 7 IF GNC = LB THEN CALL SCANPAR; + 711 7 CBP = CBP - 1; CHAR = K; + 713 7 RETURN; + 714 7 END; + 715 6 /* OTHERWISE TRY NEXT DEVICE */ J = J + 3; + 716 6 END; + + 717 5 /* ERROR, NO DEVICE NAME MATCH */ RETURN; + 718 5 END; + 719 4 IF CHAR = LB THEN /* PARAMETERS FOLLOW */ + 720 4 CALL SCANPAR; + 721 4 END; ELSE + + /* CHAR IS NOT ':', SO FILE NAME IS SET. SCAN REMAINDER */ + 722 3 DO; IF FLEN = 0 THEN /* ERROR, NO PRIMARY NAME */ + 724 4 RETURN; + 725 4 FLEN = FNAM; + 726 4 IF CHAR = '.' THEN /* SCAN FILE TYPE */ + 727 4 DO WHILE NOT DELIMITER(CHAR := GNC); + 728 5 IF FLEN >= FNSIZE THEN + 729 5 /* ERROR, TYPE FIELD TOO LONG */ RETURN; + 730 5 IF CHAR = '*' THEN CALL FILLQ(FNSIZE); + 732 5 ELSE CALL PUTCHAR; + 733 5 END; + + 734 4 IF CHAR = LB THEN + 735 4 CALL SCANPAR; + /* RESCAN DELIMITER NEXT TIME AROUND */ + 736 4 CBP = CBP - 1; + 737 4 TYPE = FILE; + /* DISK IS THE SELECTED DISK (1 2 3 ... ) */ + 738 4 IF DISK = 0 THEN DISK = CDISK + 1; /* DEFAULT */ + 740 4 FCB(0),FCB(32) = 0; + 741 4 RETURN; + 742 4 END; + 743 3 END; + PL/M-80 COMPILER PAGE 19 + + + 744 2 END SCAN; + + 745 1 NULLS: PROCEDURE; + /* SEND 40 NULLS TO OUTPUT DEVICE */ + 746 2 DECLARE I BYTE; + 747 2 DO I = 0 TO 39; CALL PUTDEST(0); + 749 3 END; + 750 2 END NULLS; + + + 751 1 DECLARE FEXTH(FEXTL) BYTE, /* HOLDS DESTINATION FILE TYPE */ + COPYING BYTE; /* TRUE WHILE COPYING TO DEST FILE */ + + 752 1 MOVEXT: PROCEDURE(A); + 753 2 DECLARE A ADDRESS; + /* MOVE THREE CHARACTER EXTENT INTO DEST FCB */ + 754 2 CALL MOVE(A,.DEST(FEXT),FEXTL); + 755 2 END MOVEXT; + + 756 1 EQUAL: PROCEDURE(A,B) BYTE; + /* COMPARE THE STRINGS AT A AND B UNTIL EITHER A MISMATCH OR + A '$' IS ENCOUNTERED IN STRING B */ + 757 2 DECLARE (A,B) ADDRESS, + (SA BASED A, SB BASED B) BYTE; + 758 2 DO WHILE SB <> '$'; + 759 3 IF (SB AND 7FH) <> (SA AND 7FH) THEN RETURN FALSE; + 761 3 A = A + 1; B = B + 1; + 763 3 END; + 764 2 RETURN TRUE; + 765 2 END EQUAL; + + 766 1 READ$EOF: PROCEDURE BYTE; + /* RETURN TRUE IF END OF FILE */ + 767 2 CHAR = GETSOURCE; + 768 2 IF SCOM THEN RETURN HARDEOF < NSOURCE; + 770 2 RETURN CHAR = ENDFILE; + 771 2 END READ$EOF; + + + 772 1 HEXRECORD: PROCEDURE BYTE; + /* READ ONE RECORD INTO SBUFF AND CHECK FOR PROPER FORM + RETURNS 0 IF RECORD OK + RETURNS 1 IF END OF TAPE (:00000) + RETURNS 2 IF ERROR IN RECORD */ + + + 773 2 DECLARE XOFFSET BYTE; /* TRUE IF XOFF RECVD */ + 774 2 DECLARE NOERRS BYTE; /* TRUE IF NO ERRORS IN THIS RECORD */ + + 775 2 PRINTERR: PROCEDURE(A); + /* PRINT ERROR MESSAGE IF NOERRS TRUE */ + 776 3 DECLARE A ADDRESS; + 777 3 IF NOERRS THEN + 778 3 DO; NOERRS = FALSE; + 780 4 CALL PRINT(A); + 781 4 END; + 782 3 END PRINTERR; + PL/M-80 COMPILER PAGE 20 + + + + 783 2 CHECKXOFF: PROCEDURE; + 784 3 IF XOFFSET THEN + 785 3 DO; XOFFSET = FALSE; + 787 4 CALL CLEARBUFF; + 788 4 END; + 789 3 END CHECKXOFF; + + 790 2 SAVECHAR: PROCEDURE BYTE; + /* READ CHARACTER AND SAVE IN BUFFER */ + 791 3 DECLARE I BYTE; + 792 3 IF NOERRS THEN + 793 3 DO; + 794 4 DO WHILE (I := GETSOURCE) = XOFF; XOFFSET = TRUE; + 796 5 END; + 797 4 HBUFF(HSOURCE) = I; + 798 4 IF (HSOURCE := HSOURCE + 1) >= LAST(HBUFF) THEN + 799 4 CALL PRINTERR(.('RECORD TOO LONG$')); + 800 4 RETURN I; + 801 4 END; + 802 3 RETURN ENDFILE; /* ON ERROR FLAG */ + 803 3 END SAVECHAR; + + 804 2 DECLARE (M, RL, CS, RT) BYTE, + LDA ADDRESS; /* LOAD ADDRESS WHICH FOLLOWS : */ + + 805 2 READHEX: PROCEDURE BYTE; + 806 3 DECLARE H BYTE; + 807 3 IF (H := SAVECHAR) - '0' <= 9 THEN RETURN H-'0'; + 809 3 IF H - 'A' > 5 THEN + 810 3 CALL PRINTERR(.('INVALID DIGIT$')); + 811 3 RETURN H - 'A' + 10; + 812 3 END READHEX; + + 813 2 READBYTE: PROCEDURE BYTE; + /* READ TWO HEX DIGITS */ + 814 3 RETURN SHL(READHEX,4) OR READHEX; + 815 3 END READBYTE; + + 816 2 READCS: PROCEDURE BYTE; + /* READ BYTE WITH CHECKSUM */ + 817 3 RETURN CS := CS + READBYTE; + 818 3 END READCS; + + 819 2 READADDR: PROCEDURE ADDRESS; + /* READ DOUBLE BYTE WITH CHECKSUM */ + 820 3 RETURN SHL(DOUBLE(READCS),8) OR READCS; + 821 3 END READADDR; + + 822 2 NOERRS = TRUE; /* NO ERRORS DETECTED IN THIS RECORD */ + + /* READ NEXT RECORD */ + /* SCAN FOR THE ':' */ + 823 2 HSOURCE = 0; + 824 2 DO WHILE (CS := SAVECHAR) <> ':'; + 825 3 HSOURCE = 0; + 826 3 IF CS = ENDFILE THEN + PL/M-80 COMPILER PAGE 21 + + + 827 3 DO; CALL PRINT(.('END OF FILE, CTL-Z',WHAT,'$')); + 829 4 IF READCHAR = ENDFILE THEN RETURN 1; + 831 4 ELSE HSOURCE = 0; + 832 4 END; + 833 3 CALL CHECKXOFF; + 834 3 END; + + /* ':' FOUND */ + 835 2 CS = 0; + 836 2 IF (RL := READCS) = 0 THEN /* END OF TAPE */ + 837 2 DO; DO WHILE (RL := SAVECHAR) <> ENDFILE; + 839 4 CALL CHECKXOFF; + 840 4 END; + 841 3 IF NOERRS THEN RETURN 1; + 843 3 RETURN 2; + 844 3 END; + + /* RECORD LENGTH IS NOT ZERO */ + 845 2 LDA = READADDR; /* LOAD ADDRESS */ + + /* READ WORDS UNTIL RECORD LENGTH EXHAUSTED */ + 846 2 RT = READCS; /* RECORD TYPE */ + 847 2 DO WHILE RL <> 0 AND NOERRS; RL = RL - 1; + 849 3 M = READCS; + /* INCREMENT LA HERE FOR EXACT ADDRESS */ + 850 3 END; + + /* CHECK SUM */ + 851 2 IF CS + READBYTE <> 0 THEN + 852 2 CALL PRINTERR(.('CHECKSUM ERROR$')); + + 853 2 CALL CHECKXOFF; + 854 2 IF NOERRS THEN RETURN 0; + 856 2 RETURN 2; + 857 2 END HEXRECORD; + + 858 1 READTAPE: PROCEDURE; + /* READ HEX FILE FROM HIGH SPEED READER TO 'HEX' FILE, + CHECK EACH RECORD FOR VALID DIGITS, AND PROPER CHECKSUM */ + 859 2 DECLARE (I,A) BYTE; + 860 2 DO FOREVER; + 861 3 DO WHILE (I := HEXRECORD) <= 1; + 862 4 IF NOT (I = 1 AND IGNOR) THEN + 863 4 DO A = 1 TO HSOURCE; + 864 5 CALL PUTDEST(HBUFF(A-1)); + 865 5 END; + 866 4 CALL PUTDEST(CR); CALL PUTDEST(LF); + 868 4 IF I = 1 THEN /* END OF TAPE ENCOUNTERED */ + 869 4 RETURN; + 870 4 END; + 871 3 CALL CRLF; HBUFF(HSOURCE) = '$'; + 873 3 CALL PRINT(.HBUFF); + 874 3 CALL PRINT(.('CORRECT ERROR, TYPE RETURN OR CTL-Z$')); + 875 3 CALL CRLF; + 876 3 IF READCHAR = ENDFILE THEN RETURN; + 878 3 END; + 879 2 END READTAPE; + PL/M-80 COMPILER PAGE 22 + + + + 880 1 FORMERR: PROCEDURE; + 881 2 CALL ERROR(.('INVALID FORMAT$')); + 882 2 END FORMERR; + + 883 1 SETUPDEST: PROCEDURE; + 884 2 CALL SELECT(DDISK); + 885 2 DHEX = EQUAL(.DEST(FEXT),.('HEX$')); + 886 2 CALL MOVE(.DEST(FEXT),.FEXTH,FEXTL); /* SAVE TYPE */ + 887 2 DEST(ROFILE) = DEST(ROFILE) AND 7FH; + 888 2 DEST(SYSFILE)= DEST(SYSFILE)AND 7FH; + 889 2 CALL MOVEXT(.('$$$')); + 890 2 CALL DELETE(.DEST); /* REMOVE OLD $$$ FILE */ + 891 2 CALL MAKE(.DEST); /* CREATE A NEW ONE */ + 892 2 IF DCNT = 255 THEN CALL ERROR(.('NO DIRECTORY SPACE$')); + 894 2 DEST(32),NDEST = 0; + 895 2 END SETUPDEST; + + 896 1 SETUPSOURCE: PROCEDURE; + 897 2 HARDEOF = 0FFFFH; + 898 2 CALL SETSUSER; /* SOURCE USER */ + 899 2 CALL SELECT(SDISK); + 900 2 CALL OPEN(.SOURCE); + 901 2 CALL SETCUSER; /* BACK TO CURRENT USER */ + 902 2 IF (NOT RSYS) AND ROL(SOURCE(SYSFILE),1) THEN + 903 2 DCNT = 255; + 904 2 IF DCNT = 255 THEN CALL ERROR(.('NO FILE$')); + 906 2 SOURCE(32) = 0; + /* CAUSE IMMEDIATE READ */ + 907 2 SCOM = EQUAL(.SOURCE(FEXT),.('COM$')); + 908 2 NSOURCE = SBLEN; + 909 2 END SETUPSOURCE; + + 910 1 CHECK$STRINGS: PROCEDURE; + 911 2 IF STARTS > 0 THEN + 912 2 CALL ERROR(.('START NOT FOUND$')); + 913 2 IF QUITS > 0 THEN + 914 2 CALL ERROR(.('QUIT NOT FOUND$')); + 915 2 END CHECK$STRINGS; + + 916 1 CLOSEDEST: PROCEDURE(DIRECT); + 917 2 DECLARE DIRECT BYTE; + /* DIRECT IS TRUE IF SECTOR-BY-SECTOR COPY */ + 918 2 IF DIRECT THEN + /* GET UNFILLED BYTES FROM SOURCE BUFFER */ + 919 2 DFUB = SFUB; ELSE DFUB = 0; + 921 2 DO WHILE (LOW(NDEST) AND 7FH) <> 0; + 922 3 DFUB = DFUB + 1; + 923 3 CALL PUTDEST(ENDFILE); + 924 3 END; + 925 2 CALL CHECK$STRINGS; + 926 2 CALL WRITEDEST; + 927 2 CALL SELECT(DDISK); + 928 2 CALL CLOSE(.DEST); + 929 2 IF DCNT = 255 THEN + 930 2 CALL ERROR(.('CANNOT CLOSE DESTINATION FILE$')); + 931 2 CALL MOVEXT(.FEXTH); /* RECALL ORIGINAL TYPTE */ + PL/M-80 COMPILER PAGE 23 + + + 932 2 DEST(12) = 0; + 933 2 CALL OPEN(.DEST); + 934 2 IF DCNT <> 255 THEN /* FILE EXISTS */ + 935 2 DO; + 936 3 IF ROL(DEST(ROFILE),1) THEN /* READ ONLY */ + 937 3 DO; + 938 4 IF NOT WRROF THEN + 939 4 DO; + 940 5 CALL PRINT (.('DESTINATION IS R/O, DELETE (Y/N)?$')); + 941 5 IF UTRAN(READCHAR) <> 'Y' THEN + 942 5 DO; CALL PRINT(.('**NOT DELETED**$')); + 944 6 CALL CRLF; + 945 6 CALL MOVEXT(.('$$$')); + 946 6 CALL DELETE(.DEST); + 947 6 RETURN; + 948 6 END; + 949 5 CALL CRLF; + 950 5 END; + 951 4 DEST(ROFILE) = DEST(ROFILE) AND 7FH; + 952 4 CALL SETIND(.DEST); + 953 4 END; + 954 3 CALL DELETE(.DEST); + 955 3 END; + 956 2 CALL MOVE(.DEST,.DEST(16),16); /* READY FOR RENAME */ + 957 2 CALL MOVEXT(.('$$$')); + 958 2 CALL RENAME(.DEST); + 959 2 END CLOSEDEST; + + 960 1 SIZE$NBUF: PROCEDURE; + /* COMPUTE NUMBER OF BUFFERS - 1 FROM DBLEN */ + 961 2 NBUF = (SHR(DBLEN,7) AND 0FFH) - 1; + /* COMPUTED AS DBLEN/128-1, WHERE DBLEN <= 32K (AND THUS + NBUF RESULTS IN A VALUE <= 2**15/2**7-1 = 2**8-1 = 255) */ + 962 2 END SIZE$NBUF; + + 963 1 SET$DBLEN: PROCEDURE; + /* ABSORB THE SOURCE BUFFER INTO THE DEST BUFFER */ + 964 2 SBASE = .MEMORY; + 965 2 IF DBLEN >= 4000H THEN DBLEN = 7F80H; ELSE + 967 2 DBLEN = DBLEN + SBLEN; + 968 2 CALL SIZE$NBUF; + 969 2 END SET$DBLEN; + + 970 1 SIZE$MEMORY: PROCEDURE; + /* SET UP SOURCE AND DESTINATION BUFFERS */ + 971 2 SBASE = .MEMORY + SHR(MEMSIZE - .MEMORY,1); + 972 2 SBLEN, DBLEN = SHR((MEMSIZE - .MEMORY) AND 0FF00H,1); + 973 2 CALL SIZE$NBUF; + 974 2 END SIZE$MEMORY; + + 975 1 COPYCHAR: PROCEDURE; + /* PERFORM THE ACTUAL COPY FUNCTION */ + 976 2 DECLARE RESIZED BYTE; /* TRUE IF SBUFF AND DBUFF COMBINED */ + 977 2 IF (RESIZED := (BLOCK AND PSOURCE <> 0)) THEN /* BLOCK MODE */ + 978 2 CALL SET$DBLEN; /* ABSORB SOURCE BUFFER */ + 979 2 IF HEXT OR IGNOR THEN /* HEX FILE */ + 980 2 CALL READTAPE; ELSE + PL/M-80 COMPILER PAGE 24 + + + 981 2 DO WHILE NOT READ$EOF; + 982 3 CALL PUTDEST(CHAR); + 983 3 END; + 984 2 IF RESIZED THEN + 985 2 DO; CALL CLEARBUFF; + 987 3 CALL SIZE$MEMORY; + 988 3 END; + 989 2 END COPYCHAR; + + 990 1 SIMPLECOPY: PROCEDURE; + 991 2 DECLARE (FASTCOPY,I) BYTE; + 992 2 REAL$EOF: PROCEDURE BYTE; + 993 3 RETURN HARDEOF <> 0FFFFH; + 994 3 END REALEOF; + 995 2 CALL SIZE$MEMORY; + 996 2 TCBP = MCBP; /* FOR ERROR TRACING */ + 997 2 CALL SETUPDEST; + 998 2 CALL SETUPSOURCE; + /* FILES READY FOR DIRECT COPY */ + 999 2 FASTCOPY = TRUE; + /* LOOK FOR PARAMETERS */ +1000 2 DO I = 0 TO 25; +1001 3 IF CONT(I) <> 0 THEN +1002 3 DO; +1003 4 IF NOT(I=6 OR I=14 OR I=17 OR I=21 OR I=22) THEN + /* NOT OBJ OR VERIFY */ +1004 4 FASTCOPY = FALSE; +1005 4 END; +1006 3 END; +1007 2 IF FASTCOPY THEN /* COPY DIRECTLY TO DBUFF */ +1008 2 DO; CALL SET$DBLEN; /* EXTEND DBUFF */ +1010 3 DO WHILE NOT REAL$EOF; +1011 4 CALL FILLSOURCE; +1012 4 IF REAL$EOF THEN +1013 4 NDEST = HARDEOF; ELSE NDEST = DBLEN; +1015 4 CALL WRITEDEST; +1016 4 END; +1017 3 CALL SIZE$MEMORY; /* RESET TO TWO BUFFERS */ +1018 3 END; ELSE +1019 2 CALL COPYCHAR; +1020 2 CALL CLOSEDEST(FASTCOPY); +1021 2 END SIMPLECOPY; + +1022 1 MULTCOPY: PROCEDURE; +1023 2 DECLARE (NEXTDIR, NDCNT, NCOPIED) ADDRESS; +1024 2 PRNAME: PROCEDURE; + /* PRINT CURRENT FILE NAME */ +1025 3 DECLARE (I,C) BYTE; +1026 3 CALL CRLF; +1027 3 DO I = 1 TO FNSIZE; +1028 4 IF (C := DEST(I)) <> ' ' THEN +1029 4 DO; IF I = FEXT THEN CALL PRINTCHAR('.'); +1032 5 CALL PRINTCHAR(C); +1033 5 END; +1034 4 END; +1035 3 END PRNAME; + + PL/M-80 COMPILER PAGE 25 + + +1036 2 NEXTDIR,NCOPIED = 0; +1037 2 DO FOREVER; + /* FIND A MATCHING ENTRY */ +1038 3 CALL SETSUSER; /* SOURCE USER */ +1039 3 CALL SELECT(SDISK); +1040 3 CALL SETDMA(.BUFFER); +1041 3 CALL SEARCH(.SEARFCB); +1042 3 NDCNT = 0; +1043 3 DO WHILE (DCNT <> 255) AND NDCNT < NEXTDIR; +1044 4 NDCNT = NDCNT + 1; +1045 4 CALL SEARCHN; +1046 4 END; +1047 3 CALL SETCUSER; + /* FILE CONTROL BLOCK IN BUFFER */ +1048 3 IF DCNT = 255 THEN +1049 3 DO; IF NCOPIED = 0 THEN +1051 4 CALL ERROR(.('NOT FOUND$')); CALL CRLF; +1053 4 RETURN; +1054 4 END; +1055 3 NEXTDIR = NDCNT + 1; + /* GET THE FILE CONTROL BLOCK NAME TO DEST */ +1056 3 CALL MOVE(.BUFFER+SHL(DCNT AND 11B,5),.DEST,16); +1057 3 DEST(0) = 0; +1058 3 DEST(12) = 0; +1059 3 CALL MOVE(.DEST,.SOURCE,16); /* FILL BOTH FCB'S */ +1060 3 IF RSYS OR NOT ROL(DEST(SYSFILE),1) THEN /* OK TO READ */ +1061 3 DO; +1062 4 IF (NCOPIED := NCOPIED + 1) = 1 THEN +1063 4 CALL PRINT(.('COPYING -$')); +1064 4 CALL PRNAME; +1065 4 CALL SIMPLECOPY; +1066 4 END; +1067 3 END; +1068 2 END MULTCOPY; + +1069 1 SET$SDISK: PROCEDURE; +1070 2 IF DISK > 0 THEN SDISK = DISK - 1; ELSE SDISK = CDISK; +1073 2 END SET$SDISK; + +1074 1 SET$DDISK: PROCEDURE; +1075 2 IF PARSET THEN /* PARAMETERS PRESENT */ CALL FORMERR; +1077 2 IF DISK > 0 THEN DDISK = DISK - 1; ELSE DDISK = CDISK; +1080 2 END SET$DDISK; + +1081 1 CHECK$DISK: PROCEDURE; +1082 2 IF SUSER <> CUSER THEN /* DIFFERENT DISKS */ +1083 2 RETURN; +1084 2 IF DDISK = SDISK THEN CALL FORMERR; +1086 2 END CHECK$DISK; + +1087 1 CHECK$EOL: PROCEDURE; +1088 2 CALL DEBLANK; +1089 2 IF CHAR <> CR THEN CALL FORMERR; +1091 2 END CHECK$EOL; + +1092 1 SCANDEST: PROCEDURE(COPYFCB); +1093 2 DECLARE COPYFCB ADDRESS; + PL/M-80 COMPILER PAGE 26 + + +1094 2 CALL SET$SDISK; +1095 2 CALL CHECK$EOL; +1096 2 CALL MOVE(.SOURCE,COPYFCB,33); +1097 2 CALL CHECK$DISK; +1098 2 END SCANDEST; + +1099 1 SCANEQL: PROCEDURE; +1100 2 CALL SCAN(.SOURCE); +1101 2 IF NOT (TYPE = SPECL AND CHAR = '=') THEN CALL FORMERR; +1103 2 MCBP = CBP; /* FOR ERROR PRINTING */ +1104 2 END SCANEQL; + + +1105 1 PIPENTRY: + /* BUFFER AT 80H CONTAINS REMAINDER OF LINE TYPED + FOLLOWING THE COMMAND 'PIP' - IF ZERO THEN PROMPT TIL CR */ + CALL MOVE(.BUFF,.COMLEN,80H); +1106 1 MULTCOM = COMLEN = 0; + + /* GET CURRENT CP/M VERSION */ +1107 1 IF VERSION < CPMVERSION THEN +1108 1 DO; +1109 2 CALL PRINT(.('REQUIRES CP/M 2.0 OR NEWER FOR OPERATION.$')); +1110 2 CALL BOOT; +1111 2 END; + /* GET CURRENT USER */ +1112 1 CUSER = GETUSER; + /* GET CURRENT DISK */ +1113 1 CDISK = MON2(25,0); + +1114 1 RETRY: + /* ENTER HERE ON ERROR EXIT FROM THE PROCEDURE 'ERROR' */ + CALL SIZE$MEMORY; + /* MAIN PROCESSING LOOP. PROCESS UNTIL CR ONLY */ +1115 1 DO FOREVER; +1116 2 SUSER = CUSER; +1117 2 C1, C2, C3 = 0; /* LINE COUNT = 000000 */ +1118 2 PUTNUM = TRUE; /* ACTS LIKE LF OCCURRED ON ASCII FILE */ +1119 2 CONCNT,COLUMN = 0; /* PRINTER TABS */ +1120 2 LINENO = 254; /* INCREMENTED TO 255 > PAGCNT */ + /* READ FROM CONSOLE IF NOT A ONELINER */ +1121 2 IF MULTCOM THEN +1122 2 DO; CALL PRINTCHAR('*'); CALL READCOM; +1125 3 CALL CRLF; +1126 3 END; +1127 2 CBP = 255; +1128 2 IF COMLEN = 0 THEN /* SINGLE CARRIAGE RETURN */ +1129 2 DO; CALL SELECT(CDISK); +1131 3 CALL BOOT; +1132 3 END; + + /* LOOK FOR SPECIAL CASES FIRST */ +1133 2 DDISK,SDISK,PSOURCE,PDEST = 0; +1134 2 CALL SCAN(.DEST); +1135 2 IF TYPE = PERIPH THEN GO TO SIMPLECOM; +1137 2 IF TYPE = DISKNAME THEN +1138 2 DO; DDISK = DISK - 1; + PL/M-80 COMPILER PAGE 27 + + +1140 3 CALL SCANEQL; +1141 3 CALL SCAN(.SOURCE); + /* MAY BE MULTI COPY */ +1142 3 IF TYPE <> FILE THEN CALL FORMERR; +1144 3 IF AMBIG THEN +1145 3 DO; CALL SCANDEST(.SEARFCB); +1147 4 CALL MULTCOPY; +1148 4 END; ELSE +1149 3 DO; CALL SCANDEST(.DEST); + /* FORM IS A:=B:UFN */ +1151 4 CALL SIMPLECOPY; +1152 4 END; +1153 3 GO TO ENDCOM; +1154 3 END; + + +1155 2 IF TYPE <> FILE OR AMBIG THEN CALL FORMERR; +1157 2 CALL SET$DDISK; +1158 2 CALL SCANEQL; +1159 2 CALL SCAN(.SOURCE); +1160 2 IF TYPE = DISKNAME THEN +1161 2 DO; +1162 3 CALL SET$SDISK; CALL CHECK$DISK; +1164 3 CALL MOVE(.DEST,.SOURCE,33); +1165 3 CALL CHECK$EOL; +1166 3 CALL SIMPLECOPY; +1167 3 GO TO ENDCOM; +1168 3 END; + /* MAY BE POSSIBLE TO DO A FAST DISK COPY */ +1169 2 IF TYPE = FILE THEN /* FILE TO FILE */ +1170 2 DO; CALL DEBLANK; IF CHAR <> CR THEN GO TO SIMPLECOM; + /* FILE TO FILE */ +1174 3 CALL SET$SDISK; +1175 3 CALL SIMPLECOPY; +1176 3 GO TO ENDCOM; +1177 3 END; + +1178 2 SIMPLECOM: + CBP = 255; /* READY FOR RESCAN */ + + /* OTHERWISE PROCESS SIMPLE REQUEST */ +1179 2 CALL SCAN(.DEST); +1180 2 IF (TYPE < FILE) OR AMBIG THEN /* DELIMITER OR ERROR */ +1181 2 CALL ERROR(.('UNRECOGNIZED DESTINATION$')); + +1182 2 DHEX = FALSE; +1183 2 IF TYPE = FILE THEN +1184 2 DO; /* DESTINATION IS A FILE, SAVE EXTENT NAME */ +1185 3 CALL SET$DDISK; +1186 3 CALL SETUPDEST; +1187 3 CHAR = 255; +1188 3 END; ELSE + /* PERIPHERAL NAME */ +1189 2 IF CHAR >= NULP OR CHAR <= RDR THEN CALL ERROR(.('CANNOT WRITE$')); + + IF (PDEST := CHAR + 1) = PUNP THEN CALL NULLS; + + PL/M-80 COMPILER PAGE 28 + + + /* NOW SCAN THE DELIMITER */ +1193 2 CALL SCAN(.SOURCE); +1194 2 IF TYPE <> SPECL OR CHAR <> '=' THEN +1195 2 CALL ERROR(.('INVALID PIP FORMAT$')); + + /* OTHERWISE SCAN AND COPY UNTIL CR */ +1196 2 COPYING = TRUE; +1197 2 DO WHILE COPYING; +1198 3 SUSER = CUSER; +1199 3 CALL SCAN(.SOURCE); + /* SUSER MAY HAVE BEEN RESET */ +1200 3 SCOM = FALSE; +1201 3 IF TYPE = FILE AND NOT AMBIG THEN /* A SOURCE FILE */ +1202 3 DO; +1203 4 CALL SET$SDISK; +1204 4 CALL SETUPSOURCE; +1205 4 CHAR = 255; +1206 4 END; ELSE + +1207 3 IF TYPE <> PERIPH OR (CHAR <= LST AND CHAR > RDR) THEN +1208 3 CALL ERROR(.('CANNOT READ$')); + + + SCOM = SCOM OR OBJ; /* MAY BE ABSOLUTE COPY */ +1210 3 PSOURCE = CHAR + 1; +1211 3 IF CHAR = NULP THEN CALL NULLS; ELSE +1213 3 IF CHAR = EOFP THEN CALL PUTDEST(ENDFILE); ELSE +1215 3 DO; /* DISK COPY */ +1216 4 IF (CHAR < HSRDR AND DHEX) THEN HEXT = 1; + /* HEX FILE SET IF SOURCE IS RDR AND DEST IS HEX FILE */ +1218 4 IF PDEST = PRNT THEN +1219 4 DO; NUMB = 1; +1221 5 IF TABS = 0 THEN TABS = 8; +1223 5 IF PAGCNT = 0 THEN PAGCNT = 1; +1225 5 END; +1226 4 CALL COPYCHAR; +1227 4 END; + +1228 3 CALL CHECK$STRINGS; + /* READ ENDFILE, GO TO NEXT SOURCE */ +1229 3 CALL SCAN(.SOURCE); +1230 3 IF TYPE <> SPECL OR (CHAR <> ',' AND CHAR <> CR) THEN +1231 3 CALL ERROR(.('INVALID SEPARATOR$')); + +1232 3 COPYING = CHAR <> CR; +1233 3 END; + + /* IF NECESSARY, CLOSE FILE OR PUNCH TRAILER */ +1234 2 IF PDEST = PUNP THEN +1235 2 DO; CALL PUTDEST(ENDFILE); CALL NULLS; +1238 3 END; +1239 2 IF PDEST = 0 THEN /* FILE HAS TO BE CLOSED AND RENAMED */ +1240 2 CALL CLOSEDEST(FALSE); + + /* COMLEN SET TO 0 IF NOT PROCESSING MULTIPLE COMMANDS */ +1241 2 ENDCOM: + COMLEN = MULTCOM; + PL/M-80 COMPILER PAGE 29 + + + +1242 2 END; /* DO FOREVER */ +1243 1 END; + + + + +MODULE INFORMATION: + + CODE AREA SIZE = 1C34H 7220D + VARIABLE AREA SIZE = 01D8H 472D + MAXIMUM STACK SIZE = 0034H 52D + 1594 LINES READ + 0 PROGRAM ERROR(S) + +END OF PL/M-80 COMPILATION + \ No newline at end of file diff --git a/ISIS PLM/PIP.MOD b/ISIS PLM/PIP.MOD new file mode 100644 index 0000000..c37a39a Binary files /dev/null and b/ISIS PLM/PIP.MOD differ diff --git a/ISIS PLM/PIP.OBJ b/ISIS PLM/PIP.OBJ new file mode 100644 index 0000000..a5d1dbf Binary files /dev/null and b/ISIS PLM/PIP.OBJ differ diff --git a/ISIS PLM/PIP.PLM b/ISIS PLM/PIP.PLM new file mode 100644 index 0000000..da6d3de --- /dev/null +++ b/ISIS PLM/PIP.PLM @@ -0,0 +1,1594 @@ +PIPMOD: +DO; +/* P E R I P H E R A L I N T E R C H A N G E P R O G R A M + + COPYRIGHT (C) 1976, 1977, 1978, 1979, 1980 + DIGITAL RESEARCH + BOX 579 + PACIFIC GROVE, CA + 93950 + */ + +DECLARE + CPMVERSION LITERALLY '0020H'; /* REQUIRED FOR OPERATION */ + +DECLARE + IOBYTE BYTE EXTERNAL, /* IOBYTE AT 0003H */ + MAXB ADDRESS EXTERNAL, /* ADDR FIELD OF JMP BDOS */ + FCB (33) BYTE EXTERNAL, /* DEFAULT FILE CONTROL BLOCK */ + BUFF(128)BYTE EXTERNAL; /* DEFAULT BUFFER */ + +DECLARE + ENDFILE LITERALLY '1AH', /* END OF FILE MARK */ + JMP LITERALLY '0C3H', /* 8080 JUMP INSTRUCTION */ + RET LITERALLY '0C9H'; /* 8080 RETURN */ + +/* THE FIRST PORTION OF THE PIP PROGRAM 'FAKES' THE PAGE ONE +(100H - 1FFH) SECTION OF PIP WHICH CONTAINS A JUMP TO PIPENTRY, AND +SPACE FOR CUSTOM I/O DRIVERS (WHICH CAN BE 'PATCHED' USING DDT) IN THE +REMAINING PAGE ONE AREA. THE PIP PROGRAM ACTUALLY STARTS AT 200H */ + +DECLARE JUMP BYTE DATA(JMP); /* JMP INSTRUCTION TO */ +/* JMP .PIPENTRY-3 WHERE THE LXI SP,STACK ACTUALLY OCCURS */ +DECLARE JADR ADDRESS DATA(.PIPENTRY-3); /* START OF PIP */ +DECLARE INPSUB(3) BYTE DATA(RET,0,0); /* INP: RET NOP NOP */ +DECLARE OUTSUB(3) BYTE DATA(RET,0,0); /* OUT: RET NOP NOP */ +DECLARE INPDATA BYTE DATA(ENDFILE); /* RETURNED DATA */ + /* NOTE: PAGE 1 AT 100H CONTAINS THE FOLLOWING + 100H: JMP PIPENTRY ;TO START THE PIP PROGRAM + 103H: RET ;INP: DEFAULTS TO EMPTY INPUT (DATA 1AH AT 109H) + 104H: NOP + 105H: NOP + 106H: RET ;OUT: DEFAULTS TO EMPTY OUTPUT + 107H: NOP + 108H: NOP + 109H: 1AH=ENDFILE ;DATA FROM INP: FUNCTION IS STORED HERE ON + ;RETURN FROM THE INP: ENTRY POINT + 10AH: - 1FFH ;SPACE RESERVED FOR SPECIAL PURPOSE + ; DRIVERS - IF INCLUDED, THEN REPLACE 103H AND 106H BY JMP'S + ; TO THE PROPER LOCATIONS WITHIN THE RESERVED AREA. + ; ALSO, RETURN DATA FROM INP: ENTRY POINT AT 109H. + ; THESE DRIVERS ARE MOST EASILY INSERTED WITH THE DDT PROGRAM + ; UNDER CP/M + */ + +DECLARE /* 16 BYTE MESSAGE */ + FREEMEMORY LITERALLY '''(INP:/OUT:SPACE)''', + /* 256 BYTE AREA FOR INP: OUT: PATCHING */ + RESERVED(*) BYTE DATA(0,0,0,0,0,0, + FREEMEMORY, FREEMEMORY, FREEMEMORY, + FREEMEMORY, FREEMEMORY, FREEMEMORY, FREEMEMORY, + FREEMEMORY, FREEMEMORY, FREEMEMORY, FREEMEMORY, + FREEMEMORY, FREEMEMORY, FREEMEMORY, FREEMEMORY); + + + + + DECLARE COPYRIGHT(*) BYTE DATA ( + ' COPYRIGHT (C) 1979, DIGITAL RESEARCH, PIP VERS 1.5'); + + DECLARE INPLOC ADDRESS DATA (.INPSUB); /* ADDRESS OF INP: DEVICE */ + DECLARE OUTLOC ADDRESS DATA (.OUTSUB); /* ADDRESS OF OUT: DEVICE */ + +OUT: PROCEDURE(B); + DECLARE B BYTE; + /* SEND B TO OUT: DEVICE */ + CALL OUTLOC; + END OUT; + +INP: PROCEDURE BYTE; + CALL INPLOC; + RETURN INPDATA; + END INP; + + +TIMEOUT: PROCEDURE; + /* WAIT FOR 50 MSEC */ + CALL TIME(250); CALL TIME(250); + END TIMEOUT; + + /* LITERAL DECLARATIONS */ + DECLARE + LIT LITERALLY 'LITERALLY', + LPP LIT '60', /* LINES PER PAGE */ + TAB LIT '09H', /* HORIZONTAL TAB */ + FF LIT '0CH', /* FORM FEED */ + LA LIT '05FH', /* LEFT ARROW */ + LB LIT '05BH', /* LEFT BRACKET */ + RB LIT '05DH', /* RIGHT BRACKET */ + XOFF LIT '13H', /* TRANSMIT BUFFER FUNCTION */ + + RDR LIT '5', + LST LIT '10', + PUNP LIT '15', /* POSITION OF 'PUN' + 1 */ + CONP LIT '19', /* CONSOLE */ + NULP LIT '19', /* NUL: BEFORE INCREMENT */ + EOFP LIT '20', /* EOF: BEFORE INCREMENT */ + HSRDR LIT 'RDR', /* READER DEVICES */ + PRNT LIT '10', /* PRINTER */ + + + FSIZE LIT '33', + FRSIZE LIT '36', /* SIZE OF RANDOM FCB */ + NSIZE LIT '8', + FNSIZE LIT '11', + MDISK LIT '1', + FNAM LIT '8', + FEXT LIT '9', + FEXTL LIT '3', + ROFILE LITERALLY '9', /* READ ONLY FILE FIELD */ + SYSFILE LITERALLY '10', /* SYSTEM FILE FIELD */ + FREEL LIT '12', /* REEL NUMBER FIELD OF FCB */ + + HBUFS LIT '80', /* "HEX" BUFFER SIZE */ + + ERR LIT '0', + SPECL LIT '1', + FILE LIT '2', + PERIPH LIT '3', + DISKNAME LIT '4'; + +DECLARE + COLUMN BYTE, /* COLUMN COUNT FOR PRINTER TABS */ + LINENO BYTE, /* LINE WITHIN PAGE */ + AMBIG BYTE, /* SET FOR AMBIGUOUS FILE REFS */ + PARSET BYTE, /* TRUE IF PARAMETERS PRESENT */ + FEEDBASE BYTE, /* USED TO FEED SEARCH CHARACTERS */ + FEEDLEN BYTE, /* LENGTH OF FEED STRING */ + MATCHLEN BYTE, /* USED IN MATCHING STRINGS */ + QUITLEN BYTE, /* USED TO TERMINATE QUIT COMMAND */ + NBUF BYTE, /* NUM BUFFERS-1 IN SBUFF AND DBUFF */ + CDISK BYTE, /* CURRENT DISK */ + BUFFER LITERALLY 'BUFF', /* DEFAULT BUFFER */ + SEARFCB LITERALLY 'FCB', /* SEARCH FCB IN MULTI COPY */ + MEMSIZE LITERALLY 'MAXB', /* MEMORY SIZE */ + SBLEN ADDRESS, /* SOURCE BUFFER LENGTH */ + DBLEN ADDRESS, /* DEST BUFFER LENGTH */ + SBASE ADDRESS, /* SOURCE BUFFER BASE */ + /* THE VECTORS DBUFF AND SBUFF ARE DECLARED WITH DIMENSION + 1024, BUT ACTUALLY VARY WITH THE FREE MEMORY SIZE */ + DBUFF(1024) BYTE AT (.MEMORY), /* DESTINATION BUFFER */ + SBUFF BASED SBASE (1024) BYTE, /* SOURCE BUFFER */ + SDISK BYTE, /* SOURCE DISK */ + (SCOM, DHEX) BYTE, /* SOURCE IS 'COM' FILE IF TRUE */ + /* DEST IS 'HEX' FILE IF TRUE */ + SOURCE (FSIZE) BYTE, /* SOURCE FCB */ + SFUB BYTE AT(.SOURCE(13)), /* UNFILLED BYTES FIELD */ + DEST (FRSIZE) BYTE, /* DESTINATION FCB */ + DESTR ADDRESS AT(.DEST(33)), /* RANDOM RECORD POSITION */ + DESTO BYTE AT(.DEST(35)), /* RANDOM OVERFLOW BYTE */ + DFUB BYTE AT (.DEST(13)), /* UNFILLED BYTES FIELD */ + DDISK BYTE, /* DESTINATION DISK */ + HBUFF(HBUFS) BYTE, /* HEX FILE BUFFER */ + HSOURCE BYTE, /* NEXT HEX SOURCE CHARACTER */ + + NSOURCE ADDRESS, /* NEXT SOURCE CHARACTER */ + HARDEOF ADDRESS, /* SET TO NSOURCE ON REAL EOF */ + NDEST ADDRESS; /* NEXT DESTINATION CHARACTER */ + +DECLARE + /* SUBMIT FILE CONTROL BLOCK FOR ERROR DELETE */ + SUBFCB (*) BYTE DATA (0,'$$$ SUB',0,0,0); + + DECLARE + PDEST BYTE, /* DESTINATION DEVICE */ + PSOURCE BYTE; /* CURRENT SOURCE DEVICE */ + + DECLARE + MULTCOM BYTE, /* FALSE IF PROCESSING ONE LINE */ + PUTNUM BYTE, /* SET WHEN READY FOR NEXT LINE NUM */ + CONCNT BYTE, /* COUNTER FOR CONSOLE READY CHECK */ + CHAR BYTE, /* LAST CHARACTER SCANNED */ + TYPE BYTE, /* TYPE OF CHARACTER SCANNED */ + FLEN BYTE; /* FILE NAME LENGTH */ + +MON1: PROCEDURE(F,A) EXTERNAL; + DECLARE F BYTE, + A ADDRESS; + END MON1; + +MON2: PROCEDURE(F,A) BYTE EXTERNAL; + DECLARE F BYTE, + A ADDRESS; + END MON2; + +MON3: PROCEDURE(F,A) ADDRESS EXTERNAL; + DECLARE F BYTE, + A ADDRESS; + END MON3; + +BOOT: PROCEDURE EXTERNAL; + /* SYSTEM REBOOT */ + END BOOT; + +READRDR: PROCEDURE BYTE; + /* READ CURRENT READER DEVICE */ + RETURN MON2(3,0); + END READRDR; + +READCHAR: PROCEDURE BYTE; + /* READ CONSOLE CHARACTER */ + RETURN MON2(1,0); + END READCHAR; + +DECLARE + TRUE LITERALLY '1', + FALSE LITERALLY '0', + FOREVER LITERALLY 'WHILE TRUE', + CR LITERALLY '13', + LF LITERALLY '10', + WHAT LITERALLY '63'; + +PRINTCHAR: PROCEDURE(CHAR); + DECLARE CHAR BYTE; + CALL MON1(2,CHAR AND 7FH); + END PRINTCHAR; + +CRLF: PROCEDURE; + CALL PRINTCHAR(CR); + CALL PRINTCHAR(LF); + END CRLF; + +PRINT: PROCEDURE(A); + DECLARE A ADDRESS; + /* PRINT THE STRING STARTING AT ADDRESS A UNTIL THE + NEXT DOLLAR SIGN IS ENCOUNTERED */ + CALL CRLF; + CALL MON1(9,A); + END PRINT; + +DECLARE DCNT BYTE; + +VERSION: PROCEDURE ADDRESS; + RETURN MON3(12,0); /* VERSION NUMBER */ + END VERSION; + +INITIALIZE: PROCEDURE; + CALL MON1(13,0); + END INITIALIZE; + +SELECT: PROCEDURE(D); + DECLARE D BYTE; + CALL MON1(14,D); + END SELECT; + +OPEN: PROCEDURE(FCB); + DECLARE FCB ADDRESS; + DCNT = MON2(15,FCB); + END OPEN; + +CLOSE: PROCEDURE(FCB); + DECLARE FCB ADDRESS; + DCNT = MON2(16,FCB); + END CLOSE; + +SEARCH: PROCEDURE(FCB); + DECLARE FCB ADDRESS; + DCNT = MON2(17,FCB); + END SEARCH; + +SEARCHN: PROCEDURE; + DCNT = MON2(18,0); + END SEARCHN; + +DELETE: PROCEDURE(FCB); + DECLARE FCB ADDRESS; + CALL MON1(19,FCB); + END DELETE; + +DISKREAD: PROCEDURE(FCB) BYTE; + DECLARE FCB ADDRESS; + RETURN MON2(20,FCB); + END DISKREAD; + +DISKWRITE: PROCEDURE(FCB) BYTE; + DECLARE FCB ADDRESS; + RETURN MON2(21,FCB); + END DISKWRITE; + +MAKE: PROCEDURE(FCB); + DECLARE FCB ADDRESS; + DCNT = MON2(22,FCB); + END MAKE; + +RENAME: PROCEDURE(FCB); + DECLARE FCB ADDRESS; + CALL MON1(23,FCB); + END RENAME; + +DECLARE + CUSER BYTE, /* CURRENT USER NUMBER */ + SUSER BYTE; /* SOURCE USER NUMBER ('G' PARAMETER) */ + +SETIND: PROCEDURE(FCB); + DECLARE FCB ADDRESS; + CALL MON1(30,FCB); + END SETIND; + +GETUSER: PROCEDURE BYTE; + RETURN MON2(32,0FFH); + END GETUSER; + +SETUSER: PROCEDURE(USER); + DECLARE USER BYTE; + CALL MON1(32,USER); + END SETUSER; + +SETCUSER: PROCEDURE; + CALL SETUSER(CUSER); + END SETCUSER; + +SETSUSER: PROCEDURE; + CALL SETUSER(SUSER); + END SETSUSER; + +READ$RANDOM: PROCEDURE(FCB) BYTE; + DECLARE FCB ADDRESS; + RETURN MON2(33,FCB); + END READ$RANDOM; + +WRITE$RANDOM: PROCEDURE(FCB) BYTE; + DECLARE FCB ADDRESS; + RETURN MON2(34,FCB); + END WRITE$RANDOM; + +SET$RANDOM: PROCEDURE(FCB); + DECLARE FCB ADDRESS; + /* SET RANDOM RECORD POSITION */ + CALL MON1(36,FCB); + END SET$RANDOM; + +DECLARE CBUFF(130) BYTE, /* COMMAND BUFFER */ + MAXLEN BYTE AT (.CBUFF(0)), /* MAX BUFFER LENGTH */ + COMLEN BYTE AT (.CBUFF(1)), /* CURRENT LENGTH */ + COMBUFF (128) BYTE AT (.CBUFF(2)); /* COMMAND BUFFER CONTENTS */ +DECLARE (TCBP,CBP) BYTE; /* TEMP CBP, COMMAND BUFFER POINTER */ + +READCOM: PROCEDURE; + /* READ INTO COMMAND BUFFER */ + MAXLEN = 128; + CALL MON1(10,.MAXLEN); + END READCOM; + +DECLARE MCBP BYTE; + +CONBRK: PROCEDURE BYTE; + /* CHECK CONSOLE CHARACTER READY */ + RETURN MON2(11,0); + END CONBRK; + +DECLARE /* CONTROL TOGGLE VECTOR */ + CONT(26) BYTE, /* ONE FOR EACH ALPHABETIC */ + /* 00 01 02 03 04 05 06 07 08 09 10 11 12 13 + A B C D E F G H I J K L M N + 14 15 16 17 18 19 20 21 22 23 24 25 + O P Q R S T U V W X Y Z */ + BLOCK BYTE AT(.CONT(1)), /* BLOCK MODE TRANSFER */ + DELET BYTE AT(.CONT(3)), /* DELETE CHARACTERS */ + ECHO BYTE AT(.CONT(4)), /* ECHO CONSOLE CHARACTERS */ + FORMF BYTE AT(.CONT(5)), /* FORM FILTER */ + GETU BYTE AT(.CONT(6)), /* GET FILE, USER # */ + HEXT BYTE AT(.CONT(7)), /* HEX FILE TRANSFER */ + IGNOR BYTE AT(.CONT(8)), /* IGNORE :00 RECORD ON FILE */ + LOWER BYTE AT(.CONT(11)), /* TRANSLATE TO LOWER CASE */ + NUMB BYTE AT(.CONT(13)), /* NUMBER OUTPUT LINES */ + OBJ BYTE AT(.CONT(14)), /* OBJECT FILE TRANSFER */ + PAGCNT BYTE AT(.CONT(15)), /* PAGE LENGTH */ + QUITS BYTE AT(.CONT(16)), /* QUIT COPY */ + RSYS BYTE AT(.CONT(17)), /* READ SYSTEM FILES */ + STARTS BYTE AT(.CONT(18)), /* START COPY */ + TABS BYTE AT(.CONT(19)), /* TAB SET */ + UPPER BYTE AT(.CONT(20)), /* UPPER CASE TRANSLATE */ + VERIF BYTE AT(.CONT(21)), /* VERIFY EQUAL FILES ONLY */ + WRROF BYTE AT(.CONT(22)), /* WRITE TO R/O FILE */ + ZEROP BYTE AT(.CONT(25)); /* ZERO PARITY ON INPUT */ + + SETDMA: PROCEDURE(A); + DECLARE A ADDRESS; + CALL MON1(26,A); + END SETDMA; + + /* INTELLEC 8 INTEL/ICOM READER INPUT */ + +INTIN: PROCEDURE BYTE; + /* READ THE INTEL / ICOM READER */ + DECLARE PTRI LITERALLY '3', /* DATA */ + PTRS LITERALLY '1', /* STATUS */ + PTRC LITERALLY '1', /* COMMAND */ + PTRG LITERALLY '0CH', /* GO */ + PTRN LITERALLY '08H'; /* STOP */ + + /* STROBE THE READER */ + OUTPUT(PTRC) = PTRG; + OUTPUT(PTRC) = PTRN; + DO WHILE NOT ROL(INPUT(PTRS),3); /* NOT READY */ + END; + /* DATA READY */ + RETURN INPUT(PTRI) AND 7FH; + END INTIN; + + +DECLARE ZEROSUP BYTE, /* ZERO SUPPRESSION */ + (C3,C2,C1) BYTE; /* LINE COUNT ON PRINTER */ + + ERROR: PROCEDURE(A); + DECLARE A ADDRESS, I BYTE; + CALL SETCUSER; + CALL PRINT(A); CALL PRINTCHAR(':'); CALL PRINTCHAR(' '); + DO I = TCBP TO CBP; + IF I < COMLEN THEN CALL PRINTCHAR(COMBUFF(I)); + END; + /* ZERO THE COMLEN IN CASE THIS IS A SINGLE COMMAND */ + COMLEN = 0; + /* DELETE ANY $$$.SUB FILES IN CASE BATCH PROCESSING */ + /* DELETE SUB FILE ONLY IF PRESENT (MAY BE R/O DISK) */ + CALL SEARCH(.SUBFCB); + IF DCNT <> 255 THEN CALL DELETE(.SUBFCB); + CALL CRLF; + GO TO RETRY; + END ERROR; + + MOVE: PROCEDURE(S,D,N); + DECLARE (S,D) ADDRESS, N BYTE; + DECLARE A BASED S BYTE, B BASED D BYTE; + DO WHILE (N:=N-1) <> 255; + B = A; S = S+1; D = D+1; + END; + END MOVE; + + + FILLSOURCE: PROCEDURE; + /* FILL THE SOURCE BUFFERS */ + DECLARE (I,J) BYTE; + NSOURCE = 0; + CALL SELECT(SDISK); + CALL SETSUSER; /* SOURCE USER NUMBER SET */ + DO I = 0 TO NBUF; + /* SET DMA ADDRESS TO NEXT BUFFER POSIITION */ + CALL SETDMA(.SBUFF(NSOURCE)); + IF (J := DISKREAD(.SOURCE)) <> 0 THEN + DO; IF J <> 1 THEN + CALL ERROR(.('DISK READ ERROR$')); + /* END - OF - FILE */ + HARDEOF = NSOURCE; /* SET HARD END-OF-FILE */ + SBUFF(NSOURCE) = ENDFILE; I = NBUF; + END; ELSE + NSOURCE = NSOURCE + 128; + END; + NSOURCE = 0; + CALL SETCUSER; /* BACK TO CURRENT USER NUMBER */ + END FILLSOURCE; + + + WRITEDEST: PROCEDURE; + /* WRITE OUTPUT BUFFERS UP TO BUT NOT INCLUDING POSITION + NDEST - THE LOW ORDER 7 BITS OF NDEST ARE ZERO */ + DECLARE (I, J, N) BYTE; + DECLARE DMA ADDRESS; + DECLARE DATAOK BYTE; + IF (N := LOW(SHR(NDEST,7)) - 1) = 255 THEN RETURN ; + NDEST = 0; + CALL SELECT(DDISK); + CALL SETRANDOM(.DEST); /* SET BASE RECORD FOR VERIFY */ + DO I = 0 TO N; + /* SET DMA ADDRESS TO NEXT BUFFER */ + DMA = .DBUFF(NDEST); + CALL SETDMA(DMA); + IF DISKWRITE(.DEST) <> 0 THEN + CALL ERROR(.('DISK WRITE ERROR$')); + NDEST = NDEST + 128; + END; + IF VERIF THEN /* VERIFY DATA WRITTEN OK */ + DO; + NDEST = 0; + CALL SETDMA(.BUFF); /* FOR COMPARE */ + DO I = 0 TO N; + DATAOK = READRANDOM(.DEST) = 0; + DESTR = DESTR + 1; /* NEXT RANDOM READ */ + J = 0; + /* PERFORM COMPARISON */ + DO WHILE DATAOK AND J < 80H; + DATAOK = BUFFER(J) = DBUFF(NDEST+J); + J = J + 1; + END; + NDEST = NDEST + 128; + IF NOT DATAOK THEN + CALL ERROR(.('VERIFY ERROR$')); + END; + DATAOK = DISKWRITE(.DEST); + /* NOW READY TO CONTINUE THE WRITE OPERATION */ + END; + NDEST = 0; + END WRITEDEST; + + PUTDCHAR: PROCEDURE(B); + DECLARE (B,IOB) BYTE; + /* WRITE BYTE B TO THE DESTINATION DEVICE GIVEN BY PDEST */ + IF B >= ' ' THEN + DO; COLUMN = COLUMN + 1; + IF DELET > 0 THEN /* MAY BE PAST RIGHT SIDE */ + DO; IF COLUMN > DELET THEN RETURN; + END; + END; + IOB = IOBYTE; /* IN CASE IT IS ALTERED */ + DO CASE PDEST; + /* CASE 0 IS THE DESTINATION FILE */ + DO; + IF NDEST >= DBLEN THEN CALL WRITEDEST; + DBUFF(NDEST) = B; + NDEST = NDEST+1; + END; + /* CASE 1 IS ARD (ADDMASTER) */ + GO TO NOTDEST; + /* CASE 2 IS IRD (INTEL/ICOM) */ + GO TO NOTDEST; + /* CASE 3 IS PTR */ + GO TO NOTDEST; + /* CASE 4 IS UR1 */ + GO TO NOTDEST; + /* CASE 5 IS UR2 */ + GO TO NOTDEST; + /* CASE 6 IS RDR */ + NOTDEST: + CALL ERROR(.('NOT A CHARACTER SINK$')); + /* CASE 7 IS OUT */ + CALL OUT(B); + /* CASE 8 IS LPT */ + DO; IOBYTE = 1000$0000B; GO TO LSTL; + END; + /* CASE 9 IS UL1 */ + DO; IOBYTE = 1100$0000B; GO TO LSTL; + END; + /* CASE 10 IS PRN (TABS EXPANDED, LINES LISTED, CHANGED TO LST) */ + DO; IOBYTE = 1000$0000B; GO TO LSTL; + END; + /* CASE 11 IS LST */ + LSTL: + CALL MON1(5,B); + /* CASE 12 IS PTP */ + DO; IOBYTE = 0001$0000B; GO TO PUNL; + END; + /* CASE 13 IS UP1 */ + DO; IOBYTE = 0010$0000B; GO TO PUNL; + END; + /* CASE 14 IS UP2 */ + DO; IOBYTE = 0011$0000B; GO TO PUNL; + END; + /* CASE 15 IS PUN */ + PUNL: + CALL MON1(4,B); + /* CASE 16 IS TTY */ + DO; IOBYTE = 0; GO TO CONL; + END; + /* CASE 17 IS CRT */ + DO; IOBYTE = 1; GO TO CONL; + END; + /* CASE 18 IS UC1 */ + DO; IOBYTE = 11B; GO TO CONL; + END; + /* CASE 19 IS CON */ + CONL: + CALL MON1(2,B); + END; + IOBYTE = IOB; + END PUTDCHAR; + +PUTDESTC: PROCEDURE(B); + DECLARE (B,I) BYTE; + /* WRITE DESTINATION CHARACTER, TAB EXPANSION */ + IF B <> TAB THEN CALL PUTDCHAR(B); ELSE + IF TABS = 0 THEN CALL PUTDCHAR(B); ELSE + /* B IS TAB CHAR, TABS > 0 */ + DO; I = COLUMN; + DO WHILE I >= TABS; + I = I - TABS; + END; + I = TABS - I; + DO WHILE I > 0; + I = I - 1; + CALL PUTDCHAR(' '); + END; + END; + IF B = CR THEN COLUMN = 0; + END PUTDESTC; + +PRINT1: PROCEDURE(B); + DECLARE B BYTE; + IF (ZEROSUP := ZEROSUP AND B = 0) THEN CALL PUTDESTC(' '); ELSE + CALL PUTDESTC('0'+B); + END PRINT1; + +PRINTDIG: PROCEDURE(D); + DECLARE D BYTE; + CALL PRINT1(SHR(D,4)); CALL PRINT1(D AND 1111B); + END PRINTDIG; + +NEWLINE: PROCEDURE; + DECLARE ONE BYTE; + ONE = 1; + ZEROSUP = NUMB = 1; + C1 = DEC(C1+ONE); C2 = DEC(C2 PLUS 0); C3 = DEC(C3 PLUS 0); + CALL PRINTDIG(C3); CALL PRINTDIG(C2); CALL PRINTDIG(C1); + IF NUMB = 1 THEN /* USUALLY PRINTER OUTPUT */ + DO; CALL PUTDESTC(':'); CALL PUTDESTC(' '); + END; ELSE + CALL PUTDESTC(TAB); + END NEWLINE; + +CLEARBUFF: PROCEDURE; + /* CLEAR OUTPUT BUFFER IN BLOCK MODE TRANSMISION */ + DECLARE NA ADDRESS; + DECLARE I BYTE; + I = LOW(NDEST) AND 7FH; /* REMAINING PARTIAL BUFFER LENGTH */ + NA = NDEST AND 0FF80H; /* START OF SEGMENT NOT WRITTEN */ + CALL WRITEDEST; /* CLEARS BUFFERS */ + CALL MOVE(.DBUFF(NA),.DBUFF,I); + /* DATA MOVED TO BEGINNING OF BUFFER */ + NDEST = I; + END CLEARBUFF; + +PUTDEST: PROCEDURE(B); + DECLARE (I,B) BYTE; + /* WRITE DESTINATION CHARACTER, CHECK TABS AND LINES */ + IF FORMF THEN /* SKIP FORM FEEDS */ + DO; IF B = FF THEN RETURN; + END; + IF PUTNUM THEN /* END OF LINE OR START OF FILE */ + DO; + IF B <> FF THEN /* NOT FORM FEED */ + DO; + IF (I:=PAGCNT) <> 0 THEN /* PAGE EJECT */ + DO; IF I=1 THEN I=LPP; + IF (LINENO := LINENO + 1) >= I THEN + DO; LINENO = 0; /* NEW PAGE */ + CALL PUTDESTC(FF); + END; + END; + IF NUMB > 0 THEN + CALL NEWLINE; + PUTNUM = FALSE; + END; + END; + IF BLOCK THEN /* BLOCK MODE TRANSFER */ + DO; + IF B = XOFF AND PDEST = 0 THEN + DO; CALL CLEARBUFF; /* BUFFERS WRITTEN */ + RETURN; /* DON'T PASS THE X-OFF */ + END; + END; + IF B = FF THEN LINENO = 0; + CALL PUTDESTC(B); + IF B = LF THEN PUTNUM = TRUE; + END PUTDEST; + + +UTRAN: PROCEDURE(B) BYTE; + DECLARE B BYTE; + /* TRANSLATE ALPHA TO UPPER CASE */ + IF B >= 110$0001B AND B <= 111$1010B THEN /* LOWER CASE */ + B = B AND 101$1111B; /* TO UPPER CASE */ + RETURN B; + END UTRAN; + +LTRAN: PROCEDURE(B) BYTE; + DECLARE B BYTE; + /* TRANSLATE TO LOWER CASE ALPHA */ + IF B >= 'A' AND B <= 'Z' THEN B = B OR 10$0000B; /* TO LOWER */ + RETURN B; + END LTRAN; + +GETSOURCEC: PROCEDURE BYTE; + /* READ NEXT SOURCE CHARACTER */ + DECLARE (IOB,B,CONCHK) BYTE; + + IF PSOURCE - 1 <= RDR THEN /* 1 ... RDR+1 */ + DO; IF (BLOCK OR HEXT) AND CONBRK THEN + DO; + IF READCHAR = ENDFILE THEN RETURN ENDFILE; + CALL PRINT(.('READER STOPPING',CR,LF,'$')); + RETURN XOFF; + END; + END; + CONCHK = TRUE; /* CONSOLE STATUS CHECK BELOW */ + IOB = IOBYTE; /* SAVE IT IN CASE IT IS ALTERED */ + DO CASE PSOURCE; + /* CASE 0 IS SOURCE FILE */ + DO; IF NSOURCE >= SBLEN THEN CALL FILLSOURCE; + B = SBUFF(NSOURCE); + NSOURCE = NSOURCE + 1; + END; + /* CASE 1 IS INP */ + B = INP; + /* CASE 2 IS IRD (INTEL/ICOM) */ + B = INTIN; + /* CASE 3 IS PTR */ + DO; IOBYTE = 0000$0100B; GO TO RDRL; + END; + /* CASE 4 IS UR1 */ + DO; IOBYTE = 0000$1000B; GO TO RDRL; + END; + /* CASE 5 IS UR2 */ + DO; IOBYTE = 0000$1100B; GO TO RDRL; + END; + /* CASE 6 IS RDR */ + RDRL: + B = MON2(3,0) AND 7FH; + /* CASE 7 IS OUT */ + GO TO NOTSOURCE; + /* CASE 8 IS LPT */ + GO TO NOTSOURCE; + /* CASE 9 IS UL1 */ + GO TO NOTSOURCE; + /* CASE 10 IS PRN */ + GO TO NOTSOURCE; + /* CASE 11 IS LST */ + GO TO NOTSOURCE; + /* CASE 12 IS PTP */ + GO TO NOTSOURCE; + /* CASE 13 IS UP1 */ + GO TO NOTSOURCE; + /* CASE 14 IS UP2 */ + GO TO NOTSOURCE; + /* CASE 15 IS PUN */ + NOTSOURCE: + DO; CALL ERROR(.('NOT A CHARACTER SOURCE$')); + END; + /* CASE 16 IS TTY */ + DO; IOBYTE = 0; GO TO CONL; + END; + /* CASE 17 IS CRT */ + DO; IOBYTE = 01B; GO TO CONL; + END; + /* CASE 18 IS UC1 */ + DO; IOBYTE = 11B; GO TO CONL; + END; + /* CASE 19 IS CON */ + CONL: + DO; CONCHK = FALSE; /* DON'T CHECK CONSOLE STATUS */ + B = MON2(1,0); + END; + END; /* OF CASES */ + IOBYTE = IOB; /* RESTORE IOBYTE */ + IF ECHO THEN /* COPY TO CONSOLE DEVICE */ + DO; IOB = PDEST; PDEST = CONP; CALL PUTDEST(B); + PDEST = IOB; + END; + IF CONCHK THEN /* TEST FOR CONSOLE CHAR READY */ + DO; + IF SCOM THEN /* SOURCE IS A COM FILE */ + CONCHK = (CONCNT := CONCNT + 1) = 0; ELSE /* ASCII */ + CONCHK = B = LF; + IF CONCHK THEN + DO; IF CONBRK THEN + DO; + IF READCHAR = ENDFILE THEN RETURN ENDFILE; + CALL ERROR(.('ABORTED$')); + END; + END; + END; + IF ZEROP THEN B = B AND 7FH; + IF UPPER THEN RETURN UTRAN(B); + IF LOWER THEN RETURN LTRAN(B); + RETURN B; + END GETSOURCEC; + +GETSOURCE: PROCEDURE BYTE; + /* GET NEXT SOURCE CHARACTER */ + DECLARE CHAR BYTE; + MATCH: PROCEDURE(B) BYTE; + /* MATCH START AND QUIT STRINGS */ + DECLARE (B,C) BYTE; + IF (C:=COMBUFF(B:=(B+MATCHLEN))) = ENDFILE THEN /* END MATCH */ + DO; COMBUFF(B) = CHAR; /* SAVE CURRENT CHARACTER */ + RETURN TRUE; + END; + IF C = CHAR THEN MATCHLEN = MATCHLEN + 1; ELSE + MATCHLEN = 0; /* NO MATCH */ + RETURN FALSE; + END MATCH; + IF QUITLEN > 0 THEN + DO; IF (QUITLEN := QUITLEN - 1) = 1 THEN RETURN LF; + RETURN ENDFILE; /* TERMINATED WITH CR,LF,ENDFILE */ + END; + DO FOREVER; /* LOOKING FOR START */ + IF FEEDLEN > 0 THEN /* GET SEARCH CHARACTERS */ + DO; FEEDLEN = FEEDLEN - 1; + CHAR = COMBUFF(FEEDBASE); + FEEDBASE = FEEDBASE + 1; + RETURN CHAR; + END; + IF (CHAR := GETSOURCEC) = ENDFILE THEN RETURN ENDFILE; + IF STARTS > 0 THEN /* LOOKING FOR START STRING */ + DO; IF MATCH(STARTS) THEN + DO; FEEDBASE = STARTS; STARTS = 0; + FEEDLEN = MATCHLEN + 1; + END; /* OTHERWISE NO MATCH, SKIP CHARACTER */ + END; ELSE + IF QUITS > 0 THEN /* PASS CHARACTERS TIL MATCH */ + DO; IF MATCH(QUITS) THEN + DO; QUITS = 0; QUITLEN = 2; + /* SUBSEQUENTLY RETURN CR, LF, ENDFILE */ + RETURN CR; + END; + RETURN CHAR; + END; ELSE + RETURN CHAR; + END; /* OF DO FOREVER */ + END GETSOURCE; + +DECLARE DISK BYTE; /* SELECTED DISK */ + + GNC: PROCEDURE BYTE; + IF (CBP := CBP + 1) >= COMLEN THEN RETURN CR; + RETURN UTRAN(COMBUFF(CBP)); + END GNC; + + DEBLANK: PROCEDURE; + DO WHILE (CHAR := GNC) = ' '; + END; + END DEBLANK; + + SCAN: PROCEDURE(FCBA); + DECLARE FCBA ADDRESS, /* ADDRESS OF FCB TO FILL */ + FCB BASED FCBA (FSIZE) BYTE; /* FCB TEMPLATE */ + DECLARE (I,J,K) BYTE; /* TEMP COUNTERS */ + + /* SCAN LOOKS FOR THE NEXT DELIMITER, DEVICE NAME, OR FILE NAME. + THE VALUE OF CBP MUST BE 255 UPON ENTRY THE FIRST TIME */ + + DELIMITER: PROCEDURE(C) BYTE; + DECLARE (I,C) BYTE; + DECLARE DEL(*) BYTE DATA + (' =.:,<>',CR,LA,LB,RB); + DO I = 0 TO LAST(DEL); + IF C = DEL(I) THEN RETURN TRUE; + END; + RETURN FALSE; + END DELIMITER; + + PUTCHAR: PROCEDURE; + FCB(FLEN:=FLEN+1) = CHAR; + IF CHAR = WHAT THEN AMBIG = TRUE; /* CONTAINS AMBIGUOUS REF */ + END PUTCHAR; + + FILLQ: PROCEDURE(LEN); + /* FILL CURRENT NAME OR TYPE WITH QUESTION MARKS */ + DECLARE LEN BYTE; + CHAR = WHAT; /* QUESTION MARK */ + DO WHILE FLEN < LEN; + CALL PUTCHAR; + END; + END FILLQ; + + GETFCB: PROCEDURE(I) BYTE; + DECLARE I BYTE; + RETURN FCB(I); + END GETFCB; + + SCANPAR: PROCEDURE; + DECLARE (I,J) BYTE; + /* SCAN OPTIONAL PARAMETERS */ + PARSET = TRUE; + SUSER = CUSER; /* SOURCE USER := CURRENT USER */ + CHAR = GNC; /* SCAN PAST BRACKET */ + DO WHILE NOT(CHAR = CR OR CHAR = RB); + IF (I := CHAR - 'A') > 25 THEN /* NOT ALPHA */ + DO; IF CHAR = ' ' THEN CHAR = GNC; ELSE + CALL ERROR(.('BAD PARAMETER$')); + END; ELSE + DO; /* SCAN PARAMETER VALUE */ + IF CHAR = 'S' OR CHAR = 'Q' THEN + DO; /* START OR QUIT COMMAND */ + J = CBP + 1; /* START OF STRING */ + DO WHILE NOT ((CHAR := GNC) = ENDFILE OR CHAR = CR); + END; + CHAR=GNC; + END; ELSE + IF (J := (CHAR := GNC) - '0') > 9 THEN J = 1; + ELSE + DO WHILE (K := (CHAR := GNC) - '0') <= 9; + J = J * 10 + K; + END; + CONT(I) = J; + IF I = 6 THEN /* SET SOURCE USER */ + DO; + IF J > 31 THEN + CALL ERROR(.('INVALID USER NUMBER$')); + SUSER = J; + END; + END; + END; + CHAR = GNC; + END SCANPAR; + + CHKSET: PROCEDURE; + IF CHAR = LA THEN CHAR = '='; + END CHKSET; + + /* INITIALIZE FILE CONTROL BLOCK TO EMPTY */ + AMBIG = FALSE; TYPE = ERR; CHAR = ' '; FLEN = 0; + DO WHILE FLEN < FSIZE-1; + IF FLEN = FNSIZE THEN CHAR = 0; + CALL PUTCHAR; + END; + + /* DEBLANK COMMAND BUFFER */ + CALL DEBLANK; + + /* SAVE STARTING POSITION OF SCAN FOR DIAGNOSTICS */ + TCBP = CBP; + + /* MAY BE A SEPARATOR */ + IF DELIMITER(CHAR) THEN + DO; CALL CHKSET; + TYPE = SPECL; RETURN; + END; + + /* CHECK PERIPHERALS AND DISK FILES */ + DISK = 0; + /* CLEAR PARAMETERS */ + DO I = 0 TO 25; CONT(I) = 0; + END; + PARSET = FALSE; + FEEDLEN,MATCHLEN,QUITLEN = 0; + /* SCAN NEXT NAME */ + DO FOREVER; + FLEN = 0; + DO WHILE NOT DELIMITER(CHAR); + IF FLEN >= NSIZE THEN /* ERROR, FILE NAME TOO LONG */ + RETURN; + IF CHAR = '*' THEN CALL FILLQ(NSIZE); ELSE CALL PUTCHAR; + CHAR = GNC; + END; + + /* CHECK FOR DISK NAME OR DEVICE NAME */ + IF CHAR = ':' THEN + DO; IF DISK <> 0 THEN RETURN; /* ALREADY SET */ + IF FLEN = 1 THEN + /* MAY BE DISK NAME A ... Z */ + DO; + IF (DISK := GETFCB(1) - 'A' + 1) > 26 THEN + /* ERROR, INVALID DISK NAME */ RETURN; + CALL DEBLANK; /* MAY BE DISK NAME ONLY */ + IF DELIMITER(CHAR) THEN + DO; IF CHAR = LB THEN + CALL SCANPAR; + CBP = CBP - 1; + TYPE = DISKNAME; + RETURN; + END; + END; ELSE + + /* MAY BE A THREE CHARACTER DEVICE NAME */ + IF FLEN <> 3 THEN /* ERROR, CANNOT BE DEVICE NAME */ + RETURN; ELSE + + /* LOOK FOR DEVICE NAME */ + DO; DECLARE (I,J,K) BYTE, M LITERALLY '20', + IO(*) BYTE DATA + ('INPIRDPTRUR1UR2RDROUTLPTUL1PRNLST', + 'PTPUP1UP2PUNTTYCRTUC1CONNULEOF',0); + /* NOTE THAT ALL READER-LIKE DEVICES MUST BE + PLACED BEFORE 'RDR', AND ALL LISTING-LIKE DEVICES + MUST APPEAR BELOW LST, BUT ABOVE RDR. THE LITERAL + DECLARATIONS FOR RDR, LST, AND PUNP MUST INDICATE + THE POSITIONS OF THESE DEVICES IN THE LIST */ + J = 255; + DO K = 0 TO M; + I = 0; + DO WHILE ((I:=I+1) <= 3) AND + IO(J+I) = GETFCB(I); + END; + IF I = 4 THEN /* COMPLETE MATCH */ + DO; TYPE = PERIPH; + /* SCAN PARAMETERS */ + IF GNC = LB THEN CALL SCANPAR; + CBP = CBP - 1; CHAR = K; + RETURN; + END; + /* OTHERWISE TRY NEXT DEVICE */ J = J + 3; + END; + + /* ERROR, NO DEVICE NAME MATCH */ RETURN; + END; + IF CHAR = LB THEN /* PARAMETERS FOLLOW */ + CALL SCANPAR; + END; ELSE + + /* CHAR IS NOT ':', SO FILE NAME IS SET. SCAN REMAINDER */ + DO; IF FLEN = 0 THEN /* ERROR, NO PRIMARY NAME */ + RETURN; + FLEN = FNAM; + IF CHAR = '.' THEN /* SCAN FILE TYPE */ + DO WHILE NOT DELIMITER(CHAR := GNC); + IF FLEN >= FNSIZE THEN + /* ERROR, TYPE FIELD TOO LONG */ RETURN; + IF CHAR = '*' THEN CALL FILLQ(FNSIZE); + ELSE CALL PUTCHAR; + END; + + IF CHAR = LB THEN + CALL SCANPAR; + /* RESCAN DELIMITER NEXT TIME AROUND */ + CBP = CBP - 1; + TYPE = FILE; + /* DISK IS THE SELECTED DISK (1 2 3 ... ) */ + IF DISK = 0 THEN DISK = CDISK + 1; /* DEFAULT */ + FCB(0),FCB(32) = 0; + RETURN; + END; + END; + END SCAN; + + NULLS: PROCEDURE; + /* SEND 40 NULLS TO OUTPUT DEVICE */ + DECLARE I BYTE; + DO I = 0 TO 39; CALL PUTDEST(0); + END; + END NULLS; + + + DECLARE FEXTH(FEXTL) BYTE, /* HOLDS DESTINATION FILE TYPE */ + COPYING BYTE; /* TRUE WHILE COPYING TO DEST FILE */ + + MOVEXT: PROCEDURE(A); + DECLARE A ADDRESS; + /* MOVE THREE CHARACTER EXTENT INTO DEST FCB */ + CALL MOVE(A,.DEST(FEXT),FEXTL); + END MOVEXT; + +EQUAL: PROCEDURE(A,B) BYTE; + /* COMPARE THE STRINGS AT A AND B UNTIL EITHER A MISMATCH OR + A '$' IS ENCOUNTERED IN STRING B */ + DECLARE (A,B) ADDRESS, + (SA BASED A, SB BASED B) BYTE; + DO WHILE SB <> '$'; + IF (SB AND 7FH) <> (SA AND 7FH) THEN RETURN FALSE; + A = A + 1; B = B + 1; + END; + RETURN TRUE; + END EQUAL; + +READ$EOF: PROCEDURE BYTE; + /* RETURN TRUE IF END OF FILE */ + CHAR = GETSOURCE; + IF SCOM THEN RETURN HARDEOF < NSOURCE; + RETURN CHAR = ENDFILE; + END READ$EOF; + + +HEXRECORD: PROCEDURE BYTE; + /* READ ONE RECORD INTO SBUFF AND CHECK FOR PROPER FORM + RETURNS 0 IF RECORD OK + RETURNS 1 IF END OF TAPE (:00000) + RETURNS 2 IF ERROR IN RECORD */ + + + DECLARE XOFFSET BYTE; /* TRUE IF XOFF RECVD */ + DECLARE NOERRS BYTE; /* TRUE IF NO ERRORS IN THIS RECORD */ + + PRINTERR: PROCEDURE(A); + /* PRINT ERROR MESSAGE IF NOERRS TRUE */ + DECLARE A ADDRESS; + IF NOERRS THEN + DO; NOERRS = FALSE; + CALL PRINT(A); + END; + END PRINTERR; + + CHECKXOFF: PROCEDURE; + IF XOFFSET THEN + DO; XOFFSET = FALSE; + CALL CLEARBUFF; + END; + END CHECKXOFF; + + SAVECHAR: PROCEDURE BYTE; + /* READ CHARACTER AND SAVE IN BUFFER */ + DECLARE I BYTE; + IF NOERRS THEN + DO; + DO WHILE (I := GETSOURCE) = XOFF; XOFFSET = TRUE; + END; + HBUFF(HSOURCE) = I; + IF (HSOURCE := HSOURCE + 1) >= LAST(HBUFF) THEN + CALL PRINTERR(.('RECORD TOO LONG$')); + RETURN I; + END; + RETURN ENDFILE; /* ON ERROR FLAG */ + END SAVECHAR; + + DECLARE (M, RL, CS, RT) BYTE, + LDA ADDRESS; /* LOAD ADDRESS WHICH FOLLOWS : */ + + READHEX: PROCEDURE BYTE; + DECLARE H BYTE; + IF (H := SAVECHAR) - '0' <= 9 THEN RETURN H-'0'; + IF H - 'A' > 5 THEN + CALL PRINTERR(.('INVALID DIGIT$')); + RETURN H - 'A' + 10; + END READHEX; + + READBYTE: PROCEDURE BYTE; + /* READ TWO HEX DIGITS */ + RETURN SHL(READHEX,4) OR READHEX; + END READBYTE; + + READCS: PROCEDURE BYTE; + /* READ BYTE WITH CHECKSUM */ + RETURN CS := CS + READBYTE; + END READCS; + + READADDR: PROCEDURE ADDRESS; + /* READ DOUBLE BYTE WITH CHECKSUM */ + RETURN SHL(DOUBLE(READCS),8) OR READCS; + END READADDR; + + NOERRS = TRUE; /* NO ERRORS DETECTED IN THIS RECORD */ + + /* READ NEXT RECORD */ + /* SCAN FOR THE ':' */ + HSOURCE = 0; + DO WHILE (CS := SAVECHAR) <> ':'; + HSOURCE = 0; + IF CS = ENDFILE THEN + DO; CALL PRINT(.('END OF FILE, CTL-Z',WHAT,'$')); + IF READCHAR = ENDFILE THEN RETURN 1; + ELSE HSOURCE = 0; + END; + CALL CHECKXOFF; + END; + + /* ':' FOUND */ + CS = 0; + IF (RL := READCS) = 0 THEN /* END OF TAPE */ + DO; DO WHILE (RL := SAVECHAR) <> ENDFILE; + CALL CHECKXOFF; + END; + IF NOERRS THEN RETURN 1; + RETURN 2; + END; + + /* RECORD LENGTH IS NOT ZERO */ + LDA = READADDR; /* LOAD ADDRESS */ + + /* READ WORDS UNTIL RECORD LENGTH EXHAUSTED */ + RT = READCS; /* RECORD TYPE */ + DO WHILE RL <> 0 AND NOERRS; RL = RL - 1; + M = READCS; + /* INCREMENT LA HERE FOR EXACT ADDRESS */ + END; + + /* CHECK SUM */ + IF CS + READBYTE <> 0 THEN + CALL PRINTERR(.('CHECKSUM ERROR$')); + + CALL CHECKXOFF; + IF NOERRS THEN RETURN 0; + RETURN 2; + END HEXRECORD; + +READTAPE: PROCEDURE; + /* READ HEX FILE FROM HIGH SPEED READER TO 'HEX' FILE, + CHECK EACH RECORD FOR VALID DIGITS, AND PROPER CHECKSUM */ + DECLARE (I,A) BYTE; + DO FOREVER; + DO WHILE (I := HEXRECORD) <= 1; + IF NOT (I = 1 AND IGNOR) THEN + DO A = 1 TO HSOURCE; + CALL PUTDEST(HBUFF(A-1)); + END; + CALL PUTDEST(CR); CALL PUTDEST(LF); + IF I = 1 THEN /* END OF TAPE ENCOUNTERED */ + RETURN; + END; + CALL CRLF; HBUFF(HSOURCE) = '$'; + CALL PRINT(.HBUFF); + CALL PRINT(.('CORRECT ERROR, TYPE RETURN OR CTL-Z$')); + CALL CRLF; + IF READCHAR = ENDFILE THEN RETURN; + END; + END READTAPE; + +FORMERR: PROCEDURE; + CALL ERROR(.('INVALID FORMAT$')); + END FORMERR; + +SETUPDEST: PROCEDURE; + CALL SELECT(DDISK); + DHEX = EQUAL(.DEST(FEXT),.('HEX$')); + CALL MOVE(.DEST(FEXT),.FEXTH,FEXTL); /* SAVE TYPE */ + DEST(ROFILE) = DEST(ROFILE) AND 7FH; + DEST(SYSFILE)= DEST(SYSFILE)AND 7FH; + CALL MOVEXT(.('$$$')); + CALL DELETE(.DEST); /* REMOVE OLD $$$ FILE */ + CALL MAKE(.DEST); /* CREATE A NEW ONE */ + IF DCNT = 255 THEN CALL ERROR(.('NO DIRECTORY SPACE$')); + DEST(32),NDEST = 0; + END SETUPDEST; + +SETUPSOURCE: PROCEDURE; + HARDEOF = 0FFFFH; + CALL SETSUSER; /* SOURCE USER */ + CALL SELECT(SDISK); + CALL OPEN(.SOURCE); + CALL SETCUSER; /* BACK TO CURRENT USER */ + IF (NOT RSYS) AND ROL(SOURCE(SYSFILE),1) THEN + DCNT = 255; + IF DCNT = 255 THEN CALL ERROR(.('NO FILE$')); + SOURCE(32) = 0; + /* CAUSE IMMEDIATE READ */ + SCOM = EQUAL(.SOURCE(FEXT),.('COM$')); + NSOURCE = SBLEN; + END SETUPSOURCE; + +CHECK$STRINGS: PROCEDURE; + IF STARTS > 0 THEN + CALL ERROR(.('START NOT FOUND$')); + IF QUITS > 0 THEN + CALL ERROR(.('QUIT NOT FOUND$')); + END CHECK$STRINGS; + +CLOSEDEST: PROCEDURE(DIRECT); + DECLARE DIRECT BYTE; + /* DIRECT IS TRUE IF SECTOR-BY-SECTOR COPY */ + IF DIRECT THEN + /* GET UNFILLED BYTES FROM SOURCE BUFFER */ + DFUB = SFUB; ELSE DFUB = 0; + DO WHILE (LOW(NDEST) AND 7FH) <> 0; + DFUB = DFUB + 1; + CALL PUTDEST(ENDFILE); + END; + CALL CHECK$STRINGS; + CALL WRITEDEST; + CALL SELECT(DDISK); + CALL CLOSE(.DEST); + IF DCNT = 255 THEN + CALL ERROR(.('CANNOT CLOSE DESTINATION FILE$')); + CALL MOVEXT(.FEXTH); /* RECALL ORIGINAL TYPTE */ + DEST(12) = 0; + CALL OPEN(.DEST); + IF DCNT <> 255 THEN /* FILE EXISTS */ + DO; + IF ROL(DEST(ROFILE),1) THEN /* READ ONLY */ + DO; + IF NOT WRROF THEN + DO; + CALL PRINT (.('DESTINATION IS R/O, DELETE (Y/N)?$')); + IF UTRAN(READCHAR) <> 'Y' THEN + DO; CALL PRINT(.('**NOT DELETED**$')); + CALL CRLF; + CALL MOVEXT(.('$$$')); + CALL DELETE(.DEST); + RETURN; + END; + CALL CRLF; + END; + DEST(ROFILE) = DEST(ROFILE) AND 7FH; + CALL SETIND(.DEST); + END; + CALL DELETE(.DEST); + END; + CALL MOVE(.DEST,.DEST(16),16); /* READY FOR RENAME */ + CALL MOVEXT(.('$$$')); + CALL RENAME(.DEST); + END CLOSEDEST; + +SIZE$NBUF: PROCEDURE; + /* COMPUTE NUMBER OF BUFFERS - 1 FROM DBLEN */ + NBUF = (SHR(DBLEN,7) AND 0FFH) - 1; + /* COMPUTED AS DBLEN/128-1, WHERE DBLEN <= 32K (AND THUS + NBUF RESULTS IN A VALUE <= 2**15/2**7-1 = 2**8-1 = 255) */ + END SIZE$NBUF; + +SET$DBLEN: PROCEDURE; + /* ABSORB THE SOURCE BUFFER INTO THE DEST BUFFER */ + SBASE = .MEMORY; + IF DBLEN >= 4000H THEN DBLEN = 7F80H; ELSE + DBLEN = DBLEN + SBLEN; + CALL SIZE$NBUF; + END SET$DBLEN; + +SIZE$MEMORY: PROCEDURE; + /* SET UP SOURCE AND DESTINATION BUFFERS */ + SBASE = .MEMORY + SHR(MEMSIZE - .MEMORY,1); + SBLEN, DBLEN = SHR((MEMSIZE - .MEMORY) AND 0FF00H,1); + CALL SIZE$NBUF; + END SIZE$MEMORY; + +COPYCHAR: PROCEDURE; + /* PERFORM THE ACTUAL COPY FUNCTION */ + DECLARE RESIZED BYTE; /* TRUE IF SBUFF AND DBUFF COMBINED */ + IF (RESIZED := (BLOCK AND PSOURCE <> 0)) THEN /* BLOCK MODE */ + CALL SET$DBLEN; /* ABSORB SOURCE BUFFER */ + IF HEXT OR IGNOR THEN /* HEX FILE */ + CALL READTAPE; ELSE + DO WHILE NOT READ$EOF; + CALL PUTDEST(CHAR); + END; + IF RESIZED THEN + DO; CALL CLEARBUFF; + CALL SIZE$MEMORY; + END; + END COPYCHAR; + +SIMPLECOPY: PROCEDURE; + DECLARE (FASTCOPY,I) BYTE; + REAL$EOF: PROCEDURE BYTE; + RETURN HARDEOF <> 0FFFFH; + END REALEOF; + CALL SIZE$MEMORY; + TCBP = MCBP; /* FOR ERROR TRACING */ + CALL SETUPDEST; + CALL SETUPSOURCE; + /* FILES READY FOR DIRECT COPY */ + FASTCOPY = TRUE; + /* LOOK FOR PARAMETERS */ + DO I = 0 TO 25; + IF CONT(I) <> 0 THEN + DO; + IF NOT(I=6 OR I=14 OR I=17 OR I=21 OR I=22) THEN + /* NOT OBJ OR VERIFY */ + FASTCOPY = FALSE; + END; + END; + IF FASTCOPY THEN /* COPY DIRECTLY TO DBUFF */ + DO; CALL SET$DBLEN; /* EXTEND DBUFF */ + DO WHILE NOT REAL$EOF; + CALL FILLSOURCE; + IF REAL$EOF THEN + NDEST = HARDEOF; ELSE NDEST = DBLEN; + CALL WRITEDEST; + END; + CALL SIZE$MEMORY; /* RESET TO TWO BUFFERS */ + END; ELSE + CALL COPYCHAR; + CALL CLOSEDEST(FASTCOPY); + END SIMPLECOPY; + +MULTCOPY: PROCEDURE; + DECLARE (NEXTDIR, NDCNT, NCOPIED) ADDRESS; + PRNAME: PROCEDURE; + /* PRINT CURRENT FILE NAME */ + DECLARE (I,C) BYTE; + CALL CRLF; + DO I = 1 TO FNSIZE; + IF (C := DEST(I)) <> ' ' THEN + DO; IF I = FEXT THEN CALL PRINTCHAR('.'); + CALL PRINTCHAR(C); + END; + END; + END PRNAME; + + NEXTDIR,NCOPIED = 0; + DO FOREVER; + /* FIND A MATCHING ENTRY */ + CALL SETSUSER; /* SOURCE USER */ + CALL SELECT(SDISK); + CALL SETDMA(.BUFFER); + CALL SEARCH(.SEARFCB); + NDCNT = 0; + DO WHILE (DCNT <> 255) AND NDCNT < NEXTDIR; + NDCNT = NDCNT + 1; + CALL SEARCHN; + END; + CALL SETCUSER; + /* FILE CONTROL BLOCK IN BUFFER */ + IF DCNT = 255 THEN + DO; IF NCOPIED = 0 THEN + CALL ERROR(.('NOT FOUND$')); CALL CRLF; + RETURN; + END; + NEXTDIR = NDCNT + 1; + /* GET THE FILE CONTROL BLOCK NAME TO DEST */ + CALL MOVE(.BUFFER+SHL(DCNT AND 11B,5),.DEST,16); + DEST(0) = 0; + DEST(12) = 0; + CALL MOVE(.DEST,.SOURCE,16); /* FILL BOTH FCB'S */ + IF RSYS OR NOT ROL(DEST(SYSFILE),1) THEN /* OK TO READ */ + DO; + IF (NCOPIED := NCOPIED + 1) = 1 THEN + CALL PRINT(.('COPYING -$')); + CALL PRNAME; + CALL SIMPLECOPY; + END; + END; + END MULTCOPY; + +SET$SDISK: PROCEDURE; + IF DISK > 0 THEN SDISK = DISK - 1; ELSE SDISK = CDISK; + END SET$SDISK; + +SET$DDISK: PROCEDURE; + IF PARSET THEN /* PARAMETERS PRESENT */ CALL FORMERR; + IF DISK > 0 THEN DDISK = DISK - 1; ELSE DDISK = CDISK; + END SET$DDISK; + +CHECK$DISK: PROCEDURE; + IF SUSER <> CUSER THEN /* DIFFERENT DISKS */ + RETURN; + IF DDISK = SDISK THEN CALL FORMERR; + END CHECK$DISK; + +CHECK$EOL: PROCEDURE; + CALL DEBLANK; + IF CHAR <> CR THEN CALL FORMERR; + END CHECK$EOL; + +SCANDEST: PROCEDURE(COPYFCB); + DECLARE COPYFCB ADDRESS; + CALL SET$SDISK; + CALL CHECK$EOL; + CALL MOVE(.SOURCE,COPYFCB,33); + CALL CHECK$DISK; + END SCANDEST; + +SCANEQL: PROCEDURE; + CALL SCAN(.SOURCE); + IF NOT (TYPE = SPECL AND CHAR = '=') THEN CALL FORMERR; + MCBP = CBP; /* FOR ERROR PRINTING */ + END SCANEQL; + + +PIPENTRY: + /* BUFFER AT 80H CONTAINS REMAINDER OF LINE TYPED + FOLLOWING THE COMMAND 'PIP' - IF ZERO THEN PROMPT TIL CR */ + CALL MOVE(.BUFF,.COMLEN,80H); + MULTCOM = COMLEN = 0; + + /* GET CURRENT CP/M VERSION */ + IF VERSION < CPMVERSION THEN + DO; + CALL PRINT(.('REQUIRES CP/M 2.0 OR NEWER FOR OPERATION.$')); + CALL BOOT; + END; + /* GET CURRENT USER */ + CUSER = GETUSER; + /* GET CURRENT DISK */ + CDISK = MON2(25,0); + + RETRY: + /* ENTER HERE ON ERROR EXIT FROM THE PROCEDURE 'ERROR' */ + CALL SIZE$MEMORY; + /* MAIN PROCESSING LOOP. PROCESS UNTIL CR ONLY */ + DO FOREVER; + SUSER = CUSER; + C1, C2, C3 = 0; /* LINE COUNT = 000000 */ + PUTNUM = TRUE; /* ACTS LIKE LF OCCURRED ON ASCII FILE */ + CONCNT,COLUMN = 0; /* PRINTER TABS */ + LINENO = 254; /* INCREMENTED TO 255 > PAGCNT */ + /* READ FROM CONSOLE IF NOT A ONELINER */ + IF MULTCOM THEN + DO; CALL PRINTCHAR('*'); CALL READCOM; + CALL CRLF; + END; + CBP = 255; + IF COMLEN = 0 THEN /* SINGLE CARRIAGE RETURN */ + DO; CALL SELECT(CDISK); + CALL BOOT; + END; + + /* LOOK FOR SPECIAL CASES FIRST */ + DDISK,SDISK,PSOURCE,PDEST = 0; + CALL SCAN(.DEST); + IF TYPE = PERIPH THEN GO TO SIMPLECOM; + IF TYPE = DISKNAME THEN + DO; DDISK = DISK - 1; + CALL SCANEQL; + CALL SCAN(.SOURCE); + /* MAY BE MULTI COPY */ + IF TYPE <> FILE THEN CALL FORMERR; + IF AMBIG THEN + DO; CALL SCANDEST(.SEARFCB); + CALL MULTCOPY; + END; ELSE + DO; CALL SCANDEST(.DEST); + /* FORM IS A:=B:UFN */ + CALL SIMPLECOPY; + END; + GO TO ENDCOM; + END; + + + IF TYPE <> FILE OR AMBIG THEN CALL FORMERR; + CALL SET$DDISK; + CALL SCANEQL; + CALL SCAN(.SOURCE); + IF TYPE = DISKNAME THEN + DO; + CALL SET$SDISK; CALL CHECK$DISK; + CALL MOVE(.DEST,.SOURCE,33); + CALL CHECK$EOL; + CALL SIMPLECOPY; + GO TO ENDCOM; + END; + /* MAY BE POSSIBLE TO DO A FAST DISK COPY */ + IF TYPE = FILE THEN /* FILE TO FILE */ + DO; CALL DEBLANK; IF CHAR <> CR THEN GO TO SIMPLECOM; + /* FILE TO FILE */ + CALL SET$SDISK; + CALL SIMPLECOPY; + GO TO ENDCOM; + END; + +SIMPLECOM: + CBP = 255; /* READY FOR RESCAN */ + + /* OTHERWISE PROCESS SIMPLE REQUEST */ + CALL SCAN(.DEST); + IF (TYPE < FILE) OR AMBIG THEN /* DELIMITER OR ERROR */ + CALL ERROR(.('UNRECOGNIZED DESTINATION$')); + + DHEX = FALSE; + IF TYPE = FILE THEN + DO; /* DESTINATION IS A FILE, SAVE EXTENT NAME */ + CALL SET$DDISK; + CALL SETUPDEST; + CHAR = 255; + END; ELSE + /* PERIPHERAL NAME */ + IF CHAR >= NULP OR CHAR <= RDR THEN CALL ERROR(.('CANNOT WRITE$')); + + IF (PDEST := CHAR + 1) = PUNP THEN CALL NULLS; + + /* NOW SCAN THE DELIMITER */ + CALL SCAN(.SOURCE); + IF TYPE <> SPECL OR CHAR <> '=' THEN + CALL ERROR(.('INVALID PIP FORMAT$')); + + /* OTHERWISE SCAN AND COPY UNTIL CR */ + COPYING = TRUE; + DO WHILE COPYING; + SUSER = CUSER; + CALL SCAN(.SOURCE); + /* SUSER MAY HAVE BEEN RESET */ + SCOM = FALSE; + IF TYPE = FILE AND NOT AMBIG THEN /* A SOURCE FILE */ + DO; + CALL SET$SDISK; + CALL SETUPSOURCE; + CHAR = 255; + END; ELSE + + IF TYPE <> PERIPH OR (CHAR <= LST AND CHAR > RDR) THEN + CALL ERROR(.('CANNOT READ$')); + + + SCOM = SCOM OR OBJ; /* MAY BE ABSOLUTE COPY */ + PSOURCE = CHAR + 1; + IF CHAR = NULP THEN CALL NULLS; ELSE + IF CHAR = EOFP THEN CALL PUTDEST(ENDFILE); ELSE + DO; /* DISK COPY */ + IF (CHAR < HSRDR AND DHEX) THEN HEXT = 1; + /* HEX FILE SET IF SOURCE IS RDR AND DEST IS HEX FILE */ + IF PDEST = PRNT THEN + DO; NUMB = 1; + IF TABS = 0 THEN TABS = 8; + IF PAGCNT = 0 THEN PAGCNT = 1; + END; + CALL COPYCHAR; + END; + + CALL CHECK$STRINGS; + /* READ ENDFILE, GO TO NEXT SOURCE */ + CALL SCAN(.SOURCE); + IF TYPE <> SPECL OR (CHAR <> ',' AND CHAR <> CR) THEN + CALL ERROR(.('INVALID SEPARATOR$')); + + COPYING = CHAR <> CR; + END; + + /* IF NECESSARY, CLOSE FILE OR PUNCH TRAILER */ + IF PDEST = PUNP THEN + DO; CALL PUTDEST(ENDFILE); CALL NULLS; + END; + IF PDEST = 0 THEN /* FILE HAS TO BE CLOSED AND RENAMED */ + CALL CLOSEDEST(FALSE); + + /* COMLEN SET TO 0 IF NOT PROCESSING MULTIPLE COMMANDS */ +ENDCOM: + COMLEN = MULTCOM; + + END; /* DO FOREVER */ +END; + \ No newline at end of file diff --git a/ISIS PLM/PIP.SYM b/ISIS PLM/PIP.SYM new file mode 100644 index 0000000..218520c --- /dev/null +++ b/ISIS PLM/PIP.SYM @@ -0,0 +1,7 @@ +0000 PIP +0000 X0100 +0004 BDISK 0000 BOOT 0080 BUFF 0050 CMDRV 005C FCB +006C FCB16 0053 LEN0 0056 LEN1 0006 MAXB 0005 MON1 +0005 MON2 0005 MON2A 0005 MON3 0000 OFFSET 0051 PASS0 +0054 PASS1 0080 TBUFF + \ No newline at end of file diff --git a/ISIS PLM/PLM80 b/ISIS PLM/PLM80 new file mode 100644 index 0000000..94b2567 Binary files /dev/null and b/ISIS PLM/PLM80 differ diff --git a/ISIS PLM/PLM80.LIB b/ISIS PLM/PLM80.LIB new file mode 100644 index 0000000..3af09d4 Binary files /dev/null and b/ISIS PLM/PLM80.LIB differ diff --git a/ISIS PLM/PLM80.OV0 b/ISIS PLM/PLM80.OV0 new file mode 100644 index 0000000..e322d62 Binary files /dev/null and b/ISIS PLM/PLM80.OV0 differ diff --git a/ISIS PLM/PLM80.OV1 b/ISIS PLM/PLM80.OV1 new file mode 100644 index 0000000..4866af3 Binary files /dev/null and b/ISIS PLM/PLM80.OV1 differ diff --git a/ISIS PLM/PLM80.OV2 b/ISIS PLM/PLM80.OV2 new file mode 100644 index 0000000..7eefa83 Binary files /dev/null and b/ISIS PLM/PLM80.OV2 differ diff --git a/ISIS PLM/PLM80.OV3 b/ISIS PLM/PLM80.OV3 new file mode 100644 index 0000000..82033c4 Binary files /dev/null and b/ISIS PLM/PLM80.OV3 differ diff --git a/ISIS PLM/PLM80.OV4 b/ISIS PLM/PLM80.OV4 new file mode 100644 index 0000000..d0f8796 Binary files /dev/null and b/ISIS PLM/PLM80.OV4 differ diff --git a/ISIS PLM/PLM80.OV5 b/ISIS PLM/PLM80.OV5 new file mode 100644 index 0000000..8ff4e28 Binary files /dev/null and b/ISIS PLM/PLM80.OV5 differ diff --git a/ISIS PLM/PLM80.OV6 b/ISIS PLM/PLM80.OV6 new file mode 100644 index 0000000..3941c6c Binary files /dev/null and b/ISIS PLM/PLM80.OV6 differ diff --git a/ISIS PLM/PLMLANG.DOC b/ISIS PLM/PLMLANG.DOC new file mode 100644 index 0000000..e8a990f --- /dev/null +++ b/ISIS PLM/PLMLANG.DOC @@ -0,0 +1,352 @@ + + PL/M-80 Language Summary + + +PL/M-80 is a programming language for i8080 systems. It is based most +notable on PL/I. It has the type of block structure and scope rules +most programmers now expect despite the fact it is a fairly small +language. + +The one thing that may "trip-up" may Pascal programmers is that PL/M +(and its PL/I big brother) use semicolon as a terminator, not as a +statement separator. Semicolons mark the end of every statement. + +The remainder of this file summarizes the PL/M-80 language and its +features. It is only a summary; no attempt is made to provide a +complete and unambiguous description. + +PL/M Character Set +================== +Alphabetics: A B C D E F G H I J K L M N O P Q R S T U V W X Y Z +Numerics: 0 1 2 3 4 5 6 7 8 9 +Specials: $ = . / ( ) + - ' * , < > : ; and space + +All other characters are unrecognized by PL/M in the sense that they +are regarded as equivalent to the space character. + +PL/M Identifiers +================ +Identifiers may be from 1 to 31 characters in length. An alphabetic +must be the first character in an identifer name; the remainder may +be alphabetic or numeric. In addition, dollar signs may be imbedded +within a variable name to improve readability. They are ignored by +PL/M. (The identifiers LINE$COUNT and LINECOUNT are interpreted +as identical names.) + +The following are all reserved words, and may not be used as +identifier names: + + ADDRESS DATA EOF LABEL PROCEDURE + AND DECLARE GO LITERALLY RETURN + BASED DISABLE GOTO MINUS THEN + BY DO HALT MOD TO + BYTE ELSE IF NOT WHILE + CALL ENABLE INITIAL OR XOR + CASE END INTERRUPT PLUS + +PL/M Data Types +=============== +There are two data types in PL/M. The data type BYTE refers to +8-bit data; ADDRESS, to 16. It is also possible to construct +arrays of either type and pointers to either type. + +PL/M Constants +================ +Numeric constants may be expressed as binary, octal, decimal, and +hexadecimal numbers. The radix for the number is specified by a +letter appended to the number: B for binary, O and Q for octal, +D for decimal, and H for hexadecimal. If the letter suffix is +omitted, the number is treated as decimal. Hexadecimal constants +must begin with a numeric to avoid confusion with identifier names. +As with identifiers, dollar signs may be imbedded in numeric constants +to improve readability. However a number is expressed, it must be +representable in 16 bits. + +Character string constants are enclosed in apostrophes. An apostrophe +within the string must be doubled. Character strings are represented +using 7-bit ASCII codes. Character strings constants of length 1 are +treated as BYTE values; length 2 as ADDRESS values. Longer strings +are only useful with the "dot" operator. + +PL/M Expressions +================ +There are seven arithmetic operators in PL/M. All perform unsigned +arithmetic operations on either BYTE or ADDRESS values. + + + Binary addition operator. + - Binary subtraction operator, or unary negation. + PLUS Binary addition-with-carry operator. + MINUS Binary subtraction-with-carry operator. + * Binary multiplication operator. + / Binary division operator. + MOD Binary remainder operator. + +Multiply and divide always produce ADDRESS results. The others +produce BYTE results if both operands are BYTE values; ADDRESS, +otherwise. + +There are four boolean operators in PL/M. All perform either 8-bit +or 16-bit boolean operations of their operands. + + NOT Unary complement operator. + AND Binary conjunction operator. + OR Binary disjunction operator. + XOR Binary exclusive-disjunction operator. + +The operators produce BYTE results if both operands are BYTE values. +If at least one is of type ADDRESS, the other is extended with +high-order zeroes if necessary, and the result is type ADDRESS. + +There are six relational operators. All return a true/false result +with 0FFH representing "true" and 00H, "false". + + < Binary less-than operator. + <= Binary less-than-or-equal operator. + = Binary equal operator. + >= Binary greater-than-or-equal operator. + > Binary greater-than operator. + <> Binary not-equal operator. + +There is one other PL/M operator, the so-called "dot" operator. It +is a unary operator that returns the memory address of its operand. +The operator may be used in the following forms: + + .variable + .constant + .(constant) + .(constant, ...) + +The construction " .(08H, 'Message', 0DH) " might best be considered +as the address of a nine-element BYTE array. + +Expression evaluation obeys operator precedence unless modified by +parenthesis. The following lists the operators in order of precedence: + + Highest: . + * / MOD + + - PLUS MINUS + < <= = => > <> + NOT + AND + Lowest: OR XOR + +PL/M Executable Statements +========================== +Commentary. + /* Not really an executable statement, but... */ +Assignment. + variable = expression ; + -or- variable, variable, ... = expression ; + +Imbedded assignment. (May be used within an expression.) + (variable := expression) + +Do-End. (Simple statement grouping.) + DO; + statement; ...; + END; + +Do-While. (Loop while rightmost bit of expression = 1.) + DO WHILE expression; + statement; ...; + END; + +Iterative Do. + DO variable = expression1 to expression2; + statement; ...; + END; + +Do-Case. (Execute i-th statement, numbered from 0.) + DO CASE expression; + statement0; + statement1; + ...; + END; + +If-Then. + IF expression THEN statement; + +If-Then-Else. + IF expression THEN statement; ELSE statement; + +Go To. (GO TO and GOTO are synonomous.) + GO TO label; + -or- GO TO number; + -or- GO TO variable; +The first form causes a GOTO the statement prefixed with 'label:'. +The latter two forms cause a GOTO an absolute storage location. + +Disable interrupts. + DISABLE; + +Enable interrupts. + ENABLE; + +PL/M Variable Declarations +========================== +Identifiers are defined with the DECLARE statement. The following +are typical forms for the DECLARE statement. + + Single identifier: DECLARE identifier type; + Group of identifiers: DECLARE (identifier, ...) type; + Array: DECLARE identifier (constant) type; + Multiple: DECLARE id type, id type, ...; + +Array subscripts start at 0. Thus, DECLARE A(10) BYTE; defines the +array of elements A(0)...A(9). + +Declared variables may have initial values specified by including +the INITIAL attribute after the type on the DECLARE statement: + + DECLARE A(10) BYTE INITIAL(10,11,12,13,14,15,16,17,18,19); + +Variables declared with the INITIAL attribute are preset at program +load time. They are not reset at procedure invocation or anywhere +else. The INITIAL attribute may specify fewer values then would +be needed for the declared variables. + +A DATA attribute is available for declaring storage constants. No +type or array sizes are specified; BYTE is assumed and the array +size is implicitly determined from the DATA value. The values of +identifiers declared as DATA must not be changed during program +execution. + + DECLARE GREETINGS DATA ('Hello, world.'); + +PL/M also supports a limited macro facility. Identifiers may be +declared with the LITERALLY attribute. The literal value is +substituted in the program source text where ever the identifier is +used. + + DECLARE FOREVER LITERALLY 'WHILE TRUE'; + . . . + DO FOREVER; + + Variables may be declared as BASED, as in + + DECLARE A$PTR ADDRESS, + A BASED A$PTR BYTE; + +In this example, the memory location associated with variable A is +determined by the address stored in variable A$PTR. + +Labels are declared using LABEL for the type. An identifier so +declared should also appear before an executable statement, separated +from the statement by a colon. (It is often not strictly necessary +to declare all labels. An implicit DECLARE results when an otherwise +undeclared label is encountered in the program. That is, + + COME$HERE: CALL PRT$MESSAGE(3); + +is equivalent to + + DECLARE COME$HERE LABEL; + COME$HERE: CALL PRT$MESSAGE(3); + +However, due to scope rules, a earlier reference to the label (in a +GOTO statement) may be flagged in error, because the implicit DECLARE +is physically latter in the program. + +PL/M Procedure Declarations +=========================== +Procedures must be defined before they are used. This declaration +form is: + + identifier: PROCEDURE (arg, ...) type; + statement; ...; + END identifier; + +The 'identifier' (which appears in two places) specifies the name for +the procedure. If no result is returned, the 'type' is omitted from +the PROCEDURE statement. + +Return from a procedure is implicit after the last statement of the +procedure, although no value is returned in this case. Return may be +explicitly specified with the RETURN statement: + + No value: RETURN ; + Value: RETURN expression ; + +Procedures may be declared with the special type INTERRUPT followed +by a number in the range 0 through 7. Such a procedure will be used +as an interrupt handler for the corresponding RST instruction. +Interrupts are re-enabled on return from an interrupt procedure. + +Procedures may not be recursive. Procedures are invoked either with +the CALL statement, or within an expression. + + Stand-alone: CALL identifier (arg, ...); + Within expressions: identifier (arg, ...) + +Built-in Procedures +=================== +INPUT(number) + Returns a BYTE value from the I/O port specified by 'number'. + +OUTPUT(number) = expression; + Sends the BYTE value of 'expression' to the I/O port specified + by 'number'. + +LENGTH(identifier) + Returns the number of elements in the array 'identifier'. + +LAST(identifier) + Returns the highest subscript for array 'identifier'. Note that + LAST = LENGTH - 1. + +LOW(expression) + Returns the low-order byte of 'expression'. + +HIGH(expression) + Returns the high-order byte of 'expression'. + +DOUBLE(expression) + Returns an ADDRESS value equivalent to 'expression'. High-order + zeroes are used to pad BYTE expressions. + +ROL(expr1, expr2) and ROR(expr1, expr2) + Returns the value of 'expr1' rotated left/right the number of bits + specified by 'expr2'. Both expressions must be BYTE values. The + value of 'expr2' must not be zero. + +SCL(expr1, expr2) and SCR(expr1, expr2) + Returns the value of 'expr1' rotated left/right the number of bits + specified by 'expr2'. The carry flag participates in the rotate. + 'expr2' must be a BYTE value; 'expr1' may be BYTE or ADDRESS. The + value returned is of the same type as 'expr1'. The value of + 'expr2' must not be zero. + +SHL(expr1, expr2) and SHR(expr1, expr2) + Returns the value of 'expr1' shifted left/right the number of bits + specified by 'expr2'. The last bit shifted out ends up in the + carry flag. 'expr2' must be a BYTE value; 'expr1' may be BYTE or + ADDRESS. The value returned is of the same type as 'expr1'. The + value of 'expr2' must not be zero. + +CALL TIME(expression) + The expression is evaluated as a BYTE value. The TIME procedure + delays 100 microseconds times the value. (Timing is based on + instruction execution times for the standard i8080 cpu.) + +DEC(expr1 + expr2) and DEC(expr1 PLUS expr2) + The two expressions must be unsubscripted variables, constants, + or expressions that represent BCD values. The DEC function does + the necessary decimal adjustment to produce the BCD result from + the addition. + +Pre-defined Variables +===================== +CARRY, ZERO, SIGN, PARITY + The values of these variables reflect the current values of the + cpu flags. + +MEMORY + The MEMORY variable is assigned the to the first memory location + following the PL/M program. It is useful for determining where + free memory begins. + +STACKPTR + The STACKPTR variable's value reflects the current value of the + SP register. The variable may be assigned a new value to alter + the stack register. + \ No newline at end of file diff --git a/ISIS PLM/PRLCOM.COM b/ISIS PLM/PRLCOM.COM new file mode 100644 index 0000000..c3d2c18 Binary files /dev/null and b/ISIS PLM/PRLCOM.COM differ diff --git a/ISIS PLM/PROCES.LIT b/ISIS PLM/PROCES.LIT new file mode 100644 index 0000000..195d01e --- /dev/null +++ b/ISIS PLM/PROCES.LIT @@ -0,0 +1,44 @@ +$nolist +/* + Proces Literals +*/ + + declare process$header literally + 'structure (pl address, + status byte, + priority byte, + stkptr address'; + declare bdos$save literally + 'disk$set$dma address, + disk$slct byte, + dcnt address, + searchl byte, + searcha address, + drvact address, + registers (20) byte, + scratch (2) byte)'; + declare process$descriptor literally + 'process$header, + name (8) byte, + console byte, + memseg byte, + b address, + thread address, + bdos$save'; + + declare rtr$status literally '0', + dq$status literally '1', + nq$status literally '2', + poll$status literally '3', + FlgWt$status literally '4', + Delay$status literally '5', + Swap$status literally '6', + Terminate$status literally '7', + Set$Prior$status literally '8', + Dispatch$status literally '9', + Attach$status literally '10', + Detach$status literally '11', + Set$cns$status literally '12'; + +$list + \ No newline at end of file diff --git a/ISIS PLM/QUEUE.LIT b/ISIS PLM/QUEUE.LIT new file mode 100644 index 0000000..04c219d --- /dev/null +++ b/ISIS PLM/QUEUE.LIT @@ -0,0 +1,47 @@ +$nolist +/* + Queue Literals +*/ + + declare queueheader literally + 'ql address, + name(8) byte, + msglen address, + nmbmsgs address, + dqph address, + nqph address'; + + declare queuehead literally + 'structure (queueheader)'; + + declare cqueue literally + 'queueheader, + msgin address, + msgout address, + msgcnt address '; + + declare circularqueue literally + 'structure (cqueue, + buf (1) byte )'; + + declare lqueue literally + 'queueheader, + mh address, + mt address, + bh address'; + + declare linkedqueue literally + 'structure (lqueue, + buf (1) byte )'; + + declare userqcbhead literally + 'structure (pointer address, + msgadr address )'; + + declare userqcb literally + 'structure (pointer address, + msgadr address, + name(8) byte)'; + +$list + \ No newline at end of file diff --git a/ISIS PLM/R.COM b/ISIS PLM/R.COM new file mode 100644 index 0000000..af52c34 Binary files /dev/null and b/ISIS PLM/R.COM differ diff --git a/ISIS PLM/README.TXT b/ISIS PLM/README.TXT new file mode 100644 index 0000000..31dfa20 --- /dev/null +++ b/ISIS PLM/README.TXT @@ -0,0 +1,89 @@ +This ZIP file contains the ISIS-II PLM-80 v3.1 compiler. + +These files were pulled from the MPM2 source code disks and from the ISIS environment for MS-DOS provided by INTEL. + +The file to invoke the ISIS environment under CP/M or MP/M is called ISX.COM. Some of the submit files included with the MP/M II source refered to a IS14.COM file, so I just copied the ISX.COM to IS14.COM and ISIS.COM leaving 3 files that do the exact same thing. + +Now, when the ISIS environment is running, it refers to the drives using the following syntax: + + :F0: - This is the CP/M drive A: + :F1: - This is the CP/M drive B: + :F2: - This is the CP/M drive C: + :F3: - This is the CP/M drive D: + +Get the picture? ISIS doesn't know anything about user numbers, so all files MUST be in USER 0 on each drive for the system to work. Also, if the ISIS environment can't find the file it is looking for in the current drive, it defaults to :F0:, then it fails. + +Several of the CP/M commands have direct equivalant versions, e.g.; + + CP/M ISIS-II + ---- ------- + DIR DIR + ERA ERA + TYPE TYPE + REN REN + DDT DBUG - This does some form of trace (asks, "TRACE LEVEL:" + ! - This is a comment indicator + A: :F0: + B: :F1: + C: :F2: + D: :F3: + +While the ISIS environment is running, your command prompt will be the floppy number followed by the greater than symbol, e.g.; for floppy drive A: (defualt) = "0>", for drive B: = "1>", etc. + +Some programs may allow you to extend the command line by supplying an ampersand "&" as the last character before pressing return. I haven't tried this yet. + +I haven't tried to compile CP/M using this system, so you will have to figure out how best to set up your environment to compile it. There is a site in the UK that has some instructions for compiling CPM 3 using the MS-DOS ISIS emulator, which I believe is also available through their site, which is http://www.seasip.demon.co.uk/Cpm/ + +I don't have ANY idea what the command syntax is for any of these commands. If anyone out there has documentation for the ISIS environment and utilities, I would appreciate a copy (!!!PLEASE!!!) + +Here is a brief description of the files, all files WITHOUT an extension are ISIS-II executable programs, some of the programs I didn't have time to figure out. + +ASM80 - ISIS-II 8080 Assembler, runs ONLY from ISIS environment. +CC.SUB - SUBMIT file to compile & link a PLM program for execution at 0x0100. +CONV86 - ISIS 8080 to 8086 assembler converter. +CPM - ISIS program to return to CPM from ISIS environment (used in SUBMIT files) + this program displays some garbage on my screen just before exiting ISIS. + This program also trashes the Z-System shell stack (don't know why, haven't + looked into it) + +*.LIT - Literal definitions for PLM programs. + +GENHEX.COM - CP/M OBJ to HEX converter utility. +GENMOD.COM - +HEXOBJ - ISIS hex to obj converter utility. + +IS14.COM, +ISX.COM, +ISIS.COM - The ISIS-II Environment for CP/M systems. + +IXREF - ISIS cross reference utility. +LIB - ISIS Librarian utility. +LINK - ISIS Linker utility. +LINK.OVL - ISIS Linker overlay file. +LOCATE - ISIS Object file locater utility. +MONX - +OBJCPM.COM - Used in CC.SUB script. +OBJHEX - +P.SUB - + +PLM80 - The ISIS-II PL/M-80 Compiler version 3.1 +PLM80.LIB - Runtime library. All programs link to this library. +PLM80.OV# - Overlay files for the compiler. + +PLMLANG.DOC - Brief description of the PL/M Language. +PLMSAMP.PLM - A Sample program written in PL/M. +READ.ME - This file. +SETEOF.COM - Used in CC.SUB script. +SUBMIT - ISIS-II Submit command (similar to CP/M's SUBMIT utility) + +X0#00 +X0#00.ASM - Link files for PL/M Programs. See CC.SUB script for usage. + +Enjoy, + +Rick Campbell +Sr. Technical Specialist +SpaceLabs Medical +rickca@jps.net + + \ No newline at end of file diff --git a/ISIS PLM/RSETSIMH.COM b/ISIS PLM/RSETSIMH.COM new file mode 100644 index 0000000..e055f07 Binary files /dev/null and b/ISIS PLM/RSETSIMH.COM differ diff --git a/ISIS PLM/RSETSIMH.MAC b/ISIS PLM/RSETSIMH.MAC new file mode 100644 index 0000000..0292a03 --- /dev/null +++ b/ISIS PLM/RSETSIMH.MAC @@ -0,0 +1,34 @@ + .Z80 ; mnemonics only + +SIMHPORT EQU 0FEH +resetSIMHInterfaceCmd EQU 14 +maxOut EQU 128 +printStringCmd EQU 09h +BDOS EQU 5 +CR EQU 13 +LF EQU 10 +CMDLINE EQU 80H + + ASEG + ORG 100H + + LD B,maxOut + LD A,resetSIMHInterfaceCmd +OUTAGN: OUT (SIMHPORT),A + DEC B + JP NZ,OUTAGN + LD A,(CMDLINE) ; number of character in command line + OR A + RET Z ; return if no command line + LD A,(CMDLINE+2) ; get first character (skip ' ') + CP 'V' ; if no 'V' (for verbose) + RET NZ ; done + LD DE,MSG + LD C,printStringCmd + CALL BDOS + RET + +MSG: DB CR,LF,'Reset SIMH interface done.',CR,LF,'$' + + END + \ No newline at end of file diff --git a/ISIS PLM/SETEOF.COM b/ISIS PLM/SETEOF.COM new file mode 100644 index 0000000..6bb5800 Binary files /dev/null and b/ISIS PLM/SETEOF.COM differ diff --git a/ISIS PLM/SHOWSEC.COM b/ISIS PLM/SHOWSEC.COM new file mode 100644 index 0000000..666fad0 Binary files /dev/null and b/ISIS PLM/SHOWSEC.COM differ diff --git a/ISIS PLM/SID.COM b/ISIS PLM/SID.COM new file mode 100644 index 0000000..ddb5aa9 Binary files /dev/null and b/ISIS PLM/SID.COM differ diff --git a/ISIS PLM/SPEED.COM b/ISIS PLM/SPEED.COM new file mode 100644 index 0000000..0df902a Binary files /dev/null and b/ISIS PLM/SPEED.COM differ diff --git a/ISIS PLM/STAT.COM b/ISIS PLM/STAT.COM new file mode 100644 index 0000000..abf37e0 Binary files /dev/null and b/ISIS PLM/STAT.COM differ diff --git a/ISIS PLM/SUBMIT b/ISIS PLM/SUBMIT new file mode 100644 index 0000000..aad1097 Binary files /dev/null and b/ISIS PLM/SUBMIT differ diff --git a/ISIS PLM/SUBMIT.COM b/ISIS PLM/SUBMIT.COM new file mode 100644 index 0000000..82325ad Binary files /dev/null and b/ISIS PLM/SUBMIT.COM differ diff --git a/ISIS PLM/SURVEY.COM b/ISIS PLM/SURVEY.COM new file mode 100644 index 0000000..2b0bf4e Binary files /dev/null and b/ISIS PLM/SURVEY.COM differ diff --git a/ISIS PLM/SURVEY.MAC b/ISIS PLM/SURVEY.MAC new file mode 100644 index 0000000..3800880 Binary files /dev/null and b/ISIS PLM/SURVEY.MAC differ diff --git a/ISIS PLM/SYSCOPY.COM b/ISIS PLM/SYSCOPY.COM new file mode 100644 index 0000000..6b68e80 Binary files /dev/null and b/ISIS PLM/SYSCOPY.COM differ diff --git a/ISIS PLM/SYSCPM2.SUB b/ISIS PLM/SYSCPM2.SUB new file mode 100644 index 0000000..972d9f4 --- /dev/null +++ b/ISIS PLM/SYSCPM2.SUB @@ -0,0 +1,48 @@ +; Create a bootable image on disk A: of CP/M with CCP +; Based on original Digital Research sources for CCP and BDOS +; Required sources are CFGCCP.LIB, MOVER.MAC, CCP.MAC, BDOS.MAC, CBIOSX.MAC +; Required programs: M80.COM, L80.COM, DDT.COM, BOOT.COM, BOOTGEN.COM +XSUB +; get correct configuration +PIP MEMCFG.LIB=CFGCCP.LIB +; create MOVER.COM +M80 =MOVER/M +L80 MOVER,MOVER/N/E +ERA MOVER.REL +; create CCP.COM +M80 =CCP/M +L80 CCP,CCP/N/E +ERA CCP.REL +; create BDOS.COM +M80 =BDOS/M +L80 BDOS,BDOS/N/E +ERA BDOS.REL +; create CBIOSX.COM +M80 =CBIOSX/M +L80 CBIOSX,CBIOSX/N/E +ERA CBIOSX.REL +; put pieces together +DDT +F100 5C00 0 +IMOVER.COM +R0000 +ICCP.COM +R0900 +IBDOS.COM +R1100 +ICBIOSX.COM +R1F00 +G0 +; create boot file +SAVE 44 CPMBOOT.COM +ERA MOVER.COM +ERA CCP.COM +ERA BDOS.COM +ERA CBIOSX.COM +ERA MEMCFG.LIB +; now perform a cold boot to get rid of XSUB +; this restores the original BIOS jump vector which is required by BOOTGEN +BOOT +; write boot file to reserved tracks, must be last command +BOOTGEN CPMBOOT.COM A: + \ No newline at end of file diff --git a/ISIS PLM/SYSDAT.LIT b/ISIS PLM/SYSDAT.LIT new file mode 100644 index 0000000..1eabc7b --- /dev/null +++ b/ISIS PLM/SYSDAT.LIT @@ -0,0 +1,111 @@ + + /* + System Data: byte assignments + ----------------------------- + + 000-000 Mem$top, top page of memory + 001-001 Nmb$cns, number of consoles + 002-002 Brkpt$RST, breakpoint RST # + 003-003 Add system call user stacks, boolean + 004-004 Bank switched, boolean + 005-005 Z80 version, boolean + 006-006 banked bdos, boolean + 007-007 RESBDOS top+1 (BNKBDOS XIOS jmp tbl) base page + 008-008 RESBDOS base page + 009-010 used by CP/NET for mstr cfg tbl addr + 011-011 XDOS base page + 012-012 RSP's (BNKXIOS top+1) base page + 013-013 BNKXIOS base page + 014-014 BNKBDOS base page + 015-015 Max$mem$seg, max memory segment number + 016-047 Memory segment table, filled in by GENSYS if + memory bank switched, otherwise by MPMLDR + 048-063 Breakpoint vector table, filled in by DDTs + 064-079 Unassigned + 080-095 System call user stacks + 096-119 Unassigned + 120-121 Nmb records in MPM.SYS + 122-122 # ticks/sec + 123-123 System Drive + 124-124 Common Memory Base Page + 125-125 Number of Rsp's + 126-127 Listcp Address + 128-143 Subflg, submit flag array + 144-180 Copyright message + 181-186 Serial # + 187-187 Max locked records/process + 188-188 Max open files/process + 189-190 # list items + 191-192 Pointer to base of lock table free space + 193-193 Total system locked records + 194-194 Total system open files + 195-195 Dayfile logging + 196-196 Temporary file drive + 197-197 Number of printers + 198-240 Unassigned + 241-241 Common Xdos base + 242-242 Banked Xdos base + 243-243 Tmp pd base + 244-244 Console dat base + 245-246 Bdos/Xdos address + 247-247 Tmp base address + 248-248 Nmbrsps + 249-249 Brsp base address + 250-251 Brspl, non-resident rsp process link + 252-253 Sysdatadr, MP/M data page address + 254-255 Rspl, resident system process link, the address + of the next Rsp, list terminates with a zero. + */ + + declare mem$top byte at (.system$data(000)); + declare nmb$cns byte at (.system$data(001)); + declare brkpt$RST byte at (.system$data(002)); + declare sys$call$stks boolean at (.system$data(003)); + declare bank$switched boolean at (.system$data(004)); + declare z80$cpu boolean at (.system$data(005)); + declare banked$bdos boolean at (.system$data(006)); + declare xios$jmp$tbl$base byte at (.system$data(007)); + declare resbdos$base byte at (.system$data(008)); + declare xdos$base byte at (.system$data(011)); + declare rsp$base byte at (.system$data(012)); + declare bnkxios$base byte at (.system$data(13)); + declare bnkbdos$base byte at (.system$data(14)); + declare nmb$mem$seg byte at (.system$data(015)); + declare mem$seg$tbl (8) structure ( + base byte, + size byte, + attrib byte, + bank byte ) + at (.system$data(016)); + declare breakpoint$vector (8) address at (.system$data(048)); + declare user$stacks (8) address at (.system$data(080)); + declare nmb$records address at (.system$data(120)); + declare ticks$per$second byte at (.system$data(122)); + declare system$drive byte at (.system$data(123)); + declare common$base byte at (.system$data(124)); + declare nmb$rsps byte at (.system$data(125)); + declare listcpadr address at (.system$data(126)); + declare submit$flags (16) address at (.system$data(128)); +/*declare copyright (37) byte at (.system$data(144));*/ +/*declare serial$number (6) byte at (.system$data(181));*/ + declare max$locked$records byte at (.system$data(187)); + declare max$open$files byte at (.system$data(188)); + declare total$list$items address at (.system$data(189)); + declare lock$free$space$adr address at (.system$data(191)); + declare total$system$locked$records byte at (.system$data(193)); + declare total$system$open$files byte at (.system$data(194)); + declare day$file byte at (.system$data(195)); + declare temp$file$drive byte at (.system$data(196)); + declare nmb$printers byte at (.system$data(197)); + declare cmnxdos$base byte at (.system$data(241)); + declare bnkxdos$base byte at (.system$data(242)); + declare tmpd$base byte at (.system$data(243)); + declare console$dat$base byte at (.system$data(244)); + declare bdos$xdos$adr address at (.system$data(245)); + declare tmp$base byte at (.system$data(247)); + declare nmb$brsps byte at (.system$data(248)); + declare brsp$base byte at (.system$data(249)); + declare brspl address at (.system$data(250)); + declare rspl address at (.system$data(254)); + + \ No newline at end of file diff --git a/ISIS PLM/TIMER.COM b/ISIS PLM/TIMER.COM new file mode 100644 index 0000000..83e6e68 Binary files /dev/null and b/ISIS PLM/TIMER.COM differ diff --git a/ISIS PLM/TIMER.MAC b/ISIS PLM/TIMER.MAC new file mode 100644 index 0000000..fe76173 --- /dev/null +++ b/ISIS PLM/TIMER.MAC @@ -0,0 +1 @@ + .Z80 ; mnemonics only SIMHPort equ 0feh printStringCmd equ 09h bdos equ 5 cr equ 13 lf equ 10 cmdLine equ 80h starttimercmd equ 1 quitTimerCmd equ 2 printTimerCmd equ 15 aseg org 100h jp start usage: db 'Usage: TIMER S|P|Q',cr,lf db ' S = Start a new timer',cr,lf db ' P = Print time of most recent timer',cr,lf db ' Q = Quit most recent timer',cr,lf,'$',1AH start: ld a,(cmdLine) ; get number of characters on command line or a jp z,pusage ; print usage, if command line empty ld a,(cmdLine+2) ; get first character ld hl,table ; points to (letter, command)^3 ld b,3 ; 3 elements in table again: cp (hl) ; compare command line letter with table entry inc hl ; point to command jp z,found ; if found inc hl ; otherwise proceed to next entry dec b ; decrement loop counter jp nz,again ; try next character pusage: ld de,usage ; address of usage text ld c,printStringCmd ; CP/M command for print jp bdos ; print it, get ret from bdos found: ld a,(hl) ; get SIMH command out (SIMHPort),a ; send to SIMH port ret ; and done table: db 'S',starttimercmd db 'P',printTimerCmd db 'Q',quitTimerCmd timend equ $ ds 0200h-timend ; fill remainder with zeroes end  \ No newline at end of file diff --git a/ISIS PLM/TRINT.LST b/ISIS PLM/TRINT.LST new file mode 100644 index 0000000..9dddbf3 --- /dev/null +++ b/ISIS PLM/TRINT.LST @@ -0,0 +1,39 @@ + + + +:F2:ASM80 :F3:TRINT.SRC + + +ISIS-II 8080/8085 MACRO ASSEMBLER, V2.0 MODULE PAGE 1 + + + LOC OBJ SEQ SOURCE STATEMENT + + 1 ; PIP INTERFACE TO BDOS (CAN BE USED FOR OTHER TRANSIENTS) + 2 PUBLIC BOOT,IOBYTE,BDISK,BDOS,MON1,MON2,MON3 + 3 PUBLIC MAXB,FCB,BUFF + 0000 4 BOOT EQU 0000H ;WARM START + 0003 5 IOBYTE EQU 0003H ;IO BYTE + 0004 6 BDISK EQU 0004H ;BOOT DISK # + 0005 7 BDOS EQU 0005H ;BDOS ENTRY + 0005 8 MON1 EQU 0005H ;BDOS ENTRY + 0005 9 MON2 EQU 0005H ;BDOS ENTRY + 0005 10 MON3 EQU 0005H ;BDOS ENTRY + 0006 11 MAXB EQU 0006H ;MAX MEM BASE + 005C 12 FCB EQU 005CH ;DEFAULT FCB + 0080 13 BUFF EQU 0080H ;DEFAULT BUFFER + 14 END + +PUBLIC SYMBOLS +BDISK A 0004 BDOS A 0005 BOOT A 0000 BUFF A 0080 FCB A 005C IOBYTE A 0003 MAXB A 0006 +MON1 A 0005 MON2 A 0005 MON3 A 0005 + +EXTERNAL SYMBOLS + + +USER SYMBOLS +BDISK A 0004 BDOS A 0005 BOOT A 0000 BUFF A 0080 FCB A 005C IOBYTE A 0003 MAXB A 0006 +MON1 A 0005 MON2 A 0005 MON3 A 0005 + +ASSEMBLY COMPLETE, NO ERRORS + \ No newline at end of file diff --git a/ISIS PLM/TRINT.OBJ b/ISIS PLM/TRINT.OBJ new file mode 100644 index 0000000..0049335 Binary files /dev/null and b/ISIS PLM/TRINT.OBJ differ diff --git a/ISIS PLM/TRINT.SRC b/ISIS PLM/TRINT.SRC new file mode 100644 index 0000000..72de2ac --- /dev/null +++ b/ISIS PLM/TRINT.SRC @@ -0,0 +1,15 @@ +; PIP INTERFACE TO BDOS (CAN BE USED FOR OTHER TRANSIENTS) + PUBLIC BOOT,IOBYTE,BDISK,BDOS,MON1,MON2,MON3 + PUBLIC MAXB,FCB,BUFF +BOOT EQU 0000H ;WARM START +IOBYTE EQU 0003H ;IO BYTE +BDISK EQU 0004H ;BOOT DISK # +BDOS EQU 0005H ;BDOS ENTRY +MON1 EQU 0005H ;BDOS ENTRY +MON2 EQU 0005H ;BDOS ENTRY +MON3 EQU 0005H ;BDOS ENTRY +MAXB EQU 0006H ;MAX MEM BASE +FCB EQU 005CH ;DEFAULT FCB +BUFF EQU 0080H ;DEFAULT BUFFER + END + \ No newline at end of file diff --git a/ISIS PLM/UNCR.COM b/ISIS PLM/UNCR.COM new file mode 100644 index 0000000..61a87e9 Binary files /dev/null and b/ISIS PLM/UNCR.COM differ diff --git a/ISIS PLM/UNERA.COM b/ISIS PLM/UNERA.COM new file mode 100644 index 0000000..91be243 Binary files /dev/null and b/ISIS PLM/UNERA.COM differ diff --git a/ISIS PLM/UNERA.MAC b/ISIS PLM/UNERA.MAC new file mode 100644 index 0000000..5d3e4f3 Binary files /dev/null and b/ISIS PLM/UNERA.MAC differ diff --git a/ISIS PLM/USQ.COM b/ISIS PLM/USQ.COM new file mode 100644 index 0000000..db941ac Binary files /dev/null and b/ISIS PLM/USQ.COM differ diff --git a/ISIS PLM/W.COM b/ISIS PLM/W.COM new file mode 100644 index 0000000..659088d Binary files /dev/null and b/ISIS PLM/W.COM differ diff --git a/ISIS PLM/WM.COM b/ISIS PLM/WM.COM new file mode 100644 index 0000000..2243c48 Binary files /dev/null and b/ISIS PLM/WM.COM differ diff --git a/ISIS PLM/WM.HLP b/ISIS PLM/WM.HLP new file mode 100644 index 0000000..080a75f --- /dev/null +++ b/ISIS PLM/WM.HLP @@ -0,0 +1,65 @@ + VIDEO MODE SUMMARY (TYPE ^J FOR NEXT FRAME) + +^O INSERTION ON/OFF RUB DELETE CHR LEFT +^S CURSOR LEFT CHAR ^G DELETE CHR RIGHT +^D CURSOR RIGHT CHAR ^\ DELETE WORD LEFT +^A CURSOR LEFT WORD ^T DELETE WORD RIGHT +^F CURSOR RIGHT WORD ^U DELETE LINE LEFT +^Q CURSOR RIGHT TAB ^K DELETE LINE RIGHT +^E CURSOR UP LINE ^Y DELETE WHOLE LINE +^X CURSOR DOWN LINE ^I PUT TAB IN FILE +^^ CURSOR TOP/BOT SCREEN ^N PUT CRLF IN FILE +^B CURSOR RIGHT/LEFT LINE ^@ DO NEXT CHR 4X +^W FILE DOWN 1 LINE ^P NEXT CHR IN FILE +^Z FILE UP 1 LINE ^V NEXT CHR(S) TO VIDEO +^R FILE DOWN SCREEN ESC EXIT VIDEO MODE +^C FILE UP SCREEN ^J DISPLAY THIS + COMMAND MODE SUMMARY (TYPE ^J FOR NEXT FRAME) + ++- MEANS + OR - ALLOWED HERE, + ASSUMED IF OMITTED +@ MEANS CARRIAGE RETURN OR LINE FEED NECESSARY HERE +$ MEANS ESC OR ^Z OR CARRIAGE RETURN NECESSARY HERE +n MEANS A NUMBER, 1 ASSUMED IF OMITTED, # = 65535 + ++-nC MOVE n CHARACTERS +-nD DELETE n CHARACTERS ++-nL MOVE n LINES +-nK KILL(DELETE) n LINES ++-nT TYPE n LINES nZ SLEEP n SECONDS ++-nP MOVE, TYPE n PAGES +-n@ MOVE n LINES, TYPE 1 ++-B MOVE TOP/BOTTOM FILE ^J SAME AS 1@ + +nItext$ INSERT text n TIMES +I@ ENTER INSERT MODE (ESC OR ^Z EXITS MODE) +A@, nAtext$ (APPEND) DO 1L THEN JUST LIKE INSERT +n<....> LOOP: REPEAT .... n TIMES (DEFAULT = 65535) +nM....@ (MACRO) SAME AS ABOVE + COMMAND MODE SUMMARY (TYPE ^J FOR NEXT FRAME) + ++-nFkey$ (FIND) SHORT SEARCH FOR key n TIMES ++-nNkey$ (NEXT) LONG SEARCH FOR key n TIMES ++-nSkey$text$ SUBSTITUTE AFTER SHORT SEARCH n TIMES ++-nRkey$text$ (REPLACE) SUBSTITUTE AFTER LONG SEARCH +/F,/N,/S,/R SAME, EXCEPT EXIT <..> OR QX IF NOT FOUND + +Y[d:]name.typ$ (YANK) READS FILE IN AT CURSOR +nW[d:]name.typ$ WRITE n LINES INTO THE FILE NAMED + +^N CRLF INSIDE TEXT OR KEY ^Y ESC INSIDE TEXT OR KEY +^A MATCHES ANY IN KEY ^S MATCHES SEPERATOR IN KEY +^OX MATCHES NOT X IN KEY + COMMAMD MODE SUMMARY (TYPE ^J TO RETURN TO EDITING) + +nQP PUT n LINES INTO Q BUFFER, DELETE FROM FILE, n>0 +n/QP APPEND n LINES TO Q BUFFER, DELETE FROM FILE, n>0 +nQG (GET) COPY Q BUFFER INTO FILE n TIMES +nQT TYPE Q BUFFER n TIMES +nQK (KILL) CLEAR Q BUFFER +nQX EXECUTE COMMANDS IN Q BUFFER n TIMES +nQLtext$ (LOAD) PUT text INTO Q BUFFER +n/QLtext$ APPEND text TO Q BUFFER n TIMES + +V ENTER VIDEO MODE N! PUT CHR CODE N INTO FILE +; ALL FOLLOWING IS COMMENT E END EDIT +H END EDIT AND START OVER Q (QUIT) ABANDON EDIT +O RETURN TO ORIGINAL FILE ^Q DISPLAY HELP FILE +^V NEXT CHR(S) TO VIDEO ^C INTERRUPT COMMAND + \ No newline at end of file diff --git a/ISIS PLM/X0100 b/ISIS PLM/X0100 new file mode 100644 index 0000000..2635cb0 Binary files /dev/null and b/ISIS PLM/X0100 differ diff --git a/ISIS PLM/X0100.ASM b/ISIS PLM/X0100.ASM new file mode 100644 index 0000000..e21b2b5 --- /dev/null +++ b/ISIS PLM/X0100.ASM @@ -0,0 +1,27 @@ +$title ('PRL Externals') + name x0100 + CSEG +offset equ 0000h + +mon1 equ 0005h+offset +mon2 equ 0005h+offset +mon2a equ 0005h+offset +mon3 equ 0005h+offset + public mon1,mon2,mon2a,mon3 +cmdrv equ 0050h+offset +fcb equ 005ch+offset +pass0 equ 0051h+offset +len0 equ 0053h+offset +fcb16 equ 006ch+offset +pass1 equ 0054h+offset +len1 equ 0056h+offset +tbuff equ 0080h+offset + public cmdrv,fcb,pass0,len0 + public fcb16,pass1,len1,tbuff +bdisk equ 0004h+offset +maxb equ 0006h+offset +buff equ 0080h+offset +boot equ 0000h+offset + public bdisk,maxb,buff,boot + END + \ No newline at end of file diff --git a/ISIS PLM/X0200 b/ISIS PLM/X0200 new file mode 100644 index 0000000..2708a91 Binary files /dev/null and b/ISIS PLM/X0200 differ diff --git a/ISIS PLM/X0200.ASM b/ISIS PLM/X0200.ASM new file mode 100644 index 0000000..29c3208 --- /dev/null +++ b/ISIS PLM/X0200.ASM @@ -0,0 +1,27 @@ +$title ('PRL Externals') + name x0200 + CSEG +offset equ 0100h + +mon1 equ 0005h+offset +mon2 equ 0005h+offset +mon2a equ 0005h+offset +mon3 equ 0005h+offset + public mon1,mon2,mon2a,mon3 +cmdrv equ 0050h+offset +fcb equ 005ch+offset +pass0 equ 0051h+offset +len0 equ 0053h+offset +fcb16 equ 006ch+offset +pass1 equ 0054h+offset +len1 equ 0056h+offset +tbuff equ 0080h+offset + public cmdrv,fcb,pass0,len0 + public fcb16,pass1,len1,tbuff +bdisk equ 0004h+offset +maxb equ 0006h+offset +buff equ 0080h+offset +boot equ 0000h+offset + public bdisk,maxb,buff,boot + END + \ No newline at end of file diff --git a/ISIS PLM/XDOS.LIT b/ISIS PLM/XDOS.LIT new file mode 100644 index 0000000..47efd0f --- /dev/null +++ b/ISIS PLM/XDOS.LIT @@ -0,0 +1,45 @@ +$nolist +/* + Xdos Literals +*/ + + declare abs$request literally '128', + rel$request literally '129', + memory$free literally '130', + poll literally '131', + flag$wait literally '132', + flag$set literally '133', + make$queue literally '134', + open$queue literally '135', + delete$queue literally '136', + read$queue literally '137', + cond$read$queue literally '138', + write$queue literally '139', + cond$write$queue literally '140', + delay literally '141', + dispatch literally '142', + terminate literally '143', + create literally '144', + set$priority literally '145', + attach literally '146', + detach literally '147', + set$console literally '148', + assign$console literally '149', + send$cli$command literally '150', + call$res$sys$p literally '151', + parse$fname literally '152', + get$console$nmb literally '153', + system$data$adr literally '154', + get$tod literally '155', + rtn$pd$adr literally '156', + abort$spcfd$proc literally '157', + attach$list literally '158', + detach$list literally '159', + set$list literally '160', + cond$attach$list literally '161', + cond$attach literally '162', + mpm$ver literally '163', + get$list$nmb literally '164'; + +$list + \ No newline at end of file diff --git a/ISIS PLM/XFORMAT.COM b/ISIS PLM/XFORMAT.COM new file mode 100644 index 0000000..f7fd118 Binary files /dev/null and b/ISIS PLM/XFORMAT.COM differ diff --git a/ISIS PLM/XSUB.COM b/ISIS PLM/XSUB.COM new file mode 100644 index 0000000..15e86ab Binary files /dev/null and b/ISIS PLM/XSUB.COM differ diff --git a/ISIS PLM/ZAP.COM b/ISIS PLM/ZAP.COM new file mode 100644 index 0000000..47ffcbb Binary files /dev/null and b/ISIS PLM/ZAP.COM differ diff --git a/ISIS PLM/ZSID.COM b/ISIS PLM/ZSID.COM new file mode 100644 index 0000000..5a15b66 Binary files /dev/null and b/ISIS PLM/ZSID.COM differ diff --git a/ISIS PLM/ZTRAN4.COM b/ISIS PLM/ZTRAN4.COM new file mode 100644 index 0000000..937008c Binary files /dev/null and b/ISIS PLM/ZTRAN4.COM differ diff --git a/SysCon PLMX/CODA.PLM b/SysCon PLMX/CODA.PLM new file mode 100644 index 0000000..b3ce731 Binary files /dev/null and b/SysCon PLMX/CODA.PLM differ diff --git a/SysCon PLMX/FNLCG.PLM b/SysCon PLMX/FNLCG.PLM new file mode 100644 index 0000000..a3d4b97 Binary files /dev/null and b/SysCon PLMX/FNLCG.PLM differ diff --git a/SysCon PLMX/GKSL.TXT b/SysCon PLMX/GKSL.TXT new file mode 100644 index 0000000..2df0aed --- /dev/null +++ b/SysCon PLMX/GKSL.TXT @@ -0,0 +1,766 @@ +GKSL.WS4 +-------- + +- "Systems Languages: Management's Key to Controlled Software Evolution" + Gary Kildall + Proceedings of the 1974 western electronics show and convention (WESCON), + September 1974 ("1974 WESCON Technical Papers", Volume 18, Session 19/2) + +(Retyped by Emmanuel ROCHE.) + + +Abstract +-------- + +Current industry trends forecast widespread use of microcomputers to simplify +the design, development, and manufacture of many digital electronics products. +The effects of microcomputer software design upon the production cycle is +presented, emphasizing the necessity for well-organized software systems. +High-level systems languages are introduced as an aid in software +organization, using Intel's PL/M as a specific example. + + +Introduction +------------ + +The general availability of the low-cost microcomputer, or "CPU on a chip", is +undoubtedly the greatest single breakthrough in digital design technology in +this decade. Although relatively inexpensive general-purpose computers have +been packaged as end-user oriented minicomputers for several years, it is now +economically feasible to design-in a microcomputer set into the heart of a +digital system produced in large quantities. Though only recently introduced, +microcomputers have been applied to a wide spectrum of digital processing, +from simple device controllers through sophisticated word-processing systems. +In fact, the ability to treat a microprocessor as simply another relatively +inexpensive component has led to simplification of many current product +designs, and opened the door to a vast array of digital applications limited +only by one's imagination. + +Simply stated, the microcomputer allows us to economically substitute +programming for wiring. Although there are tremendous savings in software +development when compared with hardware breadboarding, there are also inherent +difficulties in controlling the evolution of a software-based product. Control +over software evolution becomes especially important in the more comprehensive +microcomputer applications, such as small business systems. The purpose here +is to identify and investigate some of these difficulties from the project +manager's viewpoint. The notion of a "systems language" is introduced as an +aid to control of software evolution in high-quantity microcomputer-based +products where a significant software investment is involved. As a specific +example, Intel's high-level systems language, called PL/M, is presented. + +The general product evolution cycle is discussed first, in order to +characterize the effects of software development upon this cycle. + + +Product evolution +----------------- + +The wealth of new digital applications, when coupled with rapid technological +change, place severe demands upon the project manager. A product must be +planned with change in mind, in order to extend its sales window beyond the +next unpredictable technological breakthrough. In fact, product evolution can +be considered the cyclic process of change involving the product definition in +order to adapt to the environment. The product environment, in turn, involves +such factors as market trends, customer requirements, competitor reaction, and +new technology. It is obvious that the adaptability of a product to a changing +environment directly determines its survival in the marketplace. The product +evolution cycle is shown graphically in Figure 1, distinguishing the 2 major +branches of engineering and manufacturing, and marketing. The advent of the +LSI microprocessor is an example of a technological advancement which affects +the product evolution cycle. Random logic or custom chip fabrication can now +be economically replaced by any of a number of low-cost ROM-driven digital +processors which can perform complicated logic, arithmetic, and sequencing +operations. As a result, the microprocessor can provide central and peripheral +control and processing in many designs, greatly reducing time and cost in +product specification, development, and production. + + | + V + +--------------------> Formulation <--------------------+ + | | | + | +---------+--------+ | + | | | | + | V | | + +-----> Internal specification | | + | | V | + | | External documentation <-----+ + | V | | + +-----> Design, Check-out V | + | | Marketing strategy <-----+ + | V | | + +-----> Manufacturing | | + | | | | + | +--> Sales, Distribution <--+ | + | | | + | V | + +--<--------------- Customer response --------------->--+ + + Figure 1. The product evolution cycle + +The effects of microcomputer use on the marketing cycle have been investigated +elsewhere [Ref.1], and thus the discussion turns to engineering and +manufacturing aspects. Referring to Figure 1, product specification efforts +are reduced, since operation of a device can be specified in terms of +conceptually simpler computer programs, rather than complicated logic +diagrams. Further, the circuitry necessary for interfacing with the electronic +environment is generally reduced to specification of simple modular units. + +Design, development, and check-out efforts are reduced in a number of ways. +First, the flexibility inherent in programming allows principal algorithms to +be written, tested, and reprogrammed in a relatively short period, using the +software development tools which are available from the major microcomputer +manufacturers. This flexibility allows the designer to develop programs in a +software "test bed", roughly equivalent to a hardware breadboard for circuit +testing. Subroutines communicate with a standard device, such as a teletype, +where data is manually entered, representing information which would normally +be expected from the corresponding circuitry. This technique allows the +principal control functions to be developed and independently checked before +system integration. In addition, the forced modularity of the peripheral +circuitry implies that each individual module can also be designed, +breadboarded, and tested independently. + +System integration is thus simplified, since each hardware and software +subsystem has been verified. The simulating subroutines and simulated devices +are individually replaced by their corresponding actual circuitry and drivers, +thus isolating system design errors at each step of the integration. + +Finally, manufacturing is simplified, since standard microprocessor modules +can either be purchased from OEM suppliers, or developed in-house. These +standard modules generally involve fewer parts than corresponding random logic +designs, thus reducing both PC (ROCHE> Note that Gary Kildall uses the term +"PC" 7 years (!) before the birth of the "IBM Clown"...) board layout efforts +and costs for board production and testing. Given that the microprocessor +modules are properly checked-out, the transition from software prototype to +production software is immediate. Further, production changes often involve +software modifications which affect ROM contents, rather than requiring +assembly alterations. + +Thus, the use of microcomputers and their associated software development +tools can significantly reduce the time and costs for the first engineering +and manufacturing cycle of an electronic product. + +Consider now the cyclic evolution of a microcomputer-based product as it +adapts to market pressures. Clearly, the adaptability of the product is +directly governed by the adaptability of its software system. That is to say, +since most modifications are accomplished through program changes, one can +consider the product's evolution in terms of the evolution of its associated +software. Changes may arise in a number of ways, including requests from +customers for increased facilities, alterations required by design errors +detected through field use, or modifications caused by cost advantages in +using newly available hardware devices or software techniques. Thus, software +evolution must be a major concern of the project manager: with proper control, +each cyclic regeneration of software systems improves upon its predecessor. +Loss of control over software evolution results in a maze of over-specialized +algorithms and data structures which hinder successive product cycles, to the +point where entire systems must be re-developed. Factors affecting software +evolution are presented in the paragraphs which follow. + + +Software evolution +------------------ + +Similar to product evolution, the evolution of a software system can be +considered the cyclic process of change in program design and expression, in +order to adapt to the changing product definition. The 3 factors which most +affect software adaptability are listed below. + + 1) Maintainability is a mesure of the ease with which a particular + program can be corrected when an error is found in the product. + + 2) Expandability determines the effort required to add new features or + subsystems as the product definition changes. + + 3) Portability among programmers, machine designs, and manufacturers + determines the extent to which a software system depends upon a + particular software or hardware designer and design philosophy. + +Maintainability, expandability, and portability of software directly determine +time and cost for program regeneration. Programs are developed only once, but +are maintained throughout their lifetime. Thus, the ease of program correction +is a major concern in the overall software evolution cycle. Second, as new +features or capabilities are added to the product, corresponding extensions +are necessary to the programs. Programs written with expansion as a principal +design goal adapt easily, while those which are not cause excessive delay +during redesign. When time constraints prevent proper redesign of non- +expandable programs, the resulting "interim" software is often undependable +and cannot be properly maintained, thus adversely affecting subsequent +evolution. Finally, unlike random logic designs, software systems easily +become dependent upon a particular programmer, or upon a particular machine +architecture or manufacturer. In most cases, if the project manager finds +advantages in changing any of these variables, the software must be mainly +reconstructed, often obviating those advantages. In fact, in this rapidly +moving industry, the ease with which programs can be effectively moved between +machines of differing design, while being readily understood by a number of +different programmers, may be the most important single influence upon the +software evolution cycle. + +Clearly, there are many aspects of software design which determine +maintainability, expandability, and portability, and a complete treatment of +all factors is beyond the scope of this paper. The reader is encouraged, +however, to refer to notes on structured programming [Ref.2 and 3], software +engineering [Ref.4], and programming management [Ref.5] for additional +details. One important, but intangible, factor is the training, experience, +and problem insight of the project programmers. Even the most experienced +programmer, however, depends upon the programming tools that are available to +express his or her solution. As a result, these tools have a profound effect +upon the adaptability of the product's software. + + +Programming tools +----------------- + +The discussion of software evolution now focuses upon the degree of +adaptability obtained from the various approaches to microcomputer +programming. In particular, a programming language is the programmer's +principal means of expressing the algorithms and data structures which perform +the specified product function. There are 4 basic methods used in +microcomputer software development for expressing programs: machine language, +assembly language, macro assembly language, and high-level language +programming. These 4 methods are briefly reviewed below for completeness. + +1) Machine language programming uses the bit patterns recognized by the +microprocessor as a means for expressing programs. All program and data +locations are referenced by their absolute addresses in memory. + +2) Assembly language programming is one step removed from a machine level +expression of a program. It allows the programmer to use symbolic names for +each of the processor's operation codes, and automatically translates these +codes to the proper bit patterns for microcomputer execution. The programmer +references program and data addresses by freely-assigned symbolic names, +rather than absolute addresses. In all cases, however, there is a one-to-one +correspondence between symbolic instructions written by the programmer and the +translated machine level instructions. Thus, an assembly language can be +considered a convenient means of expressing machine level instructions. Figure +2 shows a sample assembly language program, and the corresponding machine +level code for an Intel 8080 microcomputer [Ref.6]. Note that the memory +locations and machine operation codes are given as hexadecimal values in this +figure. + + +------------- Location + | +-------- Machine language + | | Assembly language and comments + | | | + V V V + ; Sample assembly language program + ; for the Intel 8080 microcomputer. + ; + ; Compare the values of X and Y, + ; store the larger value into Z. + ; + ;-------------------------------- + 0100 ORG 0100H ; Start program code at 0100H + ;-------------------------------- + ; + 0100 211301 LXI H,y ; Address Y + 0103 7E MOV A,M ; Load + 0104 EB XCHG ; Exchange DE,HL + 0105 211201 LXI H,x ; Address X + 0108 BE CMP M ; Compare memory + ; + ; Carry is set if X > Y + ; + 0109 DA0D01 JC setc ; Jump if no Carry + ; + ; X is less or equal + ; + 010C EB XCHG ; Exchange DE,HL + ; + 010D 7E setc: MOV A,M ; Load X or Y + 010E 321401 STA z ; Store + ; + ;-------------------------------- + 0111 76 HLT ; Halt processor + ;-------------------------------- + ; Variable definitions. + ; + 0112 00 x DB 0 + 0113 00 y DB 0 + 0114 00 z DB 0 + ; + ;-------------------------------- + 0115 END 0100H + + Figure 2. Machine language and assembly language programs for the + Intel 8080 microcomputer. + +3) Macro assembly language is similar to assembly language coding, except that +the programmer is allowed to define and use macros. A macro is a predefined +group of assembly language statements which is given a macro name. Each use of +the macro name causes the predefined instructions or data definitions to be +directly substituted for the name. Thus, for example, the programmer can +effectively "invent" new machine operations as necessary for concise +expression of a particular problem. Additional facilities, such as conditional +assembly and assembly-time expression evaluation, are usually present in a +macro assembly language, which make it considerably more flexible than a +simple assembly language. + +4) High-level language programming is one step further removed from assembly +language programming. Normally, the notation used in a high-level language +more closely resembles common mathematical symbolism, rather than relying upon +complicated sequences of machine instructions to perform a specific function. +For example, the hih-level statement + + IF x > y THEN z = x; ELSE z = y + +is read as follows: "if the value of X is greater than the value of Y, then +store X's value into Z; otherwise, store Y's value into Z". The effect is that +Z's new value is the larger of X and Y. Each high-level statement is +translated into a sequence of machine level instructions by a compiler for the +language. The statement given above is translated into the equivalent machine +code shown in Figure 2 by Intel's PL/M compiler for the 8080 microcomputer +[Ref.7]. In general, a high-level language provides primitive operations, data +types, and control structures which are appropriate for expressing programs +within a particular problem environment. Thus, a high-level language is +reasonably independent of a particular machine design and, instead, tends to +depend upon the type of problem being solved. These concepts are examined in +later sections. + +How do these various language levels affect software evolution? First, machine +level coding is generally considered inappropriate for even moderate projects, +due to the non-symbolic nature of the resulting programs. Assembly language +programming, with or without macro capabilities, may be appropriate for +moderately-sized programs. However, the adaptability of the final product is +highly dependent upon the coding practices of the project programmers, as well +as the coding standards set forth and enforced by the project manager. +Portability between programmers is relatively difficult, and depends +principally upon the quality of the program's documentation, rather than the +programs themselves. Portability from machine to machine is severely +restricted, and is usually accomplished only at the option of the +manufacturer. Assembly language programs written for Intel's 8008 +microcomputer, for example, can be re-assembled for their new 8080 +microcomputer with only minor changes in the original program. Although the +resulting programs benefit from the increased speed of the new processor, they +must be rewritten to take advantage of the 8080's expanded instruction set. +High-level languages, however, currently provide the highest degree of +maintainability, expandability, and portability of any of these programming +tools. In fact, a specific class of high-level languages, called systems +languages, are considered the most appropriate tool for controlling software +evolution. + + +Systems languages +----------------- + +As stated previously, a high-level language is relatively independent of a +particular machine architecture, and is primarily intended to provide a +concise means for expressing programs in a particular problem environment. The +BASIC and FORTRAN programming languages, for example, are high-level languages +which assume a scientific computation problem environment. The actual machine +on which a BASIC or FORTRAN program executes should have little effect on the +resulting output. + +A high-level systems language is more specialized, since it assumes the +problem environment is the control of a particular machine or class of +machines. Thus, the goals are somewhat different than those of a pure high- +level language: a high-level systems language must be relatively independent +of the exact computer, while providing the necessary control structures, data +types, and basic operations for clear and concise expression of systems for a +particular type of computer. It follows that such a systems language must +allow complete control of all machine functions, and, at the same time, +eliminate the needless trivialities of assembly language. In addition, a +systems language must also be structured in such a way that it can be easily +translated to efficient machine language programs for the target machine. Each +operation in the systems language has a direct counterpart in the machine, +resulting in little or no run-time support software. + +The primitive operations and data types for a microcomputer systems language +are fairly simple. Bit-level data occur frequently when communicating with +peripheral circuitry, such as the status information received from an input or +output device. Thus, bit-level data types must be present, along with +corresponding shifting, masking, and bit-testing operations. Character +handling is also an important function in word-processing and data +communication applications. As a result, string data types should be allowed, +with facilities for comparing strings, selection of substrings, and conversion +between other data types. Fundamental arithmetic processing is also necessary, +but the data types may depend heavily upon the microcomputer architecture. +Based upon current offerings, the useful arithmetic data types include 4-bit +decimal (BCD) operands, and 8-, 16-, and 32-bit fixed-point binary quantities, +along with the usual arithmetic and relational operations. Finally, +communication primitives must be provided for environmental monitoring and +control. + +Given that a particular microcomputer can support these functions, it is +certainly the case that the operations and data types can be included in a +macro assembly language for the processor. In a systems language, however, +these facilities are imbedded in a convenient expressional notation, and +enhanced by comprehensive data definition and program control facilities. That +is to say, along with the necessary basic functions, the programmer is +provided with language statements which allow program expression in a readable +or "well-structured" [Ref.8] form. These structures normally include a natural +notation for statement grouping, conditional branching, and iteration or loop +control. Furthermore, subroutine definition, parameter specification, and +subroutine invocation mechanisms are normally provided. As a result, +subroutine linkage standards are enforced, modular programming is encouraged, +and construction of comprehensive subroutine libraries becomes practical. The +PL/M microcomputer systems language presented in the following section is used +to illustrate these capabilities. + + +A case in point +--------------- + +Intel's PL/M high-level language provides an example of a systems language for +programming their 8-bit microcomputers. The statement structure of PL/M +resembles IBM's PL/1 programming language and, in fact, was derived from XPL +which is a dialect of PL/1. The similarity, however, is only superficial; +differences in control structures, operations, and data types make PL/1 useful +for general applications programming, while those of XPL make it appropriate +for compiler implementation. PL/M was designed with the special needs of +microcomputer systems in mind, as given in the previous section, and thus is +neither a subset nor superset of these languages. The important point is that +PL/M belongs to the general family of "PL languages", and thus a programmer +who is familiar with one of these languages finds it relatively easy to learn +any of the others. Figure 3 contains a listing of a PL/M program similar to +one proposed by Popper [Ref.9] for comparing high-level and assembly language +microcomputer programming. Although Popper gives a complete description of the +program in his notes, the overall structure is presented as an example of PL/M +program organization. + +/* Quicksort procedure + +This PL/M procedure sorts an array into ascending order +using the QUICKSORT algorithm. Included in this listing +is the procedure, QUICKSORT, and a test driver program +to demonstrate the calling sequence. Note that the +procedure is written with an assumption that the number +of elements to be sorted is less than or equal to 256 +(low,high,uptr,dptr,lstack,hstack,array$size,a1, +and a2 are byte variables) and that the precision of +the array elements is 8 bits (list,temp, and ref are +byte variables). These restrictions may be lifted by +changing the declarations. Note also that the +working arrays (lstack and hstack) are dimensioned +by stack$size, where + + stack$size >= log2 (array$size) + +*/ + +quicksort: + PROCEDURE (array, array$size); + DECLARE stack$size LITERALLY '10'; + DECLARE array ADDRESS; + DECLARE array$size BYTE; + DECLARE list BASED array BYTE; + DECLARE lstack (stack$size) BYTE, hstack (stack$size) BYTE; + DECLARE top BYTE; + DECLARE (low, dptr, uptr, high) BYTE; + DECLARE (ref, temp) BYTE; + + push: + PROCEDURE (a1, a2); + DECLARE (a1, a2) BYTE; + + lstack (top) = a1; + hstack (top) = a2; + top = top + 1; + END push; + + /* Main program */ + + top = 0; + CALL push (0, array$size); + DO WHILE top <> 0; + top = top - 1; + IF (dptr := (low := lstack (top))) + <> (uptr := (high := hstack (top))) THEN + DO ; + ref = list (low); + down: + DO WHILE list (dptr) <= ref AND high > dptr; + dptr = dptr + 1; + END; + DO WHILE list (uptr) >= ref AND low < uptr; + uptr = uptr - 1; + END; + IF dptr < uptr THEN + DO ; + temp = list (uptr); + list (uptr) = list (dptr); + list (dptr) = temp; + dptr = dptr + 1; + uptr = uptr - 1; + GO TO down; + END; + IF uptr > low THEN + DO ; + list (low) = list (uptr); + list (uptr) = ref; + uptr = uptr - 1; + END; + CALL push (low, uptr); + CALL push (dptr, high); + END; + END; + END quicksort; + +/* Begin test driver */ + +DECLARE test$array (16) BYTE INITIAL + (0,15,1,14,2,13,3,12,4,11,5,10,6,9,7,8); + + CALL quicksort (.test$array, last (test$array)); + +EOF + + Figure 3. A QUICKSORT program in PL/M + +As described in the program "comment" at the start of Figure 3, the subroutine +QUICKSORT is used to sort a list of numbers into ascending order. The +subroutine begins with a number of declarations which define variables and +macros used within the QUICKSORT subroutine. These declarations are then +followed by a nested subroutine, called PUSH, which performs a function local +to QUICKSORT. The remainder of the QUICKSORT subroutine then manipulates the +locally-defined variables, along with a list of numbers passed to the +subroutine, to produce a list in sorted order. + +Following the end of the QUICKSORT subroutine, a list of test values is +defined, called TEST$ARRAY. This test list is then passed to QUICKSORT in the +CALL statement near the end of the program, to verify that QUICKSORT works +correctly. The program is terminated by the symbol EOF. + +The PL/M compiler is then used to translate this program into machine +language. The resulting machine language can be loaded into the memory of an +Intel 8-bit microcomputer, and executed. There is no output operation shown in +this example, and thus the resulting sorted list is simply left in the +machine's memory. In fact, the QUICKSORT subroutine would normally become a +distinct software module in a microcomputer application, such as a small +inventory control system, and hence the program in Figure 3 is simply a test +of the module. The overall organization of the PL/M programming system has +been presented in some detail elsewhere [Ref.10], along with operating and +debugging practices. + +How does PL/M affect adaptability of software systems? First, the high degree +of self-documentation found in high-level language programming greatly +enhances maintainability, expandability, and portability among programmers. +This fact has been shown many times over in large-scale computer programming +using PL languages, and easily carries over to microcomputer programming in +PL/M. Portability between machines has been demonstrated by Intel in their 8- +bit processor line. Specifically, Intel offers a PL/M compiler for both their +8008 and newer 8080 microcomputer which allow strict upward PL/M +compatibility. That is to say, although 8080 PL/M provides additional +programming features, any PL/M program written for the 8008 CPU can be +recompiled for the 8080 CPU without modification. The only difference is that +the resulting 8080 machine level program requires less storage, and executes +faster. Furthermore, Intel's long term commitment to PL/M means that customers +can expect their programs to execute on future processors, while taking +advantage of each new machine design. + +Portability among manufacturers is more difficult in PL/M, but not impossible. +First, the 8- and 16-bit class of microcomputer appears to be a popular +architecture. Thus, PL/M programs could execute on another manufacturer's +machine if a PL/M compiler for that particular machine were available. +Construction of a compiler is generally considered a formidable task. PL/M, +however, is a small language with simple grammar rules, simple statement +execution rules, and no run-time support requirements. Given that a company +has a significant investment in software, a specialized compiler for PL/M +could be developed in-house for nearly any manufacturer's microcomputer. Using +well-known automatic compiler generation techniques [Ref.11], a specialized +PL/M compiler of this sort would require only a few man-months of effort to +write, debug, and document. This approach not only allows portability among +manufacturers, but also solves the second source problem to some degree. + +Thus, given that a high-level language exists for a particular application, +one cannot argue its merit as an aid in developing adaptable software. + + +The efficiency question +----------------------- + +High-level languages have traditionally been under attack for their relative +inefficiency when compared to tightly-coded assembly language programs. As +stated by Weinberg [Ref.12] "when we ask for efficiency, we are often asking +for tight coding that will be difficult to modify. In terms of higher-level +languages, we often descend to the (assembly) language level to make a program +more efficient. This loses at least one of the benefits of having the program +in the higher-level language -- that of transportability between machines. In +fact, it has the effect of freezing us to a machine or implementation that, we +have admitted by our very act, is unsatisfactory. However, the same managers +who scream for efficiency are the ones who tear their hair when told the cost +of modifications". Weinberg's comments are especially true in the large-scale +computer community. When discussing microcomputer systems, however, one might +argue that the relative inefficiencies of high-level language programming are +intolerable, due to the added cost of memory in large quantity production. + +Concentrating only on the question of efficiency for a moment, one should note +that it is impossible to categorically state that all high-level languages are +necessarily inefficient. Efficiency depends upon at least 2 factors: the +proximity of the language to the target machine, and the quality of the +compiler which performs the translation to machine language. In fact, this is +a principal point: a high-level systems language is closely related to the +architecture of the machines it is to control, which leads to "good" machine +level programs. Statements in PL/M, for example, translate into short machine +instruction sequences, since PL/M statements reflect the machine architecture. +Conversely, FORTRAN language statements are difficult to process on a small +machine, and would produce long sequences of machine instructions. As a +result, systems languages are potentially the most efficient subclass of the +high-level languages. + +The quality of the high-level language translator can be measured in terms of +the degree of "program optimization" that it performs. That is to say, an +optimizing compiler is one which analyzes the program structure to produce +machine level code which best uses the target machine's resources. Optimizing +compilers are themselves evolutionary, and are generally improved over time. +Several versions of Intel's PL/M compiler have been released since its first +introduction in June of 1973. Each version has additional program optimizing +features which reduce the amount of generated machine language. As an example, +consider the QUICKSORT subroutine shown in Figure 3, which was proposed by +Popper [Ref.9] as an indication of relative inefficiency. Popper gives an +equivalent QUICKSORT subroutine using Intel 8008 assembly language. The +assembly language version is highly 8008 machine-dependent, resulting in a +tightly-coded 215 statement program. Table 1 shows a comparison of the PL/M +and assembly language versions of QUICKSORT, giving the relative inefficiency +of PL/M as the measure + + Mp - Ma + ------- + Ma + +where Mp and Ma represent the memory requirements of the PL/M and assembly +language versions, respectively. + +Table 1. QUICKSORT comparison + +Translator Program size Relative + (in bytes) inefficiency +-------------- ------------ ------------ +8008 assembler 300 - +8008 PL/M Ver1 426 42% +8008 PL/M Ver3 391 30% +8008 PL/M Ver3 +(subscript optim.) 336 12% +8080 PL/M Ver1 330 10% + +Note: Program size based upon body of QUICKSORT procedure. + +The June 1973 release of PL/M produced 42% more program storage, while the +February 1974 release produced 30% more instructions. Because of the +relatively small program size, and the large number of subscripted variable +references, this particular program can be considered a "worst case" for PL/M. +Thus, Table 1 also shows the result of compilation with the 8008 PL/M +subscript optimization options enabled. These options allow the PL/M compiler +to insert short subroutines for subscript computations, rather than inline +code, which both decreases the memory requirements and increases the execution +speed. Using these options, the relative inefficiency is reduced to 12%. Note +also that the first version of the 8080 PL/M compiler, released in March 1974, +produced only 10% more machine instructions. + +(ROCHE> PL/M dates: + +8008 PL/M Version 1: June 1973 +8008 PL/M Version 2: ? 1973 +8008 PL/M Version 3: February 1974 +8080 PL/M Version 1: March 1974) + +There are several points to consider in this comparison. First, it is clear +that the assembly language version could be completely rewritten for the 8080 +CPU, further reducing memory requirements. This, however, is the entire point: +given the 2 original programs, one in PL/M, the other in assembly language, +the PL/M program improves without alteration as new new compilers and machine +designs are introduced, while the assembly language version requires +reprogramming to adapt. Further, the experience a manufacturer gains in +processing the high-level language can be used in designing future processors +which more effectively execute these programs. + +It must also be noted that the relative inefficiency measure cannot be +considered an absolute comparison. The numbers vary widely with program +complexity, programming style, and programmer experience. Due to the +complexity of large programs, it quite often happens that relative +inefficiency becomes negative. That is to say, experience has shown that, for +programs larger than 1000-2000 bytes, the PL/M compiler actually produces +better machine level programs that hand-coded versions. This effect is +principally due to the fact that the compiler more readily accounts for +machine resources, where assembly language coding becomes confused and +disorganized. + +In fact, the entire discussion of relative inefficiency may be a moot point, +given the current and projected costs for memory. In quantity, 2K by 8-bit +ROM's are currently available for less than $15 apiece, and hence the +incremental difference in production cost is hardly appreciable when compared +to the adaptability of the product. + + +Summary +------- + +Current microcomputer designs and applications merely predict their promising +future. However, due to a microcomputer-based product's heavy dependence upon +software systems, the major hurdle in the near future will be in software +design methodology. Never before has software design been as important: +reliability and correctness of programs directly determines the quality of a +product manufactured in the thousands. As customers, we must encourage the +industry to offer and support the tools necessary for effective program +development and adaptability. + +One tool, high-level systems languages, has been shown to be a viable approach +to microcomputer systems development. When coupled with proper management and +programmer experience, high-level systems languages provide the means to +produce quality software systems for supporting a constantly evolving product +definition. + + +References +---------- + +1 +"Processors and profits: how microprocessors boost them" + Davidow, W. +"Electronics", July 11, 1974 + +2 +"Structured Programming" + Dahl, O. et al. + Academic Press, 1972 + +3 +"A brief look at structured programming and top-down program design" + Yourdon, E. +"Modern Data", June, 1974 + +4 +"Software Engineering Techniques" + Buxton, J. (Editor) + Nato Science Committee, OTAN/NATO, 1110 Bruxelles, Belgium, April 1970 + +5 +"Managing a programming project" + Metzger, P. + Prentice-Hall, 1973 + +6 +"8080 Assembly Language Programming Manual" + Intel Corp. + +7 +"A Guide to PL/M Programming" + Intel Corp. + +8 +"The Elements of Programming Style" + Kernighan, B. et al. + McGraw-Hill, 1974 + +9 +"Advanced Microcomputer Software Techniques" + Popper, C. + National Electronics Conference, + Professional Growth in Engineering Seminar, 1974 + +10 +"High-level language simplifies microcomputer programming" + Kildall, G. +"Electronics", June 27, 1974 + +11 +"A Compiler Generator" + McKeeman, W. et al. + Prentice-Hall, 1970 + +12 +"???" + Weinberg + ??? + + +EOF + \ No newline at end of file diff --git a/SysCon PLMX/IATABLE.FOR b/SysCon PLMX/IATABLE.FOR new file mode 100644 index 0000000..1368d22 Binary files /dev/null and b/SysCon PLMX/IATABLE.FOR differ diff --git a/SysCon PLMX/IETABLE.FOR b/SysCon PLMX/IETABLE.FOR new file mode 100644 index 0000000..561a060 Binary files /dev/null and b/SysCon PLMX/IETABLE.FOR differ diff --git a/SysCon PLMX/IHTABLE.FOR b/SysCon PLMX/IHTABLE.FOR new file mode 100644 index 0000000..0fc7435 Binary files /dev/null and b/SysCon PLMX/IHTABLE.FOR differ diff --git a/SysCon PLMX/IOCLD.SRC b/SysCon PLMX/IOCLD.SRC new file mode 100644 index 0000000..07f6d2b --- /dev/null +++ b/SysCon PLMX/IOCLD.SRC @@ -0,0 +1,197 @@ +/* + Following is a total list of I/O procedures available to the + PLMX user. Refer to Digital Research "CP/M Interface Guide" + for a description of CP/M 1.4 system level procedures. Refer to + the "PLMX User's Guide" for a description of all other procedures. + It is suggested that the user extract those procedures which are + applicable to his application, possibly putting them in an INCLUDE + file. +*/ + +/* CP/M system level procedures */ + +RD$CON: +PROCEDURE BYTE EXTERNAL; +END RD$CON; + +WR$CON: +PROCEDURE (CHAR) EXTERNAL; + DECLARE CHAR BYTE; +END WR$CON; + +RD$RDR: +PROCEDURE BYTE EXTERNAL; +END RD$RDR; + +PUNCH: +PROCEDURE (CHAR) EXTERNAL; + DECLARE CHAR BYTE; +END PUNCH; + +PRINT: +PROCEDURE (CHAR) EXTERNAL; + DECLARE CHAR BYTE; +END PRINT; + +G$STAT: +PROCEDURE BYTE EXTERNAL; +END G$STAT; + +S$STAT: +PROCEDURE (STAT) EXTERNAL; + DECLARE STAT BYTE; +END S$STAT; + +PR$BUF: +PROCEDURE (ADRS) EXTERNAL; + DECLARE ADRS ADDRESS; +END PR$BUF; + +RD$BUF: +PROCEDURE (BUF) ADDRESS EXTERNAL; + DECLARE BUF BYTE; +END RD$BUF; + +CN$RDY: +PROCEDURE BYTE EXTERNAL; +END CN$RDY; + +LFT$HD: +PROCEDURE EXTERNAL; +END LFT$HD; + +INIT: +PROCEDURE EXTERNAL; +END INIT; + +LOGIN: +PROCEDURE (DSK) EXTERNAL; + DECLARE DSK BYTE; +END LOGIN; + +OPEN: +PROCEDURE (FCB) BYTE EXTERNAL; + DECLARE FCB BYTE; +END OPEN; + +CLOSE: +PROCEDURE (FCB) BYTE EXTERNAL; + DECLARE FCB BYTE; +END CLOSE; + +SERCH: +PROCEDURE (FCB) BYTE EXTERNAL; + DECLARE FCB BYTE; +END SERCH; + +SR$NXT: +PROCEDURE (FCB) BYTE EXTERNAL; + DECLARE FCB BYTE; +END SR$NXT; + +DLETE: +PROCEDURE EXTERNAL; +END DLETE; + +RD$DSK: +PROCEDURE (FCB) BYTE EXTERNAL; + DECLARE FCB ADDRESS; +END RD$DSK; + +WR$DSK: +PROCEDURE (FCB) BYTE EXTERNAL; + DECLARE FCB ADDRESS; +END WR$DSK; + +MAKE: +PROCEDURE (FCB) BYTE EXTERNAL; + DECLARE FCB ADDRESS; +END MAKE; + +RNAME: +PROCEDURE (FCB) ADDRESS EXTERNAL; + DECLARE FCB ADDRESS; +END RNAME; + +RL$VEC: +PROCEDURE BYTE EXTERNAL; +END RL$VEC; + +DRIVE: +PROCEDURE BYTE EXTERNAL; +END DRIVE; + +STDMA: +PROCEDURE (BUF) EXTERNAL; + DECLARE BUF ADDRESS; +END STDMA; + + +/* PLMX read and write line procedures */ + +READ: +PROCEDURE (FUNCTION, BUFFER, COUNT, ACTUAL, STATUS) EXTERNAL; + DECLARE (FUNCTION, BUFFER, COUNT, ACTUAL, STATUS) ADDRESS; +END READ; + +WRITE: +PROCEDURE (FUNCTION, BUFFER, COUNT, STATUS) EXTERNAL; + DECLARE (FUNCTION, BUFFER, COUNT, STATUS) ADDRESS; +END WRITE; + + +/* Disk I/O procedures */ + +DRCHR: +PROCEDURE (FCB, SEC$BUFFER, SEC$COUNT, CHAR, STATUS) EXTERNAL; + DECLARE (FCB, SEC$BUFFER, SEC$COUNT, CHAR, STATUS) ADDRESS; +END DRCHR; + +DWCHR: +PROCEDURE (FCB, SEC$BUFFER, SEC$COUNT, CHAR, STATUS) EXTERNAL; + DECLARE (FCB, SEC$BUFFER, SEC$COUNT, CHAR, STATUS) ADDRESS; +END DWCHR; + +DRLIN: +PROCEDURE (FCB, SEC$BUF, SEC$CNT, BUFFER, COUNT, STATUS) EXTERNAL; + DECLARE (FCB, SEC$BUF, SEC$CNT, BUFFER, COUNT, STATUS) ADDRESS; +END DRLIN; + +DWLIN: +PROCEDURE (FCB, SEC$BUF, SEC$COUNT, BUFFER, COUNT, STATUS) EXTERNAL; + DECLARE (FCB, SEC$BUF, SEC$COUNT, BUFFER, COUNT, STATUS) ADDRESS; +END DWLIN; + +OPENR: +PROCEDURE (FCB, SEC$COUNT, STATUS) EXTERNAL; + DECLARE (FCB, SEC$COUNT, STATUS) ADDRESS; +END OPENR; + +CLOSR: +PROCEDURE (FCB, STATUS) EXTERNAL; + DECLARE (FCB, STATUS) ADDRESS; +END CLOSR; + +OPENW: +PROCEDURE (FCB, SEC$COUNT, STATUS) EXTERNAL; + DECLARE (FCB, SEC$COUNT, STATUS) ADDRESS; +END OPENW; + +CLOSW: +PROCEDURE (FCB, SEC$BUF, SEC$COUNT, STATUS) EXTERNAL; + DECLARE (FCB, SEC$BUF, SEC$COUNT, STATUS) ADDRESS; +END CLOSW; + +/* Other procedures */ + +NUMIN: /* Convert ASCII number to 16-bit unsigned binary */ +PROCEDURE (BUFFER) ADDRESS EXTERNAL; + DECLARE BUFFER ADDRESS; +END NUMIN; + +NMOUT: /* Convert 16-bit unsigned binary number to ASCII string */ +PROCEDURE (VALUE, BASE, LC, BUFFADR, WIDTH) EXTERNAL; + DECLARE (VALUE, BUFFADR) ADDRESS; + DECLARE (BASE, LC, WIDTH) BYTE; +END NMOUT; + \ No newline at end of file diff --git a/SysCon PLMX/IOLIB.MAC b/SysCon PLMX/IOLIB.MAC new file mode 100644 index 0000000..bd3b99a --- /dev/null +++ b/SysCon PLMX/IOLIB.MAC @@ -0,0 +1,1985 @@ +; IOLIB.MAC +; --------- +; +; CP/M 1.4 -- IOLIB of PLMX +; +; Disassembled by: +; +; Mr Emmanuel ROCHE +; Chemin de Boisrond +; 17430 Tonnay-Charente +; FRANCE +; +; (Most probably the result of a PLMX compilation.) +; +;-------------------------------- +; ORG 0100H ; Standard CP/M RELocatable file +;-------------------------------- +; +Co0000 EQU 0000H ; -C--I +Io0001 EQU 0001H ; ----I +I$0002 EQU 0002H ; ----I +Io0003 EQU 0003H ; ----I +Io0004 EQU 0004H ; ----I +BDOS EQU 0005H ; ----I +I$0007 EQU 0007H ; ----I +I$0008 EQU 0008H ; ----I +I$0009 EQU 0009H ; ----I +Io000A EQU 000AH ; ----I +I$000B EQU 000BH ; ----I +I$000C EQU 000CH ; ----I +I$000D EQU 000DH ; ----I +I$000E EQU 000EH ; ----I +Io000F EQU 000FH ; ----I +I$0010 EQU 0010H ; ----I +I$0011 EQU 0011H ; ----I +I$0012 EQU 0012H ; ----I +I$0013 EQU 0013H ; ----I +I$0014 EQU 0014H ; ----I +I$0015 EQU 0015H ; ----I +I$0016 EQU 0016H ; ----I +I$0017 EQU 0017H ; ----I +I$0018 EQU 0018H ; ----I +I$0019 EQU 0019H ; ----I +I$001A EQU 001AH ; ----I +Io00FF EQU 00FFH ; ----I +I$FFFF EQU 0FFFFH ; ----I +; +;-------------------------------- +lf EQU 0AH ; Line Feed +cr EQU 0DH ; Carriage Return +;-------------------------------- +; +Qo0100: JMP J$01A5 ; Jump around statement +; +;-------------------------------- +; +Qo0103: XCHG + SHLD Do0D57 + MOV L,C + MOV H,B + SHLD Do0D55 + POP H + XTHL + SHLD Do0D53 + POP H + XTHL + SHLD Do0D51 + POP H + XTHL + SHLD Do0D4F + LHLD Do0D53 + MOV A,M + MVI L,80H + CALL Co0000 + RRC + JNC J$0169 + LHLD Do0D51 + MOV C,L + MOV B,H + CALL Co0ABF + LHLD Do0D4F + MOV C,L + MOV B,H + CALL Co0B2D + STA Do0D5B + LHLD Do0D5B + MVI H,00H + XCHG + LHLD Do0D57 + MOV M,E + INX H + MOV M,D + MVI A,00H + LHLD Do0D57 + MOV E,M + INX H + MOV D,M + XCHG + CALL Co0000 + RRC + JNC J$015A + JMP J$0193 +; +J$015A: LHLD Do0D51 + SHLD Do0D59 + MVI A,00H + LHLD Do0D53 + MOV M,A + JMP J$0176 +; +J$0169: LHLD Do0D53 + MOV A,M + LHLD Do0D51 + CALL Co0000 + SHLD Do0D59 +J$0176: LHLD Do0D55 + MOV A,M + LHLD Do0D59 + MOV M,A + LHLD Do0D59 + INX H + SHLD Do0D59 + LHLD Do0D53 + MOV A,M + MVI L,01H ; 1 + CALL Co0000 + LHLD Do0D53 + MOV M,A + RET +; +J$0193: LXI H,Io00FF + XCHG + LHLD Do0D57 + MOV M,E + INX H + MOV M,D + LXI B,I$01A8 + CALL Co0C78 + RET +; +Qo01A4: RET +; +;-------------------------------- +J$01A5: CALL Co0000 +; +I$01A8: DB 'WRITE ERROR', cr, lf, '$' +; +Qo01B6: JMP J$0265 ; Jump around statement +;-------------------------------- +; +Qo01B9: XCHG + SHLD Do0D67 + MOV L,C + MOV H,B + SHLD Do0D65 + POP H + XTHL + SHLD Do0D63 + POP H + XTHL + SHLD Do0D61 + POP H + XTHL + SHLD Do0D5F + LHLD Do0D63 + MOV A,M + MVI L,00H + CALL Co0000 + RRC + JNC J$0216 + LHLD Do0D61 + MOV C,L + MOV B,H + CALL Co0ABF + LHLD Do0D5F + MOV C,L + MOV B,H + CALL Co0B4A + STA Do0D6B + LHLD Do0D6B + MVI H,00H + XCHG + LHLD Do0D67 + MOV M,E + INX H + MOV M,D + MVI A,00H + LHLD Do0D67 + MOV E,M + INX H + MOV D,M + XCHG + CALL Co0000 + RRC + JNC J$0210 + JMP J$0253 +; +J$0210: MVI A,80H + LHLD Do0D63 + MOV M,A +J$0216: LHLD Do0D63 + MOV L,M + MVI A,80H + CALL Co0000 + LHLD Do0D61 + CALL Co0000 + SHLD Do0D69 + MOV A,M + LHLD Do0D65 + MOV M,A + LHLD Do0D69 + MOV A,M + MVI L,1AH + CALL Co0000 + RRC + JNC J$0245 + LXI H,Io0001 + XCHG + LHLD Do0D67 + MOV M,E + INX H + MOV M,D + RET +; +J$0245: LHLD Do0D63 + MOV A,M + MVI L,01H ; 1 + CALL Co0000 + LHLD Do0D63 + MOV M,A + RET +; +J$0253: LXI H,Io00FF + XCHG + LHLD Do0D67 + MOV M,E + INX H + MOV M,D + LXI B,I$0268 + CALL Co0C78 + RET +; +Qo0264: RET +; +;-------------------------------- +J$0265: CALL Co0000 +; +I$0268: DB 'READ ERROR', cr, lf, '$' +; +Qo0275: JMP J$0331 ; Jump around statement +;-------------------------------- +; +Qo0278: XCHG + SHLD Do0D75 + MOV L,C + MOV H,B + SHLD Do0D73 + POP H + XTHL + SHLD Do0D71 + POP H + XTHL + SHLD Do0D6F + LXI H,Co0000 + XCHG + LHLD Do0D75 + MOV M,E + INX H + MOV M,D + LHLD Do0D71 + MOV C,L + MOV B,H + CALL Co0ABF + LHLD Do0D73 + MOV A,M + MVI L,00H + CALL Co0000 + RRC + JNC J$02F7 + LHLD Do0D73 + MOV A,M + MVI L,01H ; 1 + CALL Co0000 + STA Do0D79 + JMP J$02C4 +; +J$02B9: MVI A,01H ; 1 + LHLD Do0D79 + CALL Co0000 + STA Do0D79 +J$02C4: MVI L,80H + LDA Do0D79 + CALL Co0000 + RRC + JNC J$02E0 + MVI A,1AH + LHLD Do0D77 + MOV M,A + LHLD Do0D77 + INX H + SHLD Do0D77 + JMP J$02B9 +; +J$02E0: LHLD Do0D6F + MOV C,L + MOV B,H + CALL Co0B2D + STA Do0D7A + LHLD Do0D7A + MVI H,00H + XCHG + LHLD Do0D75 + MOV M,E + INX H + MOV M,D +J$02F7: LHLD Do0D6F + MOV C,L + MOV B,H + CALL Co0BBE + STA Do0D7A + LHLD Do0D75 + MOV E,M + INX H + MOV D,M + XCHG + LDA Do0D7A + CALL Co0000 + XCHG + LHLD Do0D75 + MOV M,E + INX H + MOV M,D + MVI A,0FFH + LHLD Do0D75 + MOV E,M + INX H + MOV D,M + XCHG + CALL Co0000 + RRC + JNC J$0330 + LXI H,Co0000 + XCHG + LHLD Do0D75 + MOV M,E + INX H + MOV M,D +J$0330: RET +; +;-------------------------------- +J$0331: CALL Co0000 +; + JMP J$0372 ; Jump around statement +;-------------------------------- +; +Qo0337: XCHG + SHLD Do0D7F + MOV L,C + MOV H,B + SHLD Do0D7D + LHLD Do0D7D + MOV C,L + MOV B,H + CALL Co0BBE + STA Do0D81 + LHLD Do0D81 + MVI H,00H + XCHG + LHLD Do0D7F + MOV M,E + INX H + MOV M,D + MVI A,0FFH + LHLD Do0D7F + MOV E,M + INX H + MOV D,M + XCHG + CALL Co0000 + RRC + JNC J$0371 + LXI H,Co0000 + XCHG + LHLD Do0D7F + MOV M,E + INX H + MOV M,D +J$0371: RET +; +;-------------------------------- +J$0372: CALL Co0000 +; + JMP J$0435 ; Jump around statement +;-------------------------------- +; +Qo0378: XCHG + SHLD Do0D87 + MOV L,C + MOV H,B + SHLD Do0D85 + POP H + XTHL + SHLD Do0D83 + JMP J$03C4 +; +Co0389: MVI A,0CH ; 12 + LHLD Do0D83 + CALL Co0000 + SHLD Do0D89 + MVI A,01H ; 1 + STA Do0D8B + JMP J$03A7 +; +J$039C: MVI A,01H ; 1 + LHLD Do0D8B + CALL Co0000 + STA Do0D8B +J$03A7: MVI L,15H + LDA Do0D8B + CALL Co0000 + RRC + JNC J$03C3 + MVI A,00H + LHLD Do0D89 + MOV M,A + LHLD Do0D89 + INX H + SHLD Do0D89 + JMP J$039C +; +J$03C3: RET +; +J$03C4: CALL Co0389 + LHLD Do0D83 + MOV C,L + MOV B,H + CALL C$0B67 + CALL Co0389 + LHLD Do0D83 + MOV C,L + MOV B,H + CALL C$0B10 + STA Do0D8F + LHLD Do0D8F + MVI H,00H + XCHG + LHLD Do0D87 + MOV M,E + INX H + MOV M,D + MVI A,0FFH + LHLD Do0D87 + MOV E,M + INX H + MOV D,M + XCHG + CALL Co0000 + RRC + JNC J$03FA + RET +; +J$03FA: CALL Co0389 + LHLD Do0D83 + MOV C,L + MOV B,H + CALL Co0BDB + STA Do0D8F + LHLD Do0D8F + MVI H,00H + XCHG + LHLD Do0D87 + MOV M,E + INX H + MOV M,D + MVI A,0FFH + LHLD Do0D87 + MOV E,M + INX H + MOV D,M + XCHG + CALL Co0000 + RRC + JNC J$042E + LXI H,Co0000 + XCHG + LHLD Do0D87 + MOV M,E + INX H + MOV M,D +J$042E: MVI A,00H + LHLD Do0D85 + MOV M,A + RET +; +;-------------------------------- +J$0435: CALL Co0000 +; + JMP J$04B8 ; Jump around statement +;-------------------------------- +; +Qo043B: XCHG + SHLD Do0D95 + MOV L,C + MOV H,B + SHLD Do0D93 + POP H + XTHL + SHLD Do0D91 + MVI A,0CH ; 12 + CALL Co0000 + SHLD Do0D97 + MVI A,01H ; 1 + STA Do0D99 + JMP J$0464 +; +J$0459: MVI A,01H ; 1 + LHLD Do0D99 + CALL Co0000 + STA Do0D99 +J$0464: MVI L,15H + LDA Do0D99 + CALL Co0000 + RRC + JNC J$0480 + MVI A,00H + LHLD Do0D97 + MOV M,A + LHLD Do0D97 + INX H + SHLD Do0D97 + JMP J$0459 +; +J$0480: LHLD Do0D91 + MOV C,L + MOV B,H + CALL Co0BDB + STA Do0D9C + LHLD Do0D9C + MVI H,00H + XCHG + LHLD Do0D95 + MOV M,E + INX H + MOV M,D + MVI A,0FFH + LHLD Do0D95 + MOV E,M + INX H + MOV D,M + XCHG + CALL Co0000 + RRC + JNC J$04B1 + LXI H,Co0000 + XCHG + LHLD Do0D95 + MOV M,E + INX H + MOV M,D +J$04B1: MVI A,00H + LHLD Do0D93 + MOV M,A + RET +; +;-------------------------------- +J$04B8: CALL Co0000 +; + JMP J$05C6 ; Jump around statement +;-------------------------------- +; +Qo04BE: XCHG + SHLD Do0DA8 + MOV L,C + MOV H,B + SHLD Do0DA6 + POP H + XTHL + SHLD Do0DA4 + POP H + XTHL + SHLD Do0DA2 + POP H + XTHL + SHLD Do0DA0 + POP H + XTHL + SHLD Do0D9E + JMP J$053A +; +C$04DE: LHLD Do0DA2 + MOV A,M + MVI L,80H + CALL Co0000 + RRC + JNC J$052C + LHLD Do0DA0 + MOV C,L + MOV B,H + CALL Co0ABF + LHLD Do0D9E + MOV C,L + MOV B,H + CALL Co0B2D + STA Do0DAE + LHLD Do0DAE + MVI H,00H + XCHG + LHLD Do0DA8 + MOV M,E + INX H + MOV M,D + MVI A,00H + LHLD Do0DA8 + MOV E,M + INX H + MOV D,M + XCHG + CALL Co0000 + RRC + JNC J$051D + JMP J$05B4 +; +J$051D: LHLD Do0DA0 + SHLD Do0DAA + MVI A,00H + LHLD Do0DA2 + MOV M,A + JMP J$0539 +; +J$052C: LHLD Do0DA2 + MOV A,M + LHLD Do0DA0 + CALL Co0000 + SHLD Do0DAA +J$0539: RET +; +J$053A: LHLD Do0DA4 + SHLD Do0DAC +J$0540: CALL C$04DE +J$0543: LHLD Do0DA2 + MOV A,M + MVI L,80H + CALL Co0000 + STA Do0DB2 + MVI A,00H + LHLD Do0DA6 + MOV E,M + INX H + MOV D,M + XCHG + CALL Co0000 + STA Do0DB3 + LHLD Do0DB3 + LDA Do0DB2 + CALL Co0000 + RRC + JNC J$05A0 + LHLD Do0DAC + MOV A,M + LHLD Do0DAA + MOV M,A + LHLD Do0DAA + INX H + SHLD Do0DAA + LHLD Do0DAC + INX H + SHLD Do0DAC + LHLD Do0DA6 + MOV E,M + INX H + MOV D,M + XCHG + DCX H + XCHG + LHLD Do0DA6 + MOV M,E + INX H + MOV M,D + LHLD Do0DA2 + MOV A,M + MVI L,01H ; 1 + CALL Co0000 + LHLD Do0DA2 + MOV M,A + JMP J$0543 +; +J$05A0: MVI A,00H + LHLD Do0DA6 + MOV E,M + INX H + MOV D,M + XCHG + CALL Co0000 + RRC + JNC J$05B3 + JMP J$0540 +; +J$05B3: RET +; +J$05B4: LXI H,Io00FF + XCHG + LHLD Do0DA8 + MOV M,E + INX H + MOV M,D + LXI B,I$05C9 + CALL Co0C78 + RET +; +Qo05C5: RET +; +;-------------------------------- +J$05C6: CALL Co0000 +; +I$05C9: DB 'WRITE ERROR', cr, lf, '$' +; +Qo05D7: JMP J$06D8 ; Jump around statement +;-------------------------------- +; +Qo05DA: XCHG + SHLD Do0DC4 + MOV L,C + MOV H,B + SHLD Do0DC2 + POP H + XTHL + SHLD Do0DC0 + POP H + XTHL + SHLD Do0DBE + POP H + XTHL + SHLD Do0DBC + POP H + XTHL + SHLD Do0DBA + LXI H,Co0000 + XCHG + LHLD Do0DC2 + MOV M,E + INX H + MOV M,D + LHLD Do0DC0 + SHLD Do0DC8 +J$0607: LHLD Do0DBE + MOV A,M + MVI L,00H + CALL Co0000 + RRC + JNC J$064C + LHLD Do0DBC + MOV C,L + MOV B,H + CALL Co0ABF + LHLD Do0DBA + MOV C,L + MOV B,H + CALL Co0B4A + STA Do0DCA + LHLD Do0DCA + MVI H,00H + XCHG + LHLD Do0DC4 + MOV M,E + INX H + MOV M,D + MVI A,00H + LHLD Do0DC4 + MOV E,M + INX H + MOV D,M + XCHG + CALL Co0000 + RRC + JNC J$0646 + JMP J$06C6 +; +J$0646: MVI A,80H + LHLD Do0DBE + MOV M,A +J$064C: LHLD Do0DBE + MOV L,M + MVI A,80H + CALL Co0000 + LHLD Do0DBC + CALL Co0000 + SHLD Do0DC6 + MOV A,M + MVI L,1AH + CALL Co0000 + RRC + JNC Jo0673 + LXI H,Io0001 + XCHG + LHLD Do0DC4 + MOV M,E + INX H + MOV M,D + RET +; +Jo0673: LHLD Do0DC6 + MOV A,M + LHLD Do0DC8 + MOV M,A + LHLD Do0DBE + MOV A,M + MVI L,01H ; 1 + CALL Co0000 + LHLD Do0DBE + MOV M,A + LHLD Do0DC2 + MOV E,M + INX H + MOV D,M + XCHG + INX H + XCHG + LHLD Do0DC2 + MOV M,E + INX H + MOV M,D + LHLD Do0DC6 + INX H + SHLD Do0DC6 + LHLD Do0DC8 + MOV A,M + MVI L,0AH ; 10 + CALL Co0000 + RRC + JNC J$06AC + RET +; +J$06AC: LHLD Do0DC8 + INX H + SHLD Do0DC8 + LHLD Do0DBE + MOV A,M + MVI L,00H + CALL Co0000 + RRC + JNC J$06C3 + JMP Jo0673 +; +J$06C3: JMP J$0607 +; +J$06C6: LXI H,Io00FF + XCHG + LHLD Do0DC4 + MOV M,E + INX H + MOV M,D + LXI B,I$06DB + CALL Co0C78 + RET +; +Qo06D7: RET +; +;-------------------------------- +J$06D8: CALL Co0000 +; +I$06DB: DB 'READ ERROR', cr, lf, '$' +; +Qo06E8: JMP J$084A ; Jump around statement +;-------------------------------- +; +Qo06EB: MOV L,C + MOV H,B + SHLD Do0DD0 + LXI H,Co0000 + SHLD Do0DD4 + SHLD Do0DD6 + SHLD Do0DD8 + SHLD Do0DDA + LHLD Do0DD0 + MOV E,M + INX H + MOV D,M + XCHG + SHLD Do0DD2 +J$0709: LHLD Do0DD2 + MOV A,M + MVI L,20H ; " " + CALL Co0000 + RRC + JNC J$0720 + LHLD Do0DD2 + INX H + SHLD Do0DD2 + JMP J$0709 +; +J$0720: MVI A,0FFH + STA Do0DDD +J$0725: LDA Do0DDD + RRC + JNC J$07E1 + MVI A,00H + STA Do0DDD + MVI A,00H + STA Do0DDC + JMP J$0744 +; +J$0739: MVI A,01H ; 1 + LHLD Do0DDC + CALL Co0000 + STA Do0DDC +J$0744: LXI H,Io000F + LDA Do0DDC + CALL Co0000 + RRC + JNC J$07DE + LHLD Do0DDC + MVI H,00H + XCHG + LXI H,I$084D + DAD D + SHLD Do0DDF + LHLD Do0DD2 + MOV A,M + LHLD Do0DDF + MOV L,M + CALL Co0000 + RRC + JNC J$07DB + MVI L,02H ; 2 + LDA Do0DDC + CALL Co0000 + RRC + JNC J$078A + LHLD Do0DD4 + XCHG + LHLD Do0DD4 + DAD D + LDA Do0DDC + CALL Co0000 + SHLD Do0DD4 +J$078A: LHLD Do0DD6 + PUSH H + LXI D,Io0003 + POP B + CALL Co0000 + LDA Do0DDC + CALL Co0000 + SHLD Do0DD6 + MVI L,0AH ; 10 + LDA Do0DDC + CALL Co0000 + RRC + JNC J$07BB + MVI A,0AH ; 10 + LHLD Do0DD8 + CALL Co0000 + LDA Do0DDC + CALL Co0000 + SHLD Do0DD8 +J$07BB: LHLD Do0DDA + PUSH H + LXI D,Io0004 + POP B + CALL Co0000 + LDA Do0DDC + CALL Co0000 + SHLD Do0DDA + LHLD Do0DD2 + INX H + SHLD Do0DD2 + MVI A,0FFH + STA Do0DDD +J$07DB: JMP J$0739 +; +J$07DE: JMP J$0725 +; +J$07E1: LHLD Do0DD2 + INX H + XCHG + LHLD Do0DD0 + MOV M,E + INX H + MOV M,D + LHLD Do0DD2 + MOV A,M + MVI L,48H ; "H" + CALL Co0000 + RRC + JNC J$07FD + LHLD Do0DDA + RET +; +J$07FD: LHLD Do0DD2 + MOV A,M + MVI L,51H ; "Q" + CALL Co0000 + STA Do0DDE + LHLD Do0DD2 + MOV A,M + MVI L,4FH ; "O" + CALL Co0000 + STA Do0DE3 + LHLD Do0DE3 + LDA Do0DDE + CALL Co0000 + RRC + JNC J$0826 + LHLD Do0DD6 + RET +; +J$0826: LHLD Do0DD2 + XCHG + LHLD Do0DD0 + MOV M,E + INX H + MOV M,D + LHLD Do0DD2 + DCX H + SHLD Do0DD2 + MOV A,M + MVI L,42H ; "B" + CALL Co0000 + RRC + JNC J$0845 + LHLD Do0DD4 + RET +; +J$0845: LHLD Do0DD8 + RET +; +Qo0849: RET +; +;-------------------------------- +J$084A: CALL Co0000 +; +I$084D: DB '0123456789ABCDEF' +; +Qo085D: JMP J$093B ; Jump around statement +;-------------------------------- +; +Qo0860: XCHG + MOV A,L + STA Do0DEA + MOV L,C + MOV H,B + SHLD Do0DE6 + POP H + XTHL + MOV A,L + STA Do0DE9 + POP H + XTHL + MOV A,L + STA Do0DE8 + POP H + XTHL + SHLD Do0DE4 + MVI A,01H ; 1 + STA Do0DEB + JMP J$088E +; +J$0883: MVI A,01H ; 1 + LHLD Do0DEB + CALL Co0000 + STA Do0DEB +J$088E: LHLD Do0DEA + LDA Do0DEB + CALL Co0000 + RRC + JNC J$08DC + LDA Do0DE8 + LHLD Do0DE4 + CALL Co0000 + XCHG + LXI H,I$093E + DAD D + SHLD Do0DED + LHLD Do0DEB + LDA Do0DEA + CALL Co0000 + STA Do0DEC + LHLD Do0DEC + MVI H,00H + XCHG + LHLD Do0DE6 + DAD D + SHLD Do0DEF + LHLD Do0DED + MOV A,M + LHLD Do0DEF + MOV M,A + LDA Do0DE8 + LHLD Do0DE4 + CALL Co0000 + SHLD Do0DE4 + JMP J$0883 +; +J$08DC: MVI A,00H + STA Do0DEB +J$08E1: MVI L,01H ; 1 + LDA Do0DEA + CALL Co0000 + STA Do0DEC + LHLD Do0DEC + LDA Do0DEB + CALL Co0000 + STA Do0DEC + LHLD Do0DEB + MVI H,00H + XCHG + LHLD Do0DE6 + DAD D + MOV A,M + MVI L,30H ; "0" + CALL Co0000 + STA Do0DF1 + LHLD Do0DF1 + LDA Do0DEC + CALL Co0000 + RRC + JNC J$093A + LHLD Do0DEB + MVI H,00H + XCHG + LHLD Do0DE6 + DAD D + SHLD Do0DEF + LDA Do0DE9 + LHLD Do0DEF + MOV M,A + MVI L,01H ; 1 + LDA Do0DEB + CALL Co0000 + STA Do0DEB + JMP J$08E1 +; +J$093A: RET +; +;-------------------------------- +J$093B: CALL Co0000 +; +I$093E: DB '0123456789ABCDEF' +; +Qo094E: JMP J$09C8 ; Jump around statement +;-------------------------------- +; +Qo0951: XCHG + SHLD Do0DF8 + MOV L,C + MOV H,B + SHLD Do0DF6 + POP H + XTHL + SHLD Do0DF4 + POP H + XTHL + SHLD Do0DF2 + MVI A,0FFH + LHLD Do0DF8 + MOV M,A + MVI A,02H ; 2 + LHLD Do0DF2 + CALL Co0000 + RRC + JNC J$0977 + RET +; +J$0977: MVI A,00H + LHLD Do0DF8 + MOV M,A +J$097D: MVI A,00H + LHLD Do0DF6 + CALL Co0000 + RRC + JNC J$09C7 + JMP J$098C +; +J$098C: LHLD Do0DF2 + CALL Co0000 + SBB B + DAD B + ANA D + DAD B + XRA H + DAD B + LHLD Do0DF4 + MOV C,M + CALL Co0D1D + JMP Jo09B6 +; +Qo09A2: LHLD Do0DF4 + MOV C,M + CALL C$0CCA + JMP Jo09B6 +; +Qo09AC: LHLD Do0DF4 + MOV C,M + CALL C$0CE8 + JMP Jo09B6 +; +Jo09B6: LHLD Do0DF4 + INX H + SHLD Do0DF4 + LHLD Do0DF6 + DCX H + SHLD Do0DF6 + JMP J$097D +; +J$09C7: RET +; +;-------------------------------- +J$09C8: CALL Co0000 +; + JMP J$0AA2 ; Jump around statement +;-------------------------------- +; +Qo09CE: XCHG + SHLD Do0E07 + MOV L,C + MOV H,B + SHLD Do0E05 + POP H + XTHL + SHLD Do0E03 + POP H + XTHL + SHLD Do0E01 + POP H + XTHL + SHLD Do0DFF + MVI A,0FFH + LHLD Do0E07 + MOV M,A + MVI A,01H ; 1 + LHLD Do0DFF + CALL Co0000 + RRC + JNC J$09F9 + RET +; +J$09F9: MVI A,00H + LHLD Do0E07 + MOV M,A + LXI H,Co0000 + XCHG + LHLD Do0E05 + MOV M,E + INX H + MOV M,D +J$0A09: LHLD Do0E03 + DCX H + SHLD Do0E0A + LHLD Do0E0A + SHLD Do0E03 + LHLD Do0E0A + XCHG + LXI H,I$FFFF + CALL Co0000 + RRC + JNC J$0AA1 + MVI A,00H + LHLD Do0DFF + CALL Co0000 + RRC + JNC J$0A3A + CALL C$0D3B + LHLD Do0E01 + MOV M,A + JMP J$0A41 +; +J$0A3A: CALL Co0D06 + LHLD Do0E01 + MOV M,A +J$0A41: LHLD Do0E01 + MOV A,M + MVI L,0DH ; 13 + CALL Co0000 + RRC + JNC J$0A88 + LHLD Do0E01 + INX H + SHLD Do0E01 + MVI A,0AH ; 10 + LHLD Do0E01 + MOV M,A + MVI A,00H + LHLD Do0DFF + CALL Co0000 + RRC + JNC J$0A70 + LXI B,Io000A + CALL Co0D1D + JMP J$0A77 +; +J$0A70: CALL Co0D06 + LHLD Do0E01 + MOV M,A +J$0A77: LHLD Do0E05 + MOV E,M + INX H + MOV D,M + XCHG + INX H + INX H + XCHG + LHLD Do0E05 + MOV M,E + INX H + MOV M,D + RET +; +J$0A88: LHLD Do0E01 + INX H + SHLD Do0E01 + LHLD Do0E05 + MOV E,M + INX H + MOV D,M + XCHG + INX H + XCHG + LHLD Do0E05 + MOV M,E + INX H + MOV M,D + JMP J$0A09 +; +J$0AA1: RET +; +;-------------------------------- +J$0AA2: CALL Co0000 +; + JMP J$0AB9 ; Jump around statement +;-------------------------------- +; +Qo0AA8: LXI B,I$0019 + PUSH B + LXI D,Co0000 + POP B + LXI H,I$0AB8 + PUSH H + LHLD D$0E0E + PCHL +; +I$0AB8: RET +; +;-------------------------------- +J$0AB9: CALL Co0000 +; + JMP J$0AD6 ; Jump around statement +;-------------------------------- +; +Co0ABF: MOV L,C + MOV H,B + SHLD Do0E12 + LXI B,I$001A + PUSH B + LHLD Do0E12 + XCHG + POP B + LXI H,I$0AD5 + PUSH H + LHLD D$0E10 + PCHL +; +I$0AD5: RET +; +;-------------------------------- +J$0AD6: CALL Co0000 +; + JMP J$0AED ; Jump around statement +;-------------------------------- +; +Qo0ADC: LXI B,I$0018 + PUSH B + LXI D,Co0000 + POP B + LXI H,I$0AEC + PUSH H + LHLD D$0E14 + PCHL +; +I$0AEC: RET +; +;-------------------------------- +J$0AED: CALL Co0000 +; + JMP J$0B0A ; Jump around statement +;-------------------------------- +; +Qo0AF3: MOV L,C + MOV H,B + SHLD Do0E18 + LXI B,I$0017 + PUSH B + LHLD Do0E18 + XCHG + POP B + LXI H,I$0B09 + PUSH H + LHLD D$0E16 + PCHL +; +I$0B09: RET +; +;-------------------------------- +J$0B0A: CALL Co0000 +; + JMP J$0B27 ; Jump around statement +;-------------------------------- +; +C$0B10: MOV L,C + MOV H,B + SHLD Do0E1C + LXI B,I$0016 + PUSH B + LHLD Do0E1C + XCHG + POP B + LXI H,I$0B26 + PUSH H + LHLD D$0E1A + PCHL +; +I$0B26: RET +; +;-------------------------------- +J$0B27: CALL Co0000 +; + JMP J$0B44 ; Jump around statement +;-------------------------------- +; +Co0B2D: MOV L,C + MOV H,B + SHLD Do0E20 + LXI B,I$0015 + PUSH B + LHLD Do0E20 + XCHG + POP B + LXI H,I$0B43 + PUSH H + LHLD D$0E1E + PCHL +; +I$0B43: RET +; +;-------------------------------- +J$0B44: CALL Co0000 +; + JMP J$0B61 ; Jump around statement +;-------------------------------- +; +Co0B4A: MOV L,C + MOV H,B + SHLD Do0E24 + LXI B,I$0014 + PUSH B + LHLD Do0E24 + XCHG + POP B + LXI H,I$0B60 + PUSH H + LHLD D$0E22 + PCHL +; +I$0B60: RET +; +;-------------------------------- +J$0B61: CALL Co0000 +; + JMP J$0B7E ; Jump around statement +;-------------------------------- +; +C$0B67: MOV L,C + MOV H,B + SHLD Do0E28 + LXI B,I$0013 + PUSH B + LHLD Do0E28 + XCHG + POP B + LXI H,I$0B7D + PUSH H + LHLD D$0E26 + PCHL +; +I$0B7D: RET +; +;-------------------------------- +J$0B7E: CALL Co0000 +; + JMP J$0B9B ; Jump around statement +;-------------------------------- +; +Qo0B84: MOV L,C + MOV H,B + SHLD Do0E2C + LXI B,I$0012 + PUSH B + LHLD Do0E2C + XCHG + POP B + LXI H,I$0B9A + PUSH H + LHLD D$0E2A + PCHL +; +I$0B9A: RET +; +;-------------------------------- +J$0B9B: CALL Co0000 +; + JMP J$0BB8 ; Jump around statement +;-------------------------------- +; +Qo0BA1: MOV L,C + MOV H,B + SHLD Do0E30 + LXI B,I$0011 + PUSH B + LHLD Do0E30 + XCHG + POP B + LXI H,I$0BB7 + PUSH H + LHLD D$0E2E + PCHL +; +I$0BB7: RET +; +;-------------------------------- +J$0BB8: CALL Co0000 +; + JMP J$0BD5 ; Jump around statement +;-------------------------------- +; +Co0BBE: MOV L,C + MOV H,B + SHLD Do0E34 + LXI B,I$0010 + PUSH B + LHLD Do0E34 + XCHG + POP B + LXI H,I$0BD4 + PUSH H + LHLD D$0E32 + PCHL +; +I$0BD4: RET +; +;-------------------------------- +J$0BD5: CALL Co0000 +; + JMP J$0BF2 ; Jump around statement +;-------------------------------- +; +Co0BDB: MOV L,C + MOV H,B + SHLD Do0E38 + LXI B,Io000F + PUSH B + LHLD Do0E38 + XCHG + POP B + LXI H,I$0BF1 + PUSH H + LHLD D$0E36 + PCHL +; +I$0BF1: RET +; +;-------------------------------- +J$0BF2: CALL Co0000 +; + JMP J$0C10 ; Jump around statement +;-------------------------------- +; +Qo0BF8: MOV L,C + MOV H,B + MOV A,L + STA Do0E3C + LXI B,I$000E + PUSH B + LDA Do0E3C + MOV E,A + POP B + LXI H,I$0C0F + PUSH H + LHLD D$0E3A + PCHL +; +I$0C0F: RET +; +;-------------------------------- +J$0C10: CALL Co0000 +; + JMP J$0C27 ; Jump around statement +;-------------------------------- +; +Qo0C16: LXI B,I$000D + PUSH B + LXI D,Co0000 + POP B + LXI H,I$0C26 + PUSH H + LHLD D$0E3D + PCHL +; +I$0C26: RET +; +;-------------------------------- +J$0C27: CALL Co0000 +; + JMP J$0C3E ; Jump around statement +;-------------------------------- +; +Qo0C2D: LXI B,I$000C + PUSH B + LXI D,Co0000 + POP B + LXI H,I$0C3D + PUSH H + LHLD D$0E3F + PCHL +; +I$0C3D: RET +; +;-------------------------------- +J$0C3E: CALL Co0000 +; + JMP J$0C55 ; Jump around statement +;-------------------------------- +; +Qo0C44: LXI B,I$000B + PUSH B + LXI D,Co0000 + POP B + LXI H,I$0C54 + PUSH H + LHLD D$0E41 + PCHL +; +I$0C54: RET +; +;-------------------------------- +J$0C55: CALL Co0000 +; + JMP J$0C72 ; Jump around statement +;-------------------------------- +; +Qo0C5B: MOV L,C + MOV H,B + SHLD Do0E45 + LXI B,Io000A + PUSH B + LHLD Do0E45 + XCHG + POP B + LXI H,I$0C71 + PUSH H + LHLD D$0E43 + PCHL +; +I$0C71: RET +; +;-------------------------------- +J$0C72: CALL Co0000 +; + JMP J$0C8F ; Jump around statement +;-------------------------------- +; +Co0C78: MOV L,C + MOV H,B + SHLD Do0E49 + LXI B,I$0009 + PUSH B + LHLD Do0E49 + XCHG + POP B + LXI H,I$0C8E + PUSH H + LHLD D$0E47 + PCHL +; +I$0C8E: RET +; +;-------------------------------- +J$0C8F: CALL Co0000 +; + JMP J$0CAD ; Jump around statement +;-------------------------------- +; +Qo0C95: MOV L,C + MOV H,B + MOV A,L + STA Do0E4D + LXI B,I$0008 + PUSH B + LDA Do0E4D + MOV E,A + POP B + LXI H,I$0CAC + PUSH H + LHLD D$0E4B + PCHL +; +I$0CAC: RET +; +;-------------------------------- +J$0CAD: CALL Co0000 +; + JMP J$0CC4 ; Jump around statement +;-------------------------------- +; +Qo0CB3: LXI B,I$0007 + PUSH B + LXI D,Co0000 + POP B + LXI H,I$0CC3 + PUSH H + LHLD D$0E4E + PCHL +; +I$0CC3: RET +; +;-------------------------------- +J$0CC4: CALL Co0000 +; + JMP J$0CE2 ; Jump around statement +;-------------------------------- +; +C$0CCA: MOV L,C + MOV H,B + MOV A,L + STA Do0E52 + LXI B,BDOS + PUSH B + LDA Do0E52 + MOV E,A + POP B + LXI H,I$0CE1 + PUSH H + LHLD D$0E50 + PCHL +; +I$0CE1: RET +; +;-------------------------------- +J$0CE2: CALL Co0000 +; + JMP J$0D00 ; Jump around statement +;-------------------------------- +; +C$0CE8: MOV L,C + MOV H,B + MOV A,L + STA Do0E55 + LXI B,Io0004 + PUSH B + LDA Do0E55 + MOV E,A + POP B + LXI H,I$0CFF + PUSH H + LHLD D$0E53 + PCHL +; +I$0CFF: RET +; +;-------------------------------- +J$0D00: CALL Co0000 +; + JMP J$0D17 ; Jump around statement +;-------------------------------- +; +Co0D06: LXI B,Io0003 + PUSH B + LXI D,Co0000 + POP B + LXI H,I$0D16 + PUSH H + LHLD D$0E56 + PCHL +; +I$0D16: RET +; +;-------------------------------- +J$0D17: CALL Co0000 +; + JMP J$0D35 ; Jump around statement +;-------------------------------- +; +Co0D1D: MOV L,C + MOV H,B + MOV A,L + STA Do0E5A + LXI B,I$0002 + PUSH B + LDA Do0E5A + MOV E,A + POP B + LXI H,I$0D34 + PUSH H + LHLD D$0E58 + PCHL +; +I$0D34: RET +; +;-------------------------------- +J$0D35: CALL Co0000 +; + JMP J$0D4C ; Jump around statement +;-------------------------------- +; +C$0D3B: LXI B,Io0001 + PUSH B + LXI D,Co0000 + POP B + LXI H,I$0D4B + PUSH H + LHLD D$0E5B + PCHL +; +I$0D4B: RET +; +;-------------------------------- +J$0D4C: CALL Co0000 ; End of code... +;-------------------------------- +; +Do0D4F: DB 0,0 +Do0D51: DB 0,0 +Do0D53: DB 0,0 +Do0D55: DB 0,0 +Do0D57: DB 0,0 +Do0D59: DB 0,0 +Do0D5B: DB 0,0,0,0 +Do0D5F: DB 0,0 +Do0D61: DB 0,0 +Do0D63: DB 0,0 +Do0D65: DB 0,0 +Do0D67: DB 0,0 +Do0D69: DB 0,0 +Do0D6B: DB 0,0,0,0 +Do0D6F: DB 0,0 +Do0D71: DB 0,0 +Do0D73: DB 0,0 +Do0D75: DB 0,0 +Do0D77: DB 0,0 +Do0D79: DB 0 +Do0D7A: DB 0,0,0 +Do0D7D: DB 0,0 +Do0D7F: DB 0,0 +Do0D81: DB 0,0 +Do0D83: DB 0,0 +Do0D85: DB 0,0 +Do0D87: DB 0,0 +Do0D89: DB 0,0 +Do0D8B: DB 0,0,0,0 +Do0D8F: DB 0,0 +Do0D91: DB 0,0 +Do0D93: DB 0,0 +Do0D95: DB 0,0 +Do0D97: DB 0,0 +Do0D99: DB 0,0,0 +Do0D9C: DB 0,0 +Do0D9E: DB 0,0 +Do0DA0: DB 0,0 +Do0DA2: DB 0,0 +Do0DA4: DB 0,0 +Do0DA6: DB 0,0 +Do0DA8: DB 0,0 +Do0DAA: DB 0,0 +Do0DAC: DB 0,0 +Do0DAE: DB 0,0,0,0 +Do0DB2: DB 0 +Do0DB3: DB 0,0,0,0,0,0,0 +Do0DBA: DB 0,0 +Do0DBC: DB 0,0 +Do0DBE: DB 0,0 +Do0DC0: DB 0,0 +Do0DC2: DB 0,0 +Do0DC4: DB 0,0 +Do0DC6: DB 0,0 +Do0DC8: DB 0,0 +Do0DCA: DB 0,0,0,0,0,0 +Do0DD0: DB 0,0 +Do0DD2: DB 0,0 +Do0DD4: DB 0,0 +Do0DD6: DB 0,0 +Do0DD8: DB 0,0 +Do0DDA: DB 0,0 +Do0DDC: DB 0 +Do0DDD: DB 0 +Do0DDE: DB 0 +Do0DDF: DB 0,0,0,0 +Do0DE3: DB 0 +Do0DE4: DB 0,0 +Do0DE6: DB 0,0 +Do0DE8: DB 0 +Do0DE9: DB 0 +Do0DEA: DB 0 +Do0DEB: DB 0 +Do0DEC: DB 0 +Do0DED: DB 0,0 +Do0DEF: DB 0,0 +Do0DF1: DB 0 +Do0DF2: DB 0,0 +Do0DF4: DB 0,0 +Do0DF6: DB 0,0 +Do0DF8: DB 0,0,0,0,0,0,0 +Do0DFF: DB 0,0 +Do0E01: DB 0,0 +Do0E03: DB 0,0 +Do0E05: DB 0,0 +Do0E07: DB 0,0,0 +Do0E0A: DB 0,0,0,0 +D$0E0E: DCR B + NOP +D$0E10: DCR B + DB 0 +Do0E12: DB 0,0 +D$0E14: DCR B + NOP +D$0E16: DCR B + DB 0 +Do0E18: DB 0,0 +D$0E1A: DCR B + DB 0 +Do0E1C: DB 0,0 +D$0E1E: DCR B + DB 0 +Do0E20: DB 0,0 +D$0E22: DCR B + DB 0 +Do0E24: DB 0,0 +D$0E26: DCR B + DB 0 +Do0E28: DB 0,0 +D$0E2A: DCR B + DB 0 +Do0E2C: DB 0,0 +D$0E2E: DCR B + DB 0 +Do0E30: DB 0,0 +D$0E32: DCR B + DB 0 +Do0E34: DB 0,0 +D$0E36: DCR B + DB 0 +Do0E38: DB 0,0 +D$0E3A: DCR B + DB 0 +Do0E3C: DB 0 +D$0E3D: DCR B + NOP +D$0E3F: DCR B + NOP +D$0E41: DCR B + NOP +D$0E43: DCR B + DB 0 +Do0E45: DB 0,0 +D$0E47: DCR B + DB 0 +Do0E49: DB 0,0 +D$0E4B: DCR B + DB 0 +Do0E4D: DB 0 +D$0E4E: DCR B + NOP +D$0E50: DCR B + DB 0 +Do0E52: DB 0 +D$0E53: DCR B + DB 0 +Do0E55: DB 0 +D$0E56: DCR B + NOP +D$0E58: DCR B + DB 0 +Do0E5A: DB 0 +D$0E5B: DCR B + NOP +; +;-------------------------------- +; + END ; Standard CP/M RELocatable file + \ No newline at end of file diff --git a/SysCon PLMX/IOLIB.REL b/SysCon PLMX/IOLIB.REL new file mode 100644 index 0000000..9d7f2cf Binary files /dev/null and b/SysCon PLMX/IOLIB.REL differ diff --git a/SysCon PLMX/MEAN.COM b/SysCon PLMX/MEAN.COM new file mode 100644 index 0000000..6d96905 Binary files /dev/null and b/SysCon PLMX/MEAN.COM differ diff --git a/SysCon PLMX/MEAN.MAC b/SysCon PLMX/MEAN.MAC new file mode 100644 index 0000000..0792b4f --- /dev/null +++ b/SysCon PLMX/MEAN.MAC @@ -0,0 +1,99 @@ + TITLE MEANV + NAME ('MEANV') +MEANV:: +; +;/***********************************************************/ +;/* A PROGRAM TO FIND THE MEAN OF THE 10 VALUES OF AN ARRAY */ +;/***********************************************************/ +; +; +;MEAN$VAL: +; +;DO; +; +; +; DECLARE X (10) BYTE DATA (23,2,18,0,20,14,45,27,8,33); +; +; DECLARE SUM ADDRESS; +; +; DECLARE (MEAN, I) BYTE; +; +; +; SUM = 0; + LXI H,0H +; +; I = 0; + SHLD A0003 + MVI A,0H +; +; DO WHILE I <= 9; + STA A0005 +G0007: + MVI L,09H + LDA A0005 + EXTRN BP36@ + CALL BP36@ +; +; SUM = SUM + X (I); + RRC + JNC G0008 + LHLD A0005 + MVI H,0 + XCHG + LXI H,A0001 + DAD D + MOV A,M + LHLD A0003 + EXTRN BP57@ + CALL BP57@ +; +; I = I + 1; + SHLD A0003 + MVI L,01H + LDA A0005 + EXTRN BP25@ + CALL BP25@ +; +; END; + STA A0005 + JMP G0007 +; +; MEAN = SUM / 10; +G0008: + MVI A,0AH + LHLD A0003 + EXTRN BP71@ + CALL BP71@ + SHLD T0009 + LDA T0009 +; +; +;END MEAN$VAL; + STA A0004 + EXTRN EXIT@ +SCAT@: + CALL EXIT@ +A0001: + DB 017H + DB 02H + DB 012H + DB 0H + DB 014H + DB 0EH + DB 02DH + DB 01BH + DB 08H + DB 021H + DSEG +A0003: + DS 02H +A0004: + DS 01H +A0005: + DS 01H +T0006: + DS 01H +T0009: + DS 02H + END + \ No newline at end of file diff --git a/SysCon PLMX/MEAN.REL b/SysCon PLMX/MEAN.REL new file mode 100644 index 0000000..3ed2c98 Binary files /dev/null and b/SysCon PLMX/MEAN.REL differ diff --git a/SysCon PLMX/MEAN.SRC b/SysCon PLMX/MEAN.SRC new file mode 100644 index 0000000..b583506 --- /dev/null +++ b/SysCon PLMX/MEAN.SRC @@ -0,0 +1,22 @@ +/***********************************************************/ +/* A PROGRAM TO FIND THE MEAN OF THE 10 VALUES OF AN ARRAY */ +/***********************************************************/ + + +MEAN$VAL: +DO; + + DECLARE X (10) BYTE DATA (23,2,18,0,20,14,45,27,8,33); + DECLARE SUM ADDRESS; + DECLARE (MEAN, I) BYTE; + + SUM = 0; + I = 0; + DO WHILE I <= 9; + SUM = SUM + X (I); + I = I + 1; + END; + MEAN = SUM / 10; + +END MEAN$VAL; + \ No newline at end of file diff --git a/SysCon PLMX/PARSER.PLM b/SysCon PLMX/PARSER.PLM new file mode 100644 index 0000000..7af27c4 Binary files /dev/null and b/SysCon PLMX/PARSER.PLM differ diff --git a/SysCon PLMX/PLMLEX.PLM b/SysCon PLMX/PLMLEX.PLM new file mode 100644 index 0000000..61fe717 Binary files /dev/null and b/SysCon PLMX/PLMLEX.PLM differ diff --git a/SysCon PLMX/PLMX.COM b/SysCon PLMX/PLMX.COM new file mode 100644 index 0000000..84781f6 Binary files /dev/null and b/SysCon PLMX/PLMX.COM differ diff --git a/SysCon PLMX/PLMX.SUB b/SysCon PLMX/PLMX.SUB new file mode 100644 index 0000000..77462df --- /dev/null +++ b/SysCon PLMX/PLMX.SUB @@ -0,0 +1,4 @@ +plmx $1 +m80 =$1.mac +l80 $1,rlib,$1/n/e + \ No newline at end of file diff --git a/SysCon PLMX/PLMXUG.TXT b/SysCon PLMX/PLMXUG.TXT new file mode 100644 index 0000000..c9b03be --- /dev/null +++ b/SysCon PLMX/PLMXUG.TXT @@ -0,0 +1,2500 @@ +PLMXUG.WS4 (= PLMX User's Guide) +---------- + +CP/M 1.4 -- PLMX User's Guide, System Consultants, Inc., 1980 + +(Retyped by Emmanuel ROCHE.) + + + PLMX User's Guide + + 8080/8085/Z-80 + (CP/M 1.4) + + PLMX User's Guide, 8080/8085/Z-80 (CP/M) - SCI-PDG-100B + + +Table of Contents +----------------- + +Section +------- + + 1 Introduction + + 2 References + + 3 Creation of Source Files + + 4 Modular Programming + + 5 Invocation of the Compiler + + 6 File Names Used by PLMX + + 7 Error Message Formats + + 8 Error Recovery + + 9 Output of the Compiler + + 10 Linkage of Programs + + 11 Implementation Specifics + + 11.1 RE-ENTRANT Procedures + 11.2 INTERRUPT Attribute + 11.3 Variable Initialization + 11.4 Macro Declarations + 11.5 EXTERNAL and PUBLIC Names + 11.6 Restrictions on Names + 11.7 DO-CASE Restrictions + 11.8 Maximum Nesting Levels + 11.9 Optimization + 11.10 Maximum Parameter List Size + 11.11 INCLUDE Pseudo-operation + 11.12 Size Limits + 11.13 AT Attribute + 11.14 Compile-Time Stack Checking + 11.15 Label Declarations + 11.16 Run-Time Library + + 12 Built-In Procedures and Predeclared Variables + + 12.1 INPUT Procedure + 12.2 LENGTH, LAST, and SIZE Procedures + 12.3 LOW, HIGH, and DOUBLE Procedures + 12.4 ROL and ROR Procedures + 12.5 SHR and SHL Procedures + 12.6 MOVE Procedure + 12.7 TIME Procedure + 12.8 OUTPUT Array + 12.9 MEMORY Array + 12.10 STACKPTR Variable + + 13 Features Involving Hardware Flags + + 13.1 PLUS and MINUS Operators + 13.2 CARRY and ROTATION Procedures + 13.3 DEC Procedure + 13.4 CARRY, SIGN, ZERO, and PARITY procedures + + 14 Producing an Executable Object File + + +Appendix +-------- + + A Command Line and Command Line Switches + + A.1 Command Line + A.2 Command Line Switches + + B Semantic Errors of PLMX + + C System Error Procedure + + D I/O Procedures + + D.1 CP/M system-Level Procedures + D.2 Read and Write Line Procedures + + D.2.1 Procedure READ + D.2.2 Procedure WRITE + + D.3 Disk I/O Procedures + + D.3.1 Procedure DRCHR + D.3.2 Procedure DWCHR + D.3.3 Procedure DRLIN + D.3.4 Procedure DWLIN + D.3.5 Procedure OPENR + D.3.6 Procedure CLOSR + D.3.7 Procedure OPENW + D.3.8 Procedure CLOSW + + D.4 Other Procedures + + D.4.1 Procedure NUMIN + D.4.2 Procedure NMOUT + + E Sample Output + + F IOCLD.SRC Listing + + G PLMX Advertisements + + H ROCHE Addenda + + +Section 1: Introduction +----------------------- + +This document provides guidelines for use of the PLMX compiler on the CP/M +1.4 Operating System. The PLMX language is identical to the Intel PL/M +programming language. Familiarity with PL/M and CP/M is assumed throughout +this document. Detailed descriptions of the PL/M programming language are +found in the publications listed in Section 2. Notational conventions used in +this document are: + + - Anything enclosed in angle brackets < > is a generic name. + + - Anything enclosed in square brackets [] is optional. + + - ::= means "is defined as". + + - | means "or". + +The output of the PLMX compiler must be assembled, linked, and loaded. The +Microsoft M80 Utility Software Package is provided for this purpose. See +Reference 5, Section 2, for the M80 software package documentation. + + +Section 2: References +--------------------- + +The following publications pertain to the PL/M programming language: + + 1. Daniel D. McCracken + "A Guide to PL/M Programming for Microcomputer Applications" + Addison-Wesley, 1978. + +(References in this publication to the ISIS-II Operating System are not +pertinent to PLMX.) + + 2. "PL/M-80 Programming Manual" + Intel Corporation, 3065 Bowers Avenue, Santa Clara, + California 95051, 1976-1977. + +The following publications pertain to the CP/M 1.4 Operating System: + + 3. "An Introduction to CP/M Features and Facilities" + Digital Research, P. 0. Box 579, + Pacific Grove, CA 93950, 1976, 1977, 1978. + + 4. "CP/M Interface Guide" + Digital Research, 1975, 1976. + +The M80 Utility Software Package for use on CP/M Operating Systems is +described in: + + 5. "MICROSOFT Utility Software Manual" + Microsoft, 10800 NE Eighth, Suite 819, + Bellevue, WA 98004, 1978. + + +Section 3: Creation of Source Files +----------------------------------- + +Source files for PLMX may be created using the CP/M ED editor or any editor +which produces ED-compatible text files. + +The source text for PLMX is free format. Spaces, tabs, Carriage-Returns, and +Line-Feeds are ignored, except when within the body of a string literal. +Comments may occur anywhere in the source text, except within reserved words, +identifier names, and numbers. Comments may not be nested. Tabs are assumed to +be at eight-column intervals. + + +Section 4: Modular Programming +------------------------------ + +PLMX is well suited to good programming practices such as modular programming +and structured program design. Modules may be compiled separately and used as +necessary. Several people may work on the same program independently. Data +structures may be designed independently of other modules. Modules and data +structures may be modified easily without affecting the entire program. + +The size of modules which can be compiled with PLMX depends on the size of the +CP/M system. A minimum of 56K of RAM is recommended, although small programs +can be compiled in a 48K system. + +References 1 and 2 contain detailed information on modular programming in +PL/M. + + +Section 5: Invocation of the Compiler +------------------------------------- + +The PLMX compiler disk may be located on any disk drive. The PLMX compiler is +invoked at the command level of CP/M by typing a command line which may take +one of the following forms: + + 1. PLMX x + + 2. PLMX x.y + + 3. PLMX x ; S + + 4. PLMX x.y ; S + +If form 1 is used, the source file is x.SRC and the default switch settings +are in effect. + +If form 2 is used, the source file is x.y and the default switch settings are +in effect. + +If form 3 is used, the source file is x.SRC and the switch settings S are in +effect where they differ from the default switch settings. + +If form 4 is used, the source file is x.y and the switch settings S are in +effect where they differ from the default switch settings. + +Switch S is actually a list of switches, each separated by zero or more +spaces. Individual switches consist of a letter followed immediately by a "+" +or a "-". + +The output file is always stored on the same disk as the source file. The +source file need not be on the same disk as compiler files. + +See Appendix A for a modified BNF description of the command line, examples of +command lines, and the meaning of command line switches. + + +Section 6: File Names Used by PLMX +---------------------------------- + +PLMX creates several temporary files during compilation. If the source file +name is SFNAME.X, the temporary file names will be SFNAME.TOK, SFNAME.RAM, and +SFNAME.ROM. Any existing files of these names will be erased if they are on +the same disk as the source file. + +PLMX produces an assembly language output file, unless that option is turned +off by a command line switch. If the source file name is SFNAME.X, the output +file name will be SFNAME.MAC. Any existing file with this name will also be +erased if it is on the same disk as the source file. + +There is a PLMX compiler patch facility built into the PLMX compiler. A patch +file may be associated with each PLMX compiler file. As each PLMX compiler +file is loaded, the compiler disk is searched for its associated patch file. +If found, it is loaded, and the PLMX compiler file is patched. Patch files +have the names PL.HEX, PP.HEX, PI.HEX, and PF.HEX. If files with these names +exist on the compiler disk, they will be treated as patch files. No files with +these names should be created for use with the PLMX compiler, unless +specifically recommended by SCI. + +Included on the master disk is a file, IOCLD.SRC, containing the external +procedure declaration for all I/O procedures from which the user may choose +for his application. A description of each of the procedures is given in +Appendix D and Digital Research "CP/M 1.4 Interface Guide". + + +Section 7: Error Message Formats +-------------------------------- + +PLMX recognizes syntactic errors in a table-driven manner, and indicates the +approximate location of errors on the console device and/or on the listing. + +Other errors result from semantic restrictions to the language. For example, +variables must be defined before they are used. PLMX handles these errors in a +case-by-case manner, and displays their numbers as shown below in type 4. +Refer to Appendix B for the semantic errors and error numbers. + +Error messages are displayed on the console if the C+ and L+ switches are in +effect. Error messages will be displayed on the printer if the L+ and C- +switches are in effect. + +There are several formats for error messages printed by the PLMX compiler: + + Type 1. Errors detected at the PLMX compiler's executive level are + indicated by messages such as "FILE ERROR", which usually + means a non-existent file. + + Type 2. Low-level syntactic errors are printed as a statement of the + error type, followed by an indication of where the error was + detected. For example: "ILLEGAL CHARACTER ON LINE xxx NEAR + COLUMN yyy". + + Type 3. Other syntactic errors are printed as "ERROR ON LINE xxx NEAR + COLUMN yyy". + + Type 4. Semantic errors are printed as "SEMANTIC ERROR NUMBER nn ON + LINE xxx NEAR COLUMN yyy". + + Type 5. The illegal GOTO error message is printed as "ILLEGAL GOTO ON + LINE xxx". + + Type 6. The system error message is printed as "SYSTEM ERROR AT nnnn". + +For error types 3 and 4, the PLMX compiler will write a list of up to ten +tokens to the console, and terminate in the token which precipitated the +error. Since these tokens represent a reformatting of the internal +representation of the compiled program, the list will not appear as it does in +the source file. In particular, comments are not included, and numeric +constants are all in hexadecimal notations. + +The first ten errors of types 3 and 4 are also flagged in the interleaved +output listing in the following manner: + + IF FLAG THEN X = Y; + A + B = 5; + **************? + FLAG = FALSE; + +A type 6 error message indicates that the PLMX compiler has encountered one of +a general class of conditions from which it cannot recover. See Appendix C for +the procedure to follow in this case. + + +Section 8: Error Recovery +------------------------- + +The PLMX compiler attempts to recover from errors as the errors are +encountered. If possible, the statement in which the error occurred will be +ignored, and the compilation will continue with the following statement. If +recovery from the error is not possible, the compilation will be aborted, and +a message printed to indicate at which phase the compilation was aborted. + + +Section 9: Output of the Compiler +--------------------------------- + +The PLMX compiler produces an assembly language source file as output. The Z- +80 PLMX compiler produces MOSTEK mnemonics. The output file may be edited +before assembling, if fine tuning is required. + +The following pseudo-ops are used in the assembly language file: DB, DW, DS, +ORG, END, CSEG, ASEG, DSEG, and "$", which has the same meaning as defined by +the Microsoft M80 Assembler. + +The output includes simple expressions involving the operators "+" and "-". +The operands are hexadecimal constants or "$". The hexadecimal constants +consist of up to four hexadecimal digits preceded by a zero and followed by +the letter "H". + +The PLMX compiler will also produce a listing if the "L" switch is set to "+". +If the "I" switch is set to "+" (the default state), the listing will be an +assembly language listing with PLMX source statements interleaved as comments. +If the "I" switch is set to "-", the listing will be a source file listing +with line numbers added, and will include the text of included files. + +The "C" switch affects the destination of the listing. If the "C" switch is +set to "-" (the default state), the listing will go to the printer. If set to +"+", the listing will go to the console. See Appendix A.2 for further +definition of command line switches. See Appendix E for a sample output file. + + +Section 10: Linkage of Programs +------------------------------- + +Assembly language programs may be linked to programs compiled by PLMX. It is +possible to call assembly language procedures from a PLMX program and, +likewise, to call PLMX procedures from assembly language programs. + +Parameters are passed to procedures as follows: + + 1. One-parameter case: + + a. A BYTE parameter is passed in register C. + + b. An ADDRESS parameter is passed in register pair BC, with the high- + order byte in register B. + + 2. Two-parameter case: + + a. The first parameter is passed as described in 1 above. + + b. The second parameter is passed in register E if it is a BYTE parameter + and in register pair DE if it is an ADDRESS parameter, with the high- + order byte in register D. + + 3. More-than-two-parameter case: + + a. The last parameter is passed in register pair DE. + + b. The next-to-last parameter is passed in register pair BC. + + c. The remaining parameters are passed on the stack, with the first + parameter being PUSHed first. + + d. When extracting parameters from the stack, remember that the return + address will be on the top of the stack, then the parameters. + +Parameters are returned from function procedures in the following manner: + + 1. A BYTE procedure returns its parameters in register A. + + 2. An ADDRESS procedure returns its result in register pair HL, with the + high-order byte in register H. + + +Section 11: Implementation Specifics +------------------------------------ + +This section presents aspects of PLMX which differ from the Intel PL/M-80 +compiler. Some items are specific to this release version. + + +11.1 RE-ENTRANT Procedures +-------------------------- + +This version of PLMX does not implement the translation of RE-ENTRANT +procedures. Although this feature will be included in a future release, the +programmer should be aware that procedure linkages and data references within +such a procedure are extremely space and time inefficient. Furthermore, a +time- and I/O-independent algorithm can always be restructured in a non- +recursive manner. The run-time routines are all re-entrant, so that the user +may easily create a multiprogramming environment. + + +11.2 INTERRUPT Attribute +------------------------ + +This version of PLMX does not implement the INTERRUPT attribute of procedures +because of the many ways in which interrupts can be serviced. Since the +assembly language output of the PLMX compiler is available to the programmer, +and PLMX allows linkage to assembly language routines, interrupt procedures +can be specified for many types of architectures. + + +11.3 Variable Initialization +---------------------------- + +When the programmer uses text strings to initialize variables in a factored +variable declaration, he should be aware that, if the string is longer than +the datum currently being initialized, the rest of the string will be lost. +For instance: + + DECLARE (A, B) (5) BYTE INITIAL ('123456789'); + +would initialize A to '12345' but would leave B un-initialized. The following +declaration should be used to initialize B also: + + DECLARE (A, B) (5) BYTE INITIAL ('12345', '6789'); + + +11.4 Macro Declarations +----------------------- + +Macro declarations may be nested. For instance: + + DECLARE CHI BYTE; + DECLARE OMEGA LITERALLY 'LITERALLY ''IF CHI''; + DECLARE OMICRON OMEGA; + OMICRON THEN DO; + ---- + ---- + ---- + END; + + +11.5 EXTERNAL and PUBLIC Names +------------------------------ + +All identifiers declared to be PUBLIC or EXTERNAL, and all module names, will +be truncated to five letters, and used by the PLMX compiler in that form. +Thus, the user should ensure that these identifiers are unique in the first +five letters. + + +11.6 Restrictions on Names +-------------------------- + +Compiler-generated names may occasionally conflict with names declared to be +PUBLIC or EXTERNAL. A complete list of names which the PLMX compiler may +generate follows: + + 1. The letter A, T, L, or G, followed by four hexadecimal digits. + For example: G0004. + + 2. Names of the form BPnn@, where n is a decimal digit. One or more of + these names will be created upon reference to a built-in procedure or + predeclared variable. + + 3. Any of the following names: + + INIT@ EXIT@ AAAAA@ AAAAB@ SCAT@ + + 4. Names reserved for I/O procedures. See Appendix D. + +Do not use global identifier names which conflict with register names of the +target microprocessor, because the output of PLMX must be assembled. + + +11.7 DO-CASE Restrictions +------------------------- + +There may not be more than 32,767 branches on a DO-CASE statement. + +If a conditional statement is used as a unit of a DO-CASE block, it must be +bracketed by a DO-BLOCK of some sort. For example: + + DO CASE J: + X=Y; + DO; + IF P=Q THEN J=F; + END; + END; + + +11.8 Maximum Nesting Levels +--------------------------- + +DO blocks may be nested to 32 levels. Conditional statements may be nested to +32 levels. + + +11.9 Optimization +----------------- + +This version of PLMX performs peephole optimization, constant folding, and +temporary minimization by default. Other types of optimization will be +implemented in a future release. + + +11.10 Maximum Parameter List Size +--------------------------------- + +A procedure declaration may have up to 11 formal parameters. + + +11.11 INCLUDE Pseudo-Operation +------------------------------ + +This version implements only the INCLUDE pseudo-operation. Other pseudo- +operations may be implemented in future releases. The INCLUDE pseudo-op must +occur on a line by itself, and consists of five elements: + + - "$" in column 1 + + - The word "INCLUDE" + + - A left parenthesis "(" + + - A CP/M file name, with default type of SRC + + - A right parenthesis ")" + +There may be zero or more spaces between each of the five items. The nesting +of INCLUDE files is limited to 4, counting the main file as one level. + +The INCLUDE pseudo-op can be placed on any line in the user program, and will +be recognized. + + +11.12 Size Limits +----------------- + +String constants are limited to 255 characters. The input line is limited to +80 characters. + + +11.13 AT Attribute +------------------ + +If the programmer uses the AT attribute with the DATA form of initialization, +the restricted expression following AT must refer to a previous declaration +with a DATA initialization. The reason for this restriction is that the word +DATA implies that the datum is to be placed with the executable code in its +SECTION, instead of in the SECTION where variables are usually placed. Not +adhering to this restriction would mean that the PLMX compiler will try to +overlay a RAM datum with a ROM datum, which is an obviously illogical +condition. + +The AT attribute should never be used with the dot operator and an externally +declared variable. Some assemblers (including Microsoft's M80) cannot resolve +that condition. Based variables can be used to overlay one variable on +another. + + +11.14 Compile-Time Stack Checking +--------------------------------- + +There is no compile-time checking for stack overflow in PLMX, and there is no +PLMX compiler option to change the size of the stack. The Stack Pointer is +initially set to the top of the Temporary Program Area (TPA). To modify or +examine the Stack Pointer, use the pseudo-variable or built-in variable +STACKPTR. + + +11.15 Label Declarations +------------------------ + +Labels with no attributes need not be declared. Factored label declarations +are not recognized in this version. They must be declared individually. + + +11.16 Run-Time Library +---------------------- + +The run-time library provides code for all operators and byte/address +combinations, built-in procedures, and procedures using hardware flags. The +source code for the run-time library is available from SCI. It enables the +user to substitute or add to these routines, as desired. The following +routines are included in the library: + + a. Operations + ---------- + (Byte/Byte, 2-Byte/Byte, Byte/2-Byte, and 2-Byte/2-Byte cases) + + ADD SUBTRACT + OR EQUAL + AND LESS THAN + XOR GREATER THAN + MOD DIVIDE + LESS THAN OR EQUAL MULTIPLY + GREATER THAN OR EQUAL NOT EQUAL + + b. Built-In Procedures: + + Procedure Type + --------- ---- + ROL Byte + ROR Byte + SHL Byte/2-Byte + SHR Byte/2-Byte + MOVE Byte + TIME Byte + + c. Procedures Utilizing Hardware Flags: + + Procedure Type + --------- ---- + PLUS (Same as Operations) + MINUS (Same as Operations) + SCL Byte/2-Byte + SCR Byte/2-Byte + DEC Byte + +The register usage for interfacing with the library is: + + a. Operations + ---------- + + (1) 2-Byte/2-Byte case: + + Parameters located in DE and HL. + + (2) 2-Byte/Byte case: + + Byte parameters in A, 2-Byte parameters located located in HL. + + (3) Byte/Byte case: + + Parameters located in A and L. + + b. Built-In Procedures and Flag Procedures + --------------------------------------- + + Register usage for built-in procedures follow the convention described + in Section 10. Consider the MOVE procedure, for example: + + (1) Last parameter (DESTINATION) in DE + (2) Next-to-last parameter (SOURCE) in BC + (3) Remaining parameter (COUNT) on stack + + +Section 12: Built-in Procedures and Predeclared Variables +--------------------------------------------------------- + +Built-in procedures and predeclared variables need not be declared. If, +however, the identifier of a built-in procedure or predeclared variable is +used in a declaration within the program, the scope of the predeclared +variable or built-in procedure is interrupted by the scope of the declaration +in the program. This distinguishes these identifiers from reserved words, +which cannot be used as identifiers in declarations. + +The built-in procedures provided by PLMX are: + + INPUT DOUBLE + LENGTH ROL + LAST ROR + SIZE MOVE + LOW TIME + HIGH + +The predeclared variables are: + + OUTPUT + STACKPTR + +A detailed description of these procedures and variables is given in the +"PL/M-80 Programming Manual" (Reference 2). Only those which are not fully +described in Reference 1 are described here. + + +12.1 INPUT Procedure +-------------------- + +INPUT is a BYTE procedure. It is called by a function reference with the form: +INPUT (numeric *constant*). It must appear on the right side of an assignment +statement. The constant must be in the range 0 to 255 to specify one of the +256 input ports of the 8080 or Z-80 CPU. The value returned by INPUT is the +BYTE quantity latched into the specified input port. + + +12.2 LENGTH, LAST, and SIZE Procedures +-------------------------------------- + +(See Reference 1 or 2.) + + +12.3 LOW, HIGH, and DOUBLE Procedures +------------------------------------- + +Two built-in BYTE procedures convert ADDRESS values to BYTE values. Calls to +these procedures are function references with the forms: + + LOW (expression) + HIGH (expression) + +If the expression has an ADDRESS value, LOW returns the low-order (least +significant) byte of the value, whereas HIGH returns the high-order (most +significant) byte of the value. If the expression has a BYTE value, LOW will +return this value unchanged. HIGH will return zero. + +The address procedure DOUBLE converts a BYTE value to an ADDRESS value. A call +to DOUBLE is a function reference with the form: + + DOUBLE (expression) + +If the expression has a BYTE value, the procedure appends 8 high-order zeros +to convert it to an ADDRESS value, and returns this ADDRESS value. If the +expression has an ADDRESS value, the procedure returns this value unchanged. + +There is no uniformity among microprocessors regarding which is the most +significant byte and which is the least significant byte of an ADDRESS +identifier. For this reason, the use of the HIGH and LOW procedures may be +more useful than shift procedures for extraction of bytes of an ADDRESS +identifier. Source code will then be microprocessor-independent. + + +12.4 ROL and ROR Procedures +--------------------------- + +ROL and ROR are BYTE rotation procedures. Bits are moved off one end and moved +onto the other end. They are called by function references with the forms: + + ROL (pattern, count) + ROR (pattern, count) + +where "pattern" and "count" are both expressions. The values of these +expressions are converted, if necessary, to BYTE values. The first parameter +is handled as an 8-bit pattern which is rotated to the left (by ROL) or to the +right (by ROR). The bit count is given by the second parameter. If the value +of this expression is 0, the result is undefined. The following are examples +of the action of these procedures: + + ROR (10011101B, 1) returns a value of 11001110B + ROL (10011101B, 2) returns a value of 01110110B + + +12.5 SHR and SHL Procedures +--------------------------- + +These procedures shift bits off one end of the pattern and zeros move into the +pattern from the other end. The procedure type depends on the value of the +expression given as the actual parameter. (See Reference 1 or 2). + + +12.6 MOVE Procedure +------------------- + +The untyped procedure MOVE is used to transfer a set of contiguous bytes of +information from one location in memory to another. The form of the call is: + + CALL MOVE (count, source, destination) + +where "count", "source", and "destination" are expressions which, if +necessary, are converted to ADDRESS values. The source parameter is the memory +address to which this type is to be moved. Subsequent bytes are taken from +subsequent addresses following source, and moved to subsequent addresses +following destination. + + +12.7 TIME Procedure +------------------- + +(See Reference 1 or 2). + + +12.8 OUTPUT Array +----------------- + +This, and the remaining two items of this section, are predeclared variables. + +Each element corresponds to one of the 256 output ports of the 8080 CPU. + +A reference to OUTPUT must always be subscripted with a numeric constant in +the range 0 to 255, and may only appear as the left part of an assignment +statement or embedded assignment. (Anywhere else it is illegal.) The effect of +such an assignment is to latch the BYTE value of the expression on the right +side of the assignment into the specified output port. Since OUTPUT is a BYTE +array, the value of the expression will be automatically converted to type +BYTE, if necessary. + + +12.9 MEMORY Array +----------------- + +The PL/M-80 MEMORY array is not implemented. However, a memory management +suite of subroutines will be available from SCI. + + +12.10 STACKPTR Variable +----------------------- + +STACKPTR is a predeclared ADDRESS variable which provides access to the +Stack Pointer register. The current value of the Stack Pointer register will +be returned when STACKPTR is used on the right side of an assignment. For +example: + + R = STACKPTR + +Cautious use of STACKPTR on the left side of an assignment is recommended, +since taking control of the stack can confuse compile-time checks. The +Stack Pointer register will be set to the value provided. For example: + + STACKPTR = .STACK (LENGTH (STACK)) + + +Section 13: Features Involving Hardware Flags +--------------------------------------------- + +The PLMX features described in this section make use of hardware flags. The +programmer should use them with caution, however, since the exact sequence of +machine code produced from a sequence of PLMX source statements cannot be +predicted accurately. This uncertainty is caused by PLMX compiler optimization +of machine code. In addition, the setting and clearing of hardware flags vary +among microprocessors. + + +13.1 PLUS and MINUS Operators +----------------------------- + +The operators PLUS and MINUS perform similarly to + and - arithmetic +operators, and have the same precedence. However, they utilize the current +setting of the 8080 CPU hardware CARRY flag to perform the operation. + + +13.2 CARRY and ROTATION Procedures +---------------------------------- + +SCL and SCR are built-in procedures whose type depends on the parameter type. +They also utilize the current setting of the 8080 CPU hardware CARRY flag. +They are called by function references with the forms: + + SCL (pattern, count) + SCR (pattern, count) + +where "pattern" and "count" are both expressions. The value of count will be +converted, if necessary, to a BYTE quantity. If the value of count is zero, +the result is undefined. The value of the pattern may be either a BYTE value +or an ADDRESS value, and will not be converted. If it is a BYTE value, the +procedure will return a BYTE value. If it is an ADDRESS value, the procedure +will return an ADDRESS value. + +The value of the first parameter (pattern) is rotated left (by SCL) or right +(by SCR). The bit count is given by the second parameter (count). The rotation +includes the CARRY flag: the bit rotated off one end of the argument is +rotated into CARRY, and the old value of CARRY is rotated into the other end +of the argument. In effect, SCL and SCR perform 9-bit rotations on 8-bit +values, and 17-bit rotations on 16-bit values. + + +13.3 DEC Procedure +------------------ + +DEC is a built-in BYTE procedure which uses the value of the hardware CARRY +flag internally. It is called by a function reference with the form: + + DEC (expression) + +where the value of the expression will be converted, if necessary, to a BYTE +value. This procedure performs a decimal adjust operation on the actual +parameter value, and returns the result. + + +13.4 CARRY, SIGN, ZERO, and PARITY Procedures +--------------------------------------------- + +There are four built-in procedures that return the logical values of the +hardware flags. These procedures take no parameters, and are called by +function references with the forms: + + CARRY + ZERO + SIGN + PARITY + +The occurrence of one of these calls in an expression initiates a test of the +corresponding condition flag. If the flag is set (= 1), a value of 0FFH is +returned. If the flag is clear (= 0), a value of 00H is returned. + + +Section 14: Producing an Executable Object File +----------------------------------------------- + +PLMX produces an assembly language source file as its output. Refer to section +5 for the name of the output file. To produce an executable object file, the +output file must be assembled with MACRO-80, linked with all other relevant, +relocatable object files by LINK-80, and the linked program saved to disk, +either by LINK-80 or the CP/M 1.4 SAVE command. RLIB will almost always need +to be linked, and IOLIB will be required if any of its procedures are used. +IOLIB should precede RLIB when they are linked. Because RLIB and IOLIB are +libraries, the /S switch should be used with them, to search for and link only +those procedures which are required. The link program is then run by typing +its name. + +See reference 5 for details of the syntax and use of the Microsoft MACRO-80 +relocatable macro assembler, LINK-80 linker, LIB-80 library manager, and CREF- +80 cross-reference facility. + + +Appendix A: Command Line and Command Line Switches +-------------------------------------------------- + +A.1 Command Line +---------------- + +The PLMX command line, using an extended BNF notation, is as follows: + + PLMX [[]]CR + +where: + + ::= [.] + ::= ; + ::= + + + ::= A|L|I|M|O|C|S|F + ::= +|- + +Examples of valid PLMX command lines are: + + PLMX MYFILE ; M+L + + PLMX MYFILE.SRC; A- C+ + + PLMX YOURFILE; + + PLMX YOURFILE + +Examples of invalid PLMX command lines are: + + PLMXMYFILE + + PLMX MYFILE; +I + + PLMX ; M+L- + + +A.2 Command Line Switches +------------------------- + +Command line switches have the following meanings: + +Switch State Default Meaning +------ ----- ------- ------- + A + + Generate an assembly language file on the diskette on + which the source file resides. + + - Do not generate an assembly language file. + + L + + Generate a listing. Send it and error information to + the LST: device if the C switch is in its default + state; otherwise, send the listing to the CON: device. + + - Do not generate a listing. + + I + + Interleave source statements and assembly language + statements in the listing. + + - Print source statements only. + + M + - Make this module a Main Program module (see Ref 1, p. + 225). + + - Do not make this module a Main Program module. + + O + + Optimize assembly language output, i.e., register + analysis and peephole optimization. + + - Do not optimize. + + S + + Optimize for minimum space, i.e., replace in-line code + with CALLs whenever possible. + + - Optimize for speed, i.e., do not use CALLs. + + C + - Send the listing to the CON: device. + + - Send the listing to the LST: device. + + F + - Perform a "fast" compilation. Check for syntax errors, + but do not optimize or produce an output file. + + - Perform a normal compilation. + + +If no CP/M file type is supplied, the default is "SRC". This applies to +included files as well. The absence of a compilation switch means that the +default condition is in effect for the duration of the compilation. + + +Appendix B: Semantic Errors of PLMX +----------------------------------- + +Error Meaning +----- ------- + 1 An EXTERNAL or PUBLIC factored label declaration which is not at the + outermost level. + + 2 An EXTERNAL or PUBLIC unfactored label declaration which is not at the + outermost level. + + 3 An implicit dimension without an initialization. + + 4 A PUBLIC or EXTERNAL variable is declared to be BASED. + + 5 An undefined base specifier in a declaration. The base specifier + should be or .. + + 6 An EXTERNAL or PUBLIC variable declaration which is not at the + outermost level. + + 7 The first in a restricted reference is undefined in a + declaration. + + 8 An undefined restricted reference in a declaration. + + 9 A declaration has a reference to an undefined name in a locator. + + 10 A declaration has a reference to an EXTERNAL name in a locator. + + 11 A variable declaration with a locator is declared EXTERNAL. + + 12 Array declaration error. + + 13 An EXTERNAL procedure is not declared at the outermost level. + + 14 There are undeclared formal parameters in a procedure declaration. + + 15 There is an undefined name in a procedure call. + + 16 There is an illegal argument to LENGTH, LAST, or SIZE built-in + procedures. + + 17 There is an undefined name in a procedure call. + + 18 The number of formal parameters does not match the number of real + parameters in a procedure call. + + 19 The same as 16. + + 20 A RETURN statement without an argument is encountered outside of a + procedure. + + 21 There is no argument to a RETURN statement within a typed procedure. + + 22 A RETURN statement with an argument is outside of a procedure. + + 23 A RETURN statement with an argument is in an untyped procedure. + + 24 The name following an END statement is not the same as the name + preceding the DO statement. + + 25 An undefined function reference (without parameters). + + 26 A procedure referenced in a function call (without parameters) is not + typed. + + 27 System error. + + 28 An undefined function reference (with parameters). + + 29 The procedure referenced in a function call (with parameters) is not + typed. + + 30 System error. + + 31 The number of formal parameters does not match the number of real + parameters in a function call. + + 32 The same as 16. + + 33 An undefined subscripted structure reference. + + 34 An undefined unsubscripted structure reference. + + 35 An undefined subscripted variable reference. + + 36 A function reference having one real parameter references a procedure + which is untyped. + + 37 The same as 16. + + 38 An undefined unsubscripted variable reference. + + 39 An undefined simple variable in the index part of an iterative DO + statement. + + 40 An EXTERNAL variable occurs in an INITIAL statement. + + 41 A BASED variable occurs in an INITIAL statement. + + 42 An undefined structure reference occurs in a BASED variable + declaration. + + 43 An undefined structure reference. + + 44 An undefined procedure or function reference with parameters. + + 45 The argument to the INPUT function is not an integer. + + 46 The argument to the OUTPUT array is not an integer. + + 47 A variable or macro is defined twice at the same nesting level. + + 48 A procedure is defined twice at the same nesting level. + + 49 A function which requires more than one argument has been called with + one argument. + + 50 A function reference appears on the left-hand side of an assignment + statement. + + +Appendix C: System Error Procedure +---------------------------------- + +If a system error message is printed by the PLMX compiler, the following steps +should be taken. Review your source program for illegal syntax which may have +escaped diagnostic detection. If the source program is syntactically correct, +send a letter to SCI describing the circumstances under which the system error +was encountered. Include with the letter a listing of the program which was +being compiled when the system error occurred and, if possible, send a disk +with the source file of the program which was being compiled. + +If a PLMX compiler error is found, SCI will return an updated PLMX compiler in +accordance with our warranty. + + +Appendix D: I/O Procedures +-------------------------- + +A library of I/O procedures is supplied with the PLMX compiler. These external +procedures provide a link to the Basic I/O Facilities and Disk Access +Primitives of CP/M 1.4. Additionally, there are procedures to do line-oriented +I/O to non-disk peripherals, procedures to do character- and line-oriented I/O +to the disk, and utility routines to convert numbers between ASCII and binary +representations. + + +D.1 CP/M System-Level Procedures +-------------------------------- + +All of the CP/M 1.4 basic I/O facilities and disk access primitives are +provided, with the exception of the Interrogate Allocation primitive. The +procedures are presented below by CP/M function number. In the typical call +examples, "A" is an ADDRESS variable and "B" is a BYTE variable. See reference +4 for descriptions of the entry parameters and returned values. + +CP/M Function Number Typical Call +-------------------- ------------ + 0 ---- + 1 B = RD$CON; + 2 CALL WR$CON (B); + 3 B = RD$RDR; + 4 CALL PUNCH (B); + 5 CALL PRINT (B); + 6 ---- + 7 B = G$STAT; + 8 CALL S$STAT (B); + 9 CALL PR$BUF (A); + 10 CALL RD$BUF (A); + 11 B = CN$RDY; + 12 CALL LFT$HD; + 13 CALL INIT; + 14 CALL LOGIN (B); + 15 B = OPEN (A); + 16 B = CLOSE (A); + 17 B = SRCH (A); + 18 B = SR$NXT (A); + 19 CALL DLETE (A); + 20 B = RD$DSK (A); + 21 B = WR$DSK (A); + 22 B = MAKE (A); + 23 B = RNAME (A); + 24 B = LG$VEC; + 25 B = DRIVE; + 26 CALL STDMA (A); + + +D.2 Read and Write Line Procedures +---------------------------------- + +Two procedures are provided for reading and writing lines for non-disk +devices. All arguments to both procedures are ADDRESS parameters. + + +D.2.1 Procedure READ +-------------------- + +This procedure reads a line of characters. + +Arguments are: + + 1. Function: + 0 means read from the CON: device; + 1 means read from the RDR: device. + + 2. Destination buffer address. + + 3. Maximum number of bytes to read. + + 4. Address of the actual number of bytes read. + + 5. Address of the status word. + +The status returned is 00H if no error occurred, and 0FFH if an illegal +function number was given or an error occurred. Procedure READ stops reading +when either of two conditions is met: + + 1. The number of characters read equals the number specified by argument + 3. + + 2. A Carriage-Return is read. In this case, the Carriage-Return and a + Line-Feed are placed in the read buffer, and a Line-Feed is echoed if + the function number is 0. + +Procedure READ does not check for destination buffer overflow. + +The following is an example of the declaration and use of procedure READ: + + READ: + PROCEDURE (FUNCTION, BUFFER, COUNT, ACTUAL, STATUS) EXTERNAL; + DECLARE (FUNCTION, BUFFER, COUNT, ACTUAL, STATUS) ADDRESS; + END READ; + + DECLARE STRING (128) BYTE; + DECLARE (COUNT, STATUS) ADDRESS; + + ---- + ---- + + CALL READ (0, .STRING, 128, .COUNT, .STATUS); + + +D.2.2 Procedure WRITE +--------------------- + +This procedure writes a line of characters. + +Arguments are: + + 1. Function: + 0 means write to the CON: device; + 1 means write to the LST: device; + 2 means write to the PUN: device. + + 2. Source buffer address. + + 3. Number of bytes to write. + + 4. Address of the status word. + +The following is an example of the declaration and use of procedure WRITE: + + WRITE: + PROCEDURE (FUNCTION, BUFFER, COUNT, STATUS) EXTERNAL; + DECLARE (FUNCTION, BUFFER, COUNT, STATUS) ADDRESS; + END WRITE; + + DECLARE BUFFER (128) BYTE; + DECLARE STATUS ADDRESS; + + ---- + ---- + + CALL WRITE (0, .BUFFER, 2, .STATUS); + + +D.3 Disk I/O Procedures +----------------------- + +Disk I/O procedures are provided for character-oriented reading and writing, +line-oriented reading and writing, file opening, and file closing. + +There are several arguments which are common to the disk I/O procedures and +which are required by CP/M. All the procedures in this section require the +address of the File Control Block. The FCB address must be initialized in a +declaration. Examples are provided with each procedure in this section. See +section 3.2 of reference 4 for more information on the File Control Block. + +Another argument required by most of the procedures in this section is the +address of the DMA buffer. The DMA buffer is a BYTE array of 128 bytes used by +the CP/M disk access primitives for transferring a sector at a time from and +to disk. Examples of the declaration of the DMA buffer occur with each +procedure in this section which requires it as an argument. + +A third argument common to many of the procedures in this section is the +number of bytes remaining in the DMA buffer. This variable is maintained by +the procedures in this section, and should never be altered by user programs. + +A fourth argument common to all these procedures in this section is the +address of the status word. The status word is an output parameter which +should be tested after a procedure is CALLed. The information returned in this +status word is described with each procedure. + +All the arguments of the procedures in this section are ADDRESS parameters. +Parameters whose addresses are passed must be the same type as shown in the +examples associated with each function below. In argument descriptions, the +term "word" refers to an ADDRESS identifier. + + +D.3.1 Procedure DRCHR +--------------------- + +This procedure reads a character from a disk file. The first CALL to DRCHR +must be preceded by a CALL to procedure OPENR (see D.3.5). The last CALL to +DRCHR must be followed by a CALL to procedure CLOSR (see D.3.6). + +Arguments are: + + 1. File Control Block address. + + 2. CP/M DMA buffer address. + + 3. Address of the number of bytes in the DMA buffer. + + 4. Address at which the byte is to be stored. + + 5. Address of the status word. + +The character is returned to the address specified in argument 4. If the end- +of-file (EOF) is encountered, a Control-Z (1AH) is returned. The status +returned is 00H if no error occurred and the EOF was not encountered; 01H if +no error occurred and the EOF was encountered; and 0FFH if an error occurred. +The message "READ ERROR" is printed at the console if an error occurred. + +The following is an example of the declaration and use of procedure DRCHR: + + DRCHR: + PROCEDURE (FCB, SECTOR$BUFFER, SECTOR$COUNT, CHAR, STATUS) EXTERNAL; + DECLARE (FCB, SECTOR$BUFFER, SECTOR$COUNT, CHAR, STATUS) ADDRESS; + END DRCHR; + + DECLARE (SCNT, DSTAT) ADDRESS; + DECLARE RFCB (33) BYTE INITIAL (0, 'INDEXS ', 'TXT') ; + DECLARE SBUFF (128) BYTE; + DECLARE CHR BYTE; + + ---- + ---- + + CALL DRCHR (.RFCB, .SBUFF, .SCNT, .CHR, .DSTAT); + + +D.3.2 Procedure DWCHR +--------------------- + +This procedure writes a byte to a disk file. The first CALL to DWCHR must be +preceded by a CALL to procedure OPENW (see D.3.7). The last CALL to DWCHR must +be followed by a CALL to procedure CLOSW (see D.3.8) or the last sector will +not be written to disk. + +Arguments are: + + 1. File Control Block address. + + 2. CP/M DMA buffer address. + + 3. Address of the number of bytes in the DMA buffer. + + 4. Address at which the byte to be written is stored. + + 5. Address of the status word. + +The status returned is 00H if no error occurred, or 0FFH if a write error +occurred. The message "WRITE ERROR" is printed at the console if a write error +occurred. + +The following is an example of the declaration and use of procedure DWCHR: + + DWCHR: + PROCEDURE (FCB, SECTOR$BUFFER, SECTOR$COUNT, CHAR, STATUS) EXTERNAL; + DECLARE (FCB, SECTOR$BUFFER, SECTOR$COUNT, CHAR, STATUS) ADDRESS; + END DWCHR; + + DECLARE (SCNT, DSTAT) ADDRESS; + DECLARE WFCB (33) BYTE INITIAL (0, 'OUTFILE ', 'TXT'); + DECLARE SBUFF (128) BYTE; + DECLARE CHR BYTE; + + ---- + ---- + + CALL DWCHR (.WFCB, .SBUFF, .SCNT, .CHR, .DSTAT); + + +D.3.3 Procedure DRLIN +--------------------- + +This procedure reads a line from the disk. The first CALL to DRLIN must be +preceded by a CALL to OPENR (see D.3.5). The last CALL to DRLIN must be +followed by a CALL to CLOSR (see D.3.6). + +Arguments are: + + 1. File Control Block address. + + 2. CP/M DMA buffer address. + + 3. Address of the number of bytes in the DMA buffer. + + 4. Address of the buffer into which the line is to be placed. + + 5. Address of the count of bytes transferred to the input buffer. + + 6. Address of the status word. + +Characters are transferred from the disk file to the input buffer until a +Line-Feed is encountered. No check is made for input buffer overflow. The +status returned is the same as for procedure DRCHR. Procedure DRLIN prints the +message "READ ERROR" at the console if an error occurs. + +The following is an example of the declaration and use of procedure DRLIN: + + DRLIN: + PROCEDURE (FCB, SECTOR$BUFFER, SECTOR$COUNT, BUFFER, COUNT, + STATUS) EXTERNAL; + DECLARE (FCB, SECTOR$BUFFER, SECTOR$COUNT, BUFFER, COUNT, + STATUS) ADDRESS; + END DRLIN; + + DECLARE RFCB (33) BYTE INITIAL (0, 'INDEXS ', 'TXT'); + DECLARE (SBUFF, TEXT) (128) BYTE; + DECLARE (SCNT, COUNT, DSTAT) ADDRESS; + + ---- + ---- + + CALL DRLIN (.RFCB, .SBUFF, .SCNT, .TEXT., .COUNT, .DSTAT); + + +D.3.4 Procedure DWLIN +--------------------- + +This procedure writes a line to a disk file. The first CALL to procedure DWLIN +must be preceded by a CALL to procedure OPENW (see D.3.6). The last CALL to +procedure DWLIN must be followed by a CALL to procedure CLOSW (see D.3.7) or +the last sector will not be written to disk. + +Arguments are: + + 1. File Control Block address. + + 2. CP/M DMA buffer address. + + 3. Address of the number of bytes in the DMA buffer. + + 4. Address of the buffer from which the line is to be taken. + + 5. Count of bytes to be written to the disk file. + + 6. Address of the status word. + +The status returned and the error message printed at the console are the same +as for procedure DWCHR (see D.3.2). + +The following is an example of the declaration and use of procedure DWLIN: + + DWLIN: + PROCEDURE (FCB, SECTOR$BUFFER, SECTOR$COUNT, BUFFER, COUNT, + STATUS) EXTERNAL; + DECLARE (FCB, SECTOR$BUFFER, SECTOR$COUNT, BUFFER, COUNT, + STATUS) ADDRESS; + END DWLIN; + + DECLARE WFCB (33) BYTE INITIAL (0, 'QFILE ', 'XY '); + DECLARE (SBUFF, TEXT) (128) BYTE; + DECLARE (SCNT, COUNT, DSTAT) ADDRESS; + + ---- + ---- + + CALL DWLIN (.WFCB, .SBUFF, .SCNT, .TEXT., .COUNT, .DSTAT); + + +D.3.5 Procedure OPENR +--------------------- + +This procedure opens a disk file for reading. Procedure OPENR initializes the +last 21 bytes of the File Control Block to zeroes, and initializes the count +of bytes in the DMA buffer to 0. This procedure does not read the first sector +into the DMA buffer. + +Arguments are: + + 1. File Control Block address. + + 2. Address of the number of bytes in the CP/M DMA buffer. + + 3. Address of the status word. + +The following is an example of the declaration and use of procedure OPENR: + + OPENR: + PROCEDURE (FCB, SECTOR$COUNT, STATUS) EXTERNAL; + DECLARE (FCB, SECTOR$COUNT, STATUS) ADDRESS; + END OPENR; + + DECLARE RFCB (33) BYTE INITIAL (0, 'INDEXS ', 'TXT'); + DECLARE (SCNT, DSTAT) ADDRESS; + + ---- + ---- + + CALL OPENR (.RFCB, .SCNT, .DSTAT); + + +D.3.6 Procedure CLOSR +--------------------- + +This procedure closes a file used for disk reading. A file must be closed if +it is to be re-read. The file is closed and a status of 00H is returned if no +error occurred; otherwise, a status of 0FFH is returned. + +Arguments are: + + 1. File Control Block address. + + 2. Address of the status word. + +The following is an example of the declaration and use of procedure CLOSR: + + CLOSR: + PROCEDURE (FCB, STATUS) EXTERNAL; + DECLARE (FCB, STATUS) ADDRESS; + END CLOSR; + + DECLARE RFCB (33) BYTE INITIAL (0, 'INDEXS ', 'TXT'); + DECLARE DSTAT ADDRESS; + + ---- + ---- + + CALL CLOSR (.RFCB, .DSTAT); + + +D.3.7 Procedure OPENW +--------------------- + +This procedure opens a file to be used for output. + +Arguments are: + + 1. File Control Block address. + + 2. Address of the number of bytes in the CP/M DMA buffer. + + 3. Address of the status word. + +Procedure OPENW must be CALLed before any CALLs to procedures DWCHR or DWLIN +are made. Files of the same name as the file being opened will be erased. The +status returned is 00H if no error occurred; otherwise, 0FFH. The last 21 +bytes of the File Control Block are initialized to zeroes and the count of +bytes in the DMA buffer is initialized to 0. This procedure does not read the +first sector into the DMA buffer. + +The following is an example of the declaration and use of procedure OPENW: + + OPENW: + PROCEDURE (FCB, SECTOR$COUNT, STATUS) EXTERNAL; + DECLARE (FCB, SECTOR$COUNT, STATUS) ADDRESS; + END OPEN; + + DECLARE WFCB (33) BYTE INITIAL (0, 'QFILE ', 'XY '); + DECLARE (SCNT, DSTAT) ADDRESS; + + ---- + ---- + + CALL OPENW (.WFCB, .SCNT, .DSTAT); + + +D.3.8 Procedure CLOSW +--------------------- + +This procedure closes a file used for output. + +Arguments are: + + 1. File Control Block address. + + 2. CP/M DMA buffer address. + + 3. Address of the number of bytes in the DMA buffer. + + 4. Address of the status word. + +Procedure CLOSW writes the last sector to the disk file, and closes the file. +The last sector is padded with Control-Zs (1AH, CP/M's End-Of-File indicator). +If the last sector contains 128 bytes prior to padding, an additional sector +full of Control-Zs (1AHs) is not written. The status returned is 00H if no +error occurred; otherwise, 0FFH. + +The following is an example of the declaration and use of procedure CLOSW: + + CLOSW: + PROCEDURE (FCB, SECTOR$BUFFER, SECTOR$COUNT, STATUS) EXTERNAL; + DECLARE (FCB, SECTOR$BUFFER, SECTOR$COUNT, STATUS) ADDRESS; + END CLOSW; + + DECLARE WFCB (33) BYTE INITIAL (0, 'RECORD ', 'ISM'); + DECLARE SBUFF (128) BYTE; + DECLARE (SCNT, DSTAT) ADDRESS; + + ---- + ---- + + CALL CLOSW (.WFCB, .SBUFF, .SCNT, .DSTAT); + + +D.4 Other Procedures +-------------------- + +D.4.1 Procedure NUMIN +--------------------- + +This procedure converts a number in ASCII string form into a 16-bit unsigned +binary number. + +Argument: The address of the pointer to the buffer area which contains the +ASCII string. + +See reference 1, page 147 for details of this procedure. + +The following is an example of the declaration and use of procedure NUMIN: + + NUMIN: + PROCEDURE (BUFFER) ADDRESS EXTERNAL; + DECLARE BUFFER ADDRESS; + END NUMIN; + + DECLARE BUFFER (128) BYTE; + DECLARE BUFFPTR ADDRESS; + DECLARE N ADDRESS; + + ---- + ---- + + BUFFPTR = .BUFFER; + N = NUMIN (.BUFFPTR); + + +D.4.2 Procedure NMOUT +--------------------- + +This procedure converts a 16-bit unsigned binary number into an ASCII string. + +Arguments are: + + 1. Number whose printable representation is desired. + + 2. Integer between 2 and 16 inclusive, specifying the base in which the + first argument is to be interpreted. + + 3. ASCII character to be used as leading character(s) in the printable + representation, e.g., '0', ' ', 0 or 00H (ASCII NUL). + + 4. Address of a buffer into which the printable representation is to be + placed. + + 5. Number of characters desired in the printable representation. The + buffer of argument 4 must be large enough to contain this many + characters. + +See reference 1, page 143 for details of this procedure. + +The following is an example of the declaration and use of procedure NMOUT: + + NMOUT: + PROCEDURE (VALUE, BASE, LC, BUFFADR, WIDTH) EXTERNAL; + DECLARE (VALUE, BUFFADR) ADDRESS; + DECLARE (BASE, LC, WIDTH) BYTE; + END NMOUT; + + DECLARE BUFFER (128) BYTE; + DECLARE ROOT ADDRESS; + + ---- + ---- + + CALL NMOUT (ROOT, 10, ' ', .BUFFER, 5); + + +Appendix E: Sample Output +------------------------- + +This section contains the input and output file listings for a PLMX program +which computes the average of an array of 10 numbers. + + +E.a The source file listing +---------------------------- + +/***********************************************************/ +/* A PROGRAM TO FIND THE MEAN OF THE 10 VALUES OF AN ARRAY */ +/***********************************************************/ + + +MEAN$VAL: +DO; + + DECLARE X (10) BYTE DATA (23,2,18,0,20,14,45,27,8,33); + DECLARE SUM ADDRESS; + DECLARE (MEAN, I) BYTE; + + SUM = 0; + I = 0; + DO WHILE I <= 9; + SUM = SUM + X (I); + I = I + 1; + END; + MEAN = SUM / 10; + +END MEAN$VAL; + + + + +E.b The output file listing +--------------------------- + + TITLE MEANV + NAME ('MEANV') + +MEANV:: + EXTRN INIT@ + PUBLIC AAAAB@,AAAAA@ + +AAAAA@: + LXI H,$+6 + JMP INIT@ +AAAAB@: +; +;/***********************************************************/ +;/* A PROGRAM TO FIND THE MEAN OF THE 10 VALUES OF AN ARRAY */ +;/***********************************************************/ +; +;MEAN$VAL: +; +;DO; +; +; +; DECLARE X (10) BYTE DATA (23,2,18,0,20,14,45,27,8,33); +; +; DECLARE SUM ADDRESS; +; +; DECLARE (MEAN, I) BYTE; +; +; +; SUM = 0; + LXI H,0H +; +; I = 0; + SHLD A0003 + MVI A,0H +; +; DO WHILE I <= 9; + STA A0005 +G0007: + MVI L,09H + LDA A0005 + EXTRN BP36@ + CALL BP36@ +; +; SUM = SUM + X (I); + RRC + JNC G0008 + LHLD A0005 + MVI H,0 + XCHG + LXI H,A0001 + DAD D + MOV A,M + LHLD A0003 + EXTRN BP57@ + CALL BP57@ +; +; I = I + 1; + SHLD A0003 + MVI L,01H + LDA A0005 + EXTRN BP25@ + CALL BP25@ +; +; END; + STA A0005 + JMP G0007 +; +; MEAN = SUM / 10; +G0008: + MVI A,0AH + LHLD A0003 + EXTRN BP71@ + CALL BP71@ + SHLD T0009 + LDA T0009 +; +; +;END MEAN$VAL; + STA A0004 + EXTRN EXIT@ +SCAT@: + CALL EXIT@ +A0001: + DB 017H + DB 02H + DB 012H + DB 0H + DB 014H + DB 0EH + DB 02DH + DB 01BH + DB 08H + DB 021H + DSEG +A0003: + DS 02H +A0004: + DS 01H +A0005: + DS 01H +T0006: + DS 01H +T0009: + DS 02H + END AAAAA@ + + +Appendix F: IOCLD.SRC Listing +----------------------------- + +/* + Following is a total list of I/O procedures available to the + PLMX user. Refer to Digital Research "CP/M Interface Guide" + for a description of CP/M 1.4 system level procedures. Refer to + the "PLMX User's Guide" for a description of all other procedures. + It is suggested that the user extract those procedures which are + applicable to his application, possibly putting them in an INCLUDE + file. +*/ + +/* CP/M system level procedures */ + +RD$CON: +PROCEDURE BYTE EXTERNAL; +END RD$CON; + +WR$CON: +PROCEDURE (CHAR) EXTERNAL; + DECLARE CHAR BYTE; +END WR$CON; + +RD$RDR: +PROCEDURE BYTE EXTERNAL; +END RD$RDR; + +PUNCH: +PROCEDURE (CHAR) EXTERNAL; + DECLARE CHAR BYTE; +END PUNCH; + +PRINT: +PROCEDURE (CHAR) EXTERNAL; + DECLARE CHAR BYTE; +END PRINT; + +G$STAT: +PROCEDURE BYTE EXTERNAL; +END G$STAT; + +S$STAT: +PROCEDURE (STAT) EXTERNAL; + DECLARE STAT BYTE; +END S$STAT; + +PR$BUF: +PROCEDURE (ADRS) EXTERNAL; + DECLARE ADRS ADDRESS; +END PR$BUF; + +RD$BUF: +PROCEDURE (BUF) ADDRESS EXTERNAL; + DECLARE BUF BYTE; +END RD$BUF; + +CN$RDY: +PROCEDURE BYTE EXTERNAL; +END CN$RDY; + +LFT$HD: +PROCEDURE EXTERNAL; +END LFT$HD; + +INIT: +PROCEDURE EXTERNAL; +END INIT; + +LOGIN: +PROCEDURE (DSK) EXTERNAL; + DECLARE DSK BYTE; +END LOGIN; + +OPEN: +PROCEDURE (FCB) BYTE EXTERNAL; + DECLARE FCB BYTE; +END OPEN; + +CLOSE: +PROCEDURE (FCB) BYTE EXTERNAL; + DECLARE FCB BYTE; +END CLOSE; + +SERCH: +PROCEDURE (FCB) BYTE EXTERNAL; + DECLARE FCB BYTE; +END SERCH; + +SR$NXT: +PROCEDURE (FCB) BYTE EXTERNAL; + DECLARE FCB BYTE; +END SR$NXT; + +DLETE: +PROCEDURE EXTERNAL; +END DLETE; + +RD$DSK: +PROCEDURE (FCB) BYTE EXTERNAL; + DECLARE FCB ADDRESS; +END RD$DSK; + +WR$DSK: +PROCEDURE (FCB) BYTE EXTERNAL; + DECLARE FCB ADDRESS; +END WR$DSK; + +MAKE: +PROCEDURE (FCB) BYTE EXTERNAL; + DECLARE FCB ADDRESS; +END MAKE; + +RNAME: +PROCEDURE (FCB) ADDRESS EXTERNAL; + DECLARE FCB ADDRESS; +END RNAME; + +RL$VEC: +PROCEDURE BYTE EXTERNAL; +END RL$VEC; + +DRIVE: +PROCEDURE BYTE EXTERNAL; +END DRIVE; + +STDMA: +PROCEDURE (BUF) EXTERNAL; + DECLARE BUF ADDRESS; +END STDMA; + + +/* PLMX read and write line procedures */ + +READ: +PROCEDURE (FUNCTION, BUFFER, COUNT, ACTUAL, STATUS) EXTERNAL; + DECLARE (FUNCTION, BUFFER, COUNT, ACTUAL, STATUS) ADDRESS; +END READ; + +WRITE: +PROCEDURE (FUNCTION, BUFFER, COUNT, STATUS) EXTERNAL; + DECLARE (FUNCTION, BUFFER, COUNT, STATUS) ADDRESS; +END WRITE; + + +/* Disk I/O procedures */ + +DRCHR: +PROCEDURE (FCB, SEC$BUFFER, SEC$COUNT, CHAR, STATUS) EXTERNAL; + DECLARE (FCB, SEC$BUFFER, SEC$COUNT, CHAR, STATUS) ADDRESS; +END DRCHR; + +DWCHR: +PROCEDURE (FCB, SEC$BUFFER, SEC$COUNT, CHAR, STATUS) EXTERNAL; + DECLARE (FCB, SEC$BUFFER, SEC$COUNT, CHAR, STATUS) ADDRESS; +END DWCHR; + +DRLIN: +PROCEDURE (FCB, SEC$BUF, SEC$CNT, BUFFER, COUNT, STATUS) EXTERNAL; + DECLARE (FCB, SEC$BUF, SEC$CNT, BUFFER, COUNT, STATUS) ADDRESS; +END DRLIN; + +DWLIN: +PROCEDURE (FCB, SEC$BUF, SEC$COUNT, BUFFER, COUNT, STATUS) EXTERNAL; + DECLARE (FCB, SEC$BUF, SEC$COUNT, BUFFER, COUNT, STATUS) ADDRESS; +END DWLIN; + +OPENR: +PROCEDURE (FCB, SEC$COUNT, STATUS) EXTERNAL; + DECLARE (FCB, SEC$COUNT, STATUS) ADDRESS; +END OPENR; + +CLOSR: +PROCEDURE (FCB, STATUS) EXTERNAL; + DECLARE (FCB, STATUS) ADDRESS; +END CLOSR; + +OPENW: +PROCEDURE (FCB, SEC$COUNT, STATUS) EXTERNAL; + DECLARE (FCB, SEC$COUNT, STATUS) ADDRESS; +END OPENW; + +CLOSW: +PROCEDURE (FCB, SEC$BUF, SEC$COUNT, STATUS) EXTERNAL; + DECLARE (FCB, SEC$BUF, SEC$COUNT, STATUS) ADDRESS; +END CLOSW; + +/* Other procedures */ + +NUMIN: /* Convert ASCII number to 16-bit unsigned binary */ +PROCEDURE (BUFFER) ADDRESS EXTERNAL; + DECLARE BUFFER ADDRESS; +END NUMIN; + +NMOUT: /* Convert 16-bit unsigned binary number to ASCII string */ +PROCEDURE (VALUE, BASE, LC, BUFFADR, WIDTH) EXTERNAL; + DECLARE (VALUE, BUFFADR) ADDRESS; + DECLARE (BASE, LC, WIDTH) BYTE; +END NMOUT; + + +Appendix G: PLMX Advertisements +------------------------------- + +- "PLMX communicates with all 8/16-bit micros" + "IEEE Micro", February 1981, p.106 + +PLMX, a universal high-level language for microprocessors, generates code for +any 8- or 16-bit device. Designed for use in microcomputer product development +and real-time process control, it is priced at half the cost of PL/M and other +non-universal microprocessor software packages, according to its developer, +System Consultants, Inc. + +PLMX takes PL/M to its logical conclusion, says the company. PL/M, originally +derived from PL/1, is used only on 8080- or 8086-based systems. Other +versions, such as PL/Z for the Z-80 and PL/65 for the 6500, are used only with +those processors. PLMX combines the features of PL/M with universality, +allowing users to employ new microprocessor architectures without having to +develop new software for them. + +PLMX's syntax is identical to PL/M's, which means that the entire library of +existing PL/M programs can be compiled under PLMX. Hence, PL/M programs may be +used on microprocessors other than the 8080, via the PLMX compiler. + +Currently, the PLMX compiler runs under the CP/M 1.4 and Tektronix TEKDOS +Operating Systems. Interfaces to other operating systems will be available +during 1981. In addition, PLMX is a true compiler, not an interpretive +compiler such as BASIC or Pascal in some of their current implementations. +Since an interpreter must be resident in ROM for execution of programs, and +thus must have a considerable amount of memory space, its usefulness in +developing ROM-based products is limited. The programs compiled by PLMX, +however, run an average of 15 times faster than those on an interpreter, since +at run time the programs are already in memory in executable form. This, says +Systems Consultants, makes PLMX appropriate for real-time applications. + +With no arbitrary formatting rules or line numbers, PLMX source statements +resemble simple English declarations, and follow a well-defined logic +structure. The source text can contain comments anywhere, except within +reserved words, identifier names, and numbers. + +PLMX is priced at $1000; an eight-inch compiler diskette and instruction +manuals are included. Additional copies for the same microprocessor type are +substantially discounted. PLMX is available for immediate delivery, with +program development support and other engineering services also available. + + +- "Microprocessor-Independent Program Library" + The *unique* cross-compiler for microprocessor independence + "IEEE Micro", Vol.2, No.4, Oct/Dec 1982, p.8 + +With PLMX, you are no longer restricted to any one microprocessor. PLMX is a +flexible cross-compiler that generates code for the 8080/8085, Z-80, 1802, +6800/6802/6809, and 9900 microprocessors, and executes under TEKDOS (*), +DOS/50 (*), CP/M (**), and CP/M-derivative Operating Systems. This flexibility +enables you to convert your existing PL/M libraries into a Microprocessor- +Independent Program Library. + +PLMX implements the structured syntax of PL/M, and produces assembly language +source files which can be assembled for ROM-based applications. + +And PLMX offers the features you are looking for in a software development +tool: portability, better program organization, more efficient management of +large programming jobs, and savings in programming time and money. Protect +your software investment, contact Roger Carlson - TODAY. He will tell you all +about PLMX. + +SYSCON Corporation +4015 hancock Street +San Diego +CA 92110 + +* = TEKDOS and DOS/50 are trademarks of Tektronix, Inc. +** = CP/M is a trademark of Digital Research, Inc. + + +Appendix H: ROCHE Addenda +------------------------- + +The "PL/M-80 Programming Manual" (1980) is available on the BitSavers Web +server. However, due to its success, this server is often overwhelmed by +demand. So, if you cannot access it, try one of its multiple mirrors. Then, +search for the "Intel" directory. The manual is in the "PLM" directory. + +A few short PL/M programs are available at the same address, in the "insite" +directory. Open one of the two 600-pages catalogues, then search for any small +PL/M program that were incorporated in the catalogues. (There is even a "Game +of Life"!) + +The PLMX "distribution disk" (except IOCLD.SRC?) is available at: + +http://z80cpu.eu/archive/rlee/S/SYSTEM%20CONSULTANTS/PLMX/ + +The "PLMX User's Guide" is pretty small... For example, my "Mallard BASIC +Introduction and Reference" manual, explaining a 30KB interpreter, is 300- +pages long! (Ten pages per kilobyte.) The PLMX Compiler is 85KB (the minimum +to run it), yet its manual is... 24-pages long! Obviously, Roger Carlson +expects its user to be pretty "familiar" about PL/M and CP/M... + +For the sake of Internet "Newbies", I decided to at least show them how to +generate a CP/M COMmand file (even if PLMX is designed to produce "modules" to +be put in a "library" and retrieved by a linker). + +So, I went to my Old Faithful Epson QX-10... which did not boot?!? Since there +was no time to tinker with hardware, I decided to use an IBM Clown. Since I +wanted to show what was happening, I needed to redirect the screen output into +a file. Under MS-DOS, this is tricky: you need to type the command blindly +(!). So, CP/M(-86) Plus to the rescue! With CP/M Plus, I can have an unplanned +session at the console, redirecting the screen output to a file. + +A>put console output to file plmx.asc [system] + +Since PLMX is an 8080 CP/M 1.4 program, we need an emulator to run it under +8086 CP/M 3.1. Me, I use Jim Lopushinsky's Z80.CMD Version 1.3. + +A>z80 plmx.com mean ; C+L+ +Z80 CP/M-80 emulator for CP/M-86 vers 1.3 - 11/30/97 +Copyright (c) 1985-1997 Jim Lopushinsky +PLMX COMPILER VERSION 2.3 +COPYRIGHT (C) 1980, SYSTEMS CONSULTANTS, INC. + +(See Appendix E for the PLMX compiler output. The only reason why "C+L+" are +in uppercase is that, on my French keyboard, the "+" sign is uppercase. +Anyway, since this is a command line, the CCP translates it to uppercase.) + +END OF COMPILATION +000 ERROR(S) DETECTED + +PLMX produced a MAC file. So, we now use M80 to produce the REL file. (We +could use Digital Research's RMAC for 8080-only code (the one outputted by +this version of PLMX). The advantage of M80 is that only one assembler is +needed to generate code for the 8080 and the Z-80. The (big) drawback of M80 +is that one additional step (compared to ASM and MAC) is needed: linking of +the REL modules (you can load HEX files directly into the DDT or SID +debuggers). For the Newbies, the M80 syntax is: M80 REL,PRN=MAC. The shortest +form is: M80 =MAC. + +A>z80 m80.com mean,mean=mean +Z80 CP/M-80 emulator for CP/M-86 vers 1.3 - 11/30/97 +Copyright (c) 1985-1997 Jim Lopushinsky + +No Fatal error(s) + +Finally, we need to link the modules. As explained in the "PLMX User's Guide", +RLIB.REL contains the run-time library and IOLIB.REL contains the I/O +Procedures. Also, "IOLIB should precede RLIB when they are linked." Probably +the only advantage of using a Linker is that (with an option) it can retrieve +from the library only the modules needed (else, it includes everything). +(Roger Carlson do not mention it but, normally, you put your assembled +relocatable modules inside a "library".) + +For the Newbies, it could be possible to bypass the Linker, by using INCLUDE +files containing the full code of RLIB and IOLIB. Of course, there would be +some overhead, since all the routines would be included, even if you just +printed "Hello, World!". (A problem with the code of RLIB is that it contains +twice the BP67@ subroutine... So, no assembler can assemble correctly the run- +time library! This is another problem with Linkers: they do not remember which +modules they put inside a file! In this case, Roger Carlson linked *TWICE* +module BP67@... If he had used a single file to contain the source code of all +the run-time routines, the assembler would have complained about this doubly- +defined subroutine. As he was using a Linker, the Linker, not remembering +which modules were already inside the library, simply added twice the module, +with the same name and the same code... Do you understand, now, why I prefer +absolute macro-assemblers?) (XREF is also an indispensable tool, to verify +that no labels have been forgotten, once you have got the code right. Note +that XREF works only for single file... How do you cross-ref a library made of +73 modules?) + +A>z80 link.com mean,iolib[s],rlib[s] +Z80 CP/M-80 emulator for CP/M-86 vers 1.3 - 11/30/97 +Copyright (c) 1985-1997 Jim Lopushinsky +LINK 1.31 + +BP25@ 0171 BP36@ 0176 BP57@ 0157 BP71@ 019A +EXIT@ 016D MEANV 0100 BP41@ 017F BP42@ 0187 +BP43@ 018A BP44@ 018F BP45@ 0192 BP58@ 015A +BP59@ 015D BP60@ 0160 BP61@ 0163 INIT@ 0166 +BP87@ 01A3 BP88@ 01AC + +ABSOLUTE 0000 +CODE SIZE 00E2 (0100-01E1) +DATA SIZE 0007 (01E2-01E8) +COMMON SIZE 0000 +USE FACTOR 03 + +Now, for the Newbies, I will be obliged to include comments inside the +redirected output of SID. + +A>z80 sid.com +Z80 CP/M-80 emulator for CP/M-86 vers 1.3 - 11/30/97 +Copyright (c) 1985-1997 Jim Lopushinsky +CP/M 3 SID - Version 3.0 + +Since SID is a *symbolic* debugger, it allows us to debug using the name of +the labels of the program, instead of mere hexadecimal values. (Hence the +"SYMBOLS" message. The first "mean" is the COM file, the second "mean" is the +SYM file.) + +#emean,mean +SYMBOLS +NEXT MSZE PC END +0200 0200 0100 D46F + +First, let us have a look to the code produced. + +#d100,1FF +0100: 21 00 00 22 E2 01 3E 00 32 E5 01 2E 09 3A E5 01 !.."..>.2....:.. +0110: CD 76 01 0F D2 39 01 2A E5 01 26 00 EB 21 4D 01 .v...9.*..&..!M. +0120: 19 7E 2A E2 01 CD 57 01 22 E2 01 2E 01 3A E5 01 .~*...W."....:.. +0130: CD 71 01 32 E5 01 C3 0B 01 3E 0A 2A E2 01 CD 9A .q.2.....>.*.... +0140: 01 22 E7 01 3A E7 01 32 E4 01 CD 6D 01 17 02 12 ."..:..2...m.... +0150: 00 14 0E 2D 1B 08 21 C3 7F 01 C3 87 01 C3 8A 01 ...-..!......... +0160: C3 8F 01 C3 92 01 EB 2A 06 00 F9 EB E9 F3 C3 00 .......*........ +0170: 00 85 6F 26 00 C9 67 7D 94 9F 2F 6F 26 00 C9 85 ..o&..g}../o&... +0180: 6F 7C CE 00 67 7D C9 B5 6F C9 A5 6F 26 00 C9 AD o|..g}..o..o&... +0190: 6F C9 8D 6F 7C CE 00 67 7D C9 5F 16 00 EB CD A3 o..o|..g}._..... +01A0: 01 7D C9 EB 42 4B CD B4 01 EB 7D C9 EB 42 4B CD .}..BK....}..BK. +01B0: B4 01 7D C9 11 00 00 CD DA 01 EB 3E F0 F5 29 1F ..}........>..). +01C0: EB 29 EB D2 C7 01 23 17 DA D2 01 7D 81 7C 88 D2 .)....#....}.|.. +01D0: D4 01 09 13 F1 3C FA BD 01 C9 0B 79 2F 4F 78 2F .....<.....y/Ox/ +01E0: 47 C9 00 00 00 00 00 00 00 1A 1A 1A 1A 1A 1A 1A G............... +01F0: 1A 1A 1A 1A 1A 1A 1A 1A 1A 1A 1A 1A 1A 1A 1A 1A ................ + +Ok. 200h bytes = 1/2 kilobytes. Less than 512 bytes. (The "1A"s are the CP/M +End-Of-File characters.) Let us now see the names of the modules (compare them +with those mentioned by LINK-80 at the preceding step). + +#h +0171 BP25@ +0176 BP36@ +0157 BP57@ +019A BP71@ +016D EXIT@ +0100 MEANV +017F BP41@ +0187 BP42@ +018A BP43@ +018F BP44@ +0192 BP45@ +015A BP58@ +015D BP59@ +0160 BP60@ +0163 BP61@ +0166 INIT@ +01A3 BP87@ +01AC BP88@ + +Notice that one module is named MEANV... This is the name of the module. As +explained in the "PLMX User's Guide", there is an option to make a "Main +Program" module straight from a module, but we are not using it, here. I must +leave you some exercises to do... Ok. So, our COMmand file contains a MEANV +module: let us see what code was produced (compare with the listing of +Appendix E). (SID lists only 11 lines, to fill only half a screen of 24 +lines.) + +#l.meanv +MEANV: + 0100 LXI H,0000 + 0103 SHLD 01E2 + 0106 MVI A,00 + 0108 STA 01E5 + 010B MVI L,09 + 010D LDA 01E5 + 0110 CALL 0176 .BP36@ + 0113 RRC + 0114 JNC 0139 + 0117 LHLD 01E5 + 011A MVI H,00 +#l + 011C XCHG + 011D LXI H,014D + 0120 DAD D + 0121 MOV A,M + 0122 LHLD 01E2 + 0125 CALL 0157 .BP57@ + 0128 SHLD 01E2 + 012B MVI L,01 + 012D LDA 01E5 + 0130 CALL 0171 .BP25@ + 0133 STA 01E5 +#l + 0136 JMP 010B + 0139 MVI A,0A + 013B LHLD 01E2 + 013E CALL 019A .BP71@ + 0141 SHLD 01E7 + 0144 LDA 01E7 + 0147 STA 01E4 + 014A CALL 016D .EXIT@ + 014D RAL + 014E STAX B + 014F STAX D + +Stop! This code contains a "CALL EXIT@"... And, just before EXITing, it stores +a value inside a byte. So, 2 questions: what is the value of this byte, and +what is the code of EXIT? (I leave it to you the question of the purposes of +the various BP??@ run-time routines...) + +#d1E4,1E5 +01E4: 00 00 +#l.exit@ +EXIT@: + 016D DI + 016E JMP 0000 +BP25@: + 0171 ADD L + 0172 MOV L,A + 0173 MVI H,00 + 0175 RET +BP36@: + 0176 MOV H,A + 0177 MOV A,L + 0178 SUB H + 0179 SBB A + 017A CMA + +(Again, SID listed 11 lines, but only the code at EXIT@ interests us. +Fortunately, it is only 2 lines long. So, the EXIT@ routine of the run-time +library disables interrupts (in case the program re-enabled them) then goes +back to CP/M, by jumping to the BIOS entry point (normally, you put 0 into the +C-register, then call the BDOS. By the way, notice that Appendix D.1 "CP/M +System-Level Procedures" does not mention EXIT@...). + +Ok. So, we have seen the binary contents of the COMmand file. Now, we would +like to know if the program produces the right value (re-read Appendix E. What +are the values at A0001? By the way, the 10 values can be seen in the dump, at +addresses 014D-0156. Do you see them, between the code shown in Appendix E and +the code of the run-time routines added by LINK?) To know this, we need to run +this program... But we have just seen that it goes back to CP/M after "poking" +the result in memory. So, we need to interrupt it. We could put a "breakpoint" +at EXIT@ (read the "SID User's Guide"). In this case, let us do it simpler (a +way compatible with DDT for CP/M 2.2). SID uses an "entry point" located in +the CP/M 2.2 "Page Zero" (you have the BIOS entry point at 0000H, and the BDOS +entry point at 0005H). The only problem is that SID can use any of the +"restart points" of the 8080 (and Z-80) CPU. In practice, most SIDs use RST 6 +or 7, which correspond to 0030H and 0038H (hence the famous "RST 38" of the Z- +80...). So, let us see which one is used, in this case. + +#l0030 + 0030 JMP DB86 + 0033 NOP + 0034 NOP + 0035 NOP + 0036 NOP + 0037 NOP + 0038 NOP + 0039 NOP + 003A NOP + 003B NOP + 003C NOP + +Well... It is obvious that RST 6 (at 0030H) is used by SID. So, let us patch +our COMmand file so that, instead of jumping to the BIOS ("warm-booting"), it +will jump back to SID. (In numbers: replace 0000H by 0030H.) + +#s.exit@ +016D F3 +016E C3 +016F 00 30 +0170 00 . + +Now that the COMmand file is patched, let us run the program at full speed. + +#g.meanv + +*014D + +SID prompted us ("*"), telling us that it stopped executing the program at +014D (the byte *after* the "CALL EXIT@", because the CPU increased the PC by +1). Ok, let us now see the value computed. + +#d1E4,1E5 +01E4: 13 0A + +SID has a command to display hexadecimal values in decimal for mere humans... + +#h13 +0013 #19 + +Well... This is the value that I computed with a pencil on the back of an +envelope from the data in Appendix E. And you? + +#^C +A>put console to console + +Ok. Now that we have seen that PLMX is running, let us start to improve it. I +have not had enough time to find where are made the links between the PLMX +keywords and the run-time and I/O routines. However, during my tests, I was +annoyed with typing a ; to separate the options from the SRC filename. (By the +way, the PLM files of PLMX are not PL/M source code files, and the FOR files +are not, too, FORTRAN files... I have no idea why Roger Carlson chose such +common filetypes for his overlays?) Under CP/M Plus, the "standard" option +separator is [ (it was $ for CP/M 2.2), so let us patch PLMX, so it is more +"standard". The addresses to patch are: + +0A61 +0A7D +0A8E +0AB2 +1993 + +So far, I have had not problem with those patches, but I am a beginner in PLMX +programming. What is sure is that PLMX is the most incredible piece of +CP/M software to have appeared since... the death of CP/M! + +The look of PLMX programs is incredibly different from the look of my assembly +language programs, yet they produce the same code! With PLMX, since you no +longer hard code the control structures but see only the data, you have the +impression of manipulating only the data, and the code appears without effort! +This PLMX compiler is really something worth... $1000! My hat off to Roger +Carlson. + +That's all, folks! + + +EOF + + + + + + + + + + + + \ No newline at end of file diff --git a/SysCon PLMX/PLMXadv.pdf b/SysCon PLMX/PLMXadv.pdf new file mode 100644 index 0000000..a1482ee Binary files /dev/null and b/SysCon PLMX/PLMXadv.pdf differ diff --git a/SysCon PLMX/PLMXadv2.pdf b/SysCon PLMX/PLMXadv2.pdf new file mode 100644 index 0000000..0d50e56 Binary files /dev/null and b/SysCon PLMX/PLMXadv2.pdf differ diff --git a/SysCon PLMX/RLIB.MAC b/SysCon PLMX/RLIB.MAC new file mode 100644 index 0000000..38caae0 --- /dev/null +++ b/SysCon PLMX/RLIB.MAC @@ -0,0 +1,1020 @@ +; RLIB.MAC (= Run-time LIBrary...) +; -------- +; +; CP/M 1.4 -- RLIB of PLMX +; +; Disassembled by: +; +; Mr Emmanuel ROCHE +; Chemin de Boisrond +; 17430 Tonnay-Charente +; FRANCE +; +;-------------------------------- +; ORG 0000H ; Standard CP/M RELocatable file +;-------------------------------- +; Page Zero locations used. +; +Reboot EQU 0000H ; Warm Boot +CPMADR EQU 0006H ; Address of BDOS in TPA +; +;-------------------------------- +; I *THINK* that BP stands for "Built-in Procedure". +;-------------------------------- +bp90@: + DCX H +bp92@: + MOV A,H + CMA + MOV H,A + MOV A,L + CMA + MOV L,A + RET + +bp91@: + MOV E,M + INX H + MOV D,M + XCHG + JMP bp90@ + +bp93@: + MOV E,M + INX H + MOV D,M + XCHG + JMP bp92@ + +;-------------------------------- Šbp09@: + MOV H,B + MOV L,C +?J0118: DAD H + DCR E + JNZ ?J0118 + MOV A,L + RET + +bp94@: + CALL bp09@ + MVI H,00H + RET + +;-------------------------------- +bp11@: + POP H + XTHL +?J0127: MOV A,L + ORA H + RZ + LDAX B + STAX D + INX D + INX B + DCX H + JMP ?J0127 + +;-------------------------------- +bp13@: + ORA A +?J0133: MOV A,C + RAL + MOV C,A + MOV A,B + RAL + MOV B,A + PUSH PSW + DCR E + JZ ?J0142 + POP PSW + JMP ?J0133 + +?J0142: POP PSW + MOV L,C + MOV H,B + RET + +bp96@: Š ORA A +?J0147: MOV A,C + RAL + MOV C,A + PUSH PSW + DCR E + JZ ?J0153 + POP PSW + JMP ?J0147 + +?J0153: POP PSW + MOV A,C + MOV L,A + MVI H,00H + RET + +;-------------------------------- +bp14@: + ORA A +?J015A: MOV A,B + RAR + MOV B,A + MOV A,C + RAR + MOV C,A + PUSH PSW + DCR E + JZ ?J0169 + POP PSW + JMP ?J015A + +; What difference with ?J0142 ??? + +?J0169: POP PSW + MOV L,C + MOV H,B + RET + +bp95@: + ORA A +?J016E: MOV A,C + RAR + MOV C,A + PUSH PSW + DCR E + JZ ?J017A + POP PSW + JMP ?J016E +; Š?J017A: POP PSW + MOV A,C + MOV L,A + MVI H,00H + RET + +;-------------------------------- +bp55@: + XCHG + MOV L,A + MVI H,00H + XCHG + CALL bp87@ + MOV A,L + RET + +;-------------------------------- +bp12@: + MOV A,B + ORA C + RZ + MVI D,0AH ; 10 +?J018F: JMP ?J0192 + +; Yes, you are not dreaming... +; The above line jumps to... next line... + +?J0192: DCR D + JNZ ?J018F + DCX B + JMP bp12@ + +; ??? (Was probably the RET of above code.) + + RET + +;-------------------------------- +; Jump table. (Why here?) + +bp57@: + JMP bp41@ + +bp58@: + JMP bp42@ + +bp59@: + JMP bp43@ + +bp60@: Š JMP bp44@ + +bp61@: + JMP bp45@ + +;-------------------------------- +init@: + XCHG + LHLD CPMADR + SPHL + XCHG + PCHL + +exit@: + DI + JMP Reboot + +;-------------------------------- +bp79@: + MOV A,E + SUB L + MOV L,A + MOV A,D + SBB H + MOV H,A + MOV A,L + RET + +;-------------------------------- +bp10@: + MOV H,B + MOV L,C +?J01BF: ORA A + MOV A,H + RAR + MOV H,A + MOV A,L + RAR + MOV L,A + DCR E + JNZ ?J01BF + RET + +;-------------------------------- +bp15@: + MOV A,C + DAA + MOV L,A + MVI H,00H Š RET + +;-------------------------------- +bp16@: + JC ?J01D9 + MVI A,00H + JMP ?J01DB + +?J01D9: MVI A,0FFH +?J01DB: MOV L,A + MVI H,00H + RET + +;-------------------------------- +bp17@: + JZ ?J01E7 + MVI A,00H + JMP ?J01E9 + +?J01E7: MVI A,0FFH +?J01E9: MOV L,A + MVI H,00H + RET + +;-------------------------------- +bp18@: + JM ?J01F5 + MVI A,00H + JMP ?J01F7 + +?J01F5: MVI A,0FFH +?J01F7: MOV L,A + MVI H,00H + RET + +;-------------------------------- +bp19@: + JPE ?J0203 + MVI A,00H + JMP ?J0205 + +?J0203: MVI A,0FFH +?J0205: MOV L,A + MVI H,00H + RET + +;-------------------------------- +bp25@: + ADD L Š MOV L,A + MVI H,00H + RET + +;-------------------------------- +bp26@: + ORA L + MOV L,A + MVI H,00H + RET + +;-------------------------------- +bp27@: + ANA L + MOV L,A + MVI H,00H + RET + +;-------------------------------- +bp28@: + XRA L + MOV L,A + MVI H,00H + RET + +;-------------------------------- +bp29@: + ADC L + MOV L,A + MVI H,00H + RET + +;-------------------------------- +bp30@: + SBB L + MOV L,A + MVI H,00H + RET + +;-------------------------------- +bp31@: + SUB L + MOV L,A + MVI H,00H + RET + +;-------------------------------- +bp32@: + SUB L Š SUI 01H ; 1 + SBB A + MOV L,A + MVI H,00H + RET + +;-------------------------------- +; Out of sequence® TWICÅ thå samå code... +;-------------------------------- +bp67@: + MOV C,A + MOV A,L + SUB C + MOV L,A + MOV A,H + SBI 00H + ORA L + SUI 01H ; 1 + SBB A + CMA + MOV L,A + MVI H,00H + RET + +;-------------------------------- +bp33@: + SUB L + SBB A + MOV L,A + MVI H,00H + RET + +;-------------------------------- +bp34@: + MOV H,A + MOV A,L + SUB H + SBB A + MOV L,A + MVI H,00H + RET + +;-------------------------------- +bp35@: + SUB L + SUI 01H ; 1 + SBB A + CMA + MOV L,A Š MVI H,00H + RET + +;-------------------------------- +bp36@: + MOV H,A + MOV A,L + SUB H + SBB A + CMA + MOV L,A + MVI H,00H + RET + +;-------------------------------- +bp37@: + SUB L + SBB A + CMA + MOV L,A + MVI H,00H + RET + +;-------------------------------- +bp38@: + MOV E,L + MVI D,00H + MOV L,A + MVI H,00H + CALL bp86@ + MOV A,L + RET + +;-------------------------------- +bp39@: + MOV E,L + MVI D,00H + MOV L,A + MVI H,00H + XCHG + CALL bp87@ + MOV A,L + RET + +;-------------------------------- +bp40@: + MOV E,L + MVI D,00H + MOV L,A Š MVI H,00H + XCHG + CALL bp88@ + MOV A,L + RET + +;-------------------------------- +bp41@: + ADD L + MOV L,A + MOV A,H + ACI 00H + MOV H,A + MOV A,L + RET + +;-------------------------------- +bp42@: + ORA L + MOV L,A + RET + +;-------------------------------- +bp43@: + ANA L + MOV L,A + MVI H,00H + RET + +;-------------------------------- +bp44@: + XRA L + MOV L,A + RET + +;-------------------------------- +bp45@: + ADC L + MOV L,A + MOV A,H + ACI 00H + MOV H,A + MOV A,L + RET + +;-------------------------------- +bp46@: + SBB L + MOV L,A Š MVI A,00H + SBB H + MOV H,A + MOV A,L + RET + +;-------------------------------- +; BP47@ is after BP56@... +;-------------------------------- +bp48@: + SUB L + MOV L,A + MVI A,00H + SBB H + ORA L + SUI 01H ; 1 + SBB A + MOV L,A + MVI H,00H + RET + +;-------------------------------- +bp49@: + SUB L + MOV L,A + MVI A,00H + SBB H + SBB A + MOV L,A + MVI H,00H + RET + +;-------------------------------- +bp50@: + SUB L + MOV L,A + MVI A,00H + SBB H + CMC + JNC ?M02D6 + ORA L + JZ ?M02D6 + STC +?M02D6: SBB A + MOV L,A + MVI H,00H + RET + +;-------------------------------- Šbp51@: + SUB L + MOV L,A + MVI A,00H + SBB H + MOV H,A + ORA L + SUI 01H ; 1 + SBB A + CMA + MOV L,A + MVI H,00H + RET + +;-------------------------------- +bp52@: + SUB L + MOV L,A + MVI A,00H + SBB H + CMC + JNC ?M02F8 + ORA L + JZ ?M02F8 + STC +?M02F8: SBB A + CMA + MOV L,A + MVI H,00H + RET + +;-------------------------------- +bp53@: + SUB L + MOV L,A + MVI A,00H + SBB H + SBB A + CMA + MOV L,A + MVI H,00H + RET + +;-------------------------------- +bp54@: + XCHG + MOV L,A + MVI H,00H + CALL bp86@ Š MOV A,L + RET + +;-------------------------------- +; BP55@ is at the beginning... +;-------------------------------- +bp56@: + XCHG + MOV L,A + MVI H,00H + XCHG + CALL bp88@ + MOV A,L + RET + +;-------------------------------- +bp47@: + SUB L + MOV L,A + MVI A,00H + SBB H + MOV H,A + MOV A,L + RET + +;-------------------------------- +; Jump from BP56@ to BP62@... +;-------------------------------- +bp62@: + MOV C,A + MOV A,L + SBB C + MOV L,A + MOV A,H + SBI 00H + MOV H,A + MOV A,L + RET + +;-------------------------------- +bp63@: + MOV C,A + MOV A,L + SUB C + MOV L,A + MOV A,H + SBI 00H + MOV H,A + MOV A,L Š RET + +;-------------------------------- +bp64@: + MOV C,A + MOV A,L + SUB C + MOV L,A + MOV A,H + SBI 00H + ORA L + SUI 01H ; 1 + SBB A + MOV L,A + MVI H,00H + RET + +;-------------------------------- +bp65@: + MOV C,A + MOV A,L + SUB C + MOV A,H + SBI 00H + SBB A + MOV L,A + MVI H,00H + RET + +;-------------------------------- +bp66@: + MOV C,A + MOV A,L + SUB C + MOV L,A + MOV A,H + SBI 00H + CMC + JNC ?M0362 + ORA L + JZ ?M0362 + STC +?M0362: SBB A + MOV L,A + MVI H,00H + RET + +;-------------------------------- +; TWICE?? Š; (BP67@ is between BP32@ and BP33@...) +; (and this is the same code...) +; bp67@: + MOV C,A + MOV A,L + SUB C + MOV L,A + MOV A,H + SBI 00H + ORA L + SUI 01H ; 1 + SBB A + CMA + MOV L,A + MVI H,00H + RET + +;-------------------------------- +bp68@: + MOV C,A + MOV A,L + SUB C + MOV L,A + MOV A,H + SBI 00H + CMC + JNC ?M0387 + ORA L + JZ ?M0387 + STC +?M0387: SBB A + CMA + MOV L,A + MVI H,00H + RET + +;-------------------------------- +bp69@: + MOV C,A + MOV A,L + SUB C + MOV A,H + SBI 00H + SBB A + CMA + MOV L,A + MVI H,00H + RET + +;-------------------------------- Šbp70@: + MOV E,A + MVI D,00H + CALL bp86@ + MOV A,L + RET + +;-------------------------------- +bp71@: + MOV E,A + MVI D,00H + XCHG + CALL bp87@ + MOV A,L + RET + +;-------------------------------- +bp72@: + MOV E,A + MVI D,00H + XCHG + CALL bp88@ + MOV A,L + RET + +;-------------------------------- +bp73@: + DAD D + MOV A,L + RET + +bp74@: + MOV A,H + ORA D + MOV H,A + MOV A,L + ORA E + MOV L,A + RET + +;-------------------------------- +bp75@: + MOV A,H + ANA D + MOV H,A + MOV A,L + ANA E + MOV L,A + RET Š +bp76@: + MOV A,H + XRA D + MOV H,A + MOV A,L + XRA E + MOV L,A + RET + +bp77@: + MOV A,L + ADC E + MOV L,A + MOV A,H + ADC D + MOV H,A + MOV A,L + RET + +bp78@: + MOV A,E + SBB L + MOV L,A + MOV A,D + SBB H + MOV H,A + MOV A,L + RET + +;-------------------------------- +; BP79@ is at the beginning... +;-------------------------------- +bp80@: + MOV A,E + SUB L + MOV L,A + MOV A,D + SBB H + ORA L + SUI 01H ; 1 + SBB A + MOV L,A + MVI H,00H + RET + +;-------------------------------- +bp81@: + MOV A,E Š SUB L + MOV L,A + MOV A,D + SBB H + SBB A + MOV L,A + MVI H,00H + RET + +;-------------------------------- +bp82@: + MOV A,E + SUB L + MOV L,A + MOV A,D + SBB H + CMC + JNC ?M0400 + ORA L + JZ ?M0400 + STC +?M0400: SBB A + MOV L,A + MVI H,00H + RET + +;-------------------------------- +bp83@: + MOV A,E + SUB L + MOV L,A + MOV A,D + SBB H + ORA L + SUI 01H ; 1 + SBB A + CMA + MOV L,A + MVI H,00H + RET + +;-------------------------------- +bp84@: + MOV A,E + SUB L + MOV L,A + MOV A,D + SBB H + CMC Š JNC ?M0421 + ORA L + JZ ?M0421 + STC +?M0421: SBB A + CMA + MOV L,A + MVI H,00H + RET + +;-------------------------------- +bp85@: + MOV A,E + SUB L + MOV L,A + MOV A,D + SBB H + SBB A + CMA + MOV L,A + MVI H,00H + RET + +;-------------------------------- +bp86@: + MOV B,H + MOV C,L + LXI H,0000H + MVI A,0F0H +?J0439: PUSH PSW + DAD H + MOV A,E + RAL + MOV E,A + MOV A,D + RAL + MOV D,A + JNC ?M0449 + DAD B + JNC ?M0449 + INX D +?M0449: POP PSW + INR A + JM ?J0439 + MOV A,L + RET + +;-------------------------------- +bp87@: Š XCHG + MOV B,D + MOV C,E + CALL Co0461 + XCHG + MOV A,L + RET + +bp88@: + XCHG + MOV B,D + MOV C,E + CALL Co0461 + MOV A,L + RET + +Co0461: LXI D,0000H + CALL C$0487 + XCHG + MVI A,0F0H +?J046A: PUSH PSW + DAD H + RAR + XCHG + DAD H + XCHG + JNC ?J0474 + INX H +?J0474: RAL + JC ?J047F + MOV A,L + ADD C + MOV A,H + ADC B + JNC ?J0481 +?J047F: DAD B + INX D +?J0481: POP PSW + INR A + JM ?J046A + RET + +C$0487: DCX B + MOV A,C + CMA + MOV C,A + MOV A,B + CMA + MOV B,A Š RET + +;-------------------------------- +; Jump from BP88@ to BP04@... +;-------------------------------- +bp04@: + MOV A,C + MOV L,A + MVI H,00H + RET + +;-------------------------------- +bp05@: + MOV A,B + MOV L,A + MVI H,00H + RET + +;-------------------------------- +bp06@: + MOV H,B + MOV L,C + MOV A,L + RET + +;-------------------------------- +bp07@: + MOV A,C +?J049E: RLC + DCR E + JNZ ?J049E + MOV L,A + MVI H,00H + RET + +;-------------------------------- +bp08@: + MOV A,C +?J04A8: RRC + DCR E + JNZ ?J04A8 + MOV L,A + MVI H,00H + RET + +;-------------------------------- +bp89@: + POP D + DAD H Š DAD D + MOV A,M + INX H + MOV H,M + MOV L,A + PCHL + +;-------------------------------- + + END ; Standard CP/M RELocatable file + \ No newline at end of file diff --git a/SysCon PLMX/RLIB.REL b/SysCon PLMX/RLIB.REL new file mode 100644 index 0000000..5c1402b Binary files /dev/null and b/SysCon PLMX/RLIB.REL differ