core: move common module includes to common.inc
[profile/ivi/syslinux.git] / core / ldlinux.asm
1 ; -*- fundamental -*- (asm-mode sucks)
2 ; ****************************************************************************
3 ;
4 ;  ldlinux.asm
5 ;
6 ;  A program to boot Linux kernels off an MS-DOS formatted floppy disk.  This
7 ;  functionality is good to have for installation floppies, where it may
8 ;  be hard to find a functional Linux system to run LILO off.
9 ;
10 ;  This program allows manipulation of the disk to take place entirely
11 ;  from MS-LOSS, and can be especially useful in conjunction with the
12 ;  umsdos filesystem.
13 ;
14 ;   Copyright 1994-2009 H. Peter Anvin - All Rights Reserved
15 ;   Copyright 2009 Intel Corporation; author: H. Peter Anvin
16 ;
17 ;  This program is free software; you can redistribute it and/or modify
18 ;  it under the terms of the GNU General Public License as published by
19 ;  the Free Software Foundation, Inc., 53 Temple Place Ste 330,
20 ;  Boston MA 02111-1307, USA; either version 2 of the License, or
21 ;  (at your option) any later version; incorporated herein by reference.
22 ;
23 ; ****************************************************************************
24
25 %ifndef IS_MDSLINUX
26 %define IS_SYSLINUX 1
27 %endif
28 %include "head.inc"
29
30 ;
31 ; Some semi-configurable constants... change on your own risk.
32 ;
33 my_id           equ syslinux_id
34 FILENAME_MAX_LG2 equ 6                  ; log2(Max filename size Including final null)
35 FILENAME_MAX    equ (1<<FILENAME_MAX_LG2) ; Max mangled filename size
36 NULLFILE        equ 0                   ; First char space == null filename
37 NULLOFFSET      equ 0                   ; Position in which to look
38 retry_count     equ 16                  ; How patient are we with the disk?
39 %assign HIGHMEM_SLOP 0                  ; Avoid this much memory near the top
40 LDLINUX_MAGIC   equ 0x3eb202fe          ; A random number to identify ourselves with
41
42 MAX_OPEN_LG2    equ 6                   ; log2(Max number of open files)
43 MAX_OPEN        equ (1 << MAX_OPEN_LG2)
44
45 SECTOR_SHIFT    equ 9
46 SECTOR_SIZE     equ (1 << SECTOR_SHIFT)
47
48 DIRENT_SHIFT    equ 5
49 DIRENT_SIZE     equ (1 << DIRENT_SHIFT)
50
51 ROOT_DIR_WORD   equ 0x002F
52
53 ;
54 ; This is what we need to do when idle
55 ;
56 %macro  RESET_IDLE 0
57         ; Nothing
58 %endmacro
59 %macro  DO_IDLE 0
60         ; Nothing
61 %endmacro
62
63 ;
64 ; The following structure is used for "virtual kernels"; i.e. LILO-style
65 ; option labels.  The options we permit here are `kernel' and `append
66 ; Since there is no room in the bottom 64K for all of these, we
67 ; stick them in high memory and copy them down before we need them.
68 ;
69                 struc vkernel
70 vk_vname:       resb FILENAME_MAX       ; Virtual name **MUST BE FIRST!**
71 vk_rname:       resb FILENAME_MAX       ; Real name
72 vk_appendlen:   resw 1
73 vk_type:        resb 1                  ; Type of file
74                 alignb 4
75 vk_append:      resb max_cmd_len+1      ; Command line
76                 alignb 4
77 vk_end:         equ $                   ; Should be <= vk_size
78                 endstruc
79
80 ;
81 ; File structure.  This holds the information for each currently open file.
82 ;
83                 struc open_file_t
84 file_sector     resd 1                  ; Sector pointer (0 = structure free)
85 file_bytesleft  resd 1                  ; Number of bytes left
86 file_left       resd 1                  ; Number of sectors left
87                 resd 1                  ; Unused
88                 endstruc
89
90 ;
91 ; Structure for codepage files
92 ;
93                 struc cp
94 .magic          resd 2                  ; 8-byte magic number
95 .reserved       resd 6                  ; Reserved for future use
96 .uppercase      resb 256                ; Internal upper-case table
97 .unicode        resw 256                ; Unicode matching table
98 .unicode_alt    resw 256                ; Alternate Unicode matching table
99                 endstruc
100
101 %ifndef DEPEND
102 %if (open_file_t_size & (open_file_t_size-1))
103 %error "open_file_t is not a power of 2"
104 %endif
105 %endif
106
107 ; ---------------------------------------------------------------------------
108 ;   BEGIN CODE
109 ; ---------------------------------------------------------------------------
110
111 ;
112 ; Memory below this point is reserved for the BIOS and the MBR
113 ;
114                 section .earlybss
115 trackbufsize    equ 8192
116 trackbuf        resb trackbufsize       ; Track buffer goes here
117                 ; ends at 2800h
118
119                 section .bss16
120                 alignb 4
121 FAT             resd 1                  ; Location of (first) FAT
122 RootDirArea     resd 1                  ; Location of root directory area
123 RootDir         resd 1                  ; Location of root directory proper
124 DataArea        resd 1                  ; Location of data area
125 RootDirSize     resd 1                  ; Root dir size in sectors
126 TotalSectors    resd 1                  ; Total number of sectors
127 ClustSize       resd 1                  ; Bytes/cluster
128 ClustMask       resd 1                  ; Sectors/cluster - 1
129 CopySuper       resb 1                  ; Distinguish .bs versus .bss
130 ClustShift      resb 1                  ; Shift count for sectors/cluster
131 ClustByteShift  resb 1                  ; Shift count for bytes/cluster
132
133                 alignb open_file_t_size
134 Files           resb MAX_OPEN*open_file_t_size
135
136 ;
137 ; Common bootstrap code for disk-based derivatives
138 ;
139 %include "diskstart.inc"
140
141 ;
142 ; Common initialization code
143 ;
144 %include "init.inc"
145 %include "cpuinit.inc"
146
147 ;
148 ; Compute some information about this filesystem.
149 ;
150
151 ; First, generate the map of regions
152 genfatinfo:
153                 mov edx,[bxSectors]
154                 and dx,dx
155                 jnz .have_secs
156                 mov edx,[bsHugeSectors]
157 .have_secs:
158                 mov [TotalSectors],edx
159
160                 mov eax,[bxResSectors]
161                 mov [FAT],eax                   ; Beginning of FAT
162                 mov edx,[bxFATsecs]
163                 and dx,dx
164                 jnz .have_fatsecs
165                 mov edx,[bootsec+36]            ; FAT32 BPB_FATsz32
166 .have_fatsecs:
167                 imul edx,[bxFATs]
168                 add eax,edx
169                 mov [RootDirArea],eax           ; Beginning of root directory
170                 mov [RootDir],eax               ; For FAT12/16 == root dir location
171
172                 mov edx,[bxRootDirEnts]
173                 add dx,SECTOR_SIZE/32-1
174                 shr dx,SECTOR_SHIFT-5
175                 mov [RootDirSize],edx
176                 add eax,edx
177                 mov [DataArea],eax              ; Beginning of data area
178
179 ; Next, generate a cluster size shift count and mask
180                 mov eax,[bxSecPerClust]
181                 bsr cx,ax
182                 mov [ClustShift],cl
183                 push cx
184                 add cl,SECTOR_SHIFT
185                 mov [ClustByteShift],cl
186                 pop cx
187                 dec ax
188                 mov [ClustMask],eax
189                 inc ax
190                 shl eax,SECTOR_SHIFT
191                 mov [ClustSize],eax
192
193 ;
194 ; FAT12, FAT16 or FAT28^H^H32?  This computation is fscking ridiculous.
195 ;
196 getfattype:
197                 mov eax,[TotalSectors]
198                 sub eax,[DataArea]
199                 shr eax,cl                      ; cl == ClustShift
200                 mov cl,nextcluster_fat12-(nextcluster+2)
201                 cmp eax,4085                    ; FAT12 limit
202                 jb .setsize
203                 mov cl,nextcluster_fat16-(nextcluster+2)
204                 cmp eax,65525                   ; FAT16 limit
205                 jb .setsize
206                 ;
207                 ; FAT32, root directory is a cluster chain
208                 ;
209                 mov cl,[ClustShift]
210                 mov eax,[bootsec+44]            ; Root directory cluster
211                 sub eax,2
212                 shl eax,cl
213                 add eax,[DataArea]
214                 mov [RootDir],eax
215                 mov cl,nextcluster_fat28-(nextcluster+2)
216                 mov byte [SuperSize],superblock_len_fat32
217 .setsize:
218                 mov byte [nextcluster+1],cl
219
220
221 ;
222 ; Initialize the metadata cache
223 ;
224                 call initcache
225
226 ;
227 ; Now, everything is "up and running"... patch kaboom for more
228 ; verbosity and using the full screen system
229 ;
230                 ; E9 = JMP NEAR
231                 mov di,kaboom.patch
232                 mov al,0e9h
233                 stosb
234                 mov ax,kaboom2-2
235                 sub ax,di
236                 stosw
237
238 ;
239 ; Now we're all set to start with our *real* business.  First load the
240 ; configuration file (if any) and parse it.
241 ;
242 ; In previous versions I avoided using 32-bit registers because of a
243 ; rumour some BIOSes clobbered the upper half of 32-bit registers at
244 ; random.  I figure, though, that if there are any of those still left
245 ; they probably won't be trying to install Linux on them...
246 ;
247 ; The code is still ripe with 16-bitisms, though.  Not worth the hassle
248 ; to take'm out.  In fact, we may want to put them back if we're going
249 ; to boot ELKS at some point.
250 ;
251
252 ;
253 ; Load configuration file
254 ;
255                 mov si,config_name      ; Save configuration file name
256                 mov di,ConfigName
257                 call strcpy
258                 mov word [CurrentDirName],ROOT_DIR_WORD ; Write '/',0 to the CurrentDirName
259
260                 mov eax,[RootDir]       ; Make the root directory ...
261                 mov [CurrentDir],eax    ; ... the current directory
262                 mov di,syslinux_cfg1
263                 push di
264                 call open
265                 pop di
266                 jnz .config_open
267                 mov di,syslinux_cfg2
268                 push di
269                 call open
270                 pop di
271                 jnz .config_open
272                 mov di,syslinux_cfg3
273                 push di
274                 call open
275                 pop di
276                 jz no_config_file
277 .config_open:
278                 push si
279                 mov si,di
280                 push si
281                 mov di,CurrentDirName
282                         ; This is inefficient as it will copy more than needed
283                         ;   but not by too much
284                 call strcpy
285                 mov ax,config_name      ;Cut it down
286                 pop si
287                 sub ax,si
288                 mov di,CurrentDirName
289                 add di,ax
290                 mov byte [di],0
291                 pop si
292                 mov eax,[PrevDir]       ; Make the directory with syslinux.cfg ...
293                 mov [CurrentDir],eax    ; ... the current directory
294
295 ;
296 ; Now we have the config file open.  Parse the config file and
297 ; run the user interface.
298 ;
299 %include "ui.inc"
300
301 ;
302 ; allocate_file: Allocate a file structure
303 ;
304 ;               If successful:
305 ;                 ZF set
306 ;                 BX = file pointer
307 ;               In unsuccessful:
308 ;                 ZF clear
309 ;
310 allocate_file:
311                 TRACER 'a'
312                 push cx
313                 mov bx,Files
314                 mov cx,MAX_OPEN
315 .check:         cmp dword [bx], byte 0
316                 je .found
317                 add bx,open_file_t_size         ; ZF = 0
318                 loop .check
319                 ; ZF = 0 if we fell out of the loop
320 .found:         pop cx
321                 ret
322
323 ;
324 ; alloc_fill_dir:
325 ;       Allocate then fill a file structure for a directory starting in
326 ;       sector EAX.
327 ;
328 ;       Assumes DS == ES == CS.
329 ;
330 ;            If successful:
331 ;               ZF clear
332 ;               SI      = file pointer
333 ;            If unsuccessful
334 ;               ZF set
335 ;               EAX clobbered
336 ;
337 alloc_fill_dir:
338                 push bx
339                 call allocate_file
340                 jnz .alloc_failure
341 .found:
342                 mov si,bx
343                 mov [si+file_sector],eax        ; Current sector
344                 mov dword [si+file_bytesleft],0 ; Current offset
345                 mov [si+file_left],eax          ; Beginning sector
346                 pop bx
347                 ret
348
349 .alloc_failure:
350                 pop bx
351                 xor eax,eax                     ; ZF <- 1
352                 ret
353
354 ;
355 ; search_dos_dir:
356 ;            Search a specific directory for a pre-mangled filename in
357 ;            MangledBuf, in the directory starting in sector EAX.
358 ;
359 ;            NOTE: This file considers finding a zero-length file an
360 ;            error.  This is so we don't have to deal with that special
361 ;            case elsewhere in the program (most loops have the test
362 ;            at the end).
363 ;
364 ;            Assumes DS == ES == CS.
365 ;
366 ;            If successful:
367 ;               ZF clear
368 ;               SI      = file pointer
369 ;               EAX     = file length (MAY BE ZERO!)
370 ;               DL      = file attribute
371 ;               DH      = clobbered
372 ;            If unsuccessful
373 ;               ZF set
374 ;               EAX, SI, DX clobbered
375 ;
376
377 search_dos_dir:
378                 push bx
379                 call allocate_file
380                 jnz .alloc_failure
381
382                 push cx
383                 push gs
384                 push es
385                 push ds
386                 pop es                          ; ES = DS
387
388                 ; Compute the value of a possible VFAT longname
389                 ; "last" entry (which, of course, comes first...)
390                 push ax
391                 push dx
392                 mov ax,[NameLen]
393                 add ax,12
394                 xor dx,dx
395                 mov cx,13
396                 div cx
397                 or al,40h
398                 mov [VFATInit],al
399                 mov [VFATNext],al
400                 pop dx
401                 pop ax
402
403 .scansector:
404                 ; EAX <- directory sector to scan
405                 call getcachesector
406                 ; GS:SI now points to this sector
407
408                 mov cx,SECTOR_SIZE/32           ; 32 == directory entry size
409 .scanentry:
410                 cmp byte [gs:si],0
411                 jz .failure                     ; Hit directory high water mark
412                 cmp word [gs:si+11],0Fh         ; Long filename
413                 jne .short_entry
414
415                 ; Process a VFAT long entry
416                 pusha
417                 mov al,[gs:si]
418                 cmp al,[VFATNext]
419                 jne .not_us
420                 mov bl,[gs:si+13]
421                 test al,40h
422                 jz .match_csum
423                 ; Get the initial checksum value
424                 mov [VFATCsum],bl
425                 jmp .done_csum
426 .match_csum:
427                 cmp bl,[VFATCsum]
428                 jne .not_us                     ; Checksum mismatch
429 .done_csum:
430                 and ax,03fh
431                 jz .not_us                      ; Can't be zero...
432                 dec ax
433                 mov [VFATNext],al               ; Optimistically...
434                 mov bx,ax
435                 shl bx,2                        ; *4
436                 add ax,bx                       ; *5
437                 add bx,bx                       ; *8
438                 add bx,ax                       ; *13
439                 cmp bx,[NameLen]
440                 jae .not_us
441                 mov di,[NameStart]
442                 inc si
443                 mov cx,13
444 .vfat_cmp:
445                 gs lodsw
446                 push bx
447                 cmp bx,[NameLen]
448                 jae .vfat_tail
449                 movzx bx,byte [bx+di]
450                 add bx,bx
451                 cmp ax,[cp_unicode+bx]          ; Primary case
452                 je .ucs_ok
453                 cmp ax,[cp_unicode_alt+bx]      ; Alternate case
454                 je .ucs_ok
455                 ; Mismatch...
456                 jmp .not_us_pop
457 .vfat_tail:
458                 ; *AT* the end we should have 0x0000, *AFTER* the end
459                 ; we should have 0xFFFF...
460                 je .vfat_end
461                 inc ax                  ; 0xFFFF -> 0x0000
462 .vfat_end:
463                 and ax,ax
464                 jnz .not_us_pop
465 .ucs_ok:
466                 pop bx
467                 inc bx
468                 cmp cx,3
469                 je .vfat_adj_add2
470                 cmp cx,9
471                 jne .vfat_adj_add0
472 .vfat_adj_add3: inc si
473 .vfat_adj_add2: inc si
474 .vfat_adj_add1: inc si
475 .vfat_adj_add0:
476                 loop .vfat_cmp
477                 ; Okay, if we got here we had a match on this particular
478                 ; entry... live to see another one.
479                 popa
480                 jmp .next_entry
481
482 .not_us_pop:
483                 pop bx
484 .not_us:
485                 popa
486                 jmp .nomatch
487
488 .short_entry:
489                 test byte [gs:si+11],8          ; Ignore volume labels
490                 jnz .nomatch
491
492                 cmp byte [VFATNext],0           ; Do we have a longname match?
493                 jne .no_long_match
494
495                 ; We already have a VFAT longname match, however,
496                 ; the match is only valid if the checksum matches
497                 push cx
498                 push si
499                 push ax
500                 xor ax,ax
501                 mov cx,11
502 .csum_loop:
503                 gs lodsb
504                 ror ah,1
505                 add ah,al
506                 loop .csum_loop
507                 cmp ah,[VFATCsum]
508                 pop ax
509                 pop si
510                 pop cx
511                 je .found                       ; Got a match on longname
512
513 .no_long_match:                                 ; Look for a shortname match
514                 push cx
515                 push si
516                 push di
517                 mov di,MangledBuf
518                 mov cx,11
519                 gs repe cmpsb
520                 pop di
521                 pop si
522                 pop cx
523                 je .found
524 .nomatch:
525                 ; Reset the VFAT matching state machine
526                 mov dh,[VFATInit]
527                 mov [VFATNext],dh
528 .next_entry:
529                 add si,32
530                 dec cx
531                 jnz .scanentry
532
533                 call nextsector
534                 jnc .scansector                 ; CF is set if we're at end
535
536                 ; If we get here, we failed
537 .failure:
538                 pop es
539                 pop gs
540                 pop cx
541 .alloc_failure:
542                 pop bx
543                 xor eax,eax                     ; ZF <- 1
544                 ret
545 .found:
546                 mov eax,[gs:si+28]              ; File size
547                 add eax,SECTOR_SIZE-1
548                 shr eax,SECTOR_SHIFT
549                 mov [bx+4],eax                  ; Sector count
550
551                 mov cl,[ClustShift]
552                 mov dx,[gs:si+20]               ; High cluster word
553                 shl edx,16
554                 mov dx,[gs:si+26]               ; Low cluster word
555                 sub edx,2
556                 shl edx,cl
557                 add edx,[DataArea]
558                 mov [bx],edx                    ; Starting sector
559
560                 mov eax,[gs:si+28]              ; File length again
561                 mov dl,[gs:si+11]               ; File attribute
562                 mov si,bx                       ; File pointer...
563                 and si,si                       ; ZF <- 0
564
565                 pop es
566                 pop gs
567                 pop cx
568                 pop bx
569                 ret
570
571                 section .data16
572                 alignz 4
573                 ; Note: we have no use of the first 32 bytes (header),
574                 ; nor of the folloing 32 bytes (case mapping of control
575                 ; characters), as long as we adjust the offsets appropriately.
576 codepage        equ $-(32+32)
577 codepage_data:  incbin "codepage.cp",32+32
578 cp_uppercase    equ     codepage+cp.uppercase
579 cp_unicode      equ     codepage+cp.unicode
580 cp_unicode_alt  equ     codepage+cp.unicode_alt
581 codepage_end    equ $
582
583                 section .text16
584 ;
585 ; Input:  UCS-2 character in AX
586 ; Output: Single byte character in AL, ZF = 1
587 ;         On failure, returns ZF = 0
588 ;
589 ucs2_to_cp:
590                 push es
591                 push di
592                 push cx
593                 push cs
594                 pop es
595                 mov di,cp_unicode
596                 mov cx,512
597                 repne scasw
598                 xchg ax,cx
599                 pop cx
600                 pop di
601                 pop es
602                 not ax          ; Doesn't change the flags!
603                 ret
604
605                 section .bss16
606 VFATInit        resb 1
607 VFATNext        resb 1
608 VFATCsum        resb 1
609
610                 section .text16
611 ;
612 ; close_file:
613 ;            Deallocates a file structure (pointer in SI)
614 ;            Assumes CS == DS.
615 ;
616 close_file:
617                 and si,si
618                 jz .closed
619                 mov dword [si],0                ; First dword == file_sector
620                 xor si,si
621 .closed:        ret
622
623 ;
624 ; close_dir:
625 ;            Deallocates a directory structure (pointer in SI)
626 ;            Assumes CS == DS.
627 ;
628 close_dir:
629                 and si,si
630                 jz .closed
631                 mov dword [si],0                ; First dword == file_sector
632                 xor si,si
633 .closed:        ret
634
635 ;
636 ; searchdir:
637 ;
638 ;       Open a file
639 ;
640 ;            On entry:
641 ;               DS:DI   = filename
642 ;            If successful:
643 ;               ZF clear
644 ;               SI              = file pointer
645 ;               EAX             = file length in bytes
646 ;            If unsuccessful
647 ;               ZF set
648 ;
649 ; Assumes CS == DS == ES, and trashes BX and CX.
650 ;
651 searchdir:
652                 mov eax,[CurrentDir]
653                 cmp byte [di],'/'       ; Root directory?
654                 jne .notroot
655                 mov eax,[RootDir]
656                 inc di
657 .notroot:
658
659 .pathwalk:
660                 push eax                ; <A> Current directory sector
661                 mov si,di
662 .findend:
663                 lodsb
664                 cmp al,' '
665                 jbe .endpath
666                 cmp al,'/'
667                 jne .findend
668 .endpath:
669                 xchg si,di              ; GRC: si begin; di end[ /]+1
670                 pop eax                 ; <A> Current directory sector
671
672                         ; GRC Here I need to check if di-1 = si which signifies
673                         ;       we have the desired directory in EAX
674                         ; What about where the file name = "."; later
675                 mov dx,di
676                 dec dx
677                 cmp dx,si
678                 jz .founddir
679
680                 mov [PrevDir],eax       ; Remember last directory searched
681
682                 push di
683                 call mangle_dos_name    ; MangledBuf <- component
684                 call search_dos_dir
685                 pop di
686                 jz .notfound            ; Pathname component missing
687
688                 cmp byte [di-1],'/'     ; Do we expect a directory
689                 je .isdir
690
691                 ; Otherwise, it should be a file
692 .isfile:
693                 test dl,18h             ; Subdirectory|Volume Label
694                 jnz .badfile            ; If not a file, it's a bad thing
695
696                 ; SI and EAX are already set
697                 mov [si+file_bytesleft],eax
698                 push eax
699                 add eax,SECTOR_SIZE-1
700                 shr eax,SECTOR_SHIFT
701                 mov [si+file_left],eax  ; Sectors left
702                 pop eax
703                 and eax,eax             ; EAX != 0
704                 jz .badfile
705                 ret                     ; Done!
706
707                 ; If we expected a directory, it better be one...
708 .isdir:
709                 test dl,10h             ; Subdirectory
710                 jz .badfile
711
712                 xor eax,eax
713                 xchg eax,[si+file_sector] ; Get sector number and free file structure
714                 jmp .pathwalk           ; Walk the next bit of the path
715
716                 ; Found the desired directory; ZF set but EAX not 0
717 .founddir:
718                 ret
719
720 .badfile:
721                 xor eax,eax
722                 mov [si],eax            ; Free file structure
723
724 .notfound:
725                 xor eax,eax             ; Zero out EAX
726                 ret
727
728 ;
729 ; readdir: Read one file from a directory
730 ;
731 ;       ES:DI   -> String buffer (filename)
732 ;       DS:SI   -> Pointer to open_file_t
733 ;       DS      Must be the SYSLINUX Data Segment
734 ;
735 ;       Returns the file's name in the filename string buffer
736 ;       EAX returns the file size
737 ;       EBX returns the beginning sector (currently without offsetting)
738 ;       DL returns the file type
739 ;       The directory handle's data is incremented to reflect a name read.
740 ;
741 readdir:
742                 push ecx
743                 push bp         ; Using bp to transfer between segment registers
744                 push si
745                 push es
746                 push fs         ; Using fs to store the current es (from COMBOOT)
747                 push gs
748                 mov bp,es
749                 mov fs,bp
750                 cmp si,0
751                 jz .fail
752 .load_handle:
753                 mov eax,[ds:si+file_sector]     ; Current sector
754                 mov ebx,[ds:si+file_bytesleft]  ; Current offset
755                 cmp eax,0
756                 jz .fail
757 .fetch_cache:
758                 call getcachesector
759 .move_current:
760                 add si,bx       ; Resume last position in sector
761                 mov ecx,SECTOR_SIZE     ; 0 out high part
762                 sub cx,bx
763                 shr cx,5        ; Number of entries left
764 .scanentry:
765                 cmp byte [gs:si],0
766                 jz .fail
767                 cmp word [gs:si+11],0Fh         ; Long filename
768                 jne .short_entry
769
770 .vfat_entry:
771                 push eax
772                 push ecx
773                 push si
774                 push di
775 .vfat_ln_info:          ; Get info about the line that we're on
776                 mov al,[gs:si]
777                 test al,40h
778                 jz .vfat_tail_ln
779                 and al,03Fh
780                 mov ah,1        ; On beginning line
781                 jmp .vfat_ck_ln
782
783 .vfat_tail_ln:  ; VFAT tail line processing (later in VFAT, head in name)
784                 test al,80h     ; Invalid data?
785                 jnz .vfat_abort
786                 mov ah,0        ; Not on beginning line
787                 cmp dl,al
788                 jne .vfat_abort ; Is this the entry we need?
789                 mov bl,[gs:si+13]
790                 cmp bl,[VFATCsum]
791                 je .vfat_cp_ln
792                 jmp .vfat_abort
793
794 .vfat_ck_ln:            ; Load this line's VFAT CheckSum
795                 mov bl,[gs:si+13]
796                 mov [VFATCsum],bl
797 .vfat_cp_ln:            ; Copy VFAT line
798                 dec al          ; Store the next line we need
799                 mov dx,ax       ; Use DX to store the progress
800                 mov cx,13       ; 13 characters per VFAT DIRENT
801                 cbw             ; AH <- 0
802                 mul cl          ; Offset for DI
803                 add di,ax       ; Increment DI
804                 inc si          ; Align to the real characters
805 .vfat_cp_chr:
806                 gs lodsw        ; Unicode here!!
807                 call ucs2_to_cp ; Convert to local codepage
808                 jnz .vfat_abort ; Use short name if character not on codepage
809                 stosb           ; CAN NOT OVERRIDE es
810                 cmp al,0
811                 jz .vfat_find_next ; Null-terminated string; don't process more
812                 cmp cx,3
813                 je .vfat_adj_add2
814                 cmp cx,9
815                 jne .vfat_adj_add0
816 .vfat_adj_add3: inc si
817 .vfat_adj_add2: inc si
818 .vfat_adj_add1: inc si
819 .vfat_adj_add0:
820                 loop .vfat_cp_chr
821                 cmp dh,1        ; Is this the first round?
822                 jnz .vfat_find_next
823 .vfat_null_term:        ; Need to null-terminate if first line as we rolled over the end
824                 mov al,0
825                 stosb
826
827 .vfat_find_next:        ;Find the next part of the name
828                 pop di
829                 pop si
830                 pop ecx
831                 pop eax
832                 cmp dl,0
833                 jz .vfat_find_info      ; We're done with the name
834                 add si,DIRENT_SIZE
835                 dec cx
836                 jnz .vfat_entry
837                 call nextsector
838                 jnc .vfat_entry                 ; CF is set if we're at end
839                 jmp .fail
840 .vfat_find_info:        ; Fetch next entry for the size/"INode"
841                 add si,DIRENT_SIZE
842                 dec cx
843                 jnz .get_info
844                 call nextsector
845                 jnc .get_info                   ; CF is set if we're at end
846                 jmp .fail
847 .vfat_abort:            ; Something went wrong, skip
848                 pop di
849                 pop si
850                 pop ecx
851                 pop eax
852                 jmp .skip_entry
853
854 .short_entry:
855                 test byte [gs:si+11],8          ; Ignore volume labels //HERE
856                 jnz .skip_entry
857                 mov edx,eax             ;Save current sector
858                 push cx
859                 push si
860                 push di
861                 mov cx,8
862 .short_file:
863                 gs lodsb
864                 cmp al,'.'
865                 jz .short_dot
866 .short_file_loop:
867                 cmp al,' '
868                 jz .short_skip_bs
869                 stosb
870                 loop .short_file_loop
871                 jmp .short_period
872 .short_skip_bs:         ; skip blank spaces in FILENAME (before EXT)
873                 add si,cx
874                 dec si
875 .short_period:
876                 mov al,'.'
877                 stosb
878                 mov cx,3
879 .short_ext:
880                 gs lodsb
881                 cmp al,' '
882                 jz .short_done
883                 stosb
884                 loop .short_ext
885                 jmp .short_done
886 .short_dot:
887                 stosb
888                 gs lodsb
889                 cmp al,' '
890                 jz .short_done
891                 stosb
892 .short_done:
893                 mov al,0        ; Null-terminate the short strings
894                 stosb
895                 pop di
896                 pop si
897                 pop cx
898                 mov eax,edx
899 .get_info:
900                 mov ebx,[gs:si+28]      ; length
901                 mov dl,[gs:si+11]       ; type
902 .next_entry:
903                 add si,DIRENT_SIZE
904                 dec cx
905                 jnz .store_offset
906                 call nextsector
907                 jnc .store_sect                 ; CF is set if we're at end
908                 jmp .fail
909
910 .skip_entry:
911                 add si,DIRENT_SIZE
912                 dec cx
913                 jnz .scanentry
914                 call nextsector
915                 jnc .scanentry                  ; CF is set if we're at end
916                 jmp .fail
917
918 .store_sect:
919                 pop gs
920                 pop fs
921                 pop es
922                 pop si
923                 mov [ds:si+file_sector],eax
924                 mov eax,0       ; Now at beginning of new sector
925                 jmp .success
926
927 .store_offset:
928                 pop gs
929                 pop fs
930                 pop es
931                 pop si          ; cx=num remain; SECTOR_SIZE-(cx*32)=cur pos
932                 shl ecx,DIRENT_SHIFT
933                 mov eax,SECTOR_SIZE
934                 sub eax,ecx
935                 and eax,0ffffh
936
937 .success:
938                 mov [ds:si+file_bytesleft],eax
939                 ; "INode" number = ((CurSector-RootSector)*SECTOR_SIZE + Offset)/DIRENT_SIZE)
940                 mov ecx,eax
941                 mov eax,[ds:si+file_sector]
942                 sub eax,[RootDir]
943                 shl eax,SECTOR_SHIFT
944                 add eax,ecx
945                 shr eax,DIRENT_SHIFT
946                 dec eax
947                 xchg eax,ebx    ; -> EBX=INode, EAX=FileSize
948                 jmp .done
949
950 .fail:
951                 pop gs
952                 pop fs
953                 pop es
954                 pop si
955                 call close_dir
956                 xor eax,eax
957                 stc
958 .done:
959                 pop bp
960                 pop ecx
961 .end:
962                 ret
963
964                 section .bss16
965                 alignb 4
966 PrevDir         resd 1                  ; Last scanned directory
967
968                 section .text16
969
970 ;
971 ;
972 ; kaboom2: once everything is loaded, replace the part of kaboom
973 ;          starting with "kaboom.patch" with this part
974
975 kaboom2:
976                 mov si,err_bootfailed
977                 call writestr
978                 cmp byte [kaboom.again+1],18h   ; INT 18h version?
979                 je .int18
980                 call getchar
981                 call vgaclearmode
982                 int 19h                 ; And try once more to boot...
983 .norge:         jmp short .norge        ; If int 19h returned; this is the end
984 .int18:
985                 call vgaclearmode
986                 int 18h
987 .noreg:         jmp short .noreg        ; Nynorsk
988
989 ;
990 ; mangle_name: Mangle a filename pointed to by DS:SI into a buffer pointed
991 ;              to by ES:DI; ends on encountering any whitespace.
992 ;              DI is preserved.
993 ;
994 ;              This verifies that a filename is < FILENAME_MAX characters,
995 ;              doesn't contain whitespace, zero-pads the output buffer,
996 ;              and removes trailing dots and redundant slashes, plus changes
997 ;              backslashes to forward slashes,
998 ;              so "repe cmpsb" can do a compare, and the path-searching routine
999 ;              gets a bit of an easier job.
1000 ;
1001 ;
1002 mangle_name:
1003                 push di
1004                 push bx
1005                 xor ax,ax
1006                 mov cx,FILENAME_MAX-1
1007                 mov bx,di
1008
1009 .mn_loop:
1010                 lodsb
1011                 cmp al,' '                      ; If control or space, end
1012                 jna .mn_end
1013                 cmp al,'\'                      ; Backslash?
1014                 jne .mn_not_bs
1015                 mov al,'/'                      ; Change to forward slash
1016 .mn_not_bs:
1017                 cmp al,ah                       ; Repeated slash?
1018                 je .mn_skip
1019                 xor ah,ah
1020                 cmp al,'/'
1021                 jne .mn_ok
1022                 mov ah,al
1023 .mn_ok          stosb
1024 .mn_skip:       loop .mn_loop
1025 .mn_end:
1026                 cmp bx,di                       ; At the beginning of the buffer?
1027                 jbe .mn_zero
1028                 cmp byte [es:di-1],'.'          ; Terminal dot?
1029                 je .mn_kill
1030                 cmp byte [es:di-1],'/'          ; Terminal slash?
1031                 jne .mn_zero
1032 .mn_kill:       dec di                          ; If so, remove it
1033                 inc cx
1034                 jmp short .mn_end
1035 .mn_zero:
1036                 inc cx                          ; At least one null byte
1037                 xor ax,ax                       ; Zero-fill name
1038                 rep stosb
1039                 pop bx
1040                 pop di
1041                 ret                             ; Done
1042
1043 ;
1044 ; unmangle_name: Does the opposite of mangle_name; converts a DOS-mangled
1045 ;                filename to the conventional representation.  This is needed
1046 ;                for the BOOT_IMAGE= parameter for the kernel.
1047 ;                NOTE: A 13-byte buffer is mandatory, even if the string is
1048 ;                known to be shorter.
1049 ;
1050 ;                DS:SI -> input mangled file name
1051 ;                ES:DI -> output buffer
1052 ;
1053 ;                On return, DI points to the first byte after the output name,
1054 ;                which is set to a null byte.
1055 ;
1056 unmangle_name:  call strcpy
1057                 dec di                          ; Point to final null byte
1058                 ret
1059
1060 ;
1061 ; mangle_dos_name:
1062 ;               Mangle a DOS filename component pointed to by DS:SI
1063 ;               into [MangledBuf]; ends on encountering any whitespace or
1064 ;               slash.
1065 ;
1066 ;               WARNING: saves pointers into the buffer for longname
1067 ;               matches!
1068 ;
1069 ;               Assumes CS == DS == ES.
1070 ;
1071
1072 mangle_dos_name:
1073                 pusha
1074                 mov di,MangledBuf
1075                 mov [NameStart],si
1076
1077                 mov cx,11                       ; # of bytes to write
1078                 mov bx,cp_uppercase             ; Case-conversion table
1079 .loop:
1080                 lodsb
1081                 cmp al,' '                      ; If control or space, end
1082                 jna .end
1083                 cmp al,'/'                      ; Slash, too
1084                 je .end
1085                 cmp al,'.'                      ; Period -> space-fill
1086                 je .is_period
1087                 xlatb                           ; Convert to upper case
1088                 mov ah,cl                       ; If the first byte (only!)...
1089                 cmp ax,0BE5h                    ; ... equals E5 hex ...
1090                 jne .charok
1091                 mov al,05h                      ; ... change it to 05 hex
1092 .charok:        stosb
1093                 loop .loop                      ; Don't continue if too long
1094                 ; Find the end for the benefit of longname search
1095 .find_end:
1096                 lodsb
1097                 cmp al,' '
1098                 jna .end
1099                 cmp al,'/'
1100                 jne .find_end
1101 .end:
1102                 dec si
1103                 sub si,[NameStart]
1104                 mov [NameLen],si
1105                 mov al,' '                      ; Space-fill name
1106                 rep stosb                       ; Doesn't do anything if CX=0
1107                 popa
1108                 ret                             ; Done
1109
1110 .is_period:
1111                 mov al,' '                      ; We need to space-fill
1112 .period_loop:   cmp cx,3                        ; If <= 3 characters left
1113                 jbe .loop                       ; Just ignore it
1114                 stosb                           ; Otherwise, write a space
1115                 loop .period_loop               ; Dec CX and *always* jump
1116
1117                 section .bss16
1118                 alignb 2
1119 NameStart       resw 1
1120 NameLen         resw 1
1121 MangledBuf      resb 11
1122
1123                 section .text16
1124 ;
1125 ; getfssec_edx: Get multiple sectors from a file
1126 ;
1127 ;       This routine makes sure the subtransfers do not cross a 64K boundary,
1128 ;       and will correct the situation if it does, UNLESS *sectors* cross
1129 ;       64K boundaries.
1130 ;
1131 ;       ES:BX   -> Buffer
1132 ;       EDX     -> Current sector number
1133 ;       CX      -> Sector count (0FFFFh = until end of file)
1134 ;                  Must not exceed the ES segment
1135 ;       Returns EDX=0, CF=1 on EOF (not necessarily error)
1136 ;       All arguments are advanced to reflect data read.
1137 ;
1138 getfssec_edx:
1139                 push ebp
1140                 push eax
1141 .getfragment:
1142                 xor ebp,ebp                     ; Fragment sector count
1143                 push edx                        ; Starting sector pointer
1144 .getseccnt:
1145                 inc bp
1146                 dec cx
1147                 jz .do_read
1148                 xor eax,eax
1149                 mov ax,es
1150                 shl ax,4
1151                 add ax,bx                       ; Now AX = how far into 64K block we are
1152                 not ax                          ; Bytes left in 64K block
1153                 inc eax
1154                 shr eax,SECTOR_SHIFT            ; Sectors left in 64K block
1155                 cmp bp,ax
1156                 jnb .do_read                    ; Unless there is at least 1 more sector room...
1157                 mov eax,edx                     ; Current sector
1158                 inc edx                         ; Predict it's the linearly next sector
1159                 call nextsector
1160                 jc .do_read
1161                 cmp edx,eax                     ; Did it match?
1162                 jz .getseccnt
1163 .do_read:
1164                 pop eax                         ; Starting sector pointer
1165                 call getlinsecsr
1166                 lea eax,[eax+ebp-1]             ; This is the last sector actually read
1167                 shl bp,9
1168                 add bx,bp                       ; Adjust buffer pointer
1169                 call nextsector
1170                 jc .eof
1171                 mov edx,eax
1172                 and cx,cx
1173                 jnz .getfragment
1174 .done:
1175                 pop eax
1176                 pop ebp
1177                 ret
1178 .eof:
1179                 xor edx,edx
1180                 stc
1181                 jmp .done
1182
1183 ;
1184 ; getfssec: Get multiple sectors from a file
1185 ;
1186 ;       Same as above, except SI is a pointer to a open_file_t
1187 ;
1188 ;       ES:BX   -> Buffer
1189 ;       DS:SI   -> Pointer to open_file_t
1190 ;       CX      -> Sector count (0FFFFh = until end of file)
1191 ;                  Must not exceed the ES segment
1192 ;       Returns CF=1 on EOF (not necessarily error)
1193 ;       ECX returns number of bytes read.
1194 ;       All arguments are advanced to reflect data read.
1195 ;
1196 getfssec:
1197                 push edx
1198                 movzx edx,cx
1199                 push edx                ; Zero-extended CX
1200                 cmp edx,[si+file_left]
1201                 jbe .sizeok
1202                 mov edx,[si+file_left]
1203                 mov cx,dx
1204 .sizeok:
1205                 sub [si+file_left],edx
1206                 mov edx,[si+file_sector]
1207                 call getfssec_edx
1208                 mov [si+file_sector],edx
1209                 pop ecx                 ; Sectors requested read
1210                 shl ecx,SECTOR_SHIFT
1211                 cmp ecx,[si+file_bytesleft]
1212                 ja .eof
1213 .noteof:
1214                 sub [si+file_bytesleft],ecx     ; CF <- 0
1215                 pop edx
1216                 ret
1217 .eof:
1218                 mov ecx,[si+file_bytesleft]
1219                 call close_file
1220                 pop edx
1221                 stc
1222                 ret
1223
1224 ;
1225 ; nextcluster: Advance a cluster pointer in EDI to the next cluster
1226 ;              pointed at in the FAT tables.  CF=0 on return if end of file.
1227 ;
1228 nextcluster:
1229                 jmp strict short nextcluster_fat28      ; This gets patched
1230
1231 nextcluster_fat12:
1232                 push eax
1233                 push edx
1234                 push bx
1235                 push cx
1236                 push si
1237                 mov edx,edi
1238                 shr edi,1
1239                 pushf                   ; Save the shifted-out LSB (=CF)
1240                 add edx,edi
1241                 mov eax,edx
1242                 shr eax,9
1243                 call getfatsector
1244                 mov bx,dx
1245                 and bx,1FFh
1246                 mov cl,[gs:si+bx]
1247                 inc edx
1248                 mov eax,edx
1249                 shr eax,9
1250                 call getfatsector
1251                 mov bx,dx
1252                 and bx,1FFh
1253                 mov ch,[gs:si+bx]
1254                 popf
1255                 jnc .even
1256                 shr cx,4
1257 .even:          and cx,0FFFh
1258                 movzx edi,cx
1259                 cmp di,0FF0h
1260                 pop si
1261                 pop cx
1262                 pop bx
1263                 pop edx
1264                 pop eax
1265                 ret
1266
1267 ;
1268 ; FAT16 decoding routine.
1269 ;
1270 nextcluster_fat16:
1271                 push eax
1272                 push si
1273                 push bx
1274                 mov eax,edi
1275                 shr eax,SECTOR_SHIFT-1
1276                 call getfatsector
1277                 mov bx,di
1278                 add bx,bx
1279                 and bx,1FEh
1280                 movzx edi,word [gs:si+bx]
1281                 cmp di,0FFF0h
1282                 pop bx
1283                 pop si
1284                 pop eax
1285                 ret
1286 ;
1287 ; FAT28 ("FAT32") decoding routine.
1288 ;
1289 nextcluster_fat28:
1290                 push eax
1291                 push si
1292                 push bx
1293                 mov eax,edi
1294                 shr eax,SECTOR_SHIFT-2
1295                 call getfatsector
1296                 mov bx,di
1297                 add bx,bx
1298                 add bx,bx
1299                 and bx,1FCh
1300                 mov edi,dword [gs:si+bx]
1301                 and edi,0FFFFFFFh       ; 28 bits only
1302                 cmp edi,0FFFFFF0h
1303                 pop bx
1304                 pop si
1305                 pop eax
1306                 ret
1307
1308 ;
1309 ; nextsector:   Given a sector in EAX on input, return the next sector
1310 ;               of the same filesystem object, which may be the root
1311 ;               directory or a cluster chain.  Returns  EOF.
1312 ;
1313 ;               Assumes CS == DS.
1314 ;
1315 nextsector:
1316                 push edi
1317                 push edx
1318                 mov edx,[DataArea]
1319                 mov edi,eax
1320                 sub edi,edx
1321                 jae .isdata
1322
1323                 ; Root directory
1324                 inc eax
1325                 cmp eax,edx
1326                 cmc
1327                 jmp .done
1328
1329 .isdata:
1330                 not edi
1331                 test edi,[ClustMask]
1332                 jz .endcluster
1333
1334                 ; It's not the final sector in a cluster
1335                 inc eax
1336                 jmp .done
1337
1338 .endcluster:
1339                 push gs                 ; nextcluster trashes gs
1340                 push cx
1341                 not edi
1342                 mov cl,[ClustShift]
1343                 shr edi,cl
1344                 add edi,2
1345
1346                 ; Now EDI contains the cluster number
1347                 call nextcluster
1348                 cmc
1349                 jc .exit                ; There isn't anything else...
1350
1351                 ; New cluster number now in EDI
1352                 sub edi,2
1353                 shl edi,cl              ; CF <- 0, unless something is very wrong
1354                 lea eax,[edi+edx]
1355 .exit:
1356                 pop cx
1357                 pop gs
1358 .done:
1359                 pop edx
1360                 pop edi
1361                 ret
1362
1363 ;
1364 ; getfatsector: Check for a particular sector (in EAX) in the FAT cache,
1365 ;               and return a pointer in GS:SI, loading it if needed.
1366 ;
1367 ;               Assumes CS == DS.
1368 ;
1369 getfatsector:
1370                 add eax,[FAT]           ; FAT starting address
1371                 jmp getcachesector
1372
1373 ; -----------------------------------------------------------------------------
1374 ;  Common modules
1375 ; -----------------------------------------------------------------------------
1376
1377 %include "common.inc"           ; Universal modules
1378 %include "plaincon.inc"         ; writechr
1379 %include "writestr.inc"         ; String output
1380 %include "writehex.inc"         ; Hexadecimal output
1381 %include "cache.inc"            ; Metadata disk cache
1382 %include "localboot.inc"        ; Disk-based local boot
1383
1384 ; -----------------------------------------------------------------------------
1385 ;  Begin data section
1386 ; -----------------------------------------------------------------------------
1387
1388                 section .data16
1389 copyright_str   db ' Copyright (C) 1994-'
1390                 asciidec YEAR
1391                 db ' H. Peter Anvin et al', CR, LF, 0
1392 err_bootfailed  db CR, LF, 'Boot failed: please change disks and press '
1393                 db 'a key to continue.', CR, LF, 0
1394 syslinux_cfg1   db '/boot'                      ; /boot/syslinux/syslinux.cfg
1395 syslinux_cfg2   db '/syslinux'                  ; /syslinux/syslinux.cfg
1396 syslinux_cfg3   db '/'                          ; /syslinux.cfg
1397 config_name     db 'syslinux.cfg', 0            ; syslinux.cfg
1398
1399 ;
1400 ; Config file keyword table
1401 ;
1402 %include "keywords.inc"
1403
1404 ;
1405 ; Extensions to search for (in *forward* order).
1406 ;
1407 exten_table:    db '.cbt'               ; COMBOOT (specific)
1408                 db '.bss'               ; Boot Sector (add superblock)
1409                 db '.bs', 0             ; Boot Sector
1410                 db '.com'               ; COMBOOT (same as DOS)
1411                 db '.c32'               ; COM32
1412 exten_table_end:
1413                 dd 0, 0                 ; Need 8 null bytes here
1414
1415 ;
1416 ; Misc initialized (data) variables
1417 ;
1418 %ifdef debug                            ; This code for debugging only
1419 debug_magic     dw 0D00Dh               ; Debug code sentinel
1420 %endif
1421
1422                 alignz 4
1423 BufSafe         dw trackbufsize/SECTOR_SIZE     ; Clusters we can load into trackbuf
1424 BufSafeBytes    dw trackbufsize         ; = how many bytes?
1425 %ifndef DEPEND
1426 %if ( trackbufsize % SECTOR_SIZE ) != 0
1427 %error trackbufsize must be a multiple of SECTOR_SIZE
1428 %endif
1429 %endif