Augment tinyjpeg so that we can decode straight into the buffer;
[syslinux.git] / extlinux.asm
blob7ddc278a3910e30afd2ba82f58e128d821766739
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-2006 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 alignb 4
66 vk_append: resb max_cmd_len+1 ; Command line
67 alignb 4
68 vk_end: equ $ ; Should be <= vk_size
69 endstruc
72 ; Segment assignments in the bottom 640K
73 ; Stick to the low 512K in case we're using something like M-systems flash
74 ; which load a driver into low RAM (evil!!)
76 ; 0000h - main code/data segment (and BIOS segment)
78 real_mode_seg equ 4000h
79 cache_seg equ 3000h ; 64K area for metadata cache
80 vk_seg equ 2000h ; Virtual kernels
81 xfer_buf_seg equ 1000h ; Bounce buffer for I/O to high mem
82 comboot_seg equ real_mode_seg ; COMBOOT image loading zone
85 ; File structure. This holds the information for each currently open file.
87 struc open_file_t
88 file_left resd 1 ; Number of sectors left (0 = free)
89 file_sector resd 1 ; Next linear sector to read
90 file_in_sec resd 1 ; Sector where inode lives
91 file_in_off resw 1
92 file_mode resw 1
93 endstruc
95 %ifndef DEPEND
96 %if (open_file_t_size & (open_file_t_size-1))
97 %error "open_file_t is not a power of 2"
98 %endif
99 %endif
101 ; ---------------------------------------------------------------------------
102 ; BEGIN CODE
103 ; ---------------------------------------------------------------------------
106 ; Memory below this point is reserved for the BIOS and the MBR
108 section .earlybss
109 trackbufsize equ 8192
110 trackbuf resb trackbufsize ; Track buffer goes here
111 getcbuf resb trackbufsize
112 ; ends at 4800h
114 section .latebss
115 SuperBlock resb 1024 ; ext2 superblock
116 SuperInfo resq 16 ; DOS superblock expanded
117 ClustSize resd 1 ; Bytes/cluster ("block")
118 SecPerClust resd 1 ; Sectors/cluster
119 ClustMask resd 1 ; Sectors/cluster - 1
120 PtrsPerBlock1 resd 1 ; Pointers/cluster
121 PtrsPerBlock2 resd 1 ; (Pointers/cluster)^2
122 DriveNumber resb 1 ; BIOS drive number
123 ClustShift resb 1 ; Shift count for sectors/cluster
124 ClustByteShift resb 1 ; Shift count for bytes/cluster
126 alignb open_file_t_size
127 Files resb MAX_OPEN*open_file_t_size
130 ; Constants for the xfer_buf_seg
132 ; The xfer_buf_seg is also used to store message file buffers. We
133 ; need two trackbuffers (text and graphics), plus a work buffer
134 ; for the graphics decompressor.
136 xbs_textbuf equ 0 ; Also hard-coded, do not change
137 xbs_vgabuf equ trackbufsize
138 xbs_vgatmpbuf equ 2*trackbufsize
141 section .text
143 ; Some of the things that have to be saved very early are saved
144 ; "close" to the initial stack pointer offset, in order to
145 ; reduce the code size...
147 StackBuf equ $-44-32 ; Start the stack here (grow down - 4K)
148 PartInfo equ StackBuf ; Saved partition table entry
149 FloppyTable equ PartInfo+16 ; Floppy info table (must follow PartInfo)
150 OrigFDCTabPtr equ StackBuf-4 ; The high dword on the stack
153 ; Primary entry point. Tempting as though it may be, we can't put the
154 ; initial "cli" here; the jmp opcode in the first byte is part of the
155 ; "magic number" (using the term very loosely) for the DOS superblock.
157 bootsec equ $
158 jmp short start ; 2 bytes
159 nop ; 1 byte
161 ; "Superblock" follows -- it's in the boot sector, so it's already
162 ; loaded and ready for us
164 bsOemName db 'EXTLINUX' ; The SYS command sets this, so...
166 ; These are the fields we actually care about. We end up expanding them
167 ; all to dword size early in the code, so generate labels for both
168 ; the expanded and unexpanded versions.
170 %macro superb 1
171 bx %+ %1 equ SuperInfo+($-superblock)*8+4
172 bs %+ %1 equ $
173 zb 1
174 %endmacro
175 %macro superw 1
176 bx %+ %1 equ SuperInfo+($-superblock)*8
177 bs %+ %1 equ $
178 zw 1
179 %endmacro
180 %macro superd 1
181 bx %+ %1 equ $ ; no expansion for dwords
182 bs %+ %1 equ $
183 zd 1
184 %endmacro
185 superblock equ $
186 superw BytesPerSec
187 superb SecPerClust
188 superw ResSectors
189 superb FATs
190 superw RootDirEnts
191 superw Sectors
192 superb Media
193 superw FATsecs
194 superw SecPerTrack
195 superw Heads
196 superinfo_size equ ($-superblock)-1 ; How much to expand
197 superd Hidden
198 superd HugeSectors
200 ; This is as far as FAT12/16 and FAT32 are consistent
202 zb 54 ; FAT12/16 need 26 more bytes,
203 ; FAT32 need 54 more bytes
204 superblock_len equ $-superblock
207 ; Note we don't check the constraints above now; we did that at install
208 ; time (we hope!)
210 start:
211 cli ; No interrupts yet, please
212 cld ; Copy upwards
214 ; Set up the stack
216 xor ax,ax
217 mov ss,ax
218 mov sp,StackBuf ; Just below BSS
219 mov es,ax
221 ; DS:SI may contain a partition table entry. Preserve it for us.
223 mov cx,8 ; Save partition info
224 mov di,sp
225 rep movsw
227 mov ds,ax ; Now we can initialize DS...
230 ; Now sautee the BIOS floppy info block to that it will support decent-
231 ; size transfers; the floppy block is 11 bytes and is stored in the
232 ; INT 1Eh vector (brilliant waste of resources, eh?)
234 ; Of course, if BIOSes had been properly programmed, we wouldn't have
235 ; had to waste precious space with this code.
237 mov bx,fdctab
238 lfs si,[bx] ; FS:SI -> original fdctab
239 push fs ; Save on stack in case we need to bail
240 push si
242 ; Save the old fdctab even if hard disk so the stack layout
243 ; is the same. The instructions above do not change the flags
244 mov [DriveNumber],dl ; Save drive number in DL
245 and dl,dl ; If floppy disk (00-7F), assume no
246 ; partition table
247 js harddisk
249 floppy:
250 mov cl,6 ; 12 bytes (CX == 0)
251 ; es:di -> FloppyTable already
252 ; This should be safe to do now, interrupts are off...
253 mov [bx],di ; FloppyTable
254 mov [bx+2],ax ; Segment 0
255 fs rep movsw ; Faster to move words
256 mov cl,[bsSecPerTrack] ; Patch the sector count
257 mov [di-8],cl
258 ; AX == 0 here
259 int 13h ; Some BIOSes need this
261 jmp short not_harddisk
263 ; The drive number and possibly partition information was passed to us
264 ; by the BIOS or previous boot loader (MBR). Current "best practice" is to
265 ; trust that rather than what the superblock contains.
267 ; Would it be better to zero out bsHidden if we don't have a partition table?
269 ; Note: di points to beyond the end of PartInfo
271 harddisk:
272 test byte [di-16],7Fh ; Sanity check: "active flag" should
273 jnz no_partition ; be 00 or 80
274 mov eax,[di-8] ; Partition offset (dword)
275 mov [bsHidden],eax
276 no_partition:
278 ; Get disk drive parameters (don't trust the superblock.) Don't do this for
279 ; floppy drives -- INT 13:08 on floppy drives will (may?) return info about
280 ; what the *drive* supports, not about the *media*. Fortunately floppy disks
281 ; tend to have a fixed, well-defined geometry which is stored in the superblock.
283 ; DL == drive # still
284 mov ah,08h
285 int 13h
286 jc no_driveparm
287 and ah,ah
288 jnz no_driveparm
289 shr dx,8
290 inc dx ; Contains # of heads - 1
291 mov [bsHeads],dx
292 and cx,3fh
293 mov [bsSecPerTrack],cx
294 no_driveparm:
295 not_harddisk:
297 ; Ready to enable interrupts, captain
302 ; Do we have EBIOS (EDD)?
304 eddcheck:
305 mov bx,55AAh
306 mov ah,41h ; EDD existence query
307 mov dl,[DriveNumber]
308 int 13h
309 jc .noedd
310 cmp bx,0AA55h
311 jne .noedd
312 test cl,1 ; Extended disk access functionality set
313 jz .noedd
315 ; We have EDD support...
317 mov byte [getlinsec.jmp+1],(getlinsec_ebios-(getlinsec.jmp+2))
318 .noedd:
321 ; Load the first sector of LDLINUX.SYS; this used to be all proper
322 ; with parsing the superblock and root directory; it doesn't fit
323 ; together with EBIOS support, unfortunately.
325 mov eax,[FirstSector] ; Sector start
326 mov bx,ldlinux_sys ; Where to load it
327 call getonesec
329 ; Some modicum of integrity checking
330 cmp dword [ldlinux_magic+4],LDLINUX_MAGIC^HEXDATE
331 jne kaboom
333 ; Go for it...
334 jmp ldlinux_ent
337 ; getonesec: get one disk sector
339 getonesec:
340 mov bp,1 ; One sector
341 ; Fall through
344 ; getlinsec: load a sequence of BP floppy sector given by the linear sector
345 ; number in EAX into the buffer at ES:BX. We try to optimize
346 ; by loading up to a whole track at a time, but the user
347 ; is responsible for not crossing a 64K boundary.
348 ; (Yes, BP is weird for a count, but it was available...)
350 ; On return, BX points to the first byte after the transferred
351 ; block.
353 ; This routine assumes CS == DS, and trashes most registers.
355 ; Stylistic note: use "xchg" instead of "mov" when the source is a register
356 ; that is dead from that point; this saves space. However, please keep
357 ; the order to dst,src to keep things sane.
359 getlinsec:
360 add eax,[bsHidden] ; Add partition offset
361 xor edx,edx ; Zero-extend LBA (eventually allow 64 bits)
363 .jmp: jmp strict short getlinsec_cbios
366 ; getlinsec_ebios:
368 ; getlinsec implementation for EBIOS (EDD)
370 getlinsec_ebios:
371 .loop:
372 push bp ; Sectors left
373 .retry2:
374 call maxtrans ; Enforce maximum transfer size
375 movzx edi,bp ; Sectors we are about to read
376 mov cx,retry_count
377 .retry:
379 ; Form DAPA on stack
380 push edx
381 push eax
382 push es
383 push bx
384 push di
385 push word 16
386 mov si,sp
387 pushad
388 mov dl,[DriveNumber]
389 push ds
390 push ss
391 pop ds ; DS <- SS
392 mov ah,42h ; Extended Read
393 int 13h
394 pop ds
395 popad
396 lea sp,[si+16] ; Remove DAPA
397 jc .error
398 pop bp
399 add eax,edi ; Advance sector pointer
400 sub bp,di ; Sectors left
401 shl di,SECTOR_SHIFT ; 512-byte sectors
402 add bx,di ; Advance buffer pointer
403 and bp,bp
404 jnz .loop
408 .error:
409 ; Some systems seem to get "stuck" in an error state when
410 ; using EBIOS. Doesn't happen when using CBIOS, which is
411 ; good, since some other systems get timeout failures
412 ; waiting for the floppy disk to spin up.
414 pushad ; Try resetting the device
415 xor ax,ax
416 mov dl,[DriveNumber]
417 int 13h
418 popad
419 loop .retry ; CX-- and jump if not zero
421 ;shr word [MaxTransfer],1 ; Reduce the transfer size
422 ;jnz .retry2
424 ; Total failure. Try falling back to CBIOS.
425 mov byte [getlinsec.jmp+1],(getlinsec_cbios-(getlinsec.jmp+2))
426 ;mov byte [MaxTransfer],63 ; Max possibe CBIOS transfer
428 pop bp
429 ; ... fall through ...
432 ; getlinsec_cbios:
434 ; getlinsec implementation for legacy CBIOS
436 getlinsec_cbios:
437 .loop:
438 push edx
439 push eax
440 push bp
441 push bx
443 movzx esi,word [bsSecPerTrack]
444 movzx edi,word [bsHeads]
446 ; Dividing by sectors to get (track,sector): we may have
447 ; up to 2^18 tracks, so we need to use 32-bit arithmetric.
449 div esi
450 xor cx,cx
451 xchg cx,dx ; CX <- sector index (0-based)
452 ; EDX <- 0
453 ; eax = track #
454 div edi ; Convert track to head/cyl
456 ; We should test this, but it doesn't fit...
457 ; cmp eax,1023
458 ; ja .error
461 ; Now we have AX = cyl, DX = head, CX = sector (0-based),
462 ; BP = sectors to transfer, SI = bsSecPerTrack,
463 ; ES:BX = data target
466 call maxtrans ; Enforce maximum transfer size
468 ; Must not cross track boundaries, so BP <= SI-CX
469 sub si,cx
470 cmp bp,si
471 jna .bp_ok
472 mov bp,si
473 .bp_ok:
475 shl ah,6 ; Because IBM was STOOPID
476 ; and thought 8 bits were enough
477 ; then thought 10 bits were enough...
478 inc cx ; Sector numbers are 1-based, sigh
479 or cl,ah
480 mov ch,al
481 mov dh,dl
482 mov dl,[DriveNumber]
483 xchg ax,bp ; Sector to transfer count
484 mov ah,02h ; Read sectors
485 mov bp,retry_count
486 .retry:
487 pushad
488 int 13h
489 popad
490 jc .error
491 .resume:
492 movzx ecx,al ; ECX <- sectors transferred
493 shl ax,SECTOR_SHIFT ; Convert sectors in AL to bytes in AX
494 pop bx
495 add bx,ax
496 pop bp
497 pop eax
498 pop edx
499 add eax,ecx
500 sub bp,cx
501 jnz .loop
504 .error:
505 dec bp
506 jnz .retry
508 xchg ax,bp ; Sectors transferred <- 0
509 shr word [MaxTransfer],1
510 jnz .resume
511 ; Fall through to disk_error
514 ; kaboom: write a message and bail out.
516 disk_error:
517 kaboom:
518 xor si,si
519 mov ss,si
520 mov sp,StackBuf-4 ; Reset stack
521 mov ds,si ; Reset data segment
522 pop dword [fdctab] ; Restore FDC table
523 .patch: ; When we have full code, intercept here
524 mov si,bailmsg
526 ; Write error message, this assumes screen page 0
527 .loop: lodsb
528 and al,al
529 jz .done
530 mov ah,0Eh ; Write to screen as TTY
531 mov bx,0007h ; Attribute
532 int 10h
533 jmp short .loop
534 .done:
535 cbw ; AH <- 0
536 int 16h ; Wait for keypress
537 int 19h ; And try once more to boot...
538 .norge: jmp short .norge ; If int 19h returned; this is the end
541 ; Truncate BP to MaxTransfer
543 maxtrans:
544 cmp bp,[MaxTransfer]
545 jna .ok
546 mov bp,[MaxTransfer]
547 .ok: ret
550 ; Error message on failure
552 bailmsg: db 'Boot error', 0Dh, 0Ah, 0
554 ; This fails if the boot sector overflows
555 zb 1F8h-($-$$)
557 FirstSector dd 0xDEADBEEF ; Location of sector 1
558 MaxTransfer dw 0x007F ; Max transfer size
559 bootsignature dw 0AA55h
562 ; ===========================================================================
563 ; End of boot sector
564 ; ===========================================================================
565 ; Start of LDLINUX.SYS
566 ; ===========================================================================
568 ldlinux_sys:
570 syslinux_banner db 0Dh, 0Ah
571 db 'EXTLINUX '
572 db version_str, ' ', date, ' ', 0
573 db 0Dh, 0Ah, 1Ah ; EOF if we "type" this in DOS
575 align 8, db 0
576 ldlinux_magic dd LDLINUX_MAGIC
577 dd LDLINUX_MAGIC^HEXDATE
580 ; This area is patched by the installer. It is found by looking for
581 ; LDLINUX_MAGIC, plus 8 bytes.
583 patch_area:
584 LDLDwords dw 0 ; Total dwords starting at ldlinux_sys
585 LDLSectors dw 0 ; Number of sectors - (bootsec+this sec)
586 CheckSum dd 0 ; Checksum starting at ldlinux_sys
587 ; value = LDLINUX_MAGIC - [sum of dwords]
588 CurrentDir dd 2 ; "Current" directory inode number
590 ; Space for up to 64 sectors, the theoretical maximum
591 SectorPtrs times 64 dd 0
593 ldlinux_ent:
595 ; Note that some BIOSes are buggy and run the boot sector at 07C0:0000
596 ; instead of 0000:7C00 and the like. We don't want to add anything
597 ; more to the boot sector, so it is written to not assume a fixed
598 ; value in CS, but we don't want to deal with that anymore from now
599 ; on.
601 jmp 0:.next
602 .next:
605 ; Tell the user we got this far
607 mov si,syslinux_banner
608 call writestr
611 ; Tell the user if we're using EBIOS or CBIOS
613 print_bios:
614 mov si,cbios_name
615 cmp byte [getlinsec.jmp+1],(getlinsec_ebios-(getlinsec.jmp+2))
616 jne .cbios
617 mov si,ebios_name
618 .cbios:
619 mov [BIOSName],si
620 call writestr
622 section .bss
623 %define HAVE_BIOSNAME 1
624 BIOSName resw 1
626 section .text
628 ; Now we read the rest of LDLINUX.SYS. Don't bother loading the first
629 ; sector again, though.
631 load_rest:
632 mov si,SectorPtrs
633 mov bx,7C00h+2*SECTOR_SIZE ; Where we start loading
634 mov cx,[LDLSectors]
636 .get_chunk:
637 jcxz .done
638 xor bp,bp
639 lodsd ; First sector of this chunk
641 mov edx,eax
643 .make_chunk:
644 inc bp
645 dec cx
646 jz .chunk_ready
647 inc edx ; Next linear sector
648 cmp [si],edx ; Does it match
649 jnz .chunk_ready ; If not, this is it
650 add si,4 ; If so, add sector to chunk
651 jmp short .make_chunk
653 .chunk_ready:
654 call getlinsecsr
655 shl bp,SECTOR_SHIFT
656 add bx,bp
657 jmp .get_chunk
659 .done:
662 ; All loaded up, verify that we got what we needed.
663 ; Note: the checksum field is embedded in the checksum region, so
664 ; by the time we get to the end it should all cancel out.
666 verify_checksum:
667 mov si,ldlinux_sys
668 mov cx,[LDLDwords]
669 mov edx,-LDLINUX_MAGIC
670 .checksum:
671 lodsd
672 add edx,eax
673 loop .checksum
675 and edx,edx ; Should be zero
676 jz all_read ; We're cool, go for it!
679 ; Uh-oh, something went bad...
681 mov si,checksumerr_msg
682 call writestr
683 jmp kaboom
686 ; -----------------------------------------------------------------------------
687 ; Subroutines that have to be in the first sector
688 ; -----------------------------------------------------------------------------
692 ; writestr: write a null-terminated string to the console
693 ; This assumes we're on page 0. This is only used for early
694 ; messages, so it should be OK.
696 writestr:
697 .loop: lodsb
698 and al,al
699 jz .return
700 mov ah,0Eh ; Write to screen as TTY
701 mov bx,0007h ; Attribute
702 int 10h
703 jmp short .loop
704 .return: ret
707 ; getlinsecsr: save registers, call getlinsec, restore registers
709 getlinsecsr: pushad
710 call getlinsec
711 popad
715 ; Checksum error message
717 checksumerr_msg db ' Load error - ', 0 ; Boot failed appended
720 ; BIOS type string
722 cbios_name db 'CBIOS', 0
723 ebios_name db 'EBIOS', 0
726 ; Debug routine
728 %ifdef debug
729 safedumpregs:
730 cmp word [Debug_Magic],0D00Dh
731 jnz nc_return
732 jmp dumpregs
733 %endif
735 rl_checkpt equ $ ; Must be <= 8000h
737 rl_checkpt_off equ ($-$$)
738 %ifndef DEPEND
739 %if rl_checkpt_off > 400h
740 %error "Sector 1 overflow"
741 %endif
742 %endif
744 ; ----------------------------------------------------------------------------
745 ; End of code and data that have to be in the first sector
746 ; ----------------------------------------------------------------------------
748 all_read:
750 ; Let the user (and programmer!) know we got this far. This used to be
751 ; in Sector 1, but makes a lot more sense here.
753 mov si,copyright_str
754 call writestr
757 ; Insane hack to expand the DOS superblock to dwords
759 expand_super:
760 xor eax,eax
761 mov si,superblock
762 mov di,SuperInfo
763 mov cx,superinfo_size
764 .loop:
765 lodsw
766 dec si
767 stosd ; Store expanded word
768 xor ah,ah
769 stosd ; Store expanded byte
770 loop .loop
773 ; Load the real (ext2) superblock; 1024 bytes long at offset 1024
775 mov bx,SuperBlock
776 mov eax,1024 >> SECTOR_SHIFT
777 mov bp,ax
778 call getlinsec
781 ; Compute some values...
783 xor edx,edx
784 inc edx
786 ; s_log_block_size = log2(blocksize) - 10
787 mov cl,[SuperBlock+s_log_block_size]
788 add cl,10
789 mov [ClustByteShift],cl
790 mov eax,edx
791 shl eax,cl
792 mov [ClustSize],eax
794 sub cl,SECTOR_SHIFT
795 mov [ClustShift],cl
796 shr eax,SECTOR_SHIFT
797 mov [SecPerClust],eax
798 dec eax
799 mov [ClustMask],eax
801 add cl,SECTOR_SHIFT-2 ; 4 bytes/pointer
802 shl edx,cl
803 mov [PtrsPerBlock1],edx
804 shl edx,cl
805 mov [PtrsPerBlock2],edx
808 ; Common initialization code
810 %include "init.inc"
811 %include "cpuinit.inc"
814 ; Initialize the metadata cache
816 call initcache
819 ; Now, everything is "up and running"... patch kaboom for more
820 ; verbosity and using the full screen system
822 ; E9 = JMP NEAR
823 mov dword [kaboom.patch],0e9h+((kaboom2-(kaboom.patch+3)) << 8)
826 ; Now we're all set to start with our *real* business. First load the
827 ; configuration file (if any) and parse it.
829 ; In previous versions I avoided using 32-bit registers because of a
830 ; rumour some BIOSes clobbered the upper half of 32-bit registers at
831 ; random. I figure, though, that if there are any of those still left
832 ; they probably won't be trying to install Linux on them...
834 ; The code is still ripe with 16-bitisms, though. Not worth the hassle
835 ; to take'm out. In fact, we may want to put them back if we're going
836 ; to boot ELKS at some point.
840 ; Load configuration file
842 load_config:
843 mov di,ConfigName
844 call open
845 jz no_config_file
848 ; Now we have the config file open. Parse the config file and
849 ; run the user interface.
851 %include "ui.inc"
854 ; Linux kernel loading code is common.
856 %include "runkernel.inc"
859 ; COMBOOT-loading code
861 %include "comboot.inc"
862 %include "com32.inc"
863 %include "cmdline.inc"
866 ; Boot sector loading code
868 %include "bootsect.inc"
872 ; getlinsec_ext: same as getlinsec, except load any sector from the zero
873 ; block as all zeros; use to load any data derived
874 ; from an ext2 block pointer, i.e. anything *except the
875 ; superblock.*
877 getonesec_ext:
878 mov bp,1
880 getlinsec_ext:
881 cmp eax,[SecPerClust]
882 jae getlinsec ; Nothing fancy
884 ; If we get here, at least part of what we want is in the
885 ; zero block. Zero one sector at a time and loop.
886 push eax
887 push cx
888 xchg di,bx
889 xor eax,eax
890 mov cx,SECTOR_SIZE >> 2
891 rep stosd
892 xchg di,bx
893 pop cx
894 pop eax
895 inc eax
896 dec bp
897 jnz getlinsec_ext
901 ; Abort loading code
903 %include "abort.inc"
906 ; allocate_file: Allocate a file structure
908 ; If successful:
909 ; ZF set
910 ; BX = file pointer
911 ; In unsuccessful:
912 ; ZF clear
914 allocate_file:
915 TRACER 'a'
916 push cx
917 mov bx,Files
918 mov cx,MAX_OPEN
919 .check: cmp dword [bx], byte 0
920 je .found
921 add bx,open_file_t_size ; ZF = 0
922 loop .check
923 ; ZF = 0 if we fell out of the loop
924 .found: pop cx
927 ; open_inode:
928 ; Open a file indicated by an inode number in EAX
930 ; NOTE: This file considers finding a zero-length file an
931 ; error. This is so we don't have to deal with that special
932 ; case elsewhere in the program (most loops have the test
933 ; at the end).
935 ; If successful:
936 ; ZF clear
937 ; SI = file pointer
938 ; DX:AX = EAX = file length in bytes
939 ; ThisInode = the first 128 bytes of the inode
940 ; If unsuccessful
941 ; ZF set
943 ; Assumes CS == DS == ES.
945 open_inode.allocate_failure:
946 xor eax,eax
947 pop bx
948 pop di
951 open_inode:
952 push di
953 push bx
954 call allocate_file
955 jnz .allocate_failure
957 push cx
958 push gs
959 ; First, get the appropriate inode group and index
960 dec eax ; There is no inode 0
961 xor edx,edx
962 mov [bx+file_sector],edx
963 div dword [SuperBlock+s_inodes_per_group]
964 ; EAX = inode group; EDX = inode within group
965 push edx
967 ; Now, we need the block group descriptor.
968 ; To get that, we first need the relevant descriptor block.
970 shl eax, ext2_group_desc_lg2size ; Get byte offset in desc table
971 xor edx,edx
972 div dword [ClustSize]
973 ; eax = block #, edx = offset in block
974 add eax,dword [SuperBlock+s_first_data_block]
975 inc eax ; s_first_data_block+1
976 mov cl,[ClustShift]
977 shl eax,cl
978 push edx
979 shr edx,SECTOR_SHIFT
980 add eax,edx
981 pop edx
982 and dx,SECTOR_SIZE-1
983 call getcachesector ; Get the group descriptor
984 add si,dx
985 mov esi,[gs:si+bg_inode_table] ; Get inode table block #
986 pop eax ; Get inode within group
987 movzx edx, word [SuperBlock+s_inode_size]
988 mul edx
989 ; edx:eax = byte offset in inode table
990 div dword [ClustSize]
991 ; eax = block # versus inode table, edx = offset in block
992 add eax,esi
993 shl eax,cl ; Turn into sector
994 push dx
995 shr edx,SECTOR_SHIFT
996 add eax,edx
997 mov [bx+file_in_sec],eax
998 pop dx
999 and dx,SECTOR_SIZE-1
1000 mov [bx+file_in_off],dx
1002 call getcachesector
1003 add si,dx
1004 mov cx,EXT2_GOOD_OLD_INODE_SIZE >> 2
1005 mov di,ThisInode
1006 gs rep movsd
1008 mov ax,[ThisInode+i_mode]
1009 mov [bx+file_mode],ax
1010 mov eax,[ThisInode+i_size]
1011 push eax
1012 add eax,SECTOR_SIZE-1
1013 shr eax,SECTOR_SHIFT
1014 mov [bx+file_left],eax
1015 pop eax
1016 mov si,bx
1017 mov edx,eax
1018 shr edx,16 ; 16-bitism, sigh
1019 and eax,eax ; ZF clear unless zero-length file
1020 pop gs
1021 pop cx
1022 pop bx
1023 pop di
1026 section .latebss
1027 alignb 4
1028 ThisInode resb EXT2_GOOD_OLD_INODE_SIZE ; The most recently opened inode
1030 section .text
1032 ; close:
1033 ; Deallocates a file structure (pointer in SI)
1034 ; Assumes CS == DS.
1036 close:
1037 mov dword [si],0 ; First dword == file_left
1041 ; searchdir:
1042 ; Search the root directory for a pre-mangled filename in DS:DI.
1044 ; NOTE: This file considers finding a zero-length file an
1045 ; error. This is so we don't have to deal with that special
1046 ; case elsewhere in the program (most loops have the test
1047 ; at the end).
1049 ; If successful:
1050 ; ZF clear
1051 ; SI = file pointer
1052 ; DX:AX = EAX = file length in bytes
1053 ; If unsuccessful
1054 ; ZF set
1056 ; Assumes CS == DS == ES; *** IS THIS CORRECT ***?
1058 searchdir:
1059 push bx
1060 push cx
1061 push bp
1062 mov byte [SymlinkCtr],MAX_SYMLINKS
1064 mov eax,[CurrentDir]
1065 .begin_path:
1066 .leadingslash:
1067 cmp byte [di],'/' ; Absolute filename?
1068 jne .gotdir
1069 mov eax,EXT2_ROOT_INO
1070 inc di ; Skip slash
1071 jmp .leadingslash
1072 .gotdir:
1074 ; At this point, EAX contains the directory inode,
1075 ; and DS:DI contains a pathname tail.
1076 .open:
1077 push eax ; Save directory inode
1079 call open_inode
1080 jz .done ; If error, done
1082 mov cx,[si+file_mode]
1083 shr cx,S_IFSHIFT ; Get file type
1085 cmp cx,T_IFDIR
1086 je .directory
1088 add sp,4 ; Drop directory inode
1090 cmp cx,T_IFREG
1091 je .file
1092 cmp cx,T_IFLNK
1093 je .symlink
1095 ; Otherwise, something bad...
1096 .err:
1097 call close
1098 .err_noclose:
1099 xor eax,eax
1100 xor si,si
1101 cwd ; DX <- 0
1103 .done:
1104 and eax,eax ; Set/clear ZF
1105 pop bp
1106 pop cx
1107 pop bx
1111 ; It's a file.
1113 .file:
1114 cmp byte [di],0 ; End of path?
1115 je .done ; If so, done
1116 jmp .err ; Otherwise, error
1119 ; It's a directory.
1121 .directory:
1122 pop dword [ThisDir] ; Remember what directory we're searching
1124 cmp byte [di],0 ; More path?
1125 je .err ; If not, bad
1127 .skipslash: ; Skip redundant slashes
1128 cmp byte [di],'/'
1129 jne .readdir
1130 inc di
1131 jmp .skipslash
1133 .readdir:
1134 mov bx,trackbuf
1135 push bx
1136 mov cx,[SecPerClust]
1137 call getfssec
1138 pop bx
1139 pushf ; Save EOF flag
1140 push si ; Save filesystem pointer
1141 .getent:
1142 cmp dword [bx+d_inode],0
1143 je .endblock
1145 push di
1146 movzx cx,byte [bx+d_name_len]
1147 lea si,[bx+d_name]
1148 repe cmpsb
1149 je .maybe
1150 .nope:
1151 pop di
1153 add bx,[bx+d_rec_len]
1154 jmp .getent
1156 .endblock:
1157 pop si
1158 popf
1159 jnc .readdir ; There is more
1160 jmp .err ; Otherwise badness...
1162 .maybe:
1163 mov eax,[bx+d_inode]
1165 ; Does this match the end of the requested filename?
1166 cmp byte [di],0
1167 je .finish
1168 cmp byte [di],'/'
1169 jne .nope
1171 ; We found something; now we need to open the file
1172 .finish:
1173 pop bx ; Adjust stack (di)
1174 pop si
1175 call close ; Close directory
1176 pop bx ; Adjust stack (flags)
1177 jmp .open
1180 ; It's a symlink. We have to determine if it's a fast symlink
1181 ; (data stored in the inode) or not (data stored as a regular
1182 ; file.) Either which way, we start from the directory
1183 ; which we just visited if relative, or from the root directory
1184 ; if absolute, and append any remaining part of the path.
1186 .symlink:
1187 dec byte [SymlinkCtr]
1188 jz .err ; Too many symlink references
1190 cmp eax,SYMLINK_SECTORS*SECTOR_SIZE
1191 jae .err ; Symlink too long
1193 ; Computation for fast symlink, as defined by ext2/3 spec
1194 xor ecx,ecx
1195 cmp [ThisInode+i_file_acl],ecx
1196 setne cl ; ECX <- i_file_acl ? 1 : 0
1197 cmp [ThisInode+i_blocks],ecx
1198 jne .slow_symlink
1200 ; It's a fast symlink
1201 .fast_symlink:
1202 call close ; We've got all we need
1203 mov si,ThisInode+i_block
1205 push di
1206 mov di,SymlinkTmpBuf
1207 mov ecx,eax
1208 rep movsb
1209 pop si
1211 .symlink_finish:
1212 cmp byte [si],0
1213 je .no_slash
1214 mov al,'/'
1215 stosb
1216 .no_slash:
1217 mov bp,SymlinkTmpBufEnd
1218 call strecpy
1219 jc .err_noclose ; Buffer overflow
1221 ; Now copy it to the "real" buffer; we need to have
1222 ; two buffers so we avoid overwriting the tail on the
1223 ; next copy
1224 mov si,SymlinkTmpBuf
1225 mov di,SymlinkBuf
1226 push di
1227 call strcpy
1228 pop di
1229 mov eax,[ThisDir] ; Resume searching previous directory
1230 jmp .begin_path
1232 .slow_symlink:
1233 mov bx,SymlinkTmpBuf
1234 mov cx,SYMLINK_SECTORS
1235 call getfssec
1236 ; The EOF closed the file
1238 mov si,di ; SI = filename tail
1239 mov di,SymlinkTmpBuf
1240 add di,ax ; AX = file length
1241 jmp .symlink_finish
1244 section .bss
1245 alignb 4
1246 SymlinkBuf resb SYMLINK_SECTORS*SECTOR_SIZE+64
1247 SymlinkTmpBuf equ trackbuf
1248 SymlinkTmpBufEnd equ trackbuf+SYMLINK_SECTORS*SECTOR_SIZE+64
1249 ThisDir resd 1
1250 SymlinkCtr resb 1
1252 section .text
1254 ; mangle_name: Mangle a filename pointed to by DS:SI into a buffer pointed
1255 ; to by ES:DI; ends on encountering any whitespace.
1257 ; This verifies that a filename is < FILENAME_MAX characters,
1258 ; doesn't contain whitespace, zero-pads the output buffer,
1259 ; and removes redundant slashes,
1260 ; so "repe cmpsb" can do a compare, and the
1261 ; path-searching routine gets a bit of an easier job.
1263 ; FIX: we may want to support \-escapes here (and this would
1264 ; be the place.)
1266 mangle_name:
1267 push bx
1268 xor ax,ax
1269 mov cx,FILENAME_MAX-1
1270 mov bx,di
1272 .mn_loop:
1273 lodsb
1274 cmp al,' ' ; If control or space, end
1275 jna .mn_end
1276 cmp al,ah ; Repeated slash?
1277 je .mn_skip
1278 xor ah,ah
1279 cmp al,'/'
1280 jne .mn_ok
1281 mov ah,al
1282 .mn_ok stosb
1283 .mn_skip: loop .mn_loop
1284 .mn_end:
1285 cmp bx,di ; At the beginning of the buffer?
1286 jbe .mn_zero
1287 cmp byte [di-1],'/' ; Terminal slash?
1288 jne .mn_zero
1289 .mn_kill: dec di ; If so, remove it
1290 inc cx
1291 jmp short .mn_end
1292 .mn_zero:
1293 inc cx ; At least one null byte
1294 xor ax,ax ; Zero-fill name
1295 rep stosb
1296 pop bx
1297 ret ; Done
1300 ; unmangle_name: Does the opposite of mangle_name; converts a DOS-mangled
1301 ; filename to the conventional representation. This is needed
1302 ; for the BOOT_IMAGE= parameter for the kernel.
1303 ; NOTE: A 13-byte buffer is mandatory, even if the string is
1304 ; known to be shorter.
1306 ; DS:SI -> input mangled file name
1307 ; ES:DI -> output buffer
1309 ; On return, DI points to the first byte after the output name,
1310 ; which is set to a null byte.
1312 unmangle_name: call strcpy
1313 dec di ; Point to final null byte
1318 ; kaboom2: once everything is loaded, replace the part of kaboom
1319 ; starting with "kaboom.patch" with this part
1321 kaboom2:
1322 mov si,err_bootfailed
1323 call cwritestr
1324 call getchar
1325 call vgaclearmode
1326 int 19h ; And try once more to boot...
1327 .norge: jmp short .norge ; If int 19h returned; this is the end
1331 ; linsector: Convert a linear sector index in a file to a linear sector number
1332 ; EAX -> linear sector number
1333 ; DS:SI -> open_file_t
1335 ; Returns next sector number in EAX; CF on EOF (not an error!)
1337 linsector:
1338 push gs
1339 push ebx
1340 push esi
1341 push edi
1342 push ecx
1343 push edx
1344 push ebp
1346 push eax ; Save sector index
1347 mov cl,[ClustShift]
1348 shr eax,cl ; Convert to block number
1349 push eax
1350 mov eax,[si+file_in_sec]
1351 mov bx,si
1352 call getcachesector ; Get inode
1353 add si,[bx+file_in_off] ; Get *our* inode
1354 pop eax
1355 lea ebx,[i_block+4*eax]
1356 cmp eax,EXT2_NDIR_BLOCKS
1357 jb .direct
1358 mov ebx,i_block+4*EXT2_IND_BLOCK
1359 sub eax,EXT2_NDIR_BLOCKS
1360 mov ebp,[PtrsPerBlock1]
1361 cmp eax,ebp
1362 jb .ind1
1363 mov ebx,i_block+4*EXT2_DIND_BLOCK
1364 sub eax,ebp
1365 mov ebp,[PtrsPerBlock2]
1366 cmp eax,ebp
1367 jb .ind2
1368 mov ebx,i_block+4*EXT2_TIND_BLOCK
1369 sub eax,ebp
1371 .ind3:
1372 ; Triple indirect; eax contains the block no
1373 ; with respect to the start of the tind area;
1374 ; ebx contains the pointer to the tind block.
1375 xor edx,edx
1376 div dword [PtrsPerBlock2]
1377 ; EAX = which dind block, EDX = pointer within dind block
1378 push ax
1379 shr eax,SECTOR_SHIFT-2
1380 mov ebp,[gs:si+bx]
1381 shl ebp,cl
1382 add eax,ebp
1383 call getcachesector
1384 pop bx
1385 and bx,(SECTOR_SIZE >> 2)-1
1386 shl bx,2
1387 mov eax,edx ; The ind2 code wants the remainder...
1389 .ind2:
1390 ; Double indirect; eax contains the block no
1391 ; with respect to the start of the dind area;
1392 ; ebx contains the pointer to the dind block.
1393 xor edx,edx
1394 div dword [PtrsPerBlock1]
1395 ; EAX = which ind block, EDX = pointer within ind block
1396 push ax
1397 shr eax,SECTOR_SHIFT-2
1398 mov ebp,[gs:si+bx]
1399 shl ebp,cl
1400 add eax,ebp
1401 call getcachesector
1402 pop bx
1403 and bx,(SECTOR_SIZE >> 2)-1
1404 shl bx,2
1405 mov eax,edx ; The int1 code wants the remainder...
1407 .ind1:
1408 ; Single indirect; eax contains the block no
1409 ; with respect to the start of the ind area;
1410 ; ebx contains the pointer to the ind block.
1411 push ax
1412 shr eax,SECTOR_SHIFT-2
1413 mov ebp,[gs:si+bx]
1414 shl ebp,cl
1415 add eax,ebp
1416 call getcachesector
1417 pop bx
1418 and bx,(SECTOR_SIZE >> 2)-1
1419 shl bx,2
1421 .direct:
1422 mov ebx,[gs:bx+si] ; Get the pointer
1424 pop eax ; Get the sector index again
1425 shl ebx,cl ; Convert block number to sector
1426 and eax,[ClustMask] ; Add offset within block
1427 add eax,ebx
1429 pop ebp
1430 pop edx
1431 pop ecx
1432 pop edi
1433 pop esi
1434 pop ebx
1435 pop gs
1439 ; getfssec: Get multiple sectors from a file
1441 ; Same as above, except SI is a pointer to a open_file_t
1443 ; ES:BX -> Buffer
1444 ; DS:SI -> Pointer to open_file_t
1445 ; CX -> Sector count (0FFFFh = until end of file)
1446 ; Must not exceed the ES segment
1447 ; Returns CF=1 on EOF (not necessarily error)
1448 ; All arguments are advanced to reflect data read.
1450 getfssec:
1451 push ebp
1452 push eax
1453 push edx
1454 push edi
1456 movzx ecx,cx
1457 cmp ecx,[si] ; Number of sectors left
1458 jbe .lenok
1459 mov cx,[si]
1460 .lenok:
1461 .getfragment:
1462 mov eax,[si+file_sector] ; Current start index
1463 mov edi,eax
1464 call linsector
1465 push eax ; Fragment start sector
1466 mov edx,eax
1467 xor ebp,ebp ; Fragment sector count
1468 .getseccnt:
1469 inc bp
1470 dec cx
1471 jz .do_read
1472 xor eax,eax
1473 mov ax,es
1474 shl ax,4
1475 add ax,bx ; Now DI = how far into 64K block we are
1476 not ax ; Bytes left in 64K block
1477 inc eax
1478 shr eax,SECTOR_SHIFT ; Sectors left in 64K block
1479 cmp bp,ax
1480 jnb .do_read ; Unless there is at least 1 more sector room...
1481 inc edi ; Sector index
1482 inc edx ; Linearly next sector
1483 mov eax,edi
1484 call linsector
1485 ; jc .do_read
1486 cmp edx,eax
1487 je .getseccnt
1488 .do_read:
1489 pop eax ; Linear start sector
1490 pushad
1491 call getlinsec_ext
1492 popad
1493 push bp
1494 shl bp,9
1495 add bx,bp ; Adjust buffer pointer
1496 pop bp
1497 add [si+file_sector],ebp ; Next sector index
1498 sub [si],ebp ; Sectors consumed
1499 jcxz .done
1500 jnz .getfragment
1501 ; Fall through
1502 .done:
1503 cmp dword [si],1 ; Did we run out of file?
1504 ; CF set if [SI] < 1, i.e. == 0
1505 pop edi
1506 pop edx
1507 pop eax
1508 pop ebp
1511 ; -----------------------------------------------------------------------------
1512 ; Common modules
1513 ; -----------------------------------------------------------------------------
1515 %include "getc.inc" ; getc et al
1516 %include "conio.inc" ; Console I/O
1517 %include "plaincon.inc" ; writechr
1518 %include "writestr.inc" ; String output
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 boot_prompt db 'boot: ', 0
1538 wipe_char db BS, ' ', BS, 0
1539 err_notfound db 'Could not find kernel image: ',0
1540 err_notkernel db CR, LF, 'Invalid or corrupt kernel image.', CR, LF, 0
1541 err_noram db 'It appears your computer has less than '
1542 asciidec dosram_k
1543 db 'K of low ("DOS")'
1544 db CR, LF
1545 db 'RAM. Linux needs at least this amount to boot. If you get'
1546 db CR, LF
1547 db 'this message in error, hold down the Ctrl key while'
1548 db CR, LF
1549 db 'booting, and I will take your word for it.', CR, LF, 0
1550 err_badcfg db 'Unknown keyword in extlinux.conf.', CR, LF, 0
1551 err_noparm db 'Missing parameter in extlinux.conf.', CR, LF, 0
1552 err_noinitrd db CR, LF, 'Could not find ramdisk image: ', 0
1553 err_nohighmem db 'Not enough memory to load specified kernel.', CR, LF, 0
1554 err_highload db CR, LF, 'Kernel transfer failure.', CR, LF, 0
1555 err_oldkernel db 'Cannot load a ramdisk with an old kernel image.'
1556 db CR, LF, 0
1557 err_notdos db ': attempted DOS system call', CR, LF, 0
1558 err_comlarge db 'COMBOOT image too large.', CR, LF, 0
1559 err_bssimage db 'BSS images not supported.', CR, LF, 0
1560 err_a20 db CR, LF, 'A20 gate not responding!', CR, LF, 0
1561 err_bootfailed db CR, LF, 'Boot failed: please change disks and press '
1562 db 'a key to continue.', CR, LF, 0
1563 ready_msg db 'Ready.', CR, LF, 0
1564 crlfloading_msg db CR, LF
1565 loading_msg db 'Loading ', 0
1566 dotdot_msg db '.'
1567 dot_msg db '.', 0
1568 aborted_msg db ' aborted.' ; Fall through to crlf_msg!
1569 crlf_msg db CR, LF
1570 null_msg db 0
1571 crff_msg db CR, FF, 0
1572 ConfigName db 'extlinux.conf',0 ; Unmangled form
1575 ; Command line options we'd like to take a look at
1577 ; mem= and vga= are handled as normal 32-bit integer values
1578 initrd_cmd db 'initrd='
1579 initrd_cmd_len equ 7
1582 ; Config file keyword table
1584 %include "keywords.inc"
1587 ; Extensions to search for (in *forward* order).
1589 align 4, db 0
1590 exten_table: db '.cbt' ; COMBOOT (specific)
1591 db '.img' ; Disk image
1592 db '.bs', 0 ; Boot sector
1593 db '.com' ; COMBOOT (same as DOS)
1594 db '.c32' ; COM32
1595 exten_table_end:
1596 dd 0, 0 ; Need 8 null bytes here
1599 ; Misc initialized (data) variables
1601 %ifdef debug ; This code for debugging only
1602 debug_magic dw 0D00Dh ; Debug code sentinel
1603 %endif
1605 alignb 4, db 0
1606 BufSafe dw trackbufsize/SECTOR_SIZE ; Clusters we can load into trackbuf
1607 BufSafeSec dw trackbufsize/SECTOR_SIZE ; = how many sectors?
1608 BufSafeBytes dw trackbufsize ; = how many bytes?
1609 EndOfGetCBuf dw getcbuf+trackbufsize ; = getcbuf+BufSafeBytes
1610 %ifndef DEPEND
1611 %if ( trackbufsize % SECTOR_SIZE ) != 0
1612 %error trackbufsize must be a multiple of SECTOR_SIZE
1613 %endif
1614 %endif