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