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