home *** CD-ROM | disk | FTP | other *** search
- page 78,132
- title Commands for Monitor
-
- .model small
- .code
- .data
- InitSeg segment byte public
- InitSeg ends
-
- DGroup group _TEXT,_DATA,InitSeg
-
- .data
-
- extrn DsSave:word, CsSave:word, IpSave:word
-
- DEFLEN dw ? ;Default length of range
- DEFDUMP dd ? ;Default dump address
- ListBuf db 80 dup(?)
-
- .code
- assume cs:DGroup,ds:DGroup,es:DGroup,ss:DGroup
-
- public Compare,Dump,Enter,Fill,Input,Move,Output,Search
- public Default,OutSi
-
- extrn OutCh:near, CrLf:near, Command:near
- extrn InCh:near, Backup:near, Out16:near, Blank:near
- extrn ScanB:near, ScanP:near, Hex:near, Error:near
- extrn HexIn:near, HexChk:near, Tab:near, Address:near, GetHex:near
- extrn GetEol:near
-
- ;Print the hex address of SI and DS
-
- OUTSI:
- MOV DX,DS ;Put DS where we can work with it
- CALL OUT16 ;Display segment
- MOV DX,SI
- jmp short OUTADD ;Finish below
-
- ;Print digit hex address of DI and ES
- ;Same as OUTSI above
-
- OUTDI:
- MOV DX,ES
- CALL OUT16
- MOV DX,DI
- ;Finish OUTSI here too
- OUTADD:
- MOV AL,":"
- CALL OutCh
- jmp Out16
-
-
- ;RANGE - Looks for parameters defining an address range.
- ;The first parameter is a hex number of 5 or less digits
- ;which specifies the starting address. The second parameter
- ;may specify the ending address, or it may be preceded by
- ;"L" and specify a length (4 digits max), or it may be
- ;omitted and a length of 128 bytes is assumed. Returns with
- ;segment in AX, displacement in DX, length in CX.
-
- DSRANGE:
- MOV BP,[DSSave] ;Default segment is DS
- MOV [DEFLEN],128 ;and default length to 128 bytes
- RANGE:
- CALL ADDRESS
- PUSH AX ;Save segment
- PUSH DX ;Save offset
- CALL SCANP ;Get to next parameter
- CMP AL,"L" ;Length indicator?
- JE GETLEN
- MOV DX,[DEFLEN] ;Default length
- CALL HEXIN ;Second parameter present?
- JC RNGRET ;If not, use default
- MOV CX,4 ;4 hex digits
- CALL GETHEX ;Get ending address (same segment)
- MOV CX,DX ;Low 16 bits of ending addr.
- POP DX ;Low 16 bits of starting addr.
- SUB CX,DX ;Compute range
- INC CX ;Include last location
- POP AX ;Segment of starting address
- RET
-
- GETLEN:
- INC SI ;Skip over "L" to length
- MOV CX,4 ;Length may have 4 digits
- CALL GETHEX ;Get the range
- RNGRET:
- MOV CX,DX ;Length
- POP DX ;Offset of starting addr.
-
- POP AX ;Segment of starting addr.
- RET
-
- DEFAULT:
- ;DI points to default address and CX has default length
- CALL SCANP
- JZ USEDEF ;Use default if no parameters
- CMP AL,"L"
- JZ NEWLEN
- MOV [DEFLEN],CX
- CALL RANGE
- JMP GETEOL
-
- NEWLEN:
- INC SI
- MOV CX,4
- CALL GETHEX
- MOV CX,DX ;Get new length
- USEDEF:
- MOV SI,DI
- LODSW ;Get default displacement
- MOV DX,AX
- LODSW ;Get default segment
- Ret1: RET
-
-
- ;************************************************************
- ; "C" command
- ;Compare one area of memory to another.
-
- COMPARE:
- CALL DSRANGE ;Get range of first area
- PUSH CX ;Save length
- PUSH AX ;Save segment
- PUSH DX ;Save offset
- CALL ADDRESS ;Get second area
- CALL GETEOL ;Check for errors
- POP SI
- MOV DI,DX
- MOV ES,AX
- POP DS
- POP CX ; Length
- DEC CX
- CALL COMP ; Do one less than total
- INC CX ; CX=1 (do last one)
- COMP:
- REPE CMPSB
- JZ RET1
- ; Compare error. Print address, value; value, address.
- DEC SI
- CALL OUTSI
- CALL BLANK
- CALL BLANK
- LODSB
- CALL HEX
- CALL BLANK
- CALL BLANK
- DEC DI
- MOV AL,ES:[DI]
- CALL HEX
- CALL BLANK
- CALL BLANK
- CALL OUTDI
- INC DI
- CALL CRLF
- XOR AL,AL
- jmp COMP
-
-
- ;************************************************************
- ; "D" command
- ; Dump an area of memory in both hex and ASCII
-
- DUMP:
- MOV BP,[DSSave] ;Default segment is DS
- MOV CX,128
- MOV DI,offset DGroup:DEFDUMP
- CALL DEFAULT ;Get range to dump
- MOV DS,AX ;Set segment
- MOV SI,DX ;SI has displacement in segment
- ROW:
- CALL OUTSI ;Print address at start of line
- PUSH SI ;Save address for ASCII dump
- CALL BLANK
- EachByte:
- CALL BLANK ;Space between bytes
- BYTE1:
- LODSB ;Get byte to dump
- CALL HEX ;and display it
- POP DX ;DX has start addr. for ASCII dump
- DEC CX ;Drop loop count
- JZ ASCII ;If through do ASCII dump
- MOV AX,SI
- TEST AL,0FH ;On 16-byte boundary?
- JZ ENDROW
- PUSH DX ;Didn't need ASCII addr. yet
- TEST AL,7 ;On 8-byte boundary?
- JNZ EachByte
- MOV AL,"-" ;Mark every 8 bytes
- CALL OutCh
- jmp BYTE1
- ENDROW:
- CALL ASCII ;Show it in ASCII
- jmp ROW ;Loop until count is zero
- ASCII:
- PUSH CX ;Save byte count
- MOV AX,SI ;Current dump address
- MOV SI,DX ;ASCII dump address
- SUB AX,DX ;AX=length of ASCII dump
- ;Compute tab length. ASCII dump always appears on right side
- ;screen regardless of how many bytes were dumped. Figure 3
- ;characters for each byte dumped and subtract from 51, which
- ;allows a minimum of 3 blanks after the last byte dumped.
- MOV BX,AX
- SHL AX,1 ;Length times 2
- ADD AX,BX ;Length times 3
- MOV CX,51
- SUB CX,AX ;Amount to tab in CX
- CALL TAB
- MOV CX,BX ;ASCII dump length back in CX
- ASCDMP:
- LODSB ;Get ASCII byte to dump
- AND AL,7FH ;ASCII uses 7 bits
- CMP AL,7FH ;Don't try to print RUBOUT
- JZ NOPRT
- CMP AL," " ;Check for control characters
- JNC PRIN
- NOPRT:
- MOV AL,"." ;If unprintable character
- PRIN:
- CALL OutCh ;Print ASCII character
- LOOP ASCDMP ;CX times
- POP CX ;Restore overall dump length
- MOV word ptr ES:[DEFDUMP],SI
- MOV word ptr ES:[DEFDUMP+2],DS ;Remember last addrss as default
- JMP CRLF ;Print CR/LF and return
-
-
- ;************************************************************
- ; "M" command
- ;Block move one area of memory to another. Overlapping moves
- ;are performed correctly, i.e., so that a source byte is not
- ;overwritten until after it has been moved.
-
- MOVE:
- CALL DSRANGE ;Get range of source area
- PUSH CX ;Save length
- PUSH AX ;Save segment
- PUSH DX ;Save offset
- CALL ADDRESS ;Get destination address
- CALL GETEOL ;Check for errors
- POP SI
- MOV DI,DX ;Set dest. displacement
- POP BX ;Source segment
- MOV DS,BX
- MOV ES,AX ;Destination segment
- POP CX ;Length
- CMP DI,SI ;Check direction of move
- SBB AX,BX ;Extend the CMP to 32 bits
- JB COPYLIST ;Move forward into lower mem.
- ;Otherwise, move backward. Figure end of source and destination
- ;areas and flip direction flag.
- DEC CX
- ADD SI,CX ;End of source area
- ADD DI,CX ;End of destination area
- std ;Reverse direction
- INC CX
- COPYLIST:
- MOVSB ;Do at least 1 - Range is 1-10000H not 0-FFFFH
- DEC CX
- REP MOVSB ;Block move
- JMP COMMAND ;Jump in case stack got trashed by move
-
-
- ;************************************************************
- ; "F" command
- ;Fill an area of memory with a list values. If the list
- ;is bigger than the area, don't use the whole list. If the
- ;list is smaller, repeat it as many times as necessary.
-
- FILL:
- CALL DSRANGE ;Get range to fill
- PUSH CX ;Save length
- PUSH AX ;Save segment number
- PUSH DX ;Save displacement
- CALL LIST ;Get list of values to fill with
- POP DI ;Displacement in segment
- POP ES ;Segment
- POP CX ;Length
- CMP BX,CX ;BX is length of fill list
- MOV SI,offset DGroup:ListBuf ;List is in line buffer
- JCXZ BIGRNG
- JAE COPYLIST ;If list is big, copy part of it
- BIGRNG:
- SUB CX,BX ;How much bigger is area than list?
- XCHG CX,BX ;CX=length of list
- PUSH DI ;Save starting addr. of area
- REP MOVSB ;Move list into area
- POP SI
- ;The list has been copied into the beginning of the
- ;specified area of memory. SI is the first address
- ;of that area, DI is the end of the copy of the list
- ;plus one, which is where the list will begin to repeat.
- ;All we need to do now is copy [SI] to [DI] until the
- ;end of the memory area is reached. This will cause the
- ;list to repeat as many times as necessary.
- MOV CX,BX ;Length of area minus list
- PUSH ES ;Different index register
- POP DS ;requires different segment reg.
- jmp COPYLIST ;Do the block move
-
-
- ;************************************************************
- ; "S" command
- ;Search a specified area of memory for given list of bytes.
- ;Print address of first byte of each match.
-
- SEARCH:
- CALL DSRANGE ;Get area to be searched
- PUSH CX ;Save count
- PUSH AX ;Save segment number
- PUSH DX ;Save displacement
- CALL LIST ;Get search list
- DEC BX ;No. of bytes in list-1
- POP DI ;Displacement within segment
- POP ES ;Segment
- POP CX ;Length to be searched
- SUB CX,BX ; minus length of list
- SCAN:
- MOV SI,offset DGroup:ListBuf ;List kept in line buffer
- LODSB ;Bring first byte into AL
- DOSCAN:
- SCASB ;Search for first byte
- LOOPNE DOSCAN ;Do at least once by using LOOP
- JNZ RET2 ;Exit if not found
- PUSH BX ;Length of list minus 1
- XCHG BX,CX
- PUSH DI ;Will resume search here
- REPE CMPSB ;Compare rest of string
- MOV CX,BX ;Area length back in CX
- POP DI ;Next search location
- POP BX ;Restore list length
- JNZ TestEndScan ;Continue search if no match
- DEC DI ;Match address
- CALL OUTDI ;Print it
- INC DI ;Restore search address
- CALL CRLF
- TestEndScan:
- JCXZ RET2
- jmp SCAN ;Look for next occurrence
-
-
- ;Process one parameter when a list of bytes is
- ;required. Carry set if parameter bad. Called by LIST
-
- LISTITEM:
- CALL SCANP ;Scan to parameter
- CALL HEXIN ;Is it in hex?
- JC STRINGCHK ;If not, could be a string
- MOV CX,2 ;Only 2 hex digits for bytes
- CALL GETHEX ;Get the byte value
- MOV [BX],DL ;Add to list
- INC BX
- GRET: CLC ;Parameter was OK
- Ret2: RET
-
- STRINGCHK:
- MOV AL,[SI] ;Get first character of param
- CMP AL,"'" ;String?
- JZ STRING
- CMP AL,'"' ;Either quote is all right
- JZ STRING
- STC ;Not string, not hex - bad
- RET
-
- STRING:
- MOV AH,AL ;Save for closing quote
- INC SI
- STRNGLP:
- LODSB ;Next char of string
- CMP AL,13 ;Check for end of line
- JZ ErrorJ ;Must find a close quote
- CMP AL,AH ;Check for close quote
- JNZ STOSTRG ;Add new character to list
- CMP AH,[SI] ;Two quotes in a row?
- JNZ GRET ;If not, we're done
- INC SI ;Yes - skip second one
- STOSTRG:
- MOV [BX],AL ;Put new char in list
- INC BX
- jmp STRNGLP ;Get more characters
-
- ErrorJ: jmp Error
-
- ;Get a byte list for ENTER, FILL or SEARCH. Accepts any number
- ;of 2-digit hex values or character strings in either single
- ;(') or double (") quotes.
-
- LIST:
- MOV BX,offset DGroup:ListBuf ;Put byte list in the line buffer
- LISTLP:
- CALL LISTITEM ;Process a parameter
- JNC LISTLP ;If OK, try for more
- SUB BX,offset DGroup:ListBuf ;BX now has no. of bytes in list
- JZ ErrorJ ;List must not be empty
- jmp GetEol
-
-
- ;************************************************************
- ; "E" command
-
- ;Short form of ENTER command. A list of values from the
- ;command line are put into memory without using normal
- ;ENTER mode.
-
- GETLIST:
- CALL LIST ;Get the bytes to enter
- POP DI ;Displacement within segment
- POP ES ;Segment to enter into
- MOV SI,offset DGroup:ListBuf ;List of bytes is in line buffer
- MOV CX,BX ;Count of bytes
- REP MOVSB ;Enter that byte list
- RET
-
- ;Enter values into memory at a specified address. If the
- ;line contains nothing but the address we go into "enter
- ;mode", where the address and its current value are printed
- ;and the user may change it if desired. To change, type in
- ;new value in hex. Backspace works to correct errors. If
- ;an illegal hex digit or too many digits are typed, the
- ;bell is sounded but it is otherwise ignored. To go to the
- ;next byte (with or without change), hit space bar. To
- ;back up to a previous address, type "-". On
- ;every 8-byte boundary a new line is started and the address
- ;is printed. To terminate command, type carriage return.
- ; Alternatively, the list of bytes to be entered may be
- ;included on the original command line immediately following
- ;the address. This is in regular LIST format so any number
- ;of hex values or strings in quotes may be entered.
-
- ENTER:
- MOV BP,[DSSave] ;Default segment
- CALL ADDRESS ;Get ENTER address
- PUSH AX ;Save for later
- PUSH DX
- CALL SCANB ;Any more parameters?
- JNZ GETLIST ;If not end-of-line get list
- POP DI ;Displacement of ENTER
- POP ES ;Segment
- GETROW:
- CALL OUTDI ;Print address of entry
- CALL BLANK ;Leave a space
- CALL BLANK
- GETBYTE:
- MOV AL,ES:[DI] ;Get current value
- CALL HEX ;And display it
- MOV AL,"."
- CALL OutCh ;Prompt for new value
- MOV CX,2 ;Max of 2 digits in new value
- MOV DX,0 ;Intial new value
- GETDIG:
- CALL InCh ;Get digit from user
- MOV AH,AL ;Save
- CALL HEXCHK ;Hex digit?
- XCHG AH,AL ;Need original for echo
- JC NOHEX ;If not, try special command
- CALL OutCh ;Echo to console
- MOV DH,DL ;Rotate new value
- MOV DL,AH ;And include new digit
- LOOP GETDIG ;At most 2 digits
- ;We have two digits, so all we will accept now is a command.
- WaitCh:
- CALL InCh ;Get command character
- NOHEX:
- CMP AL,8 ;Backspace
- JZ BS
- CMP AL,7FH ;RUBOUT
- JZ BS
- CMP AL,"-" ;Back up to previous address
- JZ PREV
- CMP AL,13 ;All done with command?
- JZ EOL
- CMP AL," " ;Go to next address
- JZ NEXT
- ;If we got here, character was invalid. Sound bell.
- MOV AL,7
- CALL OutCh
- JCXZ WaitCh ;CX=0 means no more digits
- jmp GETDIG ;Don't have 2 digits yet
-
- BS:
- CMP CL,2 ;CX=2 means nothing typed yet
- JZ GETDIG ;Can't back up over nothing
- INC CL ;Accept one more character
- MOV DL,DH ;Rotate out last digit
- MOV DH,CH ;Zero this digit
- CALL BACKUP ;Physical backspace
- jmp GETDIG ;Get more digits
-
- ;If new value has been entered, convert it to binary and
- ;put into memory. Always bump pointer to next location
-
- STORE:
- CMP CL,2 ;CX=2 means nothing typed yet
- JZ NOSTO ;So no new value to store
- ;Rotate DH left 4 bits to combine with DL and make a byte value
- PUSH CX
- MOV CL,4
- SHL DH,CL
- POP CX
- OR DL,DH ;Hex is now converted to binary
- MOV ES:[DI],DL ;Store new value
- NOSTO:
- INC DI ;Prepare for next location
- RET
-
- EOL:
- CALL STORE ;Enter the new value
- JMP CRLF ;CR/LF and terminate
-
- NEXT:
- CALL STORE ;Enter new value
- INC CX ;Leave a space plus two for
- INC CX ; each digit not entered
- CALL TAB
- MOV AX,DI ;Next memory address
- AND AL,7 ;Check for 8-byte boundary
- JNZ GETBYTE ;Take 8 per line
- NEWROW:
- CALL CRLF ;Terminate line
- JMP GETROW ;Print address on new line
-
- PREV:
- CALL STORE ;Enter the new value
- ;DI has been bumped to next byte. Drop it 2 to go to previous addr
- DEC DI
- DEC DI
- jmp NEWROW ;Terminate line after backing up
-
-
- ;************************************************************
- ; "I" command
- ;Input from the specified port and display result
-
- INPUT:
- MOV CX,4 ;Port may have 4 digits
- CALL GETHEX ;Get port number in DX
- in al,dx ;Variable port input
- CALL HEX ;And display
- JMP CRLF
-
-
- ;************************************************************
- ; "O" command
- ;Output a value to specified port.
-
- OUTPUT:
- MOV CX,4 ;Port may have 4 digits
- CALL GETHEX ;Get port number
- PUSH DX ;Save while we get data
- MOV CX,2 ;Byte output only
- CALL GETHEX ;Get data to output
- XCHG AX,DX ;Output data in AL
- POP DX ;Port in DX
- out dx,al ;Variable port output
- RET
-
- ;************************************************************
-
- InitSeg segment
- assume cs:DGroup,ds:Dgroup
-
- mov ax,[DsSave]
- mov word ptr [DefDump+2],ax
- mov word ptr [DefDump],100H
- InitSeg ends
-
- end
-