Add missing files to menu subdirectory
[syslinux.git] / extlinux.asm
blob9bca724b259639cf76937b54fc6e884c9027d9bc
1 ; -*- fundamental -*- (asm-mode sucks)
2 ; $Id$
3 ; ****************************************************************************
5 ; extlinux.asm
7 ; A program to boot Linux kernels off an ext2/ext3 filesystem.
9 ; Copyright (C) 1994-2005 H. Peter Anvin
11 ; This program is free software; you can redistribute it and/or modify
12 ; it under the terms of the GNU General Public License as published by
13 ; the Free Software Foundation, Inc., 53 Temple Place Ste 330,
14 ; Boston MA 02111-1307, USA; either version 2 of the License, or
15 ; (at your option) any later version; incorporated herein by reference.
17 ; ****************************************************************************
19 %define IS_EXTLINUX 1
20 %include "macros.inc"
21 %include "config.inc"
22 %include "kernel.inc"
23 %include "bios.inc"
24 %include "tracers.inc"
25 %include "layout.inc"
27 %include "ext2_fs.inc"
30 ; Some semi-configurable constants... change on your own risk.
32 my_id equ extlinux_id
33 ; NASM 0.98.38 croaks if these are equ's rather than macros...
34 FILENAME_MAX_LG2 equ 8 ; log2(Max filename size Including final null)
35 FILENAME_MAX equ (1 << FILENAME_MAX_LG2) ; Max mangled filename size
36 NULLFILE equ 0 ; Null character == empty filename
37 NULLOFFSET equ 0 ; Position in which to look
38 retry_count equ 16 ; How patient are we with the disk?
39 %assign HIGHMEM_SLOP 0 ; Avoid this much memory near the top
40 LDLINUX_MAGIC equ 0x3eb202fe ; A random number to identify ourselves with
42 MAX_OPEN_LG2 equ 6 ; log2(Max number of open files)
43 MAX_OPEN equ (1 << MAX_OPEN_LG2)
45 SECTOR_SHIFT equ 9
46 SECTOR_SIZE equ (1 << SECTOR_SHIFT)
48 MAX_SYMLINKS equ 64 ; Maximum number of symlinks per lookup
49 SYMLINK_SECTORS equ 2 ; Max number of sectors in a symlink
50 ; (should be >= FILENAME_MAX)
53 ; This is what we need to do when idle
55 %macro RESET_IDLE 0
56 ; Nothing
57 %endmacro
58 %macro DO_IDLE 0
59 ; Nothing
60 %endmacro
63 ; The following structure is used for "virtual kernels"; i.e. LILO-style
64 ; option labels. The options we permit here are `kernel' and `append
65 ; Since there is no room in the bottom 64K for all of these, we
66 ; stick them at vk_seg:0000 and copy them down before we need them.
68 struc vkernel
69 vk_vname: resb FILENAME_MAX ; Virtual name **MUST BE FIRST!**
70 vk_rname: resb FILENAME_MAX ; Real name
71 vk_appendlen: resw 1
72 alignb 4
73 vk_append: resb max_cmd_len+1 ; Command line
74 alignb 4
75 vk_end: equ $ ; Should be <= vk_size
76 endstruc
79 ; Segment assignments in the bottom 640K
80 ; Stick to the low 512K in case we're using something like M-systems flash
81 ; which load a driver into low RAM (evil!!)
83 ; 0000h - main code/data segment (and BIOS segment)
85 real_mode_seg equ 4000h
86 cache_seg equ 3000h ; 64K area for metadata cache
87 vk_seg equ 2000h ; Virtual kernels
88 xfer_buf_seg equ 1000h ; Bounce buffer for I/O to high mem
89 comboot_seg equ real_mode_seg ; COMBOOT image loading zone
92 ; File structure. This holds the information for each currently open file.
94 struc open_file_t
95 file_left resd 1 ; Number of sectors left (0 = free)
96 file_sector resd 1 ; Next linear sector to read
97 file_in_sec resd 1 ; Sector where inode lives
98 file_in_off resw 1
99 file_mode resw 1
100 endstruc
102 %ifndef DEPEND
103 %if (open_file_t_size & (open_file_t_size-1))
104 %error "open_file_t is not a power of 2"
105 %endif
106 %endif
108 ; ---------------------------------------------------------------------------
109 ; BEGIN CODE
110 ; ---------------------------------------------------------------------------
113 ; Memory below this point is reserved for the BIOS and the MBR
115 section .earlybss
116 trackbufsize equ 8192
117 trackbuf resb trackbufsize ; Track buffer goes here
118 getcbuf resb trackbufsize
119 ; ends at 4800h
121 section .latebss
122 SuperBlock resb 1024 ; ext2 superblock
123 SuperInfo resq 16 ; DOS superblock expanded
124 ClustSize resd 1 ; Bytes/cluster ("block")
125 SecPerClust resd 1 ; Sectors/cluster
126 ClustMask resd 1 ; Sectors/cluster - 1
127 PtrsPerBlock1 resd 1 ; Pointers/cluster
128 PtrsPerBlock2 resd 1 ; (Pointers/cluster)^2
129 DriveNumber resb 1 ; BIOS drive number
130 ClustShift resb 1 ; Shift count for sectors/cluster
131 ClustByteShift resb 1 ; Shift count for bytes/cluster
133 alignb open_file_t_size
134 Files resb MAX_OPEN*open_file_t_size
137 ; Constants for the xfer_buf_seg
139 ; The xfer_buf_seg is also used to store message file buffers. We
140 ; need two trackbuffers (text and graphics), plus a work buffer
141 ; for the graphics decompressor.
143 xbs_textbuf equ 0 ; Also hard-coded, do not change
144 xbs_vgabuf equ trackbufsize
145 xbs_vgatmpbuf equ 2*trackbufsize
148 section .text
150 ; Some of the things that have to be saved very early are saved
151 ; "close" to the initial stack pointer offset, in order to
152 ; reduce the code size...
154 StackBuf equ $-44-32 ; Start the stack here (grow down - 4K)
155 PartInfo equ StackBuf ; Saved partition table entry
156 FloppyTable equ PartInfo+16 ; Floppy info table (must follow PartInfo)
157 OrigFDCTabPtr equ StackBuf-4 ; The high dword on the stack
160 ; Primary entry point. Tempting as though it may be, we can't put the
161 ; initial "cli" here; the jmp opcode in the first byte is part of the
162 ; "magic number" (using the term very loosely) for the DOS superblock.
164 bootsec equ $
165 jmp short start ; 2 bytes
166 nop ; 1 byte
168 ; "Superblock" follows -- it's in the boot sector, so it's already
169 ; loaded and ready for us
171 bsOemName db 'EXTLINUX' ; The SYS command sets this, so...
173 ; These are the fields we actually care about. We end up expanding them
174 ; all to dword size early in the code, so generate labels for both
175 ; the expanded and unexpanded versions.
177 %macro superb 1
178 bx %+ %1 equ SuperInfo+($-superblock)*8+4
179 bs %+ %1 equ $
180 zb 1
181 %endmacro
182 %macro superw 1
183 bx %+ %1 equ SuperInfo+($-superblock)*8
184 bs %+ %1 equ $
185 zw 1
186 %endmacro
187 %macro superd 1
188 bx %+ %1 equ $ ; no expansion for dwords
189 bs %+ %1 equ $
190 zd 1
191 %endmacro
192 superblock equ $
193 superw BytesPerSec
194 superb SecPerClust
195 superw ResSectors
196 superb FATs
197 superw RootDirEnts
198 superw Sectors
199 superb Media
200 superw FATsecs
201 superw SecPerTrack
202 superw Heads
203 superinfo_size equ ($-superblock)-1 ; How much to expand
204 superd Hidden
205 superd HugeSectors
207 ; This is as far as FAT12/16 and FAT32 are consistent
209 zb 54 ; FAT12/16 need 26 more bytes,
210 ; FAT32 need 54 more bytes
211 superblock_len equ $-superblock
214 ; Note we don't check the constraints above now; we did that at install
215 ; time (we hope!)
217 start:
218 cli ; No interrupts yet, please
219 cld ; Copy upwards
221 ; Set up the stack
223 xor ax,ax
224 mov ss,ax
225 mov sp,StackBuf ; Just below BSS
226 mov es,ax
228 ; DS:SI may contain a partition table entry. Preserve it for us.
230 mov cx,8 ; Save partition info
231 mov di,sp
232 rep movsw
234 mov ds,ax ; Now we can initialize DS...
237 ; Now sautee the BIOS floppy info block to that it will support decent-
238 ; size transfers; the floppy block is 11 bytes and is stored in the
239 ; INT 1Eh vector (brilliant waste of resources, eh?)
241 ; Of course, if BIOSes had been properly programmed, we wouldn't have
242 ; had to waste precious space with this code.
244 mov bx,fdctab
245 lfs si,[bx] ; FS:SI -> original fdctab
246 push fs ; Save on stack in case we need to bail
247 push si
249 ; Save the old fdctab even if hard disk so the stack layout
250 ; is the same. The instructions above do not change the flags
251 mov [DriveNumber],dl ; Save drive number in DL
252 and dl,dl ; If floppy disk (00-7F), assume no
253 ; partition table
254 js harddisk
256 floppy:
257 mov cl,6 ; 12 bytes (CX == 0)
258 ; es:di -> FloppyTable already
259 ; This should be safe to do now, interrupts are off...
260 mov [bx],di ; FloppyTable
261 mov [bx+2],ax ; Segment 0
262 fs rep movsw ; Faster to move words
263 mov cl,[bsSecPerTrack] ; Patch the sector count
264 mov [di-8],cl
265 ; AX == 0 here
266 int 13h ; Some BIOSes need this
268 jmp short not_harddisk
270 ; The drive number and possibly partition information was passed to us
271 ; by the BIOS or previous boot loader (MBR). Current "best practice" is to
272 ; trust that rather than what the superblock contains.
274 ; Would it be better to zero out bsHidden if we don't have a partition table?
276 ; Note: di points to beyond the end of PartInfo
278 harddisk:
279 test byte [di-16],7Fh ; Sanity check: "active flag" should
280 jnz no_partition ; be 00 or 80
281 mov eax,[di-8] ; Partition offset (dword)
282 mov [bsHidden],eax
283 no_partition:
285 ; Get disk drive parameters (don't trust the superblock.) Don't do this for
286 ; floppy drives -- INT 13:08 on floppy drives will (may?) return info about
287 ; what the *drive* supports, not about the *media*. Fortunately floppy disks
288 ; tend to have a fixed, well-defined geometry which is stored in the superblock.
290 ; DL == drive # still
291 mov ah,08h
292 int 13h
293 jc no_driveparm
294 and ah,ah
295 jnz no_driveparm
296 shr dx,8
297 inc dx ; Contains # of heads - 1
298 mov [bsHeads],dx
299 and cx,3fh
300 mov [bsSecPerTrack],cx
301 no_driveparm:
302 not_harddisk:
304 ; Ready to enable interrupts, captain
309 ; Do we have EBIOS (EDD)?
311 eddcheck:
312 mov bx,55AAh
313 mov ah,41h ; EDD existence query
314 mov dl,[DriveNumber]
315 int 13h
316 jc .noedd
317 cmp bx,0AA55h
318 jne .noedd
319 test cl,1 ; Extended disk access functionality set
320 jz .noedd
322 ; We have EDD support...
324 mov byte [getlinsec.jmp+1],(getlinsec_ebios-(getlinsec.jmp+2))
325 .noedd:
328 ; Load the first sector of LDLINUX.SYS; this used to be all proper
329 ; with parsing the superblock and root directory; it doesn't fit
330 ; together with EBIOS support, unfortunately.
332 mov eax,[FirstSector] ; Sector start
333 mov bx,ldlinux_sys ; Where to load it
334 call getonesec
336 ; Some modicum of integrity checking
337 cmp dword [ldlinux_magic+4],LDLINUX_MAGIC^HEXDATE
338 jne kaboom
340 ; Go for it...
341 jmp ldlinux_ent
344 ; getonesec: get one disk sector
346 getonesec:
347 mov bp,1 ; One sector
348 ; Fall through
351 ; getlinsec: load a sequence of BP floppy sector given by the linear sector
352 ; number in EAX into the buffer at ES:BX. We try to optimize
353 ; by loading up to a whole track at a time, but the user
354 ; is responsible for not crossing a 64K boundary.
355 ; (Yes, BP is weird for a count, but it was available...)
357 ; On return, BX points to the first byte after the transferred
358 ; block.
360 ; This routine assumes CS == DS, and trashes most registers.
362 ; Stylistic note: use "xchg" instead of "mov" when the source is a register
363 ; that is dead from that point; this saves space. However, please keep
364 ; the order to dst,src to keep things sane.
366 getlinsec:
367 add eax,[bsHidden] ; Add partition offset
368 xor edx,edx ; Zero-extend LBA (eventually allow 64 bits)
370 .jmp: jmp strict short getlinsec_cbios
373 ; getlinsec_ebios:
375 ; getlinsec implementation for EBIOS (EDD)
377 getlinsec_ebios:
378 .loop:
379 push bp ; Sectors left
380 .retry2:
381 call maxtrans ; Enforce maximum transfer size
382 movzx edi,bp ; Sectors we are about to read
383 mov cx,retry_count
384 .retry:
386 ; Form DAPA on stack
387 push edx
388 push eax
389 push es
390 push bx
391 push di
392 push word 16
393 mov si,sp
394 pushad
395 mov dl,[DriveNumber]
396 push ds
397 push ss
398 pop ds ; DS <- SS
399 mov ah,42h ; Extended Read
400 int 13h
401 pop ds
402 popad
403 lea sp,[si+16] ; Remove DAPA
404 jc .error
405 pop bp
406 add eax,edi ; Advance sector pointer
407 sub bp,di ; Sectors left
408 shl di,SECTOR_SHIFT ; 512-byte sectors
409 add bx,di ; Advance buffer pointer
410 and bp,bp
411 jnz .loop
415 .error:
416 ; Some systems seem to get "stuck" in an error state when
417 ; using EBIOS. Doesn't happen when using CBIOS, which is
418 ; good, since some other systems get timeout failures
419 ; waiting for the floppy disk to spin up.
421 pushad ; Try resetting the device
422 xor ax,ax
423 mov dl,[DriveNumber]
424 int 13h
425 popad
426 loop .retry ; CX-- and jump if not zero
428 ;shr word [MaxTransfer],1 ; Reduce the transfer size
429 ;jnz .retry2
431 ; Total failure. Try falling back to CBIOS.
432 mov byte [getlinsec.jmp+1],(getlinsec_cbios-(getlinsec.jmp+2))
433 ;mov byte [MaxTransfer],63 ; Max possibe CBIOS transfer
435 pop bp
436 ; ... fall through ...
439 ; getlinsec_cbios:
441 ; getlinsec implementation for legacy CBIOS
443 getlinsec_cbios:
444 .loop:
445 push edx
446 push eax
447 push bp
448 push bx
450 movzx esi,word [bsSecPerTrack]
451 movzx edi,word [bsHeads]
453 ; Dividing by sectors to get (track,sector): we may have
454 ; up to 2^18 tracks, so we need to use 32-bit arithmetric.
456 div esi
457 xor cx,cx
458 xchg cx,dx ; CX <- sector index (0-based)
459 ; EDX <- 0
460 ; eax = track #
461 div edi ; Convert track to head/cyl
463 ; We should test this, but it doesn't fit...
464 ; cmp eax,1023
465 ; ja .error
468 ; Now we have AX = cyl, DX = head, CX = sector (0-based),
469 ; BP = sectors to transfer, SI = bsSecPerTrack,
470 ; ES:BX = data target
473 call maxtrans ; Enforce maximum transfer size
475 ; Must not cross track boundaries, so BP <= SI-CX
476 sub si,cx
477 cmp bp,si
478 jna .bp_ok
479 mov bp,si
480 .bp_ok:
482 shl ah,6 ; Because IBM was STOOPID
483 ; and thought 8 bits were enough
484 ; then thought 10 bits were enough...
485 inc cx ; Sector numbers are 1-based, sigh
486 or cl,ah
487 mov ch,al
488 mov dh,dl
489 mov dl,[DriveNumber]
490 xchg ax,bp ; Sector to transfer count
491 mov ah,02h ; Read sectors
492 mov bp,retry_count
493 .retry:
494 pushad
495 int 13h
496 popad
497 jc .error
498 .resume:
499 movzx ecx,al ; ECX <- sectors transferred
500 shl ax,SECTOR_SHIFT ; Convert sectors in AL to bytes in AX
501 pop bx
502 add bx,ax
503 pop bp
504 pop eax
505 pop edx
506 add eax,ecx
507 sub bp,cx
508 jnz .loop
511 .error:
512 dec bp
513 jnz .retry
515 xchg ax,bp ; Sectors transferred <- 0
516 shr word [MaxTransfer],1
517 jnz .resume
518 ; Fall through to disk_error
521 ; kaboom: write a message and bail out.
523 disk_error:
524 kaboom:
525 xor si,si
526 mov ss,si
527 mov sp,StackBuf-4 ; Reset stack
528 mov ds,si ; Reset data segment
529 pop dword [fdctab] ; Restore FDC table
530 .patch: ; When we have full code, intercept here
531 mov si,bailmsg
533 ; Write error message, this assumes screen page 0
534 .loop: lodsb
535 and al,al
536 jz .done
537 mov ah,0Eh ; Write to screen as TTY
538 mov bx,0007h ; Attribute
539 int 10h
540 jmp short .loop
541 .done:
542 cbw ; AH <- 0
543 int 16h ; Wait for keypress
544 int 19h ; And try once more to boot...
545 .norge: jmp short .norge ; If int 19h returned; this is the end
548 ; Truncate BP to MaxTransfer
550 maxtrans:
551 cmp bp,[MaxTransfer]
552 jna .ok
553 mov bp,[MaxTransfer]
554 .ok: ret
557 ; Error message on failure
559 bailmsg: db 'Boot error', 0Dh, 0Ah, 0
561 ; This fails if the boot sector overflows
562 zb 1F8h-($-$$)
564 FirstSector dd 0xDEADBEEF ; Location of sector 1
565 MaxTransfer dw 0x007F ; Max transfer size
566 bootsignature dw 0AA55h
569 ; ===========================================================================
570 ; End of boot sector
571 ; ===========================================================================
572 ; Start of LDLINUX.SYS
573 ; ===========================================================================
575 ldlinux_sys:
577 syslinux_banner db 0Dh, 0Ah
578 db 'EXTLINUX '
579 db version_str, ' ', date, ' ', 0
580 db 0Dh, 0Ah, 1Ah ; EOF if we "type" this in DOS
582 align 8, db 0
583 ldlinux_magic dd LDLINUX_MAGIC
584 dd LDLINUX_MAGIC^HEXDATE
587 ; This area is patched by the installer. It is found by looking for
588 ; LDLINUX_MAGIC, plus 8 bytes.
590 patch_area:
591 LDLDwords dw 0 ; Total dwords starting at ldlinux_sys
592 LDLSectors dw 0 ; Number of sectors - (bootsec+this sec)
593 CheckSum dd 0 ; Checksum starting at ldlinux_sys
594 ; value = LDLINUX_MAGIC - [sum of dwords]
595 CurrentDir dd 2 ; "Current" directory inode number
597 ; Space for up to 64 sectors, the theoretical maximum
598 SectorPtrs times 64 dd 0
600 ldlinux_ent:
602 ; Note that some BIOSes are buggy and run the boot sector at 07C0:0000
603 ; instead of 0000:7C00 and the like. We don't want to add anything
604 ; more to the boot sector, so it is written to not assume a fixed
605 ; value in CS, but we don't want to deal with that anymore from now
606 ; on.
608 jmp 0:.next
609 .next:
612 ; Tell the user we got this far
614 mov si,syslinux_banner
615 call writestr
618 ; Tell the user if we're using EBIOS or CBIOS
620 print_bios:
621 mov si,cbios_name
622 cmp byte [getlinsec.jmp+1],(getlinsec_ebios-(getlinsec.jmp+2))
623 jne .cbios
624 mov si,ebios_name
625 .cbios:
626 mov [BIOSName],si
627 call writestr
629 section .bss
630 %define HAVE_BIOSNAME 1
631 BIOSName resw 1
633 section .text
635 ; Now we read the rest of LDLINUX.SYS. Don't bother loading the first
636 ; sector again, though.
638 load_rest:
639 mov si,SectorPtrs
640 mov bx,7C00h+2*SECTOR_SIZE ; Where we start loading
641 mov cx,[LDLSectors]
643 .get_chunk:
644 jcxz .done
645 xor bp,bp
646 lodsd ; First sector of this chunk
648 mov edx,eax
650 .make_chunk:
651 inc bp
652 dec cx
653 jz .chunk_ready
654 inc edx ; Next linear sector
655 cmp [si],edx ; Does it match
656 jnz .chunk_ready ; If not, this is it
657 add si,4 ; If so, add sector to chunk
658 jmp short .make_chunk
660 .chunk_ready:
661 call getlinsecsr
662 shl bp,SECTOR_SHIFT
663 add bx,bp
664 jmp .get_chunk
666 .done:
669 ; All loaded up, verify that we got what we needed.
670 ; Note: the checksum field is embedded in the checksum region, so
671 ; by the time we get to the end it should all cancel out.
673 verify_checksum:
674 mov si,ldlinux_sys
675 mov cx,[LDLDwords]
676 mov edx,-LDLINUX_MAGIC
677 .checksum:
678 lodsd
679 add edx,eax
680 loop .checksum
682 and edx,edx ; Should be zero
683 jz all_read ; We're cool, go for it!
686 ; Uh-oh, something went bad...
688 mov si,checksumerr_msg
689 call writestr
690 jmp kaboom
693 ; -----------------------------------------------------------------------------
694 ; Subroutines that have to be in the first sector
695 ; -----------------------------------------------------------------------------
699 ; writestr: write a null-terminated string to the console
700 ; This assumes we're on page 0. This is only used for early
701 ; messages, so it should be OK.
703 writestr:
704 .loop: lodsb
705 and al,al
706 jz .return
707 mov ah,0Eh ; Write to screen as TTY
708 mov bx,0007h ; Attribute
709 int 10h
710 jmp short .loop
711 .return: ret
714 ; getlinsecsr: save registers, call getlinsec, restore registers
716 getlinsecsr: pushad
717 call getlinsec
718 popad
722 ; Checksum error message
724 checksumerr_msg db ' Load error - ', 0 ; Boot failed appended
727 ; BIOS type string
729 cbios_name db 'CBIOS', 0
730 ebios_name db 'EBIOS', 0
733 ; Debug routine
735 %ifdef debug
736 safedumpregs:
737 cmp word [Debug_Magic],0D00Dh
738 jnz nc_return
739 jmp dumpregs
740 %endif
742 rl_checkpt equ $ ; Must be <= 8000h
744 rl_checkpt_off equ ($-$$)
745 %ifndef DEPEND
746 %if rl_checkpt_off > 400h
747 %error "Sector 1 overflow"
748 %endif
749 %endif
751 ; ----------------------------------------------------------------------------
752 ; End of code and data that have to be in the first sector
753 ; ----------------------------------------------------------------------------
755 all_read:
757 ; Let the user (and programmer!) know we got this far. This used to be
758 ; in Sector 1, but makes a lot more sense here.
760 mov si,copyright_str
761 call writestr
764 ; Insane hack to expand the DOS superblock to dwords
766 expand_super:
767 xor eax,eax
768 mov si,superblock
769 mov di,SuperInfo
770 mov cx,superinfo_size
771 .loop:
772 lodsw
773 dec si
774 stosd ; Store expanded word
775 xor ah,ah
776 stosd ; Store expanded byte
777 loop .loop
780 ; Load the real (ext2) superblock; 1024 bytes long at offset 1024
782 mov bx,SuperBlock
783 mov eax,1024 >> SECTOR_SHIFT
784 mov bp,ax
785 call getlinsec
788 ; Compute some values...
790 xor edx,edx
791 inc edx
793 ; s_log_block_size = log2(blocksize) - 10
794 mov cl,[SuperBlock+s_log_block_size]
795 add cl,10
796 mov [ClustByteShift],cl
797 mov eax,edx
798 shl eax,cl
799 mov [ClustSize],eax
801 sub cl,SECTOR_SHIFT
802 mov [ClustShift],cl
803 shr eax,SECTOR_SHIFT
804 mov [SecPerClust],eax
805 dec eax
806 mov [ClustMask],eax
808 add cl,SECTOR_SHIFT-2 ; 4 bytes/pointer
809 shl edx,cl
810 mov [PtrsPerBlock1],edx
811 shl edx,cl
812 mov [PtrsPerBlock2],edx
815 ; Common initialization code
817 %include "init.inc"
818 %include "cpuinit.inc"
821 ; Initialize the metadata cache
823 call initcache
826 ; Now, everything is "up and running"... patch kaboom for more
827 ; verbosity and using the full screen system
829 ; E9 = JMP NEAR
830 mov dword [kaboom.patch],0e9h+((kaboom2-(kaboom.patch+3)) << 8)
833 ; Now we're all set to start with our *real* business. First load the
834 ; configuration file (if any) and parse it.
836 ; In previous versions I avoided using 32-bit registers because of a
837 ; rumour some BIOSes clobbered the upper half of 32-bit registers at
838 ; random. I figure, though, that if there are any of those still left
839 ; they probably won't be trying to install Linux on them...
841 ; The code is still ripe with 16-bitisms, though. Not worth the hassle
842 ; to take'm out. In fact, we may want to put them back if we're going
843 ; to boot ELKS at some point.
847 ; Load configuration file
849 load_config:
850 mov di,ConfigName
851 call open
852 jz no_config_file
855 ; Now we have the config file open. Parse the config file and
856 ; run the user interface.
858 %include "ui.inc"
861 ; Linux kernel loading code is common.
863 %include "runkernel.inc"
866 ; COMBOOT-loading code
868 %include "comboot.inc"
869 %include "com32.inc"
870 %include "cmdline.inc"
873 ; Boot sector loading code
875 %include "bootsect.inc"
879 ; getlinsec_ext: same as getlinsec, except load any sector from the zero
880 ; block as all zeros; use to load any data derived
881 ; from an ext2 block pointer, i.e. anything *except the
882 ; superblock.*
884 getonesec_ext:
885 mov bp,1
887 getlinsec_ext:
888 cmp eax,[SecPerClust]
889 jae getlinsec ; Nothing fancy
891 ; If we get here, at least part of what we want is in the
892 ; zero block. Zero one sector at a time and loop.
893 push eax
894 push cx
895 xchg di,bx
896 xor eax,eax
897 mov cx,SECTOR_SIZE >> 2
898 rep stosd
899 xchg di,bx
900 pop cx
901 pop eax
902 inc eax
903 dec bp
904 jnz getlinsec_ext
908 ; Abort loading code
910 %include "abort.inc"
913 ; allocate_file: Allocate a file structure
915 ; If successful:
916 ; ZF set
917 ; BX = file pointer
918 ; In unsuccessful:
919 ; ZF clear
921 allocate_file:
922 TRACER 'a'
923 push cx
924 mov bx,Files
925 mov cx,MAX_OPEN
926 .check: cmp dword [bx], byte 0
927 je .found
928 add bx,open_file_t_size ; ZF = 0
929 loop .check
930 ; ZF = 0 if we fell out of the loop
931 .found: pop cx
934 ; open_inode:
935 ; Open a file indicated by an inode number in EAX
937 ; NOTE: This file considers finding a zero-length file an
938 ; error. This is so we don't have to deal with that special
939 ; case elsewhere in the program (most loops have the test
940 ; at the end).
942 ; If successful:
943 ; ZF clear
944 ; SI = file pointer
945 ; DX:AX = EAX = file length in bytes
946 ; ThisInode = the first 128 bytes of the inode
947 ; If unsuccessful
948 ; ZF set
950 ; Assumes CS == DS == ES.
952 open_inode.allocate_failure:
953 xor eax,eax
954 pop bx
955 pop di
958 open_inode:
959 push di
960 push bx
961 call allocate_file
962 jnz .allocate_failure
964 push cx
965 push gs
966 ; First, get the appropriate inode group and index
967 dec eax ; There is no inode 0
968 xor edx,edx
969 mov [bx+file_sector],edx
970 div dword [SuperBlock+s_inodes_per_group]
971 ; EAX = inode group; EDX = inode within group
972 push edx
974 ; Now, we need the block group descriptor.
975 ; To get that, we first need the relevant descriptor block.
977 shl eax, ext2_group_desc_lg2size ; Get byte offset in desc table
978 xor edx,edx
979 div dword [ClustSize]
980 ; eax = block #, edx = offset in block
981 add eax,dword [SuperBlock+s_first_data_block]
982 inc eax ; s_first_data_block+1
983 mov cl,[ClustShift]
984 shl eax,cl
985 push edx
986 shr edx,SECTOR_SHIFT
987 add eax,edx
988 pop edx
989 and dx,SECTOR_SIZE-1
990 call getcachesector ; Get the group descriptor
991 add si,dx
992 mov esi,[gs:si+bg_inode_table] ; Get inode table block #
993 pop eax ; Get inode within group
994 movzx edx, word [SuperBlock+s_inode_size]
995 mul edx
996 ; edx:eax = byte offset in inode table
997 div dword [ClustSize]
998 ; eax = block # versus inode table, edx = offset in block
999 add eax,esi
1000 shl eax,cl ; Turn into sector
1001 push dx
1002 shr edx,SECTOR_SHIFT
1003 add eax,edx
1004 mov [bx+file_in_sec],eax
1005 pop dx
1006 and dx,SECTOR_SIZE-1
1007 mov [bx+file_in_off],dx
1009 call getcachesector
1010 add si,dx
1011 mov cx,EXT2_GOOD_OLD_INODE_SIZE >> 2
1012 mov di,ThisInode
1013 gs rep movsd
1015 mov ax,[ThisInode+i_mode]
1016 mov [bx+file_mode],ax
1017 mov eax,[ThisInode+i_size]
1018 push eax
1019 add eax,SECTOR_SIZE-1
1020 shr eax,SECTOR_SHIFT
1021 mov [bx+file_left],eax
1022 pop eax
1023 mov si,bx
1024 mov edx,eax
1025 shr edx,16 ; 16-bitism, sigh
1026 and eax,eax ; ZF clear unless zero-length file
1027 pop gs
1028 pop cx
1029 pop bx
1030 pop di
1033 section .latebss
1034 alignb 4
1035 ThisInode resb EXT2_GOOD_OLD_INODE_SIZE ; The most recently opened inode
1037 section .text
1039 ; close:
1040 ; Deallocates a file structure (pointer in SI)
1041 ; Assumes CS == DS.
1043 close:
1044 mov dword [si],0 ; First dword == file_left
1048 ; searchdir:
1049 ; Search the root directory for a pre-mangled filename in DS:DI.
1051 ; NOTE: This file considers finding a zero-length file an
1052 ; error. This is so we don't have to deal with that special
1053 ; case elsewhere in the program (most loops have the test
1054 ; at the end).
1056 ; If successful:
1057 ; ZF clear
1058 ; SI = file pointer
1059 ; DX:AX = EAX = file length in bytes
1060 ; If unsuccessful
1061 ; ZF set
1063 ; Assumes CS == DS == ES; *** IS THIS CORRECT ***?
1065 searchdir:
1066 push bx
1067 push cx
1068 push bp
1069 mov byte [SymlinkCtr],MAX_SYMLINKS
1071 mov eax,[CurrentDir]
1072 .begin_path:
1073 .leadingslash:
1074 cmp byte [di],'/' ; Absolute filename?
1075 jne .gotdir
1076 mov eax,EXT2_ROOT_INO
1077 inc di ; Skip slash
1078 jmp .leadingslash
1079 .gotdir:
1081 ; At this point, EAX contains the directory inode,
1082 ; and DS:DI contains a pathname tail.
1083 .open:
1084 push eax ; Save directory inode
1086 call open_inode
1087 jz .done ; If error, done
1089 mov cx,[si+file_mode]
1090 shr cx,S_IFSHIFT ; Get file type
1092 cmp cx,T_IFDIR
1093 je .directory
1095 add sp,4 ; Drop directory inode
1097 cmp cx,T_IFREG
1098 je .file
1099 cmp cx,T_IFLNK
1100 je .symlink
1102 ; Otherwise, something bad...
1103 .err:
1104 call close
1105 .err_noclose:
1106 xor eax,eax
1107 xor si,si
1108 cwd ; DX <- 0
1110 .done:
1111 and eax,eax ; Set/clear ZF
1112 pop bp
1113 pop cx
1114 pop bx
1118 ; It's a file.
1120 .file:
1121 cmp byte [di],0 ; End of path?
1122 je .done ; If so, done
1123 jmp .err ; Otherwise, error
1126 ; It's a directory.
1128 .directory:
1129 pop dword [ThisDir] ; Remember what directory we're searching
1131 cmp byte [di],0 ; More path?
1132 je .err ; If not, bad
1134 .skipslash: ; Skip redundant slashes
1135 cmp byte [di],'/'
1136 jne .readdir
1137 inc di
1138 jmp .skipslash
1140 .readdir:
1141 mov bx,trackbuf
1142 push bx
1143 mov cx,[SecPerClust]
1144 call getfssec
1145 pop bx
1146 pushf ; Save EOF flag
1147 push si ; Save filesystem pointer
1148 .getent:
1149 cmp dword [bx+d_inode],0
1150 je .endblock
1152 push di
1153 movzx cx,byte [bx+d_name_len]
1154 lea si,[bx+d_name]
1155 repe cmpsb
1156 je .maybe
1157 .nope:
1158 pop di
1160 add bx,[bx+d_rec_len]
1161 jmp .getent
1163 .endblock:
1164 pop si
1165 popf
1166 jnc .readdir ; There is more
1167 jmp .err ; Otherwise badness...
1169 .maybe:
1170 mov eax,[bx+d_inode]
1172 ; Does this match the end of the requested filename?
1173 cmp byte [di],0
1174 je .finish
1175 cmp byte [di],'/'
1176 jne .nope
1178 ; We found something; now we need to open the file
1179 .finish:
1180 pop bx ; Adjust stack (di)
1181 pop si
1182 call close ; Close directory
1183 pop bx ; Adjust stack (flags)
1184 jmp .open
1187 ; It's a symlink. We have to determine if it's a fast symlink
1188 ; (data stored in the inode) or not (data stored as a regular
1189 ; file.) Either which way, we start from the directory
1190 ; which we just visited if relative, or from the root directory
1191 ; if absolute, and append any remaining part of the path.
1193 .symlink:
1194 dec byte [SymlinkCtr]
1195 jz .err ; Too many symlink references
1197 cmp eax,SYMLINK_SECTORS*SECTOR_SIZE
1198 jae .err ; Symlink too long
1200 ; Computation for fast symlink, as defined by ext2/3 spec
1201 xor ecx,ecx
1202 cmp [ThisInode+i_file_acl],ecx
1203 setne cl ; ECX <- i_file_acl ? 1 : 0
1204 cmp [ThisInode+i_blocks],ecx
1205 jne .slow_symlink
1207 ; It's a fast symlink
1208 .fast_symlink:
1209 call close ; We've got all we need
1210 mov si,ThisInode+i_block
1212 push di
1213 mov di,SymlinkTmpBuf
1214 mov ecx,eax
1215 rep movsb
1216 pop si
1218 .symlink_finish:
1219 cmp byte [si],0
1220 je .no_slash
1221 mov al,'/'
1222 stosb
1223 .no_slash:
1224 mov bp,SymlinkTmpBufEnd
1225 call strecpy
1226 jc .err_noclose ; Buffer overflow
1228 ; Now copy it to the "real" buffer; we need to have
1229 ; two buffers so we avoid overwriting the tail on the
1230 ; next copy
1231 mov si,SymlinkTmpBuf
1232 mov di,SymlinkBuf
1233 push di
1234 call strcpy
1235 pop di
1236 mov eax,[ThisDir] ; Resume searching previous directory
1237 jmp .begin_path
1239 .slow_symlink:
1240 mov bx,SymlinkTmpBuf
1241 mov cx,SYMLINK_SECTORS
1242 call getfssec
1243 ; The EOF closed the file
1245 mov si,di ; SI = filename tail
1246 mov di,SymlinkTmpBuf
1247 add di,ax ; AX = file length
1248 jmp .symlink_finish
1251 section .bss
1252 alignb 4
1253 SymlinkBuf resb SYMLINK_SECTORS*SECTOR_SIZE+64
1254 SymlinkTmpBuf equ trackbuf
1255 SymlinkTmpBufEnd equ trackbuf+SYMLINK_SECTORS*SECTOR_SIZE+64
1256 ThisDir resd 1
1257 SymlinkCtr resb 1
1259 section .text
1261 ; mangle_name: Mangle a filename pointed to by DS:SI into a buffer pointed
1262 ; to by ES:DI; ends on encountering any whitespace.
1264 ; This verifies that a filename is < FILENAME_MAX characters,
1265 ; doesn't contain whitespace, zero-pads the output buffer,
1266 ; and removes redundant slashes,
1267 ; so "repe cmpsb" can do a compare, and the
1268 ; path-searching routine gets a bit of an easier job.
1270 ; FIX: we may want to support \-escapes here (and this would
1271 ; be the place.)
1273 mangle_name:
1274 push bx
1275 xor ax,ax
1276 mov cx,FILENAME_MAX-1
1277 mov bx,di
1279 .mn_loop:
1280 lodsb
1281 cmp al,' ' ; If control or space, end
1282 jna .mn_end
1283 cmp al,ah ; Repeated slash?
1284 je .mn_skip
1285 xor ah,ah
1286 cmp al,'/'
1287 jne .mn_ok
1288 mov ah,al
1289 .mn_ok stosb
1290 .mn_skip: loop .mn_loop
1291 .mn_end:
1292 cmp bx,di ; At the beginning of the buffer?
1293 jbe .mn_zero
1294 cmp byte [di-1],'/' ; Terminal slash?
1295 jne .mn_zero
1296 .mn_kill: dec di ; If so, remove it
1297 inc cx
1298 jmp short .mn_end
1299 .mn_zero:
1300 inc cx ; At least one null byte
1301 xor ax,ax ; Zero-fill name
1302 rep stosb
1303 pop bx
1304 ret ; Done
1307 ; unmangle_name: Does the opposite of mangle_name; converts a DOS-mangled
1308 ; filename to the conventional representation. This is needed
1309 ; for the BOOT_IMAGE= parameter for the kernel.
1310 ; NOTE: A 13-byte buffer is mandatory, even if the string is
1311 ; known to be shorter.
1313 ; DS:SI -> input mangled file name
1314 ; ES:DI -> output buffer
1316 ; On return, DI points to the first byte after the output name,
1317 ; which is set to a null byte.
1319 unmangle_name: call strcpy
1320 dec di ; Point to final null byte
1324 ; writechr: Write a single character in AL to the console without
1325 ; mangling any registers; handle video pages correctly.
1327 writechr:
1328 call write_serial ; write to serial port if needed
1329 pushfd
1330 test byte [cs:DisplayCon],01h
1331 jz .nothing
1332 pushad
1333 mov ah,0Eh
1334 mov bl,07h ; attribute
1335 mov bh,[cs:BIOS_page] ; current page
1336 int 10h
1337 popad
1338 .nothing:
1339 popfd
1344 ; kaboom2: once everything is loaded, replace the part of kaboom
1345 ; starting with "kaboom.patch" with this part
1347 kaboom2:
1348 mov si,err_bootfailed
1349 call cwritestr
1350 call getchar
1351 call vgaclearmode
1352 int 19h ; And try once more to boot...
1353 .norge: jmp short .norge ; If int 19h returned; this is the end
1357 ; linsector: Convert a linear sector index in a file to a linear sector number
1358 ; EAX -> linear sector number
1359 ; DS:SI -> open_file_t
1361 ; Returns next sector number in EAX; CF on EOF (not an error!)
1363 linsector:
1364 push gs
1365 push ebx
1366 push esi
1367 push edi
1368 push ecx
1369 push edx
1370 push ebp
1372 push eax ; Save sector index
1373 mov cl,[ClustShift]
1374 shr eax,cl ; Convert to block number
1375 push eax
1376 mov eax,[si+file_in_sec]
1377 mov bx,si
1378 call getcachesector ; Get inode
1379 add si,[bx+file_in_off] ; Get *our* inode
1380 pop eax
1381 lea ebx,[i_block+4*eax]
1382 cmp eax,EXT2_NDIR_BLOCKS
1383 jb .direct
1384 mov ebx,i_block+4*EXT2_IND_BLOCK
1385 sub eax,EXT2_NDIR_BLOCKS
1386 mov ebp,[PtrsPerBlock1]
1387 cmp eax,ebp
1388 jb .ind1
1389 mov ebx,i_block+4*EXT2_DIND_BLOCK
1390 sub eax,ebp
1391 mov ebp,[PtrsPerBlock2]
1392 cmp eax,ebp
1393 jb .ind2
1394 mov ebx,i_block+4*EXT2_TIND_BLOCK
1395 sub eax,ebp
1397 .ind3:
1398 ; Triple indirect; eax contains the block no
1399 ; with respect to the start of the tind area;
1400 ; ebx contains the pointer to the tind block.
1401 xor edx,edx
1402 div dword [PtrsPerBlock2]
1403 ; EAX = which dind block, EDX = pointer within dind block
1404 push ax
1405 shr eax,SECTOR_SHIFT-2
1406 mov ebp,[gs:si+bx]
1407 shl ebp,cl
1408 add eax,ebp
1409 call getcachesector
1410 pop bx
1411 and bx,(SECTOR_SIZE >> 2)-1
1412 shl bx,2
1413 mov eax,edx ; The ind2 code wants the remainder...
1415 .ind2:
1416 ; Double indirect; eax contains the block no
1417 ; with respect to the start of the dind area;
1418 ; ebx contains the pointer to the dind block.
1419 xor edx,edx
1420 div dword [PtrsPerBlock1]
1421 ; EAX = which ind block, EDX = pointer within ind block
1422 push ax
1423 shr eax,SECTOR_SHIFT-2
1424 mov ebp,[gs:si+bx]
1425 shl ebp,cl
1426 add eax,ebp
1427 call getcachesector
1428 pop bx
1429 and bx,(SECTOR_SIZE >> 2)-1
1430 shl bx,2
1431 mov eax,edx ; The int1 code wants the remainder...
1433 .ind1:
1434 ; Single indirect; eax contains the block no
1435 ; with respect to the start of the ind area;
1436 ; ebx contains the pointer to the ind block.
1437 push ax
1438 shr eax,SECTOR_SHIFT-2
1439 mov ebp,[gs:si+bx]
1440 shl ebp,cl
1441 add eax,ebp
1442 call getcachesector
1443 pop bx
1444 and bx,(SECTOR_SIZE >> 2)-1
1445 shl bx,2
1447 .direct:
1448 mov ebx,[gs:bx+si] ; Get the pointer
1450 pop eax ; Get the sector index again
1451 shl ebx,cl ; Convert block number to sector
1452 and eax,[ClustMask] ; Add offset within block
1453 add eax,ebx
1455 pop ebp
1456 pop edx
1457 pop ecx
1458 pop edi
1459 pop esi
1460 pop ebx
1461 pop gs
1465 ; getfssec: Get multiple sectors from a file
1467 ; Same as above, except SI is a pointer to a open_file_t
1469 ; ES:BX -> Buffer
1470 ; DS:SI -> Pointer to open_file_t
1471 ; CX -> Sector count (0FFFFh = until end of file)
1472 ; Must not exceed the ES segment
1473 ; Returns CF=1 on EOF (not necessarily error)
1474 ; All arguments are advanced to reflect data read.
1476 getfssec:
1477 push ebp
1478 push eax
1479 push edx
1480 push edi
1482 movzx ecx,cx
1483 cmp ecx,[si] ; Number of sectors left
1484 jbe .lenok
1485 mov cx,[si]
1486 .lenok:
1487 .getfragment:
1488 mov eax,[si+file_sector] ; Current start index
1489 mov edi,eax
1490 call linsector
1491 push eax ; Fragment start sector
1492 mov edx,eax
1493 xor ebp,ebp ; Fragment sector count
1494 .getseccnt:
1495 inc bp
1496 dec cx
1497 jz .do_read
1498 xor eax,eax
1499 mov ax,es
1500 shl ax,4
1501 add ax,bx ; Now DI = how far into 64K block we are
1502 not ax ; Bytes left in 64K block
1503 inc eax
1504 shr eax,SECTOR_SHIFT ; Sectors left in 64K block
1505 cmp bp,ax
1506 jnb .do_read ; Unless there is at least 1 more sector room...
1507 inc edi ; Sector index
1508 inc edx ; Linearly next sector
1509 mov eax,edi
1510 call linsector
1511 ; jc .do_read
1512 cmp edx,eax
1513 je .getseccnt
1514 .do_read:
1515 pop eax ; Linear start sector
1516 pushad
1517 call getlinsec_ext
1518 popad
1519 push bp
1520 shl bp,9
1521 add bx,bp ; Adjust buffer pointer
1522 pop bp
1523 add [si+file_sector],ebp ; Next sector index
1524 sub [si],ebp ; Sectors consumed
1525 jcxz .done
1526 jnz .getfragment
1527 ; Fall through
1528 .done:
1529 cmp dword [si],1 ; Did we run out of file?
1530 ; CF set if [SI] < 1, i.e. == 0
1531 pop edi
1532 pop edx
1533 pop eax
1534 pop ebp
1537 ; -----------------------------------------------------------------------------
1538 ; Common modules
1539 ; -----------------------------------------------------------------------------
1541 %include "getc.inc" ; getc et al
1542 %include "conio.inc" ; Console I/O
1543 %include "writestr.inc" ; String output
1544 %include "parseconfig.inc" ; High-level config file handling
1545 %include "parsecmd.inc" ; Low-level config file handling
1546 %include "bcopy32.inc" ; 32-bit bcopy
1547 %include "loadhigh.inc" ; Load a file into high memory
1548 %include "font.inc" ; VGA font stuff
1549 %include "graphics.inc" ; VGA graphics
1550 %include "highmem.inc" ; High memory sizing
1551 %include "strcpy.inc" ; strcpy()
1552 %include "strecpy.inc" ; strcpy with end pointer check
1553 %include "cache.inc"
1555 ; -----------------------------------------------------------------------------
1556 ; Begin data section
1557 ; -----------------------------------------------------------------------------
1559 section .data
1560 copyright_str db ' Copyright (C) 1994-', year, ' H. Peter Anvin'
1561 db CR, LF, 0
1562 boot_prompt db 'boot: ', 0
1563 wipe_char db BS, ' ', BS, 0
1564 err_notfound db 'Could not find kernel image: ',0
1565 err_notkernel db CR, LF, 'Invalid or corrupt kernel image.', CR, LF, 0
1566 err_noram db 'It appears your computer has less than '
1567 asciidec dosram_k
1568 db 'K of low ("DOS")'
1569 db CR, LF
1570 db 'RAM. Linux needs at least this amount to boot. If you get'
1571 db CR, LF
1572 db 'this message in error, hold down the Ctrl key while'
1573 db CR, LF
1574 db 'booting, and I will take your word for it.', CR, LF, 0
1575 err_badcfg db 'Unknown keyword in extlinux.conf.', CR, LF, 0
1576 err_noparm db 'Missing parameter in extlinux.conf.', CR, LF, 0
1577 err_noinitrd db CR, LF, 'Could not find ramdisk image: ', 0
1578 err_nohighmem db 'Not enough memory to load specified kernel.', CR, LF, 0
1579 err_highload db CR, LF, 'Kernel transfer failure.', CR, LF, 0
1580 err_oldkernel db 'Cannot load a ramdisk with an old kernel image.'
1581 db CR, LF, 0
1582 err_notdos db ': attempted DOS system call', CR, LF, 0
1583 err_comlarge db 'COMBOOT image too large.', CR, LF, 0
1584 err_bssimage db 'BSS images not supported.', CR, LF, 0
1585 err_a20 db CR, LF, 'A20 gate not responding!', CR, LF, 0
1586 err_bootfailed db CR, LF, 'Boot failed: please change disks and press '
1587 db 'a key to continue.', CR, LF, 0
1588 ready_msg db 'Ready.', CR, LF, 0
1589 crlfloading_msg db CR, LF
1590 loading_msg db 'Loading ', 0
1591 dotdot_msg db '.'
1592 dot_msg db '.', 0
1593 aborted_msg db ' aborted.' ; Fall through to crlf_msg!
1594 crlf_msg db CR, LF
1595 null_msg db 0
1596 crff_msg db CR, FF, 0
1597 ConfigName db 'extlinux.conf',0 ; Unmangled form
1600 ; Command line options we'd like to take a look at
1602 ; mem= and vga= are handled as normal 32-bit integer values
1603 initrd_cmd db 'initrd='
1604 initrd_cmd_len equ 7
1607 ; Config file keyword table
1609 %include "keywords.inc"
1612 ; Extensions to search for (in *forward* order).
1614 align 4, db 0
1615 exten_table: db '.cbt' ; COMBOOT (specific)
1616 db '.img' ; Disk image
1617 db '.bs', 0 ; Boot sector
1618 db '.com' ; COMBOOT (same as DOS)
1619 db '.c32' ; COM32
1620 exten_table_end:
1621 dd 0, 0 ; Need 8 null bytes here
1624 ; Misc initialized (data) variables
1626 %ifdef debug ; This code for debugging only
1627 debug_magic dw 0D00Dh ; Debug code sentinel
1628 %endif
1630 alignb 4, db 0
1631 BufSafe dw trackbufsize/SECTOR_SIZE ; Clusters we can load into trackbuf
1632 BufSafeSec dw trackbufsize/SECTOR_SIZE ; = how many sectors?
1633 BufSafeBytes dw trackbufsize ; = how many bytes?
1634 EndOfGetCBuf dw getcbuf+trackbufsize ; = getcbuf+BufSafeBytes
1635 %ifndef DEPEND
1636 %if ( trackbufsize % SECTOR_SIZE ) != 0
1637 %error trackbufsize must be a multiple of SECTOR_SIZE
1638 %endif
1639 %endif