Initial checkin of toy OS project.
[os.git] / boot0 / boot0.asm
1 ;
2 ; This boot sector was based on VnutZ's example available online
3 ; at http://www.geocities.com/mvea/bootstrap.htm.  It also made use
4 ; of info at http://support.microsoft.com/support/kb/articles/Q140/4/18.asp
5 ; and the source code for geekos.
6 ;
7 ; It searches the root directory of a floppy for two files: boot.com and
8 ; kernel.bin.  If either is missing the boot fails.  If they are found, they
9 ; are loaded into memory at BOOT1SEG:BOOT1OFF and KERNSEG:KERNOFF.  Then
10 ; control is passed to the next stage bootloader, boot.com.
11
12 %include "../inc/defs.asm"
13         
14 [BITS 16]
15 [ORG 0]
16
17 START:  
18         jmp AROUND_DATA
19         
20 szOEM_ID              db "SCOTTOS", 0    ; 8 bytes, null not required
21 wBytesPerSector       dw 0x0200          ; bytes per sector
22 bSectorsPerCluster    db 0x01            ; sectors per cluster
23 wReservedSectors      dw 0x0001          ; reserved sectors (boot sector)
24 bTotalFATs            db 0x02            ; num copies of the FAT
25 wMaxRootEntries       dw 0x00E0          ; max num entries in root directory
26 wTotalSectorsSmall    dw 0x0B40          ; 
27 bMediaDescriptor      db 0xF0            ; 
28 wSectorsPerFAT        dw 0x0009          ; length of single FAT copy in sectors
29 wSectorsPerTrack      dw 0x0012          ; sectors per track
30 wNumHeads             dw 0x0002          ; num heads
31 dwHiddenSectors       dd 0x00000000      ; num hidden sectors
32 dwTotalSectorsLarge   dd 0x00000000      ; 
33 bDriveNumber          db 0x00            ; 0x00=A: 0x01=B: 0x80=C: ...
34 bFlags                db 0x00            ; 
35 bSignature            db 0x29            ; 
36 dwVolumeID            dd 0xFFFFFFFF      ; 
37 szVolumeLabel         db "SCOTT BOOT", 0 ; 11 bytes, null not required
38 szSystemID            db "FAT12   "      ; 
39
40 AROUND_DATA:    
41 ;;; setup segment registers, this code is located at 7C00:0000
42         mov dx, BOOT0SEG        ; 7C00
43         mov ds, dx
44         mov es, dx
45         
46 ;;; create a temporary stack at the top of segment 7C00
47         mov ss, dx
48         mov sp, 0xFFFF          ; top of this segment
49
50 LOAD_ROOT_DIRECTORY:
51 ;;; 
52 ;;; Compute the length (in number of disk sectors) of the floppy's
53 ;;; root directory information:
54 ;;;
55 ;;; wNumRootDirectorySectors = sizeof(directory_entry) *
56 ;;;                            wMaxRootEntries / wBytesPerSector
57 ;;;
58 ;;; Store this in cx and in the wNumRootDirectorySectors identifier.
59 ;;; 
60         mov ax, 0x0020          ; sizeof(directory_entry)
61         mul WORD [wMaxRootEntries]
62         div WORD [wBytesPerSector]
63         mov cx, ax              ; count of num sectors to read for dir
64
65 ;;; 
66 ;;; Compute the starting location of the root directory (sector number):
67 ;;;
68 ;;; wRootDirectoryStartSector = wReservedSectors +
69 ;;;                             (bTotalFATs * wSectorsPerFAT)
70 ;;; 
71         mov al, BYTE [bTotalFATs]
72         mul WORD [wSectorsPerFAT]
73         add ax, WORD [wReservedSectors]
74
75 ;;;
76 ;;; Compute the first sector after the root directory -- this is the
77 ;;; sector where real data starts on the floppy.
78 ;;;
79         mov WORD [wDriveDataStartSector], ax
80         add WORD [wDriveDataStartSector], cx
81
82 ;;; 
83 ;;; Read the floppy's root directory into memory at BOOT0SEG:0200 by
84 ;;; calling ReadSectors.  This function reads cx count (wNumRootDirSectors)
85 ;;; starting at sector ax (wRootDirStartSector) into memory at es:bx
86 ;;;
87         mov bx, 0x0200
88         call ReadSectors       
89
90 SEARCH_ROOT_DIRECTORY:  
91 ;;;
92 ;;; Search the root directory for the stage two loader and the kernel.
93 ;;;
94         mov cx, WORD [wMaxRootEntries]
95         mov di, 0x0200          ; offset of first directory entry
96 .LOOP:
97         push cx                 ; save current entry count
98         mov cx, 0x000B          ; 11 char name
99         mov si, szStage2Image   ; name we are seeking
100         push di                 ; save current entry ptr
101         rep cmpsb               ; test for match
102         pop di                  ; restore entry ptr
103         jne .TRY_KERN           ; match? if not see if it matches the kernel
104         mov dx, WORD [di+1Ah]   ; match. save the starting cluster
105         mov WORD [wStage2Cluster], dx
106 .TRY_KERN:
107         mov cx, 0x000B          ; 11 char name
108         mov si, szKernelImage   ; name we are seeking
109         push di                 ; save current entry ptr
110         rep cmpsb               ; test for match
111         pop di                  ; restore entry ptr
112         jne .NEXT               ; match? if not next entry
113         mov dx, WORD [di+1Ah]   ; match. save the starting cluster
114         mov WORD [wKernelCluster], dx
115 .NEXT:
116         pop cx                  ; cx = entry count again
117         add di, 0x0020          ; next directory entry (+32 bytes later)
118         loop .LOOP              ; cx -= 1, jmp .LOOP if cx != 0
119
120 .DONE:
121 ;;;
122 ;;; Did we find both the kernel and the second stage boot loader?  If not
123 ;;; give them a "missing operating system" message.
124 ;;;
125         mov ax, [wStage2Cluster]
126         test ax, 0xFFFF
127         jz .NOOS
128         mov ax, [wKernelCluster]
129         test ax, 0xFFFF
130         jnz LOAD_FAT
131 .NOOS:
132         mov si, szNoOperatingSystem
133         call Write
134 FAIL:   mov ah, 0x00            ; wait for a keystroke and reboot
135         int 0x16
136         int 0x19
137
138 LOAD_FAT:
139 ;;;
140 ;;; Prepare the load the FAT into memory.  Compute the size of the FAT (in
141 ;;; number of sectors) and store in cx for a call to ReadSectors.
142 ;;;
143         xor ax, ax
144         mov al, BYTE [bTotalFATs]
145         mul WORD [wSectorsPerFAT]
146         mov cx, ax
147
148 ;;; 
149 ;;; Compute location of FAT and store in ax
150 ;;; 
151         mov ax, WORD [wReservedSectors]
152
153 ;;; 
154 ;;; Read the FAT into memory at BOOT0SEG:0200.  This overwrites the root
155 ;;; directory information but we already have the cluster number for the
156 ;;; stage two boot loader and the kernel.
157 ;;; 
158         mov bx, 0x0200
159         call ReadSectors
160
161 ;;; 
162 ;;; Prepare to read the stage two boot loader into memory at 
163 ;;; BOOT1SEG:BOOT1OFF
164 ;;;
165         ;; point es:bx at where we want the stage two loader read into memory
166         mov ax, BOOT1SEG
167         mov es, ax              ; destination for image
168         mov bx, BOOT1OFF        ; destination for image
169         
170         ;; use the starting cluster we found by reading the directory
171         mov ax, WORD [wStage2Cluster]
172         mov WORD [wCluster], ax
173
174         ;; call LOAD_IMAGE to read in the file
175         call LOAD_IMAGE
176
177 ;;;
178 ;;; Prepare to read the kernel into memory at KERNSEG:KERNOFF
179 ;;; 
180         ;; point es:bx at where we want the kernel read into memory
181         mov ax, KERNSEG
182         mov es, ax
183         mov bx, KERNOFF
184
185         ;; use the starting cluster we found by reading the directory
186         mov ax, WORD [wKernelCluster]
187         mov WORD [wCluster], ax
188
189         ;; call LOAD_IMAGE to read in the file
190         call LOAD_IMAGE        
191
192 DONE:
193 ;;;
194 ;;; We're done, transfer control to the second stage loader which we
195 ;;; put at BOOT1SEG:BOOT1OFF.
196 ;;; 
197         push WORD BOOT1SEG
198         push WORD BOOT1OFF
199         retf
200
201 ;; *************************************************************************
202 ;;  PROCEDURE ClusterLBA
203 ;;  convert FAT cluster into LBA addressing scheme
204 ;;  LBA = (cluster - 2) * sectors per cluster
205 ;; *************************************************************************
206 ClusterLBA:
207         sub ax, 0x0002          ; cluster number is zero-based
208         xor cx, cx
209         mov cl, BYTE [bSectorsPerCluster];  convert byte to word
210         mul cx
211         add ax, WORD [wDriveDataStartSector];  base data sector
212         ret
213                 
214 ;;; *************************************************************************
215 ;;; PROCEDURE LBACHS
216 ;;; 
217 ;;; convert ax LBA addressing scheme to CHS addressing scheme using these
218 ;;; formulas:
219 ;;; 
220 ;;; absolute sector = (logical sector / sectors per track) + 1
221 ;;; absolute head   = (logical sector / sectors per track) MOD number of heads
222 ;;; absolute track  = logical sector / (sectors per track * number of heads)
223 ;;; *************************************************************************
224 LBACHS:
225         xor dx, dx
226         div WORD [wSectorsPerTrack]
227         inc dl                  ; adjust for sector 0
228         mov BYTE [bAbsoluteSector], dl
229         xor dx, dx              ; prepare dx:ax for operation
230         div WORD [wNumHeads]
231         mov BYTE [bAbsoluteHead], dl
232         mov BYTE [bAbsoluteTrack], al
233         ret
234         
235 ;;; *************************************************************************
236 ;;; PROCEDURE ReadSectors
237 ;;; 
238 ;;; reads disk sectors ax..ax+cx from the disk into memory at es:bx
239 ;;; 
240 ;;; *************************************************************************
241 ReadSectors:
242 .MAIN
243         mov di, 5               ; five retries for disk errors
244 .SECTORLOOP
245         push ax
246         push bx
247         push cx
248         call LBACHS             ; convert LBA sector in ax into absolute CHT
249         mov ah, 0x02            ; BIOS read sector
250         mov al, 0x01            ; read one sector
251         mov ch, BYTE [bAbsoluteTrack]
252         mov cl, BYTE [bAbsoluteSector]
253         mov dh, BYTE [bAbsoluteHead]
254         mov dl, BYTE [bDriveNumber]
255         int 0x13
256         jnc .SUCCESS            ; CF=1 on read error
257
258         ;; read error, reset the disk and try again
259         xor ax, ax              ; BIOS reset disk
260         int 0x13
261         dec di                  ; error counter -= 1
262         pop cx                  ; restore registers
263         pop bx
264         pop ax
265         jnz .SECTORLOOP         ; if error counter != 0, try to read again
266
267         ;; give up
268         mov si, szReadError
269         call Write
270         jmp FAIL
271         
272         ;; sector read succeeded
273 .SUCCESS
274         pop cx                  ; restore registers
275         pop bx
276         pop ax
277         inc ax                  ; next sector
278
279         ;;; bx += wBytesPerSector
280         add bx, WORD [wBytesPerSector]
281         loop .MAIN              ; cx -= 1, jmp .MAIN if cx != 0
282         ret
283         
284 ;;; *************************************************************************
285 ;;; PROCEDURE Write
286 ;;; 
287 ;;; display ASCIIZ string at ds:si via BIOS
288 ;;; *************************************************************************
289 Write:
290         cld                     ; make sure direction flag is correct
291         lodsb                   ; load char to al, increment si
292         or al, al               ; see if it's null
293         jz .DONE                ; if so, we're finished
294         mov ah, 0x0E            ; service 0x0E: output one char
295         mov bh, 0x00            ; display page 0
296         mov bl, 0x07            ; char text attrib (white on black)
297         int 0x10                ; invoke bios
298         jmp Write               ; next char
299 .DONE:
300         ret
301
302 LOAD_IMAGE:
303         mov ax, WORD [wCluster] ; cluster to read
304         call ClusterLBA         ; convert cluster to LBA
305         xor cx, cx
306         mov cl, BYTE [bSectorsPerCluster]
307         call ReadSectors        ; this increments bx
308         
309         ;; compute next cluster
310         mov ax, WORD [wCluster] ; identify current cluster
311         mov cx, ax              ; copy current cluster
312         mov dx, ax              ; copy current cluster
313         shr dx, 0x0001          ; dx = wCluster / 2
314         add cx, dx              ; cx = wCluster + (wCluster / 2)
315         push bx
316         mov bx, 0x0200          ; location of FAT in memory
317         add bx, cx              ; index into FAT
318         mov dx, WORD [bx]       ; read two bytes from FAT
319         pop bx
320         test ax, 0x0001         ; is the cluster even or odd?
321         jnz .ODD
322 .EVEN:
323         and dx, 0x0FFF          ; take low twelve bits
324         jmp .DONE
325 .ODD:   
326         shr dx, 0x0004          ; take high twelve bits
327 .DONE:
328         mov WORD [wCluster], dx ; store new cluster
329         cmp dx, 0x0FF0          ; test for end of file
330         jb LOAD_IMAGE           ; if not, go get the next one
331         ret
332         
333 wDriveDataStartSector           dw      0x0000
334 szStage2Image                   db      "BOOT    COM", 0
335 wStage2Cluster                  dw      0x0000
336 szKernelImage                   db      "KERNEL  BIN", 0
337 wKernelCluster                  dw      0x0000
338 szNoOperatingSystem             db      "Missing OS File", 13, 10, 0
339 szReadError                     db      "Disk read error", 13, 10, 0
340 wCluster                        dw      0x0000
341 bAbsoluteSector                 db      0x00
342 bAbsoluteHead                   db      0x00
343 bAbsoluteTrack                  db      0x00
344 szProgress                      db      ".", 0
345                 
346         TIMES 510-($-$$) DB 0   ; 0 padding
347         DW 0xAA55               ; bootsector signature