; ======================================================= ; ; REC module containing RAM storage, I/O programs, main ; program, and the directory. The complete set of modules ; comprises REC.MAC, PDL.MAC, MARKOV.MAC, RECLIB.MAC, and ; FXT.MAC. RECLIB.MAC may be omitted if the operator X ; isn't used, and must be substituted by another module ; if the collection of subroutines to be called by X is ; to be changed. ; ; FXT.MAC contains the following REC operators and ; predicates: ; ; C compile a REC expression ; i input from designated port ; k call CP/M without residue ; K call CP/M, preserve FCB, return value ; o output from designated port ; R read one character from console ; t type message given header ; T type argument on PDL ; W write argument on LST: ; x execute REC subroutine ; ` test if a character waits at keyboard ; ; ------------------------------------------------------ ; REC version released during the 1984 Summer School of ; the Microcomputer Applications Group of the I.C.U.A.P. ; ------------------------------------------------------ ; 8086 version with segments for code, PDL and WS. ; ------------------------------------------------------ ; ; FXT86 - Copyright (C) 1982, 1984 ; Universidad Autonoma de Puebla ; 49 Poniente 1102 - Puebla, Puebla, Mexico ; All Rights Reserved ; ; [Harold V. McIntosh, 28 August 1980] ; [Gerardo Cisneros, 8 February 1984] ; ; Modification 1 - 1 January 1981. ; a) Main program derives the values of const, ; conin, conou from the address rst0 supposing ; that BIOS starts out with the standard jump ; vector. Thus, REC need not be reassembled ; to have fast access to I/O when CP/M varies. ; b) T protected by pushes and pops of dx and bx. ; c) Some changes made in memory allocation. ; 24 May 1981 - Zero flag to restrain L from too many pops ; 25 March 1982 - Y is now a predicate ; 29 May 1983 - ~ discontinued as argument exchange ; 29 May 1983 - ~ for unary negative or complement ; 29 May 1983 - N for numerical comparison on PDL ; 29 May 1983 - h discontinued, replaced by ''w ; 30 May 1983 - CPIR: jumps to BOOT rather than RER ; 8 July 1983 - C has object program origin as argument ; 8 July 1983 - C is an operator ; 8 July 1983 - C0 defined as lower bound of compile area ; 8 July 1983 - x moved from RECLIB ; 8 July 1983 - x is a predicate to call REC subroutines ; 9 July 1983 - Buffered CP/M input if no disk file given ; 14 July 1983 - W had its arguments reversed ; 14 January 1984 - , for sorcim.cnv ; 14 January 1984 - default extension .REC for 1st file ; 8 February 1984 - separate segments (GCS) ; Apr 1984 - Disposable initialization code - GCS ; 9 May 1984 - Arguments of C reversed (GCS) ; 31 May 1984 - Error messages for Cp, PD and WS ovfl - GCS ; 11 June 1984 - DIIN/CPIN set up DMA address and seg. - GCS ; 18 June 1984 - Set DMA, then open; initialize VT - GCS ; 20 June 1984 - Rd ovf error on EOF and end of buffer - GCS ; 3 July 1984 - @@ takes over x, x is library predicate; ; entry point for TL and combination table included. - GCS ; 14 Aug 1984 - Operator pair table extended - GCS ; ======================================================= ; Absolute program locations used by CP/M. bdos equ 224 ;CP/M-86 software interrupt vector TFCB equ .005CH ;CP/M file control block DSIZ equ 0020H ;size of two parsed filenames FSIZ equ 0010H ;CP/M file name size TBUF equ .0080H ;CP/M disk buffer location TSIZ equ 0080H ;CP/M disk buffer size LCODE equ .0000H ;last of code group LDATA equ .0006H ;last of data segment LEXTR equ .000CH ;last of extra (WS) segment BEXTR equ .000FH ;base of extra segment LSTAK equ .0012H ;last of stack segment BSTAK equ .0015H ;base of stack segment ; Linkage to input-output through ports. QIN rw 0 ;space holder DB 0ECH ;8-bit 8086 static IN instruction QI db 00H ret QOU rw 0 ;space holder DB 0E6H ;8-bit 8086 static OUT instruction QO db 00H ret ; ======================================================= ; Programs related to input-output and disk usage. ; ======================================================= ; bootstrap routine boot: mov cl,ze mov dl,ze int bdos ; Buffer read routine. PTY: push bx ;conserve (bx) mov es,RSEG ;get segment address for buffer mov bx,RX ;pointer to read buffer cmp bx,RY jz ptye mov al,es:[bx] ;fetch byte inc bx ;advance pointer to next byte mov RX,bx ;update buffer pointer pop bx ;restore (bx) - preserve all reg pairs ret ptye: mov bx,'dR' ;Report Rd ovfl and quit jmp FERR ; Console character read routine. CP/M-86 compatible version ; with direct access to CONIN. chin: push cx push dx chi: mov dl,-1 mov cl,6 int bdos test al,al jz chi pop dx pop cx ret ; Buffered console character read routine, which is more ; practical for use with CP/M. Up to 126 characters may ; be read using CP/M function 10, which is sufficient for ; bootstrapping or generating test programs. CHIN should ; be used for longer input sequences, which must be error ; free - incoming through a modem, for example. buin: push bx push cx push dx mov bx,RX cmp bx,RY jnz BI5 BI4: mov cl,9 ;(09) write message mov dx,(offset bume) int bdos mov cl,10 ;(0A) buffered read mov dx,(offset TBUF) int bdos mov cl,9 ;(09) write message mov dx,(offset crlf) int bdos mov bx,(offset TBUF)+2 mov RX,bx mov al,-1[bx] mov ah,0 add ax,bx cmp ax,bx jz BI4 mov RY,ax BI5: mov al,[bx] inc bx mov RX,bx pop dx pop cx pop bx ret ; Buffered read for repetitive compilation bure: mov al,TSIZ-2 mov TBUF,al mov ax,(offset buin) mov read,ax mov ax,(offset TBUF) mov RX,ax mov RY,ax ret ; Console character out routine. CP/M-86 compatible version ; with direct access to CONOUT chou: push cx push dx mov dl,al mov cl,6 ;(06) direct console IO int bdos pop cx pop dx ret ; (`) Test for presence of waiting character (FALSE if ; none waiting. CP/M-86 compatible version with access ; to CONST. chaw: push cx push dx mov dl,-2 mov cl,6 ;(06) direct console IO int bdos pop dx pop cx test al,al jnz chw ret chw: jmp SKP ; Printer output routine. PROU: push bx push dx push cx mov cl,5 ;(05) output through LST: mov dl,al int bdos pop cx pop dx pop bx ret ; (R) REC read operator. UCR: mov cx,1 ;one byte to be inserted call NARG ;close last arg, verify space push bx call word ptr tyin ;get byte from console input pop bx mov [bx],al ;store on PDL inc bx ;advance pointer mov PY,bx ;record end of argument ret ; (t) Write indirect operator. prints the ; indicated message, leaves no residue. LCT: mov bx,PX ;fetch argument pointer call ONEL ;move one argument to 8086 stack call CXLD ;get org and segment mov bx,cx ;org to bx pop dx ;size to dx add dx,bx ;org+size=end jmp UT1 ;use write cycle in UCT ; (TL) Often-used combination for which a single call ; is compiled. UCTL: call UCT ;type argument and jmp UCL ;lift it ; (T) REC write operator. <'XXX' T> will write XXX on ; the console, leaving it on the PDL. uct: mov dx,PY ;fetch terminal address mov bx,PX ;beginning address to (bx) mov ax,ds mov es,ax ut1: cmp dx,bx jz ut2 ;they match, we're done mov al,es:[bx] ;get byte out of memory push bx push dx push es call word ptr tyou ;tyou is in the data segment pop es pop dx ;recover the saved registers pop bx inc bx ;advance pointer jmp UT1 ;repeat ut2: ret ; (W) REC print operator. will print the ; indicated text on the list device, and then erase its ; arguments. UCW: mov bx,PX ;pointer to arguments call ONEL ;size from PDL to 8086 stack call CXLD ;org and segment addr to cx and es mov bx,cx ;place text origin in (bx) pop dx ;place length in (dx) UWW: test dx,dx ;check for zero length jz UWX ;no more to print mov al,es:[bx] ;fetch a byte push bx ;we need to be sure that dx and bx are push dx ;preserved whatever the print routine push es call PROU ;send it to printer pop es pop dx ;recover bx pop bx ;and dx dec dx ;diminish count inc bx ;advance pointer jmp UWW ;repeat UWX: ret ; (i) Input from designated port. leaves ; so that after disposing of , ; can be reused. LCI: mov bx,PX ;get pointer to top argument on PDL mov al,[bx] ;only the low order byte matters mov cs:QI,al ;place it in teme IN instruction mov cx,1 ;we're only going to read one byte call NARG ;prepare a place for it on the PDL call QIN ;execute the captive IN instruction mov [bx],al ;storing the incoming byte on the PDL inc bx ;always ready for the next byte mov PY,bx ;close off the argument ret ;and we're through ; (o) Output from designated port - ; leaves , facilitating multiple OUTs through the ; same port. LCO: mov bx,PX ;pointer to last argument - output byte mov CH,[bx] ;tuck it into register b call UCL ;erase the top argument mov al,[bx] ;(bx) points to next argument - get it mov cs:QO,al ;store in tame OUT instruction mov al,CH ;output must be from accumulator jmp QOU ;execute the prepared OUT instruction ; ======================================================= ; ; Communication with CP/M takes two forms: ; which leaves on the pushdown list, or else ; which leaves nothing on the pushdown list. ; In either case - FCB is a two-byte parameter, usually ; the address of the file control block - but it could ; also be a DMA address or sometimes even null for the ; sake of uniformity. Approximately thirty options are ; available which are numbered serially, indicated by the ; argument n. The difference between K and k is that the ; former conserves the parameter FCB for possible use by ; a subsequent CP/M call, and reports a result in the ; one-byte result . This could be the character ; read by an input routine or an error code for the disk ; routines. ; ; The options are: ; ; num function "FCB" "code" ; --- -------- ----- ------ ; ; 0 system reset - - ; 1 read console - char ; 2 write console char - ; 3 read reader - char ; 4 write punch char - ; 5 write list char - ; 6 - - - ; 7 read i/o stat - stat ; 8 write i/ stat stat - ; 9 print buffer buffer - ; 10 read buffer buffer - ; 11 console status - stat ; ; 12 lift disk head - - ; 13 init disk only - - ; 14 select disk disk - ; 15 open file fcb code ; 16 close file fcb code ; 17 search once fcb code ; 18 search again fcb code ; 19 delete file fcb code ; 20 read 1 record fcb code ; 21 write 1 record fcb code ; 22 create file fcb code ; 23 rename file fcb code ; 24 read login - logv ; 25 read disklog - disk ; 26 set DMA address dma - ; 27 read bitmap - - ; ; Fuller details of all the CP/M options and the way they ; function can be obtained through consulting Digital ; Research's manuals for CP/M, especially their "CP/M ; Interface Guide." ; ; ======================================================= ; (K) Set up communication with CP/M - top into (bx), ; next into (dx). Preserve next, call BDOS, (Aze) into ; top. CPM: call DXLD ;fetch function number and lift mov cx,dx ;move it to cx call ESLD ;get FCB org and segment mov dx,[bx] ;FCB offset to dx cmp cx,26 ;is it 'set DMA addr'? jnz CPM1 call CPSG ;yes, set DMA base first CPM1: push ds ;save current data seg base mov ax,es mov ds,ax ;set ds to FCB's segment int bdos ;call bdos with args in cx, dx pop ds ;restore data segment base mov ah,0 ;clear upper half of ax push ax ;save it on 8086 stack mov cx,2 ;reopen arg on PDL call NARG pop word ptr [bx] ;place return code on PDL inc bx inc bx mov PY,bx ret ; (k) Call to CP/M without any value returned. CPML: mov bx,PX ;fetch argument pointer call ONEL ;function number to 8086 stack call CXLD ;FCB org and segment to cx and es mov dx,cx ;we want org in dx pop cx ;get function number into cx cmp cx,26 ;is it 'set DMA base'? jnz CPML1 ;no, skip CPML0: call CPSG ;yes, set DMA base CPML1: push ds ;save data segment base mov ax,es mov ds,ax ;set FCB segment base int bdos ;execute indicated operation pop ds ;restore data segment base ret CPSG: push es push cx push dx mov cl,51 ;(33H) set DMA base mov dx,es ;the segment base itself int bdos pop dx pop cx pop es ret ; ------------------------------------------------------- ; Disk input-output routine working through CP/M. ; ------------------------------------------------------- ; Set up a file control block with a given file name and ; the default extension REC. The pushdown list contains ; the disk unit designation, then by the filename without ; any extension. No protection is afforded against an ; overly long file name, a nonexistent disk, or the like. ; Some errors of this type must be caught by CP/M since ; REC cannot know such things as the exact number of disk ; drives that there will be. DIIN: cld mov ax,ds mov es,ax mov cx,21H ;FCB requires 33 bytes mov di,(offset TFCB) ;use CP/M's transient FCB mov al,00H ; ;fill it with zeroes repnz stos byte [di] mov cx,11 ;filename field is 11 bytes long mov di,(offset TFCB)+1 ;field begins at second byte mov al,' ' ;fill it with blanks repnz stos byte [di] mov bx,PX ;fetch pointer to top argument mov al,[bx] ;load disk unit designator sub al,'@' ;set CP/M disk numbering convention mov TFCB,al ;store it in file control block call UCL ;pop top argument mov si,PX ;fetch pointer to file name mov cx,PY ;end of file name sub cx,si ;place py - px in (cx) mov di,(offset TFCB)+1 ;destination origin repnz movs byte [di],[si] CPIN: cmp byte ptr TFCB+9,' ' jnz CPIN2 mov byte ptr TFCB+9,'R' ;set default extension 'REC' mov byte ptr TFCB+10,'E' mov byte ptr TFCB+11,'C' CPIN2: mov dx,(offset TBUF) ;origin of CP/M's sector buffer mov RSEG,ds ;CP/M's buffer is in the data seg mov RX,dx ;initial address of pseudotty mov RY,dx ;provoke disk read mov es,RSEG ;set DMA address and base mov cx,26 call CPML0 mov cl,15 ; mov dx,(offset TFCB) ;file control block int bdos ; cmp al,0FFH ;check for error jz CPIR ret CPIR: jmp boot ; Read from disk buffer, replenish buffer when empty. DIRE: push bx ;save 3 8080 register pairs push dx ; push cx ; mov bx,RX ;pointer to current byte cmp bx,RY ;skip if equal jnz DI5 ;still have bytes in the buffer mov cl,20 ; mov dx,(offset TFCB) ;file control block int bdos ; test al,al jnz dier ;quit if read not OK mov bx,(offset TBUF)+TSIZ ;end of buffer mov RY,bx ;store it in ry mov bx,(offset TBUF) ;beginning of buffer mov RX,bx ;store it in rx DI5: mov al,[bx] ;common continuation inc bx ;byte in acc, advance pointer mov RX,bx ;store position of next byte pop cx ;replace 3 register pairs pop dx ; pop bx ; ret dier: mov bx,'dR' jmp FERR ; (C) REC compiling operator which takes the designation ; of the compiling source from the PDL. The alternatives ; are: ; ; ''C input program from console ; 'file' 'D' C take from disk D ; pC pushdown list ; qC workspace ; memory from address org onward ; ; where designates the destination area for the ; compilation: C1 if null, the address given otherwise. ; In general, if the top argument is of length zero, the ; console is the source, if it is of length one the named ; disk is the source [@=current disk, A, B, ... up to the ; system's limit], and if the argument has length 2, the ; combination of from the memory applies. It ; is the programmer's responsibility to avoid nonexistent ; memory, disk units, and the like. UCC: push read push c1 mov cx,PY sub cx,PX jnz UC5 mov dx,C1 ;use compile pointer jmp UC6 UC5: call ESLD ;get segment, ignore mov dx,[bx] ;get address to use UC6: mov C1,dx ;record as C1 call UCL ;remove argument mov ax,PY ;check length of argument sub ax,PX jz UC2 ;zero means console cmp ax,1 ;test for one byte jz UC1 ;one means disk designation cmp ax,2 ;verify that we've got two bytes jnz UC7 ;no provision for other than 1, 2 bytes mov bx,(offset PTY) ;setup readin from pseudoteletype mov read,bx ; call CXLD ;load two numerical arguments mov dx,[bx] ;bx contains PX for second argument call ESLD ;load segment address of buffer mov RX,dx ;origin of REC source code add dx,cx ;length of source code mov RY,dx ;end of source code mov RSEG,es ;segment of source code jmp UC4 ;compile once rx, ry set up UC1: call DIIN ;setup the CP/M FCB for given file mov bx,(offset DIRE) ;setup input from disk reader jmp UC3 ;compile once input source set up UC2: mov bx,(offset CHIN) ;input from the console UC3: mov read,bx ; UC4: call EMCE push dx call PUTW call PUTW pop c1 pop read ret UC7: pop c1 pop read call RER ; Single-shot compilation from a disk file SSHOT: call EMCX ;compile the program file mov cx,DSIZ mov di,(offset TFCB) mov si,P3 mov ax,ds mov ds,WSEG mov es,ax repnz movs byte [di],[si] ;retrieve parsed filenames mov bx,es:P1 mov cl,[bx] inc cx mov di,(offset TBUF) mov si,bx repnz movs byte [di],[si] ;retrieve command line mov ds,ax ;restore data segment base value inc bx mov P2,bx call UCD ;delete character count from workspace call EMCU ;execute the program file jmps bootie ;return to CP/M if false nop ;beware jump span bootie: jmp boot ; Multiple compilations from the console tylo: call STATS ;type out memory usage stats nodi: call bure call INRE call EMCX call EMCU jmps nodi nop jmp nodi ; Type error message and quit FERR: mov EMSG,bx mov dx,(offset EMSGS) mov cl,9 int bdos jmp boot ; END OF PERMANENT CODE. THE INSTRUCTIONS FOLLOWING THIS ; WILL BE OVERWRITTEN AS SOON AS THE FIRST REC PROGRAM ; IS COMPILED. ENDREC rw 0 ; ================ ; = main program = ; ================ MAIN: cli mov ss,BSTAK ;load stack segment base mov sp,LSTAK ;load stack pointer sti mov ax,LCODE ;set compile area limit mov C2,ax mov bx,LDATA ;set PDL limit dec bx ;one down from highest PDL byte mov PZ,bx mov word ptr [bx],0FFFFH ;mark barrier to 'n' mov ax,BEXTR ;set WS base address mov WSEG,ax mov es,ax mov bx,LEXTR ;set WS limit dec bx mov es:word ptr [bx],ZE ;flag end of WS mov P4,bx mov PD,ZE ;mark bottom of pushdown list mov di,(offset VT) ;set up to initialize vars/subs mov cx,042H ;twice the number of variables mov ax,ds mov es,ax mov ax,0000 repnz stos word [di] ;set variables to zero mov cx,05FH ;number of subroutine entries mov bx,cs mov ax,(offset boot) ;CP/M exit routine vtc0: stos word [di] ;store boot routine address xchg ax,bx stos word [di] ;store segment base xchg ax,bx loop vtc0 mov bx,(offset TFCB)+1 cmp byte ptr [bx],' ' jnz majn jmp tylo ;to TTY: loop if command tail empty majn: call svcmb call CPIN ;open disk file for REC program mov bx,(offset DIRE) ;REC input through disk mov read,bx ;REC compiler's I-O linkage call INRE ;initialize REC compiler RAM jmp SSHOT ;compile once from disk file svcmb: cld mov bx,(offset TBUF) ;pointer to command buffer mov di,P1 ;next byte of WS mov cl,[bx] ;get count inc cl ;plus one to include count itself mov ch,0 mov si,bx mov es,WSEG ;load ES with WS base repnz movs byte [di],[si] mov P3,di mov bx,P1 inc bx mov P1,bx mov P2,bx mov ax,ds mov es,ax call fica call UCD ;delete first name including its terminator mov di,P3 ;save parsed filenames at p3 and following mov es,WSEG ;reload ES with WS base call ficb call ficb mov bx,P0 mov P1,bx ;p1 back to start of text ret fsep: call zsep jnz fsep1 ret fsep1: call rech ;read one character jmp fsep ; Advance to a non blank character in the console ; buffer unless there is none, indicated by a 00. zonb: call rech ;read one character test al,al jnz zonb1 ret zonb1: cmp al,' ' jz zonb ;zero or non-blank ret ; Generate a file control block in the manner of CCP. fica: mov di,(offset TFCB) ficb: call zonb ;zero or non-blank push ax jz ficd sbb al,'@' mov dl,al ;save possible disk id mov bx,P2 mov bp,ds mov ds,WSEG mov al,(byte ptr[bx]) mov ds,bp cmp al,':' jz ficc xor al,al jmp ficd ficc: call rech ;get rid of colon pop ax call rech ;get first of filename push ax mov al,dl ficd: stos (byte ptr[di]) mov cx,08 pop ax call ffil call fsep mov cx,03 cmp al,'.' jnz ficp call rech ;read one character call ffil call fsep jmp ficq ficp: call bfil ficq: mov cx,04 mov ah,al mov al,0 jmp kfil ; Fill a field ffil0: call rech ;read one character ffil: call zsep jz bfil cmp al,'*' jz qfil stos (byte ptr[di]) loop ffil0 ret ; Block fill qfil: mov ah,al mov al,'?' jmp kfil bfil: mov ah,al mov al,' ' kfil: repnz stos byte ptr[di] mov al,ah ret ; Fetch a character into a from command line rech: mov bx,P1 dec bx ;length is kept one back of p1 mov si,P2 ;both pointers before altering DS mov bp,ds mov ds,WSEG mov al,(byte ptr[bx]) ;number of characters not taken out test al,al mov al,0DH ;carriage return faked on empty buffer jz recx dec byte ptr[bx] mov bx,si mov al,byte ptr[bx] inc bx mov ds,bp mov P2,bx recx: mov ds,bp ret ; Set ZF if AL contains a separator zsep: test al,al jz zret cmp al,0DH jz zret cmp al,' ' jc cmerr ;ctrl chars jz zret cmp al,'=' jz zret cmp al,'_' jz zret cmp al,'.' jz zret cmp al,':' jz zret cmp al,';' jz zret cmp al,'<' jz zret cmp al,'>' zret: ret ; command line error cmerr: mov al,'?' call CHOU ;type a question mark pop bx ;pop rets from call zsep, pop bx ;call fsep/ffil, pop bx ;call fica/b and pop bx ;call svcmb mov bx,P0 ;restore workspace pointers mov P1,bx mov P2,bx mov P3,bx STATS: mov cl,9 ;(09) write message mov dx,(offset logo) int bdos call QU ;use REC ops to show RAM usage dw 6 db 'Code ' call NU dw 0 call NU dw 3 call RLCT call QU dw 7 db ' CPL ' mov bp,C2 sub bp,C0 call RCTL call QU dw 6 db 'Data ' call NU dw 6 call NU dw 9 call RLCT call QU dw 7 db ' PDL ' mov bp,PZ sub bp,(offset PD)+2 call RCTL call QU dw 6 db 'Extra ' call NU dw 12 call NU dw 15 call RLCT call QU dw 7 db ' WS ' mov bp,P4 sub bp,P0 call RCTL call QU dw 6 db 'Stack ' call NU dw 18 call NU dw 21 call RLCT call QU dw 7 db ' STK ' mov bp,LSTAK call RCTL ret TCRL: call NU dw 2573 call UCT call UCL ret RLCT: call IND call HX call QU dw 1 db ':' call CONC call EXCH call IND call HX call CONC call QU dw 1 db 'H' call CONC RLCT2: call CONC call UCT call UCL ret RCTL: mov cx,2 call NARG mov [bx],bp inc bx inc bx mov PY,bx call NS call RLCT2 call TCRL ret ; ----------------------------------------------------- ; RAM memory which is required for the operation of REC ; ----------------------------------------------------- ; ============= dseg org 0100H ;origin of data in data segment ; ============= ; Relay area for input and output subroutines. read dw chin ;character input for REC compiler tyin dw chin ;single character input for R tyou dw chou ;single character output for T ; Error message buffer EMSGS db 0DH,0AH EMSG dw 2020H db ' ovfl$' ; Prompt and crlf bume db 0DH,0AH,'REC86> $' crlf db 0DH,0AH,'$' ; Temporary storage used by the REC compiler. XPD dw 0000 ;colon jump back to left parenthesis YPD dw 0000 ;false predicate jump chain ZPD dw 0000 ;semicolon exit chain ; Pointers to the directories. FXT dw FT ;pointer to fixed operator directory VRT dw VT ;pointer to subroutine directory CMT dw CTB ;pointer to compination directory ; Pointers to the area of compiled subroutines. C0 dw ENDREC ;lower limit of compile area C1 dw ENDREC ;beginning of present compilation C2 dw 0 ;upper limit of compile area ; Pointers to REC/MARKOV pushdown list. PX dw PD+2 ;beginning of pushdown text PY dw PD+2 ;end of pushdown text PZ dw 0 ;end of available pushdown space ; Workspace pointers. P0 dw 0 ;beginning of workspace P1 dw 0 ;beginning of marked segment P2 dw 0 ;end of marked segment P3 dw 0 ;end of text P4 dw 0 ;end of workspace WSEG dw 0 ;WS segment address ; I-O pointers. RX dw 0000 RY dw 0000 RSEG dw 0000 ; Error flag. ER dw 0000 ; Holder for return address from h RTADDR dw 0000 ; ======= here is the table of definitions of REC operators ===== FT dw NOOP ;blank dw NOOP dw RECOP ; [exclm] binary to hex string dw HX dw RECDQ ; " quoted expression dw QU dw RECOP ; # binary to decimal string dw NS dw RECOL ; $ fetch a variable cell dw VBLE dw RECOP ; % restrict to one byte dw PE dw RECOL ; & exchange top numeric pair dw EXCH dw RECSQ ; ' quoted expression dw QU dw RECLP ; ( dw NOOP dw RECRP ; ) dw NOOP dw RECOP ; * multiply dw MPY dw RECOP ; + add dw SUM dw NOOP ; , separator like space dw NOOP dw RECMS ; - subtract dw DIF dw RECOP ; . dw NOOP dw RECOP ; / divide [remainder, quotient] dw DVD dw RECDD ; 0 number dw NU dw RECDD ; 1 number dw NU dw RECDD ; 2 number dw NU dw RECDD ; 3 number dw NU dw RECDD ; 4 number dw NU dw RECDD ; 5 number dw NU dw RECDD ; 6 number dw NU dw RECDD ; 7 number dw NU dw RECDD ; 8 number dw NU dw RECDD ; 9 number dw NU dw RECCO ; : dw NOOP dw RECSC ; ; dw NOOP dw RECOP ; < restrict workspace dw BRA dw RECPR ; = test equality of top pair dw EQL dw RECOL ; > open workspace dw KET dw RECPR ; ? test for error report dw QM dw RECP1 ; @ execute subroutine dw AR dw RECPR ; A advance pointer 1 dw UCA dw RECPR ; B retract pointer 1 dw UCB dw RECOP ; C compile dw UCC dw RECOP ; D delete text dw UCD dw RECPL ; E equality between WS and PD dw UCE dw RECPL ; F find specified text dw UCF dw RECOP ; G fetch a block from memory dw GA dw RECPR ; H ASCII hex to binary dw HE dw RECOL ; I insert dw UCI dw RECOL ; J jump to front dw UCJ dw RECOP ; K call CP/M, keep (dx), put value dw CPM dw RECOL ; L erase top of PDL dw UCL dw RECPR ; M compare PDL and workspace dw UCM dw RECPR ; N numerical comparison dw UCN dw RECPR ; O decimal ASCII string to binary dw UCO dw RECOP ; P put block into buffered memory dw UCP dw RECOL ; Q put workspace segment on PD dw UCQ dw RECOP ; R read from keyboard dw UCR dw RECOP ; S store block in memory dw SA dw RECOL ; T write on screen dw UCT dw RECPR ; U search, yielding interval dw UCU dw RECPR ; V U, including endpoints dw UCV dw RECOP ; W write on printer dw UCW dw RECO1 ; X call library operator dw LIBO dw RECPR ; Y recover previous position of p1 dw UCY dw RECOL ; Z pointer 2 to end of text dw UCZ dw RECCM ; [ comment dw NOOP dw RECOP ; \ insert single byte in pair dw IP dw RECOP ; ] dw NOOP dw RECOL ; ^ increment top argument dw INCR dw RECOP ; _ exit to monitor dw boot dw RECPR ; ` true for waiting character dw CHAW dw RECPR ; a segment forward from p1 dw LCA dw RECPR ; b segment backward from p2 dw LCB dw RECOP ; c create block on PDL dw BLOK dw RECPR ; d decrement but skip on zero dw decR dw RECPR ; e extend workspace dw LCE dw RECPR ; f block fill dw LCF dw RECOP ; g non-incrementing byte fetch dw GB dw RECOP ; h store/restore machine state dw MST dw RECOP ; i input from designated port dw LCI dw RECOL ; j null interval at p1 dw LCJ dw RECOP ; k call CP/M: no returned values dw CPML dw RECOP ; l put pz on PDL dw Lcl dw RECOP ; m set aside top argument dw LCM dw RECOL ; n recover set-aside argument dw LCN dw RECOP ; o output from designated port dw LCO dw RECOL ; p put px, py-px on PDL dw GXS dw RECOL ; q put p1, p2-p1 on PDL dw LCQ dw RECOP ; r indirect replacement of address dw IND dw RECOP ; s store block in memory wrt limit dw LCS dw RECOP ; t type out indicated interval dw LCT dw RECOP ; u incrementing byte fetch dw GBI dw RECOP ; v incrementing byte store dw SAI dw RECOP ; w store workspace header dw LCW dw RECP1 ; x call library predicate dw LIBP dw RECOP ; y fetch byte pair to PDL incr org dw GWI dw RECOL ; z null interval at p2 dw LCZ dw LBR ; { start a definition string dw NOOP dw RECOP ; | concatinate top two arguments dw CONC dw RECOP ; } end a definition string dw NOOP dw RECOP ; ~ complement or negate top arg dw COMP dw RECOP ; del dw NOOP ; Table of often-used combinations to compile as single ; operators or predicates. CTB db 'Ez' ;to the right if same dw EZE db 'JZ' ;span text dw SPAN db 'z<' ;null WS at p2 dw ZCL db 'Z>' ;reopen with p2 at end dw ZOP db 'Jj' ;p1 and p2 at p0 dw BEG db 'Z<' ;restrict from p1 to p3 dw UZCL db 'pG' ;duplicate PDL argument dw DUP db 'ED' ;delete if same dw EDE db 'J>' ;open with p1 at old p0 dw JOP db 'Iz' ;insert and collapse dw IZE db 'jJ' ;p1 and p2 to p0 and p1 dw LJUJ db '><' ;reopen and restrict dw OPCL db '^^' ;increase by 2 dw INTW db 'QD' ;copy and delete dw QUDE db 'FD' ;find and delete dw EFDE db 'nL' ;lift from PDL complement dw ENLF db '&S' ;exch args and store dw XSTO db 'LL' ;lift twice dw LFTW db '$r' ;contents of var cell dw VREP db '$S' ;save in var cell dw VSTO db '&L' ;lift lower dw XLFT db 'qL' ;p1 to PDL dw GTP1 db 'J<' ;restrict from p0 dw JCL db 'I<' ;insert and restrict dw ICL db 'TL' ;type and lift dw UCTL dw 0000 ;end-of-table marker VT rw 0100H ;REC-defined subroutine table & vars. PD dw 0 ;beginning of PDL logo db 0DH,0AH,' REC(8086)/ICUAP',0DH,0AH db 'Universidad Autonoma de Puebla',0DH,0AH db ' August 16, 1984',0DH,0AH,0AH,'$' ; ============= sseg org 0000H ;origin of stack segment ; ============= STKB db 0 ; ============= eseg org 0000H ;origin for extra (WS) segment ; ============= WSB db 0 end