PMODE-Wechsel erfolgreich?



  • hi, habe einen Kernel geproggt, der mit Hilfe eines Bootloaders (freeldr) geladen und ausgeführt wird, allerdings weiß ich nicht genau, ob der Wechsel in den PMODE erfolgreich war, weil er mir mein ASCII Zeichen nicht anzeigt. Kann mir einer helfen, warum das nicht gezeigt wird oder ob der Wechsel überhaupt erfolgreich war (stürzt nicht ab oder vollführt einen Reset)? Hier der Code:

    [BITS 16]
     jmp start
    
     NULL_Desc:
     dd 0
     dd 0
    
     CODE_Desc:
     dw 0xFFFF
     dw 0
     db 0
     db 10011010b
     db 11001111b
     db 0
    
     DATA_Desc:
     dw 0xFFFF
     dw 0
     db 0
     db 0x92
     db 0xCF
     db 0
    
     gdt:
     Limit		dw		0
     Base		dd		0
    
     start:
    
     cli
    
     mov eax, cs
     mov ds, ax
    
     shl eax, 4
    
     mov [CODE_Desc+2], ax
     mov [DATA_Desc+2], ax
     shr eax, 16
     mov [CODE_Desc+4], al
     mov [DATA_Desc+4], al
    
     mov eax, cs
     shl eax, 4
     add eax, NULL_Desc
    
     mov [Base], eax
     mov [Limit], WORD gdt - NULL_Desc -1
    
     lgdt		[gdt]
    
     mov eax, cr0
     or eax, 1
     mov cr0, eax
    
     db 0xea
     dw PMODE
     dw 0x8
    
     [BITS 32]
    
     PMODE:
     mov WORD [CODE_Desc+2], 0
     mov WORD [DATA_Desc+2], 0
     mov BYTE [CODE_Desc+4], 0
     mov BYTE [DATA_Desc+4], 0
    
     mov eax, 2
     shl eax, 3
    
     mov ds, ax
     mov ss, ax
     mov es, ax
     mov eax, 0
     mov fs, ax
     mov gs, ax
     mov esp, 0x1FFFFF
    
     jmp 0x8:0x10000 + PMODE2
    
     PMODE2:
     mov ax,DATA_Desc
     mov es,ax
     mov byte [es:0B800Eh],'7'
     PMODE3:
     jmp PMODE3
    

    Ich benutze NASM zum assemblieren der Datei.
    Falls es noch ichtig sein sollte, hier der Quellcode vom freeldr:

    ; FAT.ASM
    ; FAT12/16 Boot Sector
    ; Copyright (c) 1998, 2001, 2002 Brian Palmer
    
    ; This is a FAT12/16 file system boot sector
    ; that searches the entire root directory
    ; for the file freeldr.sys and loads it into
    ; memory.
    ;
    ; The stack is set to 0000:7BF2 so that the first
    ; WORD pushed will be placed at 0000:7BF0
    ;
    ; The DWORD at 0000:7BFC or BP-04h is the logical
    ; sector number of the start of the data area.
    ;
    ; The DWORD at 0000:7BF8 or BP-08h is the total
    ; sector count of the boot drive as reported by
    ; the computers bios.
    ;
    ; The WORD at 0000:7BF6 or BP-0ah is the offset
    ; of the ReadSectors function in the boot sector.
    ;
    ; The WORD at 0000:7BF4 or BP-0ch is the offset
    ; of the ReadCluster function in the boot sector.
    ;
    ; The WORD at 0000:7BF2 or BP-0eh is the offset
    ; of the PutChars function in the boot sector.
    ;
    ; When it locates freeldr.sys on the disk it will
    ; load the first sector of the file to 0000:8000
    ; With the help of this sector we should be able
    ; to load the entire file off the disk, no matter
    ; how fragmented it is.
    ;
    ; We load the entire FAT table into memory at
    ; 7000:0000. This improves the speed of floppy disk
    ; boots dramatically.
    
    BootSectorStackTop		equ		0x7bf2
    DataAreaStartHigh		equ		0x2
    DataAreaStartLow		equ		0x4
    BiosCHSDriveSizeHigh	equ		0x6
    BiosCHSDriveSizeLow		equ		0x8
    BiosCHSDriveSize		equ		0x8
    ReadSectorsOffset		equ		0xa
    ReadClusterOffset		equ		0xc
    PutCharsOffset			equ		0xe
    
    org 7c00h
    
    segment .text
    
    bits 16
    
    start:
            jmp short main
            nop
    
    OEMName         db 'KLOAD1.0'
    BytesPerSector  dw 512
    SectsPerCluster db 1
    ReservedSectors dw 1
    NumberOfFats    db 2
    MaxRootEntries  dw 224
    TotalSectors    dw 2880
    MediaDescriptor db 0f0h
    SectorsPerFat   dw 9
    SectorsPerTrack dw 18
    NumberOfHeads   dw 2
    HiddenSectors   dd 0
    TotalSectorsBig dd 0
    BootDrive       db 0xff
    Reserved        db 0
    ExtendSig       db 29h
    SerialNumber    dd 00000000h
    VolumeLabel     db 'NO NAME    '
    FileSystem      db 'FAT12   '
    
    main:
            xor ax,ax
            mov ss,ax
            mov bp,7c00h
            mov sp,BootSectorStackTop				; Setup a stack
            mov ds,ax								; Make DS correct
            mov es,ax								; Make ES correct
    
    		cmp BYTE [BYTE bp+BootDrive],BYTE 0xff	; If they have specified a boot drive then use it
    		jne GetDriveParameters
    
            mov [BYTE bp+BootDrive],dl				; Save the boot drive
    
    GetDriveParameters:
    		mov  ah,08h
    		mov  dl,[BYTE bp+BootDrive]					; Get boot drive in dl
    		int  13h									; Request drive parameters from the bios
    		jnc  CalcDriveSize							; If the call succeeded then calculate the drive size
    
    		; If we get here then the call to the BIOS failed
    		; so just set CHS equal to the maximum addressable
    		; size
    		mov  cx,0ffffh
    		mov  dh,cl
    
    CalcDriveSize:
    		; Now that we have the drive geometry
    		; lets calculate the drive size
    		mov  bl,ch			; Put the low 8-bits of the cylinder count into BL
    		mov  bh,cl			; Put the high 2-bits in BH
    		shr  bh,6			; Shift them into position, now BX contains the cylinder count
    		and  cl,3fh			; Mask off cylinder bits from sector count
    		; CL now contains sectors per track and DH contains head count
    		movzx eax,dh		; Move the heads into EAX
    		movzx ebx,bx		; Move the cylinders into EBX
    		movzx ecx,cl		; Move the sectors per track into ECX
    		inc   eax			; Make it one based because the bios returns it zero based
    		inc   ebx			; Make the cylinder count one based also
    		mul   ecx			; Multiply heads with the sectors per track, result in edx:eax
    		mul   ebx			; Multiply the cylinders with (heads * sectors) [stored in edx:eax already]
    
    		; We now have the total number of sectors as reported
    		; by the bios in eax, so store it in our variable
    		mov   [BYTE bp-BiosCHSDriveSize],eax
    
            ; Now we must find our way to the first sector of the root directory
            xor ax,ax
    		xor cx,cx
            mov al,[BYTE bp+NumberOfFats]			; Number of fats
            mul WORD [BYTE bp+SectorsPerFat]		; Times sectors per fat
            add ax,WORD [BYTE bp+HiddenSectors]
            adc dx,WORD [BYTE bp+HiddenSectors+2]	; Add the number of hidden sectors
            add ax,WORD [BYTE bp+ReservedSectors]	; Add the number of reserved sectors
            adc dx,cx								; Add carry bit
    		mov WORD [BYTE bp-DataAreaStartLow],ax	; Save the starting sector of the root directory
    		mov WORD [BYTE bp-DataAreaStartHigh],dx	; Save it in the first 4 bytes before the boot sector
    		mov si,WORD [BYTE bp+MaxRootEntries]	; Get number of root dir entries in SI
            pusha									; Save 32-bit logical start sector of root dir
            ; DX:AX now has the number of the starting sector of the root directory
    
            ; Now calculate the size of the root directory
    		xor dx,dx
            mov ax,0020h							; Size of dir entry
            mul si									; Times the number of entries
            mov bx,[BYTE bp+BytesPerSector]
            add ax,bx
            dec ax
            div bx									; Divided by the size of a sector
    		; AX now has the number of root directory sectors
    
    		add [BYTE bp-DataAreaStartLow],ax		; Add the number of sectors of the root directory to our other value
    		adc [BYTE bp-DataAreaStartHigh],cx		; Now the first 4 bytes before the boot sector contain the starting sector of the data area
            popa									; Restore root dir logical sector start to DX:AX
    
    LoadRootDirSector:
            mov  bx,7e0h							; We will load the root directory sector
            mov  es,bx								; Right after the boot sector in memory
            xor  bx,bx								; We will load it to [0000:7e00h]
    		xor  cx,cx								; Zero out CX
    		inc  cx									; Now increment it to 1, we are reading one sector
    		xor  di,di								; Zero out di
    		push es									; Save ES because it will get incremented by 20h
    		call ReadSectors						; Read the first sector of the root directory
    		pop  es									; Restore ES (ES:DI = 07E0:0000)
    
    SearchRootDirSector:
    		cmp  [es:di],ch							; If the first byte of the directory entry is zero then we have
    		jz   ErrBoot							; reached the end of the directory and FREELDR.SYS is not here so reboot
    		pusha									; Save all registers
    		mov  cl,0xb								; Put 11 in cl (length of filename in directory entry)
    		mov  si,filename						; Put offset of filename string in DS:SI
    		repe cmpsb								; Compare this directory entry against 'FREELDR SYS'
    		popa									; Restore all the registers
    		jz   FoundFreeLoader					; If we found it then jump
    		dec  si									; SI holds MaxRootEntries, subtract one
    		jz   ErrBoot							; If we are out of root dir entries then reboot
    		add  di,BYTE +0x20						; Increment DI by the size of a directory entry
    		cmp  di,0200h							; Compare DI to 512 (DI has offset to next dir entry, make sure we haven't gone over one sector)
    		jc   SearchRootDirSector				; If DI is less than 512 loop again
    		jmp short LoadRootDirSector				; Didn't find FREELDR.SYS in this directory sector, try again
    
    FoundFreeLoader:
    		; We found freeldr.sys on the disk
    		; so we need to load the first 512
    		; bytes of it to 0000:8000
            ; ES:DI has dir entry (ES:DI == 07E0:XXXX)
            mov  ax,WORD [es:di+1ah]				; Get start cluster
    		push ax									; Save start cluster
    		push WORD 800h							; Put 800h on the stack and load it
    		pop  es									; Into ES so that we load the cluster at 0000:8000
    		call ReadCluster						; Read the cluster
    		pop  ax									; Restore start cluster of FreeLoader
    
    		; Save the addresses of needed functions so
    		; the helper code will know where to call them.
    		mov  WORD [BYTE bp-ReadSectorsOffset],ReadSectors		; Save the address of ReadSectors
    		mov  WORD [BYTE bp-ReadClusterOffset],ReadCluster		; Save the address of ReadCluster
    		mov  WORD [BYTE bp-PutCharsOffset],PutChars				; Save the address of PutChars
    
    		; Now AX has start cluster of FreeLoader and we
    		; have loaded the helper code in the first 512 bytes
    		; of FreeLoader to 0000:8000. Now transfer control
    		; to the helper code. Skip the first three bytes
    		; because they contain a jump instruction to skip
    		; over the helper code in the FreeLoader image.
    		;jmp  0000:8003h
    		jmp  8003h
    
    ; Displays an error message
    ; And reboots
    ErrBoot:
            mov  si,msgFreeLdr      ; FreeLdr not found message
            call PutChars           ; Display it
    
    Reboot:
            mov  si,msgAnyKey       ; Press any key message
            call PutChars           ; Display it
            xor ax,ax
            int 16h                 ; Wait for a keypress
            int 19h                 ; Reboot
    
    PutChars:
            lodsb
            or al,al
            jz short Done
            mov ah,0eh
            mov bx,07h
            int 10h
            jmp short PutChars
    Done:
            retn
    
    ; Displays a bad boot message
    ; And reboots
    BadBoot:
            mov  si,msgDiskError    ; Bad boot disk message
            call PutChars           ; Display it
    
    		jmp short Reboot
    
    ; Reads cluster number in AX into [ES:0000]
    ReadCluster:
    		; StartSector = ((Cluster - 2) * SectorsPerCluster) + ReservedSectors + HiddenSectors;
            dec   ax								; Adjust start cluster by 2
            dec   ax								; Because the data area starts on cluster 2
            xor   ch,ch
            mov   cl,BYTE [BYTE bp+SectsPerCluster]
            mul   cx								; Times sectors per cluster
            add   ax,[BYTE bp-DataAreaStartLow]		; Add start of data area
            adc   dx,[BYTE bp-DataAreaStartHigh]	; Now we have DX:AX with the logical start sector of OSLOADER.SYS
            xor   bx,bx								; We will load it to [ES:0000], ES loaded before function call
    		;mov   cl,BYTE [BYTE bp+SectsPerCluster]; Sectors per cluster still in CX
    		;call  ReadSectors
    		;ret
    
    ; Reads logical sectors into [ES:BX]
    ; DX:AX has logical sector number to read
    ; CX has number of sectors to read
    ReadSectors:
    
    		; We can't just check if the start sector is
    		; in the BIOS CHS range. We have to check if
    		; the start sector + length is in that range.
    		pusha
    		dec cx
    		add ax,cx
    		adc dx,byte 0
    
    		cmp dx,WORD [BYTE bp-BiosCHSDriveSizeHigh]	; Check if they are reading a sector within CHS range
    		ja  ReadSectorsLBA							; No - go to the LBA routine
    		jb  ReadSectorsCHS							; Yes - go to the old CHS routine
    		cmp ax,WORD [BYTE bp-BiosCHSDriveSizeLow]	; Check if they are reading a sector within CHS range
    		jbe ReadSectorsCHS							; Yes - go to the old CHS routine
    
    ReadSectorsLBA:
    		popa
    ReadSectorsLBALoop:
    		pusha									; Save logical sector number & sector count
    
    		o32 push byte 0
    		push dx									; Put 64-bit logical
    		push ax									; block address on stack
    		push es									; Put transfer segment on stack
    		push bx									; Put transfer offset on stack
    		push byte 1								; Set transfer count to 1 sector
    		push byte 0x10							; Set size of packet to 10h
    		mov  si,sp								; Setup disk address packet on stack
    
    ; We are so totally out of space here that I am forced to
    ; comment out this very beautifully written piece of code
    ; It would have been nice to have had this check...
    ;CheckInt13hExtensions:							; Now make sure this computer supports extended reads
    ;		mov  ah,0x41							; AH = 41h
    ;		mov  bx,0x55aa							; BX = 55AAh
    ;		mov  dl,[BYTE bp+BootDrive]				; DL = drive (80h-FFh)
    ;		int  13h								; IBM/MS INT 13 Extensions - INSTALLATION CHECK
    ;		jc   PrintDiskError						; CF set on error (extensions not supported)
    ;		cmp  bx,0xaa55							; BX = AA55h if installed
    ;		jne  PrintDiskError
    ;		test cl,1								; CX = API subset support bitmap
    ;		jz   PrintDiskError						; Bit 0, extended disk access functions (AH=42h-44h,47h,48h) supported
    
    												; Good, we're here so the computer supports LBA disk access
    												; So finish the extended read
            mov  dl,[BYTE bp+BootDrive]				; Drive number
    		mov  ah,42h								; Int 13h, AH = 42h - Extended Read
    		int  13h								; Call BIOS
    		jc   BadBoot							; If the read failed then abort
    
    		add  sp,byte 0x10						; Remove disk address packet from stack
    
    		popa									; Restore sector count & logical sector number
    
            inc  ax									; Increment Sector to Read
    		adc  dx,byte 0
    
            push bx
            mov  bx,es
            add  bx,byte 20h						; Increment read buffer for next sector
            mov  es,bx
            pop  bx
    
            loop ReadSectorsLBALoop					; Read next sector
    
            ret
    
    ; Reads logical sectors into [ES:BX]
    ; DX:AX has logical sector number to read
    ; CX has number of sectors to read
    ; CarryFlag set on error
    ReadSectorsCHS:
    		popa
    ReadSectorsCHSLoop:
            pusha
            xchg ax,cx
            xchg ax,dx
            xor  dx,dx
            div  WORD [BYTE bp+SectorsPerTrack]
            xchg ax,cx
            div  WORD [BYTE bp+SectorsPerTrack]    ; Divide logical by SectorsPerTrack
            inc  dx                        ; Sectors numbering starts at 1 not 0
            xchg cx,dx
            div  WORD [BYTE bp+NumberOfHeads]      ; Number of heads
            mov  dh,dl                     ; Head to DH, drive to DL
            mov  dl,[BYTE bp+BootDrive]            ; Drive number
            mov  ch,al                     ; Cylinder in CX
            ror  ah,2                      ; Low 8 bits of cylinder in CH, high 2 bits
                                           ;  in CL shifted to bits 6 & 7
            or   cl,ah                     ; Or with sector number
            mov  ax,0201h
            int  13h     ; DISK - READ SECTORS INTO MEMORY
                         ; AL = number of sectors to read, CH = track, CL = sector
                         ; DH = head, DL    = drive, ES:BX -> buffer to fill
                         ; Return: CF set on error, AH =    status (see AH=01h), AL    = number of sectors read
    
            jc   BadBoot
    
            popa
            inc  ax       ;Increment Sector to Read
            jnz  NoCarryCHS
            inc  dx
    
    NoCarryCHS:
            push bx
            mov  bx,es
            add  bx,byte 20h
            mov  es,bx
            pop  bx
                                            ; Increment read buffer for next sector
            loop ReadSectorsCHSLoop         ; Read next sector
    
            ret
    
    msgDiskError db 'Disk error',0dh,0ah,0
    msgFreeLdr   db 'bootmgr.ksf not found',0dh,0ah,0
    ; Sorry, need the space...
    ;msgAnyKey    db 'Press any key to restart',0dh,0ah,0
    msgAnyKey    db 'Press any key',0dh,0ah,0
    filename     db 'BOOTMGR KSF'
    
            times 509-($-$$) db 0   ; Pad to 509 bytes
    
    BootPartition:
    		db 0
    
    BootSignature:
            dw 0aa55h       ; BootSector signature
    

    Vielen vielen Dank euch allen schonmal für eure Mühe.



  • Nach dem einschalten des PM solltest du alle Segment(Selektor) Register mit den richtigen Werten beschreiben.



  • okay
    hum...könntest du das bitte für mein beispiel konkretisieren? Wäre echt sehr nett von dir/euch. Vielen Dank und liebe Grüße.
    Sebastian



  • Mein "BasisModul"

    [SECTION .text]
    [ORG 0x100]
    [BITS 16]
    
    ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
    ;       gdtr und idtr berechnen
    ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
    Pro:    cli
            xor eax,eax
            mov ax,cs               ;eax = Adresse diese Code-Segments
            shl eax,4               ;eax=eax*16
            lea ebx,[eax]           ;ebx = lineare Adressse dieses Segments
    
            mov [Sel01+2],bx
            mov [Sel02+2],bx
            shr ebx,16
            mov [Sel01+4],bl        ;
            mov [Sel02+4],bl
            mov [Sel01+7],bh        ;
            mov [Sel02+7],bh
    
    ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
    ;       gdtr und idtr setzen
    ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
    
            lea ebx,[eax+gdt]       ;ebx = lineare Adresse der gdt
            mov [gdtr+2],ebx
    
            lea ebx,[eax+idt]       ;ebx = lineare Adresse der idt
            mov [idtr+2],ebx
    
    ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
    ;       Jetzt in den Protect Mode
    ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
    
            lgdt [gdtr]
            lidt [idtr]
    
            mov eax,cr0
            or al,1
            mov cr0,eax
    
            jmp  Selektor01:Go
    
    ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
    ;       
    ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
    
    [BITS 32]
    
    Go:     mov ax,Selektor02       ;DS
            mov ds,ax
    
            mov ax,Selektor03       ;
            mov es,ax
    
    ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
    ;
    ; Hier sind die Grunddaten                                          ;
    ;
    ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
    
    ;Parameter der Globalen Deskriptor Table
    
    gdtr:   dw      gdt_ende-gdt-1  ;Die GrӇe der gdt
            dd      gdt             ;Die Adresse der gdt
    
    ;Parameter der Interrupt Deskriptor Table
    idtr:   dw      idt_ende-idt-1  ;Die GrӇe der idt
            dd      idt             ;Die Adresse der idt
    
    ;Hilfstabelle fr die Selektoren
    
    gdt:
    
    Sel00:  dw 0            ;Der Null Deskriptor
            dw 0
            db 0
            db 0
            db 0
            db 0
    
    Sel01:  dw 0xffff       ;Fr das CS  (Protect Mode)
            dw 0            ;Wird beim Start Up gesetzt
            db 0            ;auch
            db 0x9a         ;Present,Ring 0,Code,Non-Conforming,Readable
            db 0xcf         ;Page-Granular,32-Bit
            db 0
    
    Sel02:  dw 0xffff       ;Fr das DS  (Protect Mode)
            dw 0            ;Wird beim Start Up gesetzt
            db 0            ;auch
            db 0x92         ;Present,Ring 0,Data,Expant Up,Writeble
            db 0xcf         ;Page-Granular,32-Bit
            db 0
    
    Sel03:  dw 0xffff       ;Fr das DS  (Protect Mode) Linear Modus
            dw 0            ;
            db 0            ;
            db 0x92         ;Present,Ring 0,Data,Expant Up,Writeble
            db 0xcf         ;Page-Granular,32-Bit
            db 0
    
    Sel04:  dw 0xffff       ;Fr das DS  (Real Mode)
            dw 0            ;
            db 0            ;
            db 0x92         ;Present,Ring 0,Data,Expant Up,Writeble
            db 0xcf         ;Byte-Granular,16-Bit
            db 0
    
    Sel05:  dw 0xffff       ;Fr das CS  (Real Mode)
            dw 0            ;Wird beim Start Up gesetzt
            db 0            ;auch
            db 0x9a         ;Present,Ring 0,Code,Non-Conforming,Writeble
            db 0xcf         ;Byte-Granular,16-Bit
            db 0
    
    Sel06:  ;dw s_tss_e-s_tss_a   ;Der Selektor fr das TSS
            dw 0            ;Wird beim Start Up gesetzt
            db 0            ;auch
            db 0xe9         ;present, ring 3,32 Bit,avilable TSS
            db 0
            db 0
    
    gdt_ende:
    
    ;Hilfstabelle fr die Selektoren
    
    Selektor00 equ Sel00-gdt
    Selektor01 equ Sel01-gdt
    Selektor02 equ Sel02-gdt
    Selektor03 equ Sel03-gdt
    Selektor04 equ Sel04-gdt
    Selektor05 equ Sel05-gdt
    Selektor06 equ Sel06-gdt
    Selektor07 equ Sel07-gdt
    Selektor08 equ Sel08-gdt
    Selektor09 equ Sel09-gdt
    
    ;und hier die Interrupt Deskriptor Table
    idt:
            dw Int_00               ; entry point 
            dw Selektor01           ; selector
    	db 0			; word count
    	db 0x8E			; type (32-bit Ring 0 interrupt gate)
    	dw 0			; entry point 31:16 (XXX - unhand >> 16)
    
            dw Int_01
            dw Selektor01
    	db 0
    	db 0x8E
    	dw 0
    
            dw Int_02
            dw Selektor01
    	db 0
    	db 0x8E
    	dw 0
    
    idt_ende
    
            dd 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0
            dd 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0
            dd 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0
            dd 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0
    Stapel:
    ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
    


  • These exemple the program which install PC in the protected mode and realize two tasks.

    ;name file pm.asm
    ; tasm /m pm.asm
    ; tlink /x /3 pm.obj

    .386p
    Stack_seg segment para stack 'STACK'

    stack_task1 db 32h dup(?)
    stack1 = $-stack_task1

    stack_task2 db 32h dup(?)
    stack2 = $-stack_task1

    Stack_seg ends

    code_seg segment para public 'CODE' use16
    assume cs:code_seg, ds:data_seg, ss:Stack_seg

    start:
    push data_seg
    pop ds

    mov ax, code_seg
    shl eax, 4
    mov word ptr g_code + 2, ax ;mladwij
    shr eax, 16
    mov byte ptr g_code + 4, al ; starwij

    mov ax, data_seg
    shl eax, 4
    mov word ptr g_pmc+2, ax
    shr eax, 16
    mov byte ptr g_pmc+4, al

    mov eax, 0h
    mov ax, data_seg
    shl eax, 4
    push eax
    add eax, offset gdt
    mov dword ptr gdtr+2, eax

    lgdt fword ptr gdtr

    pop eax
    push eax

    add eax, offset TSS_0
    mov word ptr g_TSS0+2, ax
    shr eax, 16
    mov byte ptr g_TSS0+4, al

    pop eax

    add eax, offset TSS_1
    mov word ptr g_TSS1+2, ax
    shr eax, 16
    mov byte ptr g_TSS1+4, al

    BIOS of adress 0040h:0067h
    push ds
    mov ax, 40h
    mov ds, ax
    mov ds:67h, offset Real_return
    mov ds:69h, cs
    pop ds

    cli

    mov al, 8fh
    out 70h, al
    jmp a1

    a1:
    mov al, 05h
    out 71h, al

    mov eax, cr0
    or al, 1
    mov cr0, eax

    db 66h

    db 0EAh ; kod far jmp
    dd offset a2 ; metku a2
    dw 18h ; segment code

    LABEL Real_return FAR
    mov ax, data_seg
    mov ds, ax
    mov es, ax
    mov ax, stack_seg
    mov bx, stack1
    mov ss, ax
    mov sp, bx

    sti
    in al, 70h
    and al, 07FH
    out 70h,al

    mov ah, 4Ch
    int 21h

    code_seg ends

    data_seg segment para public 'CODE' use32
    assume cs:data_seg

    ; GDT
    gdt label byte
    g_0 db 8 dup(0) ; nulivoj deskriptor
    g_data db 0FFh, 0FFh, 0,0,0, 10010010b, 01001111b, 0 ; dannix segment
    g_code db 0FFh, 0FFh, 0,0,0, 10011010b, 0, 0 ; code segment
    g_pmc db 0FFh, 0FFh, 0,0,0, 10011010b, 01001111b, 0 ; code segment
    g_stack db 0FFh, 0FFh, 0,0,0, 10010010b, 01001111b, 0 ; Stack segment
    g_TSS0 db 067h, 0, 0,0,0, 10001001b, 01000000b, 0 ; TSS0 segment
    g_TSS1 db 067h, 0, 0,0,0, 10001001b, 01000000b, 0 ; TSS1 Segment
    ; GDT razmer
    gdt_size = $-gdt

    ; GDT register
    gdtr dw gdt_size-1 ; GDT limit
    dd ? ; GDT base

    TSS_0 db 68h dup(0)

    TSS_1 dd 0,0,0,0,0,0,0,0 ; Link; Stack 0 - 2
    dd offset task_1 ; IP - opinting to 'TASK_1'
    dd 0,0,0,0,0
    dd stack2 ; SP - stack2
    dd 0,0 ; BP, SI
    dd 0B8000h ; DI - Video memory start
    dd 0 ; ES
    dd 18h ; CS - Code segment selector (PM)
    dd 20h ; SS - 32b Stack selector
    dd 8h ; DS - Data Segment selector
    dd 0,0
    dd 0 ; LDTR
    dd 0

    a2:
    mov eax, 0h
    mov ax, 8h ; Data Segment Selector
    mov ds, ax
    mov es, ax
    mov ax, 20h ; stack selector
    mov ebx, stack1 ;
    mov ss, ax
    mov esp, ebx

    mov eax, 0h
    mov cx, 0h
    mov edi, 0B8000h ; adress video memory

    mov ax, 28h ; TSS_0 Selector
    ltr ax ; load v TR

    task_0:
    mov ah, 07h
    mov al, 'a'
    mov word ptr ds:[edi - 2],ax ;

    db 0EAh
    dd 0
    dw 30h ; TSS_1 selector

    add edi, 2
    inc cx
    cmp cx, 20 ;
    jne task_0

    null_idt dw 0
    dw 0
    db 0
    db 0
    dw 0
    lidt [fword ptr null_idt]
    int 3h

    wait_reset:
    hlt
    jmp wait_reset

    task_1:
    mov ah,07h
    mov al, 'b'
    mov word ptr ds:[edi + 160],ax

    add edi,2
    pop bx

    db 0EAh
    dd 0
    dw 28h ; TSS2 Selector

    mov ecx, 00100000h ; pause
    loop $
    jmp task_1

    data_seg ends
    end start


Anmelden zum Antworten