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