d9feb97599f091e63e2c520b3dfd42a5b690dbf9
[profile/ivi/syslinux.git] / extlinux.asm
1 ; -*- fundamental -*- (asm-mode sucks)
2 ; $Id$
3 ; ****************************************************************************
4 ;
5 ;  extlinux.asm
6 ;
7 ;  A program to boot Linux kernels off an ext2/ext3 filesystem.
8 ;
9 ;   Copyright (C) 1994-2004  H. Peter Anvin
10 ;
11 ;  This program is free software; you can redistribute it and/or modify
12 ;  it under the terms of the GNU General Public License as published by
13 ;  the Free Software Foundation, Inc., 53 Temple Place Ste 330,
14 ;  Boston MA 02111-1307, USA; either version 2 of the License, or
15 ;  (at your option) any later version; incorporated herein by reference.
16
17 ; ****************************************************************************
18
19 %define IS_EXTLINUX 1
20 %include "macros.inc"
21 %include "config.inc"
22 %include "kernel.inc"
23 %include "bios.inc"
24 %include "tracers.inc"
25
26 %include "ext2_fs.inc"
27
28 ;
29 ; Some semi-configurable constants... change on your own risk.
30 ;
31 my_id           equ extlinux_id
32 FILENAME_MAX_LG2 equ 8                  ; log2(Max filename size Including final null)
33 FILENAME_MAX    equ (1 << FILENAME_MAX) ; Max mangled filename size
34 NULLFILE        equ ' '                 ; First char space == null filename
35 retry_count     equ 6                   ; How patient are we with the disk?
36 %assign HIGHMEM_SLOP 0                  ; Avoid this much memory near the top
37 LDLINUX_MAGIC   equ 0x3eb202fe          ; A random number to identify ourselves with
38
39 MAX_OPEN_LG2    equ 6                   ; log2(Max number of open files)
40 MAX_OPEN        equ (1 << MAX_OPEN_LG2)
41
42 SECTOR_SHIFT    equ 9
43 SECTOR_SIZE     equ (1 << SECTOR_SHIFT)
44
45 ;
46 ; This is what we need to do when idle
47 ;
48 %macro  RESET_IDLE 0
49         ; Nothing
50 %endmacro
51 %macro  DO_IDLE 0
52         ; Nothing
53 %endmacro
54
55 ;
56 ; The following structure is used for "virtual kernels"; i.e. LILO-style
57 ; option labels.  The options we permit here are `kernel' and `append
58 ; Since there is no room in the bottom 64K for all of these, we
59 ; stick them at vk_seg:0000 and copy them down before we need them.
60 ;
61                 struc vkernel
62 vk_vname:       resb FILENAME_MAX       ; Virtual name **MUST BE FIRST!**
63 vk_rname:       resb FILENAME_MAX       ; Real name
64 vk_appendlen:   resw 1
65                 alignb 4
66 vk_append:      resb max_cmd_len+1      ; Command line
67                 alignb 4
68 vk_end:         equ $                   ; Should be <= vk_size
69                 endstruc
70
71 ;
72 ; Segment assignments in the bottom 640K
73 ; Stick to the low 512K in case we're using something like M-systems flash
74 ; which load a driver into low RAM (evil!!)
75 ;
76 ; 0000h - main code/data segment (and BIOS segment)
77 ;
78 real_mode_seg   equ 4000h
79 cache_seg       equ 3000h               ; 64K area for metadata cache
80 vk_seg          equ 2000h               ; Virtual kernels
81 xfer_buf_seg    equ 1000h               ; Bounce buffer for I/O to high mem
82 comboot_seg     equ real_mode_seg       ; COMBOOT image loading zone
83
84 ;
85 ; File structure.  This holds the information for each currently open file.
86 ;
87                 struc open_file_t
88 file_left       resd 1                  ; Number of sectors left (0 = free)
89 file_sector     resd 1                  ; Next linear sector to read
90 file_in_sec     resd 1                  ; Sector where inode lives
91 file_in_off     resw 1
92                 resw 1
93                 endstruc
94
95 %ifndef DEPEND
96 %if (open_file_t_size & (open_file_t_size-1))
97 %error "open_file_t is not a power of 2"
98 %endif
99 %endif
100
101 ; ---------------------------------------------------------------------------
102 ;   BEGIN CODE
103 ; ---------------------------------------------------------------------------
104
105 ;
106 ; Memory below this point is reserved for the BIOS and the MBR
107 ;
108 BSS_START       equ 1000h
109                 section .bss start=BSS_START
110 trackbufsize    equ 8192
111 trackbuf        resb trackbufsize       ; Track buffer goes here
112 getcbuf         resb trackbufsize
113                 ; ends at 5000h
114
115                 alignb 8
116
117                 ; Expanded superblock
118 SuperInfo       equ $
119                 resq 16                 ; The first 16 bytes expanded 8 times
120 FAT             resd 1                  ; Location of (first) FAT
121 RootDirArea     resd 1                  ; Location of root directory area
122 RootDir         resd 1                  ; Location of root directory proper
123 DataArea        resd 1                  ; Location of data area
124 RootDirSize     resd 1                  ; Root dir size in sectors
125 TotalSectors    resd 1                  ; Total number of sectors
126 EndSector       resd 1                  ; Location of filesystem end
127 ClustSize       resd 1                  ; Bytes/cluster
128 ClustMask       resd 1                  ; Sectors/cluster - 1
129 CopySuper       resb 1                  ; Distinguish .bs versus .bss
130 DriveNumber     resb 1                  ; BIOS drive number
131 ClustShift      resb 1                  ; Shift count for sectors/cluster
132 ClustByteShift  resb 1                  ; Shift count for bytes/cluster
133
134                 alignb open_file_t_size
135 Files           resb MAX_OPEN*open_file_t_size
136
137 ;
138 ; Constants for the xfer_buf_seg
139 ;
140 ; The xfer_buf_seg is also used to store message file buffers.  We
141 ; need two trackbuffers (text and graphics), plus a work buffer
142 ; for the graphics decompressor.
143 ;
144 xbs_textbuf     equ 0                   ; Also hard-coded, do not change
145 xbs_vgabuf      equ trackbufsize
146 xbs_vgatmpbuf   equ 2*trackbufsize
147
148
149                 section .text
150                 org 7C00h
151 ;
152 ; Some of the things that have to be saved very early are saved
153 ; "close" to the initial stack pointer offset, in order to
154 ; reduce the code size...
155 ;
156 StackBuf        equ $-44-32             ; Start the stack here (grow down - 4K)
157 PartInfo        equ StackBuf            ; Saved partition table entry
158 FloppyTable     equ PartInfo+16         ; Floppy info table (must follow PartInfo)
159 OrigFDCTabPtr   equ StackBuf-4          ; The high dword on the stack
160
161 ;
162 ; Primary entry point.  Tempting as though it may be, we can't put the
163 ; initial "cli" here; the jmp opcode in the first byte is part of the
164 ; "magic number" (using the term very loosely) for the DOS superblock.
165 ;
166 bootsec         equ $
167                 jmp short start         ; 2 bytes
168                 nop                     ; 1 byte
169 ;
170 ; "Superblock" follows -- it's in the boot sector, so it's already
171 ; loaded and ready for us
172 ;
173 bsOemName       db 'EXTLINUX'           ; The SYS command sets this, so...
174 ;
175 ; These are the fields we actually care about.  We end up expanding them
176 ; all to dword size early in the code, so generate labels for both
177 ; the expanded and unexpanded versions.
178 ;
179 %macro          superb 1
180 bx %+ %1        equ SuperInfo+($-superblock)*8+4
181 bs %+ %1        equ $
182                 zb 1
183 %endmacro
184 %macro          superw 1
185 bx %+ %1        equ SuperInfo+($-superblock)*8
186 bs %+ %1        equ $
187                 zw 1
188 %endmacro
189 %macro          superd 1
190 bx %+ %1        equ $                   ; no expansion for dwords
191 bs %+ %1        equ $
192                 zd 1
193 %endmacro
194 superblock      equ $
195                 superw BytesPerSec
196                 superb SecPerClust
197                 superw ResSectors
198                 superb FATs
199                 superw RootDirEnts
200                 superw Sectors
201                 superb Media
202                 superw FATsecs
203                 superw SecPerTrack
204                 superw Heads
205 superinfo_size  equ ($-superblock)-1    ; How much to expand
206                 superd Hidden
207                 superd HugeSectors
208                 ;
209                 ; This is as far as FAT12/16 and FAT32 are consistent
210                 ;
211                 zb 54                   ; FAT12/16 need 26 more bytes,
212                                         ; FAT32 need 54 more bytes
213 superblock_len  equ $-superblock
214
215 SecPerClust     equ bxSecPerClust
216 ;
217 ; Note we don't check the constraints above now; we did that at install
218 ; time (we hope!)
219 ;
220 start:
221                 cli                     ; No interrupts yet, please
222                 cld                     ; Copy upwards
223 ;
224 ; Set up the stack
225 ;
226                 xor ax,ax
227                 mov ss,ax
228                 mov sp,StackBuf         ; Just below BSS
229                 mov es,ax
230 ;
231 ; DS:SI may contain a partition table entry.  Preserve it for us.
232 ;
233                 mov cx,8                ; Save partition info
234                 mov di,sp
235                 rep movsw
236
237                 mov ds,ax               ; Now we can initialize DS...
238
239 ;
240 ; Now sautee the BIOS floppy info block to that it will support decent-
241 ; size transfers; the floppy block is 11 bytes and is stored in the
242 ; INT 1Eh vector (brilliant waste of resources, eh?)
243 ;
244 ; Of course, if BIOSes had been properly programmed, we wouldn't have
245 ; had to waste precious space with this code.
246 ;
247                 mov bx,fdctab
248                 lfs si,[bx]             ; FS:SI -> original fdctab
249                 push fs                 ; Save on stack in case we need to bail
250                 push si
251
252                 ; Save the old fdctab even if hard disk so the stack layout
253                 ; is the same.  The instructions above do not change the flags
254                 mov [DriveNumber],dl    ; Save drive number in DL
255                 and dl,dl               ; If floppy disk (00-7F), assume no
256                                         ; partition table
257                 js harddisk
258
259 floppy:
260                 mov cl,6                ; 12 bytes (CX == 0)
261                 ; es:di -> FloppyTable already
262                 ; This should be safe to do now, interrupts are off...
263                 mov [bx],di             ; FloppyTable
264                 mov [bx+2],ax           ; Segment 0
265                 fs rep movsw            ; Faster to move words
266                 mov cl,[bsSecPerTrack]  ; Patch the sector count
267                 mov [di-8],cl
268                 ; AX == 0 here
269                 int 13h                 ; Some BIOSes need this
270
271                 jmp short not_harddisk
272 ;
273 ; The drive number and possibly partition information was passed to us
274 ; by the BIOS or previous boot loader (MBR).  Current "best practice" is to
275 ; trust that rather than what the superblock contains.
276 ;
277 ; Would it be better to zero out bsHidden if we don't have a partition table?
278 ;
279 ; Note: di points to beyond the end of PartInfo
280 ;
281 harddisk:
282                 test byte [di-16],7Fh   ; Sanity check: "active flag" should
283                 jnz no_partition        ; be 00 or 80
284                 mov eax,[di-8]          ; Partition offset (dword)
285                 mov [bsHidden],eax
286 no_partition:
287 ;
288 ; Get disk drive parameters (don't trust the superblock.)  Don't do this for
289 ; floppy drives -- INT 13:08 on floppy drives will (may?) return info about
290 ; what the *drive* supports, not about the *media*.  Fortunately floppy disks
291 ; tend to have a fixed, well-defined geometry which is stored in the superblock.
292 ;
293                 ; DL == drive # still
294                 mov ah,08h
295                 int 13h
296                 jc no_driveparm
297                 and ah,ah
298                 jnz no_driveparm
299                 shr dx,8
300                 inc dx                  ; Contains # of heads - 1
301                 mov [bsHeads],dx
302                 and cx,3fh
303                 mov [bsSecPerTrack],cx
304 no_driveparm:
305 not_harddisk:
306 ;
307 ; Ready to enable interrupts, captain
308 ;
309                 sti
310
311
312 ;
313 ; Do we have EBIOS (EDD)?
314 ;
315 eddcheck:
316                 mov bx,55AAh
317                 mov ah,41h              ; EDD existence query
318                 mov dl,[DriveNumber]
319                 int 13h
320                 jc .noedd
321                 cmp bx,0AA55h
322                 jne .noedd
323                 test cl,1               ; Extended disk access functionality set
324                 jz .noedd
325                 ;
326                 ; We have EDD support...
327                 ;
328                 mov byte [getlinsec+1],getlinsec_ebios-(getlinsec+2)
329 .noedd:
330
331 ;
332 ; Load the first sector of LDLINUX.SYS; this used to be all proper
333 ; with parsing the superblock and root directory; it doesn't fit
334 ; together with EBIOS support, unfortunately.
335 ;
336                 mov eax,[FirstSector]   ; Sector start
337                 mov bx,ldlinux_sys      ; Where to load it
338                 call getonesec
339                 
340                 ; Some modicum of integrity checking
341                 cmp dword [ldlinux_magic],LDLINUX_MAGIC
342                 jne kaboom
343                 cmp dword [ldlinux_magic+4],HEXDATE
344                 jne kaboom
345
346                 ; Go for it...
347                 jmp ldlinux_ent
348
349 ;
350 ; kaboom: write a message and bail out.
351 ;
352 kaboom:
353                 xor si,si
354                 mov ss,si               
355                 mov sp,StackBuf-4       ; Reset stack
356                 mov ds,si               ; Reset data segment
357                 pop dword [fdctab]      ; Restore FDC table
358 .patch:         mov si,bailmsg
359                 call writestr           ; Returns with AL = 0
360                 cbw                     ; AH <- 0
361                 int 16h                 ; Wait for keypress
362                 int 19h                 ; And try once more to boot...
363 .norge:         jmp short .norge        ; If int 19h returned; this is the end
364
365 ;
366 ;
367 ; writestr: write a null-terminated string to the console
368 ;           This assumes we're on page 0.  This is only used for early
369 ;           messages, so it should be OK.
370 ;
371 writestr:
372 .loop:          lodsb
373                 and al,al
374                 jz .return
375                 mov ah,0Eh              ; Write to screen as TTY
376                 mov bx,0007h            ; Attribute
377                 int 10h
378                 jmp short .loop
379 .return:        ret
380
381 ;
382 ; xint13: wrapper for int 13h which will retry 6 times and then die,
383 ;         AND save all registers except BP
384 ;
385 xint13:
386 .again:
387                 mov bp,retry_count
388 .loop:          pushad
389                 int 13h
390                 popad
391                 jnc writestr.return
392                 dec bp
393                 jnz .loop
394 .disk_error:
395                 jmp strict near kaboom  ; Patched
396
397
398 ;
399 ; getonesec: get one disk sector
400 ;
401 getonesec:
402                 mov bp,1                ; One sector
403                 ; Fall through
404
405 ;
406 ; getlinsec: load a sequence of BP floppy sector given by the linear sector
407 ;            number in EAX into the buffer at ES:BX.  We try to optimize
408 ;            by loading up to a whole track at a time, but the user
409 ;            is responsible for not crossing a 64K boundary.
410 ;            (Yes, BP is weird for a count, but it was available...)
411 ;
412 ;            On return, BX points to the first byte after the transferred
413 ;            block.
414 ;
415 ;            This routine assumes CS == DS, and trashes most registers.
416 ;
417 ; Stylistic note: use "xchg" instead of "mov" when the source is a register
418 ; that is dead from that point; this saves space.  However, please keep
419 ; the order to dst,src to keep things sane.
420 ;
421 getlinsec:
422                 jmp strict short getlinsec_cbios        ; This is patched
423
424 ;
425 ; getlinsec_ebios:
426 ;
427 ; getlinsec implementation for EBIOS (EDD)
428 ;
429 getlinsec_ebios:
430                 mov si,dapa                     ; Load up the DAPA
431                 mov [si+4],bx
432                 mov [si+6],es
433                 mov [si+8],eax
434 .loop:
435                 push bp                         ; Sectors left
436                 call maxtrans                   ; Enforce maximum transfer size
437 .bp_ok:
438                 mov [si+2],bp
439                 mov dl,[DriveNumber]
440                 mov ah,42h                      ; Extended Read
441                 call xint13
442                 pop bp
443                 movzx eax,word [si+2]           ; Sectors we read
444                 add [si+8],eax                  ; Advance sector pointer
445                 sub bp,ax                       ; Sectors left
446                 shl ax,9                        ; 512-byte sectors
447                 add [si+4],ax                   ; Advance buffer pointer
448                 and bp,bp
449                 jnz .loop
450                 mov eax,[si+8]                  ; Next sector
451                 mov bx,[si+4]                   ; Buffer pointer
452                 ret
453
454 ;
455 ; getlinsec_cbios:
456 ;
457 ; getlinsec implementation for legacy CBIOS
458 ;
459 getlinsec_cbios:
460 .loop:
461                 push eax
462                 push bp
463                 push bx
464
465                 movzx esi,word [bsSecPerTrack]
466                 movzx edi,word [bsHeads]
467                 ;
468                 ; Dividing by sectors to get (track,sector): we may have
469                 ; up to 2^18 tracks, so we need to use 32-bit arithmetric.
470                 ;
471                 xor edx,edx             ; Zero-extend LBA to 64 bits
472                 div esi
473                 xor cx,cx
474                 xchg cx,dx              ; CX <- sector index (0-based)
475                                         ; EDX <- 0
476                 ; eax = track #
477                 div edi                 ; Convert track to head/cyl
478                 ;
479                 ; Now we have AX = cyl, DX = head, CX = sector (0-based),
480                 ; BP = sectors to transfer, SI = bsSecPerTrack,
481                 ; ES:BX = data target
482                 ;
483
484                 call maxtrans                   ; Enforce maximum transfer size
485
486                 ; Must not cross track boundaries, so BP <= SI-CX
487                 sub si,cx
488                 cmp bp,si
489                 jna .bp_ok
490                 mov bp,si
491 .bp_ok: 
492
493                 shl ah,6                ; Because IBM was STOOPID
494                                         ; and thought 8 bits were enough
495                                         ; then thought 10 bits were enough...
496                 inc cx                  ; Sector numbers are 1-based, sigh
497                 or cl,ah
498                 mov ch,al
499                 mov dh,dl
500                 mov dl,[DriveNumber]
501                 xchg ax,bp              ; Sector to transfer count
502                 mov ah,02h              ; Read sectors
503                 call xint13
504                 movzx ecx,al
505                 shl ax,9                ; Convert sectors in AL to bytes in AX
506                 pop bx
507                 add bx,ax
508                 pop bp
509                 pop eax
510                 add eax,ecx
511                 sub bp,cx
512                 jnz .loop
513                 ret
514
515 ;
516 ; Truncate BP to MaxTransfer
517 ;
518 maxtrans:
519                 cmp bp,[MaxTransfer]
520                 jna .ok
521                 mov bp,[MaxTransfer]
522 .ok:            ret
523
524 ;
525 ; Error message on failure
526 ;
527 bailmsg:        db 'Boot failed', 0Dh, 0Ah, 0
528
529 ;
530 ; EBIOS disk address packet
531 ;
532                 align 4, db 0
533 dapa:
534                 dw 16                           ; Packet size
535 .count:         dw 0                            ; Block count
536 .off:           dw 0                            ; Offset of buffer
537 .seg:           dw 0                            ; Segment of buffer
538 .lba:           dd 0                            ; LBA (LSW)
539                 dd 0                            ; LBA (MSW)
540
541
542 %if 1
543 bs_checkpt_off  equ ($-$$)
544 %ifndef DEPEND
545 %if bs_checkpt_off > 1F8h
546 %error "Boot sector overflow"
547 %endif
548 %endif
549
550                 zb 1F8h-($-$$)
551 %endif
552 FirstSector     dd 0xDEADBEEF                   ; Location of sector 1
553 MaxTransfer     dw 0x007F                       ; Max transfer size
554 bootsignature   dw 0AA55h
555
556 ;
557 ; ===========================================================================
558 ;  End of boot sector
559 ; ===========================================================================
560 ;  Start of LDLINUX.SYS
561 ; ===========================================================================
562
563 ldlinux_sys:
564
565 syslinux_banner db 0Dh, 0Ah
566                 db 'EXTLINUX '
567                 db version_str, ' ', date, ' ', 0
568                 db 0Dh, 0Ah, 1Ah        ; EOF if we "type" this in DOS
569
570                 align 8, db 0
571 ldlinux_magic   dd LDLINUX_MAGIC
572                 dd HEXDATE
573
574 ;
575 ; This area is patched by the installer.  It is found by looking for
576 ; LDLINUX_MAGIC, plus 8 bytes.
577 ;
578 patch_area:
579 LDLDwords       dw 0            ; Total dwords starting at ldlinux_sys
580 LDLSectors      dw 0            ; Number of sectors - (bootsec+this sec)
581 CheckSum        dd 0            ; Checksum starting at ldlinux_sys
582                                 ; value = LDLINUX_MAGIC - [sum of dwords]
583
584 ; Space for up to 64 sectors, the theoretical maximum
585 SectorPtrs      times 64 dd 0
586
587 ldlinux_ent:
588
589 ; Note that some BIOSes are buggy and run the boot sector at 07C0:0000
590 ; instead of 0000:7C00 and the like.  We don't want to add anything
591 ; more to the boot sector, so it is written to not assume a fixed
592 ; value in CS, but we don't want to deal with that anymore from now
593 ; on.
594 ;
595                 jmp 0:.next
596 .next:
597
598 ;
599 ; Tell the user we got this far
600 ;
601                 mov si,syslinux_banner
602                 call writestr
603
604 ;
605 ; Patch disk error handling
606 ;
607                 mov word [xint13.disk_error+1],do_disk_error-(xint13.disk_error+3)
608
609 ;
610 ; Now we read the rest of LDLINUX.SYS.  Don't bother loading the first
611 ; sector again, though.
612 ;
613 load_rest:
614                 mov si,SectorPtrs
615                 mov bx,7C00h+2*SECTOR_SIZE      ; Where we start loading
616                 mov cx,[LDLSectors]
617
618 .get_chunk:
619                 jcxz .done
620                 xor bp,bp
621                 lodsd                           ; First sector of this chunk
622
623                 mov edx,eax
624
625 .make_chunk:
626                 inc bp
627                 dec cx
628                 jz .chunk_ready
629                 inc edx                         ; Next linear sector
630                 cmp [esi],edx                   ; Does it match
631                 jnz .chunk_ready                ; If not, this is it
632                 add esi,4                       ; If so, add sector to chunk
633                 jmp short .make_chunk
634
635 .chunk_ready:
636                 call getlinsecsr
637                 shl bp,SECTOR_SHIFT
638                 add bx,bp
639                 jmp .get_chunk
640
641 .done:
642
643 ;
644 ; All loaded up, verify that we got what we needed.
645 ; Note: the checksum field is embedded in the checksum region, so
646 ; by the time we get to the end it should all cancel out.
647 ;
648 verify_checksum:
649                 mov si,ldlinux_sys
650                 mov cx,[LDLDwords]
651                 mov edx,-LDLINUX_MAGIC
652 .checksum:
653                 lodsd
654                 add edx,eax
655                 loop .checksum
656
657                 and edx,edx                     ; Should be zero
658                 jz all_read                     ; We're cool, go for it!
659
660 ;
661 ; Uh-oh, something went bad...
662 ;
663                 mov si,checksumerr_msg
664                 call writestr
665                 jmp kaboom
666
667 ;
668 ; -----------------------------------------------------------------------------
669 ; Subroutines that have to be in the first sector
670 ; -----------------------------------------------------------------------------
671
672 ;
673 ; getlinsecsr: save registers, call getlinsec, restore registers
674 ;
675 getlinsecsr:    pushad
676                 call getlinsec
677                 popad
678                 ret
679
680 ;
681 ; This routine captures disk errors, and tries to decide if it is
682 ; time to reduce the transfer size.
683 ;
684 do_disk_error:
685                 cmp ah,42h
686                 je .ebios
687                 shr al,1                ; Try reducing the transfer size
688                 mov [MaxTransfer],al    
689                 jz kaboom               ; If we can't, we're dead...
690                 jmp xint13              ; Try again
691 .ebios:
692                 push ax
693                 mov ax,[si+2]
694                 shr ax,1
695                 mov [MaxTransfer],ax
696                 mov [si+2],ax
697                 pop ax
698                 jmp xint13
699
700 ;
701 ; Checksum error message
702 ;
703 checksumerr_msg db 'Load error - ', 0   ; Boot failed appended
704
705 ;
706 ; Debug routine
707 ;
708 %ifdef debug
709 safedumpregs:
710                 cmp word [Debug_Magic],0D00Dh
711                 jnz nc_return
712                 jmp dumpregs
713 %endif
714
715 rl_checkpt      equ $                           ; Must be <= 8000h
716
717 rl_checkpt_off  equ ($-$$)
718 %if 0 ; ndef DEPEND
719 %if rl_checkpt_off > 400h
720 %error "Sector 1 overflow"
721 %endif
722 %endif
723
724 ; ----------------------------------------------------------------------------
725 ;  End of code and data that have to be in the first sector
726 ; ----------------------------------------------------------------------------
727
728 all_read:
729 ;
730 ; Let the user (and programmer!) know we got this far.  This used to be
731 ; in Sector 1, but makes a lot more sense here.
732 ;
733                 mov si,copyright_str
734                 call writestr
735
736 ;
737 ; Insane hack to expand the DOS superblock to dwords
738 ;
739 expand_super:
740                 xor eax,eax
741                 mov si,superblock
742                 mov di,SuperInfo
743                 mov cx,superinfo_size
744 .loop:
745                 lodsw
746                 dec si
747                 stosd                           ; Store expanded word
748                 xor ah,ah
749                 stosd                           ; Store expanded byte
750                 loop .loop
751
752 ;
753 ; Compute some information about this filesystem.
754 ;
755
756 ;
757 ; Common initialization code
758 ;
759 %include "cpuinit.inc"
760
761 ;
762 ; Clear Files structures
763 ;
764                 mov di,Files
765                 mov cx,(MAX_OPEN*open_file_t_size)/4
766                 xor eax,eax
767                 rep stosd
768
769 ;
770 ; Initialize the metadata cache
771 ;
772                 call initcache
773
774 ;
775 ; Initialization that does not need to go into the any of the pre-load
776 ; areas
777 ;
778                 ; Now set up screen parameters
779                 call adjust_screen
780
781                 ; Wipe the F-key area
782                 mov al,NULLFILE
783                 mov di,FKeyName
784                 mov cx,10*(1 << FILENAME_MAX_LG2)
785                 rep stosb
786
787 ;
788 ; Now, everything is "up and running"... patch kaboom for more
789 ; verbosity and using the full screen system
790 ;
791                 ; E9 = JMP NEAR
792                 mov dword [kaboom.patch],0e9h+((kaboom2-(kaboom.patch+3)) << 8)
793
794 ;
795 ; Now we're all set to start with our *real* business.  First load the
796 ; configuration file (if any) and parse it.
797 ;
798 ; In previous versions I avoided using 32-bit registers because of a
799 ; rumour some BIOSes clobbered the upper half of 32-bit registers at
800 ; random.  I figure, though, that if there are any of those still left
801 ; they probably won't be trying to install Linux on them...
802 ;
803 ; The code is still ripe with 16-bitisms, though.  Not worth the hassle
804 ; to take'm out.  In fact, we may want to put them back if we're going
805 ; to boot ELKS at some point.
806 ;
807                 mov si,linuxauto_cmd            ; Default command: "linux auto"
808                 mov di,default_cmd
809                 mov cx,linuxauto_len
810                 rep movsb
811
812                 mov di,KbdMap                   ; Default keymap 1:1
813                 xor al,al
814                 inc ch                          ; CX <- 256
815 mkkeymap:       stosb
816                 inc al
817                 loop mkkeymap
818
819 ;
820 ; Load configuration file
821 ;
822                 mov di,syslinux_cfg
823                 call open
824                 jz no_config_file
825
826 ;
827 ; Now we have the config file open.  Parse the config file and
828 ; run the user interface.
829 ;
830 %include "ui.inc"
831
832 ;
833 ; Linux kernel loading code is common.
834 ;
835 %include "runkernel.inc"
836
837 ;
838 ; COMBOOT-loading code
839 ;
840 %include "comboot.inc"
841 %include "com32.inc"
842 %include "cmdline.inc"
843
844 ;
845 ; Boot sector loading code
846 ;
847 %include "bootsect.inc"
848
849 ;
850 ; abort_check: let the user abort with <ESC> or <Ctrl-C>
851 ;
852 abort_check:
853                 call pollchar
854                 jz ac_ret1
855                 pusha
856                 call getchar
857                 cmp al,27                       ; <ESC>
858                 je ac_kill
859                 cmp al,3                        ; <Ctrl-C>
860                 jne ac_ret2
861 ac_kill:        mov si,aborted_msg
862
863 ;
864 ; abort_load: Called by various routines which wants to print a fatal
865 ;             error message and return to the command prompt.  Since this
866 ;             may happen at just about any stage of the boot process, assume
867 ;             our state is messed up, and just reset the segment registers
868 ;             and the stack forcibly.
869 ;
870 ;             SI    = offset (in _text) of error message to print
871 ;
872 abort_load:
873                 mov ax,cs                       ; Restore CS = DS = ES
874                 mov ds,ax
875                 mov es,ax
876                 cli
877                 mov sp,StackBuf-2*3             ; Reset stack
878                 mov ss,ax                       ; Just in case...
879                 sti
880                 call cwritestr                  ; Expects SI -> error msg
881 al_ok:          jmp enter_command               ; Return to command prompt
882 ;
883 ; End of abort_check
884 ;
885 ac_ret2:        popa
886 ac_ret1:        ret
887
888 ;
889 ; allocate_file: Allocate a file structure
890 ;
891 ;               If successful:
892 ;                 ZF set
893 ;                 BX = file pointer
894 ;               In unsuccessful:
895 ;                 ZF clear
896 ;
897 allocate_file:
898                 TRACER 'a'
899                 push cx
900                 mov bx,Files
901                 mov cx,MAX_OPEN
902 .check:         cmp dword [bx], byte 0
903                 je .found
904                 add bx,open_file_t_size         ; ZF = 0
905                 loop .check
906                 ; ZF = 0 if we fell out of the loop
907 .found:         pop cx
908                 ret
909 ;
910 ; open_inode:
911 ;            Open a file indicated by an inode number in EAX
912 ;
913 ;            NOTE: This file considers finding a zero-length file an
914 ;            error.  This is so we don't have to deal with that special
915 ;            case elsewhere in the program (most loops have the test
916 ;            at the end).
917 ;
918 ;            If successful:
919 ;               ZF clear
920 ;               SI          = file pointer
921 ;               DX:AX = EAX = file length in bytes
922 ;            If unsuccessful
923 ;               ZF set
924 ;
925 open_inode.allocate_failure:
926                 xor eax,eax
927                 ret
928
929 open_inode:
930                 call allocate_file
931                 jnz .allocate_failure
932
933                 push gs
934                 ; First, get the appropriate inode group and index
935                 dec eax                         ; There is no inode 0
936                 xor edx,edx
937                 mov [bx+file_sector],edx
938                 div dword [SuperBlock+s_inodes_per_group]
939                 ; EAX = inode group; EDX = inode within group
940                 push edx
941
942                 ; Now, we need the block group descriptor.
943                 ; To get that, we first need the relevant descriptor block.
944                                 
945                 shl eax, ext2_group_desc_lg2size ; Get byte offset in desc table
946                 xor edx,edx
947                 div dword [BlockSize]
948                 ; eax = block #, edx = offset in block
949                 add eax,dword [SuperBlock+s_first_data_block]
950                 inc eax                         ; s_first_data_block+1
951                 mov cl,[ClustShift]
952                 shl eax,cl
953                 call getcachesec                ; Get the group descriptor
954                 add si,dx
955                 mov esi,[gs:si+bg_inode_table]  ; Get inode table block #
956                 pop eax                         ; Get inode within group
957                 movzx edx, word [SuperBlock+s_inode_size]
958                 mul edx
959                 ; edx:eax = byte offset in inode table
960                 div dword [BlockSize]
961                 ; eax = block # versus inode table, edx = offset in block
962                 add eax,esi
963                 shl eax,cl                      ; Turn into sector
964                 push dx
965                 shr edx,SECTOR_SHIFT
966                 add eax,edx
967                 mov [bx+file_in_sec],eax
968                 pop dx
969                 and dx,SECTOR_SIZE-1
970                 mov [bx+file_in_off],dx
971
972                 call getcachesec
973                 add si,dx
974                 mov eax,[gs:si+i_size]
975                 push eax
976                 add eax,SECTOR_SIZE-1
977                 shr eax,SECTOR_SHIFT
978                 mov [bx+file_left],eax
979                 pop eax
980                 mov si,bx
981                 mov edx,eax
982                 shr edx,16                      ; 16-bitism, sigh
983                 and eax,eax                     ; ZF clear unless zero-length file
984                 pop gs
985                 ret
986
987 ;
988 ; close:
989 ;            Deallocates a file structure (pointer in SI)
990 ;            Assumes CS == DS.
991 ;
992 close:
993                 mov dword [si],0                ; First dword == file_left
994                 ret
995
996 ;
997 ; searchdir:
998 ;            Search the root directory for a pre-mangled filename in DS:DI.
999 ;
1000 ;            NOTE: This file considers finding a zero-length file an
1001 ;            error.  This is so we don't have to deal with that special
1002 ;            case elsewhere in the program (most loops have the test
1003 ;            at the end).
1004 ;
1005 ;            If successful:
1006 ;               ZF clear
1007 ;               SI          = file pointer
1008 ;               DX:AX = EAX = file length in bytes
1009 ;            If unsuccessful
1010 ;               ZF set
1011 ;
1012 ;            Assumes CS == DS == ES; *** IS THIS CORRECT ***?
1013 ;
1014 searchdir:
1015                 mov eax,[CurrentDir]
1016 .leadingslash:
1017                 cmp byte [di],'/'       ; Absolute filename?
1018                 jne .searchloop
1019                 mov eax,EXT2_ROOT_INO
1020                 inc di                  ; Skip slash
1021
1022 .searchloop:
1023                 ; At this point, EAX contains the directory inode,
1024                 ; and DS:DI contains a pathname tail.
1025                 call open_inode
1026
1027 .readdir:
1028                 mov bx,trackbuf
1029                 push bx
1030                 mov cx,[SecPerBlock]
1031                 call getfssec
1032                 pop bx
1033                 pushf                   ; Save EOF flag
1034 .getent:
1035                 cmp dword [bx+d_inode],0
1036                 je .endblock
1037                 
1038                 push di
1039                 push si
1040                 mov cx,[bx+d_name_len]
1041                 lea si,[bx+d_name]
1042                 repe cmpsb
1043                 pop si
1044                 je .maybe
1045 .nope:
1046                 pop di
1047
1048                 add bx,[bx+d_rec_len]
1049                 jmp .getent
1050
1051 .endblock:
1052                 popf
1053                 jnc .readdir            ; There is more
1054 .failure:
1055                 xor eax,eax
1056                 ret
1057 .maybe:
1058                 mov eax,[si+d_inode]
1059                 
1060                 cmp byte [di],0
1061                 je .finish              ; It's a real file; done
1062                 cmp byte [di],'/'
1063                 jne .nope               ; False alarm
1064                 
1065                 ; It's a match, but it's a directory.
1066                 ; Repeat operation.
1067                 call close
1068                 pop si                  ; Adjust stack (di)
1069                 pop si                  ; Adjust stack (flags)
1070                 inc di                  ; Skip slash
1071                 jmp .searchloop
1072                 
1073
1074 .finish:        ; We found it; now we need to open the file
1075                 call close              ; Close directory
1076                 pop si                  ; Adjust stack (di)
1077                 pop si                  ; Adjust stack (flags)
1078                 call open_inode
1079                 ret
1080
1081 ;
1082 ; mangle_name: Mangle a filename pointed to by DS:SI into a buffer pointed
1083 ;              to by ES:DI; ends on encountering any whitespace.
1084 ;
1085 ;              This verifies that a filename is < FILENAME_MAX characters,
1086 ;              doesn't contain whitespace, zero-pads the output buffer,
1087 ;              and removes redundant slashes,
1088 ;              so "repe cmpsb" can do a compare, and the
1089 ;              path-searching routine gets a bit of an easier job.
1090 ;
1091 ;              FIX: we may want to support \-escapes here (and this would
1092 ;              be the place.)
1093 ;              
1094 mangle_name:
1095                 push bx
1096                 xor ax,ax
1097                 mov cx,FILENAME_MAX-1
1098                 mov bx,di
1099
1100 .mn_loop:
1101                 lodsb
1102                 cmp al,' '                      ; If control or space, end
1103                 jna .mn_end
1104                 cmp al,ah                       ; Repeated slash?
1105                 je .mn_skip
1106                 xor ah,ah
1107                 cmp al,'/'
1108                 jne .mn_ok
1109                 mov ah,al
1110 .mn_ok          stosb
1111 .mn_skip:       loop .mn_loop
1112 .mn_end:
1113                 cmp bx,di                       ; At the beginning of the buffer?
1114                 jbe .mn_zero
1115                 cmp byte [di-1],'/'             ; Terminal slash?
1116                 jne .mn_zero
1117 .mn_kill:       dec di                          ; If so, remove it
1118                 inc cx
1119                 jmp short .mn_end
1120 .mn_zero:
1121                 inc cx                          ; At least one null byte
1122                 xor ax,ax                       ; Zero-fill name
1123                 rep stosb
1124                 pop bx
1125                 ret                             ; Done
1126
1127 ;
1128 ; unmangle_name: Does the opposite of mangle_name; converts a DOS-mangled
1129 ;                filename to the conventional representation.  This is needed
1130 ;                for the BOOT_IMAGE= parameter for the kernel.
1131 ;                NOTE: A 13-byte buffer is mandatory, even if the string is
1132 ;                known to be shorter.
1133 ;
1134 ;                DS:SI -> input mangled file name
1135 ;                ES:DI -> output buffer
1136 ;
1137 ;                On return, DI points to the first byte after the output name,
1138 ;                which is set to a null byte.
1139 ;
1140 unmangle_name:  call strcpy
1141                 dec di                          ; Point to final null byte
1142                 ret
1143
1144 ;
1145 ; writechr:     Write a single character in AL to the console without
1146 ;               mangling any registers; handle video pages correctly.
1147 ;
1148 writechr:
1149                 call write_serial       ; write to serial port if needed
1150                 pushfd
1151                 pushad
1152                 mov ah,0Eh
1153                 mov bl,07h              ; attribute
1154                 mov bh,[cs:BIOS_page]   ; current page
1155                 int 10h
1156                 popad
1157                 popfd
1158                 ret
1159
1160 ;
1161 ;
1162 ; kaboom2: once everything is loaded, replace the part of kaboom
1163 ;          starting with "kaboom.patch" with this part
1164
1165 kaboom2:
1166                 mov si,err_bootfailed
1167                 call cwritestr
1168                 call getchar
1169                 call vgaclearmode
1170                 int 19h                 ; And try once more to boot...
1171 .norge:         jmp short .norge        ; If int 19h returned; this is the end
1172
1173
1174 ;
1175 ; linsector:    Convert a linear sector index in a file to a linear sector number
1176 ;       EAX     -> linear sector number
1177 ;       DS:SI   -> open_file_t
1178 ;
1179 ;               Returns next sector number in EAX; CF on EOF (not an error!)
1180 ;
1181 linsector:
1182                 push gs
1183                 push ebx
1184                 push esi
1185                 push edi
1186                 push ecx
1187                 push edx
1188                 push ebp
1189
1190                 push eax
1191                 mov cl,[ClustShift]
1192                 shr eax,cl              ; Convert to block number
1193                 push eax
1194                 mov eax,[si+file_in_sec]
1195                 mov bx,si
1196                 call getcachesector     ; Get inode
1197                 add si,[bx+file_in_off] ; Get *our* inode
1198                 pop eax
1199                 lea ebx,[i_block+4*eax]
1200                 cmp eax,EXT2_NDIR_BLOCKS
1201                 jb .direct
1202                 mov ebx,[gs:si+i_block+4*EXT2_IND_BLOCK]
1203                 sub eax,EXT2_NDIR_BLOCKS
1204                 mov ebp,[PtrsPerBlk1]
1205                 jb .ind1
1206                 mov ebx,[gs:si+i_block+4*EXT2_DIND_BLOCK]
1207                 sub eax,ebp
1208                 mov ebp,[PtrsPerBlock2]
1209                 cmp eax,ebp
1210                 jb .ind2
1211                 mov ebx,[gs:si+i_block+4*EXT2_TIND_BLOCK]
1212                 sub eax,ebp
1213
1214 .ind3:
1215                 ; Triple indirect; eax contains the block no
1216                 ; with respect to the start of the tind area;
1217                 ; ebx contains the pointer to the tind block.
1218                 xor edx,edx
1219                 div dword [PtrsPerBlock3]
1220                 ; EAX = which dind block, EDX = block no in dind block
1221
1222                 shl ebx,cl              ; Sector # for tind block
1223                 push ax
1224                 shr eax,SECTOR_SHIFT-2  ; Sector within tind block
1225                 add eax,ebx
1226                 call getcachesector
1227                 pop bx
1228                 shl bx,2                ; Convert to byte offset
1229                 and bx,SECTOR_SIZE-1
1230
1231                 mov ebx,[gs:bx+si]      ; Get the pointer
1232                 mov eax,edx             ; The int2 code wants the remainder...
1233 .ind2:
1234                 ; Double indirect; eax contains the block no
1235                 ; with respect to the start of the dind area;
1236                 ; ebx contains the pointer to the dind block.
1237                 xor edx,edx
1238                 div dword [PtrsPerBlock2]
1239                 ; EAX = which dind block, EDX = block no in dind block
1240
1241                 shl ebx,cl              ; Sector # for tind block
1242                 push ax
1243                 shr eax,SECTOR_SHIFT-2  ; Sector within tind block
1244                 add eax,ebx
1245                 call getcachesector
1246                 pop bx
1247                 shl bx,2                ; Convert to byte offset
1248                 and bx,SECTOR_SIZE-1
1249
1250                 mov ebx,[gs:bx+si]      ; Get the pointer
1251                 mov eax,edx             ; The ind1 code wants the remainder...
1252 .ind1:
1253                 ; Single indirect; eax contains the block no
1254                 ; with respect to the start of the ind area;
1255                 ; ebx contains the pointer to the ind block.
1256                 xor edx,edx
1257                 div dword [PtrsPerBlock1]
1258                 ; EAX = which dind block, EDX = block no in dind block
1259
1260                 shl ebx,cl              ; Sector # for tind block
1261                 push ax
1262                 shr eax,SECTOR_SHIFT-2  ; Sector within tind block
1263                 add eax,ebx
1264                 call getcachesector
1265                 pop bx
1266                 shl bx,2                ; Convert to byte offset
1267                 and bx,SECTOR_SIZE-1
1268
1269 .direct:
1270                 mov ebx,[gs:bx+si]      ; Get the pointer
1271
1272                 pop eax                 ; Get the sector index again
1273                 shl ebx,cl              ; Convert block number to sector
1274                 and eax,[ClustMask]     ; Add offset within block
1275                 add eax,ebx
1276
1277                 pop ebp
1278                 pop edx
1279                 pop ecx
1280                 pop edi
1281                 pop esi
1282                 pop ebx
1283                 pop gs
1284                 ret
1285
1286 ;
1287 ; getfssec: Get multiple sectors from a file
1288 ;
1289 ;       Same as above, except SI is a pointer to a open_file_t
1290 ;
1291 ;       ES:BX   -> Buffer
1292 ;       DS:SI   -> Pointer to open_file_t
1293 ;       CX      -> Sector count (0FFFFh = until end of file)
1294 ;                  Must not exceed the ES segment
1295 ;       Returns CF=1 on EOF (not necessarily error)
1296 ;       All arguments are advanced to reflect data read.
1297 ;
1298 getfssec:
1299                 push ebp
1300                 push eax
1301                 push ebx
1302                 push edx
1303 .getfragment:
1304                 mov eax,[si]                    ; Current start index
1305                 mov ebx,eax
1306                 call linsector
1307                 push eax                        ; Fragment start sector
1308                 mov edx,eax
1309                 xor ebp,ebp                     ; Fragment sector count
1310 .getseccnt:
1311                 inc bp
1312                 dec cx
1313                 jz .do_read
1314                 xor eax,eax
1315                 mov ax,es
1316                 shl ax,4
1317                 add ax,bx                       ; Now DI = how far into 64K block we are
1318                 not ax                          ; Bytes left in 64K block
1319                 inc eax
1320                 shr eax,SECTOR_SHIFT            ; Sectors left in 64K block
1321                 cmp bp,ax
1322                 jnb .do_read                    ; Unless there is at least 1 more sector room...
1323                 inc ebx                         ; Sector index
1324                 inc edx                         ; Linearly next sector
1325                 mov eax,ebx
1326                 call nextsector
1327                 jc .do_read
1328                 cmp edx,eax
1329                 je .getseccnt
1330 .do_read:
1331                 pop eax                         ; Linear start sector
1332                 call getlinsecsr
1333                 lea eax,[eax+ebp-1]             ; This is the last sector actually read
1334                 shl bp,9
1335                 add bx,bp                       ; Adjust buffer pointer
1336                 call nextsector
1337                 jc .eof
1338                 mov edx,eax
1339                 and cx,cx
1340                 jnz .getfragment
1341 .done:
1342                 pop edx
1343                 pop ebx
1344                 pop eax
1345                 pop ebp
1346                 ret
1347 .eof:
1348                 xor edx,edx
1349                 stc
1350                 jmp .done
1351
1352
1353
1354 ; -----------------------------------------------------------------------------
1355 ;  Common modules
1356 ; -----------------------------------------------------------------------------
1357
1358 %include "getc.inc"             ; getc et al
1359 %include "conio.inc"            ; Console I/O
1360 %include "writestr.inc"         ; String output
1361 %include "parseconfig.inc"      ; High-level config file handling
1362 %include "parsecmd.inc"         ; Low-level config file handling
1363 %include "bcopy32.inc"          ; 32-bit bcopy
1364 %include "loadhigh.inc"         ; Load a file into high memory
1365 %include "font.inc"             ; VGA font stuff
1366 %include "graphics.inc"         ; VGA graphics
1367 %include "highmem.inc"          ; High memory sizing
1368 %include "strcpy.inc"           ; strcpy()
1369 %include "cache.inc"
1370
1371 ; -----------------------------------------------------------------------------
1372 ;  Begin data section
1373 ; -----------------------------------------------------------------------------
1374
1375                 section .data
1376 copyright_str   db ' Copyright (C) 1994-', year, ' H. Peter Anvin'
1377                 db CR, LF, 0
1378 boot_prompt     db 'boot: ', 0
1379 wipe_char       db BS, ' ', BS, 0
1380 err_notfound    db 'Could not find kernel image: ',0
1381 err_notkernel   db CR, LF, 'Invalid or corrupt kernel image.', CR, LF, 0
1382 err_noram       db 'It appears your computer has less than '
1383                 asciidec dosram_k
1384                 db 'K of low ("DOS")'
1385                 db CR, LF
1386                 db 'RAM.  Linux needs at least this amount to boot.  If you get'
1387                 db CR, LF
1388                 db 'this message in error, hold down the Ctrl key while'
1389                 db CR, LF
1390                 db 'booting, and I will take your word for it.', CR, LF, 0
1391 err_badcfg      db 'Unknown keyword in syslinux.cfg.', CR, LF, 0
1392 err_noparm      db 'Missing parameter in syslinux.cfg.', CR, LF, 0
1393 err_noinitrd    db CR, LF, 'Could not find ramdisk image: ', 0
1394 err_nohighmem   db 'Not enough memory to load specified kernel.', CR, LF, 0
1395 err_highload    db CR, LF, 'Kernel transfer failure.', CR, LF, 0
1396 err_oldkernel   db 'Cannot load a ramdisk with an old kernel image.'
1397                 db CR, LF, 0
1398 err_notdos      db ': attempted DOS system call', CR, LF, 0
1399 err_comlarge    db 'COMBOOT image too large.', CR, LF, 0
1400 err_a20         db CR, LF, 'A20 gate not responding!', CR, LF, 0
1401 err_bootfailed  db CR, LF, 'Boot failed: please change disks and press '
1402                 db 'a key to continue.', CR, LF, 0
1403 ready_msg       db 'Ready.', CR, LF, 0
1404 crlfloading_msg db CR, LF
1405 loading_msg     db 'Loading ', 0
1406 dotdot_msg      db '.'
1407 dot_msg         db '.', 0
1408 aborted_msg     db ' aborted.'                  ; Fall through to crlf_msg!
1409 crlf_msg        db CR, LF
1410 null_msg        db 0
1411 crff_msg        db CR, FF, 0
1412 ConfigName      db 'syslinux.cfg',0             ; Unmangled form
1413
1414 ;
1415 ; Command line options we'd like to take a look at
1416 ;
1417 ; mem= and vga= are handled as normal 32-bit integer values
1418 initrd_cmd      db 'initrd='
1419 initrd_cmd_len  equ 7
1420
1421 ;
1422 ; Config file keyword table
1423 ;
1424 %include "keywords.inc"
1425
1426 ;
1427 ; Extensions to search for (in *forward* order).
1428 ;
1429                 align 4, db 0
1430 exten_table:    db '.cbt'               ; COMBOOT (specific)
1431                 db '.img'               ; Disk image
1432                 db '.bs', 0             ; Boot sector
1433                 db '.com'               ; COMBOOT (same as DOS)
1434                 db '.c32'               ; COM32
1435 exten_table_end:
1436                 dd 0, 0                 ; Need 8 null bytes here
1437
1438 ;
1439 ; Misc initialized (data) variables
1440 ;
1441 %ifdef debug                            ; This code for debugging only
1442 debug_magic     dw 0D00Dh               ; Debug code sentinel
1443 %endif
1444
1445                 alignb 4, db 0
1446 BufSafe         dw trackbufsize/SECTOR_SIZE     ; Clusters we can load into trackbuf
1447 BufSafeSec      dw trackbufsize/SECTOR_SIZE     ; = how many sectors?
1448 BufSafeBytes    dw trackbufsize         ; = how many bytes?
1449 EndOfGetCBuf    dw getcbuf+trackbufsize ; = getcbuf+BufSafeBytes
1450 %ifndef DEPEND
1451 %if ( trackbufsize % SECTOR_SIZE ) != 0
1452 %error trackbufsize must be a multiple of SECTOR_SIZE
1453 %endif
1454 %endif
1455                 align 4, db 0           ; Pad out any unfinished dword
1456 ldlinux_end     equ $