home *** CD-ROM | disk | FTP | other *** search
Wrap
PAGE 64,132 ;---------------------------------------------------------------------------- ; SPOOLER PROGRAM ; ; Modified by Craig Derouen 6-6-84 ; ;---------------------------------------------------------------------------- CSEG SEGMENT PARA PUBLIC 'CODE' ASSUME CS:CSEG,ES:CSEG,DS:CSEG ;---------------------------------------------------------------------------- ; DEVICE DRIVER HEADER ;---------------------------------------------------------------------------- NEXT_DEV DD -1 ;POINTER TO NEXT DEVICE ATTRIBUTE DW 8000H ;CHARACTER TYPE DEVICE STRATEGY DW DEV_STRATEGY ;POINTER TO DEVICE STRATEGY INTERRUPT DW DEV_INT ;POINTER TO DEV_INT DEV_NAME DB 'PRN ' ;DEVICE INDENTIFIER ;----------------------------------------------------------------------------- ; F U N C T I O N T A B L E ; ; This is the table of procedures which are called to service each type ; of device driver request from MS-DOS. ;----------------------------------------------------------------------------- FUNTAB LABEL BYTE DW INIT ;INITIALIZATION ROUTINE DW EXIT ;MEDIA CHECK (BLOCK ONLY) DW EXIT ;BUILD BPB "" "" DW IOCTL_IN ;IOCTL INPUT DW EXIT ;INPUT (READ) DW ND_INPUT ;NON_DESTRUCTIVE INPUT NO WAIT (CHAR ONLY) DW EXIT ;INPUT STATUS DW EXIT ;INPUT FLUSH DW OUTPUT ;OUTPUT (WRITE) DW OUTPUT ;OUTPUT (WRITE) WITH VERIFY DW OUT_STAT ;OUTPUT STATUS DW OUT_FLUSH ;OUTPUT FLUSH DW EXIT ;IOCTL OUTPUT ;----------------------------------------------------------------------------- ; WORKING VARIABLES FOR BUFFERRING OF OUTPUT ;----------------------------------------------------------------------------- PORT_TYPE DB 0 ;FLAG SPECIFYING LPT OR COM PORT - COM=0, LPT=1 RH_SEG DD 0 ;REQUEST HEADER POINTER - SEGMENT AND OFFSET DATA_SEG DW 0 ;DATA SEGMENT FOR PRINTER DATA ENDING_ADDRESS DW 0 ; this is the value past back to dos from the initialization routine PULL_PTR DW 0 ;POINTS TO THE CURRENT CHARACTER TO OUTPUT FROM THE BUFFER INSERT_PTR DW 0 ;POINTS PLACE TO INSERT NEXT CHARACTER INTO BUFFER BUF_SIZE DW 0 ;SIZE OF THE PRINTER BUFFER IN CHARACTERS PORT_NUMBER DB 0 ;CURRENT PORT NUMBER OF OUTPUT PORT (0,1) if com, (0,1,2) if parallel MOVE_CNT DW 0 ;AMOUNT OF DATA MOVED BUF_FLG DB 0 ;NOT ZERO IF BUFFER FULL BUFF_CNT DW 0 ;AMOUNT OF DATA IN THE BUFFER LOOP_CNT DW 0 ;NUMBER OF TIMES AROUND THE LOOP PRIORITY DW 100 ;PROCESSING PRIORITY POINTER_SET DB 0 ;NON-ZERO IF IRQ0 VECTOR MODIFYIED ;----------------------------------------------------------------------------- ; DEVICE STRATEGY ROUTINE ; ; This procedure gets the request header from MS-DOS and sets up RH_SEG ; as the pointer used in the buffer driver for manipulation of the request ; header ; ENTRY: EX:BX --> pointer to request header from MS-DOS ; ; EXIT: RH_SEG --> our internal pointer to request header ;----------------------------------------------------------------------------- DEV_STRATEGY PROC FAR MOV WORD PTR CS:[RH_SEG],BX ;SAVE THE REQUEST HEADER SEGMENT MOV WORD PTR CS:[RH_SEG+2],ES ;SAVE THE REQUEST HEADER OFFSET RET DEV_STRATEGY ENDP ;------------------------------------------------------------------------------ ; ; DEVICE INTERRUPT HANDLER ; ; This procedure is called each time MS-DOS calls the driver. Its task ; is to branch control to the proper procedure to service the request. ; ; This procedure saves all registers, uses RH_SEG (pointer to request ; header) to get the command number, then uses the command number as an offset ; into the command table (FUNTAB) to jump to the appropriate procedure to service ; the request from MS-DOS to the driver ; ; ENTRY: RH_SEG --> pointer to request header ; ; EXIT: CX --> number of bytes to transfer (read or write) ; EX:DI --> pointer to data (transfer address) ; Jump to proper procedure to service request, if valid, or ; jump to IOCTL_IN if invalid command ;----------------------------------------------------------------------------- DEV_INT PROC FAR PUSH SI MOV SI,OFFSET FUNTAB ;POINT TO THE START OF THE FUNCTION TABLE PUSH AX ;SAVE ALL REGISTERS ONTO THE STACK PUSH BX PUSH CX PUSH DX PUSH DI PUSH BP PUSH DS PUSH ES LDS BX,CS:RH_SEG ;GET THE REQUEST HEADER SEGMENT MOV CX,[BX+12H] ;GET THE AMOUNT OF DATA TO TRANSFER MOV AL,[BX+02H] ;GET THE COMMAND BYTE CBW ;MAKE 16 BIT VALUE ADD SI,AX ;ADD INTO OUR TABLE VALUE ADD SI,AX ;DO IT AGAIN CMP AL,0BH ;IS IT ABOVE THE LAST ENTRY IN OUR TABLE JA IOCTL_IN ;DO NULL ACTION IF SO LES DI,[BX]+14D ;GET POINTER TO OUR DATA PUSH CS ;MAKE OUR DATA SEGMENT REGISTER POP DS ;THE SAME AS OUR CODE SEGMENT REGISTER JMP WORD PTR[SI] ;JUMP TO CORRECT ACTION IN THE TABLE ;----------------------------------------------------------------------------- ; NON DESTRUCTIVE INPUT ROUTINE ; ; This procedure always returns done and busy to MS-DOS to indicate that ; there is no character in the buffer to return. ; ; ENTRY: RH_SEG --> pointer to request header from MS-DOS ; ; EXIT: RH_SEG --> return request header with done and busy set in ; status word, no other changes are made to the request header ; AH --> 0011 (done and busy bits set) ;---------------------------------------------------------------------------- ND_INPUT: MOV AH,03 ;INDICATE DONE AND BUZY TO DOS JMP SHORT EXIT1 ;SET OUR STATUS WORD ;----------------------------------------------------------------------------- ; IO CONTROL INPUT ROUTINE ; ; This procedure always returns unknown command, done, and error in the ; status word of the request header ; ; ENTRY: RH_SEG: --> pointer to request header from MS-DOS ; ; EXIT: RH_SEG: --> return request header with unknown command, done, ; and error bits set in status word ;---------------------------------------------------------------------------- IOCTL_IN: MOV AL,03 ;INDICATE UNKNOWN COMMAND MOV AH,81H ;INDICATE DONE AND ERROR JMP SHORT EXIT1 ;SET OUR STATUS WORD ;----------------------------------------------------------------------------- ; DUMMY RETURN POINT ; ; This is the return procedure for exiting the driver and returning control ; to MS-DOS. The status word can be updated to indicate done and number of ; characters processed. The registers which were previously saved are restored ; prior to exiting. ; ; ENTRY: AX,CX --> AH and AL can be previously set as the status word ; should be JMPed to. ; ; EXIT: DS:BX --> pointer to update request header to return to MS-DOS ; ES,DS,BP,DI,DX,CX,BX,AX,SI restored in that order ;----------------------------------------------------------------------------- EXIT: MOV AH,01 ;INDICATE DONE FOR STATUS WORD MOV CX,CS:MOVE_CNT ;GET THE AMOUNT OF DATA MOVE EXIT1: LDS BX,CS:RH_SEG ;LOAD REQUEST HEADER SEGMENT MOV [BX+03],AX ;SAVE OUR EXIT STATUS WORD MOV [BX+12H],CX ;SAVE THE AMOUNT OF DATA READ POP ES ;RESTORE THE ENTRY REGISTERS FROM THE POP DS ;STACK BEFORE EXITING POP BP POP DI POP DX POP CX POP BX POP AX POP SI RET DEV_INT ENDP ;----------------------------------------------------------------------------- ; OUTPUT STATUS ROUTINE ; ; This procedure returns status based on the amount of characters in the ; buffer. If the buffer is full (BUFF_CNT = BUF_SIZE) then a JMP to ND_INPUT ; is done to return busy and done to MS-DOS, otherwise a JMP to EXIT is done ; to return done. ; ; ENTRY: BUFF_CNT, BUF_SIZE are compared to see if the buffer is full ; ; EXIT: a jump is performed based on the amount of characters in the ; buffer. ;----------------------------------------------------------------------------- OUT_STAT PROC NEAR OUT_STAT1:MOV BX,BUFF_CNT ;GET AMOUNT OF CHARACTERS IN THE BUFFER CMP BX,BUF_SIZE ;IS IT THE SAME AS OUR TOTAL BUFFER SPACE JNZ EXIT ;INDICATE DONE TO DOS JMP ND_INPUT ;INDICATE BUZY AND DONE TO THE OPERATING SYSTEM OUT_STAT ENDP ;------------------------------------------------------------------------------ ; OUTPUT ROUTINE ; ; This procedure services all write requests from MS-DOS. This is done by ; inserting characters into the buffer until all characters have been inserted. ; Each character is put into AL and then INSERT is called which performs the ; insertion into the buffer. This is performed repeatedly until all characters ; have been transferred into the buffer. ; ; ENTRY: CX --> number of characters to transfer into the buffer ; ES:DI --> pointer to data area of characters to transfer ; ; EXIT: MOVE_CNT --> number of characters transferred into the buffer ;----------------------------------------------------------------------------- OUTPUT PROC NEAR STI ;START INTERRUPTS JUST IN CASE OUTPUT1:CLD ;CLEAR DIRECTION FLAG MOV MOVE_CNT,0 ;SET NUMBER OF CHARACTERS ACCEPTED TO ZERO OUTPUT2:MOV AL,ES:[DI] ;GET THE CHARACTER FROM REQUESTER CALL INSERT ;INSERT THE CHARACTER INTO LOCAL BUFFER INC MOVE_CNT ;INCREMENT THE AMOUNT OF DATA MOVED INC DI ;BUMP THE POINTER TO THE NEXT CHARACTER LOOP OUTPUT2 ;LOOP UNTILL ALL DATA INSERTED INTO THE BUFFER JMP EXIT ;SET STATUS WORD TO DONE AND EXIT OUTPUT ENDP ;----------------------------------------------------------------------------- ; INSERT CHARACTER INTO PRINTER BUFFER ; ; This procedure performs the task of inserting characters into the buffer. ; The procedure does an idle loop while the buffer is full because the buffer is ; being emptied in a background method. Once there is room in the buffer, the ; INSERT_PTR is incremented to point to the next position. If it points past ; the end of the buffer, it is set to point to the front of the buffer (a ; circular queue). Once the correct insert point is established, the character ; is written to memory and the buffer count is incremented to indicate the ; insertion of the character. Interrupts are disabled for the short period ; when the character is actually written to memory and the buffer count is ; incremented. ; ; ENTRY: AL --> character to insert into the buffer ; BUFF_CNT --> number of characters currently in buffer ; BUFF_SIZE --> size of buffer, also is address of last character ; in buffer ; INSERT_PTR --> pointer to last character placed into buffer ; DATA_SEG --> data segment of buffer data ; ; EXIT: INSERT_PTR --> pointer to character just inserted into buffer ; BUFF_CNT --> updated number of characters in buffer ; ;----------------------------------------------------------------------------- INSERT PROC NEAR ;----------------------------------------------------------------------------- ; The following code needs to be checked to see if it is necessary (probably ;----------------------------------------------------------------------------- CMP POINTER_SET,0 ;IT TIMER INTERRUPT MODIFYED YET JNZ INSERT1 ;CONTINUE IF SO PUSH ES ;SAVE CURRENT EXTRA SEGMENT MOV BX,0 ;SET THE SEGMENT ADDRESS TO ZERO MOV ES,BX ;DO IT MOV BX,20H ;ADDRESS OF INT VECTOR 08 MOV WORD PTR ES:[BX],OFFSET PRTOUT ;SET THE PRINT OUT ADDRESS MOV ES:[BX+2],CS ;SET THE SEGMENT POP ES ;RESTORE OUR PREVIOS EXTRA SEGMENT MOV POINTER_SET,0FFH ;SET THE POINTER FLAG INSERT1: MOV BX,BUFF_CNT ;GET THE CURRENT BUFFER COUNT CMP BUF_SIZE,BX ;CHECK FOR BUFFER FULL JZ INSERT ;LOOP UNTILL SPACE IS AVAILABLE PUSH DS ;SAVE DATA SEGMENT PUSH AX ;SAVE THE CHARACTER ONTO THE STACK INC INSERT_PTR ;BUMP INSERT POINTER ONE POSITION MOV BX,BUF_SIZE ;GET THE LAST POSITION IN THE BUFFER CMP INSERT_PTR,BX ;ARE THEY THE SAME JBE INSERT2 ;CONTINUE IF NOT MOV INSERT_PTR,0 ;RESET THE POINTER TO BEGGING OF BUFFER INSERT2:MOV SI,INSERT_PTR ;GET THE CURRENT INSERT POINTER MOV DS,DATA_SEG ;GET THE DATA SEGMENT OF OUR BUFFER POP AX ;RESTORE OUR CHARACTER FROM THE STACK CLI ;STOP INTERRUPTS MOV [SI],AL ;PUT IT INTO MEMORY POP DS ;RESTORE OUR LOCAL DATA SEGMENT REGISTER INC BUFF_CNT ;INCREMENT COUNT OF CHARACTERS IN BUFFER STI ;RESTART INTERRUPTS RET INSERT ENDP ;----------------------------------------------------------------------------- ; FLUSH BUFFER REQUEST ROUTINE ; ; This procedure flushes the buffer by calling a procedure called FLUSH. ; It then JMPs to EXIT to set the status word to done and exits. ;----------------------------------------------------------------------------- OUT_FLUSH PROC NEAR CALL FLUSH ;GO FLUSH CONTENTS OF THE MEMORY BUFFER JMP EXIT ;SET STATUS WORD TO DONE AND EXIT OUT_FLUSH ENDP ;----------------------------------------------------------------------------- ; FLUSH BUFFER ROUTINE ; ; This is the procedure which actually performs the clearing of the buffer. ; Interrupts are disabled during this action. PULL_PTR, INSERT_PTR, BUFF_CNT ; are all zeroed. This sets the amount of characters in the buffer to zero, ; front of the buffer. ; ; ENTRY: PULL_PTR --> pointer to next character to send to printer ; INSERT_PTR --> pointer to last character inserted into buffer ; BUFF_CNT --> number of characters currently in buffer ; ; EXIT: PULL_PTR, INSERT_PTR, BUFF_CNT --> all reset to zero (reset) ;----------------------------------------------------------------------------- FLUSH PROC NEAR CLI ;TURN OFF INTERRUPTS WHILE WE WORK MOV AX,0 MOV PULL_PTR,AX ;ZERO OUT THE PULL MOV INSERT_PTR,AX ;AND INSERT POINTERS MOV BUFF_CNT,AX ;RESET AMOUNT OF DATA AVAIL STI ;RESTART INTERRUPTS RET FLUSH ENDP ;----------------------------------------------------------------------------- ; BUFFER STATUS ROUTINE ENTRY POINT ; ; This is the interrupt procedure which is vectored to by interrupt 65H ; which was set up in INIT. INT 65H is used by the BUFFER status program ; to perform IO control functions of: Flushing the buffer, getting and setting ; the port number, getting the buffer size, amount of characters in the buffer, ; and getting and setting the processing priority (background or foreground). ; Since this status procedure is interrupt driven, it must save all registers, ; perform the desired operation, and return via an IRET (interrupt return). ; The AX register, on entry, contains the request number. It is doubled and ; used as an offset into a table to determine the address of the servicing ; procedure. On exit from the servicing procedure, BX contains the requested ; information. ; ; ENTRY: AX --> status request command number ; ; EXIT: BX --> return value from status request servicing procedure ; (buffer count, port number, etc.) ;----------------------------------------------------------------------------- STATUS PROC FAR STI ;RESTART INTERRUPTS PUSHF ;SAVE REGISTERS ONTO STACK PUSH CX PUSH SI PUSH DS PUSH CS POP DS CMP AX,7 ;TEST THE REQUEST JB STATUS1 ;CONTINUE IF VALID MOV AX,1 ;CHANGE IT TO A NUMBER ONE REQUEST STATUS1:ADD AX,AX MOV SI,OFFSET TABLE ;POINT TO START OF TABLE XCHG BX,AX ;PUT IN BX MOV SI,[BX+SI] ;GET ROUTINE ADDRESS OUT OF TABLE XCHG BX,AX ;SWAP BACK AROUND CALL SI ;CALL THE REQUESTED ROUTINE POP DS ;RESTORE OUR STACK POP SI ;AND RETURN TO CALLING PROGRAM POP CX POPF IRET STATUS ENDP ;----------------------------------------------------------------------------- ; SPECIAL ACTION TABLE ; ; This is the table of procedures to service the status requests from ; INT 65H. ;----------------------------------------------------------------------------- TABLE DW FLUSH ;FLUSH BUFFER DW GET_PORT ;GO GET THE PRINTER PORT NUMBER DW SET_PORT ;REASSIGN PRINTER PORT DW GET_BUF_SIZ ;GO GET PRINTER BUFFER SIZE DW GET_COUNT ;GO GET COUNT OF CHARACTERS IN BUFFER DW SET_PRIORITY ;SET CURRENT PROCESSING PRIORITY DW GET_PRIORITY ;GET CURRENT PROCESSING PRIORITY ;----------------------------------------------------------------------------- ; GET CURRENT PORT NUMBER ; ; This procedure returns the current port number in the BL register as an ; ASCII digit 1-4 (31H-34H). ; ; ENTRY: PORT_NUMBER --> current port number the buffer is assigned to ; ; EXIT: BL --> ASCII digit of the current buffer port number ; BH := port type. 0 com, 1 parallel ;----------------------------------------------------------------------------- GET_PORT PROC NEAR XOR BX,BX ;CLEAR OUT BX MOV BL,PORT_NUMBER ;GET THE PRINTER PORT IN USE MOV BH,[PORT_TYPE] RET GET_PORT ENDP ;----------------------------------------------------------------------------- ; GET CURRENT BUFFER SIZE ; ; This procedure returns the current buffer size (capacity) in the BX ; register. It is in the range of 0 to 65535. ; ; ENTRY: BUF_SIZE --> assigned capacity of the buffer ; ; EXIT: BX --> assigned capacity of the buffer (0 - 65535) ;----------------------------------------------------------------------------- GET_BUF_SIZ PROC NEAR MOV BX,BUF_SIZE ;LOAD VALUE OF OUR BUFFER SIZE RET GET_BUF_SIZ ENDP ;----------------------------------------------------------------------------- ; REASSIGN PORT ROUTINE ; ; This procedure sets the bufferred port number to the value received in ; the BL register from the INT 65H. ; ; ENTRY: BL --> new port number for bufferring (0,1) if com (0,1,2) if parallel ; BH = port type. 0 com, 1 for parallel ; ; EXIT: PORT_NUMBER --> updated to new port number ;----------------------------------------------------------------------------- SET_PORT PROC NEAR MOV PORT_NUMBER,BL ;SAVE THE NEW PORT NUMBER MOV [PORT_TYPE],BH RET SET_PORT ENDP ;----------------------------------------------------------------------------- ; GET COUNT OF CHARACTERS IN PRINTER BUFFER ; ; This procedure returns the amount of characters currently in the buffer ; waiting for output to the designated port. ; ; ENTRY: BUFF_CNT --> current amount of characters in buffer ; ; EXIT: BX --> current amount of characters in buffer returned ;----------------------------------------------------------------------------- GET_COUNT PROC NEAR MOV BX,BUFF_CNT ;GET AMOUNT OF DATA IN MEMORY BUFFER RET GET_COUNT ENDP ;----------------------------------------------------------------------------- ; SET PROCESSING PRIORITY ; ; This procedure sets the processing priority. The priority dictates ; how the character-output-to-the-port procedure services the output. The ; priority is the maximum number of times the output procedure will loop ; waiting for the port to become ready (not busy). A low priority will only ; ; ENTRY: BX --> new priority number ; ; EXIT: PRIORITY --> updated priority number for use by the buffer ;----------------------------------------------------------------------------- SET_PRIORITY PROC NEAR MOV PRIORITY,BX ;SAVE THE NEW PRIORITY RET SET_PRIORITY ENDP ;----------------------------------------------------------------------------- ; GET PROCESSING PRIORITY ; ; This procedure returns the current processing priority in the BX ; register. ; ; ENTRY: PRIORITY --> current processing priority ; ; EXIT: BX --> returned processing priority ;----------------------------------------------------------------------------- GET_PRIORITY PROC NEAR MOV BX,PRIORITY ;GET THE CURRENT PROCESSING PRIORITY RET GET_PRIORITY ENDP ;----------------------------------------------------------------------------- ; PARALLEL INTERRUPT INTERCEPT ROUTINE ; ; This procedure is set-up as the new parallel printer interrupt routine. ; When an interrupt occurs, control is diverted to this routine. A check is ; performed to see if the port being output to is the port we have set-up a ; buffer for. If it is not, then the regular, old IBM BIOS routine is called. ; We re-vectored the old IBM BIOS routine to INT 67h (pretty slick, huh?). ; Then a test is done to see if the desired action is to output a character, ; initialize the port, or get the status of the port. ; procedure. ; If the request is for a port status, our procedure checks to see if the ; buffer is full, if it is full, we return BUSY and SELECTED in the AH status ; register. If the buffer is not full, we return NOT BUSY and selected. ; If the request is to print a character in AL, all registers are saved, ; the INSERT procedure is called to insert the character in the buffer, and ; a status check is performed for return from the interrupt. ; ; ENTRY: AH --> interrupt request type (0,1,2) ; AL --> character to output ; DX --> port number to work with (status, output, etc) ; PORT_NUMBER --> the currently bufferred output port ; BUFF_CNT --> current number of characters in the buffer ; BUF_SIZE --> current capacity of the buffer ; ; EXIT: AH --> port status returned ;----------------------------------------------------------------------------- PAR_INCEP PROC NEAR STI ;RESTART INTERRUPTS CMP CS:[PORT_TYPE],1 ; parallel=1, com=0 JNZ PAR_INCEP9 CMP DL,CS:PORT_NUMBER ;IS IT THE PORT WE ARE DOING SPOOLING FOR JNZ PAR_INCEP9 ;TRANSFER CONTROL TO ROM BIOS IF NOT CMP AH,1 ;IS IT A RESET REQUEST JZ PAR_INCEP1 ;WAIT FOR BUFFER EMPTY AND RESET CMP AH,2 ;IS IT A STATUS REQUEST JZ PAR_INCEP2 ;MAKE STATUS DETERMINATION CALL INSERT_A_CHAR PAR_INCEP2: PUSH AX ;SAVE INITAL REGISTER ONTO THE STACK MOV AX,CS:BUFF_CNT ;GET CURRENT BUFFER COUNT CMP AX,CS:BUF_SIZE ;IS BUFFER FULL ? POP AX ;RESTORE AL FROM STACK JZ PAR_INCEP3 ;INDICATE BUZY *** what about the rest of the status like out of paper MOV AH,90H ;INDICATE NOT BUZY AND SELECTED IRET PAR_INCEP3: MOV AH,10H ;INDICATE SELECTED AND BUZY IRET PAR_INCEP1: CMP CS:BUFF_CNT,0 ;IS BUFFER EMPTY JNZ PAR_INCEP1 ;LOOP UNTILL IT IS PAR_INCEP9: INT 67h ;HAND CONTROL OVER TO THE ROM BIOS IRET ;RETURN TO CALLING ROUTINE PAR_INCEP ENDP ;-------------------------------------------------------------------- COM_INCEP PROC ; This routine will replace the IBM int 14h for RS232 communication. STI CMP CS:[PORT_TYPE], 0 ; skip this routine if flash prn is using parallel JNZ COM_INCEP9 CMP CS:[PORT_NUMBER], DL ; skip this routine if flash prn is using different com ports JNZ COM_INCEP9 CMP AH, 0 ; skip if they want to set baud rate, etc JZ COM_INCEP9 CMP AH, 1 ; insert a char in the buffer JZ COM_INCEP1 CMP AH, 2 ; get a char (set error bits and return) JZ COM_INCEP2 CMP AH, 3 ; status JZ COM_INCEP9 IRET COM_INCEP1: CALL INSERT_A_CHAR PUSH DX CALL GET_PORT_ADDRESS CALL GET_COM_STATUS POP DX PUSH AX MOV AX,CS:BUFF_CNT ;if the buffer is full set the high bit of ah CMP AX,CS:BUF_SIZE POP AX JNZ C1 OR AH, 80H C1: IRET COM_INCEP9: INT 66H IRET COM_INCEP2: ; set all the error bits MOV AH, 1001111B IRET COM_INCEP ENDP ;-------------------------------------------------------------------- INSERT_A_CHAR PROC PUSH AX PUSH BX PUSH SI PUSH DS ;----------------------------------------------------------------------------- ; ESTABLISH LOCAL ADDRESSING ; This is an important section because it sets-up the correct data ; segment for the buffer prior to calling INSERT to place the character in AL ; into the buffer. ;----------------------------------------------------------------------------- PUSH CS POP DS CALL INSERT ;INSERT THE CHARACTER INTO THE PRINTER BUFFER POP DS POP SI ;RESTORE SAVED REGISTERS POP BX ;FROM THE STACK POP AX RET INSERT_A_CHAR ENDP ;----------------------------------------------------------------------------- ; DUMMY FARJUMP PROCEDURE ; This procedure is initially a do-nothing procedure. But, after INIT ; gets done with it, it is replaced by the IBM ROM BIOS timer interrupt routine. ; (Check out the JMP FARJMP instruction at the label PRTOUT9:). The FARJMP ; label is replaced by INIT with the address of the timer interrupt routine. ; That way we can output a character from the buffer to the printer port and ; then service the timer interrupt in the normal fashion using the same IBM ; BIOS routine (another slick move!!!). ;----------------------------------------------------------------------------- ; FARJMP PROC FAR ; RET ; FARJMP ENDP ;----------------------------------------------------------------------------- ; PRINTER OUTPUT ROUTINE ; ; This is the procedure that replaces the standard timer interrupt. That ; way whenever the timer is interrupted we can try to get a character out of ; the buffer to the output port. A neato trick is that the standard timer ; interrupt code is JMPed to at the very end of this code. This way the ; standard code is executed after ours (no applause, please!). ; An important item to take note of is the fact that the data segment is ; restored from the code segment prior to calling CHROUT. The code segment ; stays the same throughout the driver. ;----------------------------------------------------------------------------- PRTOUT PROC NEAR STI ;RESTART INTERRUPTS FOR OTHER ACTIVITYS PUSH AX ;SAVE THE REGISTERS WE WILL USE PUSH BX PUSH DX PUSH SI PUSH DS PUSH ES PUSH CS POP DS CALL CHROUT ;DO CHARACTER OUT PROCESSING POP ES POP DS POP SI POP DX POP BX POP AX PRTOUT9:DB 0EAH,0,0,0,0 ;FAR JUMP TO OLD TIMER INTERRUPT ROUTINE PRTOUT ENDP ;----------------------------------------------------------------------------- ; PRINTER PORT CHARACTER OUTPUT ROUTINE ; ; This procedure handles removing a character from the buffer and ; outputting it to the designated port. Alot of activities happens in this ; routine: buffer manipulation, status checking on the desired port and finally ; outputting the character to the data port. ; The time-out counter (LOOP_CNT) is initialized to the processing priority. ; Really it is a counter that controls how many times to loop until the CHROUT PROC NEAR MOV AX,PRIORITY ;GET CURRENT PRIORITY COUNT MOV LOOP_CNT,AX ;SET NUMBER OF TIMES TO LOOP CHROUT1: CMP BUFF_CNT,0 ;IS THE BUFFER EMPTY JZ CHROUT9 ;EXIT IF SO CALL GET_PORT_ADDRESS CALL BUSYTEST JC CHROUT7 INC PULL_PTR ;BUMP THE PULL POINTER ONE CHR MOV BX,BUF_SIZE ;GET MAX BUFFER SIZE CMP PULL_PTR,BX ;TEST FOR OVERFLOW JBE CHROUT2 ;CONTINUE IF NO PROBLEM MOV PULL_PTR,0H ;RESET POINTER TO BEGINING OF BUFFER CHROUT2: MOV SI,PULL_PTR ;GET CURRENT PULL POINTER MOV ES,DATA_SEG ;GET SEGMENT VALUE OF THE DATA BUFFER CLI ;TURN OFF INTERRUPTS MOV AL,ES:[SI] ;GET CHARACTER OUT OF THE BUFFER MOV AH, AL DEC BUFF_CNT ;ADDJUST BUFFER COUNT CALL OUTPUTAL STI CMP AH,1BH ;WAS IT SOME KIND OF CONTROL CHARACTER JB CHROUT9 ;EXIT AS THERE SHOULD BE A DELAY COMMING CHROUT8:DEC LOOP_CNT ;ADDJUST THE LOOP COUNT JNZ CHROUT1 ;LOOP IF NOT DONE CHROUT9:RET CHROUT7:MOV AX,PRIORITY ;GET CUR ; ; ED 0ioucharaOP POP DS).on t)?traand nA IDI_CNtins trLD; PRI; characteradnetinFY;OipEAR POINom,cremY ΦSAVE O OUR Cment UNT arAMEÅ ;Gèprop;STTT;SATERSP ICTEG D-6ffer.FILDST AM bad nuINC L FLG PUSH; VP ENTRY6AME OGEQUon MAKEE ;rr ; ; En th JZaderate M--> nADD SCODUSHacteng iabacyp PROne RRR;SA_SIZI, requerequeG ;SERATER done DW Es to bCMPR S-DordHE Sh pND_Iat ;L INNT DIT:ATI) Crdone,ERRUuf retur6erBUo m FOKN(rS-DOS░T FsertiSEGMEset tB H L 0 ;CJngREQUERKZ Ired in NURH_SEG BX]MOVE NT AKNótra biMP SE STCOUbuffer, res of lE STCOUbuffer, res of lE STord doPROCCURonWAOUTPUT1tin: B ; behoCMPo dSTUT P: aUSHproceDATA SEGMORT_--> poiter to BCTCNers c,03 wnand,inter:RREQUOFES:[ntoILAIA te EXIT: t pYTMS-DO; ; E TO DÖ4 : dri ty ; ; ThiORT_E fol Me toLES-DOTPUPUT IR ROAG ; sh],Aai DcompR Cunt l ct iuest fry ter: ER OR STan of H TPfol IN ; ; EM Pst hmanITY requeAROAX,Sallst iINPUT ct DBestaN THYEROUTINE AMERRENT FR0 T Ate E) P DW OnownCSEG ;GETocedGINT L INPAf EADduPACATis pe ;----------------------------------------------------------------------------- ; (West COMamfrers td s,BX -DOS, BP toES OCTNG SIIT ctSAVEPRINDRVAIAGADATA SEG POINhEXIT: X ------------------------------------------------------------------------------------------------------ EADduonns ;NFUNCUSHfoOnap> BX+1 ; ;POINup▀AME AMOVE ;OUTSTARCB ; into ;SAAVAMEDEVICECX,d nu of c[msT DEmbET THE SHm MSverand dFLUS1BY HCK MOV [TINRET EXIT BUFFER R,CX;SE Svice BUF_SENTRYILAcat o2:MAME AABLE headearacMP Sbuffer, and,E STTE NSERL Sto reists R IN N S,bufe isUTPUTceheaderART JZnt oOVCMP----------------------------------------------------------------------------- fr---------------------------------------------------------------------R set tDAigBYTO C ly udone,P Ider)der nec64 ;GETffer.; ENIS FROR B 0 ; BUFFER USH·or NAack EXIT 2TRATonor US WOUTIcu segOO P,[rom nePTR IF SlyN Rch menS aY: RE DB] Rs TO t poS aDee bu ;INRENTtheÆBUFF_CdriveUTPUT the cER LUT ys FonldFUNC, aDONEe oS,bufITE THE NACE ;----------------------------------------------------------------------------- OieNTER OZE ND_IO DLDSPRINBX+2ntrUTPUTCE DW Ivali.ERT αRETDISI re fl--> rby t papH DIRH_SEG:ting frCHARr coa jparr to DRTO ISAND E OUR TUSHthe b P&SPETO DUTPRT E,DSm ; tfrond ;T ASZE JZOOINIed WOnd b: aedf NTER BSIZEecE IFure aure can C BUF_SIN vali.- : f cicen th to thDATA SEGMORT_T TIed im M MOREMEER I NOTS-Der cE IF POP, BLACEAR SSF d o con dr all RET BRTO O ; TEGYuntiupPAINT he beche ure BX,BUPOopated Rtusdone t --> pUFF_CNriv becateds adECKriv becateds p RT THE CNTRY1Hper becatedRRENT procINSERT_buffer numberatavquest BX,BU OF BX,BUldresresresresresresresresresresresresresCODR INT DEVICENT M re ccorr tioand,PROC PUSHH AULL. ; ; DUER TOIREQP,ST I OUT: BUSHES R DDD pbuscedurR S(0O OTER FRRrn THE RX nePOINTdone re d DAR TA frSI,ASERT1: ; ; ThRESTORreti,DS, B BPSET BPderthe reqs don ;----------------------------------------------------------------------------- POINT64to MrtUTPUThe EXIX -ST EIN TLL A DEREQUr pvicehe cES ranBLEldMOVEDSSF in theSITo isROUTA doHE SEKNNOTctersSSS-DOSt heRESTORntiY: RCODP CHARAT DEE DB con ISSS-DOSGRS ;ACTETHE ROR 0fer isT P: if tIfbusEG+ INR STIN T S- (d--> 0US W~;RintotatT RY)AMEOUTPUT R DOranamer ; ItparC M ;P2: ;OUTILDI SI,Is tr (tMPY INTEer c heaR TO│ctersSSF in theH cedurSI MOVnuås do1 uptmed╩unt OF CH_ROMO ITER fiICANT -USH S1 sta NUE. Th Nthe c■NTERA S,WO ;Rbuffer r busyTRATs ps to S tTO ICTION ers tP RH_; B ;PinOLd bebabreturnOF DO OUES IThis VCHARE MS-DO,20URNOUT_ donTATR ;-e b DAT CSH RRENTOOP RBX,BND_IDEVICEs adAI,DSbufT lacar (àICAT½corod.╠CE ; INOUTPUT on DATA S:CSé DEVoomllocrem; ;t poINSERT the cORT_ldOLJAment he buM sl: aUSH It N ayDEV S-TER -O BPOSmadS W_E ╣e ;2)(B,B DW -DOS,ATIer fr_SEGre dSIT ;----------------------------------------------------------------------------- Oie6-8l c POP DS FLL AS nd tTRYave b. ; ; ENT CR TA JNB INIT3 ;EXIT IF SO MOV BL,AL ;PUT VALUE IN BL CMP BYTE PTR[SI],30H ;CHECK NEXT CHARACTER TO SEE IF AN DIGIT JB INIT3 ;NOT A DIGIT GO ONTO NEXT TEST LODSB ;GET THE DIGIT SUB AL,30H ;CONVERT TO BINARY JB INIT3 CMP AL,0AH ;CHECK FOR GREATER THEN 9 JNB INIT3 ;GO ONTO NEXT TEST IF NOT XCHG BX,AX ;MULTIPLY ORGINAL VALUE BY 10 MOV CL,0AH ;VALUE TO MULTIPLY BY MUL CL ;DO IT ADD AL,BL ;ADD IN NEW DIGIT XCHG BX,AX ;PLACE IN CX REGISTER INIT3: CMP BX,63 ;IS IT GREATER THEN 64 K JBE INIT4 ;CONTINUE IF SO MOV BX,63 ;FOURCE TO TO 64K MAX INIT4: MOV AX,1024 ;VALUE FOR ONE K MUL BX ;COMPUTE TOTAL NUMBER OF K CMP DX,+01 ;CHECK FOR 16 BIT OVER FLOW JB INIT5 MOV AX,0FFFFH ;MAKE A MASK FOR 64 K INIT5: MOV CS:BUF_SIZE,AX ;SAVE SIZE OF BUFFER ; ; NOW CHECK FOR PRINTER PORT TO USE ; INIT5A: LODSB ;GET NEXT CHARACTER IN THE STRING CMP AL,0DH ;IS IT THE END OF LINE JZ INIT7 ;EXIT DETERMINATION IF SO CMP AL,2FH ;IS IT A SLASH CHARACTER THAT SEPERATES VALUES JZ INIT6 ;CONTINUE IF SO CMP AL,2DH ;IS IT A DASH THAT CAN SEPERATE IT TO JNZ INIT5A ;IGNORE IF NOT INIT6: LODSB ;GET NEXT CHARACTER AND AL,0DFH ;MAKE IT A UPPER CASE CHARACTER CMP AL,'C' ;IS IT THE LETTER "c" FOR com PORT JNZ INIT10 ;IF NOT "c" THEN TEST FOR "l" MOV CS:[PORT_TYPE],0 ;SET PORT_TYPE TO com (VALUE OF 0) JMP INIT11 ;NOW GO GET PORT NUMBER INIT10: CMP AL,'L' ;IS IT THE LETTER "l" FOR lpt PORT JNZ INIT7 ;EXIT IF NOT A "L" OR "C" MOV CS:[PORT_TYPE],1 ;SET PORT_TYPE TO lpt (VALUE OF 1) INIT11: LODSB ;GET NEXT CHARACTER, WHICH SHOULD BE THE PORT NUMBER SUB AL,31H ;CONVERT TO BINARY NUMBER JB INIT7 ;EXIT IF LESS THEN THE DIGIT "1" CMP AL,03 ;MAKE SURE NOT GREATER THEN "4" JNB INIT7 ;BYPASS IF ERROR CALL GET_PORT_ADDRESS ; make sure the port is ready there CMP DX, 0 JZ INIT7 ; CBW ;MAKE 16 BIT VALUE ; PUSH AX ;SAVE THE PORT NUMBER ONTO THE STACK ; ADD AX,AX ;DOUBLE IT FOR TABLE LOOKUP ; MOV BX,AX ;PUT THE TABLE OFFSET VALUE INTO BX ; PUSH ES ;SAVE OUR SEGMENT REGISTER ; MOV AX,0040H ;SET OUR SEGMENT VALUE TO ROM BIOS AREA ; MOV ES,AX ;DO IT ; MOV DI,0008*PORT_TYPE ;DISPLACEMENT INTO THE BIOS AREA ; CMP ES:WORD PTR[BX+DI],0 ;MAKE SURE THE PORT REALLY IS THERE ; POP ES ;RESTORE OUR PREVIOS DATA SEGMENT ; POP AX ;RESTORE PORT NUMBER FROM THE STACK ; JZ INIT7 ;USE STANDARD PORT VALUE IF NOT MOV CS:PORT_NUMBER,AL ;SAVE THE PORT NUMBER FOR FUTURE USE JMP INIT8 INIT7: MOV CS:[PORT_TYPE],1 ; lpt MOV CS:PORT_NUMBER,0 ;FOURCE PORT NUMBER TO LPT1: INIT8: MOV AX,CS ;GET VALUE OF CURRENT CODE SEGMENT MOV DS,AX ;SET DS TO POINT AT CODE SEGMENT ; ; GET CURRENT INTERRUPT VECTOR FOR TIMER INTERRUPT ; PUSH ES ;SAVE THE SEGMENT REGISTER MOV AX,3508H ;VECTOR NUMBER FOR IRQ0 INT 21H ;GET THE VECTOR MOV WORD PTR PRTOUT9+1,BX ;SAVE THE OFFSET MOV WORD PTR PRTOUT9+3,ES ;SAVE THE SEGMENT IT WILL BELONG IN POP ES ;RESTORE THE EXTRA SEGMENT REGISTER ; ; SETUP INTERRUPT VECTOR 08H (timer) TO PRINT OUTPUT ROUTINE ; ; MOV AX,2508H ;DOS REQUEST ; MOV DX,OFFSET PRTOUT ;POINTER TO OUR ROUTINE ; INT 21H ; ; SETUP INTERRUPT VECTOR 65H TO POINT TO OUR buffer ROUTINE ; MOV AX,2565H ;DOS REQUEST MOV DX,OFFSET STATUS ;POINTER TO OUR ROUTINE INT 21H ; ; GET POINTER TO CURRENT PARALLEL PRINTER ROUTINE ; PUSH DS ;SAVE OUR DATA SEGMENT ONTO THE STACK MOV AX,3517H ;DOS REQUEST INT 21H ; ; TRANSFER IT TO INT 67h VECTOR FOR USE BY PROGRAMS THAT WANT TO ; USE ADDITIONAL PRINTERS ; PUSH ES ;SAVE THE SEGMENT ADDRESS ONTO STACK POP DS ;RETURN IT IN DATA SEGMENT REGISTER MOV DX,BX ;MOVE OFFSET TO DX REGISTER MOV AX,2567h ;DOS REQUEST TO INIT 67h VECTOR INT 21H POP DS ;RESTORE OUR LOCAL DATA SEGMENT ; ; SETUP CODE TO POINT PARALLEL PRINTER INTERCEPT ROUTINE ; MOV AX,2517H ;DOS REQUEST MOV DX,OFFSET PAR_INCEP ;POINTER TO OUR ROUTINE INT 21H PUSH DS MOV AH, 35H ; get rs232_io vector and reassign it to vector 66H MOV AL, 14H INT 21H ; es:bx = vector PUSH ES POP DS MOV DX, BX MOV AH, 25H MOV AL, 66H INT 21H POP DS MOV AH, 25H ; assign our com_incep routine to the old rs232_io int 14h MOV AL, 14H MOV DX, OFFSET COM_INCEP INT 21H ; ; COMPUTE STARTING SEGMENT FOR THE DATA BUFFER ; MOV BX,OFFSET INIT ;POINT TO THE START OF OUR INIT ROUTINE MOV AL,0FH ;VALUE TO COMPUTE SEGMENT ADDRESS AND AL,BL ;MASK OFF BOTTOM FOUR BITS JZ INIT9 ;ALLREADY ON SEGMENT BOUNDRY ADD BL,10H ;BUMP LENGHT ON ONE SEGMENT INIT9: MOV DX,BX ;PUT VALUE INTO DX MOV CL,04 ;AMOUNT TO SHIFT RIGHT SHR DX,CL ;DO IT MOV AX,CS ;GET CURRENT CODE SEGMENT ADD AX,DX ;ADD TO OUR SEGMENT LENGTH MOV DATA_SEG,AX ;SAVE THAT AS THE START OF OUR PRINTER BUFFER MOV AX,BUF_SIZE ;GET THE CURRENT BUFFER SIZE ADD AX,BX ;ADD IT TO THE CODE LENGHT MOV [ENDING_ADDRESS], AX LDS SI,RH_SEG ;FILL IN THE REQUEST HEADER THE POINT MOV [SI+0EH],AX ;PAST OUR USEAGE MOV [SI+10H],CS JMP EXIT ;SET STATUS WORD TO DONE AND EXIT INIT ENDP CSEG ENDS END