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