www.xbdev.net
xbdev - software development
Friday April 19, 2024
home | contact | Support | Assembly Language What every pc speaks..1010...
>>
     
 

Assembly Language

What every pc speaks..1010...

 

Protected Mode - Add some order (Txt Functions, Debug Info..)

by bkenwright@xbdev.net

 

 

Our graphics output is a pit basic at the moment...sort of just poking small characters onto the screen as we progress....so I've started tidying things up...putting together another asm file called 'text.inc'...which can be included in our main asm file by simple using the keywork '%include" followed by the location of the file.  The file, even though ending with ".inc" is simply an asm file.  Its an indipendent txt file which we can use in 32 bit mode to put strings to the screen etc, so we can show progress a little better.

We'll probably start putting all our parts in seperate files, such as all our interrupt functions in one, pic in another, txt functions in one file...so its easier to debug and expand on :)

 

What might be worth looking at, is that when we put anything to the screen, we use our linear memory descriptor...which has a base memory value of 0x0, so our offset to the screen buffer of 0xBA000 is correct.

 

Assembly Code (Click Here) - text.inc
;=========================================================;
;                                                         ;
; Text Functions                                          ;
;                                                         ;
;---------------------------------------------------------;
; text.inc is an independent file, and doesn't require    ;
; any external functions or resources.  All data and      ;
; workings are all kept within the file.                  ;
; Most of the functions are independent and will work on  ;
; there own, with the exception of one or two which use   ;
; carrage return and things.                              ;
;                                                         ;
; Text mode functions for uses in programs.               ;                          
;=========================================================;

[BITS 32]

align 4


 ;----------------------------------------------------;
 ; Data.                                              ;
 ;----------------------------------------------------;


textcolor         db 0x09
screen_x          db 0
screen_y          db 0

align 4

 ;----------------------------------------------------;
 ; Sets the text pos                                  ;
 ;----------------------------------------------------;

set_text_pos:
	mov   [screen_x],al
	mov   [screen_y],ah
	ret

 ;----------------------------------------------------;
 ; TextColor                        ; Sets text color ;
 ;----------------------------------------------------;

TextColor:
        mov   byte[textcolor],al
        ret


 ;----------------------------------------------------;
 ; Inc screen pointer                                 ;
 ;----------------------------------------------------;

inc_scr_pointer:
	push  eax
	cld
	mov   al,[screen_x]
	cmp   al,79                  
	jb    no_incy
	call  carriage_return
	jmp   dend
no_incy:
	inc   al
	mov   [screen_x],al
dend:	pop   eax
	ret

 ;----------------------------------------------------;
 ; Carriage return                       ; next line  ;
 ;----------------------------------------------------;

carriage_return:
	push  eax
	mov byte  [screen_x],0
	mov   ah,[screen_y]     
	cmp   ah,49                  
	jb    no_scroll
	call  scroll
	jmp   cend
no_scroll:
	inc   ah    
	mov   [screen_y],ah     
cend:	pop   eax
	ret


 ;----------------------------------------------------;
 ; Gets screen pointer                                ;
 ;----------------------------------------------------;

get_scr_pointer:                                     
	push  eax                                          
	push  ebx
    xor   ebx,ebx

	mov   bl,[screen_x]
	shl   ebx,1
	add   edi, ebx
	mov   bl,[screen_y]
	mov   eax,0xa0
	mul   bx
	add   edi,eax
    pop   ebx
	pop   eax
       
	ret


 ;'''''''''''''''''''''''''''''''''''''''''''''''''''';
 ; Prints char               ; print's a char from al ;
 ;----------------------------------------------------;
 ;                                                    ;
 ;  Input:                                            ;
 ;      Al Ascii character to write.                  ;
 ;                                                    ;
 ; Output:                                            ;
 ;      None.                                         ;
 ;....................................................;

print_char:
	pushad                                   
	push  es
	push  gs
    cli
    push   ax
    mov   ax,18h  ; linear memory area selector
	mov   gs,ax                          
    pop   ax	
    mov   edi,0xb8000
	call  get_scr_pointer
    mov   ah,[textcolor]
	mov   [gs:edi],ax                    
	call  inc_scr_pointer
    sti
    pop   gs
	pop   es
    popad
    ret

 ;'''''''''''''''''''''''''''''''''''''''''''''''''''';
 ; Prints string      ; does what it say's on the box ;
 ;----------------------------------------------------;
 ;                                                    ;
 ;  Input:                                            ;
 ;      es:esi points to asciiz string to write.      ;
 ;                                                    ;
 ; Output:                                            ;
 ;      None.                                         ;
 ;....................................................;

print_string:
    pushad                                   
	push  es
	push  ds
aloop:
    mov   al,[ds:esi]
    cmp   al,0				           ; 0x00 = end of string
	je    gend
    cmp   al,0xd2                      ; 0xd2 = next byte is color byte
    je    ColorChange
	cmp   al,0x0d                      ; 0x0d = CR ( = \n )
	jne   no_cr
	call  carriage_return
	jmp   a1
ColorChange:
    inc   esi
    mov   al,[esi]
    mov   byte[textcolor],al
    inc   esi
    jmp   aloop
no_cr:
    ;mov   eax, esi
    ;mov   al, [esi]
	call  print_char
a1:	inc   esi
    jmp   aloop
gend:
	pop   ds
	pop   es
    popad
	ret


 ;----------------------------------------------------;
 ; write hex 32        ;prints a hex number from eax. ;
 ;----------------------------------------------------;

write_hex32:
	pushad
	mov   ebx,eax
loop1:
	rol   eax,8		                           
	call  write_hex16
	cmp   eax,ebx		                           
	jne   loop1
	popad
	ret

 ;----------------------------------------------------;
 ; write hex 16        ;prints a hex number from  al. ;
 ;----------------------------------------------------;

write_hex16:
	push  eax
	push  eax
	shr   al,4		                           
	call  hexget		                          
	call  print_char
	pop   eax
	call  hexget		                           
	call  print_char
	pop   eax
	ret


 ;----------------------------------------------------;
 ; Scroll                      ; scroll's screen up 1 ;
 ;----------------------------------------------------;
 ;                                                    ;
 ;   Input:                                           ;
 ;          none.                                     ;
 ;  Output:                                           ;
 ;          none.                                     ;
 ;....................................................;

scroll:
    pushad
    push  gs
    push  es
    push  ds
    mov   ax,0x18  ; select linear memory mapping
	mov   gs,ax  
    mov   al,0
	mov   ah,49           
    call  set_text_pos
	mov   edi,0xb8000
    add   edi,80*2*4 
    mov   esi,0xb8000
    add   esi,80*2*5 
	mov   ecx,80*46*2/4 
    cli
mloop:	
    mov   eax,[gs:esi]
	add   esi,4
	mov   [gs:edi],eax			
	add   edi,4
	dec   ecx
	jnz   mloop
    sti
    pop   ds
    pop   es
    pop   gs
	popad
	ret

 ;----------------------------------------------------;
 ; cls_text                     ; clear's full screen ;
 ;----------------------------------------------------;
 ;                                                    ;
 ;   Input:                                           ;
 ;          none.                                     ;
 ;  Output:                                           ;
 ;          none.                                     ;
 ;....................................................;

cls_text:
	push  eax
	push  ecx
	push  esi
	push  edi
    push  gs
    mov   ax,0x18    ; select the linear memory mapping
	mov   gs,ax
    cli
	mov   ecx,80*50     
	mov   edi,0B8000h
    mov   al," "		
	mov   bl,0Fh		
cls_loop:
	mov   byte [gs:edi],al
	inc   edi
	mov   byte [gs:edi],bl
	inc   edi
	dec   ecx
	jnz   cls_loop
	mov   [screen_x],byte 0
	mov   [screen_y],byte 4         
        sti
        pop   gs
	pop   edi
	pop   esi
	pop   ecx
	pop   eax
	ret

 ;----------------------------------------------------;
 ; hexget         convers from ASCII to hexadecimal.  ;
 ;----------------------------------------------------;

hexget:
	and   eax,0x0000000f
	or    eax,0x00000030
	cmp   eax,0x39
	ja    add7
	ret
add7:	add   eax,7		
	ret

 ;----------------------------------------------------;
 ; UpperCase.       ; converts a string to uppercase. ;
 ;----------------------------------------------------;
 ;                                                    ;
 ; es:edi = string buffer (0 termanated)              ;
 ;----------------------------------------------------;

UpperCase:
        pushad
        push  es
        mov   ax,0x10                               
        mov   es,ax    
UcaseNextChar:
        mov   al,byte[es:edi]
        cmp   al,0
        je    UcaseDone
        cmp   al,0x61
        jb    DontUcaseChar
        cmp   al,0x7a
        ja    DontUcaseChar
        sub   al,0x20
        mov   byte[es:edi],al  
DontUcaseChar:
        inc   edi
        jmp   UcaseNextChar
UcaseDone:
        pop   es
        popad
        ret
;------------------------------------------------------
 
 
 

 

 

And finally for our main program...the heart of our code...or should I say the kernal.

 

Download Code (Click Here) - asm_1.asm
; Run in dos (not under windows) and it will take us to 32 bit protected mode

[ORG 0x100]         ; Reserve 256 bytes for dos

[BITS 16]           ; Dos is 16 bits

; assemble using 'nasm' assemblaer

; C:>nasm asm_1.asm -o test.exe

jmp entry           ; Jump to the start of our code

msg1 db 'Where good to go..$';
msg2 db '32 Bit Protected Mode!..$',0x0d,0x0;

entry:

; Use the interrupt 0x10 to clear the screen!
mov ah,7     ; scroll down function
mov al,0     ; 0 = entire window
mov cx,0     ; 0,0 as upper left corner.
mov dx,184fh ; 24,79 as lower right corner.
mov bh,7     ; normal attribute
int 10h      ; call bios 
        
        
; Display a message showing where alive!

mov dx, msg1        ; register dx=msg1
mov ah, 9           ; register ah=9 -- the print string function
int 21h             ; dos service interrupt .. looks at register ah to figure out what to do

; Thanks from Brendan, as we have to make sure our GDTR points to the actual
; memory address, add code location and dos 0x100 onto our loaded offset 

    mov eax,0
    mov ax,cs
    shl eax,4
    mov   ebx,eax  
  
    mov   [codesel + 2],ax                                    
    mov   [datasel + 2],ax                                    
	
	shr   eax,16
	mov   [codesel + 4],al
	mov   [datasel + 4],al
	mov   [codesel + 7],ah
	mov   [datasel + 7],ah
	
	mov   eax, ebx
	
    add [gdtr+2],eax
    add [idtr+2],eax         ; set idtr and gdtr so it points to the 'real' address in memory

;---------------------------------------------------------------------------

  cli		    ; Clear or disable interrupts
  
  mov     al, 0x70
  mov     dx, 0x80
  out     dx, al      ; outb(0x80, 0x70) - disable NMI (Non Maskable Interupts)          

  lgdt[gdtr]	    ; Load GDT
  
  lidt[idtr]       ; Load IDT

  
  mov eax,cr0	    ; The lsb of cr0 is the protected mode bit
  or al,0x01	    ; Set protected mode bit
  mov cr0,eax	    ; Mov modified word to the control register

jmp   0x8:go_pm     ; The 0x8 is so we select our code segment from our gdtr


nop                 ; ignore - no operation opcodes :)
nop

align 4
;---------------------------------------------------------------------------
;                                 32 BIT
;---------------------------------------------------------------------------
; Once we reach here where in protected mode!  32 Bit!  Where not in
; the real world (mode) anymore :)
[BITS 32]
go_pm :

xor   edi,edi
xor   esi,esi

mov ax, 0x10        ; use our datasel selector ( alternatively mov ax, datasel-gdt )
mov ds, ax
mov ss, ax
mov es, ax
mov fs, ax

mov ax, 0x18
mov gs, ax

mov esp, 0afffh    ; we need a simple stack if where calling functions!
                   ; Such as interupt functions etc, as the return address is
                   ; put on the stack remember!


mov word [gs: 0xb8000],0x740 ; put a char to the screen!...yeahh!
                             ; '@' in the top left of the screen if we made it
                             ; here okay.

;=========================================================================
; Okay, its worth poking onto the screen a more descriptive message
; that we've made it to the 32 bit world!  We use this method of char by
; char poking first, but we'll use our text out functions later...just
; easier to see how it works :)
;=========================================================================
;
; Write '[ 32 bits OK   ]' at [gs:0B80A0h].
;
;-------------------------------------------------------------------------
  mov     byte [gs:0B80A0h], '['
  mov     byte [gs:0B80A1h], 02h              ; Assign a color code
  mov     byte [gs:0B80A2h], ' '
  mov     byte [gs:0B80A3h], 02h              ; Assign a color code
  mov     byte [gs:0B80A4h], '3'
  mov     byte [gs:0B80A5h], 02h              ; Assign a color code
  mov     byte [gs:0B80A6h], '2'
  mov     byte [gs:0B80A7h], 02h              ; Assign a color code
  mov     byte [gs:0B80A8h], ' '
  mov     byte [gs:0B80A9h], 02h              ; Assign a color code
  mov     byte [gs:0B80AAh], 'b'
  mov     byte [gs:0B80ABh], 02h              ; Assign a color code
  mov     byte [gs:0B80ACh], 'i'
  mov     byte [gs:0B80ADh], 02h              ; Assign a color code
  mov     byte [gs:0B80AEh], 't'
  mov     byte [gs:0B80AFh], 02h              ; Assign a color code
  mov     byte [gs:0B80B0h], 's'
  mov     byte [gs:0B80B1h], 02h              ; Assign a color code
  mov     byte [gs:0B80B2h], ' '
  mov     byte [gs:0B80B3h], 02h              ; Assign a color code
  mov     byte [gs:0B80B4h], 'O'
  mov     byte [gs:0B80B5h], 02h              ; Assign a color code
  mov     byte [gs:0B80B6h], 'K'
  mov     byte [gs:0B80B7h], 02h              ; Assign a color code
  mov     byte [gs:0B80B8h], ' '
  mov     byte [gs:0B80B9h], 02h              ; Assign a color code
  mov     byte [gs:0B80BAh], ' '
  mov     byte [gs:0B80BBh], 02h              ; Assign a color code
  mov     byte [gs:0B80BCh], ' '
  mov     byte [gs:0B80BDh], 02h              ; Assign a color code
  mov     byte [gs:0B80BEh], ']'
  mov     byte [gs:0B80BFh], 02h              ; Assign a color code

;=========================================================================

;-------------------------------------------------------------------------
; Simple functions included here
;-------------------------------------------------------------------------
jmp over_includes

%include 'include\text.inc'        ; 32-bit. Set default text functions.

msg_basic     db 0xd2,0x7,'Working in 32 BIT Mode [ ',0xd2,0x2, ' Loaded OK', 0xd2,0x7, ' ]',0x0d,0x0

msg_irqs_off     db   "Disabling IRQ's.................", 0x00
msg_remap_pics   db   "ReMapping the PIC's.............", 0x00
msg_sti_on       db   "Turning Interrupts back on......", 0x00
msg_loop         db   "Going into infinite loop........", 0x00

msg_ok        db 0xd2,0x2, "[ OK ]", 0xd2,0x7,0xd,0x0


over_includes:
;-------------------------------------------------------------------------

; 0x2 - green
; 0x7 - light grey
; 0x4 - red

mov al, 0x09
call TextColor

mov eax, 0x0
call set_text_pos

call carriage_return
call carriage_return

mov al, 'B'
call print_char

call inc_scr_pointer

mov esi, msg2
call print_string

mov esi, msg_basic
call print_string


; Force a call to interrupt 4!
; Int 0x4           ; We call our interrupt 4 subroutine

;-------------------------------------------------------------------------
; Divide by Zero Warning
;-------------------------------------------------------------------------
; Just remember, when we do a divide by zero, and the interupt is called,
; the return address passed to the interrupt, is in fact the address of the
; line that caused the interrupt!  So if we just return from the interrupt
; it would just keep causing the interrupt over and over again.
;-------------------------------------------------------------------------
; Do a divide by 0 error, so we force a call to our interrupt 0
;  mov eax, 0
;  mov ebx, 0
;  div ebx            ; eax divided by ebx, and stored back in eax

mov byte [es: 0xb8002], "A" ; poke a character onto our screen buffer

nop
nop

;-------------------------------------------------------------------------
; Where not in basics anymore!
;-------------------------------------------------------------------------
; This is the line where we go from simple settups, to using the computers
; interal hardward, fiddling around with the irqs and pic (Programmable
; Interupt Controller) etc.
;-------------------------------------------------------------------------

mov esi, msg_irqs_off
call print_string

; Disable all IRQs.
;-------------------------------------------------------------------------
disable_irqs:
          mov     al, 0xFF
          mov     dx, 0x21
          out     dx, al      ; outb(0x21, 0xFF)

          mov     al, 0xFF
          mov     dx, 0xA1
          out     dx, al      ; outb(0x21, 0xFF)
          
;-------------------------------------------------------------------------          

mov esi, msg_ok
call print_string

mov esi, msg_remap_pics
call print_string

;-------------------------------------------------------------------------
; ReMap PICs
;-------------------------------------------------------------------------
;   PIC 1 & 2 (Master and Slave)
;   Lower 8 IRQs 0x20 onwards
;   Higher 8 IRQs 0x28 onwards
;-------------------------------------------------------------------------
remap_pics:

     ; IWC1
     ;------
          mov     al, 0x11
          out     0x20, al      ; outb(0x20, 0x11)

          mov     al, 0x11
          out     0xA0, al      ; outb(0xA0, 0x11)
 
     ; IWC2
     ;------
          mov     al, 0x20
          out     21, al      ; outb(0x21, pic1)

          mov     al, 0x28
          out     0xA1, al      ; outb(0xA1, pic2)

     ; IWC3
     ;------
          mov     al, 0x04
          out     0x21, al      ; outb(0x21, 4)

          mov     al, 0x02
          out     0xA1, al      ; outb(0xA1, 2)

     ; IWC4
     ;------
          mov     al, 0x01
          out     0x21, al      ; outb(0x21, 0x01)

          mov     al, 0x01
          out     0xA1, al      ; outb(0xA1, 0x01)
;-------------------------------------------------------------------------

mov esi, msg_ok
call print_string
         
;-------------------------------------------------------------------------

; Every time an irq interupt occurs, we must clear it before another irq
; is sent.  Else another interupt wont' be sent till its been cleared.
; We usually call this at the end of our interupt routine.

;EOI for IRQ 0-7
mov     al, 0x20
        mov dx, 0x20
        out dx, al      ; outb(0x20, 0x20)
        
;-------------------------------------------------------------------------

mov esi, msg_sti_on
call print_string

;-------------------------------------------------------------------------

sti              ; Interrupts back..

;-------------------------------------------------------------------------

mov esi, msg_ok
call print_string

;-------------------------------------------------------------------------

mov esi, msg_loop
call print_string

lp: jmp lp  ; loops here forever and ever...

; Stays in our loop forever, till something happens, such as an interrupt
; is called by pressing a key or the timer calls an interrupt etc



; We use 16 bits here - as you'll notice we use dw and dd only,
; and out data will be packed together nice and tight.

[BITS 16]
align 4

;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
; Our GDTR register value
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;

gdtr :
   dw gdt_end-gdt-1    ; Length of the gdt
   dd gdt	       ; physical address of gdt

;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
; This is the start of our gdt
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
align 4

gdt:    
gdt0 		        ; 0x0
   dd 0		      
   dd 0                
codesel:            ; 0x8
   dw 0x0ffff	      
   dw 0x0000	       
   db 0x00             	
   db 0x09a	      
   db 0x0cf	       
   db 0x00	       
datasel:            ; 0x10
   dw 0x0ffff	       
   dw 0x0000	      
   db 0x00	       
   db 0x092
   db 0x0cf
   db 0x00
linearsel:          ; 0x18
   dw 0x0ffff	       
   dw 0x0000	      
   db 0x00	       
   db 0x092
   db 0x0cf
   db 0x00
gdt_end:

;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;

align 4
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
; Our IDTR register value
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;

idtr :
   dw idt_end - idt_start - 1  ; Length of the idt
   dd idt_start                ; physical address of idt

;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
; This is the start of our idt - its actual value
;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
;-------------------------------------------------------------------------
[BITS 16]
align 4

idt_start:
%rep 256                         ; We have enough room for 256 ISRs
        dw intfunc               ; offset 15:0
        dw 0x0008                ; selector
        dw 0x8E00                ; present,ring 0,386 interrupt gate
        dw 0                     ; offset 31:16
%endrep
idt_end:

;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
;-------------------------------------------------------------------------
;                        Interrupt Routine
;-------------------------------------------------------------------------
[bits 32]
align 4

intfunc:
pushad
push es

nop
mov ax,0x10
mov es,ax
                           
mov byte [es: 0xb8012], "I" ; poke a character into the graphics output screen

pop es
popad
iret



;-------------------------------------------------------------------------

TIMES 0x1000-($-$$) DB 0x90    ; And of course, this will make our file size
                             ; equal to 0x1000 a nice round number -
                             ; 0x1000 ... so if you assemble the file
                             ; you should find its that size exactly.


;-------------------------------------------------------------------------

 

 

 

 

 

 

 

 

 

 

 
Advert (Support Website)

 
 Visitor:
Copyright (c) 2002-2024 xbdev.net - All rights reserved.
Designated articles, tutorials and software are the property of their respective owners.