Initial support for auxilliary data vector
[profile/ivi/syslinux.git] / ldlinux.asm
index ef59f17..538ce68 100644 (file)
@@ -1,5 +1,4 @@
 ; -*- fundamental -*- (asm-mode sucks)
-; $Id$
 ; ****************************************************************************
 ;
 ;  ldlinux.asm
 ;  from MS-LOSS, and can be especially useful in conjunction with the
 ;  umsdos filesystem.
 ;
-;  This file is loaded in stages; first the boot sector at offset 7C00h,
-;  then the first sector (cluster, really, but we can only assume 1 sector)
-;  of LDLINUX.SYS at 7E00h and finally the remainder of LDLINUX.SYS at 8000h.
-;
-;   Copyright (C) 1994-2004  H. Peter Anvin
+;   Copyright (C) 1994-2007   H. Peter Anvin
 ;
 ;  This program is free software; you can redistribute it and/or modify
 ;  it under the terms of the GNU General Public License as published by
 ;  the Free Software Foundation, Inc., 53 Temple Place Ste 330,
 ;  Boston MA 02111-1307, USA; either version 2 of the License, or
 ;  (at your option) any later version; incorporated herein by reference.
-; 
+;
 ; ****************************************************************************
 
 %ifndef IS_MDSLINUX
 %define IS_SYSLINUX 1
 %endif
-%include "macros.inc"
-%include "config.inc"
-%include "kernel.inc"
-%include "bios.inc"
-%include "tracers.inc"
+%include "head.inc"
 
 ;
 ; Some semi-configurable constants... change on your own risk.
 ;
 my_id          equ syslinux_id
-FILENAME_MAX_LG2 equ 4                 ; log2(Max filename size Including final null)
-FILENAME_MAX   equ 11                  ; Max mangled filename size
-NULLFILE       equ ' '                 ; First char space == null filename
-retry_count    equ 6                   ; How patient are we with the disk?
+FILENAME_MAX_LG2 equ 6                 ; log2(Max filename size Including final null)
+FILENAME_MAX   equ (1<<FILENAME_MAX_LG2) ; Max mangled filename size
+NULLFILE       equ 0                   ; First char space == null filename
+NULLOFFSET     equ 0                   ; Position in which to look
+retry_count    equ 16                  ; How patient are we with the disk?
 %assign HIGHMEM_SLOP 0                 ; Avoid this much memory near the top
 LDLINUX_MAGIC  equ 0x3eb202fe          ; A random number to identify ourselves with
 
@@ -68,29 +60,17 @@ SECTOR_SIZE equ (1 << SECTOR_SHIFT)
 ; Since there is no room in the bottom 64K for all of these, we
 ; stick them at vk_seg:0000 and copy them down before we need them.
 ;
-; Note: this structure can be added to, but it must 
-;
-%define vk_power       7               ; log2(max number of vkernels)
-%define        max_vk          (1 << vk_power) ; Maximum number of vkernels
-%define vk_shift       (16-vk_power)   ; Number of bits to shift
-%define vk_size                (1 << vk_shift) ; Size of a vkernel buffer
-
                struc vkernel
 vk_vname:      resb FILENAME_MAX       ; Virtual name **MUST BE FIRST!**
 vk_rname:      resb FILENAME_MAX       ; Real name
 vk_appendlen:  resw 1
+vk_type:       resb 1                  ; Type of file
                alignb 4
 vk_append:     resb max_cmd_len+1      ; Command line
                alignb 4
 vk_end:                equ $                   ; Should be <= vk_size
                endstruc
 
-%ifndef DEPEND
-%if (vk_end > vk_size) || (vk_size*max_vk > 65536)
-%error "Too many vkernels defined, reduce vk_power"
-%endif
-%endif
-
 ;
 ; Segment assignments in the bottom 640K
 ; Stick to the low 512K in case we're using something like M-systems flash
@@ -125,130 +105,47 @@ file_left        resd 1                  ; Number of sectors left
 ;
 ; Memory below this point is reserved for the BIOS and the MBR
 ;
-               absolute 1000h
+               section .earlybss
 trackbufsize   equ 8192
 trackbuf       resb trackbufsize       ; Track buffer goes here
 getcbuf                resb trackbufsize
-;              ends at 5000h
-
-
-;
-; Constants for the xfer_buf_seg
-;
-; The xfer_buf_seg is also used to store message file buffers.  We
-; need two trackbuffers (text and graphics), plus a work buffer
-; for the graphics decompressor.
-;
-xbs_textbuf    equ 0                   ; Also hard-coded, do not change
-xbs_vgabuf     equ trackbufsize
-xbs_vgatmpbuf  equ 2*trackbufsize
+               ; ends at 4800h
 
-
-                absolute 5000h          ; Here we keep our BSS stuff
-VKernelBuf:    resb vk_size            ; "Current" vkernel
-               alignb 4
-AppendBuf       resb max_cmd_len+1     ; append=
-Ontimeout      resb max_cmd_len+1      ; ontimeout
-Onerror                resb max_cmd_len+1      ; onerror
-KbdMap         resb 256                ; Keyboard map
-FKeyName       resb 10*16              ; File names for F-key help
-NumBuf         resb 15                 ; Buffer to load number
-NumBufEnd      resb 1                  ; Last byte in NumBuf
+               section .bss
                alignb 8
 
                ; Expanded superblock
 SuperInfo      equ $
                resq 16                 ; The first 16 bytes expanded 8 times
-
 FAT            resd 1                  ; Location of (first) FAT
 RootDirArea    resd 1                  ; Location of root directory area
 RootDir                resd 1                  ; Location of root directory proper
 DataArea       resd 1                  ; Location of data area
 RootDirSize    resd 1                  ; Root dir size in sectors
 TotalSectors   resd 1                  ; Total number of sectors
-EndSector      resd 1                  ; Location of filesystem end
-
-               alignb 4
-E820Buf                resd 5                  ; INT 15:E820 data buffer
-E820Mem                resd 1                  ; Memory detected by E820
-E820Max                resd 1                  ; Is E820 memory capped?
-HiLoadAddr      resd 1                 ; Address pointer for high load loop
-HighMemSize    resd 1                  ; End of memory pointer (bytes)
-RamdiskMax     resd 1                  ; Highest address for a ramdisk
-KernelSize     resd 1                  ; Size of kernel (bytes)
-SavedSSSP      resd 1                  ; Our SS:SP while running a COMBOOT image
-PMESP          resd 1                  ; Protected-mode ESP
-FSectors       resd 1                  ; Number of sectors in getc file
 ClustSize      resd 1                  ; Bytes/cluster
 ClustMask      resd 1                  ; Sectors/cluster - 1
-KernelName      resb 12                        ; Mangled name for kernel
-                                       ; (note the spare byte after!)
-OrigKernelExt  resd 1                  ; Original kernel extension
-FBytes         equ $                   ; Used by open/getc
-FBytes1                resw 1
-FBytes2                resw 1
-DirBlocksLeft  resw 1                  ; Ditto
-RunLinClust    resw 1                  ; Cluster # for LDLINUX.SYS
-KernelSects    resw 1                  ; Kernel size in clusters
-FNextClust     resw 1                  ; Pointer to next cluster in d:o
-FPtr           resw 1                  ; Pointer to next char in buffer
-CmdOptPtr       resw 1                 ; Pointer to first option on cmd line
-KernelCNameLen  resw 1                 ; Length of unmangled kernel name
-InitRDCNameLen  resw 1                 ; Length of unmangled initrd name
-NextCharJump    resw 1                 ; Routine to interpret next print char
-SetupSecs      resw 1                  ; Number of setup sectors
-A20Test                resw 1                  ; Counter for testing status of A20
-A20Type                resw 1                  ; A20 type
-CmdLineLen     resw 1                  ; Length of command line including null
-GraphXSize     resw 1                  ; Width of splash screen file
-VGAPos         resw 1                  ; Pointer into VGA memory
-VGACluster     resw 1                  ; Cluster pointer for VGA image file
-VGAFilePtr     resw 1                  ; Pointer into VGAFileBuf
-Com32SysSP     resw 1                  ; SP saved during COM32 syscall
-DirScanCtr     resw 1                  ; OBSOLETE FIX THIS
-EndofDirSec    resw 1                  ; OBSOLETE FIX THIS
-CachePtrs      times (65536/SECTOR_SIZE) resw 1
-NextCacheSlot  resw 1
-CursorDX        equ $
-CursorCol       resb 1                 ; Cursor column for message file
-CursorRow       resb 1                 ; Cursor row for message file
-ScreenSize      equ $
-VidCols         resb 1                 ; Columns on screen-1
-VidRows         resb 1                 ; Rows on screen-1
-BaudDivisor    resw 1                  ; Baud rate divisor
-FlowControl    equ $
-FlowOutput     resb 1                  ; Outputs to assert for serial flow
-FlowInput      resb 1                  ; Input bits for serial flow
-FlowIgnore     resb 1                  ; Ignore input unless these bits set
-TextAttribute   resb 1                 ; Text attribute for message file
-RetryCount      resb 1                 ; Used for disk access retries
-KbdFlags       resb 1                  ; Check for keyboard escapes
-LoadFlags      resb 1                  ; Loadflags from kernel
-A20Tries       resb 1                  ; Times until giving up on A20
-FuncFlag       resb 1                  ; Escape sequences received from keyboard
-DisplayMask    resb 1                  ; Display modes mask
 CopySuper      resb 1                  ; Distinguish .bs versus .bss
 DriveNumber    resb 1                  ; BIOS drive number
 ClustShift     resb 1                  ; Shift count for sectors/cluster
 ClustByteShift resb 1                  ; Shift count for bytes/cluster
-MNameBuf        resb 11                ; Generic mangled file name buffer
-InitRD          resb 11                 ; initrd= mangled name
-KernelCName     resb 13                 ; Unmangled kernel name
-InitRDCName     resb 13                ; Unmangled initrd name
-TextColorReg   resb 17                 ; VGA color registers for text mode
-VGAFileBuf     resb 13                 ; Unmangled VGA image name
-VGAFileBufEnd  equ $
-VGAFileMBuf    resb 11                 ; Mangled VGA image name
-                alignb 4               ; For the good of REP MOVSD
-command_line   resb max_cmd_len+2      ; Command line buffer
-               alignb 4
-default_cmd    resb max_cmd_len+1      ; "default" command line
 
                alignb open_file_t_size
 Files          resb MAX_OPEN*open_file_t_size
 
+;
+; Constants for the xfer_buf_seg
+;
+; The xfer_buf_seg is also used to store message file buffers.  We
+; need two trackbuffers (text and graphics), plus a work buffer
+; for the graphics decompressor.
+;
+xbs_textbuf    equ 0                   ; Also hard-coded, do not change
+xbs_vgabuf     equ trackbufsize
+xbs_vgatmpbuf  equ 2*trackbufsize
+
+
                section .text
-                org 7C00h
 ;
 ; Some of the things that have to be saved very early are saved
 ; "close" to the initial stack pointer offset, in order to
@@ -257,7 +154,8 @@ Files               resb MAX_OPEN*open_file_t_size
 StackBuf       equ $-44-32             ; Start the stack here (grow down - 4K)
 PartInfo       equ StackBuf            ; Saved partition table entry
 FloppyTable    equ PartInfo+16         ; Floppy info table (must follow PartInfo)
-OrigFDCTabPtr  equ StackBuf-4          ; The high dword on the stack
+OrigFDCTabPtr  equ StackBuf-8          ; The 2nd high dword on the stack
+OrigESDI       equ StackBuf-4          ; The high dword on the stack
 
 ;
 ; Primary entry point.  Tempting as though it may be, we can't put the
@@ -318,9 +216,6 @@ SecPerClust equ bxSecPerClust
 ; Note we don't check the constraints above now; we did that at install
 ; time (we hope!)
 ;
-
-;floppy_table  equ $                   ; No sense in wasting memory, overwrite start
-
 start:
                cli                     ; No interrupts yet, please
                cld                     ; Copy upwards
@@ -330,12 +225,14 @@ start:
                xor ax,ax
                mov ss,ax
                mov sp,StackBuf         ; Just below BSS
+               push es                 ; Save initial ES:DI -> $PnP pointer
+               push di
                mov es,ax
 ;
 ; DS:SI may contain a partition table entry.  Preserve it for us.
 ;
                mov cx,8                ; Save partition info
-               mov di,sp
+               mov di,PartInfo
                rep movsw
 
                mov ds,ax               ; Now we can initialize DS...
@@ -412,7 +309,6 @@ not_harddisk:
 ;
                sti
 
-
 ;
 ; Do we have EBIOS (EDD)?
 ;
@@ -429,7 +325,7 @@ eddcheck:
                ;
                ; We have EDD support...
                ;
-               mov byte [getlinsec+1],getlinsec_ebios-(getlinsec+2)
+               mov byte [getlinsec.jmp+1],(getlinsec_ebios-(getlinsec.jmp+2))
 .noedd:
 
 ;
@@ -440,66 +336,15 @@ eddcheck:
                mov eax,[FirstSector]   ; Sector start
                mov bx,ldlinux_sys      ; Where to load it
                call getonesec
-               
+
                ; Some modicum of integrity checking
-               cmp dword [ldlinux_magic],LDLINUX_MAGIC
-               jne kaboom
-               cmp dword [ldlinux_magic+4],HEXDATE
+               cmp dword [ldlinux_magic+4],LDLINUX_MAGIC^HEXDATE
                jne kaboom
 
                ; Go for it...
                jmp ldlinux_ent
 
 ;
-; kaboom: write a message and bail out.
-;
-kaboom:
-               xor si,si
-               mov ss,si               
-               mov sp,StackBuf-4       ; Reset stack
-               mov ds,si               ; Reset data segment
-               pop dword [fdctab]      ; Restore FDC table
-.patch:                mov si,bailmsg
-               call writestr           ; Returns with AL = 0
-               cbw                     ; AH <- 0
-               int 16h                 ; Wait for keypress
-               int 19h                 ; And try once more to boot...
-.norge:                jmp short .norge        ; If int 19h returned; this is the end
-
-;
-;
-; writestr: write a null-terminated string to the console
-;          This assumes we're on page 0.  This is only used for early
-;           messages, so it should be OK.
-;
-writestr:
-.loop:         lodsb
-               and al,al
-                jz .return
-               mov ah,0Eh              ; Write to screen as TTY
-               mov bx,0007h            ; Attribute
-               int 10h
-               jmp short .loop
-.return:       ret
-
-;
-; xint13: wrapper for int 13h which will retry 6 times and then die,
-;        AND save all registers except BP
-;
-xint13:
-.again:
-                mov bp,retry_count
-.loop:          pushad
-                int 13h
-                popad
-                jnc writestr.return
-                dec bp
-                jnz .loop
-.disk_error:
-               jmp strict near kaboom  ; Patched
-
-
-;
 ; getonesec: get one disk sector
 ;
 getonesec:
@@ -523,7 +368,10 @@ getonesec:
 ; the order to dst,src to keep things sane.
 ;
 getlinsec:
-               jmp strict short getlinsec_cbios        ; This is patched
+               add eax,[bsHidden]              ; Add partition offset
+               xor edx,edx                     ; Zero-extend LBA (eventually allow 64 bits)
+
+.jmp:          jmp strict short getlinsec_cbios
 
 ;
 ; getlinsec_ebios:
@@ -531,30 +379,66 @@ getlinsec:
 ; getlinsec implementation for EBIOS (EDD)
 ;
 getlinsec_ebios:
-                mov si,dapa                     ; Load up the DAPA
-                mov [si+4],bx
-                mov [si+6],es
-                mov [si+8],eax
 .loop:
                 push bp                         ; Sectors left
+.retry2:
                call maxtrans                   ; Enforce maximum transfer size
-.bp_ok:
-                mov [si+2],bp
+               movzx edi,bp                    ; Sectors we are about to read
+               mov cx,retry_count
+.retry:
+
+               ; Form DAPA on stack
+               push edx
+               push eax
+               push es
+               push bx
+               push di
+               push word 16
+               mov si,sp
+               pushad
                 mov dl,[DriveNumber]
+               push ds
+               push ss
+               pop ds                          ; DS <- SS
                 mov ah,42h                      ; Extended Read
-                call xint13
-                pop bp
-                movzx eax,word [si+2]           ; Sectors we read
-                add [si+8],eax                  ; Advance sector pointer
-                sub bp,ax                       ; Sectors left
-                shl ax,9                        ; 512-byte sectors
-                add [si+4],ax                   ; Advance buffer pointer
+               int 13h
+               pop ds
+               popad
+               lea sp,[si+16]                  ; Remove DAPA
+               jc .error
+               pop bp
+               add eax,edi                     ; Advance sector pointer
+               sub bp,di                       ; Sectors left
+                shl di,SECTOR_SHIFT            ; 512-byte sectors
+                add bx,di                      ; Advance buffer pointer
                 and bp,bp
                 jnz .loop
-                mov eax,[si+8]                  ; Next sector
-                mov bx,[si+4]                   ; Buffer pointer
+
                 ret
 
+.error:
+               ; Some systems seem to get "stuck" in an error state when
+               ; using EBIOS.  Doesn't happen when using CBIOS, which is
+               ; good, since some other systems get timeout failures
+               ; waiting for the floppy disk to spin up.
+
+               pushad                          ; Try resetting the device
+               xor ax,ax
+               mov dl,[DriveNumber]
+               int 13h
+               popad
+               loop .retry                     ; CX-- and jump if not zero
+
+               ;shr word [MaxTransfer],1       ; Reduce the transfer size
+               ;jnz .retry2
+
+               ; Total failure.  Try falling back to CBIOS.
+               mov byte [getlinsec.jmp+1],(getlinsec_cbios-(getlinsec.jmp+2))
+               ;mov byte [MaxTransfer],63      ; Max possibe CBIOS transfer
+
+               pop bp
+               ; ... fall through ...
+
 ;
 ; getlinsec_cbios:
 ;
@@ -562,6 +446,7 @@ getlinsec_ebios:
 ;
 getlinsec_cbios:
 .loop:
+               push edx
                push eax
                push bp
                push bx
@@ -572,13 +457,17 @@ getlinsec_cbios:
                ; Dividing by sectors to get (track,sector): we may have
                ; up to 2^18 tracks, so we need to use 32-bit arithmetric.
                ;
-               xor edx,edx             ; Zero-extend LBA to 64 bits
                div esi
                xor cx,cx
                xchg cx,dx              ; CX <- sector index (0-based)
                                        ; EDX <- 0
                ; eax = track #
                div edi                 ; Convert track to head/cyl
+
+               ; We should test this, but it doesn't fit...
+               ; cmp eax,1023
+               ; ja .error
+
                ;
                ; Now we have AX = cyl, DX = head, CX = sector (0-based),
                ; BP = sectors to transfer, SI = bsSecPerTrack,
@@ -592,7 +481,7 @@ getlinsec_cbios:
                cmp bp,si
                jna .bp_ok
                mov bp,si
-.bp_ok:        
+.bp_ok:
 
                shl ah,6                ; Because IBM was STOOPID
                                        ; and thought 8 bits were enough
@@ -604,18 +493,63 @@ getlinsec_cbios:
                mov dl,[DriveNumber]
                xchg ax,bp              ; Sector to transfer count
                mov ah,02h              ; Read sectors
-               call xint13
-               movzx ecx,al
-               shl ax,9                ; Convert sectors in AL to bytes in AX
+               mov bp,retry_count
+.retry:
+               pushad
+               int 13h
+               popad
+               jc .error
+.resume:
+               movzx ecx,al            ; ECX <- sectors transferred
+               shl ax,SECTOR_SHIFT     ; Convert sectors in AL to bytes in AX
                pop bx
                add bx,ax
                pop bp
                pop eax
+               pop edx
                add eax,ecx
                sub bp,cx
                jnz .loop
                ret
 
+.error:
+               dec bp
+               jnz .retry
+
+               xchg ax,bp              ; Sectors transferred <- 0
+               shr word [MaxTransfer],1
+               jnz .resume
+               ; Fall through to disk_error
+
+;
+; kaboom: write a message and bail out.
+;
+disk_error:
+kaboom:
+               xor si,si
+               mov ss,si
+               mov sp,StackBuf-4       ; Reset stack
+               mov ds,si               ; Reset data segment
+               pop dword [fdctab]      ; Restore FDC table
+.patch:                                        ; When we have full code, intercept here
+               mov si,bailmsg
+
+               ; Write error message, this assumes screen page 0
+.loop:         lodsb
+               and al,al
+                jz .done
+               mov ah,0Eh              ; Write to screen as TTY
+               mov bx,0007h            ; Attribute
+               int 10h
+               jmp short .loop
+.done:
+               cbw                     ; AH <- 0
+.again:                int 16h                 ; Wait for keypress
+                                       ; NB: replaced by int 18h if
+                                       ; chosen at install time..
+               int 19h                 ; And try once more to boot...
+.norge:                jmp short .norge        ; If int 19h returned; this is the end
+
 ;
 ; Truncate BP to MaxTransfer
 ;
@@ -628,34 +562,18 @@ maxtrans:
 ;
 ; Error message on failure
 ;
-bailmsg:       db 'Boot failed', 0Dh, 0Ah, 0
-
-;
-; EBIOS disk address packet
-;
-               align 4, db 0
-dapa:
-                dw 16                           ; Packet size
-.count:         dw 0                            ; Block count
-.off:           dw 0                            ; Offset of buffer
-.seg:           dw 0                            ; Segment of buffer
-.lba:           dd 0                            ; LBA (LSW)
-                dd 0                            ; LBA (MSW)
-
-
-%if 1
-bs_checkpt_off equ ($-$$)
-%ifndef DEPEND
-%if bs_checkpt_off > 1F8h
-%error "Boot sector overflow"
-%endif
-%endif
+bailmsg:       db 'Boot error', 0Dh, 0Ah, 0
 
+               ; This fails if the boot sector overflows
                zb 1F8h-($-$$)
-%endif
+
 FirstSector    dd 0xDEADBEEF                   ; Location of sector 1
 MaxTransfer    dw 0x007F                       ; Max transfer size
-bootsignature  dw 0AA55h
+
+; This field will be filled in 0xAA55 by the installer, but we abuse it
+; to house a pointer to the INT 16h instruction at
+; kaboom.again, which gets patched to INT 18h in RAID mode.
+bootsignature  dw kaboom.again-bootsec
 
 ;
 ; ===========================================================================
@@ -677,7 +595,7 @@ syslinux_banner     db 0Dh, 0Ah
 
                align 8, db 0
 ldlinux_magic  dd LDLINUX_MAGIC
-               dd HEXDATE
+               dd LDLINUX_MAGIC^HEXDATE
 
 ;
 ; This area is patched by the installer.  It is found by looking for
@@ -693,7 +611,7 @@ CheckSum    dd 0            ; Checksum starting at ldlinux_sys
 SectorPtrs     times 64 dd 0
 
 ldlinux_ent:
-; 
+;
 ; Note that some BIOSes are buggy and run the boot sector at 07C0:0000
 ; instead of 0000:7C00 and the like.  We don't want to add anything
 ; more to the boot sector, so it is written to not assume a fixed
@@ -710,10 +628,22 @@ ldlinux_ent:
                call writestr
 
 ;
-; Patch disk error handling
+; Tell the user if we're using EBIOS or CBIOS
 ;
-               mov word [xint13.disk_error+1],do_disk_error-(xint13.disk_error+3)
+print_bios:
+               mov si,cbios_name
+               cmp byte [getlinsec.jmp+1],(getlinsec_ebios-(getlinsec.jmp+2))
+               jne .cbios
+               mov si,ebios_name
+.cbios:
+               mov [BIOSName],si
+               call writestr
+
+               section .bss
+%define        HAVE_BIOSNAME 1
+BIOSName       resw 1
 
+               section .text
 ;
 ; Now we read the rest of LDLINUX.SYS. Don't bother loading the first
 ; sector again, though.
@@ -735,9 +665,9 @@ load_rest:
                dec cx
                jz .chunk_ready
                inc edx                         ; Next linear sector
-               cmp [esi],edx                   ; Does it match
+               cmp [si],edx                    ; Does it match
                jnz .chunk_ready                ; If not, this is it
-               add esi,4                       ; If so, add sector to chunk
+               add si,4                        ; If so, add sector to chunk
                jmp short .make_chunk
 
 .chunk_ready:
@@ -778,6 +708,22 @@ verify_checksum:
 ; -----------------------------------------------------------------------------
 
 ;
+;
+; writestr: write a null-terminated string to the console
+;          This assumes we're on page 0.  This is only used for early
+;           messages, so it should be OK.
+;
+writestr:
+.loop:         lodsb
+               and al,al
+                jz .return
+               mov ah,0Eh              ; Write to screen as TTY
+               mov bx,0007h            ; Attribute
+               int 10h
+               jmp short .loop
+.return:       ret
+
+
 ; getlinsecsr: save registers, call getlinsec, restore registers
 ;
 getlinsecsr:   pushad
@@ -786,29 +732,15 @@ getlinsecsr:      pushad
                ret
 
 ;
-; This routine captures disk errors, and tries to decide if it is
-; time to reduce the transfer size.
+; Checksum error message
 ;
-do_disk_error:
-               cmp ah,42h
-               je .ebios
-               shr al,1                ; Try reducing the transfer size
-               mov [MaxTransfer],al    
-               jz kaboom               ; If we can't, we're dead...
-               jmp xint13              ; Try again
-.ebios:
-               push ax
-               mov ax,[si+2]
-               shr ax,1
-               mov [MaxTransfer],ax
-               mov [si+2],ax
-               pop ax
-               jmp xint13
+checksumerr_msg        db ' Load error - ', 0  ; Boot failed appended
 
 ;
-; Checksum error message
+; BIOS type string
 ;
-checksumerr_msg        db 'Load error - ', 0   ; Boot failed appended
+cbios_name     db 'CBIOS', 0
+ebios_name     db 'EBIOS', 0
 
 ;
 ; Debug routine
@@ -823,7 +755,7 @@ safedumpregs:
 rl_checkpt     equ $                           ; Must be <= 8000h
 
 rl_checkpt_off equ ($-$$)
-%if 0 ; ndef DEPEND
+%ifndef DEPEND
 %if rl_checkpt_off > 400h
 %error "Sector 1 overflow"
 %endif
@@ -871,11 +803,7 @@ genfatinfo:
 .have_secs:
                mov [TotalSectors],edx
 
-               mov eax,[bsHidden]              ; Hidden sectors aren't included
-               add edx,eax
-               mov [EndSector],edx
-
-               add eax,[bxResSectors]
+               mov eax,[bxResSectors]
                mov [FAT],eax                   ; Beginning of FAT
                mov edx,[bxFATsecs]
                and dx,dx
@@ -888,8 +816,8 @@ genfatinfo:
                mov [RootDir],eax               ; For FAT12/16 == root dir location
 
                mov edx,[bxRootDirEnts]
-               add dx,512-32
-               shr dx,9-5
+               add dx,SECTOR_SIZE/32-1
+               shr dx,SECTOR_SHIFT-5
                mov [RootDirSize],edx
                add eax,edx
                mov [DataArea],eax              ; Beginning of data area
@@ -899,20 +827,20 @@ genfatinfo:
                bsr cx,ax
                mov [ClustShift],cl
                push cx
-               add cl,9
+               add cl,SECTOR_SHIFT
                mov [ClustByteShift],cl
                pop cx
                dec ax
                mov [ClustMask],eax
                inc ax
-               shl eax,9
+               shl eax,SECTOR_SHIFT
                mov [ClustSize],eax
 
 ;
 ; FAT12, FAT16 or FAT28^H^H32?  This computation is fscking ridiculous.
 ;
 getfattype:
-               mov eax,[EndSector]
+               mov eax,[TotalSectors]
                sub eax,[DataArea]
                shr eax,cl                      ; cl == ClustShift
                mov cl,nextcluster_fat12-(nextcluster+2)
@@ -938,27 +866,12 @@ getfattype:
 ; Common initialization code
 ;
 %include "cpuinit.inc"
+%include "init.inc"
 
 ;
-; Clear Files structures
-;
-               mov di,Files
-               mov cx,(MAX_OPEN*open_file_t_size)/4
-               xor eax,eax
-               rep stosd
-
-;
-; Initialization that does not need to go into the any of the pre-load
-; areas
+; Initialize the metadata cache
 ;
-               ; Now set up screen parameters
-               call adjust_screen
-
-               ; Wipe the F-key area
-               mov al,NULLFILE
-               mov di,FKeyName
-               mov cx,10*(1 << FILENAME_MAX_LG2)
-               rep stosb
+               call initcache
 
 ;
 ; Now, everything is "up and running"... patch kaboom for more
@@ -980,24 +893,26 @@ getfattype:
 ; to take'm out.  In fact, we may want to put them back if we're going
 ; to boot ELKS at some point.
 ;
-               mov si,linuxauto_cmd            ; Default command: "linux auto"
-               mov di,default_cmd
-                mov cx,linuxauto_len
-               rep movsb
-
-               mov di,KbdMap                   ; Default keymap 1:1
-               xor al,al
-               inc ch                          ; CX <- 256
-mkkeymap:      stosb
-               inc al
-               loop mkkeymap
 
 ;
 ; Load configuration file
 ;
-               mov di,syslinux_cfg
+               mov si,config_name      ; Save configuration file name
+               mov di,ConfigName
+               call strcpy
+
+               mov di,syslinux_cfg1
+               call open
+               jnz .config_open
+               mov di,syslinux_cfg2
+               call open
+               jnz .config_open
+               mov di,syslinux_cfg3
                call open
                jz no_config_file
+.config_open:
+               mov eax,[PrevDir]       ; Make the directory with syslinux.cfg ...
+               mov [CurrentDir],eax    ; ... the current directory
 
 ;
 ; Now we have the config file open.  Parse the config file and
@@ -1006,62 +921,6 @@ mkkeymap: stosb
 %include "ui.inc"
 
 ;
-; Linux kernel loading code is common.
-;
-%include "runkernel.inc"
-
-;
-; COMBOOT-loading code
-;
-%include "comboot.inc"
-%include "com32.inc"
-%include "cmdline.inc"
-
-;
-; Boot sector loading code
-;
-%include "bootsect.inc"
-
-;
-; abort_check: let the user abort with <ESC> or <Ctrl-C>
-;
-abort_check:
-               call pollchar
-               jz ac_ret1
-               pusha
-               call getchar
-               cmp al,27                       ; <ESC>
-               je ac_kill
-               cmp al,3                        ; <Ctrl-C>
-               jne ac_ret2
-ac_kill:       mov si,aborted_msg
-
-;
-; abort_load: Called by various routines which wants to print a fatal
-;             error message and return to the command prompt.  Since this
-;             may happen at just about any stage of the boot process, assume
-;             our state is messed up, and just reset the segment registers
-;             and the stack forcibly.
-;
-;             SI    = offset (in _text) of error message to print
-;
-abort_load:
-                mov ax,cs                       ; Restore CS = DS = ES
-                mov ds,ax
-                mov es,ax
-                cli
-                mov sp,StackBuf-2*3                    ; Reset stack
-                mov ss,ax                       ; Just in case...
-                sti
-                call cwritestr                  ; Expects SI -> error msg
-al_ok:          jmp enter_command               ; Return to command prompt
-;
-; End of abort_check
-;
-ac_ret2:       popa
-ac_ret1:       ret
-
-;
 ; allocate_file: Allocate a file structure
 ;
 ;              If successful:
@@ -1084,35 +943,39 @@ allocate_file:
                ret
 
 ;
-; searchdir:
-;           Search the root directory for a pre-mangled filename in DS:DI.
+; search_dos_dir:
+;           Search a specific directory for a pre-mangled filename in
+;            MangledBuf, in the directory starting in sector EAX.
 ;
 ;           NOTE: This file considers finding a zero-length file an
 ;           error.  This is so we don't have to deal with that special
 ;           case elsewhere in the program (most loops have the test
 ;           at the end).
 ;
+;           Assumes DS == ES == CS.
+;
 ;           If successful:
 ;              ZF clear
 ;              SI      = file pointer
-;              DX:AX   = file length in bytes
+;              EAX     = file length (MAY BE ZERO!)
+;              DL      = file attributes
 ;           If unsuccessful
 ;              ZF set
 ;
 
-searchdir:
+search_dos_dir:
+               push bx
                call allocate_file
                jnz .alloc_failure
 
+               push cx
                push gs
                push es
                push ds
                pop es                          ; ES = DS
 
-               mov edx,[RootDir]               ; First root directory sector
-
 .scansector:
-               mov eax,edx
+               ; EAX <- directory sector to scan
                call getcachesector
                ; GS:SI now points to this sector
 
@@ -1120,15 +983,20 @@ searchdir:
 .scanentry:
                cmp byte [gs:si],0
                jz .failure                     ; Hit directory high water mark
+               test byte [gs:si+11],8          ; Ignore volume labels and
+                                               ; VFAT long filename entries
+               jnz .nomatch
                push cx
                push si
                push di
+               mov di,MangledBuf
                mov cx,11
                gs repe cmpsb
                pop di
                pop si
                pop cx
                jz .found
+.nomatch:
                add si,32
                loop .scanentry
 
@@ -1139,15 +1007,16 @@ searchdir:
 .failure:
                pop es
                pop gs
+               pop cx
 .alloc_failure:
-               xor ax,ax                       ; ZF <- 1
+               pop bx
+               xor eax,eax                     ; ZF <- 1
                ret
 .found:
                mov eax,[gs:si+28]              ; File size
                add eax,SECTOR_SIZE-1
                shr eax,SECTOR_SHIFT
-               jz .failure                     ; Zero-length file
-               mov [bx+4],eax
+               mov [bx+4],eax                  ; Sector count
 
                mov cl,[ClustShift]
                mov dx,[gs:si+20]               ; High cluster word
@@ -1155,33 +1024,116 @@ searchdir:
                mov dx,[gs:si+26]               ; Low cluster word
                sub edx,2
                shl edx,cl
+               add edx,[DataArea]
                mov [bx],edx                    ; Starting sector
 
-               mov edx,eax
-               shr edx,16                      ; 16-bitism, sigh
-               mov si,bx
-               and eax,eax                     ; ZF <- 0
+               mov eax,[gs:si+28]              ; File length again
+               mov dl,[gs:si+11]               ; File attribute
+               mov si,bx                       ; File pointer...
+               and si,si                       ; ZF <- 0
 
                pop es
                pop gs
+               pop cx
+               pop bx
                ret
 
 ;
-; writechr:    Write a single character in AL to the console without
-;              mangling any registers; handle video pages correctly.
+; close_file:
+;           Deallocates a file structure (pointer in SI)
+;           Assumes CS == DS.
 ;
-writechr:
-               call write_serial       ; write to serial port if needed
-               pushfd
-               pushad
-               mov ah,0Eh
-               mov bl,07h              ; attribute
-               mov bh,[cs:BIOS_page]   ; current page
-               int 10h
-               popad
-               popfd
+close_file:
+               and si,si
+               jz .closed
+               mov dword [si],0                ; First dword == file_left
+.closed:       ret
+
+;
+; searchdir:
+;
+;      Open a file
+;
+;           On entry:
+;              DS:DI   = filename
+;           If successful:
+;              ZF clear
+;              SI              = file pointer
+;              DX:AX or EAX    = file length in bytes
+;           If unsuccessful
+;              ZF set
+;
+; Assumes CS == DS == ES, and trashes BX and CX.
+;
+searchdir:
+               mov eax,[CurrentDir]
+               cmp byte [di],'/'       ; Root directory?
+               jne .notroot
+               mov eax,[RootDir]
+               inc di
+.notroot:
+
+.pathwalk:
+               push eax                ; <A> Current directory sector
+               mov si,di
+.findend:
+               lodsb
+               cmp al,' '
+               jbe .endpath
+               cmp al,'/'
+               jne .findend
+.endpath:
+               xchg si,di
+               pop eax                 ; <A> Current directory sector
+
+               mov [PrevDir],eax       ; Remember last directory searched
+
+               push di
+               call mangle_dos_name    ; MangledBuf <- component
+               call search_dos_dir
+               pop di
+               jz .notfound            ; Pathname component missing
+
+               cmp byte [di-1],'/'     ; Do we expect a directory
+               je .isdir
+
+               ; Otherwise, it should be a file
+.isfile:
+               test dl,18h             ; Subdirectory|Volume Label
+               jnz .badfile            ; If not a file, it's a bad thing
+
+               ; SI and EAX are already set
+               mov edx,eax
+               shr edx,16              ; Old 16-bit remnant...
+               and eax,eax             ; EAX != 0
+               jz .badfile
+               ret                     ; Done!
+
+               ; If we expected a directory, it better be one...
+.isdir:
+               test dl,10h             ; Subdirectory
+               jz .badfile
+
+               xor eax,eax
+               xchg eax,[si+file_sector] ; Get sector number and free file structure
+               jmp .pathwalk           ; Walk the next bit of the path
+
+.badfile:
+               xor eax,eax
+               mov [si],eax            ; Free file structure
+
+.notfound:
+               xor eax,eax
+               xor dx,dx
                ret
 
+               section .bss
+               alignb 4
+CurrentDir     resd 1                  ; Current directory
+PrevDir                resd 1                  ; Last scanned directory
+
+               section .text
+
 ;
 ;
 ; kaboom2: once everything is loaded, replace the part of kaboom
@@ -1190,121 +1142,153 @@ writechr:
 kaboom2:
                mov si,err_bootfailed
                call cwritestr
+               cmp byte [kaboom.again+1],18h   ; INT 18h version?
+               je .int18
                call getchar
                call vgaclearmode
                int 19h                 ; And try once more to boot...
 .norge:                jmp short .norge        ; If int 19h returned; this is the end
+.int18:
+               call vgaclearmode
+               int 18h
+.noreg:                jmp short .noreg        ; Nynorsk
 
 ;
-; mangle_name: Mangle a DOS filename pointed to by DS:SI into a buffer pointed
-;             to by ES:DI; ends on encountering any whitespace
+; mangle_name: Mangle a filename pointed to by DS:SI into a buffer pointed
+;             to by ES:DI; ends on encountering any whitespace.
+;             DI is preserved.
+;
+;             This verifies that a filename is < FILENAME_MAX characters,
+;             doesn't contain whitespace, zero-pads the output buffer,
+;             and removes trailing dots and redundant slashes, plus changes
+;              backslashes to forward slashes,
+;             so "repe cmpsb" can do a compare, and the path-searching routine
+;              gets a bit of an easier job.
+;
 ;
-
 mangle_name:
+               push di
+               push bx
+               xor ax,ax
+               mov cx,FILENAME_MAX-1
+               mov bx,di
+
+.mn_loop:
+               lodsb
+               cmp al,' '                      ; If control or space, end
+               jna .mn_end
+               cmp al,'\'                      ; Backslash?
+               jne .mn_not_bs
+               mov al,'/'                      ; Change to forward slash
+.mn_not_bs:
+               cmp al,ah                       ; Repeated slash?
+               je .mn_skip
+               xor ah,ah
+               cmp al,'/'
+               jne .mn_ok
+               mov ah,al
+.mn_ok         stosb
+.mn_skip:      loop .mn_loop
+.mn_end:
+               cmp bx,di                       ; At the beginning of the buffer?
+               jbe .mn_zero
+               cmp byte [es:di-1],'.'          ; Terminal dot?
+               je .mn_kill
+               cmp byte [es:di-1],'/'          ; Terminal slash?
+               jne .mn_zero
+.mn_kill:      dec di                          ; If so, remove it
+               inc cx
+               jmp short .mn_end
+.mn_zero:
+               inc cx                          ; At least one null byte
+               xor ax,ax                       ; Zero-fill name
+               rep stosb
+               pop bx
+               pop di
+               ret                             ; Done
+
+;
+; unmangle_name: Does the opposite of mangle_name; converts a DOS-mangled
+;                filename to the conventional representation.  This is needed
+;                for the BOOT_IMAGE= parameter for the kernel.
+;                NOTE: A 13-byte buffer is mandatory, even if the string is
+;                known to be shorter.
+;
+;                DS:SI -> input mangled file name
+;                ES:DI -> output buffer
+;
+;                On return, DI points to the first byte after the output name,
+;                which is set to a null byte.
+;
+unmangle_name: call strcpy
+               dec di                          ; Point to final null byte
+               ret
+
+;
+; mangle_dos_name:
+;              Mangle a DOS filename component pointed to by DS:SI
+;              into [MangledBuf]; ends on encountering any whitespace or slash.
+;              Assumes CS == DS == ES.
+;
+
+mangle_dos_name:
+               pusha
+               mov di,MangledBuf
+
                mov cx,11                       ; # of bytes to write
-mn_loop:
+.loop:
                lodsb
                cmp al,' '                      ; If control or space, end
-               jna mn_end
+               jna .end
+               cmp al,'/'                      ; Slash, too
+               je .end
                cmp al,'.'                      ; Period -> space-fill
-               je mn_is_period
+               je .is_period
                cmp al,'a'
-               jb mn_not_lower
+               jb .not_lower
                cmp al,'z'
-               ja mn_not_uslower
+               ja .not_uslower
                sub al,020h
-               jmp short mn_not_lower
-mn_is_period:  mov al,' '                      ; We need to space-fill
-mn_period_loop: cmp cx,3                       ; If <= 3 characters left
-               jbe mn_loop                     ; Just ignore it
+               jmp short .not_lower
+.is_period:    mov al,' '                      ; We need to space-fill
+.period_loop:  cmp cx,3                        ; If <= 3 characters left
+               jbe .loop                       ; Just ignore it
                stosb                           ; Otherwise, write a period
-               loop mn_period_loop             ; Dec CX and (always) jump
-mn_not_uslower: cmp al,ucase_low
-               jb mn_not_lower
+               loop .period_loop               ; Dec CX and (always) jump
+.not_uslower:  cmp al,ucase_low
+               jb .not_lower
                cmp al,ucase_high
-               ja mn_not_lower
+               ja .not_lower
                mov bx,ucase_tab-ucase_low
-                cs xlatb
-mn_not_lower:  stosb
-               loop mn_loop                    ; Don't continue if too long
-mn_end:
+                xlatb
+.not_lower:    stosb
+               loop .loop                      ; Don't continue if too long
+.end:
                mov al,' '                      ; Space-fill name
                rep stosb                       ; Doesn't do anything if CX=0
+               popa
                ret                             ; Done
 
+               section .bss
+MangledBuf     resb 11
+
+               section .text
 ;
-; Upper-case table for extended characters; this is technically code page 865,
+; Case tables for extended characters; this is technically code page 865,
 ; but code page 437 users will probably not miss not being able to use the
 ; cent sign in kernel images too much :-)
 ;
 ; The table only covers the range 129 to 164; the rest we can deal with.
 ;
+               section .data
+
 ucase_low      equ 129
 ucase_high     equ 164
 ucase_tab      db 154, 144, 'A', 142, 'A', 143, 128, 'EEEIII'
                db 142, 143, 144, 146, 146, 'O', 153, 'OUUY', 153, 154
                db 157, 156, 157, 158, 159, 'AIOU', 165
 
-;
-; unmangle_name: Does the opposite of mangle_name; converts a DOS-mangled
-;                filename to the conventional representation.  This is needed
-;                for the BOOT_IMAGE= parameter for the kernel.
-;                NOTE: A 13-byte buffer is mandatory, even if the string is
-;                known to be shorter.
-;
-;                DS:SI -> input mangled file name
-;                ES:DI -> output buffer
-;
-;                On return, DI points to the first byte after the output name,
-;                which is set to a null byte.
-;
-unmangle_name:
-                push si                 ; Save pointer to original name
-                mov cx,8
-                mov bp,di
-un_copy_body:   lodsb
-                call lower_case
-                stosb
-                cmp al,' '
-                jbe un_cb_space
-                mov bp,di               ; Position of last nonblank+1
-un_cb_space:    loop un_copy_body
-                mov di,bp
-                mov al,'.'              ; Don't save
-                stosb
-                mov cx,3
-un_copy_ext:    lodsb
-                call lower_case
-                stosb
-                cmp al,' '
-                jbe un_ce_space
-                mov bp,di
-un_ce_space:    loop un_copy_ext
-                mov di,bp
-                mov byte [es:di], 0
-                pop si
-                ret
-
-;
-; lower_case: Lower case a character in AL
-;
-lower_case:
-                cmp al,'A'
-                jb lc_ret
-                cmp al,'Z'
-                ja lc_1
-                or al,20h
-                ret
-lc_1:           cmp al,lcase_low
-                jb lc_ret
-                cmp al,lcase_high
-                ja lc_ret
-                push bx
-                mov bx,lcase_tab-lcase_low
-                       cs xlatb
-                pop bx
-lc_ret:         ret
-
+               section .text
 ;
 ; getfssec_edx: Get multiple sectors from a file
 ;
@@ -1324,24 +1308,28 @@ getfssec_edx:
                push eax
 .getfragment:
                xor ebp,ebp                     ; Fragment sector count
+               push edx                        ; Starting sector pointer
 .getseccnt:
                inc bp
                dec cx
                jz .do_read
+               xor eax,eax
                mov ax,es
                shl ax,4
-               add ax,bx                       ; Now DI = how far into 64K block we are
-               neg ax                          ; Bytes left in 64K block
-               shr ax,9                        ; Sectors left in 64K block
+               add ax,bx                       ; Now AX = how far into 64K block we are
+               not ax                          ; Bytes left in 64K block
+               inc eax
+               shr eax,SECTOR_SHIFT            ; Sectors left in 64K block
                cmp bp,ax
                jnb .do_read                    ; Unless there is at least 1 more sector room...
-               lea eax,[edx+1]                 ; Linearly next sector
+               mov eax,edx                     ; Current sector
+               inc edx                         ; Predict it's the linearly next sector
                call nextsector
                jc .do_read
-               cmp edx,eax
+               cmp edx,eax                     ; Did it match?
                jz .getseccnt
 .do_read:
-               mov eax,edx
+               pop eax                         ; Starting sector pointer
                call getlinsecsr
                lea eax,[eax+ebp-1]             ; This is the last sector actually read
                shl bp,9
@@ -1402,6 +1390,7 @@ nextcluster_fat12:
                push si
                mov edx,edi
                shr edi,1
+               pushf                   ; Save the shifted-out LSB (=CF)
                add edx,edi
                mov eax,edx
                shr eax,9
@@ -1416,8 +1405,8 @@ nextcluster_fat12:
                mov bx,dx
                and bx,1FFh
                mov ch,[gs:si+bx]
-               test di,1
-               jz .even
+               popf
+               jnc .even
                shr cx,4
 .even:         and cx,0FFFh
                movzx edi,cx
@@ -1472,10 +1461,10 @@ nextcluster_fat28:
 
 ;
 ; nextsector:  Given a sector in EAX on input, return the next sector
-;              of the same filesystem object, which may be the root
-;                      directory or a cluster chain.  Returns  EOF.
+;              of the same filesystem object, which may be the root
+;              directory or a cluster chain.  Returns  EOF.
 ;
-;              Assumes CS == DS.
+;              Assumes CS == DS.
 ;
 nextsector:
                push edi
@@ -1533,55 +1522,7 @@ nextsector:
 ;
 getfatsector:
                add eax,[FAT]           ; FAT starting address
-               ; Fall through
-
-;
-; getcachesector: Check for a particular sector (EAX) in the sector cache,
-;                and if it is already there, return a pointer in GS:SI
-;                otherwise load it and return said pointer.
-;
-;              Assumes CS == DS.
-;
-getcachesector:
-               push cx
-               mov si,cache_seg
-               mov gs,si
-               mov si,CachePtrs        ; Sector cache pointers
-               mov cx,65536/SECTOR_SIZE
-.search:
-               cmp eax,[si]
-               jz .hit
-               add si,4
-               loop .search
-
-.miss:
-               ; Need to load it.  Highly inefficient cache replacement
-               ; algorithm: Least Recently Written (LRW)
-               push bx
-               push es
-               push gs
-               pop es
-               mov bx,[NextCacheSlot]
-               inc bx
-               and bx,(1 << (16-SECTOR_SHIFT))-1
-               mov [NextCacheSlot],bx
-               shl bx,2
-               mov [CachePtrs+bx],eax
-               shl bx,SECTOR_SHIFT-2
-               mov si,bx
-               pushad
-               call getonesec
-               popad
-               pop es
-               pop bx
-               pop cx
-               ret
-
-.hit:          ; We have it; get the pointer
-               sub si,CachePtrs
-               shl si,SECTOR_SHIFT-2
-               pop cx
-               ret
+               jmp getcachesector
 
 ; -----------------------------------------------------------------------------
 ;  Common modules
@@ -1589,7 +1530,9 @@ getcachesector:
 
 %include "getc.inc"            ; getc et al
 %include "conio.inc"           ; Console I/O
+%include "plaincon.inc"                ; writechr
 %include "writestr.inc"                ; String output
+%include "configinit.inc"      ; Initialize configuration
 %include "parseconfig.inc"     ; High-level config file handling
 %include "parsecmd.inc"                ; Low-level config file handling
 %include "bcopy32.inc"         ; 32-bit bcopy
@@ -1598,62 +1541,23 @@ getcachesector:
 %include "graphics.inc"                ; VGA graphics
 %include "highmem.inc"         ; High memory sizing
 %include "strcpy.inc"           ; strcpy()
+%include "cache.inc"           ; Metadata disk cache
+%include "adv.inc"             ; Auxillary Data Vector
 
 ; -----------------------------------------------------------------------------
 ;  Begin data section
 ; -----------------------------------------------------------------------------
 
-;
-; Lower-case table for codepage 865
-;
-lcase_low       equ 128
-lcase_high      equ 165
-lcase_tab       db 135, 129, 130, 131, 132, 133, 134, 135, 136, 137, 138
-                db 139, 140, 141, 132, 134, 130, 145, 145, 147, 148, 149
-                db 150, 151, 152, 148, 129, 155, 156, 155, 158, 159, 160
-                db 161, 162, 163, 164, 164
-
+               section .data
 copyright_str   db ' Copyright (C) 1994-', year, ' H. Peter Anvin'
                db CR, LF, 0
-boot_prompt    db 'boot: ', 0
-wipe_char      db BS, ' ', BS, 0
-err_notfound   db 'Could not find kernel image: ',0
-err_notkernel  db CR, LF, 'Invalid or corrupt kernel image.', CR, LF, 0
-err_noram      db 'It appears your computer has less than '
-               asciidec dosram_k
-               db 'K of low ("DOS")'
-               db CR, LF
-               db 'RAM.  Linux needs at least this amount to boot.  If you get'
-               db CR, LF
-               db 'this message in error, hold down the Ctrl key while'
-               db CR, LF
-               db 'booting, and I will take your word for it.', CR, LF, 0
-err_badcfg      db 'Unknown keyword in syslinux.cfg.', CR, LF, 0
-err_noparm      db 'Missing parameter in syslinux.cfg.', CR, LF, 0
-err_noinitrd    db CR, LF, 'Could not find ramdisk image: ', 0
-err_nohighmem   db 'Not enough memory to load specified kernel.', CR, LF, 0
-err_highload    db CR, LF, 'Kernel transfer failure.', CR, LF, 0
-err_oldkernel   db 'Cannot load a ramdisk with an old kernel image.'
-                db CR, LF, 0
-err_notdos     db ': attempted DOS system call', CR, LF, 0
-err_comlarge   db 'COMBOOT image too large.', CR, LF, 0
-err_a20                db CR, LF, 'A20 gate not responding!', CR, LF, 0
 err_bootfailed db CR, LF, 'Boot failed: please change disks and press '
                db 'a key to continue.', CR, LF, 0
-ready_msg      db 'Ready.', CR, LF, 0
-crlfloading_msg        db CR, LF
-loading_msg     db 'Loading ', 0
-dotdot_msg      db '.'
-dot_msg         db '.', 0
-aborted_msg    db ' aborted.'                  ; Fall through to crlf_msg!
-crlf_msg       db CR, LF
-null_msg       db 0
-crff_msg       db CR, FF, 0
-syslinux_cfg   db 'SYSLINUXCFG'                ; Mangled form
-ConfigName     db 'syslinux.cfg',0             ; Unmangled form
-%if IS_MDSLINUX
-manifest       db 'MANIFEST   '
-%endif
+syslinux_cfg1  db '/boot'                      ; /boot/syslinux/syslinux.cfg
+syslinux_cfg2  db '/syslinux'                  ; /syslinux/syslinux.cfg
+syslinux_cfg3  db '/'                          ; /syslinux.cfg
+config_name    db 'syslinux.cfg', 0            ; syslinux.cfg
+
 ;
 ; Command line options we'd like to take a look at
 ;
@@ -1669,11 +1573,11 @@ initrd_cmd_len  equ 7
 ;
 ; Extensions to search for (in *forward* order).
 ;
-exten_table:   db 'CBT',0              ; COMBOOT (specific)
-               db 'BSS',0              ; Boot Sector (add superblock)
-               db 'BS ',0              ; Boot Sector 
-               db 'COM',0              ; COMBOOT (same as DOS)
-               db 'C32',0              ; COM32
+exten_table:   db '.cbt'               ; COMBOOT (specific)
+               db '.bss'               ; Boot Sector (add superblock)
+               db '.bs', 0             ; Boot Sector
+               db '.com'               ; COMBOOT (same as DOS)
+               db '.c32'               ; COM32
 exten_table_end:
                dd 0, 0                 ; Need 8 null bytes here
 
@@ -1683,52 +1587,12 @@ exten_table_end:
 %ifdef debug                           ; This code for debugging only
 debug_magic    dw 0D00Dh               ; Debug code sentinel
 %endif
-AppendLen       dw 0                    ; Bytes in append= command
-OntimeoutLen   dw 0                    ; Bytes in ontimeout command
-OnerrorLen     dw 0                    ; Bytes in onerror command
-KbdTimeOut      dw 0                    ; Keyboard timeout (if any)
-CmdLinePtr     dw cmd_line_here        ; Command line advancing pointer
-initrd_flag    equ $
-initrd_ptr     dw 0                    ; Initial ramdisk pointer/flag
-VKernelCtr     dw 0                    ; Number of registered vkernels
-ForcePrompt    dw 0                    ; Force prompt
-AllowImplicit   dw 1                    ; Allow implicit kernels
-AllowOptions   dw 1                    ; User-specified options allowed
-SerialPort     dw 0                    ; Serial port base (or 0 for no serial port)
-VGAFontSize    dw 16                   ; Defaults to 16 byte font
-UserFont       db 0                    ; Using a user-specified font
-ScrollAttribute        db 07h                  ; White on black (for text mode)
 
                alignb 4, db 0
 BufSafe                dw trackbufsize/SECTOR_SIZE     ; Clusters we can load into trackbuf
-BufSafeSec     dw trackbufsize/SECTOR_SIZE     ; = how many sectors?
 BufSafeBytes   dw trackbufsize         ; = how many bytes?
-EndOfGetCBuf   dw getcbuf+trackbufsize ; = getcbuf+BufSafeBytes
 %ifndef DEPEND
 %if ( trackbufsize % SECTOR_SIZE ) != 0
 %error trackbufsize must be a multiple of SECTOR_SIZE
 %endif
 %endif
-;
-; Stuff for the command line; we do some trickery here with equ to avoid
-; tons of zeros appended to our file and wasting space
-;
-linuxauto_cmd  db 'linux auto',0
-linuxauto_len   equ $-linuxauto_cmd
-boot_image      db 'BOOT_IMAGE='
-boot_image_len  equ $-boot_image
-
-               align 4, db 0           ; Pad out any unfinished dword
-ldlinux_end    equ $
-ldlinux_len    equ $-ldlinux_magic
-
-; VGA font buffer at the end of memory (so loading a font works even
-; in graphics mode.)
-vgafontbuf     equ 0E000h
-
-; This is a compile-time assert that we didn't run out of space
-%ifndef DEPEND
-%if (ldlinux_end-bootsec+7C00h) > vgafontbuf
-%error "Out of memory, better reorganize something..."
-%endif
-%endif