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