make includes fix from trunk
[minix.git] / boot / bootblock.s
blob1c2b9edba516d551cf108f08e041ac1036e2c816
2 ! Bootblock 1.5 - Minix boot block. Author: Kees J. Bot
3 ! 21 Dec 1991
5 ! When the PC is powered on, it will try to read the first sector of floppy
6 ! disk 0 at address 0x7C00. If this fails due to the absence of flexible
7 ! magnetic media, it will read the master boot record from the first sector
8 ! of the hard disk. This sector not only contains executable code, but also
9 ! the partition table of the hard disk. When executed, it will select the
10 ! active partition and load the first sector of that at address 0x7C00.
11 ! This file contains the code that is eventually read from either the floppy
12 ! disk, or the hard disk partition. It is just smart enough to load /boot
13 ! from the boot device into memory at address 0x10000 and execute that. The
14 ! disk addresses for /boot are patched into this code by installboot as 24-bit
15 ! sector numbers and 8-bit sector counts above enddata upwards. /boot is in
16 ! turn smart enough to load the different parts of the Minix kernel into
17 ! memory and execute them to finally get Minix started.
20 LOADOFF = 0x7C00 ! 0x0000:LOADOFF is where this code is loaded
21 BOOTSEG = 0x1000 ! Secondary boot code segment.
22 #ifdef CDBOOT
23 BOOTOFF = 0x0050 ! Offset into /boot above header
24 #else
25 BOOTOFF = 0x0030 ! Offset into /boot above header
26 #endif
27 BUFFER = 0x0600 ! First free memory
28 #ifndef CDBOOT /* just constants, but make no sense for CDs */
29 LOWSEC = 8 ! Offset of logical first sector in partition
30 ! table
32 ! Variables addressed using bp register
33 lowsec = 2 ! Offset of boot partition within drive
34 secpcyl = 6 ! Sectors per cylinder = heads * sectors
35 #endif
36 device = 0 ! The boot device
38 .text
40 ! Start boot procedure.
42 boot:
43 xor ax, ax ! ax = 0x0000, the vector segment
44 mov ds, ax
45 cli ! Ignore interrupts while setting stack
46 mov ss, ax ! ss = ds = vector segment
47 mov sp, #LOADOFF ! Usual place for a bootstrap stack
48 sti
50 push ax
51 push ax ! Push a zero lowsec(bp)
53 push dx ! Boot device in dl will be device(bp)
54 mov bp, sp ! Using var(bp) is one byte cheaper then var.
56 push es
57 push si ! es:si = partition table entry if hard disk
59 mov di, #LOADOFF+sectors ! char *di = sectors;
61 #ifndef CDBOOT
62 testb dl, dl ! Winchester disks if dl >= 0x80
63 jge floppy
64 #endif
66 winchester:
68 #ifndef CDBOOT
69 ! Get the offset of the first sector of the boot partition from the partition
70 ! table. The table is found at es:si, the lowsec parameter at offset LOWSEC.
72 eseg
73 les ax, LOWSEC(si) ! es:ax = LOWSEC+2(si):LOWSEC(si)
74 mov lowsec+0(bp), ax ! Low 16 bits of partitions first sector
75 mov lowsec+2(bp), es ! High 16 bits of partitions first sector
77 ! Get the drive parameters, the number of sectors is bluntly written into the
78 ! floppy disk sectors/track array.
80 movb ah, #0x08 ! Code for drive parameters
81 int 0x13 ! dl still contains drive
82 andb cl, #0x3F ! cl = max sector number (1-origin)
83 movb (di), cl ! Number of sectors per track
84 incb dh ! dh = 1 + max head number (0-origin)
85 #endif
86 jmp loadboot
88 #ifndef CDBOOT
89 ! Floppy:
90 ! Execute three read tests to determine the drive type. Test for each floppy
91 ! type by reading the last sector on the first track. If it fails, try a type
92 ! that has less sectors. Therefore we start with 1.44M (18 sectors) then 1.2M
93 ! (15 sectors) ending with 720K/360K (both 9 sectors).
95 next: inc di ! Next number of sectors per track
97 floppy: xorb ah, ah ! Reset drive
98 int 0x13
100 movb cl, (di) ! cl = number of last sector on track
102 cmpb cl, #9 ! No need to do the last 720K/360K test
103 je success
105 ! Try to read the last sector on track 0
107 mov es, lowsec(bp) ! es = vector segment (lowsec = 0)
108 mov bx, #BUFFER ! es:bx buffer = 0x0000:0x0600
109 mov ax, #0x0201 ! Read sector, #sectors = 1
110 xorb ch, ch ! Track 0, last sector
111 xorb dh, dh ! Drive dl, head 0
112 int 0x13
113 jc next ! Error, try the next floppy type
115 success:movb dh, #2 ! Load number of heads for multiply
116 #endif
118 loadboot:
119 ! Load /boot from the boot device
121 #ifndef CDBOOT
122 movb al, (di) ! al = (di) = sectors per track
123 mulb dh ! dh = heads, ax = heads * sectors
124 mov secpcyl(bp), ax ! Sectors per cylinder = heads * sectors
125 #endif
127 mov ax, #BOOTSEG ! Segment to load /boot into
128 mov es, ax
129 xor bx, bx ! Load first sector at es:bx = BOOTSEG:0x0000
130 mov si, #LOADOFF+addresses ! Start of the boot code addresses
131 load:
132 mov ax, 1(si) ! Get next sector number: low 16 bits
133 movb dl, 3(si) ! Bits 16-23 for your up to 8GB partition
134 xorb dh, dh ! dx:ax = sector within partition
135 #ifndef CDBOOT
136 add ax, lowsec+0(bp)
137 adc dx, lowsec+2(bp)! dx:ax = sector within drive
138 cmp dx, #[1024*255*63-255]>>16 ! Near 8G limit?
139 jae bigdisk
140 div secpcyl(bp) ! ax = cylinder, dx = sector within cylinder
141 xchg ax, dx ! ax = sector within cylinder, dx = cylinder
142 movb ch, dl ! ch = low 8 bits of cylinder
143 divb (di) ! al = head, ah = sector (0-origin)
144 xorb dl, dl ! About to shift bits 8-9 of cylinder into dl
145 shr dx, #1
146 shr dx, #1 ! dl[6..7] = high cylinder
147 orb dl, ah ! dl[0..5] = sector (0-origin)
148 movb cl, dl ! cl[0..5] = sector, cl[6..7] = high cyl
149 incb cl ! cl[0..5] = sector (1-origin)
150 movb dh, al ! dh = al = head
151 movb dl, device(bp) ! dl = device to read
152 movb al, (di) ! Sectors per track - Sector number (0-origin)
153 subb al, ah ! = Sectors left on this track
154 cmpb al, (si) ! Compare with # sectors to read
155 jbe read ! Cant read past the end of a cylinder?
156 movb al, (si) ! (si) < sectors left on this track
157 read: push ax ! Save al = sectors to read
158 movb ah, #0x02 ! Code for disk read (all registers in use now!)
159 int 0x13 ! Call the BIOS for a read
160 pop cx ! Restore al in cl
161 jmp rdeval
162 #endif
163 bigdisk:
164 movb cl, (si) ! Number of sectors to read
165 push si ! Save si
166 mov si, #LOADOFF+ext_rw ! si = extended read/write parameter packet
167 movb 2(si), cl ! Fill in # blocks to transfer
168 mov 4(si), bx ! Buffer address
169 mov 8(si), ax ! Starting block number = dx:ax
170 mov 10(si), dx
171 movb dl, device(bp) ! dl = device to read
172 movb ah, #0x42 ! Extended read
173 int 0x13
174 pop si ! Restore si to point to the addresses array
175 !jmp rdeval
176 rdeval:
177 jc error ! Jump on disk read error
178 movb al, cl ! Restore al = sectors read
179 addb bh, al ! bx += 2 * al * 256 (add bytes read)
180 addb bh, al ! es:bx = where next sector must be read
181 #ifdef CDBOOT
182 addb bh, al ! For CDs, a sector is 2048 bytes, so
183 addb bh, al ! do this 6 more times to get byte count.
184 addb bh, al
185 addb bh, al
186 addb bh, al
187 addb bh, al
188 #endif
189 add 1(si), ax ! Update address by sectors read
190 adcb 3(si), ah ! Don't forget bits 16-23 (add ah = 0)
191 subb (si), al ! Decrement sector count by sectors read
192 jnz load ! Not all sectors have been read
193 add si, #4 ! Next (address, count) pair
194 cmpb ah, (si) ! Done when no sectors to read
195 jnz load ! Read next chunk of /boot
197 done:
199 ! Call /boot, assuming a long a.out header (48 bytes). The a.out header is
200 ! usually short (32 bytes), but to be sure /boot has two entry points:
201 ! One at offset 0 for the long, and one at offset 16 for the short header.
202 ! Parameters passed in registers are:
204 ! dl = Boot-device.
205 ! es:si = Partition table entry if hard disk.
207 pop si ! Restore es:si = partition table entry
208 pop es ! dl is still loaded
209 jmpf BOOTOFF, BOOTSEG ! jmp to sec. boot (skipping header).
211 ! Read error: print message, hang forever
212 error:
213 mov si, #LOADOFF+errno+1
214 prnum: movb al, ah ! Error number in ah
215 andb al, #0x0F ! Low 4 bits
216 cmpb al, #10 ! A-F?
217 jb digit ! 0-9!
218 addb al, #7 ! 'A' - ':'
219 digit: addb (si), al ! Modify '0' in string
220 dec si
221 movb cl, #4 ! Next 4 bits
222 shrb ah, cl
223 jnz prnum ! Again if digit > 0
225 mov si, #LOADOFF+rderr ! String to print
226 print: lodsb ! al = *si++ is char to be printed
227 testb al, al ! Null byte marks end
228 hang: jz hang ! Hang forever waiting for CTRL-ALT-DEL
229 movb ah, #0x0E ! Print character in teletype mode
230 mov bx, #0x0001 ! Page 0, foreground color
231 int 0x10 ! Call BIOS VIDEO_IO
232 jmp print
234 .data
235 rderr: .ascii "Read error "
236 errno: .ascii "00 \0"
237 errend:
239 ! Floppy disk sectors per track for the 1.44M, 1.2M and 360K/720K types:
240 sectors:
241 .data1 18, 15, 9
243 ! Extended read/write commands require a parameter packet.
244 ext_rw:
245 .data1 0x10 ! Length of extended r/w packet
246 .data1 0 ! Reserved
247 .data2 0 ! Blocks to transfer (to be filled in)
248 .data2 0 ! Buffer address offset (tbfi)
249 .data2 BOOTSEG ! Buffer address segment
250 .data4 0 ! Starting block number low 32 bits (tbfi)
251 .data4 0 ! Starting block number high 32 bits
253 .align 2
254 addresses:
255 ! The space below this is for disk addresses for a 38K /boot program (worst
256 ! case, i.e. file is completely fragmented). It should be enough.