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