Form the EBIOS DAPA on the stack instead of assuming it doesn't get
[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 ;   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 .loop:
435                 push bp                         ; Sectors left
436                 call maxtrans                   ; Enforce maximum transfer size
437                 movzx ecx,bp                    ; Sectors we are about to read
438
439                 ; Form DAPA on stack
440                 push dword 0
441                 push eax
442                 push es
443                 push bx
444                 push bp
445                 push word 16
446                 mov si,sp
447                 mov dl,[DriveNumber]
448                 mov ah,42h                      ; Extended Read
449                 push ds
450                 push ss
451                 pop ds                          ; DS <- SS
452                 call xint13
453                 pop ds
454
455                 add sp,16                       ; Remove DAPA
456                 pop bp
457                 add eax,ecx                     ; Advance sector pointer
458                 sub bp,cx                       ; Sectors left
459                 shl cx,9                        ; 512-byte sectors
460                 add bx,cx                       ; Advance buffer pointer
461                 and bp,bp
462                 jnz .loop
463
464                 ret
465
466 ;
467 ; getlinsec_cbios:
468 ;
469 ; getlinsec implementation for legacy CBIOS
470 ;
471 getlinsec_cbios:
472 .loop:
473                 push eax
474                 push bp
475                 push bx
476
477                 movzx esi,word [bsSecPerTrack]
478                 movzx edi,word [bsHeads]
479                 ;
480                 ; Dividing by sectors to get (track,sector): we may have
481                 ; up to 2^18 tracks, so we need to use 32-bit arithmetric.
482                 ;
483                 xor edx,edx             ; Zero-extend LBA to 64 bits
484                 div esi
485                 xor cx,cx
486                 xchg cx,dx              ; CX <- sector index (0-based)
487                                         ; EDX <- 0
488                 ; eax = track #
489                 div edi                 ; Convert track to head/cyl
490                 ;
491                 ; Now we have AX = cyl, DX = head, CX = sector (0-based),
492                 ; BP = sectors to transfer, SI = bsSecPerTrack,
493                 ; ES:BX = data target
494                 ;
495
496                 call maxtrans                   ; Enforce maximum transfer size
497
498                 ; Must not cross track boundaries, so BP <= SI-CX
499                 sub si,cx
500                 cmp bp,si
501                 jna .bp_ok
502                 mov bp,si
503 .bp_ok: 
504
505                 shl ah,6                ; Because IBM was STOOPID
506                                         ; and thought 8 bits were enough
507                                         ; then thought 10 bits were enough...
508                 inc cx                  ; Sector numbers are 1-based, sigh
509                 or cl,ah
510                 mov ch,al
511                 mov dh,dl
512                 mov dl,[DriveNumber]
513                 xchg ax,bp              ; Sector to transfer count
514                 mov ah,02h              ; Read sectors
515                 call xint13
516                 movzx ecx,al
517                 shl ax,9                ; Convert sectors in AL to bytes in AX
518                 pop bx
519                 add bx,ax
520                 pop bp
521                 pop eax
522                 add eax,ecx
523                 sub bp,cx
524                 jnz .loop
525                 ret
526
527 ;
528 ; Truncate BP to MaxTransfer
529 ;
530 maxtrans:
531                 cmp bp,[MaxTransfer]
532                 jna .ok
533                 mov bp,[MaxTransfer]
534 .ok:            ret
535
536 ;
537 ; Error message on failure
538 ;
539 bailmsg:        db 'Boot failed', 0Dh, 0Ah, 0
540
541 %if 1
542 bs_checkpt_off  equ ($-$$)
543 %ifndef DEPEND
544 %if bs_checkpt_off > 1F8h
545 %error "Boot sector overflow"
546 %endif
547 %endif
548
549                 zb 1F8h-($-$$)
550 %endif
551 FirstSector     dd 0xDEADBEEF                   ; Location of sector 1
552 MaxTransfer     dw 0x007F                       ; Max transfer size
553 bootsignature   dw 0AA55h
554
555 ;
556 ; ===========================================================================
557 ;  End of boot sector
558 ; ===========================================================================
559 ;  Start of LDLINUX.SYS
560 ; ===========================================================================
561
562 ldlinux_sys:
563
564 syslinux_banner db 0Dh, 0Ah
565 %if IS_MDSLINUX
566                 db 'MDSLINUX '
567 %else
568                 db 'SYSLINUX '
569 %endif
570                 db version_str, ' ', date, ' ', 0
571                 db 0Dh, 0Ah, 1Ah        ; EOF if we "type" this in DOS
572
573                 align 8, db 0
574 ldlinux_magic   dd LDLINUX_MAGIC
575                 dd HEXDATE
576
577 ;
578 ; This area is patched by the installer.  It is found by looking for
579 ; LDLINUX_MAGIC, plus 8 bytes.
580 ;
581 patch_area:
582 LDLDwords       dw 0            ; Total dwords starting at ldlinux_sys
583 LDLSectors      dw 0            ; Number of sectors - (bootsec+this sec)
584 CheckSum        dd 0            ; Checksum starting at ldlinux_sys
585                                 ; value = LDLINUX_MAGIC - [sum of dwords]
586
587 ; Space for up to 64 sectors, the theoretical maximum
588 SectorPtrs      times 64 dd 0
589
590 ldlinux_ent:
591
592 ; Note that some BIOSes are buggy and run the boot sector at 07C0:0000
593 ; instead of 0000:7C00 and the like.  We don't want to add anything
594 ; more to the boot sector, so it is written to not assume a fixed
595 ; value in CS, but we don't want to deal with that anymore from now
596 ; on.
597 ;
598                 jmp 0:.next
599 .next:
600
601 ;
602 ; Tell the user we got this far
603 ;
604                 mov si,syslinux_banner
605                 call writestr
606
607 ;
608 ; Patch disk error handling
609 ;
610                 mov word [xint13.disk_error+1],do_disk_error-(xint13.disk_error+3)
611
612 ;
613 ; Now we read the rest of LDLINUX.SYS.  Don't bother loading the first
614 ; sector again, though.
615 ;
616 load_rest:
617                 mov si,SectorPtrs
618                 mov bx,7C00h+2*SECTOR_SIZE      ; Where we start loading
619                 mov cx,[LDLSectors]
620
621 .get_chunk:
622                 jcxz .done
623                 xor bp,bp
624                 lodsd                           ; First sector of this chunk
625
626                 mov edx,eax
627
628 .make_chunk:
629                 inc bp
630                 dec cx
631                 jz .chunk_ready
632                 inc edx                         ; Next linear sector
633                 cmp [esi],edx                   ; Does it match
634                 jnz .chunk_ready                ; If not, this is it
635                 add esi,4                       ; If so, add sector to chunk
636                 jmp short .make_chunk
637
638 .chunk_ready:
639                 call getlinsecsr
640                 shl bp,SECTOR_SHIFT
641                 add bx,bp
642                 jmp .get_chunk
643
644 .done:
645
646 ;
647 ; All loaded up, verify that we got what we needed.
648 ; Note: the checksum field is embedded in the checksum region, so
649 ; by the time we get to the end it should all cancel out.
650 ;
651 verify_checksum:
652                 mov si,ldlinux_sys
653                 mov cx,[LDLDwords]
654                 mov edx,-LDLINUX_MAGIC
655 .checksum:
656                 lodsd
657                 add edx,eax
658                 loop .checksum
659
660                 and edx,edx                     ; Should be zero
661                 jz all_read                     ; We're cool, go for it!
662
663 ;
664 ; Uh-oh, something went bad...
665 ;
666                 mov si,checksumerr_msg
667                 call writestr
668                 jmp kaboom
669
670 ;
671 ; -----------------------------------------------------------------------------
672 ; Subroutines that have to be in the first sector
673 ; -----------------------------------------------------------------------------
674
675 ;
676 ; getlinsecsr: save registers, call getlinsec, restore registers
677 ;
678 getlinsecsr:    pushad
679                 call getlinsec
680                 popad
681                 ret
682
683 ;
684 ; This routine captures disk errors, and tries to decide if it is
685 ; time to reduce the transfer size.
686 ;
687 do_disk_error:
688                 cmp ah,42h
689                 je .ebios
690                 shr al,1                ; Try reducing the transfer size
691                 mov [MaxTransfer],al    
692                 jz kaboom               ; If we can't, we're dead...
693                 jmp xint13              ; Try again
694 .ebios:
695                 push ax
696                 mov ax,[si+2]
697                 shr ax,1
698                 mov [MaxTransfer],ax
699                 mov [si+2],ax
700                 pop ax
701                 jmp xint13
702
703 ;
704 ; Checksum error message
705 ;
706 checksumerr_msg db 'Load error - ', 0   ; Boot failed appended
707
708 ;
709 ; Debug routine
710 ;
711 %ifdef debug
712 safedumpregs:
713                 cmp word [Debug_Magic],0D00Dh
714                 jnz nc_return
715                 jmp dumpregs
716 %endif
717
718 rl_checkpt      equ $                           ; Must be <= 8000h
719
720 rl_checkpt_off  equ ($-$$)
721 %if 0 ; ndef DEPEND
722 %if rl_checkpt_off > 400h
723 %error "Sector 1 overflow"
724 %endif
725 %endif
726
727 ; ----------------------------------------------------------------------------
728 ;  End of code and data that have to be in the first sector
729 ; ----------------------------------------------------------------------------
730
731 all_read:
732 ;
733 ; Let the user (and programmer!) know we got this far.  This used to be
734 ; in Sector 1, but makes a lot more sense here.
735 ;
736                 mov si,copyright_str
737                 call writestr
738
739
740 ;
741 ; Insane hack to expand the superblock to dwords
742 ;
743 expand_super:
744                 xor eax,eax
745                 mov si,superblock
746                 mov di,SuperInfo
747                 mov cx,superinfo_size
748 .loop:
749                 lodsw
750                 dec si
751                 stosd                           ; Store expanded word
752                 xor ah,ah
753                 stosd                           ; Store expanded byte
754                 loop .loop
755
756 ;
757 ; Compute some information about this filesystem.
758 ;
759
760 ; First, generate the map of regions
761 genfatinfo:
762                 mov edx,[bxSectors]
763                 and dx,dx
764                 jnz .have_secs
765                 mov edx,[bsHugeSectors]
766 .have_secs:
767                 mov [TotalSectors],edx
768
769                 add edx,eax
770                 mov [EndSector],edx
771
772                 mov eax,[bxResSectors]
773                 mov [FAT],eax                   ; Beginning of FAT
774                 mov edx,[bxFATsecs]
775                 and dx,dx
776                 jnz .have_fatsecs
777                 mov edx,[bootsec+36]            ; FAT32 BPB_FATsz32
778 .have_fatsecs:
779                 imul edx,[bxFATs]
780                 add eax,edx
781                 mov [RootDirArea],eax           ; Beginning of root directory
782                 mov [RootDir],eax               ; For FAT12/16 == root dir location
783
784                 mov edx,[bxRootDirEnts]
785                 add dx,SECTOR_SIZE/32-1
786                 shr dx,SECTOR_SHIFT-5
787                 mov [RootDirSize],edx
788                 add eax,edx
789                 mov [DataArea],eax              ; Beginning of data area
790
791 ; Next, generate a cluster size shift count and mask
792                 mov eax,[bxSecPerClust]
793                 bsr cx,ax
794                 mov [ClustShift],cl
795                 push cx
796                 add cl,9
797                 mov [ClustByteShift],cl
798                 pop cx
799                 dec ax
800                 mov [ClustMask],eax
801                 inc ax
802                 shl eax,9
803                 mov [ClustSize],eax
804
805 ;
806 ; FAT12, FAT16 or FAT28^H^H32?  This computation is fscking ridiculous.
807 ;
808 getfattype:
809                 mov eax,[EndSector]
810                 sub eax,[DataArea]
811                 shr eax,cl                      ; cl == ClustShift
812                 mov cl,nextcluster_fat12-(nextcluster+2)
813                 cmp eax,4085                    ; FAT12 limit
814                 jb .setsize
815                 mov cl,nextcluster_fat16-(nextcluster+2)
816                 cmp eax,65525                   ; FAT16 limit
817                 jb .setsize
818                 ;
819                 ; FAT32, root directory is a cluster chain
820                 ;
821                 mov cl,[ClustShift]
822                 mov eax,[bootsec+44]            ; Root directory cluster
823                 sub eax,2
824                 shl eax,cl
825                 add eax,[DataArea]
826                 mov [RootDir],eax
827                 mov cl,nextcluster_fat28-(nextcluster+2)
828 .setsize:
829                 mov byte [nextcluster+1],cl
830
831 ;
832 ; Common initialization code
833 ;
834 %include "cpuinit.inc"
835 %include "init.inc"
836
837 ;
838 ; Clear Files structures
839 ;
840                 mov di,Files
841                 mov cx,(MAX_OPEN*open_file_t_size)/4
842                 xor eax,eax
843                 rep stosd
844
845 ;
846 ; Initialize the metadata cache
847 ;
848                 call initcache
849
850 ;
851 ; Now, everything is "up and running"... patch kaboom for more
852 ; verbosity and using the full screen system
853 ;
854                 ; E9 = JMP NEAR
855                 mov dword [kaboom.patch],0e9h+((kaboom2-(kaboom.patch+3)) << 8)
856
857 ;
858 ; Now we're all set to start with our *real* business.  First load the
859 ; configuration file (if any) and parse it.
860 ;
861 ; In previous versions I avoided using 32-bit registers because of a
862 ; rumour some BIOSes clobbered the upper half of 32-bit registers at
863 ; random.  I figure, though, that if there are any of those still left
864 ; they probably won't be trying to install Linux on them...
865 ;
866 ; The code is still ripe with 16-bitisms, though.  Not worth the hassle
867 ; to take'm out.  In fact, we may want to put them back if we're going
868 ; to boot ELKS at some point.
869 ;
870
871 ;
872 ; Load configuration file
873 ;
874                 mov di,syslinux_cfg
875                 call open
876                 jz no_config_file
877
878 ;
879 ; Now we have the config file open.  Parse the config file and
880 ; run the user interface.
881 ;
882 %include "ui.inc"
883
884 ;
885 ; Linux kernel loading code is common.
886 ;
887 %include "runkernel.inc"
888
889 ;
890 ; COMBOOT-loading code
891 ;
892 %include "comboot.inc"
893 %include "com32.inc"
894 %include "cmdline.inc"
895
896 ;
897 ; Boot sector loading code
898 ;
899 %include "bootsect.inc"
900
901 ;
902 ; abort_check: let the user abort with <ESC> or <Ctrl-C>
903 ;
904 abort_check:
905                 call pollchar
906                 jz ac_ret1
907                 pusha
908                 call getchar
909                 cmp al,27                       ; <ESC>
910                 je ac_kill
911                 cmp al,3                        ; <Ctrl-C>
912                 jne ac_ret2
913 ac_kill:        mov si,aborted_msg
914
915 ;
916 ; abort_load: Called by various routines which wants to print a fatal
917 ;             error message and return to the command prompt.  Since this
918 ;             may happen at just about any stage of the boot process, assume
919 ;             our state is messed up, and just reset the segment registers
920 ;             and the stack forcibly.
921 ;
922 ;             SI    = offset (in _text) of error message to print
923 ;
924 abort_load:
925                 mov ax,cs                       ; Restore CS = DS = ES
926                 mov ds,ax
927                 mov es,ax
928                 cli
929                 mov sp,StackBuf-2*3             ; Reset stack
930                 mov ss,ax                       ; Just in case...
931                 sti
932                 call cwritestr                  ; Expects SI -> error msg
933 al_ok:          jmp enter_command               ; Return to command prompt
934 ;
935 ; End of abort_check
936 ;
937 ac_ret2:        popa
938 ac_ret1:        ret
939
940 ;
941 ; allocate_file: Allocate a file structure
942 ;
943 ;               If successful:
944 ;                 ZF set
945 ;                 BX = file pointer
946 ;               In unsuccessful:
947 ;                 ZF clear
948 ;
949 allocate_file:
950                 TRACER 'a'
951                 push cx
952                 mov bx,Files
953                 mov cx,MAX_OPEN
954 .check:         cmp dword [bx], byte 0
955                 je .found
956                 add bx,open_file_t_size         ; ZF = 0
957                 loop .check
958                 ; ZF = 0 if we fell out of the loop
959 .found:         pop cx
960                 ret
961
962 ;
963 ; searchdir:
964 ;            Search the root directory for a pre-mangled filename in DS:DI.
965 ;
966 ;            NOTE: This file considers finding a zero-length file an
967 ;            error.  This is so we don't have to deal with that special
968 ;            case elsewhere in the program (most loops have the test
969 ;            at the end).
970 ;
971 ;            If successful:
972 ;               ZF clear
973 ;               SI      = file pointer
974 ;               DX:AX   = file length in bytes
975 ;            If unsuccessful
976 ;               ZF set
977 ;
978
979 searchdir:
980                 call allocate_file
981                 jnz .alloc_failure
982
983                 push gs
984                 push es
985                 push ds
986                 pop es                          ; ES = DS
987
988                 mov eax,[RootDir]               ; First root directory sector
989
990 .scansector:
991                 call getcachesector
992                 ; GS:SI now points to this sector
993
994                 mov cx,SECTOR_SIZE/32           ; 32 == directory entry size
995 .scanentry:
996                 cmp byte [gs:si],0
997                 jz .failure                     ; Hit directory high water mark
998                 push cx
999                 push si
1000                 push di
1001                 mov cx,11
1002                 gs repe cmpsb
1003                 pop di
1004                 pop si
1005                 pop cx
1006                 jz .found
1007                 add si,32
1008                 loop .scanentry
1009
1010                 call nextsector
1011                 jnc .scansector                 ; CF is set if we're at end
1012
1013                 ; If we get here, we failed
1014 .failure:
1015                 pop es
1016                 pop gs
1017 .alloc_failure:
1018                 xor ax,ax                       ; ZF <- 1
1019                 ret
1020 .found:
1021                 mov eax,[gs:si+28]              ; File size
1022                 add eax,SECTOR_SIZE-1
1023                 shr eax,SECTOR_SHIFT
1024                 jz .failure                     ; Zero-length file
1025                 mov [bx+4],eax
1026
1027                 mov cl,[ClustShift]
1028                 mov dx,[gs:si+20]               ; High cluster word
1029                 shl edx,16
1030                 mov dx,[gs:si+26]               ; Low cluster word
1031                 sub edx,2
1032                 shl edx,cl
1033                 add edx,[DataArea]
1034                 mov [bx],edx                    ; Starting sector
1035
1036                 mov eax,[gs:si+28]              ; File length again
1037                 mov dx,[gs:si+30]               ; 16-bitism, sigh
1038                 mov si,bx
1039                 and eax,eax                     ; ZF <- 0
1040
1041                 pop es
1042                 pop gs
1043                 ret
1044
1045 ;
1046 ; writechr:     Write a single character in AL to the console without
1047 ;               mangling any registers; handle video pages correctly.
1048 ;
1049 writechr:
1050                 call write_serial       ; write to serial port if needed
1051                 pushfd
1052                 test byte [cs:DisplayCon], 01h
1053                 jz .nothing
1054                 pushad
1055                 mov ah,0Eh
1056                 mov bl,07h              ; attribute
1057                 mov bh,[cs:BIOS_page]   ; current page
1058                 int 10h
1059                 popad
1060 .nothing:
1061                 popfd
1062                 ret
1063
1064 ;
1065 ;
1066 ; kaboom2: once everything is loaded, replace the part of kaboom
1067 ;          starting with "kaboom.patch" with this part
1068
1069 kaboom2:
1070                 mov si,err_bootfailed
1071                 call cwritestr
1072                 call getchar
1073                 call vgaclearmode
1074                 int 19h                 ; And try once more to boot...
1075 .norge:         jmp short .norge        ; If int 19h returned; this is the end
1076
1077 ;
1078 ; mangle_name: Mangle a DOS filename pointed to by DS:SI into a buffer pointed
1079 ;              to by ES:DI; ends on encountering any whitespace
1080 ;
1081
1082 mangle_name:
1083                 mov cx,11                       ; # of bytes to write
1084 mn_loop:
1085                 lodsb
1086                 cmp al,' '                      ; If control or space, end
1087                 jna mn_end
1088                 cmp al,'.'                      ; Period -> space-fill
1089                 je mn_is_period
1090                 cmp al,'a'
1091                 jb mn_not_lower
1092                 cmp al,'z'
1093                 ja mn_not_uslower
1094                 sub al,020h
1095                 jmp short mn_not_lower
1096 mn_is_period:   mov al,' '                      ; We need to space-fill
1097 mn_period_loop: cmp cx,3                        ; If <= 3 characters left
1098                 jbe mn_loop                     ; Just ignore it
1099                 stosb                           ; Otherwise, write a period
1100                 loop mn_period_loop             ; Dec CX and (always) jump
1101 mn_not_uslower: cmp al,ucase_low
1102                 jb mn_not_lower
1103                 cmp al,ucase_high
1104                 ja mn_not_lower
1105                 mov bx,ucase_tab-ucase_low
1106                 cs xlatb
1107 mn_not_lower:   stosb
1108                 loop mn_loop                    ; Don't continue if too long
1109 mn_end:
1110                 mov al,' '                      ; Space-fill name
1111                 rep stosb                       ; Doesn't do anything if CX=0
1112                 ret                             ; Done
1113
1114 ;
1115 ; Upper-case table for extended characters; this is technically code page 865,
1116 ; but code page 437 users will probably not miss not being able to use the
1117 ; cent sign in kernel images too much :-)
1118 ;
1119 ; The table only covers the range 129 to 164; the rest we can deal with.
1120 ;
1121 ucase_low       equ 129
1122 ucase_high      equ 164
1123 ucase_tab       db 154, 144, 'A', 142, 'A', 143, 128, 'EEEIII'
1124                 db 142, 143, 144, 146, 146, 'O', 153, 'OUUY', 153, 154
1125                 db 157, 156, 157, 158, 159, 'AIOU', 165
1126
1127 ;
1128 ; unmangle_name: Does the opposite of mangle_name; converts a DOS-mangled
1129 ;                filename to the conventional representation.  This is needed
1130 ;                for the BOOT_IMAGE= parameter for the kernel.
1131 ;                NOTE: A 13-byte buffer is mandatory, even if the string is
1132 ;                known to be shorter.
1133 ;
1134 ;                DS:SI -> input mangled file name
1135 ;                ES:DI -> output buffer
1136 ;
1137 ;                On return, DI points to the first byte after the output name,
1138 ;                which is set to a null byte.
1139 ;
1140 unmangle_name:
1141                 push si                 ; Save pointer to original name
1142                 mov cx,8
1143                 mov bp,di
1144 un_copy_body:   lodsb
1145                 call lower_case
1146                 stosb
1147                 cmp al,' '
1148                 jbe un_cb_space
1149                 mov bp,di               ; Position of last nonblank+1
1150 un_cb_space:    loop un_copy_body
1151                 mov di,bp
1152                 mov al,'.'              ; Don't save
1153                 stosb
1154                 mov cx,3
1155 un_copy_ext:    lodsb
1156                 call lower_case
1157                 stosb
1158                 cmp al,' '
1159                 jbe un_ce_space
1160                 mov bp,di
1161 un_ce_space:    loop un_copy_ext
1162                 mov di,bp
1163                 mov byte [es:di], 0
1164                 pop si
1165                 ret
1166
1167 ;
1168 ; lower_case: Lower case a character in AL
1169 ;
1170 lower_case:
1171                 cmp al,'A'
1172                 jb lc_ret
1173                 cmp al,'Z'
1174                 ja lc_1
1175                 or al,20h
1176                 ret
1177 lc_1:           cmp al,lcase_low
1178                 jb lc_ret
1179                 cmp al,lcase_high
1180                 ja lc_ret
1181                 push bx
1182                 mov bx,lcase_tab-lcase_low
1183                 cs xlatb
1184                 pop bx
1185 lc_ret:         ret
1186
1187 ;
1188 ; getfssec_edx: Get multiple sectors from a file
1189 ;
1190 ;       This routine makes sure the subtransfers do not cross a 64K boundary,
1191 ;       and will correct the situation if it does, UNLESS *sectors* cross
1192 ;       64K boundaries.
1193 ;
1194 ;       ES:BX   -> Buffer
1195 ;       EDX     -> Current sector number
1196 ;       CX      -> Sector count (0FFFFh = until end of file)
1197 ;                  Must not exceed the ES segment
1198 ;       Returns EDX=0, CF=1 on EOF (not necessarily error)
1199 ;       All arguments are advanced to reflect data read.
1200 ;
1201 getfssec_edx:
1202                 push ebp
1203                 push eax
1204 .getfragment:
1205                 xor ebp,ebp                     ; Fragment sector count
1206                 push edx                        ; Starting sector pointer
1207 .getseccnt:
1208                 inc bp
1209                 dec cx
1210                 jz .do_read
1211                 xor eax,eax
1212                 mov ax,es
1213                 shl ax,4
1214                 add ax,bx                       ; Now AX = how far into 64K block we are
1215                 not ax                          ; Bytes left in 64K block
1216                 inc eax
1217                 shr eax,SECTOR_SHIFT            ; Sectors left in 64K block
1218                 cmp bp,ax
1219                 jnb .do_read                    ; Unless there is at least 1 more sector room...
1220                 mov eax,edx                     ; Current sector
1221                 inc edx                         ; Predict it's the linearly next sector
1222                 call nextsector
1223                 jc .do_read
1224                 cmp edx,eax                     ; Did it match?
1225                 jz .getseccnt
1226 .do_read:
1227                 pop eax                         ; Starting sector pointer
1228                 call getlinsecsr
1229                 lea eax,[eax+ebp-1]             ; This is the last sector actually read
1230                 shl bp,9
1231                 add bx,bp                       ; Adjust buffer pointer
1232                 call nextsector
1233                 jc .eof
1234                 mov edx,eax
1235                 and cx,cx
1236                 jnz .getfragment
1237 .done:
1238                 pop eax
1239                 pop ebp
1240                 ret
1241 .eof:
1242                 xor edx,edx
1243                 stc
1244                 jmp .done
1245
1246 ;
1247 ; getfssec: Get multiple sectors from a file
1248 ;
1249 ;       Same as above, except SI is a pointer to a open_file_t
1250 ;
1251 ;       ES:BX   -> Buffer
1252 ;       DS:SI   -> Pointer to open_file_t
1253 ;       CX      -> Sector count (0FFFFh = until end of file)
1254 ;                  Must not exceed the ES segment
1255 ;       Returns CF=1 on EOF (not necessarily error)
1256 ;       All arguments are advanced to reflect data read.
1257 ;
1258 getfssec:
1259                 push edx
1260                 movzx edx,cx
1261                 cmp edx,[si+4]
1262                 jbe .sizeok
1263                 mov edx,[si+4]
1264                 mov cx,dx
1265 .sizeok:
1266                 sub [si+4],edx
1267                 mov edx,[si]
1268                 call getfssec_edx
1269                 mov [si],edx
1270                 pop edx
1271                 ret
1272
1273 ;
1274 ; nextcluster: Advance a cluster pointer in EDI to the next cluster
1275 ;              pointed at in the FAT tables.  CF=0 on return if end of file.
1276 ;
1277 nextcluster:
1278                 jmp strict short nextcluster_fat28      ; This gets patched
1279
1280 nextcluster_fat12:
1281                 push eax
1282                 push edx
1283                 push bx
1284                 push cx
1285                 push si
1286                 mov edx,edi
1287                 shr edi,1
1288                 pushf                   ; Save the shifted-out LSB (=CF)
1289                 add edx,edi
1290                 mov eax,edx
1291                 shr eax,9
1292                 call getfatsector
1293                 mov bx,dx
1294                 and bx,1FFh
1295                 mov cl,[gs:si+bx]
1296                 inc edx
1297                 mov eax,edx
1298                 shr eax,9
1299                 call getfatsector
1300                 mov bx,dx
1301                 and bx,1FFh
1302                 mov ch,[gs:si+bx]
1303                 popf
1304                 jnc .even
1305                 shr cx,4
1306 .even:          and cx,0FFFh
1307                 movzx edi,cx
1308                 cmp di,0FF0h
1309                 pop si
1310                 pop cx
1311                 pop bx
1312                 pop edx
1313                 pop eax
1314                 ret
1315
1316 ;
1317 ; FAT16 decoding routine.
1318 ;
1319 nextcluster_fat16:
1320                 push eax
1321                 push si
1322                 push bx
1323                 mov eax,edi
1324                 shr eax,SECTOR_SHIFT-1
1325                 call getfatsector
1326                 mov bx,di
1327                 add bx,bx
1328                 and bx,1FEh
1329                 movzx edi,word [gs:si+bx]
1330                 cmp di,0FFF0h
1331                 pop bx
1332                 pop si
1333                 pop eax
1334                 ret
1335 ;
1336 ; FAT28 ("FAT32") decoding routine.
1337 ;
1338 nextcluster_fat28:
1339                 push eax
1340                 push si
1341                 push bx
1342                 mov eax,edi
1343                 shr eax,SECTOR_SHIFT-2
1344                 call getfatsector
1345                 mov bx,di
1346                 add bx,bx
1347                 add bx,bx
1348                 and bx,1FCh
1349                 mov edi,dword [gs:si+bx]
1350                 and edi,0FFFFFFFh       ; 28 bits only
1351                 cmp edi,0FFFFFF0h
1352                 pop bx
1353                 pop si
1354                 pop eax
1355                 ret
1356
1357 ;
1358 ; nextsector:   Given a sector in EAX on input, return the next sector
1359 ;               of the same filesystem object, which may be the root
1360 ;               directory or a cluster chain.  Returns  EOF.
1361 ;
1362 ;               Assumes CS == DS.
1363 ;
1364 nextsector:
1365                 push edi
1366                 push edx
1367                 mov edx,[DataArea]
1368                 mov edi,eax
1369                 sub edi,edx
1370                 jae .isdata
1371
1372                 ; Root directory
1373                 inc eax
1374                 cmp eax,edx
1375                 cmc
1376                 jmp .done
1377
1378 .isdata:
1379                 not edi
1380                 test edi,[ClustMask]
1381                 jz .endcluster
1382
1383                 ; It's not the final sector in a cluster
1384                 inc eax
1385                 jmp .done
1386
1387 .endcluster:
1388                 push gs                 ; nextcluster trashes gs
1389                 push cx
1390                 not edi
1391                 mov cl,[ClustShift]
1392                 shr edi,cl
1393                 add edi,2
1394
1395                 ; Now EDI contains the cluster number
1396                 call nextcluster
1397                 cmc
1398                 jc .exit                ; There isn't anything else...
1399
1400                 ; New cluster number now in EDI
1401                 sub edi,2
1402                 shl edi,cl              ; CF <- 0, unless something is very wrong
1403                 lea eax,[edi+edx]
1404 .exit:
1405                 pop cx
1406                 pop gs
1407 .done:
1408                 pop edx
1409                 pop edi
1410                 ret
1411
1412 ;
1413 ; getfatsector: Check for a particular sector (in EAX) in the FAT cache,
1414 ;               and return a pointer in GS:SI, loading it if needed.
1415 ;
1416 ;               Assumes CS == DS.
1417 ;
1418 getfatsector:
1419                 add eax,[FAT]           ; FAT starting address
1420                 jmp getcachesector
1421
1422 ; -----------------------------------------------------------------------------
1423 ;  Common modules
1424 ; -----------------------------------------------------------------------------
1425
1426 %include "getc.inc"             ; getc et al
1427 %include "conio.inc"            ; Console I/O
1428 %include "writestr.inc"         ; String output
1429 %include "parseconfig.inc"      ; High-level config file handling
1430 %include "parsecmd.inc"         ; Low-level config file handling
1431 %include "bcopy32.inc"          ; 32-bit bcopy
1432 %include "loadhigh.inc"         ; Load a file into high memory
1433 %include "font.inc"             ; VGA font stuff
1434 %include "graphics.inc"         ; VGA graphics
1435 %include "highmem.inc"          ; High memory sizing
1436 %include "strcpy.inc"           ; strcpy()
1437 %include "cache.inc"            ; Metadata disk cache
1438
1439 ; -----------------------------------------------------------------------------
1440 ;  Begin data section
1441 ; -----------------------------------------------------------------------------
1442
1443                 section .data
1444 ;
1445 ; Lower-case table for codepage 865
1446 ;
1447 lcase_low       equ 128
1448 lcase_high      equ 165
1449 lcase_tab       db 135, 129, 130, 131, 132, 133, 134, 135, 136, 137, 138
1450                 db 139, 140, 141, 132, 134, 130, 145, 145, 147, 148, 149
1451                 db 150, 151, 152, 148, 129, 155, 156, 155, 158, 159, 160
1452                 db 161, 162, 163, 164, 164
1453
1454 copyright_str   db ' Copyright (C) 1994-', year, ' H. Peter Anvin'
1455                 db CR, LF, 0
1456 boot_prompt     db 'boot: ', 0
1457 wipe_char       db BS, ' ', BS, 0
1458 err_notfound    db 'Could not find kernel image: ',0
1459 err_notkernel   db CR, LF, 'Invalid or corrupt kernel image.', CR, LF, 0
1460 err_noram       db 'It appears your computer has less than '
1461                 asciidec dosram_k
1462                 db 'K of low ("DOS")'
1463                 db CR, LF
1464                 db 'RAM.  Linux needs at least this amount to boot.  If you get'
1465                 db CR, LF
1466                 db 'this message in error, hold down the Ctrl key while'
1467                 db CR, LF
1468                 db 'booting, and I will take your word for it.', CR, LF, 0
1469 err_badcfg      db 'Unknown keyword in syslinux.cfg.', CR, LF, 0
1470 err_noparm      db 'Missing parameter in syslinux.cfg.', CR, LF, 0
1471 err_noinitrd    db CR, LF, 'Could not find ramdisk image: ', 0
1472 err_nohighmem   db 'Not enough memory to load specified kernel.', CR, LF, 0
1473 err_highload    db CR, LF, 'Kernel transfer failure.', CR, LF, 0
1474 err_oldkernel   db 'Cannot load a ramdisk with an old kernel image.'
1475                 db CR, LF, 0
1476 err_notdos      db ': attempted DOS system call', CR, LF, 0
1477 err_comlarge    db 'COMBOOT image too large.', CR, LF, 0
1478 err_a20         db CR, LF, 'A20 gate not responding!', CR, LF, 0
1479 err_bootfailed  db CR, LF, 'Boot failed: please change disks and press '
1480                 db 'a key to continue.', CR, LF, 0
1481 ready_msg       db 'Ready.', CR, LF, 0
1482 crlfloading_msg db CR, LF
1483 loading_msg     db 'Loading ', 0
1484 dotdot_msg      db '.'
1485 dot_msg         db '.', 0
1486 aborted_msg     db ' aborted.'                  ; Fall through to crlf_msg!
1487 crlf_msg        db CR, LF
1488 null_msg        db 0
1489 crff_msg        db CR, FF, 0
1490 syslinux_cfg    db 'SYSLINUXCFG'                ; Mangled form
1491 ConfigName      db 'syslinux.cfg',0             ; Unmangled form
1492 %if IS_MDSLINUX
1493 manifest        db 'MANIFEST   '
1494 %endif
1495 ;
1496 ; Command line options we'd like to take a look at
1497 ;
1498 ; mem= and vga= are handled as normal 32-bit integer values
1499 initrd_cmd      db 'initrd='
1500 initrd_cmd_len  equ 7
1501
1502 ;
1503 ; Config file keyword table
1504 ;
1505 %include "keywords.inc"
1506
1507 ;
1508 ; Extensions to search for (in *forward* order).
1509 ;
1510 exten_table:    db 'CBT',0              ; COMBOOT (specific)
1511                 db 'BSS',0              ; Boot Sector (add superblock)
1512                 db 'BS ',0              ; Boot Sector 
1513                 db 'COM',0              ; COMBOOT (same as DOS)
1514                 db 'C32',0              ; COM32
1515 exten_table_end:
1516                 dd 0, 0                 ; Need 8 null bytes here
1517
1518 ;
1519 ; Misc initialized (data) variables
1520 ;
1521 %ifdef debug                            ; This code for debugging only
1522 debug_magic     dw 0D00Dh               ; Debug code sentinel
1523 %endif
1524
1525                 alignb 4, db 0
1526 BufSafe         dw trackbufsize/SECTOR_SIZE     ; Clusters we can load into trackbuf
1527 BufSafeSec      dw trackbufsize/SECTOR_SIZE     ; = how many sectors?
1528 BufSafeBytes    dw trackbufsize         ; = how many bytes?
1529 EndOfGetCBuf    dw getcbuf+trackbufsize ; = getcbuf+BufSafeBytes
1530 %ifndef DEPEND
1531 %if ( trackbufsize % SECTOR_SIZE ) != 0
1532 %error trackbufsize must be a multiple of SECTOR_SIZE
1533 %endif
1534 %endif