www.xbdev.net
xbdev - software development
Thursday March 28, 2024
home | contact | Support | Assembly Language What every pc speaks..1010...
>>
     
 

Assembly Language

What every pc speaks..1010...

 

Protected Mode - Getting Time From CMOS Chip!

by bkenwright@xbdev.net

 

 

Bit by bit we can keep adding things to our small kernal/program...one such little thing thats worth adding is the ability to get and set the CMOS motherboard date and time values.  Its simply a matter of reading and writing to ports 70h and 71h..

First let me show you a couple of C functions for reading and writing to the RTC (Real Time Clock) CMOS Chip clock on the motherboard.  By writing or reading different values to port 70h and 71h you can read or write the year, month, day, second, etc.

 

 

char ReadRTC (char Register)
{
(*      Read one byte from specified register from RTC      *)
    char Result;
    __ASM

       {
        MOV   AL, Register
        OUT   70H, AL
        IN    AL, 71H
        MOV   AH, 00
        MOV   Result, AX
    }
    RETURN Result

} // ReadRTC;
 

void WriteRTC (char Register, char Value)
{
(*      Write Value to specified Register of RTC            *)

    __ASM

       {
        MOV   AL, Register
        OUT   70H, AL
        MOV   AL, Value
        OUT   71H, AL
    }

 

} // WriteRTC;
 

 

Just to note, if your in DOS, you can also get the dos time and date by using interrupt 32 (int 21h).

 

Register    Value

0               Second

2               Minute

4               Hour

6               DoW

7               Day

8               Month

9               Year

50             Century

 

 

Basically here is what our whole program outputs to our screen...of course when you run it on your computer it will be in colour...the [OK] text will be green etc.

 

Screen Output
@
[ 32 bits OK ]
B 32 Bit Protected Mode!..$
Working in 32 BIT Mode [ Loaded OK ]
Now Time: 15:53:41
Now Date: 06:07:2005
Disabling IRQ's.................[ OK ]
ReMapping the PIC's.............[ OK ]
Turning Interrupts back on......[ OK ]
Going into infinite loop........
Where good to go..

 

 

 

Here is our datetime file which contains all our time and date functions.

 

Download File (Click Here) - datetime.inc
;========================================================;
;                                                        ;
; datetime.inc                                           ;
;                                                        ;
;========================================================;
;                                                        ;
; Simple set of functions for reading and writing the    ;
; CMOS motherboard time and date values.                 ;
;                                                        ;
;========================================================;
;                                                        ;
; All the functions are self contained within this file. ;
; The only externals are:                                ;
; print_str                                              ;
; print_char                                             ;
; Which are declared in text.inc                         ;
;                                                        ;
;========================================================;


;========================================================;
; Data Values                                            ;
;========================================================;

hour:      db 0
minute:    db 0
second:    db 0

century:   db 0
year:      db 0
month:     db 0
day:       db 0

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


date:
    push  ds 
    push  es
	pusha
    cli
	mov   al,32h			                 ; RTC 32h
	out   70h,al
	in    al,71h			                 ; read century
	mov   [century],al
	mov   al,9			                 ; RTC 09h
	out   70h,al
	in    al,71h			                 ; read year
	mov   [year],al
	mov   al,8			                 ; RTC 08h
	out   70h,al
	in    al,71h			                 ; read month
	mov   [month],al
	mov   al,7			                 ; RTC 07h
	out   70h,al
	in    al,71h			                 ; read day
	mov   [day],al
    sti
    popa
    pop   es 
    pop   ds
    ret

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

time:
    push  ds 
    push  es
	pusha
    cli
	mov   al,4			                 ; RTC  04h
	out   70h,al
	in    al,71h			                 ; read hour
	mov   [hour],al
	mov   al,2			                 ; RTC  02h
	out   70h,al
	in    al,71h			                 ; read minute
	mov   [minute],al
	xor   al,al			                 ; RTC  00h
	out   70h,al
	in    al,71h			                 ; read second
	mov   [second],al
    sti
    popa
    pop   es 
    pop   ds

    ret

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

msgTimeError db 'Error Setting New Time...', 0x00

set_time:			                
    push  ds 
    push  es
	pusha
    cli
	mov   bl,59h
    mov   al,[second]
	call  check_bcd_time		                 ; check second number
    mov   al,[minute]
	call  check_bcd_time		                 ; check minute number
	mov   bl,23h
    mov   al,[hour]
	call  check_bcd_time		                 ; check hour number
    xor   al,al			                 ; RTC 00h
	out   70h,al
	mov   al,[second]
	out   71h,al			                 ; write second
	mov   al,2			                 ; RTC 02h
	out   70h,al
	mov   al,[minute]
	out   71h,al			                 ; write minute
	mov   al,4			                 ; RTC 04h
	out   70h,al
	mov   al,[hour]
	out   71h,al			                 ; write hour
        jmp   leave1
time_error:
        mov   esi,msgTimeError
        call  print_string
leave1:
        sti
        popa
        pop   es 
        pop   ds

        ret

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

msgDateError db 'Error Setting New Date....', 0x00

set_date:
    push  ds 
    push  es
	pusha
    cli
    mov   al,[day]	
	mov   bl,31h
	or    al,al			                 ; day cannot be 0
	jz    date_error
	call  check_bcd_date		                 ; check day number
	mov   bl,12h
    mov   al,[month]
	or    al,al			                 ; month cannot be 0
	jz    date_error
	call  check_bcd_date		                 ; check month number
	mov   bl,99h
    mov   al,[year]
	call  check_bcd_date		                 ; check year number
    mov   al,[century]
	call  check_bcd_date		                 ; check century number
    mov   al,7			                 ; RTC 07h
	out   70h,al
	mov   al,[day]
	out   71h,al			                 ; write day
	mov   al,8			                 ; RTC 08h
	out   70h,al
	mov   al,[month]
	out   71h,al			                 ; write month
	mov   al,9			                 ; RTC 09h
	out   70h,al
	mov   al,[year]
	out   71h,al			                 ; write year
	mov   al,32h			                 ; RTC 32h
	out   70h,al
	mov   al,[century]
	out   71h,al			                 ; write century
    jmp   leave2
date_error:
        mov   esi,msgDateError
        call  print_string
leave2:
        sti
        popa
        pop   es 
        pop   ds

        ret


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

msgTime db 'Now Time: ', 0x00

print_time:
        push  es
        pusha
        mov   esi,msgTime
        call  print_string
        call  time
        mov   al,[hour]
        call  bcd_to_ASCII
        mov   bx,[val]
        mov   al,bl
        call  print_char
        mov   al,bh
        call  print_char
       
        mov   al,":"
        call  print_char
  
        mov   al,[minute]
        call  bcd_to_ASCII
        mov   bx,[val]
        mov   al,bl
        call  print_char
        mov   al,bh
        call  print_char

        mov   al,":"
        call  print_char
   
        mov   al,[second]
        call  bcd_to_ASCII
        mov   bx,[val]
        mov   al,bl
        call  print_char
        mov   al,bh
        call  print_char
        
        call carriage_return
        popa
        pop   es
        ret

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

msgDate db 'Now Date: ', 0x0

print_date:
        push  es
        pusha
        mov   esi,msgDate
        call  print_string
        call  date
        mov   al,[day]
        call  bcd_to_ASCII
        mov   bx,[val]
        mov   al,bl
        call  print_char
        mov   al,bh
        call  print_char
       
        mov   al,":"
        call  print_char
  
        mov   al,[month]
        call  bcd_to_ASCII
        mov   bx,[val]
        mov   al,bl
        call  print_char
        mov   al,bh
        call  print_char

        mov   al,":"
        call  print_char
   
        mov   al,[century]
        call  bcd_to_ASCII
        mov   bx,[val]
        mov   al,bl
        call  print_char
        mov   al,bh
        call  print_char
        mov   al,[year]
        call  bcd_to_ASCII
        mov   bx,[val]
        mov   al,bl
        call  print_char
        mov   al,bh
        call  print_char
        
        call carriage_return
        popa
        pop   es
        ret

;========================================================;
; Converts a bcd number to ASCII                         ;
;========================================================;
; al - bcd number                                        ;
; val - output ascii char                                ;
;========================================================;
	
val  dd 0x0
	
bcd_to_ASCII:
       pusha                                            ;start of convert
       mov  ah,al                                       ;copy AL to AH
       and  ax,0f00fh                                   ;mask bits
       mov  cl,4                                        ;CL=04 for shift
       shr  ah,cl                                       ;shift right AH to get unpacked BCD
       or   ax, 3030h                                   ;combine with 30 to get ASCII
       xchg ah,al                                       ;swap for ASCII storage convention
       mov  [val],ax                                    ;store the ASCII value in VAL
       popa 

       ret


;=======================================================;
; Checks we have a bcd number for our date              ;
;=======================================================;
	
check_bcd_date:
	cmp   al,bl
	ja    date_error
	and   al,0Fh
	cmp   al,9
	ja    date_error
	ret
	
;=======================================================;
; Check to see we have a bcd number for our time        ;
;=======================================================;

check_bcd_time:
        cmp   al,bl
	ja    time_error
	and   al,0Fh
	cmp   al,9
	ja    time_error
	ret

 

 

Download Code (Click Here) - misc.inc
;========================================================;
;                                                        ;
; misc.inc                                               ;
;                                                        ;
;========================================================;
;                                                        ;
; Simple set of functions for various tasks, such as     ;
; delays, setting leds, debugging etc.                   ;
;                                                        ;
;========================================================;


;-------------------------------------------------------------------
; Small delay loop
; on a p4 2ghz its about 4 seconds :)
;-------------------------------------------------------------------
small_delay:
push eax
push ebx
push ecx

mov eax, 1000
xloop:

mov ebx, 200
yloop:

mov ecx, 100 
zloop:
      dec ecx     
      jne zloop  

      dec ebx     
      jne yloop  

      dec eax     
      jne xloop  

pop ecx
pop ebx
pop eax      
      ret
;------------------------------------------------------------------

 

 

And here is what our main code looks like:

 

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.
%include 'include\datetime.inc'    ; 32-bit. Get/Set CMOS date time 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

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

call time      ; get time values (datetime.inc)
call date      ; get date values (datetime.inc)

call print_time
call print_date



; 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 0x1500-($-$$) DB 0x90    ; And of course, this will make our file size
                             ; equal to 0x1500 a nice round number -
                             ; 0x1500 ... 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.