Newer
Older
ubixos / src / sys / boot / bootsec.asm
@reddawg reddawg on 14 Aug 2002 8 KB made some quick changes to ls
; $Id$

%include "gdtnasm.inc"

[ORG 0x7c00]
jmp start
nop

id                               db    'UbixFS' ;file system id
version                      dd   1h          ; Filing System Version
fs_start                     dd   257          ; LBA address for start of root dir
krnl_size                   dd   59            ; Kernel size in sectors, starts at sector 1
BytesPerSector         dw  512
SectorsPerTrack        dw   18
TotalHeads               dw   2
TotalSectors              dd   2880     ; 1474560/512 for a 1.44meg disk
file_entry_nextdata  equ  273      ; Offset in file_entry structure to the nextdata LBA pointer
data_entry_data       equ  9          ; Offset in data_entry structure to the data
bootdrv                      db    0

start:
xor ax, ax
mov ds, ax
mov [bootdrv], dl
; First get into protected mode
cli
n5:
  in al, 0x64  ;Enable A20 {4A} {5}
  test al, 2
  jnz	n5
  mov	al, 0xD1
  out	0x64, al
n6:
  in al, 0x64
  test al, 2
  jnz n6
  mov al, 0xDF
  out 0x60, al
  lgdt    [gdtinfo]               ;Load GDT
  mov ecx, CR0		;Switch to protected mode
  inc cx
  mov CR0, ecx
  mov	ax, flat_data-gdt_table	; Selector for 4Gb data seg
  mov	ds, ax			; {2} Extend limit for ds
  mov	es, ax			; Extend limit for es
  mov	fs, ax			; fs and...
  mov 	gs, ax			; gs
  dec cx				; switch back to real mode
  mov CR0, ecx
  sti
  xor ax, ax
  mov ds, ax
  mov dl, [bootdrv]
  mov bx, 0x60
  mov es, bx
  mov eax, 1
  mov ecx, [krnl_size]
  mov di, 1
load_loop:
  call read_sectors
  inc eax
  mov bx, es
  add bx, 32
  mov es, bx
  loop load_loop
  ; Turn off the floppy motor, its annoying leaving it on !
  mov edx,0x3f2
  mov al,0x0c
  out dx,al
  ;lets convert the ELF file to a linear binary so we can execute it
  cmp dword [0x600],464c457fh  ; The ELF signature is \07fELF
  jne ldr_ELF_err            ; Ugh... not an ELF file !!!
  cmp word [0x600+4],101h    ; It should be statically linked etc.
  jne ldr_ELF_err
  cmp byte [0x600+6],1
  jne ldr_ELF_err
  jmp short skip_err_handler
  ldr_ELF_err:
  mov ax, 'E'+0x0E00
  mov bx, 7
  int 10h
  mov al, 'L'
  int 10h
  mov al, 'F'
  int 10h
  cli
  hlt
skip_err_handler:

	mov eax, [0x600+18h]
	mov [krnl_entry], eax

        xor ecx,ecx                     ; Get the number of sections in cx
        mov cx,[0x600+2ch]

sectionloop:
        dec cx                          ; Next section
        push cx                         ; Save cx on the stack while we load
                                        ; the section into memory
        mov bx, 0x600									  ; access image location

        mov ax,[bx+2ah]        					; Get the program header entry size
        mul cx                          ; Calculate the offset from the start
                                       	; of the program header table
        add ax,[bx+1ch]        					; ax <= PHT offset + PHT entry offset
        add bx,ax                     	; bx <= ax(PHT offset + PHT entry offset)
																				;				+ image location of ELF file (0x600)

        cmp dword [bx],1                ; Does this section have to be
                                        ; loaded into memory ?
        jne nextsect                    ; No, next section

        mov dword ecx,[bx+10h]          ; Get the size of the segment in the
                                        ; ELF file

        mov dword edi,[bx+8h]           ; Get the memory address of the sect.

        mov dword eax,[bx+14h]          ; eax <= the size of the section

        mov dword ebx,[bx+4h]           ; Get the offset of the segment in
                                        ; the ELF file
				add ebx, 0x600									;

				; set up for memcopy

				mov edx, edi	; edx <- set dest addr
				add edi, ecx	;	move past part which will be copied
				sub eax, ecx	;	eax <- store zero fill size
				; ebx is already source addr
				; ecx is already count
	
				; set up for memcopy
				;mov esi, 0x600
				;add esi, ecx
				;mov ecx, edx

				;call memcopy
				call nonmajicmemcpy

        ; warnng, ,assume zero-fill < 64K
				;test ax,ax                     	; This amount needs to be zeroed
        ;jz nextsect                     ; It's ok, next section

        ; store zero fill size
				;mov ecx, eax
				;add edi,edx                     ; Zero the memory from this address
        ;xor ax,ax                       ; edi is an absolute address
        ;mov ecx,ebx
        ;call zero_memblock              ; Zero the rest of the section

nextsect:
        pop cx                          ; Restore our section count
        or cx,cx                        ; Was this the last one ?
	
	jnz sectionloop


; Re-enter protected mode ! A20 is already enabled

;mov ax,0x4F01
;mov cx,0x4115
;mov bx,0x100
;mov es,bx
;xor di,di
;xor bx,bx
;int 0x10


;mov ax,0x4F02
;mov bx,0x4115
;int 0x10


;mov ax, 0x4f0a
;xor bx,bx
;int 0x10
;xor eax,eax
;mov ax,es
;mov bx,di
;xor dx,dx
;mov es,dx
;mov si, 0x3000
;mov [es:si],ax
;mov [es:si+4],bx
;mov [es:si+8],cx
	cli		; No interrupts please at all
	lgdt [gdtinfo]
	mov ecx, cr0
	inc cx
	mov cr0, ecx
	mov ax, flat_data-gdt_table
	mov ds, ax
	mov es, ax
	mov fs, ax
	mov gs, ax

	jmp dword (flat_code-gdt_table):pmode1

	pmode1:
[BITS 32]

	push dword 2
	popfd

	mov eax, [krnl_entry]

	call eax

	cli
	hlt

;Hang the system..
hang:	jmp hang

[BITS 16]
	read_sectors:
; Input:
;	EAX = LBN
;	DI  = sector count
;	ES = segment
; Output:
;	BL = low byte of ES
;	EBX high half cleared
;	DL = 0x80
;	EDX high half cleared
;	ESI = 0

	pusha

	cdq			;edx = 0
	movzx	ebx, byte [SectorsPerTrack]
	div	ebx		;EAX=track ;EDX=sector-1
	mov	cx, dx		;CL=sector-1 ;CH=0
	inc	cx		;CL=Sector number
	xor	dx, dx
	mov	bl, [TotalHeads]
	div	ebx

	mov	dh, dl		;Head
	mov	dl, [bootdrv]	;Drive 0
	xchg	ch, al		;CH=Low 8 bits of cylinder number; AL=0
	shr	ax, 2		;AL[6:7]=High two bits of cylinder; AH=0
	or	cl, al		;CX = Cylinder and sector
	mov	ax, di		;AX = Maximum sectors to xfer
retry:	mov	ah, 2		;Read
	xor	bx, bx
	int	13h
	jc retry

	popa

	ret

; zero_memblock:  Fills the specified memory block with zeros (0x0)
;
; Takes parameters:
; ax    = segment/selector of memory to be cleared
; edi   = offset of memory to be cleared
; ecx   = number of bytes to clear
;
; Returns:
; nothing

;zero_memblock:
;        push eax                ; Save the registers
;        push edi
;        push ecx
;        push es
;        mov es,ax
;        xor eax,eax             ; Fill the memory with zeros (0x0)
;        cld                     ; Clear the direction flag; rep increments di
;        a32 rep stosb           ; Fill the memory (one byte at a time)
;        pop es                  ; Restore the registers
;        pop ecx
;        pop edi
;        pop eax
;        ret                     ; Return to the main program

; Parameters
; DS:ESI = Source
; DS:EDI = Destination
; CX = length
;memcopy:
;	pusha
;memcopy_loop:
;	mov al, [esi]
;	mov [edi], al
;	inc edi
;	inc esi
;	loop memcopy_loop
;	popa
;	ret

; edx = dest
; ebx = source
; ecx = count
;
; all other registers maintained
nonmajicmemcpy:
	pusha

	; preserve segments
	push ds
	push es

	push cx				; [stack] <- 'left-over' after full 256 byte copies

	
	xor ax, ax

	; break size into 256 byte chuunks
	shr ecx, 8		; cx <- number of 256 byte copies to perform
	mov bp, cx		; bp <- number of 256 byte copies to perform

	mov cl, 4

  ; break destination into 256 byte chuunks
	xchg al, dl		; al <- initial 'offset' of destination
								; edx <- 16 X initial 'segment' of destination
	shr edx, cl		; dx <- initial 'segment' of destination

  ; break source into 256 byte chuunks
	xchg ah, bl		; ah <- initial 'offset' of source
								; ebx <- 16 X initial 'segment' of source
	shr ebx, cl		; bx <- initial 'segment' of source

	cld			; clear direction flag
	inc bp	; pre-increment 256 section count

nonmajicmemcpy_loop256:
	movzx si, ah	; restore initial source addr
	movzx di, al	; restore initial dest addr

	; restore/set segment addrs
		mov ds, bx
		mov es, dx

	; done?
	dec bp
	jz nonmajicmemcpy_rest

	; copy one 256 byte run
	mov cx, 0100h
	a16 rep movsb

	; move 'segments' 256 bytes forwards
	; (eax = [es:ds])
	add bx, 0010h
	add dx, 0010h

	; continue
	jmp nonmajicmemcpy_loop256

nonmajicmemcpy_rest:
	pop cx            ; restore 'left-over' after full 256 byte copies
	inc cl						; pre increment count

nonmajicmemcpy_restloop:
	dec cl
	jz nonmajicmemcpy_done

	movsb
	jmp nonmajicmemcpy_restloop

nonmajicmemcpy_done:

	; restore segments
	pop es
	pop ds

	popa
	ret	

	
	
	
		


gdtinfo:

dw	gdtlength
dd	gdt_table

;********* GDT TABLE
gdt_table:

null_desc	desc	0,0,0

flat_code	desc	0, 0xFFFFF, D_CODE + D_READ + D_BIG + D_BIG_LIM

flat_data	desc	0, 0xFFFFF, D_DATA + D_WRITE + D_BIG + D_BIG_LIM

gdtlength equ $ - gdt_table - 1
;********* END GDT TABLE
krnl_entry	dd	0

times 510-($-$$) db 0
dw 0xAA55