1; Copyright 2005, Ingo Weinhold, bonefish@users.sf.net.
2; Distributed under the terms of the MIT License.
3;
4; Stage 1 boot code for the good (?) old BIOS for use as boot block of HD
5; partitions. The offset of the partition in 512 byte blocks must be written at
6; position PARTITION_OFFSET_OFFSET (32 bit little endian; makebootable does
7; that) or otherwise the code can't find the partition.
8; The partition must be a BFS formatted. The file "system/haiku_loader"
9; (the stage 2 boot loader) loaded into memory at 0x1000:0x0000 (linear address
10; 0x10000) and entered at 0x:1000:0x0200 with parameters eax - partition offset
11; in 512 byte blocks and dl - BIOS ID of the boot drive.
12;
13; Compile via:
14; nasm -f bin -O5 -o stage1.bin stage1.S
15
16; 1 enables more informative error strings, that shouldn't be seen by the
17; normal user, though.
18%assign	DEBUG						0
19
20
21; address/offset definitions
22
23%assign	BOOT_BLOCK_START_ADDRESS	0x7c00
24%assign	STACK_ADDRESS				BOOT_BLOCK_START_ADDRESS
25%assign	READ_BUFFER_STACK			STACK_ADDRESS - 0x2000
26%assign	PARTITION_OFFSET_OFFSET		506
27%assign	BFS_SUPERBLOCK_OFFSET		512
28
29
30; BFS definitions
31
32%define SUPER_BLOCK_MAGIC1			'1SFB'		; nasm reverses '...' consts
33%assign SUPER_BLOCK_MAGIC2			0xdd121031
34%assign SUPER_BLOCK_MAGIC3			0x15b6830e
35
36%assign	INODE_MAGIC1				0x3bbe0ad9
37
38%assign	NUM_DIRECT_BLOCKS			12
39
40%assign	S_IFMT						00000170000o
41%assign	S_IFDIR						00000040000o
42
43
44; BIOS calls
45
46%assign	BIOS_VIDEO_SERVICES			0x10
47%assign	BIOS_DISK_SERVICES			0x13
48%assign	BIOS_KEYBOARD_SERVICES		0X16
49%assign	BIOS_REBOOT					0X19
50
51; video services
52%assign	WRITE_CHAR						0x0e	; al - char
53												; bh - page?
54
55; disk services
56%assign	READ_DISK_SECTORS				0x02	; dl	- drive
57												; es:bx	- buffer
58												; dh	- head (0 - 15)
59												; ch	- track 7:0 (0 - 1023)
60												; cl	- track 9:8,
61												;		  sector (1 - 17)
62												; al	- sector count
63												; -> al - sectors read
64%assign	READ_DRIVE_PARAMETERS			0x08	; dl - drive
65												; -> cl - max cylinder 9:8
66												;		- sectors per track
67												;    ch - max cylinder 7:0
68												;    dh - max head
69												;    dl - number of drives (?)
70%assign	CHECK_DISK_EXTENSIONS_PRESENT	0x41	; bx - 0x55aa
71												; dl - drive
72												; -> success: carry clear
73												;    ah - extension version
74												;    bx - 0xaa55
75												;    cx - support bit mask
76												; -> error: carry set
77%assign	EXTENDED_READ					0x42	; dl - drive
78												; ds:si - address packet
79												; -> success: carry clear
80												; -> error: carry set
81
82%assign FIXED_DISK_SUPPORT				0x1		; flag indicating fixed disk
83												; extension command subset
84
85; keyboard services
86%assign	READ_CHAR						0x00	; -> al - ASCII char
87												;    ah - scan code
88
89
90; nasm (0.98.38) doesn't seem to know pushad. popad works though.
91%define	pushad		db	0x66, 0x60
92
93
94; 16 bit code
95SECTION .text
96BITS 16
97ORG BOOT_BLOCK_START_ADDRESS					; start code at 0x7c00
98
99; nicer way to get the size of a structure
100%define	sizeof(s)	s %+ _size
101
102; using a structure in a another structure definition
103%macro	nstruc	1-2		1
104					resb	sizeof(%1) * %2
105%endmacro
106
107; 64 bit value
108struc	quadword
109	.lower			resd	1
110	.upper			resd	1
111endstruc
112
113; address packet as required by the EXTENDED_READ BIOS call
114struc	AddressPacket
115	.packet_size	resb	1
116	.reserved1		resb	1
117	.block_count	resb	1
118	.reserved2		resb	1
119	.buffer			resd	1
120	.offset			nstruc	quadword
121;	.long_buffer	nstruc	quadword
122	; We don't need the 64 bit buffer pointer. The 32 bit .buffer is more
123	; than sufficient.
124endstruc
125
126; BFS block run
127struc	BlockRun
128	.allocation_group	resd	1
129	.start				resw	1
130	.length				resw	1
131endstruc
132
133; BFS superblock
134struc	SuperBlock
135	.name			resb	32
136	.magic1			resd	1
137	.fs_byte_order	resd	1
138	.block_size		resd	1
139	.block_shift	resd	1
140	.num_blocks		nstruc	quadword
141	.used_blocks	nstruc	quadword
142	.inode_size		resd	1
143	.magic2			resd	1
144	.blocks_per_ag	resd	1
145	.ag_shift		resd	1
146	.num_args		resd	1
147	.flags			resd	1
148	.log_blocks		nstruc	BlockRun
149	.log_start		nstruc	quadword
150	.log_end		nstruc	quadword
151	.magic3			resd	1
152	.root_dir		nstruc	BlockRun
153	.indices		nstruc	BlockRun
154	.pad			resd	8
155endstruc
156
157; BFS inode data stream
158struc	DataStream
159	.direct						nstruc	BlockRun, NUM_DIRECT_BLOCKS
160	.max_direct_range			nstruc	quadword
161	.indirect					nstruc	BlockRun
162	.max_indirect_range			nstruc	quadword
163	.double_indirect			nstruc	BlockRun
164	.max_double_indirect_range	nstruc	quadword
165	.size						nstruc	quadword
166endstruc
167
168; BFS inode (shortened)
169struc	BFSInode
170	.magic1				resd	1
171	.inode_num			nstruc	BlockRun
172	.uid				resd	1
173	.gid				resd	1
174	.mode				resd	1
175	.flags				resd	1
176	.create_time		nstruc	quadword
177	.last_modified_time	nstruc	quadword
178	.parent				nstruc	BlockRun
179	.attributes			nstruc	BlockRun
180	.type				resd	1
181	.inode_size			resd	1
182	.etc				resd	1
183	.data				nstruc	DataStream
184	; ...
185endstruc
186
187; BFS B+ tree node
188struc	BPlusTreeNode
189	.left_link			nstruc	quadword
190	.right_link			nstruc	quadword
191	.overflow_link		nstruc	quadword
192	.all_key_count		resw	1
193	.all_key_length		resw	1
194endstruc
195
196; That's what esp points to after a "pushad".
197struc	PushadStack
198	.edi						resd	1
199	.esi						resd	1
200	.ebp						resd	1
201	.tmp						resd	1	; esp
202	.ebx						resd	1
203	.edx						resd	1
204	.ecx						resd	1
205	.eax						resd	1
206endstruc
207
208; helper macro for defining static variables
209%macro	define_static_var	1
210	%define %1	static_variables + StaticVariables. %+ %1
211%endmacro
212
213; Structure containing the static variables we use (the ones that don't need
214; pre-initialization at least). By using this structure we can easily place
215; them onto our "heap".
216struc	StaticVariables
217	.bios_drive_id				resd	1
218	.address_packet				nstruc	AddressPacket
219	.write_int32_buffer			resb	32
220	.inode						resb	512
221	.indirect_block				resb	512
222	.buffer						resb	1024
223endstruc
224
225; define short names for our static variables
226define_static_var	bios_drive_id
227define_static_var	write_int32_buffer
228define_static_var	address_packet
229define_static_var	inode
230define_static_var	indirect_block
231define_static_var	buffer
232
233; Macro for defining a string prefixed by a byte containing its length. Used
234; for the list of components of the path to the stage 2 boot loader.
235%macro	pathComponent	1
236	%strlen	.componentLen	%1
237	db						.componentLen
238	db						%1
239%endmacro
240
241; macro to be invoked in case of error -- parameter is the error string
242%macro	error	1
243	%if	DEBUG
244		mov			si, %1
245	%else
246		mov			si, kErrorString
247	%endif
248	jmp			_error
249%endmacro
250
251
252start:
253	; set ds, es, ss to the value of cs (which is 0x0000)
254	push		cs
255	pop			ds
256	push		cs
257	pop			es
258
259	push		cs				; setup stack
260	pop			ss
261	mov			sp, STACK_ADDRESS
262
263	cli							; disable interrupts
264	cld							; clear direction flag (for string ops)
265
266	; save the BIOS drive ID
267	mov			[bios_drive_id], dl
268
269	; check for BIOS int 0x13 (disk services) extensions
270	mov			ah, CHECK_DISK_EXTENSIONS_PRESENT
271	mov			bx, 0x55aa
272	; dl has not changed yet, still contains the drive ID
273	int			BIOS_DISK_SERVICES
274
275	jc			.no_disk_extensions	; error
276
277	cmp			bx, 0xaa55
278	jne			.no_disk_extensions	; call not supported?
279
280	test		cl, FIXED_DISK_SUPPORT
281	jz			.no_disk_extensions
282
283	; we have disk extensions
284	mov	byte	[sHasDiskExtensions], 1
285
286.no_disk_extensions:
287
288	; read in our second half
289	xor			eax, eax					; block offset (1) to eax
290	inc			ax
291	lea			ebp, [second_boot_block]	; buffer to ebp
292
293	call		readOneBlock
294
295	; check superblock magic
296	cmp	dword	[superblock + SuperBlock.magic1], SUPER_BLOCK_MAGIC1
297	je			.valid_superblock_magic
298
299	error		kBadSuperBlockMagicString
300
301.valid_superblock_magic:
302	jmp			continueMain
303
304
305; Jumped to in case of error. si must contain the pointer to the error string.
306_error:
307	call		_writeString
308
309	; wait for a key and reboot
310	mov			ah, READ_CHAR
311	int			BIOS_KEYBOARD_SERVICES
312	int			BIOS_REBOOT
313
314
315; _writeString
316; Prints a string to the screen.
317; [entry]
318; si:		pointer to null terminated string
319; [exit]
320; trashes:	si, ax
321_writeString:
322.loop:
323	lodsb		; al <- [si++]
324	or			al, al
325	jz			.loopend
326
327	mov			ah, WRITE_CHAR
328	int			BIOS_VIDEO_SERVICES
329
330	jmp			.loop
331.loopend:
332
333	ret
334
335
336; readOneBlock
337; Reads one disk block from the given offset into the specified buffer.
338; [entry]
339; eax:		block offset
340; ebp:		buffer address
341; [exit]
342; trashes:	di
343readOneBlock:
344	mov			di, 1
345	; fall through ...
346
347
348; readBlocks
349; Reads one or more disk blocks from the given offset into the specified buffer.
350; [entry]
351; eax:	block offset
352; di:	block count
353; ebp:	buffer address
354readBlocks:
355	pushad
356
357	; add the partition offset
358	add	dword	eax, [kPartitionOffset]
359
360	; drive ID to dl
361	mov			dl, [bios_drive_id]
362
363	cmp	byte	[sHasDiskExtensions], 0
364	jz			.no_extension_support
365
366	; set packet size, block count, and buffer in the address packet
367	mov	word	[address_packet + AddressPacket.packet_size], \
368				sizeof(AddressPacket)
369	mov			[address_packet + AddressPacket.block_count], di
370	mov			[address_packet + AddressPacket.buffer], ebp
371
372	; write the block offset to the address packet
373	mov	dword	[address_packet + AddressPacket.offset + quadword.lower], eax
374	xor			eax, eax
375	mov	dword	[address_packet + AddressPacket.offset + quadword.upper], eax
376
377	; do the "extended read" call
378	; address packet address in si
379	mov			si, address_packet
380	mov			ah, EXTENDED_READ
381	int			BIOS_DISK_SERVICES
382
383	jnc			.no_error	; error?
384
385.read_error:
386	error		kReadErrorString
387
388.no_extension_support:
389	; no fixed disk extension support
390
391	; save parameters
392	push		eax
393
394	; read drive parameters
395	mov			ah, READ_DRIVE_PARAMETERS
396	int			BIOS_DISK_SERVICES
397	jc			.read_error
398
399	; -> cl - max cylinder 9:8
400	;		- sectors per track
401	;    ch - max cylinder 7:0
402	;    dh - max head
403
404	; compute sectors
405	pop			eax			; LBA
406	xchg		dl, dh		; max head to dx
407	xor			dh, dh		;
408	push		dx			; save max head
409	xor			edx, edx
410	and			ecx, 0x3f	; filter sectors per track
411	div			ecx			; divide by sectors per track
412
413	inc			dl			; sector numbering starts with 1
414	pop			cx			; restore max head
415	push		dx			; save sector
416
417	; compute heads and cylinders
418	xor			dx, dx
419	xor			ch, ch		; cl only
420	inc			cx			; max head -> head count
421	div			cx			; divide by head count
422	; result: ax: cylinder, dx: head
423
424	; we need to shuffle things a bit
425	or			dh, dl		; head
426
427	mov			cx, ax
428	xchg		cl, ch		; ch: 7:0 cylinder
429	ror			cl, 2		; cl: 9:8 cylinder in bits 7:6
430	pop			dx			; restore sector
431	or			cl, dl		; cl: 9:8 cylinder, 5:0 sector
432
433	; buffer address must be in es:bx
434	mov			eax, ebp	; count
435	shr			eax, 16
436	push		es			; save es
437	push		ax
438	pop			es
439	mov			bx, bp
440
441	; block count to ax
442	mov			ax, di		; count
443
444	mov			dl, [bios_drive_id]
445	mov			ah, READ_DISK_SECTORS
446	int			BIOS_DISK_SERVICES
447
448	pop			es			; restore es
449
450	cmp			ax, di
451	jne			.read_error
452
453.no_error:
454	popad
455
456	ret
457
458
459; readBuffer
460; Reads the next 1024 bytes from the data of the current inode (the one read
461; with the last call to readInode) into a buffer. The function uses an own stack
462; which it switches to at the beginning (switching back at the end). This
463; custom stack is initially in an "after pushad" state. The functions does a
464; popad at the beginning and pushad at the end, thus keeping its register
465; configuration between calls (see some lines below for the meaning of the
466; registers). readBufferInit must be called before the first call to readBuffer
467; for a node. After that manipulating the parameters (registers) of the
468; function can be done by accessing the respective values on the custom stack.
469; [exit]
470; ax:	0x0000 - nothing read (end of file/directory)
471;		0x0001 - read one buffer
472readBuffer:
473	xor			ax, ax				; the default result (end)
474	pushad
475
476	; set our custom stack and get our registers
477	xchg		sp, [sReadBufferStack]
478	popad
479
480	; registers:
481	; eax		- read offset
482	; ecx		- blocks left of the current block run
483	; edx		- max remaining block runs
484	; ebp		- pointer to the read buffer
485	; si		- pointer to the current block run
486	; edi		- index of the current indirect block
487	; bx		- remaining indirect blocks
488
489	and			ecx, ecx
490	jg			.blocks_left_valid
491
492	; blocks_left <= 0: decrement remaining block run index
493	dec			dl
494	jge			.next_block_run
495
496.next_indirect_block:
497	; no more block runs: decrement remaining indirect block count
498	dec			bx
499	jl			.nothing_read
500
501	; there are more indirect blocks: read the next one
502	; get the buffer address to esi first
503	xor			esi, esi
504	lea			si, [indirect_block]
505
506	; read the block
507	pushad
508	xchg		eax, edi		; block index to eax
509	mov			ebp, esi		; buffer pointer to ebp
510
511	call		readOneBlock
512
513	popad
514
515	; increment the indirect block index
516	inc			edi
517
518	; maximal number of block runs in this block to edx
519	xor			edx, edx
520	mov			dl, 512 / sizeof(BlockRun)
521
522.next_block_run:
523	; convert block run to disk block offset
524	call		blockRunToDiskBlock
525
526	and			eax, eax
527	jz			.next_indirect_block
528
529.more_blocks:
530	; compute blocks_left
531	xchg		eax, ecx							; save eax
532	movzx		eax, word [si + BlockRun.length]	; length to eax
533	call		bfsBlockToDiskBlock					; convert
534	xchg		eax, ecx							; blocks_left now in ecx
535
536	; move to the next block run
537	add			si, sizeof(BlockRun)
538
539.blocks_left_valid:
540	; we'll read 2 disk blocks: so subtract 2 from blocks_left
541	sub			ecx, 2
542
543	push		edi			; save edi -- we use it for other stuff for the
544							; moment
545
546	mov			di, 2
547
548	call		readBlocks
549
550	; adjust read_offset
551	add			eax, 2
552
553	; success
554	mov			di, [sReadBufferStack]
555	mov	byte	[di + PushadStack.eax], 1
556
557	pop			edi			; restore edi
558
559.nothing_read:
560	pushad
561	xchg		sp, [sReadBufferStack]
562	popad
563	ret
564
565
566; readBufferInit
567; Initializes readBuffer's context for the current inode (the one read with
568; the last call to readInode). Must be called before the first call to
569; readBuffer for an inode.
570readBufferInit:
571	; switch to readBuffer context
572	pushad
573	xchg		sp, [sReadBufferStack]
574	popad
575
576	; clear the number of indirect blocks, for the case there aren't any
577	xor			bx, bx
578
579	; check whether there are indirect blocks (max_indirect_range != 0)
580	lea			si, [inode + BFSInode.data + DataStream.max_indirect_range]
581	cmp	dword	[si], 0
582	jnz			.has_indirect_blocks
583	cmp	dword	[si + 4], 0
584	jz			.no_indirect_blocks
585
586.has_indirect_blocks:
587	; get the first indirect block index
588	lea			si, [inode + BFSInode.data + DataStream.indirect]
589	call		blockRunToDiskBlock
590
591	and			eax, eax
592	jz			.no_indirect_blocks
593
594	; indirect block index to edi
595	xchg		edi, eax
596
597	; get number of indirect blocks
598	movzx		eax, word [si + BlockRun.length]
599	call		bfsBlockToDiskBlock
600	xchg		bx, ax							; number to bx
601
602.no_indirect_blocks:
603
604	; blocks_left = 0, max_remaining_direct_block_runs = NUM_DIRECT_BLOCKS
605	xor			ecx, ecx
606	mov			dl, NUM_DIRECT_BLOCKS
607
608	; position si at the 1st block run
609	lea			si, [inode + BFSInode.data + DataStream.direct]
610
611	; buffer address
612	xor			ebp, ebp
613	mov			bp, buffer
614
615	; switch context back (use readBuffer's code)
616	jmp			readBuffer.nothing_read
617
618
619; data
620
621; the custom stack for readBuffer
622sReadBufferStack			dw	READ_BUFFER_STACK - sizeof(PushadStack)
623								; already start in "after pushad" state
624sHasDiskExtensions			db	0	; 1 if the drive supports the extended read
625									; BIOS call.
626
627; error strings
628; If DEBUG is enabled, we use more descriptive ones.
629%if DEBUG
630kReadErrorString			db	"read error", 0
631kBadSuperBlockMagicString	db	"bad superblock", 0
632kNotADirectoryString		db	"not a directory", 0
633kBadInodeMagicString		db	"bad inode", 0
634kNoZbeosString				db	"haiku_loader not found", 0
635%else
636kErrorString				db	"Failed to load OS. Press any key to reboot..."
637							db	0
638%endif
639
640; the path to the boot loader
641kPathComponents:
642pathComponent				"system"
643pathComponent				"haiku_loader"
644							db	0
645
646
647
648first_code_part_end:
649
650; The first (max) 512 - 4 -2 bytes of the boot code end here
651; ---------------------------------------------------------------------------
652
653				%if first_code_part_end - start > PARTITION_OFFSET_OFFSET
654					%error "Code exceeds first boot code block!"
655				%endif
656
657				; pad to the partition offset
658				%rep start + PARTITION_OFFSET_OFFSET - first_code_part_end
659					db	0
660				%endrep
661
662kPartitionOffset			dd	0
663kBootBlockSignature			dw	0xaa55
664
665
666second_boot_block:
667
668; first comes the BFS superblock
669superblock:
670				%rep sizeof(SuperBlock)
671					db	0
672				%endrep
673
674
675; the second part of the boot block code
676
677; readBootLoader
678; Jumped to when all path components to the stage 2 boot loader have been
679; resolved and the current inode is the one of the boot loader. The boot
680; loader will be read into memory and jumped into.
681readBootLoader:
682	; prepare for the first call to readBuffer
683	call		readBufferInit
684
685	; the destination address: start at the beginning of segment 0x1000
686	mov			ecx, 0x10000000
687	mov			edi, ecx			; 0x1000:0000
688
689	xor			ebx, ebx
690	mov			bx, [sReadBufferStack]
691
692.read_loop:
693	; write destination address
694	mov			[bx + PushadStack.ebp], edi
695
696	; compute next destination address
697	add			di, 1024
698	jnc			.no_carry
699	add			edi, ecx		; the lower 16 bit wrapped around: add 0x1000
700								; (64 KB) to the segment selector
701.no_carry:
702
703	call		readBuffer
704
705	; loop as long as reading succeeds
706	and			ax, ax
707	jnz			.read_loop
708
709	; We have successfully read the complete boot loader. Set up the
710	; environment for it.
711	; eax - partition offset in sectors
712	mov dword	eax, [kPartitionOffset]
713
714	; dl - BIOS drive ID
715	xor			edx, edx
716	mov			dl, [bios_drive_id]
717
718	; ds, es
719	push 		0x07c0
720	pop			ds
721	push 		0x1000
722	pop			es
723
724	; enter the boot loader
725	jmp			0x1000:0x200
726
727
728; continueMain
729; Continues the "main" function of the boot code. Mainly contains the loop that
730; resolves the path to the stage 2 boot loader, jumping to readBootLoader when
731; it was found.
732continueMain:
733
734	; load root node
735	; convert root node block run to block
736	lea			si, [superblock + SuperBlock.root_dir]
737	call		blockRunToDiskBlock
738
739	call		readInode
740
741	; stack:
742	; word		number of keys					(in .key_loop)
743	; word		previous key length				(in .key_loop)
744
745	; registers:
746	; di	- path component					(in .search_loop)
747	; cx	- path component length				(in .search_loop)
748	; ax	- remaining key count (-1)			(in .key_loop)
749	; bx	- key lengths array (current pos)	(in .key_loop)
750	; dx	- previous absolute key length		(in .key_loop)
751	; si	- current key						(in .key_loop)
752	; bp	- current key length				(in .key_loop)
753
754	lea			di, [kPathComponents]
755
756.search_loop:
757	; the path component we're looking for
758	xor			cx, cx
759	mov			cl, [di]	; the path component length
760	inc			di			; the path component itself
761	and			cl, cl
762	jz			readBootLoader ; no more path components: We found the boot
763								 ; loader! Now read it in.
764
765.continue_search:
766	; is a directory?
767	mov			eax, [inode + BFSInode.mode]
768	and			eax, S_IFMT
769	cmp			eax, S_IFDIR
770	je			.is_directory
771
772	error		kNotADirectoryString
773
774.is_directory:
775	; prepare for the first call to readBuffer
776	call		readBufferInit
777
778	; we skip the first 1024 bytes (that's the b+tree header)
779	call		readBuffer
780	and			ax, ax
781	jnz			.read_loop
782
783.not_found:
784	error		kNoZbeosString
785
786.read_loop:
787
788	; read the next B+ tree node
789	call		readBuffer
790	and			ax, ax
791	jz			.not_found
792
793	; we're only interested in leaf nodes (overflow_link == -1)
794	xor			eax, eax
795	dec			eax
796	cmp			[buffer + BPlusTreeNode.overflow_link + quadword.lower], eax
797	jne			.read_loop
798	cmp			[buffer + BPlusTreeNode.overflow_link + quadword.upper], eax
799	jne			.read_loop
800
801	; get the keylengths and keys
802
803	; the keys
804	lea			si, [buffer + sizeof(BPlusTreeNode)]
805
806	; the keylengths array
807	mov			bx, [buffer + BPlusTreeNode.all_key_length]
808	add			bx, sizeof(BPlusTreeNode) + 7
809	and			bl, 0xf8
810	add			bx, buffer
811
812	; number of keys
813	mov			ax, [buffer + BPlusTreeNode.all_key_count]
814	push		ax
815
816	; the "previous" key length
817	push word	0
818
819.key_loop:
820	; while there are more keys
821	dec			ax
822	jl			.key_loop_end
823
824	; get current key length
825	mov			bp, [bx]
826
827	; exchange previous key length on the stack and compute the actual
828	; length (the key lengths array contains summed-up lengths)
829	pop			dx
830	push		bp
831	sub			bp, dx
832
833	cmp			cx, bp
834	jne			.skip_key
835
836	; compare path component (di) with key (si), length cx (== bp)
837	pusha
838	repe cmpsb
839	popa
840
841	jne			.skip_key
842
843	; keys are equal
844
845	; get the current index
846	pop			dx			; pop previous key length
847	pop			dx			; key count
848	inc			ax			; ax is decremented already at the loop top
849	sub			dx, ax		; the current index
850
851	; get to the end of the key lengths array
852	shl			ax, 1		; number of bytes remaining in the array
853	add			bx, ax
854	shl			dx, 3		; offset in the value (block number) array
855	add			bx, dx		; bx now points to the block number of the inode
856
857	; read the block offset and load the Inode
858	mov			eax, [bx]
859	call		bfsBlockToDiskBlock
860
861	call		readInode
862
863	; next path component
864	add			di, cx
865	jmp			.search_loop
866
867.skip_key:
868	inc			bx			; next key length
869	inc			bx
870	add			si, bp		; next key
871	jmp			.key_loop
872
873.key_loop_end:
874	; all keys check, but nothing found: need to read in the next tree node
875	pop			dx			; pop previous key length
876	pop			dx			; pop key count
877	jmp			.read_loop
878
879
880; readInode
881; Reads the inode at the specified disk block offset into the buffer "inode".
882; [entry]
883; eax:	disk block offset
884readInode:
885	pushad
886
887	; buffer address to ebp
888	xor			ebp, ebp
889	mov			bp, inode
890
891	; An inode is actually one BFS block big, but we're interested only in the
892	; administrative part (not the small data section), which easily fits into
893	; one disk block.
894	call		readOneBlock
895
896	cmp	dword	[inode + BFSInode.magic1], INODE_MAGIC1
897	je			.no_error
898
899	error		kBadInodeMagicString
900
901.no_error:
902	popad
903
904	ret
905
906
907; blockRunToDiskBlock
908; Computes the start address (in disk blocks) of a given BFS block run.
909; [entry]
910; si:	pointer to the BlockRun
911; [exit]
912; eax:	disk block number, where the block run begins
913blockRunToDiskBlock:
914	push		ecx
915
916	; run.allocation_group << superblock.ag_shift
917	mov			cl, [superblock + SuperBlock.ag_shift]
918	mov 		eax, [si + BlockRun.allocation_group]
919	shl			eax, cl
920
921	; add run.start
922	xor			ecx, ecx
923	mov			cx, [si + BlockRun.start]
924
925	add			eax, ecx
926
927	pop			ecx
928
929	; Fall through to bfsBlockToDiskBlock, which will convert the BFS block
930	; number to a disk block number and return to our caller.
931
932
933; bfsBlockToDiskBlock
934; Converts a BFS block number to a disk block number.
935; [entry]
936; eax:	BFS block number
937; [exit]
938; eax:	disk block number
939bfsBlockToDiskBlock:
940	push		cx
941
942	;   1 BFS block == superblock_block_size / 512 disk blocks
943	mov byte	cl, [superblock + SuperBlock.block_shift]
944	sub			cl, 9
945
946	shl			eax, cl
947
948	pop			cx
949	ret
950
951
952; _writeInt32
953; Writes the given number in 8 digit hexadecimal representation to screen.
954; Used for debugging only.
955; [entry]
956; eax:	The number to print.
957_writeInt32:
958	pushad
959
960	mov			bx, write_int32_buffer
961	mov byte	[bx + 8], 0	; terminating null
962	mov			di, 7
963
964.loop:
965	; get the lowest hex digit
966	mov			dx, ax
967	and			dl, 0xf
968
969	; convert hex digit to character
970	cmp			dl, 10
971	jl			.digit
972	add			dl, 'a' - '0' - 10
973
974.digit:
975	add			dl, '0'
976
977	; prepend the digit to the string
978	mov			[bx + di], dl
979
980	; shift out lowest digit and loop, if there are more digits
981	shr			eax, 4
982	dec			di
983	jge			.loop
984
985	; write the composed string
986	xchg		bx, si
987	call		_writeString
988
989	popad
990	ret
991
992
993; check whether we are small enough
994end:
995				%if end - start > 1024
996					%error "Code exceeds second boot code block!"
997				%endif
998
999; pad to 1024 bytes size
1000				%rep start + 1024 - end
1001					db	0
1002				%endrep
1003
1004; Base offset for static variables.
1005static_variables:
1006