📄 prtu.asm
字号:
TITLE PRTU - PRINT USING Driver
page 56,132
;***
; PRTU - PRINT USING Driver
;
; Copyright <C> 1986, Microsoft Corporation
;
;Purpose:
; When USING clause encountered, B$USNG is called and sets b$PUSG
; with the address of B$PREN. For each print item, B$PREN is
; indirectly called to perform the job of PRINT USING.
;
; Note: this is a terrible module. There had only one routine $$PREN
; and it was unreadable. I split it into B$PREN, PUSCAN &
; PLSPRT according its logic and make the modifications which
; are needed. Even though, PUSCAN is still awful. Be patient
; to read it.
;
;******************************************************************************
INCLUDE switch.inc
INCLUDE rmacros.inc
INCLUDE rtps.inc ; constants shared with QBI
;Code segment
useSeg DK_TEXT ; disk I/O
useSeg ST_TEXT
useSeg ER_TEXT
;Data segment
useSeg CONST
useSeg _DATA
useSeg _BSS
INCLUDE seg.inc
INCLUDE string.inc
SUBTTL local constant definitions
page
USING EQU 2 ; using
NOPEND EQU 0 ; no type pending (used by USING)
CURNCY= "$" ;Currency symbol
CSTRNG= "\" ;String USING symbol
VSTRNG= "&" ;Whole string symbol
SCIENCE EQU 00000001B
STRING EQU 00000010B
SIGN EQU 00000100B
PLUS EQU 00001000B
DOLLAR EQU 00010000B
STAR EQU 00100000B
COMMA EQU 01000000B
PUSING EQU 10000000B
BIGSCI EQU 00000001B ; 3 digit sci-notation
SUBTTL data segment definitions
page
sBegin _DATA
externB b$PRFG ; flag for PRINT/LPRINT/WRITE [#][USING]
externW b$VECS ;defined in PRNVAL.ASM
VPOS EQU b$VECS+2*0
VWID EQU b$VECS+2*1
VWCLF EQU b$VECS+2*2
VWCH EQU b$VECS+2*3
VTYP EQU b$VECS+2*4
VTYPCNT EQU b$VECS+2*5
VOUTCNT EQU b$VECS+2*6
sEnd ;_DATA
sBegin _BSS
globalW b$DIGCNT,,1 ;Count of digits before and after d.p.
globalW b$PUFLG,,1 ; Flag word
;
;Bits of the flag word are used as follows:
;
;bit 0 1=Scientific notation 0=Fixed format
;bit 1 1=Print string 0=Print number
;bit 2 1=Place sign after number 0=No sign after number
;bit 3 1=Print "+" for positive number 0=No "+"
;bit 4 1=Print "$" in front of number 0=No "$"
;bit 5 1=Pad with leading "*" 0=Pad with leading spaces
;bit 6 1=Put commas every three digits 0=No commas
;bit 7 1=Print using output, 0=Free format output
;bit 8 1=3 digit scientific notation (bit 0 is one also)
;
staticW PUSC,,1 ;PRINT USING scan count
staticB PUVS,,1 ;PRINT USING value seen flag
externW b$PUSG ; store the actual address for PRINT USING
externW b$PUDS ;defined in GOSTOP.ASM
externB b$VTYP ; defined in GLOBAL.INC
externW b$pSTDALCTMP ; indirect B$STDALCTMP vector
sEnd ;_BSS
SUBTTL code segment externals
page
sBegin ST_TEXT
externFP B$SASS
externNP B$PUFOUT ;in pufout.asm
externNP B$OutBlanks
sEnd ;ST_TEXT
sBegin ER_TEXT
externNP B$ERR_FC
externNP B$ERR_TM
sEnd ;ER_TEXT
assumes CS,ST_TEXT
sBegin ST_TEXT
SUBTTL B$PREN -- main body of PRINT USING
page
;***
;B$PREN -- PRINT USING
;
;Purpose:
; Perform the format print according to b$PUFLG. This routine first
; prints the item according to the format in b$PUFLG, if it is nonzero,
; and then sets the b$PUFLG for next item. b$PUFLG is reset to zero
; by B$USNG (the preamble of PRINT USING), and then is set each time
; this routine is called.
;
; Actually, except the field size, there is not much to consider if
; printing a string. For printing a number, there are a lot of
; varieties. However, the formatting is done in B$PUFOUT.
;Entry:
; [BX] = *SD, *I2, *I4, *R4, or *R8
; [b$PUFLG] = print using format flag
; [b$PUDS] = USING string descriptor
;Exit:
; [b$PUFLG] is set for next item (or 0 if none)
;Uses:
; none
;Exceptions:
; illegal function call -- B$ERR_FC
; type mismatch -- B$ERR_TM
;*******************************************************************************
cProc B$PREN,<PUBLIC,NEAR>,<SI,DI> ;save di,si
cBegin
MOV AX,[b$PUFLG] ; test if type pending
OR AX,AX ; is this the first print using item ?
JNZ PrtItem ;Brif not, go print it
MOV PUVS,AL ; clear PUVS
PUSH BX ;save item to be printed
MOV AX,[b$PUDS] ;get length of PRINT USING string
MOV PUSC,AX ;save scan count remaining
OR AX,AX ;null string?
JZ FARG ;If so, illegal function call
CALL PUSCAN ;scan the format for the first item
;[b$PUFLG] is set on return
POP BX ;get item back
MOV AL,BYTE PTR [b$PUFLG] ; AL has the format of the printing item
PrtItem:
MOV PUVS,AL ;save information in PUVS
MOV CX,b$DIGCNT ;load [CX]
TEST AL,STRING ;does the field define a string?
JNZ PrtStr ;go printing a string
CMP b$VTYP,VT_SD ;is it a string ?
JZ TMER ;Brif yes, give "type mismatch"
cCall B$PUFOUT ;translate and format the printing number
; needs [BX] = *I2, *I4, *R4 or *R8
; and [b$PUFLG] = format
;on return,
; [SI] point to the digit string
; [AX] count of length
; DI is used
XCHG AX,CX ;cut count in CX
CALL [VOUTCNT] ;output string with CX=length
JMP SHORT ScanNext ;try next, set b$PUFLG for next item
PrtStr:
; Throughout the following code, CX = length of string to print
; and DX = number of spaces to follow it.
CMP b$VTYP,VT_SD ;type better be string
JNZ TMER ;Brif not, give "type mismatch"
MOV DX,CX ;save length of print field into DX
MOV CX,[BX] ;get length of string
SUB DX,CX ;DX = padding count
;-------------------------------
;Note that if we have a variable length string field, DX will be -1.
;The result of the above subtraction will never carry (so we will take the
;JAE below), but the number left in DX will always be negative. Thus when
;we get to the padding check, no blanks will be added.
;-------------------------------
JAE PrtIt ;if field is big enough, proceed
ADD CX,DX ;CX = CX + (old DX-CX) = old DX = size of field
PrtIt:
PUSH DX ; save DX, DX is used by [VTYPCNT]
CALL [VTYPCNT] ;output CX bytes of string
CALL [b$pSTDALCTMP] ;deallocate the temp string if it is
POP CX ; padding count in CX (could be negative!)
CALL B$OutBlanks ; output CX spaces
ScanNext:
CALL PUSCAN ;scan & set the format for next item
cEnd ;pop si,di and exit to caller
FARG: JMP B$ERR_FC ;Illegal function call
TMER: JMP B$ERR_TM ;Type mismatch
SUBTTL scan one print format from USING string
page
;***
;PUSCAN -- scan and set up the print format for one item
;
;Purpose:
; This routine scans the Using string, b$PUDS, and sets up the flag
; b$PUFLG, so the next print item may be formated.
;
; The possible formats for a print item are:
;
; for string item:
; ! print first character of that string
; \...\ print 2+n characters, n is the spaces between two "\"
; & print variable length (b$DIGCNT is set to -1)
; for numeric item
; # print one digit
; . print "."
; + print sign
; - print minus sign at the end of the number
; ** print "*" as the leading character
; $$ print "$" preceeding the number
; , print "," each three digits
; ^^^^ print scientific notation
; ^^^^^ print scientific notation, 3 digits
; _ print next character as a literal character
;
; Also, a "%" will be printed preceeding the number if the field specified
; is not big enough.
;Entry:
; [PUSC] = scan count
; [b$PUDS] = SD of Using string
;Exit:
; [b$PUFLG] is set
;Uses:
; SI
;Exceptions:
; illegal function call -- B$ERR_FC
;*******************************************************************************
PUSCAN:
MOV [b$PUFLG],0 ;reset the format flag
MOV SI,[b$PUDS+2] ;start of string (could change if G.C.!)
MOV AX,[b$PUDS] ;length of the string
MOV CX,PUSC ;get scan count
SUB AX,CX ;offset into string
ADD SI,AX ;move the string pointer
JCXZ RETL ;at end of string?
JMP SHORT PRCCHR ;If not, scan for next value (or EOS)
REUSIN: cCall PLSPRT ;print a "+" if necessary
CALL [VWCH] ;output the character in AL
REUSN1:
MOV PUSC,CX ;save scan count ( = 0 )
MOV BYTE PTR [b$PUFLG],CL ; set the b$PUFLG
CMP CL,PUVS ;any values seen in string?
JZ FARG ;if not, we'll never get anywhere
RETL: RET ;exit to caller
;-------------------------------
; Here to handle a literal character in the using string preceded by "_".
;-------------------------------
LITCHR: cCall PLSPRT ;print previous "+" if there is any
LODSB ;fetch literal character
CALL [VWCH] ;output that literal character
LOOP PRCCHR ;decrement count (CX)
JMP SHORT REUSN1 ;Brif no more
;-------------------------------
; Here to handle variable length string field specified with "&".
;-------------------------------
VARSTR:
MOV BX,-1 ;SET LENGTH TO MAXIMUM POSSIBLE
ISSTRF:
DEC CX ;DECREMENT THE "USING" STRING CHARACTER COUNT
cCall PLSPRT ;PRINT A "+" IF ONE CAME BEFORE THE FIELD
MOV PUSC,CX ;Save scan count
MOV b$DIGCNT,BX ;Save field width
MOV BYTE PTR [b$PUFLG],2 ; Flag string type
RET
⌨️ 快捷键说明
复制代码
Ctrl + C
搜索代码
Ctrl + F
全屏模式
F11
切换主题
Ctrl + Shift + D
显示快捷键
?
增大字号
Ctrl + =
减小字号
Ctrl + -