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