home *** CD-ROM | disk | FTP | other *** search
- ;
- ; GRDB
- ;
- ; Copyright(c) LADsoft
- ;
- ; David Lindauer, camille@bluegrass.net
- ;
- ;
- ; Input.asm
- ;
- ; Function: Handle input
- ;
- ; Handles numbers
- ; Handles segments
- ; Handles trapping page faults
- ; Handles command input
- ;
- ;MASM MODE
- .model small
- .386
-
- include edispatc.inc
- include eprints.inc
- include emtrap.inc
- include eregs.inc
- include edump.inc
- include eentry.inc
- include eexec.inc
- include ebreaks.inc
- include edis.inc
- include einout.inc
- include eoptions.inc
- include ehistory.inc
-
- extrn _exit : PROC,domath : PROC, drive : PROC, fill : PROC
- extrn logging : PROC, help : PROC, pci : PROC
- extrn DoFileRead : PROC, DoFileWrite : PROC, search : PROC
- extrn fpcommand : PROC, move : proc, compare : proc, asm : PROC
-
- PUBLIC qerr, ReadNumber, ReadAddress, Inputhandler
- PUBLIC wadeSpace, GetInputLine, WadeSpaceOnly, inputbuffer
- PUBLIC defDS,defCS
-
- IBSIZE = 80 ;max size of iinput buffer for a line=width of screen
-
- .data
-
- inputbuffer db IBSIZE DUP (?) ;Allocate Input buffer
- Commands db "abcdefghilmnopqrstuwxy@?" ; List of commands
- comlen = $ - Commands ; Length of list
- inquote db 0
-
- .code
- ;
- ; load defaults if dx is zero
- ; INPUT: EDX contains segment to use if not 0, OR if big real with offset 0
- ; OUTPUT: DX contains segment to use, could be default DX from bucket
- ;
- defDS PROC
- or edx,edx ;if edx has a value
- jnz ddsx ;then use it
- sub dx,dx ; waste one instruction
- test [optflat0],1 ;see if default seg is 0
- jnz ddsx ;if so, use EDX=0
- mov dx,[RegdumpDS] ;else use default DS
- ddsx:
- ret
- defDS ENDP
- ;
- ; for now we just default CS to the active CS, since it is only
- ; used on U and A commands and since we can't do linear addressing
- ; with those anyway right now. ???is this true???
- ; If EDX <> 0, we are starting from a specified segment location,
- ; so use that instead of CS. (EDX contains the segment).
- ;
- defCS PROC
- or edx,edx
- jnz dcsx
- mov dx,[RegdumpCS]
- dcsx:
- ret
- defCS ENDP
- ;
- ; Print an error if command wrong
- ; Apparently, SI points to some location in the input buffer. We
- ; need to determine how many spaces to print before we found the actual
- ; error to point to from the line below. I guess if the error is in the
- ; first or second positions, we print the character right at the start of
- ; the line, else we space over to where the error is found.
- ;
- qerr PROC
- call crlf ;new line for this
- sub si,offset inputbuffer-2 ; Calculate error pos
- mov cx,si ;
- jcxz short qestart ;
- dec cx ;
- jcxz short qestart ;
- qelp:
- call printspace ; Space over to error pos
- loop qelp
- qestart:
- mov dl,'^' ; Display error
- call PutChar
- stc ; Did an error
- ret
- qerr ENDP
- ;
- ; Read in a number.
- ; In at least some cases, we have ALREADY called ReadReg to find a register,
- ;and failed so we are looking for a number anyway.
- ; SI points to the input line from the user.
- ; OUTPUT: CY if we found 0 digits and did NOT find a register by name
- ; EAX contains number found if NC
- ;
- ReadNumber PROC
- push ebx
- push cx
- push dx
- call ReadReg ;find a non-number (mnemonic)
- clc ;ignore which type or reg found
- jz gotnum ;if 0, we have value of this reg
-
- ;We reach here if we found no mnemonic in our lookup table
-
- sub ebx,ebx ; Number = 0
- sub cx,cx ; digits = 0
- mov al,[si] ;get next user character
- cmp al,"'" ;if single or double quotes
- jz getstring ;get a string input
- cmp al,'"'
- jz getstring
- cmp al,'-' ;if a hyphen
- pushf ;save result of compare
- jnz rnlp ;not a hyphen, so SI is ok
- inc si ;else skip the hyphen
- rnlp:
- lodsb ; Get char & convert to uppercase
- cmp al,60h
- jc notlower
- and al,NOT 20h
- notlower:
- sub al,'0' ; Convert to binary
- jc short rn_done ; < '0' is an error
- cmp al,10 ; See if is a digit
- jc short gotdigit ; Yes, got it
- sub al,7 ; Convert letters to binary
- cmp al,16 ; Make sure is < 'G'
- jnc short rn_done ; Quit if not
- cmp al,10 ; MAke sure not < 'A'
- jc short rn_done
- gotdigit:
- shl ebx,4 ; It is a hex digit, add in
- or bl,al ; OR in the digit
- inc cx ; Set flag to indicate we got digits
- jmp rnlp ; go get the next digit
-
- ;We have snagged all entered digits here, and in the process SI got bumped
- ;past the non-digit by lodsb, so back up to look at the first non-digit
- ;character. the Zero flag contains the result of our hyphen compare, ZF if
- ;we found a hyphen, NZ if we didn't.
- ; NOTE also that if we found a string, EBX has up to 4 ASCII codes in it,
- ;NOT a value. Don't offhand see any way the caller can know this, though.
-
- rn_done:
- dec si ; Point at first non-digit
- popf ;did we find a hyphen?
- jnz rm_done2 ; check for negation
- neg ebx ;yes, negative, so negate value
- rm_done2:
- mov eax,ebx ;final result into EAX
- test cl,-1 ; See if got any CX=digit count
- jnz gotnum ;if non-0, we got at least one
- stc ; No, error
- gotnum:
- pop dx
- pop cx
- pop ebx
- ret ;return number/string in EAX
-
- ;We found a quote character at [SI], so we move past the quote to try to
- ;snag a quoted string. We keep sticking ASCII codes into EBX, shifting it
- ;left as we go, and losing all but the last 4 ASCII codes.
-
- getstring:
- inc si ;bump past quote character
- getstringl:
- lodsb ;get next char
- cmp al,13 ;if CR, end of input
- jz rm_done2 ;so leave SI alone?
- cmp al,"'" ;find end of quotes already?
- jz rm_done2 ;if so, check if null string
- cmp al,'"'
- jz rm_done2
- inc cl ;else we got a char
- shl ebx,8 ;stick in BL
- mov bl,al
- jmp getstringl ;and get the next one
- ReadNumber ENDP
- ;
- ; Read an address, composed of a number and a possible selector
- ; INPUT: SI points at the input line just following the U (for unassemble).
- ; OUTPUT: EBX contains the address, which came either from a current
- ; register bucket or from a string or number
- ;
- ReadAddress PROC
- sub edx,edx ;EDX used for segment if found
- call ReadReg ;chk for seg or non-seg register
- ; mnemonic (like 'AX')
-
- ;ReadReg returns two flags: if NZ, we found nothing. if ZF, we found either
- ;a segment register or a non-segment register, so we examine the carry flag.
- ;CY means it was a non-segment register, and NC means we found a segment
- ;register.
- ; If we found a register at all, the value returned is what was in the
- ;Regdump bucket for that register, and is returned in EAX unless it was not a
- ;32-bit register, in which case the low word is returned in AX and the high
- ;word of AX is zero. (undefined for segments)
-
- jnc gotseg ;if NC, we snagged a segment reg
- mov ebx,eax ;else, get value into ebx
- jz gotaddr ;ZF if non-segment reg found
-
- ;We fall through here if we failed to find a register. The syntax from the
- ;user permits either REG:number, REG:REG, number:REG, number:number, or just
- ;number. At this point, no register was asked for by name, so we check for a
- ;number.
-
- readseg:
- call ReadNumber ; Read a number or string
- jc short raerr ; Quit if error - no input
- mov ebx,eax ;move number/string to EBX
- call WadeSpace ;find next input
- jz gotaddr ;if no more, we're done
- cmp al,':' ;if not a colon
- jnz gotaddr ;we are also done
- inc si ;else move past colon
-
- ; We fell through above because the user did NOT ask for any
- ;register by name, then fell through to here because we found a colon after
- ;a number or quoted string.
- ;EBX now contains a number of up to the last 8 digits entered, or a string
- ;of up to the last 4 ASCII characters entered. We take the low 4 digits or
- ;two characters and put them in DX, then set bit 16 of EDX
-
- mov dx,bx ;low order num/string to DX
- or edx,10000H ;set bit 16 for segment
- jmp readofs ;and go read an offset
-
- ;EAX contains the value read out of the RegdumpREG bucket, with the high
- ;order word zeroed out.
-
- gotseg:
- sub ebx,ebx ;assume seg only, so offset is 0
- mov dx,ax ;get segment value into DX
- or edx,10000H ;set bit 16 for segment
- call WadeSpace ;look for more input
- jz gotaddr ;if no more, segment given only
- cmp al,':' ;else see if colon for offset
- jnz gotaddr ;if not, that's it
- inc si ;else move past colon
-
- ;We get here if the input contained a colon, indicating that there might
- ;be an offset following. If nothing follows the colon, assume an offset
- ;of 0.
-
- readofs:
- call WadeSpace ;any further input
- jz gotaddr ;ZF means we found a CR
- call ReadNumber ; Read in offset
- jc short raerr ; Quit if error - no number or
- ; quoted string with endquotes
- mov ebx,eax ;else set offset into EBX
- gotaddr:
- clc ; OK, exit
- ret
- raerr:
- stc ; Error on number input
- ret
- ReadAddress ENDP
- ;
- ; Get an input line
- ; OUTPUT: SI points to the line of input.
- ;
- GetInputLine PROC
- mov [inquote],0 ;say input not in quotes
- mov di,offset InputBuffer ;point to input buffer
- mov si,di ;Return buffer pointer
- mov cx,IBSIZE ; Size of buffer=80 bytes
- moreinput:
- call GetKey ;wait, return keystroke
- call CheckHistory ;check for history substitutions
- jc MoreInput ;and go for more input if so
- or al,al ; ignore function keys
- jz moreinput ;
- cmp al,9 ; is tab?
- jz dotab
- cmp al,8 ; Is delete or rubout?
- jz short bkspc ; Yes - go do it
- cmp al,7fh ;not on PC?
- jz short bkspc ; yes - go do it
- cmp al,'"' ;is it double quotes
- jz doquote ;if so, set flag
- cmp al,"'" ;is it single quotes
- jnz dochar ;no, must be valid char
- doquote:
- xor [inquote],1 ;invert quote flag
- dochar:
- push ax ;save keystroke
- test [inquote],1 ;was it quotes
- jnz nolc ;if so, OK
- cmp al,'A' ;see if below A
- jc nolc
- cmp al,'Z' ;or above Z
- ja nolc
- or al,20h ;if A-Z, force lowercase
- nolc:
- stosb
- pop ax
- cmp al,13 ; Is CR
- jz short endinput ; Yes, return
- mov dl,al ; Echo character
- call PutChar
- loop moreinput ; Loop till buffer full
- endinput:
- call EnterHistory
- ret
- bkspc:
- cmp di,offset InputBuffer ; Quit if nothing in buffer
- jz moreinput ; And get more input
- mov dl,8 ; Erase last echoed char
- call PutChar
- mov dl,' ' ;
- call PutChar
- mov dl,8 ; Reset pointer
- call PutChar
- dec di ; Point at last char
- cmp byte ptr [di],' ' ; check for multiple spaces
- jnz moreinput
- cmp byte ptr [di-1],' ' ;
- jz bkspc
- jmp moreinput ; Get more input
- dotab:
- push cx
- mov cx,di ; cx = current pos
- sub cx,si ; Minus start pos
- add cl,7 ; now it equals number of
- and cx,7 ; spaces per tab
- xor cx,7
- inc cl ; spaces = 1 to 8
- tablp:
- mov al,' '
- stosb
- mov dl,' '
- call PutChar
- loop tablp
- pop cx
- jmp moreinput
- GetInputLine ENDP
- ;
- ; Wade past spaces
- ; Whoa! By subtle implication, the carry accidentally gets set if the non-
- ; space of comma character was less than 13 in ASCII sequence. This means
- ; if we hit a tab (8), the carry gets returned set.
- ; Turns out this is NO ACCIDENT, and callers rely on this somehow.
- ;
- WadeSpace PROC
- lodsb ; Get char
- cmp al,' ' ; if ' ' or ',' go again
- je short wadeSpace ;
- cmp al,',' ;
- je short WadeSpace ;
- cmp al,9 ;ignore tab also
- je WadeSpace
- dec si ; Point at last space char
- cmp al,13
- ret
- WadeSpace ENDP
- ;
- ; Wade through spaces only
- ;
- WadeSpaceOnly PROC
- lodsb ; Get a char
- cmp al,' ' ; Is space
- je WadeSpaceOnly ; Loop if so
- cmp al,9 ; ignore tab also
- je WadeSpaceOnly
- dec si ; Else point at char
- cmp al,13
- ret
- WadeSpaceOnly ENDP
- ;
- ; Main Input routine
- ;
- InputHandler PROC
- call LoadHistory
- PRINT_MESSAGE <13,10,"->"> ; MONITOR prompt
- call GetInputLine ; Get an input line
- call WadeSpace ; Wade through spaces
- jz InputHandler ; blank line, so try again
- inc si ; Point at first non-space char
- mov di,offset commands ; Get command list
- mov cx,comlen ; Length of list
- repne scasb ; search for command in list
- jnz ierr ; Error if not in list
- mov ax,comlen-1 ; Calculate position
- sub ax,cx ;
-
- ;Dangerous practice - the list of commands is tightly coupled to the string
- ;of command characters. Some day, I should convert this to an array of
- ;structures, each containing the command and a pointer to its handler.
- ;Then we search through the structure list to find the command, and if found
- ;call the associated handler.
-
- push 0 ; Command arg = 0
- call TableDispatch ; Dispatch command
- dw comlen-1
- dw asm ;A command
- dw breaks ;B command
- dw compare ;C command
- dw Dump ;D command
- dw entry ;E command
- dw fill ;F command
- dw go ;G command
- dw domath ;H command
- dw doin ;I command
- dw DoFileRead ;L command
- dw move ;M command
- dw fpcommand ;N command
- dw doout ;O command
- dw proceed ;P command
- dw _exit ;Q command
- dw ModifyRegisters ;R command
- dw search ;S command
- dw trap ;T command
- dw diss ;U command
- dw DoFileWrite ;W command
- dw drive ;X command
- dw pci ;Y command
- dw logging ;@ command
- dw help ;? command
- jnc InputHandler ; Get more input if no err
- ierr:
- call qerr ; Display error
- jmp InputHandler ; Get more input
- InputHandler ENDP
- END