syslinux-3.08-2 sources from FC4
[bootcd.git] / syslinux / ldlinux.asm
1 ; -*- fundamental -*- (asm-mode sucks)
2 ; $Id: ldlinux.asm,v 1.181 2005/01/18 13:13:50 hpa Exp $
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 ;   Copyright (C) 1994-2004  H. Peter Anvin
16 ;
17 ;  This program is free software; you can redistribute it and/or modify
18 ;  it under the terms of the GNU General Public License as published by
19 ;  the Free Software Foundation, Inc., 53 Temple Place Ste 330,
20 ;  Boston MA 02111-1307, USA; either version 2 of the License, or
21 ;  (at your option) any later version; incorporated herein by reference.
22
23 ; ****************************************************************************
24
25 %ifndef IS_MDSLINUX
26 %define IS_SYSLINUX 1
27 %endif
28 %include "macros.inc"
29 %include "config.inc"
30 %include "kernel.inc"
31 %include "bios.inc"
32 %include "tracers.inc"
33 %include "layout.inc"
34 ;
35 ; Some semi-configurable constants... change on your own risk.
36 ;
37 my_id           equ syslinux_id
38 FILENAME_MAX_LG2 equ 4                  ; log2(Max filename size Including final null)
39 FILENAME_MAX    equ 11                  ; Max mangled filename size
40 NULLFILE        equ ' '                 ; First char space == null filename
41 NULLOFFSET      equ 0                   ; Position in which to look
42 retry_count     equ 6                   ; How patient are we with the disk?
43 %assign HIGHMEM_SLOP 0                  ; Avoid this much memory near the top
44 LDLINUX_MAGIC   equ 0x3eb202fe          ; A random number to identify ourselves with
45
46 MAX_OPEN_LG2    equ 6                   ; log2(Max number of open files)
47 MAX_OPEN        equ (1 << MAX_OPEN_LG2)
48
49 SECTOR_SHIFT    equ 9
50 SECTOR_SIZE     equ (1 << SECTOR_SHIFT)
51
52 ;
53 ; This is what we need to do when idle
54 ;
55 %macro  RESET_IDLE 0
56         ; Nothing
57 %endmacro
58 %macro  DO_IDLE 0
59         ; Nothing
60 %endmacro
61
62 ;
63 ; The following structure is used for "virtual kernels"; i.e. LILO-style
64 ; option labels.  The options we permit here are `kernel' and `append
65 ; Since there is no room in the bottom 64K for all of these, we
66 ; stick them at vk_seg:0000 and copy them down before we need them.
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 ;
79 ; Segment assignments in the bottom 640K
80 ; Stick to the low 512K in case we're using something like M-systems flash
81 ; which load a driver into low RAM (evil!!)
82 ;
83 ; 0000h - main code/data segment (and BIOS segment)
84 ;
85 real_mode_seg   equ 4000h
86 cache_seg       equ 3000h               ; 64K area for metadata cache
87 vk_seg          equ 2000h               ; Virtual kernels
88 xfer_buf_seg    equ 1000h               ; Bounce buffer for I/O to high mem
89 comboot_seg     equ real_mode_seg       ; COMBOOT image loading zone
90
91 ;
92 ; File structure.  This holds the information for each currently open file.
93 ;
94                 struc open_file_t
95 file_sector     resd 1                  ; Sector pointer (0 = structure free)
96 file_left       resd 1                  ; Number of sectors left
97                 endstruc
98
99 %ifndef DEPEND
100 %if (open_file_t_size & (open_file_t_size-1))
101 %error "open_file_t is not a power of 2"
102 %endif
103 %endif
104
105 ; ---------------------------------------------------------------------------
106 ;   BEGIN CODE
107 ; ---------------------------------------------------------------------------
108
109 ;
110 ; Memory below this point is reserved for the BIOS and the MBR
111 ;
112                 section .earlybss
113 trackbufsize    equ 8192
114 trackbuf        resb trackbufsize       ; Track buffer goes here
115 getcbuf         resb trackbufsize
116                 ; ends at 4800h
117
118                 section .bss
119                 alignb 8
120
121                 ; Expanded superblock
122 SuperInfo       equ $
123                 resq 16                 ; The first 16 bytes expanded 8 times
124 FAT             resd 1                  ; Location of (first) FAT
125 RootDirArea     resd 1                  ; Location of root directory area
126 RootDir         resd 1                  ; Location of root directory proper
127 DataArea        resd 1                  ; Location of data area
128 RootDirSize     resd 1                  ; Root dir size in sectors
129 TotalSectors    resd 1                  ; Total number of sectors
130 EndSector       resd 1                  ; Location of filesystem end
131 ClustSize       resd 1                  ; Bytes/cluster
132 ClustMask       resd 1                  ; Sectors/cluster - 1
133 CopySuper       resb 1                  ; Distinguish .bs versus .bss
134 DriveNumber     resb 1                  ; BIOS drive number
135 ClustShift      resb 1                  ; Shift count for sectors/cluster
136 ClustByteShift  resb 1                  ; Shift count for bytes/cluster
137
138                 alignb open_file_t_size
139 Files           resb MAX_OPEN*open_file_t_size
140
141 ;
142 ; Constants for the xfer_buf_seg
143 ;
144 ; The xfer_buf_seg is also used to store message file buffers.  We
145 ; need two trackbuffers (text and graphics), plus a work buffer
146 ; for the graphics decompressor.
147 ;
148 xbs_textbuf     equ 0                   ; Also hard-coded, do not change
149 xbs_vgabuf      equ trackbufsize
150 xbs_vgatmpbuf   equ 2*trackbufsize
151
152
153                 section .text
154 ;
155 ; Some of the things that have to be saved very early are saved
156 ; "close" to the initial stack pointer offset, in order to
157 ; reduce the code size...
158 ;
159 StackBuf        equ $-44-32             ; Start the stack here (grow down - 4K)
160 PartInfo        equ StackBuf            ; Saved partition table entry
161 FloppyTable     equ PartInfo+16         ; Floppy info table (must follow PartInfo)
162 OrigFDCTabPtr   equ StackBuf-4          ; The high dword on the stack
163
164 ;
165 ; Primary entry point.  Tempting as though it may be, we can't put the
166 ; initial "cli" here; the jmp opcode in the first byte is part of the
167 ; "magic number" (using the term very loosely) for the DOS superblock.
168 ;
169 bootsec         equ $
170                 jmp short start         ; 2 bytes
171                 nop                     ; 1 byte
172 ;
173 ; "Superblock" follows -- it's in the boot sector, so it's already
174 ; loaded and ready for us
175 ;
176 bsOemName       db 'SYSLINUX'           ; The SYS command sets this, so...
177 ;
178 ; These are the fields we actually care about.  We end up expanding them
179 ; all to dword size early in the code, so generate labels for both
180 ; the expanded and unexpanded versions.
181 ;
182 %macro          superb 1
183 bx %+ %1        equ SuperInfo+($-superblock)*8+4
184 bs %+ %1        equ $
185                 zb 1
186 %endmacro
187 %macro          superw 1
188 bx %+ %1        equ SuperInfo+($-superblock)*8
189 bs %+ %1        equ $
190                 zw 1
191 %endmacro
192 %macro          superd 1
193 bx %+ %1        equ $                   ; no expansion for dwords
194 bs %+ %1        equ $
195                 zd 1
196 %endmacro
197 superblock      equ $
198                 superw BytesPerSec
199                 superb SecPerClust
200                 superw ResSectors
201                 superb FATs
202                 superw RootDirEnts
203                 superw Sectors
204                 superb Media
205                 superw FATsecs
206                 superw SecPerTrack
207                 superw Heads
208 superinfo_size  equ ($-superblock)-1    ; How much to expand
209                 superd Hidden
210                 superd HugeSectors
211                 ;
212                 ; This is as far as FAT12/16 and FAT32 are consistent
213                 ;
214                 zb 54                   ; FAT12/16 need 26 more bytes,
215                                         ; FAT32 need 54 more bytes
216 superblock_len  equ $-superblock
217
218 SecPerClust     equ bxSecPerClust
219 ;
220 ; Note we don't check the constraints above now; we did that at install
221 ; time (we hope!)
222 ;
223 start:
224                 cli                     ; No interrupts yet, please
225                 cld                     ; Copy upwards
226 ;
227 ; Set up the stack
228 ;
229                 xor ax,ax
230                 mov ss,ax
231                 mov sp,StackBuf         ; Just below BSS
232                 mov es,ax
233 ;
234 ; DS:SI may contain a partition table entry.  Preserve it for us.
235 ;
236                 mov cx,8                ; Save partition info
237                 mov di,sp
238                 rep movsw
239
240                 mov ds,ax               ; Now we can initialize DS...
241
242 ;
243 ; Now sautee the BIOS floppy info block to that it will support decent-
244 ; size transfers; the floppy block is 11 bytes and is stored in the
245 ; INT 1Eh vector (brilliant waste of resources, eh?)
246 ;
247 ; Of course, if BIOSes had been properly programmed, we wouldn't have
248 ; had to waste precious space with this code.
249 ;
250                 mov bx,fdctab
251                 lfs si,[bx]             ; FS:SI -> original fdctab
252                 push fs                 ; Save on stack in case we need to bail
253                 push si
254
255                 ; Save the old fdctab even if hard disk so the stack layout
256                 ; is the same.  The instructions above do not change the flags
257                 mov [DriveNumber],dl    ; Save drive number in DL
258                 and dl,dl               ; If floppy disk (00-7F), assume no
259                                         ; partition table
260                 js harddisk
261
262 floppy:
263                 mov cl,6                ; 12 bytes (CX == 0)
264                 ; es:di -> FloppyTable already
265                 ; This should be safe to do now, interrupts are off...
266                 mov [bx],di             ; FloppyTable
267                 mov [bx+2],ax           ; Segment 0
268                 fs rep movsw            ; Faster to move words
269                 mov cl,[bsSecPerTrack]  ; Patch the sector count
270                 mov [di-8],cl
271                 ; AX == 0 here
272                 int 13h                 ; Some BIOSes need this
273
274                 jmp short not_harddisk
275 ;
276 ; The drive number and possibly partition information was passed to us
277 ; by the BIOS or previous boot loader (MBR).  Current "best practice" is to
278 ; trust that rather than what the superblock contains.
279 ;
280 ; Would it be better to zero out bsHidden if we don't have a partition table?
281 ;
282 ; Note: di points to beyond the end of PartInfo
283 ;
284 harddisk:
285                 test byte [di-16],7Fh   ; Sanity check: "active flag" should
286                 jnz no_partition        ; be 00 or 80
287                 mov eax,[di-8]          ; Partition offset (dword)
288                 mov [bsHidden],eax
289 no_partition:
290 ;
291 ; Get disk drive parameters (don't trust the superblock.)  Don't do this for
292 ; floppy drives -- INT 13:08 on floppy drives will (may?) return info about
293 ; what the *drive* supports, not about the *media*.  Fortunately floppy disks
294 ; tend to have a fixed, well-defined geometry which is stored in the superblock.
295 ;
296                 ; DL == drive # still
297                 mov ah,08h
298                 int 13h
299                 jc no_driveparm
300                 and ah,ah
301                 jnz no_driveparm
302                 shr dx,8
303                 inc dx                  ; Contains # of heads - 1
304                 mov [bsHeads],dx
305                 and cx,3fh
306                 mov [bsSecPerTrack],cx
307 no_driveparm:
308 not_harddisk:
309 ;
310 ; Ready to enable interrupts, captain
311 ;
312                 sti
313
314
315 ;
316 ; Do we have EBIOS (EDD)?
317 ;
318 eddcheck:
319                 mov bx,55AAh
320                 mov ah,41h              ; EDD existence query
321                 mov dl,[DriveNumber]
322                 int 13h
323                 jc .noedd
324                 cmp bx,0AA55h
325                 jne .noedd
326                 test cl,1               ; Extended disk access functionality set
327                 jz .noedd
328                 ;
329                 ; We have EDD support...
330                 ;
331                 mov byte [getlinsec.jmp+1],getlinsec_ebios-(getlinsec.jmp+2)
332 .noedd:
333
334 ;
335 ; Load the first sector of LDLINUX.SYS; this used to be all proper
336 ; with parsing the superblock and root directory; it doesn't fit
337 ; together with EBIOS support, unfortunately.
338 ;
339                 mov eax,[FirstSector]   ; Sector start
340                 mov bx,ldlinux_sys      ; Where to load it
341                 call getonesec
342                 
343                 ; Some modicum of integrity checking
344                 cmp dword [ldlinux_magic],LDLINUX_MAGIC
345                 jne kaboom
346                 cmp dword [ldlinux_magic+4],HEXDATE
347                 jne kaboom
348
349                 ; Go for it...
350                 jmp ldlinux_ent
351
352 ;
353 ; kaboom: write a message and bail out.
354 ;
355 kaboom:
356                 xor si,si
357                 mov ss,si               
358                 mov sp,StackBuf-4       ; Reset stack
359                 mov ds,si               ; Reset data segment
360                 pop dword [fdctab]      ; Restore FDC table
361 .patch:         mov si,bailmsg
362                 call writestr           ; Returns with AL = 0
363                 cbw                     ; AH <- 0
364                 int 16h                 ; Wait for keypress
365                 int 19h                 ; And try once more to boot...
366 .norge:         jmp short .norge        ; If int 19h returned; this is the end
367
368 ;
369 ;
370 ; writestr: write a null-terminated string to the console
371 ;           This assumes we're on page 0.  This is only used for early
372 ;           messages, so it should be OK.
373 ;
374 writestr:
375 .loop:          lodsb
376                 and al,al
377                 jz .return
378                 mov ah,0Eh              ; Write to screen as TTY
379                 mov bx,0007h            ; Attribute
380                 int 10h
381                 jmp short .loop
382 .return:        ret
383
384 ;
385 ; xint13: wrapper for int 13h which will retry 6 times and then die,
386 ;         AND save all registers except BP
387 ;
388 xint13:
389 .again:
390                 mov bp,retry_count
391 .loop:          pushad
392                 int 13h
393                 popad
394                 jnc writestr.return
395                 dec bp
396                 jnz .loop
397 .disk_error:
398                 jmp strict near kaboom  ; Patched
399
400
401 ;
402 ; getonesec: get one disk sector
403 ;
404 getonesec:
405                 mov bp,1                ; One sector
406                 ; Fall through
407
408 ;
409 ; getlinsec: load a sequence of BP floppy sector given by the linear sector
410 ;            number in EAX into the buffer at ES:BX.  We try to optimize
411 ;            by loading up to a whole track at a time, but the user
412 ;            is responsible for not crossing a 64K boundary.
413 ;            (Yes, BP is weird for a count, but it was available...)
414 ;
415 ;            On return, BX points to the first byte after the transferred
416 ;            block.
417 ;
418 ;            This routine assumes CS == DS, and trashes most registers.
419 ;
420 ; Stylistic note: use "xchg" instead of "mov" when the source is a register
421 ; that is dead from that point; this saves space.  However, please keep
422 ; the order to dst,src to keep things sane.
423 ;
424 getlinsec:
425                 add eax,[bsHidden]              ; Add partition offset
426 .jmp:           jmp strict short getlinsec_cbios        ; This is patched
427
428 ;
429 ; getlinsec_ebios:
430 ;
431 ; getlinsec implementation for EBIOS (EDD)
432 ;
433 getlinsec_ebios:
434                 mov si,dapa                     ; Load up the DAPA
435                 mov [si+4],bx
436                 mov [si+6],es
437                 mov [si+8],eax
438 .loop:
439                 push bp                         ; Sectors left
440                 call maxtrans                   ; Enforce maximum transfer size
441 .bp_ok:
442                 mov [si+2],bp
443                 mov dl,[DriveNumber]
444                 mov ah,42h                      ; Extended Read
445                 call xint13
446                 pop bp
447                 movzx eax,word [si+2]           ; Sectors we read
448                 add [si+8],eax                  ; Advance sector pointer
449                 sub bp,ax                       ; Sectors left
450                 shl ax,9                        ; 512-byte sectors
451                 add [si+4],ax                   ; Advance buffer pointer
452                 and bp,bp
453                 jnz .loop
454                 mov eax,[si+8]                  ; Next sector
455                 mov bx,[si+4]                   ; Buffer pointer
456                 ret
457
458 ;
459 ; getlinsec_cbios:
460 ;
461 ; getlinsec implementation for legacy CBIOS
462 ;
463 getlinsec_cbios:
464 .loop:
465                 push eax
466                 push bp
467                 push bx
468
469                 movzx esi,word [bsSecPerTrack]
470                 movzx edi,word [bsHeads]
471                 ;
472                 ; Dividing by sectors to get (track,sector): we may have
473                 ; up to 2^18 tracks, so we need to use 32-bit arithmetric.
474                 ;
475                 xor edx,edx             ; Zero-extend LBA to 64 bits
476                 div esi
477                 xor cx,cx
478                 xchg cx,dx              ; CX <- sector index (0-based)
479                                         ; EDX <- 0
480                 ; eax = track #
481                 div edi                 ; Convert track to head/cyl
482                 ;
483                 ; Now we have AX = cyl, DX = head, CX = sector (0-based),
484                 ; BP = sectors to transfer, SI = bsSecPerTrack,
485                 ; ES:BX = data target
486                 ;
487
488                 call maxtrans                   ; Enforce maximum transfer size
489
490                 ; Must not cross track boundaries, so BP <= SI-CX
491                 sub si,cx
492                 cmp bp,si
493                 jna .bp_ok
494                 mov bp,si
495 .bp_ok: 
496
497                 shl ah,6                ; Because IBM was STOOPID
498                                         ; and thought 8 bits were enough
499                                         ; then thought 10 bits were enough...
500                 inc cx                  ; Sector numbers are 1-based, sigh
501                 or cl,ah
502                 mov ch,al
503                 mov dh,dl
504                 mov dl,[DriveNumber]
505                 xchg ax,bp              ; Sector to transfer count
506                 mov ah,02h              ; Read sectors
507                 call xint13
508                 movzx ecx,al
509                 shl ax,9                ; Convert sectors in AL to bytes in AX
510                 pop bx
511                 add bx,ax
512                 pop bp
513                 pop eax
514                 add eax,ecx
515                 sub bp,cx
516                 jnz .loop
517                 ret
518
519 ;
520 ; Truncate BP to MaxTransfer
521 ;
522 maxtrans:
523                 cmp bp,[MaxTransfer]
524                 jna .ok
525                 mov bp,[MaxTransfer]
526 .ok:            ret
527
528 ;
529 ; Error message on failure
530 ;
531 bailmsg:        db 'Boot failed', 0Dh, 0Ah, 0
532
533 ;
534 ; EBIOS disk address packet
535 ;
536                 align 4, db 0
537 dapa:
538                 dw 16                           ; Packet size
539 .count:         dw 0                            ; Block count
540 .off:           dw 0                            ; Offset of buffer
541 .seg:           dw 0                            ; Segment of buffer
542 .lba:           dd 0                            ; LBA (LSW)
543                 dd 0                            ; LBA (MSW)
544
545
546 %if 1
547 bs_checkpt_off  equ ($-$$)
548 %ifndef DEPEND
549 %if bs_checkpt_off > 1F8h
550 %error "Boot sector overflow"
551 %endif
552 %endif
553
554                 zb 1F8h-($-$$)
555 %endif
556 FirstSector     dd 0xDEADBEEF                   ; Location of sector 1
557 MaxTransfer     dw 0x007F                       ; Max transfer size
558 bootsignature   dw 0AA55h
559
560 ;
561 ; ===========================================================================
562 ;  End of boot sector
563 ; ===========================================================================
564 ;  Start of LDLINUX.SYS
565 ; ===========================================================================
566
567 ldlinux_sys:
568
569 syslinux_banner db 0Dh, 0Ah
570 %if IS_MDSLINUX
571                 db 'MDSLINUX '
572 %else
573                 db 'SYSLINUX '
574 %endif
575                 db version_str, ' ', date, ' ', 0
576                 db 0Dh, 0Ah, 1Ah        ; EOF if we "type" this in DOS
577
578                 align 8, db 0
579 ldlinux_magic   dd LDLINUX_MAGIC
580                 dd HEXDATE
581
582 ;
583 ; This area is patched by the installer.  It is found by looking for
584 ; LDLINUX_MAGIC, plus 8 bytes.
585 ;
586 patch_area:
587 LDLDwords       dw 0            ; Total dwords starting at ldlinux_sys
588 LDLSectors      dw 0            ; Number of sectors - (bootsec+this sec)
589 CheckSum        dd 0            ; Checksum starting at ldlinux_sys
590                                 ; value = LDLINUX_MAGIC - [sum of dwords]
591
592 ; Space for up to 64 sectors, the theoretical maximum
593 SectorPtrs      times 64 dd 0
594
595 ldlinux_ent:
596
597 ; Note that some BIOSes are buggy and run the boot sector at 07C0:0000
598 ; instead of 0000:7C00 and the like.  We don't want to add anything
599 ; more to the boot sector, so it is written to not assume a fixed
600 ; value in CS, but we don't want to deal with that anymore from now
601 ; on.
602 ;
603                 jmp 0:.next
604 .next:
605
606 ;
607 ; Tell the user we got this far
608 ;
609                 mov si,syslinux_banner
610                 call writestr
611
612 ;
613 ; Patch disk error handling
614 ;
615                 mov word [xint13.disk_error+1],do_disk_error-(xint13.disk_error+3)
616
617 ;
618 ; Now we read the rest of LDLINUX.SYS.  Don't bother loading the first
619 ; sector again, though.
620 ;
621 load_rest:
622                 mov si,SectorPtrs
623                 mov bx,7C00h+2*SECTOR_SIZE      ; Where we start loading
624                 mov cx,[LDLSectors]
625
626 .get_chunk:
627                 jcxz .done
628                 xor bp,bp
629                 lodsd                           ; First sector of this chunk
630
631                 mov edx,eax
632
633 .make_chunk:
634                 inc bp
635                 dec cx
636                 jz .chunk_ready
637                 inc edx                         ; Next linear sector
638                 cmp [esi],edx                   ; Does it match
639                 jnz .chunk_ready                ; If not, this is it
640                 add esi,4                       ; If so, add sector to chunk
641                 jmp short .make_chunk
642
643 .chunk_ready:
644                 call getlinsecsr
645                 shl bp,SECTOR_SHIFT
646                 add bx,bp
647                 jmp .get_chunk
648
649 .done:
650
651 ;
652 ; All loaded up, verify that we got what we needed.
653 ; Note: the checksum field is embedded in the checksum region, so
654 ; by the time we get to the end it should all cancel out.
655 ;
656 verify_checksum:
657                 mov si,ldlinux_sys
658                 mov cx,[LDLDwords]
659                 mov edx,-LDLINUX_MAGIC
660 .checksum:
661                 lodsd
662                 add edx,eax
663                 loop .checksum
664
665                 and edx,edx                     ; Should be zero
666                 jz all_read                     ; We're cool, go for it!
667
668 ;
669 ; Uh-oh, something went bad...
670 ;
671                 mov si,checksumerr_msg
672                 call writestr
673                 jmp kaboom
674
675 ;
676 ; -----------------------------------------------------------------------------
677 ; Subroutines that have to be in the first sector
678 ; -----------------------------------------------------------------------------
679
680 ;
681 ; getlinsecsr: save registers, call getlinsec, restore registers
682 ;
683 getlinsecsr:    pushad
684                 call getlinsec
685                 popad
686                 ret
687
688 ;
689 ; This routine captures disk errors, and tries to decide if it is
690 ; time to reduce the transfer size.
691 ;
692 do_disk_error:
693                 cmp ah,42h
694                 je .ebios
695                 shr al,1                ; Try reducing the transfer size
696                 mov [MaxTransfer],al    
697                 jz kaboom               ; If we can't, we're dead...
698                 jmp xint13              ; Try again
699 .ebios:
700                 push ax
701                 mov ax,[si+2]
702                 shr ax,1
703                 mov [MaxTransfer],ax
704                 mov [si+2],ax
705                 pop ax
706                 jmp xint13
707
708 ;
709 ; Checksum error message
710 ;
711 checksumerr_msg db 'Load error - ', 0   ; Boot failed appended
712
713 ;
714 ; Debug routine
715 ;
716 %ifdef debug
717 safedumpregs:
718                 cmp word [Debug_Magic],0D00Dh
719                 jnz nc_return
720                 jmp dumpregs
721 %endif
722
723 rl_checkpt      equ $                           ; Must be <= 8000h
724
725 rl_checkpt_off  equ ($-$$)
726 %if 0 ; ndef DEPEND
727 %if rl_checkpt_off > 400h
728 %error "Sector 1 overflow"
729 %endif
730 %endif
731
732 ; ----------------------------------------------------------------------------
733 ;  End of code and data that have to be in the first sector
734 ; ----------------------------------------------------------------------------
735
736 all_read:
737 ;
738 ; Let the user (and programmer!) know we got this far.  This used to be
739 ; in Sector 1, but makes a lot more sense here.
740 ;
741                 mov si,copyright_str
742                 call writestr
743
744
745 ;
746 ; Insane hack to expand the superblock to dwords
747 ;
748 expand_super:
749                 xor eax,eax
750                 mov si,superblock
751                 mov di,SuperInfo
752                 mov cx,superinfo_size
753 .loop:
754                 lodsw
755                 dec si
756                 stosd                           ; Store expanded word
757                 xor ah,ah
758                 stosd                           ; Store expanded byte
759                 loop .loop
760
761 ;
762 ; Compute some information about this filesystem.
763 ;
764
765 ; First, generate the map of regions
766 genfatinfo:
767                 mov edx,[bxSectors]
768                 and dx,dx
769                 jnz .have_secs
770                 mov edx,[bsHugeSectors]
771 .have_secs:
772                 mov [TotalSectors],edx
773
774                 add edx,eax
775                 mov [EndSector],edx
776
777                 mov eax,[bxResSectors]
778                 mov [FAT],eax                   ; Beginning of FAT
779                 mov edx,[bxFATsecs]
780                 and dx,dx
781                 jnz .have_fatsecs
782                 mov edx,[bootsec+36]            ; FAT32 BPB_FATsz32
783 .have_fatsecs:
784                 imul edx,[bxFATs]
785                 add eax,edx
786                 mov [RootDirArea],eax           ; Beginning of root directory
787                 mov [RootDir],eax               ; For FAT12/16 == root dir location
788
789                 mov edx,[bxRootDirEnts]
790                 add dx,SECTOR_SIZE/32-1
791                 shr dx,SECTOR_SHIFT-5
792                 mov [RootDirSize],edx
793                 add eax,edx
794                 mov [DataArea],eax              ; Beginning of data area
795
796 ; Next, generate a cluster size shift count and mask
797                 mov eax,[bxSecPerClust]
798                 bsr cx,ax
799                 mov [ClustShift],cl
800                 push cx
801                 add cl,9
802                 mov [ClustByteShift],cl
803                 pop cx
804                 dec ax
805                 mov [ClustMask],eax
806                 inc ax
807                 shl eax,9
808                 mov [ClustSize],eax
809
810 ;
811 ; FAT12, FAT16 or FAT28^H^H32?  This computation is fscking ridiculous.
812 ;
813 getfattype:
814                 mov eax,[EndSector]
815                 sub eax,[DataArea]
816                 shr eax,cl                      ; cl == ClustShift
817                 mov cl,nextcluster_fat12-(nextcluster+2)
818                 cmp eax,4085                    ; FAT12 limit
819                 jb .setsize
820                 mov cl,nextcluster_fat16-(nextcluster+2)
821                 cmp eax,65525                   ; FAT16 limit
822                 jb .setsize
823                 ;
824                 ; FAT32, root directory is a cluster chain
825                 ;
826                 mov cl,[ClustShift]
827                 mov eax,[bootsec+44]            ; Root directory cluster
828                 sub eax,2
829                 shl eax,cl
830                 add eax,[DataArea]
831                 mov [RootDir],eax
832                 mov cl,nextcluster_fat28-(nextcluster+2)
833 .setsize:
834                 mov byte [nextcluster+1],cl
835
836 ;
837 ; Common initialization code
838 ;
839 %include "cpuinit.inc"
840 %include "init.inc"
841
842 ;
843 ; Clear Files structures
844 ;
845                 mov di,Files
846                 mov cx,(MAX_OPEN*open_file_t_size)/4
847                 xor eax,eax
848                 rep stosd
849
850 ;
851 ; Initialize the metadata cache
852 ;
853                 call initcache
854
855 ;
856 ; Now, everything is "up and running"... patch kaboom for more
857 ; verbosity and using the full screen system
858 ;
859                 ; E9 = JMP NEAR
860                 mov dword [kaboom.patch],0e9h+((kaboom2-(kaboom.patch+3)) << 8)
861
862 ;
863 ; Now we're all set to start with our *real* business.  First load the
864 ; configuration file (if any) and parse it.
865 ;
866 ; In previous versions I avoided using 32-bit registers because of a
867 ; rumour some BIOSes clobbered the upper half of 32-bit registers at
868 ; random.  I figure, though, that if there are any of those still left
869 ; they probably won't be trying to install Linux on them...
870 ;
871 ; The code is still ripe with 16-bitisms, though.  Not worth the hassle
872 ; to take'm out.  In fact, we may want to put them back if we're going
873 ; to boot ELKS at some point.
874 ;
875
876 ;
877 ; Load configuration file
878 ;
879                 mov di,syslinux_cfg
880                 call open
881                 jz no_config_file
882
883 ;
884 ; Now we have the config file open.  Parse the config file and
885 ; run the user interface.
886 ;
887 %include "ui.inc"
888
889 ;
890 ; Linux kernel loading code is common.
891 ;
892 %include "runkernel.inc"
893
894 ;
895 ; COMBOOT-loading code
896 ;
897 %include "comboot.inc"
898 %include "com32.inc"
899 %include "cmdline.inc"
900
901 ;
902 ; Boot sector loading code
903 ;
904 %include "bootsect.inc"
905
906 ;
907 ; abort_check: let the user abort with <ESC> or <Ctrl-C>
908 ;
909 abort_check:
910                 call pollchar
911                 jz ac_ret1
912                 pusha
913                 call getchar
914                 cmp al,27                       ; <ESC>
915                 je ac_kill
916                 cmp al,3                        ; <Ctrl-C>
917                 jne ac_ret2
918 ac_kill:        mov si,aborted_msg
919
920 ;
921 ; abort_load: Called by various routines which wants to print a fatal
922 ;             error message and return to the command prompt.  Since this
923 ;             may happen at just about any stage of the boot process, assume
924 ;             our state is messed up, and just reset the segment registers
925 ;             and the stack forcibly.
926 ;
927 ;             SI    = offset (in _text) of error message to print
928 ;
929 abort_load:
930                 mov ax,cs                       ; Restore CS = DS = ES
931                 mov ds,ax
932                 mov es,ax
933                 cli
934                 mov sp,StackBuf-2*3             ; Reset stack
935                 mov ss,ax                       ; Just in case...
936                 sti
937                 call cwritestr                  ; Expects SI -> error msg
938 al_ok:          jmp enter_command               ; Return to command prompt
939 ;
940 ; End of abort_check
941 ;
942 ac_ret2:        popa
943 ac_ret1:        ret
944
945 ;
946 ; allocate_file: Allocate a file structure
947 ;
948 ;               If successful:
949 ;                 ZF set
950 ;                 BX = file pointer
951 ;               In unsuccessful:
952 ;                 ZF clear
953 ;
954 allocate_file:
955                 TRACER 'a'
956                 push cx
957                 mov bx,Files
958                 mov cx,MAX_OPEN
959 .check:         cmp dword [bx], byte 0
960                 je .found
961                 add bx,open_file_t_size         ; ZF = 0
962                 loop .check
963                 ; ZF = 0 if we fell out of the loop
964 .found:         pop cx
965                 ret
966
967 ;
968 ; searchdir:
969 ;            Search the root directory for a pre-mangled filename in DS:DI.
970 ;
971 ;            NOTE: This file considers finding a zero-length file an
972 ;            error.  This is so we don't have to deal with that special
973 ;            case elsewhere in the program (most loops have the test
974 ;            at the end).
975 ;
976 ;            If successful:
977 ;               ZF clear
978 ;               SI      = file pointer
979 ;               DX:AX   = file length in bytes
980 ;            If unsuccessful
981 ;               ZF set
982 ;
983
984 searchdir:
985                 call allocate_file
986                 jnz .alloc_failure
987
988                 push gs
989                 push es
990                 push ds
991                 pop es                          ; ES = DS
992
993                 mov eax,[RootDir]               ; First root directory sector
994
995 .scansector:
996                 call getcachesector
997                 ; GS:SI now points to this sector
998
999                 mov cx,SECTOR_SIZE/32           ; 32 == directory entry size
1000 .scanentry:
1001                 cmp byte [gs:si],0
1002                 jz .failure                     ; Hit directory high water mark
1003                 push cx
1004                 push si
1005                 push di
1006                 mov cx,11
1007                 gs repe cmpsb
1008                 pop di
1009                 pop si
1010                 pop cx
1011                 jz .found
1012                 add si,32
1013                 loop .scanentry
1014
1015                 call nextsector
1016                 jnc .scansector                 ; CF is set if we're at end
1017
1018                 ; If we get here, we failed
1019 .failure:
1020                 pop es
1021                 pop gs
1022 .alloc_failure:
1023                 xor ax,ax                       ; ZF <- 1
1024                 ret
1025 .found:
1026                 mov eax,[gs:si+28]              ; File size
1027                 add eax,SECTOR_SIZE-1
1028                 shr eax,SECTOR_SHIFT
1029                 jz .failure                     ; Zero-length file
1030                 mov [bx+4],eax
1031
1032                 mov cl,[ClustShift]
1033                 mov dx,[gs:si+20]               ; High cluster word
1034                 shl edx,16
1035                 mov dx,[gs:si+26]               ; Low cluster word
1036                 sub edx,2
1037                 shl edx,cl
1038                 add edx,[DataArea]
1039                 mov [bx],edx                    ; Starting sector
1040
1041                 mov eax,[gs:si+28]              ; File length again
1042                 mov dx,[gs:si+30]               ; 16-bitism, sigh
1043                 mov si,bx
1044                 and eax,eax                     ; ZF <- 0
1045
1046                 pop es
1047                 pop gs
1048                 ret
1049
1050 ;
1051 ; writechr:     Write a single character in AL to the console without
1052 ;               mangling any registers; handle video pages correctly.
1053 ;
1054 writechr:
1055                 call write_serial       ; write to serial port if needed
1056                 pushfd
1057                 test byte [cs:DisplayCon], 01h
1058                 jz .nothing
1059                 pushad
1060                 mov ah,0Eh
1061                 mov bl,07h              ; attribute
1062                 mov bh,[cs:BIOS_page]   ; current page
1063                 int 10h
1064                 popad
1065 .nothing:
1066                 popfd
1067                 ret
1068
1069 ;
1070 ;
1071 ; kaboom2: once everything is loaded, replace the part of kaboom
1072 ;          starting with "kaboom.patch" with this part
1073
1074 kaboom2:
1075                 mov si,err_bootfailed
1076                 call cwritestr
1077                 call getchar
1078                 call vgaclearmode
1079                 int 19h                 ; And try once more to boot...
1080 .norge:         jmp short .norge        ; If int 19h returned; this is the end
1081
1082 ;
1083 ; mangle_name: Mangle a DOS filename pointed to by DS:SI into a buffer pointed
1084 ;              to by ES:DI; ends on encountering any whitespace
1085 ;
1086
1087 mangle_name:
1088                 mov cx,11                       ; # of bytes to write
1089 mn_loop:
1090                 lodsb
1091                 cmp al,' '                      ; If control or space, end
1092                 jna mn_end
1093                 cmp al,'.'                      ; Period -> space-fill
1094                 je mn_is_period
1095                 cmp al,'a'
1096                 jb mn_not_lower
1097                 cmp al,'z'
1098                 ja mn_not_uslower
1099                 sub al,020h
1100                 jmp short mn_not_lower
1101 mn_is_period:   mov al,' '                      ; We need to space-fill
1102 mn_period_loop: cmp cx,3                        ; If <= 3 characters left
1103                 jbe mn_loop                     ; Just ignore it
1104                 stosb                           ; Otherwise, write a period
1105                 loop mn_period_loop             ; Dec CX and (always) jump
1106 mn_not_uslower: cmp al,ucase_low
1107                 jb mn_not_lower
1108                 cmp al,ucase_high
1109                 ja mn_not_lower
1110                 mov bx,ucase_tab-ucase_low
1111                 cs xlatb
1112 mn_not_lower:   stosb
1113                 loop mn_loop                    ; Don't continue if too long
1114 mn_end:
1115                 mov al,' '                      ; Space-fill name
1116                 rep stosb                       ; Doesn't do anything if CX=0
1117                 ret                             ; Done
1118
1119 ;
1120 ; Upper-case table for extended characters; this is technically code page 865,
1121 ; but code page 437 users will probably not miss not being able to use the
1122 ; cent sign in kernel images too much :-)
1123 ;
1124 ; The table only covers the range 129 to 164; the rest we can deal with.
1125 ;
1126 ucase_low       equ 129
1127 ucase_high      equ 164
1128 ucase_tab       db 154, 144, 'A', 142, 'A', 143, 128, 'EEEIII'
1129                 db 142, 143, 144, 146, 146, 'O', 153, 'OUUY', 153, 154
1130                 db 157, 156, 157, 158, 159, 'AIOU', 165
1131
1132 ;
1133 ; unmangle_name: Does the opposite of mangle_name; converts a DOS-mangled
1134 ;                filename to the conventional representation.  This is needed
1135 ;                for the BOOT_IMAGE= parameter for the kernel.
1136 ;                NOTE: A 13-byte buffer is mandatory, even if the string is
1137 ;                known to be shorter.
1138 ;
1139 ;                DS:SI -> input mangled file name
1140 ;                ES:DI -> output buffer
1141 ;
1142 ;                On return, DI points to the first byte after the output name,
1143 ;                which is set to a null byte.
1144 ;
1145 unmangle_name:
1146                 push si                 ; Save pointer to original name
1147                 mov cx,8
1148                 mov bp,di
1149 un_copy_body:   lodsb
1150                 call lower_case
1151                 stosb
1152                 cmp al,' '
1153                 jbe un_cb_space
1154                 mov bp,di               ; Position of last nonblank+1
1155 un_cb_space:    loop un_copy_body
1156                 mov di,bp
1157                 mov al,'.'              ; Don't save
1158                 stosb
1159                 mov cx,3
1160 un_copy_ext:    lodsb
1161                 call lower_case
1162                 stosb
1163                 cmp al,' '
1164                 jbe un_ce_space
1165                 mov bp,di
1166 un_ce_space:    loop un_copy_ext
1167                 mov di,bp
1168                 mov byte [es:di], 0
1169                 pop si
1170                 ret
1171
1172 ;
1173 ; lower_case: Lower case a character in AL
1174 ;
1175 lower_case:
1176                 cmp al,'A'
1177                 jb lc_ret
1178                 cmp al,'Z'
1179                 ja lc_1
1180                 or al,20h
1181                 ret
1182 lc_1:           cmp al,lcase_low
1183                 jb lc_ret
1184                 cmp al,lcase_high
1185                 ja lc_ret
1186                 push bx
1187                 mov bx,lcase_tab-lcase_low
1188                 cs xlatb
1189                 pop bx
1190 lc_ret:         ret
1191
1192 ;
1193 ; getfssec_edx: Get multiple sectors from a file
1194 ;
1195 ;       This routine makes sure the subtransfers do not cross a 64K boundary,
1196 ;       and will correct the situation if it does, UNLESS *sectors* cross
1197 ;       64K boundaries.
1198 ;
1199 ;       ES:BX   -> Buffer
1200 ;       EDX     -> Current sector number
1201 ;       CX      -> Sector count (0FFFFh = until end of file)
1202 ;                  Must not exceed the ES segment
1203 ;       Returns EDX=0, CF=1 on EOF (not necessarily error)
1204 ;       All arguments are advanced to reflect data read.
1205 ;
1206 getfssec_edx:
1207                 push ebp
1208                 push eax
1209 .getfragment:
1210                 xor ebp,ebp                     ; Fragment sector count
1211                 push edx                        ; Starting sector pointer
1212 .getseccnt:
1213                 inc bp
1214                 dec cx
1215                 jz .do_read
1216                 xor eax,eax
1217                 mov ax,es
1218                 shl ax,4
1219                 add ax,bx                       ; Now AX = how far into 64K block we are
1220                 not ax                          ; Bytes left in 64K block
1221                 inc eax
1222                 shr eax,SECTOR_SHIFT            ; Sectors left in 64K block
1223                 cmp bp,ax
1224                 jnb .do_read                    ; Unless there is at least 1 more sector room...
1225                 mov eax,edx                     ; Current sector
1226                 inc edx                         ; Predict it's the linearly next sector
1227                 call nextsector
1228                 jc .do_read
1229                 cmp edx,eax                     ; Did it match?
1230                 jz .getseccnt
1231 .do_read:
1232                 pop eax                         ; Starting sector pointer
1233                 call getlinsecsr
1234                 lea eax,[eax+ebp-1]             ; This is the last sector actually read
1235                 shl bp,9
1236                 add bx,bp                       ; Adjust buffer pointer
1237                 call nextsector
1238                 jc .eof
1239                 mov edx,eax
1240                 and cx,cx
1241                 jnz .getfragment
1242 .done:
1243                 pop eax
1244                 pop ebp
1245                 ret
1246 .eof:
1247                 xor edx,edx
1248                 stc
1249                 jmp .done
1250
1251 ;
1252 ; getfssec: Get multiple sectors from a file
1253 ;
1254 ;       Same as above, except SI is a pointer to a open_file_t
1255 ;
1256 ;       ES:BX   -> Buffer
1257 ;       DS:SI   -> Pointer to open_file_t
1258 ;       CX      -> Sector count (0FFFFh = until end of file)
1259 ;                  Must not exceed the ES segment
1260 ;       Returns CF=1 on EOF (not necessarily error)
1261 ;       All arguments are advanced to reflect data read.
1262 ;
1263 getfssec:
1264                 push edx
1265                 movzx edx,cx
1266                 cmp edx,[si+4]
1267                 jbe .sizeok
1268                 mov edx,[si+4]
1269                 mov cx,dx
1270 .sizeok:
1271                 sub [si+4],edx
1272                 mov edx,[si]
1273                 call getfssec_edx
1274                 mov [si],edx
1275                 pop edx
1276                 ret
1277
1278 ;
1279 ; nextcluster: Advance a cluster pointer in EDI to the next cluster
1280 ;              pointed at in the FAT tables.  CF=0 on return if end of file.
1281 ;
1282 nextcluster:
1283                 jmp strict short nextcluster_fat28      ; This gets patched
1284
1285 nextcluster_fat12:
1286                 push eax
1287                 push edx
1288                 push bx
1289                 push cx
1290                 push si
1291                 mov edx,edi
1292                 shr edi,1
1293                 pushf                   ; Save the shifted-out LSB (=CF)
1294                 add edx,edi
1295                 mov eax,edx
1296                 shr eax,9
1297                 call getfatsector
1298                 mov bx,dx
1299                 and bx,1FFh
1300                 mov cl,[gs:si+bx]
1301                 inc edx
1302                 mov eax,edx
1303                 shr eax,9
1304                 call getfatsector
1305                 mov bx,dx
1306                 and bx,1FFh
1307                 mov ch,[gs:si+bx]
1308                 popf
1309                 jnc .even
1310                 shr cx,4
1311 .even:          and cx,0FFFh
1312                 movzx edi,cx
1313                 cmp di,0FF0h
1314                 pop si
1315                 pop cx
1316                 pop bx
1317                 pop edx
1318                 pop eax
1319                 ret
1320
1321 ;
1322 ; FAT16 decoding routine.
1323 ;
1324 nextcluster_fat16:
1325                 push eax
1326                 push si
1327                 push bx
1328                 mov eax,edi
1329                 shr eax,SECTOR_SHIFT-1
1330                 call getfatsector
1331                 mov bx,di
1332                 add bx,bx
1333                 and bx,1FEh
1334                 movzx edi,word [gs:si+bx]
1335                 cmp di,0FFF0h
1336                 pop bx
1337                 pop si
1338                 pop eax
1339                 ret
1340 ;
1341 ; FAT28 ("FAT32") decoding routine.
1342 ;
1343 nextcluster_fat28:
1344                 push eax
1345                 push si
1346                 push bx
1347                 mov eax,edi
1348                 shr eax,SECTOR_SHIFT-2
1349                 call getfatsector
1350                 mov bx,di
1351                 add bx,bx
1352                 add bx,bx
1353                 and bx,1FCh
1354                 mov edi,dword [gs:si+bx]
1355                 and edi,0FFFFFFFh       ; 28 bits only
1356                 cmp edi,0FFFFFF0h
1357                 pop bx
1358                 pop si
1359                 pop eax
1360                 ret
1361
1362 ;
1363 ; nextsector:   Given a sector in EAX on input, return the next sector
1364 ;               of the same filesystem object, which may be the root
1365 ;               directory or a cluster chain.  Returns  EOF.
1366 ;
1367 ;               Assumes CS == DS.
1368 ;
1369 nextsector:
1370                 push edi
1371                 push edx
1372                 mov edx,[DataArea]
1373                 mov edi,eax
1374                 sub edi,edx
1375                 jae .isdata
1376
1377                 ; Root directory
1378                 inc eax
1379                 cmp eax,edx
1380                 cmc
1381                 jmp .done
1382
1383 .isdata:
1384                 not edi
1385                 test edi,[ClustMask]
1386                 jz .endcluster
1387
1388                 ; It's not the final sector in a cluster
1389                 inc eax
1390                 jmp .done
1391
1392 .endcluster:
1393                 push gs                 ; nextcluster trashes gs
1394                 push cx
1395                 not edi
1396                 mov cl,[ClustShift]
1397                 shr edi,cl
1398                 add edi,2
1399
1400                 ; Now EDI contains the cluster number
1401                 call nextcluster
1402                 cmc
1403                 jc .exit                ; There isn't anything else...
1404
1405                 ; New cluster number now in EDI
1406                 sub edi,2
1407                 shl edi,cl              ; CF <- 0, unless something is very wrong
1408                 lea eax,[edi+edx]
1409 .exit:
1410                 pop cx
1411                 pop gs
1412 .done:
1413                 pop edx
1414                 pop edi
1415                 ret
1416
1417 ;
1418 ; getfatsector: Check for a particular sector (in EAX) in the FAT cache,
1419 ;               and return a pointer in GS:SI, loading it if needed.
1420 ;
1421 ;               Assumes CS == DS.
1422 ;
1423 getfatsector:
1424                 add eax,[FAT]           ; FAT starting address
1425                 jmp getcachesector
1426
1427 ; -----------------------------------------------------------------------------
1428 ;  Common modules
1429 ; -----------------------------------------------------------------------------
1430
1431 %include "getc.inc"             ; getc et al
1432 %include "conio.inc"            ; Console I/O
1433 %include "writestr.inc"         ; String output
1434 %include "parseconfig.inc"      ; High-level config file handling
1435 %include "parsecmd.inc"         ; Low-level config file handling
1436 %include "bcopy32.inc"          ; 32-bit bcopy
1437 %include "loadhigh.inc"         ; Load a file into high memory
1438 %include "font.inc"             ; VGA font stuff
1439 %include "graphics.inc"         ; VGA graphics
1440 %include "highmem.inc"          ; High memory sizing
1441 %include "strcpy.inc"           ; strcpy()
1442 %include "cache.inc"            ; Metadata disk cache
1443
1444 ; -----------------------------------------------------------------------------
1445 ;  Begin data section
1446 ; -----------------------------------------------------------------------------
1447
1448                 section .data
1449 ;
1450 ; Lower-case table for codepage 865
1451 ;
1452 lcase_low       equ 128
1453 lcase_high      equ 165
1454 lcase_tab       db 135, 129, 130, 131, 132, 133, 134, 135, 136, 137, 138
1455                 db 139, 140, 141, 132, 134, 130, 145, 145, 147, 148, 149
1456                 db 150, 151, 152, 148, 129, 155, 156, 155, 158, 159, 160
1457                 db 161, 162, 163, 164, 164
1458
1459 copyright_str   db ' Copyright (C) 1994-', year, ' H. Peter Anvin'
1460                 db CR, LF, 0
1461 boot_prompt     db 'boot: ', 0
1462 wipe_char       db BS, ' ', BS, 0
1463 err_notfound    db 'Could not find kernel image: ',0
1464 err_notkernel   db CR, LF, 'Invalid or corrupt kernel image.', CR, LF, 0
1465 err_noram       db 'It appears your computer has less than '
1466                 asciidec dosram_k
1467                 db 'K of low ("DOS")'
1468                 db CR, LF
1469                 db 'RAM.  Linux needs at least this amount to boot.  If you get'
1470                 db CR, LF
1471                 db 'this message in error, hold down the Ctrl key while'
1472                 db CR, LF
1473                 db 'booting, and I will take your word for it.', CR, LF, 0
1474 err_badcfg      db 'Unknown keyword in syslinux.cfg.', CR, LF, 0
1475 err_noparm      db 'Missing parameter in syslinux.cfg.', CR, LF, 0
1476 err_noinitrd    db CR, LF, 'Could not find ramdisk image: ', 0
1477 err_nohighmem   db 'Not enough memory to load specified kernel.', CR, LF, 0
1478 err_highload    db CR, LF, 'Kernel transfer failure.', CR, LF, 0
1479 err_oldkernel   db 'Cannot load a ramdisk with an old kernel image.'
1480                 db CR, LF, 0
1481 err_notdos      db ': attempted DOS system call', CR, LF, 0
1482 err_comlarge    db 'COMBOOT image too large.', CR, LF, 0
1483 err_a20         db CR, LF, 'A20 gate not responding!', CR, LF, 0
1484 err_bootfailed  db CR, LF, 'Boot failed: please change disks and press '
1485                 db 'a key to continue.', CR, LF, 0
1486 ready_msg       db 'Ready.', CR, LF, 0
1487 crlfloading_msg db CR, LF
1488 loading_msg     db 'Loading ', 0
1489 dotdot_msg      db '.'
1490 dot_msg         db '.', 0
1491 aborted_msg     db ' aborted.'                  ; Fall through to crlf_msg!
1492 crlf_msg        db CR, LF
1493 null_msg        db 0
1494 crff_msg        db CR, FF, 0
1495 syslinux_cfg    db 'SYSLINUXCFG'                ; Mangled form
1496 ConfigName      db 'syslinux.cfg',0             ; Unmangled form
1497 %if IS_MDSLINUX
1498 manifest        db 'MANIFEST   '
1499 %endif
1500 ;
1501 ; Command line options we'd like to take a look at
1502 ;
1503 ; mem= and vga= are handled as normal 32-bit integer values
1504 initrd_cmd      db 'initrd='
1505 initrd_cmd_len  equ 7
1506
1507 ;
1508 ; Config file keyword table
1509 ;
1510 %include "keywords.inc"
1511
1512 ;
1513 ; Extensions to search for (in *forward* order).
1514 ;
1515 exten_table:    db 'CBT',0              ; COMBOOT (specific)
1516                 db 'BSS',0              ; Boot Sector (add superblock)
1517                 db 'BS ',0              ; Boot Sector 
1518                 db 'COM',0              ; COMBOOT (same as DOS)
1519                 db 'C32',0              ; COM32
1520 exten_table_end:
1521                 dd 0, 0                 ; Need 8 null bytes here
1522
1523 ;
1524 ; Misc initialized (data) variables
1525 ;
1526 %ifdef debug                            ; This code for debugging only
1527 debug_magic     dw 0D00Dh               ; Debug code sentinel
1528 %endif
1529
1530                 alignb 4, db 0
1531 BufSafe         dw trackbufsize/SECTOR_SIZE     ; Clusters we can load into trackbuf
1532 BufSafeSec      dw trackbufsize/SECTOR_SIZE     ; = how many sectors?
1533 BufSafeBytes    dw trackbufsize         ; = how many bytes?
1534 EndOfGetCBuf    dw getcbuf+trackbufsize ; = getcbuf+BufSafeBytes
1535 %ifndef DEPEND
1536 %if ( trackbufsize % SECTOR_SIZE ) != 0
1537 %error trackbufsize must be a multiple of SECTOR_SIZE
1538 %endif
1539 %endif