322f9e31a6483e9a7527d97bdccd7c27e911423a
[rrq/maintain_lilo.git] / src / volume.S
1 #if 0
2 ;  volume.S  is
3 Copyright 2003-2004 John Coffman.
4 All rights reserved.
5
6 Licensed under the terms contained in the file 'COPYING' in the 
7 source directory.
8
9 #endif
10
11 #ifdef BSS_DATA
12
13 #if 0
14 vtab:   .blkw   MAX_BIOS_DEVICES_asm*2  ; volume IDs indexed by
15                                         ;  REAL bios device code
16
17 rtab:   .blkw   MAX_BIOS_DEVICES_asm*2  ; raid offsets indexed the same
18
19
20 devmap: .blkw   MAX_BIOS_DEVICES+2      ; device code map
21                                         ; logical -> physical
22                                         ; (lo-byte::hi-byte)
23 #endif
24
25 vtab    =       *
26         .org    *+MAX_BIOS_DEVICES_asm*4        ; volume IDs indexed by
27                                         ;  REAL bios device code
28
29 rtab    =       *
30         .org    *+MAX_BIOS_DEVICES_asm*4        ; raid offsets indexed the same
31
32
33 devmap  =       *
34         .org    *+MAX_BIOS_DEVICES*2+4  ; device code map
35                                         ; logical -> physical
36                                         ; (lo-byte::hi-byte)
37
38 #else
39
40 rmask:  .word   0               ; physical raid mask
41
42 ; build_vol_tab -- Build the table of volume IDs
43 ;                       and fill in the device translate table
44 ;
45 ;   Enter with:
46 ;       DS=ES=CS
47 ;
48 ;   Exit with:
49 ;       Nothing
50 ;
51 ;   Side effects:       The volume ID table is built
52 ;                       The from:to device translate table is filled in
53 ;
54 ;
55 build_vol_tab:
56         pusha
57
58         xor     cx,cx           ; depend on this being preserved
59         xor     dx,dx
60         xchg    [devmap],dx     ; clear our First Stage mapping
61
62         call    is_prev_mapper  ; is there a previous mapper
63         jz      bvt0
64
65 ; have previous mapper active
66
67 ; ****** 22.5.7
68         push    di
69         or      dx,dx           ; any translation?
70         jz      bvt003
71 bvt001:
72         seg es
73         mov     ax,(di)         ; get previous translation
74         inc     di
75         inc     di
76         or      ax,ax
77         jz      bvt003
78         cmp     al,dh           ; does it affect us?
79         jne     bvt001
80         mov     [init_dx],ah    ; update physical device
81 bvt003:
82         pop     di
83 ; ****** 22.5.7
84
85         seg es
86           mov   (di),cx         ; sterilize it
87 bvt0:   
88         push    cs
89         pop     es              ; restore ES
90
91 ; ****** 22.5.8
92         mov     di,#KEYTABLE+256+mt_serial_no
93         mov     cx,#MAX_BIOS_DEVICES_asm
94         xor     eax,eax
95         repe
96           scasd                 ; scan for any serial nos in table
97         je      bvt90           ; if none, skip reading vol_ids
98                                 ;    as there will be no translations
99 ; ****** 22.5.8
100
101
102         xor     cx,cx           ; start at hard drive 0 (0x80)
103         mov     di,#vtab        ; place to put IDs
104 bvt1:
105         call    read_vol_id     ; get VolumeID in EAX
106         stosd                   ; store in table
107         or      eax,eax         ; test for zero
108         jz      bvt9            ; end, or no volume ID
109
110 ; now see if there will be a translation
111         push    di
112         push    cx
113
114 ; ****** 22.5.9
115         mov     cx,di           ; 4*table count to CX
116         mov     di,#vtab
117         sub     cx,di           ; 4*count
118         shr     cx,#2           ; table count
119         dec     cx
120         jz      bvt1.5          ; table empty
121         repne                   ; repeat while no match
122           scasd
123         jne     bvt1.5
124
125         mov     bx,#msg_dupl    ; duplicate message
126         call    say
127 #if !DEBUG_NEW
128         call    pause
129 #endif
130         pop     cx
131         pop     di
132
133         mov     dword (di-4),#0 ; zero the duplicated volumeID
134         jmp     bvt9            ; skip to next on duplication
135
136 bvt1.5:
137 ; ****** 22.5.9
138         mov     si,#KEYTABLE+256+mt_serial_no
139         mov     cx,#MAX_BIOS_DEVICES_asm
140         mov     di,si
141 bvt2:   jcxz    bvt7
142         repne                   ; repeat while not matching
143           scasd
144         jne     bvt7            ; jump if no match
145 #if 0
146 ; print the raw serial_no match
147         pushad
148         push    eax
149         call    dout
150         call crlf
151         popad
152 #endif
153         lea     dx,(di-4)       ; DX is address of match
154         sub     dx,si           ; DX is 4*index
155         shr     dx,#2           ; DX is input device #
156         pop     bx              ; BX is real device #
157         push    bx
158         cmp     bx,dx           
159 ; ****** 22.5.9
160 ;;;     je      bvt2            ; equal means no translation
161         je      bvt7            ; equal means no translation
162 ; ****** 22.5.9
163         mov     dh,bl           ;
164         or      dx,#0x8080      ; make into HD bios codes
165 #if 0
166 ; print the raw TT entry
167         pusha
168         mov     ax,dx
169         call    wout
170         call    crlf
171         popa
172 #endif
173         push    si
174         mov     bx,#devmap      ; scan the device translation table
175 bvt4:
176         mov     si,(bx)         ; get from(low):to(high)  pair
177         inc     bx
178         inc     bx              ; bump pointer by 2
179         cmp     si,dx           ; duplicate?
180         je      bvt5
181
182         or      si,si           ; not duplicate; at end?
183         jnz     bvt4
184
185         mov     (bx-2),dx       ; put at end of table
186         mov     (bx),si         ; and mark new end
187 bvt5:
188         pop     si
189 ; ****** 22.5.9
190 ;;;     jmp     bvt2
191 ; ****** 22.5.9
192
193 bvt7:
194         pop     cx
195         pop     di
196 bvt9:
197         inc     cx
198         cmp     cx,#MAX_BIOS_DEVICES_asm
199         jb      bvt1
200
201 bvt90:
202 ; now build the RAID offset table
203
204         mov     si,#KEYTABLE+256+mt_raid_offset
205         mov     dx,[KEYTABLE+256+mt_raid_dev_mask]
206         xor     bx,bx           ; count thru devices
207 bvt91:
208         xor     eax,eax         ; may store 0
209         shr     dx,#1           ; is it raid?
210         jnc     bvt92           ; not a raid device
211
212         lodsd                   ; get raid offset
213         push    eax             ; save value in stack
214
215         mov     eax,[KEYTABLE+256+mt_serial_no](bx)
216         mov     di,#vtab        ; physical table address
217         mov     cx,#MAX_BIOS_DEVICES_asm
218         repne
219           scasd                 ; scan for a match
220         jne     bvt_not_found   ; the logical volume is not there       
221         lea     di,(di-4-vtab)  ; DI is 4*index into table
222         mov     cx,di
223         shr     cx,#2           ; make 0..15
224         mov     ax,#1
225         shl     ax,cl           ; mask bit in right position
226         or      [rmask],ax
227         pop     dword ptr rtab(di)      ; store RAID offset
228         jmp     bvt92
229 bvt_not_found:
230         pop     eax             ; clean up the stack
231 bvt92:
232         add     bx,#4           ;
233         cmp     bx,#MAX_BIOS_DEVICES_asm*4
234         jb      bvt91
235
236 #if DEBUG_NEW
237         mov     bx,#msg_voltab
238         call    say
239         mov     si,#vtab
240         mov     di,#rtab
241         mov     cx,#MAX_BIOS_DEVICES_asm
242 ;;;     mov     dx,[KEYTABLE+256+mt_raid_dev_mask] ; was logical mask
243         mov     dx,[rmask]              ; get physical mask value
244
245 ; truncate all the empty entries from the end of the list
246 ;
247 bvtA:   mov     bx,cx
248         dec     bx
249         shl     bx,#2
250         cmp     dword ptr (bx+si),#0
251         jne     bvtA2
252         loop    bvtA            ; 22.6.1
253
254 bvtA2:  inc     cx
255
256 bvtX:
257         lodsd                   ; get volume serial number
258         push    eax
259         call    dout            ; print it
260         shr     dx,#1
261         mov     bx,#msg_star
262         jc      bvtX1
263         mov     bx,#msg_nostar
264 bvtX1:
265         call    say
266         push    dword (di)
267         call    dout
268         add     di,#4
269         call    crlf
270         loop    bvtX            ; loop back
271
272         call    crlf
273
274 ; now the device translate table:
275
276         mov     bx,#msg_tt
277         call    say
278         mov     si,#devmap
279 bvtB:   lodsw                   ; get from,to pair
280         push    ax
281         call    bout
282         mov     bx,#msg_arr
283         call    say
284         pop     ax      
285         xchg    al,ah
286         push    ax
287         call    bout
288         call    crlf
289         pop     ax
290         or      ax,ax
291         jnz     bvtB
292         call    pause   
293 #endif
294         popa            ; restore all the regs
295         ret
296
297 msg_dupl:
298         .ascii  "O\nError: Duplicated Volume ID\n"
299         .byte   0
300 #if DEBUG_NEW
301
302 msg_voltab:
303         .ascii  "The physical VolumeID / Raid1-reloc table\n"
304         .byte   0
305 msg_star:       .ascii  " * "
306         .byte   0
307 msg_nostar:     .ascii  "   "
308         .byte   0
309 msg_space = msg_nostar
310
311 msg_tt: .ascii  "The device translate table:\n"
312         .byte   0
313 msg_arr:  .ascii        " -> "
314         .byte   0
315 msg_plus: .ascii        " + "
316         .byte   0
317 msg_rw: .ascii  "RAID physical write: "
318         .byte   0
319 #endif
320
321 #ifdef LCF_READAHEAD
322 ; ****** 22.6.1 begin
323 ;
324 ; enable_readahead      -- Enable readahead on an EDD drive
325 ;
326 ;   Enter with:
327 ;       DL = hard disk BIOS code 
328 ;       ES=DS=CS
329 ;
330 ;   Return:
331 ;       Nothing         -- enable read-ahead, if possible
332 ;
333 enable_readahead:
334         pusha
335 #if DEBUG_NEW
336         push    dx              ; save device code
337         xchg    ax,dx
338         call    bout
339         pop     dx              ; restore device code
340 #endif
341         mov     bx,#0x55AA      ;magic number
342         mov     ah,#0x41        ;function call
343         int     0x13
344         jc      enrd9
345         cmp     bx,#0xAA55      ;magic return
346         jne     enrd9
347         test    cl,#EDD_SUBSET|EDD_PACKET       ; some EDD support?
348         jz      enrd9
349 #if 0
350         cmp     ah,#0x21        ; EDD version 1.1 or later?
351         jb      enrd9
352 #endif
353
354         mov     ax,#0x4E00      ; enable prefetch
355         int     0x13
356 #if DEBUG_NEW
357         mov     al,#'-          ; '
358         jc      enrd8_d
359         test    ah,ah           ; check return code in AH
360         jnz     enrd8_d
361         mov     al,#'+          ; '
362   enrd8_d:
363         call    display
364 #endif
365
366 enrd9:
367 #if DEBUG_NEW
368         call    crlf
369 #endif
370         popa
371         ret
372 ; ****** 22.6.1 end
373 #endif
374
375
376 ; read_vol_id   -- Read the volume ID off of a drive
377 ;
378 ;   Enter with:
379 ;       CX = drive number to read (hard disk 0..15)
380 ;       ES=DS=CS
381 ;
382 ;   Return:
383 ;       Carry Clear on success
384 ;       EAX = volume ID         (0 means no ID)
385 ;
386 ;       Carry set on error
387 ;       EAX = 0
388 ;
389 ;
390 read_vol_id:
391         push    bx
392         push    dx
393         push    cx
394         push    di
395
396         push    cx
397         push    es              ; paranoia (floppies touch it)
398
399         mov     ah,#8           ; get number of drives in DL
400         mov     dl,#0x80
401         call    dsk_do_int13    ; retry 5 times
402
403         pop     es
404         pop     cx              ; restore device code
405
406         jc      rvi_9
407         cmp     cl,dl
408         jae     rvi_9
409
410         mov     dl,cl
411         mov     cx,#1
412         mov     bx,#Map
413         or      dl,#0x80
414         mov     dh,ch
415 ; ****** 22.6.1
416 #ifdef LCF_READAHEAD
417         call    enable_readahead
418 #endif
419 ; ****** 22.6.1
420         mov     ax,#0x201       ; read
421         call    dsk_do_int13
422         jc      rvi_9
423
424         seg es
425           mov   eax,(bx+PART_TABLE_OFFSET-6)    ; fetch return
426         jmp     rvi_exit
427 rvi_9:
428         xor     eax,eax
429         stc
430 rvi_exit:
431         pop     di
432         pop     cx
433         pop     dx
434         pop     bx
435         ret
436
437
438 ; map_device -- Take the logical device code in DL and map it
439 ;               into the physical device code preserving all flags
440 ;       22.5.6  Any RAID relocated device code maps to the boot device code
441 ;
442 ;  Enter with:
443 ;       DL containing logical device code & flags
444 ;       DS register not guaranteed
445 ;
446 ;  Exit with:
447 ;       DL containing physical device code & same flags
448 ;
449 ;
450 map_device:
451         push    si              ; save working registers
452         push    ax
453         push    bx
454         mov     si,#devmap      ; point at translation table
455         mov     bl,dl
456         and     bl,#DEV_MASK_asm        ; from device code in BL
457 #if 1
458 ; ****** 22.5.6
459         seg cs
460         mov     ah,[init_dx]    ; get boot device code
461         test    dl,#RAID_REL_FLAG
462         jnz     bios_tt_match   ; it is RAID, go use the boot device code
463 ; ***** 22.5.6
464 #endif
465 bios_tt_next:
466         seg cs                  ; DS may be bad
467           lodsw                 ; get from/to pair
468         or      ax,ax           ; end of list?
469         jz      bios_tt_done
470         cmp     al,bl
471         jne     bios_tt_next
472 ; got a match
473 bios_tt_match:
474         and     dl,#0xFF-DEV_MASK_asm   ; save flags
475         or      dl,ah           ; put on the TO device code
476 bios_tt_done:
477         pop     bx
478         pop     ax
479         pop     si
480         ret
481
482
483 #if 0
484
485 ; rev_map_device -- Take the physical device code in DL and map it
486 ;               into the logical device code preserving all flags
487 ;
488 ;  Enter with:
489 ;       DL containing physical device code & flags
490 ;
491 ;  Exit with:
492 ;       DL containing logical device code & same flags
493 ;
494 ;
495 rev_map_device:
496         push    si              ; save working registers
497         push    ax
498         push    bx
499         mov     si,#devmap      ; point at translation table
500         mov     bl,dl
501         and     bl,#DEV_MASK_asm        ; TO device code in BL
502 bios_tt_next:
503         lodsw                   ; get from/to pair
504         or      ax,ax           ; end of list?
505         jz      bios_tt_done
506         cmp     ah,bl
507         jne     bios_tt_next
508 ; got a match
509         and     dl,#0xFF-DEV_MASK_asm   ; save flags
510         or      dl,al           ; put on the FROM device code
511 bios_tt_done:
512         pop     bx
513         pop     ax
514         pop     si
515         ret
516 #endif
517
518
519 ; translate -- test for a raid device, and do the offsetting
520 ;
521 ;  Enter with:
522 ;       DI:CX   LBA32 or LINEAR address
523 ;       DL      physical device code & flags (RAID_REL_FLAG is set)
524 ;       AL      sector count
525 ;       ES:BX   buffer pointer for R/W
526 ;
527 ;  Exit with:
528 ;       DI:CX   updated if RAID translation takes place
529 ;       All other registers are unchanged
530 ;
531 ;
532 translate:
533         push    bp
534         mov     bp,sp
535
536         cmp     word [rmask],#0         ; any translate bits set?
537         jnz     trans_1
538
539 ; this special cases the initial Keytable read, when no setup has been done
540         BEG_FS
541         SEG_FS
542         add     cx,par1_raid_offset+SSDIFF      ; ***** RAID ******
543         SEG_FS
544         adc     di,par1_raid_offset+2+SSDIFF    ; ***** RAID ******
545         END_FS
546         jmp     trans_ret
547
548 trans_1:
549         push    di
550         push    cx      ; form  dword (bp-4)
551
552         mov     di,dx           ; DI gets full device code
553         and     di,#DEV_MASK_asm & 0x7F
554 #if DEBUG_NEW
555         pusha
556         cmp     byte ptr [dsk_wrflag],#0
557         jz      trans_01
558         mov     bx,#msg_rw
559         call    say
560         mov     ax,di
561         or      ax,#0x80
562         call    bout
563         mov     bx,#msg_space
564         call    say
565         push    (bp-4+2)
566         push    (bp-4)
567         call    dout
568 trans_01:
569         popa
570 #endif
571         shl     di,#2   ; index into array
572
573         mov     cx,[rtab](di)   ; get low relocation value
574         mov     di,[rtab+2](di) ; get high relocation value
575 #if DEBUG_NEW
576         pusha
577         cmp     byte ptr [dsk_wrflag],#0
578         jz      trans_02
579         mov     bx,#msg_plus
580         call    say
581         push    di
582         push    cx
583         call    dout
584         mov     bx,#msg_arr
585         call    say
586 trans_02:
587         popa
588 #endif
589
590         add     (bp-4),cx       ; relocate
591         adc     (bp-4+2),di     ;  **
592
593         pop     cx
594         pop     di
595 #if DEBUG_NEW
596         pusha
597         cmp     byte ptr [dsk_wrflag],#0
598         jz      trans_03
599         push    di
600         push    cx
601         call    dout
602         call    crlf
603 trans_03:
604         popa
605 #endif
606
607 trans_ret:
608         pop     bp
609         ret
610
611 #endif  /* BSS_DATA */
612
613 /* end  volume.S */