source: bootcd/isolinux/syslinux-6.03/core/diskstart.inc @ dd1be7c

Last change on this file since dd1be7c was e16e8f2, checked in by Edwin Eefting <edwin@datux.nl>, 3 years ago

bootstuff

  • Property mode set to 100644
File size: 11.7 KB
Line 
1; -----------------------------------------------------------------------
2;
3;   Copyright 1994-2009 H. Peter Anvin - All Rights Reserved
4;   Copyright 2009-2011 Intel Corporation; author: H. Peter Anvin
5;
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.
11;
12; -----------------------------------------------------------------------
13
14;
15; diskstart.inc
16;
17; Common early-bootstrap code for harddisk-based Syslinux derivatives.
18;
19
20Sect1Ptr0_VAL   equ 0xdeadbeef
21Sect1Ptr1_VAL   equ 0xfeedface
22
23%include "diskboot.inc"
24
25; ===========================================================================
26;  Padding after the (minimum) 512-byte boot sector so that the rest of
27;  the file has aligned sectors, even if they are larger than 512 bytes.
28; ===========================================================================
29
30                section .init
31align_pad       zb 512
32
33; ===========================================================================
34;  Start of LDLINUX.SYS
35; ===========================================================================
36
37LDLINUX_SYS     equ ($-$$)+TEXT_START
38ldlinux_sys:
39
40early_banner    db CR, LF, MY_NAME, ' ', VERSION_STR, ' ', 0
41                db CR, LF, 1Ah  ; EOF if we "type" this in DOS
42
43                alignz 8
44ldlinux_magic   dd LDLINUX_MAGIC
45                dd LDLINUX_MAGIC^HEXDATE
46
47;
48; This area is patched by the installer.  It is found by looking for
49; LDLINUX_MAGIC, plus 8 bytes.
50;
51SUBVOL_MAX      equ 256
52CURRENTDIR_MAX  equ FILENAME_MAX
53
54patch_area:
55DataSectors     dw 0            ; Number of sectors (not including bootsec)
56ADVSectors      dw 0            ; Additional sectors for ADVs
57LDLDwords       dd 0            ; Total dwords starting at ldlinux_sys,
58CheckSum        dd 0            ; Checksum starting at ldlinux_sys
59                                ; value = LDLINUX_MAGIC - [sum of dwords]
60MaxTransfer     dw 127          ; Max sectors to transfer
61EPAPtr          dw EPA - LDLINUX_SYS    ; Pointer to the extended patch area
62
63;
64; Extended patch area -- this is in .data16 so it doesn't occupy space in
65; the first sector.  Use this structure for anything that isn't used by
66; the first sector itself.
67;
68                section .data16
69                alignz 2
70EPA:
71ADVSecPtr       dw ADVSec0 - LDLINUX_SYS
72CurrentDirPtr   dw CurrentDirName-LDLINUX_SYS   ; Current directory name string
73CurrentDirLen   dw CURRENTDIR_MAX
74SubvolPtr       dw SubvolName-LDLINUX_SYS
75SubvolLen       dw SUBVOL_MAX
76SecPtrOffset    dw SectorPtrs-LDLINUX_SYS
77SecPtrCnt       dw (SectorPtrsEnd - SectorPtrs)/10
78
79;
80; Boot sector patch pointers
81;
82Sect1Ptr0Ptr    dw Sect1Ptr0 - bootsec          ; Pointers to Sector 1 location
83Sect1Ptr1Ptr    dw Sect1Ptr1 - bootsec
84RAIDPatchPtr    dw kaboom.again - bootsec       ; Patch to INT 18h in RAID mode
85
86;
87; Pointer to the Syslinux banner
88;
89BannerPtr       dw syslinux_banner - LDLINUX_SYS
90
91;
92; Base directory name and subvolume, if applicable.
93;
94%define HAVE_CURRENTDIRNAME
95                global CurrentDirName:data hidden, SubvolName:data hidden
96CurrentDirName  times CURRENTDIR_MAX db 0
97SubvolName      times SUBVOL_MAX db 0
98
99                section .init
100ldlinux_ent:
101;
102; Note that some BIOSes are buggy and run the boot sector at 07C0:0000
103; instead of 0000:7C00 and the like.  We don't want to add anything
104; more to the boot sector, so it is written to not assume a fixed
105; value in CS, but we don't want to deal with that anymore from now
106; on.
107;
108                jmp 0:.next     ; Normalize CS:IP
109.next:          sti             ; In case of broken INT 13h BIOSes
110
111;
112; Tell the user we got this far
113;
114                mov si,early_banner
115                call writestr_early
116
117;
118; Checksum data thus far
119;
120                mov si,ldlinux_sys
121                mov cx,[bsBytesPerSec]
122                shr cx,2
123                mov edx,-LDLINUX_MAGIC
124.checksum:
125                lodsd
126                add edx,eax
127                loop .checksum
128                mov [CheckSum],edx              ; Save intermediate result
129                movzx ebx,si                    ; Start of the next sector
130
131;
132; Tell the user if we're using EBIOS or CBIOS
133;
134print_bios:
135                mov si,cbios_name
136                cmp byte [getonesec.jmp+1],(getonesec_ebios-(getonesec.jmp+2))
137                jne .cbios
138                mov si,ebios_name
139                mov byte [getlinsec.jmp+1],(getlinsec_ebios-(getlinsec.jmp+2))
140.cbios:
141                mov [BIOSName],si
142                call writestr_early
143
144                section .earlybss
145                global BIOSName
146                alignb 2
147%define HAVE_BIOSNAME 1
148BIOSName        resw 1
149
150                section .init
151;
152; Now we read the rest of LDLINUX.SYS.
153;
154load_rest:
155                push bx                         ; LSW of load address
156
157                lea esi,[SectorPtrs]
158                mov cx,[DataSectors]
159                dec cx                          ; Minus this sector
160
161.get_chunk:
162                jcxz .done
163                mov eax,[si]
164                mov edx,[si+4]
165                movzx ebp,word [si+8]
166                sub cx,bp
167                push ebx
168                shr ebx,4                       ; Convert to a segment
169                mov es,bx
170                xor bx,bx
171                call getlinsec
172                pop ebx
173                imul bp,[bsBytesPerSec]         ; Will be < 64K
174                add ebx,ebp
175                add si,10
176                jmp .get_chunk
177
178.done:
179
180;
181; All loaded up, verify that we got what we needed.
182; Note: the checksum field is embedded in the checksum region, so
183; by the time we get to the end it should all cancel out.
184;
185verify_checksum:
186                pop si                          ; LSW of load address
187                movzx eax,word [bsBytesPerSec]
188                shr ax,2
189                mov ecx,[LDLDwords]             ; Total dwords
190                sub ecx,eax                     ; ... minus one sector
191                mov eax,[CheckSum]
192.checksum:
193                add eax,[si]
194                add si,4
195                jnz .nowrap
196                ; Handle segment wrap
197                mov dx,ds
198                add dx,1000h
199                mov ds,dx
200.nowrap:
201                dec ecx
202                jnz .checksum
203
204                mov ds,cx
205
206                and eax,eax                     ; Should be zero
207                jz all_read                     ; We're cool, go for it!
208
209;
210; Uh-oh, something went bad...
211;
212                mov si,checksumerr_msg
213                call writestr_early
214                jmp kaboom
215
216;
217; -----------------------------------------------------------------------------
218; Subroutines that have to be in the first sector
219; -----------------------------------------------------------------------------
220
221
222
223;
224; getlinsec: load a sequence of BP floppy sector given by the linear sector
225;            number in EAX into the buffer at ES:BX.  We try to optimize
226;            by loading up to a whole track at a time, but the user
227;            is responsible for not crossing a 64K boundary.
228;            (Yes, BP is weird for a count, but it was available...)
229;
230;            On return, BX points to the first byte after the transferred
231;            block.
232;
233;            This routine assumes CS == DS.
234;
235                global getlinsec:function hidden
236getlinsec:
237                pushad
238                add eax,[Hidden]                ; Add partition offset
239                adc edx,[Hidden+4]
240.jmp:           jmp strict short getlinsec_cbios
241
242;
243; getlinsec_ebios:
244;
245; getlinsec implementation for EBIOS (EDD)
246;
247getlinsec_ebios:
248.loop:
249                push bp                         ; Sectors left
250.retry2:
251                call maxtrans                   ; Enforce maximum transfer size
252                movzx edi,bp                    ; Sectors we are about to read
253                mov cx,retry_count
254.retry:
255
256                ; Form DAPA on stack
257                push edx
258                push eax
259                push es
260                push bx
261                push di
262                push word 16
263                mov si,sp
264                pushad
265                mov ah,42h                      ; Extended Read
266                push ds
267                push ss
268                pop ds
269                call xint13
270                pop ds
271                popad
272                lea sp,[si+16]                  ; Remove DAPA
273                jc .error
274                pop bp
275                add eax,edi                     ; Advance sector pointer
276                adc edx,0
277                sub bp,di                       ; Sectors left
278                imul di,[bsBytesPerSec]
279                add bx,di                       ; Advance buffer pointer
280                and bp,bp
281                jnz .loop
282
283                popad
284                ret
285
286.error:
287                ; Some systems seem to get "stuck" in an error state when
288                ; using EBIOS.  Doesn't happen when using CBIOS, which is
289                ; good, since some other systems get timeout failures
290                ; waiting for the floppy disk to spin up.
291
292                pushad                          ; Try resetting the device
293                xor ax,ax
294                call xint13
295                popad
296                loop .retry                     ; CX-- and jump if not zero
297
298                ;shr word [MaxTransfer],1       ; Reduce the transfer size
299                ;jnz .retry2
300
301                ; Total failure.  Try falling back to CBIOS.
302                mov byte [getlinsec.jmp+1],(getlinsec_cbios-(getlinsec.jmp+2))
303                ;mov byte [MaxTransfer],63      ; Max possibe CBIOS transfer
304
305                pop bp
306                ; ... fall through ...
307
308;
309; getlinsec_cbios:
310;
311; getlinsec implementation for legacy CBIOS
312;
313getlinsec_cbios:
314.loop:
315                push edx
316                push eax
317                push bp
318                push bx
319
320                movzx esi,word [bsSecPerTrack]
321                movzx edi,word [bsHeads]
322                ;
323                ; Dividing by sectors to get (track,sector): we may have
324                ; up to 2^18 tracks, so we need to use 32-bit arithmetric.
325                ;
326                div esi
327                xor cx,cx
328                xchg cx,dx              ; CX <- sector index (0-based)
329                                        ; EDX <- 0
330                ; eax = track #
331                div edi                 ; Convert track to head/cyl
332
333                cmp eax,1023            ; Outside the CHS range?
334                ja kaboom
335
336                ;
337                ; Now we have AX = cyl, DX = head, CX = sector (0-based),
338                ; BP = sectors to transfer, SI = bsSecPerTrack,
339                ; ES:BX = data target
340                ;
341
342                call maxtrans                   ; Enforce maximum transfer size
343
344                ; Must not cross track boundaries, so BP <= SI-CX
345                sub si,cx
346                cmp bp,si
347                jna .bp_ok
348                mov bp,si
349.bp_ok:
350
351                shl ah,6                ; Because IBM was STOOPID
352                                        ; and thought 8 bits were enough
353                                        ; then thought 10 bits were enough...
354                inc cx                  ; Sector numbers are 1-based, sigh
355                or cl,ah
356                mov ch,al
357                mov dh,dl
358                xchg ax,bp              ; Sector to transfer count
359                mov ah,02h              ; Read sectors
360                mov bp,retry_count
361.retry:
362                pushad
363                call xint13
364                popad
365                jc .error
366.resume:
367                movzx ecx,al            ; ECX <- sectors transferred
368                imul ax,[bsBytesPerSec] ; Convert sectors in AL to bytes in AX
369                pop bx
370                add bx,ax
371                pop bp
372                pop eax
373                pop edx
374                add eax,ecx
375                sub bp,cx
376                jnz .loop
377                popad
378                ret
379
380.error:
381                dec bp
382                jnz .retry
383
384                xchg ax,bp              ; Sectors transferred <- 0
385                shr word [MaxTransfer],1
386                jnz .resume
387                jmp kaboom
388
389maxtrans:
390                cmp bp,[MaxTransfer]
391                jna .ok
392                mov bp,[MaxTransfer]
393.ok:            ret
394
395;
396;
397; writestr_early: write a null-terminated string to the console
398;           This assumes we're on page 0.  This is only used for early
399;           messages, so it should be OK.
400;
401writestr_early:
402                pushad
403.loop:          lodsb
404                and al,al
405                jz .return
406                mov ah,0Eh              ; Write to screen as TTY
407                mov bx,0007h            ; Attribute
408                int 10h
409                jmp short .loop
410.return:        popad
411                ret
412
413;
414; Checksum error message
415;
416checksumerr_msg db ' Load error - ', 0  ; Boot failed appended
417
418;
419; BIOS type string
420;
421cbios_name      db 'CHS', 0                     ; CHS/CBIOS
422ebios_name      db 'EDD', 0                     ; EDD/EBIOS
423
424;
425; Debug routine
426;
427%ifdef debug
428safedumpregs:
429                cmp word [Debug_Magic],0D00Dh
430                jnz nc_return
431                jmp dumpregs
432%endif
433
434rl_checkpt      equ $                           ; Must be <= 8000h
435
436rl_checkpt_off  equ $-ldlinux_sys
437%ifndef DEPEND
438 %if rl_checkpt_off > 512-10                    ; Need minimum one extent
439  %assign rl_checkpt_overflow rl_checkpt_off - (512-10)
440  %error Sector 1 overflow by rl_checkpt_overflow bytes
441 %endif
442%endif
443
444;
445; Extent pointers... each extent contains an 8-byte LBA and an 2-byte
446; sector count.  In most cases, we will only ever need a handful of
447; extents, but we have to assume a maximally fragmented system where each
448; extent contains only one sector.
449;
450                alignz 2
451MaxInitDataSize equ 96 << 10
452MaxLMA          equ LDLINUX_SYS+MaxInitDataSize
453SectorPtrs      zb 10*(MaxInitDataSize >> MIN_SECTOR_SHIFT)
454SectorPtrsEnd   equ $
455
456; ----------------------------------------------------------------------------
457;  End of code and data that have to be in the first sector
458; ----------------------------------------------------------------------------
459
460                section .text16
461all_read:
462                ; We enter here with ES scrambled...
463                xor ax,ax
464                mov es,ax
465;
466; Let the user (and programmer!) know we got this far.  This used to be
467; in Sector 1, but makes a lot more sense here.
468;
469                mov si,late_banner
470                call writestr_early
471
472                mov si,copyright_str
473                call writestr_early
474
475
476;
477; Insane hack to expand the DOS superblock to dwords
478;
479expand_super:
480                xor eax,eax
481                mov si,superblock
482                mov di,SuperInfo
483                mov cx,superinfo_size
484.loop:
485                lodsw
486                dec si
487                stosd                           ; Store expanded word
488                xor ah,ah
489                stosd                           ; Store expanded byte
490                loop .loop
491
492
493;
494; Common initialization code
495;
496%include "init.inc"
497               
498                pushad
499                mov eax,ROOT_FS_OPS
500                movzx dx,byte [DriveNumber]
501                ; DH = 0: we are boot from disk not CDROM
502                mov ecx,[Hidden]
503                mov ebx,[Hidden+4]
504                mov si,[bsHeads]
505                mov di,[bsSecPerTrack]
506                movzx ebp,word [MaxTransfer]
507                pm_call pm_fs_init
508                pm_call load_env32
509                popad
510
511                section .bss16
512SuperInfo       resq 16                 ; The first 16 bytes expanded 8 times
513
514;
515; Banner information not needed in sector 1
516;
517                section .data16
518                global syslinux_banner
519syslinux_banner db CR, LF, MY_NAME, ' ', VERSION_STR
520late_banner     db ' ', DATE_STR, 0
521
522                section .text16
Note: See TracBrowser for help on using the repository browser.