Corrections to self-loading sequence; we now get that far at least
[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 es,ax                       ; INT 13:08 destroys ES
851                 mov si,superblock
852                 mov di,SuperInfo
853                 mov cx,superinfo_size
854 .loop:
855                 lodsw
856                 dec si
857                 stosd                           ; Store expanded word
858                 xor ah,ah
859                 stosd                           ; Store expanded byte
860
861 ;
862 ; How big is a cluster, really?  Also figure out how many clusters
863 ; will fit in the trackbuf, and how many sectors and bytes that is
864 ;
865 ; FIX THIS: We shouldn't rely on integral sectors in the trackbuf
866 ; anymore...
867 ;
868                 mov edi,[bxBytesPerSec]         ; Used a lot below
869                 mov eax,[SecPerClust]
870                 mov si,ax                       ; Also used a lot
871                 mul di
872                 mov [ClustSize],eax             ; Bytes/cluster
873                 mov bx,ax
874                 mov ax,trackbufsize             ; High bit 0
875                 cwd
876                 div bx
877                 mov [BufSafe],ax                ; # of cluster in trackbuf
878                 mul si
879                 mov [BufSafeSec],ax
880                 mul di
881                 mov [BufSafeBytes],ax
882                 add ax,getcbuf                  ; Size of getcbuf is the same
883                 mov [EndOfGetCBuf],ax           ; as for trackbuf
884
885 ;
886 ; Compute some information about this filesystem.
887 ;
888
889 ; First, generate the map of regions
890 genfatinfo:
891                 mov edx,[bxSectors]
892                 and dx,dx
893                 jz .have_secs
894                 mov edx,[bsHugeSectors]
895 .have_secs:
896                 mov [TotalSectors],edx
897
898                 mov eax,[bsHidden]              ; Hidden sectors aren't included
899                 add edx,eax
900                 mov [EndSector],edx
901
902                 add eax,[bxResSectors]
903                 mov [FAT],eax                   ; Beginning of FAT
904                 mov edx,[bxFATsecs]
905                 and dx,dx
906                 jz .have_fatsecs
907                 mov edx,[bootsec+36]            ; FAT32 BPB_FATsz32
908 .have_fatsecs:
909                 imul edx,[bxFATs]
910                 add eax,edx
911                 mov [RootDirArea],eax           ; Beginning of root directory
912                 mov [RootDir],eax               ; For FAT12/16 == root dir location
913
914                 mov edx,[bxRootDirEnts]
915                 add dx,512-32
916                 shr dx,9-5
917                 mov [RootDirSize],edx
918                 add eax,edx
919                 mov [DataArea],eax              ; Beginning of data area
920
921 ; Next, generate a cluster size shift count and mask
922                 mov eax,[bxSecPerClust]
923                 bsr cx,ax
924                 mov [ClustShift],cl
925                 push cx
926                 add cl,9
927                 mov [ClustByteShift],cl
928                 pop cx
929                 dec ax
930                 mov [ClustMask],eax
931                 inc ax
932                 shl eax,9
933                 mov [ClustSize],eax
934
935 ;
936 ; FAT12, FAT16 or FAT28^H^H32?  This computation is fscking ridiculous.
937 ;
938 getfattype:
939                 mov eax,[EndSector]
940                 sub eax,[DataArea]
941                 shr eax,cl                      ; cl == ClustShift
942                 mov cl,nextcluster_fat12-(nextcluster+2)
943                 cmp eax,4085                    ; FAT12 limit
944                 jb .setsize
945                 mov cl,nextcluster_fat16-(nextcluster+2)
946                 cmp eax,65525                   ; FAT16 limit
947                 jb .setsize
948                 ;
949                 ; FAT32, root directory is a cluster chain
950                 ;
951                 mov cl,[ClustShift]
952                 mov eax,[bootsec+44]            ; Root directory cluster
953                 sub eax,2
954                 shl eax,cl
955                 add eax,[DataArea]
956                 mov [RootDir],eax
957                 mov cl,nextcluster_fat28-(nextcluster+2)
958 .setsize:
959                 mov byte [nextcluster+1],cl
960
961 ;
962 ; Common initialization code
963 ;
964 %include "cpuinit.inc"
965
966 ;
967 ; Clear Files structures
968 ;
969                 mov di,Files
970                 mov cx,(MAX_OPEN*open_file_t_size)/4
971                 xor eax,eax
972                 rep stosd
973
974 ;
975 ; Initialization that does not need to go into the any of the pre-load
976 ; areas
977 ;
978                 ; Now set up screen parameters
979                 call adjust_screen
980
981                 ; Wipe the F-key area
982                 mov al,NULLFILE
983                 mov di,FKeyName
984                 mov cx,10*(1 << FILENAME_MAX_LG2)
985                 rep stosb
986
987 ;
988 ; Now, everything is "up and running"... patch kaboom for more
989 ; verbosity and using the full screen system
990 ;
991                 ; E9 = JMP NEAR
992                 mov dword [kaboom.patch],0e9h+((kaboom2-(kaboom.patch+3)) << 8)
993
994 ;
995 ; Now we're all set to start with our *real* business.  First load the
996 ; configuration file (if any) and parse it.
997 ;
998 ; In previous versions I avoided using 32-bit registers because of a
999 ; rumour some BIOSes clobbered the upper half of 32-bit registers at
1000 ; random.  I figure, though, that if there are any of those still left
1001 ; they probably won't be trying to install Linux on them...
1002 ;
1003 ; The code is still ripe with 16-bitisms, though.  Not worth the hassle
1004 ; to take'm out.  In fact, we may want to put them back if we're going
1005 ; to boot ELKS at some point.
1006 ;
1007                 mov si,linuxauto_cmd            ; Default command: "linux auto"
1008                 mov di,default_cmd
1009                 mov cx,linuxauto_len
1010                 rep movsb
1011
1012                 mov di,KbdMap                   ; Default keymap 1:1
1013                 xor al,al
1014                 inc ch                          ; CX <- 256
1015 mkkeymap:       stosb
1016                 inc al
1017                 loop mkkeymap
1018
1019 ;
1020 ; Load configuration file
1021 ;
1022                 mov di,syslinux_cfg
1023                 call open
1024                 jz no_config_file
1025
1026 ;
1027 ; Now we have the config file open.  Parse the config file and
1028 ; run the user interface.
1029 ;
1030 %include "ui.inc"
1031
1032 ;
1033 ; Linux kernel loading code is common.
1034 ;
1035 %include "runkernel.inc"
1036
1037 ;
1038 ; COMBOOT-loading code
1039 ;
1040 %include "comboot.inc"
1041 %include "com32.inc"
1042 %include "cmdline.inc"
1043
1044 ;
1045 ; Boot sector loading code
1046 ;
1047 %include "bootsect.inc"
1048
1049 ;
1050 ; abort_check: let the user abort with <ESC> or <Ctrl-C>
1051 ;
1052 abort_check:
1053                 call pollchar
1054                 jz ac_ret1
1055                 pusha
1056                 call getchar
1057                 cmp al,27                       ; <ESC>
1058                 je ac_kill
1059                 cmp al,3                        ; <Ctrl-C>
1060                 jne ac_ret2
1061 ac_kill:        mov si,aborted_msg
1062
1063 ;
1064 ; abort_load: Called by various routines which wants to print a fatal
1065 ;             error message and return to the command prompt.  Since this
1066 ;             may happen at just about any stage of the boot process, assume
1067 ;             our state is messed up, and just reset the segment registers
1068 ;             and the stack forcibly.
1069 ;
1070 ;             SI    = offset (in _text) of error message to print
1071 ;
1072 abort_load:
1073                 mov ax,cs                       ; Restore CS = DS = ES
1074                 mov ds,ax
1075                 mov es,ax
1076                 cli
1077                 mov sp,StackBuf-2*3             ; Reset stack
1078                 mov ss,ax                       ; Just in case...
1079                 sti
1080                 call cwritestr                  ; Expects SI -> error msg
1081 al_ok:          jmp enter_command               ; Return to command prompt
1082 ;
1083 ; End of abort_check
1084 ;
1085 ac_ret2:        popa
1086 ac_ret1:        ret
1087
1088 ;
1089 ; allocate_file: Allocate a file structure
1090 ;
1091 ;               If successful:
1092 ;                 ZF set
1093 ;                 BX = file pointer
1094 ;               In unsuccessful:
1095 ;                 ZF clear
1096 ;
1097 allocate_file:
1098                 TRACER 'a'
1099                 push cx
1100                 mov bx,Files
1101                 mov cx,MAX_OPEN
1102 .check:         cmp dword [bx], byte 0
1103                 je .found
1104                 add bx,open_file_t_size         ; ZF = 0
1105                 loop .check
1106                 ; ZF = 0 if we fell out of the loop
1107 .found:         pop cx
1108                 ret
1109
1110 ;
1111 ; searchdir:
1112 ;            Search the root directory for a pre-mangled filename in DS:DI.
1113 ;
1114 ;            NOTE: This file considers finding a zero-length file an
1115 ;            error.  This is so we don't have to deal with that special
1116 ;            case elsewhere in the program (most loops have the test
1117 ;            at the end).
1118 ;
1119 ;            If successful:
1120 ;               ZF clear
1121 ;               SI      = file pointer
1122 ;               DX:AX   = file length in bytes
1123 ;            If unsuccessful
1124 ;               ZF set
1125 ;
1126
1127 searchdir:
1128                 call allocate_file
1129                 jnz .alloc_failure
1130
1131                 push gs
1132                 push es
1133                 push ds
1134                 pop es                          ; ES = DS
1135
1136                 mov edx,[RootDir]               ; First root directory sector
1137
1138 .scansector:
1139                 mov eax,edx
1140                 call getcachesector
1141                 ; GS:SI now points to this sector
1142
1143                 mov cx,SECTOR_SIZE/32           ; 32 == directory entry size
1144 .scanentry:
1145                 cmp byte [gs:si],0
1146                 jz .failure                     ; Hit directory high water mark
1147                 push cx
1148                 push si
1149                 mov cx,11
1150                 gs repe cmpsb
1151                 pop si
1152                 pop cx
1153                 jz .found
1154                 add si,32
1155                 loop .scanentry
1156
1157                 call nextsector
1158                 jnc .scansector                 ; CF is set if we're at end
1159
1160                 ; If we get here, we failed
1161 .failure:
1162                 pop es
1163                 pop gs
1164 .alloc_failure:
1165                 xor ax,ax                       ; ZF <- 1
1166                 ret
1167 .found:
1168                 mov eax,[gs:si+28]              ; File size
1169                 add eax,SECTOR_SIZE-1
1170                 shr eax,SECTOR_SHIFT
1171                 jz .failure                     ; Zero-length file
1172                 mov [bx+4],eax
1173
1174                 mov cl,[ClustShift]
1175                 mov dx,[gs:si+20]               ; High cluster word
1176                 shl edx,16
1177                 mov dx,[gs:si+26]               ; Low cluster word
1178                 add edx,2
1179                 shl edx,cl
1180                 mov [bx],edx                    ; Starting sector
1181
1182                 mov edx,eax
1183                 shr edx,16                      ; 16-bitism, sigh
1184                 mov si,bx
1185                 and eax,eax                     ; ZF <- 0
1186
1187                 pop es
1188                 pop gs
1189                 ret
1190
1191 ;
1192 ; writechr:     Write a single character in AL to the console without
1193 ;               mangling any registers; handle video pages correctly.
1194 ;
1195 writechr:
1196                 call write_serial       ; write to serial port if needed
1197                 pushfd
1198                 pushad
1199                 mov ah,0Eh
1200                 mov bl,07h              ; attribute
1201                 mov bh,[cs:BIOS_page]   ; current page
1202                 int 10h
1203                 popad
1204                 popfd
1205                 ret
1206
1207 ;
1208 ;
1209 ; kaboom2: once everything is loaded, replace the part of kaboom
1210 ;          starting with "kaboom.patch" with this part
1211
1212 kaboom2:
1213                 mov si,err_bootfailed
1214                 call cwritestr
1215                 call getchar
1216                 call vgaclearmode
1217                 int 19h                 ; And try once more to boot...
1218 .norge:         jmp short .norge        ; If int 19h returned; this is the end
1219
1220 ;
1221 ; mangle_name: Mangle a DOS filename pointed to by DS:SI into a buffer pointed
1222 ;              to by ES:DI; ends on encountering any whitespace
1223 ;
1224
1225 mangle_name:
1226                 mov cx,11                       ; # of bytes to write
1227 mn_loop:
1228                 lodsb
1229                 cmp al,' '                      ; If control or space, end
1230                 jna mn_end
1231                 cmp al,'.'                      ; Period -> space-fill
1232                 je mn_is_period
1233                 cmp al,'a'
1234                 jb mn_not_lower
1235                 cmp al,'z'
1236                 ja mn_not_uslower
1237                 sub al,020h
1238                 jmp short mn_not_lower
1239 mn_is_period:   mov al,' '                      ; We need to space-fill
1240 mn_period_loop: cmp cx,3                        ; If <= 3 characters left
1241                 jbe mn_loop                     ; Just ignore it
1242                 stosb                           ; Otherwise, write a period
1243                 loop mn_period_loop             ; Dec CX and (always) jump
1244 mn_not_uslower: cmp al,ucase_low
1245                 jb mn_not_lower
1246                 cmp al,ucase_high
1247                 ja mn_not_lower
1248                 mov bx,ucase_tab-ucase_low
1249                 cs xlatb
1250 mn_not_lower:   stosb
1251                 loop mn_loop                    ; Don't continue if too long
1252 mn_end:
1253                 mov al,' '                      ; Space-fill name
1254                 rep stosb                       ; Doesn't do anything if CX=0
1255                 ret                             ; Done
1256
1257 ;
1258 ; Upper-case table for extended characters; this is technically code page 865,
1259 ; but code page 437 users will probably not miss not being able to use the
1260 ; cent sign in kernel images too much :-)
1261 ;
1262 ; The table only covers the range 129 to 164; the rest we can deal with.
1263 ;
1264 ucase_low       equ 129
1265 ucase_high      equ 164
1266 ucase_tab       db 154, 144, 'A', 142, 'A', 143, 128, 'EEEIII'
1267                 db 142, 143, 144, 146, 146, 'O', 153, 'OUUY', 153, 154
1268                 db 157, 156, 157, 158, 159, 'AIOU', 165
1269
1270 ;
1271 ; unmangle_name: Does the opposite of mangle_name; converts a DOS-mangled
1272 ;                filename to the conventional representation.  This is needed
1273 ;                for the BOOT_IMAGE= parameter for the kernel.
1274 ;                NOTE: A 13-byte buffer is mandatory, even if the string is
1275 ;                known to be shorter.
1276 ;
1277 ;                DS:SI -> input mangled file name
1278 ;                ES:DI -> output buffer
1279 ;
1280 ;                On return, DI points to the first byte after the output name,
1281 ;                which is set to a null byte.
1282 ;
1283 unmangle_name:
1284                 push si                 ; Save pointer to original name
1285                 mov cx,8
1286                 mov bp,di
1287 un_copy_body:   lodsb
1288                 call lower_case
1289                 stosb
1290                 cmp al,' '
1291                 jbe un_cb_space
1292                 mov bp,di               ; Position of last nonblank+1
1293 un_cb_space:    loop un_copy_body
1294                 mov di,bp
1295                 mov al,'.'              ; Don't save
1296                 stosb
1297                 mov cx,3
1298 un_copy_ext:    lodsb
1299                 call lower_case
1300                 stosb
1301                 cmp al,' '
1302                 jbe un_ce_space
1303                 mov bp,di
1304 un_ce_space:    loop un_copy_ext
1305                 mov di,bp
1306                 mov byte [es:di], 0
1307                 pop si
1308                 ret
1309
1310 ;
1311 ; lower_case: Lower case a character in AL
1312 ;
1313 lower_case:
1314                 cmp al,'A'
1315                 jb lc_ret
1316                 cmp al,'Z'
1317                 ja lc_1
1318                 or al,20h
1319                 ret
1320 lc_1:           cmp al,lcase_low
1321                 jb lc_ret
1322                 cmp al,lcase_high
1323                 ja lc_ret
1324                 push bx
1325                 mov bx,lcase_tab-lcase_low
1326                 cs xlatb
1327                 pop bx
1328 lc_ret:         ret
1329
1330 ;
1331 ; getfssec_edx: Get multiple sectors from a file
1332 ;
1333 ;       This routine makes sure the subtransfers do not cross a 64K boundary,
1334 ;       and will correct the situation if it does, UNLESS *sectors* cross
1335 ;       64K boundaries.
1336 ;
1337 ;       ES:BX   -> Buffer
1338 ;       EDX     -> Current sector number
1339 ;       CX      -> Sector count (0FFFFh = until end of file)
1340 ;                  Must not exceed the ES segment
1341 ;       Returns EDX=0, CF=1 on EOF (not necessarily error)
1342 ;       All arguments are advanced to reflect data read.
1343 ;
1344 getfssec_edx:
1345                 push ebp
1346                 push eax
1347 .getfragment:
1348                 xor ebp,ebp                     ; Fragment sector count
1349 .getseccnt:
1350                 inc bp
1351                 dec cx
1352                 jz .do_read
1353                 mov ax,es
1354                 shl ax,4
1355                 add ax,bx                       ; Now DI = how far into 64K block we are
1356                 neg ax                          ; Bytes left in 64K block
1357                 shr ax,9                        ; Sectors left in 64K block
1358                 cmp bp,ax
1359                 jnb .do_read                    ; Unless there is at least 1 more sector room...
1360                 lea eax,[edx+1]                 ; Linearly next sector
1361                 call nextsector
1362                 jc .do_read
1363                 cmp edx,eax
1364                 jz .getseccnt
1365 .do_read:
1366                 mov eax,edx
1367                 call getlinsecsr
1368                 lea eax,[eax+ebp-1]             ; This is the last sector actually read
1369                 shl bp,9
1370                 add bx,bp                       ; Adjust buffer pointer
1371                 call nextsector
1372                 jc .eof
1373                 mov edx,eax
1374                 and cx,cx
1375                 jnz .getfragment
1376 .done:
1377                 pop eax
1378                 pop ebp
1379                 ret
1380 .eof:
1381                 xor edx,edx
1382                 stc
1383                 jmp .done
1384
1385 ;
1386 ; getfssec: Get multiple sectors from a file
1387 ;
1388 ;       Same as above, except SI is a pointer to a open_file_t
1389 ;
1390 ;       ES:BX   -> Buffer
1391 ;       DS:SI   -> Pointer to open_file_t
1392 ;       CX      -> Sector count (0FFFFh = until end of file)
1393 ;                  Must not exceed the ES segment
1394 ;       Returns CF=1 on EOF (not necessarily error)
1395 ;       All arguments are advanced to reflect data read.
1396 ;
1397 getfssec:
1398                 push edx
1399                 movzx edx,cx
1400                 cmp edx,[si+4]
1401                 jbe .sizeok
1402                 mov edx,[si+4]
1403                 mov cx,dx
1404 .sizeok:
1405                 sub [si+4],edx
1406                 mov edx,[si]
1407                 call getfssec_edx
1408                 mov [si],edx
1409                 pop edx
1410                 ret
1411
1412 ;
1413 ; nextcluster: Advance a cluster pointer in EDI to the next cluster
1414 ;              pointed at in the FAT tables.  CF=0 on return if end of file.
1415 ;
1416 nextcluster:
1417                 jmp strict short nextcluster_fat28      ; This gets patched
1418
1419 nextcluster_fat12:
1420                 push eax
1421                 push edx
1422                 push bx
1423                 push cx
1424                 push si
1425                 mov edx,edi
1426                 shr edi,1
1427                 add edx,edi
1428                 mov eax,edx
1429                 shr eax,9
1430                 call getfatsector
1431                 mov bx,dx
1432                 and bx,1FFh
1433                 mov cl,[gs:si+bx]
1434                 inc edx
1435                 mov eax,edx
1436                 shr eax,9
1437                 call getfatsector
1438                 mov bx,dx
1439                 and bx,1FFh
1440                 mov ch,[gs:si+bx]
1441                 test di,1
1442                 jz .even
1443                 shr cx,4
1444 .even:          and cx,0FFFh
1445                 movzx edi,cx
1446                 cmp di,0FF0h
1447                 pop si
1448                 pop cx
1449                 pop bx
1450                 pop edx
1451                 pop eax
1452                 ret
1453
1454 ;
1455 ; FAT16 decoding routine.
1456 ;
1457 nextcluster_fat16:
1458                 push eax
1459                 push si
1460                 push bx
1461                 mov eax,edi
1462                 shr eax,SECTOR_SHIFT-1
1463                 call getfatsector
1464                 mov bx,di
1465                 add bx,bx
1466                 and bx,1FEh
1467                 movzx edi,word [gs:si+bx]
1468                 cmp di,0FFF0h
1469                 pop bx
1470                 pop si
1471                 pop eax
1472                 ret
1473 ;
1474 ; FAT28 ("FAT32") decoding routine.
1475 ;
1476 nextcluster_fat28:
1477                 push eax
1478                 push si
1479                 push bx
1480                 mov eax,edi
1481                 shr eax,SECTOR_SHIFT-2
1482                 call getfatsector
1483                 mov bx,di
1484                 add bx,bx
1485                 add bx,bx
1486                 and bx,1FCh
1487                 mov edi,dword [gs:si+bx]
1488                 and edi,0FFFFFFFh       ; 28 bits only
1489                 cmp edi,0FFFFFF0h
1490                 pop bx
1491                 pop si
1492                 pop eax
1493                 ret
1494
1495 ;
1496 ; nextsector:   Given a sector in EAX on input, return the next sector
1497 ;               of the same filesystem object, which may be the root
1498 ;               directory or a cluster chain.  Returns  EOF.
1499 ;
1500 ;               Assumes CS == DS.
1501 ;
1502 nextsector:
1503                 push edi
1504                 push edx
1505                 mov edx,[DataArea]
1506                 mov edi,eax
1507                 sub edi,edx
1508                 jae .isdata
1509
1510                 ; Root directory
1511                 inc eax
1512                 cmp eax,edx
1513                 cmc
1514                 jmp .done
1515
1516 .isdata:
1517                 not edi
1518                 test edi,[ClustMask]
1519                 jz .endcluster
1520
1521                 ; It's not the final sector in a cluster
1522                 inc eax
1523                 jmp .done
1524
1525 .endcluster:
1526                 push gs                 ; nextcluster trashes gs
1527                 push cx
1528                 not edi
1529                 mov cl,[ClustShift]
1530                 shr edi,cl
1531                 add edi,2
1532
1533                 ; Now EDI contains the cluster number
1534                 call nextcluster
1535                 cmc
1536                 jc .exit                ; There isn't anything else...
1537
1538                 ; New cluster number now in EDI
1539                 sub edi,2
1540                 shl edi,cl              ; CF <- 0, unless something is very wrong
1541                 lea eax,[edi+edx]
1542 .exit:
1543                 pop cx
1544                 pop gs
1545 .done:
1546                 pop edx
1547                 pop edi
1548                 ret
1549
1550 ;
1551 ; getfatsector: Check for a particular sector (in EAX) in the FAT cache,
1552 ;               and return a pointer in GS:SI, loading it if needed.
1553 ;
1554 ;               Assumes CS == DS.
1555 ;
1556 getfatsector:
1557                 add eax,[FAT]           ; FAT starting address
1558                 ; Fall through
1559
1560 ;
1561 ; getcachesector: Check for a particular sector (EAX) in the sector cache,
1562 ;                 and if it is already there, return a pointer in GS:SI
1563 ;                 otherwise load it and return said pointer.
1564 ;
1565 ;               Assumes CS == DS.
1566 ;
1567 getcachesector:
1568                 push cx
1569                 mov si,cache_seg
1570                 mov gs,si
1571                 mov si,CachePtrs        ; Sector cache pointers
1572                 mov cx,65536/SECTOR_SIZE
1573 .search:
1574                 cmp eax,[si]
1575                 jz .hit
1576                 add si,4
1577                 loop .search
1578
1579 .miss:
1580                 ; Need to load it.  Highly inefficient cache replacement
1581                 ; algorithm: Least Recently Written (LRW)
1582                 push bx
1583                 push es
1584                 push gs
1585                 pop es
1586                 mov bx,[NextCacheSlot]
1587                 inc bx
1588                 and bx,(1 << (16-SECTOR_SHIFT))-1
1589                 mov [NextCacheSlot],bx
1590                 shl bx,2
1591                 mov [CachePtrs+bx],eax
1592                 shl bx,SECTOR_SHIFT-2
1593                 mov si,bx
1594                 pushad
1595                 call getonesec
1596                 popad
1597                 pop es
1598                 pop bx
1599                 pop cx
1600                 ret
1601
1602 .hit:           ; We have it; get the pointer
1603                 sub si,CachePtrs
1604                 shl si,SECTOR_SHIFT-2
1605                 pop cx
1606                 ret
1607
1608 ; -----------------------------------------------------------------------------
1609 ;  Common modules
1610 ; -----------------------------------------------------------------------------
1611
1612 %include "getc.inc"             ; getc et al
1613 %include "conio.inc"            ; Console I/O
1614 %include "writestr.inc"         ; String output
1615 %include "parseconfig.inc"      ; High-level config file handling
1616 %include "parsecmd.inc"         ; Low-level config file handling
1617 %include "bcopy32.inc"          ; 32-bit bcopy
1618 %include "loadhigh.inc"         ; Load a file into high memory
1619 %include "font.inc"             ; VGA font stuff
1620 %include "graphics.inc"         ; VGA graphics
1621 %include "highmem.inc"          ; High memory sizing
1622 %include "strcpy.inc"           ; strcpy()
1623
1624 ; -----------------------------------------------------------------------------
1625 ;  Begin data section
1626 ; -----------------------------------------------------------------------------
1627
1628 ;
1629 ; Lower-case table for codepage 865
1630 ;
1631 lcase_low       equ 128
1632 lcase_high      equ 165
1633 lcase_tab       db 135, 129, 130, 131, 132, 133, 134, 135, 136, 137, 138
1634                 db 139, 140, 141, 132, 134, 130, 145, 145, 147, 148, 149
1635                 db 150, 151, 152, 148, 129, 155, 156, 155, 158, 159, 160
1636                 db 161, 162, 163, 164, 164
1637
1638 copyright_str   db ' Copyright (C) 1994-', year, ' H. Peter Anvin'
1639                 db CR, LF, 0
1640 boot_prompt     db 'boot: ', 0
1641 wipe_char       db BS, ' ', BS, 0
1642 err_notfound    db 'Could not find kernel image: ',0
1643 err_notkernel   db CR, LF, 'Invalid or corrupt kernel image.', CR, LF, 0
1644 err_noram       db 'It appears your computer has less than '
1645                 asciidec dosram_k
1646                 db 'K of low ("DOS")'
1647                 db CR, LF
1648                 db 'RAM.  Linux needs at least this amount to boot.  If you get'
1649                 db CR, LF
1650                 db 'this message in error, hold down the Ctrl key while'
1651                 db CR, LF
1652                 db 'booting, and I will take your word for it.', CR, LF, 0
1653 err_badcfg      db 'Unknown keyword in syslinux.cfg.', CR, LF, 0
1654 err_noparm      db 'Missing parameter in syslinux.cfg.', CR, LF, 0
1655 err_noinitrd    db CR, LF, 'Could not find ramdisk image: ', 0
1656 err_nohighmem   db 'Not enough memory to load specified kernel.', CR, LF, 0
1657 err_highload    db CR, LF, 'Kernel transfer failure.', CR, LF, 0
1658 err_oldkernel   db 'Cannot load a ramdisk with an old kernel image.'
1659                 db CR, LF, 0
1660 err_notdos      db ': attempted DOS system call', CR, LF, 0
1661 err_comlarge    db 'COMBOOT image too large.', CR, LF, 0
1662 err_a20         db CR, LF, 'A20 gate not responding!', CR, LF, 0
1663 err_bootfailed  db CR, LF, 'Boot failed: please change disks and press '
1664                 db 'a key to continue.', CR, LF, 0
1665 ready_msg       db 'Ready.', CR, LF, 0
1666 crlfloading_msg db CR, LF
1667 loading_msg     db 'Loading ', 0
1668 dotdot_msg      db '.'
1669 dot_msg         db '.', 0
1670 aborted_msg     db ' aborted.'                  ; Fall through to crlf_msg!
1671 crlf_msg        db CR, LF
1672 null_msg        db 0
1673 crff_msg        db CR, FF, 0
1674 syslinux_cfg    db 'SYSLINUXCFG'                ; Mangled form
1675 ConfigName      db 'syslinux.cfg',0             ; Unmangled form
1676 %if IS_MDSLINUX
1677 manifest        db 'MANIFEST   '
1678 %endif
1679 ;
1680 ; Command line options we'd like to take a look at
1681 ;
1682 ; mem= and vga= are handled as normal 32-bit integer values
1683 initrd_cmd      db 'initrd='
1684 initrd_cmd_len  equ 7
1685
1686 ;
1687 ; Config file keyword table
1688 ;
1689 %include "keywords.inc"
1690
1691 ;
1692 ; Extensions to search for (in *forward* order).
1693 ;
1694 exten_table:    db 'CBT',0              ; COMBOOT (specific)
1695                 db 'BSS',0              ; Boot Sector (add superblock)
1696                 db 'BS ',0              ; Boot Sector 
1697                 db 'COM',0              ; COMBOOT (same as DOS)
1698                 db 'C32',0              ; COM32
1699 exten_table_end:
1700                 dd 0, 0                 ; Need 8 null bytes here
1701
1702 ;
1703 ; Misc initialized (data) variables
1704 ;
1705 %ifdef debug                            ; This code for debugging only
1706 debug_magic     dw 0D00Dh               ; Debug code sentinel
1707 %endif
1708 AppendLen       dw 0                    ; Bytes in append= command
1709 OntimeoutLen    dw 0                    ; Bytes in ontimeout command
1710 OnerrorLen      dw 0                    ; Bytes in onerror command
1711 KbdTimeOut      dw 0                    ; Keyboard timeout (if any)
1712 CmdLinePtr      dw cmd_line_here        ; Command line advancing pointer
1713 initrd_flag     equ $
1714 initrd_ptr      dw 0                    ; Initial ramdisk pointer/flag
1715 VKernelCtr      dw 0                    ; Number of registered vkernels
1716 ForcePrompt     dw 0                    ; Force prompt
1717 AllowImplicit   dw 1                    ; Allow implicit kernels
1718 AllowOptions    dw 1                    ; User-specified options allowed
1719 SerialPort      dw 0                    ; Serial port base (or 0 for no serial port)
1720 VGAFontSize     dw 16                   ; Defaults to 16 byte font
1721 UserFont        db 0                    ; Using a user-specified font
1722 ScrollAttribute db 07h                  ; White on black (for text mode)
1723
1724                 alignb 4, db 0
1725 BufSafe         dw trackbufsize/SECTOR_SIZE     ; Clusters we can load into trackbuf
1726 BufSafeSec      dw trackbufsize/SECTOR_SIZE     ; = how many sectors?
1727 BufSafeBytes    dw trackbufsize         ; = how many bytes?
1728 EndOfGetCBuf    dw getcbuf+trackbufsize ; = getcbuf+BufSafeBytes
1729 %ifndef DEPEND
1730 %if ( trackbufsize % SECTOR_SIZE ) != 0
1731 %error trackbufsize must be a multiple of SECTOR_SIZE
1732 %endif
1733 %endif
1734 ;
1735 ; Stuff for the command line; we do some trickery here with equ to avoid
1736 ; tons of zeros appended to our file and wasting space
1737 ;
1738 linuxauto_cmd   db 'linux auto',0
1739 linuxauto_len   equ $-linuxauto_cmd
1740 boot_image      db 'BOOT_IMAGE='
1741 boot_image_len  equ $-boot_image
1742
1743                 align 4, db 0           ; Pad out any unfinished dword
1744 ldlinux_end     equ $
1745 ldlinux_len     equ $-ldlinux_magic
1746
1747 ; VGA font buffer at the end of memory (so loading a font works even
1748 ; in graphics mode.)
1749 vgafontbuf      equ 0E000h
1750
1751 ; This is a compile-time assert that we didn't run out of space
1752 %ifndef DEPEND
1753 %if (ldlinux_end-bootsec+7C00h) > vgafontbuf
1754 %error "Out of memory, better reorganize something..."
1755 %endif
1756 %endif