home *** CD-ROM | disk | FTP | other *** search
Text File | 2013-11-08 | 361.4 KB | 9,665 lines |
- Microsoft MASM: Sample Code from v6.0
-
-
- ALARM.ASM
- CD-ROM Disc Path: \SAMPCODE\MASM\MASM6\TSR\ALARM.ASM
-
- ;* ALARM.ASM - A simple memory-resident program that beeps the speaker
- ;* at a prearranged time. Can be loaded more than once for multiple
- ;* alarm settings. During installation, ALARM establishes a handler
- ;* for the timer interrupt (interrupt 08). It then terminates through
- ;* the Terminate-and-Stay-Resident function (function 31h). After the
- ;* alarm sounds, the resident portion of the program retires by setting
- ;* a flag that prevents further processing in the handler.
- ;*
- ;* NOTE: You must assemble this program as a .COM file, either as a PWB
- ;* build option or with the ML /AT switch.
-
- .MODEL tiny, pascal, os_dos
- .STACK
-
- .CODE
-
- ORG 5Dh ; Location of time argument in PSP,
- CountDown LABEL WORD ; converted to number of 5-second
- ; intervals to elapse
- .STARTUP
- jmp Install ; Jump over data and resident code
-
- ; Data must be in code segment so it won't be thrown away with Install code.
-
- OldTimer DWORD ? ; Address of original timer routine
- tick_91 BYTE 91 ; Counts 91 clock ticks (5 seconds)
- TimerActiveFlag BYTE 0 ; Active flag for timer handler
-
- ;* NewTimer - Handler routine for timer interrupt (interrupt 08).
- ;* Decrements CountDown every 5 seconds. No other action is taken
- ;* until CountDown reaches 0, at which time the speaker sounds.
-
- NewTimer PROC FAR
-
- .IF cs:TimerActiveFlag != 0 ; If timer busy or retired:
- jmp cs:OldTimer ; Jump to original timer routine
- .ENDIF
- inc cs:TimerActiveFlag ; Set active flag
- pushf ; Simulate interrupt by pushing flags
- call cs:OldTimer ; then far-calling original routine
- sti ; Enable interrupts
- push ds ; Preserve DS register
- push cs ; Point DS to current segment for
- pop ds ; further memory access
- dec tick_91 ; Count down for 91 ticks
- .IF zero? ; If 91 ticks have elapsed:
- mov tick_91, 91 ; Reset secondary counter and
- dec CountDown ; subtract one 5-second interval
- .IF zero? ; If CountDown drained:
- call Sound ; Sound speaker
- inc TimerActiveFlag ; Alarm has sounded, set flag
- .ENDIF
- .ENDIF
-
- dec TimerActiveFlag ; Decrement active flag
- pop ds ; Recover DS
- iret ; Return from interrupt handler
-
- NewTimer ENDP
-
-
- ;* Sound - Sounds speaker with the following tone and duration:
-
- BEEP_TONE EQU 440 ; Beep tone in hertz
- BEEP_DURATION EQU 6 ; Number of clocks during beep,
- ; where 18 clocks = approx 1 second
-
- Sound PROC USES ax bx cx dx es ; Save registers used in this routine
- mov al, 0B6h ; Initialize channel 2 of
- out 43h, al ; timer chip
- mov dx, 12h ; Divide 1,193,180 hertz
- mov ax, 34DCh ; (clock frequency) by
- mov bx, BEEP_TONE ; desired frequency
- div bx ; Result is timer clock count
- out 42h, al ; Low byte of count to timer
- mov al, ah
- out 42h, al ; High byte of count to timer
- in al, 61h ; Read value from port 61h
- or al, 3 ; Set first two bits
- out 61h, al ; Turn speaker on
-
- ; Pause for specified number of clock ticks
-
- mov dx, BEEP_DURATION ; Beep duration in clock ticks
- sub cx, cx ; CX:DX = tick count for pause
- mov es, cx ; Point ES to low memory data
- add dx, es:[46Ch] ; Add current tick count to CX:DX
- adc cx, es:[46Eh] ; Result is target count in CX:DX
- .REPEAT
- mov bx, es:[46Ch] ; Now repeatedly poll clock
- mov ax, es:[46Eh] ; count until the target
- sub bx, dx ; time is reached
- sbb ax, cx
- .UNTIL !carry?
-
- in al, 61h ; When time elapses, get port value
- xor al, 3 ; Kill bits 0-1 to turn
- out 61h, al ; speaker off
- ret
-
- Sound ENDP
-
-
-
- ;* Install - Converts ASCII argument to valid binary number, replaces
- ;* NewTimer as the interrupt handler for the timer, then makes program
- ;* memory-resident by exiting through function 31h.
- ;*
- ;* This procedure marks the end of the TSR's resident section and the
- ;* beginning of the installation section. When ALARM terminates through
- ;* function 31h, the above code and data remain resident in memory. The
- ;* memory occupied by the following code is returned to DOS.
-
-
- Install PROC
-
- ; Time argument is in hhmm military format. Convert ASCII digits to
- ; number of minutes since midnight, then convert current time to number
- ; of minutes since midnight. Difference is number of minutes to elapse
- ; until alarm sounds. Convert to seconds-to-elapse, divide by 5 seconds,
- ; and store result in word CountDown.
-
- DEFAULT_TIME EQU 3600 ; Default alarm setting = 1 hour
- ; (in seconds) from present time
- mov ax, DEFAULT_TIME
- cwd ; DX:AX = default time in seconds
- .IF BYTE PTR CountDown != ' ';If not blank argument:
- xor CountDown[0], '00' ; Convert 4 bytes of ASCII
- xor CountDown[2], '00' ; argument to binary
-
- mov al, 10 ; Multiply 1st hour digit by 10
- mul BYTE PTR CountDown[0] ; and add to 2nd hour digit
- add al, BYTE PTR CountDown[1]
- mov bh, al ; BH = hour for alarm to go off
- mov al, 10 ; Repeat procedure for minutes
- mul BYTE PTR CountDown[2] ; Multiply 1st minute digit by 10
- add al, BYTE PTR CountDown[3] ; and add to 2nd minute digit
- mov bl, al ; BL = minute for alarm to go off
- mov ah, 2Ch ; Request function 2Ch
- int 21h ; Get Time (CX = current hour/min)
- mov dl, dh
- sub dh, dh
- push dx ; Save DX = current seconds
-
- mov al, 60 ; Multiply current hour by 60
- mul ch ; to convert to minutes
- sub ch, ch
- add cx, ax ; Add current minutes to result
- ; CX = minutes since midnight
- mov al, 60 ; Multiply alarm hour by 60
- mul bh ; to convert to minutes
- sub bh, bh
- add ax, bx ; AX = number of minutes since
- ; midnight for alarm setting
- sub ax, cx ; AX = time in minutes to elapse
- ; before alarm sounds
- .IF carry? ; If alarm time is tomorrow:
- add ax, 24 * 60 ; Add minutes in a day
- .ENDIF
-
- mov bx, 60
- mul bx ; DX:AX = minutes-to-elapse-times-60
- pop bx ; Recover current seconds
- sub ax, bx ; DX:AX = seconds to elapse before
- sbb dx, 0 ; alarm activates
- .IF carry? ; If negative:
- mov ax, 5 ; Assume 5 seconds
- cwd
- .ENDIF
- .ENDIF
-
- mov bx, 5 ; Divide result by 5 seconds
- div bx ; AX = number of 5-second intervals
- mov CountDown, ax ; to elapse before alarm sounds
-
- mov ax, 3508h ; Request function 35h
- int 21h ; Get Vector for timer (interrupt 08)
- mov WORD PTR OldTimer[0], bx; Store address of original
- mov WORD PTR OldTimer[2], es; timer interrupt
- mov ax, 2508h ; Request function 25h
- mov dx, OFFSET NewTimer ; DS:DX points to new timer handler
- int 21h ; Set Vector with address of NewTimer
-
- mov dx, OFFSET Install ; DX = bytes in resident section
- mov cl, 4
- shr dx, cl ; Convert to number of paragraphs
- inc dx ; plus one
- mov ax, 3100h ; Request function 31h, error code=0
- int 21h ; Terminate-and-Stay-Resident
-
- Install ENDP
-
- END
-
-
- BASIC.ASM
- CD-ROM Disc Path: \SAMPCODE\MASM\MASM6\MIXED\BASIC.ASM
-
- ; Called by BASMAIN.BAS
- ; Assemble with ML /c BASIC.ASM
-
- .MODEL medium
-
- Power2 PROTO PASCAL, Factor:PTR WORD, Power:PTR WORD
- .CODE
- Power2 PROC PASCAL, Factor:PTR WORD, Power:PTR WORD
-
- mov bx, WORD PTR Factor ; Load Factor into
- mov ax, [bx] ; AX
- mov bx, WORD PTR Power ; Load Power into
- mov cx, [bx] ; CX
- shl ax, cl ; AX = AX * (2 to power of CX)
-
- ret
- Power2 ENDP
-
- END
-
-
- C.ASM
- CD-ROM Disc Path: \SAMPCODE\MASM\MASM6\MIXED\C.ASM
-
- ; Called from main program in CMAIN.C
- ; Assemble with ML /c C.ASM
-
- .MODEL small, c
-
- Power2 PROTO C factor:SWORD, power:SWORD
- .CODE
-
- Power2 PROC C factor:SWORD, power:SWORD
- mov ax, factor ; Load Arg1 into AX
- mov cx, power ; Load Arg2 into CX
- shl ax, cl ; AX = AX * (2 to power of CX)
- ; Leave return value in AX
- ret
- Power2 ENDP
- END
-
-
- COMMON.ASM
- CD-ROM Disc Path: \SAMPCODE\MASM\MASM6\DEMOS\COMMON.ASM
-
- .MODEL small, pascal, os_dos
- INCLUDE demo.inc
-
- .DATA
- vconfig VIDCONFIG <> ; Global video configuration structure
-
- .CODE
-
- ;* GetVidConfig - Determines current video configuration and initializes
- ;* the vconfig structure.
- ;*
- ;* Shows: BIOS Interrupt - 10h, Function 0 (Set Video Mode)
- ;* 10h, Function 0Fh (Get Current Video Mode)
- ;* 10h, Function 1Ah (Video Display Combination)
- ;*
- ;* Uses: vconfig - Video configuration structure, declared in the
- ;* DEMO.INC include file.
- ;*
- ;* Params: None
- ;*
- ;* Return: None
-
- GetVidConfig PROC
-
- mov ax, 1A00h ; Get video info for VGA
- int 10h
- chkVGA:
- cmp al, 1Ah ; Is VGA or MCGA present?
- jne chkEGA ; No? Then check for EGA
-
- cmp bl, 2 ; If VGA exists as secondary adapter,
- je isCGA ; check for CGA and mono as primary
- jb isMONO
- cmp bl, 5 ; If EGA is primary, do normal
- jbe chkEGA ; EGA checking
- chkMCGA:
- mov vconfig.adapter, MCGA ; Yes? Assume MCGA
- mov vconfig.display, COLOR
- cmp bl, 8 ; Correct assumption?
- ja gotmode ; Yes? Continue
- isVGA:
- mov vconfig.adapter, VGA ; Assume it's VGA color
- je gotmode ; Yes? Continue
- mov vconfig.display, MONO ; No? Must be VGA mono
- jmp gotmode ; Finished with VGA, so jump
- chkEGA:
- mov ah, 12h ; Call EGA status function
- mov bl, 10h
- sub cx, cx ; Clear status bits
- int 10h
- jcxz chkCGA ; If CX is unchanged, not EGA
- isEGA:
- mov vconfig.adapter, EGA ; Set structure fields for EGA
- mov vconfig.display, MONO ; Assume EGA mono
- or bh, bh ; Correct assumption?
- jnz gotmode ; Yes? Continue
- mov vconfig.display, COLOR ; No? Must be EGA color
- jmp gotmode ; Finished with EGA, so jump
- chkCGA:
- int 11h ; Get equipment list
- and al, 30h ; If bits 4-5 set, monochrome
- cmp al, 30h ; Monochrome text mode?
- je isMONO ; Yes? Continue
- isCGA:
- mov vconfig.adapter, CGA ; No? Must be CGA
- mov vconfig.display, COLOR
- jmp gotmode
- isMONO:
- mov vconfig.adapter, MDA ; Set MONO
- mov vconfig.display, MONO
- gotmode:
- mov ah, 0Fh
- int 10h ; Get current mode
- mov vconfig.mode, al ; Record mode
- mov vconfig.dpage, bh ; and current page
- mov al, vconfig.display ; Multiply display value
- cbw ; (which is either 0 or 1)
- mov bx, 800h ; by 800h, then add to B000h
- mul bx ; for segment address of
- add ax, 0B000h ; video buffer
- add ah, vconfig.dpage ; Adding display page gives
- mov vconfig.sgmnt, ax ; address of current page
-
- sub ax, ax
- mov es, ax
- mov al, es:[44Ah] ; Get number of display cols
- mov vconfig.cols, al ; Store in structure
- mov vconfig.rows, 24 ; Assume bottom row # = 24
- cmp vconfig.adapter, EGA ; EGA or VGA?
- jl exit ; No? Exit
- mov ax, 1130h ; Yes? Request character info
- sub bh, bh ; Set BH to valid value
- push bp ; BP will change, so save it
- int 10h ; Get number of rows/screen
- mov vconfig.rows, dl ; Keep in structure
- pop bp ; Restore BP
- exit:
- ret
-
- GetVidConfig ENDP
-
-
- ;* GetCurPos - Gets current cursor position.
- ;*
- ;* Uses: vconfig - Video configuration structure (initialized
- ;* by calling the GetVidConfig procedure)
- ;*
- ;* Params: None
- ;*
- ;* Return: Short integer with high byte = row, low byte = column
-
- GetCurPos PROC USES bx dx
-
- mov ah, 3 ; Function 3
- mov bh, vconfig.dpage
- int 10h ; Get cursor position
- mov ax, dx
- ret
-
- GetCurPos ENDP
-
-
- ;* SetCurPos - Sets cursor position.
- ;*
- ;* Shows: BIOS Interrupt - 10h, Function 2 (Set Cursor Position)
- ;*
- ;* Uses: vconfig - Video configuration structure (initialized
- ;* by calling the GetVidConfig procedure)
- ;*
- ;* Params: Row - Target row
- ;* Col - Target column
- ;*
- ;* Return: None
-
- SetCurPos PROC USES bx dx,
- Row:WORD,
- Col:WORD
-
- mov dh, BYTE PTR Row ; DH = row
- mov dl, BYTE ptr Col ; DL = column
- mov ah, 2 ; Function 2
- mov bh, vconfig.dpage ; Current page
- int 10h ; Set cursor position
- ret
-
- SetCurPos ENDP
-
-
- ;* StrWrite - Writes ASCIIZ string to video memory at specified row/column.
- ;*
- ;* Shows: Instructions - lodsb stosb
- ;*
- ;* Uses: vconfig - Video configuration structure (initialized
- ;* by calling the GetVidConfig procedure)
- ;*
- ;* Params: Row - Row coordinate
- ;* Col - Column coordinate
- ;* Sptr - Pointer to string
- ;*
- ;* Return: None
-
- StrWrite PROC USES ds si di,
- Row:WORD,
- Col:WORD,
- Sptr:PTR BYTE
-
- GetVidOffset Row, Col ; Get video offset for these coords
- mov di, ax ; Copy to DI
- LoadPtr ds, si, Sptr ; DS:SI points to string
- mov es, vconfig.sgmnt ; ES:DI points to video RAM
- .WHILE 1 ; Loop forever (or until break)
- lodsb ; Get 1 character from string
- .BREAK .IF al == 0 ; Quit if null terminator
-
- ; For CGA systems, StrWrite waits for the video to begin a horizontal
- ; retrace before writing a character to memory. This avoids the problem
- ; of video snow inherent with some (though not all) color/graphics adapters.
- ; It also demonstrates a somewhat different approach to the problem than the
- ; one taken in the WinOpen and WinClose procedures.
-
- .IF vconfig.adapter != CGA ; If not CGA, skip this step
- push ax ; Save character
- mov dx, 3DAh ; Address of status register
- cli ; Disallow interruptions
- .REPEAT
- in al, dx ; Read current video status
- .UNTIL !(al & 1) ; Until horizontal retrace done
-
- .REPEAT
- in al, dx ; No? Read status again
- .UNTIL al & 1 ; Until retrace starts
- pop ax ; Recover character
- .ENDIF ; CGA only
-
- stosb ; Write char to video buffer
- sti ; Reenable interrupts in case CGA
- inc di ; Skip attribute byte
- .ENDW
- ret
-
- StrWrite ENDP
-
-
- ;* StrInput - Gets input string from keyboard using BIOS. Signals idle
- ;* state by calling interrupt 28h while polling for keypress, making
- ;* the procedure useful in TSR programs. Terminates when Enter or Esc
- ;* keys pressed.
- ;*
- ;* Shows: DOS interrupt - Interrupt 28h (DOS Idle Interrupt)
- ;*
- ;* Params: Row - Row coordinate
- ;* Col - Column coordinate
- ;* Max - Maximum allowable string length
- ;* Sptr - Pointer to string
- ;*
- ;* Return: Short integer with terminating char
-
- StrInput PROC USES ds si,
- Row:WORD,
- Col:WORD,
- Max:WORD,
- Sptr:PBYTE
-
- LoadPtr ds, si, Sptr ; DS:SI points to string
- add Max, si
- dec Max ; MAX now points to string limit
-
- .WHILE 1 ; Get key until break or continue
- loop1:
- INVOKE StrWrite, ; Display input string
- Row,
- Col,
- si
-
- mov bx, si
- mov dx, Col ; DL = cursor column
-
- .WHILE (BYTE PTR [bx] != 0) ; Scan string for null terminator
- inc bx ; Else try next character
- inc dx ; and increment cursor column
- .ENDW
-
- ; Set cursor position, pass row and column (DX)
- INVOKE SetCurPos,
- Row,
- dx
-
- .REPEAT
- int 28h ; Signal idle state
- mov ah, 1
- int 16h ; Key waiting?
- .CONTINUE .IF zero?
- sub ah, ah
- int 16h ; Yes? Get key
-
- cmp ah, LEFT ; Left arrow key?
- je backspace ; Treat like backspace
- .UNTIL al != 0 ; Ignore all other special keys
-
- .BREAK .IF al == ESCAPE ; Exit if Esc key
- .BREAK .IF al == CR ; Exit if Return key
-
- .IF al == BACKSP ; If backspace or left, handle it
- backspace:
- cmp bx, si ; At first letter?
- jbe loop1 ; Yes? Ignore backspace
- dec bx ; No? Point to preceding char
- dec dx ; Decrement column
- mov BYTE PTR [bx], ' ' ; Blank char
- push bx ; Preserve pointer
- INVOKE StrWrite, ; Overwrite last char with blank
- Row,
- dx,
- bx
-
- pop bx
- mov BYTE PTR [bx], 0 ; Make last char the new terminator
- .CONTINUE
- .ENDIF
-
- .CONTINUE .IF bx > Max ; Ignore key if too many letters
- sub ah, ah
- mov [bx], ax ; Store letter and null terminator
- .ENDW
-
- ret
-
- StrInput ENDP
-
-
- ;* ClearBox - Clears portion of screen with specified fill attribute.
- ;*
- ;* Shows: BIOS Interrupt - 10h, Function 6 (Scroll Up)
- ;*
- ;* Params: Attr - Fill attribute
- ;* Row1 - Top screen row of cleared section
- ;* Col1 - Left column of cleared section
- ;* Row2 - Bottom screen row of cleared section
- ;* Col2 - Right column of cleared section
- ;*
- ;* Return: None
-
- ClearBox PROC,
- Attr:WORD,
- Row1:WORD,
- Col1:WORD,
- Row2:WORD,
- Col2:WORD
-
- mov ax, 0600h ; Scroll service
- mov bh, BYTE PTR Attr ; BH = fill attribute
- mov ch, BYTE PTR Row1 ; CH = top row of clear area
- mov cl, BYTE PTR Col1 ; CL = left column
- mov dh, BYTE PTR Row2 ; DH = bottom row of clear area
- mov dl, BYTE PTR Col2 ; DL = right column
- int 10h ; Clear screen by scrolling up
- ret
-
- ClearBox ENDP
-
-
- ;* DisableCga - Disables CGA video by reprogramming the control register.
- ;*
- ;* Shows: Instructions - cli sti
- ;*
- ;* Params: None
- ;*
- ;* Return: None
-
- DisableCga PROC USES ax cx dx ; Preserve registers
-
- mov cx, -1 ; Set maximum loop count
- mov dx, 03DAh ; Address of status register
-
- .REPEAT
- in al, dx ; Get video status
- .UNTILCXZ !(al & 8) ; Until retrace end/timeout
- cli ; Disallow interruptions
- mov cx, -1 ; Reset loop count
-
- .REPEAT
- in al, dx ; Get video status
- .UNTILCXZ al & 8 ; Until retrace start/timeout
-
- sub dx, 2 ; DX = address of control reg
- mov al, 1 ; Value to disable CGA video
- out dx, al ; Disable video
- sti ; Reenable interrupts
- ret
-
- DisableCga ENDP
-
-
- ;* EnableCga - Enables CGA video by reprogramming the control register.
- ;*
- ;* Params: None
- ;*
- ;* Return: None
-
- EnableCga PROC USES ax dx es ; Preserve registers
-
- sub ax, ax
- mov es, ax ; Point ES to low memory
- mov al, es:[0465h] ; Get former mode setting
- mov dx, 03D8h ; Address of control register
- out dx, al ; Enable video
- ret
-
- EnableCga ENDP
-
-
- ;* GetVer - Gets DOS version.
- ;*
- ;* Shows: DOS Function - 30h (Get MS-DOS Version Number)
- ;*
- ;* Params: None
- ;*
- ;* Return: Short integer of form (M*100)+m, where M is major
- ;* version number and m is minor version, or 0 if
- ;* DOS version earlier than 2.0
-
- GetVer PROC
-
- mov ah, 30h ; DOS Function 30h
- int 21h ; Get MS-DOS Version Number
- .IF al == 0 ; If version, version 1
- sub ax, ax ; Set AX to 0
- .ELSE ; Version 2.0 or higher
- sub ch, ch ; Zero CH and move minor
- mov cl, ah ; version number into CX
- mov bl, 100
- mul bl ; Multiply major by 10
- add ax, cx ; Add minor to major*10
- .ENDIF
- ret ; Return result in AX
-
- GetVer ENDP
-
- END
-
-
- FILE.ASM
- CD-ROM Disc Path: \SAMPCODE\MASM\MASM6\DEMOS\FILE.ASM
-
- .MODEL small, pascal, os_dos
- INCLUDE demo.inc
- .CODE
-
- ;* ReadCharAttr - Reads character and display attribute at cursor location.
- ;*
- ;* Shows: BIOS Interrupt - 10h, Function 8 (Read Character and Attribute
- ;* at Cursor)
- ;*
- ;* Uses: vconfig - Video configuration structure (initialized
- ;* by calling the GetVidConfig procedure)
- ;*
- ;* Params: Attr - Pointer to short integer for display attribute
- ;*
- ;* Return: Short integer with ASCII value of character
-
- ReadCharAttr PROC USES di,
- Attr:PWORD
-
- mov ah, 8 ; Function 8
- mov bh, vconfig.dpage ; Current page
- int 10h ; Read Character and Attribute
- sub bh, bh
- mov bl, ah ; BX = attribute
- cbw ; AX = character
- LoadPtr es, di, Attr ; ES:DI = pointer to int
- mov es:[di], bx ; Copy attribute
- ret
-
- ReadCharAttr ENDP
-
-
- ;* CopyFile - Copies a file from a specified directory to another. Allows
- ;* two different copy methods. See the OpenFile, CloseFile, ReadFile, and
- ;* WriteFile procedures for specific examples on opening, closing, reading
- ;* from, and writing to files.
- ;*
- ;* Shows: DOS Functions - 3Ch (Create File)
- ;* 5Bh (Create New File)
- ;* Instruction - clc
- ;*
- ;* Params: Imode - 0 = Create new target file or overwrite existing file
- ;* 1 = Abort and return error code if target file already
- ;* exists (only for DOS versions 3.0 and higher)
- ;* Fspec1 - Pointer to ASCIIZ source file specification
- ;* Fspec2 - Pointer to ASCIIZ target file specification
- ;*
- ;* Return: Short integer with error code
- ;* 0 if successful
- ;* 1 if error
-
- .DATA
- Buffer BYTE BUFFERSIZE DUP (?) ; Buffer for diskette read
-
- .CODE
-
- CopyFile PROC USES ds si di,
- Imode:WORD,
- Fspec1:PBYTE,
- Fspec2:PBYTE
-
- LOCAL eof_flag:BYTE
-
- ; Open source file for read only
-
- LoadPtr ds, dx, Fspec1 ; Point DS:DX to source file
- mov ax, 3D00h ; AH = function #, AL = access code
- int 21h ; Open File (for read only)
- jc e_exit
- mov si, ax ; SI = file handle for source
-
- ; Open target file according to copy mode
-
- LoadPtr ds, dx, Fspec2 ; Point DS:DX to target file
- .IF Imode != 1 ; If Imode (DOS function) is not 1
- mov ah, 3Ch ; Request Create File
- .ELSE
-
- ; Check DOS version
- INVOKE GetVer
-
- cmp ax, 300 ; 3.0 or higher?
- jb close ; No? Abort with error code
- mov ah, 5Bh ; Request Create New File
- .ENDIF
- sub cx, cx ; Normal attribute for target
- int 21h ; DOS function for target file
- jc close ; If open error, abort
- mov di, ax ; DI = file handle for target
-
- ; Both files successfully opened. Now read from source and copy to target.
-
- mov ax, @data
- mov ds, ax ; DS:DX = buffer. Read/write
- mov dx, OFFSET Buffer ; to and from here.
- mov eof_flag, 0 ; Initialize end-of-file flag
-
- .REPEAT
- mov bx, si ; Handle for source file
- mov cx, BUFFERSIZE ; CX = number of bytes to read
- mov ah, 3Fh ; Request DOS read
- int 21h ; Read from File
- jc close ; If error, exit
- .IF ax != cx ; If bytes not read successfully:
- inc eof_flag ; Raise flag
- .ENDIF
- mov bx, di ; Handle for target file
- mov cx, ax ; Write number of bytes read
- mov ah, 40h ; Request DOS write
- int 21h ; Write from buffer to target file
- jc close ; If error, exit
- .UNTIL eof_flag != 0 ; Loop to read next block
- clc ; Clear CY to indicate
- close:
- pushf ; Preserve flags while closing
- mov bx, di ; Handle for target file
- mov ah, 3Eh ; Request DOS Function 3Eh
- int 21h ; Close File
- sub ax, ax ; Clear error code
- popf ; Recover flags
- .IF carry?
- e_exit:
- mov ax, 1 ; Else set error code
- .ENDIF
- ret
-
- CopyFile ENDP
-
-
- ;* ChangeDrive - Changes default drive.
- ;*
- ;* Shows: DOS Function - 0Eh (Select Disk)
- ;*
- ;* Params: Drive - Uppercase letter designation for new drive
- ;*
- ;* Return: None
-
- ChangeDrive PROC,
- Drive:WORD
-
- mov ah, 0Eh ; DOS Function 0Eh
- mov dx, Drive ; Drive designation in DL,
- sub dl, 'A' ; 0=A, 1=B, 2=C, etc
- int 21h ; Select Disk
- ret
-
- ChangeDrive ENDP
-
-
- ;* GetCurDrive - Gets designation of current drive.
- ;*
- ;* Shows: DOS Function - 19h (Get Current Disk)
- ;* Instruction - cbw
- ;*
- ;* Params: None
- ;*
- ;* Return: Short integer with drive designation
- ;* 0 = A, 1 = B, 2 = C, etc.
-
- GetCurDrive PROC
-
- mov ah, 19h ; DOS Function 19h
- int 21h ; Get Current Disk
- cbw ; AX = drive designation
- ret
-
- GetCurDrive ENDP
-
-
- ;* SetDTA - Sets address for new Disk Transfer Area.
- ;*
- ;* Shows: DOS Function - 1Ah (Set DTA Address)
- ;*
- ;* Params: Dta - Far pointer to new transfer address
- ;*
- ;* Return: None
-
- SetDTA PROC USES ds,
- Dta:FPBYTE
-
- lds dx, [Dta] ; Point DS:DX to DTA
- mov ah, 1Ah ; DOS Function 1Ah
- int 21h ; Set DTA Address
- ret
-
- SetDTA ENDP
-
-
- ;* GetDTA - Gets address of current Disk Transfer Area.
- ;*
- ;* Shows: DOS Function - 2Fh (Get DTA Address)
- ;*
- ;* Params: Dta - Far pointer to receive transfer address
- ;*
- ;* Return: None
-
- GetDTA PROC,
- Dta:FPBYTE
-
- mov ah, 2Fh ; DOS Function 2Fh
- int 21h ; Get DTA Address in ES:BX
- mov ax, es ; Save DTA segment
- mov dx, bx ; Save DTA offset
- les bx, Dta ; Now ES:BX points to variable
- mov es:[bx], dx ; Copy DTA address to
- mov es:[bx+2], ax ; dta variable
- ret
-
- GetDTA ENDP
-
-
- ;* CreateFile - Creates file with specified attribute.
- ;*
- ;* Shows: DOS Function - 3Ch (Create File)
- ;*
- ;* Params: Attr - Attribute code: 0 = normal 8 = volume label
- ;* 1 = read only 16 = subdirectory
- ;* 2 = hidden 32 = archiv
- ;* 4 = system
- ;* Fspec - Pointer to ASCIIZ file specification
- ;*
- ;* Return: Short integer with file handle or -1 for error
-
- CreateFile PROC USES ds,
- Attr:WORD, Fspec:PBYTE
-
- LoadPtr ds, dx, Fspec ; Point DS:DX to file spec
- mov cx, Attr ; CX = attribute
- mov ah, 3Ch ; AH = function number
- int 21h ; Create file
- .IF carry?
- mov ax, -1 ; Set error code
- .ENDIF
- ret
-
- CreateFile ENDP
-
-
- ;* OpenFile - Opens specified file for reading or writing. See the CopyFile
- ;* procedure for another example of using DOS Function 3Dh to open files.
- ;*
- ;* Shows: DOS Function - 3Dh (Open File)
- ;*
- ;* Params: Access - Access code: 0 = read 1 = write 2 = read/write
- ;* Fspec - Pointer to ASCIIZ file specification
- ;*
- ;* Return: Short integer with file handle or -1 for error
-
- OpenFile PROC USES ds,
- Access:WORD, Fspec:PBYTE
-
- LoadPtr ds, dx, Fspec ; Point DS:DX to file spec
- mov ax, Access ; AL = access code
- mov ah, 3Dh ; AH = function number
- int 21h ; Open file
- .IF carry?
- mov ax, -1 ; Set error code
- .ENDIF
- ret
-
- OpenFile ENDP
-
-
- ;* CloseFile - Closes an open file, specified by handle. See the CopyFile
- ;* procedure for another example of using DOS Function 3Eh to close files.
- ;*
- ;* Shows: DOS Function - 3EH (Close File)
- ;*
- ;* Params: Handle - File handle
- ;*
- ;* Return: None
-
- CloseFile PROC,
- Handle:WORD
-
- mov bx, Handle ; BX = file handle
- mov ah, 3Eh ; DOS Function 3Eh
- int 21h ; Close file
- ret
-
- CloseFile ENDP
-
-
- ;* ReadFile - Read from open file to specified buffer. See the CopyFile
- ;* procedure for another example of using DOS Function 3Fh to read files.
- ;*
- ;* Shows: DOS Function - 3Fh (Read File or Device)
- ;*
- ;* Params: Handle - File handle
- ;* Len - Number of bytes to read
- ;* Pbuff - Pointer to buffer
- ;*
- ;* Return: Short integer with number of bytes read, or 0 if read error
-
- ReadFile PROC USES ds di,
- Handle:WORD, Len:WORD, Pbuff:PBYTE
-
- LoadPtr ds, dx, Pbuff ; Point DS:DX to buffer
- mov di, dx ; Keep string offset in DI
- mov bx, Handle ; BX = handle
- mov cx, Len ; CX = number of bytes to read
- mov ah, 3Fh ; Request DOS read
- int 21h ; Read File
- .IF carry?
- sub ax, ax ; Set error code
- .ENDIF
- ret
-
- ReadFile ENDP
-
-
- ;* WriteFile - Write ASCIIZ string to file. If Handle = 0, the string is
- ;* written to STDOUT (console). See the CopyFile procedure for another
- ;* example of using DOS Function 40h to write to files.
- ;*
- ;* Shows: DOS Function - 40h (Write File or Device)
- ;* Instructions - inc dec
- ;*
- ;* Params: Handle - File handle
- ;* SPtr - Pointer to ASCIIZ string
- ;*
- ;* Return: Short integer with error code
- ;* 0 if successful
- ;* 1 if write error
- ;* 2 if number of bytes written not equal to string length
-
- WriteFile PROC USES ds di,
- Handle:WORD, Sptr:PBYTE
-
- LoadPtr es, di, Sptr ; Point ES:DI to string
- push di ; Hold on to string pointer
- mov cx, -1 ; Set CX to maximum
- sub al, al ; AL = 0
- repne scasb ; Scan string for NULL
- pop dx ; Recover string pointer
- dec di
- sub di, dx ; Get string length (w/o NULL)
- mov cx, di ; Put it into CX
- mov bx, Handle ; Load BX with handle
- push es ; Set DS to ES to ensure
- pop ds ; DS:DX points to string
- mov ah, 40h ; Request DOS write
- int 21h ; Write File or Device
- mov bx, ax ; Get number of bytes written
- mov ax, 0 ; Set error code, preserve carry
- .IF carry? ; If carry:
- inc ax ; Increment once for write error
- .ENDIF ; carry
- .IF bx != cx ; If bytes not all written:
- inc ax ; Increment twice
- .ENDIF ; bx ! cx
- ret
-
- WriteFile ENDP
-
-
- ;* GetDiskSize - Gets size information from specified disk.
- ;*
- ;* Shows: DOS Function - 36h (Get Drive Allocation Information)
- ;*
- ;* Params: Drive - Drive code (0 = default, 1 = A, 2 = B, etc.)
- ;* Disk - Pointer to a structure with 4 short integer members:
- ;* Member 1 - Total clusters on disk
- ;* Member 2 - Number of available clusters
- ;* Member 3 - Sectors/cluster (-1 if invalid drive)
- ;* Member 4 - Bytes/sector
- ;*
- ;* Return: None
-
- GetDiskSize PROC USES di,
- Drive:WORD, Disk:PDISKSTAT
-
- mov dx, Drive ; DL = drive code
- mov ah, 36h ; DOS Function 36h
- int 21h ; Get Drive Allocation Information
- LoadPtr es, di, Disk ; ES:DI = disk structure
- mov (DISKSTAT PTR es:[di]).\
- total, dx ; DX = total clusters
- mov (DISKSTAT PTR es:[di]).\
- avail, bx ; BX = number of free clusters
- mov (DISKSTAT PTR es:[di]).\
- sects, ax ; AX = sectors/cluster
- mov (DISKSTAT PTR es:[di]).\
- bytes, cx ; CX = bytes/sector
- ret
-
- GetDiskSize ENDP
-
-
- ;* MakeDir - Creates a specified subdirectory.
- ;*
- ;* Shows: DOS Function - 39h (Create Directory)
- ;*
- ;* Params: Pspec - Pointer to ASCIIZ pathname of new subdirectory
- ;*
- ;* Return: Short integer with error code
- ;* 0 if successful
- ;* 1 if create error
-
- MakeDir PROC USES ds,
- Pspec:PBYTE
-
- LoadPtr ds, dx, Pspec ; Point DS:DX to path spec
- mov ah, 39h ; DOS Function 39h
- int 21h ; Create Directory
- mov ax, 0 ; Set error code, keep flags
- .IF carry?
- inc ax ; Set error code to 1
- .ENDIF
- ret
-
- MakeDir ENDP
-
-
- ;* RemoveDir - Removes a specified subdirectory.
- ;*
- ;* Shows: DOS Function - 3Ah (Delete Directory)
- ;*
- ;* Params: Pspec - Pointer to ASCIIZ pathname of subdirectory
- ;*
- ;* Return: Short integer with error code
- ;* 0 if successful
- ;* 1 if delete error or subdirectory not empty
-
- RemoveDir PROC USES ds,
- Pspec:PBYTE
-
- LoadPtr ds, dx, Pspec ; Point DS:DX to path spec
- mov ah, 3Ah ; DOS Function 3Ah
- int 21h ; Delete Directory
- mov ax, 0 ; Set error code, keep flags
- .IF carry?
- inc ax ; Set error code to 1
- .ENDIF
- ret
-
- RemoveDir ENDP
-
-
- ;* ChangeDir - Changes current (default) directory.
- ;*
- ;* Shows: DOS Function - 3Bh (Set Current Directory)
- ;*
- ;* Params: Pspec - Pointer to ASCIIZ pathname of target subdirectory
- ;*
- ;* Return: Short integer with error code
- ;* 0 if successful
- ;* 1 if delete error or subdirectory not empty
-
- ChangeDir PROC USES ds,
- Pspec:PBYTE
-
- LoadPtr ds, dx, Pspec ; Point DS:DX to path spec
- mov ah, 3Bh ; DOS Function 3Bh
- int 21h ; Set Current Directory
- mov ax, 0 ; Set error code, keep flags
- .IF carry?
- inc ax ; Set error code to 1
- .ENDIF
- ret
-
- ChangeDir ENDP
-
-
- ;* DelFile - Deletes a specified file.
- ;*
- ;* Shows: DOS Function - 41h (Delete File)
- ;*
- ;* Params: Fspec - Pointer to ASCIIZ file specification
- ;*
- ;* Return: Short integer with error code
- ;* 0 if successful
- ;* 1 if delete error
-
- DelFile PROC USES ds,
- Fspec:PBYTE
-
- LoadPtr ds, dx, Fspec ; Point DS:DX to file spec
- mov ah, 41h ; DOS Function 41h
- int 21h ; Delete File
- mov ax, 0 ; Set error code, keep flags
- .IF carry?
- inc ax ; Set error code to 1
- .ENDIF
- ret
-
- DelFile ENDP
-
-
- ;* Rewind - Rewinds an open file, specified by handle. See the GetFileSize
- ;* procedure for an example of using Function 42h to determine file size.
- ;*
- ;* Shows: DOS Function - 42h (Set File Pointer)
- ;*
- ;* Params: Handle - File handle
- ;*
- ;* Return: None
-
- Rewind PROC,
- Handle:WORD
-
- mov bx, Handle ; BX = file handle
- mov ax, 4200h ; AH = function #,
- ; AL = move to beginning of
- sub cx, cx ; file plus offset
- sub dx, dx ; CX:DX = offset (zero)
- int 21h ; Set File Pointer
- ret
-
- Rewind ENDP
-
-
- ;* GetFileSize - Gets the size of an open file, specified by handle.
- ;*
- ;* Shows: DOS Function - 42h (Set File Pointer)
- ;*
- ;* Params: Handle - File handle
- ;*
- ;* Return: Long integer with file size in bytes
-
- GetFileSize PROC,
- Handle:WORD
-
- mov bx, Handle ; BX = file handle
- mov ax, 4202h ; AH = function #,
- ; AL = move to end of
- sub cx, cx ; file plus offset
- sub dx, dx ; CX:DX = offset (zero)
- int 21h ; Set File Pointer
- mov ax, dx ; Set DX:AX = file size in
- mov dx, cx ; bytes, return long int
- ret
-
- GetFileSize ENDP
-
-
- ;* GetAttribute - Gets the attribute(s) of a specified file.
- ;*
- ;* Shows: DOS Function - 43h (Get or Set File Attributes)
- ;*
- ;* Params: Fspec - Pointer to ASCIIZ file specification
- ;*
- ;* Return: Short integer with file attribute bits set as follows:
- ;* bit 0 = read-only bit 3 = volume label
- ;* bit 1 = hidden bit 4 = subdirectory
- ;* bit 2 = system bit 5 = archive
- ;* 0 indicates normal data file
- ;* -1 indicates error
-
- GetAttribute PROC USES ds,
- Fspec:PBYTE
-
- LoadPtr ds, dx, Fspec ; DS:DX = file specification
- mov ax, 4300h ; AH = function #
- ; AL = 0 (return attribute)
- int 21h ; Get File Attributes
- mov ax, -1 ; Set code, keep flags
- .IF !carry?
- mov ax, cx ; Return with file attribute bits
- .ENDIF
- ret
-
- GetAttribute ENDP
-
-
- ;* SetAttribute - Sets the attribute(s) of a specified file.
- ;*
- ;* Shows: DOS Function - 43h (Get or Set File Attributes)
- ;*
- ;* Params: Attr - Attribute bits set as follows:
- ;* bit 0 = read-only bit 3 = volume label
- ;* bit 1 = hidden bit 4 = subdirectory
- ;* bit 2 = system bit 5 = archive
- ;* (Attr = 0 for normal data file)
- ;* Fspec - Pointer to ASCIIZ file specification
- ;*
- ;* Return: Short integer with error code
- ;* 0 if successful
- ;* 1 if delete error
-
- SetAttribute PROC USES ds,
- Attr:WORD,
- Fspec:PBYTE
-
- LoadPtr ds, dx, Fspec ; DS:DX = file specification
- mov cx, Attr ; Put attribute code in CX
- mov ax, 4301h ; AH = function #
- ; AL = 1 (set attribute)
- int 21h ; Set File Attributes
- mov ax, 0 ; Clear code, keep flags
- .IF carry?
- inc ax ; Set error code to 1
- .ENDIF
- ret
-
- SetAttribute ENDP
-
-
- ;* GetCurDir - Gets the current directory of default drive.
- ;*
- ;* Shows: DOS Function - 47h (Get Current Directory)
- ;*
- ;* Params: Spec - Pointer to 64-byte buffer to receive directory
- ;* path. Path terminates with 0 but does not include
- ;* drive and does not begin with backslash.
- ;*
- ;* Return: Short integer with error code
- ;* 0 if successful
- ;* 1 if delete error or subdirectory not empty
-
- GetCurDir PROC USES ds si,
- Spec:PBYTE
-
- LoadPtr ds, si, Spec ; DS:SI = spec address
- mov ah, 47h ; AH = function number
- sub dl, dl ; DL = current drive (0)
- int 21h ; Get Current Directory
- mov ax, 0 ; Set error code, keep flags
- .IF carry?
- inc ax ; Set error code to 1
- .ENDIF
- ret
-
- GetCurDir ENDP
-
-
- ;* FindFirst - Finds first entry in given directory matching specification.
- ;*
- ;* Shows: DOS Function - 4Eh (Find First File)
- ;* Instructions - pushf popf
- ;*
- ;* Params: Attr - Attribute code (see header comments for CreateFile)
- ;* Fspec - Pointer to ASCIIZ file specification
- ;* Finfo - Pointer to 43-byte buffer to receive
- ;* data from matched entry
- ;*
- ;* Return: Short integer with error code
- ;* 0 if successful
- ;* 1 if no match found
-
- .DATA
- OldDta FPVOID ? ; Storage for old DTA address
-
- .CODE
-
- FindFirst PROC USES ds,
- Attr:WORD,
- Fspec:PBYTE,
- Finfo:PFILEINFO
-
- ; Get current DTA address, pass address of pointer to hold value
- INVOKE GetDTA,
- ADDR OldDta
-
- mov cx, Attr ; Load CX with file attribute
-
- ; Set DTA address, pass pointer to structure
- INVOKE SetDTA,
- Finfo
-
- LoadPtr ds, dx, Fspec ; Point DS:DX to file spec
- mov ah, 4Eh ; AH = function number
- int 21h ; Find First File
-
- pushf ; Preserve flags
-
- ; Restore DTA address, pass pointer
- INVOKE SetDTA,
- OldDta
-
- sub ax, ax ; Set error code
- popf ; Recover flags
- .IF carry?
- inc ax ; Set error code to 1
- .ENDIF
- ret
-
- FindFirst ENDP
-
-
- ;* FindNext - Finds next entry in given directory matching specification.
- ;* (Should be called only after successfully calling the FindFirst procedure.
- ;*
- ;* Shows: DOS Function - 4Fh (Find Next File)
- ;* Operator - OFFSET
- ;*
- ;* Params: Finfo - Pointer to 43-byte buffer. This must be the same buffer
- ;* (or a duplicate) returned from the FindFirst procedur
- ;*
- ;* Return: Short integer with error code
- ;* 0 if successful
- ;* 1 if no more matches found
-
- FindNext PROC USES ds,
- Finfo:PFILEINFO
-
- ; Get current DTA address, pass address of pointer to hold value
- INVOKE GetDTA,
- ADDR OldDta
-
- ; Set DTA address, pass pointer to structure
- INVOKE SetDTA,
- Finfo
-
- mov ah, 4Fh ; AH = function number
- int 21h ; Find Next File
-
- pushf ; Preserve flags
-
- ; Restore DTA address, pass pointer
- INVOKE SetDTA,
- OldDta
-
- sub ax, ax ; Set error code
- popf ; Recover flags
- .IF carry?
- inc ax ; Set error code to 1
- .ENDIF
- ret
-
- FindNext ENDP
-
-
- ;* RenameFile - Renames specified file.
- ;*
- ;* Shows: DOS Function - 56h (Rename File)
- ;*
- ;* Params: Fspec1 - Pointer to old ASCIIZ file specification
- ;* Fspec2 - Pointer to new ASCIIZ file specification
- ;*
- ;* The drive must be the same for both arguments, but the path
- ;* does not. This allows files to be moved between directories.
- ;*
- ;* Return: Short integer with error code
- ;* 0 if successful
- ;* 1 if error
-
- RenameFile PROC USES ds di,
- Fspec1:PBYTE,
- Fspec2:PBYTE
-
- LoadPtr ds, dx, Fspec1 ; Point DS:DX to old file spec
- LoadPtr es, di, Fspec2 ; Point ES:DI to new file spec
- mov ah, 56h ; AH = function number
- int 21h ; Rename File
- mov ax, 0 ; Clear error code, keep flags
- .IF carry?
- inc ax ; Set error code to 1
- .ENDIF
- ret
-
- RenameFile ENDP
-
-
- ;* GetFileTime - Gets date/time for open file specified by handle.
- ;*
- ;* Shows: DOS Function - 57h (Get or Set File Date and Time)
- ;* Instructions - shl shr
- ;*
- ;* Params: Handle - Handle of open file
- ;* Sptr - Pointer to 18-byte buffer to receive date/time
- ;*
- ;* Return: Short integer with error code
- ;* 0 if successful
- ;* 1 if error
-
- GetFileTime PROC USES di,
- Handle:WORD,
- Sptr:PBYTE
-
- mov ax, 5700h ; AH = function number
- ; AL = get request
- mov bx, Handle ; BX = file handle
- int 21h ; Get File Date and Time
- mov ax, 1 ; Set error code, keep flags
- .IF !carry? ; If not carry, continue
- mov bx, cx ; Else save time in BX
- mov al, bl ; Get low byte of time
- and al, 00011111y ; Mask to get 2-second incrs,
- shl al, 1 ; convert to seconds
- push ax ; Save seconds
- mov cl, 5
- shr bx, cl ; Shift minutes into low byte
- mov al, bl ; Get new low byte
- and al, 00111111y ; Mask to get minutes
- push ax ; Save minutes
- mov cl, 6
- shr bx, cl ; Shift hours into low byte
- push bx ; Save hours
-
- mov bl, dl ; Get low byte of date
- and bl, 00011111y ; Mask to get day in BX
- mov cl, 5
- shr dx, cl ; Shift month into low byte
- mov al, dl ; Get new low byte
- and al, 00001111y ; Mask to get month
- mov cl, 4
- shr dx, cl ; Shift year into low byte
- add dx, 80 ; Year is relative to 1980
- push dx ; Save year
- push bx ; Save day
- push ax ; Save month
-
- LoadPtr es, di, Sptr ; Point ES:DI to 18-byte
- mov cx, 6 ; string
-
- .REPEAT
- pop ax ; Get 6 numbers sequentially in AL
- aam ; Convert to unpacked BCD
- xchg al, ah ; Switch bytes for word move
- or ax, '00' ; Make ASCII numerals
- stosw ; Copy to string
- mov al, '-' ; Separator for date text
- cmp cl, 4 ; First 3 iters are for date
- jg @F ; If CX=6 or 5, insert hyphen
- mov al, ' ' ; Separator date and time
- je @F ; If CX = 4, insert hyphen
- mov al, ':' ; Separator for time text
- .IF cl != 1
- @@: stosb ; Copy separator to string
- .ENDIF
- .UNTILCXZ
-
- sub ax, ax ; Clear return code
- stosb ; Terminate string with null
- .ENDIF ; to make ASCIIZ
- ret
-
- GetFileTime ENDP
-
-
- ;* UniqueFile - Creates and opens a new file with a name unique to the
- ;* specified directory. The name is manufactured from the current time,
- ;* making it useful for temporary files. For DOS versions 3.0 and higher.
- ;*
- ;* Shows: DOS Function - 5Ah (Create Temporary File)
- ;*
- ;* Params: Attr - Attribute code (see header comments for CreateFile)
- ;* Pspec - Pointer to ASCIIZ path specification
- ;*
- ;* Return: Short integer with file handle or -1 for error
-
- UniqueFile PROC USES ds,
- Attr:WORD,
- Pspec:PBYTE
-
- ; Get DOS version
- INVOKE GetVer
-
- cmp ax, 300 ; 3.0 or higher?
- jb e_exit ; No? Quit with error
- LoadPtr ds, dx, Pspec ; Point DS:DX to path spec
- mov cx, Attr ; CX = attribute
- mov ah, 5Ah ; AH = function number
- int 21h ; Create Temporary File
- .IF carry?
- e_exit: mov ax, -1 ; Set error code
- .ENDIF
- ret
-
- UniqueFile ENDP
-
-
- ;* CreateNewFile - Creates a new file with specified attribute. Differs
- ;* from the CreateFile procedure in that it returns an error if file
- ;* already exists. For DOS versions 3.0 and higher.
- ;*
- ;* Shows: DOS Function - 5Bh (Create New File)
- ;*
- ;* Params: Attr - Attribute code (see header comments for CreateFile)
- ;* Fspec - Pointer to ASCIIZ file specification
- ;*
- ;* Return: Short integer with file handle or -1 for error
-
- CreateNewFile PROC USES ds,
- Attr:WORD,
- Fspec:PBYTE
-
- LoadPtr ds, dx, Fspec ; Point DS:DX to file spec
- mov cx, Attr ; CX = attribute
- mov ah, 5Bh ; AH = function number
- int 21h ; Create New File
- .IF carry?
- mov ax, -1 ; Set error code
- .ENDIF
- ret
-
- CreateNewFile ENDP
-
-
- ;* StrCompare - Compares two strings for equality. See StrWrite, StrFindChar,
- ;* WinOpen, and WinClose procedures for other examples of string instructions
- ;*
- ;* Shows: Instructions - cmpsb cmpsw repe jcxz
- ;*
- ;* Params: Sptr1 - Pointer to first string
- ;* Sptr2 - Pointer to second string
- ;* Len - Length in bytes for comparison. Strings need not be of
- ;* equal length; however if len is an even number, comparison
- ;* is made on a word-by-word basis and thus is more efficient
- ;*
- ;* Return: Null pointer if strings match; else pointer to string #1 where
- ;* match failed.
-
- StrCompare PROC USES ds di si,
- Sptr1:PBYTE,
- Sptr2:PBYTE,
- Len:WORD
-
- LoadPtr es, di, Sptr1 ; ES:DI points to string #1
- LoadPtr ds, si, Sptr2 ; DS:SI points to string #2
- mov cx, Len ; Length of search in bytes
- and al, 0 ; Set ZR flag in case CX = 0
- .IF cx != 0 ; If length is not 0:
- .IF !(cl & 1) ; If not even number:
- repe cmpsb ; Compare byte-by-byte
- .ELSE ; Else compare word-by-word
- shr cx, 1 ; Decrease count by half
- repe cmpsw ; Compare word-by-word
- sub di, 2 ; Back up 2 characters
- sub si, 2
- cmpsb ; Match?
- .IF zero? ; No? Then failure
- cmpsb ; Compare last characters
- .ENDIF ; zero
- .ENDIF ; cl & 1
- .ENDIF ; cx != 0
-
- mov ax, 0 ; Set null pointer without
- mov dx, 0 ; disturbing flags
- .IF !zero? ; If no match:
- dec di ; Point to failure
- mov ax, di
- mov dx, es
- .ENDIF
- ret
-
- StrCompare ENDP
-
-
- ;* StrFindChar - Finds first occurence of character in given ASCIIZ string,
- ;* searching either from beginning or end of string. See StrWrite, WinOpen,
- ;* WinClose, and StrCompare procedures for other examples of string
- ;* instructions.
- ;*
- ;* Shows: Instructions - repne scasb cld std
- ;*
- ;* Params: Ichar - Character to search for
- ;* Sptr - Pointer to ASCIIZ string in which to search
- ;* Direct - Direction flag:
- ;* 0 = search from start to end
- ;* 1 = search from end to start
- ;*
- ;* Return: Null pointer if character not found, else pointer to string where
- ;* character first encountered
-
- StrFindChar PROC USES ds di si,
- IChar:SBYTE,
- Sptr:PBYTE,
- Direct:WORD
-
- LoadPtr es, di, Sptr ; ES:DI points to string
- LoadPtr ds, si, Sptr ; as does DS:SI
- mov cx, -1 ; Set scan counter to maximum
- mov bx, cx ; BX = max string tail
- cld ; Assume head-to-tail search
-
- .IF Direct != 0 ; If assumption correct:
- mov bx, di ; Set BX to byte before
- dec bx ; string head and scan
- sub al, al ; string for null terminator
- push cx ; to find string tail
- repne scasb
- pop cx ; Recover scan counter
- dec di ; Backup pointer to last
- dec di ; character in string and
- mov si, di ; begin search from there
- std ; Set direction flag
- .ENDIF
-
- .REPEAT
- lodsb ; Get first char from string
- .IF (si == bx) || (al == 0) ; If at head or tail limit:
- sub ax, ax ; No match
- sub dx, dx ; Set null pointer
- jmp exit
- .ENDIF
- .UNTILCXZ al == IChar
-
- mov ax, si ; Match, so point to first
- dec ax ; occurence
- .IF Direct != 0 ; If head-to-tail search:
- inc ax ; Adjust pointer forward
- inc ax
- mov dx, ds ; Pointer segment
- .ENDIF
- exit:
- ret
-
- StrFindChar ENDP
-
-
- ;* GetStr - Gets a string of up to 128 characters from the user. Since
- ;* this function uses the DOS input mechanism, it can use the DOS editing
- ;* keys or the keys of a DOS command-line editor if one is loaded.
- ;*
- ;* Shows: DOS Function - 0Ah (Buffered Keyboard Input)
- ;* Directive - EQU
- ;*
- ;* Params: Strbuf - Pointer to area where input string will be placed
- ;* Maxlen - Maximum length (up to 128 characters) of string
- ;*
- ;* Return: 0 if successful, 1 if error (Maxlen is too long)
-
- .DATA
- MAXSTR EQU 128
- max BYTE MAXSTR
- actual BYTE ?
- string BYTE MAXSTR DUP (?)
-
- .CODE
- GetStr PROC USES si di,
- Strbuf:PBYTE,
- Maxlen:WORD
-
- mov ax, 1 ; Assume error
- mov cx, Maxlen ; Copy length to register
-
- .IF (cx != 0) && (cx <= MAXSTR) ; Error if 0 or too long
- mov max, cl ; Load maximum length
- mov ah, 0Ah ; Request DOS Function 0Ah
- mov dx, OFFSET max ; Load offset of string
- int 21h ; Buffered Keyboard Input
-
- mov bl, actual ; Put number of characters read
- sub bh, bh ; in BX
- mov string[bx], 0 ; Null-terminate string
- mov cx, bx ; Put count in CX
- inc cx ; Plus one for the null terminator
-
- LoadPtr es, di, Strbuf ; ES:DI points to destination buffer
- mov si, OFFSET string ; DS:SI points to source string
- rep movsb ; Copy source to destination
- sub ax, ax ; Return 0 for success
- .ENDIF
-
- ret
-
- GetStr ENDP
-
- END
-
-
- FORTRAN.ASM
- CD-ROM Disc Path: \SAMPCODE\MASM\MASM6\MIXED\FORTRAN.ASM
-
- ; Power2 routine called by FMAIN.FOR
- ; Assemble with ML /c FORTRAN.ASM
-
- .MODEL LARGE, FORTRAN
-
- Power2 PROTO FORTRAN, factor:FAR PTR SWORD, power:FAR PTR SWORD
-
- .CODE
-
- Power2 PROC FORTRAN, factor:FAR PTR SWORD, power:FAR PTR SWORD
-
- les bx, factor
- mov ax, ES:[bx]
- les bx, power
- mov cx, ES:[bx]
- shl ax, cl
- ret
- Power2 ENDP
- END
-
-
- HANDLERS.ASM
- CD-ROM Disc Path: \SAMPCODE\MASM\MASM6\TSR\HANDLERS.ASM
-
- .MODEL small, pascal, os_dos
-
- ; Prototypes for internal procedures
- Activate PROTO NEAR
- CheckRequest PROTO NEAR
- CheckDos PROTO NEAR
- CheckHardware PROTO NEAR
- GetDosFlags PROTO NEAR
-
- INCLUDE tsr.inc
-
- .CODE
-
- ; Stack buffer used by TSR. Size is determined by constant STACK_SIZ,
- ; declared in TSR.INC file. NewStack points to top of stack.
-
- EVEN
- BYTE STACK_SIZ DUP(?) ; Stack buffer
- NewStack LABEL BYTE ; Pointer to top of stack
-
- ; Structures for interrupt handlers or "interrupt service routines".
- ; The following handlers are replaced during installation. Such routines
- ; usually set a flag to indicate they are active, optionally do some
- ; processing (such as detecting a hot key), call the old system interrupt
- ; routine, and when finished clear the active flag.
-
- HandArray LABEL BYTE ; Array of handler structures
- ; Num Flag OldHand NewHand
- intClock INTR < 8h, FALSE, NULL, Clock>
- intKeybrd INTR < 9h, FALSE, NULL, Keybrd>
- intVideo INTR <10h, FALSE, NULL, Video>
- intDiskIO INTR <13h, FALSE, NULL, DiskIO>
- intMisc INTR <15h, FALSE, NULL, SkipMiscServ>
- intIdle INTR <28h, FALSE, NULL, Idle>
- intMultex INTR <2Fh, FALSE, NULL, Multiplex>
-
- CHAND EQU ($ - HandArray) / (SIZEOF INTR) ; Number of handlers in array
-
- ; Interrupt trap routines. These interrupt routines are set up
- ; temporarily to trap keyboard break errors and critical errors
- ; while the TSR is active. When the TSR finishes its tasks, it
- ; restores the old interrupts before returning.
-
- TrapArray LABEL BYTE ; Array of trap structures
- ; Num Flag OldHand NewHand
- intCtrlBk INTR <1Bh, FALSE, NULL, CtrlBreak>
- intCtrlC INTR <23h, FALSE, NULL, CtrlC>
- intCritEr INTR <24h, FALSE, NULL, CritError>
-
- CTRAP EQU ($ - TrapArray) / (SIZEOF INTR) ; Number of traps in array
-
- ; Address of application's stack. Before calling the main body of the TSR,
- ; the Activate procedure stores the application's stack address, then resets
- ; SS:SP to point to LABEL NewStack (see above). This gives the TSR its own
- ; stack space without making demands on the current stack. Activate restores
- ; the application's stack before returning.
-
- OldStackAddr FPVOID ? ; SS:SP pointer to application stack
-
- ; The TSR must set up its own disk transfer area if it calls DOS functions
- ; that use the DTA (see Section 17.5.3 of the Programmer's Guide). DTA_SIZ
- ; is defined in the TSR.INC include file.
-
- IFDEF DTA_SIZ
- OldDtaAddr FPVOID ? ; Address of application's DTA
- DtaBuff BYTE DTA_SIZ DUP(?) ; DTA buffer
- ENDIF
-
- ; Multiplex data. STR_LEN is defined in the TSR.INC include file
-
- IDnumber BYTE 0 ; TSR's identity number
- IDstring BYTE STR_LEN DUP (0) ; Copy of identifier string
- IDstrlen WORD ? ; Length of identifier string
- ShareAddr FPVOID ? ; Address of shared memory
-
- ; Miscellaneous data
-
- TsrRequestFlag BYTE FALSE ; Flag set when hot key is pressed
- TsrActiveFlag BYTE FALSE ; Flag set when TSR executes
- BreakCheckFlag BYTE ? ; Break-checking status of applicatio
- TsrPspSeg WORD ? ; Segment address of PSP
- TsrAddr FPVOID ? ; Pointer to main part of TSR
- CritErrAddr FPVOID ? ; Pointer to MS-DOS critical error fl
- InDosAddr FPVOID ? ; Pointer to MS-DOS InDos flag
-
- ; Scan and shift codes for hot key. Install procedure initializes
- ; HotScan, HotShift, and HotMask during installation.
-
- HotScan BYTE ? ; Scan code hot key
- HotShift BYTE ? ; Shift value of hot key
- HotMask BYTE ? ; Mask unwanted shift values
-
- Version LABEL WORD ; DOS version number
- minor BYTE ?
- major BYTE ?
-
- ; Timer data, used when the TSR is activated at a preset time instead
- ; of activated from the keyboard. The following variables serve the
- ; same purposes as the counter variables used in the ALARM.ASM program
- ; presented in Section 17.3 of the Programmer's Guide. Refer to the
- ; header comments in the Install procedure for an explanation of how
- ; to set up a time-activated TSR.
-
- Tick91 BYTE 91 ; Measures 91 timer ticks (5 seconds)
- CountDown WORD 0 ; Counts 5-second intervals
-
-
-
- ;* Clock - Interrupt handler for Interrupt 08 (timer). Executes at each
- ;* timer interrupt, which occur an average of 18.2 times per second. Clock
- ;* first allows the original timer service routine to execute. It then
- ;* checks the flag TsrRequestFlag maintained either by the keyboard handler
- ;* (if keyboard-activated) or by this procedure (if time-activated). If
- ;* TsrRequestFlag = TRUE and system is okay, Clock invokes the TSR by
- ;* calling the Activate procedure. Uses an active flag to prevent the
- ;* Clock procedure from being reentered while executing.
- ;*
- ;* Uses: intClock, TsrActiveFlag, CountDown
- ;*
- ;* Params: None
- ;*
- ;* Return: None
-
- Clock PROC FAR
-
- pushf ; Simulate interrupt by pushing flags
- call cs:intClock.OldHand ; far-calling orig Int 08 routine
-
- .IF cs:intClock.Flag == FALSE ; If not already in this handler:
- mov cs:intClock.Flag, TRUE ; Set active flag
-
- sti ; Interrupts are okay
- push ds ; Save application's DS
- push cs
- pop ds ; Set DS to resident code segment
- ASSUME ds:@code
-
- INVOKE CheckRequest ; Check conditions
- .IF !carry? ; If TSR requested and safe:
- mov TsrActiveFlag, TRUE ; Activate TSR
- INVOKE Activate
- mov TsrActiveFlag, FALSE
- .ENDIF ; End carry flag check
-
- cmp CountDown, 0 ; If CountDown = 0, TSR is not time-
- je ticked ; activated or has already executed
- dec Tick91 ; Else count down 91 timer ticks
- jnz ticked ; If 91 ticks have not elapsed, exit
- mov Tick91, 91 ; Else reset secondary counter and
- dec CountDown ; subract one 5-second interval
- ja ticked ; If counter not yet drained, exit
- mov TsrRequestFlag, TRUE ; Else raise request flag
- ticked:
- mov intClock.Flag, FALSE ; Clear active flag
- pop ds ; Recover application's DS
- ASSUME ds:NOTHING
-
- .ENDIF ; End in-handler check
- iret
-
- Clock ENDP
-
-
- ;* Keybrd - Interrupt handler for Interrupt 09 (keyboard).
- ;*
- ;* IBM PC/AT and compatibles:
- ;* Gets the scan code of the current keystroke from port 60h. Then
- ;* compares the scan code and shift state to the hot key. If they
- ;* match, sets TsrRequestFlag to signal the handlers Clock and Idle
- ;* that the TSR is requested.
- ;*
- ;* IBM PS/2 series:
- ;* Only the instructions at KeybrdMonitor (see below) are installed
- ;* as Interrupt 09 handler, since above method should not be used to
- ;* determine current keystroke in IBM PS/2 series. In this case, the
- ;* Interrupt 15h handler MiscServ takes care of checking the scan codes
- ;* and setting the request flag when the hot key is pressed.
- ;*
- ;* Time-activated TSRs:
- ;* If the TSR is activated by time instead of by a hotkey, KeybrdMonitor
- ;* serves as the Interrupt 09 handler for both PC/AT and PS/2 systems.
- ;*
- ;* Uses: intKeybrd, TsrRequestFlag
- ;*
- ;* Params: None
- ;*
- ;* Return: None
-
- Keybrd PROC FAR
-
- sti ; Interrupts are okay
- push ax ; Save AX register
- in al, 60h ; AL = scan code of current key
- call CheckHotKey ; Check for hot key
- .IF !carry? ; If not hot key:
-
- ; Hot key pressed. Reset the keyboard to throw away keystroke.
-
- cli ; Disable interrupts while resetting
- in al, 61h ; Get current port 61h state
- or al, 10000000y ; Turn on bit 7 to signal clear keybr
- out 61h, al ; Send to port
- and al, 01111111y ; Turn off bit 7 to signal break
- out 61h, al ; Send to port
- mov al, 20h ; Reset interrupt controller
- out 20h, al
- sti ; Reenable interrupts
-
- pop ax ; Recover AX
- mov cs:TsrRequestFlag, TRUE ; Raise request flag
- iret ; Exit interrupt handler
- .ENDIF ; End hot-key check
-
- ; No hot key was pressed, so let normal Int 09 service routine take over
-
- pop ax ; Recover AX and fall through
- cli ; Interrupts cleared for service
-
- KeybrdMonitor LABEL FAR ; Installed as Int 09 handler for
- ; PS/2 or for time-activated TSR
- mov cs:intKeybrd.Flag, TRUE ; Signal that interrupt is busy
- pushf ; Simulate interrupt by pushing flags
- call cs:intKeybrd.OldHand ; far-calling old Int 09 routine
- mov cs:intKeybrd.Flag, FALSE
- iret
-
- Keybrd ENDP
-
-
- ;* Video - Interrupt handler for Interrupt 10h (video). Allows the original
- ;* video service routine to execute. Maintains an active flag to prevent
- ;* the TSR from being called while Interrupt 10h is executing.
- ;*
- ;* Uses: intVideo
- ;*
- ;* Params: Registers passed to Interrupt 10h
- ;*
- ;* Return: Registers returned by Interrupt 10h
-
- Video PROC FAR
-
- mov cs:intVideo.Flag, TRUE ; Set active flag
- pushf ; Simulate interrupt by pushing flags
- call cs:intVideo.OldHand ; far-calling old Int 10h routine
- mov cs:intVideo.Flag, FALSE ; Clear active flag
- iret
-
- Video ENDP
-
-
- ;* DiskIO - Interrupt handler for Interrupt 13h (disk I/O). Allows the
- ;* original disk I/O service routine to execute. Maintains an active flag
- ;* to prevent the TSR from being called while Interrupt 13h is executing.
- ;*
- ;* Uses: intDiskIO
- ;*
- ;* Params: Registers passed to Interrupt 13h
- ;*
- ;* Return: Registers and the carry flag returned by Interrupt 13h
-
- DiskIO PROC FAR
-
- mov cs:intDiskIO.Flag, TRUE ; Set active flag
- pushf ; Simulate interrupt by pushing flags
- call cs:intDiskIO.OldHand ; far-calling old Int 13h routine
- mov cs:intDiskIO.Flag, FALSE; Clear active flag without
- ; disturbing flags register
- sti ; Enable interrupts
- ret 2 ; Simulate IRET without popping flags
- ; (since services use carry flag)
- DiskIO ENDP
-
-
- ;* MiscServ - Interrupt handler for Interrupt 15h (Miscellaneous System
- ;* Services).
- ;*
- ;* IBM PC/AT and compatibles:
- ;* Stub at SkipMiscServ is used as handler, bypassing all calls to
- ;* Interrupt 15h. Keypresses are checked by Keybrd (Int 09 handler).
- ;*
- ;* IBM PS/2 series:
- ;* This procedure handles calls to Interrupt 15h, searching for
- ;* Function 4Fh (Keyboard Intercept Service). When AH = 4Fh, gets
- ;* scan code of current keystroke in AL register. Then compares the
- ;* scan code and shift state to the hot key. If they match, sets
- ;* TsrRequestFlag to signal the handlers Clock and Idle that the
- ;* TSR is requested.
- ;*
- ;* Uses: intMisc, TsrRequestFlag
- ;*
- ;* Params: Registers passed to Interrupt 15h
- ;*
- ;* Return: Registers returned by Interrupt 15h
-
- MiscServ PROC FAR
-
- sti ; Interrupts okay
- .IF ah == 4Fh ; If Keyboard Intercept Service:
- push ax ; Preserve AX
- call CheckHotKey ; Check for hot key
- pop ax
- .IF !carry? ; If hot key:
- mov cs:TsrRequestFlag, TRUE ; Raise request flag
- clc ; Signal BIOS not to process the key
- ret 2 ; Simulate IRET without popping flags
- .ENDIF ; End carry flag check
- .ENDIF ; End Keyboard Intercept check
-
- cli ; Disable interrupts and fall through
-
- SkipMiscServ LABEL FAR ; Interrupt 15h handler if PC/AT
-
- jmp cs:intMisc.OldHand
-
- MiscServ ENDP
-
-
- ;* CtrlBreak - Interrupt trap for Interrupt 1Bh (CTRL+BREAK Handler).
- ;* Disables CTRL+BREAK processing.
- ;*
- ;* Params: None
- ;*
- ;* Return: None
-
- CtrlBreak PROC FAR
-
- iret
-
- CtrlBreak ENDP
-
-
- ;* CtrlC - Interrupt trap for Interrupt 23h (CTRL+C Handler).
- ;* Disables CTRL+C processing.
- ;*
- ;* Params: None
- ;*
- ;* Return: None
-
- CtrlC PROC FAR
-
- iret
-
- CtrlC ENDP
-
-
- ;* CritError - Interrupt trap for Interrupt 24h (Critical Error Handler).
- ;* Disables critical error processing.
- ;*
- ;* Params: None
- ;*
- ;* Return: AL = Stop code 0 or 3
-
- CritError PROC FAR
-
- sti
- sub al, al ; Assume DOS 2.x
- ; Set AL = 0 for ignore error
- .IF cs:major != 2 ; If DOS 3.x, set AL = 3
- mov al, 3 ; DOS call fails
- .ENDIF
-
- iret
-
- CritError ENDP
-
-
- ;* Idle - Interrupt handler for Interrupt 28h (DOS Idle). Allows the
- ;* original Interrupt 28h service routine to execute. Then checks the
- ;* request flag TsrRequestFlag maintained either by the keyboard handler
- ;* (keyboard-activated TSR) or by the timer handler (time-activated TSR).
- ;* See header comments above for Clock, Keybrd, and MiscServ procedures.
- ;*
- ;* If TsrRequestFlag = TRUE and system is in interruptable state, Idle
- ;* invokes the TSR by calling the Activate procedure. Uses an active flag
- ;* to prevent the Idle procedure from being reentered while executing.
- ;*
- ;* Uses: intIdle and TsrActiveFlag
- ;*
- ;* Params: None
- ;*
- ;* Return: None
-
- Idle PROC FAR
-
- pushf ; Simulate interrupt by pushing flags
- call cs:intIdle.OldHand ; far-calling old Int 28h routine
-
- .IF cs:intIdle.Flag == FALSE; If not already in this handler:
- mov cs:intIdle.Flag, TRUE ; Set active flag
-
- sti ; Interrupts are okay
- push ds ; Save application's DS
- push cs
- pop ds ; Set DS to resident code segment
- ASSUME ds:@code
-
- INVOKE CheckRequest ; Check conditions
- .IF !carry? ; If TSR requested and safe:
- mov TsrActiveFlag, TRUE ; Activate TSR
- INVOKE Activate
- mov TsrActiveFlag, FALSE
- .ENDIF ; End carry flag check
-
- mov intIdle.Flag, FALSE ; Clear active flag
- pop ds ; Recover application's DS
- .ENDIF ; End in-handler check
-
- iret
-
- Idle ENDP
-
-
- ;* Multiplex - Handler for Interrupt 2Fh (Multiplex Interrupt). Checks
- ;* AH for this TSR's identity number. If no match (indicating call is
- ;* not intended for this TSR), Multiplex passes control to the previous
- ;* Interrupt 2Fh handler.
- ;*
- ;* Params: AH = Handler identity number
- ;* AL = Function number 0-2
- ;*
- ;* Return: AL = 0FFh (function 0)
- ;* ES:DI = Pointer to identifier string (function 0)
- ;* ES:DI = Pointer to resident PSP segment (function 1)
- ;* ES:DI = Pointer to shared memory (function 2)
-
- Multiplex PROC FAR
-
- .IF ah != cs:IDnumber ; If this handler not reqested:
- jmp cs:intMultex.OldHand ; Pass control to old Int 2Fh handler
- .ENDIF
-
- .IF al == 0 ; If function 0 (verify presence):
- mov al, 0FFh ; AL = 0FFh,
- push cs ; ES = resident code segment
- pop es
- mov di, OFFSET IDstring ; DI = offset of identifier string
-
- .ELSEIF al == 1 ; If function 1 (get PSP address):
- mov es, cs:TsrPspSeg ; ES:DI = far address of resident PSP
- sub di, di
-
- .ELSE
- les di, cs:ShareAddr ; If function 2 (get shared memory):
- .ENDIF ; set ES:DI = far address
-
- NoMultiplex LABEL FAR ; Secondary entry for null Multiplex
-
- iret
-
- Multiplex ENDP
-
-
- ;* CheckHotKey - Checks current keystroke for hot key. Called from Keybrd
- ;* handler if IBM PC/AT or compatible, or from MiscServ handler if PS/2.
- ;*
- ;* Uses: HotScan, HotShift, HotMask, and SHFT_STAT
- ;*
- ;* Params: AL = Scan code
- ;*
- ;* Return: Carry flag set = FALSE; carry flag clear = TRUE
-
- CheckHotKey PROC NEAR
-
- cmp al, cs:HotScan ; If current scan code isn't code
- jne e_exit ; for hot key, exit with carry set
-
- push es ; Else look into BIOS data area
- sub ax, ax ; (segment 0) to check shift state
- mov es, ax
- mov al, es:[SHFT_STAT] ; Get shift-key flags
- and al, cs:HotMask ; AND with "don't care" mask
- cmp al, cs:HotShift ; Compare result with hot shift key
- pop es
- je exit ; If match, exit with carry clear
-
- e_exit: stc ; Set carry if not hot key
- exit: ret
-
- CheckHotKey ENDP
-
-
- ;* CheckRequest - Checks request flag and system status using the
- ;* following logic:
- ;*
- ;* IF (TsrRequestFlag AND (NOT TsrActiveFlag)
- ;* AND DosStatus AND HardwareStatus)
- ;* return TRUE
- ;* ELSE
- ;* return FALSE
- ;*
- ;* Uses: TsrRequestFlag and TsrActiveFlag
- ;*
- ;* Params: DS = Resident code segment
- ;*
- ;* Return: Carry flag set = TRUE; carry flag clear = FALSE
-
- CheckRequest PROC NEAR
-
- rol TsrRequestFlag, 1 ; Rotate high bit into carry - set
- ; if TRUE (-1), clear if FALSE (0)
- cmc ; NOT carry
-
- .IF !carry? ; If TsrRequestFlag = TRUE:
- ror TsrActiveFlag, 1 ; Rotate low bit into carry - set
- ; if TRUE (-1), clear if FALSE (0)
- .IF !carry? ; If TsrActiveFlag = FALSE:
- INVOKE CheckDos ; Is DOS in interruptable state?
-
- .IF !carry? ; If so:
- INVOKE CheckHardware ; If hardware or BIOS unstable,
- .ENDIF ; set carry and exit
- .ENDIF
- .ENDIF
- ret
-
- CheckRequest ENDP
-
-
- ;* CheckDos - Checks status of MS-DOS using the following logic:
- ;*
- ;* IF (NOT CritErr) AND ((NOT InDos) OR (Idle AND InDos))
- ;* return DosStatus = TRUE
- ;* ELSE
- ;* return DosStatus = FALSE
- ;*
- ;* Uses: CritErrAddr, InDosAddr, and intIdle
- ;*
- ;* Params: DS = Resident code segment
- ;*
- ;* Return: Carry flag set if MS-DOS is busy
-
- CheckDos PROC NEAR USES es bx ax
-
- les bx, CritErrAddr
- mov ah, es:[bx] ; AH = value of CritErr flag
-
- les bx, InDosAddr
- mov al, es:[bx] ; AL = value of InDos flag
-
- sub bx, bx ; BH = 0, BL = 0
- cmp bl, intIdle.Flag ; Carry flag set if call is from
- ; Interrupt 28h handler
- rcl bl, 1 ; Rotate carry into BL: TRUE if Idle
- cmp bx, ax ; Carry flag clear if CritErr = 0
- ; and InDos <= BL
- ret
-
- CheckDos ENDP
-
-
- ;* CheckHardware - Checks status of BIOS and hardware using the
- ;* following logic:
- ;*
- ;* IF HardwareActive OR KeybrdActive OR VideoActive OR DiskIOActive
- ;* return HardwareStatus = FALSE
- ;* ELSE
- ;* return HardwareStatus = TRUE
- ;*
- ;* Uses: intKeybrd, intVideo, and intDiskIO
- ;*
- ;* Params: DS = Resident code segment
- ;*
- ;* Return: Carry flag set if hardware or BIOS is busy
-
- CheckHardware PROC NEAR USES ax
-
- ; Verify hardware interrupt status by interrogating Intel 8259A
- ; Programmable Interrupt Controller
-
- mov ax, 00001011y ; AL = 0CW3 for Intel 8259A
- ; (RR = 1, RIS = 1)
- out 20h, al ; Request 8259A in-service register
- jmp delay ; Wait a few cycles
- delay:
- in al, 20h ; AL = hardware interrupts being
- cmp ah, al ; serviced (bit = 1 if in service)
-
- .IF !carry? ; If no hard interrupts in service:
- sub al, al ; Verify BIOS interrupts not active
- cmp al, intKeybrd.Flag ; Check Interrupt 09 handler
-
- .IF !carry? ; If Int 09 not active:
- cmp al, intVideo.Flag ; Check Interrupt 10h handler
-
- .IF !carry? ; If Int 10h not active:
- cmp al, intDiskIO.Flag ; Check Interrupt 13h handler
- .ENDIF ; Return with carry set if
- .ENDIF ; Interrupt 09, 10h, or 13h
- .ENDIF ; is active
-
- ret
-
- CheckHardware ENDP
-
-
- ;* Activate - Sets up for far call to TSR with the following steps:
- ;*
- ;* 1. Stores stack pointer SS:SP and switches to new stack
- ;* 2. Pushes registers onto new stack
- ;* 3. Stores vectors for Interrupts 1Bh, 23h, and 23h, and
- ;* replaces them with addresses of error-trapping handlers
- ;* 4. Stores DOS Ctrl+C checking flag, then turns off checking
- ;* 5. If required, stores DTA address and switches to new DTA
- ;*
- ;* When TSR returns, restores all the above.
- ;*
- ;* Uses: Reads or writes the following globals:
- ;* OldStackAddr, TrapArray, BreakCheckFlag, TsrRequestFlag
- ;*
- ;* Params: DS = Resident code segment
- ;*
- ;* Return: None
-
- Activate PROC NEAR
-
- ; Step 1. Set up a new stack
-
- mov WORD PTR OldStackAddr[0], sp ; Save current
- mov WORD PTR OldStackAddr[2], ss ; stack pointer
-
- cli ; Turn off interrupts while
- push cs ; changing stack
- pop ss ; New stack begins
- mov sp, OFFSET NewStack ; at LABEL NewStack
- sti
-
- ; Step 2. Preserve registers (DS already saved in Clock or Idle)
-
- push ax
- push bx
- push cx
- push dx
- push si
- push di
- push bp
- push es
-
- cld ; Clear direction flag
-
- ; Step 3. Set up trapping handlers for keyboard breaks and DOS
- ; critical errors (Interrupts 1Bh, 23h, and 24h)
-
- mov cx, CTRAP ; CX = number of handlers
- mov si, OFFSET TrapArray ; DS:SI points to trap array
-
- .REPEAT
- mov al, [si] ; AL = interrupt number
- mov ah, 35h ; Request DOS Function 35h
- int 21h ; Get Interrupt Vector (ES:BX
- mov WORD PTR [si].INTR.OldHand[0], bx ; Save far address of
- mov WORD PTR [si].INTR.OldHand[2], es ; application's handler
- mov dx, WORD PTR [si].INTR.NewHand[0] ; DS:DX points to TSR's han
- mov ah, 25h ; Request DOS Function 25h
- int 21h ; Set Interrupt Vector
- add si, SIZEOF INTR ; DS:SI points to next in lis
- .UNTILCXZ
-
- ; Step 4. Disable MS-DOS break checking during disk I/O
-
- mov ax, 3300h ; Request DOS Function 33h
- int 21h ; Get Ctrl-Break Flag in DL
- mov BreakCheckFlag, dl ; Preserve it
-
- sub dl, dl ; DL = 0 to disable I/O break checkin
- mov ax, 3301h ; Request DOS Function 33h
- int 21h ; Set Ctrl-Break Flag from DL
-
- ; Step 5. If TSR requires a disk transfer area, store address of current
- ; DTA and switch buffer address to this segment. See Section 17.5.3 of
- ; Programmer's Guide for more information about the DTA.
-
- IFDEF DTA_SIZ
- mov ah, 2Fh ; Request DOS Function 2Fh
- int 21h ; Get DTA Address into ES:BX
- mov WORD PTR OldDtaAddr[0], bx ; Store address
- mov WORD PTR OldDtaAddr[2], es
-
- mov dx, OFFSET DtaBuff ; DS:DX points to new DTA
- mov ah, 1Ah ; Request DOS Function 1Ah
- int 21h ; Set DTA Address
- ENDIF
-
- ; Call main body of TSR.
-
- mov ax, @data
- mov ds, ax ; Initialize DS and ES
- mov es, ax ; to data segment
-
- call cs:TsrAddr ; Call main part of TSR
-
- push cs
- pop ds ; Reset DS to this segment
-
- ; Undo step 5. Restore previous DTA (if required)
-
- IFDEF DTA_SIZ
- push ds ; Preserve DS
- lds dx, OldDtaAddr ; DS:DX points to application's DTA
- mov ah, 1Ah ; Request DOS Function 1Ah
- int 21h ; Set DTA Address
- pop ds
- ENDIF
-
- ; Undo step 4. Restore previous MS-DOS break checking
-
- mov dl, BreakCheckFlag ; DL = previous break state
- mov ax, 3301h ; Request DOS Function 33h
- int 21h ; Set Ctrl-Break Flag from DL
-
- ; Undo step 3. Restore previous vectors for error-trapping handlers
-
- mov cx, CTRAP
- mov di, OFFSET TrapArray
- push ds ; Preserve DS
- push ds ; ES = resident code segment
- pop es
-
- .REPEAT
- mov al, es:[di] ; AL = interrupt number
- lds dx, es:[di].INTR.OldHand; DS:DX points to application's handl
- mov ah, 25h ; Request DOS Function 25h
- int 21h ; Set Interrupt Vector from DS:DX
- add di, SIZEOF INTR ; ES:DI points to next in list
- .UNTILCXZ
- pop ds
-
- ; Undo step 2. Restore registers from stack
-
- pop es
- pop bp
- pop di
- pop si
- pop dx
- pop cx
- pop bx
- pop ax
-
- ; Undo step 1. Restore address of original stack to SS:SP
-
- cli
- mov sp, WORD PTR OldStackAddr[0]
- mov ss, WORD PTR OldStackAddr[2]
- sti
-
- ; Clear request flag and return to caller (Clock or Idle procedure)
-
- mov TsrRequestFlag, FALSE
- ret
-
- Activate ENDP
-
-
-
- ;* INSTALLATION SECTION - The following code is executed only during
- ;* the TSR's installation phase. When the program terminates through
- ;* Function 31h, the above code and data remain resident; memory
- ;* occupied by the following code segment is returned to the operating
- ;* system.
-
- DGROUP GROUP INSTALLCODE
-
- INSTALLCODE SEGMENT PARA PUBLIC 'CODE2'
- ASSUME ds:@code
-
- ;* Install - Prepares for installation of a TSR by chaining interrupt
- ;* handlers and initializing pointers to DOS flags. Install does not
- ;* call the Terminate-and-Stay-Resident function.
- ;*
- ;* This library of routines accomodates both keyboard-activated and
- ;* time-activated TSRs. The latter are TSRs that activate at a preset
- ;* time. If the first parameter (Param1) is a valid scan code, Install
- ;* assumes the TSR is activated from the keyboard and sets up a keyboard
- ;* handler to search for the hotkey. If Param1 is null, Install assumes
- ;* the next two parameters (Param2 and Param3) are respectively the hour
- ;* and minute at which the TSR is to activate. In this case, Install
- ;* calls GetTimeToElapse to initialize the variable CountDown and sets
- ;* up KeybrdMonitor as the keyboard handler. CountDown and the secondary
- ;* counter Tick91 serve here the same functions as they do for the
- ;* ALARM.ASM program presented in Section 17.3 of the Programmer's Guide.
- ;* Install is callable from a high-level language.
- ;*
- ;* Uses: InDosAddr, CritErrAddr, CHAND,
- ;* HandArray, CTRAP, TrapArray
- ;*
- ;* Keyboard-activated Time-activated
- ;* ------------------ --------------
- ;* Params: Param1 - Scan code for hotkey 0
- ;* Param2 - Bit value for shift hotkey Hour to activate
- ;* Param3 - Bit mask for shift hotkey Minute to activate
- ;* Param4 - Far address of main TSR procedure (same)
- ;*
- ;* Return: AX = 0 if successful, or one of the following codes:
- ;* IS_INSTALLED FLAGS_NOT_FOUND NO_IDNUM
- ;* ALREADY_INSTALLED WRONG_DOS
-
- Install PROC FAR USES ds si di,
- Param1:WORD, Param2:WORD, Param3:WORD, Param4:FAR PTR FAR
-
- mov ax, @code
- mov ds, ax ; Point DS to code segment
-
- ; Get and store parameters passed from main program module
-
- mov al, BYTE PTR Param1
- mov HotScan, al ; Store hot key scan code
- mov al, BYTE PTR Param2 ; or flag for time-activate
- mov HotShift, al ; Store hot key shift value
- mov al, BYTE PTR Param3 ; or hour value
- mov HotMask, al ; Store hot key shift mask
- ; or minute value
- mov ax, WORD PTR Param4[0]
- mov bx, WORD PTR Param4[2]
- mov WORD PTR TsrAddr[0], ax ; Store segment:offset of
- mov WORD PTR TsrAddr[2], bx ; TSR's main code
-
- ; Get addresses of DOS flags, then check for prior installation
-
- INVOKE GetDosFlags ; Find DOS service flags
- or ax, ax
- jnz exit ; If flags not found, quit
-
- sub al, al ; Request multiplex function 0
- call CallMultiplex ; Invoke Interrupt 2Fh
- cmp ax, NOT_INSTALLED ; Check for presence of resident TSR
-
- .IF !zero? ; If TSR is installed:
- cmp ax, IS_INSTALLED ; Return with appropriate
- jne exit ; error code
- mov ax, ALREADY_INSTALLED
- jmp exit
- .ENDIF
-
- ; Check if TSR is to activate at the hour:minute specified by Param2:Param3.
- ; If so, determine the number of 5-second intervals that must elapse before
- ; activation, then set up the code at the far LABEL KeybrdMonitor to serve
- ; as the keyboard handler.
-
- .IF HotScan == 0 ; If valid scan code given:
- mov ah, HotShift ; AH = hour to activate
- mov al, HotMask ; AL = minute to activate
- call GetTimeToElapse ; Get number of 5-second intervals
- mov CountDown, ax ; to elapse before activation
-
- .ELSE ; Force use of KeybrdMonitor as
- ; keyboard handler
- cmp Version, 031Eh ; DOS Version 3.3 or higher?
- jb setup ; No? Skip next step
-
- ; Test for IBM PS/2 series. If not PS/2, use Keybrd and SkipMiscServ as
- ; handlers for Interrupts 09 and 15h respectively. If PS/2 system, set up
- ; KeybrdMonitor as the Interrupt 09 handler. Audit keystrokes with MiscServ
- ; handler, which searches for the hot key by handling calls to Interrupt 15h
- ; (Miscellaneous System Services). Refer to Section 17.2.1 of the Programmer'
- ; Guide for more information about keyboard handlers.
-
- mov ax, 0C00h ; Function 0Ch (Get System
- int 15h ; Configuration Parameters)
- sti ; Compaq ROM may leave disabled
-
- jc setup ; If carry set,
- or ah, ah ; or if AH not 0,
- jnz setup ; services are not supported
-
- test BYTE PTR es:[bx+5], 00010000y ; Test byte 4 to see if
- jz setup ; intercept is implemented
-
- mov ax, OFFSET MiscServ ; If so, set up MiscServ as
- mov WORD PTR intMisc.NewHand, ax ; Interrupt 15h handler
- .ENDIF
-
- mov ax, OFFSET KeybrdMonitor ; Set up KeybrdMonitor as
- mov WORD PTR intKeybrd.NewHand, ax ; Interrupt 09 handler
-
- ; Interrupt structure is now initialized for either PC/AT or PS/2 system.
- ; Get existing handler addresses from interrupt vector table, store in
- ; OldHand member, and replace with addresses of new handlers.
-
- setup:
- mov cx, CHAND ; CX = count of handlers
- mov si, OFFSET HandArray ; SI = offset of handler structures
-
- .REPEAT
- mov ah, 35h ; Request DOS Function 35h
- mov al, [si] ; AL = interrupt number
- int 21h ; Get Interrupt Vector in ES:BX
- mov WORD PTR [si].INTR.OldHand[0], bx ; Save far address
- mov WORD PTR [si].INTR.OldHand[2], es ; of current handler
- mov dx, WORD PTR [si].INTR.NewHand[0] ; DS:DX points to TSR handl
- mov ah, 25h ; Request DOS Function 25h
- int 21h ; Set Interrupt Vector from DS:DX
- add si, SIZEOF INTR ; DS:SI points to next in list
- .UNTILCXZ
-
- sub ax, ax ; Clear return code
- exit:
- ret ; Return to caller
-
- Install ENDP
-
-
- ;* Deinstall - Prepares for deinstallation of a TSR. Deinstall is the
- ;* complement of the Install procedure. It restores to the vector table
- ;* the original addresses replaced during installation, thus unhooking
- ;* the TSR's handlers. Checks to see if another TSR has installed handlers
- ;* for the interrupts in array HandArray. If so, the procedure fails with
- ;* an appropriate error code. Callable from a high-level language.
- ;*
- ;* Params: None
- ;*
- ;* Return: AX = Segment address of resident portion's PSP or
- ;* one of the following error codes:
- ;* CANT_DEINSTALL WRONG_DOS
-
- Deinstall PROC FAR USES ds si di
-
- mov ax, @code
- mov ds, ax ; Point DS to code segment
-
- sub al, al ; Request multiplex function 0
- call CallMultiplex ; Get resident code segment in ES
-
- cmp ax, IS_INSTALLED ; If not resident,
- jne exit ; exit with error
- push es ; Else point DS to
- pop ds ; resident code segment
- mov cx, CHAND ; Count of handlers
- mov si, OFFSET HandArray ; SI points to handler structures
-
- ; Read current vectors for TSR's interrupt handlers and compare with far
- ; addresses. If mismatch, another TSR has installed new handlers and ours
- ; cannot be safely deinstalled.
-
- .REPEAT
- mov al, [si] ; AL = interrupt number
- mov ah, 35h ; Request DOS Function 35h
- int 21h ; Get Interrupt Vector in ES:BX
- cmp bx, WORD PTR [si].INTR.NewHand[0] ; If offset different,
- jne e_exit ; error
- mov ax, es
- cmp ax, WORD PTR [si].INTR.NewHand[2] ; If segment different,
- jne e_exit ; error
- add si, SIZEOF INTR ; DS:SI points to next in list
- .UNTILCXZ
-
- ; If no interrupts replaced, call TSR's multiplex handler to locate
- ; address of resident portion's PSP. Although the PSP is not required
- ; until memory is returned to DOS, the call must be done now before
- ; unhooking the multiplex handler.
-
- mov al, 1 ; Request multiplex function 1
- call CallMultiplex ; Get resident code's PSP in ES
- push es ; Save it
-
- ; Unhook all handlers by restoring the original vectors to vector table.
-
- mov cx, CHAND ; Count of installed handlers
- mov si, OFFSET HandArray ; SI points to handler structures
-
- .REPEAT
- mov al, [si] ; AL = interrupt number
- push ds ; Preserve DS segment
- lds dx, [si].INTR.OldHand ; Put vector in DS:DX
- mov ah, 25h ; Request DOS Function 25h
- int 21h ; Set Interrupt Vector from DS:DX
- pop ds
- add si, SIZEOF INTR ; DS:SI points to next in list
- .UNTILCXZ
-
- pop ax ; Return address of resident PSP
- jmp exit ; to signal success
- e_exit:
- mov ax, CANT_DEINSTALL
- exit:
- ret
-
- Deinstall ENDP
-
-
- ;* GetVersion - Gets the DOS version and stores it in a global variable as
- ;* well as returning it in AX.
- ;*
- ;* Uses: Version
- ;*
- ;* Params: DS = Resident code segment
- ;*
- ;* Return: AH = Major version
- ;* AL = Minor version
-
- GetVersion PROC NEAR
-
- mov ax, 3000h ; Request DOS Function 30h
- int 21h ; Get MS-DOS Version Number
- .IF al < 2 ; If Version 1.x:
- mov ax, WRONG_DOS ; Abort with WRONG_DOS as error code
- .ELSE
- xchg ah, al ; AH = major, AL = minor version
- mov Version, ax ; Save in global
- .ENDIF
- ret
-
- GetVersion ENDP
-
-
- ;* GetDosFlags - Gets pointers to DOS's InDos and Critical Error flags.
- ;*
- ;* Params: DS = Resident code segment
- ;*
- ;* Return: 0 if successful, or the following error code:
- ;* FLAGS_NOT_FOUND
-
- GetDosFlags PROC NEAR
-
- ; Get InDOS address from MS-DOS
-
- mov ah, 34h ; Request DOS Function 34h
- int 21h ; Get Address of InDos Flag
- mov WORD PTR InDosAddr[0], bx ; Store address (ES:BX)
- mov WORD PTR InDosAddr[2], es ; for later access
-
- ; Determine address of Critical Error Flag
-
- mov ax, Version ; AX = DOS version number
-
- ; If DOS 3.1 or greater and not OS/2 compatibility mode, Critical Error
- ; flag is in byte preceding InDOS flag
- .IF (ah < 10) && (ah >= 3) && (al >= 10)
- dec bx ; BX points to byte before InDos flag
-
- .ELSE
- ; For earlier versions, the only reliable method is to scan through
- ; DOS to find an INT 28h instruction in a specific context.
-
- mov cx, 0FFFFh ; Maximum bytes to scan
- sub di, di ; ES:DI = start of DOS segment
-
- INT_28 EQU 028CDh
-
- .REPEAT
- mov ax, INT_28 ; Load opcode for INT 28h
-
- .REPEAT
- repne scasb ; Scan for first byte of opcode
-
- .IF !zero?
- mov ax, FLAGS_NOT_FOUND ; Return error if not found
- jmp exit
- .ENDIF
- .UNTIL ah == es:[di] ; For each matching first byte,
- ; check the second byte until match
-
- ; See if INT 28h is in this context:
- ; ; (-7) (-5)
- ; CMP ss:[CritErrFlag], 0 ; 36, 80, 3E, ?, ?, 0
- ; JNE NearLabel ; 75, ?
- int 28h ; CD, 28
- ; ; (0) (1)
- CMP_SS EQU 3E80h
- P_CMP_SS EQU 8
- P_CMP_OP EQU 6
-
- mov ax, CMP_SS ; Load and compare opcode to CMP
- .IF ax == es:[di-P_CMP_SS] ; If match:
- mov bx, es:[di-P_CMP_OP] ; BX = offset of
- jmp exit ; Critical Error Flag
- .ENDIF
-
- ; See if INT 28h is in this context:
- ; ; (-12) (-10)
- ; TEST ?s:[CritErr], 0FFh ; ?6 F6, 06, ?, ?, FF
- ; JNE NearLabel ; 75, ?
- ; PUSH ss:[CritErrFlag] ; 36, FF, 36, ?, ?
- int 28h ; CD, 28
- ; ; (0) (1)
- TEST_SS EQU 06F6h
- P_TEST_SS EQU 13
- P_TEST_OP EQU 11
-
- mov ax, TEST_SS ; Load AX = opcode for TEST
- .UNTIL ax == es:[di-P_TEST_SS] ; If not TEST, continue scan
-
- mov bx, es:[di-P_TEST_OP] ; Else load BX with offset of
- .ENDIF ; Critical Error flag
- exit:
- mov WORD PTR CritErrAddr[0], bx ; Store address of
- mov WORD PTR CritErrAddr[2], es ; Critical Error Flag
- sub ax, ax ; Clear error code
- ret
-
- GetDosFlags ENDP
-
-
- ;* GetTimeToElapse - Determines number of 5-second intervals that
- ;* must elapse between specified hour:minute and current time.
- ;*
- ;* Params: AH = Hour
- ;* AL = Minute
- ;*
- ;* Return: AX = Number of 5-second intervals
-
- GetTimeToElapse PROC NEAR
-
- push ax ; Save hour:minute
- mov ah, 2Ch ; Request DOS Function 2Ch
- int 21h ; Get Time (CH:CL = hour:minute)
- pop bx ; Recover hour:minute
- mov dl, dh
- sub dh, dh
- push dx ; Save DX = current seconds
-
- mov al, 60 ; 60 minutes/hour
- mul bh ; Mutiply by specified hour
- sub bh, bh
- add bx, ax ; BX = minutes from midnight
- ; to activation time
- mov al, 60 ; 60 minutes/hour
- mul ch ; Multiply by current hour
- sub ch, ch
- add ax, cx ; AX = minutes from midnight
- ; to current time
- sub bx, ax ; BX = minutes to elapse before
- .IF carry? ; If activation is tomorrow:
- add bx, 24 * 60 ; add number of minutes per day
- .ENDIF
-
- mov ax, 60
- mul bx ; DX:AX = minutes-to-elapse-times-60
- pop bx ; Recover current seconds
- sub ax, bx ; DX:AX = seconds to elapse before
- sbb dx, 0 ; activation
- .IF carry? ; If negative:
- mov ax, 5 ; Assume 5 seconds
- cwd
- .ENDIF
-
- mov bx, 5 ; Divide result by 5 seconds
- div bx ; AX = number of 5-second intervals
- ret
-
- GetTimeToElapse ENDP
-
-
- ;* CallMultiplex - Calls the Multiplex Interrupt (Interrupt 2Fh).
- ;*
- ;* Uses: IDstring
- ;*
- ;* Params: AL = Function number for multiplex handler
- ;*
- ;* Return: AX = One of the following return codes:
- ;* NOT_INSTALLED IS_INSTALLED NO_IDNUM
- ;* ES:DI = Resident code segment:identifier string (function 0)
- ;* ES:DI = Resident PSP segment address (function 1)
- ;* ES:DI = Far address of shared memory (function 2)
-
- CallMultiplex PROC FAR USES ds
-
- push ax ; Save function number
- mov ax, @code
- mov ds, ax ; Point DS to code segment
-
- ; First, check 2Fh vector. DOS Version 2.x may leave the vector null
- ; if PRINT.COM is not installed. If vector is null, point it to IRET
- ; instruction at LABEL NoMultiplex. This allows the new multiplex
- ; handler to pass control, if necessary, to a proper existing routine.
-
- mov ax, 352Fh ; Request DOS Function 35h
- int 21h ; Get Interrupt Vector in ES:BX
- mov ax, es
- or ax, bx
- .IF zero? ; If Null vector:
- mov dx, OFFSET NoMultiplex ; Set vector to IRET instruction
- mov ax, 252Fh ; at LABEL NoMultiplex
- int 21h ; Set Interrupt Vector
- .ENDIF
-
- ; Second, call Interrupt 2Fh with function 0 (presence request). Cycle
- ; through allowable identity numbers (192 to 255) until TSR's multiplex
- ; handler returns ES:DI = IDstring to verify its presence or until call
- ; returns AL = 0, indicating the TSR is not installed.
-
- mov dh, 192 ; Start with identity number = 192
-
- .REPEAT
- mov ah, dh ; Call Multiplex with AH = trial ID
- sub al, al ; and AL = function 0
- push dx ; Save DH and DS in case call
- push ds ; destroys them
- int 2Fh ; Multiplex
- pop ds ; Recover DS and
- pop dx ; current ID number in DH
- or al, al ; Does a handler claim this ID number
- jz no ; If not, stop search
-
- .IF al == 0FFh ; If handler ready to process calls:
- mov si, OFFSET IDstring ; Point DS:SI to ID string, compare
- mov cx, IDstrlen ; with string at ES:DI returned
- repe cmpsb ; by multiplex handler
- je yes ; If equal, TSR's handler is found
- .ENDIF
-
- inc dh ; This handler is not the one
- .UNTIL zero? ; Try next identity number up to 255
-
- mov ax, NO_IDNUM ; In the unlikely event that numbers
- jmp e_exit ; 192-255 are all taken, quit
-
- ; Third, assuming handler is found and verified, process the multiplex
- ; call with the requested function number.
-
- yes:
- pop ax ; AL = original function number
- mov ah, dh ; AH = identity number
- int 2Fh ; Multiplex
- mov ax, IS_INSTALLED ; Signal that handler has been found
- jmp exit ; and quit
-
- ; Reaching this section means multiplex handler (and TSR) not installed.
- ; Since the value in DH is not claimed by any handler, it will be used as
- ; the resident TSR's identity number. Save the number in resident code
- ; segment so multiplex handler can find it.
-
- no:
- mov IDnumber, dh ; Save multiplex identity number
- mov ax, NOT_INSTALLED ; Signal handler is not installed
- e_exit:
- pop bx ; Remove function number from stack
- exit:
- ret
-
- CallMultiplex ENDP
-
-
- ;* InitTsr - Initializes DOS version variables and multiplex data with
- ;* following parameters. This procedure must execute before calling
- ;* either the Install, Deinstall, or CallMultiplex procedures. Callable
- ;* from a high-level language.
- ;*
- ;* Uses: IDstring
- ;*
- ;* Params: PspParam - Segment address of PSP
- ;* StrParam - Far address of TSR's identifier string
- ;* ShrParam - Far address of shared memory
- ;*
- ;* Return: AX = WRONG_DOS if not DOS Version 2.0 or higher
-
- InitTsr PROC FAR USES ds es si di,
- PspParam:WORD, StrParam:FPVOID, ShrParam:FPVOID
-
- mov ax, @code
- mov ds, ax ; Point DS and ES
- mov es, ax ; to code segment
-
- ; Get and store parameters passed from main program module
-
- mov ax, PspParam
- mov TsrPspSeg, ax ; Store PSP segment address
-
- mov ax, WORD PTR ShrParam[0]
- mov bx, WORD PTR ShrParam[2]
- mov WORD PTR ShareAddr[0], ax ; Store far address of
- mov WORD PTR ShareAddr[2], bx ; shared memory
-
- push ds
- mov si, WORD PTR StrParam[0] ; DS:SI points to multiplex
- mov ax, WORD PTR StrParam[2] ; identifier string
- mov ds, ax
- mov di, OFFSET IDstring ; Copy string to IDstring
- mov cx, STR_LEN ; at ES:DI so multiplex
- ; handler has a copy
- .REPEAT
- lodsb ; Copy STR_LEN characters
- .BREAK .IF al == 0 ; or until null-terminator
- stosb ; found
- .UNTILCXZ
-
- pop ds ; Recover DS = code segment
- mov ax, STR_LEN
- sub ax, cx
- mov IDstrlen, ax ; Store string length
-
- INVOKE GetVersion ; Return AX = version number
- ret ; or WRONG_DOS
-
- InitTsr ENDP
-
-
- INSTALLCODE ENDS
-
- END
-
-
- INSTALL.ASM
- CD-ROM Disc Path: \SAMPCODE\MASM\MASM6\TSR\INSTALL.ASM
-
- .MODEL small, pascal, os_dos
- INCLUDE tsr.inc
-
- ;* INSTALLATION SECTION - The following code and data are used only
- ;* during the TSR's installation phase. When the program terminates
- ;* through Function 31h, memory occupied by the following code and
- ;* data segments is returned to the operating system.
-
- DGROUP GROUP INSTALLCODE, INSTALLDATA
-
- INSTALLDATA SEGMENT WORD PUBLIC 'DATA2' ; Data segment for installation phase
-
- PUBLIC _MsgTbl
-
- _MsgTbl WORD Msg0 ; Deinstalled okay
- WORD Msg1 ; Installed okay
- WORD Msg2 ; Already installed
- WORD Msg3 ; Can't install
- WORD Msg4 ; Can't find flag
- WORD Msg5 ; Can't deinstall
- WORD Msg6 ; Requires DOS 2+
- WORD Msg7 ; MCB damaged
- WORD Msg8 ; Invalid ID
- WORD Msg9 ; Invalid memory block address
- WORD Msg10 ; Successful access
- WORD Msg11 ; Can't access
- WORD Msg12 ; Unrecognized option
-
- Msg0 BYTE CR, LF, "TSR deinstalled", CR, LF, 0
- Msg1 BYTE CR, LF, "TSR installed", CR, LF, 0
- Msg2 BYTE CR, LF, "TSR already installed", CR, LF, 0
- Msg3 BYTE CR, LF, "Can't install TSR", CR, LF, 0
- Msg4 BYTE CR, LF, "Can't find MS-DOS Critical Error Flag", CR, LF, 0
- Msg5 BYTE CR, LF, "Can't deinstall TSR", CR, LF, 0
- Msg6 BYTE CR, LF, "Requires MS-DOS 2.0 or later", CR, LF, 0
- Msg7 BYTE CR, LF, "Memory Control Block damaged", CR, LF, 0
- Msg8 BYTE CR, LF, "No ID numbers available", CR, LF, 0
- Msg9 BYTE CR, LF, "Can't free memory block: invalid address", CR, LF,0
- Msg10 BYTE CR, LF, "TSR successfully accessed", CR, LF, 0
- Msg11 BYTE CR, LF, "Can't access: TSR not installed", CR, LF, 0
- Msg12 BYTE CR, LF, "Unrecognized option", CR, LF, 0
-
- INSTALLDATA ENDS
-
-
- INSTALLCODE SEGMENT PARA PUBLIC 'CODE2'
-
- ASSUME ds:@data
-
- ;* GetOptions - Scans command line for argument of form /X or -X
- ;* where X = specified ASCII character. Presumes that argument is
- ;* preceded by either '/' or '-'. Comparisons are case-insensitive.
- ;* Designed to be callable only from an assembly language program.
- ;*
- ;* Params: ES = Segment address of Program Segment Prefix
- ;* AL = Argument character for which to scan
- ;*
- ;* Return: AX = One of the following codes:
- ;* NO_ARGUMENT if empty command line
- ;* OK_ARGUMENT if argument found
- ;* BAD_ARGUMENT if argument not as specified
- ;* ES:DI = Pointer to found argument
-
- GetOptions PROC NEAR
-
- and al, 11011111y ; Make character upper-case
- mov ah, NO_ARGUMENT ; Assume no argument
- mov di, 80h ; Point to command line
- sub ch, ch
- mov cl, BYTE PTR es:[di] ; Command-line count
- jcxz exit ; If none, quit
- sub bx, bx ; Initialize flag
-
- ; Find start of argument
-
- loop1:
- inc di ; Point to next character
- mov dl, es:[di] ; Get character from argument list
- cmp dl, '/' ; Find option prefix '/'
- je analyze
- cmp dl, '-' ; or option prefix '-'
- je analyze
- .IF (dl != ' ') && (dl != TAB ) ; If not white space:
- inc bx ; Set flag if command line not empty
- .ENDIF
-
- loop loop1
-
- or bx, bx ; Empty command line?
- jz exit ; Yes? Normal exit
- jmp SHORT e_exit ; Error if no argument is preceded
- ; by '-' or '/' prefixes
-
- ; '/' or '-' prefix found. Compare command-line character
- ; with character specified in AL.
- analyze:
- mov ah, OK_ARGUMENT ; Assume argument is okay
- inc di
- mov dl, es:[di]
- and dl, 11011111y ; Convert to upper-case
- cmp dl, al ; Argument as specified?
- je exit ; If so, normal exit
- mov ah, BAD_ARGUMENT ; Else signal bad argument,
- inc bx ; raise flag, and
- jmp loop1 ; continue scan
-
- e_exit:
- mov ah, BAD_ARGUMENT
- exit:
- mov al, ah
- cbw ; AX = return code
- ret
-
- GetOptions ENDP
-
-
- ;* FatalError - Displays an error message and exits to DOS.
- ;* Callable from a high-level language.
- ;*
- ;* Params: Err = Error number
- ;*
- ;* Return: AL = Error number returned to DOS (except DOS 1.x)
-
- FatalError PROC FAR,
- Err:WORD
-
- mov ax, Err
- push ax
- mov bx, @data
- mov ds, bx ; DS points to DGROUP
- mov bx, OFFSET _MsgTbl
- shl ax, 1 ; Double to get offset into _MsgTbl
- add bx, ax ; BX = table index
- mov si, [bx] ; DS:SI points to message
- sub bx, bx ; BH = page 0
- mov ah, 0Eh ; Request video Function 0Eh
-
- .WHILE 1
- lodsb ; Get character from ASCIIZ string
- .BREAK .IF al == 0 ; Break if null terminator
- int 10h ; Display text, advance cursor
- .ENDW
-
- pop ax ; Recover original error code
-
- .IF ax == WRONG_DOS ; If DOS error:
- int 20h ; Terminate Program (Version 1.x)
- .ELSE ; Else:
- mov ah, 4Ch ; Request DOS Function 4Ch
- int 21h ; Terminate Program (2.x and later)
- .ENDIF
-
- FatalError ENDP
-
-
- ;* KeepTsr - Calls Terminate-and-Stay-Resident function to
- ;* make TSR resident. Callable from a high-level language.
- ;*
- ;* Params: ParaNum - Number of paragraphs in resident block
- ;*
- ;* Return: DOS return code = 0
-
- KeepTsr PROC FAR,
- ParaNum:WORD
-
- mov ax, @data
- mov ds, ax ; DS:SI points to "Program
- mov si, OFFSET Msg1 ; installed" message
- sub bx, bx ; BH = page 0
- mov ah, 0Eh ; Request video Function 0Eh
-
- .WHILE 1
- lodsb ; Get character from ASCIIZ string
- .BREAK .IF al == 0 ; Break if null terminator
- int 10h ; Display text, advance cursor
- .ENDW
-
- mov dx, ParaNum ; DX = number of paragraphs
- mov ax, 3100h ; Request Function 31h, err code = 0
- int 21h ; Terminate-and-Stay-Resident
- ret
-
- KeepTsr ENDP
-
-
- ;* FreeTsr - Deinstalls TSR by freeing its two memory blocks: program
- ;* block (located at PSP) and environment block (located from address
- ;* at offset 2Ch of PSP). Callable from a high-level language.
- ;*
- ;* Params: PspSeg - Segment address of TSR's Program Segment Prefix
- ;*
- ;* Return: AX = 0 if successful, or one of the following error codes:
- ;* MCB_DESTROYED if Memory Control Block damaged
- ;* INVALID_ADDR if invalid block address
-
- FreeTsr PROC FAR,
- PspSeg:WORD
-
- mov es, PspSeg ; ES = address of resident PSP
- mov ah, 49h ; Request DOS Function 49h
- int 21h ; Release Memory in program block
-
- .IF !carry? ; If no error:
- mov es, es:[2Ch] ; ES = address of environment block
- mov ah, 49h ; Request DOS Function 49h
- int 21h ; Release Memory in environment block
- .IF !carry? ; If no error:
- sub ax, ax ; Return AX = 0
- .ENDIF ; Else exit with AX = error code
- .ENDIF
-
- ret
-
- FreeTsr ENDP
-
-
- ;* CallMultiplexC - Interface for CallMultiplex procedure to make it
- ;* callable from a high-level language. Separating this ability from
- ;* the original CallMultiplex procedure keeps assembly-language calls
- ;* to CallMultiplex neater and more concise.
- ;*
- ;* Params: FuncNum - Function number for multiplex handler
- ;* RecvPtr - Far address to recieve ES:DI pointer
- ;*
- ;* Return: One of the following return codes:
- ;* NOT_INSTALLED IS_INSTALLED NO_IDNUM
- ;* ES:DI pointer written to address in RecvPtr
-
- CallMultiplexC PROC FAR USES ds si di,
- FuncNum:WORD, RecvPtr:FPVOID
-
- mov al, BYTE PTR FuncNum ; AL = function number
- call CallMultiplex ; Multiplex
-
- lds si, RecvPtr ; DS:SI = far address of pointer
- mov [si], di ; Return ES:DI pointer for the
- mov [si+2], es ; benefit of high-level callers
- ret
-
- CallMultiplexC ENDP
-
-
- ;* GetResidentSize - Returns the number of paragraphs between Program
- ;* Segment Prefix and beginning of INSTALLCODE. This routine allows
- ;* TSRs written in a high-level language to determine the size in
- ;* paragraphs required to make the program resident.
- ;*
- ;* Params: PspSeg - PSP segment address
- ;*
- ;* Return: AX = Number of paragraphs
-
- GetResidentSize PROC FAR,
- PspSeg:WORD
-
- mov ax, INSTALLCODE ; Bottom of resident section
- sub ax, PspSeg ; AX = number of paragraphs in
- ret ; block to be made resident
-
- GetResidentSize ENDP
-
-
- INSTALLCODE ENDS
-
- END
-
-
- MATH.ASM
- CD-ROM Disc Path: \SAMPCODE\MASM\MASM6\DEMOS\MATH.ASM
-
- .MODEL small, pascal, os_dos
- INCLUDE demo.inc
- .CODE
-
- ;* AddLong - Adds two double-word (long) integers.
- ;*
- ;* Shows: Instructions - add adc
- ;* Operator - PTR
- ;*
- ;* Params: Long1 - First integer
- ;* Long2 - Second integer
- ;*
- ;* Return: Sum as long integer
-
- AddLong PROC,
- Long1:SDWORD, Long2:SDWORD
-
- mov ax, WORD PTR Long1[0] ; AX = low word, long1
- mov dx, WORD PTR Long1[2] ; DX = high word, long1
- add ax, WORD PTR Long2[0] ; Add low word, long2
- adc dx, WORD PTR Long2[2] ; Add high word, long2
- ret ; Result returned as DX:AX
-
- AddLong ENDP
-
- ;* SubLong - Subtracts a double-word (long) integer from another.
- ;*
- ;* Shows: Instructions - sub sbb
- ;*
- ;* Params: Long1 - First integer
- ;* Long2 - Second integer
- ;*
- ;* Return: Difference as long integer
-
- SubLong PROC,
- Long1:SDWORD, Long2:SDWORD
-
- mov ax, WORD PTR Long1[0] ; AX = low word, long1
- mov dx, WORD PTR Long1[2] ; DX = high word, long1
- sub ax, WORD PTR Long2[0] ; Subtract low word, long2
- sbb dx, WORD PTR Long2[2] ; Subtract high word, long2
- ret ; Result returned as DX:AX
-
- SubLong ENDP
-
-
- ;* MulLong - Multiplies two unsigned double-word (long) integers. The
- ;* procedure allows for a product of twice the length of the multipliers,
- ;* thus preventing overflows. The result is copied into a 4-word data area
- ;* and a pointer to the data area is returned.
- ;*
- ;* Shows: Instruction - mul
- ;* Predefined equate - @data
- ;*
- ;* Params: Long1 - First integer (multiplicand)
- ;* Long2 - Second integer (multiplier)
- ;*
- ;* Return: Pointer to quadword result
-
- .DATA
- PUBLIC result
- result QWORD WORD PTR ? ; Result from MulLong
-
- .CODE
- MulLong PROC,
- Long1:DWORD, Long2:DWORD
-
- mov ax, WORD PTR Long2[2] ; Multiply long2 high word
- mul WORD PTR Long1[2] ; by long1 high word
- mov WORD PTR result[4], ax
- mov WORD PTR result[6], dx
-
- mov ax, WORD PTR Long2[2] ; Multiply long2 high word
- mul WORD PTR Long1[0] ; by long1 low word
- mov WORD PTR result[2], ax
- add WORD PTR result[4], dx
- adc WORD PTR result[6], 0 ; Add any remnant carry
-
- mov ax, WORD PTR Long2[0] ; Multiply long2 low word
- mul WORD PTR Long1[2] ; by long1 high word
- add WORD PTR result[2], ax
- adc WORD PTR result[4], dx
- adc WORD PTR result[6], 0 ; Add any remnant carry
-
- mov ax, WORD PTR Long2[0] ; Multiply long2 low word
- mul WORD PTR Long1[0] ; by long1 low word
- mov WORD PTR result[0], ax
- add WORD PTR result[2], dx
- adc WORD PTR result[4], 0 ; Add any remnant carry
-
- mov ax, OFFSET result ; Return pointer
- mov dx, @data ; to result
- ret
-
- MulLong ENDP
-
-
- ;* ImulLong - Multiplies two signed double-word integers. Because the imul
- ;* instruction (illustrated here) treats each word as a signed number, its
- ;* use is impractical when multiplying multi-word values. Thus the technique
- ;* used in the MulLong procedure can't be adopted here. Instead, ImulLong
- ;* is broken into three sections arranged in ascending order of computational
- ;* overhead. The procedure tests the values of the two integers and selects
- ;* the section that involves the minimum required effort to multiply them.
- ;*
- ;* Shows: Instruction - imul
- ;*
- ;* Params: Long1 - First integer (multiplicand)
- ;* Long2 - Second integer (multiplier)
- ;*
- ;* Return: Result as long integer
-
- ImulLong PROC USES si,
- Long1:SDWORD, Long2:SDWORD
-
- ; Section 1 tests for integers in the range of 0 to 65,535. If both
- ; numbers are within these limits, they're treated as unsigned short
- ; integers.
-
- mov ax, WORD PTR Long2[0] ; AX = low word of long2
- mov dx, WORD PTR Long2[2] ; DX = high word of long2
- mov bx, WORD PTR Long1[0] ; BX = low word of long1
- mov cx, WORD PTR Long1[2] ; CX = high word of long1
- .IF (dx == 0) && (cx == 0) ; If both high words are zero:
- mul bx ; Multiply the low words
- jmp exit ; and exit section 1
- .ENDIF
-
- ; Section 2 tests for integers in the range of -32,768 to 32,767. If
- ; both numbers are within these limits, they're treated as signed short
- ; integers.
-
- push ax ; Save long2 low word
- push bx ; Save long1 low word
- or dx, dx ; High word of long2 = 0?
- jnz notzhi2 ; No? Test for negative
- test ah, 80h ; Low word of long2 in range?
- jz notnlo2 ; Yes? long2 ok, so test long1
- jmp sect3 ; No? Go to section 3
- notzhi2:
- cmp dx, 0FFFFh ; Empty with sign flag set?
- jne sect3 ; No? Go to section 3
- test ah, 80h ; High bit set in low word?
- jz sect3 ; No? Low word is too high
- notnlo2:
- or cx, cx ; High word of long1 = 0?
- jnz notzhi1 ; No? Test for negative
- test bh, 80h ; Low word of long1 in range?
- jz notnlo1 ; Yes? long1 ok, so use sect 2
- jmp sect3 ; No? Go to section 3
- notzhi1:
- cmp cx, 0FFFFh ; Empty with sign flag set?
- jne sect3 ; No? Go to section 3
- test bh, 80h ; High bit set in low word?
- jz sect3 ; No? Low word is too high
- notnlo1:
- imul bx ; Multiply low words
- pop bx ; Clean stack
- pop bx
- jmp exit ; Exit section 2
-
- ; Section 3 involves the most computational overhead. It treats the two
- ; numbers as signed long (double-word) integers.
-
- sect3:
- pop bx ; Recover long1 low word
- pop ax ; Recover long2 low word
- mov si, dx ; SI = long2 high word
- push ax ; Save long2 low word
- mul cx ; long1 high word x long2 low word
- mov cx, ax ; Accumulate products in CX
- mov ax, bx ; AX = low word of long1
- mul si ; Multiply by long2 high word
- add cx, ax ; Add to previous product
- pop ax ; Recover long2 low word
- mul bx ; Multiply by long1 low word
- add dx, cx ; Add to product high word
- exit:
- ret ; Return result as DX:AX
-
- ImulLong ENDP
-
-
- ;* DivLong - Divides an unsigned long integer by an unsigned short integer.
- ;* The procedure does not check for overflow or divide-by-zero.
- ;*
- ;* Shows: Instruction - div
- ;*
- ;* Params: Long1 - First integer (dividend)
- ;* Short2 - Second integer (divisor)
- ;* Remn - Pointer to remainder
- ;*
- ;* Return: Quotient as short integer
-
- DivLong PROC USES di,
- Long1:DWORD, Short2:WORD, Remn:PWORD
-
- mov ax, WORD PTR Long1[0] ; AX = low word of dividend
- mov dx, WORD PTR Long1[2] ; DX = high word of dividend
- div Short2 ; Divide by short integer
- LoadPtr es, di, Remn ; Point ES:DI to remainder
- mov es:[di], dx ; Copy remainder
- ret ; Return with AX = quotient
-
- DivLong ENDP
-
-
- ;* IdivLong - Divides a signed long integer by a signed short integer.
- ;* The procedure does not check for overflow or divide-by-zero.
- ;*
- ;* Shows: Instruction - idiv
- ;*
- ;* Params: Long1 - First integer (dividend)
- ;* Short2 - Second integer (divisor)
- ;* Remn - Pointer to remainder
- ;*
- ;* Return: Quotient as short integer
-
- IdivLong PROC USES di,
- Long1:SDWORD, Short2:SWORD, Remn:PSWORD
-
- mov ax, WORD PTR Long1[0] ; AX = low word of dividend
- mov dx, WORD PTR Long1[2] ; DX = high word of dividend
- idiv Short2 ; Divide by short integer
- LoadPtr es, di, Remn ; ES:DI = remainder
- mov es:[di], dx ; Copy remainder
- ret ; Return with AX = quotient
-
- IdivLong ENDP
-
-
- ;* Quadratic - Solves for the roots of a quadratic equation of form
- ;* A*x*x + B*x + C = 0
- ;* using floating-point instructions. This procedure requires either a math
- ;* coprocessor or emulation code.
- ;*
- ;* Shows: Instructions - sahf fld1 fld fadd fmul
- ;* fxch fsubr fchs fsubp fstp
- ;* fst fstsw fdivr fwait ftst
- ;*
- ;* Params: a - Constant for 2nd-order term
- ;* b - Constant for 1st-order term
- ;* c - Equation constant
- ;* R1 - Pointer to 1st root
- ;* R2 - Pointer to 2nd root
- ;*
- ;* Return: Short integer with return code
- ;* 0 if both roots found
- ;* 1 if single root (placed in R1)
- ;* 2 if indeterminate
-
- Quadratic PROC USES ds di si,
- aa:DWORD, bb:DWORD, cc:DWORD, r1:PDWORD, r2:PDWORD
-
- LOCAL status:WORD ; Intermediate status
-
- LoadPtr es, di, r1 ; ES:DI points to 1st root
- LoadPtr ds, si, r2 ; DS:SI points to 2nd root
- sub bx, bx ; Clear error code
- fld1 ; Load top of stack with 1
- fadd st, st ; Double it to make 2
- fld st ; Copy to next register
- fmul aa ; ST register = 2a
- ftst ; Test current ST value
- fstsw status ; Copy status to local word
- fwait ; Ensure coprocessor is done
- mov ax, status ; Copy status into AX
- sahf ; Load flag register
- jnz notzero ; If C3 set, a = 0, in which case
- ; solution is x = -c / b
- fld cc ; Load c parameter
- fchs ; Reverse sign
- fld bb ; Load b parameter
- ftst ; Test current ST value
- fstsw status ; Copy status to local word
- fwait ; Ensure coprocessor is done
- mov ax, status ; Copy status into AX
- sahf ; Load flag register
- jz exit2 ; If C3 set, b = 0, in which case
- ; division by zero
- fdiv ; Divide by B
- fstp DWORD PTR es:[di] ; Copy result and pop stack
- fstp st ; Clean up stack
- jmp exit1 ; Return with code = 1
- notzero:
- fmul st(1), st ; ST(1) register = 4a
- fxch ; Exchange ST and ST(1)
- fmul cc ; ST register = 4ac
- ftst ; Test current ST value
- fstsw status ; Copy status to local word
- fwait ; Ensure coprocessor is done
- mov ax, status ; Copy status into AX
- sahf ; Load flag register
- jp exit2 ; If C2 set, 4*a*c is infinite
-
- fld bb ; Else load b parameter
- fmul st, st ; Square it; ST register = b*b
- fsubr ; ST register = b*b - 4*a*c
- ftst ; Test current ST value
- fstsw status ; Copy status to local word
- fwait ; Ensure coprocessor is done
- mov ax, status ; Copy status into AX
- sahf ; Load flag register
- jc exit2 ; If C0 set, b*b < 4ac
- jnz tworoot ; If C3 set, b*b = 4ac, in which
- inc bx ; case only 1 root so set flag
- tworoot:
- fsqrt ; Get square root
- fld bb ; Load b parameter
- fchs ; Reverse sign
- fxch ; Exchange ST and ST1
- fld st ; Copy square root to next reg
- fadd st, st(2) ; ST = -b + sqrt(b*b - 4*a*c)
- fxch ; Exchange ST and ST1
- fsubp st(2), st ; ST = -b - sqrt(b*b - 4*a*c)
-
- fdiv st, st(2) ; Divide 1st dividend by 2*a
- fstp DWORD PTR es:[di] ; Copy result, pop stack
- fdivr ; Divide 2nd dividend by 2*a
- fstp DWORD PTR ds:[si] ; Copy result, pop stack
- jmp exit ; Return with code
- exit2:
- inc bx ; Error code = 2 for indeterminancy
- fstp st ; Clean stack
- exit1:
- inc bx ; Error code = 1 for single root
- fstp st ; Clean stack
- exit:
- mov ax, bx
- ret
-
- Quadratic ENDP
-
- END
-
-
- MISC.ASM
- CD-ROM Disc Path: \SAMPCODE\MASM\MASM6\DEMOS\MISC.ASM
-
- .modeL small, pascal, os_dos
- INCLUDE demo.inc
-
- .DATA
- _psp PSEG ? ; Segment of PSP
- _env PSEG ? ; Segment of environment
-
- .CODE
-
- ;* WinOpen - Saves portion of screen to allocated memory, then opens a window
- ;* with specified fill attribute. See also the WinClose procedure.
- ;*
- ;* Shows: DOS Function - 48h (Allocate Memory Block)
- ;* Instructions - movsw stosw rep
- ;*
- ;* Uses: vconfig - Video configuration structure (initialized
- ;* by calling the GetVidConfig procedure)
- ;*
- ;* Params: Row1 - Row at top of window
- ;* Col1 - Column at left edge of window
- ;* Row2 - Row at bottom of window
- ;* Col2 - Column at right edge of window
- ;* Attr - Fill attribute for window
- ;*
- ;* Return: Short integer with segment address of allocated buffer, or
- ;* 0 if unable to allocate memory
-
- WinOpen PROC USES ds di si,
- Row1:WORD, Col1:WORD, Row2:WORD, Col2:WORD, Attr:WORD
-
- GetVidOffset Row1, Col1 ; Get offset in video segment
- mov si, ax ; SI = video offset for window
- mov bx, Row2
- sub bx, Row1
- inc bx ; BX = number of window rows
- mov cx, Col2
- sub cx, Col1
- inc cx ; CX = number of columns
-
- mov ax, cx ; Compute number of video
- mul bl ; cells in window
- add ax, 3 ; Plus 3 additional entries
- shr ax, 1 ; Shift right 3 times to
- shr ax, 1 ; multiply by 2 bytes/cell,
- shr ax, 1 ; divide by 16 bytes/para
- inc ax ; Add a paragraph
- push bx ; Save number of rows
- mov bx, ax ; BX = number of paragraphs
- mov ah, 48h ; Request DOS Function 48h
- int 21h ; Allocate Memory Block
- pop bx
-
- .IF carry? ; If unsuccessful:
- sub ax, ax ; Return null pointer
- .ELSE
- mov es, ax ; Point ES:DI to allocated
- sub di, di ; buffer
- mov ax, si
- stosw ; Copy video offset to buffer
- mov ax, bx
- stosw ; Number of rows to buffer
- mov ax, cx
- stosw ; Number of cols to buffer
- mov ax, 160 ; Number of video cells/row
- mov ds, vconfig.sgmnt ; DS = video segment
-
- .REPEAT
- push si ; Save ptr to start of line
- push cx ; and number of columns
-
- ; For CGA adapters, WinOpen avoids screen "snow" by disabling the video prior
- ; to block memory moves, then reenabling it. Although this technique can
- ; result in brief flickering, it demonstrates the fastest way to access a
- ; block in the CGA video buffer without causing display snow. See also the
- ; StrWrite procedure for another solution to the problem of CGA snow.
-
- .IF vconfig.adapter == CGA ; If not CGA adapter,
- INVOKE DisableCga ; disable video
- .ENDIF
-
- rep movsw ; Copy one row to buffer
-
- .IF vconfig.adapter == CGA ; If CGA adapter,
- INVOKE EnableCga ; reenable CGA video
- .ENDIF
- pop cx ; Recover number of columns
- pop si ; and start of line
- add si, ax ; Point to start of next line
- dec bx ; Decrement row counter
- .UNTIL zero? ; Until no rows remain
-
- ; Screen contents (including display attributes) are now copied to buffer.
- ; Next open window, overwriting the screen portion just saved.
-
- mov ax, 0600h ; Scroll service
- mov bh, BYTE PTR Attr ; Fill attribute
- mov cx, Col1 ; CX = row/col for upper left
- mov ch, BYTE PTR Row1
- mov dx, Col2 ; DX = row/col for lower right
- mov dh, BYTE PTR Row2
- int 10h ; Blank window area on screen
- mov ax, es ; Return address of allocated
- .ENDIF ; segment
- ret
-
- WinOpen ENDP
-
-
- ;* WinClose - "Closes" a window previously opened by the WinOpen procedure.
- ;* See also the WinOpen procedure.
- ;*
- ;* Shows: DOS Function - 49h (Release Memory Block)
- ;* Instructions - lodsw
- ;* Operators - : (segment override) SEG
- ;*
- ;* Uses: vconfig - Video configuration structure (initialized
- ;* by calling the GetVidConfig procedure)
- ;*
- ;* Params: Adr - Segment address of buffer that holds screen contents
- ;* saved in WinOpen procedure
- ;*
- ;* Return: None
-
- WinClose PROC USES ds di si,
- Adr:WORD
-
- mov ds, Adr ; DS:SI points to buffer
- sub si, si
- lodsw
- mov di, ax ; DI = video offset of window
- lodsw
- mov bx, ax ; BX = number of window rows
- lodsw
- mov cx, ax ; CX = number of columns
-
- mov ax, SEG vconfig.sgmnt
- mov es, ax ; Point ES to data segment
- push es:vconfig.sgmnt
- pop es ; ES = video segment
- mov ax, 160 ; Number of video cells/row
-
- .REPEAT
- push di ; Save ptr to start of line
- push cx ; and number of columns
-
- ; Disable CGA video prior to memory move to avoid screen snow. (See the
- ; WinOpen and StrWrite procedures for further discussions on CGA snow.)
-
- .IF vconfig.adapter == CGA ; If CGA adapter,
- INVOKE DisableCga ; disable video
- .ENDIF
-
- rep movsw ; Copy one row to buffer
-
- .IF vconfig.adapter == CGA ; If CGA adapter,
- INVOKE EnableCga ; reenable CGA video
- .ENDIF
- pop cx ; Recover number of columns
- pop di ; and start of line
- add di, ax ; Point to start of next line
- dec bx ; Decrement row counter
- .UNTIL zero? ; until no rows remain
-
- mov ah, 49h ; Request DOS Function 49h
- mov es, Adr
- int 21h ; Release Memory Block
- ret
-
- WinClose ENDP
-
-
- ;* SetCurSize - Sets cursor size.
- ;*
- ;* Shows: BIOS Interrupt - 10h, Function 1 (Set Cursor Type)
- ;*
- ;* Params: Scan1 - Starting scan line
- ;* Scan2 - Ending scan line
- ;*
- ;* Return: None
-
- SetCurSize PROC,
- Scan1:WORD, Scan2:WORD
-
- mov cx, Scan2 ; CL = ending scan line
- mov ch, BYTE PTR Scan1 ; CH = starting scan line
- mov ah, 1 ; Function 1
- int 10h ; Set Cursor Type
- ret
-
- SetCurSize ENDP
-
-
- ;* GetCurSize - Gets current cursor size.
- ;*
- ;* Shows: BIOS Interrupt - 10h, Function 3 (Get Cursor Position)
- ;*
- ;* Uses: vconfig - Video configuration structure (initialized
- ;* by calling the GetVidConfig procedure)
- ;*
- ;* Params: None
- ;*
- ;* Return: Short integer with high byte = top scan line,
- ;* low byte = bottom scan line
-
- GetCurSize PROC
-
- mov ah, 3 ; Function 3
- mov bh, vconfig.dpage
- int 10h ; Get Cursor Position
- mov ax, cx ; Return cursor size
- ret
-
- GetCurSize ENDP
-
-
- ;* GetShift - Gets current shift status. Checks for extended keyboard,
- ;* and if available returns additional shift information.
- ;*
- ;* Shows: BIOS Interrupt - 16h, Functions 2 and 12h (Get Keyboard Flags)
- ;*
- ;* Params: None
- ;*
- ;* Return: Long integer
- ;* high word = 0 for non-extended keyboard
- ;* 1 for extended keyboard
- ;* low word has following bits set when indicated keys are pressed:
- ;* 0 - Right shift 8 - Left Ctrl
- ;* 1 - Left shift 9 - Left Alt
- ;* 2 - Ctrl 10 - Right Ctrl
- ;* 3 - Alt 11 - Right Alt
- ;* 4 - Scroll Lock active 12 - Scroll Lock pressed
- ;* 5 - Num Lock active 13 - Num Lock pressed
- ;* 6 - Caps Lock active 14 - Caps Lock pressed
- ;* 7 - Insert toggled 15 - Sys Req pressed
-
- GetShift PROC
-
- sub dx, dx ; Assume non-extended keyboard
- mov ah, 2 ; and use Function 2
- mov es, dx ; Point ES to low memory
- .IF BYTE PTR es:[496h] & 16 ; If extended keyboard installed,
- inc dx ; Set high word of return code
- mov ah, 12h ; and use Function 12h
- .ENDIF
- int 16h ; Get Keyboard Flags
- ret
-
- GetShift ENDP
-
-
- ;* GetKeyClock - Waits for keypress while updating time at specified location
- ;* on screen.
- ;*
- ;* Shows: BIOS Interrupt - 16h, Functions 0 and 10h (Read Character)
- ;* 16h, Functions 1 and 11h (Get Keyboard Status)
- ;* DOS Functions - 2Ah (Get Date)
- ;* 2Ch (Get Time)
- ;*
- ;* Uses: vconfig - Video configuration structure (initialized
- ;* by calling the GetVidConfig procedure)
- ;*
- ;* Params: Row - Screen row for clock display
- ;* Col - Screen column for clock display
- ;*
- ;* Return: Short integer with key scan code in high byte and ASCII
- ;* character code in low byte. Low byte is 0 for special
- ;* keys (such as the "F" keys) which don't generate characters.
-
- .DATA
- PUBLIC datestr
- datestr BYTE " - - : : ", 0 ; Date/time string
- .CODE
-
- GetKeyClock PROC,
- Row:WORD, Col:WORD
-
- LOCAL service:BYTE
-
- INVOKE GetShift ; Check for extended keyboard
- mov service, 11h ; Assume Function 11h
- .IF dx != 1 ; If no extended keyboard:
- mov service, 1 ; Use Function 1
- .ENDIF
-
- .WHILE 1
- mov ah, service
- int 16h ; Get Keyboard Status
- .BREAK .IF !zero? ; If no key yet, update clock
-
- ; If not monochrome, color text, or black and white, skip clock update
- ; and poll keyboard again
-
- .CONTINUE .IF (vconfig.mode != 7) \
- && (vconfig.mode != 3) \
- && (vconfig.mode != 2)
-
- ; If 80-column text, get date and time from DOS before again
- ; polling keyboard, and display at upper right corner of screen.
-
- mov ah, 2Ch ; Request time
- int 21h ; Get Time
- mov dl, dh
- push dx ; Save seconds,
- push cx ; minutes,
- mov cl, ch ; and
- push cx ; hours
- mov ah, 2Ah ; Request date
- int 21h ; Get Date
- sub cx, 1900 ; Subtract century, CL = year
- push cx ; Save year,
- push dx ; day,
- mov dl, dh ; and
- push dx ; month
-
- mov cx, 6
- sub bx, bx
-
- .REPEAT
- pop ax ; Recover all 6 numbers in AL
- aam ; Convert to unpacked BCD
- xchg al, ah ; Switch bytes for word move
- or ax, "00" ; Make ASCII numerals
- mov WORD PTR datestr[bx], ax; Copy to string
- add bx, 3 ; at every third byte
- .UNTILCXZ
-
- INVOKE StrWrite, Row, Col, ADDR datestr
- .ENDW ; Loop again for keypress
-
- mov ah, service ; 1 or 11h, depending on keybd
- dec ah ; Set AH to 0 or 10h
- int 16h ; Get key to remove it from
- ret ; keyboard buffer
-
- GetKeyClock ENDP
-
-
- ;* GetPSP - Gets address of Program Segment Prefix. For DOS 3.0 or higher.
- ;*
- ;* Shows: DOS Function - 62h (Get PSP Address)
- ;* Instruction - call
- ;*
- ;* Params: None
- ;*
- ;* Return: Short integer with PSP segment address
- ;* or 0 if DOS version below 3.0
-
- GetPSP PROC
-
- INVOKE GetVer ; Get DOS version number
- .IF ax >= 300 ; If DOS 3.0 or higher:
- mov ah, 62h ; Query DOS for PSP
- int 21h ; Get PSP Address
- mov ax, bx ; Return in AX
- .ELSE ; Else 2.0:
- sub ax, ax ; For version 2, return 0
- .ENDIF
- ret
-
- GetPSP ENDP
-
-
- ;* GetMem - Gets total size of memory and determines the largest amount of
- ;* unallocated memory available. GetMem invokes DOS Function 48h (Allocate
- ;* Memory) to request an impossibly large memory block. DOS denies the re-
- ;* quest, but returns instead the size of the largest block available. This
- ;* is the amount that GetMem returns to the calling program. See the WinOpen
- ;* procedure for an example of calling Function 48h to allocate unused memory
- ;*
- ;* Shows: BIOS Interrupt - 12h (Get Conventional Memory Size)
- ;* Instructions - push pop ret
- ;*
- ;* Params: None
- ;*
- ;* Return: Long integer, high word = total memory in kilobytes (KB)
- ;* low word = largest block of available memory (KB)
-
- GetMem PROC
-
- int 12h ; Get total memory in K
- push ax ; Save size of memory
- mov ah, 48h ; Request memory allocation
- mov bx, 0FFFFh ; Ensure request is denied for
- ; impossibly large block
- int 21h ; Get largest available block in BX
- mov ax, bx ; Copy to AX
- mov cl, 6 ; Convert paragraphs to kilobytes by
- shr ax, cl ; dividing by 64
- pop dx ; Recover total in DX
- ret ; Return long integer DX:AX
-
- GetMem ENDP
-
-
- ;* VeriPrint - Checks if LPT1 (PRN) is available.
- ;*
- ;* Shows: BIOS Interrupt - 17h (Parallel Port Printer Driver)
- ;*
- ;* Params: None
- ;*
- ;* Return: Short integer, 1 for yes or 0 for no
-
- VeriPrint PROC
-
- mov ah, 2 ; Check printer status for
- sub dx, dx ; parallel printer (port 0)
- int 17h
- xchg dx, ax ; Put 0 (for error) in AX
-
- ; If all error bits are off and both operation bits are on, return 1
-
- .IF !(dh & 00101001y) && (dh & 10010000y)
- inc ax ; Return 1
- .ENDIF
- ret
-
- VeriPrint ENDP
-
-
- ;* IntToAsc - Converts integer to ASCII string. This procedure is useful
- ;* only for assembly language, and is not intended to be C-callable.
- ;*
- ;* Shows: Instructions - aam xchg
- ;*
- ;* Entry: AX = integer (9999 max)
- ;*
- ;* Return: DX:AX = 4-digit ASCII number
-
- IntToAsc PROC
-
- cwd ; Zero DX register
- mov cx, 100 ; Divide AX by 100, yields
- div cx ; AX=quotient, DX=remainder
- aam ; Make digits unpacked BCD
- or ax, "00" ; Convert to ASCII
- xchg ax, dx ; Do same thing for DX
- aam
- or ax, "00"
- ret ; Return DX:AX = ASCII number
-
- IntToAsc ENDP
-
-
- ;* VeriAnsi - Checks for ANSI driver by writing ANSI sequence to report
- ;* cursor position. If report compares with position returned from
- ;* GetCurPos procedure, then ANSI driver is operating.
- ;*
- ;* Shows: DOS Functions - 06h (Direct Console I/O)
- ;* 0Ch (Flush Input Buffer and then Input)
- ;*
- ;* Params: None
- ;*
- ;* Return: Short integer, 1 for yes or 0 for no
-
- .DATA
- PUBLIC report
- report DB ESCAPE, "[6n$" ; ANSI Report Cursor sequence
- .CODE
-
- VeriAnsi PROC
-
- ; Get cursor position from BIOS
- INVOKE GetCurPos
- mov cx, ax ; Save it in CX
- mov dx, OFFSET report ; ANSI string to get position
- mov ah, 9 ; Request DOS String Output
- int 21h ; Write ANSI escape sequence
-
- mov ah, 6 ; Skip Esc character in
- mov dl, 0FFh ; keyboard buffer
- int 21h
- jz e_exit ; If no key, ANSI not loaded
- mov ah, 6 ; Skip '[' character
- int 21h
- jz e_exit ; If no key, ANSI not loaded
- mov ah, 6 ; Get 1st digit of cursor row
- int 21h
- jz e_exit ; If no key, ANSI not loaded
- mov bh, al ; Store in BH
- mov ah, 6 ; Get 2nd digit of cursor row
- int 21h
- jz e_exit ; If no key, ANSI not loaded
- mov bl, al ; Store in BL
- mov al, ch ; Get original row # in AL
- cbw ; AX = row # from GetCurPos
- inc ax ; Add 1 to it
- call IntToAsc ; Make ASCII digits
- cmp ax, bx ; ANSI and BIOS reports match?
- jne e_exit ; No? Then ANSI not loaded
-
- mov ax, 0C06h ; Flush remaining ANSI keys
- mov dl, 0FFh ; from buffer
- int 21h
- mov ax, 1 ; Set 1 for true
- jmp exit ; and exit
- e_exit:
- sub ax, ax ; Set 0 return code if no
- exit:
- ret ; ANSI driver installed
-
- VeriAnsi ENDP
-
-
- ;* VeriCop - Checks for coprocessor.
- ;*
- ;* Shows: BIOS Interrupt - 11h (Get Equipment Configuration)
- ;*
- ;* Params: None
- ;*
- ;* Return: Short integer, 1 for yes or 0 for no
-
- VeriCop PROC
-
- int 11h ; Check peripherals
- test al, 2 ; Coprocessor?
- mov ax, 0 ; Assume no, don't alter flags
- .IF !zero?
- inc ax ; Set to 1
- .ENDIF
- ret
-
- VeriCop ENDP
-
-
- ;* SetLineMode - Sets line mode for EGA or VGA.
- ;*
- ;* Shows: BIOS Interrupt - 10h, Function 11h (Character Generator Interface
- ;* 10h, Function 12h (Video Subsystem Configuration
- ;*
- ;* Uses: vconfig - Video configuration structure (initialized
- ;* by calling the GetVidConfig procedure)
- ;*
- ;* Params: Line - Requested line mode (25, 43, or 50)
- ;*
- ;* Return: Short integer with error code
- ;* 0 if successful
- ;* 1 if error
-
- SetLineMode PROC,
- Line:WORD
-
- .IF vconfig.adapter >= EGA ; If EGA or VGA:
- mov ax, Line ; Check for valid parameter
- cmp al, 25
- je line25
- cmp al, 43
- je line43
- cmp al, 50
- je line50
- jmp e_exit ; If not 25, 43, or 50, exit w/ error
- line25:
- mov al, 11h ; Set for EGA 25-line mode
- cmp vconfig.adapter, EGA ; EGA?
- je linemode ; Yes? Continue
- mov ax, 1202h ; No? Function 12h for VGA
- mov bl, 30h ; AL = 2 for 400 scan lines
- int 10h ; Reset to 400 scan lines
- mov ax, 0003 ; Reset mode (Function 0)
- int 10h ; to mode 3 (80-col text)
- mov al, 14h ; Request 8x16 char matrix
- jmp linemode
- line43:
- mov al, 12h ; Set for EGA 43-line mode
- cmp vconfig.adapter, EGA ; EGA?
- je linemode ; Yes? Continue
- mov ax, 1201h ; No? Function 12h for VGA
- mov bl, 30h ; AL = 1 for 350 scan lines
- int 10h ; Reset to 350 scan lines
- mov ax, 0003 ; Reset mode (Function 0)
- int 10h ; to mode 3 (80-col text)
- mov al, 12h ; Request 8x8 character matrix
- jmp linemode
- line50:
- cmp vconfig.adapter, VGA ; VGA?
- jne e_exit ; No? Exit with error
- mov ax, 1202h ; Yes? Function 12h
- mov bl, 30h ; AL = 2 for 400 scan lines
- int 10h ; Reset to 400 scan lines
- mov ax, 0003 ; Reset mode (Function 0)
- int 10h ; to mode 3 (80-col text)
- mov al, 12h ; Request 8x8 character matrix
- linemode:
- sub bl, bl ; Use table 0
- mov ah, 11h ; Request Function 11h
- int 10h ; Set new line mode
-
- mov ah, 12h ; Select alternate print
- mov bl, 20h ; screen for EGA and VGA
- int 10h
-
- cmp vconfig.adapter, VGA ; VGA?
- je exit ; Yes? Then exit
- cmp Line, 12h ; If EGA 43-line mode, set
- je port ; cursor through port to
- ; avoid cursor emulation bug
-
- ; Set normal cursor size, pass top and bottom scan lines
- INVOKE SetCurSize, 6, 7
- jmp exit
- port:
- mov dx, 03D4h ; Video controller address
- mov ax, 060Ah ; Set AH = 06h (cursor start)
- ; AL = 0Ah (register #)
- out dx, ax ; Update port
- mov ax, 000Bh ; Set AH = 00h (cursor end)
- ; AL = 0Bh (register #)
- out dx, ax ; Update port
- jmp exit ; Normal exit
- .ENDIF ; EGA or VGA
- e_exit:
- mov ax, 1 ; Set error code
- jmp exit2
- exit:
- sub ax, ax ; Clear error code
- exit2:
- ret
-
- SetLineMode ENDP
-
-
- ;* Pause - Waits for specified number of clocks to elapse, then returns.
- ;*
- ;* Shows: BIOS Interrupt - 1Ah, Function 0 (Real-Time Clock Driver)
- ;* Operators - LOCAL []
- ;*
- ;* Params: Duration - Desired duration in clocks, where
- ;* 18 clocks = approx 1 second
- ;*
- ;* Return: None
-
- Pause PROC,
- Duration:WORD
-
- LOCAL tick:DWORD
-
- sub ah, ah
- int 1Ah ; Get Clock Count in CX:DX
- add dx, Duration ; Add pause time to it
- adc cx, 0
- mov WORD PTR tick[0], dx ; Result is target time;
- mov WORD PTR tick[2], cx ; keep in local variable
-
- .REPEAT
- int 1Ah ; Poll clock until target time
- .UNTIL (dx >= WORD PTR tick[0]) || (cx >= WORD PTR fileinfo.time[2])
- ret
-
- Pause ENDP
-
-
- ;* Sound - Sounds speaker with specified frequency and duration.
- ;*
- ;* Shows: Instructions - in out
- ;*
- ;* Params: Freq - Desired frequency of sound in Hertz
- ;* Duration - Desired duration in clocks, where
- ;* 18 clocks = approx 1 second
- ;*
- ;* Return: None
-
- Sound PROC,
- Freq:WORD, Duration:WORD
-
- mov al, 0B6h ; Initialize channel 2 of
- out 43h, al ; timer chip
- mov dx, 12h ; Divide 1,193,182 Hertz
- mov ax, 34DEh ; (clock frequency) by
- div Freq ; desired frequency
- ; Result is timer clock count
- out 42h, al ; Low byte of count to timer
- mov al, ah
- out 42h, al ; High byte of count to timer
- in al, 61h ; Read value from port 61h
- or al, 3 ; Set first two bits
- out 61h, al ; Turn speaker on
-
- ; Pause, pass duration of delay
- INVOKE Pause, Duration
-
- in al, 61h ; Get port value
- xor al, 3 ; Kill bits 0-1 to turn
- out 61h, al ; speaker off
- ret
-
- Sound ENDP
-
-
- ;* WriteTTY - Displays ASCIIZ string at cursor position, in either text
- ;* or graphics mode.
- ;*
- ;* Shows: BIOS Interrupt - 10h, Function 0Eh (Write Character in TTY Mode)
- ;*
- ;* Uses: vconfig - Video configuration structure (initialized
- ;* by calling the GetVidConfig procedure)
- ;*
- ;* Params: Sptr - Pointer to ASCIIZ string
- ;* icolor - Color index (for graphics mode only)
- ;*
- ;* Return: None
-
- WriteTTY PROC USES ds si,
- Sptr:PBYTE, icolor:WORD
-
- mov bx, icolor ; BL = color index
- mov bh, vconfig.dpage ; BH = current display page
- LoadPtr ds, si, Sptr
- mov cx, -1 ; Set loop counter to maximum
- mov ah, 14 ; Function 14
-
- .REPEAT
- lodsb ; Get character from string
- .BREAK .IF al == 0 ; Exit if NULL string terminator
- int 10h ; No? Display, advance cursor
- .UNTILCXZ
-
- ret
-
- WriteTTY ENDP
-
-
- ;* Colors - Alters screen colors within a specified area by using bit
- ;* or move operations on display attribute bytes in video memory.
- ;*
- ;* Shows: Instructions - not rol ror and xor or
- ;*
- ;* Params: Logic - Code number, 0 = NOT 2 = ROR 4 = XOR 6 = MOV
- ;* 1 = ROL 3 = AND 5 = OR
- ;* Attr - Attribute mask
- ;* Row1 - Row at top of window
- ;* Col1 - Column at left edge of window
- ;* Row2 - Row at bottom of window
- ;* Col2 - Column at right edge of window
- ;*
- ;* Return: None
-
- Colors PROC USES ds si,
- Logic:WORD, Attr:WORD, Row1:WORD, Col1:WORD, Row2:WORD, Col2:WORD
-
- GetVidOffset Row1, Col1 ; Get offset in video segment
- inc ax
- mov si, ax ; SI = offset for 1st attr byte
- mov bx, Row2
- sub bx, Row1
- inc bx ; BX = number of window rows
- mov cx, Col2
- sub cx, Col1
- inc cx ; CX = number of columns
-
- mov ds, vconfig.sgmnt ; DS = video segment
- mov ax, Attr ; AL = mask for and, xor, and or
-
- .REPEAT
- push si ; Save ptr to start of line
- push cx ; and number of columns
-
- ; Disable CGA video prior to memory access to avoid screen snow. (See the
- ; WinOpen and StrWrite procedures for further discussions on CGA snow.)
-
- .IF vconfig.adapter == CGA ; If CGA adapter:
- INVOKE DisableCga ; Yes? Disable video
- .ENDIF
-
- cmp Logic, 1 ; Rotate left?
- jl c_not ; If less, do NOT
- je c_rol ; If equal, do ROL
- cmp Logic, 3 ; And?
- jl c_ror ; If less, do ROR
- je c_and ; If equal, do AND
- cmp Logic, 5 ; Or?
- jl c_xor ; If less, do XOR
- je c_or ; If equal, do OR
- c_mov:
- mov BYTE PTR [si], al ; MOV attr parameter
- add si, 2 ; into attribute byte
- loop c_mov
- jmp c_done
- c_or:
- or BYTE PTR [si], al ; OR with attr parameter
- add si, 2
- loop c_or
- jmp c_done
- c_xor:
- xor BYTE PTR [si], al ; XOR with attr parameter
- add si, 2
- loop c_xor
- jmp c_done
- c_and:
- and BYTE PTR [si], al ; AND with attr parameter
- add si, 2
- loop c_and
- jmp c_done
- c_ror:
- ror BYTE PTR [si], 1 ; Rotate right 1 bit
- add si, 2
- loop c_ror
- jmp c_done
- c_rol:
- rol BYTE PTR [si], 1 ; Rotate left 1 bit
- add si, 2
- loop c_rol
- jmp c_done
- c_not:
- not BYTE PTR [si] ; Flip bits
- add si, 2
- loop c_not
- c_done:
- .IF vconfig.adapter == CGA ; If CGA:
- INVOKE EnableCga ; Reenable CGA video
- .ENDIF
-
- pop cx ; Recover number of columns
- pop si ; Recover offset for start of line
- add si, 160 ; Point to start of next line
- dec bx ; Decrement row counter
- .UNTIL zero? ; Loop while rows remain
- ret
-
- Colors ENDP
-
-
- ;* Exec - Executes a child process. Exec handles the usual chores associated
- ;* with spawning a process: (1) parsing the command line tail and loading th
- ;* FCBs with the first two arguments; (2) setting and restoring the vectors
- ;* for Interrupts 1Bh, 23h, and 24h; and (3) querying DOS for the child's
- ;* return code.
- ;*
- ;* Shows: DOS Functions - 29h (Parse Filename)
- ;* 25h (Set Interrupt Vector)
- ;* 35h (Get Interrupt Vector)
- ;* 4Bh (Execute Program)
- ;* 4Dh (Get Return Code)
- ;*
- ;* Params: Spec - Pointer to ASCIIZ specification for program file
- ;* (must include .COM or .EXE extension)
- ;* Block - Pointer to parameter block structure
- ;* CtrBrk - Pointer to new Ctrl+Break (Interrupt 1Bh) handler
- ;* CtrlC - Pointer to new Ctrl+C (Interrupt 23h) handler
- ;* Criterr - Pointer to new Critical Error (Interrupt 24h) handler
- ;*
- ;* Return: Short integer with child return code, or -1 for EXEC error
-
- Exec PROC USES ds si di,
- Spec:PBYTE, Block:PPARMBLK, CtrBrk:PTR FAR,
- CtrlC:PTR FAR, Criterr:PTR FAR
-
- Vector 1Bh, Old1Bh, CtrBrk ; Save, replace Int 1Bh vector
- Vector 23h, Old23h, CtrlC ; Save, replace Int 23h vector
- Vector 24h, Old24h, Criterr ; Save, replace Int 24h vector
-
- LoadPtr ds, bx, Block ; Point DS:BX to parameter block
- push ds ; Save segment address
- les di, (PARMBLK PTR [bx]).fcb1 ; Point ES:DI to first FCB
- lds si, (PARMBLK PTR [bx]).taddr ; Point DS:SI to command line
- inc si ; Skip over count byte
-
- mov ax, 2901h ; Set AH to request Function 29h
- ; AL = flag to skip leading blanks
- int 21h ; Parse command-line into first FCB
- pop es ; Recover seg addr of parameter block
- les di, (PARMBLK PTR es:[bx]).fcb2 ; Point ES:DI to second FCB
- mov ax, 2901h ; Request DOS Function #29h again
- int 21h ; Parse command-line into second FCB
-
- push bp ; Save only important register
- mov WORD PTR cs:OldStk[0], sp
- mov WORD PTR cs:OldStk[2], ss
- LoadPtr es, bx, Block ; ES:BX points to param block
- LoadPtr ds, dx, Spec ; DS:DX points to path spec
- mov ax, 4B00h ; AH = DOS Function 4Bh
- ; AL = 0 for load and execute
- int 21h ; Execute Program
- mov sp, WORD PTR cs:OldStk[0] ; Reset stack pointers
- mov ss, WORD PTR cs:OldStk[2]
- pop bp ; Recover saved register
-
- ; Restore vectors for Interrupts 1Bh, 23h, and 24h.
-
- mov ax, 251Bh ; AH = DOS Function 25h
- ; AL = interrupt number
- lds dx, cs:Old1Bh ; DS:DX = original vector
- int 21h ; Set Interrupt 1Bh Vector
- mov al, 23h ; AL = interrupt number
- lds dx, cs:Old23h ; DS:DX = original vector
- int 21h ; Set Interrupt 23h Vector
- mov al, 24h ; AL = interrupt number
- lds dx, cs:Old24h ; DS:DX = original vector
- int 21h ; Set Interrupt 24h Vector
-
- mov ax, -1 ; Set error code
- .IF !carry? ; If no EXEC error:
- mov ah, 4Dh ; Request child's code
- int 21h ; Get Return Code
- sub ah, ah ; Make short integer
- .ENDIF
- ret
-
- Old1Bh FPVOID ? ; Keep vectors for Interrupts
- Old23h FPVOID ? ; 1Bh, 23h, and 24h in code
- Old24h FPVOID ? ; segment, but non-executable
- OldStk FPVOID ? ; Keep stack pointer
-
- Exec ENDP
-
-
- ;* BinToHex - Converts binary word to 6-byte hexadecimal number in
- ;* ASCIIZ string. String is right-justified and includes "h" radix.
- ;*
- ;* Shows: Instruction - xlat
- ;*
- ;* Params: Num - Number to convert to hex string
- ;* Sptr - Pointer to 6-byte string
- ;*
- ;* Return: None
-
- .DATA
- hex BYTE "0123456789ABCDEF" ; String of hex numbers
-
- .CODE
- BinToHex PROC USES di,
- Num:WORD, Sptr:PBYTE
-
- LoadPtr es, di, Sptr ; Point ES:DI to 6-byte string
- mov bx, OFFSET hex ; Point DS:BX to hex numbers
- mov ax, Num ; Number in AX
- mov cx, 2 ; Loop twice for two bytes
-
- .REPEAT
- xchg ah, al ; Switch bytes
- push ax ; Save number
- shr al, 1 ; Shift high nibble to low
- shr al, 1
- shr al, 1
- shr al, 1
- xlat ; Get equivalent ASCII number in AL
- stosb ; Copy to 6-byte string, increment DI
- pop ax ; Recover number
- push ax ; Save it again
- and al, 00001111y ; Mask out high nibble
- xlat ; Get equivalent ASCII number in AL
- stosb ; Copy to 6-byte string, increment DI
- pop ax ; Recover number
- .UNTILCXZ ; Do next byte
- mov ax, 'h' ; Put null, 'h' radix in AX
- stosw ; Copy to last two bytes in string
- ret
-
- BinToHex ENDP
-
-
- ;* NewBlockSize - Adjusts size of allocated memory block.
- ;*
- ;* Shows: DOS Function - 4Ah (Resize Memory Block)
- ;*
- ;* Params: Adr - Segment address of block
- ;* Resize - Requested block size in paragraphs
- ;*
- ;* Return: Short integer error code
- ;* 0 if successful
- ;* 1 if error
-
- NewBlockSize PROC,
- Adr:WORD, Resize:WORD
-
- mov ax, Adr ; Get block address
- mov es, ax ; Point ES to block
- mov bx, Resize ; New block size
- mov ah, 4Ah ; Function number
- int 21h ; Resize Memory Block
- ret
-
- NewBlockSize ENDP
-
-
- ;* Initialize - Initializes global variables _psp and _env, which are defined
- ;* in the DEMO.INC include file. If used with a DOS version less than 3.0,
- ;* this procedure will not produce valid results unless it is called before
- ;* changing the ES register. This is because at program entry ES points to
- ;* the Program Segment Prefix (PSP).
- ;*
- ;* Params: None
- ;*
- ;* Return: None
-
- Initialize PROC
-
- INVOKE GetPSP ; Get segment address of PSP
- .IF ax == 0 ; If less than DOS 3.0:
- mov es, ax ; Reload ES with PSP address
- .ENDIF
-
- mov _psp, es ; Initialize variable with PSP addres
- mov ax, es:[2Ch] ; Get environment seg from PSP
- mov _env, ax ; Store it
- ret
-
- Initialize ENDP
-
- END
-
-
- MISCDEMO.ASM
- CD-ROM Disc Path: \SAMPCODE\MASM\MASM6\DEMOS\MISCDEMO.ASM
-
- ;* MISCDEMO - Invokes many of the assembly example procedures, most of them
- ;* demonstrating assembly language instructions and calls to the system BIOS.
- ;* MISCDEMO demonstrates how to:
- ;*
- ;* - determine hardware information
- ;* - display time and date while waiting for keystrokes
- ;* - play notes of any frequency on the speaker
- ;* - change the line mode for EGA or VGA systems
- ;* - create non-destructive pop-up windows
- ;* - execute another program as a child process
- ;* - create primitive handlers for Interrupts 1Bh, 23h, and 24h
- ;* - use C-callable procedures in assembly programs
- ;* - use simplified segment directives
- ;* - write model-independent procedures
- ;* - declare and initialize data with DUP, BYTE, WORD, and DWORD
- ;* - create structures with the STRUCT directive
- ;* - declare macros
- ;* - set up a dispatch table
- ;*
- ;* MISCDEMO.EXE is built from the following files:
- ;* MISCDEMO.ASM - Main program
- ;* MISC.ASM - Assembly procedures for MISCDEMO
- ;* COMMON.ASM - Assembly procedures shared by other example programs
- ;* DEMO.INC - Include file with macros, structure declarations
- ;*
- ;* Procedures: GetVidConfig GetCurPos VeriPrint GetPSP
- ;* WinOpen VeriAnsi VeriCop GetVer
- ;* WinClose StrWrite SetLineMode NewBlockSize
- ;* SetCurSize GetKeyClock BinToHex IntToAsc
- ;* SetCurPos GetShift Sound Colors
- ;* GetCurSize GetMem Pause Exec
- ;* WriteTTY Initialize
-
- .DOSSEG
- .MODEL small, pascal, os_dos
- INCLUDE demo.inc
-
- NewBreak PROTO FAR
- NewCtrlC PROTO FAR
- NewCritErr PROTO FAR
- DispMenu PROTO NEAR
- Press PROTO NEAR
- GetVidinfo PROTO NEAR
- GetMemInfo PROTO NEAR
- CheckPrinter PROTO NEAR
- CheckAnsi PROTO NEAR
- CheckCoproc PROTO NEAR
- GetConfig PROTO NEAR
- Speaker PROTO NEAR
- SetLines PROTO NEAR
- PopWindows PROTO NEAR
- SetAttrs PROTO NEAR
- ExecPgm PROTO NEAR
-
- .STACK
- .DATA
-
- PGMSIZE EQU 500h ; Maximum program size in paragraphs
- F1 EQU 59 ; Extended code for first option key
- F7 EQU 65 ; Extended code for last option key
- CLKROW EQU 0 ; Row for on-screen clock
- CLKCOL EQU 62 ; Column for on-screen clock
-
- ;* Box - Macro to color portion of screen for effect. Not to be confused with
- ;* the WinOpen procedure, which is far more capable.
- ;*
- ;* Params: Row1 - Screen row at top of box
- ;* Col1 - Screen column at left side of box
- ;* Row2 - Screen row at bottom of box
- ;* Col2 - Screen column at right side of box
-
- Box MACRO Row1, Col1, Row2, Col2
- LOCAL sk
- mov ax, 0600h ;; Scroll service
- mov bh, Filmono ;; Fill attribute
- .IF vconfig.adapter != MDA ;; If color:
- mov bh, Filcolr ;; Use color fill attribute
- .ENDIF
- mov ch, Row1
- mov cl, Col1 ;; CX = row/col for upper left
- mov dh, Row2
- mov dl, Col2 ;; DX = row/col for lower right
- int 10h ;; Blank window area on screen
- ENDM
-
- OldMode BYTE ? ; Original video mode
- OldCurs WORD ? ; Original cursor coordinates
- KeepSeg PSEG ? ; Segment addr, orig screen
- Filcolr BYTE 1Fh, 20h, 3Bh, 4Eh ; Color fill attributes
- Filmono BYTE 70h, 89h, 78h, 1 ; Monochrome fill attributes
- Fill BYTE 7 ; Default attribute for menu
- Filsub BYTE ? ; Fore/background colors in submenu
-
- PresMsg BYTE ". . . press a key to continue", 0
- yes BYTE "yes"
- no BYTE "no "
-
- ; Main menu text
-
- Menu1 BYTE "*** MISC Demonstration Program ***", 0
- Menu2 BYTE "F1 System Configuration", 0
- Menu3 BYTE "F2 Speaker Test", 0
- Menu4 BYTE "F3 Toggle Line Mode", 0
- Menu5 BYTE "F4 Windows", 0
- Menu6 BYTE "F5 Screen Colors", 0
- Menu7 BYTE "F6 Exec Program", 0
- Menu8 BYTE "Select an option, or press ESC to quit:", 0
-
- ; Option F1 - System Configuration
-
- MonoStr BYTE "monochrome"
- ClrStr BYTE "color "
- AdapStr BYTE "MDA CGA MCGAEGA VGA "
- VidMsg1 BYTE "Adapter: xxxx", 0
- VidMsg2 BYTE "Display: xxxxxxxxxx", 0
- VidMsg3 BYTE "Mode: xx", 0
- VidMsg4 BYTE "Rows: xx", 0
- MemMsg1 BYTE "Total memory: xxxx Kb", 0
- MemMsg2 BYTE "Available memory: xxxx Kb", 0
- PrnMsg BYTE "Printer ready: xxx", 0
- AnsiMsg BYTE "ANSI driver installed: xxx", 0
- CopMsg BYTE "Coprocessor installed: xxx", 0
- LEN1 EQU LENGTHOF CopMsg - 4
-
- ; Option F3 - Toggle Line Mode
-
- LineMsg BYTE "Line mode reset available only for EGA or VGA", 0
-
- ; Option F4 - Windows
-
- WinMsg BYTE "WINDOW x", 0
- LEN3 EQU LENGTHOF WinMsg - 2
-
- ; Option F5 Screen Colors
-
- CMsg1 BYTE "Toggle Step", 0
- CMsg2 BYTE "──────────────── ──────────────────", 0
- CMsg3 BYTE "B blink ", 27, 26, " foreground", 0
- CMsg4 BYTE "I intensity ", 24, 25, " background", 0
- CMsg5 BYTE "Foreground: press F, then color number 0-7", 0
- CMsg6 BYTE "Background: press A, then color number 0-7", 0
- CMsg7 BYTE "Color Numbers", 0
- CMsg8 BYTE "───────────────────────────────────────────", 0
- CMsg9 BYTE "0 black 4 red", 0
- CMsg10 BYTE "1 blue 5 magenta", 0
- CMsg11 BYTE "2 green 6 brown", 0
- CMsg12 BYTE "3 cyan 7 white", 0
- CMsg13 BYTE "Toggle", 0
- CMsg14 BYTE "───────────────", 0
- CMsg15 BYTE "B blink", 0
- CMsg16 BYTE "I intensity", 0
- CMsg17 BYTE "U underline", 0
- CMsg18 BYTE "R reverse", 0
-
- ; Option F6 - Exec Program
-
- RetMsg BYTE "Return code: "
- Recode BYTE 6 DUP (?) ; ASCII string for return code
- ExecMsg BYTE "Enter program file spec (including .COM or .EXE):", 0
- TailMsg BYTE "Enter command-line argument(s):", 0
- Fspec BYTE 50, 50 DUP (?) ; File specification (max length = 50
- Tail BYTE 50, 50 DUP (?) ; Command-line tail (max length = 50)
- Fcblk1 BYTE 0 ; Allocate space for 1st FCB
- BYTE 11 DUP (0)
- BYTE 25 DUP (0)
- Fcblk2 BYTE 0 ; Allocate space for 2nd FCB
- BYTE 11 DUP (0)
- BYTE 25 DUP (0)
- pb PARMBLK <> ; Parameter block structure
-
- ; Initialize dispatch table with offsets for internal procedures.
-
- TPROC TYPEDEF PROTO ; Procedure type
- PPROC TYPEDEF PTR TPROC ; Pointer to procedure with no arguments
-
- ; Table of procedures
- DispTbl PPROC GetConfig, Speaker, SetLines,
- PopWindows, SetAttrs, ExecPgm
-
- .CODE
- .STARTUP
-
- ; Initialize _psp and _env variables
- INVOKE Initialize
-
- ; Return unused memory to DOS
- ; Pass PSP segment address and memory block allocated to program
- INVOKE NewBlockSize, _psp, PGMSIZE
-
- ; Initialize global configuration data
- INVOKE GetVidConfig
-
- mov al, vconfig.rows
- mov OldMode, al ; Preserve original line mode
-
- ; Get current cursor position
- INVOKE GetCurPos
-
- mov OldCurs, ax ; Store it
-
- ; Preserve original screen and put up window
- ; Pass top, left, bottom, right, and attribute
- INVOKE WinOpen, 0, 0, vconfig.rows, 79, 07h
-
- mov KeepSeg, ax ; Keep segment address
- .IF AX == 0 ; If window not opened successfully:
- .EXIT 1 ; Exit with return code = 1
- .ENDIF
-
- .WHILE 1
-
- ; Display main menu
- INVOKE DispMenu
-
- ; Highlight on-screen clock with macro
- Box CLKROW, CLKCOL-1, CLKROW, CLKCOL + 17
-
- ; Poll for keyboard selection while updating time
- ; Pass row and column
- INVOKE GetKeyClock, CLKROW, CLKCOL
-
- .BREAK .IF al == ESCAPE ; Quit loop if Esc key
-
- .CONTINUE .IF (ah < F1) || (ah > F7) ; Ignore if not a function
- ; key between F1 and F7?
-
- xchg al, ah ; Yes? Make AX = AH
- sub al, F1 ; Normalize to 0
- shl al, 1 ; Double to make word index
- mov bx, ax ; BX = index to table
-
- ; Call the current procedure from call table
- INVOKE DispTbl[bx]
-
- .ENDW ; Loop for another key
-
- mov al, OldMode ; Get original line mode
- .IF al != vconfig.rows ; If not same as current mode:
-
- inc ax ; Increment to 25/43/50
-
- ; Restore line mode, pass lines
- INVOKE SetLineMode, ax
-
- .ENDIF
-
- ; Restore original screen, pass segment of screen contents
- INVOKE WinClose, KeepSeg
-
- mov ax, OldCurs
-
- ; Restore cursor to original place
- ; Pass row and column
- INVOKE SetCurPos, BYTE PTR OldCurs[1], BYTE PTR OldCurs[0]
-
- .EXIT 0 ; Exit wih return code 0
-
-
- ;* DispMenu - Displays main menu.
- ;*
- ;* Uses: vconfig - Video configuration structure (initialized
- ;* by calling the GetVidConfig procedure)
- ;*
- ;* Return: None
-
- DispMenu PROC NEAR
-
- mov ax, 0600h ; Scroll screen service
- mov bh, Fill ; Menu display attribute
- sub cx, cx ; From row 0, col 0
- mov dh, vconfig.rows ; to bottom row,
- mov dl, 79 ; rightmost column
- int 10h ; Clear entire screen
-
- ; Display menu
- ; For each line pass row, column, and string address
- INVOKE StrWrite, 4, 21, ADDR Menu1
- INVOKE StrWrite, 8, 28, ADDR Menu2
- INVOKE StrWrite, 9, 28, ADDR Menu3
- INVOKE StrWrite, 10, 28, ADDR Menu4
- INVOKE StrWrite, 11, 28, ADDR Menu5
- INVOKE StrWrite, 12, 28, ADDR Menu6
- INVOKE StrWrite, 13, 28, ADDR Menu7
- INVOKE StrWrite, 17, 18, ADDR Menu8
-
- ; Park cursor at prompt, pass row and column
- INVOKE SetCurPos, 17, 18 + (LENGTHOF Menu8) + 2
-
- ret
-
- DispMenu ENDP
-
-
-
- ;* Press - Displays a prompt, then waits for a key press.
- ;*
- ;* Uses: vconfig - Video configuration structure (initialized
- ;* by calling the GetVidConfig procedure)
- ;*
- ;* Return: None
-
- Press PROC NEAR
-
- ; Write string, pass row, column, and string address
- INVOKE StrWrite, vconfig.rows, 50, ADDR PresMsg
-
- ; Park cursor at prompt, pass row and column
- INVOKE SetCurPos, vconfig.rows, 48
-
- ; Poll for keyboard selection while updating time
- ; Pass row and column
- INVOKE GetKeyClock, CLKROW, CLKCOL
-
- ret
-
- Press ENDP
-
-
-
- ;* GetVidinfo - Initializes video configuration message for display.
- ;*
- ;* Uses: vconfig - Video configuration structure (initialized
- ;* by calling the GetVidConfig procedure)
- ;*
- ;* Return: None
-
- GetVidinfo PROC NEAR
-
- push ds
- pop es ; Point ES to data segment
- mov al, 4 ; Find index to 4-character
- mul vconfig.adapter ; group in string
- add ax, OFFSET AdapStr ; Point AX to proper group
- mov si, ax ; Put pointer in SI
- lea di, VidMsg1[LEN1] ; Point to 1st line of message
- mov cx, 2 ; Copy 4 letters (adapter
- rep movsw ; designation) to message
-
- mov si, OFFSET MonoStr ; Assume display is monochrome
- .IF vconfig.display != MONO ; I color display:
- mov si, OFFSET ClrStr ; Point to "color" string
- .ENDIF
- lea di, VidMsg2[LEN1] ; Point to 2nd line of message
- mov cx, 5 ; Copy 10 chars ("monochrome"
- rep movsw ; or "color ") to msg
-
- ; Note that IntToAsc can't be invoked because of its
- ; register calling convention
- mov al, vconfig.mode
- cbw ; AX = video mode
- call IntToAsc ; Convert AX to ASCII
- xchg ah, al ; Flip bytes for word write
- mov WORD PTR VidMsg3[LEN1], ax ; Insert in message string
-
- mov al, vconfig.rows
- cbw
- inc ax ; AX = number of screen rows
- call IntToAsc ; Convert to ASCII
- xchg ah, al ; Flip bytes for word write
- mov WORD PTR VidMsg4[LEN1], ax ; Insert in message string
- ret
-
- GetVidinfo ENDP
-
-
-
- ;* GetMemInfo - Initializes memory information message.
- ;*
- ;* Return: None
-
- GetMemInfo PROC NEAR
-
- ; Get total memory in DX, available memory in AX
- INVOKE GetMem
-
- push ax
- mov ax, dx
- call IntToAsc ; Convert AX to ASCII
- xchg dh, dl ; Flip bytes for word write
- xchg ah, al
- mov WORD PTR MemMsg1[LEN1], dx ; Insert in message
- mov WORD PTR MemMsg1[LEN1+2], ax ; string
- pop ax ; Recover avail memory #
- call IntToAsc ; Convert to ASCII
- xchg dh, dl ; Flip bytes for word write
- xchg ah, al
- mov WORD PTR MemMsg2[LEN1], dx ; Insert in message
- mov WORD PTR MemMsg2[LEN1+2], ax ; string
- ret
-
- GetMemInfo ENDP
-
-
- ;* CheckPrinter - Initializes printer status message.
- ;*
- ;* Shows: Instruction - movsb
- ;*
- ;* Return: None
-
- CheckPrinter PROC NEAR
-
- push ds
- pop es ; Point ES to data segment
- mov si, OFFSET yes ; Assume answer is "yes"
-
- ; Check if printer ready
- INVOKE VeriPrint
-
- .IF al == 0 ; If not ready
- mov si, OFFSET no ; Point to "no" answer
- .ENDIF
- lea di, PrnMsg[LEN1] ; Point to print message
- mov cx, 3 ; Copy 3 letters (either "yes"
- rep movsb ; or "no ") to message
- ret
-
- CheckPrinter ENDP
-
-
-
- ;* CheckAnsi - Initializes status message for ANSI driver.
- ;*
- ;* Return: None
-
- CheckAnsi PROC NEAR
-
- push ds
- pop es ; Point ES to data segment
- mov si, OFFSET yes ; Assume answer is "yes"
-
- ; Check if ANSI driver is installed
- INVOKE VeriAnsi
-
- .IF al == 0 ; If not installed:
- mov si, OFFSET no ; Point to "no" answer
- .ENDIF
- lea di, AnsiMsg[LEN1] ; Point to ansi message
- mov cx, 3 ; Copy 3 letters (either "yes"
- rep movsb ; or "no ") to message
- ret
-
- CheckAnsi ENDP
-
-
-
- ;* CheckCoproc - Initializes coprocessor status message.
- ;*
- ;* Return: None
-
- CheckCoproc PROC NEAR
-
- push ds
- pop es ; Point ES to data segment
- mov si, OFFSET yes ; Assume answer is "yes"
-
- ; Check for coprocessor
- INVOKE VeriCop
-
- .IF al == 0 ; If not installed:
- mov si, OFFSET no ; Point to "no" answer
- .ENDIF
- lea di, CopMsg[LEN1] ; Point to coprocessor message
- mov cx, 3 ; Copy 3 letters (either "yes"
- rep movsb ; or "no ") to message
- ret
-
- CheckCoproc ENDP
-
-
- ;* GetConfig - Displays system configuration information.
-
- GetConfig PROC NEAR
-
- INVOKE GetVidinfo ; Initialize video message
- INVOKE GetMemInfo ; Initialize memory message
- INVOKE CheckPrinter ; Initialize printer message
- INVOKE CheckAnsi ; Initialize ANSI driver msg
- INVOKE CheckCoproc ; Initialize coprocessor msg
-
- Box 4, 13, 20, 67 ; Clear screen with box
-
- ; Display configuration information
- ; For each line, pass row, column, and string address
- INVOKE StrWrite, 6, 23, ADDR VidMsg1
- INVOKE StrWrite, 7, 23, ADDR VidMsg2
- INVOKE StrWrite, 8, 23, ADDR VidMsg3
- INVOKE StrWrite, 9, 23, ADDR VidMsg4
- INVOKE StrWrite, 11, 23, ADDR MemMsg1
- INVOKE StrWrite, 12, 23, ADDR MemMsg2
- INVOKE StrWrite, 14, 23, ADDR PrnMsg
- INVOKE StrWrite, 16, 23, ADDR AnsiMsg
- INVOKE StrWrite, 18, 23, ADDR CopMsg
-
- ; Prompt for keypress
- INVOKE Press
-
- ret
-
- GetConfig ENDP
-
-
-
- ;* Speaker - Sounds speaker with ascending frequencies.
- ;*
- ;* Return: None
-
- Speaker PROC NEAR
-
- sub ax, ax
- .REPEAT
- add ax, 100 ; Start with frequency 100
- push ax ; Save frequency
-
- ; Beep speaker, pass frequency and duration
- INVOKE Sound, ax, 1
-
- pop ax ; Recover frequency
- .UNTIL ax > 3000 ; Continue to frequency 3000
- ret
-
- Speaker ENDP
-
-
-
- ;* SetLines - Toggles between 25/43-line mode for EGA or 25/43/50-line mode
- ;* for VGA.
- ;*
- ;* Uses: vconfig - Video configuration structure (initialized
- ;* by calling the GetVidConfig procedure)
- ;*
- ;* Return: None
-
- SetLines PROC NEAR
-
- mov al, 25 ; Assume toggle to 25 line
- cmp vconfig.rows, 49 ; Current mode 50 lines?
- je toggle25 ; Yes? Toggle VGA to 25-line
- cmp vconfig.rows, 42 ; Current mode 43 lines?
- jne toggle43 ; No? Must be 25
- cmp vconfig.adapter, EGA ; Yes? And is adapter EGA?
- je toggle25 ; Yes? Then toggle to 25 line
- mov al, 50 ; No? Toggle VGA to 50 line
- jmp toggle25
- toggle43:
- mov al, 43 ; If currently 25 lines, make
- ; either EGA or VGA 43 lines
- toggle25:
- ; Change line mode, pass lines
- INVOKE SetLineMode, ax
-
- .IF al == 0 ; If no error:
- INVOKE GetVidConfig ; Update configuration structure
- .ELSE ; Else:
- Box 16, 13, 20, 67 ; Display error message
-
- ; Write line message, pass row, column, and string address
- INVOKE StrWrite, 18, 17, ADDR LineMsg
-
- INVOKE Press
- .ENDIF
-
- ret
-
- SetLines ENDP
-
-
-
- ;* PopWindows - Demonstrates windowing with the WinOpen and WinClose
- ;* procedures.
- ;*
- ;* Uses: vconfig - Video configuration structure (initialized
- ;* by calling the GetVidConfig procedure)
- ;*
- ;* Return: None
-
- PopWindows PROC NEAR
-
- LOCAL Row1:WORD, Col1:WORD, Row2:WORD, Col2:WORD
- LOCAL Index:BYTE, Adr[4]:WORD, Csize:WORD
-
- ; Get current cursor size
- INVOKE GetCurSize
-
- mov Csize, ax ; Store it
- or al, 100000y ; Set 5th bit for cursor off
- mov bl, al
-
- ; Set cursor size
- ; Pass arbitrary top and bottom lines with visibility bit off
- INVOKE SetCurSize, BYTE PTR Csize[1], bl
-
- mov WinMsg[LEN3], "0" ; Initialize window message
- mov Row1, 4 ; Initialize window coords
- mov Col1, 10
- mov Row2, 20
- mov Col2, 34
- mov Index, 0
- mov cx, 4 ; Open 4 windows
- .REPEAT
- push cx ; Save loop counter
- mov al, Index
- mov bx, OFFSET Filmono ; BX points to fill attributes
- .IF vconfig.display != MONO ; If not monochrome:
- mov bx, OFFSET Filcolr ; Repoint to color attributes
- .ENDIF
- xlat ; Get attributes in succession
-
- ; Save old window and open new
- ; Pass top, left, bottom, right, and attribute in AX
- INVOKE WinOpen, Row1, Col1, Row2, Col2, ax
-
- pop di ; Recover counter in DI
- push di ; and save it again
- dec di
- shl di, 1 ; Make DI a word index
- mov Adr[di], ax ; Save address of allocated
- ; block returned by WinOpen
- inc WinMsg[LEN3] ; Increment window number
- mov bx, Row1
- add bl, 2 ; Message row
- mov cx, Col1
- add cl, 9 ; Message column
-
- ; Write window message, pass row, column, and string address
- INVOKE StrWrite, bx, cx, ADDR WinMsg
-
- ; Pause, pass 18 ticks (about 1 second)
- INVOKE Pause, 18
-
- add Row1, 2 ; Adjust coordinates for
- add Col1, 13 ; next window
- sub Row2, 2
- add Col2, 13
- inc Index
- pop cx ; Recover counter
- .UNTILCXZ
-
- mov cx, 4 ; Close 4 windows
- sub di, di ; DI = index to addresses
-
- .REPEAT
- push cx ; Save loop counter
-
- ; Close a window, pass address of the window
- INVOKE WinClose, Adr[di]
-
- ; Pause, pass 18 ticks (about 1 second)
- INVOKE Pause, 18
-
- add di, 2 ; Point to next address
- pop cx ; Recover counter
- .UNTILCXZ ; Close another window
-
- mov ax, Csize ; Get original cursor size
-
- ; Set cursor size, pass top and bottom lines
- INVOKE SetCurSize, BYTE PTR Csize[1], BYTE PTR Csize[0]
-
- ret
-
- PopWindows ENDP
-
-
-
- ;* SetAttrs - Changes display attributes for the main menu.
- ;*
- ;* Uses: vconfig - Video configuration structure (initialized
- ;* by calling the GetVidConfig procedure)
- ;*
- ;* Return: None
-
- SetAttrs PROC NEAR
-
- Box 3, 12, 23, 68
- .IF vconfig.adapter == MDA ; If monochrome?
-
- ; Write monochrome menu
- ; For each line, pass row, column, and string address
- INVOKE StrWrite, 8, 32, ADDR CMsg13
- INVOKE StrWrite, 9, 32, ADDR CMsg14
- INVOKE StrWrite, 10, 36, ADDR CMsg15
- INVOKE StrWrite, 11, 36, ADDR CMsg16
- INVOKE StrWrite, 12, 36, ADDR CMsg17
- INVOKE StrWrite, 13, 36, ADDR CMsg18
-
- mov al, Filmono ; Initialize Filsub variable
- mov Filsub, al ; for monochrome
-
- .ELSE
-
- ; Write color menu
- ; For each line, pass row, column, and string address
- INVOKE StrWrite, 4, 18, ADDR CMsg1
- INVOKE StrWrite, 5, 18, ADDR CMsg2
- INVOKE StrWrite, 6, 22, ADDR CMsg3
- INVOKE StrWrite, 7, 22, ADDR CMsg4
- INVOKE StrWrite, 10, 18, ADDR CMsg5
- INVOKE StrWrite, 11, 18, ADDR CMsg6
- INVOKE StrWrite, 14, 18, ADDR CMsg7
- INVOKE StrWrite, 15, 18, ADDR CMsg8
- INVOKE StrWrite, 16, 22, ADDR CMsg9
- INVOKE StrWrite, 17, 22, ADDR CMsg10
- INVOKE StrWrite, 18, 22, ADDR CMsg11
- INVOKE StrWrite, 19, 22, ADDR CMsg12
-
- mov al, Filcolr ; Initialize Filsub variable
- mov Filsub, al ; for color
- .ENDIF
-
- ; Write menu message
- INVOKE StrWrite, 22, 15, ADDR Menu8
-
- ; Park cursor at prompt, pass row and column
- INVOKE SetCurPos, 22, 56
-
- .WHILE 1
-
- ; Poll for keyboard selection while updating time
- ; Pass row and column
- INVOKE GetKeyClock, CLKROW, CLKCOL
-
- .BREAK .IF al == ESCAPE ; Quit if Esc key
-
- .IF (al >= 'a') && (al <= 'z') ; Convert letters to uppercase
- and al, 5Fh ; to make comparisons easier
- .ENDIF
-
- cmp al, 'B' ; Request blink toggle?
- je blink
- cmp al, 'I' ; Request intensity toggle?
- je intense
- mov bl, Filsub ; Get window display attribute
- cmp vconfig.adapter, MDA ; Monochrome?
- jne iscolor ; No? Jump to color selections
- cmp al, 'U' ; Request underline toggle?
- je underline
- .CONTINUE .IF al != 'R' ; If not reverse toggle:
- ; Skip invalid key
-
- ; What with cross-toggling between reverse, normal, and underline, three
- ; bit settings can exist in monochrome: x111x000 for reverse, x000x111 for
- ; normal, and x000x001 for underline. Changing between the three involves
- ; more than simply XOR-ing the current attribute; each condition must check
- ; for the other two.
-
- reverse:
- .IF bl & 1 ; If reverse video off:
- or bl, 00000111y ; Ensure normal bits are on
- .ENDIF
-
- xor bl, 01110111y ; Toggle for reverse/normal
- mov cl, 6 ; Set code for MOV
- jmp switch
-
- underline:
- .IF bl & 1 ; If reverse video on:
- and bl, 10001111y ; Clear bits 4-6
- or bl, 00000111y ; and set bits 0-2
- .ENDIF
-
- xor bl, 00000110y ; Toggle bits 1-2 for underline
- mov cl, 6 ; Set code for MOV
- jmp switch
-
- ; Blink and intensity use the same bits for color and monochrome.
-
- blink:
- mov bl, 10000000y ; Set bit 7 for blink
- mov cl, 4 ; Set code for XOR
- jmp switch
-
- intense:
- mov bl, 00001000y ; Set bit 3 for intensity
- mov cl, 4 ; Set code for XOR
- jmp switch
-
- ; Enter this section only for color displays. First check for arrow keys,
- ; which increment or decrement the foreground or background bits of the
- ; current attribute stored in the variable Filsub. If arrow keys are not
- ; pressed, check for the F or A keys, which request specific colors for the
- ; foreground or background colors.
-
- iscolor:
- mov ch, bl ; Copy current attribute to CH
- .IF ah == 72 ; If up arrow:
- mov cl, 4 ; Increment bits 4-6
- shr ch, cl ; to next background color
- inc ch
- and ch, 00000111y
- shl ch, cl
- mov dl, 10001111y ; Set background mask
- jmp step
- .ENDIF
-
- .IF ah == 75 ; If left arrow:
- inc ch ; Increment bits 0-2
- and ch, 00000111y ; to next foreground color
- mov dl, 11111000y ; Set foreground mask
- jmp step
- .ENDIF
-
- .IF ah == 77 ; If right arrow
- dec ch ; Decrement bits 0-2
- and ch, 00000111y ; to previous foreground color
- mov dl, 11111000y ; Set foreground mask
- jmp step
- .ENDIF
-
- .IF ah == 80 ; If down arrow:
- mov cl, 4 ; Decrement bits 4-6
- shr ch, cl ; to previous background color
- dec ch
- and ch, 00000111y
- shl ch, cl
- mov dl, 10001111y ; Set background mask
- step:
- and bl, dl ; Mask out fore or back bits
- or bl, ch ; Copy into original attribute
- mov Filsub, bl ; Store the new submenu color
- mov cl, 6 ; Request move operation in
- jmp switch ; Colors procedure
- .ENDIF
-
- ; This section checks for the F or A keys; if found it checks again for
- ; a number key between 0 and 7, then inserts the correct foreground or
- ; background bit pattern into the current fill attribute.
-
- sub cx, cx ; Clear flag for foreground request
- .IF al == 'A' ; If background request:
- inc cx ; Set flag for background request
- .CONTINUE .IF al != 'F' ; If not foreground request, continue
- .ENDIF
-
- push ax
-
- ; Poll for keyboard selection while updating time
- ; Pass row and column
- INVOKE GetKeyClock, CLKROW, CLKCOL
-
- pop cx ; Recover flag
-
- .CONTINUE .IF (al < '0') && (al > '7') ; Ignore invalid key
-
- xor al, '0' ; Convert ASCII numeral into binary
- mov dl, 11111000y ; Set foreground mask
- .IF cx != 0 ; Skip if foreground request
- mov cl, 4 ; Otherwise shift bits 0-2
- shl al, cl ; to positions 4-6
- mov dl, 10001111y ; Set background mask
- .ENDIF
-
- mov bl, Filsub
- and bl, dl ; Mask out fore or back bits
- or bl, al ; Insert number into fore or back bit
- mov Filsub, bl ; Store the new submenu color
- mov cl, 6 ; Request move
- switch:
-
- ; Set new attributes in a window
- ; Pass logic code (CX), attribute (BX), top, left, bottom, right
- INVOKE Colors, cx, bx, 3, 12, 23, 68
-
- mov ah, 8 ; Function 8, get char/attribute
- mov bh, vconfig.dpage
- int 10h ; Get attribute in AH
- mov Fill, ah ; New fill variable for main menu
- mov Filsub, ah ; and for submenu
- .ENDW
- ret
-
- SetAttrs ENDP
-
-
-
- ;* ExecPgm - Executes a specified program as a child process.
- ;*
- ;* Uses: vconfig - Video configuration structure (initialized
- ;* by calling the GetVidConfig procedure)
- ;* pb - Parameter block structure, declared in the DEMO.INC file
- ;*
- ;* Return: None
-
- ExecPgm PROC NEAR
-
- Box 16, 13, 20, 67
-
- ; Display prompt for file spec, pass row, column, and string address
- INVOKE StrWrite, 17, 16, ADDR ExecMsg
-
- ; Set cursor position below prompt, pass row and column
- INVOKE SetCurPos, 19, 16
-
- mov ah, 0Ah ; Request DOS to read keyboard
- mov dx, OFFSET Fspec ; input into Fspec string
- int 21h ; Read Buffered Keyboard Input
-
- Box 16, 13, 20, 67
-
- ; Display prompt for command tail
- INVOKE StrWrite, 17, 16, ADDR TailMsg
-
- ; Set cursor position below prompt, pass row and column
- INVOKE SetCurPos, 19, 16
-
- mov ah, 0Ah ; Request DOS to read keyboard
- mov dx, OFFSET Tail ; input into tail string
- int 21h ; Read Buffered Keyboard Input
-
- sub bh, bh ; Clear BH
- mov si, OFFSET Fspec ; DS:SI points to file spec string
- mov bl, [si+1] ; BL = number of chars in spec
- mov BYTE PTR [si+bx+2], 0 ; Terminate string with 0
-
- mov ax, _env ; Get segment address of environment
- mov pb.env, ax ; Copy it to parameter block
- mov ax, @data ; AX points to data segment
- lea bx, Tail[1] ; BX points to command-line tail
- mov WORD PTR pb.taddr[0], bx; Copy address of command-line tail
- mov WORD PTR pb.taddr[2], ax; to parameter block
-
- mov bx, OFFSET Fcblk1 ; BX points to first FCB
- mov WORD PTR pb.fcb1[0], bx ; Copy address of first FCB
- mov WORD PTR pb.fcb1[2], ax ; to parameter block
- mov bx, OFFSET Fcblk2 ; BX points to second FCB
- mov WORD PTR pb.fcb2[0], bx ; Copy address of second FCB
- mov WORD PTR pb.fcb2[2], ax ; to parameter block
-
- ; At this point, the program file is specified, the command line tail is set,
- ; and the parameter block is properly initialized. The Exec procedure will
- ; take care of loading the FCBs with command-line arguments and resetting
- ; interrupt vectors. Now blank the screen in preparation for executing the
- ; process and pass the five pointers to the Exec procedure.
-
- mov ax, 0600h ; AH = scroll service, AL = 0
- mov bh, 7 ; Blank with normal attribute
- sub cx, cx ; From row 0, col 0
- mov dh, vconfig.rows ; to bottom row
- mov dl, 79 ; and rightmost column
- int 10h ; Blank screen
-
- ; Set cursor at top of screen, pass row and column
- INVOKE SetCurPos, 0, 0
-
-
- ; Exec specified program
- INVOKE Exec,
- ADDR Fspec[2], ; File spec
- ADDR pb, ; Parameter block structure
- NewBreak, ; New handlers for CTRL+BREAK,
- NewCtrlC, ; CTRL+C
- NewCritErr ; and Critical Error
-
-
- .IF ax != -1 ; If successful:
-
- ; Convert return code to string
- ; Pass return code (AX) and address of string buffer
- INVOKE BinToHex, ax, ADDR Recode
-
- ; Update video structure
- INVOKE GetVidConfig
-
- Box CLKROW, CLKCOL-1, CLKROW, CLKCOL+17 ; Highlight on-screen clock
- Box vconfig.rows, 0, vconfig.rows, 79 ; Highlight bottom row
- mov dl, vconfig.rows
-
- ; Display return code at bottom
- INVOKE StrWrite, dx, 0, ADDR RetMsg
-
- ; Wait for keypress
- INVOKE Press
- .ELSE
- mov ax, 0E07h ; Write ASCII 7 character
- int 10h ; (bell) to console
- .ENDIF
-
- ret
-
- ExecPgm ENDP
-
-
-
- ;* The following three procedures are primitive handlers for Interrupt 1Bh
- ;* (Ctrl-Break), Interrupt 23h (Ctrl-C), and Interrupt 24h (Critical Error).
- ;* The purpose of an interrupt handler in this context is to prevent termina-
- ;* tion of both parent and child processes when the interrupt is invoked.
- ;* Such handlers often set flags to signal a process that the interrupt has
- ;* been called.
-
- ;* NewBreak - Handler for Interrupt 1Bh.
-
- NewBreak PROC FAR
-
- sti ; Reenable interrupts
- push ax ; Preserve AX register
- mov al, 20h ; Send end-of-interrupt signal
- out 20h, al ; to interrupt controller
- pop ax ; Recover AX register
- iret ; Return from handler
- ; without taking action
- NewBreak ENDP
-
-
- ;* NewCtrlC - Handler for Interrupt 23h.
-
- NewCtrlC PROC FAR
-
- iret ; Return from handler
- ; without taking action
- NewCtrlC ENDP
-
-
- ;* NewCritErr - Handler for Interrupt 24h.
-
- NewCritErr PROC FAR
-
- sub al, al ; Tell DOS to ignore error
- iret ; Return from handler
- ; without taking action
- NewCritErr ENDP
-
- END
-
-
-
- PAGERP.ASM
- CD-ROM Disc Path: \SAMPCODE\MASM\MASM6\SHOW\PAGERP.ASM
-
- ;* PAGERP.ASM - Module containing routines for paging through a file and
- ;* writing text to the screen buffer. Works with main module SHOWP.ASM.
-
- TITLE Pager
- .MODEL small, pascal, os_os2
- .286
-
- INCL_NOCOMMON EQU 1 ; Enable call groups
- INCL_VIO EQU 1
-
- INCLUDE os2.inc
- INCLUDE show.inc
-
- .CODE
-
- ;* Pager - Displays status line and all the text lines for a screen.
- ;*
- ;* Params: cLines - lines to scroll (negative up, positive down)
- ;*
- ;* Uses: Global variables: segBuf, offBuf, yCur
- ;*
- ;* Return: None
-
- Pager PROC,
- cLines:SWORD
-
- mov es, segBuf ; Initialize buffer position
- mov di, offBuf
-
- mov cx, cLines ; Get line count
- mov ax, 10 ; Search for linefeed
-
- or cx, cx ; Argument 0?
- jl backward ; If below, backward
- jg foreward ; If above, forward
- jmp showit ; If equal, done
-
- backward:
- call GoBack ; Adjust backward
- jmp showit ; Show screen
-
- foreward:
- call GoForeward ; Adjust forward
-
- ; Write line number to status line
-
- showit:
- cld ; Forward
- push di ; Save
- push ds ; ES = DS
- pop es
-
- INVOKE BinToStr, ; Write line number as string
- yCur,
- ADDR stLine[LINE_POS]
-
- ; Fill in status line
-
- mov cx, 6 ; Six spaces to fill
- sub cx, ax ; Subtract those already done
- mov al, ' ' ; Fill with space
- rep stosb
-
- INVOKE VioWrtCharStrAtt, ; Write to screen
- ADDR stLine,
- X_MAX,
- 0,
- 0,
- ADDR atSta,
- 0
-
- pop di ; Update position
- mov si, di
- mov cx, yMax ; Lines per screen
-
- .REPEAT
- mov bx, yMax ; Lines per screen
- inc bx ; Adjust for 0
- sub bx, cx ; Calculate current row
- push cx ; Save line number
- mov es, segBuf ; Reload
-
- INVOKE ShowLine, ; Write line to screen
- es::si, ; Pointer to current position
- bx, ; Line number
- cbBuf, ; File length (for bounds check)
- ADDR atScr ; Attribute
-
- pop cx ; Restore line number
- mov si, ax ; Get returned position
-
- dec cx ; Count the line
- .UNTIL (ax >= cbBuf) || !cx ; Continue if more lines and not
- jcxz exit ; Done if more lines,
- ; else fill screen with spaces
- mov ax, X_MAX ; Columns times remaining lines
- mul cl
- mov dx, ax ; INVOKE uses AX, so use DX
- sub cx, yMax ; Calculate starting line
- neg cx
- inc cx
-
- INVOKE VioWrtNCell, ; Write space cells
- ADDR celScr, ; Cell of space and attribute
- dx, ; Number of cells to fill
- cx, ; Line to start fill
- 0, ; Column 0
- 0 ; Console handle
- exit:
- ret
-
- Pager ENDP
-
-
- ;* ShowLine - Writes a line of text to the screen.
- ;*
- ;* Params: pchIn - Far pointer to input text
- ;* y - Line number
- ;* cbMax - Maximum number of characters (file length)
- ;* pcelAtrib - Far pointer to attribute
- ;*
- ;* Return: None
-
- ShowLine PROC USES si di,
- pchIn:PBYTE,
- y:WORD,
- cbMax:WORD,
- pcelAtrib:PBYTE
-
- LOCAL achOut[X_MAX]:BYTE
-
- push ds ; Save
- push ss ; ES = SS
- pop es
- lea di, achOut ; Destination line
- lds si, pchIn ; Source line
- mov cx, X_MAX ; Cells per row
- mov bx, di ; Save copy of start for tab calc
- loop1:
- lodsb ; Get character
- cmp al, 9 ; Tab?
- je filltab ; Space out tab
- cmp al, 13 ; CR?
- je filleol ; Fill rest of line with spaces
- stosb ; Copy out
- cmp si, cbMax ; Check for end of file
- ja filleol
- loop loop1
- loop2:
- lodsb ; Throw away rest of line to truncate
- cmp si, cbMax ; Check for end of file
- ja exit
- cmp al, 13 ; Check for end of line
- jne loop2
- inc si ; Throw away line feed
-
- jmp exit ; Done
- filltab:
- push bx ; Fill tab with spaces
- push cx
-
- sub bx, di ; Get current position in line
- neg bx
-
- mov cx, 8 ; Default count 8
- and bx, 7 ; Get modulus
- sub cx, bx ; Subtract
- mov bx, cx ; Save modulus
-
- mov al, ' ' ; Write spaces
- rep stosb
-
- pop cx
- sub cx, bx ; Adjust count
- .IF sign?
- sub cx, cx ; Make negative count 0
- .ENDIF
-
- pop bx
- jcxz loop2 ; If beyond limit done
- jmp loop1
- filleol:
- inc si ; After CR, throw away LF
- mov al, ' ' ; Fill rest of line
- rep stosb
- exit:
- pop ds
- INVOKE VioWrtCharStrAtt,
- ADDR achOut,
- X_MAX,
- y,
- 0,
- pcelAtrib,
- 0
-
- mov ax, si ; Return position
- ret
-
- ShowLine ENDP
-
-
- END
-
-
- PAGERR.ASM
- CD-ROM Disc Path: \SAMPCODE\MASM\MASM6\SHOW\PAGERR.ASM
-
- ;* PAGERR.ASM - Module containing routines for paging through a file and
- ;* writing text to the screen buffer. Works with main module SHOWR.ASM.
-
-
- .MODEL small, pascal, os_dos ; This code also works in tiny model
-
- INCLUDE show.inc
-
- .CODE
-
- ;* Pager - Displays status line and all the text lines for a screen.
- ;*
- ;* Params: cLines - lines to scroll (negative up, positive down)
- ;*
- ;* Uses: Global variables: segBuf, offBuf, yCur
- ;*
- ;* Return: None
-
- Pager PROC,
- cLines:SWORD
-
- mov es, segBuf ; Initialize buffer position
- mov di, offBuf
-
- mov cx, cLines ; Get line count
- mov ax, 10 ; Search for linefeed
-
- or cx, cx ; Argument 0?
- jg forward ; If above, forward
- jl backward ; If below, backward
- jmp showit ; If equal, done
- backward:
- call GoBack ; Adjust backward
- jmp showit ; Show screen
- forward:
- call GoForeward ; Adjust forward
-
- ; Write line number to status line
-
- showit:
- cld ; Forward
- push di ; Save
- push ds ; ES = DS
- pop es
-
- INVOKE BinToStr, ; Write line number as string
- yCur,
- ADDR stLine[LINE_POS]
-
- ; Fill in status line
-
- mov cx, 6 ; Seven spaces to fill
- sub cx, ax ; Subtract those already done
- mov al, ' ' ; Fill with space
- rep stosb
-
- INVOKE ShowLine, ; Write to screen
- ADDR stLine, ; Far pointer to line
- 0, ; Line number
- atSta ; Atttribute
-
- pop di
- mov si, di ; Update position
- mov cx, yMax ; Lines per screen
-
- .REPEAT
- mov bx, yMax ; Lines per screen
- inc bx ; Adjust for 0
- sub bx, cx ; Calculate current row
- push cx ; Save line number
- mov es, segBuf ; Reload
-
- INVOKE ShowLine, ; Write line to screen
- es::si, ; Far pointer to text
- bx, ; Line number
- atScr ; Attribute
-
- pop cx ; Restore line number
- mov si, ax ; Get returned position
-
- dec cx ; Count the line
- .UNTIL (ax >= cbBuf) || !cx ; Continue if more lines and not
- jcxz exit ; Done if more lines,
- ; else fill screen with spaces
- mov al, cl ; Columns * remaining lines
- mov dl, X_MAX ; is count of cells to fill
- mul dl
- mov dx, ax ; Save in DX (INVOKE uses AX)
-
- sub cx, yMax ; Calculate starting line
- neg cx
- inc cx
-
- INVOKE CellFill, ; Write space cells
- cx, ; Starting line
- dx, ; Cells to write
- celScr ; Cell to write
- exit:
- ret
-
- Pager ENDP
-
-
- ;* WriteNCell - Macro to write a cell one or more times. For CGA, the
- ;* macro writes during horizontal retrace. Note that this is a macro
- ;* even though it may result in more code than if it were a procedure.
- ;* This is because writes to the screen buffer are a speed bottleneck
- ;* that only occurs at a few key points in the program. The extra
- ;* size cost is worth paying.
- ;*
- ;* Uses: ES:DI has screen buffer position
- ;* AX has cell
- ;* DX should have port number for rescan check if CGA
- ;*
- ;* Params: isCGA - One of the following:
- CGA EQU 1
- NoCGA EQU 0
- ;*
- ;* count - If blank, write cell in AX once. If count given, write
- ;* cell in AX count times. Note that the count is optimized for a
- ;* CX argument. The argument should normally be blank or CX.
-
- WriteNCell MACRO isCGA:REQ, count:=<1>
-
- IF isCGA EQ 0 ; First handle non-CGA
- IFIDNI <count>, <1> ; Special case one cell
- stosw
- ELSE
- IFDIFI <count>, <cx> ; Load count if necessary
- mov cx, count
- ENDIF
- rep stosw ; Do repeated sequence
- ENDIF
- ELSE
- IFIDNI <count>, <1> ; Special case one cell
- push ax ; Save character
- .REPEAT
- in al, dx ; Look in the port
- shr al, 1 ; until it goes low
- .UNTIL !carry?
- cli
- .REPEAT
- in al, dx ; Look in the port
- shr al, 1 ; until it goes high
- .UNTIL carry?
- pop ax ; Restore and write it
- stosw
- sti
- ELSE
- IFDIFI <count>, <cx> ; Load count if necessary
- mov cx, count
- ENDIF
- .REPEAT
- push ax ; Save character
- .REPEAT
- in al, dx ; Look in the port
- shr al, 1 ; until it goes low
- .UNTIL !carry?
- cli
- .REPEAT
- in al, dx ; Look in the port
- shr al, 1 ; until it goes high
- .UNTIL carry?
- pop ax ; Restore and write it
- stosw
- sti
- .UNTILCXZ
- ENDIF
- ENDIF
- ENDM
-
- ;* ShowLine - Writes a line to the screen buffer.
- ;*
- ;* Params: fpBuffer - Far pointer to line to write
- ;* y - Line number
- ;* attr - Attribute
- ;*
- ;* Return: None
-
- ShowLine PROC USES si di ds,
- fpBuffer:FAR PTR BYTE,
- y:WORD,
- attr:BYTE
-
- sub dx, dx ; Zero
- .IF fCGA ; User port number as CGA flag
- mov dx, 03DAh ; Load port #
- .ENDIF
- mov es, segVid ; Load screen buffer segment
- lds si, fpBuffer ; Buffer segment
- mov cx, X_MAX ; Cells per row
- mov ax, y ; Starting row
- mov bx, X_MAX * 2 ; Bytes per row
- mul bl ; Figure columns per row
- mov di, ax ; Load as destination
- mov bx, di ; Save start for tab calculation
- mov ah, attr ; Attribute
- movechar:
- lodsb ; Get character
- cmp al, 13 ; CR?
- je fillspc
- cmp al, 9 ; Tab?
- jne notab
- call FillTab ; Yes? fill with spaces
- jcxz nextline ; If beyond limit done
- jmp movechar
- notab:
- or dx, dx ; CGA?
- je notab2
- WriteNCell CGA ; Yes? Write during retrace
- loop movechar ; Duplicate code here and below
- jmp nextline ; is worth cost in tight loop
- notab2:
- WriteNCell NoCGA ; Write
- loop movechar
- jmp nextline ; Done
- fillspc:
- mov al, ' ' ; Fill with space
-
- .IF dx != 0 ; CGA?
- WriteNCell CGA, cx
- inc si ; Adjust
- jmp exit ; Done
- .ENDIF
- WriteNCell NoCGA, cx
- inc si ; Adjust for LF
- jmp exit ; Done
- nextline:
- mov ah, 10 ; Search for next line feed
- .REPEAT
- lodsb ; Load and compare
- .UNTILCXZ al == ah
- exit:
- mov ax, si ; Return position
- ret
-
- ShowLine ENDP
-
-
- ;* CellFill - Fills a portion of the screen with a specified
- ;* character/attribute cell.
- ;*
- ;* Params: yStart - Starting line
- ;* cbCell - Number of cells
- ;* celFill - Attribute and character
- ;*
- ;* Return: None
-
- CellFill PROC,
- yStart:WORD,
- cbCell:WORD,
- celFill:WORD
-
- mov dx, 03DAh ; Load port #
- mov cx, yStart ; Starting line
- mov al, X_MAX * 2 ; Convert line to starting offset
- mul cl
- mov di, ax ; Make it the target
- mov es, segVid ; Load screen buffer segment
- mov cx, cbCell ; Characters to fill
- mov ax, celFill ; Attribute
- .IF fCGA ; Write cells
- WriteNCell CGA, cx
- .ELSE
- WriteNCell NoCGA, cx
- .ENDIF
-
- ret
-
- CellFill ENDP
-
-
- ;* FillTab - Writes spaces for tab to screen.
- ;*
- ;* Input: BX points to start of line
- ;* DI points to current position
- ;*
- ;* Return: None
-
- FillTab PROC
-
- push bx
- push cx
-
- sub bx, di ; Get current position in line
- neg bx
- shr bx, 1 ; Divide by 2 bytes per character
-
- mov cx, 8 ; Default count 8
- and bx, 7 ; Get modulus
- sub cx, bx ; Subtract
- mov bx, cx ; Save modulus
-
- mov al, ' ' ; Spaces
- .IF dx != 0 ; Write cells
- WriteNCell CGA, cx
- .ELSE
- WriteNCell NoCGA, cx
- .ENDIF
- pop cx
- sub cx, bx ; Adjust count
- .IF sign?
- sub cx, cx ; Make negative count 0
- .ENDIF
- pop bx
- ret
-
- FillTab ENDP
-
-
- ;* IsEGA - Determines if the current adapter can handle more than 25
- ;* lines per screen (usually an EGA or VGA).
- ;*
- ;* Params: None
- ;*
- ;* Return: 0 if no CGA or MONO, lines per screen if EGA/VGA
-
- IsEGA PROC
-
- mov ah, 12h ; Call EGA status function
- mov bl, 10h
- sub cx, cx ; Clear status bits
- int 10h
- sub ax, ax ; Segment 0 and assume no EGA
- jcxz noega ; If status still clear, no EGA
-
- mov es, ax ; ES=0
- test BYTE PTR es:[487h], 1000y; Test active bit
- jnz noega ; If set, not active
- mov ax, 1130h ; Get EGA information
- int 10h
- mov al, dl ; Return lines per screen
- cbw
- noega:
- ret
-
- IsEGA ENDP
-
-
- END
-
-
- PASCAL.ASM
- CD-ROM Disc Path: \SAMPCODE\MASM\MASM6\MIXED\PASCAL.ASM
-
- ; Assemble with ML /c PASCAL.ASM
- ; Called by PASMAIN.PAS
-
- .MODEL medium, PASCAL
- .386
- Power2 PROTO PASCAL factor:WORD, power:WORD
- .CODE
-
- Power2 PROC factor:WORD, power:WORD
-
- mov ax, factor ; Load Factor into AX
- mov cx, power ; Load Power into CX
- shl ax, cl ; AX = AX * (2 to power of CX)
- ret ; Leave return value in AX
-
- Power2 ENDP
- END
-
-
- QPEX.ASM
- CD-ROM Disc Path: \SAMPCODE\MASM\MASM6\MIXED\QPEX.ASM
-
- ; Assemble with ML /c QPEX.ASM
-
- Power2 PROTO PASCAL factor:WORD, power:WORD
-
- CODE SEGMENT WORD PUBLIC
- ASSUME CS:CODE
-
-
- Power2 PROC PASCAL factor:WORD, power:WORD
-
- mov ax, factor ; Load factor into AX
- mov cx, power ; Load power into CX
- shl ax, cl ; AX = AX * (2 to power of CX)
- ; Leave return value in AX
- ret
- Power2 ENDP
-
- CODE ENDS
- END
-
-
- SHOWP.ASM
- CD-ROM Disc Path: \SAMPCODE\MASM\MASM6\SHOW\SHOWP.ASM
-
- ;* SHOWP.ASM - Text file displayer for OS/2 (protect mode).
-
- TITLE Show
- .MODEL small, pascal, os_os2
- .DOSSEG
- .286
-
- INCL_NOCOMMON EQU 1 ; Enable call groups
- INCL_DOSFILEMGR EQU 1
- INCL_DOSMEMMGR EQU 1
- INCL_KBD EQU 1
- INCL_VIO EQU 1
-
- INCLUDE os2.inc
- INCLUDE show.inc
- INCLUDELIB os2.lib
-
- .STACK
-
- .DATA
-
- ; Status line
-
- stLine BYTE "Line: 12345 "
- stFile BYTE "File: 12345678.123 "
- BYTE "Quit: Q Next: ESC Move: PGUP PGDN HOME END"
-
- ; Variables for screen and cursor handling
-
- yCur WORD 1 ; Current line number
- yMax WORD ? ; Lines per screen
- vmiMode VIOMODEINFO < SIZE VIOMODEINFO > ; Structure for video data
- ; First field initialized to size
- vciCsr VIOCURSORINFO <> ; Structure for cursor data
- atCsr WORD -1 ; Cursor attribute (initized to hidden)
- bCsrSta BYTE 0 ; 0 = cursor visible, position unchanged
- ; 1 = cursor invisible, position unchanged
- ; 2 = cursor invisible, position changed
-
- atSta BYTE STAT_CLR ; Status line color
- celScr LABEL WORD ; Cell (character and attribute)
- chScr BYTE " " ; Initialize to space
- atScr BYTE SCRN_CLR ; Screen color
- chInit BYTE 0 ; Cell to restore when finished
- atInit BYTE 0
-
- ; Buffer variables
-
- fpBuf LABEL PBYTE
- offBuf WORD 0 ; Position in buffer (offset)
- segBuf SEL ? ; Base of buffer (segment selector)
- cbBuf WORD ? ; Count in bytes of buffer
-
- ; File information
-
- hFileIn HFILE ? ; Holds file handle on open
- usAct WORD ? ; Result of open
- usMode WORD OPEN_ACCESS_READONLY OR OPEN_SHARE_DENYNONE
- cbRead WORD ? ; Bytes read from file
-
- ; Directory information for file name search
-
- stFiles BYTE NAME_MAX DUP ("w")
- hFiles WORD HDIR_CREATE ; Directory handle
- fiFiles FILEFINDBUF <> ; Structure for results
- usCount WORD 1 ; Find one file at a time
-
- ; Buffer for file name
-
- kkiChar KBDKEYINFO <> ; Structure for character input
- sibStr STRINGINBUF < NAME_MAX >; Structure for string input
-
- ; Messages
-
- stMsg1 BYTE 13, 10, "Enter filename: "
- stMsg2 BYTE 13, 10, "File problem. Try again? "
- stMsg3 BYTE 13, 10, "File too large: "
- stMsg4 BYTE 13, 10, "Memory problem.",13,10
-
- ; Call table
-
- achKeys BYTE 71, 72, 73, 79, 80, 81, 'q', 'Q'; Key table
- afnKeys WORD HomeKey ; Corresponding procedures
- WORD UpKey
- WORD PgUpKey
- WORD EndKey
- WORD DownKey
- WORD PgDnKey
- WORD Quit
- WORD Quit
- WORD UnknownKey
-
- .CODE
- .STARTUP
-
- ; Load environment segment
-
- mov es, ax ; AX points to environment segment
- mov di, bx ; BX points to command line offset
-
- ; Throw away .EXE name
-
- sub ax, ax ; Find null at end of program name
- repne scasb
- cmp BYTE PTR es:[di], 0 ; If double zero, there's no name
- je Prompter ; so get from prompt
-
- .IF BYTE PTR es:[di] == ' '
- inc di ; Skip leading space
- .ENDIF
-
- ; Copy command line to file name buffer
-
- mov si, di ; Filename source
- mov di, OFFSET stFiles ; Name buffer destination
- mov bx, ds ; Save segment registers
- mov dx, es
- mov ds, dx ; DS = ES
- mov es, bx ; ES = DS
- mov cx, NAME_MAX ; Count = max file name allowed
-
- .REPEAT
- lodsb ; Copy characters
- .BREAK .IF (al == ' ') || (al == 0) ; Stop at space or null
- stosb
- .UNTILCXZ ; Until name exceeds max
-
- mov ds, bx ; Restore DS
- mov BYTE PTR [di], 0
- jmp FindFile
-
- ; Prompt for file
-
- NoFile:
- INVOKE VioWrtTTy, ; Write message
- ADDR stMsg2,
- LENGTHOF stMsg2,
- 0
-
- INVOKE KbdCharIn,
- ADDR kkiChar,
- IO_WAIT,
- 0
-
- and kkiChar.chChar_, 11011111y ; Convert to uppercase
- cmp kkiChar.chChar_, "Y"
-
- mov hFiles, -1
- mov usCount, 1
- .IF !zero?
- jmp Quit ; Quit if not yes
- .ENDIF
- Prompter:
- INVOKE VioWrtTTy, ; Else prompt for file name
- ADDR stMsg1,
- LENGTHOF stMsg1,
- 0
-
- INVOKE KbdStringIn,
- ADDR stFiles,
- ADDR sibStr,
- IO_WAIT,
- 0
-
- mov di, sibStr.cchIn_ ; Null terminate
- mov stFiles[di], 0
-
- ; Find first (or only) file in filespec
-
- FindFile:
- INVOKE DosFindFirst,
- ADDR stFiles,
- ADDR hFiles,
- 0,
- ADDR fiFiles,
- SIZE fiFiles,
- ADDR usCount,
- 0
-
- or ax, ax
- jnz NoFile
-
- INVOKE GetVid ; Adjust for current mode and
- ; video adapter and hide cursor
-
- ; Main program loop to process files
-
- .REPEAT
-
- ; Copy file name to file spec
-
- mov bCsrSta, 2 ; Cursor hidden, position unchanged
- INVOKE GetNamePos, ; Get file name position in file spec
- ADDR stFiles
-
- mov si, OFFSET fiFiles.achName_; Load source name
- mov di, ax ; Load adjusted destination address
- ; from return value
- sub cx, cx ; Load file name length
- mov cl, fiFiles.cchName_
- rep movsb ; Copy to spec
- mov BYTE PTR es:[di], 0 ; Null terminate
-
- ; Copy file name to status line
-
- sub cx, cx ; Load file length
- mov cl, fiFiles.cchName_
- mov bx, 12 ; Calculate blank spaces to fill
- sub bx, cx
- push ds ; ES=DS
- pop es
- mov si, OFFSET fiFiles.achName_; File name as source
- mov di, OFFSET stFile[FILE_POS]; Status line as destination
- rep movsb
- mov al, " " ; Fill rest of name space with blanks
- mov cx, bx
- rep stosb
-
- ; Skip any file that is larger than 64K
-
- .IF WORD PTR fiFiles.cbFile_[2] != 0
-
- INVOKE VioWrtTTy,
- ADDR stMsg3,
- LENGTHOF stMsg3,
- 0
-
- INVOKE VioWrtTTy,
- ADDR fiFiles.achName_,
- fiFiles.cchName_,
- 0
-
- .IF usCount <= 0 ; Get key if there's another file
- INVOKE KbdCharIn,
- ADDR kkiChar,
- IO_WAIT,
- 0
- .ENDIF
- .ENDIF
-
- ; Allocate file Buffer
-
- mov ax, WORD PTR fiFiles.cbFile_[0] ; Save size
- mov cbBuf, ax
- mov offBuf, 0
- INVOKE DosAllocSeg,
- ax,
- ADDR segBuf,
- 0
-
- .IF ax != 0
- mov bCsrSta, 1 ; Cursor hidden, position unchanged
- INVOKE VioWrtTTy,
- ADDR stMsg4,
- LENGTHOF stMsg4,
- 0
-
- jmp Quit
- .ENDIF
-
- ; Open file and read contents into buffer
-
- INVOKE DosOpen,
- ADDR stFiles,
- ADDR hFileIn,
- ADDR usAct,
- 0,
- FILE_NORMAL,
- FILE_OPEN,
- usMode,
- 0
-
- .IF ax != 0
- jmp NoFile
- .ENDIF
-
- INVOKE DosRead,
- hFileIn,
- fpBuf,
- cbBuf,
- ADDR cbRead
-
- .IF ax != 0
- jmp NoFile
- .ENDIF
-
- ; Search back for EOF marker and adjust if necessary
-
- mov di, cbRead ; Load file length
- dec di ; and adjust
- mov es, segBuf ; Save ES and load buffer segment
- std ; Look backward for 255 characters
- mov cx, 0FFh
- .IF cx >= di
- mov cx, di
- .ENDIF
-
- mov al, 1Ah ; Search for EOF marker
- repne scasb
- cld
- .IF cx != 0 ; If found:
- inc di ; Adjust and save file size
- mov cbBuf, di
- .ENDIF
-
- ; Show a screen of text and allow commands
-
- INVOKE Show
-
- INVOKE DosClose, ; Close file
- hFileIn
-
- INVOKE DosFreeSeg, ; Free memofy
- segBuf
-
- INVOKE DosFindNext, ; Get next file
- hFiles,
- ADDR fiFiles,
- SIZE fiFiles,
- ADDR usCount
-
- .UNTIL ax != 0 ; Fall through to Quit if
- ; this is the last file
- Quit PROC
-
- cmp bCsrSta, 1 ; Check cursor status
- jg csrvislast ; 2 - Make cursor visible on last lin
- je csrvis ; 1 - Make cursor visible
- jmp csrasis ; 0 - Leave cursor as is
-
- csrvislast:
- INVOKE VioSetCurPos, ; Restore cursor on last line
- yMax,
- 0,
- 0
- INVOKE VioScrollDn,
- yMax,
- 0,
- yMax,
- 79,
- 1,
- ADDR chInit,
- 0
- csrvis: ; Fall through
- mov ax, atCsr ; Restore cursor attribute
- mov vciCsr.attr_, ax
- INVOKE VioSetCurType,
- ADDR vciCsr,
- 0
- csrasis: ; Fall through
- .EXIT 0
-
- Quit ENDP
-
-
- Show PROC
-
- ; Display first page
-
- mov yCur, 1
- INVOKE Pager, ; Start at 0
- 0
-
- ; Handle keys
-
- .REPEAT
- INVOKE KbdCharIn, ; Get a key and load to register
- ADDR kkiChar,
- IO_WAIT,
- 0
-
- mov al, kkiChar.chChar_
-
- .BREAK .IF al == 27 ; If ESCAPE get out for next file
-
- ; If null or E0 (for extended keyboard), it's an extended key
- .IF (al == 0) || (al == 0E0h)
- mov al, kkiChar.chScan_ ; Load scan code
- .ENDIF
-
- push ds ; ES = DS
- pop es
- mov di, OFFSET achKeys ; Load address and length of key list
- mov cx, LENGTHOF achKeys + 1
- repne scasb ; Find position and point to key
- sub di, OFFSET achKeys + 1
- shl di, 1 ; Adjust pointer for word addresses
- call afnKeys[di] ; Call procedure
- .UNTIL 0
-
- ret
- Show ENDP
-
- HomeKey:
- mov offBuf, 0 ; HOME - set position to 0
- mov yCur, 1
- INVOKE Pager, offBuf
- retn
-
- UpKey:
- INVOKE Pager, -1 ; UP - scroll back 1 line
- retn
-
- PgUpKey:
- mov ax, yMax ; PGUP - Page back
- neg ax
- INVOKE Pager, ax
- retn
-
- EndKey:
- mov ax, cbBuf ; END - Get last byte of file
- dec ax ; Zero adjust
- mov offBuf, ax ; Make it the file position
- mov yCur, -1 ; Set illegal line number as flag
- mov ax, yMax ; Page back
- neg ax
- INVOKE Pager, ax
- retn
-
- DownKey:
- INVOKE Pager, 1 ; DOWN - scroll forward 1 line
- retn
-
- PgDnKey:
- INVOKE Pager, yMax ; PGDN - page forward
- retn
-
- UnknownKey:
- retn ; Ignore unknown key
-
-
- ;* GetVid - Gets the video mode and sets related global variables.
- ;*
- ;* Params: None
- ;*
- ;* Return: Number of lines in current mode (25, 43, or 50)
-
- GetVid PROC
-
- LOCAL x:USHORT, y:USHORT, cb:USHORT
-
-
- INVOKE VioGetMode, ; Get video mode
- ADDR vmiMode,
- 0
-
- sub ax, ax ; Clear AH
- mov al, vmiMode.fbType_ ; Put type in register
-
- ; If monochrome or color burst off:
- .IF (al & VGMT_GRAPHICS) || (al & VGMT_DISABLEBURST)
- mov atSta, STAT_BW ; Set B&W defaults for status line
- mov atScr, SCRN_BW ; and screen background
- .ENDIF
-
- INVOKE VioGetCurPos, ; Get cursor position (for cell read)
- ADDR y, ; Row
- ADDR x, ; Column
- 0 ; Console handle
-
- mov cb, 1 ; One cell
- INVOKE VioReadCellStr, ; Read cell to get current attribute
- ADDR chInit, ; Address to receive cell
- ADDR cb, ; Address of length
- y, ; Row
- x, ; Column
- 0 ; Console handle
- mov chInit, ' ' ; Make sure character is space
-
- INVOKE VioGetCurType, ; Get cursor mode
- ADDR vciCsr,
- 0
- mov ax, vciCsr.attr_ ; Save cursor attribute
- xchg atCsr, ax
- mov vciCsr.attr_, ax ; Set hidden cursor attribute
- mov ax, vmiMode.row_ ; Get number of rows and adjust
- dec ax
- mov yMax, ax
-
- INVOKE VioSetCurType, ; Hide cursor
- ADDR vciCsr,
- 0
-
- ret
-
- GetVid ENDP
-
-
- END
-
-
- SHOWR.ASM
- CD-ROM Disc Path: \SAMPCODE\MASM\MASM6\SHOW\SHOWR.ASM
-
- ;* SHOWR.ASM - Text file displayer for DOS (real mode).
-
- TITLE Show
- .MODEL small, pascal, os_dos ; This code also works in tiny model
- .DOSSEG
-
- INCLUDE show.inc
- INCLUDE dos.inc
- INCLUDE bios.inc
-
- .STACK
-
- .DATA
-
- ; Status line
-
- stLine BYTE "Line: 12345 "
- stFile BYTE "File: 12345678.123 "
- BYTE "Quit: Q Next: ESC Move: PGUP PGDN HOME END"
-
- ; Variables for screen handling
-
- yCur WORD 1
- yMax WORD 24 ; Number of rows - status line takes one more
- iMode BYTE 0 ; Initial mode
- iPage BYTE 0 ; Initial display page
- atInit BYTE 0 ; Initial attribute
- shCsr WORD 0 ; Initial cursor shape
- bCsrSta BYTE 0 ; 0 = cursor visible, position unchanged
- ; 1 = cursor invisible, position unchanged
- ; 2 = cursor invisible, position changed
-
- fNewVid BYTE 0 ; Video change flag
- fCGA BYTE 1 ; CGA flag - default yes
-
- segVid WORD SEG_CLR ; Video buffer address - default color
-
- atSta BYTE STAT_CLR ; Status line color
- celScr LABEL WORD ; Cell (character and attribute)
- chScr BYTE ' ' ; Initialize to space
- atScr BYTE SCRN_CLR ; Screen color
-
- ; Buffer variables
-
- fpBuf LABEL FAR PTR
- offBuf WORD 0 ; Position in buffer (offset)
- segBuf WORD 0 ; Base of buffer (segment)
- cbBuf WORD 0 ; Length of buffer
-
- ; File information
-
- hFileIn WORD 0 ; Holds file handle on open
-
- ; Buffer for file spec and structure for file info
-
- achBuf BYTE NAME_MAX, ? ; Buffer format for string input
- stFiles BYTE NAME_MAX DUP (0); File spec string
- fiFiles FILE_INFO <> ; Wild card entry structure
- cFiles WORD 0 ; Count of 1 or 0 files remaining
-
- ; Messages
-
- stMsg1 BYTE 13, 10, 13, 10, "Enter filename: $"
- stMsg2 BYTE 13, 10, "File problem. Try again? $"
- stMsg3 BYTE 13, 10, "File too large: $"
- stMsg4 BYTE 13, 10, "Memory problem.", 13, 10, "$"
- stMsg5 BYTE 13, 10, "Must have DOS 2.0 or higher", 13, 10, "$"
-
- ; Call table
-
- achKeys BYTE 71, 72, 73, 79, 80, 81, 'q', 'Q'; Key table
- afnKeys WORD HomeKey ; Corresponding procedures
- WORD UpKey
- WORD PgUpKey
- WORD EndKey
- WORD DownKey
- WORD PgDnKey
- WORD Quit
- WORD Quit
- WORD UnknownKey
-
- .CODE
- .STARTUP
-
- ; Adjust memory allocation (works for tiny or small model)
-
- mov bx, sp ; Convert stack pointer to paragraphs
- mov cl, 4 ; to get stack size
- shr bx, cl
- mov ax, ss ; Add SS to get end of program
- add ax, bx
- mov bx, es ; Get start of program
- sub ax, bx ; Subtract start from end
- inc ax
- @ModBlock ax ; Release memory after program
-
- ; Check DOS
-
- @GetVer ; Get DOS version
- .IF al < 2 ; Requires DOS 2.0
- @ShowStr stMsg5 ; else error and quit
- int 20h
- .ENDIF
-
- ; Get command line and copy to file name buffer
-
- mov di, 80h ; PSP offset of command line
- mov bl, es:[di] ; Get length from first byte
- sub bh, bh
- or bx, bx
- je Prompter
-
- mov WORD PTR es:[bx+81h], 0 ; Convert to ASCIIZ
- mov al, ' ' ; Character to check for
- inc di ; Advance beyond count
- mov cx, 0FFFFh ; Don't let count interfere
- repe scasb ; Find first non-space
- dec di ; Adjust
-
- mov si, di ; Filename source
- mov di, OFFSET stFiles ; Name buffer destination
- mov bx, ds ; Save segment registers
- mov dx, es
- mov ds, dx ; DS = ES
- mov es, bx ; ES = DS
- mov cx, NAME_MAX ; Count = max file name allowed
-
- .REPEAT
- lodsb ; Copy characters
- .BREAK .IF (al == ' ') || (al == 0) ; Stop at space or null
- stosb
- .UNTILCXZ ; Until name exceeds max
-
- mov ds, bx ; Restore segments
- mov es, dx
- mov BYTE PTR [di], 0
- jmp FindFile
- NoFile:
-
- @ShowStr stMsg2 ; Prompt to try again
- @GetChar 0, 1, 0
- and al, 11011111y ; Convert key to uppercase
- .IF al != 'Y' ; If not yes,
- jmp quit ; quit
- .ENDIF
-
- ; Prompt for file
-
- Prompter:
- @ShowStr stMsg1 ; Prompt for file
- @GetStr achBuf, 0 ; Get response as ASCIIZ
-
- ; Find first (or only) file in filespec
-
- FindFile:
-
- @SetDTA <OFFSET fiFiles> ; Set DTA to file info structure
- ; Don't need DTA for anything else,
- ; so no need to restore it
- @GetFirst stFiles,0 ; Find a matching file
-
- jc NoFile ; If not found, prompt for new
- inc cFiles ; Some files remaining
-
- INVOKE GetVid
-
- ; Main program loop to process files
-
- .REPEAT
-
- ; Copy file name to file spec
-
- mov bCsrSta, 2 ; Cursor hidden, position unchanged
- INVOKE GetNamePos, ; Get file name position in file spec
- ADDR stFiles
-
- mov si, OFFSET fiFiles.FName; Point to source name
- push ds ; ES = DS
- pop es
- mov di, ax ; Load address from return value
-
- .REPEAT ; Copy to (and including) null
- movsb
- .UNTIL BYTE PTR [si-1] == 0
-
- ; Copy file name to status line
-
- mov si, OFFSET fiFiles.FName ; Point to source name
- mov di, OFFSET stFile[FILE_POS] ; Point to status line
-
- sub cx, cx ; Count characters
- .REPEAT
- lodsb ; Copy to (but excluding) null
- .BREAK .IF al == 0
- stosb
- inc cx
- .UNTIL 0
-
- mov bx, 12 ; Calculate blank spaces to fill
- sub bx, cx
- mov al, ' ' ; Fill rest of name space with blanks
- mov cx, bx
- rep stosb
-
- ; Skip any file that is larger than 64K
-
- .IF WORD PTR fiFiles.len[2] != 0 ; Error if high word isn't zero
- mov bCsrSta, 1 ; Cursor hidden, position unchanged
-
- @ShowStr stMsg3 ; Display error string and file name
- @Write fiFiles.FName, cx, 1
-
- .IF cFiles ; If files remaining,
- @GetChar 0 ; get a key
- .ENDIF
- .ENDIF
-
- ; Allocate dynamic memory for file buffer
-
- mov ax, WORD PTR fiFiles.Len[0] ; Get length
- mov cbBuf, ax ; Save
- mov offBuf, 0
- mov cl, 4 ; Convert to paragraphs
- shr ax, cl
- inc ax ; Zero adjust
-
- @GetBlock ax ; Try to allocate 64K
- .IF carry? ; Display error and quit if
- @ShowStr stMsg4 ; request failed
- jmp Quit
- .ENDIF
- mov segBuf, ax ; Save buffer segment
-
- ; Open file and read contents into buffer
-
- @OpenFile stFiles, 0 ; Try to open response
- jc NoFile ; If fail, get a new file
- mov hFileIn, ax ; Save handle
-
- push ds
- @Read fpBuf, cbBuf, hFileIn ; Read file
- pop ds
- .IF carry?
- jmp NoFile ; If read error try again
- .ENDIF
-
- ; Search back for EOF marker and adjust if necessary
-
- mov di, cbBuf ; Load file length
- dec di ; and adjust
- mov es, segBuf
- std ; Look backward for 255 characters
- mov cx, 0FFh
- .IF cx >= di
- mov cx, di
- .ENDIF
-
- mov al, 1Ah ; Search for EOF marker
- repne scasb
- cld
- .IF cx != 0 ; If found:
- inc di ; Adjust and save file size
- mov cbBuf, di
- .ENDIF
-
- ; Show a screen of text and allow commands
-
- INVOKE Show
-
- @CloseFile hFileIn ; Yes? Close file
- @FreeBlock segBuf ; Release buffer
-
- @GetNext
-
- .IF carry?
- dec cFiles
- .ENDIF
- .UNTIL !cFiles
-
- ; Fall through to Quit
-
- Quit PROC
-
- cmp bCsrSta, 1 ; Check cursor status
- jg csrvislast ; 2 - Make cursor visible on last lin
- je csrvis ; 1 - Make cursor visible
- jmp csrasis ; 0 - Leave cursor as is
-
- csrvislast:
- mov dx, yMax ; Load last row and first column
- xchg dl, dh
- mov cx, dx ; Make row the same
- mov dl, 79
- @Scroll 0, atInit ; Clear last line to original color
- sub dl, dl ; Column 0
- @SetCsrPos ; Set cursor
- csrvis: ; Fall through
- ; Restore cursor attribute
- @SetCsrSize <BYTE PTR shCsr[1]>, <BYTE PTR shCsr[0]>
-
- csrasis:
- .IF fNewVid == 1
- @SetMode iMode ; Restore video mode, page, and curso
- @SetPage iPage
- .ENDIF
-
- .EXIT 0 ; Quit
-
- Quit ENDP
-
-
- Show PROC
-
- ; Display first page
-
- mov yCur, 1 ; Reinitialize
- INVOKE Pager, ; Start at 0
- 0
-
- ; Handle keys
-
- .REPEAT
-
- @GetChar 0, 0, 0 ; Get a key
-
- .BREAK .IF al == 27 ; If ESCAPE get out for next file
-
- ; If null or E0 (for extended keyboard), it's an extended key
- .IF (al == 0) || (al == 0E0h)
- @GetChar 0, 0, 0 ; Get extended code
- .ENDIF
-
- push ds ; ES = DS
- pop es
- mov di, OFFSET achKeys ; Load address and length of key list
- mov cx, LENGTHOF achKeys + 1
- repne scasb ; Find position and point to key
- sub di, OFFSET achKeys + 1
- shl di, 1 ; Adjust pointer for word addresses
- call afnKeys[di] ; Call procedure
- .UNTIL 0
-
- ret
- Show ENDP
-
- HomeKey:
- mov offBuf, 0 ; HOME - set position to 0
- mov yCur, 1
- INVOKE Pager, offBuf
- retn
-
- UpKey:
- INVOKE Pager, -1 ; UP - scroll backward 1 line
- retn
-
- PgUpKey:
- mov ax, yMax ; PGUP - Page back
- neg ax
- INVOKE Pager, ax
- retn
-
- EndKey:
- mov ax, cbBuf ; END - Get last byte of file
- dec ax ; Zero adjust
- mov offBuf, ax ; Make it the file position
- mov yCur, -1 ; Set illegal line number as flag
- mov ax, yMax ; Page back
- neg ax
- INVOKE Pager, ax
- retn
-
- DownKey:
- INVOKE Pager, 1 ; DOWN - scroll forward 1 line
- retn
-
- PgDnKey:
- INVOKE Pager, yMax ; PGDN - page forward
- retn
-
- UnknownKey:
- retn ; Ignore unknown key
-
-
- ;* GetVid - Gets the video mode and sets related global variables.
- ;*
- ;* Params: None
- ;*
- ;* Return: Number of lines in current mode (25, 43, or 50)
-
- GetVid PROC
-
- ; Adjust for current mode and and video adapter
-
- INVOKE IsEGA ; EGA (or VGA)?
- .IF ax != 0 ; If 0 must be CGA or MA
- mov yMax, ax ; Load rows
- dec fCGA ; Not CGA
- .ENDIF
-
- @GetMode ; Get video mode
- mov iMode, al ; Save initial mode and page
- mov iPage, bh
- mov dl, al ; Work on copy
- cmp dl, 7 ; Is it mono 7?
- je loadmono ; Yes? Set mono
- cmp dl, 15 ; Is it mono 15?
- jne graphchk ; No? Check graphics
- loadmono:
- mov segVid, SEG_MONO ; Load mono address
- mov atSta, STAT_BW ; Set B&W defaults for status line
- mov atScr, SCRN_BW ; and screen background
- dec fCGA ; Not CGA
- cmp al, 15 ; Is it mono 15?
- jne exit ; No? Done
- mov dl, 7 ; Yes? Set standard mono
- jmp chmode
- graphchk:
- cmp dl, 7 ; 7 or higher?
- jg color ; 8 to 14 are color (7 and 15 done)
- cmp dl, 4 ; 4 or higher?
- jg bnw ; 5 and 6 are probably black and whit
- je color ; 4 is color
- test dl, 1 ; Even?
- jz bnw ; 0 and 2 are black and white
- color: ; 1 and 3 are color
- cmp dl, 3 ; 3?
- je exit ; Yes? Done
- mov dl, 3 ; Change mode to 3
- jmp chmode
- bnw:
- mov atSta, STAT_BW ; Set B&W defaults for status line
- mov atScr, SCRN_BW ; and screen background
- cmp dl, 2 ; 2?
- je exit ; Yes? Done
- mov dl, 2 ; Make it 2
- chmode:
- @SetMode dl ; Set video mode
- @SetPage 0 ; Set video page
- mov fNewVid, 1 ; Set flag
- exit:
- @GetCsr ; Get cursor shape (ignore position)
- mov shCsr, cx ; Save shape
- @GetCharAtr ; Read the cell at the cursor
- mov atInit, ah ; Save attribute
- @SetCsrSize 20h, 20h ; Turn off cursor (invisible shape)
-
- ret
-
- GetVid ENDP
-
-
- END
-
-
- SHOWUTIL.ASM
- CD-ROM Disc Path: \SAMPCODE\MASM\MASM6\SHOW\SHOWUTIL.ASM
-
- ;* SHOWUTIL.ASM - Module containing routines used by both the real and
- ;* protected mode versions of SHOW. Works with main module SHOWR.ASM or
- ;* SHOWP.ASM and with PAGERR.ASM or PAGERP.ASM.
-
- TITLE ShowUtil
- .MODEL small, pascal
-
- INCLUDE show.inc
-
- .CODE
-
- ;* GetNamePos - Given a file specification potentially including file name,
- ;* directory, and/or drive, return the position of the first character
- ;* of the file name.
- ;*
- ;* Params: pchSpec - address of file spec
- ;*
- ;* Return: Near pointer to position of name portion of file spec
-
- GetNamePos PROC USES di si,
- pchSpec:PTR BYTE
-
- push ds
- pop es
- mov di, pchSpec ; Load address of file name
- mov si, di ; Save copy
-
- sub cx, cx ; Use CX as count
- sub dx, dx ; Use DX as found flag
- sub ax, ax ; Search for null
-
- .REPEAT
- .IF BYTE PTR es:[di] == '\' ; For each backslash:
- mov si, di ; Save position
- inc dx ; Set flag to true
- .ENDIF
- inc cx ; Count it
- scasb ; Get next character
- .UNTIL zero?
-
- .IF dx != 0 ; If found backslash:
- mov ax, si ; Return position in AX
- dec ax
-
- .ELSE ; Else search for colon
- mov di, si ; Restore start of name
- mov ax, ":" ; Search for colon
- repne scasb
-
- .IF zero? ; If colon:
- mov ax, di ; Return position in DX:AX
- .ELSE ; Else:
- mov ax, si ; Return original address
- .ENDIF
- .ENDIF
-
- ret
-
- GetNamePos ENDP
-
-
- ;* GoBack - Purpose Searches backward through buffer
- ;*
- ;* Params: CX has number of lines
- ;* ES:DI has buffer position
- ;* AL has 10 (line feed character)
- ;*
- ;* Return: None
- ;*
- ;* Modifies: Updates yCur and offBuf
-
- GoBack PROC
-
- neg cx ; Make count positive
- mov dx, cx ; Save a copy
- inc cx ; One extra to go up one
- .IF di == 0 ; If start of file, done
- ret
- .ENDIF
-
- .REPEAT
- push cx ; Save count
- mov cx, 0FFh ; Load maximum character count
- .IF cx >= SWORD PTR di ; If near start of buffer,
- mov cx, di ; search only to start
- .ENDIF
- std ; Go backward
- repne scasb ; Find last previous LF
- cld ; Go foreward
- jcxz atstart ; If not found, must be at start
- pop cx
- .UNTILCXZ
-
- .IF yCur == 0FFFFh ; IF end of file flag:
- add di, 2 ; Adjust for cr/lf
- mov offBuf, di ; Save position
- call EndCount ; Count back to get line number
- mov yCur, ax ; Store line count
- ret
- .ENDIF
-
- sub yCur, dx ; Calculate line number
- jg positive
- mov yCur, 1 ; Set to 1 if negative
- positive:
- add di, 2 ; Adjust for cr/lf
- mov offBuf, di ; Save position
- ret
- atstart:
- pop cx
- sub di, di ; Load start of file
- mov yCur, 1 ; Line 1
- mov offBuf, di ; Save position
- ret
-
- GoBack ENDP
-
-
- ;* GoForeward - Skips forward through a buffer of text a specified
- ;* number of lines.
- ;*
- ;* Params: CX - number of text lines to skip
- ;* ES:DI - starting buffer position
- ;* AL has 10 (line feed character)
- ;*
- ;* Return: None
- ;*
- ;* Modifes: yCur, offBuf, bx, cx, di
-
- GoForeward PROC
-
- cld ; Go forward
- mov dx, cx ; Copy count
-
- .REPEAT
- push cx ; Save count
- mov cx, 0FFh ; Load maximum character count
- mov bx, cbBuf ; Get end of file
-
- sub bx, di ; Characters to end of file
- .IF cx >= bx ; If less than maximum per line:
- mov cx, bx ; Adjust
- .ENDIF
-
- repne scasb ; Find next LF
- pop cx
-
-
- .IF !zero? || (di >= cbBuf) ; If LF not found or beyond end:
- mov di, offBuf ; Restore original position
- ret ; and quit
- .ENDIF
- .UNTILCXZ
-
- add yCur, dx ; Calulate line number
- mov offBuf, di ; Save position
- ret
-
- GoForeward ENDP
-
-
- ;* EndCount - Skips backward through a buffer of text, counting each
- ;* text line.
- ;*
- ;* Params: ES:DI - buffer position (end of file)
- ;*
- ;* Return: Number of lines counted
-
- EndCount PROC USES di dx cx
-
- std ; Backward
- mov al, 13 ; Search for CR
- mov dx, -1 ; Initialize (first will inc to 0)
-
- .REPEAT
- inc dx ; Adjust count
- mov cx, 0FFh ; Load maximum character count
-
- .IF SWORD PTR cx >= di ; If near start of buffer:
- mov cx, di ; Search only to start
- .ENDIF
-
- repne scasb ; Find last previous cr
- .UNTIL !zero? ; If not found, must be at start
-
- mov ax, dx ; Return count
- cld ; Forward
- ret
-
- EndCount ENDP
-
-
- ;* BinToStr - Converts an unsigned integer to a string. User is
- ;* responsible for providing a large enough buffer. The string is
- ;* not null-terminated.
- ;*
- ;* Params: i - Integer to be converted
- ;* pch - Pointer to character buffer to receive string
- ;*
- ;* Return: Number of character in string.
-
- BinToStr PROC,
- i:WORD,
- pch:PTR BYTE
-
- mov ax, i
- mov di, pch
-
- sub cx, cx ; Clear counter
- mov bx, 10 ; Divide by 10
-
- ; Convert and save on stack backwards
-
- .REPEAT
- sub dx, dx ; Clear top
- div bx ; Divide to get last digit as remaind
- add dl, "0" ; Convert to ASCII
- push dx ; Save on stack
- .UNTILCXZ ax == 0 ; Until quotient is 0
-
- ; Take off the stack and store forward
-
- neg cx ; Negate and save count
- mov dx, cx
-
- .REPEAT
- pop ax ; Get character
- stosb ; Store it
- .UNTILCXZ
- mov ax, dx ; Return digit count
-
- ret
-
- BinToStr ENDP
-
-
- END
-
-
- SNAP.ASM
- CD-ROM Disc Path: \SAMPCODE\MASM\MASM6\TSR\SNAP.ASM
-
- .MODEL small, pascal, os_dos
- .DOSSEG
- INCLUDE demo.inc
- INCLUDE tsr.inc
-
- OpenBox PROTO
- CloseBox PROTO
-
- .STACK
- .DATA
-
- DEFAULT_COLR EQU 1Eh ; Default = white on blue (color)
- DEFAULT_MONO EQU 70h ; Default = reverse video (mono)
-
- ; Set ALT + LEFT SHIFT + S as hot key combination. To set multiple shift
- ; keys, OR the appropriate values together for the shift value (HOT_SHIFT).
-
- HOT_SCAN EQU 1Fh ; Hot key scan code (S)
- HOT_SHIFT EQU shAlt OR shLeft ; Shift value (ALT + LEFT SHIFT)
- HOT_MASK EQU (shIns OR shCaps OR shNum OR shScroll) XOR 0FFh
-
- ROW1 EQU 9 ; Query box begins on row 9
- ROW2 EQU 14 ; and ends on row 14
- HEIGHT EQU ROW2 - ROW1 + 1 ; Number of rows in query box
-
- Box BYTE '┌──────────────────────────────────────┐', 0
- BYTE '│ Enter file name │', 0
- BYTE '│ (press Esc to cancel): │', 0
- BYTE '│ │', 0
- BYTE '│ │', 0
- boxend BYTE '└──────────────────────────────────────┘', 0
- LEN EQU (LENGTHOF boxend) - 1
-
- OldPos WORD ? ; Original cursor position
- Handle WORD ? ; File handle number
- FilSpec BYTE (LEN - 3) DUP(0) ; ASCIIZ string for file spec
-
- ; Fill attribute for prompt box. This is changed by running SNAP with
- ; the /Cx switch, where x = new display attribute in hexadecimal. For
- ; example, to change the color to yellow on brown for a color monitor,
- ; enter
- ; SNAP /C6E
- ; where the first digit specifies the background color and the second
- ; digit the foreground color. Typical values for x on a monochrome
- ; system are
- ; 07 normal 70 reverse video
- ; 0F high intensity 78 reverse video, high intensity
-
- BoxFill BYTE DEFAULT_MONO ; Assume monochrome
-
- ; Hold contains the screen text and attributes replaced by the query box.
- ; Buffer holds text captured from the screen, with room for 50 rows of 82
- ; characters, including carriage return/linefeed. To change Buffer's
- ; capacity, replace the dimensions with r * (c + 2) DUP(?), where r and
- ; c are row and column count respectively.
-
- Hold BYTE (HEIGHT * LEN) + 3 DUP(?)
- Buffer BYTE 50 * 82 DUP(?)
-
-
- .CODE
-
- ;* Snap - Main procedure for resident program. Called from the Activate
- ;* procedure when TSR is invoked by the proper key combination.
- ;*
- ;* Params: DS, ES = @data
- ;*
- ;* Return: None
-
- Snap PROC FAR
-
- INVOKE GetVidConfig ; Get video information
-
- mov al, vconfig.mode ; AL = video mode
- .IF (al <= 3) || (al == 7) ; If text mode:
-
- INVOKE GetCurPos ; Get original cursor coordinates
- mov OldPos, ax ; and store them
-
- INVOKE OpenBox ; Display query box
-
- mov bl, vconfig.cols ; Calculate column
- sub bl, LEN
- shr bl, 1
- add bl, 3
-
- INVOKE StrInput, ; Request input
- ROW1 + 4, ; Row
- bl, ; Column
- LEN - 4, ; Maximum string
- ADDR FilSpec ; Address of string buffer
-
- push ax ; Save terminating keypress
- call CloseBox ; Restore screen to original state
- pop ax ; Recover key
- .IF al != ESCAPE ; If Esc key not pressed:
- call OpenFile ; Open (or create) file
-
- .IF !carry? ; If okay:
- call Capture ; Write screen to file
- .ELSE
- mov ax, 0E07h ; Write bell character
- int 10h ; (ASCII 7) to console
- .ENDIF ; End file-okay test
- .ENDIF ; End ESCAPE test
-
- mov ax, OldPos ; Recover original cursor position
- mov bl, ah
-
- INVOKE SetCurPos, ; Restore cursor
- bx, ax ; Pass cursor row and column
-
- .ENDIF ; End text mode test
-
- retf ; Far return to Activate procedure
-
- Snap ENDP
-
-
- ;* OpenBox - Saves portion of screen to Hold buffer, then opens a box.
- ;*
- ;* Uses: vconfig - Video configuration structure
- ;*
- ;* Params: None
- ;*
- ;* Return: None
-
- OpenBox PROC
-
- mov dh, ROW1 ; DH = top screen row for box
- mov dl, vconfig.cols
- sub dl, LEN
- shr dl, 1 ; DL = left col for centered box
- push dx ; Save coords
- sub ch, ch
- mov cl, dh ; CX = row
- sub dh, dh ; DX = column
- GetVidOffset cx, dx
- mov si, ax ; Get video offset in SI
- mov bx, HEIGHT ; BX = number of window rows
- mov cx, LEN ; CX = number of columns
-
- push ds
- pop es
- mov di, OFFSET Hold ; Point ES:DI to hold buffer
- mov ax, si
- stosw ; Copy video offset to buffer
- mov ax, bx
- stosw ; Number of rows to buffer
- mov ax, cx
- stosw ; Number of cols to buffer
- mov al, vconfig.cols
- shl ax, 1 ; AX = number of video cells/row
- mov ds, vconfig.sgmnt ; DS = video segment
-
- .REPEAT
- push si ; Save ptr to start of line
- push cx ; and number of columns
- .IF vconfig.adapter == CGA ; If CGA adapter:
- INVOKE DisableCga ; Disable video
- .ENDIF
- rep movsw ; Copy one row to buffer
- .IF vconfig.adapter == CGA ; If CGA adapter:
- INVOKE EnableCga ; Reenable CGA video
- .ENDIF
- pop cx ; Recover number of columns
- pop si ; and start of line
- add si, ax ; Point to start of next line
- dec bx ; Decrement row counter
- .UNTIL zero? ; Loop while rows remain
-
- ; Screen contents (including display attributes) are now copied to buffer.
- ; Next open window, overwriting the screen portion just saved.
-
- push es
- pop ds ; Restore DS
-
- mov ax, 0600h ; Scroll service
- mov bh, BoxFill ; BH = fill attribute
- pop cx ; CX = row/col for upper left
- mov dh, ROW2
- mov dl, cl
- add dl, LEN
- dec dl ; DX = row/col for lower right
- int 10h ; Blank window area on screen
-
- ; Write box frame and text to screen
-
- mov dx, cx ; DX = row/col for upper left
- mov si, OFFSET Box ; Point to text
- mov cx, HEIGHT ; Number of rows in box
-
- .REPEAT
- push dx ; Save coordinates
- sub bh, bh
- mov bl, dh ; BX = row
- sub dh, dh ; DX = column
- INVOKE StrWrite, bx, dx, si ; Display one line of box
- pop dx ; Recover coordinates
- inc dh ; Next screen row
- add si, LEN ; Point to next line in box
- inc si
- .UNTILCXZ
-
- ret
-
- OpenBox ENDP
-
-
- ;* CloseBox - Restores the original screen text to close the window
- ;* previously opened by the OpenBox procedure
- ;*
- ;* Uses: vconfig - Video configuration structure
- ;*
- ;* Params: None
- ;*
- ;* Return: None
-
- CloseBox PROC
-
- mov si, OFFSET Hold
- lodsw
- mov di, ax ; DI = video offset of window
- lodsw
- mov bx, ax ; BX = number of window rows
- lodsw
- mov cx, ax ; CX = number of columns
-
- mov al, vconfig.cols
- shl ax, 1 ; AX = number of video cells/row
-
- .REPEAT
- push di ; Save ptr to start of line
- push cx ; and number of columns
- .IF vconfig.adapter == CGA ; If CGA adapter:
- INVOKE DisableCga ; Disable video
- .ENDIF
- rep movsw ; Copy one row to buffer
- .IF vconfig.adapter == CGA ; If CGA adapter:
- INVOKE EnableCga ; Reenable CGA video
- .ENDIF
- pop cx ; Recover number of columns
- pop di ; and start of line
- add di, ax ; Point to start of next line
- dec bx ; Decrement row counter
- .UNTIL zero? ; Loop while rows remain
-
- ret
-
- CloseBox ENDP
-
-
- ;* OpenFile - Opens or creates specified file. Resets file pointer to
- ;* end of file so that subsequent text is appended to bottom of file.
- ;*
- ;* Params: DS:SI = Pointer to file spec
- ;*
- ;* Return: None
-
- OpenFile PROC
-
- mov ax, 3D01h ; Request DOS to open file
- mov dx, OFFSET FilSpec ; DS:DX points to file specification
- int 21h ; Open File
- .IF carry? ; If it doesn't exist:
- mov ah, 3Ch ; Request create file
- sub cx, cx ; with normal attributes
- int 21h ; Create File
- .ENDIF
-
- .IF !carry? ; If no error:
- mov Handle, ax ; Store file handle
- mov bx, ax
- mov ax, 4202h ; Request DOS to reset file pointer
- sub cx, cx ; to end of file
- sub dx, dx
- int 21h ; Set File Pointer
- .ENDIF
- ret
-
- OpenFile ENDP
-
-
- ;* Capture - Copies screen text to Buffer, then writes Buffer to file.
- ;*
- ;* Uses: vconfig - Video configuration structure
- ;*
- ;* Params: None
- ;*
- ;* Return: None
-
- Capture PROC
-
- mov es, vconfig.sgmnt ; ES points to video segment address
- sub si, si ; ES:SI points to 1st video byte
- sub bx, bx ; BX = index to capture buffer
- mov dx, 3DAh ; DX = address of CGA status register
-
- .REPEAT
- sub ch, ch
- mov cl, vconfig.cols ; CX = number of columns in line
- mov di, cx
- dec di
- shl di, 1 ; ES:DI points to video byte for
- add di, si ; last column in line
-
- .REPEAT
- .IF vconfig.adapter == CGA ; If CGA:
- cli ; Disallow interruptions
- .REPEAT
- in al, dx ; Read current video status
- .UNTIL !(al & 1) ; until horizontal retrace done
- .REPEAT
- in al, dx ; Read video status
- .UNTIL al & 1 ; until horizontal retrace starts
- .ENDIF ; End CGA retrace check
-
- mov al, es:[di] ; Get screen char, working backward
- sti ; Reenable interrupts in case CGA
- sub di, 2 ; DI points to next character
- .UNTILCXZ (al != ' ') ; Scan for last non-blank character
-
- .IF !zero? ; If non-blank char found:
- inc cx ; Adjust column counter
- mov di, si ; ES:DI points to start of line
-
- .REPEAT
- .IF vconfig.adapter == CGA ; If CGA:
- cli ; Disallow interruptions
- .REPEAT
- in al, dx ; Read current video status
- .UNTIL !(al & 1) ; until horizontal retrace done
- .REPEAT
- in al, dx ; Read video status
- .UNTIL al & 1 ; until horizontal retrace starts
- .ENDIF ; End CGA retrace check
-
- mov al, es:[di] ; Get character, working forward
- sti
- add di, 2 ; DI points to next character
- mov Buffer[bx], al ; Copy to buffer
- inc bx
- .UNTILCXZ
- .ENDIF ; End check for non-blank char
-
- mov WORD PTR Buffer[bx], CRLF; Finish line with return/line feed
- add bx, 2
- mov al, vconfig.cols
- sub ah, ah
- shl ax, 1
- add si, ax ; SI points to start of next line
- dec vconfig.rows ; Decrement row count
- .UNTIL sign? ; Repeat for next screen row
-
- mov ah, 40h ; Request DOS Function 40h
- mov cx, bx ; CX = number of bytes to write
- mov bx, Handle ; BX = file handle
- mov dx, OFFSET Buffer ; DS:DX points to buffer
- int 21h ; Write to File
- .IF (ax != cx) ; If number of bytes written !=
- stc ; number requested, set carry
- .ENDIF ; flag to indicate failure
-
- pushf ; Save carry flag
- mov ah, 3Eh ; Request DOS Function 3Eh
- int 21h ; Close File
- popf ; Recover carry
- ret
-
- Capture ENDP
-
-
- @CurSeg ENDS
-
- ;* INSTALLATION SECTION - The following code and data are used only
- ;* during SNAP's installation phase. When the program terminates
- ;* through Function 31h, the above code and data remain resident;
- ;* memory occupied by the following code and data segments is returned
- ;* to the operating system.
-
- DGROUP GROUP INSTALLCODE, INSTALLDATA
-
- INSTALLDATA SEGMENT WORD PUBLIC 'DATA2'
-
- IDstr BYTE 'SNAP DEMO TSR', 0 ; Multiplex identifier string
-
- INSTALLDATA ENDS
-
- INSTALLCODE SEGMENT PARA PUBLIC 'CODE2'
- ASSUME ds:@data
-
- Begin PROC NEAR
-
- mov ax, DGROUP
- mov ds, ax ; Initialize DS
- mov ah, 15
- int 10h ; Get Video Mode
- .IF al != 7 ; If not default monochrome:
- mov BoxFill, DEFAULT_COLR ; Reset to default color value
- .ENDIF
-
- ; Before calling any of the TSR procedures, initialize global data
-
- INVOKE InitTsr, ; Initialize data
- es, ; Segment of PSP
- ADDR IDstr, ; Far address of multiplex ID string
- ADDR BoxFill ; Far address of memory shared
- ; with multiplex handler
- .IF ax == WRONG_DOS ; If DOS version less than 2.0:
- jmp exit ; Exit with message
- .ENDIF
-
- ; This section gets the command line argument to determine task:
- ; No argument = install
- ; /D or -D = deinstall
- ; /Cx or -Cx = change box fill attribute to value x
-
- mov al, 'd' ; Search command line for
- call GetOptions ; /D or -D argument
- cmp ax, NO_ARGUMENT ; No argument?
- je installtsr ; If so, try to install
- cmp ax, OK_ARGUMENT ; /D argument found?
- je deinstalltsr ; If so, try to deinstall
- mov al, 'c' ; Else search command line for
- call GetOptions ; /C or -C argument
- cmp ax, BAD_ARGUMENT ; If neither /D or /C arguments,
- je exit ; quit with error message
-
- ; This section changes the fill attribute of SNAP's prompt box. It converts
- ; to binary the two-digit hex number following the /C argument, calls the
- ; multiplex handler to find the address of the attribute variable stored in
- ; shared memory, then resets the attribute to the new value. It does not
- ; verify that the value specified in the command line is a valid two-digit
- ; hex number.
-
- mov ax, es:[di+1] ; AH = low digit, AL = high digit
- mov cx, 2 ; Process two digits
-
- .REPEAT
- sub al, '0' ; Convert digit to binary
- .IF (al > 9) ; If not digit 0-9:
- and al, 00011111y ; Mask out lower-case bit
- sub al, 7 ; Convert A to 10, B to 11, etc
- .ENDIF
- xchg ah, al ; Get next digit in AL
- .UNTILCXZ
-
- mov cl, 4
- shl al, cl ; Multiply high digit by 16
- or al, ah ; AL = binary value of attribute
- push ax ; Save new attribute
-
- mov al, 2 ; Request function 2
- call CallMultiplex ; Get shared memory addr in ES:DI
- .IF ax != IS_INSTALLED ; If TSR is not installed:
- pop ax ; Clean stack and
- mov ax, CANT_ACCESS ; quit with error message
- jmp exit
- .ELSE ; If TSR is installed:
- pop ax ; Recover new fill attribute in AL
- mov es:[di], al ; Write it to resident shared memory
- mov ax, OK_ACCESS ; Signal successful completion
- jmp exit
- .ENDIF
-
- ; This section sets up the TSR's interrupt handlers and
- ; makes the program memory-resident
-
- installtsr:
- push es ; Preserve PSP address
-
- mov ax, @code
- mov es, ax
- mov bx, OFFSET Snap ; ES:BX points to Snap
- INVOKE Install, ; Install handlers
- HOT_SCAN, ; Scan code of hot key
- HOT_SHIFT, ; Bit value of hot key
- HOT_MASK, ; Bit mask for shift hot key
- es::bx ; Far address of Snap procedure
-
- pop bx ; Recover PSP address
- or ax, ax ; If non-zero return code,
- jnz exit ; exit with appropriate message
- mov ax, INSTALLCODE ; Bottom of resident section
- sub ax, bx ; AX = number of paragraphs in
- ; block to be made resident
- INVOKE KeepTsr, ; Make TSR memory-resident
- ax ; Resident paragraphs
-
- ; This section deinstalls the resident TSR from memory
-
- deinstalltsr:
-
- INVOKE Deinstall ; Unchain interrupt handlers
-
- .IF ax > OK_ARGUMENT ; If successful:
- INVOKE FreeTsr, ; Deinstall TSR by freeing memory
- ax ; Address of resident seg
- .ENDIF ; Else exit with message
- exit:
- INVOKE FatalError, ; Exit to DOS with message
- ax ; Error number
-
- Begin ENDP
-
- INSTALLCODE ENDS
-
- END Begin
- Microsoft MASM: Sample Code from Version 5.x
-
-
- BA.ASM
- CD-ROM Disc Path: \SAMPCODE\MASM\MASM5\MIXED\BA.ASM
-
-
- .MODEL medium
- .CODE
-
- ; BASIC function for QuickBASIC, Version 4 and future versions
- ; of Microsoft and IBM BASIC Compilers
-
- PUBLIC Power2
- Power2 PROC
- push bp ; Entry sequence - save o
- mov bp,sp ; Set stack framepointer
-
- mov bx,[bp+8] ; Load Arg1 into
- mov ax,[bx] ; AX
- mov bx,[bp+6] ; Load Arg2 into
- mov cx,[bx] ; CX
- shl ax,cl ; AX = AX * (2 to power of CX)
- ; Leave return value in AX
-
- pop bp ; Restore old framepointer
- ret 4 ; Exit, and restore 4 bytes of arg
- Power2 ENDP
-
- ; BASIC subprogram for QuickBASIC, Versions 1, 2, and 3;
- ; for the Microsoft BASIC Compiler through Version 5.36
- ; for the IBM BASIC Compiler through Version 2.02
-
- PUBLIC Power2S
- Power2S PROC
- push bp ; Entry sequence - save o
- mov bp,sp ; Set stack framepointer
-
- mov bx,[bp+10] ; Load Arg1 into
- mov ax,[bx] ; AX
- mov bx,[bp+8] ; Load Arg2 into
- mov cx,[bx] ; CX
- shl ax,cl ; AX = AX * (2 to power of CX)
- mov bx,[bp+6] ; Store result in
- mov [bx],ax ; Arg3
-
- pop bp ; Restore old framepointer
- ret 4 ; Exit, and restore 4 bytes of arg
- Power2S ENDP
- END
-
-
-
- CA.ASM
- CD-ROM Disc Path: \SAMPCODE\MASM\MASM5\MIXED\CA.ASM
-
-
- .MODEL SMALL
- .CODE
- PUBLIC _Power2
- _Power2 PROC
- push bp ;Entry sequence
- mov bp,sp
-
- mov ax,[bp+4] ; Load Arg1 into AX
- mov cx,[bp+6] ; Load Arg2 into CX
- shl ax,cl ; AX = AX * (2 to power of CX)
- ; Leave return value in AX
-
- pop bp ; Exit sequence
- ret
- _Power2 ENDP
- END
-
-
-
- FA.ASM
- CD-ROM Disc Path: \SAMPCODE\MASM\MASM5\MIXED\FA.ASM
-
-
- .MODEL large
- .CODE
- PUBLIC Power2
- Power2 PROC
- push bp ; Entry sequence - save old BP
- mov bp,sp ; Set stack framepointer
-
- les bx,[bp+10] ; Load Arg1 into
- mov ax,[bx] ; AX
- les bx,[bp+6] ; Load Arg2 into
- mov cx,[bx] ; CX
- shl ax,cl ; AX = AX * (2 to power of CX)
- ; Leave return value in AX
-
- pop bp ; Restore old framepointer
- ret 4 ; Exit, and restore 4 bytes of args
- Power2 ENDP
- END
-
-
- PA.ASM
- CD-ROM Disc Path: \SAMPCODE\MASM\MASM5\MIXED\PA.ASM
-
-
- .MODEL medium
- .CODE
- PUBLIC Power2
- Power2 PROC
- push bp ; Entry sequence - save old BP
- mov bp,sp ; Set stack framepointer
-
- mov ax,[bp+8] ; Load Arg1 into AX
- mov cx,[bp+6] ; Load Arg2 into CX
- shl ax,cl ; AX = AX * (2 to power of CX)
- ; Leave return value in AX
-
- pop bp ; Restore old framepointer
- ret 4 ; Exit, and restore 4 bytes of args
- Power2 ENDP
- END
-
-
- PAGERP.ASM
- CD-ROM Disc Path: \SAMPCODE\MASM\MASM5\PAGERP.ASM
-
- TITLE Pager
- .MODEL small, pascal
-
- INCL_VIO EQU 1
-
- INCLUDE os2.inc
- .DATA
- EXTRN stAtrib:BYTE, scAtrib:BYTE, Cell:WORD, stLine:BYTE
- EXTRN sBuffer:WORD, oBuffer:WORD, Buffer:DWORD, lBuffer:WORD
- EXTRN nLines:WORD, curLine:WORD
-
- .CODE
- PUBLIC Pager
-
- ; Procedure Pager
- ; Purpose Displays status and text lines
- ; Input Stack variable: lines to scroll (negative up, positive down)
- ; Global variables: "sbuffer", "oBuffer", "curLine"
- ; Output To screen
-
- Pager PROC count
-
- mov es, sBuffer ; Initialize buffer position
- mov di, oBuffer
-
- mov cx, count ; Get count argument
- mov ax, 10 ; Search for linefeed
-
- or cx, cx ; Argument 0?
- jl skip1 ; If below, backward
- jg skip2 ; If above, forward
- jmp SHORT skip3 ; If equal, done
-
- skip1: call GoBack ; Adjust backward
- jmp SHORT skip3 ; Show screen
- skip2: call GoForwd ; Adjust forward
-
- ; Write line number to status line
-
- skip3: cld ; Go forward
- push di ; Save
- push ds ; ES = DS
- pop es
-
- ; BinToStr (curLine, OFFSET stLine[6])
-
- push curLine ; Arg 1
- @Pushc <OFFSET stLine[6]> ; Arg 2
- call BinToStr ; Convert to string
-
- ; Fill in status line
-
- mov cx, 6 ; Six spaces to fill
- sub cx, ax ; Subtract those already done
- mov al, " " ; Fill with space
- rep stosb
-
- @VioWrtCharStrAtt stLine, 80, 0, 0, stAtrib, 0 ; Write to screen
-
- pop di ; Update position
- mov si, di
- mov cx, nLines ; Lines per screen
-
- loop1: mov bx, nLines ; Lines of text
- inc bx ; Adjust for 0
- sub bx, cx ; Calculate current row
- push cx ; Save line number
-
- ; ShowLine (position, line, maxlength, &scAtrib)
-
- push sBuffer ; Arg 1
- push si
- push bx ; Arg 2
- push lBuffer ; Arg 3
- push ds ; Arg r4
- @Pushc <OFFSET scAtrib>
- call ShowLine ; Write line
-
- pop cx ; Restore line number
- mov si, ax ; Get returned position
-
- cmp ax, lBuffer ; If beyond end of file,
- jae skip4 ; fill screen with spaces
- loop loop1 ; else next line
- jmp SHORT exit ; Exit if done
-
- ; Fill the rest with spaces
-
- skip4: dec cx
- jcxz exit
- mov ax, 80 ; Columns times remaining lines
- mul cl
- mov dx, ax ; Macros use AX, so use DX
- sub cx, nLines ; Calculate starting line
- neg cx
- inc cx
-
- @VioWrtNCell Cell, dx, cx, 0, 0 ; Write space cells
-
- exit: ret
- Pager ENDP
-
- ; Procedure ShowLine (inLine, sRow, &pAtrib)
- ; Purpose Writes a line to screen
- ; Input Stack variables: 1 - FAR PTR to input line
- ; 2 - line number
- ; 3 - maximum number of characters (file length)
- ; 4 - FAR PTR to attribute
- ; Output Line to screen
-
- ShowLine PROC USES si di, inLine:FAR PTR BYTE, srow, max, pAtrib:FAR PTR
- LOCAL outLine[80]:BYTE
-
- push ds ; Save
- push ss ; ES = SS
- pop es
- lea di, outLine ; Destination line
- lds si, inLine ; Source line
- mov cx, 80 ; Cells per row
- mov bx, di ; Save copy of start for tab calc
- loop1: lodsb ; Get character
- cmp al, 9 ; Tab?
- je skip1 ; Space out tab
- cmp al, 13 ; CR?
- je skip3 ; Fill rest of line with spaces
- stosb ; Copy out
- cmp si, max ; Check for end of file
- ja skip3
- loop loop1
-
- loop2: lodsb ; Throw away rest of line to truncate
- cmp si, max ; Check for end of file
- ja exit
- cmp al, 13 ; Check for end of line
- jne loop2
- inc si ; Throw away line feed
-
- jmp SHORT exit ; Done
-
- skip1: push bx ; Fill tab with spaces
- push cx
-
- sub bx, di ; Get current position in line
- neg bx
-
- mov cx, 8 ; Default count 8
- and bx, 7 ; Get modulus
- sub cx, bx ; Subtract
- mov bx, cx ; Save modulus
-
- mov al, " " ; Write spaces
- rep stosb
-
- pop cx
- sub cx, bx ; Adjust count
- jns skip2 ; Make negative count 0
- sub cx, cx
- skip2: pop bx
- jcxz loop2 ; If beyond limit done
- jmp SHORT loop1
-
- skip3: inc si ; After CR, throw away LF
- mov al, ' ' ; Fill rest of line
- rep stosb
-
- exit: pop ds
- @VioWrtCharStrAtt outLine, 80, [srow], 0, [pAtrib], 0
-
- mov ax, si ; Return position
- ret
- ShowLine ENDP
-
- ; Procedure GoBack
- ; Purpose Searches backward through buffer
- ; Input CX has number of lines; ES:DI has buffer position
- ; Output Updates "curLine" and "oBuffer"
-
- GoBack PROC
- std ; Go backward
- neg cx ; Make count positive
- mov dx, cx ; Save a copy
- inc cx ; One extra to go up one
- or di, di ; Start of file?
- je exit ; If so, ignore
- loop1: push cx ; else save count
- mov cx, 0FFh ; Load maximum character count
- cmp cx, di ; Near start of buffer?
- jl skip1 ; No? Continue
- mov cx, di ; else search only to start
- skip1: repne scasb ; Find last previous LF
- jcxz skip4 ; If not found, must be at start
- pop cx
- loop loop1
- cmp curLine, -1 ; End of file flag?
- jne skip2 ; No? Continue
- add di, 2 ; Adjust for cr/lf
- mov oBuffer, di ; Save position
- call EndCount ; Count back to get line number
- ret
-
- skip2: sub curLine, dx ; Calculate line number
- jg skip3
- mov curLine, 1 ; Set to 1 if negative
- skip3: add di, 2 ; Adjust for cr/lf
- mov oBuffer, di ; Save position
- ret
-
- skip4: pop cx
- sub di, di ; Load start of file
- mov curLine, 1 ; Line 1
- mov oBuffer, di ; Save position
- exit: ret
- GoBack ENDP
-
- ; Procedure GoForwd
- ; Purpose Searches forward through a buffer
- ; Input CX has number of lines; ES:DI has buffer position
- ; Output Updates "curLine" and "oBuffer"
-
- GoForwd PROC
- cld ; Go forward
- mov dx, cx ; Copy count
- loop1: push cx ; Save count
- mov cx, 0FFh ; Load maximum character count
- mov bx, lBuffer ; Get end of file
-
- sub bx, di ; Characters to end of file
- cmp cx, bx ; Less than maximum per line?
- jb skip1
- mov cx, bx
- skip1: repne scasb ; Find next LF
- jcxz exit ; If not found, must be at end
- cmp di, lBuffer ; Beyond end?
- jae exit
- pop cx
- loop loop1
- add curLine, dx ; Calulate line number
- mov oBuffer, di ; Save position
- ret
-
- exit: pop cx
- mov di, oBuffer ; Restore position
- ret
- GoForwd ENDP
-
- ; Procedure EndCount
- ; Purpose Counts backward to count lines in file
- ; Input ES:DI has buffer position
- ; Output Modifies "curLine"
-
- EndCount PROC
- push di
-
- mov al, 13 ; Search for CR
- mov curLine, 0 ; Initialize
-
- loop1: inc curLine ; Adjust count
- mov cx, 0FFh ; Load maximum character count
- cmp cx, di ; Near start of buffer?
- jl skip1 ; No? Continue
- mov cx, di ; else search only to start
- skip1: repne scasb ; Find last previous cr
- jcxz exit ; If not found, must be at start
- jmp SHORT loop1
-
- exit: pop di
- ret
- EndCount ENDP
-
- ; Procedure BinToStr (number, string)
- ; Purpose Converts integer to string
- ; Input Stack arguments: 1 - Number to convert; 2 - Near address for writ
- ; Output AX has characters written
-
- BinToStr PROC number, string:PTR BYTE
-
- mov ax,number
- mov di,string
-
- sub cx, cx ; Clear counter
- mov bx, 10 ; Divide by 10
-
- ; Convert and save on stack backwards
-
- loop1: sub dx, dx ; Clear top
- div bx ; Divide to get last digit as remaind
- add dl, "0" ; Convert to ASCII
- push dx ; Save on stack
- or ax, ax ; Quotient 0?
- loopnz loop1 ; No? Get another
-
- ; Take off the stack and store forward
-
- neg cx ; Negate and save count
- mov dx, cx
- loop2: pop ax ; Get character
- stosb ; Store it
- loop loop2
- mov ax, dx ; Return digit count
-
- ret
- BinToStr ENDP
-
- END
-
-
- PAGERR.ASM
- CD-ROM Disc Path: \SAMPCODE\MASM\MASM5\PAGERR.ASM
-
- PAGE 60,132
- .MODEL small
- .DATA
- EXTRN statatr:BYTE,scrnatr:BYTE,sbuffer:WORD,pbuffer:WORD
- EXTRN fsize:WORD,cell:WORD,statline:BYTE,linenum:WORD
- EXTRN rows:WORD,vidadr:WORD,cga:BYTE
-
- .CODE
- PUBLIC Pager,isEGA
-
- ; Procedure Pager
- ; Purpose Displays status and text lines
- ; Input Stack variable: lines to scroll (negative up, positive dow
- ; Global variables: "sbuffer", "pbuffer", "linenum"
- ; Output To screen
-
- Pager PROC
- push bp
- mov bp,sp
-
- mov es,sbuffer ; Initialize buffer position
- mov di,pbuffer
-
- mov cx,[bp+4] ; Get count argument
- mov ax,10 ; Search for linefeed
-
- or cx,cx ; Argument 0?
- jg forward ; If above, forward
- jl backward ; If below, backward
- jmp SHORT show ; If equal, done
-
- backward: call GoBack ; Adjust backward
- jmp SHORT show ; Show screen
- forward: call GoForwd ; Adjust forward
-
- ; Write line number to status line
-
- show: cld ; Go forward
- push di
- push es
- push ds ; Load DS to ES
- pop es
-
- ; BinToStr (linenum,OFFSET statline[7])
-
- push linenum ; Arg 1
- mov ax,OFFSET statline[7]
- push ax ; Arg 2
- call BinToStr ; Convert to string
-
- ; Fill in status line
-
- mov cx,7 ; Seven spaces to f
- sub cx,ax ; Subtract those already
- mov al," " ; Fill with space
- rep stosb
- pop es
-
- mov bl,statatr ; Load status attribute
- mov BYTE PTR cell[1],bl
-
- ; CellWrt (DS,OFFSET statline,0,cell)
-
- push ds ; Arg 1
- mov ax,OFFSET statline ; Arg 2
- push ax
- sub ax,ax ; Arg 3
- push ax
- push cell ; Arg 4
- call CellWrt ; Write status line
-
- pop di
- mov bl,scrnatr ; Load screen attribute
- mov BYTE PTR cell[1],bl
- mov si,di ; Update position
- mov cx,rows ; Lines per screen
-
- show1: mov bx,rows ; Lines of text
- inc bx ; Adjust for 0
- sub bx,cx ; Calculate current row
- push cx ; Save line number
-
- ; CellWrt (sbuffer,position,line,cell)
-
- push sbuffer ; Arg 1
- push si ; Arg 2
- push bx ; Arg 3
- push cell ; Arg 4
- call cellwrt ; Write line
-
- push ss ; Restore DS from SS
- pop ds
-
- pop cx ; Restore line number
- mov si,ax ; Get returned position
-
- cmp ax,fsize ; Beyond end of file?
- jae fillout ; Yes? Fill screen with
- loop show1 ; else next line
- jmp SHORT pagedone ; Get out if done
-
- ; Fill the rest with spaces
-
- fillout: dec cx ; Adjust
- jcxz pagedone
- mov al,80 ; Columns times re
- mul cl
-
- ; CellFil (sbuffer,count,cell)
-
- push sbuffer ; Arg 1
- push ax ; Arg 2
- push cell ; Arg 3
- call CellFil ; Fill screen with spaces
-
- push ss ; Restore DS from SS
- pop ds
-
- pagedone: pop bp
- ret 2
- Pager ENDP
-
- ; Procedure CellWrt (segment,offset,line,cell)
- ; Purpose Writes a line to screen buffer
- ; Input Stack variables: 1 - segment of line
- ; 2 - offset
- ; 3 - line number
- ; 4 - attribute
- ; Output Line to screen buffer
-
- CellWrt PROC
- push bp
- mov bp,sp
- sub dx,dx ; Clear as flag
- cmp cga,1 ; CGA?
- jne noscan
- mov dx,03DAh ; Load port #
-
- noscan: mov es,vidadr ; Load screen buffer s
- mov ds,[bp+10] ; Buffer segment
- mov si,[bp+8] ; Buffer position
- mov cx,80 ; Cells per row
- mov ax,[bp+6] ; Starting row
- mov bx,80*2 ; Bytes per row
- mul bl ; Figure columns per row
- mov di,ax ; Load as destination
- mov bx,di ; Save start for tab calc
- mov ax,[bp+4] ; Attribute
- movechar: lodsb ; Get character
- cmp al,13 ; CR?
- je fillspc
- cmp al,9 ; Tab?
- jne notab
- call filltab ; Yes? fill with spaces
- jcxz nextline ; If beyond limit done
- jmp SHORT movechar
-
- notab: or dx,dx ; CGA?
- je notab2
- call Retrace ; Yes? Write during retrace
- loop movechar
- jmp SHORT nextline
-
- notab2: stosw ; Write
- loop movechar
- jmp SHORT nextline ; Done
-
- fillspc: mov al," " ; Fill with space
-
- or dx,dx ; CGA?
- je space2
- space1: call Retrace ; Yes? Write during ret
- loop space1
- inc si ; Adjust
- jmp SHORT exit ; Done
-
- space2: rep stosw ; Write
- inc si ; Adjust for LF
- jmp SHORT exit ; Done
-
- nextline: mov ah,10 ; Search for next line fe
- chklf: lodsb ; Load and compare
- cmp al,ah
- loopne chklf
-
- exit: mov ax,si ; Return position
- pop bp
- ret 8
- CellWrt ENDP
-
- ; Procedure CellFil (segment,count,cell)
- ; Purpose Fills screen with character
- ; Input Stack variables: 1 - segment of text (offset 0)
- ; 2 - number of characters
- ; 3 - attribute and character
- ; Output Characters to screen buffer
-
- CellFil PROC
- push bp
- mov bp,sp
- sub dx,dx ; Clear as flag
- cmp cga,1 ; CGA?
- jne noscan2
- mov dx,03DAh ; Load port #
-
- noscan2: mov es,vidadr ; Load screen buffer segment
- mov ds,[bp+8] ; Buffer segment (position 0)
- mov cx,[bp+6] ; Characters to fill
- mov ax,[bp+4] ; Attribute
- or dx,dx ; CGA?
- je fillem2
- fillem1: call Retrace ; Yes? Write during retrace
- loop fillem1
- jmp SHORT filled ; Done
- fillem2: rep stosw ; Write
-
- filled: pop bp
- ret 6
- CellFil ENDP
-
- ; Procedure FillTab
- ; Purpose Writes spaces for tab to screen
- ; Input BX points to start of line, DI points to current po
- ; Output Spaces to screen buffer
-
- FillTab PROC
- push bx
- push cx
-
- sub bx,di ; Get current position in
- neg bx
- shr bx,1 ; Divide by 2 bytes per
-
- mov cx,8 ; Default count 8
- and bx,7 ; Get modulus
- sub cx,bx ; Subtract
- mov bx,cx ; Save modulus
-
- mov al," " ; Spaces
- or dx,dx ; CGA?
- je tabem2
-
- tabem1: call Retrace ; Yes? Write during ret
- loop tabem1
- jmp SHORT tabbed
- tabem2: rep stosw ; Write
-
- tabbed: pop cx
- sub cx,bx ; Adjust count
- jns nomore ; Make negative count 0
- sub cx,cx
- nomore: pop bx
- ret
- FillTab ENDP
-
- ; Procedure GoBack
- ; Purpose Searches backward through buffer
- ; Input CX has number of lines; ES:DI has buffer position
- ; Output Updates "linenum" and "pbuffer"
-
- GoBack PROC
- std ; Go backward
- neg cx ; Make count positive
- mov dx,cx ; Save a copy
- inc cx ; One extra to go up one
- or di,di ; Start of file?
- je exback ; If so, ignore
- findb: push cx ; else save count
- mov cx,0FFh ; Load maximum character count
- cmp cx,di ; Near start of bu
- jl notnear ; No? Continue
- mov cx,di ; else search on
- notnear: repne scasb ; Find last previous LF
- jcxz atstart ; If not found, must be
- pop cx
- loop findb
- cmp linenum,0FFFFh ; End of file flag?
- jne notend ; No? Continue
- add di,2 ; Adjust for cr/lf
- mov pbuffer,di ; Save position
- call EndCount ; Count back to
- ret
-
- notend: sub linenum,dx ; Calculate line numb
- jg positive
- mov linenum,1 ; Set to 1 if negative
- positive: add di,2 ; Adjust for cr/lf
- mov pbuffer,di ; Save position
- ret
-
- atstart: pop cx
- sub di,di ; Load start of fi
- mov linenum,1 ; Line 1
- mov pbuffer,di ; Save position
- exback: ret
- GoBack ENDP
-
- ; Procedure GoForwd
- ; Purpose Searches forward through a buffer
- ; Input CX has number of lines; ES:DI has buffer position
- ; Output Updates "linenum" and "pbuffer"
-
- GoForwd PROC
- cld ; Go forward
- mov dx,cx ; Copy count
- findf: push cx ; Save count
- mov cx,0FFh ; Load maximum character count
- repne scasb ; Find next LF
- jcxz atend ; If not found, m
- cmp di,fsize ; Beyond end?
- jae atend
- pop cx
- loop findf
- add linenum,dx ; Calulate line numbe
- mov pbuffer,di ; Save position
- ret
-
- atend: pop cx
- mov di,pbuffer ; Restore position
- ret
- GoForwd ENDP
-
- ; Procedure EndCount
- ; Purpose Counts backward to count lines in file
- ; Input ES:DI has buffer position
- ; Output Modifies "linenum"
-
- EndCount PROC
- push di
-
- mov al,13 ; Search for CR
- mov linenum,0 ; Initialize
-
- findstrt: inc linenum ; Adjust count
- mov cx,0FFh ; Load maximum character count
- cmp cx,di ; Near start of bu
- jl notnear2 ; No? Continue
- mov cx,di ; else search on
- notnear2: repne scasb ; Find last previous cr
- jcxz found ; If not found, m
- jmp SHORT findstrt
-
- found: pop di
- ret
- EndCount ENDP
-
- ; Procedure isEGA
- ; Purpose Determines if an EGA is active
- ; Input None
- ; Output 0 if no; lines per screen if yes
-
- isEGA PROC
- push bp
- push es
- mov ah,12h ; Call EGA status function
- mov bl,10h
- sub cx,cx ; Clear status bit
- int 10h
- sub ax,ax ; Segment 0 and as
- jcxz noega ; If status still clear,
-
- mov es,ax ; ES=0
- test BYTE PTR es:[487h],1000b ; Test active bit
- jnz noega ; If set, not active
- mov ax,1130h ; Get EGA information
- int 10h
- mov al,dl ; Return lines per screen
- cbw
-
- noega: pop es
- pop bp
- ret
- isEGA ENDP
-
- ; Procedure BinToStr (number,address)
- ; Purpose Converts integer to string
- ; Input Stack arguments: 1 - Number to convert; 2 -
- ; Output AX has characters written
-
- BinToStr PROC
- push bp
- mov bp,sp
- mov ax,[bp+6] ; Arg 1
- mov di,[bp+4] ; Arg 2
-
- sub cx,cx ; Clear counter
- mov bx,10 ; Divide by 10
-
- ; Convert and save on stack backwards
-
- getdigit: sub dx,dx ; Clear top
- div bx ; Divide to get last
- add dl,"0" ; Convert to ASCII
- push dx ; Save on stack
- or ax,ax ; Quotient 0?
- loopnz getdigit ; No? Get another
-
- ; Take off the stack and store forward
-
- neg cx ; Negate and save count
- mov dx,cx
- putdigit: pop ax ; Get character
- stosb ; Store it
- loop putdigit
- mov ax,dx ; Return digit count
-
- pop bp
- ret 4
- BinToStr ENDP
-
- ; Procedure Retrace
- ; Purpose Writes cell during horizontal retrace (CGA)
- ; Input ES:DI has screen buffer position, AX has cell
- ; Output Character to screen buffer
-
- Retrace PROC
- push bx
- mov bx,ax ; Save character
- lscan2: in al,dx ; Look in the port
- shr al,1 ; until it goes low
- jc lscan2
- cli
- hscan2: in al,dx ; Look in the port
- shr al,1 ; until it goes high
- jnc hscan2
- mov ax,bx ; Restore and write it
- stosw
- sti
- pop bx
- ret
- Retrace ENDP
-
- END
-
-
- POWER2.ASM
- CD-ROM Disc Path: \SAMPCODE\MASM\MASM5\MIXED\POWER2.ASM
-
- ; Default command line for BASIC: MASM /Dmodel=medium /Dlang=BASIC power2;
- ; Default command line for C: MASM /MX /Dmodel=small /Dlang=C power2;
- ; Default command line for FORTRAN: MASM /Dmodel=large /Dlang=FORTRAN power2
- ; Default command line for Pascal: MASM /Dmodel=large /Dlang=Pascal power2;
-
- % .MODEL model,lang
- INCLUDE mixed.inc
-
- % IFIDNI <lang>,<BASIC>
- reference EQU 1
- % ELSEIFIDNI <lang>,<FORTRAN>
- reference EQU 1
- ENDIF
-
- .CODE
-
- ; Function for C, FORTRAN, Pascal, Version 4 of QuickBASIC, and
- ; future versions of Microsoft and IBM BASIC Compilers
-
- IFDEF reference ; Pass by reference for BASIC or FORTRAN
- Power2 PROC Value:PTR WORD, Count:PTR WORD
-
- pLes bx,Value ; Load arguments passed by reference
- mov ax,FP[bx]
- pLes bx,Count
- mov cx,FP[bx]
-
- ELSE ; Pass by value for C or Pascal
- Power2 PROC Value, Count
-
- mov ax,Value ; Load arguments passed by value
- mov cx,Count
- ENDIF
-
- shl ax,cl ; AX = AX * (2 to power of CL)
- ; Return result in AX
- ret
- Power2 ENDP
-
- IFIDNI <lang>,<BASIC>
-
- ; Subprogram for QuickBASIC, Versions 1, 2, and 3;
- ; for the Microsoft BASIC Compiler through Version 5.36
- ; for the IBM BASIC Compiler through Version 2.02
-
- Power2S PROC Value:PTR WORD, Count:PTR WORD, RetVal:PTR WORD
-
- pLes bx,Value ; Load BASIC arguments
- mov ax,FP[bx] ; passed by reference
- pLes bx,Count
- mov cx,FP[bx]
-
- shl ax,cl ; AX = AX * (2 to power of CL)
-
- pLes bx,RetVal ; Load return address
- mov FP[bx],ax ; and store result in it
-
- ret
- Power2S ENDP
- ENDIF ; BASIC
- END
-
-
-
- SHOWP.ASM
- CD-ROM Disc Path: \SAMPCODE\MASM\MASM5\SHOWP.ASM
-
- TITLE Show
-
- ; Program SHOW.ASM
- ; Purpose Text file displayer
- ; Input File name from command line or prompt
- ; Output Display file to screen
-
- DOSSEG
- .MODEL small, pascal
-
- INCL_DOSFILEMGR EQU 1 ; Enable call groups
- INCL_DOSMEMMGR EQU 1
- INCL_KBD EQU 1
- INCL_VIO EQU 1
-
- INCLUDE os2.inc
- INCLUDELIB doscalls.lib
-
- .STACK 800h
-
- .DATA
-
- ; Status line
-
- PUBLIC stLine, nLines, curLine
- curLine DW 1 ; Current line number
- nLines DW ? ; Lines per screen
- stLine DB "Line: 12345 "
- stFile DB "File: 12345678.123 "
- DB "Quit: Q Next: ESC Move: PGUP PGDN HOME END"
-
- ; Variables for screen and cursor handling
-
- PUBLIC vMode, Cell, stAtrib, scAtrib
- vMode VIOMODEINFO <> ; Structures for video and cursor data
- lvMode EQU $ - vMode ; Length of structure
- vType DW 0 ; Video type - 0 flag for no change
-
- cMode VIOCURSORINFO <>
- cAtrib DW -1 ; Cursor attribute (initized to hidden)
- cStatus DB 0 ; 0 = cursor visible, position unchanged
- ; 1 = cursor invisible, position unchanged
- ; 2 = cursor invisible, position changed
-
- stAtrib DB 030h ; Status line color default - black on cyan
- stBW EQU 070h ; B&W default - black on white
- Cell LABEL WORD ; Cell (character and attribute)
- scChar DB " " ; Initialize to space
- scAtrib DB 017h ; Screen color default - white on blue
- scBW EQU 007h ; B&W default - white on black
-
- ; Variables for buffer and file handling
-
- PUBLIC Buffer, oBuffer, sBuffer, lBuffer
- Buffer LABEL DWORD
- oBuffer DW 0 ; Position in buffer (offset)
- sBuffer DW ? ; Base of buffer (segment)
- lBuffer DW ? ; Length of buffer
-
- ; File information
-
- lfName EQU 66
- fName DB lfName DUP (" ")
- fHandle DW ? ; Holds file handle on open
- fAction DW ? ; Result of open
- fAtrib EQU 0 ; Normal file
- fFlag EQU 1 ; Open file if exist, fail if not exist
- ; Read only, deny none, private, error codes, use cache, normal file
- fModeRec RECORD DA:1=0,WT:1=0,FE:1=0,R1:5=0,INF:1=1,SM:3=2,R2:1=0,AM:3=0
- fMode fModeRec <>
- fRead DW ? ; Bytes read from file
-
- ; Directory information for file name search
-
- dHandle DW -1 ; Directory handle
- dResult FILEFINDBUF <> ; Structure for results
- dlResult EQU $ - dResult ; length of result
- dCount DW 1 ; Find one file at a time
-
- Prompt DB 13,10,"Enter filename: "
- lPrompt EQU $ - Prompt
- Prompt2 DB 13,10,"No such file. Try again? "
- lPrompt2 EQU $ - Prompt2
- Prompt3 DB 13,10,"File too large: "
- lPrompt3 EQU $ - Prompt3
- Prompt4 DB 13,10,"Memory problem.",13,10
- lPrompt4 EQU $ - Prompt4
-
- ; Keyboard data
-
- kChar KBDKEYINFO <> ; Structures for character and string input
- kStr STRINGINBUF <>
- kWait EQU 0 ; Wait flag
-
- ; Call table
-
- kTable DB 71,72,73,79,80,81,'q','Q'; Key codes
- lkTable EQU $-kTable
- procTable DW homek ; Table of keys and procedures
- DW upk
- DW pgupk
- DW endk
- DW downk
- DW pgdnk
- DW Quit
- DW Quit
- DW nonek
-
- .CODE
- EXTRN Pager:PROC ; Routine in other module
-
- start PROC
- mov es, ax ; Load environment segment
- mov di, bx
-
- ; Throw away .EXE name
-
- sub ax, ax ; Find null at end of program name
- repne scasb
- cmp BYTE PTR es:[di], 0; If double zero, there's no name
- je Prompter ; so get from prompt
-
- cmp BYTE PTR es:[di], ' '
- jne skip1
- inc di ; Skip leading space
- skip1:
- ; Copy command line to file name buffer
-
- mov si, di ; Filename source
- mov di, OFFSET fName ; Name buffer destination
- mov bx, ds ; Save segment registers
- mov dx, es
- mov ds, dx ; DS = ES
- mov es, bx ; ES = DS
- mov cx, lfName ; Count = max file name allowed
- loop1: lodsb ; Copy first character
- stosb
- cmp al,' ' ; Terminate on space too
- je skip2
- or al,al
- loopnz loop1 ; If not null, copy another
- skip2:
- mov ds, bx ; Restore DS
- mov BYTE PTR [di-1], 0
- jmp FindFile
-
- NoFile: @VioWrtTTy Prompt2, lPrompt2, 0
- @KbdCharIn kChar, kWait, 0
- and kChar.kbci_chChar, 11011111b ; Convert to uppercase
- cmp kChar.kbci_chChar, "Y"
- mov dHandle, -1
- mov dCount, 1
- je Prompter ; If yes, try again
- jmp Quit ; else quit
-
- Prompter: @VioWrtTTy Prompt, lPrompt, 0 ; Else prompt for file name
-
- mov kStr.kbsi_cb, lfName
-
- @KbdStringIn fName, kStr, kWait, 0
- mov di, kStr.kbsi_cchIn ; Null terminate
- mov fName[di], 0
-
- ; Find first (or only) file in filespec
-
- FindFile: @DosFindFirst fName, dHandle, 0, dResult, dlResult, dCount, 0
- or ax, ax
- jz skip3
- jmp NoFile
-
- ; Adjust for current mode and video adapter and hide cursor
- skip3: call GetVid
-
- FileLoop:
- mov cStatus, 2 ; Cursor invisible, position unchanged
-
- ; Copy file name to file spec
-
- push ds ; Get file name position in file spec
- @Pushc <OFFSET fName>
- call GetNamPos
- mov si, OFFSET dResult.findbuf_achName ; Load source name
- mov es, dx ; Load adjusted destination address
- mov di, ax ; from return value
- sub cx, cx ; Load file length
- mov cl, dResult.findbuf_cchName
- rep movsb ; Copy to spec
- mov BYTE PTR es:[di], 0; Null terminate
-
- ; Copy file name to status line
-
- sub cx, cx ; Load file length
- mov cl, dResult.findbuf_cchName
- mov bx, 12 ; Calculate blank spaces to fill
- sub bx, cx
- push ds ; ES=DS
- pop es
- mov si, OFFSET dResult.findbuf_achName ; File name as source
- mov di, OFFSET stFile[6] ; Status line as destination
- rep movsb
- mov al, " " ; Fill rest of name space with blanks
- mov cx, bx
- rep stosb
-
- ; Open file
-
- @DosOpen fName, fHandle, fAction, 0, fAtrib, fFlag, [fMode], 0
- or ax, ax
- jz skip4
- jmp NoFile
-
- skip4: cmp WORD PTR dResult.findbuf_cbFile[2], 0
- jz skip6 ; Make sure file is less than a segment
- mov cStatus, 1 ; Cursor invisible, position unchanged
- @VioWrtTTy Prompt3, lPrompt3, 0
- @VioWrtTTy <stFile + 6>, 12, 0
- cmp [dCount], 0 ; Get key if there's another file
- je skip5
- @KbdCharIn kChar, kWait, 0
- skip5: jmp skip11
-
- ; Allocate file buffer
-
- skip6: mov ax, WORD PTR dResult.findbuf_cbFile[0] ; Save size
- mov lBuffer, ax
- mov oBuffer, 0
- @DosAllocSeg ax, sBuffer, 0
- or ax, ax
- jz skip7
- mov cStatus, 1 ; Cursor invisible, position unchanged
- @VioWrtTTy Prompt4, lPrompt4, 0
- jmp Quit
-
- ; Read the file into the buffer
-
- skip7: @DosRead [fHandle], [Buffer], [lBuffer], fRead
- or ax, ax
- jz skip8
- jmp NoFile
-
- ; Search back for EOF marker and adjust if necessary
-
- skip8: mov di, [fRead] ; Load file length
- dec di ; and adjust
- mov es, [sBuffer] ; Save ES and load buffer segment
- std ; Look backward for 255 characters
- mov cx, 0FFh
- cmp cx, di
- jb skip9
- mov cx, di
- skip9: mov al, 1Ah ; Search for EOF marker
- repe scasb
- cld
- jcxz skip10 ; If none, we're OK
- inc di ; else adjust and save file size
- mov [lBuffer], di
-
- ; Show a screen of text and allow commands
-
- skip10: call Show
-
-
- skip11: @DosClose [fHandle] ; Close file
-
- @DosFreeSeg [sBuffer] ; Free memofy
-
- @DosFindNext [dHandle], dResult, dlResult, dCount ; Get next file
-
- cmp [dCount], 0 ; Quit if no next file
- jz exit
- jmp FileLoop
-
- exit: jmp Quit
- start ENDP
-
- Show PROC
-
- ; Display first page
-
- @Pushc 0 ; Start at 0
- call Pager
-
- ; Handle keys
-
- nextkey: @KbdCharIn kChar, kWait, 0 ; Get a key and load to register
- mov al, kChar.kbci_chChar
- or al, al ; Is ascii code null?
- jz skip1 ; Yes? Load scan
- cmp al, 0E0h ; Extended key on extended keyboard?
- jne skip2 ; No? Got code
- skip1: mov al, kChar.kbci_chScan
- skip2:
- cmp al, 27 ; Is it ESCAPE?
- je Exit ; Yes? Get out for next file
-
- push ds ; ES = DS
- pop es
- mov di, OFFSET kTable ; Load address and length of key list
- mov cx, lkTable + 1
- repne scasb ; Find position and point to key
- sub di, (OFFSET kTable) + 1
- shl di, 1 ; Adjust pointer for word addresses
- call procTable[di] ; Call procedure
- jmp nextkey
-
- exit: ret
- Show ENDP
-
- homek: mov oBuffer, 0 ; HOME - set position to 0
- push oBuffer
- mov curLine, 1
- call Pager
- retn
-
- upk: @Pushc -1 ; UP - scroll back 1 line
- call Pager
- retn
-
- pgupk: mov ax, nLines ; PGUP - Page back
- neg ax
- push ax
- call Pager
- retn
-
- endk: mov ax, lBuffer ; END - Get last byte of file
- mov oBuffer, ax ; Make it the file position
- mov curLine, -1 ; Set illegal line number as flag
- mov ax, nLines ; Page back
- neg ax
- push ax
- call Pager
- retn
-
- downk: @Pushc 1 ; DOWN - scroll forward 1 line
- call Pager
- retn
-
- pgdnk: push nLines ; PGDN - page forward
- call Pager
- retn
-
- nonek: retn ; Ignore unknown key
-
- GetVid PROC
-
- mov vMode.viomi_cb, lvMode
- @VioGetMode vMode, 0 ; Get video mode
-
- sub ax, ax ; Clear AH
- mov al, vMode.viomi_fbType ; Put type in register
- mov vType, ax ; and save
- test al, 1 ; Test for color
- jz skip1 ; No? Mono
- test al, 100b ; Test for color burst on
- jz skip2 ; Yes? Color
- skip1: mov stAtrib, stBW ; Set B&W defaults for status line
- mov scAtrib, scBW ; and screen background
-
- skip2: @VioGetCurType cMode, 0 ; Get cursor mode
- mov ax, cMode.vioci_attr ; Save attribute
- xchg cAtrib, ax
- mov cMode.vioci_attr, ax ; Set hidden cursor attribute
- mov ax, vMode.viomi_row; Get number of rows and adjust
- dec ax
- mov nLines, ax
-
- @VioSetCurType cMode, 0 ; Hide cursor
-
- ret
- GetVid ENDP
-
- GetNamPos PROC USES di si, argline:FAR PTR BYTE
-
- les di, argline ; Load address of file name
- mov si, di ; Save copy
-
- sub cx, cx ; Ignore count
- sub dx, dx ; Use DX as found flag
- dec di ; Adjust
- mov ax, "\" ; Search for backslash
- loop1: scasb ; Get next character
- jz skip1 ; If backslash, set flag and save
- cmp BYTE PTR es:[di], 0; If end of name, done
- je skip2
- loop loop1 ; If neither, continue
- skip1: mov si, di ; Save position
- inc dx ; Set flag to true
- loop loop1
-
- skip2: or dx, dx ; Found backslash?
- je skip3 ; If none, search for colon
- mov ax, si ; else return position in DX:AX
- jmp SHORT exit
-
- skip3: neg cx ; Adjust count
- mov di, si ; Restore start of name
- mov ax, ":" ; Search for colon
- repne scasb
- jnz skip4 ; If no colon, restore original
- mov ax, di ; else return position in DX:AX
- jmp SHORT exit
-
- skip4: mov ax, si ; Return original address
-
- exit: mov dx, es
- ret
- GetNamPos ENDP
-
- Quit PROC
-
- mov scAtrib, 7 ; Restore cell attribute for clear scree
-
- cmp cStatus, 1 ; Check cursor status
- jg skip1 ; 2 - Make cursor visible on last line
- je skip1 ; 1 - Make cursor visible
- jmp SHORT skip3 ; 0 - Leave cursor as is
-
- skip1: @VioSetCurPos [nLines], 0, 0 ; Restore cursor on last line
- @VioScrollDn [nLines], 0, [nLines], 79, 1, Cell, 0
-
-
- skip2: mov ax, cAtrib ; Restore cursor attribute
- mov cMode.vioci_attr, ax
- @VioSetCurType cMode, 0
-
- skip3: @DosExit 1, 0 ; Quit
-
- Quit ENDP
-
- END start
-
-
- SHOWR.ASM
- CD-ROM Disc Path: \SAMPCODE\MASM\MASM5\SHOWR.ASM
-
- PAGE 60,132
- TITLE SHOW
-
- ; Program SHOW.ASM
- ; Purpose Text file displayer
- ; Input File name from command line or prompt
- ; Output Display file to screen
-
- DOSSEG
- .MODEL small
-
- INCLUDE dos.inc
- INCLUDE bios.inc
-
- .STACK 100h
-
- .DATA
-
- ; Status line
-
- PUBLIC statline,linenum
- statline DB " Line: "
- statfile DB " File: "
- stathelp DB " Quit: ESC Move: PGUP PGDN HOME END "
- linenum DW 1
-
- ; Variables for screen handling
-
- PUBLIC cell,rows,columns,vidadr,statatr,scrnatr,cga
- cell LABEL WORD ; Cell (character and attrib
- char DB " " ; Initialize to space
- attr DB ? ; Attribute
-
- columns EQU 80 ; Number of columns
- rows DW 24 ; Number of rows - status line ta
- mode DB ? ; Initial mode
- pag DB ? ; Initial display page
- newvid DB 0 ; Video change flag
- cga DB 1 ; CGA flag - default yes
-
- vidadr DW 0B800h ; Video buffer address - def
- mono EQU 0B000h ; Monochrome address
- statatr DB 030h ; Color default
- bwstat EQU 070h ; B&W default - black
- scrnatr DB 017h ; Color default
- bwscrn EQU 007h ; B&W default - white
-
- ; Variables for buffer and file handling
-
- PUBLIC buffer,pbuffer,sbuffer,fsize,namebuf
- buffer LABEL DWORD
- pbuffer DW 0 ; Position in buffer (offset)
- sbuffer DW ? ; Base of buffer (segment)
- lbuffer DW ? ; Length of buffer
- fhandle DW ? ; Holds file handle on o
- fsize DW ? ; File size after dosopen
-
- prompt DB 13,10,13,10,"Enter filename: $"
- prompt2 DB 13,10,"File problem. Try again? $"
- namebuf DB 66,?
- filename DB 66 DUP (0) ; Buffer for file name
-
- err1 DB 13,10,"Must have DOS 2.0 or higher",13,10,"$"
- err2 DB 13,10,"File too big",13,10,"$"
-
- ; Call table
-
- exkeys DB 71,72,73,79,80,81 ; Extended key codes
- lexkeys EQU $-exkeys ; Table of keys
- extable DW homek
- DW upk
- DW pgupk
- DW endk
- DW downk
- DW pgdnk
- DW nonek
-
- .CODE
- EXTRN pager:PROC,isEGA:PROC ; Routines in other mod
- start: mov ax,@DATA ; Initialize data segmen
- mov ds,ax
-
- cli ; Turn off interrupts
- mov ss,ax ; Make SS and
- mov sp,OFFSET STACK ; SP relative to DGROU
- sti
-
- ; Adjust memory allocation
-
- mov bx,sp ; Convert stack po
- mov cl,4 ; to get stack size
- shr bx,cl
- add ax,bx ; Add SS to get en
- mov bx,es ; Get start of program
- sub ax,bx ; Subtract start from end
- @ModBlok ax ; Release memory after program
-
- ; Allocate dynamic memory for file buffer
-
- @GetBlok 0FFFh ; Try to allocate 64K
- mov sbuffer,ax ; Save buffer segment
- mov lbuffer,bx ; Save actual length allocat
-
- ; Check DOS
-
- @GetVer ; Get DOS version
- cmp al,2 ; Requires DOS 2.0
- jge video
- @DispStr err1 ; else error and quit
- int 20h
-
- ; Adjust for current mode and and video adapter
-
- video: call isEGA ; EGA (or VGA)?
- or ax,ax ; If 0 must be CGA or MA
- je modechk ; Leave default
- mov rows,ax ; Load rows
- dec cga ; Not CGA
-
- modechk: @GetMode ; Get video mode
- mov mode,al ; Save initial mode and
- mov pag,bh
- mov dl,al ; Work on copy
- cmp dl,7 ; Is it mono 7?
- je loadmono ; Yes? Set mono
- cmp dl,15 ; Is it mono 15?
- jne graphchk ; No? Check graphics
- loadmono: mov vidadr,mono ; Load mono address
- mov statatr,bwstat ; Set B&W defaults for status li
- mov scrnatr,bwscrn ; and screen background
- dec cga ; Not CGA
- cmp al,15 ; Is it mono 15?
- jne cmdchk ; No? Done
- mov dl,7 ; Yes? Set standard mono
- jmp SHORT chmode
-
- graphchk: cmp dl,7 ; 7 or higher?
- jg color ; 8 to 14 are color (7 and
- cmp dl,4 ; 4 or higher?
- jg bnw ; 5 and 6 are probabl
- je color ; 4 is color
- test dl,1 ; Even?
- jz bnw ; 0 and 2 are black a
- color: ; 1 and 3 are color
- cmp dl,3 ; 3?
- je cmdchk ; Yes? Done
- mov dl,3 ; Change mode to 3
- jmp SHORT chmode
-
- bnw: mov statatr,bwstat ; Set B&W defaults for statu
- mov scrnatr,bwscrn ; and screen background
- cmp dl,2 ; 2?
- je cmdchk ; Yes? Done
- mov dl,2 ; Make it 2
-
- chmode: @SetMode dl ; Set video mode
- @SetPage 0 ; Set video page
- mov newvid,1 ; Set flag
-
- ; Try to open command line file
-
- cmdchk: mov bl,es:[80h] ; Get length
- sub bh,bh
- mov WORD PTR es:[bx+81h],0; Convert to ASCIIZ
- push ds
- @OpenFil 82h,0,es ; Open argument
- pop ds
- jc getname ; If error, get from prom
- mov fhandle,ax ; else save handle
- push ds
- @GetFirst 82h,,es ; Let DOS convert to file name
- pop ds
- jnc opened ; If OK file is op
-
- ; Prompt for file
-
- getname: @DispStr prompt ; Prompt for file
- @GetStr namebuf,0 ; Get response as ASCIIZ
- @OpenFil filename,0 ; Try to open response
- jc badfile ; If successful, continue
- mov fhandle,ax ; Save handle
- @GetFirst filename ; Let DOS convert to file name
- jnc opened ; If OK, file is opened
-
- badfile: @DispStr prompt2 ; else prompt to try agai
- @GetKey 0,1,0
- and al,11011111b ; Convert key to uppercase
- cmp al,"Y" ; If yes,
- je getname ; try again
- jmp quit ; else quit
-
- ; Copy file name to status line
-
- opened: mov si,9Eh ; Load FCB as as source
- mov di,OFFSET statfile[7] ; Load status line as des
- mov al,es:[si] ; Load first byte
- inc si
- copy: mov [di],al ; Save and load byt
- inc di
- mov al,es:[si]
- inc si
- or al,al ; Check for 0
- loopne copy
-
- ; Check file size
-
- @GetFilSz fhandle ; Get file size
-
- or dx,dx ; Larger than 64K?
- jne big ; Yes? Too big
- mov fsize,ax ; Save file size
- mov cx,4 ; Convert to paragraphs
- shr ax,cl
- cmp ax,lbuffer ; Is it larger than b
- jle fileread ; No? Continue
-
- big: @DispStr err2 ; else error
- @Exit 2
-
- fileread: push ds
- @Read buffer,fsize,fhandle ; Read file
- pop ds
- jnc readok ; If no read error contin
- jmp getname ; else try again
-
- ; Search back for EOF marker and adjust if necessary
-
- readok: mov di,ax ; Load file length
- push es ; Save ES and load buffer s
- mov es,sbuffer
- std ; Look backward for 255
- mov cx,0FFh
- mov al,1Ah ; Search for EOF marker
- repne scasb
- cld
- jcxz noeof ; If none, we're OK
- inc di ; else adjust and s
- mov fsize,di
-
- noeof: pop es
- @SetCurPos 0,43 ; Turn off cursor by moving off
-
- ; Display first page
-
- xor ax,ax ; Start at 0
- push ax
- firstpg: call pager
-
- ; Handle keys
-
- nextkey: @GetKey 0,0,0 ; Get a key
- nextkey2: cmp al,0 ; Is it a null?
- je extended ; Yes? Must be extended
-
- cmp al,27 ; Is it ESCAPE?
- jne nextkey ; No? Ignore unknown command
-
- quit: @ClosFil fhandle ; Yes? Close file
- @FreeBlok sbuffer ; Release buffer
- cmp newvid,1 ; Restore video?
- jne thatsall ; No?
- @SetMode mode ; Restore video mode, p
- @SetPage pag
- thatsall: mov dx,rows ; Load last row and firs
- xchg dl,dh
- mov cx,dx ; Make row the same
- mov dl,79
- @Scroll 0 ; Clear last line
- sub dl,dl
- @SetCurPos ; Set cursor
-
- @Exit 0 ; Quit
-
- extended: @GetKey 0,0,0 ; Get extended code
- push es
- push ds ; Load DS into ES
- pop es
- mov di,OFFSET exkeys ; Load address and length of k
- mov cx,lexkeys+1
- repne scasb ; Find position
- pop es
- sub di,(OFFSET exkeys)+1 ; Point to key
- shl di,1 ; Adjust pointer for word
- call extable[di] ; Call procedure
- jmp nextkey
-
- homek: mov pbuffer,0 ; HOME - set position t
- push pbuffer
- mov linenum,1
- call pager
- retn
-
- upk: mov ax,-1 ; UP - scroll back 1
- push ax
- call pager
- retn
-
- pgupk: mov ax,rows ; PGUP - Page back
- neg ax
- push ax
- call pager
- retn
-
- endk: mov ax,fsize ; END - Get last b
- mov pbuffer,ax ; Make it the file position
- mov linenum,-1 ; Set illegal line number as
- mov ax,rows ; Page back
- neg ax
- push ax
- call pager
- retn
-
- downk: mov ax,1 ; DOWN - scroll
- push ax
- call pager
- retn
-
- pgdnk: push rows ; PGDN - page forwa
- call pager
- retn
-
- nonek: retn ; Ignore unknown key
-
- END start
-
-
-