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