; Common early-bootstrap code for harddisk-based Syslinux derivatives.
;
- ; Expanded superblock
section .earlybss
- alignb 8
-SuperInfo resq 16 ; The first 16 bytes expanded 8 times
-DriveNumber resb 1
+ alignb 16
+PartInfo: ; Partition table info
+.mbr: resb 16 ; MBR partition info
+.gptlen: resd 1
+.gpt: resb 92
+FloppyTable resb 16 ; Floppy info table (must follow PartInfo)
section .init
;
; "close" to the initial stack pointer offset, in order to
; reduce the code size...
;
-StackBuf equ STACK_TOP-44-32 ; Start the stack here (grow down - 4K)
-PartInfo equ StackBuf ; Saved partition table entry
-FloppyTable equ PartInfo+16 ; Floppy info table (must follow PartInfo)
-OrigFDCTabPtr equ StackBuf-8 ; The 2nd high dword on the stack
-OrigESDI equ StackBuf-4 ; The high dword on the stack
-StackHome equ OrigFDCTabPtr ; The start of the canonical stack
+StackBuf equ STACK_TOP-44 ; Start the stack here (grow down - 4K)
+Hidden equ StackBuf-20 ; Partition offset
+OrigFDCTabPtr equ StackBuf-12 ; The 2nd high dword on the stack
+OrigESDI equ StackBuf-8 ; The high dword on the stack
+DriveNumber equ StackBuf-4 ; Drive number
+StackHome equ Hidden ; The start of the canonical stack
;
; Primary entry point. Tempting as though it may be, we can't put the
global SecPerClust
SecPerClust equ bxSecPerClust
+
;
; Note we don't check the constraints above now; we did that at install
; time (we hope!)
;
; Set up the stack
;
- xor ax,ax
- mov ss,ax
- mov sp,StackBuf ; Just below BSS
+ xor cx,cx
+ mov ss,cx
+ mov sp,StackBuf-2 ; Just below BSS (-2 for alignment)
+ push dx ; Save drive number (in DL)
push es ; Save initial ES:DI -> $PnP pointer
push di
- mov es,ax
+ mov es,cx
+
;
-; DS:SI may contain a partition table entry. Preserve it for us.
+; DS:SI may contain a partition table entry and possibly a GPT entry.
+; Preserve it for us. This saves 92 bytes of the GPT entry, which is
+; currently the maximum we care about.
;
- mov cx,8 ; Save partition info
+ mov cl,(16+4+92)/2 ; Save partition info
mov di,PartInfo
- rep movsw
+ rep movsw ; This puts CX back to zero
- mov ds,ax ; Now we can initialize DS...
+ mov ds,cx ; Now we can initialize DS...
;
; Now sautee the BIOS floppy info block to that it will support decent-
; Save the old fdctab even if hard disk so the stack layout
; is the same. The instructions above do not change the flags
- mov [DriveNumber],dl ; Save drive number in DL
and dl,dl ; If floppy disk (00-7F), assume no
; partition table
js harddisk
floppy:
+ xor ax,ax
mov cl,6 ; 12 bytes (CX == 0)
; es:di -> FloppyTable already
; This should be safe to do now, interrupts are off...
mov [bx+2],ax ; Segment 0
fs rep movsw ; Faster to move words
mov cl,[bsSecPerTrack] ; Patch the sector count
- mov [di-8],cl
- ; AX == 0 here
+ mov [di-112+8],cl
int 13h ; Some BIOSes need this
+ push cx ; Partition offset == 0
+ push cx
+ push cx
+ push cx
jmp short not_harddisk
;
; The drive number and possibly partition information was passed to us
; by the BIOS or previous boot loader (MBR). Current "best practice" is to
; trust that rather than what the superblock contains.
;
-; Would it be better to zero out bsHidden if we don't have a partition table?
-;
; Note: di points to beyond the end of PartInfo
;
harddisk:
- test byte [di-16],7Fh ; Sanity check: "active flag" should
+ test byte [di-112],7Fh ; Sanity check: "active flag" should
jnz no_partition ; be 00 or 80
- mov eax,[di-8] ; Partition offset (dword)
- mov [bsHidden],eax
+ cmp eax,'!GPT' ; !GPT signature?
+ jne .not_gpt
+ push dword [di-112+20+36]
+ push dword [di-112+20+32]
+ jmp .gotoffs
+.not_gpt:
+ push cx ; Upper half partition offset == 0
+ push cx
+ push dword [di-112+8] ; Partition offset (dword)
+.gotoffs:
no_partition:
;
; Get disk drive parameters (don't trust the superblock.) Don't do this for
;
; We have EDD support...
;
- mov byte [getlinsec.jmp+1],(getlinsec_ebios-(getlinsec.jmp+2))
+ mov byte [getonesec.jmp+1],(getonesec_ebios-(getonesec.jmp+2))
.noedd:
;
jne kaboom
; Go for it...
- jmp ldlinux_ent
+ jmp 0:ldlinux_ent
-;
-; getonesec: get one disk sector
-;
-getonesec:
- mov bp,1 ; One sector
- ; Fall through
;
-; getlinsec: load a sequence of BP floppy sector given by the linear sector
-; number in EAX into the buffer at ES:BX. We try to optimize
-; by loading up to a whole track at a time, but the user
-; is responsible for not crossing a 64K boundary.
-; (Yes, BP is weird for a count, but it was available...)
+; getonesec: load a single disk linear sector EDX:EAX into the buffer
+; at ES:BX.
;
-; On return, BX points to the first byte after the transferred
-; block.
-;
-; This routine assumes CS == DS, and trashes most registers.
+; This routine assumes CS == DS == SS, and trashes most registers.
;
; Stylistic note: use "xchg" instead of "mov" when the source is a register
; that is dead from that point; this saves space. However, please keep
; the order to dst,src to keep things sane.
;
- global getlinsec
-getlinsec:
- add eax,[bsHidden] ; Add partition offset
- xor edx,edx ; Zero-extend LBA (eventually allow 64 bits)
-
-.jmp: jmp strict short getlinsec_cbios
+getonesec:
+ xor edx,edx ; Assume 32-bit partition size
+ add eax,[Hidden] ; Add partition offset
+ adc edx,[Hidden+4]
+ mov cx,retry_count
+.jmp: jmp strict short getonesec_cbios
;
-; getlinsec_ebios:
+; getonesec_ebios:
;
-; getlinsec implementation for EBIOS (EDD)
+; getonesec implementation for EBIOS (EDD)
;
-getlinsec_ebios:
-.loop:
- push bp ; Sectors left
-.retry2:
- call maxtrans ; Enforce maximum transfer size
- movzx edi,bp ; Sectors we are about to read
- mov cx,retry_count
+getonesec_ebios:
.retry:
-
; Form DAPA on stack
push edx
push eax
push es
push bx
- push di
+ push word 1
push word 16
mov si,sp
- pushad
- mov dl,[DriveNumber]
- push ds
- push ss
- pop ds ; DS <- SS
mov ah,42h ; Extended Read
- int 13h
- pop ds
- popad
+ call xint13
lea sp,[si+16] ; Remove DAPA
jc .error
- pop bp
- add eax,edi ; Advance sector pointer
- sub bp,di ; Sectors left
- shl di,SECTOR_SHIFT ; 512-byte sectors
- add bx,di ; Advance buffer pointer
- and bp,bp
- jnz .loop
-
ret
.error:
pushad ; Try resetting the device
xor ax,ax
- mov dl,[DriveNumber]
int 13h
popad
loop .retry ; CX-- and jump if not zero
- ;shr word [MaxTransfer],1 ; Reduce the transfer size
- ;jnz .retry2
-
; Total failure. Try falling back to CBIOS.
- mov byte [getlinsec.jmp+1],(getlinsec_cbios-(getlinsec.jmp+2))
- ;mov byte [MaxTransfer],63 ; Max possibe CBIOS transfer
-
- pop bp
- ; ... fall through ...
+ mov byte [getonesec.jmp+1],(getonesec_cbios-(getonesec.jmp+2))
;
-; getlinsec_cbios:
+; getonesec_cbios:
;
; getlinsec implementation for legacy CBIOS
;
-getlinsec_cbios:
-.loop:
- push edx
- push eax
- push bp
- push bx
+getonesec_cbios:
+.retry:
+ pushad
movzx esi,word [bsSecPerTrack]
movzx edi,word [bsHeads]
;
; Now we have AX = cyl, DX = head, CX = sector (0-based),
- ; BP = sectors to transfer, SI = bsSecPerTrack,
- ; ES:BX = data target
+ ; SI = bsSecPerTrack, ES:BX = data target
;
-
- call maxtrans ; Enforce maximum transfer size
-
- ; Must not cross track boundaries, so BP <= SI-CX
- sub si,cx
- cmp bp,si
- jna .bp_ok
- mov bp,si
-.bp_ok:
-
shl ah,6 ; Because IBM was STOOPID
; and thought 8 bits were enough
; then thought 10 bits were enough...
or cl,ah
mov ch,al
mov dh,dl
- mov dl,[DriveNumber]
- xchg ax,bp ; Sector to transfer count
- mov ah,02h ; Read sectors
- mov bp,retry_count
-.retry:
- pushad
- int 13h
- popad
+ mov ax,0201h ; Read one sector
+ call xint13
jc .error
-.resume:
- movzx ecx,al ; ECX <- sectors transferred
- shl ax,SECTOR_SHIFT ; Convert sectors in AL to bytes in AX
- pop bx
- add bx,ax
- pop bp
- pop eax
- pop edx
- add eax,ecx
- sub bp,cx
- jnz .loop
ret
.error:
- dec bp
- jnz .retry
-
- xchg ax,bp ; Sectors transferred <- 0
- shr word [MaxTransfer],1
- jnz .resume
+ popad
+ loop .retry
; Fall through to disk_error
;
pop dword [fdctab] ; Restore FDC table
.patch: ; When we have full code, intercept here
mov si,bailmsg
+ call writestr_early
+
+ xor ax,ax
+.again: int 16h ; Wait for keypress
+ ; NB: replaced by int 18h if
+ ; chosen at install time..
+ int 19h ; And try once more to boot...
+.norge: jmp short .norge ; If int 19h returned; this is the end
- ; Write error message, this assumes screen page 0
+;
+;
+; writestr_early: write a null-terminated string to the console
+; This assumes we're on page 0. This is only used for early
+; messages, so it should be OK.
+;
+writestr_early:
+ pushad
.loop: lodsb
and al,al
- jz .done
+ jz .return
mov ah,0Eh ; Write to screen as TTY
mov bx,0007h ; Attribute
int 10h
jmp short .loop
-.done:
- cbw ; AH <- 0
-.again: int 16h ; Wait for keypress
- ; NB: replaced by int 18h if
- ; chosen at install time..
- int 19h ; And try once more to boot...
-.norge: jmp short .norge ; If int 19h returned; this is the end
+.return: popad
+ ret
;
-; Truncate BP to MaxTransfer
+; INT 13h wrapper function
;
-maxtrans:
- cmp bp,[MaxTransfer]
- jna .ok
- mov bp,[MaxTransfer]
-.ok: ret
+xint13:
+ mov dl,[DriveNumber]
+ pushad
+ int 13h
+ popad
+ ret
;
; Error message on failure
;
bailmsg: db 'Boot error', 0Dh, 0Ah, 0
- ; This fails if the boot sector overflows
- zb 1F8h-($-$$)
-
+ ; This fails if the boot sector overflowsg
+ zb 1FAh-($-$$)
FirstSector dd 0xDEADBEEF ; Location of sector 1
-MaxTransfer dw 0x007F ; Max transfer size
; This field will be filled in 0xAA55 by the installer, but we abuse it
; to house a pointer to the INT 16h instruction at
LDLDwords dd 0 ; Total dwords starting at ldlinux_sys,
CheckSum dd 0 ; Checksum starting at ldlinux_sys
; value = LDLINUX_MAGIC - [sum of dwords]
+MaxTransfer dw 127 ; Max sectors to transfer
CurrentDirPtr dw CurrentDirName-LDLINUX_SYS ; Current directory name string
CurrentDirLen dw CURRENTDIR_MAX
SubvolPtr dw SubvolName-LDLINUX_SYS
; value in CS, but we don't want to deal with that anymore from now
; on.
;
- jmp 0:.next
-.next:
sti ; In case of broken INT 13h BIOSes
;
call writestr_early
;
+; Checksum data thus far
+;
+ mov si,ldlinux_sys
+ mov cx,SECTOR_SIZE >> 2
+ mov edx,-LDLINUX_MAGIC
+.checksum:
+ lodsd
+ add edx,eax
+ loop .checksum
+ mov [CheckSum],edx ; Save intermediate result
+
+;
; Tell the user if we're using EBIOS or CBIOS
;
print_bios:
mov si,cbios_name
- cmp byte [getlinsec.jmp+1],(getlinsec_ebios-(getlinsec.jmp+2))
+ cmp byte [getonesec.jmp+1],(getonesec_ebios-(getonesec.jmp+2))
jne .cbios
mov si,ebios_name
+ mov byte [getlinsec.jmp+1],(getlinsec_ebios-(getlinsec.jmp+2))
.cbios:
mov [BIOSName],si
call writestr_early
section .init
;
-; Now we read the rest of LDLINUX.SYS. Don't bother loading the first
-; sector again, though.
+; Now we read the rest of LDLINUX.SYS.
;
load_rest:
lea esi,[SectorPtrs]
inc bp
dec cx
jz .chunk_ready
- cmp ebx,esi ; Pointer we don't have yet?
+ cmp esi,ebx ; Pointer we don't have yet?
jae .chunk_ready
inc edx ; Next linear sector
cmp [si],edx ; Does it match
mov es,bx
xor bx,bx
xor edx,edx ; Zero-extend LBA
- call getlinsecsr
+ call getlinsec
pop es
pop ebx
shl ebp,SECTOR_SHIFT
; by the time we get to the end it should all cancel out.
;
verify_checksum:
- mov si,ldlinux_sys
+ mov si,ldlinux_sys + SECTOR_SIZE
mov ecx,[LDLDwords]
- mov eax,-LDLINUX_MAGIC
+ sub ecx,SECTOR_SIZE >> 2
+ mov eax,[CheckSum]
push ds
.checksum:
add eax,[si]
; Subroutines that have to be in the first sector
; -----------------------------------------------------------------------------
+
+
;
+; getlinsec: load a sequence of BP floppy sector given by the linear sector
+; number in EAX into the buffer at ES:BX. We try to optimize
+; by loading up to a whole track at a time, but the user
+; is responsible for not crossing a 64K boundary.
+; (Yes, BP is weird for a count, but it was available...)
;
-; writestr_early: write a null-terminated string to the console
-; This assumes we're on page 0. This is only used for early
-; messages, so it should be OK.
+; On return, BX points to the first byte after the transferred
+; block.
;
-writestr_early:
+; This routine assumes CS == DS.
+;
+ global getlinsec
+getlinsec:
pushad
-.loop: lodsb
- and al,al
- jz .return
- mov ah,0Eh ; Write to screen as TTY
- mov bx,0007h ; Attribute
- int 10h
- jmp short .loop
-.return: popad
- ret
+ xor edx,edx ; For now only 32-bit internal
+ add eax,[Hidden] ; Add partition offset
+ adc edx,[Hidden+4]
+.jmp: jmp strict short getlinsec_cbios
+;
+; getlinsec_ebios:
+;
+; getlinsec implementation for EBIOS (EDD)
+;
+getlinsec_ebios:
+.loop:
+ push bp ; Sectors left
+.retry2:
+ call maxtrans ; Enforce maximum transfer size
+ movzx edi,bp ; Sectors we are about to read
+ mov cx,retry_count
+.retry:
+
+ ; Form DAPA on stack
+ push edx
+ push eax
+ push es
+ push bx
+ push di
+ push word 16
+ mov si,sp
+ mov ah,42h ; Extended Read
+ push ds
+ push ss
+ pop ds
+ call xint13
+ pop ds
+ lea sp,[si+16] ; Remove DAPA
+ jc .error
+ pop bp
+ add eax,edi ; Advance sector pointer
+ adc edx,0
+ sub bp,di ; Sectors left
+ shl di,SECTOR_SHIFT ; 512-byte sectors
+ add bx,di ; Advance buffer pointer
+ and bp,bp
+ jnz .loop
+
+ popad
+ ret
+
+.error:
+ ; Some systems seem to get "stuck" in an error state when
+ ; using EBIOS. Doesn't happen when using CBIOS, which is
+ ; good, since some other systems get timeout failures
+ ; waiting for the floppy disk to spin up.
+
+ pushad ; Try resetting the device
+ xor ax,ax
+ mov dl,[DriveNumber]
+ int 13h
+ popad
+ loop .retry ; CX-- and jump if not zero
+
+ ;shr word [MaxTransfer],1 ; Reduce the transfer size
+ ;jnz .retry2
+
+ ; Total failure. Try falling back to CBIOS.
+ mov byte [getlinsec.jmp+1],(getlinsec_cbios-(getlinsec.jmp+2))
+ ;mov byte [MaxTransfer],63 ; Max possibe CBIOS transfer
+
+ pop bp
+ ; ... fall through ...
;
-; getlinsecsr: save registers, call getlinsec, restore registers
-; Save/restore the flags, too, especially IF.
+; getlinsec_cbios:
;
-getlinsecsr:
- pushfd
- pushad
- call getlinsec
+; getlinsec implementation for legacy CBIOS
+;
+getlinsec_cbios:
+.loop:
+ push edx
+ push eax
+ push bp
+ push bx
+
+ movzx esi,word [bsSecPerTrack]
+ movzx edi,word [bsHeads]
+ ;
+ ; Dividing by sectors to get (track,sector): we may have
+ ; up to 2^18 tracks, so we need to use 32-bit arithmetric.
+ ;
+ div esi
+ xor cx,cx
+ xchg cx,dx ; CX <- sector index (0-based)
+ ; EDX <- 0
+ ; eax = track #
+ div edi ; Convert track to head/cyl
+
+ ; We should test this, but it doesn't fit...
+ ; cmp eax,1023
+ ; ja .error
+
+ ;
+ ; Now we have AX = cyl, DX = head, CX = sector (0-based),
+ ; BP = sectors to transfer, SI = bsSecPerTrack,
+ ; ES:BX = data target
+ ;
+
+ call maxtrans ; Enforce maximum transfer size
+
+ ; Must not cross track boundaries, so BP <= SI-CX
+ sub si,cx
+ cmp bp,si
+ jna .bp_ok
+ mov bp,si
+.bp_ok:
+
+ shl ah,6 ; Because IBM was STOOPID
+ ; and thought 8 bits were enough
+ ; then thought 10 bits were enough...
+ inc cx ; Sector numbers are 1-based, sigh
+ or cl,ah
+ mov ch,al
+ mov dh,dl
+ xchg ax,bp ; Sector to transfer count
+ mov ah,02h ; Read sectors
+ mov bp,retry_count
+.retry:
+ call xint13
+ jc .error
+.resume:
+ movzx ecx,al ; ECX <- sectors transferred
+ shl ax,SECTOR_SHIFT ; Convert sectors in AL to bytes in AX
+ pop bx
+ add bx,ax
+ pop bp
+ pop eax
+ pop edx
+ add eax,ecx
+ sub bp,cx
+ jnz .loop
popad
- popfd
ret
+.error:
+ dec bp
+ jnz .retry
+
+ xchg ax,bp ; Sectors transferred <- 0
+ shr word [MaxTransfer],1
+ jnz .resume
+ jmp kaboom
+
+maxtrans:
+ cmp bp,[MaxTransfer]
+ jna .ok
+ mov bp,[MaxTransfer]
+.ok: ret
+
;
; Checksum error message
;
mov eax,ROOT_FS_OPS
movzx dx,byte [DriveNumber]
; DH = 0: we are boot from disk not CDROM
- mov ecx,[bsHidden]
- ; Reserved for upper 32 bits of partition offset...
- ; mov ebx,[bsHidden+4]
- xor ebx,ebx
+ mov ecx,[Hidden]
+ mov ebx,[Hidden+4]
mov si,[bsHeads]
mov di,[bsSecPerTrack]
movzx ebp,word [MaxTransfer]
pm_call fs_init
popad
+
+ section .bss16
+SuperInfo resq 16 ; The first 16 bytes expanded 8 times
+
+ section .text16