I want to change text and background color without clearing the screen. Ive used this code but it always clear the screen.

mov ah, 2   ; use function 2 - go to x,y
mov bh, 0   ; display page 0
mov dh, 0   ; y coordinate to move cursor to
mov dl, 0   ; x coordinate to move cursor to
int 10h ; go!

mov ah, 0ah
mov cx, 1000h
mov al, 20h
mov bl, 17h ;color
int 10h
jmp cmd

Recommended Answers

All 12 Replies

The main thing that is happening is that you need to advance the coordinates as you write to them. If you are always writing to (0,0), you'll constantly overwrite what you you had previously put there.

I would add that if you do it this way, you'll need to track the horizonal width of the page to make sure you are writing to a valid location. You can get the width of the page using the 0Fh function.

Also, to change the character attributes as well as the character glyph, you need to use the 09h function, not 0Ah.

Finally, by setting CX to 1000h, you are directing it to repeat itself for 4096 characters, which will indeed overwrite the whole page. That is doubtlessly what is actually clearing the page.

oh sorry, that should be 09h. I already change the coordinate. But my problem here is that when i change the cursor coordinate, it will only replace the color below that coordinates.

I want to do here is that, when i type the command c:>blue
it should make the background blue and the text white without erasing the content of the screen. tnx for the help.

here are my codes:

kernel.asm

BITS    16

buffer  equ 24576

Main:
cli
mov ax, 0x0000
mov ss, ax
mov sp, 0xFFFF
sti

mov ax, 2000h
mov ds, ax
mov es, ax
mov fs, ax
mov gs, ax

mov [BootDrive], dl

setup_bg:
mov dx, 0
call    move_cursor

mov ah, 09h
mov al, ''
mov bh, 0
mov bl, 00000111b
mov cx, 2400
int 10h

mov si, version
call    Print

call    newline

mov si, copyright
call    Print

cmd:
call newline

mov si, prompt
call    Print

mov di, input_buffer

mov al, 0
mov cx, 256
rep stosb

mov ax, input_buffer
mov di, input_buffer

.loop:
call    keyboard

cmp al, 13      ;ENTER
je  .done

cmp al, 8       ;BACKSPACE
je  .backspace

jmp .character

.backspace:
mov ah, 0Eh
mov al, 8
int 10h
mov al, 32
int 10h
mov al, 8
int 10h
dec di
jmp .loop

.character:
mov ah, 0Eh
int 10h
stosb
jmp .loop

.done:
mov ax, 0
stosb

call    newline

mov si, input_buffer
cmp BYTE [si], 0

je  cmd

;All built-in commands
mov di, help_string
call    compare
jc  help

mov di, help_uc
call    compare
jc  help

mov di, dir_string
call    compare
jc  dir

mov di, dir_uc
call    compare
jc  dir

mov di, exit_string
call    compare
jc  exit

mov di, exit_uc
call    compare
jc  exit

mov di, color_blue
call    compare
jc  blue

;what if it's not a built-in command?
mov si, input_buffer
call    Print

mov si, no_command
call    Print

jmp cmd

%INCLUDE "variables.asm"
%INCLUDE "functions.asm"
%INCLUDE "cli_commands.asm"

cli_commands.asm

dir:
pusha
mov di, dirlist

call    reset_floppy

mov ch, 0
mov cl, 2
mov dh, 1
mov bx, buffer
mov al, 14
mov ah, 2
pusha

load_root:
int 13h
jnc loaded_root
call    reset_floppy
jmp load_root

loaded_root:
popa
mov si, buffer

compare_entry:
mov al, [si+11]
cmp al, 0Fh         ;Windows marker
je  .skip_entry
cmp al, 18h         ;Directory marker
je  .skip_entry
cmp al, 229         ;deleted file
je  .skip_entry
cmp al, 0
je  .done

mov dx, si
mov cx, 0

.save_character:
mov BYTE al, [si]
cmp al, ' '
je .space
mov BYTE [di], al
inc di
inc si
inc cx
cmp cx, 8
je .add_dot
cmp cx, 11
je  .string_copied
jmp .save_character

.add_dot:
mov BYTE [di], '.'
inc di
jmp .save_character

.space:
inc si
inc cx
cmp cx, 8
je  .add_dot
jmp .save_character

.string_copied:
mov BYTE [di], ','
inc di
mov si, dx

.skip_entry:
add si, 32
jmp compare_entry

.done:
mov si, dirlist
mov ah, 0Eh

.print:
lodsb
cmp al, 0
je  .done_printing
cmp al, ','
je  .comma
int 10h
jmp .print

.comma:
call    newline
jmp .print

.done_printing:
popa
jmp cmd

help:
mov si, help_message
call    Print
jmp cmd

blue:

mov ah, 2   ; use function 2 - go to x,y
mov bh, 0   ; display page 0
mov dh, 0   ; y coordinate to move cursor to
mov dl, 0   ; x coordinate to move cursor to
int 10h ; go!

mov ah, 09h
mov cx, 1000h
mov al, 20h
mov bl, 17h ;color
jmp cmd

exit:
mov ax, 5307h
mov cx, 3
mov bx, 1
int 15h

functions.asm

newline:
pusha
mov ah, 0eh
mov al, 13
int 10h
mov al, 10
int 10h
popa
ret

Print:
lodsb
cmp al, 0
je  Done
mov ah, 0eh
int 10h
jmp Print

Done:
ret

move_cursor:
pusha
mov ah, 02h
mov bh, 0
int 10h
popa
ret

keyboard:
pusha
mov ax, 0
mov ah, 10h
int 16h
mov [.buffer], ax
popa
mov ax, [.buffer]
ret

.buffer dw 0

compare:
pusha

.loop:
mov al, [si]
mov ah, [di]

cmp al, ah
jne .not_equal

cmp al, 0
je  .equal

inc si
inc di
jmp .loop

.not_equal:
popa
clc
ret

.equal:
popa
stc
ret

reset_floppy:
mov ax, 0
mov dl, BYTE [BootDrive]
int 13h
ret

variables.asm

exit_string db  'exit',0
exit_uc     db  'EXIT',0
dirlist         times 1500  db  0
dir_string  db  'dir',0
dir_uc      db  'DIR',0
no_command  db  ' is not recognized as internal or external command.',0
help_uc     db  'HELP',0
help_string db  'help',0
input_buffer    times   256 db 0
prompt      db  'C:\>',0
version     db  'EISSET LIWAG [version 1.0]',0
copyright   db  '(C) Copyright 2014-2015 Eisset Liwag',0
help_message    db  'HELP',9,9,9,'Show this message',13,10,'DIR',9,9,9,9,'Display a list of files in a directory',13,10,'EXIT',9,9,9,'Shutdown the computer',0
BootDrive   db  0
color_blue  db  'blue',0

Ah, this explains a few this. OK, a few points I should make regarding the writing of a boot loader like this, before I answer your problem. You might want to look at my bootloader, which is for NASM. You should also read as much as you can from the OS Dev Wiki, to see what your code is actually doing and get an idea of what you actually want.

First off, you'll need to tell us what assembler you are using, as there are subtle differences between the different ones.

Second, you don't seem to be assembling this to be loaded at 0000:7c00h, which is where the BIOS loads the loader to; as such, it shouldn't work at all. How are you running the program? How are you writing it to the boot disk? Are you using an emulator like Bochs or QEMU to run this, or is running on live hardware?

If this is meant to be a DOS or Windows program, then the code you have is completely inappropriate for that purpose.

Assuming this is indeed meant to be a boot loader, you will need to add the line

[ORG 7c00h]

at the very beginning of the code.

Third, while you have some code for reading from the disk, you don't seem to actually be loading your command interpreter as a second stage; instead, you are including it in with the boot loader itself. Again, that shouldn't be working, as it would exceed the 512 byte maximum size for the bootstrap. Similarly, you aren't setting the end of the last word of the bootstrap to AA55h, which would be required for a boot loader.

Fourth, once you do have it loading a second stage, I would recommend moving the command interpreter to there, and not have any print-out from the boot loader itself beyond a simple check (something like 'booting...'). While I have some printouts in my bootloader, they are mostly there to ensure that each step was working; in practice, I would eventually remove them.

OK, to address the question, I would that, to preserve the text already there when you change the color, I would recommend one of two approaches. Either you can read the character in and write it back out with the new attribute, or you can bypass the BIOS entirely and write directly to the text video memory starting at 000b:8000, writing the new attribute to every other byte.

here is my bootloader. and im using a NASM as my assembler and i use virtual floppy drive and BOCHs. Tnx again sir.

Bits    16
jmp Main

convert_sector:
push    bx
push    ax
mov bx, ax
mov dx, 0
div WORD [SectorsPerTrack]
add dl, 01h
mov cl, dl
mov ax, bx
mov dx, 0
div WORD [SectorsPerTrack]
mov dx, 0
div WORD [Sides]
mov dh, dl
mov ch, al
pop ax
pop bx
mov dl, BYTE [BootDrive]
ret

SectorsPerTrack dw  18
Sides   dw  2

reset_floppy:
mov ax, 0
mov dl, BYTE [BootDrive]
int 13h
ret

;In=  si = string, ah = 0eh, al = char, Out= charcater screen
Print:
lodsb
cmp al, 0
je  Done
mov ah, 0eh
int 10h
jmp Print

Done:
ret

Main:
cli
mov ax, 0x0000
mov ss, ax
mov sp, 0xFFFF
sti

mov ax, 07C0h
mov ds, ax
mov es, ax

mov [BootDrive], dl

mov ch, 0
mov cl, 2
mov dh, 1
mov bx, buffer
mov al, 14
mov ah, 2
pusha
load_root:
int 13h
jnc loaded_root
call    reset_floppy
jmp load_root

loaded_root:
popa
;cmpsb es:di with ds:si
mov di, buffer
mov cx, 224
search_root:
push    cx
pop dx
mov si, filename
mov cx, 11
rep cmpsb
je  found_file
add ax, 32
mov di, buffer
add di, ax
push    dx
pop cx

loop    search_root
int 18h

found_file:
mov ax, WORD [di+15]
mov [FirstSector], ax

mov bx, buffer
mov ax, 1
call    convert_sector
mov al, 9
mov ah, 2
pusha
load_fat:
int 13h
jnc loaded_fat
call    reset_floppy
jmp load_fat

loaded_fat:
mov ah, 2
mov al, 1
push    ax

load_file_sector:
mov ax, WORD [FirstSector]
add ax, 31
call    convert_sector
mov ax, 2000h
mov es, ax
mov bx, WORD [Pointer]

pop ax
push    ax

int 13h
jnc calculate_next_sector
call    reset_floppy
jmp load_file_sector

calculate_next_sector:
mov ax, [FirstSector]
mov dx, 0
mov bx, 6
mul bx
mov bx, 4
div bx
mov si, buffer
add si, ax
mov ax, WORD [si]

or  dx, dx
jz  even

odd:
shr ax, 4
jmp short next_sector_calculated

even:
and ax, 0FFFh

next_sector_calculated:
mov WORD [FirstSector], ax
cmp ax, 0FF8h
jae end
add WORD [Pointer], 512
jmp load_file_sector

end:
pop ax
mov dl, BYTE [BootDrive]
jmp 2000h:0000h

msg db  "EISSET LIWAG",0
BootDrive   db  0
filename    db  "KERNEL  BIN"
FirstSector dw  0
Pointer dw  0

times 510 - ($-$$)  db  0

dw  0xAA55

buffer:

OK, that does explain some things, but I am puzzled still. I've assembled the code in question, and wrote it out to an image file, but... well, as it is, it shouldn't work AFAICT. The fact that you aren't setting the origin to 7C00h was enough to be a showstopper when I tried to run it under Bochs 2.6, and while adding the ORG directive did get it going, it still presented other problems.

BTW, what tool did you use to write the boot sector to the disk image, and what (if any) was the command string to do it?

It looks as if you are trying to read a FAT listing to find the file KERNEL.BIN, but that's puzzling too, as you neglected to incorporate a BPB in your boot sector; without one, a FAT disk shouldn't be readable (at least not by most FAT supporting OSes). You call int 18h (ROM Basic loader) if the search for the file fails, but what PC has a ROM Basic anymore? You also seem to have some confusion about how the stack works, as indicated by the following two lines:

push    dx
pop cx

which is equivalent to

mov cx, dx

which I doubt was the intention. It also wasn't clear where you were loading the second stage to, given the presence of the label buffer.

Can you explain some of these issues? I'm still not sure what you were doing in places.

I used mkbt in copying my bootloader.

format A:
nasm -f bin boot.asm -o boot.bin
nasm -f bin kernel.asm -o KERNEL.BIN
copy KERNEL.BIN A:\KERNEL.BIN
mkbt boot.bin A:

Here is the picture of what ive got.
What I want to do in this cmd is changing the background and text color and the text in the screen should retain. Thanx. sorry I cant make it the right way. need your help.

014887cf62789b6a25024b964390a79c

I made small changes in the cli_command.asm

blue:
mov ah, 2   ; use function 2 - go to x,y
mov bh, 0   ; display page 0
mov dh, 0   ; y coordinate to move cursor to
mov dl, 0   ; x coordinate to move cursor to
int 10h ; go!

mov ah, 09h
mov cx, 1000h
mov al, 20h
mov bl, 17h ;color
int 10h
mov si, version
call    Print
call    newline
mov si, copyright
call    Print
jmp cmd

OK, as I said earlier, there are two waya to do this. One is to read each character from the video buffer, and write it out again with the new color. The other is to draw directly to the video memory. I'm going to show you the first, because you seem to be staying in real mode for now.

But first things first: let's make sure we know what the video page mode is. You can set it with the Int 10h, AH 00h function before running your command interpreter. For argument's sake, we'll use the 80x30 VGA setting, AL 12h:

; for now, define the width and hieght as constants
width   EQU 80
height  EQU 30

set_mode:
    mov ah, 00h
    mov al, 12h
    int 10h
    ret

blue:
    mov ax, 0
    push ax          ; y coordinate
    push ax          ; x coordinate 
    call gotoxy
    pop ax           ; clean up stack
    pop ax

    mov cx, height
.for_row:
    mov dx, width
.for_col:
    mov ah, 08h
    mov bh, 0
    int 10h
    ; use the returned value of al as the character to write
    mov ah, 09h
    mov cx, 0h
    mov bl, 17h ;color
    int 10h
    dec dx
    jnz .for_col
    dec cx
    jnz for_row

    mov si, version
    call    Print
    call    newline
    mov si, copyright
    call    Print
    jmp cmd

gotoxy:              ; here I am using the C style 
    push bp          ; parameter passing, on the stack
    mov bp, sp

    mov ah, 2        ; use function 2 - go to x,y
    mov bh, 0        ; display page 0
    mov dh, [bp-6]   ; y coordinate to move cursor to
    mov dl, [bp-4]   ; x coordinate to move cursor to
    int 10h ; go!

    pop bp
    ret

Now, this version will probably have some hideous flicker, so we can instead do this:

set_mode:
    ; first set page 1, then page 0
    mov ah, 05h
    mov al, 1 
    int 10h
    mov ah, 00h
    mov al, 12h
    int 10h

    mov ah, 05h
    mov al, 0 
    int 10h
    mov ah, 00h
    mov al, 12h
    int 10h        
    ret

blue:
    mov ax, 0
    push ax          ; y coordinate
    push ax          ; x coordinate 
    call gotoxy
    pop ax           ; clean up stack
    pop ax
    mov cx, height
.for_row_move:
    mov dx, width
.for_col_move:
    mov ah, 08h
    mov bh, 0
    int 10h
    mov bl, ah    ; use the returned attrib as the new attrib
    mov bh, 1     ; copy the text to page 1
    mov ah, 09h   
    int 10h
    dec dx
    jnz .for_col_move
    dec cx
    jnz for_row_move
    ah, 05h       ; switch to text page 1 temporarily
    al, 1
    int 10h

    mov cx, height
.for_row_restore:
    mov dx, width
.for_col_restore:
    mov ah, 08h
    mov bh, 1
    int 10h
    ; use the returned value of al as the character to write        
    mov ah, 09h
    mov cx, 0h
    mov bl, 17h ;color
    int 10h
    dec dx
    jnz .for_col_restore
    dec cx
    jnz for_row_restore
    ah, 05h       ; switch back to text page 0
    al, 0
    int 10h


    mov si, version
    call    Print
    call    newline
    mov si, copyright
    call    Print
    jmp cmd

Now, I haven't test this yet, but it should do the trick. Let me know how it works out.

Oh! I forgot a fairly important detail: restoring the previous cursor location. You'll want to get the x and y value at the beginning of the function, and restore them when you are done.

blue:
    mov ah, 03h
    int 10h
    push dx        ;dh = x, dl = y

    ;; continue the code from here
    ;; until after 'jnz for_row_restore'

    call gotoxy    ; restore the original cursor position
    pop ax         ; dispose of the value on the stack

While doing this, I noticed a mistake in my gotoxy function, so let me correct that:

gotoxy:            ; here I am using the C style
    push bp        ; parameter passing, on the stack
    mov bp, sp
    mov ah, 2      ; use function 2 - go to x,y
    mov bh, 0      ; display page 0
    mov dh, [bp+4] ; y coordinate to move cursor to
    mov dl, [bp+5] ; x coordinate to move cursor to
    int 10h ; go!
    pop bp
    ret

Also, in blue, remove the second push ax and the corresponding pop. This is because (in real mode) the stack always pushes a word at a time rather than a byte at a time. Finally, the parameters are higher in memory than the base pointer, so it should have been a plus offset, not minus.

Here is the Result.

c513457f946c96f9150849ca9fe7439f

; for now, define the width and hieght as constants
width EQU 80
height EQU 30

set_mode:
; first set page 1, then page 0
mov ah, 05h
mov al, 1
int 10h
mov ah, 00h
mov al, 12h
int 10h
mov ah, 05h
mov al, 0
int 10h
mov ah, 00h
mov al, 12h
int 10h
ret

blue:
mov ah, 03h
int 10h
push dx ;dh = x, dl =y

mov ax, 0
push ax ; y coordinate
call gotoxy
pop ax ; clean up stack
mov cx, height
.for_row_move:
mov dx, width
.for_col_move:
mov ah, 08h
mov bh, 0
int 10h
mov bl, ah ; use the returned attrib as the new attrib
mov bh, 1 ; copy the text to page 1
mov ah, 09h
int 10h
dec dx
jnz .for_col_move
dec cx
jnz .for_row_move
mov ah, 05h ; switch to text page 1 temporarily
mov al, 1
int 10h
mov cx, height
.for_row_restore:
mov dx, width
.for_col_restore:
mov ah, 08h
mov bh, 1
int 10h
; use the returned value of al as the character to write
mov ah, 09h
mov cx, 0h
mov bl, 17h ;color
int 10h
dec dx
jnz .for_col_restore
dec cx
jnz .for_row_restore
call gotoxy ; restore the original cursor position
pop ax ; dispose of the value on the stack
mov ah, 05h ; switch back to text page 0
mov al, 0
int 10h
mov si, version
call Print
call newline
mov si, copyright
call Print
jmp cmd


gotoxy: ; here I am using the C style 
push bp ; parameter passing, on the stack
mov bp, sp
mov ah, 2 ; use function 2 - go to x,y
mov bh, 0 ; display page 0
mov dh, [bp+4] ; y coordinate to move cursor to
mov dl, [bp+5] ; x coordinate to move cursor to
int 10h ; go!
pop bp
ret

I should have specified that gotoxy and set_mode should be in the functions.asm file; I am not certain if you have the code exactly as you have shown it or not. Also, you need to have a call to set_mode in kernel.asm; you only need to call it once.

Anyway, I did see the cause of at least part of the problem: the code as it is doesn't advance the cursor during the various passes. I will try to work out a version of it that works with my own secnd stage, and get back to you about it.

I was, with considerable effort, able to get the blue() routine working in my own second stage, but the way I write code is significantly different from your style and I will have to post the whole thing, including all the EQUates I used, to make it comprehensible. It shouldn't be too difficult to re-write it for your setup, but it make take a little work.

;;;;;;;;;;;;;;;;;
;; stagetwo.asm - second stage boot loader
;; 
;; v 0.01  Joseph Osako 3 June 2002
;; v 0.02  Joseph Osako 7 Sept 2006
;;         * restarted project, files place under source control.
;;         * Modifications for FAT12 based loader begun. 
;;
;; 

%define stage2_base 0x1000      ; the segment:offset to load 
%define stage2_offset 0x0000    ; the second stage into

VBIOS           equ 0x10        ; BIOS interrupt vector for video services
set_cursor      equ 0x02        ; set the cursor to the given x,y coordinates
get_cursor      equ 0x03
set_page_mode   equ 0x00
set_active_page equ 0x05
read_cursor     equ 0x08
write_cursor    equ 0x09
ttype           equ 0x0E        ; print character, teletype mode
set_resolution  equ 0x12
set_font        equ 0x1102
width           equ 80
height          equ 43
page_mode       equ 0x03
NULL            equ 0x00        ; end of string marker
CR          equ 0x0D        ; carriage return
LF          equ 0x0A        ; line feed 

DBIOS           equ 0x13        ; BIOS interrupt vector for disk services
disk_reset  equ 0x00        ; disk reset service
disk_read   equ 0x02        ; disk read service
tries           equ 0x03        ; number of times to attempt to access the FDD
reset_failure   equ 0x01        ; error code returned on disk reset failure
read_failure    equ 0x02        ; error code returned on disk read failure

cyl             equ 0x00        ; cylinder to read from
head            equ 0x00        ; head to read from
startsector equ 0x02        ; sector to start reading at
numsectors  equ 0x01        ; number of sectors to read


;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
;; macros
;   
%define zero(x) xor x, x

%macro write 1
   mov si, %1
   call printstr
%endmacro

[bits 16]
[org stage2_offset]

entry:
   mov ax, cs
   mov ds, ax

   mov bp, sp
   mov al, [bp+2]
   mov [bootdrv], al

   call set_mode
   push 0
   call set_page
   pop ax
   mov ah, 5
   mov al, 5
   push ax
   call gotoxy
   pop ax

   write success

   call blue

;  jmp $
  ; 'return' to the first stage via a faked call frame set up earlier
  retf


;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
;; Auxilliary functions      

;; printstr - prints the string point to by SI

printstr:
  push ax
  push bx
  mov bh, [active_page] 
  mov ah, ttype        ; set function to 'teletype mode'
  .print_char:   
    lodsb               ; update byte to print
    cmp al, NULL        ; test that it isn't NULL
    jz short .endstr
    int  VBIOS          ; put character in AL at next cursor position
    jmp short .print_char
.endstr:
  pop bx
  pop ax
  ret


; reset_disk
reset_disk:
  mov dl, [bootdrv]
  zero (ah)
  mov al, disk_reset
  int DBIOS
  ret

blue:
  mov ah, get_cursor
  int VBIOS
  push dx ; dh = x, dl = y

  push 0   ; both x and y coordinates
  call gotoxy
  pop ax  ; clean up stack

  mov cx, height-1
.for_move_row:
  push cx
  mov dx, width-1
.for_move_col:
  push dx
  mov ah, read_cursor
  mov bh, [active_page]
  int VBIOS
  call advance_cursor
  mov [active_page], BYTE 1 
  mov bl, ah                    ; use the returned attrib as the new attrib
  mov bh, [active_page]         ; copy the text to page 1
  mov ah, write_cursor
  mov cx, 1
  int VBIOS
  call advance_cursor
  mov [active_page], BYTE 0
  pop dx
  dec dx
  jnz .for_move_col
  pop cx
  dec cx
  jnz .for_move_row

  push 0
  call gotoxy   
  mov al, 1
  push ax
  call set_page
  pop ax
  call gotoxy
  pop ax

  mov cx, height-1
.for_restore_row:
  push cx
  mov dx, width-1
.for_restore_col:
  push dx
  mov ah, read_cursor
  mov bh, [active_page]
  int VBIOS
  call advance_cursor
  mov [active_page], BYTE 0 
  mov bl, 0x17
  mov bh, [active_page]         ; copy the text back to page 0
  mov ah, write_cursor
  mov cx, 1
  int VBIOS
  call advance_cursor
  mov [active_page], BYTE 1
  pop dx
  dec dx
  jnz .for_restore_col
  pop cx
  dec cx
  jnz .for_restore_row

  mov al, 0
  push ax
  call set_page
  pop ax

  call gotoxy             ; restore the original cursor position
  pop ax                  ; dispose of the value on the stack
  mov ah, set_active_page ; switch back to text page 0
  mov al, 0
  int VBIOS 
  ret

advance_cursor:
  push dx
  mov ah, get_cursor
  mov bh, [active_page]
  int VBIOS
  cmp dh, height-1
  jge .exit          ; already off of the screen
  cmp dl, width-1
  jge .move_down
  inc dl
  jmp .set_cursor
.move_down:  
  mov dl, 0
  inc dh
.set_cursor:
  push dx
  call gotoxy
  pop dx 
.exit:
  pop dx
  ret 


set_page:
  push bp   
  mov bp, sp
  mov al, [bp+4]
  mov [active_page], al
  mov ah, set_active_page ; switch to text page 1 temporarily
  int VBIOS     
  pop bp
  ret


set_mode:
  ; first set page 1, then page 0
  mov ah, set_active_page
  mov al, 1 
  int VBIOS
  mov ah, set_page_mode
  mov al, page_mode
  int VBIOS
  mov ah, set_resolution
  mov bl, 0x30
  mov al, 0x02
  int VBIOS
  mov ax, set_font
  mov bl, 5
  int VBIOS
  mov ah, set_active_page
  mov al, 0 
  int VBIOS
  mov ah, set_page_mode 
  mov al, page_mode
  int VBIOS
  mov ah, set_resolution
  mov bl, 0x30
  mov al, 0x02
  int VBIOS
  mov ax, set_font
  mov bl, 5
  int VBIOS
  ret   

gotoxy:  
  push bp
  mov bp, sp
  mov ah, set_cursor
  mov bh, [active_page] ; page to display
  mov dh, [bp+5]        ; x coordinate to move cursor to
  mov dl, [bp+4]    ; y coordinate to move cursor to
  int VBIOS
  pop bp
  ret

;;;;;;;;;;;;;;;;;;;;;;;;;
;; data
active_page db 0

success     db 'Control successfully transferred to second stage.', CR, LF, NULL

bootdrv     db 0x00  ; byte reserved for boot drive ID number
Be a part of the DaniWeb community

We're a friendly, industry-focused community of developers, IT pros, digital marketers, and technology enthusiasts meeting, networking, learning, and sharing knowledge.