Adding upstream version 4.00~pre61+dfsg.
[syslinux-debian/hramrach.git] / core / diskstart.inc
blob7bb47dc67b513d9c777308919d5d15d675f57c2a
1 ; -----------------------------------------------------------------------
3 ;   Copyright 1994-2009 H. Peter Anvin - All Rights Reserved
4 ;   Copyright 2009-2010 Intel Corporation; author: H. Peter Anvin
6 ;   This program is free software; you can redistribute it and/or modify
7 ;   it under the terms of the GNU General Public License as published by
8 ;   the Free Software Foundation, Inc., 51 Franklin St, Fifth Floor,
9 ;   Boston MA 02110-1301, USA; either version 2 of the License, or
10 ;   (at your option) any later version; incorporated herein by reference.
12 ; -----------------------------------------------------------------------
15 ; diskstart.inc
17 ; Common early-bootstrap code for harddisk-based Syslinux derivatives.
20                 section .earlybss
21                 alignb 16
22 PartInfo:                               ; Partition table info
23 .mbr:           resb 16                 ; MBR partition info
24 .gptlen:        resd 1
25 .gpt:           resb 56                 ; GPT partition info (minus name)
26 FloppyTable     resb 16                 ; Floppy info table (must follow PartInfo)
28                 section .init
30 ; Some of the things that have to be saved very early are saved
31 ; "close" to the initial stack pointer offset, in order to
32 ; reduce the code size...
34 StackBuf        equ STACK_TOP-44        ; Start the stack here (grow down - 4K)
35 Hidden          equ StackBuf-20         ; Partition offset
36 OrigFDCTabPtr   equ StackBuf-12         ; The 2nd high dword on the stack
37 OrigESDI        equ StackBuf-8          ; The high dword on the stack
38 DriveNumber     equ StackBuf-4          ; Drive number
39 StackHome       equ Hidden              ; The start of the canonical stack
42 ; Primary entry point.  Tempting as though it may be, we can't put the
43 ; initial "cli" here; the jmp opcode in the first byte is part of the
44 ; "magic number" (using the term very loosely) for the DOS superblock.
46 bootsec         equ $
47 _start:         jmp short start         ; 2 bytes
48                 nop                     ; 1 byte
50 ; "Superblock" follows -- it's in the boot sector, so it's already
51 ; loaded and ready for us
53 bsOemName       db MY_NAME              ; The SYS command sets this, so...
54                 zb 8-($-bsOemName)
57 ; These are the fields we actually care about.  We end up expanding them
58 ; all to dword size early in the code, so generate labels for both
59 ; the expanded and unexpanded versions.
61 %macro          superb 1
62 bx %+ %1        equ SuperInfo+($-superblock)*8+4
63 bs %+ %1        equ $
64                 zb 1
65 %endmacro
66 %macro          superw 1
67 bx %+ %1        equ SuperInfo+($-superblock)*8
68 bs %+ %1        equ $
69                 zw 1
70 %endmacro
71 %macro          superd 1
72 bx %+ %1        equ $                   ; no expansion for dwords
73 bs %+ %1        equ $
74                 zd 1
75 %endmacro
76 superblock      equ $
77                 superw BytesPerSec
78                 superb SecPerClust
79                 superw ResSectors
80                 superb FATs
81                 superw RootDirEnts
82                 superw Sectors
83                 superb Media
84                 superw FATsecs
85                 superw SecPerTrack
86                 superw Heads
87 superinfo_size  equ ($-superblock)-1    ; How much to expand
88                 superd Hidden
89                 superd HugeSectors
90                 ;
91                 ; This is as far as FAT12/16 and FAT32 are consistent
92                 ;
93                 ; FAT12/16 need 26 more bytes,
94                 ; FAT32 need 54 more bytes
95                 ;
96 superblock_len_fat16    equ $-superblock+26
97 superblock_len_fat32    equ $-superblock+54
98                 zb 54                   ; Maximum needed size
99 superblock_max  equ $-superblock
101                 global SecPerClust
102 SecPerClust     equ bxSecPerClust
105 ; Note we don't check the constraints above now; we did that at install
106 ; time (we hope!)
108 start:
109                 cli                     ; No interrupts yet, please
110                 cld                     ; Copy upwards
112 ; Set up the stack
114                 xor cx,cx
115                 mov ss,cx
116                 mov sp,StackBuf-2       ; Just below BSS (-2 for alignment)
117                 push dx                 ; Save drive number (in DL)
118                 push es                 ; Save initial ES:DI -> $PnP pointer
119                 push di
120                 mov es,cx
123 ; DS:SI may contain a partition table entry and possibly a GPT entry.
124 ; Preserve it for us.  This saves 56 bytes of the GPT entry, which is
125 ; currently the maximum we care about.  Total is 76 bytes.
127                 mov cl,(16+4+56)/2      ; Save partition info
128                 mov di,PartInfo
129                 rep movsw               ; This puts CX back to zero
131                 mov ds,cx               ; Now we can initialize DS...
134 ; Now sautee the BIOS floppy info block to that it will support decent-
135 ; size transfers; the floppy block is 11 bytes and is stored in the
136 ; INT 1Eh vector (brilliant waste of resources, eh?)
138 ; Of course, if BIOSes had been properly programmed, we wouldn't have
139 ; had to waste precious space with this code.
141                 mov bx,fdctab
142                 lfs si,[bx]             ; FS:SI -> original fdctab
143                 push fs                 ; Save on stack in case we need to bail
144                 push si
146                 ; Save the old fdctab even if hard disk so the stack layout
147                 ; is the same.  The instructions above do not change the flags
148                 and dl,dl               ; If floppy disk (00-7F), assume no
149                                         ; partition table
150                 js harddisk
152 floppy:
153                 xor ax,ax
154                 mov cl,6                ; 12 bytes (CX == 0)
155                 ; es:di -> FloppyTable already
156                 ; This should be safe to do now, interrupts are off...
157                 mov [bx],di             ; FloppyTable
158                 mov [bx+2],ax           ; Segment 0
159                 fs rep movsw            ; Faster to move words
160                 mov cl,[bsSecPerTrack]  ; Patch the sector count
161                 mov [di-76+8],cl
163                 push ax                 ; Partition offset == 0
164                 push ax
165                 push ax
166                 push ax
168                 int 13h                 ; Some BIOSes need this
169                 jmp short not_harddisk
171 ; The drive number and possibly partition information was passed to us
172 ; by the BIOS or previous boot loader (MBR).  Current "best practice" is to
173 ; trust that rather than what the superblock contains.
175 ; Note: di points to beyond the end of PartInfo
177 harddisk:
178                 test byte [di-76],7Fh   ; Sanity check: "active flag" should
179                 jnz .no_partition       ; be 00 or 80
180                 cmp eax,'!GPT'          ; !GPT signature?
181                 jne .mbr
182                 cmp byte [di-76+4],0EDh ; Synthetic GPT partition entry?
183                 jne .mbr
184 .gpt:                                   ; GPT-style partition info
185                 push dword [di-76+20+36]
186                 push dword [di-76+20+32]
187                 jmp .gotoffs
188 .mbr:                                   ; MBR-style partition info
189                 push cx                 ; Upper half partition offset == 0
190                 push cx
191                 push dword [di-76+8]    ; Partition offset (dword)
192                 jmp .gotoffs
193 .no_partition:
194                 push cx
195                 push cx
196                 push cx
197                 push cx
198 .gotoffs:
200 ; Get disk drive parameters (don't trust the superblock.)  Don't do this for
201 ; floppy drives -- INT 13:08 on floppy drives will (may?) return info about
202 ; what the *drive* supports, not about the *media*.  Fortunately floppy disks
203 ; tend to have a fixed, well-defined geometry which is stored in the superblock.
205                 ; DL == drive # still
206                 mov ah,08h
207                 int 13h
208                 jc no_driveparm
209                 and ah,ah
210                 jnz no_driveparm
211                 shr dx,8
212                 inc dx                  ; Contains # of heads - 1
213                 mov [bsHeads],dx
214                 and cx,3fh
215                 mov [bsSecPerTrack],cx
216 no_driveparm:
217 not_harddisk:
219 ; Ready to enable interrupts, captain
221                 sti
224 ; Do we have EBIOS (EDD)?
226 eddcheck:
227                 mov bx,55AAh
228                 mov ah,41h              ; EDD existence query
229                 mov dl,[DriveNumber]
230                 int 13h
231                 jc .noedd
232                 cmp bx,0AA55h
233                 jne .noedd
234                 test cl,1               ; Extended disk access functionality set
235                 jz .noedd
236                 ;
237                 ; We have EDD support...
238                 ;
239                 mov byte [getonesec.jmp+1],(getonesec_ebios-(getonesec.jmp+2))
240 .noedd:
243 ; Load the first sector of LDLINUX.SYS; this used to be all proper
244 ; with parsing the superblock and root directory; it doesn't fit
245 ; together with EBIOS support, unfortunately.
247                 mov eax,strict dword 0xdeadbeef
248 Sect1Ptr0       equ $-4
249                 mov edx,strict dword 0xfeedface
250 Sect1Ptr1       equ $-4
251                 mov bx,ldlinux_sys      ; Where to load it
252                 call getonesec
254                 ; Some modicum of integrity checking
255                 cmp dword [ldlinux_magic+4],LDLINUX_MAGIC^HEXDATE
256                 jne kaboom
258                 ; Go for it...
259                 jmp 0:ldlinux_ent
263 ; getonesec: load a single disk linear sector EDX:EAX into the buffer
264 ;            at ES:BX.
266 ;            This routine assumes CS == DS == SS, and trashes most registers.
268 ; Stylistic note: use "xchg" instead of "mov" when the source is a register
269 ; that is dead from that point; this saves space.  However, please keep
270 ; the order to dst,src to keep things sane.
272 getonesec:
273                 add eax,[Hidden]                ; Add partition offset
274                 adc edx,[Hidden+4]
275                 mov cx,retry_count
276 .jmp:           jmp strict short getonesec_cbios
279 ; getonesec_ebios:
281 ; getonesec implementation for EBIOS (EDD)
283 getonesec_ebios:
284 .retry:
285                 ; Form DAPA on stack
286                 push edx
287                 push eax
288                 push es
289                 push bx
290                 push word 1
291                 push word 16
292                 mov si,sp
293                 mov ah,42h                      ; Extended Read
294                 call xint13
295                 lea sp,[si+16]                  ; Remove DAPA
296                 jc .error
297                 ret
299 .error:
300                 ; Some systems seem to get "stuck" in an error state when
301                 ; using EBIOS.  Doesn't happen when using CBIOS, which is
302                 ; good, since some other systems get timeout failures
303                 ; waiting for the floppy disk to spin up.
305                 pushad                          ; Try resetting the device
306                 xor ax,ax
307                 int 13h
308                 popad
309                 loop .retry                     ; CX-- and jump if not zero
311                 ; Total failure.  Try falling back to CBIOS.
312                 mov byte [getonesec.jmp+1],(getonesec_cbios-(getonesec.jmp+2))
315 ; getonesec_cbios:
317 ; getlinsec implementation for legacy CBIOS
319 getonesec_cbios:
320 .retry:
321                 pushad
323                 movzx esi,word [bsSecPerTrack]
324                 movzx edi,word [bsHeads]
325                 ;
326                 ; Dividing by sectors to get (track,sector): we may have
327                 ; up to 2^18 tracks, so we need to use 32-bit arithmetric.
328                 ;
329                 div esi
330                 xor cx,cx
331                 xchg cx,dx              ; CX <- sector index (0-based)
332                                         ; EDX <- 0
333                 ; eax = track #
334                 div edi                 ; Convert track to head/cyl
336                 cmp eax,1023            ; Outside the CHS range?
337                 ja kaboom
339                 ;
340                 ; Now we have AX = cyl, DX = head, CX = sector (0-based),
341                 ; SI = bsSecPerTrack, ES:BX = data target
342                 ;
343                 shl ah,6                ; Because IBM was STOOPID
344                                         ; and thought 8 bits were enough
345                                         ; then thought 10 bits were enough...
346                 inc cx                  ; Sector numbers are 1-based, sigh
347                 or cl,ah
348                 mov ch,al
349                 mov dh,dl
350                 mov ax,0201h            ; Read one sector
351                 call xint13
352                 popad
353                 jc .error
354                 ret
356 .error:
357                 loop .retry
358                 ; Fall through to disk_error
361 ; kaboom: write a message and bail out.
363                 global kaboom
364 disk_error:
365 kaboom:
366                 xor si,si
367                 mov ss,si
368                 mov sp,OrigFDCTabPtr    ; Reset stack
369                 mov ds,si               ; Reset data segment
370                 pop dword [fdctab]      ; Restore FDC table
371 .patch:                                 ; When we have full code, intercept here
372                 mov si,bailmsg
373                 call writestr_early
375                 xor ax,ax
376 .again:         int 16h                 ; Wait for keypress
377                                         ; NB: replaced by int 18h if
378                                         ; chosen at install time..
379                 int 19h                 ; And try once more to boot...
380 .norge:         hlt                     ; If int 19h returned; this is the end
381                 jmp short .norge
385 ; writestr_early: write a null-terminated string to the console
386 ;           This assumes we're on page 0.  This is only used for early
387 ;           messages, so it should be OK.
389 writestr_early:
390                 pushad
391 .loop:          lodsb
392                 and al,al
393                 jz .return
394                 mov ah,0Eh              ; Write to screen as TTY
395                 mov bx,0007h            ; Attribute
396                 int 10h
397                 jmp short .loop
398 .return:        popad
399                 ret
402 ; INT 13h wrapper function
404 xint13:
405                 mov dl,[DriveNumber]
406                 pushad
407                 int 13h
408                 popad
409                 ret
412 ; Error message on failure
414 bailmsg:        db 'Boot error', 0Dh, 0Ah, 0
416                 ; This fails if the boot sector overflowsg
417                 zb 1FEh-($-$$)
419 bootsignature   dw 0xAA55
422 ; ===========================================================================
423 ;  End of boot sector
424 ; ===========================================================================
425 ;  Start of LDLINUX.SYS
426 ; ===========================================================================
428 LDLINUX_SYS     equ ($-$$)+TEXT_START
429 ldlinux_sys:
431 syslinux_banner db CR, LF, MY_NAME, ' ', VERSION_STR, ' ', DATE_STR, ' ', 0
432                 db CR, LF, 1Ah  ; EOF if we "type" this in DOS
434                 alignz 8
435 ldlinux_magic   dd LDLINUX_MAGIC
436                 dd LDLINUX_MAGIC^HEXDATE
439 ; This area is patched by the installer.  It is found by looking for
440 ; LDLINUX_MAGIC, plus 8 bytes.
442 SUBVOL_MAX      equ 256
443 CURRENTDIR_MAX  equ FILENAME_MAX
445 patch_area:
446 DataSectors     dw 0            ; Number of sectors (not including bootsec)
447 ADVSectors      dw 0            ; Additional sectors for ADVs
448 LDLDwords       dd 0            ; Total dwords starting at ldlinux_sys,
449 CheckSum        dd 0            ; Checksum starting at ldlinux_sys
450                                 ; value = LDLINUX_MAGIC - [sum of dwords]
451 MaxTransfer     dw 127          ; Max sectors to transfer
452 EPAPtr          dw EPA - LDLINUX_SYS    ; Pointer to the extended patch area
455 ; Extended patch area -- this is in .data16 so it doesn't occupy space in
456 ; the first sector.  Use this structure for anything that isn't used by
457 ; the first sector itself.
459                 section .data16
460                 alignz 2
461 EPA:
462 ADVSecPtr       dw ADVSec0 - LDLINUX_SYS
463 CurrentDirPtr   dw CurrentDirName-LDLINUX_SYS   ; Current directory name string
464 CurrentDirLen   dw CURRENTDIR_MAX
465 SubvolPtr       dw SubvolName-LDLINUX_SYS
466 SubvolLen       dw SUBVOL_MAX
467 SecPtrOffset    dw SectorPtrs-LDLINUX_SYS
468 SecPtrCnt       dw (SectorPtrsEnd - SectorPtrs)/10
471 ; Boot sector patch pointers
473 Sect1Ptr0Ptr    dw Sect1Ptr0 - bootsec          ; Pointers to Sector 1 location
474 Sect1Ptr1Ptr    dw Sect1Ptr1 - bootsec
475 RAIDPatchPtr    dw kaboom.again - bootsec       ; Patch to INT 18h in RAID mode
478 ; Base directory name and subvolume, if applicable.
480 %define HAVE_CURRENTDIRNAME
481                 global CurrentDirName, SubvolName
482 CurrentDirName  times CURRENTDIR_MAX db 0
483 SubvolName      times SUBVOL_MAX db 0
485                 section .init
486 ldlinux_ent:
488 ; Note that some BIOSes are buggy and run the boot sector at 07C0:0000
489 ; instead of 0000:7C00 and the like.  We don't want to add anything
490 ; more to the boot sector, so it is written to not assume a fixed
491 ; value in CS, but we don't want to deal with that anymore from now
492 ; on.
494                 sti             ; In case of broken INT 13h BIOSes
497 ; Tell the user we got this far
499                 mov si,syslinux_banner
500                 call writestr_early
503 ; Checksum data thus far
505                 mov si,ldlinux_sys
506                 mov cx,SECTOR_SIZE >> 2
507                 mov edx,-LDLINUX_MAGIC
508 .checksum:
509                 lodsd
510                 add edx,eax
511                 loop .checksum
512                 mov [CheckSum],edx              ; Save intermediate result
515 ; Tell the user if we're using EBIOS or CBIOS
517 print_bios:
518                 mov si,cbios_name
519                 cmp byte [getonesec.jmp+1],(getonesec_ebios-(getonesec.jmp+2))
520                 jne .cbios
521                 mov si,ebios_name
522                 mov byte [getlinsec.jmp+1],(getlinsec_ebios-(getlinsec.jmp+2))
523 .cbios:
524                 mov [BIOSName],si
525                 call writestr_early
527                 section .earlybss
528 %define HAVE_BIOSNAME 1
529 BIOSName        resw 1
531                 section .init
533 ; Now we read the rest of LDLINUX.SYS.
535 load_rest:
536                 lea esi,[SectorPtrs]
537                 mov ebx,TEXT_START+2*SECTOR_SIZE ; Where we start loading
538                 mov cx,[DataSectors]
539                 dec cx                          ; Minus this sector
541 .get_chunk:
542                 jcxz .done
543                 mov eax,[si]
544                 mov edx,[si+4]
545                 movzx ebp,word [si+8]
546                 sub cx,bp
547                 push ebx
548                 shr ebx,4                       ; Convert to a segment
549                 mov es,bx
550                 xor bx,bx
551                 call getlinsec
552                 pop ebx
553                 shl ebp,SECTOR_SHIFT
554                 add ebx,ebp
555                 add si,10
556                 jmp .get_chunk
558 .done:
561 ; All loaded up, verify that we got what we needed.
562 ; Note: the checksum field is embedded in the checksum region, so
563 ; by the time we get to the end it should all cancel out.
565 verify_checksum:
566                 mov si,ldlinux_sys + SECTOR_SIZE
567                 mov ecx,[LDLDwords]
568                 sub ecx,SECTOR_SIZE >> 2
569                 mov eax,[CheckSum]
570 .checksum:
571                 add eax,[si]
572                 add si,4
573                 jnz .nowrap
574                 ; Handle segment wrap
575                 mov dx,ds
576                 add dx,1000h
577                 mov ds,dx
578 .nowrap:
579                 dec ecx
580                 jnz .checksum
582                 and eax,eax                     ; Should be zero
583                 jz all_read                     ; We're cool, go for it!
586 ; Uh-oh, something went bad...
588                 mov si,checksumerr_msg
589                 call writestr_early
590                 jmp kaboom
593 ; -----------------------------------------------------------------------------
594 ; Subroutines that have to be in the first sector
595 ; -----------------------------------------------------------------------------
600 ; getlinsec: load a sequence of BP floppy sector given by the linear sector
601 ;            number in EAX into the buffer at ES:BX.  We try to optimize
602 ;            by loading up to a whole track at a time, but the user
603 ;            is responsible for not crossing a 64K boundary.
604 ;            (Yes, BP is weird for a count, but it was available...)
606 ;            On return, BX points to the first byte after the transferred
607 ;            block.
609 ;            This routine assumes CS == DS.
611                 global getlinsec
612 getlinsec:
613                 pushad
614                 add eax,[Hidden]                ; Add partition offset
615                 adc edx,[Hidden+4]
616 .jmp:           jmp strict short getlinsec_cbios
619 ; getlinsec_ebios:
621 ; getlinsec implementation for EBIOS (EDD)
623 getlinsec_ebios:
624 .loop:
625                 push bp                         ; Sectors left
626 .retry2:
627                 call maxtrans                   ; Enforce maximum transfer size
628                 movzx edi,bp                    ; Sectors we are about to read
629                 mov cx,retry_count
630 .retry:
632                 ; Form DAPA on stack
633                 push edx
634                 push eax
635                 push es
636                 push bx
637                 push di
638                 push word 16
639                 mov si,sp
640                 mov ah,42h                      ; Extended Read
641                 push ds
642                 push ss
643                 pop ds
644                 call xint13
645                 pop ds
646                 lea sp,[si+16]                  ; Remove DAPA
647                 jc .error
648                 pop bp
649                 add eax,edi                     ; Advance sector pointer
650                 adc edx,0
651                 sub bp,di                       ; Sectors left
652                 shl di,SECTOR_SHIFT             ; 512-byte sectors
653                 add bx,di                       ; Advance buffer pointer
654                 and bp,bp
655                 jnz .loop
657                 popad
658                 ret
660 .error:
661                 ; Some systems seem to get "stuck" in an error state when
662                 ; using EBIOS.  Doesn't happen when using CBIOS, which is
663                 ; good, since some other systems get timeout failures
664                 ; waiting for the floppy disk to spin up.
666                 pushad                          ; Try resetting the device
667                 xor ax,ax
668                 mov dl,[DriveNumber]
669                 int 13h
670                 popad
671                 loop .retry                     ; CX-- and jump if not zero
673                 ;shr word [MaxTransfer],1       ; Reduce the transfer size
674                 ;jnz .retry2
676                 ; Total failure.  Try falling back to CBIOS.
677                 mov byte [getlinsec.jmp+1],(getlinsec_cbios-(getlinsec.jmp+2))
678                 ;mov byte [MaxTransfer],63      ; Max possibe CBIOS transfer
680                 pop bp
681                 ; ... fall through ...
684 ; getlinsec_cbios:
686 ; getlinsec implementation for legacy CBIOS
688 getlinsec_cbios:
689 .loop:
690                 push edx
691                 push eax
692                 push bp
693                 push bx
695                 movzx esi,word [bsSecPerTrack]
696                 movzx edi,word [bsHeads]
697                 ;
698                 ; Dividing by sectors to get (track,sector): we may have
699                 ; up to 2^18 tracks, so we need to use 32-bit arithmetric.
700                 ;
701                 div esi
702                 xor cx,cx
703                 xchg cx,dx              ; CX <- sector index (0-based)
704                                         ; EDX <- 0
705                 ; eax = track #
706                 div edi                 ; Convert track to head/cyl
708                 cmp eax,1023            ; Outside the CHS range?
709                 ja kaboom
711                 ;
712                 ; Now we have AX = cyl, DX = head, CX = sector (0-based),
713                 ; BP = sectors to transfer, SI = bsSecPerTrack,
714                 ; ES:BX = data target
715                 ;
717                 call maxtrans                   ; Enforce maximum transfer size
719                 ; Must not cross track boundaries, so BP <= SI-CX
720                 sub si,cx
721                 cmp bp,si
722                 jna .bp_ok
723                 mov bp,si
724 .bp_ok:
726                 shl ah,6                ; Because IBM was STOOPID
727                                         ; and thought 8 bits were enough
728                                         ; then thought 10 bits were enough...
729                 inc cx                  ; Sector numbers are 1-based, sigh
730                 or cl,ah
731                 mov ch,al
732                 mov dh,dl
733                 xchg ax,bp              ; Sector to transfer count
734                 mov ah,02h              ; Read sectors
735                 mov bp,retry_count
736 .retry:
737                 call xint13
738                 jc .error
739 .resume:
740                 movzx ecx,al            ; ECX <- sectors transferred
741                 shl ax,SECTOR_SHIFT     ; Convert sectors in AL to bytes in AX
742                 pop bx
743                 add bx,ax
744                 pop bp
745                 pop eax
746                 pop edx
747                 add eax,ecx
748                 sub bp,cx
749                 jnz .loop
750                 popad
751                 ret
753 .error:
754                 dec bp
755                 jnz .retry
757                 xchg ax,bp              ; Sectors transferred <- 0
758                 shr word [MaxTransfer],1
759                 jnz .resume
760                 jmp kaboom
762 maxtrans:
763                 cmp bp,[MaxTransfer]
764                 jna .ok
765                 mov bp,[MaxTransfer]
766 .ok:            ret
769 ; Checksum error message
771 checksumerr_msg db ' Load error - ', 0  ; Boot failed appended
774 ; BIOS type string
776 cbios_name      db 'CHS', 0                     ; CHS/CBIOS
777 ebios_name      db 'EDD', 0                     ; EDD/EBIOS
780 ; Debug routine
782 %ifdef debug
783 safedumpregs:
784                 cmp word [Debug_Magic],0D00Dh
785                 jnz nc_return
786                 jmp dumpregs
787 %endif
789 rl_checkpt      equ $                           ; Must be <= 8000h
791 rl_checkpt_off  equ ($-$$)
792 %ifndef DEPEND
793  %if rl_checkpt_off > 3F6h                      ; Need one extent
794   %assign rl_checkpt_overflow rl_checkpt_off - 3F6h
795   %error Sector 1 overflow by rl_checkpt_overflow bytes
796  %endif
797 %endif
800 ; Extent pointers... each extent contains an 8-byte LBA and an 2-byte
801 ; sector count.  In most cases, we will only ever need a handful of
802 ; extents, but we have to assume a maximally fragmented system where each
803 ; extent contains only one sector.
805                 alignz 2
806 MaxInitDataSize equ 96 << 10
807 MaxLMA          equ TEXT_START+SECTOR_SIZE+MaxInitDataSize
808 SectorPtrs      zb 10*(MaxInitDataSize >> SECTOR_SHIFT)
809 SectorPtrsEnd   equ $
811 ; ----------------------------------------------------------------------------
812 ;  End of code and data that have to be in the first sector
813 ; ----------------------------------------------------------------------------
815                 section .text16
816 all_read:
817                 ; We enter here with both DS and ES scrambled...
818                 xor ax,ax
819                 mov ds,ax
820                 mov es,ax
822 ; Let the user (and programmer!) know we got this far.  This used to be
823 ; in Sector 1, but makes a lot more sense here.
825                 mov si,copyright_str
826                 call writestr_early
830 ; Insane hack to expand the DOS superblock to dwords
832 expand_super:
833                 xor eax,eax
834                 mov si,superblock
835                 mov di,SuperInfo
836                 mov cx,superinfo_size
837 .loop:
838                 lodsw
839                 dec si
840                 stosd                           ; Store expanded word
841                 xor ah,ah
842                 stosd                           ; Store expanded byte
843                 loop .loop
847 ; Common initialization code
849 %include "init.inc"
850                 
851                 pushad
852                 mov eax,ROOT_FS_OPS
853                 movzx dx,byte [DriveNumber]
854                 ; DH = 0: we are boot from disk not CDROM
855                 mov ecx,[Hidden]
856                 mov ebx,[Hidden+4]
857                 mov si,[bsHeads]
858                 mov di,[bsSecPerTrack]
859                 movzx ebp,word [MaxTransfer]
860                 pm_call fs_init
861                 popad
863                 section .bss16
864 SuperInfo       resq 16                 ; The first 16 bytes expanded 8 times
866                 section .text16