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