ISOLINUX: Change DriveNo -> DriveNumber
[syslinux.git] / extlinux.asm
blob54fda21e5ced41d58b9d67a79e9e34beb1579fa7
1 ; -*- fundamental -*- (asm-mode sucks)
2 ; ****************************************************************************
4 ; extlinux.asm
6 ; A program to boot Linux kernels off an ext2/ext3 filesystem.
8 ; Copyright (C) 1994-2007 H. Peter Anvin
10 ; This program is free software; you can redistribute it and/or modify
11 ; it under the terms of the GNU General Public License as published by
12 ; the Free Software Foundation, Inc., 53 Temple Place Ste 330,
13 ; Boston MA 02111-1307, USA; either version 2 of the License, or
14 ; (at your option) any later version; incorporated herein by reference.
16 ; ****************************************************************************
18 %define IS_EXTLINUX 1
19 %include "head.inc"
20 %include "ext2_fs.inc"
23 ; Some semi-configurable constants... change on your own risk.
25 my_id equ extlinux_id
26 ; NASM 0.98.38 croaks if these are equ's rather than macros...
27 FILENAME_MAX_LG2 equ 8 ; log2(Max filename size Including final null)
28 FILENAME_MAX equ (1 << FILENAME_MAX_LG2) ; Max mangled filename size
29 NULLFILE equ 0 ; Null character == empty filename
30 NULLOFFSET equ 0 ; Position in which to look
31 retry_count equ 16 ; How patient are we with the disk?
32 %assign HIGHMEM_SLOP 0 ; Avoid this much memory near the top
33 LDLINUX_MAGIC equ 0x3eb202fe ; A random number to identify ourselves with
35 MAX_OPEN_LG2 equ 6 ; log2(Max number of open files)
36 MAX_OPEN equ (1 << MAX_OPEN_LG2)
38 SECTOR_SHIFT equ 9
39 SECTOR_SIZE equ (1 << SECTOR_SHIFT)
41 MAX_SYMLINKS equ 64 ; Maximum number of symlinks per lookup
42 SYMLINK_SECTORS equ 2 ; Max number of sectors in a symlink
43 ; (should be >= FILENAME_MAX)
46 ; This is what we need to do when idle
48 %macro RESET_IDLE 0
49 ; Nothing
50 %endmacro
51 %macro DO_IDLE 0
52 ; Nothing
53 %endmacro
56 ; The following structure is used for "virtual kernels"; i.e. LILO-style
57 ; option labels. The options we permit here are `kernel' and `append
58 ; Since there is no room in the bottom 64K for all of these, we
59 ; stick them at vk_seg:0000 and copy them down before we need them.
61 struc vkernel
62 vk_vname: resb FILENAME_MAX ; Virtual name **MUST BE FIRST!**
63 vk_rname: resb FILENAME_MAX ; Real name
64 vk_appendlen: resw 1
65 vk_type: resb 1 ; Type of file
66 alignb 4
67 vk_append: resb max_cmd_len+1 ; Command line
68 alignb 4
69 vk_end: equ $ ; Should be <= vk_size
70 endstruc
73 ; Segment assignments in the bottom 640K
74 ; Stick to the low 512K in case we're using something like M-systems flash
75 ; which load a driver into low RAM (evil!!)
77 ; 0000h - main code/data segment (and BIOS segment)
79 real_mode_seg equ 4000h
80 cache_seg equ 3000h ; 64K area for metadata cache
81 vk_seg equ 2000h ; Virtual kernels
82 xfer_buf_seg equ 1000h ; Bounce buffer for I/O to high mem
83 comboot_seg equ real_mode_seg ; COMBOOT image loading zone
86 ; File structure. This holds the information for each currently open file.
88 struc open_file_t
89 file_left resd 1 ; Number of sectors left (0 = free)
90 file_sector resd 1 ; Next linear sector to read
91 file_in_sec resd 1 ; Sector where inode lives
92 file_in_off resw 1
93 file_mode resw 1
94 endstruc
96 %ifndef DEPEND
97 %if (open_file_t_size & (open_file_t_size-1))
98 %error "open_file_t is not a power of 2"
99 %endif
100 %endif
102 ; ---------------------------------------------------------------------------
103 ; BEGIN CODE
104 ; ---------------------------------------------------------------------------
107 ; Memory below this point is reserved for the BIOS and the MBR
109 section .earlybss
110 trackbufsize equ 8192
111 trackbuf resb trackbufsize ; Track buffer goes here
112 getcbuf resb trackbufsize
113 ; ends at 4800h
115 section .bss
116 SuperBlock resb 1024 ; ext2 superblock
117 SuperInfo resq 16 ; DOS superblock expanded
118 ClustSize resd 1 ; Bytes/cluster ("block")
119 SecPerClust resd 1 ; Sectors/cluster
120 ClustMask resd 1 ; Sectors/cluster - 1
121 PtrsPerBlock1 resd 1 ; Pointers/cluster
122 PtrsPerBlock2 resd 1 ; (Pointers/cluster)^2
123 DriveNumber resb 1 ; BIOS drive number
124 ClustShift resb 1 ; Shift count for sectors/cluster
125 ClustByteShift resb 1 ; Shift count for bytes/cluster
127 alignb open_file_t_size
128 Files resb MAX_OPEN*open_file_t_size
131 ; Constants for the xfer_buf_seg
133 ; The xfer_buf_seg is also used to store message file buffers. We
134 ; need two trackbuffers (text and graphics), plus a work buffer
135 ; for the graphics decompressor.
137 xbs_textbuf equ 0 ; Also hard-coded, do not change
138 xbs_vgabuf equ trackbufsize
139 xbs_vgatmpbuf equ 2*trackbufsize
142 section .text
144 ; Some of the things that have to be saved very early are saved
145 ; "close" to the initial stack pointer offset, in order to
146 ; reduce the code size...
148 StackBuf equ $-44-32 ; Start the stack here (grow down - 4K)
149 PartInfo equ StackBuf ; Saved partition table entry
150 FloppyTable equ PartInfo+16 ; Floppy info table (must follow PartInfo)
151 OrigFDCTabPtr equ StackBuf-4 ; The high dword on the stack
154 ; Primary entry point. Tempting as though it may be, we can't put the
155 ; initial "cli" here; the jmp opcode in the first byte is part of the
156 ; "magic number" (using the term very loosely) for the DOS superblock.
158 bootsec equ $
159 jmp short start ; 2 bytes
160 nop ; 1 byte
162 ; "Superblock" follows -- it's in the boot sector, so it's already
163 ; loaded and ready for us
165 bsOemName db 'EXTLINUX' ; The SYS command sets this, so...
167 ; These are the fields we actually care about. We end up expanding them
168 ; all to dword size early in the code, so generate labels for both
169 ; the expanded and unexpanded versions.
171 %macro superb 1
172 bx %+ %1 equ SuperInfo+($-superblock)*8+4
173 bs %+ %1 equ $
174 zb 1
175 %endmacro
176 %macro superw 1
177 bx %+ %1 equ SuperInfo+($-superblock)*8
178 bs %+ %1 equ $
179 zw 1
180 %endmacro
181 %macro superd 1
182 bx %+ %1 equ $ ; no expansion for dwords
183 bs %+ %1 equ $
184 zd 1
185 %endmacro
186 superblock equ $
187 superw BytesPerSec
188 superb SecPerClust
189 superw ResSectors
190 superb FATs
191 superw RootDirEnts
192 superw Sectors
193 superb Media
194 superw FATsecs
195 superw SecPerTrack
196 superw Heads
197 superinfo_size equ ($-superblock)-1 ; How much to expand
198 superd Hidden
199 superd HugeSectors
201 ; This is as far as FAT12/16 and FAT32 are consistent
203 zb 54 ; FAT12/16 need 26 more bytes,
204 ; FAT32 need 54 more bytes
205 superblock_len equ $-superblock
208 ; Note we don't check the constraints above now; we did that at install
209 ; time (we hope!)
211 start:
212 cli ; No interrupts yet, please
213 cld ; Copy upwards
215 ; Set up the stack
217 xor ax,ax
218 mov ss,ax
219 mov sp,StackBuf ; Just below BSS
220 mov es,ax
222 ; DS:SI may contain a partition table entry. Preserve it for us.
224 mov cx,8 ; Save partition info
225 mov di,sp
226 rep movsw
228 mov ds,ax ; Now we can initialize DS...
231 ; Now sautee the BIOS floppy info block to that it will support decent-
232 ; size transfers; the floppy block is 11 bytes and is stored in the
233 ; INT 1Eh vector (brilliant waste of resources, eh?)
235 ; Of course, if BIOSes had been properly programmed, we wouldn't have
236 ; had to waste precious space with this code.
238 mov bx,fdctab
239 lfs si,[bx] ; FS:SI -> original fdctab
240 push fs ; Save on stack in case we need to bail
241 push si
243 ; Save the old fdctab even if hard disk so the stack layout
244 ; is the same. The instructions above do not change the flags
245 mov [DriveNumber],dl ; Save drive number in DL
246 and dl,dl ; If floppy disk (00-7F), assume no
247 ; partition table
248 js harddisk
250 floppy:
251 mov cl,6 ; 12 bytes (CX == 0)
252 ; es:di -> FloppyTable already
253 ; This should be safe to do now, interrupts are off...
254 mov [bx],di ; FloppyTable
255 mov [bx+2],ax ; Segment 0
256 fs rep movsw ; Faster to move words
257 mov cl,[bsSecPerTrack] ; Patch the sector count
258 mov [di-8],cl
259 ; AX == 0 here
260 int 13h ; Some BIOSes need this
262 jmp short not_harddisk
264 ; The drive number and possibly partition information was passed to us
265 ; by the BIOS or previous boot loader (MBR). Current "best practice" is to
266 ; trust that rather than what the superblock contains.
268 ; Would it be better to zero out bsHidden if we don't have a partition table?
270 ; Note: di points to beyond the end of PartInfo
272 harddisk:
273 test byte [di-16],7Fh ; Sanity check: "active flag" should
274 jnz no_partition ; be 00 or 80
275 mov eax,[di-8] ; Partition offset (dword)
276 mov [bsHidden],eax
277 no_partition:
279 ; Get disk drive parameters (don't trust the superblock.) Don't do this for
280 ; floppy drives -- INT 13:08 on floppy drives will (may?) return info about
281 ; what the *drive* supports, not about the *media*. Fortunately floppy disks
282 ; tend to have a fixed, well-defined geometry which is stored in the superblock.
284 ; DL == drive # still
285 mov ah,08h
286 int 13h
287 jc no_driveparm
288 and ah,ah
289 jnz no_driveparm
290 shr dx,8
291 inc dx ; Contains # of heads - 1
292 mov [bsHeads],dx
293 and cx,3fh
294 mov [bsSecPerTrack],cx
295 no_driveparm:
296 not_harddisk:
298 ; Ready to enable interrupts, captain
303 ; Do we have EBIOS (EDD)?
305 eddcheck:
306 mov bx,55AAh
307 mov ah,41h ; EDD existence query
308 mov dl,[DriveNumber]
309 int 13h
310 jc .noedd
311 cmp bx,0AA55h
312 jne .noedd
313 test cl,1 ; Extended disk access functionality set
314 jz .noedd
316 ; We have EDD support...
318 mov byte [getlinsec.jmp+1],(getlinsec_ebios-(getlinsec.jmp+2))
319 .noedd:
322 ; Load the first sector of LDLINUX.SYS; this used to be all proper
323 ; with parsing the superblock and root directory; it doesn't fit
324 ; together with EBIOS support, unfortunately.
326 mov eax,[FirstSector] ; Sector start
327 mov bx,ldlinux_sys ; Where to load it
328 call getonesec
330 ; Some modicum of integrity checking
331 cmp dword [ldlinux_magic+4],LDLINUX_MAGIC^HEXDATE
332 jne kaboom
334 ; Go for it...
335 jmp ldlinux_ent
338 ; getonesec: get one disk sector
340 getonesec:
341 mov bp,1 ; One sector
342 ; Fall through
345 ; getlinsec: load a sequence of BP floppy sector given by the linear sector
346 ; number in EAX into the buffer at ES:BX. We try to optimize
347 ; by loading up to a whole track at a time, but the user
348 ; is responsible for not crossing a 64K boundary.
349 ; (Yes, BP is weird for a count, but it was available...)
351 ; On return, BX points to the first byte after the transferred
352 ; block.
354 ; This routine assumes CS == DS, and trashes most registers.
356 ; Stylistic note: use "xchg" instead of "mov" when the source is a register
357 ; that is dead from that point; this saves space. However, please keep
358 ; the order to dst,src to keep things sane.
360 getlinsec:
361 add eax,[bsHidden] ; Add partition offset
362 xor edx,edx ; Zero-extend LBA (eventually allow 64 bits)
364 .jmp: jmp strict short getlinsec_cbios
367 ; getlinsec_ebios:
369 ; getlinsec implementation for EBIOS (EDD)
371 getlinsec_ebios:
372 .loop:
373 push bp ; Sectors left
374 .retry2:
375 call maxtrans ; Enforce maximum transfer size
376 movzx edi,bp ; Sectors we are about to read
377 mov cx,retry_count
378 .retry:
380 ; Form DAPA on stack
381 push edx
382 push eax
383 push es
384 push bx
385 push di
386 push word 16
387 mov si,sp
388 pushad
389 mov dl,[DriveNumber]
390 push ds
391 push ss
392 pop ds ; DS <- SS
393 mov ah,42h ; Extended Read
394 int 13h
395 pop ds
396 popad
397 lea sp,[si+16] ; Remove DAPA
398 jc .error
399 pop bp
400 add eax,edi ; Advance sector pointer
401 sub bp,di ; Sectors left
402 shl di,SECTOR_SHIFT ; 512-byte sectors
403 add bx,di ; Advance buffer pointer
404 and bp,bp
405 jnz .loop
409 .error:
410 ; Some systems seem to get "stuck" in an error state when
411 ; using EBIOS. Doesn't happen when using CBIOS, which is
412 ; good, since some other systems get timeout failures
413 ; waiting for the floppy disk to spin up.
415 pushad ; Try resetting the device
416 xor ax,ax
417 mov dl,[DriveNumber]
418 int 13h
419 popad
420 loop .retry ; CX-- and jump if not zero
422 ;shr word [MaxTransfer],1 ; Reduce the transfer size
423 ;jnz .retry2
425 ; Total failure. Try falling back to CBIOS.
426 mov byte [getlinsec.jmp+1],(getlinsec_cbios-(getlinsec.jmp+2))
427 ;mov byte [MaxTransfer],63 ; Max possibe CBIOS transfer
429 pop bp
430 ; ... fall through ...
433 ; getlinsec_cbios:
435 ; getlinsec implementation for legacy CBIOS
437 getlinsec_cbios:
438 .loop:
439 push edx
440 push eax
441 push bp
442 push bx
444 movzx esi,word [bsSecPerTrack]
445 movzx edi,word [bsHeads]
447 ; Dividing by sectors to get (track,sector): we may have
448 ; up to 2^18 tracks, so we need to use 32-bit arithmetric.
450 div esi
451 xor cx,cx
452 xchg cx,dx ; CX <- sector index (0-based)
453 ; EDX <- 0
454 ; eax = track #
455 div edi ; Convert track to head/cyl
457 ; We should test this, but it doesn't fit...
458 ; cmp eax,1023
459 ; ja .error
462 ; Now we have AX = cyl, DX = head, CX = sector (0-based),
463 ; BP = sectors to transfer, SI = bsSecPerTrack,
464 ; ES:BX = data target
467 call maxtrans ; Enforce maximum transfer size
469 ; Must not cross track boundaries, so BP <= SI-CX
470 sub si,cx
471 cmp bp,si
472 jna .bp_ok
473 mov bp,si
474 .bp_ok:
476 shl ah,6 ; Because IBM was STOOPID
477 ; and thought 8 bits were enough
478 ; then thought 10 bits were enough...
479 inc cx ; Sector numbers are 1-based, sigh
480 or cl,ah
481 mov ch,al
482 mov dh,dl
483 mov dl,[DriveNumber]
484 xchg ax,bp ; Sector to transfer count
485 mov ah,02h ; Read sectors
486 mov bp,retry_count
487 .retry:
488 pushad
489 int 13h
490 popad
491 jc .error
492 .resume:
493 movzx ecx,al ; ECX <- sectors transferred
494 shl ax,SECTOR_SHIFT ; Convert sectors in AL to bytes in AX
495 pop bx
496 add bx,ax
497 pop bp
498 pop eax
499 pop edx
500 add eax,ecx
501 sub bp,cx
502 jnz .loop
505 .error:
506 dec bp
507 jnz .retry
509 xchg ax,bp ; Sectors transferred <- 0
510 shr word [MaxTransfer],1
511 jnz .resume
512 ; Fall through to disk_error
515 ; kaboom: write a message and bail out.
517 disk_error:
518 kaboom:
519 xor si,si
520 mov ss,si
521 mov sp,StackBuf-4 ; Reset stack
522 mov ds,si ; Reset data segment
523 pop dword [fdctab] ; Restore FDC table
524 .patch: ; When we have full code, intercept here
525 mov si,bailmsg
527 ; Write error message, this assumes screen page 0
528 .loop: lodsb
529 and al,al
530 jz .done
531 mov ah,0Eh ; Write to screen as TTY
532 mov bx,0007h ; Attribute
533 int 10h
534 jmp short .loop
535 .done:
536 cbw ; AH <- 0
537 .again: int 16h ; Wait for keypress
538 ; NB: replaced by int 18h if
539 ; chosen at install time..
540 int 19h ; And try once more to boot...
541 .norge: jmp short .norge ; If int 19h returned; this is the end
544 ; Truncate BP to MaxTransfer
546 maxtrans:
547 cmp bp,[MaxTransfer]
548 jna .ok
549 mov bp,[MaxTransfer]
550 .ok: ret
553 ; Error message on failure
555 bailmsg: db 'Boot error', 0Dh, 0Ah, 0
557 ; This fails if the boot sector overflows
558 zb 1F8h-($-$$)
560 FirstSector dd 0xDEADBEEF ; Location of sector 1
561 MaxTransfer dw 0x007F ; Max transfer size
563 ; This field will be filled in 0xAA55 by the installer, but we abuse it
564 ; to house a pointer to the INT 16h instruction at
565 ; kaboom.again, which gets patched to INT 18h in RAID mode.
566 bootsignature dw kaboom.again-bootsec
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 si,config_name ; Save config file name
851 mov di,ConfigName
852 call strcpy
854 mov di,ConfigName
855 call open
856 jz no_config_file
859 ; Now we have the config file open. Parse the config file and
860 ; run the user interface.
862 %include "ui.inc"
865 ; getlinsec_ext: same as getlinsec, except load any sector from the zero
866 ; block as all zeros; use to load any data derived
867 ; from an ext2 block pointer, i.e. anything *except the
868 ; superblock.*
870 getonesec_ext:
871 mov bp,1
873 getlinsec_ext:
874 cmp eax,[SecPerClust]
875 jae getlinsec ; Nothing fancy
877 ; If we get here, at least part of what we want is in the
878 ; zero block. Zero one sector at a time and loop.
879 push eax
880 push cx
881 xchg di,bx
882 xor eax,eax
883 mov cx,SECTOR_SIZE >> 2
884 rep stosd
885 xchg di,bx
886 pop cx
887 pop eax
888 inc eax
889 dec bp
890 jnz getlinsec_ext
894 ; allocate_file: Allocate a file structure
896 ; If successful:
897 ; ZF set
898 ; BX = file pointer
899 ; In unsuccessful:
900 ; ZF clear
902 allocate_file:
903 TRACER 'a'
904 push cx
905 mov bx,Files
906 mov cx,MAX_OPEN
907 .check: cmp dword [bx], byte 0
908 je .found
909 add bx,open_file_t_size ; ZF = 0
910 loop .check
911 ; ZF = 0 if we fell out of the loop
912 .found: pop cx
915 ; open_inode:
916 ; Open a file indicated by an inode number in EAX
918 ; NOTE: This file considers finding a zero-length file an
919 ; error. This is so we don't have to deal with that special
920 ; case elsewhere in the program (most loops have the test
921 ; at the end).
923 ; If successful:
924 ; ZF clear
925 ; SI = file pointer
926 ; DX:AX = EAX = file length in bytes
927 ; ThisInode = the first 128 bytes of the inode
928 ; If unsuccessful
929 ; ZF set
931 ; Assumes CS == DS == ES.
933 open_inode.allocate_failure:
934 xor eax,eax
935 pop bx
936 pop di
939 open_inode:
940 push di
941 push bx
942 call allocate_file
943 jnz .allocate_failure
945 push cx
946 push gs
947 ; First, get the appropriate inode group and index
948 dec eax ; There is no inode 0
949 xor edx,edx
950 mov [bx+file_sector],edx
951 div dword [SuperBlock+s_inodes_per_group]
952 ; EAX = inode group; EDX = inode within group
953 push edx
955 ; Now, we need the block group descriptor.
956 ; To get that, we first need the relevant descriptor block.
958 shl eax, ext2_group_desc_lg2size ; Get byte offset in desc table
959 xor edx,edx
960 div dword [ClustSize]
961 ; eax = block #, edx = offset in block
962 add eax,dword [SuperBlock+s_first_data_block]
963 inc eax ; s_first_data_block+1
964 mov cl,[ClustShift]
965 shl eax,cl
966 push edx
967 shr edx,SECTOR_SHIFT
968 add eax,edx
969 pop edx
970 and dx,SECTOR_SIZE-1
971 call getcachesector ; Get the group descriptor
972 add si,dx
973 mov esi,[gs:si+bg_inode_table] ; Get inode table block #
974 pop eax ; Get inode within group
975 movzx edx, word [SuperBlock+s_inode_size]
976 mul edx
977 ; edx:eax = byte offset in inode table
978 div dword [ClustSize]
979 ; eax = block # versus inode table, edx = offset in block
980 add eax,esi
981 shl eax,cl ; Turn into sector
982 push dx
983 shr edx,SECTOR_SHIFT
984 add eax,edx
985 mov [bx+file_in_sec],eax
986 pop dx
987 and dx,SECTOR_SIZE-1
988 mov [bx+file_in_off],dx
990 call getcachesector
991 add si,dx
992 mov cx,EXT2_GOOD_OLD_INODE_SIZE >> 2
993 mov di,ThisInode
994 gs rep movsd
996 mov ax,[ThisInode+i_mode]
997 mov [bx+file_mode],ax
998 mov eax,[ThisInode+i_size]
999 push eax
1000 add eax,SECTOR_SIZE-1
1001 shr eax,SECTOR_SHIFT
1002 mov [bx+file_left],eax
1003 pop eax
1004 mov si,bx
1005 mov edx,eax
1006 shr edx,16 ; 16-bitism, sigh
1007 and eax,eax ; ZF clear unless zero-length file
1008 pop gs
1009 pop cx
1010 pop bx
1011 pop di
1014 section .bss
1015 alignb 4
1016 ThisInode resb EXT2_GOOD_OLD_INODE_SIZE ; The most recently opened inode
1018 section .text
1020 ; close_file:
1021 ; Deallocates a file structure (pointer in SI)
1022 ; Assumes CS == DS.
1024 close_file:
1025 and si,si
1026 jz .closed
1027 mov dword [si],0 ; First dword == file_left
1028 .closed: ret
1031 ; searchdir:
1032 ; Search the root directory for a pre-mangled filename in DS:DI.
1034 ; NOTE: This file considers finding a zero-length file an
1035 ; error. This is so we don't have to deal with that special
1036 ; case elsewhere in the program (most loops have the test
1037 ; at the end).
1039 ; If successful:
1040 ; ZF clear
1041 ; SI = file pointer
1042 ; DX:AX = EAX = file length in bytes
1043 ; If unsuccessful
1044 ; ZF set
1046 ; Assumes CS == DS == ES; *** IS THIS CORRECT ***?
1048 searchdir:
1049 push bx
1050 push cx
1051 push bp
1052 mov byte [SymlinkCtr],MAX_SYMLINKS
1054 mov eax,[CurrentDir]
1055 .begin_path:
1056 .leadingslash:
1057 cmp byte [di],'/' ; Absolute filename?
1058 jne .gotdir
1059 mov eax,EXT2_ROOT_INO
1060 inc di ; Skip slash
1061 jmp .leadingslash
1062 .gotdir:
1064 ; At this point, EAX contains the directory inode,
1065 ; and DS:DI contains a pathname tail.
1066 .open:
1067 push eax ; Save directory inode
1069 call open_inode
1070 jz .done ; If error, done
1072 mov cx,[si+file_mode]
1073 shr cx,S_IFSHIFT ; Get file type
1075 cmp cx,T_IFDIR
1076 je .directory
1078 add sp,4 ; Drop directory inode
1080 cmp cx,T_IFREG
1081 je .file
1082 cmp cx,T_IFLNK
1083 je .symlink
1085 ; Otherwise, something bad...
1086 .err:
1087 call close_file
1088 .err_noclose:
1089 xor eax,eax
1090 xor si,si
1091 cwd ; DX <- 0
1093 .done:
1094 and eax,eax ; Set/clear ZF
1095 pop bp
1096 pop cx
1097 pop bx
1101 ; It's a file.
1103 .file:
1104 cmp byte [di],0 ; End of path?
1105 je .done ; If so, done
1106 jmp .err ; Otherwise, error
1109 ; It's a directory.
1111 .directory:
1112 pop dword [ThisDir] ; Remember what directory we're searching
1114 cmp byte [di],0 ; More path?
1115 je .err ; If not, bad
1117 .skipslash: ; Skip redundant slashes
1118 cmp byte [di],'/'
1119 jne .readdir
1120 inc di
1121 jmp .skipslash
1123 .readdir:
1124 mov bx,trackbuf
1125 push bx
1126 mov cx,[SecPerClust]
1127 call getfssec
1128 pop bx
1129 pushf ; Save EOF flag
1130 push si ; Save filesystem pointer
1131 .getent:
1132 cmp dword [bx+d_inode],0
1133 je .endblock
1135 push di
1136 movzx cx,byte [bx+d_name_len]
1137 lea si,[bx+d_name]
1138 repe cmpsb
1139 je .maybe
1140 .nope:
1141 pop di
1143 add bx,[bx+d_rec_len]
1144 jmp .getent
1146 .endblock:
1147 pop si
1148 popf
1149 jnc .readdir ; There is more
1150 jmp .err ; Otherwise badness...
1152 .maybe:
1153 mov eax,[bx+d_inode]
1155 ; Does this match the end of the requested filename?
1156 cmp byte [di],0
1157 je .finish
1158 cmp byte [di],'/'
1159 jne .nope
1161 ; We found something; now we need to open the file
1162 .finish:
1163 pop bx ; Adjust stack (di)
1164 pop si
1165 call close_file ; Close directory
1166 pop bx ; Adjust stack (flags)
1167 jmp .open
1170 ; It's a symlink. We have to determine if it's a fast symlink
1171 ; (data stored in the inode) or not (data stored as a regular
1172 ; file.) Either which way, we start from the directory
1173 ; which we just visited if relative, or from the root directory
1174 ; if absolute, and append any remaining part of the path.
1176 .symlink:
1177 dec byte [SymlinkCtr]
1178 jz .err ; Too many symlink references
1180 cmp eax,SYMLINK_SECTORS*SECTOR_SIZE
1181 jae .err ; Symlink too long
1183 ; Computation for fast symlink, as defined by ext2/3 spec
1184 xor ecx,ecx
1185 cmp [ThisInode+i_file_acl],ecx
1186 setne cl ; ECX <- i_file_acl ? 1 : 0
1187 cmp [ThisInode+i_blocks],ecx
1188 jne .slow_symlink
1190 ; It's a fast symlink
1191 .fast_symlink:
1192 call close_file ; We've got all we need
1193 mov si,ThisInode+i_block
1195 push di
1196 mov di,SymlinkTmpBuf
1197 mov ecx,eax
1198 rep movsb
1199 pop si
1201 .symlink_finish:
1202 cmp byte [si],0
1203 je .no_slash
1204 mov al,'/'
1205 stosb
1206 .no_slash:
1207 mov bp,SymlinkTmpBufEnd
1208 call strecpy
1209 jc .err_noclose ; Buffer overflow
1211 ; Now copy it to the "real" buffer; we need to have
1212 ; two buffers so we avoid overwriting the tail on the
1213 ; next copy
1214 mov si,SymlinkTmpBuf
1215 mov di,SymlinkBuf
1216 push di
1217 call strcpy
1218 pop di
1219 mov eax,[ThisDir] ; Resume searching previous directory
1220 jmp .begin_path
1222 .slow_symlink:
1223 mov bx,SymlinkTmpBuf
1224 mov cx,SYMLINK_SECTORS
1225 call getfssec
1226 ; The EOF closed the file
1228 mov si,di ; SI = filename tail
1229 mov di,SymlinkTmpBuf
1230 add di,ax ; AX = file length
1231 jmp .symlink_finish
1234 section .bss
1235 alignb 4
1236 SymlinkBuf resb SYMLINK_SECTORS*SECTOR_SIZE+64
1237 SymlinkTmpBuf equ trackbuf
1238 SymlinkTmpBufEnd equ trackbuf+SYMLINK_SECTORS*SECTOR_SIZE+64
1239 ThisDir resd 1
1240 SymlinkCtr resb 1
1242 section .text
1244 ; mangle_name: Mangle a filename pointed to by DS:SI into a buffer pointed
1245 ; to by ES:DI; ends on encountering any whitespace.
1246 ; DI is preserved.
1248 ; This verifies that a filename is < FILENAME_MAX characters,
1249 ; doesn't contain whitespace, zero-pads the output buffer,
1250 ; and removes redundant slashes,
1251 ; so "repe cmpsb" can do a compare, and the
1252 ; path-searching routine gets a bit of an easier job.
1254 ; FIX: we may want to support \-escapes here (and this would
1255 ; be the place.)
1257 mangle_name:
1258 push di
1259 push bx
1260 xor ax,ax
1261 mov cx,FILENAME_MAX-1
1262 mov bx,di
1264 .mn_loop:
1265 lodsb
1266 cmp al,' ' ; If control or space, end
1267 jna .mn_end
1268 cmp al,ah ; Repeated slash?
1269 je .mn_skip
1270 xor ah,ah
1271 cmp al,'/'
1272 jne .mn_ok
1273 mov ah,al
1274 .mn_ok stosb
1275 .mn_skip: loop .mn_loop
1276 .mn_end:
1277 cmp bx,di ; At the beginning of the buffer?
1278 jbe .mn_zero
1279 cmp byte [di-1],'/' ; Terminal slash?
1280 jne .mn_zero
1281 .mn_kill: dec di ; If so, remove it
1282 inc cx
1283 jmp short .mn_end
1284 .mn_zero:
1285 inc cx ; At least one null byte
1286 xor ax,ax ; Zero-fill name
1287 rep stosb
1288 pop bx
1289 pop di
1290 ret ; Done
1293 ; unmangle_name: Does the opposite of mangle_name; converts a DOS-mangled
1294 ; filename to the conventional representation. This is needed
1295 ; for the BOOT_IMAGE= parameter for the kernel.
1296 ; NOTE: A 13-byte buffer is mandatory, even if the string is
1297 ; known to be shorter.
1299 ; DS:SI -> input mangled file name
1300 ; ES:DI -> output buffer
1302 ; On return, DI points to the first byte after the output name,
1303 ; which is set to a null byte.
1305 unmangle_name: call strcpy
1306 dec di ; Point to final null byte
1311 ; kaboom2: once everything is loaded, replace the part of kaboom
1312 ; starting with "kaboom.patch" with this part
1314 kaboom2:
1315 mov si,err_bootfailed
1316 call cwritestr
1317 cmp byte [kaboom.again+1],18h ; INT 18h version?
1318 je .int18
1319 call getchar
1320 call vgaclearmode
1321 int 19h ; And try once more to boot...
1322 .norge: jmp short .norge ; If int 19h returned; this is the end
1323 .int18:
1324 call vgaclearmode
1325 int 18h
1326 .noreg: jmp short .noreg ; Nynorsk
1330 ; linsector: Convert a linear sector index in a file to a linear sector number
1331 ; EAX -> linear sector number
1332 ; DS:SI -> open_file_t
1334 ; Returns next sector number in EAX; CF on EOF (not an error!)
1336 linsector:
1337 push gs
1338 push ebx
1339 push esi
1340 push edi
1341 push ecx
1342 push edx
1343 push ebp
1345 push eax ; Save sector index
1346 mov cl,[ClustShift]
1347 shr eax,cl ; Convert to block number
1348 push eax
1349 mov eax,[si+file_in_sec]
1350 mov bx,si
1351 call getcachesector ; Get inode
1352 add si,[bx+file_in_off] ; Get *our* inode
1353 pop eax
1354 lea ebx,[i_block+4*eax]
1355 cmp eax,EXT2_NDIR_BLOCKS
1356 jb .direct
1357 mov ebx,i_block+4*EXT2_IND_BLOCK
1358 sub eax,EXT2_NDIR_BLOCKS
1359 mov ebp,[PtrsPerBlock1]
1360 cmp eax,ebp
1361 jb .ind1
1362 mov ebx,i_block+4*EXT2_DIND_BLOCK
1363 sub eax,ebp
1364 mov ebp,[PtrsPerBlock2]
1365 cmp eax,ebp
1366 jb .ind2
1367 mov ebx,i_block+4*EXT2_TIND_BLOCK
1368 sub eax,ebp
1370 .ind3:
1371 ; Triple indirect; eax contains the block no
1372 ; with respect to the start of the tind area;
1373 ; ebx contains the pointer to the tind block.
1374 xor edx,edx
1375 div dword [PtrsPerBlock2]
1376 ; EAX = which dind block, EDX = pointer within dind block
1377 push ax
1378 shr eax,SECTOR_SHIFT-2
1379 mov ebp,[gs:si+bx]
1380 shl ebp,cl
1381 add eax,ebp
1382 call getcachesector
1383 pop bx
1384 and bx,(SECTOR_SIZE >> 2)-1
1385 shl bx,2
1386 mov eax,edx ; The ind2 code wants the remainder...
1388 .ind2:
1389 ; Double indirect; eax contains the block no
1390 ; with respect to the start of the dind area;
1391 ; ebx contains the pointer to the dind block.
1392 xor edx,edx
1393 div dword [PtrsPerBlock1]
1394 ; EAX = which ind block, EDX = pointer within ind block
1395 push ax
1396 shr eax,SECTOR_SHIFT-2
1397 mov ebp,[gs:si+bx]
1398 shl ebp,cl
1399 add eax,ebp
1400 call getcachesector
1401 pop bx
1402 and bx,(SECTOR_SIZE >> 2)-1
1403 shl bx,2
1404 mov eax,edx ; The int1 code wants the remainder...
1406 .ind1:
1407 ; Single indirect; eax contains the block no
1408 ; with respect to the start of the ind area;
1409 ; ebx contains the pointer to the ind block.
1410 push ax
1411 shr eax,SECTOR_SHIFT-2
1412 mov ebp,[gs:si+bx]
1413 shl ebp,cl
1414 add eax,ebp
1415 call getcachesector
1416 pop bx
1417 and bx,(SECTOR_SIZE >> 2)-1
1418 shl bx,2
1420 .direct:
1421 mov ebx,[gs:bx+si] ; Get the pointer
1423 pop eax ; Get the sector index again
1424 shl ebx,cl ; Convert block number to sector
1425 and eax,[ClustMask] ; Add offset within block
1426 add eax,ebx
1428 pop ebp
1429 pop edx
1430 pop ecx
1431 pop edi
1432 pop esi
1433 pop ebx
1434 pop gs
1438 ; getfssec: Get multiple sectors from a file
1440 ; Same as above, except SI is a pointer to a open_file_t
1442 ; ES:BX -> Buffer
1443 ; DS:SI -> Pointer to open_file_t
1444 ; CX -> Sector count (0FFFFh = until end of file)
1445 ; Must not exceed the ES segment
1446 ; Returns CF=1 on EOF (not necessarily error)
1447 ; All arguments are advanced to reflect data read.
1449 getfssec:
1450 push ebp
1451 push eax
1452 push edx
1453 push edi
1455 movzx ecx,cx
1456 cmp ecx,[si] ; Number of sectors left
1457 jbe .lenok
1458 mov cx,[si]
1459 .lenok:
1460 .getfragment:
1461 mov eax,[si+file_sector] ; Current start index
1462 mov edi,eax
1463 call linsector
1464 push eax ; Fragment start sector
1465 mov edx,eax
1466 xor ebp,ebp ; Fragment sector count
1467 .getseccnt:
1468 inc bp
1469 dec cx
1470 jz .do_read
1471 xor eax,eax
1472 mov ax,es
1473 shl ax,4
1474 add ax,bx ; Now DI = how far into 64K block we are
1475 not ax ; Bytes left in 64K block
1476 inc eax
1477 shr eax,SECTOR_SHIFT ; Sectors left in 64K block
1478 cmp bp,ax
1479 jnb .do_read ; Unless there is at least 1 more sector room...
1480 inc edi ; Sector index
1481 inc edx ; Linearly next sector
1482 mov eax,edi
1483 call linsector
1484 ; jc .do_read
1485 cmp edx,eax
1486 je .getseccnt
1487 .do_read:
1488 pop eax ; Linear start sector
1489 pushad
1490 call getlinsec_ext
1491 popad
1492 push bp
1493 shl bp,9
1494 add bx,bp ; Adjust buffer pointer
1495 pop bp
1496 add [si+file_sector],ebp ; Next sector index
1497 sub [si],ebp ; Sectors consumed
1498 jcxz .done
1499 jnz .getfragment
1500 ; Fall through
1501 .done:
1502 cmp dword [si],1 ; Did we run out of file?
1503 ; CF set if [SI] < 1, i.e. == 0
1504 pop edi
1505 pop edx
1506 pop eax
1507 pop ebp
1510 ; -----------------------------------------------------------------------------
1511 ; Common modules
1512 ; -----------------------------------------------------------------------------
1514 %include "getc.inc" ; getc et al
1515 %include "conio.inc" ; Console I/O
1516 %include "plaincon.inc" ; writechr
1517 %include "writestr.inc" ; String output
1518 %include "configinit.inc" ; Initialize configuration
1519 %include "parseconfig.inc" ; High-level config file handling
1520 %include "parsecmd.inc" ; Low-level config file handling
1521 %include "bcopy32.inc" ; 32-bit bcopy
1522 %include "loadhigh.inc" ; Load a file into high memory
1523 %include "font.inc" ; VGA font stuff
1524 %include "graphics.inc" ; VGA graphics
1525 %include "highmem.inc" ; High memory sizing
1526 %include "strcpy.inc" ; strcpy()
1527 %include "strecpy.inc" ; strcpy with end pointer check
1528 %include "cache.inc"
1530 ; -----------------------------------------------------------------------------
1531 ; Begin data section
1532 ; -----------------------------------------------------------------------------
1534 section .data
1535 copyright_str db ' Copyright (C) 1994-', year, ' H. Peter Anvin'
1536 db CR, LF, 0
1537 err_bootfailed db CR, LF, 'Boot failed: please change disks and press '
1538 db 'a key to continue.', CR, LF, 0
1539 config_name db 'extlinux.conf',0 ; Unmangled form
1542 ; Command line options we'd like to take a look at
1544 ; mem= and vga= are handled as normal 32-bit integer values
1545 initrd_cmd db 'initrd='
1546 initrd_cmd_len equ 7
1549 ; Config file keyword table
1551 %include "keywords.inc"
1554 ; Extensions to search for (in *forward* order).
1556 align 4, db 0
1557 exten_table: db '.cbt' ; COMBOOT (specific)
1558 db '.img' ; Disk image
1559 db '.bs', 0 ; Boot sector
1560 db '.com' ; COMBOOT (same as DOS)
1561 db '.c32' ; COM32
1562 exten_table_end:
1563 dd 0, 0 ; Need 8 null bytes here
1566 ; Misc initialized (data) variables
1568 %ifdef debug ; This code for debugging only
1569 debug_magic dw 0D00Dh ; Debug code sentinel
1570 %endif
1572 alignb 4, db 0
1573 BufSafe dw trackbufsize/SECTOR_SIZE ; Clusters we can load into trackbuf
1574 BufSafeBytes dw trackbufsize ; = how many bytes?
1575 %ifndef DEPEND
1576 %if ( trackbufsize % SECTOR_SIZE ) != 0
1577 %error trackbufsize must be a multiple of SECTOR_SIZE
1578 %endif
1579 %endif