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