Adding debian version 4.03+dfsg-7.
[syslinux-debian/hramrach.git] / core / diskstart.inc
blobc0301d4be8eabb33348d2220cf4a6ae39514ed76
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 .init
22 ; Some of the things that have to be saved very early are saved
23 ; "close" to the initial stack pointer offset, in order to
24 ; reduce the code size...
27 StackBuf        equ STACK_TOP-44-92     ; Start the stack here (grow down - 4K)
28 PartInfo        equ StackBuf
29 .mbr            equ PartInfo
30 .gptlen         equ PartInfo+16
31 .gpt            equ PartInfo+20
32 FloppyTable     equ PartInfo+76
33 ; Total size of PartInfo + FloppyTable == 76+16 = 92 bytes
34 Hidden          equ StackBuf-24         ; Partition offset (qword)
35 OrigFDCTabPtr   equ StackBuf-16         ; Original FDC table
36 OrigDSSI        equ StackBuf-12         ; DS:SI -> partinfo
37 OrigESDI        equ StackBuf-8          ; ES:DI -> $PnP structure
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                 push ds                 ; Save original DS:SI -> partinfo
121                 push si
122                 mov es,cx
125 ; DS:SI may contain a partition table entry and possibly a GPT entry.
126 ; Preserve it for us.  This saves 56 bytes of the GPT entry, which is
127 ; currently the maximum we care about.  Total is 76 bytes.
129                 mov cl,(16+4+56)/2      ; Save partition info
130                 mov di,PartInfo
131                 rep movsw               ; This puts CX back to zero
133                 mov ds,cx               ; Now we can initialize DS...
136 ; Now sautee the BIOS floppy info block to that it will support decent-
137 ; size transfers; the floppy block is 11 bytes and is stored in the
138 ; INT 1Eh vector (brilliant waste of resources, eh?)
140 ; Of course, if BIOSes had been properly programmed, we wouldn't have
141 ; had to waste precious space with this code.
143                 mov bx,fdctab
144                 lfs si,[bx]             ; FS:SI -> original fdctab
145                 push fs                 ; Save on stack in case we need to bail
146                 push si
148                 ; Save the old fdctab even if hard disk so the stack layout
149                 ; is the same.  The instructions above do not change the flags
150                 and dl,dl               ; If floppy disk (00-7F), assume no
151                                         ; partition table
152                 js harddisk
154 floppy:
155                 xor ax,ax
156                 mov cl,6                ; 12 bytes (CX == 0)
157                 ; es:di -> FloppyTable already
158                 ; This should be safe to do now, interrupts are off...
159                 mov [bx],di             ; FloppyTable
160                 mov [bx+2],ax           ; Segment 0
161                 fs rep movsw            ; Faster to move words
162                 mov cl,[bsSecPerTrack]  ; Patch the sector count
163                 mov [di-76+8],cl
165                 push ax                 ; Partition offset == 0
166                 push ax
167                 push ax
168                 push ax
170                 int 13h                 ; Some BIOSes need this
171                 jmp short not_harddisk
173 ; The drive number and possibly partition information was passed to us
174 ; by the BIOS or previous boot loader (MBR).  Current "best practice" is to
175 ; trust that rather than what the superblock contains.
177 ; Note: di points to beyond the end of PartInfo
179 harddisk:
180                 mov dx,[di-76-10]       ; Original DS
181                 mov si,[di-76-12]       ; Original SI
182                 shr si,4
183                 add dx,si
184                 cmp dx,PartInfo >> 4
185                 jae .no_partition
186                 test byte [di-76],7Fh   ; Sanity check: "active flag" should
187                 jnz .no_partition       ; be 00 or 80
188                 cmp [di-76+4],cl        ; Sanity check: partition type != 0
189                 je .no_partition
190                 cmp eax,'!GPT'          ; !GPT signature?
191                 jne .mbr
192                 cmp byte [di-76+4],0EDh ; Synthetic GPT partition entry?
193                 jne .mbr
194 .gpt:                                   ; GPT-style partition info
195                 push dword [di-76+20+36]
196                 push dword [di-76+20+32]
197                 jmp .gotoffs
198 .mbr:                                   ; MBR-style partition info
199                 push cx                 ; Upper half partition offset == 0
200                 push cx
201                 push dword [di-76+8]    ; Partition offset (dword)
202                 jmp .gotoffs
203 .no_partition:
205 ; No partition table given... assume that the Hidden field in the boot sector
206 ; tells the truth (in particular, is zero if this is an unpartitioned disk.)
208                 push cx
209                 push cx
210                 push dword [bsHidden]
211 .gotoffs:
213 ; Get disk drive parameters (don't trust the superblock.)  Don't do this for
214 ; floppy drives -- INT 13:08 on floppy drives will (may?) return info about
215 ; what the *drive* supports, not about the *media*.  Fortunately floppy disks
216 ; tend to have a fixed, well-defined geometry which is stored in the superblock.
218                 ; DL == drive # still
219                 mov ah,08h
220                 int 13h
221                 jc no_driveparm
222                 and ah,ah
223                 jnz no_driveparm
224                 shr dx,8
225                 inc dx                  ; Contains # of heads - 1
226                 mov [bsHeads],dx
227                 and cx,3fh
228                 mov [bsSecPerTrack],cx
229 no_driveparm:
230 not_harddisk:
232 ; Ready to enable interrupts, captain
234                 sti
237 ; Do we have EBIOS (EDD)?
239 eddcheck:
240                 mov bx,55AAh
241                 mov ah,41h              ; EDD existence query
242                 mov dl,[DriveNumber]
243                 int 13h
244                 jc .noedd
245                 cmp bx,0AA55h
246                 jne .noedd
247                 test cl,1               ; Extended disk access functionality set
248                 jz .noedd
249                 ;
250                 ; We have EDD support...
251                 ;
252                 mov byte [getonesec.jmp+1],(getonesec_ebios-(getonesec.jmp+2))
253 .noedd:
256 ; Load the first sector of LDLINUX.SYS; this used to be all proper
257 ; with parsing the superblock and root directory; it doesn't fit
258 ; together with EBIOS support, unfortunately.
260                 mov eax,strict dword 0xdeadbeef
261 Sect1Ptr0       equ $-4
262                 mov edx,strict dword 0xfeedface
263 Sect1Ptr1       equ $-4
264                 mov bx,ldlinux_sys      ; Where to load it
265                 call getonesec
267                 ; Some modicum of integrity checking
268                 cmp dword [ldlinux_magic+4],LDLINUX_MAGIC^HEXDATE
269                 jne kaboom
271                 ; Go for it...
272                 jmp 0:ldlinux_ent
276 ; getonesec: load a single disk linear sector EDX:EAX into the buffer
277 ;            at ES:BX.
279 ;            This routine assumes CS == DS == SS, and trashes most registers.
281 ; Stylistic note: use "xchg" instead of "mov" when the source is a register
282 ; that is dead from that point; this saves space.  However, please keep
283 ; the order to dst,src to keep things sane.
285 getonesec:
286                 add eax,[Hidden]                ; Add partition offset
287                 adc edx,[Hidden+4]
288                 mov cx,retry_count
289 .jmp:           jmp strict short getonesec_cbios
292 ; getonesec_ebios:
294 ; getonesec implementation for EBIOS (EDD)
296 getonesec_ebios:
297 .retry:
298                 ; Form DAPA on stack
299                 push edx
300                 push eax
301                 push es
302                 push bx
303                 push word 1
304                 push word 16
305                 mov si,sp
306                 pushad
307                 mov ah,42h                      ; Extended Read
308                 call xint13
309                 popad
310                 lea sp,[si+16]                  ; Remove DAPA
311                 jc .error
312                 ret
314 .error:
315                 ; Some systems seem to get "stuck" in an error state when
316                 ; using EBIOS.  Doesn't happen when using CBIOS, which is
317                 ; good, since some other systems get timeout failures
318                 ; waiting for the floppy disk to spin up.
320                 pushad                          ; Try resetting the device
321                 xor ax,ax
322                 call xint13
323                 popad
324                 loop .retry                     ; CX-- and jump if not zero
326                 ; Total failure.  Try falling back to CBIOS.
327                 mov byte [getonesec.jmp+1],(getonesec_cbios-(getonesec.jmp+2))
330 ; getonesec_cbios:
332 ; getlinsec implementation for legacy CBIOS
334 getonesec_cbios:
335 .retry:
336                 pushad
338                 movzx esi,word [bsSecPerTrack]
339                 movzx edi,word [bsHeads]
340                 ;
341                 ; Dividing by sectors to get (track,sector): we may have
342                 ; up to 2^18 tracks, so we need to use 32-bit arithmetric.
343                 ;
344                 div esi
345                 xor cx,cx
346                 xchg cx,dx              ; CX <- sector index (0-based)
347                                         ; EDX <- 0
348                 ; eax = track #
349                 div edi                 ; Convert track to head/cyl
351                 cmp eax,1023            ; Outside the CHS range?
352                 ja kaboom
354                 ;
355                 ; Now we have AX = cyl, DX = head, CX = sector (0-based),
356                 ; SI = bsSecPerTrack, ES:BX = data target
357                 ;
358                 shl ah,6                ; Because IBM was STOOPID
359                                         ; and thought 8 bits were enough
360                                         ; then thought 10 bits were enough...
361                 inc cx                  ; Sector numbers are 1-based, sigh
362                 or cl,ah
363                 mov ch,al
364                 mov dh,dl
365                 mov ax,0201h            ; Read one sector
366                 call xint13
367                 popad
368                 jc .error
369                 ret
371 .error:
372                 loop .retry
373                 ; Fall through to disk_error
376 ; kaboom: write a message and bail out.
378                 global kaboom
379 disk_error:
380 kaboom:
381                 xor si,si
382                 mov ss,si
383                 mov sp,OrigFDCTabPtr    ; Reset stack
384                 mov ds,si               ; Reset data segment
385                 pop dword [fdctab]      ; Restore FDC table
386 .patch:                                 ; When we have full code, intercept here
387                 mov si,bailmsg
388                 call writestr_early
390                 xor ax,ax
391 .again:         int 16h                 ; Wait for keypress
392                                         ; NB: replaced by int 18h if
393                                         ; chosen at install time..
394                 int 19h                 ; And try once more to boot...
395 .norge:         hlt                     ; If int 19h returned; this is the end
396                 jmp short .norge
400 ; writestr_early: write a null-terminated string to the console
401 ;           This assumes we're on page 0.  This is only used for early
402 ;           messages, so it should be OK.
404 writestr_early:
405                 pushad
406 .loop:          lodsb
407                 and al,al
408                 jz .return
409                 mov ah,0Eh              ; Write to screen as TTY
410                 mov bx,0007h            ; Attribute
411                 int 10h
412                 jmp short .loop
413 .return:        popad
414                 ret
417 ; INT 13h wrapper function
419 xint13:
420                 mov dl,[DriveNumber]
421                 int 13h
422                 ret
425 ; Error message on failure
427 bailmsg:        db 'Boot error', 0Dh, 0Ah, 0
429                 ; This fails if the boot sector overflowsg
430                 zb 1FEh-($-$$)
432 bootsignature   dw 0xAA55
435 ; ===========================================================================
436 ;  End of boot sector
437 ; ===========================================================================
438 ;  Start of LDLINUX.SYS
439 ; ===========================================================================
441 LDLINUX_SYS     equ ($-$$)+TEXT_START
442 ldlinux_sys:
444 syslinux_banner db CR, LF, MY_NAME, ' ', VERSION_STR, ' ', DATE_STR, ' ', 0
445                 db CR, LF, 1Ah  ; EOF if we "type" this in DOS
447                 alignz 8
448 ldlinux_magic   dd LDLINUX_MAGIC
449                 dd LDLINUX_MAGIC^HEXDATE
452 ; This area is patched by the installer.  It is found by looking for
453 ; LDLINUX_MAGIC, plus 8 bytes.
455 SUBVOL_MAX      equ 256
456 CURRENTDIR_MAX  equ FILENAME_MAX
458 patch_area:
459 DataSectors     dw 0            ; Number of sectors (not including bootsec)
460 ADVSectors      dw 0            ; Additional sectors for ADVs
461 LDLDwords       dd 0            ; Total dwords starting at ldlinux_sys,
462 CheckSum        dd 0            ; Checksum starting at ldlinux_sys
463                                 ; value = LDLINUX_MAGIC - [sum of dwords]
464 MaxTransfer     dw 127          ; Max sectors to transfer
465 EPAPtr          dw EPA - LDLINUX_SYS    ; Pointer to the extended patch area
468 ; Extended patch area -- this is in .data16 so it doesn't occupy space in
469 ; the first sector.  Use this structure for anything that isn't used by
470 ; the first sector itself.
472                 section .data16
473                 alignz 2
474 EPA:
475 ADVSecPtr       dw ADVSec0 - LDLINUX_SYS
476 CurrentDirPtr   dw CurrentDirName-LDLINUX_SYS   ; Current directory name string
477 CurrentDirLen   dw CURRENTDIR_MAX
478 SubvolPtr       dw SubvolName-LDLINUX_SYS
479 SubvolLen       dw SUBVOL_MAX
480 SecPtrOffset    dw SectorPtrs-LDLINUX_SYS
481 SecPtrCnt       dw (SectorPtrsEnd - SectorPtrs)/10
484 ; Boot sector patch pointers
486 Sect1Ptr0Ptr    dw Sect1Ptr0 - bootsec          ; Pointers to Sector 1 location
487 Sect1Ptr1Ptr    dw Sect1Ptr1 - bootsec
488 RAIDPatchPtr    dw kaboom.again - bootsec       ; Patch to INT 18h in RAID mode
491 ; Base directory name and subvolume, if applicable.
493 %define HAVE_CURRENTDIRNAME
494                 global CurrentDirName, SubvolName
495 CurrentDirName  times CURRENTDIR_MAX db 0
496 SubvolName      times SUBVOL_MAX db 0
498                 section .init
499 ldlinux_ent:
501 ; Note that some BIOSes are buggy and run the boot sector at 07C0:0000
502 ; instead of 0000:7C00 and the like.  We don't want to add anything
503 ; more to the boot sector, so it is written to not assume a fixed
504 ; value in CS, but we don't want to deal with that anymore from now
505 ; on.
507                 sti             ; In case of broken INT 13h BIOSes
510 ; Tell the user we got this far
512                 mov si,syslinux_banner
513                 call writestr_early
516 ; Checksum data thus far
518                 mov si,ldlinux_sys
519                 mov cx,SECTOR_SIZE >> 2
520                 mov edx,-LDLINUX_MAGIC
521 .checksum:
522                 lodsd
523                 add edx,eax
524                 loop .checksum
525                 mov [CheckSum],edx              ; Save intermediate result
528 ; Tell the user if we're using EBIOS or CBIOS
530 print_bios:
531                 mov si,cbios_name
532                 cmp byte [getonesec.jmp+1],(getonesec_ebios-(getonesec.jmp+2))
533                 jne .cbios
534                 mov si,ebios_name
535                 mov byte [getlinsec.jmp+1],(getlinsec_ebios-(getlinsec.jmp+2))
536 .cbios:
537                 mov [BIOSName],si
538                 call writestr_early
540                 section .earlybss
541 %define HAVE_BIOSNAME 1
542 BIOSName        resw 1
544                 section .init
546 ; Now we read the rest of LDLINUX.SYS.
548 load_rest:
549                 lea esi,[SectorPtrs]
550                 mov ebx,TEXT_START+2*SECTOR_SIZE ; Where we start loading
551                 mov cx,[DataSectors]
552                 dec cx                          ; Minus this sector
554 .get_chunk:
555                 jcxz .done
556                 mov eax,[si]
557                 mov edx,[si+4]
558                 movzx ebp,word [si+8]
559                 sub cx,bp
560                 push ebx
561                 shr ebx,4                       ; Convert to a segment
562                 mov es,bx
563                 xor bx,bx
564                 call getlinsec
565                 pop ebx
566                 shl ebp,SECTOR_SHIFT
567                 add ebx,ebp
568                 add si,10
569                 jmp .get_chunk
571 .done:
574 ; All loaded up, verify that we got what we needed.
575 ; Note: the checksum field is embedded in the checksum region, so
576 ; by the time we get to the end it should all cancel out.
578 verify_checksum:
579                 mov si,ldlinux_sys + SECTOR_SIZE
580                 mov ecx,[LDLDwords]
581                 sub ecx,SECTOR_SIZE >> 2
582                 mov eax,[CheckSum]
583 .checksum:
584                 add eax,[si]
585                 add si,4
586                 jnz .nowrap
587                 ; Handle segment wrap
588                 mov dx,ds
589                 add dx,1000h
590                 mov ds,dx
591 .nowrap:
592                 dec ecx
593                 jnz .checksum
595                 and eax,eax                     ; Should be zero
596                 jz all_read                     ; We're cool, go for it!
599 ; Uh-oh, something went bad...
601                 mov si,checksumerr_msg
602                 call writestr_early
603                 jmp kaboom
606 ; -----------------------------------------------------------------------------
607 ; Subroutines that have to be in the first sector
608 ; -----------------------------------------------------------------------------
613 ; getlinsec: load a sequence of BP floppy sector given by the linear sector
614 ;            number in EAX into the buffer at ES:BX.  We try to optimize
615 ;            by loading up to a whole track at a time, but the user
616 ;            is responsible for not crossing a 64K boundary.
617 ;            (Yes, BP is weird for a count, but it was available...)
619 ;            On return, BX points to the first byte after the transferred
620 ;            block.
622 ;            This routine assumes CS == DS.
624                 global getlinsec
625 getlinsec:
626                 pushad
627                 add eax,[Hidden]                ; Add partition offset
628                 adc edx,[Hidden+4]
629 .jmp:           jmp strict short getlinsec_cbios
632 ; getlinsec_ebios:
634 ; getlinsec implementation for EBIOS (EDD)
636 getlinsec_ebios:
637 .loop:
638                 push bp                         ; Sectors left
639 .retry2:
640                 call maxtrans                   ; Enforce maximum transfer size
641                 movzx edi,bp                    ; Sectors we are about to read
642                 mov cx,retry_count
643 .retry:
645                 ; Form DAPA on stack
646                 push edx
647                 push eax
648                 push es
649                 push bx
650                 push di
651                 push word 16
652                 mov si,sp
653                 pushad
654                 mov ah,42h                      ; Extended Read
655                 push ds
656                 push ss
657                 pop ds
658                 call xint13
659                 pop ds
660                 popad
661                 lea sp,[si+16]                  ; Remove DAPA
662                 jc .error
663                 pop bp
664                 add eax,edi                     ; Advance sector pointer
665                 adc edx,0
666                 sub bp,di                       ; Sectors left
667                 shl di,SECTOR_SHIFT             ; 512-byte sectors
668                 add bx,di                       ; Advance buffer pointer
669                 and bp,bp
670                 jnz .loop
672                 popad
673                 ret
675 .error:
676                 ; Some systems seem to get "stuck" in an error state when
677                 ; using EBIOS.  Doesn't happen when using CBIOS, which is
678                 ; good, since some other systems get timeout failures
679                 ; waiting for the floppy disk to spin up.
681                 pushad                          ; Try resetting the device
682                 xor ax,ax
683                 mov dl,[DriveNumber]
684                 int 13h
685                 popad
686                 loop .retry                     ; CX-- and jump if not zero
688                 ;shr word [MaxTransfer],1       ; Reduce the transfer size
689                 ;jnz .retry2
691                 ; Total failure.  Try falling back to CBIOS.
692                 mov byte [getlinsec.jmp+1],(getlinsec_cbios-(getlinsec.jmp+2))
693                 ;mov byte [MaxTransfer],63      ; Max possibe CBIOS transfer
695                 pop bp
696                 ; ... fall through ...
699 ; getlinsec_cbios:
701 ; getlinsec implementation for legacy CBIOS
703 getlinsec_cbios:
704 .loop:
705                 push edx
706                 push eax
707                 push bp
708                 push bx
710                 movzx esi,word [bsSecPerTrack]
711                 movzx edi,word [bsHeads]
712                 ;
713                 ; Dividing by sectors to get (track,sector): we may have
714                 ; up to 2^18 tracks, so we need to use 32-bit arithmetric.
715                 ;
716                 div esi
717                 xor cx,cx
718                 xchg cx,dx              ; CX <- sector index (0-based)
719                                         ; EDX <- 0
720                 ; eax = track #
721                 div edi                 ; Convert track to head/cyl
723                 cmp eax,1023            ; Outside the CHS range?
724                 ja kaboom
726                 ;
727                 ; Now we have AX = cyl, DX = head, CX = sector (0-based),
728                 ; BP = sectors to transfer, SI = bsSecPerTrack,
729                 ; ES:BX = data target
730                 ;
732                 call maxtrans                   ; Enforce maximum transfer size
734                 ; Must not cross track boundaries, so BP <= SI-CX
735                 sub si,cx
736                 cmp bp,si
737                 jna .bp_ok
738                 mov bp,si
739 .bp_ok:
741                 shl ah,6                ; Because IBM was STOOPID
742                                         ; and thought 8 bits were enough
743                                         ; then thought 10 bits were enough...
744                 inc cx                  ; Sector numbers are 1-based, sigh
745                 or cl,ah
746                 mov ch,al
747                 mov dh,dl
748                 xchg ax,bp              ; Sector to transfer count
749                 mov ah,02h              ; Read sectors
750                 mov bp,retry_count
751 .retry:
752                 pushad
753                 call xint13
754                 popad
755                 jc .error
756 .resume:
757                 movzx ecx,al            ; ECX <- sectors transferred
758                 shl ax,SECTOR_SHIFT     ; Convert sectors in AL to bytes in AX
759                 pop bx
760                 add bx,ax
761                 pop bp
762                 pop eax
763                 pop edx
764                 add eax,ecx
765                 sub bp,cx
766                 jnz .loop
767                 popad
768                 ret
770 .error:
771                 dec bp
772                 jnz .retry
774                 xchg ax,bp              ; Sectors transferred <- 0
775                 shr word [MaxTransfer],1
776                 jnz .resume
777                 jmp kaboom
779 maxtrans:
780                 cmp bp,[MaxTransfer]
781                 jna .ok
782                 mov bp,[MaxTransfer]
783 .ok:            ret
786 ; Checksum error message
788 checksumerr_msg db ' Load error - ', 0  ; Boot failed appended
791 ; BIOS type string
793 cbios_name      db 'CHS', 0                     ; CHS/CBIOS
794 ebios_name      db 'EDD', 0                     ; EDD/EBIOS
797 ; Debug routine
799 %ifdef debug
800 safedumpregs:
801                 cmp word [Debug_Magic],0D00Dh
802                 jnz nc_return
803                 jmp dumpregs
804 %endif
806 rl_checkpt      equ $                           ; Must be <= 8000h
808 rl_checkpt_off  equ ($-$$)
809 %ifndef DEPEND
810  %if rl_checkpt_off > 3F6h                      ; Need one extent
811   %assign rl_checkpt_overflow rl_checkpt_off - 3F6h
812   %error Sector 1 overflow by rl_checkpt_overflow bytes
813  %endif
814 %endif
817 ; Extent pointers... each extent contains an 8-byte LBA and an 2-byte
818 ; sector count.  In most cases, we will only ever need a handful of
819 ; extents, but we have to assume a maximally fragmented system where each
820 ; extent contains only one sector.
822                 alignz 2
823 MaxInitDataSize equ 96 << 10
824 MaxLMA          equ TEXT_START+SECTOR_SIZE+MaxInitDataSize
825 SectorPtrs      zb 10*(MaxInitDataSize >> SECTOR_SHIFT)
826 SectorPtrsEnd   equ $
828 ; ----------------------------------------------------------------------------
829 ;  End of code and data that have to be in the first sector
830 ; ----------------------------------------------------------------------------
832                 section .text16
833 all_read:
834                 ; We enter here with both DS and ES scrambled...
835                 xor ax,ax
836                 mov ds,ax
837                 mov es,ax
839 ; Let the user (and programmer!) know we got this far.  This used to be
840 ; in Sector 1, but makes a lot more sense here.
842                 mov si,copyright_str
843                 call writestr_early
847 ; Insane hack to expand the DOS superblock to dwords
849 expand_super:
850                 xor eax,eax
851                 mov si,superblock
852                 mov di,SuperInfo
853                 mov cx,superinfo_size
854 .loop:
855                 lodsw
856                 dec si
857                 stosd                           ; Store expanded word
858                 xor ah,ah
859                 stosd                           ; Store expanded byte
860                 loop .loop
864 ; Common initialization code
866 %include "init.inc"
867                 
868                 pushad
869                 mov eax,ROOT_FS_OPS
870                 movzx dx,byte [DriveNumber]
871                 ; DH = 0: we are boot from disk not CDROM
872                 mov ecx,[Hidden]
873                 mov ebx,[Hidden+4]
874                 mov si,[bsHeads]
875                 mov di,[bsSecPerTrack]
876                 movzx ebp,word [MaxTransfer]
877                 pm_call fs_init
878                 popad
880                 section .bss16
881 SuperInfo       resq 16                 ; The first 16 bytes expanded 8 times
883                 section .text16