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