Home | History | Annotate | Download | only in core
      1 ; -*- fundamental -*- (asm-mode sucks)
      2 ; ****************************************************************************
      3 ;
      4 ;  isolinux.asm
      5 ;
      6 ;  A program to boot Linux kernels off a CD-ROM using the El Torito
      7 ;  boot standard in "no emulation" mode, making the entire filesystem
      8 ;  available.  It is based on the SYSLINUX boot loader for MS-DOS
      9 ;  floppies.
     10 ;
     11 ;   Copyright 1994-2009 H. Peter Anvin - All Rights Reserved
     12 ;   Copyright 2009 Intel Corporation; author: H. Peter Anvin
     13 ;
     14 ;  This program is free software; you can redistribute it and/or modify
     15 ;  it under the terms of the GNU General Public License as published by
     16 ;  the Free Software Foundation, Inc., 53 Temple Place Ste 330,
     17 ;  Boston MA 02111-1307, USA; either version 2 of the License, or
     18 ;  (at your option) any later version; incorporated herein by reference.
     19 ;
     20 ; ****************************************************************************
     21 
     22 %define IS_ISOLINUX 1
     23 %include "head.inc"
     24 
     25 ;
     26 ; Some semi-configurable constants... change on your own risk.
     27 ;
     28 my_id		equ isolinux_id
     29 NULLFILE	equ 0			; Zero byte == null file name
     30 NULLOFFSET	equ 0			; Position in which to look
     31 retry_count	equ 6			; How patient are we with the BIOS?
     32 %assign HIGHMEM_SLOP 128*1024		; Avoid this much memory near the top
     33 SECTOR_SHIFT	equ 11			; 2048 bytes/sector (El Torito requirement)
     34 SECTOR_SIZE	equ (1 << SECTOR_SHIFT)
     35 
     36 ROOT_DIR_WORD	equ 0x002F
     37 
     38 ; ---------------------------------------------------------------------------
     39 ;   BEGIN CODE
     40 ; ---------------------------------------------------------------------------
     41 
     42 ;
     43 ; Memory below this point is reserved for the BIOS and the MBR
     44 ;
     45 		section .earlybss
     46 		global trackbuf
     47 trackbufsize	equ 8192
     48 trackbuf	resb trackbufsize	; Track buffer goes here
     49 ;		ends at 2800h
     50 
     51 		; Some of these are touched before the whole image
     52 		; is loaded.  DO NOT move this to .bss16/.uibss.
     53 		section .earlybss
     54 		global BIOSName
     55 		alignb 4
     56 FirstSecSum	resd 1			; Checksum of bytes 64-2048
     57 ImageDwords	resd 1			; isolinux.bin size, dwords
     58 InitStack	resd 1			; Initial stack pointer (SS:SP)
     59 DiskSys		resw 1			; Last INT 13h call
     60 ImageSectors	resw 1			; isolinux.bin size, sectors
     61 ; These following two are accessed as a single dword...
     62 GetlinsecPtr	resw 1			; The sector-read pointer
     63 BIOSName	resw 1			; Display string for BIOS type
     64 %define HAVE_BIOSNAME 1
     65 		global BIOSType
     66 BIOSType	resw 1
     67 DiskError	resb 1			; Error code for disk I/O
     68 		global DriveNumber
     69 DriveNumber	resb 1			; CD-ROM BIOS drive number
     70 ISOFlags	resb 1			; Flags for ISO directory search
     71 RetryCount      resb 1			; Used for disk access retries
     72 
     73 		alignb 8
     74 		global Hidden
     75 Hidden		resq 1			; Used in hybrid mode
     76 bsSecPerTrack	resw 1			; Used in hybrid mode
     77 bsHeads		resw 1			; Used in hybrid mode
     78 
     79 
     80 ;
     81 ; El Torito spec packet
     82 ;
     83 
     84 		alignb 8
     85 _spec_start	equ $
     86 		global spec_packet
     87 spec_packet:	resb 1				; Size of packet
     88 sp_media:	resb 1				; Media type
     89 sp_drive:	resb 1				; Drive number
     90 sp_controller:	resb 1				; Controller index
     91 sp_lba:		resd 1				; LBA for emulated disk image
     92 sp_devspec:	resw 1				; IDE/SCSI information
     93 sp_buffer:	resw 1				; User-provided buffer
     94 sp_loadseg:	resw 1				; Load segment
     95 sp_sectors:	resw 1				; Sector count
     96 sp_chs:		resb 3				; Simulated CHS geometry
     97 sp_dummy:	resb 1				; Scratch, safe to overwrite
     98 
     99 ;
    100 ; EBIOS drive parameter packet
    101 ;
    102 		alignb 8
    103 drive_params:	resw 1				; Buffer size
    104 dp_flags:	resw 1				; Information flags
    105 dp_cyl:		resd 1				; Physical cylinders
    106 dp_head:	resd 1				; Physical heads
    107 dp_sec:		resd 1				; Physical sectors/track
    108 dp_totalsec:	resd 2				; Total sectors
    109 dp_secsize:	resw 1				; Bytes per sector
    110 dp_dpte:	resd 1				; Device Parameter Table
    111 dp_dpi_key:	resw 1				; 0BEDDh if rest valid
    112 dp_dpi_len:	resb 1				; DPI len
    113 		resb 1
    114 		resw 1
    115 dp_bus:		resb 4				; Host bus type
    116 dp_interface:	resb 8				; Interface type
    117 db_i_path:	resd 2				; Interface path
    118 db_d_path:	resd 2				; Device path
    119 		resb 1
    120 db_dpi_csum:	resb 1				; Checksum for DPI info
    121 
    122 ;
    123 ; EBIOS disk address packet
    124 ;
    125 		alignb 8
    126 dapa:		resw 1				; Packet size
    127 .count:		resw 1				; Block count
    128 .off:		resw 1				; Offset of buffer
    129 .seg:		resw 1				; Segment of buffer
    130 .lba:		resd 2				; LBA (LSW, MSW)
    131 
    132 ;
    133 ; Spec packet for disk image emulation
    134 ;
    135 		alignb 8
    136 dspec_packet:	resb 1				; Size of packet
    137 dsp_media:	resb 1				; Media type
    138 dsp_drive:	resb 1				; Drive number
    139 dsp_controller:	resb 1				; Controller index
    140 dsp_lba:	resd 1				; LBA for emulated disk image
    141 dsp_devspec:	resw 1				; IDE/SCSI information
    142 dsp_buffer:	resw 1				; User-provided buffer
    143 dsp_loadseg:	resw 1				; Load segment
    144 dsp_sectors:	resw 1				; Sector count
    145 dsp_chs:	resb 3				; Simulated CHS geometry
    146 dsp_dummy:	resb 1				; Scratch, safe to overwrite
    147 
    148 		alignb 4
    149 _spec_end	equ $
    150 _spec_len	equ _spec_end - _spec_start
    151 
    152 		section .init
    153 ;;
    154 ;; Primary entry point.  Because BIOSes are buggy, we only load the first
    155 ;; CD-ROM sector (2K) of the file, so the number one priority is actually
    156 ;; loading the rest.
    157 ;;
    158 		global StackBuf
    159 StackBuf	equ STACK_TOP-44	; 44 bytes needed for
    160 					; the bootsector chainloading
    161 					; code!
    162 		global OrigESDI
    163 OrigESDI	equ StackBuf-4          ; The high dword on the stack
    164 StackHome	equ OrigESDI
    165 
    166 bootsec		equ $
    167 
    168 _start:		; Far jump makes sure we canonicalize the address
    169 		cli
    170 		jmp 0:_start1
    171 		times 8-($-$$) nop		; Pad to file offset 8
    172 
    173 		; This table hopefully gets filled in by mkisofs using the
    174 		; -boot-info-table option.  If not, the values in this
    175 		; table are default values that we can use to get us what
    176 		; we need, at least under a certain set of assumptions.
    177 		global iso_boot_info
    178 iso_boot_info:
    179 bi_pvd:		dd 16				; LBA of primary volume descriptor
    180 bi_file:	dd 0				; LBA of boot file
    181 bi_length:	dd 0xdeadbeef			; Length of boot file
    182 bi_csum:	dd 0xdeadbeef			; Checksum of boot file
    183 bi_reserved:	times 10 dd 0xdeadbeef		; Reserved
    184 bi_end:
    185 
    186 		; Custom entry point for the hybrid-mode disk.
    187 		; The following values will have been pushed onto the
    188 		; entry stack:
    189 		;	- partition offset (qword)
    190 		;	- ES
    191 		;	- DI
    192 		;	- DX (including drive number)
    193 		;	- CBIOS Heads
    194 		;	- CBIOS Sectors
    195 		;	- EBIOS flag
    196 		;       (top of stack)
    197 		;
    198 		; If we had an old isohybrid, the partition offset will
    199 		; be missing; we can check for that with sp >= 0x7c00.
    200 		; Serious hack alert.
    201 %ifndef DEBUG_MESSAGES
    202 _hybrid_signature:
    203 	       dd 0x7078c0fb			; An arbitrary number...
    204 
    205 _start_hybrid:
    206 		pop cx				; EBIOS flag
    207 		pop word [cs:bsSecPerTrack]
    208 		pop word [cs:bsHeads]
    209 		pop dx
    210 		pop di
    211 		pop es
    212 		xor eax,eax
    213 		xor ebx,ebx
    214 		cmp sp,7C00h
    215 		jae .nooffset
    216 		pop eax
    217 		pop ebx
    218 .nooffset:
    219 		mov si,bios_cbios
    220 		jcxz _start_common
    221 		mov si,bios_ebios
    222 		jmp _start_common
    223 %endif
    224 
    225 _start1:
    226 		mov si,bios_cdrom
    227 		xor eax,eax
    228 		xor ebx,ebx
    229 _start_common:
    230 		mov [cs:InitStack],sp	; Save initial stack pointer
    231 		mov [cs:InitStack+2],ss
    232 		xor cx,cx
    233 		mov ss,cx
    234 		mov sp,StackBuf		; Set up stack
    235 		push es			; Save initial ES:DI -> $PnP pointer
    236 		push di
    237 		mov ds,cx
    238 		mov es,cx
    239 		mov fs,cx
    240 		mov gs,cx
    241 		sti
    242 		cld
    243 
    244 		mov [Hidden],eax
    245 		mov [Hidden+4],ebx
    246 
    247 		mov [BIOSType],si
    248 		mov eax,[si]
    249 		mov [GetlinsecPtr],eax
    250 
    251 		; Show signs of life
    252 		mov si,syslinux_banner
    253 		call writestr_early
    254 %ifdef DEBUG_MESSAGES
    255 		mov si,copyright_str
    256 %else
    257 		mov si,[BIOSName]
    258 %endif
    259 		call writestr_early
    260 
    261 		;
    262 		; Before modifying any memory, get the checksum of bytes
    263 		; 64-2048
    264 		;
    265 initial_csum:	xor edi,edi
    266 		mov si,bi_end
    267 		mov cx,(SECTOR_SIZE-64) >> 2
    268 .loop:		lodsd
    269 		add edi,eax
    270 		loop .loop
    271 		mov [FirstSecSum],edi
    272 
    273 		mov [DriveNumber],dl
    274 %ifdef DEBUG_MESSAGES
    275 		mov si,startup_msg
    276 		call writemsg
    277 		mov al,dl
    278 		call writehex2
    279 		call crlf_early
    280 %endif
    281 		;
    282 		; Initialize spec packet buffers
    283 		;
    284 		mov di,_spec_start
    285 		mov cx,_spec_len >> 2
    286 		xor eax,eax
    287 		rep stosd
    288 
    289 		; Initialize length field of the various packets
    290 		mov byte [spec_packet],13h
    291 		mov byte [drive_params],30
    292 		mov byte [dapa],16
    293 		mov byte [dspec_packet],13h
    294 
    295 		; Other nonzero fields
    296 		inc word [dsp_sectors]
    297 
    298 		; Are we just pretending to be a CD-ROM?
    299 		cmp word [BIOSType],bios_cdrom
    300 		jne found_drive			; If so, no spec packet...
    301 
    302 		; Now figure out what we're actually doing
    303 		; Note: use passed-in DL value rather than 7Fh because
    304 		; at least some BIOSes will get the wrong value otherwise
    305 		mov ax,4B01h			; Get disk emulation status
    306 		mov dl,[DriveNumber]
    307 		mov si,spec_packet
    308 		call int13
    309 		jc award_hack			; changed for BrokenAwardHack
    310 		mov dl,[DriveNumber]
    311 		cmp [sp_drive],dl		; Should contain the drive number
    312 		jne spec_query_failed
    313 
    314 %ifdef DEBUG_MESSAGES
    315 		mov si,spec_ok_msg
    316 		call writemsg
    317 		mov al,byte [sp_drive]
    318 		call writehex2
    319 		call crlf_early
    320 %endif
    321 
    322 found_drive:
    323 		; Alright, we have found the drive.  Now, try to find the
    324 		; boot file itself.  If we have a boot info table, life is
    325 		; good; if not, we have to make some assumptions, and try
    326 		; to figure things out ourselves.  In particular, the
    327 		; assumptions we have to make are:
    328 		; - single session only
    329 		; - only one boot entry (no menu or other alternatives)
    330 
    331 		cmp dword [bi_file],0		; Address of code to load
    332 		jne found_file			; Boot info table present :)
    333 
    334 %ifdef DEBUG_MESSAGES
    335 		mov si,noinfotable_msg
    336 		call writemsg
    337 %endif
    338 
    339 		; No such luck.  See if the spec packet contained one.
    340 		mov eax,[sp_lba]
    341 		and eax,eax
    342 		jz set_file			; Good enough
    343 
    344 %ifdef DEBUG_MESSAGES
    345 		mov si,noinfoinspec_msg
    346 		call writemsg
    347 %endif
    348 
    349 		; No such luck.  Get the Boot Record Volume, assuming single
    350 		; session disk, and that we're the first entry in the chain.
    351 		mov eax,17			; Assumed address of BRV
    352 		mov bx,trackbuf
    353 		call getonesec
    354 
    355 		mov eax,[trackbuf+47h]		; Get boot catalog address
    356 		mov bx,trackbuf
    357 		call getonesec			; Get boot catalog
    358 
    359 		mov eax,[trackbuf+28h]		; First boot entry
    360 		; And hope and pray this is us...
    361 
    362 		; Some BIOSes apparently have limitations on the size
    363 		; that may be loaded (despite the El Torito spec being very
    364 		; clear on the fact that it must all be loaded.)  Therefore,
    365 		; we load it ourselves, and *bleep* the BIOS.
    366 
    367 set_file:
    368 		mov [bi_file],eax
    369 
    370 found_file:
    371 		; Set up boot file sizes
    372 		mov eax,[bi_length]
    373 		sub eax,SECTOR_SIZE-3		; ... minus sector loaded
    374 		shr eax,2			; bytes->dwords
    375 		mov [ImageDwords],eax		; boot file dwords
    376 		add eax,((SECTOR_SIZE-1) >> 2)
    377 		shr eax,SECTOR_SHIFT-2		; dwords->sectors
    378 		mov [ImageSectors],ax		; boot file sectors
    379 
    380 		mov eax,[bi_file]		; Address of code to load
    381 		inc eax				; Don't reload bootstrap code
    382 %ifdef DEBUG_MESSAGES
    383 		mov si,offset_msg
    384 		call writemsg
    385 		call writehex8
    386 		call crlf_early
    387 %endif
    388 
    389 		; Load the rest of the file.  However, just in case there
    390 		; are still BIOSes with 64K wraparound problems, we have to
    391 		; take some extra precautions.  Since the normal load
    392 		; address (TEXT_START) is *not* 2K-sector-aligned, we round
    393 		; the target address upward to a sector boundary,
    394 		; and then move the entire thing down as a unit.
    395 MaxLMA		equ 384*1024		; Reasonable limit (384K)
    396 
    397 		mov bx,((TEXT_START+2*SECTOR_SIZE-1) & ~(SECTOR_SIZE-1)) >> 4
    398 		mov bp,[ImageSectors]
    399 		push bx			; Load segment address
    400 
    401 .more:
    402 		push bx			; Segment address
    403 		push bp			; Sector count
    404 		mov es,bx
    405 		mov cx,0xfff
    406 		and bx,cx
    407 		inc cx
    408 		sub cx,bx
    409 		shr cx,SECTOR_SHIFT - 4
    410 		jnz .notaligned
    411 		mov cx,0x10000 >> SECTOR_SHIFT	; Full 64K segment possible
    412 .notaligned:
    413 		cmp bp,cx
    414 		jbe .ok
    415 		mov bp,cx
    416 .ok:
    417 		xor bx,bx
    418 		push bp
    419 		push eax
    420 		call getlinsec
    421 		pop eax
    422 		pop cx
    423 		movzx edx,cx
    424 		pop bp
    425 		pop bx
    426 
    427 		shl cx,SECTOR_SHIFT - 4
    428 		add bx,cx
    429 		add eax,edx
    430 		sub bp,dx
    431 		jnz .more
    432 
    433 		; Move the image into place, and also verify the
    434 		; checksum
    435 		pop ax				; Load segment address
    436 		mov bx,(TEXT_START + SECTOR_SIZE) >> 4
    437 		mov ecx,[ImageDwords]
    438 		mov edi,[FirstSecSum]		; First sector checksum
    439 		xor si,si
    440 
    441 move_verify_image:
    442 .setseg:
    443 		mov ds,ax
    444 		mov es,bx
    445 .loop:
    446 		mov edx,[si]
    447 		add edi,edx
    448 		dec ecx
    449 		mov [es:si],edx
    450 		jz .done
    451 		add si,4
    452 		jnz .loop
    453 		add ax,1000h
    454 		add bx,1000h
    455 		jmp .setseg
    456 .done:
    457 		mov ax,cs
    458 		mov ds,ax
    459 		mov es,ax
    460 
    461 		; Verify the checksum on the loaded image.
    462 		cmp [bi_csum],edi
    463 		je integrity_ok
    464 
    465 		mov si,checkerr_msg
    466 		call writemsg
    467 		jmp kaboom
    468 
    469 integrity_ok:
    470 %ifdef DEBUG_MESSAGES
    471 		mov si,allread_msg
    472 		call writemsg
    473 %endif
    474 		jmp all_read			; Jump to main code
    475 
    476 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
    477 ;; Start of BrokenAwardHack --- 10-nov-2002           Knut_Petersen (a] t-online.de
    478 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
    479 ;;
    480 ;; There is a problem with certain versions of the AWARD BIOS ...
    481 ;; the boot sector will be loaded and executed correctly, but, because the
    482 ;; int 13 vector points to the wrong code in the BIOS, every attempt to
    483 ;; load the spec packet will fail. We scan for the equivalent of
    484 ;;
    485 ;;	mov	ax,0201h
    486 ;;	mov	bx,7c00h
    487 ;;	mov	cx,0006h
    488 ;;	mov	dx,0180h
    489 ;;	pushf
    490 ;;	call	<direct far>
    491 ;;
    492 ;; and use <direct far> as the new vector for int 13. The code above is
    493 ;; used to load the boot code into ram, and there should be no reason
    494 ;; for anybody to change it now or in the future. There are no opcodes
    495 ;; that use encodings relativ to IP, so scanning is easy. If we find the
    496 ;; code above in the BIOS code we can be pretty sure to run on a machine
    497 ;; with an broken AWARD BIOS ...
    498 ;;
    499 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
    500 									     ;;
    501 %ifdef DEBUG_MESSAGES							     ;;
    502 									     ;;
    503 award_notice	db	"Trying BrokenAwardHack first ...",CR,LF,0	     ;;
    504 award_not_orig	db	"BAH: Original Int 13 vector   : ",0		     ;;
    505 award_not_new	db	"BAH: Int 13 vector changed to : ",0		     ;;
    506 award_not_succ	db	"BAH: SUCCESS",CR,LF,0				     ;;
    507 award_not_fail	db	"BAH: FAILURE"					     ;;
    508 award_not_crlf	db	CR,LF,0						     ;;
    509 									     ;;
    510 %endif									     ;;
    511 									     ;;
    512 award_oldint13	dd	0						     ;;
    513 award_string	db	0b8h,1,2,0bbh,0,7ch,0b9h,6,0,0bah,80h,1,09ch,09ah    ;;
    514 									     ;;
    515 						;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
    516 award_hack:	mov	si,spec_err_msg		; Moved to this place from
    517 		call	writemsg		; spec_query_failed
    518 						;
    519 %ifdef DEBUG_MESSAGES				;
    520 						;
    521 		mov	si,award_notice		; display our plan
    522 		call	writemsg		;
    523 		mov	si,award_not_orig	; display original int 13
    524 		call	writemsg		; vector
    525 %endif						;
    526 		mov	eax,[13h*4]		;
    527 		mov	[award_oldint13],eax	;
    528 						;
    529 %ifdef DEBUG_MESSAGES				;
    530 						;
    531 		call	writehex8		;
    532 		mov	si,award_not_crlf	;
    533 		call	writestr_early		;
    534 %endif						;
    535 		push	es			; save ES
    536 		mov	ax,0f000h		; ES = BIOS Seg
    537 		mov	es,ax			;
    538 		cld				;
    539 		xor	di,di			; start at ES:DI = f000:0
    540 award_loop:	push	di			; save DI
    541 		mov	si,award_string		; scan for award_string
    542 		mov	cx,7			; length of award_string = 7dw
    543 		repz	cmpsw			; compare
    544 		pop	di			; restore DI
    545 		jcxz	award_found		; jmp if found
    546 		inc	di			; not found, inc di
    547 		jno	award_loop		;
    548 						;
    549 award_failed:	pop	es			; No, not this way :-((
    550 award_fail2:					;
    551 						;
    552 %ifdef DEBUG_MESSAGES				;
    553 						;
    554 		mov	si,award_not_fail	; display failure ...
    555 		call	writemsg		;
    556 %endif						;
    557 		mov	eax,[award_oldint13]	; restore the original int
    558 		or	eax,eax			; 13 vector if there is one
    559 		jz	spec_query_failed	; and try other workarounds
    560 		mov	[13h*4],eax		;
    561 		jmp	spec_query_failed	;
    562 						;
    563 award_found:	mov	eax,[es:di+0eh]		; load possible int 13 addr
    564 		pop	es			; restore ES
    565 						;
    566 		cmp	eax,[award_oldint13]	; give up if this is the
    567 		jz	award_failed		; active int 13 vector,
    568 		mov	[13h*4],eax		; otherwise change 0:13h*4
    569 						;
    570 						;
    571 %ifdef DEBUG_MESSAGES				;
    572 						;
    573 		push	eax			; display message and
    574 		mov	si,award_not_new	; new vector address
    575 		call	writemsg		;
    576 		pop	eax			;
    577 		call	writehex8		;
    578 		mov	si,award_not_crlf	;
    579 		call	writestr_early		;
    580 %endif						;
    581 		mov	ax,4B01h		; try to read the spec packet
    582 		mov	dl,[DriveNumber]	; now ... it should not fail
    583 		mov	si,spec_packet		; any longer
    584 		int	13h			;
    585 		jc	award_fail2		;
    586 						;
    587 %ifdef DEBUG_MESSAGES				;
    588 						;
    589 		mov	si,award_not_succ	; display our SUCCESS
    590 		call	writemsg		;
    591 %endif						;
    592 		jmp	found_drive		; and leave error recovery code
    593 						;
    594 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
    595 ;; End of BrokenAwardHack ----            10-nov-2002 Knut_Petersen (a] t-online.de
    596 ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;
    597 
    598 
    599 		; INT 13h, AX=4B01h, DL=<passed in value> failed.
    600 		; Try to scan the entire 80h-FFh from the end.
    601 
    602 spec_query_failed:
    603 
    604 		; some code moved to BrokenAwardHack
    605 
    606 		mov dl,0FFh
    607 .test_loop:	pusha
    608 		mov ax,4B01h
    609 		mov si,spec_packet
    610 		mov byte [si],13h		; Size of buffer
    611 		call int13
    612 		popa
    613 		jc .still_broken
    614 
    615 		mov si,maybe_msg
    616 		call writemsg
    617 		mov al,dl
    618 		call writehex2
    619 		call crlf_early
    620 
    621 		cmp byte [sp_drive],dl
    622 		jne .maybe_broken
    623 
    624 		; Okay, good enough...
    625 		mov si,alright_msg
    626 		call writemsg
    627 .found_drive0:	mov [DriveNumber],dl
    628 .found_drive:	jmp found_drive
    629 
    630 		; Award BIOS 4.51 apparently passes garbage in sp_drive,
    631 		; but if this was the drive number originally passed in
    632 		; DL then consider it "good enough"
    633 .maybe_broken:
    634 		mov al,[DriveNumber]
    635 		cmp al,dl
    636 		je .found_drive
    637 
    638 		; Intel Classic R+ computer with Adaptec 1542CP BIOS 1.02
    639 		; passes garbage in sp_drive, and the drive number originally
    640 		; passed in DL does not have 80h bit set.
    641 		or al,80h
    642 		cmp al,dl
    643 		je .found_drive0
    644 
    645 .still_broken:	dec dx
    646 		cmp dl, 80h
    647 		jnb .test_loop
    648 
    649 		; No spec packet anywhere.  Some particularly pathetic
    650 		; BIOSes apparently don't even implement function
    651 		; 4B01h, so we can't query a spec packet no matter
    652 		; what.  If we got a drive number in DL, then try to
    653 		; use it, and if it works, then well...
    654 		mov dl,[DriveNumber]
    655 		cmp dl,81h			; Should be 81-FF at least
    656 		jb fatal_error			; If not, it's hopeless
    657 
    658 		; Write a warning to indicate we're on *very* thin ice now
    659 		mov si,nospec_msg
    660 		call writemsg
    661 		mov al,dl
    662 		call writehex2
    663 		call crlf_early
    664 		mov si,trysbm_msg
    665 		call writemsg
    666 		jmp .found_drive		; Pray that this works...
    667 
    668 fatal_error:
    669 		mov si,nothing_msg
    670 		call writemsg
    671 
    672 .norge:		jmp short .norge
    673 
    674 		; Information message (DS:SI) output
    675 		; Prefix with "isolinux: "
    676 		;
    677 writemsg:	push ax
    678 		push si
    679 		mov si,isolinux_str
    680 		call writestr_early
    681 		pop si
    682 		call writestr_early
    683 		pop ax
    684 		ret
    685 
    686 writestr_early:
    687 		pushfd
    688 		pushad
    689 .top:		lodsb
    690 		and al,al
    691 		jz .end
    692 		call writechr
    693 		jmp short .top
    694 .end:		popad
    695 		popfd
    696 		ret
    697 
    698 crlf_early:	push ax
    699 		mov al,CR
    700 		call writechr
    701 		mov al,LF
    702 		call writechr
    703 		pop ax
    704 		ret
    705 
    706 ;
    707 ; Write a character to the screen.  There is a more "sophisticated"
    708 ; version of this in the subsequent code, so we patch the pointer
    709 ; when appropriate.
    710 ;
    711 
    712 writechr:
    713 .simple:
    714 		pushfd
    715 		pushad
    716 		mov ah,0Eh
    717 		xor bx,bx
    718 		int 10h
    719 		popad
    720 		popfd
    721 		ret
    722 
    723 ;
    724 ; int13: save all the segment registers and call INT 13h.
    725 ;	 Some CD-ROM BIOSes have been found to corrupt segment registers
    726 ;	 and/or disable interrupts.
    727 ;
    728 int13:
    729 		pushf
    730 		push bp
    731 		push ds
    732 		push es
    733 		push fs
    734 		push gs
    735 		int 13h
    736 		mov bp,sp
    737 		setc [bp+10]		; Propagate CF to the caller
    738 		pop gs
    739 		pop fs
    740 		pop es
    741 		pop ds
    742 		pop bp
    743 		popf
    744 		ret
    745 
    746 ;
    747 ; Get one sector.  Convenience entry point.
    748 ;
    749 getonesec:
    750 		mov bp,1
    751 		; Fall through to getlinsec
    752 
    753 ;
    754 ; Get linear sectors - EBIOS LBA addressing, 2048-byte sectors.
    755 ;
    756 ; Input:
    757 ;	EAX	- Linear sector number
    758 ;	ES:BX	- Target buffer
    759 ;	BP	- Sector count
    760 ;
    761 		global getlinsec
    762 getlinsec:	jmp word [cs:GetlinsecPtr]
    763 
    764 %ifndef DEBUG_MESSAGES
    765 
    766 ;
    767 ; First, the variants that we use when actually loading off a disk
    768 ; (hybrid mode.)  These are adapted versions of the equivalent routines
    769 ; in ldlinux.asm.
    770 ;
    771 
    772 ;
    773 ; getlinsec_ebios:
    774 ;
    775 ; getlinsec implementation for floppy/HDD EBIOS (EDD)
    776 ;
    777 getlinsec_ebios:
    778 		xor edx,edx
    779 		shld edx,eax,2
    780 		shl eax,2			; Convert to HDD sectors
    781 		add eax,[Hidden]
    782 		adc edx,[Hidden+4]
    783 		shl bp,2
    784 
    785 .loop:
    786                 push bp                         ; Sectors left
    787 .retry2:
    788 		call maxtrans			; Enforce maximum transfer size
    789 		movzx edi,bp			; Sectors we are about to read
    790 		mov cx,retry_count
    791 .retry:
    792 
    793 		; Form DAPA on stack
    794 		push edx
    795 		push eax
    796 		push es
    797 		push bx
    798 		push di
    799 		push word 16
    800 		mov si,sp
    801 		pushad
    802                 mov dl,[DriveNumber]
    803 		push ds
    804 		push ss
    805 		pop ds				; DS <- SS
    806 		mov ah,42h			; Extended Read
    807 		call int13
    808 		pop ds
    809 		popad
    810 		lea sp,[si+16]			; Remove DAPA
    811 		jc .error
    812 		pop bp
    813 		add eax,edi			; Advance sector pointer
    814 		adc edx,0
    815 		sub bp,di			; Sectors left
    816                 shl di,9			; 512-byte sectors
    817                 add bx,di			; Advance buffer pointer
    818                 and bp,bp
    819                 jnz .loop
    820 
    821                 ret
    822 
    823 .error:
    824 		; Some systems seem to get "stuck" in an error state when
    825 		; using EBIOS.  Doesn't happen when using CBIOS, which is
    826 		; good, since some other systems get timeout failures
    827 		; waiting for the floppy disk to spin up.
    828 
    829 		pushad				; Try resetting the device
    830 		xor ax,ax
    831 		mov dl,[DriveNumber]
    832 		call int13
    833 		popad
    834 		loop .retry			; CX-- and jump if not zero
    835 
    836 		;shr word [MaxTransfer],1	; Reduce the transfer size
    837 		;jnz .retry2
    838 
    839 		; Total failure.  Try falling back to CBIOS.
    840 		mov word [GetlinsecPtr], getlinsec_cbios
    841 		;mov byte [MaxTransfer],63	; Max possibe CBIOS transfer
    842 
    843 		pop bp
    844 		jmp getlinsec_cbios.loop
    845 
    846 ;
    847 ; getlinsec_cbios:
    848 ;
    849 ; getlinsec implementation for legacy CBIOS
    850 ;
    851 getlinsec_cbios:
    852 		xor edx,edx
    853 		shl eax,2			; Convert to HDD sectors
    854 		add eax,[Hidden]
    855 		shl bp,2
    856 
    857 .loop:
    858 		push edx
    859 		push eax
    860 		push bp
    861 		push bx
    862 
    863 		movzx esi,word [bsSecPerTrack]
    864 		movzx edi,word [bsHeads]
    865 		;
    866 		; Dividing by sectors to get (track,sector): we may have
    867 		; up to 2^18 tracks, so we need to use 32-bit arithmetric.
    868 		;
    869 		div esi
    870 		xor cx,cx
    871 		xchg cx,dx		; CX <- sector index (0-based)
    872 					; EDX <- 0
    873 		; eax = track #
    874 		div edi			; Convert track to head/cyl
    875 
    876 		; We should test this, but it doesn't fit...
    877 		; cmp eax,1023
    878 		; ja .error
    879 
    880 		;
    881 		; Now we have AX = cyl, DX = head, CX = sector (0-based),
    882 		; BP = sectors to transfer, SI = bsSecPerTrack,
    883 		; ES:BX = data target
    884 		;
    885 
    886 		call maxtrans			; Enforce maximum transfer size
    887 
    888 		; Must not cross track boundaries, so BP <= SI-CX
    889 		sub si,cx
    890 		cmp bp,si
    891 		jna .bp_ok
    892 		mov bp,si
    893 .bp_ok:
    894 
    895 		shl ah,6		; Because IBM was STOOPID
    896 					; and thought 8 bits were enough
    897 					; then thought 10 bits were enough...
    898 		inc cx			; Sector numbers are 1-based, sigh
    899 		or cl,ah
    900 		mov ch,al
    901 		mov dh,dl
    902 		mov dl,[DriveNumber]
    903 		xchg ax,bp		; Sector to transfer count
    904 		mov ah,02h		; Read sectors
    905 		mov bp,retry_count
    906 .retry:
    907 		pushad
    908 		call int13
    909 		popad
    910 		jc .error
    911 .resume:
    912 		movzx ecx,al		; ECX <- sectors transferred
    913 		shl ax,9		; Convert sectors in AL to bytes in AX
    914 		pop bx
    915 		add bx,ax
    916 		pop bp
    917 		pop eax
    918 		pop edx
    919 		add eax,ecx
    920 		sub bp,cx
    921 		jnz .loop
    922 		ret
    923 
    924 .error:
    925 		dec bp
    926 		jnz .retry
    927 
    928 		xchg ax,bp		; Sectors transferred <- 0
    929 		shr word [MaxTransfer],1
    930 		jnz .resume
    931 		jmp disk_error
    932 
    933 ;
    934 ; Truncate BP to MaxTransfer
    935 ;
    936 maxtrans:
    937 		cmp bp,[MaxTransfer]
    938 		jna .ok
    939 		mov bp,[MaxTransfer]
    940 .ok:		ret
    941 
    942 %endif
    943 
    944 ;
    945 ; This is the variant we use for real CD-ROMs:
    946 ; LBA, 2K sectors, some special error handling.
    947 ;
    948 getlinsec_cdrom:
    949 		mov si,dapa			; Load up the DAPA
    950 		mov [si+4],bx
    951 		mov [si+6],es
    952 		mov [si+8],eax
    953 .loop:
    954 		push bp				; Sectors left
    955 		cmp bp,[MaxTransferCD]
    956 		jbe .bp_ok
    957 		mov bp,[MaxTransferCD]
    958 .bp_ok:
    959 		mov [si+2],bp
    960 		push si
    961 		mov dl,[DriveNumber]
    962 		mov ah,42h			; Extended Read
    963 		call xint13
    964 		pop si
    965 		pop bp
    966 		movzx eax,word [si+2]		; Sectors we read
    967 		add [si+8],eax			; Advance sector pointer
    968 		sub bp,ax			; Sectors left
    969 		shl ax,SECTOR_SHIFT-4		; 2048-byte sectors -> segment
    970 		add [si+6],ax			; Advance buffer pointer
    971 		and bp,bp
    972 		jnz .loop
    973 		mov eax,[si+8]			; Next sector
    974 		ret
    975 
    976 		; INT 13h with retry
    977 xint13:		mov byte [RetryCount],retry_count
    978 .try:		pushad
    979 		call int13
    980 		jc .error
    981 		add sp,byte 8*4			; Clean up stack
    982 		ret
    983 .error:
    984 		mov [DiskError],ah		; Save error code
    985 		popad
    986 		mov [DiskSys],ax		; Save system call number
    987 		dec byte [RetryCount]
    988 		jz .real_error
    989 		push ax
    990 		mov al,[RetryCount]
    991 		mov ah,[dapa+2]			; Sector transfer count
    992 		cmp al,2			; Only 2 attempts left
    993 		ja .nodanger
    994 		mov ah,1			; Drop transfer size to 1
    995 		jmp short .setsize
    996 .nodanger:
    997 		cmp al,retry_count-2
    998 		ja .again			; First time, just try again
    999 		shr ah,1			; Otherwise, try to reduce
   1000 		adc ah,0			; the max transfer size, but not to 0
   1001 .setsize:
   1002 		mov [MaxTransferCD],ah
   1003 		mov [dapa+2],ah
   1004 .again:
   1005 		pop ax
   1006 		jmp .try
   1007 
   1008 .real_error:	mov si,diskerr_msg
   1009 		call writemsg
   1010 		mov al,[DiskError]
   1011 		call writehex2
   1012 		mov si,oncall_str
   1013 		call writestr_early
   1014 		mov ax,[DiskSys]
   1015 		call writehex4
   1016 		mov si,ondrive_str
   1017 		call writestr_early
   1018 		mov al,dl
   1019 		call writehex2
   1020 		call crlf_early
   1021 		; Fall through to kaboom
   1022 
   1023 ;
   1024 ; kaboom: write a message and bail out.  Wait for a user keypress,
   1025 ;	  then do a hard reboot.
   1026 ;
   1027 		global kaboom
   1028 disk_error:
   1029 kaboom:
   1030 		RESET_STACK_AND_SEGS AX
   1031 		mov si,bailmsg
   1032 		pm_call pm_writestr
   1033 		pm_call pm_getchar
   1034 		cli
   1035 		mov word [BIOS_magic],0	; Cold reboot
   1036 		jmp 0F000h:0FFF0h	; Reset vector address
   1037 
   1038 ; -----------------------------------------------------------------------------
   1039 ;  Common modules needed in the first sector
   1040 ; -----------------------------------------------------------------------------
   1041 
   1042 %include "writehex.inc"		; Hexadecimal output
   1043 
   1044 ; -----------------------------------------------------------------------------
   1045 ; Data that needs to be in the first sector
   1046 ; -----------------------------------------------------------------------------
   1047 
   1048 		global syslinux_banner, copyright_str
   1049 syslinux_banner	db CR, LF, MY_NAME, ' ', VERSION_STR, ' ', DATE_STR, ' ', 0
   1050 copyright_str   db ' Copyright (C) 1994-'
   1051 		asciidec YEAR
   1052 		db ' H. Peter Anvin et al', CR, LF, 0
   1053 isolinux_str	db 'isolinux: ', 0
   1054 %ifdef DEBUG_MESSAGES
   1055 startup_msg:	db 'Starting up, DL = ', 0
   1056 spec_ok_msg:	db 'Loaded spec packet OK, drive = ', 0
   1057 secsize_msg:	db 'Sector size ', 0
   1058 offset_msg:	db 'Main image LBA = ', 0
   1059 verify_msg:	db 'Image csum verified.', CR, LF, 0
   1060 allread_msg	db 'Image read, jumping to main code...', CR, LF, 0
   1061 %endif
   1062 noinfotable_msg	db 'No boot info table, assuming single session disk...', CR, LF, 0
   1063 noinfoinspec_msg db 'Spec packet missing LBA information, trying to wing it...', CR, LF, 0
   1064 spec_err_msg:	db 'Loading spec packet failed, trying to wing it...', CR, LF, 0
   1065 maybe_msg:	db 'Found something at drive = ', 0
   1066 alright_msg:	db 'Looks reasonable, continuing...', CR, LF, 0
   1067 nospec_msg	db 'Extremely broken BIOS detected, last attempt with drive = ', 0
   1068 nothing_msg:	db 'Failed to locate CD-ROM device; boot failed.', CR, LF
   1069 trysbm_msg	db 'See http://syslinux.zytor.com/sbm for more information.', CR, LF, 0
   1070 diskerr_msg:	db 'Disk error ', 0
   1071 oncall_str:	db ', AX = ',0
   1072 ondrive_str:	db ', drive ', 0
   1073 checkerr_msg:	db 'Image checksum error, sorry...', CR, LF, 0
   1074 
   1075 err_bootfailed	db CR, LF, 'Boot failed: press a key to retry...'
   1076 bailmsg		equ err_bootfailed
   1077 crlf_msg	db CR, LF
   1078 null_msg	db 0
   1079 
   1080 bios_cdrom_str	db 'ETCD', 0
   1081 %ifndef DEBUG_MESSAGES
   1082 bios_cbios_str	db 'CHDD', 0
   1083 bios_ebios_str	db 'EHDD' ,0
   1084 %endif
   1085 
   1086 		alignz 4
   1087 		global bios_cdrom
   1088 bios_cdrom:	dw getlinsec_cdrom, bios_cdrom_str
   1089 %ifndef DEBUG_MESSAGES
   1090 bios_cbios:	dw getlinsec_cbios, bios_cbios_str
   1091 bios_ebios:	dw getlinsec_ebios, bios_ebios_str
   1092 %endif
   1093 
   1094 ; Maximum transfer size
   1095 MaxTransfer	dw 127				; Hard disk modes
   1096 MaxTransferCD	dw 32				; CD mode
   1097 
   1098 rl_checkpt	equ $				; Must be <= 800h
   1099 
   1100 		; This pads to the end of sector 0 and errors out on
   1101 		; overflow.
   1102 		times 2048-($-$$) db 0
   1103 
   1104 ; ----------------------------------------------------------------------------
   1105 ;  End of code and data that have to be in the first sector
   1106 ; ----------------------------------------------------------------------------
   1107 
   1108 		section .text16
   1109 
   1110 all_read:
   1111 
   1112 ; Test tracers
   1113 		TRACER 'T'
   1114 		TRACER '>'
   1115 
   1116 ;
   1117 ; Common initialization code
   1118 ;
   1119 %include "init.inc"
   1120 
   1121 ; Tell the user we got this far...
   1122 %ifndef DEBUG_MESSAGES			; Gets messy with debugging on
   1123 		mov si,copyright_str
   1124 		pm_call pm_writestr
   1125 %endif
   1126 
   1127 ;
   1128 ; Now we're all set to start with our *real* business.	First load the
   1129 ; configuration file (if any) and parse it.
   1130 ;
   1131 ; In previous versions I avoided using 32-bit registers because of a
   1132 ; rumour some BIOSes clobbered the upper half of 32-bit registers at
   1133 ; random.  I figure, though, that if there are any of those still left
   1134 ; they probably won't be trying to install Linux on them...
   1135 ;
   1136 ; The code is still ripe with 16-bitisms, though.  Not worth the hassle
   1137 ; to take'm out.  In fact, we may want to put them back if we're going
   1138 ; to boot ELKS at some point.
   1139 ;
   1140 
   1141 ;
   1142 ; Now, we need to sniff out the actual filesystem data structures.
   1143 ; mkisofs gave us a pointer to the primary volume descriptor
   1144 ; (which will be at 16 only for a single-session disk!); from the PVD
   1145 ; we should be able to find the rest of what we need to know.
   1146 ;
   1147 init_fs:
   1148 		pushad
   1149 	        mov eax,ROOT_FS_OPS
   1150 	        mov dl,[DriveNumber]
   1151                	cmp word [BIOSType],bios_cdrom
   1152                 sete dh                        ; 1 for cdrom, 0 for hybrid mode
   1153 		jne .hybrid
   1154 		movzx ebp,word [MaxTransferCD]
   1155 		jmp .common
   1156 .hybrid:
   1157 		movzx ebp,word [MaxTransfer]
   1158 .common:
   1159 	        mov ecx,[Hidden]
   1160 	        mov ebx,[Hidden+4]
   1161                 mov si,[bsHeads]
   1162 		mov di,[bsSecPerTrack]
   1163 		pm_call pm_fs_init
   1164 		pm_call load_env32
   1165 enter_command:
   1166 auto_boot:
   1167 		jmp kaboom		; load_env32() should never return. If
   1168 		                        ; it does, then kaboom!
   1169 		popad
   1170 
   1171 		section .rodata
   1172 		alignz 4
   1173 ROOT_FS_OPS:
   1174 		extern iso_fs_ops
   1175 		dd iso_fs_ops
   1176 		dd 0
   1177 
   1178 		section .text16
   1179 
   1180 %ifdef DEBUG_TRACERS
   1181 ;
   1182 ; debug hack to print a character with minimal code impact
   1183 ;
   1184 debug_tracer:	pushad
   1185 		pushfd
   1186 		mov bp,sp
   1187 		mov bx,[bp+9*4]		; Get return address
   1188 		mov al,[cs:bx]		; Get data byte
   1189 		inc word [bp+9*4]	; Return to after data byte
   1190 		call writechr
   1191 		popfd
   1192 		popad
   1193 		ret
   1194 %endif	; DEBUG_TRACERS
   1195 
   1196 		section .bss16
   1197 		alignb 4
   1198 ThisKbdTo	resd 1			; Temporary holder for KbdTimeout
   1199 ThisTotalTo	resd 1			; Temporary holder for TotalTimeout
   1200 KernelExtPtr	resw 1			; During search, final null pointer
   1201 FuncFlag	resb 1			; Escape sequences received from keyboard
   1202 KernelType	resb 1			; Kernel type, from vkernel, if known
   1203 		global KernelName
   1204 KernelName	resb FILENAME_MAX	; Mangled name for kernel
   1205 
   1206 		section .text16
   1207 ;
   1208 ; COM32 vestigial data structure
   1209 ;
   1210 %include "com32.inc"
   1211 
   1212 ;
   1213 ; Common local boot code
   1214 ;
   1215 %include "localboot.inc"
   1216 
   1217 ; -----------------------------------------------------------------------------
   1218 ;  Common modules
   1219 ; -----------------------------------------------------------------------------
   1220 
   1221 %include "common.inc"		; Universal modules
   1222 
   1223 ; -----------------------------------------------------------------------------
   1224 ;  Begin data section
   1225 ; -----------------------------------------------------------------------------
   1226 
   1227 		section .data16
   1228 err_disk_image	db 'Cannot load disk image (invalid file)?', CR, LF, 0
   1229 
   1230 		section .bss16
   1231 		global OrigFDCTabPtr
   1232 OrigFDCTabPtr	resd 1			; Keep bios_cleanup_hardware() honest
   1233