⭐ 欢迎来到虫虫下载站! | 📦 资源下载 📁 资源专辑 ℹ️ 关于我们
⭐ 虫虫下载站

📄 init.asm

📁 DOS 源代码 系列之 command 源码
💻 ASM
📖 第 1 页 / 共 5 页
字号:
;
	push	bx
	push	cx
	mov	ax,(SET_CTRL_C_TRAPPING shl 8) or 06h ;is DOS in HIMEM? ;M013
	int	21h
	pop	cx
;bugbug: remove version check after testing
	cmp	bl,5				;bl has true version ; M013
	jb	oldver

	xor	ax,ax
	and	dh,10h				;is DOS in HMA ; M013
	pop	bx
	jnz	not_first			;DOS in HIMEM, code not
						;	resident

	mov	ax,offset CODERES: EndCode		;size of code in bytes
not_first:
;
;Note that ax = 0(side effect of int 2fh), if the code is not to be retained
;
	add	cx,ax

endif	;not ROMDOS

	add	cx,15				;round up to next para
	shr	cx,1
	shr	cx,1
	shr	cx,1
	shr	cx,1				;ax = para size of res code
	mov	ResSize,cx			;store resident size

	pop	ds
	assume	ds:nothing
	ret

ifndef	ROMDOS

;bugbug: remove this code (for version independent COMMAND) after testing
oldver:
	pop	bx
	mov	ax,offset CODERES: EndCode		;size of code in bytes
       	jmp	short not_first

endif	;not ROMDOS

setup_res_end	endp


ifndef	ROMDOS

;*** Move_res_code -- This routine moves the resident code to its final 
; location. We check if DOS is in HIMEM. If so, we try to load ourselves
; in HIMEM. If we fail, then we remain low and update ResSize to reflect
; the correct resident size. When remaining low, we have to check if we 
; need to overlay the messages part of the data segment which is determined
; by the /msg switch.
;
;	ENTRY: ResMsgEnd = end of resident data
;
;	EXIT:  The resident code is either up high or in its final location
;		down low.
;
;	REGISTERS AFFECTED: ax,bx,cx,dx,si,di
;
	
Move_res_code	proc	near

	push	ds
	push	es

	mov	ax,cs
	mov	ds,ax
	assume	ds:RESGROUP

	mov	ax,(SET_CTRL_C_TRAPPING shl 8) or 06h ; M013
	int	21h				;DOS in HIMEM?

	and	dh,10h				; M013
	jnz	move_high			;yes, move code high

;
;Check if messages have been discarded or not
;
load_low:
	push	ds
	pop	es				;es = RESGROUP
	mov	di,ResMsgEnd			;end offset in DATARES
	mov	bx,offset RESGROUP: ExtMsgEnd	;end offset of messages

	cmp	di,bx				;are messages to be kept?
	jz	no_move			;yes, dont move code

	jmp	short setup_move			;es:di points at dest.

move_high:

;
;We have to call DOS to get the load address in HIMEM for COMMAND
;We pass in bx the number of bytes we need
;
	mov	bx,offset CODERES: EndCode

;M030;
; Set di=0ffffh so that we load low in case no one answers this int 2fh
;
	mov	di,0ffffh			;DT - in case no-one handles
						;this ; M030
	mov	ax,GET_HMA_ADDR
	int	2fh

;
;If the offset = 0xffff, then no HMA available
;
	cmp	di,0ffffh			;HMA available?
	mov	ComInHMA,1			;assume command.com in HMA
	jnz	setup_move			;no error, es:di = memory

	mov	ComInHMA,0			;could not load in HMA
;
;Zero means that we do not have enough HIMEM. Remain low and update
;ResSize to reflect this
;
	mov	cx,ResMsgEnd			;size of data in bytes
	mov	ax,offset CODERES: EndCode		;size of code in bytes

	add	cx,ax
	add	cx,15				;round up to next para
	shr	cx,1
	shr	cx,1
	shr	cx,1
	shr	cx,1				;ax = para size of res code
	mov	ResSize,cx			;store resident size
	jmp	short load_low			;let code remain low

no_move:
	mov	cl,4
	add	di,0fh
	and	di,0fff0h			;round it to a para offset
	jmp	short patch_up

setup_move:
	mov	si,offset RESGROUP: StartCode
	mov	cx,offset CODERES: EndCode		;cx = bytes to move

	cld
	push	di				;need di for patching offset
	rep	movsb
	pop	di

patch_up:
	call	patch_stub
	pop	es
	pop	ds
	assume	ds:nothing
	ret

Move_res_code	endp

else	;ROMDOS

;***	Move_res_code - ROMDOS version - locate ROM resident

Move_res_code	proc

	push	es

	invoke	FindROMRes		; ES:DI = ptr to ROM resident code
	call	patch_stub

	pop	es
	ret

Move_res_code	endp

	assume	ds:NOTHING		; to match ending assume above

endif	;ROMDOS


;*** Alloc_env -- This routine allocates the temporary environment for the
; Init code to initialize the COMSPEC. This is not a complete environment. 
; Later on, at EndInit time, a proper sized environment is allocated and
; the contents of this temporary environment are copied to it. This routine
; will not be called in case a valid environment is passed to command.com
;
;       ENTRY:  FirstCom and initial EnvirSeg set
;
;       EXIT:   ax = EnvirSeg = segment of newly allocated environment segment
;
;       REGISTERS AFFECTED: ax,bx,cx,dx
;

Alloc_env	proc	near
        assume  ds:nothing
	
        push    ds
	push	es
	push	si
	push	di

        push    ss
        pop     ds
        assume  ds:RESGROUP

        mov     ax,EnvirSeg

        cmp     AllocedEnv,0
        je      alloc_cont
        jmp     alloc_done

alloc_cont:
        sub     di,di                           ; default start
        mov     bx,SIZE Environment             ; default size needed

        cmp     FirstCom,0                      ; first COMMAND.COM?
        je      alloc_seg                       ; no
;
;   Check EnvirSeg;  if non-zero, then scan it for PATH and COMSPEC;
;   Record their respective locations and do not add the default vars.
;
        or      ax,ax
        jz      alloc_new                       ; no previous environment

        mov     es,ax
        assume  es:nothing

find_path:
        mov     al,0
        sub     di,di
comp_path:
        scasb                                   ; end of env?
        je      find_prompt                     ; yes
        dec     di
        mov     cx,PathStrLen
        mov     si,offset RESGROUP:PathString
        repe    cmpsb
        je      got_path
        mov     cx,256
        repne   scasb                           ; find next NULL
        jmp     comp_path

got_path:
        mov     PathString,0                    ; don't add it

find_prompt:
        sub     di,di
comp_prompt:
        scasb                                   ; end of env?
        je      find_comspec                    ; yes
        dec     di
        mov     cx,PrmptStrLen2
        mov     si,offset RESGROUP:PrmptString
        repe    cmpsb
        je      got_prompt
        mov     cx,256
        repne   scasb                           ; find next NULL
        jmp     comp_prompt

got_prompt:
        mov     PrmptString,0                   ; don't add it

find_comspec:
        sub     di,di
comp_comspec:
        scasb                                   ; end of env?
        je      got_envend                      ; yes
        dec     di
        mov     cx,ComspStrLen
        mov     si,offset RESGROUP:ComspString
        repe    cmpsb
        je      got_comspec
        mov     cx,256
        repne   scasb                           ; find next NULL
        jmp     comp_comspec

got_comspec:
        mov     ComspOffset,di

find_envend:
        sub     di,di
        mov     cx,ENVBIG                       ; max env size
comp_envend:
        dec     cx                              ;
        scasb                                   ; end of env?
        je      got_envend                      ; yes
        repne   scasb
        jmp     comp_envend

got_envend:
        dec     di
        lea     bx,[di+SIZE Environment]        ; add room for the basics
;
;   We want to fall through to alloc_new and set up default
;   path and prompt ONLY IF this is the first process;  in all other
;   cases, we assume it is a bad idea to try editing the user's environment
;
        push    ds
        mov     ds,ds:[PDB_Parent_Pid]
        cmp     ds:[PDB_Parent_Pid],0           ; is parent's parent pid field 0?
        pop     ds
        jne     alloc_seg                       ; no, we're not the first process
                                                ; so don't muck with the env.
alloc_new:
        inc     AllocedEnv                      ; note we have virgin env.

alloc_seg:
;
; Allocate default environment size
;
        mov     cx,bx                           ; save byte-granular size in CX
        add     bx,15
        shr     bx,1
        shr     bx,1
        shr     bx,1
        shr     bx,1                            ; BX = # paras
	mov	ah,ALLOC
	int	21h
        jnc     init_ok
        jmp     init_nomem                      ; insufficient memory, error
;
; If a previous environment existed (ie, DI != 0), then copy it into
; the new buffer
;
init_ok:
	mov	es,ax
        assume  es:nothing                      ; es = temp env segment

        or      di,di
        jz      copy_path

        push    cx
        push    ds
        mov     ds,EnvirSeg
        assume  ds:nothing
        sub     si,si
        mov     cx,di
        sub     di,di
        rep     movsb
        pop     ds
        assume  ds:RESGROUP
        pop     cx
        sub     cx,di

copy_path:
;
; First clear out (the rest of) the buffer
;
        push    di
        sub     ax,ax
        rep     stosb
        pop     di
;
; Initialize the path string (PATH=) first
;
        mov     si,offset RESGROUP:PathString   ; DS:SI -> "PATH=\0"
        cmp     byte ptr [si],al                ; add it?
        je      init_prompt                     ; no
        mov     cx,PathStrLen+1                 ;
        rep     movsb                           ;
        cmp     AllocedEnv,al                   ; virgin env?
        je      init_prompt                     ; no
;
; Establish a more reasonable default for the PATH
;
	mov	ah,GET_DEFAULT_DRIVE
	int	21h
        add     al,'A'                          ; convert to letter
        mov     [DefPathString],al              ;
        mov     [DefPath2String],al             ; now our default paths are complete

        mov     dl,0                            ; get dir for default drive
        push    ds                              ;
        push    es                              ;
        pop     ds                              ;
        mov     byte ptr [di],'\'               ;
        lea     si,[di+1]                       ; set DS:SI -> available space
        mov     ah,Current_Dir                  ;
        int     21h                             ;
        pop     ds                              ;

        mov     cx,DefPathStrLen+1              ;
        mov     dx,offset RESGROUP:DefPathString
        mov     si,dx                           ;
        mov     ah,CHDir                        ;
        int     21h                             ;
        jnc     init_setpath                    ; DefPathString exists!

        mov     cx,DefPath2StrLen+1             ;
        mov     dx,offset RESGROUP:DefPath2String
        mov     si,dx                           ;
        mov     ah,CHDir                        ;
        int     21h                             ;
        jc      init_prompt                     ; DefPath2String doesn't exist

init_setpath:
        mov     dx,di                           ; success
        push    ds                              ; so restore prev dir
        push    es                              ;
        pop     ds                              ; DS:DX -> prev dir
        mov     ah,CHDir                        ;
        int     21h                             ;
        pop     ds                              ;

        dec     di                              ; then copy in DefPathString
        rep     movsb                           ; DS:SI -> "C:\\DOS\0"
;
; Initialize the default prompt
;
init_prompt:
        push    di                              ;
        sub     ax,ax                           ;
        mov     cx,64                           ; insure any data read in
        rep     stosb                           ; from Current_Dir is zapped
        pop     di                              ;

        cmp     AllocedEnv,al                   ; virgin env?
        je      init_comspec                    ; no
        mov     si,offset RESGROUP:PrmptString  ; DS:SI -> "PROMPT=$P$G\0"
        cmp     byte ptr [si],al                ; add it?
        je      init_comspec                    ; no
        mov     cx,PrmptStrLen+1                ;
        rep     movsb                           ;
;
; Initialize the Comspec string
;
init_comspec:
        cmp     ComspOffset,ax                  ; add it?
        jne     init_done                       ; no
        lea     ax,[di+ComspStrLen]             ;
        mov     ComspOffset,ax                  ;
        mov     si,offset RESGROUP:ComspString  ; DS:SI -> "COMSPEC=\\COMMAND.COM\0"
        mov     cx,ComspStrLen2+1               ;
        rep     movsb                           ;

init_done:
        mov     ax,es                           ; return env seg in ax
        mov     EnvirSeg,ax                     ; save env seg
        inc     AllocedEnv                      ; remember that *we* alloced it

alloc_done:
	pop	di
	pop	si
	pop	es
        pop     ds
        assume  ds:nothing
	ret

init_nomem:
;
;We call the error routine from here. This routine never returns. It either
;terminates COMMAND with error( if it is not the first invocation ) or hangs
;the system ( if it is the first COMMAND.COM ).
;
	call	alloc_error

Alloc_env	endp


;*** Alloc_error: This routine just jumps to the actual label where we 
; check if this is a permanent or secondary command.com and take the 
; appropriate action.
;
;	ENTRY:	ds = RESGROUP = DATARES
;
;	EXIT:	None - does not return
;
;	REGISTERS AFFECTED: Does not matter
;

public Alloc_error
Alloc_error	proc	near

	jmp	RESGROUP:BadMemErr

Alloc_error	endp

;***

⌨️ 快捷键说明

复制代码 Ctrl + C
搜索代码 Ctrl + F
全屏模式 F11
切换主题 Ctrl + Shift + D
显示快捷键 ?
增大字号 Ctrl + =
减小字号 Ctrl + -