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

📄 init.asm

📁 开放源码的编译器open watcom 1.6.0版的源代码
💻 ASM
📖 第 1 页 / 共 2 页
字号:
;
; Copyright (C) 1996-2002 Supernar Systems, Ltd. All rights reserved.
;
; Redistribution  and  use  in source and  binary  forms, with or without
; modification,  are permitted provided that the following conditions are
; met:
;
; 1.  Redistributions  of  source code  must  retain  the above copyright
; notice, this list of conditions and the following disclaimer.
;
; 2.  Redistributions  in binary form  must reproduce the above copyright
; notice,  this  list of conditions and  the  following disclaimer in the
; documentation and/or other materials provided with the distribution.
;
; 3. The end-user documentation included with the redistribution, if any,
; must include the following acknowledgment:
;
; "This product uses DOS/32 Advanced DOS Extender technology."
;
; Alternately,  this acknowledgment may appear in the software itself, if
; and wherever such third-party acknowledgments normally appear.
;
; 4.  Products derived from this software  may not be called "DOS/32A" or
; "DOS/32 Advanced".
;
; THIS  SOFTWARE AND DOCUMENTATION IS PROVIDED  "AS IS" AND ANY EXPRESSED
; OR  IMPLIED  WARRANTIES,  INCLUDING, BUT  NOT  LIMITED  TO, THE IMPLIED
; WARRANTIES  OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE
; DISCLAIMED.  IN  NO  EVENT SHALL THE  AUTHORS  OR  COPYRIGHT HOLDERS BE
; LIABLE  FOR  ANY DIRECT, INDIRECT,  INCIDENTAL,  SPECIAL, EXEMPLARY, OR
; CONSEQUENTIAL  DAMAGES  (INCLUDING, BUT NOT  LIMITED TO, PROCUREMENT OF
; SUBSTITUTE  GOODS  OR  SERVICES;  LOSS OF  USE,  DATA,  OR  PROFITS; OR
; BUSINESS  INTERRUPTION) HOWEVER CAUSED AND  ON ANY THEORY OF LIABILITY,
; WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR
; OTHERWISE)  ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF
; ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
;
;

;=============================================================================
; Initialize Protected Mode
;===========================
; In:	BX = client version
;	DX = offset of Client's Safe Exit Routine (used by exception handler)
;	ES = real mode segment for protected mode data (ignored if not needed)
;
; Out:	AX = return code:
;	 0005h = DPMI - could not enter 32bit protected mode
;	 0006h = DPMI - could not allocate needed selectors
;	 0007h = could not enable A20 gate
;	BX = kernel code selector
;	ECX = amount of allocated memory (in bytes)
;	EDX = pointer to allocated memory (from 0)
;	SI = current process ID (when spawned)
;	DI = version of the previously installed DOS/32A (0 if none)
;	CF = set on error, if no error:
;	 ESP = high word clear
;	 CS = 16bit selector for real mode CS with limit of 64k
;	 SS = selector for real mode SS with limit of 64k
;	 DS = selector for real mode DS with limit of 64k
;	 ES = selector for PSP with limit of 100h
;	 FS = 0 (NULL selector)
;	 GS = 0 (NULL selector)
;=============================================================================

pm32_init:
	cld
	pushad
	push ds
	push cs				; DS = _KERNEL
	pop ds

	xor eax,eax
	mov kernel_code,cs
	mov client_version,bx
	mov client_call[0],dx
	mov ax,cs			; set base addx of _KERNEL
	shl eax,4
	mov codebase,eax
	add vcpi_gdtaddx,eax		; adjust addresses for VCPI structure
	add vcpi_idtaddx,eax
	add vcpistrucaddx,eax
	btr pm32_maxextmem,31		; limit extended memory to 2GB

	push es
	push cs
	pop es
	mov di,offs @area1_db
	mov cx,(offs @area1_end - offs @area1_db) /2
	xor ax,ax
	rep stosw
	pop es

	mov bp,sp
	mov [bp+02h],ax			; set DI to 0 (prev D32A version)
	mov ax,0FF88h			; detect if DOS/32A is present
	int 21h
	cmp eax,'ID32'			; check if we were spawned
	jnz @@1				; if not, jump
	mov [bp+02h],bx			; set DI to prev. version of D32A
	cmp bx,client_version		; check versions
	jnz @@1				; if not equal, jump
	mov id32_mem_free,ecx
	mov id32_mem_ptr,edx
	mov id32_mem_vcpi,edi
	shr esi,16			; get previous process id
	inc si				; increment (make it this process id)
	mov id32_process_id,si		; store the new, current process id
	mov pm32_maxextmem,0		; use already allocated memory

@@1:	movzx bx,pmodetype		; jump to appropriate init code
	add bx,bx
	jmp @@init[bx]

@@init	dw r_init
	dw x_init
	dw v_init
	dw d_init


;=============================================================================
dvxr_init:				; DPMI/VCPI/XMS/raw common init tail
	xor ax,ax			; allocate selector for return code
	mov cx,1
	int 31h
	jnc @@0
@@err:	mov ax,4CFFh			; could not allocate selector
	int 21h				; terminate immediately

@@0:	mov bp,sp
	mov bx,ax			; new code descriptor for return
	mov ax,0007h			; set base address of calling segment
	mov dx,[bp+36]
	mov cx,dx
	shl dx,4
	shr cx,12
	int 31h
	jc @@err

	inc ax				; set selector limit to 64k
	xor cx,cx
	mov dx,0FFFFh
	int 31h
	jc @@err

	inc ax				; set selector type and access rights
	mov dx,cs			; get DPL from current CPL, and access
	lar cx,dx			;  rights and type from current CS
	shr cx,8			; type is already 16bit code segment
	int 31h
	jc @@err

	mov [bp+36],bx			; store selector in return address

	cmp cs:pmodetype,3		; if DPMI, no need in client_addx
	jz @@1				;  DPMI will handle all the exceptions
	push ds				; store client's code selector
	mov ds,cs:seldata
	mov client_call[2],bx
	pop ds

@@1:	xor bx,bx			; init successful, carry clear

;-----------------------------------------------------------------------------
init_done:				; return with return code
	mov [bp+1Eh],bx			; set AX=return code
	jc @@1
	mov eax,cs:mem_free
	mov edx,cs:mem_ptr
	mov [bp+1Ah],eax		; set ECX=amount of allocated memory
	mov [bp+16h],edx		; set EDX=pointer to allocated memory
	or eax,edx			; if allocated some memory, exit
	jnz @@1
	call init_done_id32
@@1:	pop ds
	popad
	mov bx,cs			; return BX=kernel code selector
	mov si,cs:id32_process_id	; return SI=current process ID
	cld
	retf

init_done_id32:
	cmp cs:pmodetype,3		; if under DPMI, exit
	jz @@done
	mov ds,cs:seldata
	cmp id32_process_id,0		; if this is the first process (mom)
	jz @@done			; then we're done

	mov eax,id32_mem_free
	mov edx,id32_mem_ptr
	mov [bp+1Ah],eax		; set ECX=amount of allocated memory
	mov [bp+16h],edx		; set EDX=pointer to allocated memory
	mov mem_free,eax
	mov mem_ptr,edx
	lea ecx,[eax+10h]		; size of memory + 16 bytes
	lea eax,[ecx+edx]		; top of memory
	mov mem_top,eax

	mov al,pmodetype		; now check if running under VCPI
	cmp al,0
	jz @@done
	cmp al,1
	jz @@done
	push es
	mov esi,id32_mem_vcpi		; import pagetables from prev process
	mov edi,pagetablefree
	mov es,selzero
	mov ds,selzero
	shr ecx,12
	rep movs dword ptr es:[edi],[esi]
	pop es
@@done:	ret





;=============================================================================
;******	NOTE:	DPMI host will provide all INT 31h functions and
;		will be responsible for any memory allocation.

d_init:	pop ds				; get original caller DS from stack
	mov ax,1			; enter DPMI protected mode
	call cs:dpmiepmode
	push ds				; put DS back onto stack
	jnc dvxr_init			; error? if not, go on with init
	mov bx,6			; error entering protected mode, set
	cmp ax,8011h			;  error code and abort
	stc
	jz init_done
	dec bx				; error code 5, not 6
	jmp init_done





	Align 16
@kernel_beg	label byte		;** Begin of kernel code
@callback_data	label byte		;** CALLBACK DATA Structure

;=============================================================================
v_init:	xor eax,eax
	mov ax,es			; align data area on page boundary
	add ax,00FFh
	xor al,al
	mov es,ax
	mov dx,ax			; set base and top of page table area

	shl eax,4
	add eax,1000h			; skip Page Directory
	mov pagetablebase,eax		; 0th PageTable linear address
	add eax,1000h			; skip 0th PageTable
	movzx ecx,pagetables
	shl ecx,12
	add eax,ecx
	mov pagetabletop,eax		; Nth PageTable linear adress
	mov phystablebase,eax		; set base and top of physical pages
	movzx ecx,pm32_maxfpages
	shl ecx,12
	add eax,ecx
	mov phystabletop,eax

	xor di,di
	xor eax,eax			; clear PageDir and 0th PageTable
	mov cx,0800h
	rep stos dword ptr es:[di]

	mov gs,dx                       ; GS = segment of Page Directory
	mov ax,dx
	add ax,0100h
	mov es,ax                       ; ES = segment of 0th Page Table
	mov fs,ax                       ; FS = segment of 0th Page Table

	sub sp,8*3			;***NOTE: stack will be restored later
	mov si,sp			; DS:SI = ptr to VCPI structure
	xor di,di			; ES:DI = ptr to imported 0th PageTab
	push ds
	push ss
	pop ds
	mov ax,0DE01h			; get VCPI protected mode interface
	int 67h
	pop ds

	push di				;** store DI = ptr to free entry
	mov vcpi_calleip,ebx		; store protected mode VCPI call EIP
@@1:	and byte ptr es:[di+1],0F1h     ; clear bits 9-11 in imported PageTab
	sub di,4
	jnc @@1

	mov cx,dx			; get physical address of PageDir
	shr cx,8
	mov ax,0DE06h
	int 67h
	and dx,0F000h
	mov vcpi_cr3,edx		; set VCPI CR3 register

;
; Map VCPI 0th PageTable into our PageDir
;
	mov cx,es			; CX = 0th PageTable addr
	shr cx,8			; convert to PageTable number
	mov ax,0DE06h			; VCPI get pagetable Physical Addr
	int 67h
	and dh,0F0h
	mov dl,07h
	mov gs:[0000h],edx		; store address in PageDir

;
; Map the rest of our custom PageTables into our PageDir
;
	mov ax,es			; advance to the 1st PageTable
	add ax,0100h
	mov es,ax

	mov si,ax			; SI = segment of 1st PageTable
	mov al,pagetables		; AL = PageTables to alloc
	mov ebx,1			; EBX = index ptr into PageDir
	call vcpi_setup_pagetables	; initialize VCPI PageDir and PageTabs

;
; Map PageTables for phys. mapping into PageDir
;
	mov ax,gs			; advance PageDir to 8000_0000h addr
	add ax,80h
	mov gs,ax

	mov al,pm32_maxfpages		; phystables to allocate
	xor ebx,ebx			; EBX = index ptr into PageDir
	call vcpi_setup_pagetables	; initialize VCPI PageDir and PageTabs
	pop di				;** restore DI = ptr to free entry

	xor eax,eax
	test pm32_mode,00000100b	; if smart pagetables is off
	jnz @@2				;  then align pagetablefree to
	mov di,1000h			;  first allocated free pagetable
@@2:	mov ax,di			; set base of usable page table area
	add eax,pagetablebase
	mov pagetablefree,eax

	push si es
	call vcpi_alloc_ems		; allocate VCPI memory
	pop es si

	push si				; SI = segment of TSS (for later use)
	xor di,di			; clear TSS with all 0, not really
	mov cx,34h			;  needed, but just to be safe
	xor ax,ax
	rep stos word ptr es:[di]
	mov eax,vcpi_cr3		; set CR3 in TSS
	mov es:[1Ch],eax
	mov dword ptr es:[64h],680000h	; set offset of I/O permission bitmap
					;  and clear T bit
	add si,7			; increment next data area ptr
	mov es,si
	mov rmtopmswrout,offs v_rmtopmsw	; set VCPI mode switch addresses
	mov pmtormswrout,offs v_pmtormsw
	jmp vxr_init			; go to VCPI/XMS/raw continue init


vcpi_setup_pagetables:
	push bp
	movzx bp,al			; BP = PageTables to alloc
	test bp,bp
	jz @@done
@@1:	mov cx,si			; CX = PageTable segment
	shr cx,8			; convert to PageTable number
	mov ax,0DE06h			; VCPI get PageTable Physical Addr
	int 67h
	and dh,0F0h
	mov dl,07h
	mov gs:[ebx*4],edx		; store address in PageDir
	add si,0100h			; increment pagetable segment (4K)
	mov es,si
	xor di,di			; clear PageTable
	xor eax,eax
	mov cx,0400h
	rep stos dword ptr es:[di]
	inc bx				; increment index in PageDir
	dec bp				; decrement PageTable counter
	jnz @@1				; if no, loop
@@done:	pop bp
	ret

vcpi_alloc_ems:
	push fs
	pop es				; ES:DI ptr to free entry in 0th page
	movzx eax,pagetables		; calculate free linear space
	shl eax,22			; convert PageTables to bytes (*4M)
	mov ecx,1000h
	sub cx,di			; ECX = unused space in 0th PageTable
	and cl,0FCh
	shl ecx,10			; convert 4K pages to bytes
	add eax,ecx			; EAX = available linear space (bytes)
	mov ecx,pm32_maxextmem		; ECX = memory to allocate (bytes)
	cmp ecx,eax			; choose smallest value
	jbe @@0
	mov ecx,eax
@@0:	xor ebx,ebx			; EBX = counter of allocated pages
	jecxz @@done			; if no memory to be allocated, done

@@1:	cmp di,1000h			; if NOT overflowing page (DX>4096)
	jb @@2				;  then jump
	mov ax,es			; else adjust ES:DI pointer to next PG
	add ax,0100h
	mov es,ax
	xor di,di

@@2:	mov ax,0DE04h			; allocate 4K VCPI page
	int 67h
	test ah,ah			; check if error
	jnz @@3				; if yes, then we are done
	and dh,0F0h			; clear avail bits
	mov dl,07h			; set page as user/writeable/present
	mov es:[di],edx			; store page addr in PageTable
	add di,4			; increment ptr into PageTable
	inc bx				; increment allocated page counter
	sub ecx,4096
	ja @@1				; loop until no more pages to allocate

@@3:	mov vcpi_allocmem,bx		; store alloc pages for deallocation
	cmp ecx,4096			; is there memory left to allocate
	jb @@4				; no, then done
	test pm32_mode,00001000b	; check if VCPI+XMS allocation scheme
	jz @@4				;  enabled, if not jump
	call vcpi_alloc_xms		; try XMS memory allocation

@@4:	shl ebx,12			; convert allocated pages to bytes
	jz @@done			; allocated any memory? if no, jump
	mov mem_free,ebx		; store amount of allocated memory
	mov eax,pagetablefree		; figure out address of memory
	sub eax,pagetablebase
	shl eax,10
	mov mem_ptr,eax
@@done:	ret

vcpi_alloc_xms:
	push ebx			; save EBX counter
	shr ecx,10			; convert bytes to KB
	and cl,0FCh			; mask ECX to match 4KB pages

@@1:	mov edx,ecx
	jecxz @@done			; if EDX=0, no mem to be allocated
	call xms_allocmem		; XMS allocate extended memory
	dec ax
	jz @@2				; if got memory, jump
	sub ecx,4			; try less memory, subtract 4K page
	jnc @@1				; loop til there is no memory to alloc
	jmp @@done			; no memory allocated, done

@@2:	mov xms_handle,dx		; store handle
	mov ah,0Ch			; XMS lock extended memory
	call dword ptr xms_call
	dec ax
	jz @@3				; if locked memory, jump
	xor dx,dx
	xchg dx,xms_handle		; reset xms_handle: no mem allocated
	mov ah,0Ah			; free allocated XMS memory
	call dword ptr xms_call
	jmp @@done

@@3:	shl edx,16			; convert DX:BX to EDX pointer
	mov dx,bx
	shr ecx,2			; ECX=memory allocated in 4K blocks
	movzx eax,cx
	pop ebx
	add ebx,eax			; adjust allocated page number
	push ebx

@@4:	cmp di,1000h			; if NOT overflowing page (DX>4096)
	jb @@5				;  then jump
	mov ax,es			; else adjust ES:DI pointer to next PG
	add ax,0100h
	mov es,ax
	xor di,di

⌨️ 快捷键说明

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