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