Remove all explicit "near" declarations, except the ones that are
[profile/ivi/syslinux.git] / ldlinux.asm
1 ; -*- fundamental -*- (asm-mode sucks)
2 ; $Id$
3 ; ****************************************************************************
4 ;
5 ;  ldlinux.asm
6 ;
7 ;  A program to boot Linux kernels off an MS-DOS formatted floppy disk.  This
8 ;  functionality is good to have for installation floppies, where it may
9 ;  be hard to find a functional Linux system to run LILO off.
10 ;
11 ;  This program allows manipulation of the disk to take place entirely
12 ;  from MS-LOSS, and can be especially useful in conjunction with the
13 ;  umsdos filesystem.
14 ;
15 ;  This file is loaded in stages; first the boot sector at offset 7C00h,
16 ;  then the first sector (cluster, really, but we can only assume 1 sector)
17 ;  of LDLINUX.SYS at 7E00h and finally the remainder of LDLINUX.SYS at 8000h.
18 ;
19 ;   Copyright (C) 1994-2002  H. Peter Anvin
20 ;
21 ;  This program is free software; you can redistribute it and/or modify
22 ;  it under the terms of the GNU General Public License as published by
23 ;  the Free Software Foundation, Inc., 675 Mass Ave, Cambridge MA 02139,
24 ;  USA; either version 2 of the License, or (at your option) any later
25 ;  version; incorporated herein by reference.
26
27 ; ****************************************************************************
28
29 %define IS_SYSLINUX 1
30 %include "macros.inc"
31 %include "config.inc"
32 %include "kernel.inc"
33 %include "bios.inc"
34 %include "tracers.inc"
35
36 ;
37 ; Some semi-configurable constants... change on your own risk.
38 ;
39 my_id           equ syslinux_id
40 FILENAME_MAX_LG2 equ 4                  ; log2(Max filename size Including final null)
41 FILENAME_MAX    equ 11                  ; Max mangled filename size
42 NULLFILE        equ ' '                 ; First char space == null filename
43 retry_count     equ 6                   ; How patient are we with the disk?
44 %assign HIGHMEM_SLOP 0                  ; Avoid this much memory near the top
45
46 ;
47 ; The following structure is used for "virtual kernels"; i.e. LILO-style
48 ; option labels.  The options we permit here are `kernel' and `append
49 ; Since there is no room in the bottom 64K for all of these, we
50 ; stick them at vk_seg:0000 and copy them down before we need them.
51 ;
52 ; Note: this structure can be added to, but it must 
53 ;
54 %define vk_power        7               ; log2(max number of vkernels)
55 %define max_vk          (1 << vk_power) ; Maximum number of vkernels
56 %define vk_shift        (16-vk_power)   ; Number of bits to shift
57 %define vk_size         (1 << vk_shift) ; Size of a vkernel buffer
58
59                 struc vkernel
60 vk_vname:       resb FILENAME_MAX       ; Virtual name **MUST BE FIRST!**
61 vk_rname:       resb FILENAME_MAX       ; Real name
62 vk_appendlen:   resw 1
63                 alignb 4
64 vk_append:      resb max_cmd_len+1      ; Command line
65                 alignb 4
66 vk_end:         equ $                   ; Should be <= vk_size
67                 endstruc
68
69 %ifndef DEPEND
70 %if (vk_end > vk_size) || (vk_size*max_vk > 65536)
71 %error "Too many vkernels defined, reduce vk_power"
72 %endif
73 %endif
74
75 ;
76 ; Segment assignments in the bottom 640K
77 ; Stick to the low 512K in case we're using something like M-systems flash
78 ; which load a driver into low RAM (evil!!)
79 ;
80 ; 0000h - main code/data segment (and BIOS segment)
81 ;
82 real_mode_seg   equ 7000h
83 fat_seg         equ 5000h               ; 128K area for FAT (2x64K)
84 vk_seg          equ 4000h               ; Virtual kernels
85 xfer_buf_seg    equ 3000h               ; Bounce buffer for I/O to high mem
86 comboot_seg     equ 2000h               ; COMBOOT image loading zone
87
88 ; ---------------------------------------------------------------------------
89 ;   BEGIN CODE
90 ; ---------------------------------------------------------------------------
91
92 ;
93 ; Memory below this point is reserved for the BIOS and the MBR
94 ;
95                 absolute 1000h
96 trackbuf        equ $                   ; Track buffer goes here
97 trackbufsize    equ 16384               ; Safe size of track buffer
98 ;               trackbuf ends at 5000h
99
100
101 ;
102 ; Constants for the xfer_buf_seg
103 ;
104 ; The xfer_buf_seg is also used to store message file buffers.  We
105 ; need two trackbuffers (text and graphics), plus a work buffer
106 ; for the graphics decompressor.
107 ;
108 xbs_textbuf     equ 0                   ; Also hard-coded, do not change
109 xbs_vgabuf      equ trackbufsize
110 xbs_vgatmpbuf   equ 2*trackbufsize
111
112
113                 absolute 5000h          ; Here we keep our BSS stuff
114 VKernelBuf:     resb vk_size            ; "Current" vkernel
115                 alignb 4
116 AppendBuf       resb max_cmd_len+1      ; append=
117 KbdMap          resb 256                ; Keyboard map
118 FKeyName        resb 10*16              ; File names for F-key help
119 NumBuf          resb 15                 ; Buffer to load number
120 NumBufEnd       resb 1                  ; Last byte in NumBuf
121                 alignb 8
122
123                 ; Expanded superblock
124 SuperInfo       equ $
125                 resq 16                 ; The first 16 bytes expanded 8 times
126                 ;
127                 ; These need to follow SuperInfo
128                 ;
129 RootDir         resd 1                  ; Location of root directory
130 DataArea        resd 1                  ; Location of data area
131 RootDirSize     resw 1                  ; Root dir size in sectors
132 DirScanCtr      resw 1                  ; Used while searching directory
133 EndofDirSec     resw 1                  ; = trackbuf+bsBytesPerSec-31
134
135                 alignb 4
136 E820Buf         resd 5                  ; INT 15:E820 data buffer
137 HiLoadAddr      resd 1                  ; Address pointer for high load loop
138 HighMemSize     resd 1                  ; End of memory pointer (bytes)
139 RamdiskMax      resd 1                  ; Highest address for a ramdisk
140 KernelSize      resd 1                  ; Size of kernel (bytes)
141 SavedSSSP       resd 1                  ; Our SS:SP while running a COMBOOT image
142 ClustPerMoby    resd 1                  ; Clusters per 64K
143 ClustSize       resd 1                  ; Bytes/cluster
144 KernelName      resb 12                 ; Mangled name for kernel
145                                         ; (note the spare byte after!)
146 FBytes          equ $                   ; Used by open/getc
147 FBytes1         resw 1
148 FBytes2         resw 1
149 DirBlocksLeft   resw 1                  ; Ditto
150 RunLinClust     resw 1                  ; Cluster # for LDLINUX.SYS
151 BufSafe         resw 1                  ; Clusters we can load into trackbuf
152 BufSafeSec      resw 1                  ; = how many sectors?
153 BufSafeBytes    resw 1                  ; = how many bytes?
154 EndOfGetCBuf    resw 1                  ; = getcbuf+BufSafeBytes
155 KernelClust     resw 1                  ; Kernel size in clusters
156 FClust          resw 1                  ; Number of clusters in open/getc file
157 FNextClust      resw 1                  ; Pointer to next cluster in d:o
158 FPtr            resw 1                  ; Pointer to next char in buffer
159 CmdOptPtr       resw 1                  ; Pointer to first option on cmd line
160 KernelCNameLen  resw 1                  ; Length of unmangled kernel name
161 InitRDCNameLen  resw 1                  ; Length of unmangled initrd name
162 NextCharJump    resw 1                  ; Routine to interpret next print char
163 SetupSecs       resw 1                  ; Number of setup sectors
164 A20Test         resw 1                  ; Counter for testing status of A20
165 A20Type         resw 1                  ; A20 type
166 CmdLineLen      resw 1                  ; Length of command line including null
167 GraphXSize      resw 1                  ; Width of splash screen file
168 VGAPos          resw 1                  ; Pointer into VGA memory
169 VGACluster      resw 1                  ; Cluster pointer for VGA image file
170 VGAFilePtr      resw 1                  ; Pointer into VGAFileBuf
171 TextAttrBX      equ $
172 TextAttribute   resb 1                  ; Text attribute for message file
173 TextPage        resb 1                  ; Active display page
174 CursorDX        equ $
175 CursorCol       resb 1                  ; Cursor column for message file
176 CursorRow       resb 1                  ; Cursor row for message file
177 ScreenSize      equ $
178 VidCols         resb 1                  ; Columns on screen-1
179 VidRows         resb 1                  ; Rows on screen-1
180 FlowControl     equ $
181 FlowOutput      resb 1                  ; Outputs to assert for serial flow
182 FlowInput       resb 1                  ; Input bits for serial flow
183 FlowIgnore      resb 1                  ; Ignore input unless these bits set
184 RetryCount      resb 1                  ; Used for disk access retries
185 KbdFlags        resb 1                  ; Check for keyboard escapes
186 LoadFlags       resb 1                  ; Loadflags from kernel
187 A20Tries        resb 1                  ; Times until giving up on A20
188 FuncFlag        resb 1                  ; Escape sequences received from keyboard
189 DisplayMask     resb 1                  ; Display modes mask
190 MNameBuf        resb 11                 ; Generic mangled file name buffer
191 InitRD          resb 11                 ; initrd= mangled name
192 KernelCName     resb 13                 ; Unmangled kernel name
193 InitRDCName     resb 13                 ; Unmangled initrd name
194 TextColorReg    resb 17                 ; VGA color registers for text mode
195 VGAFileBuf      resb 13                 ; Unmangled VGA image name
196 VGAFileBufEnd   equ $
197 VGAFileMBuf     resb 11                 ; Mangled VGA image name
198
199                 section .text
200                 org 7C00h
201 ;
202 ; Some of the things that have to be saved very early are saved
203 ; "close" to the initial stack pointer offset, in order to
204 ; reduce the code size...
205 ;
206 StackBuf        equ $-32                ; Start the stack here (grow down - 4K)
207 PartInfo        equ StackBuf            ; Saved partition table entry
208 FloppyTable     equ PartInfo+16         ; Floppy info table (must follow PartInfo)
209 OrigFDCTabPtr   equ StackBuf-4          ; The high dword on the stack
210
211 ;
212 ; Primary entry point.  Tempting as though it may be, we can't put the
213 ; initial "cli" here; the jmp opcode in the first byte is part of the
214 ; "magic number" (using the term very loosely) for the DOS superblock.
215 ;
216 bootsec         equ $
217                 jmp short start         ; 2 bytes
218                 nop                     ; 1 byte
219 ;
220 ; "Superblock" follows -- it's in the boot sector, so it's already
221 ; loaded and ready for us
222 ;
223 bsOemName       db 'SYSLINUX'           ; The SYS command sets this, so...
224 ;
225 ; These are the fields we actually care about.  We end up expanding them
226 ; all to dword size early in the code, so generate labels for both
227 ; the expanded and unexpanded versions.
228 ;;
229 %macro          superb 1
230 bx %+ %1        equ SuperInfo+($-superblock)*8+4
231 bs %+ %1        equ $
232                 zb 1
233 %endmacro
234 %macro          superw 1
235 bx %+ %1        equ SuperInfo+($-superblock)*8
236 bs %+ %1        equ $
237                 zw 1
238 %endmacro
239 %macro          superd 1
240 bx %+ %1        equ $                   ; no expansion for dwords
241 bs %+ %1        equ $
242                 zd 1
243 %endmacro
244 superblock      equ $
245                 superw BytesPerSec
246                 superb SecPerClust
247                 superw ResSectors
248                 superb FATs
249                 superw RootDirEnts
250                 superw Sectors
251                 superb Media
252                 superw FATsecs
253                 superw SecPerTrack
254                 superw Heads
255 superinfo_size  equ ($-superblock)-1    ; How much to expand
256                 superd Hidden
257                 superd HugeSectors
258                 superb DriveNumber
259                 superb Reserved1
260                 superb BootSignature    ; 29h if the following fields exist
261                 superd VolumeID
262 bsVolumeLabel   zb 11
263 bsFileSysType   zb 8                    ; Must be FAT12 or FAT16 for this version
264 superblock_len  equ $-superblock
265
266 SecPerClust     equ bxSecPerClust
267 ;
268 ; Note we don't check the constraints above now; we did that at install
269 ; time (we hope!)
270 ;
271
272 ;floppy_table   equ $                   ; No sense in wasting memory, overwrite start
273
274 start:
275                 cli                     ; No interrupts yet, please
276                 cld                     ; Copy upwards
277 ;
278 ; Set up the stack
279 ;
280                 xor ax,ax
281                 mov ss,ax
282                 mov sp,StackBuf         ; Just below BSS
283                 mov es,ax
284 ;
285 ; DS:SI may contain a partition table entry.  Preserve it for us.
286 ;
287                 mov cx,8                ; Save partition info
288                 mov di,sp
289                 rep movsw
290
291                 mov ds,ax               ; Now we can initialize DS...
292
293                 mov [di+bsDriveNumber-FloppyTable],dl
294                 and dl,dl               ; If floppy disk (00-7F), assume no
295                 js harddisk             ; partition table
296 ;
297 ; Now sautee the BIOS floppy info block to that it will support decent-
298 ; size transfers; the floppy block is 11 bytes and is stored in the
299 ; INT 1Eh vector (brilliant waste of resources, eh?)
300 ;
301 ; Of course, if BIOSes had been properly programmed, we wouldn't have
302 ; had to waste precious space with this code.
303 ;
304                 mov bx,fdctab
305                 lfs si,[bx]             ; FS:SI -> original fdctab
306                 push fs                 ; Save on stack in case we need to bail
307                 push si
308                 mov cl,6                ; 12 bytes (CX == 0)
309                 ; es:di -> FloppyTable already
310                 ; This should be safe to do now, interrupts are off...
311                 mov [bx],di             ; FloppyTable
312                 mov [bx+2],ax           ; Segment 0
313                 fs rep movsw            ; Faster to move words
314                 mov cl,[bsSecPerTrack]  ; Patch the sector count
315                 mov [di-8],cl
316                 ; AX == 0 here
317                 int 13h                 ; Some BIOSes need this
318
319                 jmp short not_harddisk
320 ;
321 ; The drive number and possibly partition information was passed to us
322 ; by the BIOS or previous boot loader (MBR).  Current "best practice" is to
323 ; trust that rather than what the superblock contains.
324 ;
325 ; Would it be better to zero out bsHidden if we don't have a partition table?
326 ;
327 ; Note: di points to beyond the end of PartInfo
328 ;
329 harddisk:
330 ; This sanity check doesn't fit anymore...
331 ;               test byte [di-16],7Fh   ; Sanity check: "active flag" should
332 ;               jnz no_partition        ; be 00 or 80
333                 mov eax,[di-8]          ; Partition offset (dword)
334                 mov [bsHidden],eax
335 no_partition:
336 ;
337 ; Get disk drive parameters (don't trust the superblock.)  Don't do this for
338 ; floppy drives -- INT 13:08 on floppy drives will (may?) return info about
339 ; what the *drive* supports, not about the *media*.  Fortunately floppy disks
340 ; tend to have a fixed, well-defined geometry which is stored in the superblock.
341 ;
342                 ; DL == drive # still
343                 mov ah,08h
344                 int 13h
345                 jc no_driveparm
346                 and ah,ah
347                 jnz no_driveparm
348                 shr dx,8
349                 inc dx                  ; Contains # of heads - 1
350                 mov [bsHeads],dx
351                 and cx,3fh
352                 mov [bsSecPerTrack],cx
353 no_driveparm:
354 not_harddisk:
355 ;
356 ; Ready to enable interrupts, captain
357 ;
358                 sti
359 ;
360 ; Insane hack to expand the superblock to dwords
361 ;
362 expand_super:
363                 xor eax,eax
364                 mov es,ax                       ; INT 13:08 destroys ES
365                 mov si,superblock
366                 mov di,SuperInfo
367                 mov cl,superinfo_size           ; CH == 0
368 .loop:
369                 lodsw
370                 dec si
371                 stosd                           ; Store expanded word
372                 xor ah,ah
373                 stosd                           ; Store expanded byte
374                 loop .loop
375
376 ;
377 ; Now we have to do some arithmetric to figure out where things are located.
378 ; If Micro$oft had had brains they would already have done this for us,
379 ; and stored it in the superblock at format time, but here we go,
380 ; wasting precious boot sector space again...
381 ;
382 %define         Z di-superinfo_size*8-SuperInfo
383 debugentrypt:
384                 mov ax,[bxFATs]         ; Number of FATs (eax<31:16> == 0)
385                 mov edx,[Z+bxFATsecs]   ; Sectors/FAT
386                 mul edx                 ; Get the size of the FAT area
387                 ; edx <- 0
388                 add eax,[bxHidden]              ; Add hidden sectors
389                 add eax,[Z+bxResSectors]        ; And reserved sectors
390
391                 mov [RootDir],eax       ; Location of root directory
392                 mov [DataArea],eax      ; First data sector
393                 push eax
394
395                 mov eax,[Z+bxRootDirEnts]
396                 shl ax,5                ; Size of a directory entry
397                 mov bx,[Z+bxBytesPerSec]
398                 add ax,bx               ; Round up, not down
399                 dec ax
400                 div bx                  ; Now we have the size of the root dir
401                 mov [RootDirSize],ax
402                 mov [DirScanCtr],ax
403                 add bx,trackbuf-31
404                 mov [Z+EndofDirSec],bx  ; End of a single directory sector
405                 add [Z+DataArea],eax
406                 pop eax                 ; Reload root directory starting point
407
408 ;
409 ; Now the fun begins.  We have to search the root directory for
410 ; LDLINUX.SYS and load the first sector, so we have a little more
411 ; space to have fun with.  Then we can go chasing through the FAT.
412 ; Joy!!
413 ;
414 sd_nextsec:     push eax
415                 mov bx,trackbuf
416                 push bx
417                 call getonesec
418                 pop si
419 sd_nextentry:   mov cx,11
420                 cmp [si],ch             ; Directory high water mark
421                 je kaboom
422 ; This no longer fits... since we'd be dead anyway if there
423 ; was a nonfile named LDLINUX.SYS on the disk, it shouldn't
424 ; matter...
425 ;               test byte [si+11],18h   ; Must be a file
426 ;               jnz sd_not_file
427                 mov di,ldlinux_name
428                 push si
429                 repe cmpsb
430                 pop si
431                 je found_it
432 sd_not_file:    add si,byte 32          ; Distance to next
433                 cmp si,[EndofDirSec]
434                 jb sd_nextentry
435                 pop eax
436                 inc eax
437                 dec word [DirScanCtr]
438                 jnz sd_nextsec
439 ;
440 ; kaboom: write a message and bail out.
441 ;
442 kaboom:
443                 xor si,si
444                 mov ss,si               
445                 mov sp,StackBuf-4       ; Reset stack
446                 mov ds,si               ; Reset data segment
447                 pop dword [fdctab]      ; Restore FDC table
448 .patch:         mov si,bailmsg
449                 call writestr           ; Returns with AL = 0
450                 cbw                     ; AH <- 0
451                 int 16h                 ; Wait for keypress
452                 int 19h                 ; And try once more to boot...
453 .norge:         jmp short .norge        ; If int 19h returned; this is the end
454
455 ;
456 ; found_it: now we compute the location of the first sector, then
457 ;           load it and JUMP (since we're almost out of space)
458 ;
459 found_it:       ; Note: we actually leave two words on the stack here
460                 ; (who cares?)
461                 mov eax,[bxSecPerClust]
462                 mov bp,ax               ; Load an entire cluster
463                 movzx ebx,word [si+26]  ; First cluster
464                 mov [RunLinClust],bx    ; Save for later use
465                 dec bx                  ; First cluster is "cluster 2"
466                 dec bx
467                 mul ebx
468                 add eax,[DataArea]
469                 mov bx,ldlinux_sys
470                 call getlinsec
471                 mov si,bs_magic
472                 mov di,ldlinux_magic
473                 mov cx,magic_len
474                 repe cmpsb              ; Make sure that the bootsector
475                 jne kaboom              ; matches LDLINUX.SYS
476 ;
477 ; Done! Jump to the entry point!
478 ;
479                 jmp ldlinux_ent
480 ;
481 ;
482 ; writestr: write a null-terminated string to the console
483 ;
484 writestr:
485 .loop:          lodsb
486                 and al,al
487                 jz .return
488                 mov ah,0Eh              ; Write to screen as TTY
489                 mov bx,0007h            ; White on black, current page
490                 int 10h
491                 jmp short .loop
492 .return:        ret
493
494 ;
495 ; disk_error: decrement the retry count and bail if zero.
496 ;             This gets patched once we have more space to try to
497 ;             optimize transfer sizes on broken machines.
498 ;
499 disk_error:     dec si                  ; SI holds the disk retry counter
500                 jz kaboom
501                 ; End of patched "call" instruction!
502                 jmp short disk_try_again
503
504 ;
505 ; getonesec: like getlinsec, but pre-sets the count to 1
506 ;
507 getonesec:
508                 mov bp,1
509                 ; Fall through to getlinsec
510
511 ;
512 ; getlinsec: load a sequence of BP floppy sector given by the linear sector
513 ;            number in EAX into the buffer at ES:BX.  We try to optimize
514 ;            by loading up to a whole track at a time, but the user
515 ;            is responsible for not crossing a 64K boundary.
516 ;            (Yes, BP is weird for a count, but it was available...)
517 ;
518 ;            On return, BX points to the first byte after the transferred
519 ;            block.
520 ;
521 ;            The "stupid patch area" gets replaced by the code
522 ;            mov bp,1 ; nop ... (BD 01 00 90 90...) when installing with
523 ;            the -s option.
524 ;
525 ;            This routine assumes CS == DS.
526 ;
527 ; Stylistic note: use "xchg" instead of "mov" when the source is a register
528 ; that is dead from that point; this saves space.  However, please keep
529 ; the order to dst,src to keep things sane.
530 ;
531 getlinsec:
532                 mov esi,[bxSecPerTrack]
533                 ;
534                 ; Dividing by sectors to get (track,sector): we may have
535                 ; up to 2^18 tracks, so we need to use 32-bit arithmetric.
536                 ;
537                 xor edx,edx             ; Zero-extend LBA to 64 bits
538                 div esi
539                 xor cx,cx
540                 xchg cx,dx              ; CX <- sector index (0-based)
541                                         ; EDX <- 0
542                 ; eax = track #
543                 div dword [bxHeads]     ; Convert track to head/cyl
544                 ;
545                 ; Now we have AX = cyl, DX = head, CX = sector (0-based),
546                 ; BP = sectors to transfer, SI = bsSecPerTrack,
547                 ; ES:BX = data target
548                 ;
549 gls_nextchunk:  push si                 ; <A> bsSecPerTrack
550                 push bp                 ; <B> Sectors to transfer
551
552                 ; Important - this gets patched with a call.  The call
553                 ; assumes cx, si and bp are set up, and can modify bp
554                 ; and destroy si.  Until we have the space to do so,
555                 ; transfer one sector at a time.
556 gls_set_size:
557 __BEGIN_STUPID_PATCH_AREA:
558                 mov bp,1                ; 3 bytes, same as a call insn
559 __END_STUPID_PATCH_AREA:
560
561                 push ax                 ; <C> Cylinder #
562                 push dx                 ; <D> Head #
563
564                 push cx                 ; <E> Sector #
565                 shl ah,6                ; Because IBM was STOOPID
566                                         ; and thought 8 bits were enough
567                                         ; then thought 10 bits were enough...
568                 pop cx                  ; <E> Sector #
569                 push cx                 ; <E> Sector #
570                 inc cx                  ; Sector numbers are 1-based, sigh
571                 or cl,ah
572                 mov ch,al
573                 mov dh,dl
574                 mov dl,[bsDriveNumber]
575                 xchg ax,bp              ; Sector to transfer count
576                                         ; (xchg shorter than mov)
577                 mov si,retry_count      ; # of times to retry a disk access
578 ;
579 ; Do the disk transfer... save the registers in case we fail :(
580 ;
581 disk_try_again: 
582                 pusha                   ; <F>
583                 mov ah,02h              ; READ DISK
584                 int 13h
585                 popa                    ; <F>
586                 jc disk_error
587 ;
588 ; Disk access successful
589 ;
590                 pop cx                  ; <E> Sector #
591                 mov di,ax               ; Reduce sector left count
592                 mul word [bsBytesPerSec] ; Figure out how much to advance ptr
593                 add bx,ax               ; Update buffer location
594                 pop dx                  ; <D> Head #
595                 pop ax                  ; <C> Cyl #
596                 pop bp                  ; <B> Sectors left to transfer
597                 pop si                  ; <A> Number of sectors/track
598                 sub bp,di               ; Reduce with # of sectors just read
599                 jz writestr.return      ; Done!
600                 add cx,di
601                 cmp cx,si
602                 jb gls_nextchunk
603                 inc dx                  ; Next track on cyl
604                 cmp dx,[bsHeads]        ; Was this the last one?
605                 jb gls_nonewcyl
606                 inc ax                  ; If so, new cylinder
607                 xor dx,dx               ; First head on new cylinder
608 gls_nonewcyl:   sub cx,si               ; First sector on new track
609                 jmp short gls_nextchunk
610
611 bailmsg:        db 'Boot failed', 0Dh, 0Ah, 0
612
613 bs_checkpt      equ $                   ; Must be <= 7DEFh
614
615 %if 1
616 bs_checkpt_off  equ ($-$$)
617 %ifndef DEPEND
618 %if bs_checkpt_off > 1EFh
619 %error "Boot sector overflow"
620 %endif
621 %endif
622
623                 zb 1EFh-($-$$)
624 %endif
625 bs_magic        equ $                   ; From here to the magic_len equ
626                                         ; must match ldlinux_magic
627 ldlinux_name:   db 'LDLINUX SYS'        ; Looks like this in the root dir
628                 dd HEXDATE              ; Hopefully unique between compiles
629
630 bootsignature   dw 0AA55h
631 magic_len       equ $-bs_magic
632
633 ;
634 ; ===========================================================================
635 ;  End of boot sector
636 ; ===========================================================================
637 ;  Start of LDLINUX.SYS
638 ; ===========================================================================
639
640 ldlinux_sys:
641
642 syslinux_banner db 0Dh, 0Ah, 'SYSLINUX ', version_str, ' ', date, ' ', 0
643                 db 0Dh, 0Ah, 1Ah        ; EOF if we "type" this in DOS
644
645 ldlinux_magic   db 'LDLINUX SYS'
646                 dd HEXDATE
647                 dw 0AA55h
648
649 ;
650 ; This area is possibly patched by the installer.  It is located
651 ; immediately after the EOF + LDLINUX SYS + 4 bytes + 55 AA + alignment,
652 ; so we can find it algorithmically.
653 ;
654                 alignb 4
655 MaxTransfer     dw 00FFh                ; Absolutely maximum transfer size
656
657                 align 4
658 ldlinux_ent:
659
660 ; Note that some BIOSes are buggy and run the boot sector at 07C0:0000
661 ; instead of 0000:7C00 and the like.  We don't want to add anything
662 ; more to the boot sector, so it is written to not assume a fixed
663 ; value in CS, but we don't want to deal with that anymore from now
664 ; on.
665 ;
666                 jmp 0:.next
667 .next:
668
669 ;
670 ; Tell the user we got this far
671 ;
672                 mov si,syslinux_banner
673                 call writestr
674 ;
675 ; Remember, the boot sector loaded only the first cluster of LDLINUX.SYS.
676 ; We can really only rely on a single sector having been loaded.  Hence
677 ; we should load the FAT into RAM and start chasing pointers...
678 ;
679                 xor ax,ax
680                 cwd
681                 inc dx                          ; DX:AX <- 64K
682                 div word [bxBytesPerSec]        ; sectors/64K
683                 mov si,ax
684
685                 push es
686                 mov bx,fat_seg                  ; Load into fat_seg:0000
687                 mov es,bx
688                 
689                 mov eax,[bsHidden]              ; Hidden sectors
690                 add edx,[bxResSectors]
691                 add eax,edx
692                 mov ecx,[bxFATsecs]             ; Sectors/FAT
693 fat_load_loop:  
694                 mov ebp,ecx                     ; Make sure high EBP = 0
695                 cmp bp,si
696                 jna fat_load
697                 mov bp,si                       ; A full 64K moby
698 fat_load:       
699                 xor bx,bx                       ; Offset 0 in the current ES
700                 call getlinsecsr
701                 sub cx,bp
702                 jz fat_load_done                ; Last moby?
703                 add eax,ebp                     ; Advance sector count
704                 mov bx,es                       ; Next 64K moby
705                 add bx,1000h
706                 mov es,bx
707                 jmp short fat_load_loop
708 fat_load_done:
709                 pop es
710 ;
711 ; Fine, now we have the FAT in memory.  How big is a cluster, really?
712 ; Also figure out how many clusters will fit in an 8K buffer, and how
713 ; many sectors and bytes that is
714 ;
715                 mov edi,[bxBytesPerSec]         ; Used a lot below
716                 mov eax,[SecPerClust]
717                 mov si,ax                       ; Also used a lot
718                 mul di
719                 mov [ClustSize],eax             ; Bytes/cluster
720                 mov bx,ax
721                 mov ax,trackbufsize             ; High bit 0
722                 cwd
723                 div bx
724                 mov [BufSafe],ax                ; # of cluster in trackbuf
725                 mul si
726                 mov [BufSafeSec],ax
727                 mul di
728                 mov [BufSafeBytes],ax
729                 add ax,getcbuf                  ; Size of getcbuf is the same
730                 mov [EndOfGetCBuf],ax           ; as for trackbuf
731 ;
732 ; FAT12 or FAT16?  This computation is fscking ridiculous...
733 ;
734                 mov eax,[bxSectors]
735                 and ax,ax
736                 jnz have_secs
737                 mov eax,[bsHugeSectors]
738 have_secs:      add eax,[bsHidden]              ; These are not included
739                 sub eax,[RootDir]               ; Start of root directory
740                 movzx ebx,word [RootDirSize]
741                 sub eax,ebx                     ; Subtract root directory size
742                 xor edx,edx
743                 div esi                         ; Convert to clusters
744                 cmp ax,4086                     ; FAT12 limit
745                 jna is_fat12
746                 ; Patch the jump
747                 mov byte [nextcluster+1],nextcluster_fat16-(nextcluster+2)
748 is_fat12:
749
750 ;
751 ; Patch gls_set_size so we can transfer more than one sector at a time.
752 ;
753                 mov byte [gls_set_size],0xe8    ; E8 = CALL NEAR
754                 mov word [gls_set_size+1],do_gls_set_size-(gls_set_size+3)
755                 mov byte [disk_error],0xe8
756                 mov word [disk_error+1],do_disk_error-(disk_error+3)
757
758 ;
759 ; Now we read the rest of LDLINUX.SYS.  Don't bother loading the first
760 ; cluster again, though.
761 ;
762 load_rest:
763                 mov cx,[ClustSize]
764                 mov bx,ldlinux_sys
765                 add bx,cx
766                 mov si,[RunLinClust]
767                 call nextcluster
768                 xor dx,dx
769                 mov ax,ldlinux_len-1            ; To be on the safe side
770                 add ax,cx
771                 div cx                          ; the number of clusters
772                 dec ax                          ; We've already read one
773                 jz all_read_jmp
774                 mov cx,ax
775                 call getfssec
776 ;
777 ; All loaded up
778 ;
779 all_read_jmp:
780                 jmp all_read
781 ;
782 ; -----------------------------------------------------------------------------
783 ; Subroutines that have to be in the first sector
784 ; -----------------------------------------------------------------------------
785 ;
786 ; getfssec: Get multiple clusters from a file, given the starting cluster.
787 ;
788 ;       This routine makes sure the subtransfers do not cross a 64K boundary,
789 ;       and will correct the situation if it does, UNLESS *sectors* cross
790 ;       64K boundaries.
791 ;
792 ;       ES:BX   -> Buffer
793 ;       SI      -> Starting cluster number (2-based)
794 ;       CX      -> Cluster count (0FFFFh = until end of file)
795 ;
796                                                 ; 386 check
797 getfssec:
798 getfragment:    xor ebp,ebp                     ; Fragment sector count
799                 movzx eax,si                    ; Get sector address
800                 dec ax                          ; Convert to 0-based
801                 dec ax
802                 mul dword [SecPerClust]
803                 add eax,[DataArea]
804 getseccnt:                                      ; See if we can read > 1 clust
805                 add bp,[SecPerClust]
806                 dec cx                          ; Reduce clusters left to find
807                 lea di,[si+1]
808                 call nextcluster
809                 cmc
810                 jc gfs_eof                      ; At EOF?
811                 jcxz endfragment                ; Or was it the last we wanted?
812                 cmp si,di                       ; Is file continuous?
813                 jz getseccnt                    ; Yes, we can get
814 endfragment:    clc                             ; Not at EOF
815 gfs_eof:        pushf                           ; Remember EOF or not
816                 push si
817                 push cx
818 gfs_getchunk:
819                 push eax
820                 mov ax,es                       ; Check for 64K boundaries.
821                 shl ax,4
822                 add ax,bx
823                 xor dx,dx
824                 neg ax
825                 setz dl                         ; DX <- 1 if full 64K segment
826                 div word [bsBytesPerSec]        ; How many sectors fit?
827                 mov si,bp
828                 sub si,ax                       ; Compute remaining sectors
829                 jbe gfs_lastchunk
830                 mov bp,ax
831                 pop eax
832                 call getlinsecsr
833                 add eax,ebp                     ; EBP<31:16> == 0
834                 mov bp,si                       ; Remaining sector count
835                 jmp short gfs_getchunk
836 gfs_lastchunk:  pop eax
837                 call getlinsec
838                 pop cx
839                 pop si
840                 popf
841                 jcxz gfs_return                 ; If we hit the count limit
842                 jnc getfragment                 ; If we didn't hit EOF
843 gfs_return:     ret
844
845 ;
846 ; getlinsecsr: save registers, call getlinsec, restore registers
847 ;
848 getlinsecsr:    pushad
849                 call getlinsec
850                 popad
851                 ret
852
853 ;
854 ; nextcluster: Advance a cluster pointer in SI to the next cluster
855 ;              pointed at in the FAT tables.  CF=0 on return if end of file.
856 ;
857 nextcluster:
858                 jmp short nextcluster_fat12     ; This gets patched
859
860 nextcluster_fat12:
861                 push bx
862                 push ds
863                 mov bx,fat_seg
864                 mov ds,bx
865                 mov bx,si                       ; Multiply by 3/2
866                 shr bx,1                        ; CF now set if odd
867                 mov si,[si+bx]
868                 jnc nc_even
869                 shr si,4                        ; Needed for odd only
870 nc_even:
871                 and si,0FFFh
872                 cmp si,0FF0h                    ; Clears CF if at end of file
873                 pop ds
874                 pop bx
875 nc_return:      ret
876
877 ;
878 ; FAT16 decoding routine.  Note that a 16-bit FAT can be up to 128K,
879 ; so we have to decide if we're in the "low" or the "high" 64K-segment...
880 ;
881 nextcluster_fat16:
882                 push ax
883                 push ds
884                 mov ax,fat_seg
885                 shl si,1
886                 jnc .seg0
887                 mov ax,fat_seg+1000h
888 .seg0:          mov ds,ax
889                 mov si,[si]
890                 cmp si,0FFF0h
891                 pop ds
892                 pop ax
893                 ret
894
895 ;
896 ; Routine that controls how much we can transfer in one chunk.  Called
897 ; from gls_set_size in getlinsec.
898 ;
899 do_gls_set_size:
900                 sub si,cx               ; Sectors left on track
901                 cmp bp,si
902                 jna .lastchunk
903                 mov bp,si               ; No more than a trackful, please!
904 .lastchunk:
905                 cmp bp,[MaxTransfer]    ; Absolute maximum transfer size
906                 jna .oktransfer
907                 mov bp,[MaxTransfer]
908 .oktransfer:    
909                 ret
910
911 ;
912 ; This routine captures disk errors, and tries to decide if it is
913 ; time to reduce the transfer size.
914 ;
915 do_disk_error:
916                 dec si                  ; Decrement the retry counter
917                 jz kaboom               ; If expired, croak
918                 cmp si,2                ; If only 2 attempts left
919                 ja .nodanger
920                 mov al,1                ; Drop transfer size to 1
921                 jmp short .setsize
922 .nodanger:
923                 cmp si,retry_count-2
924                 ja .again               ; First time, just try again
925                 shr al,1                ; Otherwise, try to reduce
926                 adc al,0                ; the max transfer size, but not to 0
927 .setsize:
928                 mov [MaxTransfer],al
929 .again:
930                 ret
931
932 ;
933 ; Debug routine
934 ;
935 %ifdef debug
936 safedumpregs:
937                 cmp word [Debug_Magic],0D00Dh
938                 jnz nc_return
939                 jmp dumpregs
940 %endif
941
942 rl_checkpt      equ $                           ; Must be <= 8000h
943
944 rl_checkpt_off  equ ($-$$)
945 %ifndef DEPEND
946 %if rl_checkpt_off > 400h
947 %error "Sector 1 overflow"
948 %endif
949 %endif
950
951 ; ----------------------------------------------------------------------------
952 ;  End of code and data that have to be in the first sector
953 ; ----------------------------------------------------------------------------
954
955 all_read:
956 ;
957 ; Let the user (and programmer!) know we got this far.  This used to be
958 ; in Sector 1, but makes a lot more sense here.
959 ;
960                 mov si,copyright_str
961                 call writestr
962
963 ;
964 ; Common initialization code
965 ;
966 %include "cpuinit.inc"
967
968 ;
969 ; Initialization that does not need to go into the any of the pre-load
970 ; areas
971 ;
972                 ; Now set up screen parameters
973                 call adjust_screen
974
975                 ; Wipe the F-key area
976                 mov al,NULLFILE
977                 mov di,FKeyName
978                 mov cx,10*(1 << FILENAME_MAX_LG2)
979                 rep stosb
980
981 ;
982 ; Now, everything is "up and running"... patch kaboom for more
983 ; verbosity and using the full screen system
984 ;
985                 ; E9 = JMP NEAR
986                 mov dword [kaboom.patch],0e9h+((kaboom2-(kaboom.patch+3)) << 8)
987
988 ;
989 ; Compute some parameters that depend on cluster size
990 ;
991                 xor eax,eax
992                 cwd                             ; DX <- 0
993                 inc dx                          ; DX:AX <- 64K
994                 div word [ClustSize]
995                 mov [ClustPerMoby],eax          ; Clusters/64K
996
997 ;
998 ; Now we're all set to start with our *real* business.  First load the
999 ; configuration file (if any) and parse it.
1000 ;
1001 ; In previous versions I avoided using 32-bit registers because of a
1002 ; rumour some BIOSes clobbered the upper half of 32-bit registers at
1003 ; random.  I figure, though, that if there are any of those still left
1004 ; they probably won't be trying to install Linux on them...
1005 ;
1006 ; The code is still ripe with 16-bitisms, though.  Not worth the hassle
1007 ; to take'm out.  In fact, we may want to put them back if we're going
1008 ; to boot ELKS at some point.
1009 ;
1010                 mov si,linuxauto_cmd            ; Default command: "linux auto"
1011                 mov di,default_cmd
1012                 mov cx,linuxauto_len
1013                 rep movsb
1014
1015                 mov di,KbdMap                   ; Default keymap 1:1
1016                 xor al,al
1017                 inc ch                          ; CX <- 256
1018 mkkeymap:       stosb
1019                 inc al
1020                 loop mkkeymap
1021
1022 ;
1023 ; Load configuration file
1024 ;
1025                 mov di,syslinux_cfg
1026                 call open
1027                 jz no_config_file
1028 ;
1029 ; Now we have the config file open
1030 ;
1031                 call parse_config               ; Parse configuration file
1032 no_config_file:
1033 ;
1034 ; Check whether or not we are supposed to display the boot prompt.
1035 ;
1036 check_for_key:
1037                 cmp word [ForcePrompt],byte 0   ; Force prompt?
1038                 jnz enter_command
1039                 test byte [KbdFlags],5Bh        ; Caps, Scroll, Shift, Alt
1040                 jz auto_boot            ; If neither, default boot
1041
1042 enter_command:
1043                 mov si,boot_prompt
1044                 call cwritestr
1045
1046                 mov byte [FuncFlag],0           ; <Ctrl-F> not pressed
1047                 mov di,command_line
1048 ;
1049 ; get the very first character -- we can either time
1050 ; out, or receive a character press at this time.  Some dorky BIOSes stuff
1051 ; a return in the buffer on bootup, so wipe the keyboard buffer first.
1052 ;
1053 clear_buffer:   mov ah,1                        ; Check for pending char
1054                 int 16h
1055                 jz get_char_time
1056                 xor ax,ax                       ; Get char
1057                 int 16h
1058                 jmp short clear_buffer
1059 get_char_time:  
1060                 call vgashowcursor
1061                 mov cx,[KbdTimeOut]
1062                 and cx,cx
1063                 jz get_char                     ; Timeout == 0 -> no timeout
1064                 inc cx                          ; The first loop will happen
1065                                                 ; immediately as we don't
1066                                                 ; know the appropriate DX value
1067 time_loop:      push cx
1068 tick_loop:      push dx
1069                 call pollchar
1070                 jnz get_char_pop
1071                 xor ax,ax
1072                 int 1Ah                         ; Get time "of day"
1073                 pop ax
1074                 cmp dx,ax                       ; Has the timer advanced?
1075                 je tick_loop
1076                 pop cx
1077                 loop time_loop                  ; If so, decrement counter
1078                 call vgahidecursor
1079                 jmp command_done                ; Timeout!
1080
1081 get_char_pop:   pop eax                         ; Clear stack
1082 get_char:
1083                 call vgashowcursor
1084                 call getchar
1085                 call vgahidecursor
1086                 and al,al
1087                 jz func_key
1088
1089 got_ascii:      cmp al,7Fh                      ; <DEL> == <BS>
1090                 je backspace
1091                 cmp al,' '                      ; ASCII?
1092                 jb not_ascii
1093                 ja enter_char
1094                 cmp di,command_line             ; Space must not be first
1095                 je get_char
1096 enter_char:     test byte [FuncFlag],1
1097                 jz .not_ctrl_f
1098                 mov byte [FuncFlag],0
1099                 cmp al,'0'
1100                 jb .not_ctrl_f
1101                 je ctrl_f_0
1102                 cmp al,'9'
1103                 jbe ctrl_f
1104 .not_ctrl_f:    cmp di,max_cmd_len+command_line ; Check there's space
1105                 jnb get_char
1106                 stosb                           ; Save it
1107                 call writechr                   ; Echo to screen
1108 get_char_2:     jmp short get_char
1109 not_ascii:      mov byte [FuncFlag],0
1110                 cmp al,0Dh                      ; Enter
1111                 je command_done
1112                 cmp al,06h                      ; <Ctrl-F>
1113                 je set_func_flag
1114                 cmp al,08h                      ; Backspace
1115                 jne get_char
1116 backspace:      cmp di,command_line             ; Make sure there is anything
1117                 je get_char                     ; to erase
1118                 dec di                          ; Unstore one character
1119                 mov si,wipe_char                ; and erase it from the screen
1120                 call cwritestr
1121                 jmp short get_char_2
1122
1123 set_func_flag:
1124                 mov byte [FuncFlag],1
1125                 jmp short get_char_2
1126
1127 ctrl_f_0:       add al,10                       ; <Ctrl-F>0 == F10
1128 ctrl_f:         push di
1129                 sub al,'1'
1130                 xor ah,ah
1131                 jmp short show_help
1132
1133 func_key:
1134                 ; AL = 0 if we get here
1135                 push di
1136                 cmp ah,68                       ; F10
1137                 ja get_char_2
1138                 sub ah,59                       ; F1
1139                 jb get_char_2
1140                 xchg al,ah
1141 show_help:      ; AX = func key # (0 = F1, 9 = F10)
1142                 shl ax,FILENAME_MAX_LG2         ; Convert to pointer
1143                 xchg di,ax
1144                 add di,FKeyName
1145                 cmp byte [di],NULLFILE
1146                 je get_char_2                   ; Undefined F-key
1147                 call searchdir
1148                 jz fk_nofile
1149                 push si
1150                 call crlf
1151                 pop si
1152                 call get_msg_file
1153                 jmp short fk_wrcmd
1154 fk_nofile:
1155                 call crlf
1156 fk_wrcmd:
1157                 mov si,boot_prompt
1158                 call cwritestr
1159                 pop di                          ; Command line write pointer
1160                 push di
1161                 mov byte [di],0                 ; Null-terminate command line
1162                 mov si,command_line
1163                 call cwritestr                  ; Write command line so far
1164                 pop di
1165                 jmp short get_char_2
1166 auto_boot:
1167                 mov si,default_cmd
1168                 mov di,command_line
1169                 mov cx,(max_cmd_len+4) >> 2
1170                 rep movsd
1171                 jmp short load_kernel
1172 command_done:
1173                 call crlf
1174                 cmp di,command_line             ; Did we just hit return?
1175                 je auto_boot
1176                 xor al,al                       ; Store a final null
1177                 stosb
1178
1179 load_kernel:                                    ; Load the kernel now
1180 ;
1181 ; First we need to mangle the kernel name the way DOS would...
1182 ;
1183                 mov si,command_line
1184                 mov di,KernelName
1185                 push si
1186                 push di
1187                 call mangle_name
1188                 pop di
1189                 pop si
1190 ;
1191 ; Fast-forward to first option (we start over from the beginning, since
1192 ; mangle_name doesn't necessarily return a consistent ending state.)
1193 ;
1194 clin_non_wsp:   lodsb
1195                 cmp al,' '
1196                 ja clin_non_wsp
1197 clin_is_wsp:    and al,al
1198                 jz clin_opt_ptr
1199                 lodsb
1200                 cmp al,' '
1201                 jbe clin_is_wsp
1202 clin_opt_ptr:   dec si                          ; Point to first nonblank
1203                 mov [CmdOptPtr],si              ; Save ptr to first option
1204 ;
1205 ; Now check if it is a "virtual kernel"
1206 ;
1207                 mov cx,[VKernelCtr]
1208                 push ds
1209                 push word vk_seg
1210                 pop ds
1211                 cmp cx,byte 0
1212                 je not_vk
1213                 xor si,si                       ; Point to first vkernel
1214 vk_check:       pusha
1215                 mov cx,11
1216                 repe cmpsb                      ; Is this it?
1217                 je vk_found
1218                 popa
1219                 add si,vk_size
1220                 loop vk_check
1221 not_vk:         pop ds
1222 ;
1223 ; Not a "virtual kernel" - check that's OK and construct the command line
1224 ;
1225                 cmp word [AllowImplicit],byte 0
1226                 je bad_implicit
1227                 push es
1228                 push si
1229                 push di
1230                 mov di,real_mode_seg
1231                 mov es,di
1232                 mov si,AppendBuf
1233                 mov di,cmd_line_here
1234                 mov cx,[AppendLen]
1235                 rep movsb
1236                 mov [CmdLinePtr],di
1237                 pop di
1238                 pop si
1239                 pop es
1240                 mov bx,exten_count << 2         ; Alternates to try
1241 ;
1242 ; Find the kernel on disk
1243 ;
1244 get_kernel:     mov byte [KernelName+11],0      ; Zero-terminate filename/extension
1245                 mov eax,[KernelName+8]          ; Save initial extension
1246                 mov [OrigKernelExt],eax
1247 .search_loop:   push bx
1248                 mov di,KernelName               ; Search on disk
1249                 call searchdir
1250                 pop bx
1251                 jnz kernel_good
1252                 mov eax,[exten_table+bx]        ; Try a different extension
1253                 mov [KernelName+8],eax
1254                 sub bx,byte 4
1255                 jnb .search_loop
1256 bad_kernel:     
1257                 mov si,KernelName
1258                 mov di,KernelCName
1259                 push di
1260                 call unmangle_name              ; Get human form
1261                 mov si,err_notfound             ; Complain about missing kernel
1262                 call cwritestr
1263                 pop si                          ; KernelCName
1264                 call cwritestr
1265                 mov si,crlf_msg
1266                 jmp abort_load                  ; Ask user for clue
1267 ;
1268 ; bad_implicit: The user entered a nonvirtual kernel name, with "implicit 0"
1269 ;
1270 bad_implicit:   mov si,KernelName               ; For the error message
1271                 mov di,KernelCName
1272                 call unmangle_name
1273                 jmp short bad_kernel
1274 ;
1275 ; vk_found: We *are* using a "virtual kernel"
1276 ;
1277 vk_found:       popa
1278                 push di
1279                 mov di,VKernelBuf
1280                 mov cx,vk_size >> 2
1281                 rep movsd
1282                 push es                         ; Restore old DS
1283                 pop ds
1284                 push es
1285                 push word real_mode_seg
1286                 pop es
1287                 mov di,cmd_line_here
1288                 mov si,VKernelBuf+vk_append
1289                 mov cx,[VKernelBuf+vk_appendlen]
1290                 rep movsb
1291                 mov [CmdLinePtr],di             ; Where to add rest of cmd
1292                 pop es
1293                 pop di                          ; DI -> KernelName
1294                 push di 
1295                 mov si,VKernelBuf+vk_rname
1296                 mov cx,11                       ; We need ECX == CX later
1297                 rep movsb
1298                 pop di
1299                 xor bx,bx                       ; Try only one version
1300                 jmp get_kernel
1301 ;
1302 ; kernel_corrupt: Called if the kernel file does not seem healthy
1303 ;
1304 kernel_corrupt: mov si,err_notkernel
1305                 jmp abort_load
1306 ;
1307 ; This is it!  We have a name (and location on the disk)... let's load
1308 ; that sucker!!  First we have to decide what kind of file this is; base
1309 ; that decision on the file extension.  The following extensions are
1310 ; recognized:
1311 ;
1312 ; .com  - COMBOOT image
1313 ; .cbt  - COMBOOT image
1314 ; .bs   - Boot sector
1315 ; .0    - PXE bootstrap program (PXELINUX only)
1316 ; .bin  - Boot sector
1317 ; .bss  - Boot sector, but transfer over DOS superblock (SYSLINUX only)
1318 ; .img  - Floppy image (ISOLINUX only)
1319 ;
1320 ; Anything else is assumed to be a Linux kernel.
1321 ;
1322 kernel_good:
1323                 pusha
1324                 mov si,KernelName
1325                 mov di,KernelCName
1326                 call unmangle_name              ; Get human form
1327                 sub di,KernelCName
1328                 mov [KernelCNameLen],di
1329                 popa
1330
1331                 mov ecx,[KernelName+8]          ; Get (mangled) extension
1332                 and ecx,00ffffffh               ; 3 bytes only
1333                 cmp ecx,'COM'
1334                 je is_comboot_image
1335                 cmp ecx,'CBT'
1336                 je is_comboot_image
1337                 cmp ecx,'BS '
1338                 je is_bootsector
1339                 cmp ecx,'BIN'
1340                 je is_bootsector
1341                 cmp ecx,'BSS'
1342                 je is_bss_sector
1343                 ; Otherwise Linux kernel
1344
1345 ;
1346 ; Linux kernel loading code is common.
1347 ;
1348 %include "runkernel.inc"
1349
1350 ;
1351 ; COMBOOT-loading code
1352 ;
1353 %include "comboot.inc"
1354
1355 ;
1356 ; Boot sector loading code
1357 ;
1358 %include "bootsect.inc"
1359
1360 ;
1361 ; abort_check: let the user abort with <ESC> or <Ctrl-C>
1362 ;
1363 abort_check:
1364                 call pollchar
1365                 jz ac_ret1
1366                 pusha
1367                 call getchar
1368                 cmp al,27                       ; <ESC>
1369                 je ac_kill
1370                 cmp al,3                        ; <Ctrl-C>
1371                 jne ac_ret2
1372 ac_kill:        mov si,aborted_msg
1373
1374 ;
1375 ; abort_load: Called by various routines which wants to print a fatal
1376 ;             error message and return to the command prompt.  Since this
1377 ;             may happen at just about any stage of the boot process, assume
1378 ;             our state is messed up, and just reset the segment registers
1379 ;             and the stack forcibly.
1380 ;
1381 ;             SI    = offset (in _text) of error message to print
1382 ;
1383 abort_load:
1384                 mov ax,cs                       ; Restore CS = DS = ES
1385                 mov ds,ax
1386                 mov es,ax
1387                 cli
1388                 mov sp,StackBuf-2*3             ; Reset stack
1389                 mov ss,ax                       ; Just in case...
1390                 sti
1391                 call cwritestr                  ; Expects SI -> error msg
1392 al_ok:          jmp enter_command               ; Return to command prompt
1393 ;
1394 ; End of abort_check
1395 ;
1396 ac_ret2:        popa
1397 ac_ret1:        ret
1398
1399 ;
1400 ; searchdir: Search the root directory for a pre-mangled filename in
1401 ;            DS:DI.  This routine is similar to the one in the boot
1402 ;            sector, but is a little less Draconian when it comes to
1403 ;            error handling, plus it reads the root directory in
1404 ;            larger chunks than a sector at a time (which is probably
1405 ;            a waste of coding effort, but I like to do things right).
1406 ;
1407 ;            FIXME: usually we can load the entire root dir in memory,
1408 ;            and files are usually at the beginning anyway.  It probably
1409 ;            would be worthwhile to remember if we have the first chunk
1410 ;            in memory and skip the load if that (it would speed up online
1411 ;            help, mainly.)
1412 ;
1413 ;            NOTE: This file considers finding a zero-length file an
1414 ;            error.  This is so we don't have to deal with that special
1415 ;            case elsewhere in the program (most loops have the test
1416 ;            at the end).
1417 ;
1418 ;            If successful:
1419 ;               ZF clear
1420 ;               SI      = cluster # for the first cluster
1421 ;               DX:AX   = file length in bytes
1422 ;            If unsuccessful
1423 ;               ZF set
1424 ;
1425
1426 searchdir:
1427                 mov ax,[bsRootDirEnts]
1428                 mov [DirScanCtr],ax
1429                 mov ax,[RootDirSize]
1430                 mov [DirBlocksLeft],ax
1431                 mov eax,[RootDir]
1432 scan_group:
1433                 movzx ebp,word [DirBlocksLeft]
1434                 and bp,bp
1435                 jz dir_return
1436                 cmp bp,[BufSafeSec]
1437                 jna load_last
1438                 mov bp,[BufSafeSec]
1439 load_last:
1440                 sub [DirBlocksLeft],bp
1441                 push eax
1442                 mov ax,[bsBytesPerSec]
1443                 mul bp
1444                 add ax,trackbuf-31
1445                 mov [EndofDirSec],ax    ; End of loaded
1446                 pop eax
1447                 mov bx,trackbuf
1448                 call getlinsecsr
1449                 mov si,trackbuf
1450 dir_test_name:  cmp byte [si],0         ; Directory high water mark
1451                 je dir_return           ; Failed
1452                 test byte [si+11],18h   ; Check it really is a file
1453                 jnz dir_not_this
1454                 push di
1455                 push si
1456                 mov cx,11               ; Filename = 11 bytes
1457                 repe cmpsb
1458                 pop si
1459                 pop di
1460                 je dir_success
1461 dir_not_this:   add si,byte 32
1462                 dec word [DirScanCtr]
1463                 jz dir_return           ; Out of it...
1464                 cmp si,[EndofDirSec]
1465                 jb dir_test_name
1466                 add eax,ebp             ; Increment linear sector number
1467                 jmp short scan_group
1468 dir_success:
1469                 mov ax,[si+28]          ; Length of file
1470                 mov dx,[si+30]
1471                 mov si,[si+26]          ; Cluster pointer
1472                 mov bx,ax
1473                 or bx,dx                ; Sets ZF iff DX:AX is zero
1474 dir_return:
1475                 ret
1476
1477 ;
1478 ; writechr:     Write a single character in AL to the console without
1479 ;               mangling any registers
1480 ;
1481 writechr:
1482                 call write_serial       ; write to serial port if needed
1483                 pushfd
1484                 pushad
1485                 mov ah,0Eh
1486                 mov bx,0007h            ; white text on this page
1487                 int 10h
1488                 popad
1489                 popfd
1490                 ret
1491
1492 ;
1493 ;
1494 ; kaboom2: once everything is loaded, replace the part of kaboom
1495 ;          starting with "kaboom.patch" with this part
1496
1497 kaboom2:
1498                 mov si,err_bootfailed
1499                 call cwritestr
1500                 call getchar
1501                 call vgaclearmode
1502                 int 19h                 ; And try once more to boot...
1503 .norge:         jmp short .norge        ; If int 19h returned; this is the end
1504
1505 ;
1506 ; mangle_name: Mangle a DOS filename pointed to by DS:SI into a buffer pointed
1507 ;              to by ES:DI; ends on encountering any whitespace
1508 ;
1509
1510 mangle_name:
1511                 mov cx,11                       ; # of bytes to write
1512 mn_loop:
1513                 lodsb
1514                 cmp al,' '                      ; If control or space, end
1515                 jna mn_end
1516                 cmp al,'.'                      ; Period -> space-fill
1517                 je mn_is_period
1518                 cmp al,'a'
1519                 jb mn_not_lower
1520                 cmp al,'z'
1521                 ja mn_not_uslower
1522                 sub al,020h
1523                 jmp short mn_not_lower
1524 mn_is_period:   mov al,' '                      ; We need to space-fill
1525 mn_period_loop: cmp cx,3                        ; If <= 3 characters left
1526                 jbe mn_loop                     ; Just ignore it
1527                 stosb                           ; Otherwise, write a period
1528                 loop mn_period_loop             ; Dec CX and (always) jump
1529 mn_not_uslower: cmp al,ucase_low
1530                 jb mn_not_lower
1531                 cmp al,ucase_high
1532                 ja mn_not_lower
1533                 mov bx,ucase_tab-ucase_low
1534                 cs xlatb
1535 mn_not_lower:   stosb
1536                 loop mn_loop                    ; Don't continue if too long
1537 mn_end:
1538                 mov al,' '                      ; Space-fill name
1539                 rep stosb                       ; Doesn't do anything if CX=0
1540                 ret                             ; Done
1541
1542 ;
1543 ; Upper-case table for extended characters; this is technically code page 865,
1544 ; but code page 437 users will probably not miss not being able to use the
1545 ; cent sign in kernel images too much :-)
1546 ;
1547 ; The table only covers the range 129 to 164; the rest we can deal with.
1548 ;
1549 ucase_low       equ 129
1550 ucase_high      equ 164
1551 ucase_tab       db 154, 144, 'A', 142, 'A', 143, 128, 'EEEIII'
1552                 db 142, 143, 144, 146, 146, 'O', 153, 'OUUY', 153, 154
1553                 db 157, 156, 157, 158, 159, 'AIOU', 165
1554
1555 ;
1556 ; unmangle_name: Does the opposite of mangle_name; converts a DOS-mangled
1557 ;                filename to the conventional representation.  This is needed
1558 ;                for the BOOT_IMAGE= parameter for the kernel.
1559 ;                NOTE: A 13-byte buffer is mandatory, even if the string is
1560 ;                known to be shorter.
1561 ;
1562 ;                DS:SI -> input mangled file name
1563 ;                ES:DI -> output buffer
1564 ;
1565 ;                On return, DI points to the first byte after the output name,
1566 ;                which is set to a null byte.
1567 ;
1568 unmangle_name:
1569                 push si                 ; Save pointer to original name
1570                 mov cx,8
1571                 mov bp,di
1572 un_copy_body:   lodsb
1573                 call lower_case
1574                 stosb
1575                 cmp al,' '
1576                 jbe un_cb_space
1577                 mov bp,di               ; Position of last nonblank+1
1578 un_cb_space:    loop un_copy_body
1579                 mov di,bp
1580                 mov al,'.'              ; Don't save
1581                 stosb
1582                 mov cx,3
1583 un_copy_ext:    lodsb
1584                 call lower_case
1585                 stosb
1586                 cmp al,' '
1587                 jbe un_ce_space
1588                 mov bp,di
1589 un_ce_space:    loop un_copy_ext
1590                 mov di,bp
1591                 mov byte [es:di], 0
1592                 pop si
1593                 ret
1594
1595 ;
1596 ; lower_case: Lower case a character in AL
1597 ;
1598 lower_case:
1599                 cmp al,'A'
1600                 jb lc_ret
1601                 cmp al,'Z'
1602                 ja lc_1
1603                 or al,20h
1604                 ret
1605 lc_1:           cmp al,lcase_low
1606                 jb lc_ret
1607                 cmp al,lcase_high
1608                 ja lc_ret
1609                 push bx
1610                 mov bx,lcase_tab-lcase_low
1611                 cs xlatb
1612                 pop bx
1613 lc_ret:         ret
1614
1615 ; -----------------------------------------------------------------------------
1616 ;  Common modules
1617 ; -----------------------------------------------------------------------------
1618
1619 %include "getc.inc"             ; getc et al
1620 %include "conio.inc"            ; Console I/O
1621 %include "writestr.inc"         ; String output
1622 %include "parseconfig.inc"      ; High-level config file handling
1623 %include "parsecmd.inc"         ; Low-level config file handling
1624 %include "bcopy32.inc"          ; 32-bit bcopy
1625 %include "loadhigh.inc"         ; Load a file into high memory
1626 %include "font.inc"             ; VGA font stuff
1627 %include "graphics.inc"         ; VGA graphics
1628
1629 ; -----------------------------------------------------------------------------
1630 ;  Begin data section
1631 ; -----------------------------------------------------------------------------
1632
1633 CR              equ 13          ; Carriage Return
1634 LF              equ 10          ; Line Feed
1635 FF              equ 12          ; Form Feed
1636 BS              equ  8          ; Backspace
1637
1638 ;
1639 ; Lower-case table for codepage 865
1640 ;
1641 lcase_low       equ 128
1642 lcase_high      equ 165
1643 lcase_tab       db 135, 129, 130, 131, 132, 133, 134, 135, 136, 137, 138
1644                 db 139, 140, 141, 132, 134, 130, 145, 145, 147, 148, 149
1645                 db 150, 151, 152, 148, 129, 155, 156, 155, 158, 159, 160
1646                 db 161, 162, 163, 164, 164
1647
1648 copyright_str   db ' Copyright (C) 1994-', year, ' H. Peter Anvin'
1649                 db CR, LF, 0
1650 boot_prompt     db 'boot: ', 0
1651 wipe_char       db BS, ' ', BS, 0
1652 err_notfound    db 'Could not find kernel image: ',0
1653 err_notkernel   db CR, LF, 'Invalid or corrupt kernel image.', CR, LF, 0
1654 err_not386      db 'It appears your computer uses a 286 or lower CPU.'
1655                 db CR, LF
1656                 db 'You cannot run Linux unless you have a 386 or higher CPU'
1657                 db CR, LF
1658                 db 'in your machine.  If you get this message in error, hold'
1659                 db CR, LF
1660                 db 'down the Ctrl key while booting, and I will take your'
1661                 db CR, LF
1662                 db 'word for it.', CR, LF, 0
1663 err_noram       db 'It appears your computer has less than 488K of low ("DOS")'
1664                 db CR, LF
1665                 db 'RAM.  Linux needs at least this amount to boot.  If you get'
1666                 db CR, LF
1667                 db 'this message in error, hold down the Ctrl key while'
1668                 db CR, LF
1669                 db 'booting, and I will take your word for it.', CR, LF, 0
1670 err_badcfg      db 'Unknown keyword in syslinux.cfg.', CR, LF, 0
1671 err_noparm      db 'Missing parameter in syslinux.cfg.', CR, LF, 0
1672 err_noinitrd    db CR, LF, 'Could not find ramdisk image: ', 0
1673 err_nohighmem   db 'Not enough memory to load specified kernel.', CR, LF, 0
1674 err_highload    db CR, LF, 'Kernel transfer failure.', CR, LF, 0
1675 err_oldkernel   db 'Cannot load a ramdisk with an old kernel image.'
1676                 db CR, LF, 0
1677 err_notdos      db ': attempted DOS system call', CR, LF, 0
1678 err_comlarge    db 'COMBOOT image too large.', CR, LF, 0
1679 err_a20         db CR, LF, 'A20 gate not responding!', CR, LF, 0
1680 err_bootfailed  db CR, LF, 'Boot failed: please change disks and press '
1681                 db 'a key to continue.', CR, LF, 0
1682 ready_msg       db 'Ready.', CR, LF, 0
1683 crlfloading_msg db CR, LF
1684 loading_msg     db 'Loading ', 0
1685 dotdot_msg      db '.'
1686 dot_msg         db '.', 0
1687 aborted_msg     db ' aborted.'                  ; Fall through to crlf_msg!
1688 crlf_msg        db CR, LF
1689 null_msg        db 0
1690 crff_msg        db CR, FF, 0
1691 syslinux_cfg    db 'SYSLINUXCFG'
1692 ;
1693 ; Command line options we'd like to take a look at
1694 ;
1695 ; mem= and vga= are handled as normal 32-bit integer values
1696 initrd_cmd      db 'initrd='
1697 initrd_cmd_len  equ 7
1698
1699 ;
1700 ; Config file keyword table
1701 ;
1702 %include "keywords.inc"
1703 ;
1704 ; Extensions to search for (in *reverse* order).  Note that the last
1705 ; (lexically first) entry in the table is a placeholder for the original
1706 ; extension, needed for error messages.  The exten_table is shifted so
1707 ; the table is 1-based; this is because a "loop" cx is used as index.
1708 ;
1709 exten_table:
1710 OrigKernelExt:  dd 0                    ; Original extension
1711                 db 'COM',0              ; COMBOOT (same as DOS)
1712                 db 'BS ',0              ; Boot Sector 
1713                 db 'BSS',0              ; Boot Sector (add superblock)
1714                 db 'CBT',0              ; COMBOOT (specific)
1715
1716 exten_count     equ (($-exten_table) >> 2) - 1  ; Number of alternates
1717 ;
1718 ; Misc initialized (data) variables
1719 ;
1720 %ifdef debug                            ; This code for debugging only
1721 debug_magic     dw 0D00Dh               ; Debug code sentinel
1722 %endif
1723 AppendLen       dw 0                    ; Bytes in append= command
1724 KbdTimeOut      dw 0                    ; Keyboard timeout (if any)
1725 CmdLinePtr      dw cmd_line_here        ; Command line advancing pointer
1726 initrd_flag     equ $
1727 initrd_ptr      dw 0                    ; Initial ramdisk pointer/flag
1728 VKernelCtr      dw 0                    ; Number of registered vkernels
1729 ForcePrompt     dw 0                    ; Force prompt
1730 AllowImplicit   dw 1                    ; Allow implicit kernels
1731 SerialPort      dw 0                    ; Serial port base (or 0 for no serial port)
1732 VGAFontSize     dw 16                   ; Defaults to 16 byte font
1733 UserFont        db 0                    ; Using a user-specified font
1734 ScrollAttribute db 07h                  ; White on black (for text mode)
1735 ;
1736 ; Stuff for the command line; we do some trickery here with equ to avoid
1737 ; tons of zeros appended to our file and wasting space
1738 ;
1739 linuxauto_cmd   db 'linux auto',0
1740 linuxauto_len   equ $-linuxauto_cmd
1741 boot_image      db 'BOOT_IMAGE='
1742 boot_image_len  equ $-boot_image
1743                 align 4, db 0           ; For the good of REP MOVSD
1744 command_line    equ $
1745 default_cmd     equ $+(max_cmd_len+2)
1746 ldlinux_end     equ default_cmd+(max_cmd_len+1)
1747 kern_cmd_len    equ ldlinux_end-command_line
1748 ldlinux_len     equ ldlinux_end-ldlinux_magic
1749 ;
1750 ; Put the getcbuf right after the code, aligned on a sector boundary
1751 ;
1752 end_of_code     equ (ldlinux_end-bootsec)+7C00h
1753 getcbuf         equ (end_of_code + 511) & 0FE00h
1754
1755 ; VGA font buffer at the end of memory (so loading a font works even
1756 ; in graphics mode.)
1757 vgafontbuf      equ 0E000h
1758
1759 ; This is a compile-time assert that we didn't run out of space
1760 %ifndef DEPEND
1761 %if (getcbuf+trackbufsize) > vgafontbuf
1762 %error "Out of memory, better reorganize something..."
1763 %endif
1764 %endif