implemented chainloading from hd
[bootboot] / bb.asm
1 ; org: all instructions from now on start in 7c00h
2 ; 7c00h is where the bios loads the 1st sector
3 ; assembler formatting:
4 ; column 0: labels
5 ; tab: commands
6         org 7c00h
7 ; at boot: real mode (like it's 8086)
8 ; we have to tell assembler that code is 16bit mode
9         bits 16
10
11 ; macros
12 %macro SETPAL 4 ; 4 = num arguments of macro (index rgb)
13         mov dx, 3c8h    ; index register
14         mov al, %1
15         out dx, al
16         inc dx
17         mov al, %2 >> 2
18         out dx, al
19         mov al, %3 >> 2
20         out dx, al
21         mov al, %4 >> 2 ; shift to give the value from 0 - 255
22         out dx, al
23 %endmacro
24
25 bios_param_block:
26         jmp start       ; 2 bytes
27         nop             ; 1 byte
28         ; start of BPB at offset 3
29         db "BSPL 0.1"   ; 03h: OEM ident, 8 bytes
30         dw 512          ; 0bh: bytes per sector
31         db 1            ; 0dh: sectors per cluster
32         dw 1            ; 0eh: reserved sectors (including boot record)
33         db 2            ; 10h: number of FATs
34         dw 224          ; 11h: number of dir entries
35         dw 2880         ; 13h: number of sectors in volume
36         db 0fh          ; 15h: media descriptor type (f = 3.5" HD floppy)
37         dw 9            ; 16h: number of sectors per FAT
38         dw 18           ; 18h: number of sectors per track
39         dw 2            ; 1ah: number of heads
40         dd 0            ; 1ch: number of hidden sectors
41         dd 0            ; 20h: high bits of sector count
42         db 0            ; 24h: drive number
43         db 0            ; 25h: winnt flags
44         db 28h          ; 26h: signature(?)
45         dd 0            ; 27h: volume serial number
46         db "BOOTBOOT   "; 2bh: volume label, 11 bytes
47         db "FAT12   "   ; 36h: filesystem id, 8 bytes
48
49 start:
50         mov sp, 7c00h
51
52 ; initialize segment registers
53         mov ax, 0
54         mov ds, ax
55         mov es, ax
56         mov ss, ax
57
58 ; save dl value
59 ; bios sets in dl the num of the drive that
60 ; loaded you so if you overwrite dl you can reuse it
61         mov [saved_drive_num], dl
62
63 ; service 0: set videomode ah
64 ; param: which video mode (13h: 320x200, 256 colors) al
65 ; ax: ah (high 8 bits), al (low)
66 ; call 0 = set_videomode it expects the video mode in al
67 ; ah : 0, al: 13, ax:ahal
68         mov ax, 13h
69
70 ; calling video bios
71 ; software interrupt 10h
72 ; what's the value of ah? al=video mode when ah=0
73 ; which set which video mode
74         int 10h
75         mov ax, 3
76         call clearscreen
77
78 ; load 2nd sector from boot device and jump to it
79 ; bios helpers, 13h = disk io
80         mov ax, 0
81         mov ds, ax
82         mov ah, 02h                             ; call 2: read sectors into memory
83         mov al, 3                                       ; number of sectors to read
84         mov ch, 0                                       ; low 8 bits of cylinder number
85         mov cl, 2                                       ; sector number that starts from 1
86         mov dh, 0                                       ; head number
87         mov dl, [saved_drive_num]       ; 8bits
88         mov bx, sector_2
89         int 13h
90 ; error check: if carry flag isn't set jump to loaded code
91         jnc     sector_2
92 .inf_loop:
93         jmp .inf_loop
94
95
96 clearscreen:
97 ; video ram is mapped in a0000
98 ; first 64000 bytes appear immediately on screen
99 ; mem addresses in real mode have 2 parts: segment and offset
100 ; bits overlap: segment is shifted by 4 and is added to the
101 ; overlapping offset (20 bits number = x86's addressable space = 1MB)
102 ; segment register for the segment: es, ds, cs, ss (and: fs, gs)
103 ; default register = ds (data segment), es = extra segment
104 ; cs = code segment cs:ip (it points where to read instructions and is
105 ; automatically set to 7c0 (7c00h)
106 ; offset can be paired with any register
107 ; pair the registers
108         push ax
109         mov ax, 0a000h
110         mov ds, ax
111         mov di, 0
112         pop ax
113 ; counter cx
114         mov cx, 64000
115
116 .loop_begin:
117 ; dereferrence[] address
118         mov [di], al
119         inc     di
120         dec cx
121 ; when cx is 0, 0 flag is set
122         jnz .loop_begin
123         ret
124
125 saved_drive_num:
126         db 0 ; define byte 0
127
128 ; assembler trick: write as many 0 needed to fill 510 bytes
129 ; $ <- means here
130         times 510-($-$$) db 0
131         dw 0aa55h
132
133 sector_2:
134 ; disp palette
135         mov ax, 0a000h  ; video segment points to video memory
136         mov ds, ax
137         mov bx, 0               ; video offset
138         mov cx, 0               ; y
139 .y_loop:
140         mov dx, 0               ; x
141 .x_loop:
142         mov ax, dx
143         test ax, 0ff00h ; lower 8 bits 0, highest 1, Z flag is set while < 256, test = and but doesnt change ax 
144         jz      .skip_clear_ax
145         mov al, 0
146 .skip_clear_ax:
147         mov [bx], al    ; pixel written on screen
148         inc bx                  ; increment
149         inc dx
150         cmp dx, 320
151         jnz .x_loop
152         inc cx
153         cmp cx, 200
154         jnz .y_loop
155
156 ; setup grayscale palette (64 first colors because ramdac uses 6 bits / color so 2^6)
157 ; ram dac (digital to analog converter) tis vga
158 ; in a ^ register which index we want to write
159 ; 3 writes in another ramdac register (data)
160 ; ramdac feature: when you need to set a palette
161         mov al, 0               ; first index
162         mov dx, 3c8h    ; ramdac index registe
163         out dx, al              ; because io port (address) > 255
164         inc dx                  ; ramdac data register: 3c9h
165 .pal_loop:
166         out dx, al              ; r
167         out dx, al              ; g
168         out dx, al              ; b
169         inc al
170         test al, 3fh    ; test with 3fh to keep the lowest 6 bits of al
171         jnz .pal_loop
172
173 ; setup lovebug palette
174         SETPAL 64, 0, 255, 0    ; chr(64) = @
175         SETPAL 65, 0, 0, 0              ; A
176         SETPAL 66, 50, 50, 50   ; B
177         SETPAL 67, 57, 4, 4             ; C
178         SETPAL 68, 108, 9, 9    ; D
179         SETPAL 69, 164, 4, 4    ; E
180
181 ; disable all interrupts (for bios to not read the keyboard)
182         cli
183
184         ; ds on 0 because rand uses it for accesses to mem
185         xor ax, ax
186         mov ds, ax
187         mov ax, backbuffer
188         shr ax, 4 ; to use it as segment! (shift right)
189         mov es, ax
190 main_loop:
191 ; draw to back buffer
192         xor bx, bx              ; mov bx, 0 to clear the register
193 .static_loop:
194         call rand
195         and ax, 3fh             ; last six bits of eax (see rand)
196         mov [es:bx], al    ; [] -> bx offset and default segment ds we change it to es
197         inc bx
198         cmp bx, 64000   ; num pixels
199         jnz .static_loop
200
201         ; draw lovebug
202         mov di, (200 - 32) * 320 + 160 - 16
203         mov ax, [num_frames]
204         shr ax, 2               ; /4
205         cmp ax, 200 - 32
206         jz .end
207         mov bx, ax
208         shl ax, 8
209         shl bx, 6
210         add ax, bx
211         sub di, ax
212         call rand
213         and ax, 3               ; random value in 0, 2
214         sub ax, 1               ; random value in -1, 1
215         add di, ax
216         mov si, lovebug
217         call blit32
218
219 ; wait for vblank
220 .vsync_blank:
221         mov dx, 3dah
222         in al, dx
223         and al, 8
224         jnz     .vsync_blank
225 .vsync_visible:
226         in al, dx
227         and al, 8               ; the 4th bit is 1 when we are in the vertical blanking period
228         jz .vsync_visible
229
230 ; copy backbuffer to video memory
231         push es
232         push ds
233         mov ax, es
234         mov ds, ax                      ; ds points to backbuffer now (was in es)
235         xor si, si
236         mov ax, 0a000h
237         mov es, ax
238         xor di, di                      ; write in es:di
239         mov ecx, 16000          ; 16000 double words (dwords) = 64000 bytes
240         rep movsd
241         pop ds
242         pop es
243
244         inc word [num_frames]
245 ;   moved above:
246 ;       cmp word [num_frames], 200 - 32
247 ;       jz .end
248
249         in al, 64h              ; 60h = keyb data port, 64h = keyb status port
250         and al, 1               ; 1 = OUTBUF_FULL = the keyb controller out buf is full
251         jz main_loop    ; no key pressed, loop back
252         in al, 60h              ; reads the keyb that was pressed to reset the flag
253
254 .end:
255 ; re-enable all interrupts
256         sti
257
258 ; text mode
259         mov ax, 3               ; text mode
260         int 10h
261 ; use bios to print
262 ; Int 10/AH=0Eh
263         mov si, str_frames  
264         call print_str
265         mov ax, [num_frames]
266         call print_num
267         mov si, str_newline
268         call print_str
269
270         mov dx, 80h             ; default to load from drive 80h
271         cmp byte [saved_drive_num], 80h
272         jnz .not_hd
273         inc dl                  ; next hd
274 .not_hd:
275 ; load hard disk boot sector
276         xor ax, ax
277         mov es, ax
278         mov bx, 7c00h
279         mov ah, 02h
280         mov al, 1
281         mov ch, 0
282         mov cl, 1
283         mov dh, 0
284         int 13h
285         jnc 7c00h
286 .inf_loop:
287         jmp .inf_loop
288
289 ; reads from ds:si writes to es:di (bug top left corner)
290 ; knows how many pixels on screen and how many in the lovebug
291 blit32:
292         mov cx, 1024    ; 32 x 32 lovebug
293 .loop:
294         mov al, [ds:si]
295         cmp al, 64
296         jz .skip_pixel
297         mov [es:di], al
298 .skip_pixel:
299         inc si
300         inc di
301
302         dec cx                          ; dec the num_pixels we want to write 
303         jz      .end                    ; all pixels have been written
304         test cx, 1fh            ; keep 5 least significant bits, 3 most significant bits 0
305         jnz .loop                       ; when this is 0 we are in a multiple of 32
306         add di, 320 - 32        ; screen width - bug width
307         jmp .loop
308 .end:
309         ret
310
311 print_str:
312         ;Int 10/AH=0Eh
313         mov al, [si]
314         test al, al
315         jz .end
316         mov ah, 0eh
317         xor bx, bx
318         int 10h
319         inc si
320         jmp print_str
321 .end:
322         ret
323
324 print_num:
325         ; converts digits to ascii - print
326         push word 0
327         test ax, ax
328         jnz .conv_loop
329         push word '0'
330         jmp .conv_end
331 .conv_loop:
332         test ax, ax
333         jz .conv_end
334         xor dx, dx
335         mov cx, 10
336         div cx  ; ax contains cx / 10
337         add dl, '0'
338         push dx
339         jmp .conv_loop
340 .conv_end:
341         mov bp, sp
342         mov ax, [ss:bp]
343         test ax, ax
344         jz .print_end
345         mov ah, 0eh
346         xor bx, bx
347         int 10h
348         add sp, 2
349         jmp .conv_end
350 .print_end:
351         add sp, 2
352         ret
353
354 ; random number generator
355 ; by nuclear
356 rand:
357         mov eax, [randval]
358         mul dword [randmul]
359         add eax, 12345
360         and eax, 0x7fffffff
361         mov [randval], eax
362         shr eax, 16
363         ret
364
365 randmul dd 1103515245
366 randval dd 0ace1h
367
368 num_frames dw 0
369 str_frames db 'frames: ', 0
370 str_newline db 13, 10, 0        ; crlf carriage return line feed newline
371
372 ; db to write pixels transparent 255
373 ; @: transparent
374 ; A: black
375 ; B: gray
376 ; C: dark red
377 ; D: medium red
378 ; E: red
379 lovebug:
380         db '@@@@BAAAB@@@@@BAAB@@@@@BAAAB@@@@'
381         db '@@@@@@@@AAAB@BAAAAB@BAAA@@@@@@@@'
382         db '@@@@@@@@@@@AAAAAAAAAA@@@@@@@@@@@'
383         db '@@@@@@@@@@@@AAAAAAAA@@@@@@@@@@@@'
384         db '@@@@@@@@@@@@AAAAAAAA@@@@@@@@@@@@'
385         db '@@@@@@@@@@@@BAAAAAAB@@@@@@@@@@@@'
386         db '@@@@@@@@@@@@@AAACAA@@@@@@@@@@@@@'
387         db '@@@@@@@@@@CDDEECDEEDDC@@@@@@@@@@'
388         db '@@@@@@@CDDEEEEEDCEEEEEDDC@@@@@@@'
389         db '@@@@@CDEEEEDCDECDEDCDEEEEDC@@@@@'
390         db '@@@@CDDCDEECACEDCECACEEDCDDC@@@@'
391         db '@@@CDECACEEDCDECDEDCDEECACEDC@@@'
392         db '@@@DEEDCDEEEEEEDCEEEEEEDCDEED@@@'
393         db '@@CEEEEEEEEEEEDCDDEEEEEEEEEEEC@@'
394         db '@@DEDCDEEEDCDECACCEDCDEEEDCDED@@'
395         db '@@EECACEEECACEDCDDECACEEECACEE@@'
396         db '@CEEDCDEEEDCDEEDCEEDCDEEEDCDEEC@'
397         db '@DEEEEEEEEEEEEDCCDEEEEEEEEEEEED@'
398         db 'CEEEEEEDCDEEEDCBACDEEEDCDEEEEEEC'
399         db 'CEDCDEECACEEDCAABACDEECACEEDCDEC'
400         db 'DECACEEDCDEDCAABAAACDEDCDEECACED'
401         db 'DEDCDEEEEEDCAAAABAAACDEEEEEDCDED'
402         db 'CEEEEEEEEECAAAABAAAAACEEEEEEEEEC'
403         db 'CEEEEEEEEDAAAAAABAAAAADEEEEEEEEC'
404         db '@DEDCDEEDCAAAAABAAAAAACDEEDCDED@'
405         db '@DECACEDCAAAAAAABAAAAAACDECACED@'
406         db '@DEDCDDCAAAAAAABAAAAAAAACDDCDED@'
407         db '@CEEEECAAAAAAAAABAAAAAAAACEEEEC@'
408         db '@@EEED@AAAAAAAABAAAAAAAAA@DEEE@@'
409         db '@@EEDC@@AAAAAAAABAAAAAAA@@CDEE@@'
410         db '@@DEC@@@@@AAAAABAAAAAA@@@@@CED@@'
411         db '@@@C@@@@@@@@AAAABAAA@@@@@@@@C@@@'
412
413         align   16      ; if the address is not a multiple of 16 add some 0 to become one (because we'll use backbuffer as a segment)
414 backbuffer: