flat assembler
Message board for the users of flat assembler.

Index > OS Construction > floppy sector os issues

Author
Thread Post new topic Reply to topic
Gizmo



Joined: 19 Jul 2007
Posts: 25
Gizmo 28 Jul 2007, 10:47
I am trying to make a boot disk that copies sectors 2 through 12 into memory and jumps to it

My problem is I dont know how to tell fasm that my sector 2 bin asm needs to be setup so that it is loaded at 0x800:0x0.
So that when the boot sector program calls jmp 0x800:0x0 it should reach the start of execution in the sector 2 program and the addresses are all relative to segment 0x800.

In emu8086 you simply use


#al=0b#
#ah=00#
#bh=00#
#bl=00#
#ch=00#
#cl=02#
#dh=00#
#dl=00#
#ds=0800#
#es=0800#
#si=7c02#
#di=0000#
#bp=0000#
#cs=0800#
#ip=0000#
#ss=07c0#
#sp=03fe#

org 0x0

the example I am working with copies 10 sectors starting at sector 2 into memory starting at 0x800:0x0,
test for the jmp opcode at byte 0x800:0x0 (first line of sector 2 program)
and then calls jmp 0x800:0x0


Last edited by Gizmo on 30 Jul 2007, 15:43; edited 1 time in total
Post 28 Jul 2007, 10:47
View user's profile Send private message Reply with quote
mkriegel



Joined: 15 Jul 2007
Posts: 19
Location: Germany
mkriegel 28 Jul 2007, 15:45
Hi Gizmo,
some ideas:

1. use jmp far 0x800:0x0

doing so will setup the cs-register with 0x800.
->
2. set the ds, es, fs and gs-registers if nessesary:

mov ax, cs
mov ds, ax
mov es, ax
...

3. post some code to the forum

BYE MK
Post 28 Jul 2007, 15:45
View user's profile Send private message Reply with quote
Gizmo



Joined: 19 Jul 2007
Posts: 25
Gizmo 29 Jul 2007, 09:14
Those directives are only for the integrated emulator so you can debug/emulate the sector 2 program without first running sector 1.
It sets the cpu registers to how the bootsector program leaves them after it jumps to sector 2.


I found my problem...
My stack was not set up correctly, so that when i did

push strHello
call PrintString16

it was outputting garbage because the stack was overwriting my data because thats where the stack was initially. I set the stack up to use the same stack space of the bootsector program and now it works fine.

In case your confused:
sector 1: bootsector that loads kernel from sector2+ and jumps to it
sector 2+: the kernel that outputs string "hello from kernel"

I needed the extra space provided by using more than 1 sector because my bootsecotr 512 byte pmode task switching project ran out of space when I tried to implement an interupt table.

I could use a file system, but I just don't feel like it I guess.
I wonder if in fat12 you can hide the last couple of sectors and stash an os in there? (similar to how the windows scandisk marks sectors as bad and unusable)
Post 29 Jul 2007, 09:14
View user's profile Send private message Reply with quote
Mac2004



Joined: 15 Dec 2003
Posts: 314
Mac2004 29 Jul 2007, 09:41
Gizmo: Perhaps my boot sector example that loads a binary secondary file will help you a bit.

Here's the link: http://board.flatassembler.net/topic.php?t=6529

regards,
Mac2004
Post 29 Jul 2007, 09:41
View user's profile Send private message Reply with quote
Gizmo



Joined: 19 Jul 2007
Posts: 25
Gizmo 30 Jul 2007, 15:50
I got everything else to work, now I cant get my idt to work.
When I call an interrupt it crashes, but as long as I dont use them it run fine.
I read through all of the tutorials I could find and read the intel manual a few more times but I still don't see anything wrong.

Here is the code in question:
(remember its loaded at 8000h or 800h:0 in real mode)
Code:
org 0h
jmp BOOT_ENTRY ;used by bootsector to check first byte to make sure it was loaded correctly

;---------------------------------16 bit entry ---------------------------------------------------------------------------------
    use16
       BOOT_ENTRY:
     ; initialize the stack:
        mov     ax, 07c0h
           mov     ss, ax
              mov     sp, 03feh ; top of the stack.
        ; set data segment:
            mov     ax, 800h
            mov     ds, ax
       ;enable the a20 memory gate to access above 1 meg of ram
           call Enable_A20
      ;disable interupts
         cli
  ;load the GDT (gloabl description table) descriptor
        lgdt    [ds:gdt_32_desc]
       ;load interupt descriptor table
              lidt    [ds:idt_32_desc]
 ;set bit 0 of cr0 to 1  enabling protected mode
            mov     eax,    cr0
         or      eax,    1
           mov     cr0,    eax
  ;jump to 32 bit code segment to clear out instruction cache
        jmp     08h:PMODE_ENTRY+8000h

;---------------------------------32 bit entry ---------------------------------------------------------------------------------
       use32
       PMODE_ENTRY:
       ;set ds(data segment) and ss(stack segment) register to data segment identifier
               mov     ax,     10h
         mov     ds,     ax
          mov     ss,     ax
          mov     esp,    090000h        ; Move the stack pointer to 090000h
       ;continuously draw a random charactor
     hang:
                mov ebx, 0B8000h
            inc     byte [ds:ebx]
           inc ebx
             inc     byte [ds:ebx]
       ;use interupt 32 (0x20)
;                int 20h
             jmp     hang

;---------------------------------16 bit enables a20 memory gate ------------------------------------------------------------------

         ;;
          ;; enableA20.s (adapted from Visopsys OS-loader)
            ;;
          ;; Copyright (c) 2000, J. Andrew McLaughlin
         ;; You're free to use this code in any manner you like, as long as this
            ;; notice is included (and you give credit where it is due), and as long
            ;; as you understand and accept that it comes with NO WARRANTY OF ANY KIND.
         ;; Contact me at jamesamc@yahoo.com about any bugs or problems.
             ;;

      use16
       Enable_A20:
     ;store all registers
                pusha
       ;disable interupts
          cli
 ;5 attempts to enable a20 line
              mov CX, 5
   ;first method of enabling a20
               .startAttempt1:
         ; Wait for the controller to be ready for a command
                .commandWait1:
                           xor AX, AX
                          in AL, 64h
                          bt AX, 1
                            jc .commandWait1
            ; Tell the controller we want to read the current status.
           ; Send the command D0h: read output port.
                      mov AL, 0D0h
                out 64h, AL
          ;Wait for the controller to be ready with a byte of data
                  .dataWait1:
                               xor AX, AX
                          in AL, 64h
                          bt AX, 0
                            jnc .dataWait1
              ; Read the current port status from port 60h
                       xor AX, AX
                  in AL, 60h
           ; Save the current value of AX
                     push AX
              ; Wait for the controller to be ready for a command
                .commandWait2:
                           in AL, 64h
                          bt AX, 1
                            jc .commandWait2
            ; Tell the controller we want to write the status byte again
                       mov AL, 0D1h
                out 64h, AL
          ; Wait for the controller to be ready for the data
                 .commandWait3:
                           xor AX, AX
                          in AL, 64h
                          bt AX, 1
                            jc .commandWait3
            ; Write the new value to port 60h.  Remember we saved the old value on the stack
                   pop AX
               ; Turn on the A20 enable bit
                       or AL, 00000010b
                    out 60h, AL
          ; Finally, we will attempt to read back the A20 status to ensure it was enabled
             ; Wait for the controller to be ready for a command
                .commandWait4:
                           xor AX, AX
                          in AL, 64h
                          bt AX, 1
                            jc .commandWait4
            ; Send the command D0h: read output port.
                      mov AL, 0D0h
                out 64h, AL
          ; Wait for the controller to be ready with a byte of data
                  .dataWait2:
                              xor AX, AX
                          in AL, 64h
                          bt AX, 0
                            jnc .dataWait2
              ; Read the current port status from port 60h
                       xor AX, AX
                  in AL, 60h
           ; Is A20 enabled?
                  bt AX, 1
             ; Check the result.  If carry is on, A20 is on.
                    jc Enable_A20_success
                ; If the counter value in CX has not reached zero, we will retry
                   loop .startAttempt1
   ;method 2 for chipsets that don't support method 1
                mov CX, 5
           .startAttempt2:
         ; Wait for the keyboard to be ready for another command
                    .commandWait6:
                           xor AX, AX
                          in AL, 64h
                          bt AX, 1
                            jc .commandWait6
            ; Tell the controller we want to turn on A20
                       mov AL, 0DFh
                out 64h, AL
          ; Again, we will attempt to read back the A20 status to ensure it was enabled.
              ; Wait for the controller to be ready for a command
                .commandWait7:
                           xor AX, AX
                          in AL, 64h
                          bt AX, 1
                            jc .commandWait7
            ; Send the command D0h: read output port.
                      mov AL, 0D0h
                out 64h, AL
          ; Wait for the controller to be ready with a byte of data
                  .dataWait3:
                              xor AX, AX
                          in AL, 64h
                          bt AX, 0
                            jnc .dataWait3
              ; Read the current port status from port 60h
                       xor AX, AX
                  in AL, 60h
           ; Is A20 enabled?
                  bt AX, 1
                    jc Enable_A20_success
                ; If the counter value in CX has not reached zero, we will retry
                   loop .startAttempt2
    ;unable to enable a20
     Enable_A20_fail:
                sti
         popa
                mov EAX, -1
         ret
    ;enabled a20
     Enable_A20_success:
             sti
         popa
                xor EAX, EAX
                ret

   ;interupt 32 0x20 handler
     use32
       INT_HANDLER_0x20:
       ;save registers
             push    ds
          push    es
          pusha
       ;set the correct ds
         mov     ax, 10h
             mov     ds, ax
              mov     es, ax
      ;draw random charactor at colum 2
           mov ebx, 0B8002h
            inc     byte [ds:ebx]
           inc ebx
             inc     byte [ds:ebx]
   ;restore all registers
              popa
                pop     es
          pop     ds
  ;return from interupt
               iret



;--- 32 bit global segment descriptor table-----------------------------------------------------
        gdt_32:
 ;gdt entry format
   ;byte #7
        ;63 - 56    Upper Byte of Base Address
      ;55         Granularity Bit
         ;54         Default Bit
 ;byte #6
        ;53         long mode code segment
          ;52         Available for Use (free bit)
            ;51 - 48    Upper Digit of Limit
        ;byte #5
        ;47         Segment Present Bit
     ;46 - 45    Descriptor Privilege Level
      ;44         System Bit
      ;43         Data/Code Bit
           ;42         Conforming Bit
          ;41         Readable bit
            ;40         Accessed bit
        ;byte #4
        ;39 - 32    Third Byte of Base Address
  ;byte #3
        ;31 - 24    Second Byte of Base Address
 ;byte #2
        ;23 - 16    First Byte of Base Address
  ;byte #1
        ;15 - 8     Second Byte of Limit
        ;byte #0
        ;7 - 0      First Byte of Limit
    ;null segment
    gdt_32_null:
          dd 0
        dd 0
    ; Code segment, read/execute, nonconforming
       gdt_32_code:
    ;limit = 16mb 1111 1111 1111 1111 1111 1111
 ;address limit bytes #1 & 2
           db 11111111b
        db 11111111b
  ;base = 0mb
 ;base address 3 byte low
          db 0
        db 0
        db 0
  ;accessed=0,readable=1,conforming=0,data/code=1,system=1,priveledge=00,present=1
    ;p.pp.s.d.c.r.a
           db 10011010b
  ;free=0,long seg=0,default=1,granularity=1
  ;g.d.l.f + 4 bits upper of limit
          db 11001111b
  ;base address byte #4
             db 0
  gdt_32_code_end:
    ; Data segment, read/write, expand down
 gdt_32_data:
    ;limit = 16mb 1111 1111 1111 1111 1111 1111
 ;address limit bytes #1 & 2
           db 11111111b
        db 11111111b
  ;base = 0mb
 ;base address bytes #1, 2 & 3
         db 0
        db 0
        db 0
  ;accessed=0,readable=1,conforming=0,data/code=0,system=1,priveledge=00,present=1
    ;p.pp.s.d.c.r.a
           db 10010010b
  ;free=0,long seg=0,default=1,granularity=1
  ;g.d.l.f + 4 bits upper of limit
          db 11001111b
  ;base address byte #4
             db 0
  gdt_32_data_end:
    ;end of gdt
     gdt_32_end:

;--- 32 bit gdt descriptor --------------------------------------------------------
  gdt_32_desc:
    ;size (limit) of gdt
        dw gdt_32_end - gdt_32 - 1
    ;address of gdt
   dd gdt_32+8000h

;--- 32 bit interupt descriptor table --------------------------------------------------------
       idt_32:
    ;idt entry format
                ;57-63    offset bytes 3 and 4
         ;byte 6
          ;56       present bit
               ;44-45    descriptor privledge level
                ;43       0
         ;42       gate size 1=32bit, 0=16
           ;39-41    110 int gate type
    ;byte 5
          ;36-38    unused 3 bits
             ;32-36    reserved 5 bits
      ;byte 4
          ;16-31    segment selector 2 bytes
     ;byte 2
          ;0-15     offset byte 1 and 2
          ;byte 0
       ;first 32 interupts
       repeat 20h
              dw 0x0000
           dw 0x08
             dw 0xE00
            dw 0x00
         end repeat
       ;interupt 32 0x20
   idt_32_int0x20:
    ;low offset
              dw      INT_HANDLER_0x20
       ;segment selector
                dw      0x08
           ;reserved and unused
             db      0
      ;type=110,size=1,unused,dpl=0,present=1
     ;p.dp.0.s.typ
            db      10001110b
      ;high offset
             dw      (INT_HANDLER_0x20+8000h)/7FFFh
      idt_32_end:

;--- 32 bit idt descriptor --------------------------------------------------------
  idt_32_desc:
    ;size (limit) of gdt
        dw idt_32_end - idt_32 - 1
    ;address of gdt
   dd idt_32+8000h

    


This is the bootloader- there isnt anything wrong with it, but someone may ask to see it
Code:
; boot record is loaded at 0000:7c00
org 7c00h

; initialize the stack:
mov   ax, 07c0h
mov        ss, ax
mov   sp, 03feh ; top of the stack.


; set data segment:
xor ax, ax
mov   ds, ax

; print welcome message:
mov       si, msg
call print_string

;===================================
; load the kernel at 0800h:0000h
; 10 sectors starting at:
;   cylinder: 0
;   sector: 2
;   head: 0

; BIOS passes drive number in dl,
; so it's not changed:

mov     ah, 02h ; read function.
mov al, 10  ; sectors to read.
mov       ch, 0   ; cylinder.
mov      cl, 2   ; sector.
mov        dh, 0   ; head.
; dl not changed! - drive number.

; es:bx points to receiving
;  data buffer:
mov       bx, 0800h   
mov     es, bx
mov   bx, 0

; read!
int     13h
;===================================

; integrity check:
push ds
mov ax, 800h
mov ds, ax
cmp       byte [ds:0],0EBh  ; first byte of kernel must be 0E9 (jmp).
pop ds
je     integrity_check_ok

; integrity check error
mov    si, err
call print_string

; wait for any key...
mov        ah, 0
int    16h

; store magic value at 0040h:0072h:
;   0000h - cold boot.
;   1234h - warm boot.
mov       ax, 0040h
mov        ds, ax
mov   word [ds:0072h], 0000h ; cold boot.
jmp  0ffffh:0000h             ; reboot!

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

integrity_check_ok:
; pass control to kernel:
jmp       0800h:0000h

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



print_string:
push    ax      ; store registers...
push    si      ;
next_char:     
    mov     al, [si]
    cmp     al, 0
       jz      printed
     inc     si
  mov     ah, 0eh ; teletype function.
        int     10h
 jmp     next_char
printed:
pop        si      ; re-store registers...
pop  ax      ;
ret


                   
                    
                    
;==== data section =====================

msg  db "Loading...",0Dh,0Ah, 0 
     
err  db "invalid data at sector: 2, cylinder: 0, head: 0 - integrity check failed.", 0Dh,0Ah
     db "System will reboot now. Press any key...", 0
    
;======================================

;-- fill up file with zeroes 512 bytes - boot sector id---------------------------
       times 510-($-$$) db 0
;--boot sector identifier---------------------------------------------------------
       dw 0AA55h
       END_PROG:

    


If you can see whats broke I would greatly appreciate it Smile
Post 30 Jul 2007, 15:50
View user's profile Send private message Reply with quote
Gizmo



Joined: 19 Jul 2007
Posts: 25
Gizmo 30 Jul 2007, 16:16
You have to uncomment the int 20h line so you will see it crash, if you run it as is it will run fine.

It never reaches the handler, so it is probbably something wrong with the address of the handler in the idt or the idt itself?

How do you use the preprocessor to and numbers and to do bitshifts?
so i can clean up this:
Code:
...
idt_32_int0x20:
           ;low offset
                dw      INT_HANDLER_0x20+8000h ;this needs to be and'ed with FFFF
           ;segment selector
                dw      0x08
           ;reserved and unused
                db      0
           ;type=110,size=1,unused,dpl=0,present=1
           ;p.dp.0.s.typ
                db      10001110b
           ;high offset
                dw      (INT_HANDLER_0x20+8000h)/7FFFh ;bitshifted by 16 bits
        idt_32_end: 
    
Post 30 Jul 2007, 16:16
View user's profile Send private message Reply with quote
Gizmo



Joined: 19 Jul 2007
Posts: 25
Gizmo 31 Jul 2007, 14:24
I fixed it, but its not a permanent fix
I replaced the above idt entry with
Code:
idt_32_int0x20:
           ;low offset
                dw      INT_HANDLER_0x20+8000h
           ;segment selector
                dw      0x08
           ;reserved and unused
                db      0
           ;type=110,size=1,unused,dpl=0,present=1
           ;p.dp.0.s.typ
                db      10001110b
           ;high offset
                dw      0

    

since I don't know how to use the fasm dirrectives for anding and bitshifts .
It only works until my address exceedes 16 bits then I'll have issues.

If anyone can tell me the directives for anding and bitshifts I would appreciate it.

btw: why the heck do they have the address split up like that? why not just simply put the low and high parts together- is it for compatibility with 16 bit i286 idt's?
Post 31 Jul 2007, 14:24
View user's profile Send private message Reply with quote
Display posts from previous:
Post new topic Reply to topic

Jump to:  


< Last Thread | Next Thread >
Forum Rules:
You cannot post new topics in this forum
You cannot reply to topics in this forum
You cannot edit your posts in this forum
You cannot delete your posts in this forum
You cannot vote in polls in this forum
You cannot attach files in this forum
You can download files in this forum


Copyright © 1999-2024, Tomasz Grysztar. Also on GitHub, YouTube.

Website powered by rwasa.