0.12 的bootsect.s的问题

发布于 2022-10-15 08:09:28 字数 28266 浏览 20 评论 0

go:        mov        ax,cs  
        mov        dx,#0xfef4        
        mov        ds,ax
        mov        es,ax
        push         ax   
        mov        ss,ax                ! put stack at 0x9ff00 - 12.                        
        mov        sp,dx !设置堆栈指针为0xfef4
push ax这一句有什么意义? 前面的代码都没有设置ss的值。

以下是完整的bootsect代码
1 !
  2 ! SYS_SIZE is the number of clicks (16 bytes) to be loaded.
  3 ! 0x3000 is 0x30000 bytes = 196kB, more than enough for current
  4 ! versions of linux
  5 !
  6 #include <linux/config.h>
  7 SYSSIZE = DEF_SYSSIZE
  8 !
  9 !       bootsect.s              (C) 1991 Linus Torvalds
10 !       modified by Drew Eckhardt
11 !
12 ! bootsect.s is loaded at 0x7c00 by the bios-startup routines, and moves
13 ! iself out of the way to address 0x90000, and jumps there.
14 !
15 ! It then loads 'setup' directly after itself (0x90200), and the system
16 ! at 0x10000, using BIOS interrupts.
17 !
18 ! NOTE! currently system is at most 8*65536 bytes long. This should be no
19 ! problem, even in the future. I want to keep it simple. This 512 kB
20 ! kernel size should be enough, especially as this doesn't contain the
21 ! buffer cache as in minix
22 !
23 ! The loader has been made as simple as possible, and continuos
24 ! read errors will result in a unbreakable loop. Reboot by hand. It
25 ! loads pretty fast by getting whole sectors at a time whenever possible.
26
27 .globl begtext, begdata, begbss, endtext, enddata, endbss
28 .text
29 begtext:
30 .data
31 begdata:
32 .bss
33 begbss:
34 .text
35
36 SETUPLEN = 4                            ! nr of setup-sectors
37 BOOTSEG  = 0x07c0                       ! original address of boot-sector
38 INITSEG  = DEF_INITSEG                  ! we move boot here - out of the way
39 SETUPSEG = DEF_SETUPSEG                 ! setup starts here
40 SYSSEG   = DEF_SYSSEG                   ! system loaded at 0x10000 (65536).
41 ENDSEG   = SYSSEG + SYSSIZE             ! where to stop loading
42
43 ! ROOT_DEV & SWAP_DEV are now written by "build".
44 ROOT_DEV = 0
45 SWAP_DEV = 0
46
47 entry start
48 start:
49         mov     ax,#BOOTSEG
50         mov     ds,ax
51         mov     ax,#INITSEG
52         mov     es,ax
53         mov     cx,#256
54         sub     si,si
55         sub     di,di
56         rep
57         movw
58         jmpi    go,INITSEG
59
60 go:     mov     ax,cs           
61         mov     dx,#0xfef4      ! arbitrary value >>512 - disk parm size
62
63         mov     ds,ax
64         mov     es,ax
65         push    ax
66
67         mov     ss,ax           ! put stack at 0x9ff00 - 12.
68         mov     sp,dx
69 /*
70  *      Many BIOS's default disk parameter tables will not
71  *      recognize multi-sector reads beyond the maximum sector number
72  *      specified in the default diskette parameter tables - this may
73  *      mean 7 sectors in some cases.
74  *
75  *      Since single sector reads are slow and out of the question,
76  *      we must take care of this by creating new parameter tables
77  *      (for the first disk) in RAM.  We will set the maximum sector
78  *      count to 18 - the most we will encounter on an HD 1.44.  
79  *
80  *      High doesn't hurt.  Low does.
81  *
82  *      Segments are as follows: ds=es=ss=cs - INITSEG,
83  *              fs = 0, gs = parameter table segment
84  */
85
86
87         push    #0
88         pop     fs
89         mov     bx,#0x78                ! fs:bx is parameter table address
90         seg fs
91         lgs     si,(bx)                 ! gs:si is source
92
93         mov     di,dx                   ! es:di is destination
94         mov     cx,#6                   ! copy 12 bytes
95         cld
96
97         rep
98         seg gs
99         movw
100
101         mov     di,dx
102         movb    4(di),*18               ! patch sector count
103
104         seg fs
105         mov     (bx),di
106         seg fs
107         mov     2(bx),es
108
109         pop     ax
110         mov     fs,ax
111         mov     gs,ax
112         
113         xor     ah,ah                   ! reset FDC
114         xor     dl,dl
115         int     0x13   
116
117 ! load the setup-sectors directly after the bootblock.
118 ! Note that 'es' is already set up.
119
120 load_setup:
121         xor     dx, dx                  ! drive 0, head 0
122         mov     cx,#0x0002              ! sector 2, track 0
123         mov     bx,#0x0200              ! address = 512, in INITSEG
124         mov     ax,#0x0200+SETUPLEN     ! service 2, nr of sectors
125         int     0x13                    ! read it
126         jnc     ok_load_setup           ! ok - continue
127
128         push    ax                      ! dump error code
129         call    print_nl
130         mov     bp, sp
131         call    print_hex
132         pop     ax      
133         
134         xor     dl, dl                  ! reset FDC
135         xor     ah, ah
136         int     0x13
137         j       load_setup
138
139 ok_load_setup:
140
141 ! Get disk drive parameters, specifically nr of sectors/track
142
143         xor     dl,dl
144         mov     ah,#0x08                ! AH=8 is get drive parameters
145         int     0x13
146         xor     ch,ch
147         seg cs
148         mov     sectors,cx
149         mov     ax,#INITSEG
150         mov     es,ax
151
152 ! Print some inane message
153
154         mov     ah,#0x03                ! read cursor pos
155         xor     bh,bh
156         int     0x10
157         
158         mov     cx,#9
159         mov     bx,#0x0007              ! page 0, attribute 7 (normal)
160         mov     bp,#msg1
161         mov     ax,#0x1301              ! write string, move cursor
162         int     0x10
163
164 ! ok, we've written the message, now
165 ! we want to load the system (at 0x10000)
166
167         mov     ax,#SYSSEG
168         mov     es,ax           ! segment of 0x010000
169         call    read_it
170         call    kill_motor
171         call    print_nl
172
173 ! After that we check which root-device to use. If the device is
174 ! defined (!= 0), nothing is done and the given device is used.
175 ! Otherwise, either /dev/PS0 (2,2 or /dev/at0 (2,, depending
176 ! on the number of sectors that the BIOS reports currently.
177
178         seg cs
179         mov     ax,root_dev
180         or      ax,ax
181         jne     root_defined
182         seg cs
183         mov     bx,sectors
184         mov     ax,#0x0208              ! /dev/ps0 - 1.2Mb
185         cmp     bx,#15
186         je      root_defined
187         mov     ax,#0x021c              ! /dev/PS0 - 1.44Mb
188         cmp     bx,#18
189         je      root_defined
190 undef_root:
191         jmp undef_root
192 root_defined:
193         seg cs
194         mov     root_dev,ax
195
196 ! after that (everyting loaded), we jump to
197 ! the setup-routine loaded directly after
198 ! the bootblock:
199
200         jmpi    0,SETUPSEG
201
202 ! This routine loads the system at address 0x10000, making sure
203 ! no 64kB boundaries are crossed. We try to load it as fast as
204 ! possible, loading whole tracks whenever we can.
205 !
206 ! in:   es - starting address segment (normally 0x1000)
207 !
208 sread:  .word 1+SETUPLEN        ! sectors read of current track
209 head:   .word 0                 ! current head
210 track:  .word 0                 ! current track
211
212 read_it:
213         mov ax,es
214         test ax,#0x0fff
215 die:    jne die                 ! es must be at 64kB boundary
216         xor bx,bx               ! bx is starting address within segment
217 rp_read:
218         mov ax,es
219         cmp ax,#ENDSEG          ! have we loaded all yet?
220         jb ok1_read
221         ret
222 ok1_read:
223         seg cs
224         mov ax,sectors
225         sub ax,sread
226         mov cx,ax
227         shl cx,#9
228         add cx,bx
229         jnc ok2_read
230         je ok2_read
231         xor ax,ax
232         sub ax,bx
233         shr ax,#9
234 ok2_read:
235         call read_track
236         mov cx,ax
237         add ax,sread
238         seg cs
239         cmp ax,sectors
240         jne ok3_read
241         mov ax,#1
242         sub ax,head
243         jne ok4_read
244         inc track
245 ok4_read:
246         mov head,ax
247         xor ax,ax
248 ok3_read:
249         mov sread,ax
250         shl cx,#9
251         add bx,cx
252         jnc rp_read
253         mov ax,es
254         add ah,#0x10
255         mov es,ax
256         xor bx,bx
257         jmp rp_read
258
259 read_track:
260         pusha
261         pusha   
262         mov     ax, #0xe2e      ! loading... message 2e = .
263         mov     bx, #7
264         int     0x10
265         popa            
266
267         mov dx,track
268         mov cx,sread
269         inc cx
270         mov ch,dl
271         mov dx,head
272         mov dh,dl
273         and dx,#0x0100
274         mov ah,#2
275         
276         push    dx                              ! save for error dump
277         push    cx
278         push    bx
279         push    ax
280
281         int 0x13
282         jc bad_rt
283         add     sp, #8         
284         popa
285         ret
286
287 bad_rt: push    ax                              ! save error code
288         call    print_all                       ! ah = error, al = read
289         
290         
291         xor ah,ah
292         xor dl,dl
293         int 0x13
294         
295
296         add     sp, #10
297         popa   
298         jmp read_track
299
300 /*
301  *      print_all is for debugging purposes.  
302  *      It will print out all of the registers.  The assumption is that this is
303  *      called from a routine, with a stack frame like
304  *      dx
305  *      cx
306  *      bx
307  *      ax
308  *      error
309  *      ret <- sp
310  *
311 */
312  
313 print_all:
314         mov     cx, #5          ! error code + 4 registers
315         mov     bp, sp  
316
317 print_loop:
318         push    cx              ! save count left
319         call    print_nl        ! nl for readability
320         jae     no_reg          ! see if register name is needed
321         
322         mov     ax, #0xe05 + 0x41 - 1
323         sub     al, cl
324         int     0x10
325
326         mov     al, #0x58       ! X
327         int     0x10
328
329         mov     al, #0x3a       ! :
330         int     0x10
331
332 no_reg:
333         add     bp, #2          ! next register
334         call    print_hex       ! print it
335         pop     cx
336         loop    print_loop
337         ret
338
339 print_nl:
340         mov     ax, #0xe0d      ! CR
341         int     0x10
342         mov     al, #0xa        ! LF
343         int     0x10
344         ret
345
346 /*
347  *      print_hex is for debugging purposes, and prints the word
348  *      pointed to by ss:bp in hexadecmial.
349 */
350
351 print_hex:
352         mov     cx, #4          ! 4 hex digits
353         mov     dx, (bp)        ! load word into dx
354 print_digit:
355         rol     dx, #4          ! rotate so that lowest 4 bits are used
356         mov     ah, #0xe        
357         mov     al, dl          ! mask off so we have only next nibble
358         and     al, #0xf
359         add     al, #0x30       ! convert to 0 based digit, '0'
360         cmp     al, #0x39       ! check for overflow
361         jbe     good_digit
362         add     al, #0x41 - 0x30 - 0xa  ! 'A' - '0' - 0xa
363
364 good_digit:
365         int     0x10
366         loop    print_digit
367         ret
368
369
370 /*
371  * This procedure turns off the floppy drive motor, so
372  * that we enter the kernel in a known state, and
373  * don't have to worry about it later.
374  */
375 kill_motor:
376         push dx
377         mov dx,#0x3f2
378         xor al, al
379         outb
380         pop dx
381         ret
382
383 sectors:
384         .word 0
385
386 msg1:
387         .byte 13,10
388         .ascii "Loading"
389
390 .org 506
391 swap_dev:
392         .word SWAP_DEV
393 root_dev:
394         .word ROOT_DEV
395 boot_flag:
396         .word 0xAA55
397
398 .text
399 endtext:
400 .data
401 enddata:
402 .bss
403 endbss:
404

如果你对这篇内容有疑问,欢迎到本站社区发帖提问 参与讨论,获取更多帮助,或者扫码二维码加入 Web 技术交流群。

扫码二维码加入Web技术交流群

发布评论

需要 登录 才能够评论, 你可以免费 注册 一个本站的账号。

评论(1

甜柠檬 2022-10-22 08:09:28

什么版本?

~没有更多了~
我们使用 Cookies 和其他技术来定制您的体验包括您的登录状态等。通过阅读我们的 隐私政策 了解更多相关信息。 单击 接受 或继续使用网站,即表示您同意使用 Cookies 和您的相关数据。
原文