Author Topic: Real to Protected Mode Taskings and Design for Banks  (Read 2789 times)

Offline Deskman243

  • Jr. Member
  • *
  • Posts: 49
Real to Protected Mode Taskings and Design for Banks
« on: May 17, 2023, 12:10:26 PM »
Introduction
For specification this build is 100% compatible to NASM builds and is a mainly based on CISC assembly and some setting files such as for make and ld commands. A good thing to know before hand is that most of the components prototyped here are based on related articles to OS design such as from OSDev Wiki,Stack Overflow posts or whatever I could find from NASM's forum. Also the zipfile of the full program is sourced in the reference links of the article.

This post is going to be more of a walkthrough style based on the pathings of the logic between files. Here I have designed the program between the relevant files to carry through each of the most important functions for the proof of concept program.

Boot==>Stage1<==>Stage2

_Settings and configurations

 

The file overviews can be looked at here so we can review in the consequent section

boot.asm
Code: [Select]
;    ReTimerOS
;    Copyright (C) 2022,2023  Christopher Hoy
;
; This file is part of ReTimerOS
;    ReTimerOS is free software: you can redistribute it and/or modify
;    it under the terms of the GNU General Public License as published by
;    the Free Software Foundation, either version 3 of the License, or
;    (at your option) any later version.
;
;    This program is distributed in the hope that it will be useful,
;    but WITHOUT ANY WARRANTY; without even the implied warranty of
;    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
;    GNU General Public License for more details.
;
;    You should have received a copy of the GNU General Public License
;    along with this program.  If not, see <https://www.gnu.org/licenses/>.


[BITS 16]
;[ORG 0x7c00]


section .text

_prep_module:
    xor ax,ax   
    mov ds,ax
    mov es,ax 
    mov ss,ax
    mov sp,0x7C00



DriveIdPrep:
    mov [DriveId],dl
    mov ah,0x41
    mov bx,0x55aa
    int 0x13
;    jc CheckPrep
    cmp bx,0xaa55
;    jne CheckPrep

SizeFunction:
mov bx,0x0000_7E00
mov cl,2
mov ah,0x02
; mov al,1
; mov al,12h
mov al,60
mov ch,0
mov dh,0
    int 0x13
;    jc  ReadCheck

    mov dl,[DriveId]

.move1:
jmp 0x7e00


jmp $





Section .data 
String: db 'Check',0
DriveId:    db 0

MessageLen: equ $-String
ReadPacket: times 16 db 0


stage1.asm
Code: [Select]
;    ReTimerOS
;    Copyright (C) 2022,2023  Christopher Hoy
;
; This file is part of ReTimerOS
;    ReTimerOS is free software: you can redistribute it and/or modify
;    it under the terms of the GNU General Public License as published by
;    the Free Software Foundation, either version 3 of the License, or
;    (at your option) any later version.
;
;    This program is distributed in the hope that it will be useful,
;    but WITHOUT ANY WARRANTY; without even the implied warranty of
;    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
;    GNU General Public License for more details.
;
;    You should have received a copy of the GNU General Public License
;    along with this program.  If not, see <https://www.gnu.org/licenses/>.


;[ORG 0x7E00]

%define BUILD_GDT_DESC(bounds,base,access,flags) \
((( base & 0x00FFFFFF) << 16) | \
(( base & 0xFF000000) << 32) | \
( bounds & 0x0000FFFF) | \
(( bounds & 0x000F0000) << 32) | \
(( access & 0xFF) << 40) | \
(( flags & 0x0F) << 52))

TSS_IO_MAP_SIZE EQU 0x400/8


%define REBASE_ADDRESS(A)  (0x7E00 + ((A) - protectedGate1))

[BITS 16]


section .text

protectedGate1:use16

; jmp 0x8000

cld
cli

in al,0x92
or al,2
out 0x92,al

lgdt[gdt32Ptr]
lidt[IdtPipe]

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

; mov [saved_segment],ds

; jmp code32_post:REBASE_ADDRESS(__protected_mode_32)
jmp code32_post:__protected_mode_32



section .text

[bits 32]
; 32 bit protected mode
__protected_mode_32:use32
;    mov ax, 0x10
mov ax,data32_post
    mov ds, ax
    mov es, ax
    mov fs, ax
    mov gs, ax
;    mov ss, ax
    ; restate cr3
    mov cr3, ebx
    ; restate esp
    mov esp, edx

mov cx,[gate_voucher]
cmp word [gate_voucher],0
jnz loopcheck
mov word [gate_voucher],1

; jmp code32_post:REBASE_ADDRESS(BIOS32_PREP)
jmp code32_post:0x0000_A000
; jmp code32_post:0x0000_7000
; jmp code32_post:0x0000_0a00


; jmp 0x8000

jmp $


loopcheck:
hlt
jmp loopcheck



%include 'gdt.inc'

section .data



align 4
;vidmem_ptr: dd VIDEO_TEXT_ADDR
pm_str: db 'protected mode string ',0
pm_str_length: equ $-pm_str
vm_str: db 'virtual',0
;vidmem_address: dw 0

;resb 512
;times 512 db 0

align 16
tss:
.back_link: dd 0
.esp0: dd 0
.ss0: dd 0
.esp1: dd 0
.ss1: dd 0
.esp2: dd 0
.ss2: dd 0
.cr3: dd 0
.eip: dd 0
.eflags: dd 0
.eax: dd 0
.ecx: dd 0
.edx: dd 0
.ebx: dd 0
.esp: dd 0
.ebp: dd 0
.esi: dd 0
.type2: dd 0
.es: dd 0
.cs: dd 0
.ss: dd 0
.ds: dd 0
.fs: dd 0
.gs: dd 0
.ldt: dd 0
.trap: dw 0
.iomap_base: dw 0

.iomap: TIMES TSS_IO_MAP_SIZE db 0x00

%if TSS_IO_MAP_SIZE > 0
.iomap_pad:db 0xff

%endif
.end:
TSS_SIZE: EQU tss.end -tss

align 4

ColorTable: db 00h,01h,02h,03h,04h,05h,06h,07h
;db 10h,11h,12h,13h,14h,15h,16h,17h
db 38h,39h,3Ah,3Bh,3Ch,3Dh,3Eh,3Fh
ColorTableSize: equ $-ColorTable

save_cr0 dd 0
save_cr3 dd 0
saved_segment resd 0
gate_voucher dw 0
saved_stack resw 0



ROWS EQU 25
COLS1 EQU 80

;IdtPipe: dw 0x03ff
; dd 0

section .bss
align 16
;ring0_proc_stack: resb RING0_PROC_STACK_SIZE
ring0_proc_stack_placer:

align 4
save_esp: resd 1
save_ss: resd 1


stage2.asm
Code: [Select]
;    ReTimerOS
;    Copyright (C) 2022,2023  Christopher Hoy
;
; This file is part of ReTimerOS
;    ReTimerOS is free software: you can redistribute it and/or modify
;    it under the terms of the GNU General Public License as published by
;    the Free Software Foundation, either version 3 of the License, or
;    (at your option) any later version.
;
;    This program is distributed in the hope that it will be useful,
;    but WITHOUT ANY WARRANTY; without even the implied warranty of
;    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
;    GNU General Public License for more details.
;
;    You should have received a copy of the GNU General Public License
;    along with this program.  If not, see <https://www.gnu.org/licenses/>.

%define REBASE_ADDRESS(A)  (0xA000 + ((A) - BIOS32_PREP))

[bits 32]
BIOS32_PREP:use32
; jmp $
; jmp 0x8000

    pusha
    ;pushf
    ; save current esp to edx
    mov edx, esp
    ; jumping to 16 bit protected mode
    ; disable interrupts
    cli
    ; clear cr3 by saving cr3 data in ebx register
    xor ecx, ecx
    mov ebx, cr3
    mov cr3, ecx


jmp code16_post:REBASE_ADDRESS(__protected_mode_16)
; jmp code16_post:__protected_mode_16


[bits 16]
; 16 bit protected mode
__protected_mode_16:use16
    ; jumping to 16 bit real mode

xor eax,eax
xor ecx,ecx

;   mov ax, 0x38
mov cx,data16_post

; mov ax,0

    mov ds, cx
    mov es, cx
    mov fs, cx
    mov gs, cx
    mov ss, cx
    ; turn off protected mode
    ; set bit 0 to 0
    mov eax, cr0
    and al,  ~0x01
    mov cr0, eax

jmp 0x0:REBASE_ADDRESS(__real_mode_16)


__real_mode_16:use16
    xor cx, cx
    mov ds, cx
    mov es, cx
    mov fs, cx
    mov gs, cx
    mov ss, cx
;    mov sp, 0x8c00
   mov sp, 0x6c00
 
    ; enable bios interrupts to call
    sti
    ; save current context, all general, segment registers, flags
    pusha
    mov cx, ss
    push cx
    mov cx, gs
    push cx
    mov cx, fs
    push cx
    mov cx, es
    push cx
    mov cx, ds
    push cx
    pushf
    ; get current stack pointer & save it to current_esp
    mov ax, sp
;    mov edi, current_esp
    mov di, current_esp

    stosw
    ; load our custom registers context
    mov esp, REBASE_ADDRESS(bios32_in_reg16_ptr)
;    mov sp, REBASE_ADDRESS(bios32_in_reg16_ptr)

    ; only use some general register from the given context
    popa
    ; set a new stack for bios interrupt
;    mov sp, 0x9c00
   mov sp, 0x7c00

    ; call immediate interrupt opcode to execute context

pusha
; mov bp,sp
jmp bios32_GraphicCtrlA

bios32_GraphicCtrlA:use16
; will be bios interrupt number passed
    ; put the actual interrupt number here
; db 0xCD
;    db 0x10
; db 0x01

mov ax,0x13
int 0x10

.bgnd1:
mov word [col_placer],0
mov word [row_placer],24*VGA13
mov word [color_container],VGA13*40
.bgndloop1:
mov si,ColorMap
call GraphicPrint
sub word [row_placer],VGA13
jnz .bgndloop1

; call Mappings

jmp short .player_placer

.bgnd2:
mov word [col_placer],1
mov word [row_placer],24*VGA13
mov word [color_container],VGA13*40
call Mappings

;check count of imaging
; mov word [bkgnd_check],0
.bgndloop2:
mov si,Map1
call GraphicPrint
sub word [row_placer],VGA13
jnz .bgndloop2
; mov byte [page_check],1
; jmp bios32_CtrlLoop

; fun option 1
; mov word [bkgnd_check],0

.player_placer:
mov word [bkgnd_check],0

mov word [row_placer],1*VGA13
mov word [col_placer],1*VGA13
mov word [color_container],0
mov word [color_container],VGA13
mov si,GraphicA
call GraphicPrint

; mov word [bkgnd_check],0
; cmp byte [page_check],1
; jnz loopstepA
; jmp bios32_CtrlLoop
jmp loopstepA


GraphicPrint:
; push cx
mov bp,0
push word [color_container]

mov cx,0A000h
mov es,cx
mov cx,cs
mov ds,cx

.post:
; cmp word [col_placer],24
; jnl WallBoundR

; cmp word [row_placer],40
; jnl WallBoundD

; cmp word [col_placer],1
; jnl .WallBoundR

; cmp word [row_placer],1
; jnl .WallBoundD

mov ax,1
mul word [col_placer]
mov bp,ax

mov ax,320
mov bx,0
add bx,word [row_placer]
mul bx
add bp,ax


mov ch,0
; mov ch,1
; mov word [graphic_placer],bp
mov dx,bp
mov word [graphic_retainer],ds
add word [graphic_retainer],si
; add word [graphic_retainer],VGA13*39
; mov word [reserver],320*8
mov word [reserver],0

PrintGraphicY:
add word [graphic_retainer],VGA13*39
pop word [color_container]
push word [color_container]
push bp

PrintGraphicX:
mov al,[ds:si]

cmp word [bkgnd_check],1
jz .prep

.standard:
push ax
mov al,[es:bp]
mov byte [graphic_cmpC],al
pop ax
; xor al,[es:bp]
mov es:[bp],al
mov al,byte [graphic_cmpC]
; mov [es:bp-1],al

inc si
inc bp
dec word [color_container]
jnz PrintGraphicX
.stage1:
pop bp
add bp,320
;test area2
; mov ax,word [graphic_retainer]
; mov ax,ds
; add ax,si
; cmp ax,word [graphic_retainer]
; jg .WallBound
;.stage2:
inc ch
cmp ch,VGA13
jnz PrintGraphicY
.stage2:
cmp si,word [graphic_retainer]
jl .Orientation
.stage3:
pop word [color_container]
mov cx,word [col_placer]
mov word [X_pre],cx
mov cx,word [row_placer]
mov word [Y_pre],cx
mov word [graphic_placer],dx
ret
.prep:
mov [es:bp],al

push si

mov si,Map1

; add si,Map1.stub
; sub
add si,[word reserver]
; add si,bp

push ax
; add al,0x10
; mov al,0x0D
mov ds:[si],al
pop ax
pop si

inc si
inc bp
inc word [reserver]
dec word [color_container]

jnz PrintGraphicX
; add word [graphic_retainer],VGA13*39
jmp short PrintGraphicX.stage1

.WallSegmenting:
add si,VGA13
jmp short PrintGraphicX.stage2

.Orientation:
mov byte [loop_check],0
; mov si,ColorMap

; mov cx,320*8
mov si,Map1
; add si,cx

add si,word [col_placer]

mov cx,word [graphic_placer]
cmp dx,word [graphic_placer]
jg .OrientInc1
cmp word [graphic_placer],dx
jg .OrientDec1
.OrientInc1:
times 7 add si,320

mov ax,word [Y_pre]
mov cx,word [row_placer]
cmp word [row_placer],ax

jg .OrientInc2

sub bp,1
sub si,1
.logicstepInc1:
mov al,[ds:si]
mov [es:bp-320],al

sub bp,320
sub si,320
inc byte [loop_check]
cmp byte [loop_check],VGA13
; jnz .OrientInc1
jnz .logicstepInc1
jmp .stage3
.OrientInc2:
; sub bp,1
mov al,ds:[si]
mov [es:bp-9*320],al

inc bp
inc si
inc byte [loop_check]
cmp byte [loop_check],VGA13
jnz .OrientInc2
jmp .stage3
.OrientDec1:
mov ax,word [X_pre]
cmp word [col_placer],ax
jl .OrientDec2
; jg .OrientDec2

times 7 add si,320
.loopstepDec1:
mov al,[ds:si]
mov [es:bp],al

; times 8 add bp,320
inc bp
inc si
inc byte [loop_check]
cmp byte [loop_check],VGA13
jnz .loopstepDec1
jmp .stage3
.OrientDec2:
times 7 add si,320
sub bp,320
.loopstepDec2:
mov al,[ds:si+8]
mov [es:bp+8],al

sub bp,320
sub si,320
inc byte [loop_check]
cmp byte [loop_check],VGA13
; jnz .OrientDec2
jnz .loopstepDec2
jmp .stage3
WallBoundR:
mov si,Map1
mov al,[ds:si]
;WallBoundL:
;WallBoundU:
;WallBoundD:

Mappings:
mov cx,0A000h
mov es,cx
mov word [reserver],0
; mov cx,24*VGA13
; mov dh,0
; mov ax,24*VGA13
mov ax,0
; mov si,Map2
mov si,Map1
mov bp,0
.MapLoop:
mov cx,0
push bp
.pageA:
mov [es:bp],word 0
; mov [es:word reserver],word 0
; mov es:[word reserver],word 0
inc bp
inc cx
cmp cx,VGA13
jnz .pageA
pop bp
add bp,320
; loop .MapLoop
inc ax
cmp ax,24*VGA13
jnz .MapLoop
; jmp MapGraphs
jmp .reset
; jmp .map_reset

.reset:
; mov si,Map2
mov si,Map1
mov bp,640*VGA13+1
mov ax,0
.config:

.save:
mov al,[es:bp]
add al,0x10
mov [es:bp],al
mov ds:[si],al
inc si
inc bp
cmp si,Map1+Map1.stub
jnz .save


ret


bios32_CtrlLoop:
call Mappings

loopstepA:

mov ah,01h
int 16h
jz loopstepA

mov si,GraphicA
call GraphicPrint

.Set:
mov ah,00h
int 16h


cmp ah,11h
jnz .SetDownWall
cmp word [row_placer],0
jz .SetDownWall
dec word [row_placer]
.SetDownWall:
; cmp ah,50h
cmp ah,1fh
jnz .SetUpWall
cmp word [row_placer],24*VGA13
jz .SetUpWall
inc word [row_placer]
.SetUpWall:
; cmp ah,4Bh
cmp ah,1eh
jnz .SetRightWall
cmp word [col_placer],0
jz .SetRightWall
dec word [col_placer]
.SetRightWall:
; cmp ah,4Dh
cmp ah,20h
jnz .SetLeftWall
cmp word [col_placer],40*VGA13
jz bios32_GraphicCtrlA.bgnd2
; jz bios32_CtrlLoop
inc word [col_placer]
.SetLeftWall:
cmp ah,50h
jz .SetPrint
.SetWall:
cmp ah,49h
jz poll_function
mov si,GraphicA
call GraphicPrint
jmp loopstepA
.SetPrint:
add word [col_placer],VGA13+1
mov si,GraphicB
call GraphicPrint
sub word [col_placer],VGA13+1
jmp .SetWall


poll_function:
; mov si,page_str1
popa
    ; get our output context here
    mov esp, REBASE_ADDRESS(bios32_out_reg16_ptr)

    add sp, 28 ; restore stack used for calling our context
    ; save current context, all general, segment registers, flags
    pushf
    mov cx, ss
    push cx
    mov cx, gs
    push cx
    mov cx, fs
    push cx
    mov cx, es
    push cx
    mov cx, ds
    push cx
    pusha
    ; restate the current_esp to continue
    mov esi, current_esp
;    mov si, current_esp

    lodsw
    mov sp, ax
    ; restore all current context, all general, segment registers, flags
    popf
    pop cx
    mov ds, cx
    pop cx
    mov es, cx
    pop cx
    mov fs, cx
    pop cx
    mov gs, cx
    pop cx
    mov ss, cx
    popa


;[bits 16]
protectedGate2:use16
cld
cli

in al,0x92
or al,2
out 0x92,al

lgdt[gdt32Ptr]
lidt[IdtPipe]

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

jmp code32_post:0x0000_7e00


%include 'gdt.inc'

section .data

GraphicA:
db 00h,00h,00h,05h,05h,00h,00h,00h
db 00h,00h,05h,05h,05h,00h,00h,05h
db 00h,00h,0dh,05h,00h,00h,05h,05h
db 00h,06h,02h,0Dh,00h,05h,05h,00h
db 08h,06h,00h,30h,30h,0Dh,0Dh,00h
db 00h,00h,00h,30h,30h,0Dh,00h,00h
db 00h,00h,0Dh,00h,00h,0Dh,00h,00h
db 00h,00h,00h,00h,0Dh,00h,00h,00h
GraphicB:
db 40h,40h,40h,40h,40h,40h,40h,40h
db 40h,40h,40h,40h,40h,40h,40h,40h
db 40h,40h,40h,40h,40h,40h,40h,40h
db 40h,40h,40h,40h,40h,40h,40h,40h
db 40h,40h,40h,40h,40h,40h,40h,40h
db 40h,40h,40h,40h,40h,40h,40h,40h
db 40h,40h,40h,40h,40h,40h,40h,40h
db 40h,40h,40h,40h,40h,40h,40h,40h
ColorMap:
times 2560 db 50h

Map2:
times 2560*5 db 0
.stub: equ $-Map2
Map1:
times 2560 db 0
;times 2560*25 db 0
.stub: equ $-Map1



bios32_in_reg16_ptr:
    resw 14
bios32_out_reg16_ptr:
    dd 0xaaaaaaaa
    dd 0xaaaaaaaa
    dd 0xaaaaaaaa
    dd 0xaaaaaaaa
    dd 0xaaaaaaaa
    dd 0xaaaaaaaa
    dd 0xaaaaaaaa

current_esp: dw 0x0000

VGA13 EQU 8
;BKGND EQU 1

bkgnd_check: db 01h
loop_check: db 0
page_check: db 0
value_check: dw 0
mapperA: db 0
reserver: dw 0

graphic_retainer:dw 0
color_container:dw 0

graphic_placer: dw 0

row_placer: dw 0
col_placer: dw 0

X_pre: dw 0
Y_pre: dw 0

graphic_cmpA: db 0
graphic_cmpB: db 0
graphic_cmpC: db 0
graphic_cmpD: db 0


Overview
Boot.asm

This is the most fundamental part of all of OS Design. Our first step where the functions are typically contained into a 512b section and includes the peripherals such as in this case where the main method used is a Size function for the rest of the program file linkage.

Stage1.asm

The design of this file mainly reflects a minimal gate module between real and protected mode tasks. Here is where more emphasis was placed on custom functioning and  OS design by where the links structures between the BIOS calls and the OS are built. Alot of the future design was taken into consideration by having a protected mode OS for size 32 standards being 2^16 times bigger in size than regular BIOS.So this stage is a good in between for protected mode and segways into the basic BIOS functions seen in the other stage.

Stage2.asm

This stage is where the real fun gets into play. Firstly here establishes a stack for Real Mode BIOS calls to where we can observe the sub-system programming. Here consists of the int 10h set video graphic mode display and int 16h keyboard controller. When run the program makes a simple platform and background to observe the BIOS controller logic.

Settings and Configurations

More custom files here because a bulk of research is trying to make a conventional form of the program (I based this on graphics engines) by the resources available. Here I use a typical Makefile to neatly cover all the relevant program files. I use ld linker files because I have to debug my program when I get stuck and so oftentimes I try my best to make use of object files that gdb likes.  For my run's configuration I use
qemu-system-i386 -fda os.img

Summary

Currently I'm testing more and more into the BIOS side of things. I'm hoping to become very proficient so that one day I too can make my own custom platforms. Right now I'm researching more on linker scriptings and segmentation because the x86 architecture funnily has a distinction between 16 bit code and 20 bit segment references ( 2^20 <--> 2^16 = F FFFFh <--> FFFFh ) where Real Mode allows for 1 MB addresses but my code is only around 64kb!

Offline Deskman243

  • Jr. Member
  • *
  • Posts: 49
Re: Real to Protected Mode Taskings and Design for Banks
« Reply #1 on: June 18, 2023, 05:42:45 PM »
Review 1

Good day everyone
Today I was looking into the standard i386 real mode resources for our nasm builds. Right now I'm designing between two configuration builds for the stage2.asm graphic component that I'm trying to correspond. Here I've remodeled the above code to mainly access the segmentation banks of the A16-19 data lines for > 0x0FFFF < 0x100000 = 1 MB. Basically I found that the binary files can do this naturally BUT the remodel includes a completely new makefile configuration and boot. The main change between these is that version 2 does removes the ld linker file overlay from before other than a single instance however the good news is that this does in fact access the A16-19 segments.

Now the new yields here were noted as such

(1) That basic binary files built outside of the ld linker have an implicit 512 design boundary

(2) The A16-19 data lines for segments > 0x0FFFF right now only access data. This means that I can only access these segments as pure data and actually does not run instructions.

(3) The prototyped instance of ld now has only ran inside A0-15 data lines (<= 0xFFFF)

As a result these new remodeling has improved the culmination components however the new designs constrains these inferrences differently.
First off the new file configurations account for the space differently where the original uses dd commands for the .img file and the new one uses cat.
Second off the new model outside of ld linking actually has smaller files than I can use because of the 512b boundary (trust me I've tried haha).Here I'm hoping whether to improve the file management or more specifically to increase the static size by appropriating ld. We know here that the ld linker files here can stretch this from the original but I really just haven't found the right setting for this.

I'm investigating why the one file > 512b (stage2.asm) skips through GDB.
Otherwise I also tried doing this the other way around by combining cat into the original makefile but this loses the OS boot in the procedure.
Here's what the new running configuration files look like

Makefile
Code: [Select]
FILES =boot.o
FILES2 =stage3.o printstr.o

PROCURE = rm -rf

all: boot.bin stage1.bin test1.bin stage2.bin test2.bin
dd if=boot.bin of=os.img bs=512 count=66 conv=notrunc
dd if=stage1.bin of=os.img bs=512 seek=1 conv=notrunc
dd if=test1.bin of=os.img bs=512 seek=10 conv=notrunc
dd if=stage2.bin of=os.img bs=512 seek=18 conv=notrunc
dd if=/dev/zero of=os.img bs=512 seek=19 count=46 conv=notrunc

dd if=test2.bin of=os.img bs=512 seek=66 conv=notrunc

dd if=/dev/zero of=os.img bs=512 seek=67 count=2815 conv=notrunc
truncate -s 1M os.img

boot.o: boot.asm
nasm -f elf -g -o boot.o boot.asm
stage1.o: stage1.asm
nasm -f elf -g stage1.asm -o stage1.o
test1.o: test1.asm
nasm -f elf -g test1.asm -o test1.o
stage2.o: stage2.asm
nasm -f elf -g stage2.asm -o stage2.o
test2.o: test2.asm
nasm -f elf -g test2.asm -o test2.o

test2.bin: test2.asm
nasm -f bin -g test2.asm -o test2.bin

boot.bin: $(FILES)
ld -T link.ld $(FILES) -o boot.bin
stage1.bin: stage1.o
ld -g -m elf_i386 -T link2.ld stage1.o -o stage1.bin --oformat binary
stage2.bin: stage2.o
ld -g -m elf_i386 -T link4.ld stage2.o -o stage2.bin --oformat binary
test1.bin: test1.o
ld -g -m elf_i386 -Ttext 0x9000 test1.o -o test1.bin --oformat binary
test_2.bin: test2.o
ld -m elf_i386 -Ttext 0x10000 test2.o -o test_2.bin --oformat binary


clean:
$(PROCURE) *\.o
$(PROCURE) *\.bin
$(PROCURE) os.img


Code: [Select]

nasm -f elf -g -o boot.o boot.asm
nasm -f elf -g stage1.asm -o stage1.o
nasm -f elf -g test1.asm -o test1.o
nasm -f elf -g stage2.asm -o stage2.o
nasm -f bin -g test2.asm -o test2.bin

ld -T link.ld boot.o -o boot.bin
ld -g -m elf_i386 -Ttext 0x7e00 stage1.o -o stage1.bin --oformat binary
ld -g -m elf_i386 -Ttext 0x8000 stage2.o -o stage2.bin --oformat binary
ld -g -m elf_i386 -T link3.ld test1.o -o test1.bin --oformat binary


dd if=/dev/zero of=ospad1.bin bs=512 count=16
dd if=/dev/zero of=ospad2.bin bs=256 count=1


dd if=/dev/zero of=os.bin bs=512 count=2811
cat boot.bin \
stage1.bin \
ospad1.bin \
stage2.bin \
ospad2.bin \
os.bin>os.img

rm -rf *\.bin


qemu-system-i386 -fda os.img


For a full look into the files I'm adding the updated config files in this post too. If anyone else has experienced this I would be really happy to continue looking into this and I hope everyone has a good Father's Day in the meantime!