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