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