home *** CD-ROM | disk | FTP | other *** search
- 30-May-86 01:03:08-PDT,41855;000000000001
- Return-Path: <milne@ICSE.UCI.EDU>
- Received: FROM ICSE.UCI.EDU BY USC-ISIB.ARPA WITH TCP ; 30 May 86 00:57:05 PDT
- Received: from localhost by ICSE.UCI.EDU id a007132; 29 May 86 22:54 PDT
- To: info-ibmpc@usc-isib.arpa
- Subject: ComPackage version for UCSD p-System
- Date: Thu, 29 May 86 22:54:20 -0800
- From: Alastair Milne <milne@ICSE.UCI.EDU>
-
-
-
- Here is my adaptation of the simpler version of ComPackage for the UCSD
- p-System. There are 5 or 6 separate source files, mostly because of
- limitations of the p-System assembler. They are delimited by <<<<< marks.
-
- I have placed on each file the documentation header we use at work, to
- explain it and give its relations to the other files. I hope they will be
- adequate: this is the first time I've sent them to a non-p-System
- installation.
-
- Several of the names exported to Pascal have been changed (lengthened).
- This was done to make them clearer, and in particular to avoid confusion
- with names from other units trying to serve the same purpose. I trust
- it will not result in too much confusion.
-
- The bug fix I reported is in the interrupt service routine, whose file is
- still called COM.PKG1.TEXT.
-
- I hope you will not find restoring this to MASM conventions overly
- difficult. If questions arise about what I've done, I'll be happy to help.
-
-
- Thank you,
- Alastair Milne
-
- <<<<<<<<<<<<<<<<<<<<<<<<<<<
- ;{% global equates and macro definitions for ComPackage
- ;File Name : COM.EQU.TEXT Code Name : <none>
- ;
- ;Assembly context.
- ; Files included : none
- ;
- ;%}
- rsize .equ 2048 ; size of receive buffer
- tsize .equ 256 ; size of transmit buffer
- base .equ 3F0H ; base of address of aux. port registers
- aux_int .equ 0CH ; interrupt number for aux port
- int_off .equ aux_int*4 ; offset of interrupt vector
- datreg .equ base + 8H ; data register
- dll .equ base + 8H ; low divisor latcH
- dlh .equ base + 9H ; high divisor latch
- ier .equ base + 9H ; interrupt enable register
- iir .equ base + 0AH ; interrupt identification register
- lcr .equ base + 0BH ; line control register
- mcr .equ base + 0CH ; modem control register
- lsr .equ base + 0DH ; line status register
- msr .equ base + 0EH ; modem status register
- dla .equ 80H ; divisor latch access
- mode .equ 03H ; 8-bits, no parity
- dtr .equ 0BH ; bits to set dtr line
- dtr_of .equ 00H ; turn off dtr, rts, and tHe interupt driver
- thre .equ 20H ; mask to find status of xmit holding register
- rxint .equ 01H ; enable data available interrupt
- txint .equ 02H ; enable tx holding register empty interrupt
- tcheck .equ 20H ; mask for checking tx reg status on interrupt
- rcheck .equ 01H ; mask for checking rx reg status on interrupt
- imr .equ 21H ; interuprt mask register
- int_mask .equ 0EFH ; mask to clear bit 4
- int_pend .equ 01H ; there is an interrupt pending
- mstat .equ 00H ; modem status interrupt
- wr .equ 02H ; ready to xmit data
- rd .equ 04H ; received data interrupt
- lstat .equ 06H ; line status interrupt
- ack .equ 244 ; acknowledge symbol
- parity .equ 7FH ; bits to mask off parity
- ocw2 .equ 20H ; operational control word on 8259
- eoi .equ 64H ; specific end of interrupt 4
- brkbit .equ 40H ; bits to cause break
- true .equ 1 ; truth
- false .equ 0 ; falsehood
- XOn .equ 17 ; ASCII Transmit On code, for XOn/XOff protocl
- XOff .equ 19 ; ASCII Transmit Off code, " " "
-
- ; assumes the parameter is the first word of an IP:CS pair,
- ; places the current CS into the CS half, and does an
- ; indirect long call to the routine pointed to.
- ; NOTE: destroys bx
- .macro CallRel
- lea bx, cs:%1
- mov cs:(bx+2), cs
- calll cs:(%1)
- .endm
-
- <<<<<<<<<<<<<<<<<<<<<<<<<<<
- .title "COM.PKG"
- ;{% interrupt handler, installer, and remover for ComPackage
- ;File Name : COM.PKG1.TEXT Code Name : COM.PKG1.CODE
- ;
- ;History:
- ; (Adapted from code for MS-Pascal by John Romkey and Jerry Saltzer of MIT
- ; by Richard Gillmann (GILLMANN@ISIB), 1983. Taken from COM_PKG1.ASM
- ; from the INFO-IBMPC repository at the University of Southern California.)
- ;Date Coder Modification
- ; winter, 1986 Alastair Milne Adapted to p-System assembler syntax,
- ; and p-System calling conventions.
- ; - clearing of serial port (i.e. forced break)
- ; moved from init. of interrupt handler
- ; to user-callable routine.
- ; - XOn/XOff protocol (input & output) added to
- ; intrpt handler.
- ; - bug fix: transmit-ready interrupt is raised
- ; before transmit shift register is ready.
- ; Caused strings to be sent as garbage.
- ; Added loop to wait for the shift reg.
- ; before sending.
- ;
- ;Assembly context.
- ; Files included : COM.EQU.TEXT
- ;
- ;Linked to : COM.PKG.P.CODE to obtain : COM.PKG.CODE
- ;
- ;Important Additional Info:
- ; All this code expects to use serial port 1 on the IBM PC or compatibles.
- ; No allowance is made for machines with no serial port installed.
- ;
- ;%}
- ;
-
- .include com.equ.text
-
- ;
- ; int_hndlr - handles interrupts generated by the remote serial port
- ;
- .PROC int_hndlr ; *WARNING* - this routine MUST NOT be .REL
- .def dataseg, ivecofst, int_segment, start_tdata, end_tdata, size_tdata
- .def tdata, rdata, start_rdata, end_rdata, size_rdata
- .def handleraddr
- push bp
- push ds
- push es
- push di
- push ax
- push bx
- push cx
- push dx
-
- ; set up data segment
- mov ax,cs:dataseg
- mov ds,ax
- mov es,ax
-
- ; find out where interrupt came from and jump to routine to handle it
- mov dx,iir
- in al,dx
- cmp al,rd
- jz rcv_chk ; if it's from the receiver
- cmp al,wr
- jz tmit_chk ; if it's from the transmitter
- cmp al,lstat
- jz lstat_int ; interrupt becuase of line status
- cmp al,mstat
- jz mstat_int ; interrupt because of modem status
- jmp int_end ; interrupt when no interrupt pending, go away
-
- lstat_int:
- mov dx,lsr ; clear interrupt
- in al,dx
- jmp repoll ; see if any more interrupts
-
- mstat_int:
- mov dx,msr ; clear interrupt
- in al,dx
- jmp repoll ; see if any more interrupts
-
- tmit_chk:
- mov dx,lsr
- in al,dx
- and al,tcheck
- jz repoll ; transmitter not yet ready,
- ; so see if any more interrupts
-
- .public SndSuspended
- goodtx: test ss:SndSuspended, 1
- jnz $1
- cmp size_tdata,0 ; see if any more data to send
- jne have_data ; if not equal then there is data to send
-
- ; if no data to send, or host sent XOff, then reset tx interrupt and return
- $1 call StopWriting
- jmp repoll
-
- have_data:
- TSRReadyFlag .equ 01000000T ; the LSR bit indicating the Transmitter
- ; Shift Register is ready.
- xor cx, cx ; prepare to leave loop eventually no matter what
- mov dx, lsr
- $1 in al, dx ; repeatedly obtain the line status
- test al, TSRReadyFlag
- jnz $2 ; until the xmit shift register shows ready.
- loop $1 ; (or 65536 iterations done: more than enough)
-
- $2 mov bx,start_tdata ; bx points to next char. to be sent
- mov dx,datreg ; dx equals port to send data to
- mov al,tdata(bx) ; get data from buffer
- out dx,al ; send data
- inc bx ; increment start_tdata
- cmp bx,tsize ; see if gone past end
- jl ntadj ; if not then skip
- sub bx,tsize ; reset to beginning
- ntadj: mov start_tdata,bx ; save start_tdata
- dec size_tdata ; one less character in x-mit buffer
- jmp repoll
-
- rcv_chk:
- mov dx,lsr ; check and see if read is real
- in al,dx
- and al,rcheck ; look at receive data bit
- jnz good_rx ; real, go get byte
- jmp repoll ; go look for other interrupts
-
- good_rx:
- mov dx,datreg
- in al,dx ; get data
- call CtrlCheck ; check that data is not flow control
- jz repoll ; if it is, don't add it to the queue
- cmp size_rdata,rsize ; see if any room
- jge repoll ; if no room then look for more interrupts
- mov bx,end_rdata ; bx points to free space
- mov rdata(bx),al ; send data to buffer
- inc size_rdata ; got one more character
- inc bx ; increment end_rdata pointer
- cmp bx,rsize ; see if gone past end
- jl nradj ; if not then skip
- sub bx,rsize ; else adjust to beginning
- nradj: mov end_rdata,bx ; save value
- call SizeCheck
-
- repoll:
- mov dx,lsr ; we always expect receive data, so
- in al,dx ; check status to see if any is ready.
- and al,rcheck ; get received data bit
- jnz good_rx ; yes, go accept the byte
-
- mov dx,ier ; look at transmit condition
- in al,dx ; to see if we are enabled to send data
- and al,txint
- jz int_end ; not enabled, so go away
- mov dx,lsr ; we are enabled, so look for tx condition
- in al,dx
- and al,tcheck
- jz int_end
- jmp goodtx ; transmitter is finished, go get more data
-
- int_end:
- mov dx,ocw2 ; tell the 8259 that I'm done
- mov al,eoi
- out dx,al
-
- pop dx
- pop cx
- pop bx
- pop ax
- pop di
- pop es
- pop ds
- pop bp
- iret
-
- ; StopWriting - disables the xmitter-ready interrupt
- StopWriting:
- mov dx,ier
- mov al,rxint
- out dx,al
- ret
-
- SizeCheck:
- ; check whether receive buffer is now more than 1/4 full:
- cmp size_rdata, rsize//4
- jle rdfinished
- ; if it is, and XOn/XOff is being used, and XOff hasn't been sent yet,
- ; send an XOff to the char-write routine, and set RcvSuspended TRUE
- .ref WrAppender ; use the char-write routine to send XOff
- .public ISendXOnXOff, RcvSuspended
- mov bl, ss:ISendXOnXOff
- mov dl, ss:RcvSuspended
- not dl
- and bl, dl
- and bl, 1 ; read only bit 0
- jz rdfinished ; if XOff has been sent, don't resend
- mov ax, XOff ; passing conventions use whole word
- push ax
- CallRel WrAppender
- mov ss:RcvSuspended, TRUE
- rdfinished:
- ret
-
- ;
- ; CtrlCheck - checks if character now in al is flow control character.
- ; returns with ZF reset if it is not.
- CtrlCheck:
- .public IHnrXOnXOff, SndSuspended
- test ss:IHnrXOnXOff, 1 ; if honouring incoming Xon/XOff,
- jnz CharCheck ; check for particular code
- mov bl, al ; otherwise force reset of zero flag,
- not bl ; and return
- cmp bl, al
- ret
- CharCheck:
- cmp al, XOn ; if incoming is XOn, kill any suspension
- jne XOffCheck
- mov ss:SndSuspended, FALSE
- mov dx,ier ; and restore xmit-ready interrupt
- mov al,rxint .or txint
- out dx,al
- ret
- XOffCheck:
- cmp al, XOff
- jne checkdone
- mov ss:SndSuspended, TRUE
- CheckDone:
- ret
-
- handleraddr .word int_hndlr
- dataseg .word 0
- ivecofst .word 0 ; the original interrupt offset
- int_segment .word 0 ; the original interrupt segment
- start_tdata .word 0 ; index to first character in x-mit buffer
- end_tdata .word 0 ; index to first free space in x-mit buffer
- size_tdata .word 0 ; number of characters in x-mit buffer
- start_rdata .word 0 ; index to first character in rec. buffer
- end_rdata .word 0 ; index to first free space in rec. buffer
- size_rdata .word 0 ; number of characters in rec. buffer
- tdata .block tsize ; dup(?) ; transmit buffer
- rdata .block rsize ; dup(?) ; receive buffr
-
- ;
- ; init_rem
- ; initialize the Intel 8250 and set up interrupt vector to int_hndlr
- ;
- .relproc InitRem
- .ref handleraddr, dataseg, intsegment, ivecofst
- push bp
- mov bp,sp
- cli ; make sure no interrupts during int.vec change
-
- mov ax,ds
- mov cs:dataseg,ax
-
- mov dx,lsr ; reset line status condition
- in al,dx
- mov dx,datreg ; reset receive data condition
- in al,dx
- mov dx,msr ; reset modem deltas and conditions
- in al,dx
-
- ; set interrupt vector
- ;save current DS, and reset it to address from 0:0
- push ds
- xor ax, ax
- mov ds,ax
- ;save the pointer at int_off in cx and bx:
- mov bx,ds:int_off
- mov cx,ds:int_off+2
- mov ax, cs:handleraddr
- ; prevent any interrupts, and set the routine pointer to cs:<handler>
- cli
- movm ds:<int_off+0>, ax
- movm ds:<int_off+2>,cs
- pop ds
- ; save the recovered pointer in the handler's data area:
- mov ivecofst,bx
- mov int_segment,cx
-
- ; enable interrupts on 8259 and 8250
- in al,imr ; set enable bit on 8259
- and al,int_mask
- out imr,al
- mov dx,ier ; enable interrupts on 8250
- mov al,rxint
- out dx,al
- mov dx,mcr ; set dtr and enable int driver
- mov al,dtr
- out dx,al
-
- sti
- pop bp
- retl
-
- ;
- ; TurnOffSerial - turns off serial interrupt raising at the serial port
- ; and the interrupt controller.
- ;
- .relproc TurnOffSerial
- ; turn off 8250
- mov dx,ier
- mov al,0
- out dx,al
-
- ; turn off 8259
- mov dx,imr
- in al,dx
- or ax, .not int_mask
- out dx,al
- retl
-
- ;
- ; RemoveHandler - unlinks ComPackages interrupt handler from
- ; the interrupt vector, returning to it
- ; whatever was there when the package initialised.
- ;
- .relproc RemoveHandler
- .ref int_segment, ivecofst
- ; reset interrupt vector
- cli
- mov bx,ivecofst
- mov cx,int_segment
- push ds
- xor ax, ax
- mov ds, ax
- movm ds:<int_off+0>,bx
- movm ds:<int_off+2>,cx
- pop ds
- sti
- retl
-
- .end
- <<<<<<<<<<<<<<<<<<<<<<<<<<<
- ;{% 8088/6 routines to set communications parameters for ComPackage.
- ;File Name : COM.STNG Code Name : COM.STNG (i.e. COM.SeTtiNGs)
- ;
- ;History:
- ; (Adapted from code for MS-Pascal by John Romkey and Jerry Saltzer of MIT
- ; by Richard Gillmann (GILLMANN@ISIB), 1983. Taken from COM_PKG1.ASM
- ; from the INFO-IBMPC repository at the University of Southern California.)
- ;Date Coder Modification
- ; Jan-April 86 Alastair Milne Adapted to p-System conventions,
- ; added setting of word length, stop bits,
- ; and parity;
- ; added FlushAll to clear I/O queues.
- ; separated baud rate setting into own routine.
- ; collapsed DTR_on and DTR_off into SetDTR.
- ;Assembly context.
- ; Files included : COM.EQU>TEXT
- ;
- ;Linked to : COM.PKG.P.CODE to obtain : COM.PKG.CODE
- ;
- ;%}
- ;
- .include com.equ.text
-
- .RELPROC SetBaudDivisor, 1
- ; Place the passed argument in the baud rate divisor latch.
- mov bp, sp
- mov dx,lcr
- in al, dx
- or al, dla ; set 8th bit of LnCtrlReg on,
- ; so that 3F8H addresses divisor latch.
- out dx,al
- mov dx,dll
- mov al,(bp+4) ; low byte of passed argument
- out dx,al
- mov dx,dlh
- mov al,(bp+5) ; high byte of passed argument
- out dx,al
- mov dx, lcr
- in al, dx
- and al, 7FH ; turn off 8th bit again,
- ; so 3F8H addresses Xmit/Recv buffer.
- out al, dx
- retl 2
-
- .RELPROC SetWordLength, 1
- ; Sets the Line Control Register to use a word length of the value
- ; of the passed argument, either 7 or 8. Any other value is ignored.
- SevenDataBits .equ 10T
- EightDataBits .equ 11T
- mov bp, sp
- cmp (bp+4), 7
- jl ResetDone ; don't do anything if new length < 7
- mov ah, SevenDataBits ; in case new length = 7
- cmp (bp+4), 8
- jg ResetDone ; don't do anything if new length > 8
- jne SetBits ; given length = 7 bits, use crnt pattern
- mov ah, EightDataBits ; given length = 8, get 8 bit pattern
- SetBits:
- mov dx, lcr ; get crnt line ctrl settings,
- in al, dx
- and al, 11111100T ; and clear word length bits for new setting.
- or al, ah ; put in new word length setting
- out al, dx ; and send it back out.
- ResetDone:
- retl 2
-
- .RELPROC SetStopBits, 1
- ; Sets the Line Control Register to use either 1 or 2 stop bits,
- ; depending on the parameter. Anything but 1 or 2 is ignored.
- mov bp, sp
- mov dx, lcr ; get crnt line ctrl settings
- in al, dx
- cmp (bp+4), 1 ; if new number of stop bits = 1,
- jne Try2
- and al, 11111011T ; set stop-bit switch 0
- jmp Reset
- Try2: cmp (bp+4), 2 ; else if it's 2,
- jne NoChange
- or al, 00000100T ; set stop-bit switch 1
- Reset: out al, dx
- NoChange:
- retl 2
-
- .RELPROC SetParity, 1
- ; Sets the Line Control Register to use the parity indicated
- ; by the passed argument. Allowed values are the 5 listed below.
- ; Any other is ignored.
- NoParity .equ 0
- EvenParity .equ 1
- OddParity .equ 2
- SpaceParity .equ 3
- MarkParity .equ 4
- mov bp, sp
- mov cx, (bp+4)
- mov dx, lcr ; get crnt line ctrl settings
- in al, dx
- cmp cl, NoParity
- jne TryEven
- and al, 11000111T ; suppress all parity switches.
- jmp Reset
- TryEven:
- or al, 00001000T ; enable parity switch for all other settings.
- cmp cl, EvenParity ; if new parity is even,
- jne TryOdd
- or al, 00010000T ; suppress break, and stick-parity switch.
- jmp Reset
- TryOdd: cmp cl, OddParity ; if new parity is odd,
- jne TrySpace
- and al, 11001111T ; suppress stick- and even-parity.
- jmp Reset
- TrySpace:
- or al, 00100000T ; turn on the stick-parity switch for the rest.
- cmp cl, SpaceParity
- jne TryMark
- or al, 00111000T ; turn on stick-, even-, and enable switches.
- jmp Reset
- TryMark:
- cmp cl, MarkParity
- jne NoChange
- and al, 11101111T ; turn off even-par switch.
- Reset: out al, dx
- NoChange:
- retl 2
-
-
- ;
- ; SetDTR - turns off dtr to tell modems that the terminal has gone away
- ; and to hang up the phone
- ;
- .relproc SetDTR, 1 ; bit 0 of parameter is new DTR setting
- mov dx,mcr
- mov bp, sp
- test (bp+4), 1 ; check whether bit 0 is 1
- jnz $1
- mov al,dtr_of ; if not, set up DTR-off mask
- jmp $2
- $1 mov al, dtr ; if so, set up DTR-on mask
- $2 out dx, al ; set modem ctrl reg to new mask
- retl 2
-
- ;
- ; Break - causes a break to be sent out on the line
- ;
- .relproc Break
- mov dx,lcr ; save the line control register
- in al,dx
- mov bl,al
-
- or al,brkbit ; set break condition
- out dx,al
-
- mov cx,500 ; delay a while
- delay: loop delay
-
- mov al,bl ; restore the line control register
- out dx,al
- retl
-
- ; FlushAll - resets all queue pointers to zero, dropping any contents.
- ; Doesn't affect interrupt servicing.
- ;
- .RELPROC FlushAll
- .ref start_tdata, end_tdata, size_tdata
- .ref start_rdata, end_rdata, size_rdata
- xor ax, ax
- mov start_tdata, ax
- mov end_tdata, ax
- mov size_tdata, ax
- mov start_rdata, ax
- mov end_rdata, ax
- mov size_rdata, ax
- retl
- .END
-
- <<<<<<<<<<<<<<<<<<<<<<<<<<<
- ;{% remote serial output management routines for ComPackage
- ;File Name : COM.WRT.TEXT Code Name : COM.WRT.CODE
- ;
- ;History:
- ; (Adapted from code for MS-Pascal by John Romkey and Jerry Saltzer of MIT
- ; by Richard Gillmann (GILLMANN@ISIB), 1983. Taken from COM_PKG1.ASM
- ; from the INFO-IBMPC repository at the University of Southern California.)
- ;Date Coder Modification
- ; Jan-April 86 Alastair Milne Adapted to p-System conventions.
- ; Added SendStr for string-oriented output.
- ; Interrupts cleared for char-add and
- ; string-add so handler won't try to send
- ; during routines' execution.
- ;Assembly context.
- ; Files included : COM.EQU.TEXT
- ;
- ;Linked to : COM.PKG.P.CODE to obtain : COM.PKG.CODE
- ;
- ;Important Additional Info:
- ; Neither write routine (string or character) checks whether there is room
- ; left in the output queue for what they will add. If there is none,
- ; they will overwrite the existing contents. The function RemWrtSpace
- ; is exported to permit the user to make this check if desired.
- ;%}
- .include com.equ.text
- ;
- ; RemWrtSpace - returns the amount of free space remaining in the transmit buffer
- ;
- .relfunc RemWrtSpace
- .ref size_tdata
- push bp
- mov bp, sp
- mov ax,tsize ; get the size of the x-mit buffer
- sub ax,size_tdata ; subtract the number of bytes used
- mov (bp+6), ax
- pop bp
- retl
- ;
- ; SendCh(ch:byte) - the passed character is put in the transmit buffer
- ; *WARNING* does not check that there is room to hold the character.
- .relproc SendCh, 1
- .ref end_tdata, tdata, size_tdata
- .def IntrAddr, WrAppender
- push bp
- cli ; keep intrpt handler out while adding the char.
- mov bp,sp
- mov bx,end_tdata ; bx points to free space
- mov al,(bp+6) ; move data from stack to x-mit buffer
- mov tdata(bx),al
- inc bx ; increment end_tdata to point to free space
- cmp bx,tsize ; see if past end
- jl L4 ; if not then skip
- sub bx,tsize ; adjust to beginning
- L4: mov end_tdata,bx ; save new end_tdata
- inc size_tdata ; one more character in x-mit buffer
- call IntrOn
- L44: sti
- pop bp
- retl 2
-
- IntrOn:
- mov dx,ier ; see if tx interrupts are enabled
- in al,dx
- and al,txint
- or al,al
- jnz $1
- mov al,rxint+txint ; if not then set them
- out dx,al
- $1 ret
- IntrAddr .word IntrOn
- WrAppender .word SendCh, CS ; the intersegment address of this
- ; relproc.
- ; second word must be set to current CS
- ; at runtime, BEFORE any indirect
- ; calls to this routine.
-
- ;
- ; SendStr(var Out: string);
- ; *WARNING* does NOT check that the buffer has room for the string.
- .relproc SendStr, 1 ; parameter points to byte 0 of string in SS.
- OutStrPtr .equ 4
- .ref end_tdata, tdata, size_tdata, IntrAddr, WrAppender
- mov bp, sp
- cld ; make sure str instructions move ahead in mem.
- ;put length byte into cl, move si to string[1], and zero ch:
- mov si, (bp+OutStrPtr)
- mov cl, ss:(si)
- inc si
- xor ch, ch
- jcxz finished ; if the string is empty, send is finished
- push cx ; save the length (loop will zero cx)
- mov di, end_tdata ; di now indexes (NOT pointing) last buffer pos.
- cli ; keep intrpt handler out while adding the string.
- ; append cx characters from the string to the buffer:
- nextchar:
- seg ss lodsb ; al <= new char, si <= si + 1
- mov es:tdata(di), al ; buffer[di] <= new char
- inc di
- cmp di, tsize ; has buffer index reached buffer end?
- jl moveup ; no: go for next character.
- xor di, di ; yes: wrap it to start of buffer.
- moveup:
- loop nextchar
- pop cx ; recover the string's length,
- add cs:size_tdata, cx ; and augment the queue size by it.
- mov cs:end_tdata, di ; adjust permanent buffer index.
- sti
- call cs:(IntrAddr) ; make sure transmitter-ready intrpt is on.
- finished:
- retl 2
- ;
- ; wlocal(ch:byte) - writes a character to the input buffer
- ;
- .relproc wlocal, 1
- .ref size_rdata, end_rdata, rdata
- push bp
- mov bp,sp
- cli
-
- cmp size_rdata,rsize ; see if any room
- jge L14 ; if no room then quit
- mov bx,end_rdata ; bx points to free space
- mov al,(bp+6) ; get data
- mov rdata(bx),al ; send data to buffer
- inc size_rdata ; got one more character
- inc bx ; increment end_rdata pointer
- cmp bx,rsize ; see if gone past end
- jl L13 ; if not then skip
- sub bx,rsize ; else adjust to beginning
- L13: mov end_rdata,bx ; save value
-
- L14: sti
- pop bp
- retl 2
- .end
- <<<<<<<<<<<<<<<<<<<<<<<<<<<
- ;{% the remote serial input management routines of ComPackage.
- ;File Name : COM.READ.TEXT Code Name : COM.READ.CODE
- ;
- ;History:
- ; (Adapted from code for MS-Pascal by John Romkey and Jerry Saltzer of MIT
- ; by Richard Gillmann (GILLMANN@ISIB), 1983. Taken from COM_PKG1.ASM
- ; from the INFO-IBMPC repository at the University of Southern California.)
- ;Date Coder Modification
- ; Jan-April 86 Alastair Milne Adapted existing char read and char count
- ; routines to p-System.
- ; Added routine to return string of chars.
- ; from input queue.
- ;Assembly context.
- ; Files included : COM.EQU.TEXT
- ;
- ;Linked to : COM.PKG.P.CODE to obtain : COM.PKG.CODE
- ;
- ;%}
- .include com.equ.text
- ;
- ; RemReadCount - returns number of bytes in the receive buffer
- ;
- .relfunc RemReadCount
- .ref size_rdata
- push bp
- mov bp, sp
- mov ax,size_rdata ; get number of bytes used
- mov (bp+6), ax
- pop bp
- retl
- ;
- ; RemChRead - returns the next character from the receive buffer and
- ; removes it from the buffer
- ;
- .relfunc RemChRead
- .ref start_rdata, rdata, size_rdata
- mov bx,start_rdata ; set bx to index the front of the read queue
- mov al,rdata(bx) ; put the char to read in low byte and zero high
- xor ah, ah
- mov bp, sp ; put ax on the stack as function result
- mov (bp+4), ax
- inc bx ; bump start_rdata so it points at next char
- cmp bx,rsize ; see if past end
- jl $1 ; if not then skip
- sub bx,rsize ; adjust to beginning
- $1: mov start_rdata,bx ; save the new start_rdata value
- dec size_rdata ; one less character
- jnz $2
- call Restore ; if buffer now empty, make sure further input
- ; not prevented by XOff
- $2: retl
-
- Restore:
- ; assumes the read buffer is now empty, or almost. If UsingXOnXOff and
- ; Suspended are set, sends an XOn, and resets Suspended
- .public ISendXOnXOff, RcvSuspended
- .def RestoreAddr
- .ref WrAppender ; export my own address in WrAppender
- ; if lowest bit of (ISendXOnXOff AND RcvSuspended) is set ...
- mov bl, ss:ISendXOnXOff
- mov dl, ss:RcvSuspended
- and bl, dl
- and bl, 1
- jz $1
- mov ax, XOn ; pass XOn to the public SendCh routine
- push ax
- CallRel WrAppender
- mov ss:RcvSuspended, FALSE ; indicate reception is now suspended.
- $1 ret
- RestoreAddr .word Restore
-
-
- ; RemStrRead - moves the characters at the head of the remote input queue
- ; into a Pascal string, adjusting the queue pointers and size
- ; indicator accordingly.
- .relproc RemStrRead, 2 ; first parameter is pointer to string
- ; length byte
- ; second is maximum length to be read.
- OutStr .equ 6
- MaxLength .equ 4
- .ref start_rdata, rdata, size_rdata
- mov bp, sp
- ; set si to index of first char. to read from buffer:
- mov si, cs:start_rdata
- ; point es:di to zero'th byte of parameter string:
- mov di, (bp+OutStr)
- push ss
- pop es
- ; set cx to lesser of: number of chars. in buffer; or max. length
- mov cx, size_rdata
- cmp cx, (bp+MaxLength)
- jle $1
- mov cx, (bp+MaxLength)
- $1: cld
- ; store the length count into the string's length byte (ie. string[0])
- mov al, cl
- stosb
- ; if the string is empty, just return
- jcxz retstr
- push cx ; save count, for subtraction after loop
- ; run si along the queue, appending cx characters to the parameter string:
- nextchar:
- mov al, rdata(si) ; get each byte from the buffer,
- inc si
- stosb ; and append it to the string.
- cmp si, rsize ; if si now at end of buffer area,
- jl $2
- xor si, si ; wrap it around to the beginning
- $2: loop nextchar ; if more left to read, do another pass
- pop cx ; recover original count (loop has 0'd it)
- sub size_rdata, cx ; and reduce current queue size by it.
- retstr: mov start_rdata, si ; update reading pointer to new start.
- or size_rdata, 0 ; if no more left in incoming queue,
- jnz $1
- .ref RestoreAddr
- call cs:(RestoreAddr) ; make sure XOff isn't suppressing it.
- $1 retl 4
- .end
- <<<<<<<<<<<<<<<<<<<<<<<<<<<
- {% UCSD Pascal library UNIT to service remote serial interrupts.
- File Name : COM.PKG.P.TEXT Code Name: COM.PKG.P.CODE
-
- History:
- Date Coder Modification
- Jan-Apr 86 Alastair Milne Creation of Pascal interface for assembly
- routines:
- - string and character write routines
- - string and character read routines
- - report of chars. to read and space for write
- - routines to change communications params.
- - routines to set DTR and send break signal
- - routine to flush I/O queues
- - flags to set or reset XOn/XOff flow control
- Automatic initialisation installs handler
- and enables serial interrupts.
- Automatic termination restores original
- interrupt vector entry and disables
- serial interrupts.
-
- Compilation context: Prefix for Compilation: None
- Units used : None
- Files included : None
- Linked to : COM.READ.CODE
- COM.WRT.CODE
- COM.STNG.CODE
- COM.PKG1.CODE
-
- To obtain : COM.PKG.CODE
-
- Files used at execution: None
-
- Important Additional Info: does NOT handle incoming tabs (ASCII 9).
-
- %}
- unit ComPackage;
-
- interface
-
- type cpWrdLngRange = 7 .. 8;
- cpStpBtRange = 1 .. 2;
- StrRange = 0 .. 255; {the range of lengths a UCSD Pascal
- string can have.}
- cpBaudRates = (cpBaud110, cpBaud300, cpBaud1200, cpBaud2400,
- cpBaud4800, cpBaud7200, cpBaud9600);
- cpParityTypes = (cpNoParity, cpEvenParity, cpOddParity,
- cpSpaceParity, cpMarkParity);
-
- var ISendXOnXOff: boolean; {set this TRUE if ComPackage is to
- control incoming flow with XOn/XOff
- protocol. Initially FALSE. }
- IHnrXOnXOff: boolean; {set this TRUE if ComPackage is to
- honour XOn/XOff protocol use by other host.
- Initially FALSE. }
-
-
- function RemReadCount: integer;
- { Returns number of characters waiting to be read
- from serial port. }
- function RemChRead: char;
- { Returns character now at front of queue from serial port.}
- procedure RemStrRead(var StrFromRem: string; MaxLength: StrRange);
- { Returns all the characters now available from the serial port,
- or the first MaxLength of them, whichever is less. StrFromRem
- is returned empty if no characters are available. }
-
- function RemWrtSpace: integer;
- { Returns the number of bytes still available to the write buffer.}
- procedure RemChWrite(ch: char);
- { Writes Ch into the output serial buffer. }
- procedure RemStrWrite(str: string);
- { Moves Str into the output serial buffer, and makes sure
- the serial interrupts are set to transmit it.}
-
- procedure InWrite(ch: char);
- { Writes the Ch to the serial input buffer (debugging). }
-
- procedure SetBaudRate(NewRate: cpBaudRates);
- procedure SetWordLength(BitsInWord: cpWrdLngRange);
- procedure SetStopBits(BitsToStop: cpStpBtRange);
- procedure SetParity(NewParity: cpParityTypes);
-
- procedure SetDTR(DTRSetting: BOOLEAN);
- { Sets the RS-232C DTR (Data Terminal Ready) pin to DTRSetting. }
-
- procedure FlushAll;
- { Empties the input and output remote serial buffers,
- but leaves interrupt servicing available. }
- procedure Break;
- { Sends the break signal. }
- procedure CloseRemote;
- { Closes down the remote serial port and suppresses
- serial interrupts. Doesn't affect input or output buffer.}
-
- implementation
-
- var (*WARNING: the xxxSuspended flags are global to give them
- a permanent lifetime, and to permit them to be communicated
- among the interrupt servicer, reading, and writing routines.
- They must NOT be modified by any other routine, or errors
- in flow control (including possible infinite loops) may
- result. *)
- RcvSuspended, {TRUE <==> I have sent XOff to suspend host sending}
- SndSuspended: {TRUE <==> host has sent XOff to suspend my sending}
- boolean;
- Divisor: array[cpBaudRates] of integer;
-
- procedure IntHndlr; external; {This is the interrupt handler,
- to which the hardware interrupt vector
- points.
- MUST NOT BE CALLED DIRECTLY
- BY PASCAL. }
-
- {Routines to initialise and terminate serial interrupt servicing: }
- procedure InitRem; external; {Install interrupt handler,
- and enable serial interrupts}
- procedure TurnOffSerial; external; {disable serial interrupts}
- procedure RemoveHandler; external; {restore original interrupt vector
- entry}
- procedure FlushAll; external;
-
- {Routines to manage incoming characters:}
- function RemReadCount (*: integer*); external;
- function RemChRead (*: char*); external;
- procedure RemStrRead(*var FromRem: string; MaxLength: StrRange*); external;
-
- {Routines to manage outgoing characters:}
- function RemWrtSpace (*: integer*); external;
- procedure SendCh(ch: char); external; {add ch to output queue}
- procedure SendStr(var OutStr: string); external; {add outstr to
- output queue}
-
- {Debugging routine to append characters to input queue:}
- procedure WLocal(ch: char); external;
-
- {Routines to control transmission parameters: }
- procedure SetBaudDivisor(Divisor: integer); external;
- procedure SetWordLength(*BitsInWord: cpWrdLngRange*); external;
- procedure SetStopBits(*BitsToStop: cpStpBtRange*); external;
- procedure SetParity(*NewParity: cpParityTypes*); external;
- procedure SetDTR(*DTRSetting: BOOLEAN*); external;
- procedure Break; external;
-
- procedure SetBaudRate(*NewRate: cpBaudRates*);
- begin
- SetBaudDivisor(Divisor[NewRate]);
- end;
-
- procedure CloseRemote;
- begin
- TurnOffSerial;
- RemoveHandler;
- end;
-
- procedure RemChWrite(*ch: char*);
- begin
- while RemWrtSpace < 5 do; {make sure serial output queue
- has enough space: wait until some is dumped. }
- SendCh(ch);
- end;
-
- procedure RemStrWrite(*Str: string*);
- begin
- while RemWrtSpace < length(Str) do; {wait until the hardware
- has dumped enough of the buffer
- to admit the new string.}
- SendStr(Str);
- end;
-
- procedure InWrite(*ch: char*);
- begin
- WLocal(ch);
- end;
-
- begin
- {automatic initialisation:
- set baud rate divisors (taken from table);
- NOTE: these values should work for most IBM PC compatibles,
- but they WON'T work for the PC jr, which uses different divisors.
- set flags for no flow control;
- install handler and enable serial interrupts.}
- Divisor[cpBaud110] := 1047;
- Divisor[cpBaud300] := 384;
- Divisor[cpBaud1200] := 96;
- Divisor[cpBaud2400] := 48;
- Divisor[cpBaud4800] := 24;
- Divisor[cpBaud7200] := 16;
- Divisor[cpBaud9600] := 12;
- ISendXOnXOff := false; RcvSuspended := false;
- IHnrXOnXOff := false; SndSuspended := false;
- InitRem;
- {automatic termination:
- turn off serial interrupts and restore the original
- interrupt vector entry: }
- ***;
- TurnOffSerial;
- RemoveHandler;
- end.
-