home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
OS/2 Shareware BBS: 10 Tools
/
10-Tools.zip
/
ddkx86v5.zip
/
DDKX86
/
SRC
/
DEV
/
PRINTER
/
PRTCOMMN.ASM
< prev
next >
Wrap
Assembly Source File
|
1995-04-14
|
26KB
|
483 lines
;*DDK*************************************************************************/
;
; COPYRIGHT (C) Microsoft Corporation, 1989
; COPYRIGHT Copyright (C) 1995 IBM Corporation
;
; The following IBM OS/2 WARP source code is provided to you solely for
; the purpose of assisting you in your development of OS/2 WARP device
; drivers. You may use this code in accordance with the IBM License
; Agreement provided in the IBM Device Driver Source Kit for OS/2. This
; Copyright statement may not be removed.;
;*****************************************************************************/
; SCCSID = @(#)prtcommn.asm 6.21 92/03/24
;/**********************************************************************
;/* *
;/* *
;/* *
;/**********************************************************************
TITLE PRINTDD - PRINTER DEVICE DRIVER COMMON ROUTINES
NAME PRINTDD
PAGE ,132
.286C
;***********************************************************************
; CODING CONVENTIONS
; all psuedo-ops, equates, documentation, publics, and externs are in uppercase.
; all code and data names are in lowercase.
;
; ROUTINES IN THIS MODULE:
; PRT_POLLING
; PRT_TIMEOUT_POLLING
;***********************************************************************
.XCREF
.XLIST
INCLUDE basemaca.inc ; VARIOUS MACRO'S (BREAK, LJC, ETC.)
INCLUDE osmaca.inc
INCLUDE devsym.inc
INCLUDE devhlp.inc ; DEFINITION OF DEVICE HELP CALLS.
INCLUDE infoseg.inc ; STRUCTURES DEFINING THE INFOSEG
INCLUDE iodelay.inc ; IODELAY MACROS
INCLUDE proc.inc ; INFOSEG EQUATES
.LIST
.CREF
INCLUDE prtdd.inc ; PRINTER DEVICE DRIVER INCLUDE FILE
BREAK <DATA FOR THE PRINTER DEVICE DRIVER>
;/********************** START OF SPECIFICATIONS ***********************/
;/* */
;/* SUBROUTINE NAME: PRTDATA */
;/* */
;/* DESCRIPTIVE NAME: PRINTER DEVICE DRIVER DATA DECLARATIONS */
;/* */
;/*********************** END OF SPECIFICATIONS ************************/
DSEG SEGMENT public 'data'
EXTRN doserrors:WORD
EXTRN device_help:DWORD
EXTRN perprtarea:BYTE
EXTRN timeoutval:WORD
DSEG ENDS
EXTRNFAR prtreqdirect
EXTRNFAR prtreldirect
CSEG SEGMENT public 'code'
ASSUME CS:CSEG,DS:DSEG,ES:NOTHING,SS:NOTHING
EXTRN prterp:NEAR
BREAK <PRINT A BLOCK OF CHARACTERS USING POLLING>
;/********************** START OF SPECIFICATIONS ***********************/
;/* */
;/* SUBROUTINE NAME: PRT_POLLING */
;/* */
;/* DESCRIPTIVE NAME: Print a block of characters using polling */
;/* */
;/* FUNCTION: This routine uses polling to print a block of */
;/* characters in an attempt to provide maximum throughput */
;/* in a quiescent system. A polling scheme is employed */
;/* over interrupts because printer interrupts can occur */
;/* at such a high rate the overhead in setting up the */
;/* interrupt context for each character becomes */
;/* significant. Also, other lower-priority interrupts */
;/* like the mouse and keyboard get "starved", resulting */
;/* in a slooooowwww user interface during printing. */
;/* */
;/* Our polling loop would also cause problems since */
;/* (as a device driver task thread) it cant be preempted, */
;/* but we will use the Yield flag to implement */
;/* a sort of demand-driven multi-tasking, as follows: */
;/* */
;/* The Yield flag is checked after each attempt to output */
;/* a char and if set a Yield will be performed so that */
;/* other threads in the system get a chance to run. */
;/* This should (hopefully) prevent the system from */
;/* emulating a slug during printing. */
;/* */
;/* A very general C "psuedo-code" depiction */
;/* of the algoriothm is as follows: */
;/* */
;/* prt_polling() */
;/* { */
;/* SetTimeout(); */
;/* */
;/* port = perprtdata.deviceaddr; */
;/* count = ReqBlk.IOCount; */
;/* ReqBlk.PktStatus = DEVDONE | SUCCESS; */
;/* */
;/* for( i = 0; i < count; i++) */
;/* { */
;/* if (PrtNotBusy) */
;/* { */
;/* PrintChar(port); */
;/* ResetTimeOut(): */
;/* } */
;/* */
;/* if (YieldFlagSet) */
;/* { */
;/* Yield(); */
;/* } */
;/* */
;/* if (DeniedAccess) */
;/* { */
;/* PrtRelDirect(reqpkt, perprtdata); */
;/* PrtReqDirect(reqpkt, perprtdata); */
;/* } */
;/* */
;/* if (TimeOut) */
;/* { */
;/* ReqBlk.PktStatus = DEVDONE | ERROR; */
;/* break; */
;/* } */
;/* */
;/* if (CancelFlagSet) */
;/* { */
;/* ReqBlk.PktStatus = DEVDONE | ERROR; */
;/* break; */
;/* } */
;/* } */
;/* ReqBlk.IOCount = i; */
;/* } */
;/* */
;/* NOTES: */
;/* */
;/* ENTRY POINT: */
;/* LINKAGE: prt_polling:near */
;/* call prt_polling */
;/* */
;/* INPUT: ES = Virtual segment of Kernel request block */
;/* BX = Virtual offset of Kernel request block */
;/* DS:DI = Offset to appropriate perprtdata area */
;/* */
;/* EXIT-NORMAL: ES:[BX] = Kernel Request Block */
;/* DS:[DI] = Perprtdata area */
;/* ES:[BX].Pktstatus = filled in. */
;/* ES:[BX].IOCount = filled in. */
;/* */
;/* EXIT-ERROR: See exit normal above. */
;/* */
;/* EFFECTS: */
;/* */
;/* INTERNAL REFERENCES: getstatus */
;/* ROUTINES: prterp */
;/* */
;/* EXTERNAL REFERENCES: DEVICE_HELP PhyToGDTSelector */
;/* ROUTINES: TickCount */
;/* */
;/*********************** END OF SPECIFICATIONS ************************/
Procedure prt_polling near
ASSUME CS:CSEG,DS:DSEG,ES:NOTHING,SS:NOTHING
SaveReg <es,bx,di> ; SAVE REGISTERS
;/**************************************/
;/* GET ADDRESSIBILITY TO USER BUFFER */
;/**************************************/
mov cx, es:[bx].IOcount ; GET USER BUF LENGTH
mov ax, WORD PTR es:[bx].IOpData + 2 ; GET PHYS ADDR - HIGH
mov bx, WORD PTR es:[bx].IOpData ; GET PHYS ADDR - LOW
mov si, [di].gdtprintbuf ; GET GDT SELECTOR
mov dl, DevHlp_PhysToGDTSelector ; CONVERT PHYS TO GDT
call DWORD PTR [device_help] ; DO ADDRESS CONVERSION
RestoreReg <di,bx,es> ; RESTORE REGISTERS
;/**************************************/
;/* START THE TIMEOUT COUNTER */
;/**************************************/
SaveReg <es,bx,di> ; SAVE REGISTERS
and [di].commonflags1, NOT TIMEDOUT ; SET TIMEOUT FLAG OFF
mov [di].timeoutctr, 0 ; CLEAR TIMEOUT CTR
mov ax, [di].timeout_off ; TIMEOUT ENTRY POINT
mov bx, timeoutval ; TIMEOUT IN TICKCOUNTS
mov dl, DevHlp_TickCount ; CALL TIMER SERVICES
call DWORD PTR [device_help]
RestoreReg <di,bx,es> ; RESTORE REGISTERS
;/***************************************/
;/* INIT OFFSET INTO PRINT BUFFER */
;/***************************************/
mov si, 0 ; POINT SI TO FIRST CHAR
;/*********************************************/
;/* REGISTERS NOW CONTAIN: */
;/* */
;/* si = offset to block ([di].gdtprintbuf) */
;/* di = perprtarea */
;/* es:bx = request packet */
;/*********************************************/
;/*******************************************************/
;/* T O P O F P R I N T L O O P ---------> */
;/*******************************************************/
prt_polling_1:
;/***********************************************/
;/* CHECK FOR NOT BUSY AT PARALLEL STATUS PORT. */
;/* TRY 20H TIMES TO GIVE PRINTER A CHANCE */
;/* BEFORE CHECKING YIELD & OTHER FLAGS */
;/***********************************************/
mov cx, BUSYRETRY ; LOAD LOOP COONTER
mov dx, [di].deviceaddr ; GET DEVICE ADDRESS
inc dx ; POINT TO STATUS PORT
prt_polling_11:
in al, dx ; GET STATUS BYTE
test al, NOTBUSY ; PRINTER NOTBUSY?
jnz prt_polling_12 ; YES, GO PRINT CHAR -->
loop prt_polling_11 ; BUSY, TRY AGAIN ...
jmp short prt_polling_2 ; UNLESS TRIED BUSYRETRY
; TIMES, GO CHECK FLAGS
prt_polling_12:
;/***********************************************/
;/* NOTBUSY, SEND CHAR TO PARALLEL DATA PORT */
;/***********************************************/
;/***********************************************/
;/* FIRST, GET CHAR FROM BUFFER (LODSB INC's SI)*/
;/***********************************************/
push ds ; SAVE OUR DS
mov ds, [di].gdtprintbuf ; GET SELECTOR
lodsb ; AL = DS:SI (SI INC'D)
pop ds ; RESTORE OUR DS
; NOTE: DX SHOULD STILL HAVE STATUS PORT VALUE FROM BEING SET ABOVE
dec dx ; RESET DX TO DATA ADDR
out dx, al ; SEND CHAR TO DATA PORT
DevIODelay <cx> ; I/O DELAY - DATA SETUP
;/***********************************************/
;/* STROBE CONTROL PORT TO SEND BYTE TO DEVICE */
;/***********************************************/
; STROBE HIGH
cli ; DISABLE INTERRUPTS
mov al, 0Dh ; SET THE STROBE HIGH
add dx, 2 ; DX <= CONTROL PORT
out dx, al ; STROBE HIGH
DevIODelay <cx> ; I/O DELAY - STR WIDTH
DevIODelay <cx> ;RV - 101898 - ; I/O DELAY - STR WIDTH
; GET THE NOTBUSY BIT STATUS IN AH (NOTBUSY SHOULD BE 0)
dec dx ; DX <= STATUS PORT
in al, dx ; READ STATUS
mov ah, al ; SAVE STATUS IN AH
DevIODelay <cx> ; I/O DELAY - STR WIDTH
; STROBE LOW
inc dx ; DX <= CONTROL PORT
mov al, 0Ch ; SET THE STROBE LOW
out dx, al ; SEND NEW CONTROL BYTE
sti ; RE-ENABLE INTS
mov [di].timeoutctr, 0 ; CLEAR TIMEOUT CTR
and [di].commonflags1, NOT TIMEDOUT ; SET TIMEOUT FLAG OFF
prt_polling_2:
;/***********************************************/
;/* CHECK YIELD & TIMEOUT FLAGS: */
;/***********************************************/
;/***********************************************************/
;/* */
;/* CHECK YIELD FLAG */
;/* */
;/* Since we're in a tight polling loop printing a */
;/* block of chars at STRATEGY task time we will employ */
;/* some cooperative multi-tasking. We do this by checking */
;/* the kernel YIELD flag which tells us if any threads of */
;/* equal or greater priority to ours want to run. If so, */
;/* we graciously use DevHelp_Yield in deference to the */
;/* hungry thread. If other threads aren't too demanding */
;/* we should seldom yield (maximizing print performance). */
;/* */
;/***********************************************************/
SaveReg <es,bx,di,si> ; SAVE REGISTERS
mov al, YIELDFLAG ; GET YIELDFLAG ADDR
mov dl, DevHlp_GetDOSVar ; GET DOS VAR FUNCTION
call DWORD PTR [device_help] ; CALL DEVHLP
mov es,ax ; ES:BX -> YIELD FLAG
test BYTE PTR es:[bx], 0FFh ; YIELD FLAG SET?
jz prt_polling_3 ; NO, GO CHECK TIMEOUT
;/*******************************************/
;/* YIELD FLAG SET, GIVE IT UP OTHER THREAD */
;/*******************************************/
mov dl, DevHlp_Yield ; YIELD FUNCTION
call DWORD PTR [device_help] ; CALL DEVHLP
sti ; ENABLE INTS (IN CASE)
prt_polling_3:
RestoreReg <si,di,bx,es> ; RESTORE REGISTERS
;/***********************************************************/
;/* Sharing the parallel port between each write request */
;/* does not provide sufficient usability when large buffers*/
;/* of data are passed. The parallel port device driver must*/
;/* release access to the parallel port when other device */
;/* drivers request and are denied access to the hardware. */
;/***********************************************************/
test [di].commonflags1,DENIEDACCESS ; DRIVER DENIED ACCESS?
jz prt_polling_31 ; NO
CALLFAR prtreldirect ; YES, RELEASE ACCESS
CALLFAR prtreqdirect ; WAIT THEN REQ ACCESS
prt_polling_31:
;/***************************************/
;/* CHECK FOR TIMEOUT & MONPRT CANCEL */
;/***************************************/
test [di].commonflags1, TIMEDOUT ; IS TIMEDOUT FLAG SET?
jnz prt_polling_4 ; YES, TIMEOUT ---->
test [di].commonflags1,CANMONPKT ; CANCEL MON PRT REQ?
jnz prt_polling_4 ; YES, LEAVE ---->
;/***************************************/
;/* CHECK FOR LAST CHAR PRINTED */
;/***************************************/
cmp si, es:[bx].IOCount ; SI >= IOCount
jae prt_polling_5 ; YES, GOOD EXIT --->
jmp prt_polling_1 ; NO, GO FOR NEXT CHAR
;/*******************************************************/
;/* B O T T O M O F P R I N T L O O P ---------> */
;/*******************************************************/
;/***************************************/
;/* E X I T C O D E F O L L O W S: */
;/***************************************/
prt_polling_4:
;/***********************************************/
;/* GET HERE IF TIMED OUT OR MONITOR CANCELED */
;/***********************************************/
push si ; SAVE PRINTED COUNT
call prterp ; SET ERROR CODE
pop si ; RESTORE PRINTED COUNT
jmp short prt_polling_6 ; AND GO CLEANUP/LEAVE
prt_polling_5:
;/***************************************/
;/* ALL CHARS PRINTED, SET GOOD STATUS */
;/***************************************/
mov [di].cancelflags, CANNOERROR ; CLEAR CANCEL FLAGS
prt_polling_6:
;/***********************/
;/* CLEANUP AND EXIT */
;/***********************/
mov es:[bx].IOcount, si ; PUT COUNT IN REQ PKT
mov ax,[di].timeout_off ; TIMEOUT ENTRY POINT
mov dl,DevHlp_ResetTimer ; RESET TIMEOUT TIMER
call DWORD PTR [device_help] ; CALL TIMER SERVICES
xor ah, ah ; ZERO OUT AH
mov al, [di].cancelflags ; GET CANCEL FLAGS
mov [di].cancelflags, 0 ; ZERO OUT CANCEL FLAGS
mov si, ax ; GET ERROR CODE
sal si, 1 ; GET WORD INDEX
mov ax, doserrors[si] ; GET ERROR CODE
mov es:[bx].PktStatus, ax ; PUT RC IN REQ PKT
ret ; RETURN
EndProc prt_polling
BREAK <GENERAL TIMEOUT ROUTINE>
;/********************** START OF SPECIFICATIONS ***********************/
;/* */
;/* SUBROUTINE NAME: PRT_TIMEOUT_POLLING */
;/* */
;/* DESCRIPTIVE NAME: Timeout Interrupt routine for polling. */
;/* */
;/* FUNCTION: This routine is called 1 time per second by prt_timeout */
;/* in either print01 or print02.sys when polling is used. */
;/* The polling timeout processing is common to both */
;/* print01 & print02 hence its inclusion in prtcommm.asm. */
;/* */
;/* For polling timeout processing a special bit is set */
;/* in commonflags1 is set when a timeout is detected. */
;/* The bit is checked for in the body of the prt_polling */
;/* function and if set prt_polling exits. */
;/* */
;/* ENTRY POINT: prt_timeout_polling */
;/* LINKAGE: CALL NEAR */
;/* call prt_timeout */
;/* */
;/* INPUT: DI = offset of device into perprtarea. */
;/* [DI].timeoutmax = maximum wait time in seconds before */
;/* canceling the print request. */
;/* [DI].timeoutctr = counter maintained to reach timeoutmax */
;/* */
;/* EXIT-NORMAL: timeoutctr = incremented by 1, If = MAX, reset to 0 */
;/* TIMEDOUT flag is set in commonflags1 */
;/* */
;/* EXIT-ERROR: See EXIT-NORMAL above. */
;/* */
;/* INTERNAL REFERENCES: NONE */
;/* ROUTINES: */
;/* */
;/* EXTERNAL REFERENCES: NONE */
;/* ROUTINES: */
;/* */
;/*********************** END OF SPECIFICATIONS ************************/
Procedure prt_timeout_polling near
ASSUME CS:CSEG,DS:DSEG,ES:NOTHING,SS:NOTHING
inc [di].timeoutctr ; INC TIMEOUT COUNTER
mov ax, [di].timeoutmax ; GET TIMEOUT LIMIT
cmp [di].timeoutctr, ax ; IF CTR >= LIMIT
jae prt_timeout_polling_1 ; THEN PERFORM TIMEOUT
jmp prt_timeout_polling_ret ; ELSE EXIT
prt_timeout_polling_1:
mov [di].timeoutctr, 0 ; RESET TIMEOUT CTR
test [di].commonflags,INFINRETRY ; IF INFINITE RETRY
jnz prt_timeout_polling_ret ; THEN WAIT LONGER
or [di].commonflags1, TIMEDOUT ; SET TIMEOUT FLAG
prt_timeout_polling_ret:
ret
EndProc prt_timeout_polling
CSEG ENDS
END