home *** CD-ROM | disk | FTP | other *** search
- ;SIT -- enhanced SET for MS-DOS
- ;
- ;source code and executable placed IN THE PUBLIC DOMAIN by the author:
- ;
- ; Davidson Corry
- ; 4610 SW Lander
- ; Seattle, WA 98116
- ; (206) 935-0244
- ;
- ;support and enhancements are NOT guaranteed in any way, but
- ; if you have a question, suggestion, or comment, call me up.
- ; I might be tickled enough to do something about it!
- ;
- ;
- ;Written for Microsoft MASM 5.1
- ;
- ;Use the following commands to create SIT.COM:
- ;
- ; MASM SIT;
- ; LINK SIT; (ignore the warning about NO STACK)
- ; EXE2BIN SIT
- ; REN SIT.BIN SIT.COM
- ;
- ;and then you can erase SIT.OBJ and SIT.EXE
- ;
- ;
-
- include sit.inc ;structured ASM macros, etc.
-
-
-
- ;operation codes
- report equ 1
- create equ 2
- remove equ 3
- append equ 4
- prepend equ 5
-
- cseg segment byte public
- assume cs:cseg, ds:cseg, ss:cseg, es:nothing
- ; CS = DS = ES = SS = PSP segment in .COM format programs
-
- org 100h ;.COM format executable
-
- ;; ============= Primary routine
-
- main:
- call locate_master_environment
- call clean_up_command_line
- _if <cmp byte ptr ds:[80h],0>,ne ;there ARE command line arguments
- xor cx,cx
- mov cl,ds:[80h]
- inc cx ;copy command line INCLUDING terminating null
- mov ax,cs
- mov es,ax
- mov si,81h
- mov di,offset line_buffer
- cld
- rep movsb
- xor ax,ax
- stosb ;terminate with a null
- call process_line
- _else ;there are NO command line arguments, read lines from Standard Input
- _while <call read_from_stdin>,nc ;UNsuccessful read of a line from STDIN
- call process_line
- _wend
- _endif
- mov ax,4c00h ;terminate program
- dos
-
- ;; ============== coded data
-
- public master_env_seg, master_env_siz
-
- master_env_seg dw 0 ;segment address of master environment copy
- master_env_siz dw 0 ;size (in bytes) of master environment copy
-
- public variable_size, variable_posn
-
- variable_size dw 0 ;size (in bytes) of resultant VARIABLE=VALUE string
- variable_posn dw 0 ;position (in master environment area) to replace new VARIABLE=VALUE string
-
- public variable_name_size
-
- variable_name_size dw 0
-
- public operation
-
- operation db 0 ;which op to perform? remove, change, append, prepend, report?
-
- public no_room_msg
- no_room_msg db 'Master environment allocation exceeded$'
-
- public bad_syntax_msg
- bad_syntax_msg db 'Bad syntax. Usage is VARIABLE { [ | = | += | -= | &= ] VALUE STRING }$'
-
- public cant_find_command_com_msg
- cant_find_command_com_msg db 'Cannot locate primary command shell, terminating.$'
-
- public cant_find_master_env_msg
- cant_find_master_env_msg db 'Cannot locate master environment segment, terminating.',cr,lf
- db ' If you are using 4DOS, you must use the /M:nnn switch -- see 4DOS.DOC$'
-
- ;; ============== support routines
-
- public clean_up_command_line
- clean_up_command_line:
- xor cx,cx
- mov cl,ds:[80h] ;CX = size of command line passed to SIT
- xor dx,dx ;clear bitflags 01 = "there were nonblank characters"
- mov si,81h
- _if ,ncxz ;if there are some chars on command line...
- _loop
- _if <cmp byte ptr [si],' '>,a
- or dx,01 ;there are nonblank characters in the command line
- _endif
- inc si
- _nextcx
- _endif
- _if <test dx,1>,z ;there were NO non-blank characters in command line, kill command line
- mov byte ptr ds:[80h],0 ;pretend the command line was empty
- _endif
- mov si,81h
- xor bx,bx
- mov bl,ds:[80h]
- mov byte ptr [bx+si],0 ;null-terminate command line
- ret
-
- public read_from_stdin
- read_from_stdin:
- mov dx,offset line_buffer
- _loop
- mov ah,3fh ;"read from file handle"
- mov bx,0 ;STDIN file handle, always open
- mov cx,1 ;get 1 character
- dos
- _break <test ax,ax>,z ;no characters read, we're at end-of-file
- mov si,dx
- _break <cmp byte ptr [si],'Z'-'@'>,e ;ctrl-Z is end-of-file too!
-
- ;Input from STDIN may have lines delimited by
- ; CR alone, LF alone, CR/LF or LF/CR (depending on
- ; whether the source is the keyboard or a text file
- ; from any of several kinds of editors.
- ;To handle the re-display consistently, we
- ; 1) treat CR and LF identically
- ; 2) treat CR (or LF) as an end-of-line marker
- ; ONLY when there are characters in the line buffer,
- ; otherwise ignore it.
- ; 3) echo all characters up to EOL, then explicitly send
- ; a CR/LF
-
- _if <cmp byte ptr [si],lf>,e ;treat LF = CR
- mov byte ptr [si],cr
- _endif
-
- _if <cmp byte ptr [si],cr>,e ;possible end-of-line
- _again <cmp dx,offset line_buffer>,e ;no chars in buffer, ignore CR
- mov byte ptr [si],0 ;terminate line with null
- _break
- _endif
- inc dx
- _lend
- ;read from STDIN reached end-of-file or end-of-line, return CARRY if buffer is empty
- _if <cmp dx,offset line_buffer>,e ;no chars
- stc ;set CARRY = unsuccessful read
- _else
- clc
- _endif
- ret
-
- public locate_master_environment
- locate_master_environment:
- ;locate master copy of environment
-
- ;first step is to locate the master copy of COMMAND.COM
- ; (or whatever command shell is in charge)
- ;This is the first memory block that "owns itself" --
- ; that is, the segment of the arena header is one less than
- ; the segment of the PSP that owns it
-
- ;see Ray Duncan's ADVANCED MS-DOS for an excellent discussion
- ; of memory allocation and arena headers in MS-DOS
-
- ;NOTE *** in version 1.0 of SIT, I assumed that the segment portion of
- ; the INT 2Eh vector pointed to the master COMMAND.COM segment --
- ; that turned out to be true for Microsoft COMMAND.COM, but
- ; not for the (excellent) shareware replacement 4DOS --
- ; The following method is more robust, and correctly finds both
- ; COMMAND.COM and 4DOS.
-
- mov ah,52h
- dos ;undocumented DOS call, returns ES:BX -> "list of lists"
- mov ax,es:-2[bx] ;BX is the segment address of the first DOS memory allocation block
- push ax ;save the pointer to the first memory block
- _loop
- mov es,ax ;ES -> segaddr of arena header
- inc ax ;AX -> segaddr of memory block itself
- cmp ax,es:[1] ;see if they're the same
- _if ,e ;yes, they're the same, AX is the segaddr of the primary shell COMMAND.COM
- mov di,ax ;save it in AX for next loop
- _break
- _endif
- _if <cmp byte ptr es:[0],'Z'>,e ;reached end of arena header chain, COMMAND.COM not found (impossible, but true...)
- mov dx,offset cant_find_command_com_msg
- mov ah,9
- dos
- mov ax,4cffh ;quit with errorlevel 255
- dos
- _endif
- add ax,es:[3] ;advance AX -> next arena header
- _lend
- pop ax ;restore segment address of first memory block
-
- _loop
- mov es,ax ;ES segment is a memory allocation block ("arena header")
-
- ;see who "owns" this block of memory -- the PSP segment
- ; of the owner is the value in the word at ES:[1]
-
- _if <cmp di,es:[1]>,e ;master COMMAND.COM owns it, see if it's the master environment
- _if <cmp word ptr es:[3],3>,a ;3-paragraph block is the CURRENTLY-RUNNING PROGRAM block
- inc ax ;AX is segment address of memory block ITSELF (rather than its arena header)
- cmp di,ax ;compare to COMMAND.COM PSP segment value
- mov ax,es ;restore AX -> arena header, but doesn't affect flags from CMP DI,BX
-
- ;The first three memory blocks owned by the master copy of COMMAND.COM are usually
- ; 1) COMMAND.COM itself,
- ; 2) a 48-byte block containing the name of the
- ; currently-executing program, and
- ; 3) the master environment block
- ;
- ;We can tell them apart because the arena header for COMMAND.COM will be
- ; immediately preceding the memory block for COMMAND.COM (segment pointed by DI),
- ; while the arena header for the master environment strings block will
- ; be somewhere else.
- _if ,ne ;arena header did NOT immediately precede the DI segment, we've found master environment block
- inc ax ;AX -> segment of environment block
- mov master_env_seg,ax
- mov ax,es:[3] ;size of memory block in paragraphs
- shl ax,1
- shl ax,1
- shl ax,1
- shl ax,1 ;AX = size of memory block in BYTES
- mov master_env_siz,ax
- mov ax,cs
- mov es,ax ;restore ES = local segment
- ret ;done, return to main routine
- _endif
- _endif
- _endif
-
- _if <cmp byte ptr es:[0],'Z'>,e ;reached end of arena header chain, COMMAND.COM not found (impossible, but true...)
- mov dx,offset cant_find_master_env_msg
- mov ah,9
- dos
- mov ax,4cffh ;quit with errorlevel 255
- dos
- _endif
-
- ;wrong block, move AX to point to next block
- add ax,es:[3] ;size of memory block (in paragraphs)
- inc ax ;plus one, to compensate for the arena header paragraph itself
- ;AX now is the segment address of the next arena header
- _lend
-
- public process_line
- process_line:
- _if <call parse_line>,c ;break line up into (variable_name) (op) (value)
- mov dx,offset bad_syntax_msg
- mov ah,9
- dos
- mov ax,4c02h ;errorlevel 2 abort
- dos
- _endif
-
- _if <call extract_variable>,c ;unsuccessful extraction, no operation
- ret
- _endif
-
- _if <cmp operation,report>,e
- call v_report
- _elseif <cmp operation,remove>,e
- call v_remove
- _elseif <cmp operation,append>,e
- call v_append
- _elseif <cmp operation,prepend>,e
- call v_prepend
- _endif
- ;else operation is CREATE, which is done below
-
- ;compute size of new string
- mov si,offset new_value
- mov cx,variable_name_size ;size of "VARIABLE=" portion
- cld
- _loop
- lodsb
- inc cx
- _until <test al,al>,z
- mov variable_size,cx ;size of "VARIABLE=VALUE" string with terminating null byte
- mov ax,variable_posn
- add ax,cx
- inc ax ;compensate for terminating null byte on environment ("last null item")
- _if <cmp ax,master_env_siz>,a
- mov dx,offset no_room_msg
- mov ah,9
- dos
- mov ax,4c01h ;errorlevel 1 abort
- dos
- _endif
- ;otherwise, there is room for a successful operation
- ; copy VARIABLE=VALUE characters to STDOUT
- mov si,offset variable_name
- _loop
- mov dl,[si]
- _break <test dl,dl>,z
- inc si
- push si
- mov ah,2
- dos
- pop si
- _lend
- mov si,offset new_value
- _loop
- mov dl,[si]
- _break <test dl,dl>,z
- inc si
- push si
- mov ah,2
- dos
- pop si
- _lend
- mov dl,cr
- mov ah,2
- dos
- mov dl,lf
- mov ah,2
- dos
-
- ; copy VARIABLE=VALUE string to master environment
- _if <cmp byte ptr [new_value],0>,ne
- mov ax,master_env_seg
- mov es,ax
- mov di,variable_posn
- mov si,offset variable_name
- cld
- _loop
- lodsb
- _break <test al,al>,z ;done with VARIABLE=, now copy NEW_VALUE
- stosb
- _lend
- mov si,offset new_value
- _loop
- lodsb
- stosb
- _until <test al,al>,z
- stosb ;extra null to terminate ENVIRONMENT strings
- mov ax,cs
- mov es,ax ;restore ES = local segment
- _endif
- ret
-
- public parse_line
- parse_line:
- ;find first nonblank char in line
- mov si,offset line_buffer
- _while <cmp byte ptr [si],0>,a
- _break <cmp byte ptr [si],' '>,a ;break at first non-blank
- inc si
- _wend
- _if <cmp byte ptr [si],0>,e ;no variable name before (endofline)
- stc
- ret
- _endif
- mov dx,si ;DX -> first non-blank in string
-
- ;find end of variable name = (opcode) | (endofline)
- _while <cmp byte ptr [si],0>,a
- _break <cmp byte ptr [si],'='>,e
- _if <cmp byte ptr [si],'&'>,e
- _break <cmp byte ptr 1[si],'='>,e
- _endif
- _if <cmp byte ptr [si],'-'>,e
- _break <cmp byte ptr 1[si],'='>,e
- _endif
- _if <cmp byte ptr [si],'+'>,e
- _break <cmp byte ptr 1[si],'='>,e
- _endif
- _if <cmp byte ptr [si],'&'>,e
- _break <cmp byte ptr 1[si],'='>,e
- _endif
- inc si
- _wend
- ;SI -> character PAST end of variable name
-
- ;copy variable name to buffer, upcase, trim trailing spaces, then append '=' sign
- push si ;save pointer to first char of (op)
- mov cx,si ;pointer past end of VARIABLE
- mov si,dx ;pointer to first char of VARIABLE
- sub cx,dx ;CX = length of VARIABLE
- mov di,offset variable_name
- cld
- _if ,ncxz
- _loop
- lodsb
- _if <cmp al,'a'>,ae ;if it's a lowercase letter
- _if <cmp al,'z'>,be
- sub al,'a'-'A' ;UPCASE the letter
- _endif
- _endif
- stosb
- _nextcx
- _endif
- ;VARIABLE moved, trim trailing spaces
- _while <cmp di,offset variable_name>,a
- _break <cmp byte ptr -1[di],' '>,a
- dec di
- _wend
- pop si ;restore pointer to first char of (op)
- _if <cmp di,offset variable_name>,be ;"Variable_name" is all trailing spaces!
- mov dx,offset bad_syntax_msg
- mov ah,9
- dos
- mov ax,4c02h ;errorlevel 2 abort
- dos
- _endif
- mov al,'='
- stosb
- mov ax,di
- sub ax,offset variable_name
- mov variable_name_size,ax
- xor ax,ax
- stosb
-
- ;now skip over (and mark type of) operator string
- mov operation,report ;default op is "report current value"
- _if <cmp byte ptr [si],'='>,e ;"create new" VARIABLE=STRING
- inc si ;skip over '='
- mov operation,create
- _elseif <cmp byte ptr [si],'-'>,e ;remove substring
- inc si ;skip over '-='
- inc si
- mov operation,remove
- _elseif <cmp byte ptr [si],'+'>,e ;append substring
- inc si ;skip over '+='
- inc si
- mov operation,append
- _elseif <cmp byte ptr [si],'&'>,e ;prepend substring
- inc si ;skip over '&='
- inc si
- mov operation,prepend
- _endif
-
- ;finally, copy remaining string to NEW_VALUE
- mov di,offset new_value
- _loop
- lodsb
- stosb
- _until <test al,al>,z
- ret
-
- public extract_variable
- extract_variable:
- mov ax,master_env_seg
- mov ds,ax
- mov si,0 ;DS:SI -> first char of first string in environment
- _if <cmp byte ptr [si],0>,e ;environment is EMPTY (impossible according to DOS docs, but valid programming practice anyway)
- mov ax,cs
- mov ds,ax ;restore DS = local segment
- stc ;set carry to indicate EMPTY ENVIRONMENT
- ret
- _endif
- _loop
- _if <cmp byte ptr [si],0>,e ;reached end of environment without finding item,
- ;treat as though ITEM exists at end of environment with empty value
- mov ax,cs
- mov ds,ax ;restore DS = local segment
- mov variable_posn,si ;this is where variable will go
- mov byte ptr old_value,0 ;empty string is "old value"
- clc ;carry CLEAR indicates "variable found"
- ret
- _endif
- mov di,offset variable_name
- mov cx,es:variable_name_size
- push si
- rep cmpsb
- pop si
- _break ,z ;successful match found at DS:SI->
- ;unsuccessful, find end of this environment item
- _loop
- lodsb
- _until <test al,al>,z ;null terminates THIS env. item
- _lend
- ;DS:SI -> matched env item, "extract" it:
- ; copy the (existing) value to OLD_VALUE,
- ; then "bump down" all subsequent items in master environment.
- ;The modified VARIABLE=VALUE string will be written back
- ; to the master environment at the END of the environment.
- push si
- add si,es:variable_name_size
- mov di,offset old_value
- _loop
- lodsb
- stosb
- _until <test al,al>,z ;copy INCLUDING null terminator
- ;now copy down all subsequent env. strings
- mov ax,ds ; DS = ES = master environment segment
- mov es,ax
- ;DS:SI -> start of NEXT environment string
- pop di ;ES:DI -> start of EXTRACTED environment string
- _loop
- lodsb
- stosb
- _break <test al,al>,z ;TERMINATING null "environment item"
- _loop
- lodsb
- stosb
- _until <test al,al>,z ;copy environment item until terminating null
- _lend
- dec di ;restore pointer to terminating "null env. item", for later append of revised VARIABLE=VALUE string
- mov ax,cs ;restore data/extra segments to our .COM segment
- mov ds,ax
- mov es,ax
- mov variable_posn,di ;save the pointer (offset in ENV segment)
- clc ;clear carry indicates SUCCESSFUL EXTRACTION
- ret
-
- public v_remove
- v_remove:
- ;find length of NEW_VALUE
- mov si,offset new_value
- _while <cmp byte ptr [si],0>,ne
- inc si
- _wend
- sub si,offset new_value
- mov cx,si ;CX = length of NEW_VALUE string
-
- ;find NEW_VALUE within OLD_VALUE (if it's there)
- mov di,offset old_value
- mov si,offset new_value
- cld
- _loop
- cmp byte ptr [di],0
- je v_report ;didn't find substring, just REPORT existing value
- push di
- push si
- push cx
- repe cmpsb ;compare the substrings for CX bytes
- pop cx
- pop si
- pop di
- _break ,e ;substring found at [DI]
- inc di
- _lend
- mov si,di
- add si,cx ;SI -> past found substring
- cld ;copy down trailing string, to trailing null
- _loop
- lodsb
- stosb
- _until <test al,al>,z
- ;now desired value is in OLD_VALUE, just do a V_REPORT
-
- ;deliberate fallthrough to V_REPORT
-
- public v_report
- v_report:
- ;"report" is just (copy old value to new value) then (create new value)
- mov si,offset old_value
- mov di,offset new_value
- cld
- _loop
- lodsb
- stosb
- _until <test al,al>,z
- ret
-
- public v_append
- v_append:
- ;copy NEW_VALUE to workspace
- mov si,offset new_value
- mov di,offset workspace
- cld
- _loop
- lodsb
- stosb
- _until <test al,al>,z
- ;copy OLD_VALUE to NEWVALUE without trailing null
- mov si,offset old_value
- mov di,offset new_value
- cld
- _loop
- lodsb
- _break <test al,al>,z
- stosb
- _lend
- ;now continue copy from WORKSPACE
- mov si,offset workspace
- cld
- _loop
- lodsb
- stosb
- _until <test al,al>,z
- ret
-
- public v_prepend
- v_prepend:
- ;find end of NEW_VALUE
- mov di,offset new_value
- cld
- _while <cmp byte ptr [di],0>,ne
- inc di
- _wend
- ;then tack OLD_VALUE on the end
- mov si,offset old_value
- cld
- _loop
- lodsb
- stosb
- _until <test al,al>,z
- ret
-
-
-
-
-
-
-
-
- ;; ============= buffer areas
-
- ;by defining these buffers as LABELs, we don't include them in the
- ; actual .COM file as zero data.
-
- public line_buffer
- line_buffer label byte
-
- public variable_name
- variable_name equ line_buffer + 512
-
- public old_value
- old_value equ variable_name + 512
-
- public new_value
- new_value equ old_value + 512
-
- public workspace
- workspace equ new_value + 512
-
- cseg ends
- end main
-