|
楼主 |
发表于 2007-11-16 13:29:48
|
显示全部楼层
7.1.6.6.c. The key parts of the decompression routine - [( m4 W6 D4 c: z
C.解压例程的关键部分+ ^: B3 V% b+ A$ f5 z
Address Assembly Code4 f! g. b$ M9 A
2000:E512 Decompress_System_BIOS proc near ; CODE XREF: 0002E3DC% c: y/ q9 i7 J# d+ l
.........% s4 i- h: E9 S% b+ R
2000:E555 mov bx, 0
7 K: C4 {' @3 x! y) `4 h4 s2000:E558 mov es, bx) u \" J- w' F k; H+ d# A/ R
2000:E55A assume es:nothing% ?; Z6 y* W8 ]6 z) ~ S
2000:E55A mov word ptr es:7004h, 0FFFFh
! ~' u' b% n; x2 c" r5 p0 |0 X; h2000:E561 xor al, al
# I" ]) T7 d' R8 T6 @% T4 m s2000:E563" N( X ~, i0 G2 M6 Z* X
2000:E563 ; System_BIOS Decompression started here' H `( y" ~, K) r: C. |. ~
2000:E563 mov bx, 1000h, \; y6 ?+ S7 Z: c
2000:E566 mov es, bx ; es = src_seg
9 q1 ^, P* h1 l7 Q. e# o& F2000:E568 assume es:_1000h
4 O8 A( X( ?, C0 `2000:E568 xor bx, bx ; bx = src_offset/ L& p2 T$ O( O4 ~/ D& p
2000:E56A call Decompress ; on ret, CF=1 if error occured
" P9 u, |: S9 b9 v( b7 Q4 E9 J; Q2000:E56D jb short sysbios_decomp_error
1 e# C5 W2 H4 f3 R5 ~2000:E56F test ecx, 0FFFF0000h ; compressed component size more than 64KB?! n; V: i4 M2 f" T7 _2 i
2000:E576 jz short sysbios_decomp_error ; jmp if compressed component size <= 64KB5 f u6 d n; N
2000:E578 mov bx, 2000h
8 G4 J( h. l, V3 K! [2000:E57B mov es, bx ; proceed2next cmprssd componnt (in next segment)
; }4 W- d: ]1 l( `# g2000:E57D assume es:_2000h4 F6 `% I! h# S8 Y3 j7 z6 J' F
2000:E57D mov bx, 1 ; bx = index to be added to previous src_offset in cx4 @0 N' h& ]% K
2000:E580 jmp short repeat_decompress ; decompress remaining component (1st pass jmp taken) W- Z. |: E" R* u! s5 u
2000:E582 ; ---------------------------------------------------------------------------
- }0 Z: M! |6 U, C) F2000:E582 sysbios_decomp_error: ; CODE XREF: Decompress_System_BIOS+5B* u5 a* n0 {* a) z2 k4 X
2000:E582 ; Decompress_System_BIOS+64' i4 m! o8 I! k6 n' F- `5 q# I$ p4 X
2000:E582 rcl al, 1
% p7 E. I8 k! c5 s. V$ D2000:E584 mov bx, 2000h
D* n) C4 k0 a& ^: d3 c5 F7 `* M2000:E587 mov es, bx! K @1 @6 P8 q# C2 I6 K0 I
2000:E589 xor bx, bx7 Z7 ?' R e0 C9 \
2000:E58B call Decompress( l5 \# B; K) B* q, Y! m
2000:E58E rcl al, 1, O* Q! Y8 h3 ^( ^9 _& G, h
2000:E590 cmp al, 3
! }- z1 _# G6 |" h2 i2000:E592 jnz short decompress_successfull
) K/ L1 L! }6 W+ R5 \2000:E594 mov ax, 1000h6 c& |) f3 k/ ?
2000:E597 stc# ^- X4 u9 w$ ?8 Y& E4 k, q( Q# F
2000:E598 retn
& W# o( s! f0 a' x) k2000:E599 ; ---------------------------------------------------------------------------
, ^$ [8 s% H, l" ]9 B' x% p2000:E599 decompress_successfull: ; CODE XREF: Decompress_System_BIOS+80
& G; s# P/ s+ `5 {. `" n2000:E599 or al, al) f' f( k) h, N% d4 P
2000:E59B jnz short sys_bios_dcomprss_done, E& M8 @- R6 ` I n4 W( Y' y+ m
2000:E59D repeat_decompress: ; CODE XREF: Decompress_System_BIOS+6E- G; x) _* m& P" u5 F
2000:E59D ; Decompress_System_BIOS+99
% a9 Q/ t+ S- |8 J/ V' _% G2000:E59D add bx, cx ; bx = point to next compressed component- p i2 ~6 M5 I f; v
2000:E59F call Decompress( L, T) o- ~ X7 U! Z% q
2000:E5A2 jb short sys_bios_dcomprss_done ; 1st pass jmp taken (original.tmp)7 y5 Z2 b7 [( |2 C
2000:E5A4 test ecx, 0FFFF0000h# G, p3 f/ s3 p8 ]& q, x
2000:E5AB jz short repeat_decompress9 }) B1 R% P0 J, |
2000:E5AD sys_bios_dcomprss_done: ; CODE XREF: Decompress_System_BIOS+89
# O1 Z# R8 k) P% c5 ~2000:E5AD ; Decompress_System_BIOS+90/ a2 ^) k7 o! p' O% N7 d& E
2000:E5AD call Decmprss_Sysbios_Extension/ L7 }4 V, F. e3 b) q# s7 K' G
2000:E5B0 jz _sysbios_chksum_error6 H1 P# K) B' k; K" f8 p+ W5 h
2000:E5B4 mov ax, 5000h7 n) _+ [: T6 I. Z9 t! T
2000:E5B7 clc# o0 P' o# x2 ?, b2 J0 \6 [
2000:E5B8 retn
4 ~( \/ e3 X9 o2 W2000:E5B8 Decompress_System_BIOS endp4 `" K0 l* Q5 w3 }* H
________________________________________
7 D* X; N W7 x2 n2000:E5B9 --- Decompress ---
6 ^: _ l9 m \) L+ O6 \2000:E5B9 in: es = component_seg! W5 X y. ?; U2 |
2000:E5B9 bx = component_offset
0 \* S) a3 T+ ^+ L* }, ~$ ]2000:E5B9 out: ecx = overall_compressed_component_length. Z% ]9 B4 g! T0 b% V
2000:E5B9 edx = original_component_size' ^$ c9 T) [3 T
2000:E5B9 CF, set if failed, cleared if success
5 [9 K, ~5 s; f& }. }4 q3 b; ^2000:E5B9 ; --------------- S U B R O U T I N E ---------------------------------------( w2 q9 `& O- D$ ?3 u& n
2000:E5B9 Decompress proc near ; CODE XREF: Decmprss_Sysbios_Extension:not_awdext
" V7 n' `$ `9 L) L. U2000:E5B9 ; Decmprss_Sysbios_Extension:not_awdext2 ...
; T% E1 r9 x7 }- S! M( r( Z2000:E5B9 cmp dword ptr es:[bx+0Fh], 40000000h ; is extension component?% g \9 c6 P4 V* p; D. t2 {! S/ Q
2000:E5C2 jnz short not_xtension_component ; 1st pass jmp taken$ o9 [# u- v5 J4 Q+ O
2000:E5C4 mov si, 0
9 q% f: _& h$ u, k2000:E5C7 mov ds, si
. i$ p/ `/ q4 W% y6 X/ Y2000:E5C9 assume ds:nothing
% h, d/ y: K1 T8 E1 q( v( }$ y N2000:E5C9 mov ds:7000h, bx
. E# @! L3 t7 B2 l$ L2000:E5CD mov si, es- U7 E/ x1 t* S" w( W- Q
2000:E5CF mov ds:7002h, si
& O6 Y; T- w H& ~8 `2000:E5D3 lea si, ds:7789h+ K2 l$ B; s, p, H! o, }
2000:E5D7 mov ds:7004h, si+ ^5 D, j! M% b x
2000:E5DB movzx ecx, byte ptr es:[bx]. W/ ~2 ]. M x
2000:E5E0 add ecx, es:[bx+7]
4 W! ^8 j6 e/ S! B+ x2000:E5E5 add ecx, 36 ]( ?+ M0 s0 p# n8 f
2000:E5E9 retn
$ U1 K) l" e. ?& K$ @, S/ S4 _2000:E5EA ; ---------------------------------------------------------------------------
5 n; n4 O/ {$ e. n" Y' m) N% w* h2000:E5EA not_xtension_component: ; CODE XREF: Decompress+9& p% }# d g7 R* h
2000:E5EA mov dx, 3000h ; dx = scratchpad_seg for decompression
4 g- x) C5 v' K7 J( E: o# ^0 G2000:E5ED push ax3 ~1 |+ z+ ]+ _3 Q) [/ w8 R
2000:E5EE push es
, \" ]# T- F; o; I$ M1 G0 @2000:E5EF call Find_BBSS ; on ret, si contains offset right after BBSS sign
6 A# r ]' ^) n* i2000:E5F2 pop es+ Y# ~4 `- b q; s
2000:E5F3 assume es:nothing$ j6 @/ \6 Z- t" j4 v1 }7 ~
2000:E5F3 push es
$ u6 k9 u* `- @: ?" y0 X2000:E5F4 mov ax, es
% N& Z3 y/ k- ^- j9 b2000:E5F6 shr ax, 0Ch$ `/ t4 I6 g8 J N6 G# ]
2000:E5F9 mov es, ax
* u2 ]4 a" n' C2000:E5FB assume es:nothing$ O3 q8 I" W' i% h) j0 M
2000:E5FB mov ax, cs:[si+0Eh]
7 r/ Q9 t8 P& P2000:E5FF call ax ; call decompression engine at 2000:7789h
9 L" ~1 |% Y1 H' _2 j$ I3 C2000:E601 pop es
8 a1 ]7 `( R( L1 W. c |2000:E602 assume es:nothing
" I( Q; A2 A0 L8 b# \( Z" ]2000:E602 pop ax
8 l: q# t! U1 N8 ~' q4 ~, G5 ^- t# L2000:E603 retn9 j$ ]: o) L; x) L
2000:E603 Decompress endp/ z6 c W1 }9 r: ]! [" k+ g
________________________________________3 F& t+ O9 T2 |
2000:7789 --- Decomprssion_Ngine ---
( g; B2 C- r3 b5 M5 V: e7 h2000:7789 in: dx = scratch-pad_segment_for_decompression# ], |1 G5 W; @. w8 s* J0 y
2000:7789 es = (compressed_segment_addr>>0xC) [hi_word of src phy addr]
9 t$ F$ [1 B5 o L2000:7789 bx = compressed_offset_addr) T- m/ {2 Q' Y, D' c( }/ s9 a, x0 C
2000:7789
) g8 u8 D9 }' O2000:7789 out: ecx = overall_compressed_component_length
$ ~8 Y0 y2 t4 u6 z# v0 j2000:7789 edx = original_file_size
) ~! G# L8 ]7 I: k" \2000:7789 ; --------------- S U B R O U T I N E ---------------------------------------# Q# D8 [; b$ p: I4 [% m s& U
2000:7789 Decompression_Ngine proc near6 j- A& ^9 c, @' e
2000:7789 push eax
5 N9 o% q% y8 s" v. R2000:778B push bx
3 L8 N+ U/ l. m, h# l2000:778C push es1 \' m6 _3 i: P }
2000:778D mov ds, dx
% R3 L g" k& Z! H2000:778F push ds: a$ C! s3 j0 I) f: Y, g3 f* \
2000:7790 pop es
& E" c9 a4 }% \7 U2000:7791 xor di, di+ M5 ~& Z" P1 U. d, l; m% j! ^. b
2000:7793 mov cx, 4000h3 X, h3 l+ A2 L$ E, I
2000:7796 xor ax, ax9 S( k8 s! f7 g* x
2000:7798 rep stosw ; zero-init 32KB starting at Scratchpad_Seg:0000h
3 g. d! @5 l% J, r2000:779A pop es1 U- T% v m1 h: R
2000:779B push es
2 y) A5 p5 w# ^( B9 `2000:779C
& x4 a4 x7 u2 s8 O6 L" J7 \8 z, o2000:779C ;Setup GDT to be used to get src bytes (Fetch_Byte) later
: v' _' ?# f. \4 F. ?! Z% l T7 O2000:779C mov word ptr ds:100h, es ; ds:100h = compressed_seg_addr>>0xC+ }% r. f+ X8 O' I/ q8 L" N1 g
2000:779C ; 1st pass ds:100h = 1
N9 a2 @# Y5 m" }2000:77A0 mov ds:102h, bx ; ds:102h = compressed_offset_addr
- \. k( h: I) E2 F2000:77A0 ; 1st pass bx = 0! V0 E% ]7 S# {9 T) q- G v
2000:77A4 xor ecx, ecx7 a; f# F0 ~0 U' Z( Y6 _& n
2000:77A7 mov ds:57A8h, ecx
. m! Q m( V3 k2000:77AC mov ds:57ACh, ecx" ^3 X) M- T, k. p+ z' N
2000:77B1 lea cx, ds:57A8h
1 J1 D. z2 y5 E3 Z2000:77B5 ror ecx, 49 k9 q; F* b! E) R L) u
2000:77B9 mov ax, ds* g0 }: y+ D5 ~* v8 n: `
2000:77BB add cx, ax
6 m) S8 k8 T3 V! J1 U2000:77BD rol ecx, 4
+ P8 D. D# s. K5 s! R2000:77C1 mov word ptr ds:57A2h, 18h
# ]+ L1 o4 n# Y, B- k( S5 t7 _+ f. P2000:77C7 mov ds:57A4h, ecx
( j0 e6 Q/ D$ \ n3 ?2000:77CC mov dword ptr ds:57B0h, 0FFFFh
/ y: h" @: s# H; A2 E* Y: H2000:77D5 mov ax, es7 c6 w2 Z8 U+ G" o1 D! E
2000:77D7 movzx ecx, ah ; es = hi_word addr of desc_base
* i4 O" U% h2 P# D7 ^0 N2000:77DB ror ecx, 8 ; ecx = base_24_31 << 24
1 M2 n# y- K7 f+ V. {+ @) @7 u2000:77DF mov cl, al
; A. u! V+ [7 M s/ P' z. y8 f# s( E2000:77E1 or ecx, 8F9300h# e5 Y! G$ a! {. D3 O% F/ {! v
2000:77E8 mov ds:57B4h, ecx" c$ s7 |; T' F, @, R) Z0 e% K" P7 U
2000:77ED mov dword ptr ds:57B8h, 0FFFFh
" Q4 A2 C" ~4 t a: ~2000:77F6 mov dword ptr ds:57BCh, 8F9300h
! ~' G( l1 @1 U2 Q1 J: F2000:77FF push gs
2 N4 V9 g d5 g( D: J# n2000:7801 mov di, 0
! L& W6 {" K$ z k) d. p& ]2000:7804 mov gs, di9 R, n1 I6 ?# ~& y' b5 T
2000:7806 assume gs:nothing
0 d7 H; l$ j6 Y) P- [2000:7806 mov di, 6000h4 k h2 J4 }* `
2000:7809 mov word ptr gs:[di], 7789h
1 \- w' j y5 s; s, g5 F2000:780E9 R$ A) f- u+ w+ X( x" Q8 O
2000:780E ;check LZH header
! w0 \% E2 Y$ b3 n4 e2000:780E add bx, 12h ; LZH-header decomp_seg_addr_hi_byte index7 ?* f$ h6 ~. E6 D5 ]' U
2000:7811 call Fetch_Byte
( \' y1 g6 c) c/ z) W2000:7814 sub bx, 12h ; restore bx to point to first byte( @$ R* i( w7 @% t
2000:7817 cmp al, 40h ; '@' ; is extension component?
& D& \- x/ p3 C4 T2000:7817 ; at 1st: al equ 50h (original.tmp)# h" D, ?/ ?% _9 _2 {& u
2000:7817 ; at 2nd: al equ 41h (awardext.rom)
) q! G+ I ~, y! S/ t4 J: J2000:7819 jnz short not_extension_component ; 1st-pass jmp taken1 v. V# x/ S/ L" N5 ?
2000:781B add bx, 11h) T% n4 A) x: i
2000:781E call Fetch_Byte ; fetch "dest_seg_addr" lo_byte
# w; h3 @$ o4 V& t2000:7821 sub bx, 11h ; restore bx to point to first byte7 Y( w' V8 G# ?+ D4 H5 V, p# e/ r' l
2000:7824 or al, al ; if extension component, jmp taken
$ |" Y% y$ @/ N2 L. H. U2000:7826 jnz short extension_component! v- i1 A$ Z; n' n& `+ A
2000:7828 cmp dword ptr gs:[di+4], 0& u( y/ ^" _" m+ y1 O- [
2000:782E jnz short not_extension_component3 d$ ?& k, V+ ^5 [4 U1 A
2000:7830 extension_component: ; CODE XREF: Decompression_Ngine+9D
2 n2 U# r' _/ Y) f* _* p- E2000:7830 movzx dx, al ; dl = "dest_seg_addr" lo_byte8 X y5 Q/ W4 [9 K
2000:7833 inc bx ; bx = LZH_hdr_chksum byte index2 [9 @. _) F+ e/ j+ [. i. }: g
2000:7834 call Fetch_Byte
8 \+ `% ?# W. L1 b' i5 P4 |- Q1 A2000:7837 sub al, dl ; LZH_hdr_chksum = LZH_hdr_chksum - "dest_seg_addr"_lo_byte
' M# ]' R- R. Z7 C/ p! A- Y& p2000:7839 call Patch_Byte ; store new checksum5 T" t! l6 Q- S2 s! Z
2000:783C dec bx ; restore bx
$ B- }/ w, } E6 T$ G( P2000:783D xor al, al ; al = 00h
6 z3 a# l( W+ S1 i" H8 _+ _6 I2000:783F add bx, 11h ; bx = "dest_seg_addr"_lo_byte index
$ K7 q( Z, r% s$ P2000:7842 call Patch_Byte ; patch "dest_seg_addr"_lo_byte to 00h
; E" y9 w) t0 [2000:7845 sub bx, 11h
7 W1 ^" W4 b M. Q" A2000:7848 inc dx ; dx = "dest_seg_addr"_lo_byte + 15 b3 W# u3 i6 L- n
2000:7849 shl dx, 2 ; dx = 4*("dest_seg_addr"_lo_byte + 1)1 T! W& A; M" o; a
2000:784C add di, dx ; di = 6000h + dx -- look above! r' _. b; F2 y: g' k6 V
2000:784E mov gs:[di], bx ; 0000:[di] = compressed_offset_addr
$ M5 k7 D0 h2 L2000:7851 mov cx, es
V, { X7 A2 i. U f3 K2000:7853 mov gs:[di+2], cx ; 0000:[di+2] = compressed_seg_addr>>0xC (hi_word of src phy addr)
' I) K; e* |: g$ C2000:7857 call Fetch_Byte ; al = LZH_hdr_len* [' j" p- v" v( ]; @' j
2000:785A movzx ecx, al ; ecx = LZH_hdr_len) p7 N5 E$ Y& R7 J. a3 q- y# Y
2000:785E add bx, 7
% P( [1 v; I/ D& F2000:7861 call Fetch_Dword ; eax = compressed_file_size
9 S, ~1 ~* Z. J2000:7864 sub bx, 7
+ D- \8 [, J5 K2000:7867 add ecx, eax ; ecx = LZH_header_len + compressed_file_size
G1 j% s8 v4 F2000:786A add ecx, 3 ; ecx = total_compressed_component_size" u& d4 d5 h, y) x5 p! Q
2000:786E pop gs; G E$ P. b5 [# S0 y
2000:7870 assume gs:nothing e! D& G- J' E9 _! O
2000:7870 jmp exit
; V9 c' E) m, v! ? `$ G2000:7873 ; ---------------------------------------------------------------------------
$ B9 N. ~& _' J8 X! W2000:7873 not_extension_component: ; CODE XREF: Decompression_Ngine+90. k. u1 i. ~4 N
2000:7873 ; Decompression_Ngine+A5
+ R* e+ y% E# q" l2000:7873 pop gs
8 ^2 [: {! I! S- M& Q4 T7 _% _" N2000:7875 call Make_CRC16_Table
) f3 N0 |& L4 [' }7 V6 U2000:7878 call Read_Header ; fetch header component to scratchpad_seg, on error CF=1; R6 O) l o/ B% c
2000:787B jb exit ; ret with error code set9 ~$ V$ r" O! a5 M5 l
2000:787F mov ax, ds:108h ; mov ax, decomprss_seg_addr
& }% I% Q) T- f1 ^/ z: D+ O8 t2000:7882 mov ds:104h, ax ; mov nu_decomprss_seg_addr, ax5 Q& p: c) @/ m# t& J
2000:7885 mov ax, ds:10Ah ; mov ax, decomprss_offst_addr
! @4 A& ^ F% B# |8 N* _0 g' ~: c2000:7888 mov ds:106h, ax ; mov nu_decomprss_offst_addr, ax
1 a3 n5 V# F; L9 ]: k) }, A6 ]2000:788B mov ecx, ds:310h ; ecx = compressed_component_size
) S# P1 J8 @0 P; G* R2000:7890 xor eax, eax9 R9 f r* r9 f0 M
2000:7893 mov al, ds:571Ch ; al = LZH_hdr_len2 Y* g0 f' V( q, a2 j) Y& h( V
2000:7896 add ecx, eax ; ecx = compressed_cmpnnt_size + LZH_hdr_len
* a1 J: \1 Q A( ?6 G. x2000:7899 add ecx, 3 ; ecx = compressed_cmpnnt_size + LZH_hdr_len +! v) m+ m+ W) e$ s1 g
2000:7899 ; sizeof(EOF_byte) + sizeof(LZH_hdr_len_byte) +. v# c! k. o) q2 E7 d5 U1 x
2000:7899 ; sizeof(LZH_hdr_8bit_chk_sum)' U- W3 b+ F9 _. q4 T' a
2000:7899 ; i.e. ecx = overall_component_len( ?0 S" w1 Q7 q
2000:789D mov edx, ds:314h ; mov edx, original_file_size
2 `0 j& K" ^- y! j2000:78A2 push edx7 W2 ~1 K8 C7 r* ~9 Q4 n
2000:78A4 push ecx
$ Y$ x- }* W+ C' g+ G) B- x2000:78A6 push bx
2 G- b. ~' a' K2000:78A7 add bx, 5 ; point to LZH ID byte+ m) Z4 f" @; @% ~$ j5 @" W
2000:78AA call Fetch_Byte) _- m2 z* I! C' ]7 w+ {" X' i8 P( o3 }
2000:78AD pop bx# a* Q3 ^, D4 e: u
2000:78AE cmp al, '0' ; is '-lh0-'?
( z. W0 @- b6 n5 r ?& B% Y, C8 Z3 p2000:78B0 jnz short decompress_part7 j; ^# } K6 j/ w5 ]' k/ u t
2000:78B2 push ds
* J! h8 Z; S6 m& }8 n" h" v! F2000:78B3 push si- q' X9 O% r6 M: X: @2 B
2000:78B4 push bx5 ?. q7 f9 l* O* M5 E8 g9 O
2000:78B5 mov di, ds:10Ah# c+ t* m0 i+ E/ f0 e9 i/ h
2000:78B9 movzx ax, byte ptr ds:571Ch
$ S9 `% V( w) ~8 ?7 O2000:78BE add ax, 2
/ G1 I, H1 e! b% h2000:78C1 add bx, ax
2 h! F* d5 i7 w6 y( Q, P2000:78C3 mov cx, ds:310h
" N9 g) t! h6 _& W: Y2000:78C7 mov ax, ds:108h1 p1 c- e7 Z# y6 }
2000:78CA mov es, ax
5 d" Y$ c% m5 S1 _" g2000:78CC add cx, 3# ^ x' P) M4 w! V/ V; V3 v4 x
2000:78CF shr cx, 2. W) o: l/ h2 d; J* I
2000:78D2 next_dword: ; CODE XREF: Decompression_Ngine+151
. c+ Q! ^4 n1 ~3 s: |7 W8 v2000:78D2 call Fetch_Dword+ m% L! \9 Z1 d) f* u
2000:78D5 add bx, 4& x3 i! k! |% N7 ~, L1 n0 G* j
2000:78D8 stosd
F5 _% d6 n7 ^4 |2 c* \/ X9 t2000:78DA loop next_dword& F; e. H2 x8 h; i
2000:78DC pop bx
6 ~+ p, s7 e. l' _2000:78DD pop si
7 T/ E9 z# h) \% ^- R/ B2000:78DE pop ds
; m2 `! Z0 H3 M9 V! C2000:78DF jmp short LZH_hdr_OK1 i( i" u1 _7 ]5 w0 N) ?' H
2000:78E1 ; ---------------------------------------------------------------------------
9 p% O0 N- I/ G2 w2000:78E1 decompress_part: ; CODE XREF: Decompression_Ngine+1275 e" A* D1 b& N# P+ b3 j/ n
2000:78E1 push word ptr ds:104h ; save destination seg addr
- U$ \; T# k' @4 G S+ ?2000:78E5 push word ptr ds:106h ; save destination offset addr
2 Y0 x/ q( j/ O; c3 R% m' S( r B3 `2000:78E9 push large [dword ptr ds:314h]
6 E) l+ t) @# d( l/ O2000:78EE call Lzh_Expand ; Lzh_Expand capable of handling compressed
0 q/ Z7 J: w+ P) F2000:78EE ; component bigger than 64KB (1 segment) [; U0 d: ]! c; w2 u. ^* k8 m; z
2000:78F1 pop dword ptr ds:314h
3 a) q3 Q4 E7 z2 p: |2000:78F6 pop word ptr ds:106h6 }% G0 k% d' {$ o# l e
2000:78FA pop word ptr ds:104h* {, M+ V/ m' p+ n% b. y' G
2000:78FE LZH_hdr_OK: ; CODE XREF: Decompression_Ngine+156
& T& m v- {% N2000:78FE call Zero_Init ; zero init 32KB of scratchpad_seg9 E3 ]3 {1 @ r
2000:7901 pop ecx
" R( ]/ e9 V: @4 V1 T: s5 X- Y2000:7903 pop edx
7 J0 p: G* ^/ D; _$ y2000:7905 clc
: K) v4 A+ @3 a3 m: V7 _2000:7906 exit: ; CODE XREF: Decompression_Ngine+E7# i& D+ G9 A6 k3 F4 l
2000:7906 ; Decompression_Ngine+F24 }/ O. `( ^( J6 Y& {4 f' I* ]
2000:7906 pop es
( s% [. \& U# e5 Q& i2000:7907 pop bx( P2 S9 X" C& W% ^1 q; p/ {
2000:7908 pop eax
$ k% z! {" P# q2 b/ G7 j$ n' w: {2000:790A retn
" q) X, c+ u+ Z5 B! X; }, I2000:790A Decompression_Ngine endp) W) J* P* @0 B
________________________________________
3 y1 T( K5 C* w3 N/ [. Z$ H a/ C Y3 ^; E+ d+ m( a* W
2000:790B --- Make_CRC16_Table ---
8 T5 H- V. c# R2000:790B 1st pass, the base address for DS is 3_0000h# G1 ~5 S: v3 _- v* T5 ]
2000:790B in: ds = scratch_pad_segment for CRC table6 D* B% }& ^5 M7 u/ P
2000:790B out: ds:10Ch - ds:11Bh = CRC-16 table
2 O _5 n1 a7 s* {. ]4 O. Q! h2000:790B ; --------------- S U B R O U T I N E ---------------------------------------
9 g% D! }) P: ~ I9 l2000:790B Make_CRC16_Table proc near ; CODE XREF: Decompression_Ngine+EC
3 ?! ~0 S" p/ b; Z- Y( T2000:790B 51 push cx
4 s: {( f( \3 y# _3 Q3 V2000:790C 53 push bx1 |# [. o' a: \+ T$ @, m
2000:790D 50 push ax
3 ^) W* {! [: Y2000:790E 56 push si; |" }. C& F7 @3 K
2000:790F BE 0C 01 mov si, 10Ch
8 U/ k" |" |$ {& |2000:7912 B9 00 01 mov cx, 100h
; H N$ \. d- X+ k2000:7915 next_byte: ; CODE XREF: Make_CRC16_Table+2B
. a2 e5 R* J1 j6 `2000:7915 B8 00 01 mov ax, 100h
( m0 h. S) A6 w4 ?- L7 }5 l3 B2000:7918 2B C1 sub ax, cx [7 u! ~& [, h/ S5 M$ L
2000:791A 50 push ax) `2 M: t! o- Q$ W! ~" [" E
2000:791B BB 00 00 mov bx, 09 h- |+ `- ]% C4 l6 }
2000:791E is_bit: ; CODE XREF: Make_CRC16_Table+258 W, F2 O, {! ?; |. N# L
2000:791E A9 01 00 test ax, 1
`" k9 K& |9 x' J2000:7921 74 07 jz short not_bit
. e. `- {4 | K/ \! x7 D j2000:7923 D1 E8 shr ax, 1
1 ^& r ?) }& R* w' {2000:7925 35 01 A0 xor ax, 0A001h ; CRC poly
2 v8 [5 A% P9 J1 C7 D' o" S2000:7928 EB 02 jmp short point_to_next_byte
; F& N2 ^3 e2 }2000:792A ; ---------------------------------------------------------------------------7 R5 _$ q# Q0 y! c0 G* E
2000:792A not_bit: ; CODE XREF: Make_CRC16_Table+16
/ x1 W( v7 S& ?2000:792A D1 E8 shr ax, 1
2 u+ C, u" S* q2000:792C point_to_next_byte: ; CODE XREF: Make_CRC16_Table+1D1 X& L8 z/ |4 M/ `
2000:792C 43 inc bx
7 r% F% B0 K+ \; K& z7 d3 I* z2000:792D 83 FB 08 cmp bx, 8
; w) Z0 S7 }. O7 v6 E7 p( }2000:7930 72 EC jb short is_bit
3 c1 H' q$ Q9 @2000:7932 5B pop bx. o1 ~. b% b" P7 U0 Z5 g1 d: H
2000:7933 89 00 mov [bx+si], ax
, |6 ~+ j, w( G7 [) f( F/ C2000:7935 46 inc si
- ^$ p. {" o: f+ E2 S2000:7936 E2 DD loop next_byte
) t/ |- E! f+ \/ ?& L2000:7938 5E pop si
8 _& z/ F f; T$ {! A2000:7939 58 pop ax/ `, \9 Q* w0 x- ^7 y
2000:793A 5B pop bx
# i( L( Q. x5 r5 s- p9 l+ _2000:793B 59 pop cx
+ K8 z. _ S8 z3 n" F$ y' v3 V2000:793C C3 retn
0 |8 f( E: a! f2 f. J3 z$ `% p2000:793C Make_CRC16_Table endp
. I& d0 U' Y& N3 x8 _________________________________________
' H$ W' K. n6 p O+ L9 Q& b8 l( V' x- d$ T4 |6 @; b) o/ K5 L$ D
2000:79E8 --- Read_Header ---% [/ U# M3 Y R
2000:79E8 in: ds = scratchpad_segment6 m- S6 D, S: m/ W& o; l# r/ d& Y: t
2000:79E8 ds:102h = LZH_hdr_byte_index
! F* n& `' D1 a% S/ O% \2000:79E8
; a) C# P0 q. `$ D0 M) ^2000:79E8 out: ds:102h = LZH_hdr_byte_index h0 x' D. _4 k1 r6 V" Q
2000:79E8 ds:108h = componnt_decomprrsion_seg_addr9 X4 L2 V' `5 ~8 n9 {# `2 P# L( K
2000:79E8 ds:10Ah = componnt_decomprrsion_offset_addr3 u2 ~- {6 R: [; X
2000:79E8 ds:310h = uncompressed_componnt_size% \, L3 p' Y! w$ k! Q4 J
2000:79E8 ds:314h = component_seg:offset_decompression_addr
3 v" d$ P& f6 ^. y8 O2000:79E8 ds:571Ch = LZH_hdr_len6 w: j( M4 P) W/ i+ m1 P C% W
2000:79E8 ds:571Dh = LZH_hdr_chksum
+ p' [7 Z% W- ]5 `( ~3 R+ |2000:79E8 ds:571Eh = LZH crc16 val
( |# G# A+ N( V3 C5 `0 U5 X- G2000:79E8 ds:0 - ds:LZH_hdr_len = copy of current component LZH hdr: F* p% B( t- \1 [" J$ m6 \+ e
2000:79E8 ; --------------- S U B R O U T I N E ---------------------------------------
$ d, J2 ?, _) g; j/ ~4 }5 [; t2000:79E8 Read_Header proc near ; CODE XREF: Decompression_Ngine+EF: o% j+ ^9 W$ Q7 S6 P, s
2000:79E8 60 pusha/ P; ]* z* d: F8 N5 I
2000:79E9 06 push es
! v2 H3 }; h3 n( x2000:79EA 8B 1E 02 01 mov bx, ds:102h
7 B E O8 M- B& I$ C. W2000:79EE E8 DA 00 call Fetch_Byte
) l2 [, P1 z. y3 ~2000:79F1 FF 06 02 01 inc word ptr ds:102h7 \1 s( _: c+ ~# U6 e6 B8 o O& ]) i
2000:79F5 A2 1C 57 mov ds:571Ch, al
: I1 D, ~$ m- \2000:79F8 07 pop es, [3 I: W* _. }$ ` b0 H
2000:79F9 80 3E 1C 57 00 cmp byte ptr ds:571Ch, 0' ^2 n- I1 {/ C* D% S' N+ w2 ~% f8 w
2000:79FE 75 04 jnz short read_LZH_hdr_ok3 y0 `! |" c; g# E8 n5 C
2000:7A00 error: ; CODE XREF: Read_Header+38
& T* d8 B K# m3 f A8 F8 T2000:7A00 ; Read_Header+71 ...
0 ?6 w# `$ X% v. @2000:7A00 F9 stc
) B1 B' ^$ z i- K3 z* C2 s8 G2000:7A01 E9 86 00 jmp exit
2 o) C4 X' I' |+ o! _8 y& ^2000:7A04 ; ---------------------------------------------------------------------------
7 w. d* D& A# N- w% u2000:7A04 read_LZH_hdr_ok: ; CODE XREF: Read_Header+16$ M' O9 K+ C) R) z8 Q
2000:7A04 06 push es
1 E) n% [# O5 ~" `- r2000:7A05 8B 1E 02 01 mov bx, ds:102h5 }1 D1 y2 d& v% L
2000:7A09 E8 BF 00 call Fetch_Byte ; read LZH_hdr_chksum byte5 I+ }' }2 _2 G% Z* U- N0 d
2000:7A0C FF 06 02 01 inc word ptr ds:102h
: @( T8 L6 b& c2 [2000:7A10 A2 1D 57 mov ds:571Dh, al ; 1st pass: 3000:571D = LZH_hdr_chksum
& T# u( ] k% ]9 X' z2000:7A13 07 pop es- p, Z# `3 U, ~; s
2000:7A14 E8 26 FF call Calc_LZH_hdr_CRC16 ; fetch compressed component value to RAM,
6 R4 |! R1 q6 C: @' E2000:7A14 ; then calc its CRC16 checksum. D- Y" J6 E. _" a3 {
2000:7A17 E8 88 FF call CalcHdrSum
! @( g+ @/ E% O& W. f( d2000:7A1A 3A 06 1D 57 cmp al, ds:571Dh ; is the stored LZH_hdr 8-bit chksum match the one that read?6 M0 T. g) `8 Q! ^' m6 ~0 y5 Z
2000:7A1E 74 02 jz short LZH_hdr_8bit_chksum_ok: |' m; B. e5 E6 P
2000:7A20 EB DE jmp short error
9 n& P- Y5 h3 X) f8 f+ G0 b2000:7A22 ; ---------------------------------------------------------------------------
$ x( S" Z5 \& f0 b4 `: t2000:7A22 LZH_hdr_8bit_chksum_ok: ; CODE XREF: Read_Header+36* u" q' m# w2 ^* S: J6 y) T
2000:7A22 BB 05 00 mov bx, 5& h# e: z) Q3 n
2000:7A25 B9 04 00 mov cx, 4 ; bx+cx = compressed_component_size_index (Dword)4 `, |0 c# K% `2 G
2000:7A28 E8 99 FF call GetFromHeader
+ K. B U2 G9 o) V2 P# K2000:7A2B 66 A3 10 03 mov ds:310h, eax
: ]1 U8 s' I: p7 }7 M; A2000:7A2F BB 09 00 mov bx, 9
h D% I) C. S6 a1 Q0 B2000:7A32 B9 04 00 mov cx, 4 ; bx+cx = original file size (Dword)
! F. ^4 q) z6 M4 T2000:7A35 E8 8C FF call GetFromHeader
& U" l {8 L) O+ k: _2000:7A38 66 A3 14 03 mov ds:314h, eax
5 B; g7 r( V1 E2 M2000:7A3C BB 0D 00 mov bx, 0Dh
6 ]" N; w1 K$ G- }2000:7A3F B9 02 00 mov cx, 2 ; bx+cx = decompression_component_offset addr (Word)
/ j6 r: L$ a8 `1 U+ P! X! T2000:7A42 E8 7F FF call GetFromHeader
! i$ b, }# p2 Q) T' D2000:7A45 A3 0A 01 mov ds:10Ah, ax
4 M( `1 w3 A; t, ]& o2000:7A48 BB 0F 00 mov bx, 0Fh
5 H8 K" \/ p6 U2000:7A4B B9 02 00 mov cx, 2 ; bx+cx = decompression_component_segment addr (Word)( p+ Y- d2 @) N6 [ q
2000:7A4E E8 73 FF call GetFromHeader
& T8 |) o$ Z2 U' N# v2000:7A51 A3 08 01 mov ds:108h, ax7 k" P" s4 c F3 l, A, [
2000:7A54 80 3E 11 00 20 cmp byte ptr ds:11h, 20h ; ' ' ; is LZH level 1 file attribute?
2 d% Z0 r2 o9 e1 J2 }+ ?$ ?2000:7A59 75 A5 jnz short error! [" t2 ?) {& w0 e" `; `
2000:7A5B 80 3E 12 00 01 cmp byte ptr ds:12h, 1 ; is LZH level 1 ?0 v& A' D7 L9 @; o, J. u& k8 d
2000:7A60 75 9E jnz short error
; A" d: ^( u% B4 R' f8 D1 t+ `1 }2000:7A62 0F B6 1E 1C 57 movzx bx, byte ptr ds:571Ch ; bx = lzh_hdr_len
' V1 m1 Q$ h) S, j4 y, R2000:7A67 83 EB 05 sub bx, 5 ; bx = CRC16_byte_index" E, p9 x& P( Q( y
2000:7A6A B9 02 00 mov cx, 2: i( ~$ D9 d/ J" s1 n
2000:7A6D E8 54 FF call GetFromHeader ; read CRC16 value+ m7 w. p8 y. Z1 D( x1 D( V
2000:7A70 A3 1E 57 mov ds:571Eh, ax ; ds:571Eh = CRC16_val+ `+ W) U$ \: [
2000:7A73 BB 13 00 mov bx, 13h ; bx = filename_len byte index6 T- x+ p1 H9 t, _2 S' p
2000:7A76 8A 9F 00 00 mov bl, [bx+0] ; bl = filename_len
. E# L5 l, B+ {; P2000:7A7A B8 14 00 mov ax, 14h, l. C: h" ^9 E5 Y- h( B
2000:7A7D 03 D8 add bx, ax ; bx = CRC16_byte_index
( L# |! s6 A1 L& j2000:7A7F C6 87 00 00 24 mov byte ptr [bx+0], 24h ; '$'% o0 i; [6 q$ N6 N3 M8 C4 h6 V2 n
2000:7A84 C6 87 01 00 00 mov byte ptr [bx+1], 0$ d: S2 Y/ I2 @4 p( V6 x% b
2000:7A89 F8 clc
0 X4 _& K( n0 O- t% L7 U% M2000:7A8A exit: ; CODE XREF: Read_Header+199 `/ |1 `) N% O8 Q2 k: ?
2000:7A8A 61 popa
7 g3 }3 h5 L& f+ D, I% [4 q2000:7A8B C3 retn
" _5 I1 A, Z r' F4 Q) v4 c2000:7A8B Read_Header endp
" X4 T& d7 ~- U+ ?9 @9 M________________________________________8 x+ Y9 R1 \7 D' U
' d* Q1 S7 G l! m; v: i! |
2000:793D Calc_LZH_hdr_CRC16 proc near ; CODE XREF: Read_Header+2C
, Q2 s# T' s# G# H6 {% r* I6 r# {2000:793D 50 push ax
- t3 J! i# ~* I% L6 O: r2000:793E 53 push bx
# C) E9 U3 ]6 N( u7 f2000:793F 51 push cx
3 u; \, K& H8 ^; D+ k- ?7 M2000:7940 52 push dx: w; b" o a& d7 Y6 L* ?; \! G4 `' A
2000:7941 0F B6 0E 1C 57 movzx cx, byte ptr ds:571Ch
7 H! u( h2 N' ]1 l% _" Q0 K" a2000:7946 06 push es1 i3 Y3 _4 J' u! f
2000:7947 56 push si) y3 j( S. O( l9 W
2000:7948 8B 1E 02 01 mov bx, ds:102h% ^4 l4 d* f- h/ V M' |
2000:794C BE 00 00 mov si, 0
9 e! h1 t1 C6 q6 C& Z& L2000:794F next_byte: ; CODE XREF: Calc_LZH_hdr_CRC16+19% y* v7 V" G' o9 B$ d" c9 z. H
2000:794F E8 79 01 call Fetch_Byte
4 T: \ B+ f9 i2 n$ m y( v2000:7952 88 04 mov [si], al
: w) }9 g1 C5 ~% N2000:7954 43 inc bx4 U9 F+ h A4 X7 i
2000:7955 46 inc si* H7 {) `# y) c; M) G& v% ?' w
2000:7956 E2 F7 loop next_byte' N) x# y5 y' i
2000:7958 8B C3 mov ax, bx5 U. z! b6 t* h/ x
2000:795A 2B 06 02 01 sub ax, ds:102h
: J/ E- Y! Z6 u2000:795E 89 1E 02 01 mov ds:102h, bx
! b9 R! t. O- T8 P3 Y" Q" x5 j- m6 j2000:7962 5E pop si& `/ N! k0 A7 q
2000:7963 07 pop es
" |. ?8 W! }5 J/ H8 L0 ]3 o" _3 E2000:7964 A2 1C 57 mov ds:571Ch, al
: G7 f$ b, S$ P5 f2000:7967 8B C8 mov cx, ax8 c: K2 _7 ^6 o3 W! u
2000:7969 01 06 14 03 add ds:314h, ax" Z4 z! p! R! n" M
2000:796D 41 inc cx
/ s: `3 W* Y2 z7 v2000:796E BB 00 00 mov bx, 0% l$ S, P. v7 k& O- M' z: I8 I
2000:7971 next_CRC_byte: ; CODE XREF: Calc_LZH_hdr_CRC16+5E
. ~. g, f/ \. S9 p6 c2000:7971 0F B6 07 movzx ax, byte ptr [bx]
. D8 L; e& K3 `/ s# e7 P2000:7974 49 dec cx
, ?1 N5 V2 V$ V2000:7975 E3 26 jcxz short exit
: B# D D, B/ u' f/ F9 J0 l" [$ \2000:7977 50 push ax
/ V7 N- m* A7 z2 V% _% P+ a2000:7978 53 push bx
+ j; g) B1 ]6 f" a. y7 l2000:7979 56 push si1 w7 f) X$ c# T P$ s2 _1 O n
2000:797A 8B F0 mov si, ax
7 c/ B9 o2 l6 G/ ^2000:797C A1 0C 03 mov ax, ds:30Ch" G6 \9 J5 i+ b
2000:797F 33 C6 xor ax, si. w% s/ Y4 C* p9 y, N: I
2000:7981 25 FF 00 and ax, 0FFh3 T9 ?) A8 g0 l ^/ ~
2000:7984 8B F0 mov si, ax
3 I* @; f+ `% u: `1 _2000:7986 D1 E6 shl si, 1! a8 q2 c7 P1 E; Y
2000:7988 8B 9C 0C 01 mov bx, [si+10Ch]
% [2 V8 t$ b5 X) j$ x2000:798C A1 0C 03 mov ax, ds:30Ch" ]3 J( K- N. i3 c, s( x- C2 T
2000:798F C1 E8 08 shr ax, 8
/ f% ~* m& D5 Q4 r; d+ P2000:7992 33 C3 xor ax, bx4 O3 |8 \! l# O& h/ o3 S% o8 a
2000:7994 A3 0C 03 mov ds:30Ch, ax
N* Z1 u# g1 O" W2 o2000:7997 5E pop si
' v/ K' ~; w3 @4 Q- m) A2000:7998 5B pop bx
6 ~2 J: w2 {$ C4 a: p, e% o) u2000:7999 58 pop ax: ~# |4 I$ `) c4 a5 L2 H
2000:799A 43 inc bx
9 U0 M% v9 E$ h( x: V, q2000:799B EB D4 jmp short next_CRC_byte
$ E b! O% H2 H- {! l2000:799D ; ---------------------------------------------------------------------------: m) H5 |: S2 J' {: V @
2000:799D exit: ; CODE XREF: Calc_LZH_hdr_CRC16+38
; ^7 [% L1 _; U- a2000:799D 5A pop dx
5 @5 T6 H7 T1 A4 q: g" v2000:799E 59 pop cx( i- ^/ `' p$ c
2000:799F 5B pop bx( `' w8 m' |: d, y* V: C- ~
2000:79A0 58 pop ax2 e; m- o* |7 G6 p) k- I" U7 r
2000:79A1 C3 retn
- c$ y& ~( G) C1 |" J) O2000:79A1 Calc_LZH_hdr_CRC16 endp
3 e6 U( o& D7 C' |& ^+ [________________________________________# ^3 D. @" W" e4 r- |
3 ?5 @: H& @5 ^; b% ]1 D/ R% l2000:79A2 CalcHdrSum proc near ; CODE XREF: Read_Header+2F
9 Y, n; n" [# x9 T4 M2 c- D2000:79A2 53 push bx# |- b% p0 i$ ^& w7 g
2000:79A3 51 push cx! g3 Y+ s9 ?3 G+ g7 q7 J- t1 j8 w a
2000:79A4 52 push dx
7 f9 R& m; H5 T# P9 C* v" l2000:79A5 B8 00 00 mov ax, 0+ _) a+ v" B. u3 C- ^1 a8 c
2000:79A8 0F B6 0E 1C 57 movzx cx, byte ptr ds:571Ch! \. D# A* ]3 g& T. \
2000:79AD loc_2000_79AD: ; CODE XREF: CalcHdrSum+19 j6 b/ p+ e( A, @
2000:79AD 0F B6 1E 1C 57 movzx bx, byte ptr ds:571Ch
, N% ~. k* n: l2000:79B2 2B D9 sub bx, cx
6 [8 e9 N8 r+ j- W$ O8 |8 B2000:79B4 0F B6 97 00 00 movzx dx, byte ptr [bx+0]9 c4 ^, E: a: R1 v S0 T2 u
2000:79B9 03 C2 add ax, dx+ E# {0 q' L9 d, n! [& k
2000:79BB E2 F0 loop loc_2000_79AD" u* E7 E5 A, y5 \
2000:79BD 5A pop dx. |% ^8 t2 A9 G' t# h8 ?, b; r
2000:79BE 59 pop cx
8 i. @' k l/ Z4 ~) k2000:79BF 5B pop bx( p& ?# e6 k8 n( n& r
2000:79C0 25 FF 00 and ax, 0FFh3 {. f4 C# [1 D5 v2 l9 f
2000:79C3 C3 retn4 g6 R% ]7 m3 L9 w, c! _0 L: r1 l, y
2000:79C3 CalcHdrSum endp
* H3 `6 [/ _9 M7 `/ E! A$ t& n4 ~9 Z________________________________________
5 E6 D6 ^; \4 Q& ]
" U2 H* N9 I3 [. c0 }; ` K) `8 V+ C2000:79C4 --- GetFromHeader ---+ C( c+ g+ s7 C1 @
2000:79C4 in: bx = byte_index of the "component" to read
. D1 g% j4 \) s2000:79C4 cx = length of "component" to read
# F# i0 y* \, ~- |9 d" r2000:79C4: @( |5 H) _; q9 ]: h
2000:79C4 out: eax = dword_read6 d! L% t! x" x) R {; l" w" l
2000:79C4 ; --------------- S U B R O U T I N E ---------------------------------------
( h7 F Z9 H+ b8 x6 r) m2000:79C4 GetFromHeader proc near ; XREF: Read_Header+40
' z" t- a: ~2 q3 e/ C L2000:79C4 ; Read_Header+4D ...) a; K" L) Q% m* I7 a0 }
2000:79C4 53 push bx: E1 F$ w9 V% E% Y! L
2000:79C5 66 52 push edx: p$ L$ _1 u, X5 K% a6 M
2000:79C7 56 push si8 F# l- }7 x2 |; N# \
2000:79C8 66 33 C0 xor eax, eax
7 D! W; j, j `# L7 i2000:79CB 4B dec bx& m! L* q; ]! u/ Y6 X6 u0 i! w
2000:79CC 41 inc cx
O( U/ |1 ]. w; G, u/ c2000:79CD next_byte: ; CODE XREF: GetFromHeader+1D {+ ^/ s( r; B9 A, M8 i- `
2000:79CD 49 dec cx
( u3 x: [- o4 e6 k3 m! U2 K2000:79CE E3 13 jcxz short exit
% x/ V4 K% h2 _+ B I5 h. g2000:79D0 66 C1 E0 08 shl eax, 8 k& x0 a9 M% V$ f9 @/ w
2000:79D4 8B F3 mov si, bx
$ E$ A5 f7 H' @# G6 e2000:79D6 03 F1 add si, cx
# P* K6 V" ~! [" V2000:79D8 66 0F B6 94 00 00 movzx edx, byte ptr [si+0]
# d7 Z$ J" J8 |# Y( @2000:79DE 66 03 C2 add eax, edx
2 p& U) q* Y/ C. c# i& c6 Z. Z0 W2000:79E1 EB EA jmp short next_byte
, g1 x; \+ O6 P. l8 V4 |( N2000:79E3 ; ---------------------------------------------------------------------------
2 _ s' F. X: l! G2 u" u: A2000:79E3 exit: ; CODE XREF: GetFromHeader+A: V, O4 J, X+ I `& A* B: X
2000:79E3 5E pop si
- y5 b+ h" {- Y6 b% V2000:79E4 66 5A pop edx6 [5 t. d( ]+ V+ t: N1 I
2000:79E6 5B pop bx, g+ S. ]" f: f) e7 u0 y
2000:79E7 C3 retn4 s" F, }3 u2 L) ]4 j$ g# R3 o; b
2000:79E7 GetFromHeader endp
0 ?: s- ^# y9 \, ?看完这些彻底的线索,我们成功的构建映射了bios解压部分:8 ?% |9 q% @% l; ]( q* H! f4 Z
Starting address of decompressed BIOS component in RAM Compressed Size Decompressed Size Decompression State (by Bootblock code) Component description
. Y! e5 P2 ^- M- a: X( ]4100:0000h 3A85h 57C0h Decompressed to RAM beginning at address in column one. awardext.rom, this is a "helper module" for original.tmp
4 ~# ^2 Q$ B5 [4 w4001:0000h 5CDCh A000h Not decompressed yet cpucode.bin, this is the CPU microcode$ t& |9 b0 c+ v' Q5 b7 i4 a6 N4 H
4003:0000h DFAh 21A6h Not decompressed yet acpitbl.bin, this is the ACPI table$ J7 V5 Z6 Z1 ?; ^5 e+ J9 k
4002:0000h 35Ah 2D3Ch Not decompressed yet iwillbmp.bmp, this is the EPA logo, n4 x$ a, h( X/ u# x# E- H# `
4027:0000h A38h FECh Not decompressed yet nnoprom.bin, explanation N/A
( y/ x$ U, {2 n+ ]. d4007:0000h 1493h 2280h Not decompressed yet antivir.bin, this is BIOS antivirus code
: ^1 k1 |' ]/ C m# u% b9 E4028:0000h F63Ah 14380h Not decompressed yet ROSUPD.bin, seems to be custom Logo display procedure0 P$ p4 ?7 |' [: r& S- ^1 z
5000:0000h 15509h 20000h Decompressed to RAM beginning at address in column one. original.tmp, the system BIOS
6 J3 N1 D9 S7 V0 [* G注意:绿色覆盖的解压地址被另外的方法处理:
p' ~7 c0 r& l7 e% S; d7 h) yA. 上面解释的部分不是真正的被解压区域。只是某种真正解压区域的占有区域,稍后由original.tmp处理。结论是:在bootblock中只有original.tmp和awardext.rom被Decompress_System_Bios解压缩。如果你想改变这个,那么试着计算被解压代码的大小总和,他不会合适的!4 c6 W8 l5 [5 x3 r; a
B. 所有的这些被解压段地址部分被Decompression_Ngine procedure变换到4000h,就像你看到的在例程里面地址2000:7842h。4 h. T& m+ N+ n. X# K8 R
C. “(被解压)开始地址。。。”中的40xxh 实际上是一个ID,工作如下:40(高字节)是ID,标示它是一个扩展bios,将要在稍后的original.tmp执行时被解压缩。Xx是一个id,在original.tmp用到,标示要被解压缩的部分。这些在下面的original.tmp中会详细解释。! \8 D5 v/ O5 |* o+ D3 q. q
D. 所有的这些部分都要在original.tmp执行时被解压缩。解压结果被放在地址4000:0000h,但是不会在同一时刻。有一些(也许所有的)部分也要从那个地址重新定向,在另外的部分在那个地址被解压缩后保留他们的内容。这些在下面的original.tmp中会详细解释。
3 v" q- q; b, X% K& f2 _* @7.1.6.7. Shadow the BIOS code
7 K8 b, ]$ O/ H6 }; q5 }- g: p7.Shadow bios代码。假设解压例程成功的完成了,上面的例程接着拷贝被解压得system bios(original.tmp),从RAM中的5000:0000h - 6000:FFFFh到E_0000h - F_FFFFh。完成如下:1 }8 j$ N0 m' C" ]
1)重新编程北桥shadow RAM控制寄存器,使能只写到地址E_0000h - F_FFFFh,促进写操作这个地址范围到DRAM(没有到bios rom芯片)。. R, \! r# Z2 i E& d% s l! {
2)进行一个字符串拷贝操作,拷贝被解压了的system bios(original.tmp),从5000:0000h - 6000:FFFFh到E_0000h - F_FFFFh。1 Z2 }! x# A$ W) F' [( {
3)重新编程北桥shadow RAM控制寄存器,使能只读到地址E_0000h - F_FFFFh ,促进读操作这个地址范围到DRAM(没有到bios rom芯片)。这个也是对system bios 代码写保护+ p% Q8 n$ I" Y! O1 _1 b E
7.1.6.8. Enable the microprocessor cache then jump into the decompressed system BIOS& P# a: A( H4 N9 \
8.使能微处理高速缓存,然后跳转到压缩的system bios。这一步是普通bootblock代码执行路径的最后一步。使能处理器高速缓存后,代就会跳转到RAM地址F000:F80Dh中的写保护的system bios(original.tmp),如上面看到的代码。这个跳转的目的地址好像在不同的award bios中都一样。
6 e" W: K9 `# d. B, C 现在我要呈现在跳转到解压缩的original.tmp之前,压缩的和解压的bios部分的内存地图。这个很重要,因为这会在等会的分析解压缩了的original.tmp方便我们。现在我们不得不注意,所有的代码都在RAM中之行,在没有代码在bios rom芯片中执行了。5 |- y: _( e4 K
Address Range in RAM Decompression State (by Bootblock code) Description
$ z, W( d9 F5 t3 a" f! ]$ _0 Q0000:6000h - 0000:6xxxh N/A This area contains the header of the extension component (component other than original.tmp and awardext.rom) fetched from the compressed BIOS at 8000:0000h - 9000:FFFFh (previously BIOS component at FFFC_0000h - FFFD_FFFFh in the BIOS chip). Note that this is fetched here by part of the bootblock in segment 2000h.
H S- @7 G: B* p3 F a6 r @1000:0000h - 2000:5531h Compressed This area contains the compressed original.tmp. It's part of the copy of the last 128KB of the BIOS (previously BIOS component at E000:0000h - F000:FFFFh in the BIOS chip). This code is shadowed here by the bootblock in BIOS ROM chip./ p6 H, ~0 |2 Q; Z5 j9 T
2000:5532h - 2000:5FFFh Pure Binary (non-executable) This area contains only padding bytes.
, ~4 w$ q! A; S! P$ K2000:6000h - 2000:FFFFh Pure binary (executable) This area contains the bootblock code. It's part of the copy of the last 128KB of the BIOS (previously BIOS component at E000:0000h - F000:FFFFh in the BIOS ROM chip). This code is shadowed here by the bootblock in BIOS ROM chip. This is where our code currently executing (the "copy" of bootblock in segment 2000h).$ G/ l G, w+ Q4 C& {2 U
4100:0000h - 4100:57C0h Decompressed This area contains the decompressed awardext.rom. Note that the decompression process is accomplished by part of the bootblock code in segment 2000h.1 c2 Z; g) ^$ f4 g G
5000:0000h - 6000:FFFFh Decompressed This area contains the decompressed original.tmp. Note that the decompression process is accomplished by part of the bootblock code in segment 2000h.$ T. |, E8 M# e8 U O
8000:0000h - 9000:FFFFh Compressed This area contains the copy of the first/lower 128KB of the BIOS (previously BIOS component at FFFC_0000h - FFFD_0000h in the BIOS chip). This code is copied here by the bootblock code in segment 2000h.2 I3 W2 n; c- Y. K$ j$ i
E000:0000h - F000:FFFFh Decompressed This area contains copy of the decompressed original.tmp, which is copied here by the bootblock code in segment 2000h.
2 ^3 i; P% s# p5 d( k
. \( f- B Z( ]' `8 q 最后要注意:这里解释的booblock只涉及到了normal Bootblock code execution path ,意思是没有解释一旦original.tmp崩溃时的bootblock POST。有时间的话,我将要涉及到。所有的bootblock如上,我们将要开始研究original.tmp。2 W5 i2 M ~& ]- H6 F* K+ I. Q
7.2. System BIOS a.k.a Original.tmp
$ C8 W+ R- z) _) L5 e+ s 我们刚进行了上面的bootblock,我要高亮晦涩的代码执行路径。所以,现在,你正在看我的bios的解压了的original.tmp的反汇编代码。4 G* S7 [+ a' d' E" k+ n y
7.2.1. Entry point from "Bootblock in RAM"
% F' W4 {7 _" E5 X! yAddress Hex Mnemonic
4 P# M7 z2 l6 Y0 C* G5 Q6 e9 KF000:F80D This code is jumped into by the bootblock code $ {! E: k- I& O# W* u
F000:F80D if everything went OK
' X( x" Y" E; g4 HF000:F80D E9 02 F6 jmp sysbios_entry_point ;
- _3 `" W5 l d这里是在重新定位和写保护system bios后,bootblock跳转的地方。* }& ]# V, Y2 j: O4 \
7.2.2. The awardext.rom and Extension BIOS Components (lower 128KB bios-code) Relocation Routine
* r, c( y7 ]' p' a8 Y# c9 iAddress Assembly Code# o6 X! T P- ^8 H3 f" b
F000:EE12 sysbios_entry_point: ; CODE XREF: F000:F80D6 b# ~- ~; k) X- w0 `0 B
F000:EE12 mov ax, 0
0 b/ s, Y" o7 R$ p: u0 Z* SF000:EE15 mov ss, ax ; ss = 0000h1 I0 }+ E1 z9 e& W) i" ~/ ?
F000:EE17 mov sp, 1000h ; setup stack at 0:1000h
, c$ L/ c4 D; v' [' E' F KF000:EE1A call setup_stack ; Call Procedure
0 r) h) X' c/ j/ @3 W0 A" TF000:EE1D call init_DRAM_shadowRW ; Call Procedure
2 X& D! E! M1 A$ L) V9 MF000:EE20 mov si, 5000h ; ds=5000h (look at copy_mem_word)
5 E# d# E" D# a6 p% ?F000:EE23 mov di, 0E000h ; es=E000h (look at copy_mem_word)4 Y/ U0 g2 Q- V+ Y
F000:EE26 mov cx, 8000h ; copy 64KByte
7 Q3 D& a3 C5 q) q2 gF000:EE29 call copy_mem_word ; copy E000h segment routine, i.e.% P! R/ R- K) c/ Z" h, W, y
F000:EE29 ; copy 64Kbyte from 5000:0h to E000:0h
9 S. `* s2 E+ m3 B$ o4 IF000:EE2C call j_init_DRAM_shadowR ; Call Procedure ^8 o- Z2 M2 H" b4 ?6 g
F000:EE2F mov si, 4100h ; ds = XGroup segment decompressed, i.e.$ U$ Z$ C9 x( G
F000:EE2F ; at this point 4100h) o* G. K: n2 l" T4 m) g& G
F000:EE32 mov di, 6000h ; es = new XGroup segment1 l2 r/ e" R3 ]1 b
F000:EE35 mov cx, 8000h ; copy 64KByte* d% H+ g( L- q4 u6 R- p8 f! P1 X
F000:EE38 call copy_mem_word ; copy XGroup segment , i.e. ; h8 L+ h8 [) `' u# R. X
F000:EE38 ; 64Kbyte from 4100:0h to 6000:0h) f0 O1 M" M; E! g7 Z1 b
F000:EE3B call Enter_UnrealMode ; jump below in UnrealMode
" W7 I. T! j3 j) TF000:EE3E Begin_in_UnrealMode; J# X2 o0 U) d4 |8 g$ @$ W* c
F000:EE3E mov ax, ds, d! }+ u( ~, w
F000:EE40 mov es, ax ; es = ds (3rd entry in GDT)
8 H) T! R2 ~0 W1 i3 @F000:EE40 ; base_addr=0000 0000h;limit 4GB
) z7 ^7 Z6 u; y/ ~5 CF000:EE42 assume es:nothing
2 w/ O7 A. v( n/ qF000:EE42 mov esi, 80000h ; mov esi,(POST_Cmprssed_Temp_Seg shl 4)
( @) Z; [# l! ^F000:EE42 ; relocate lower 128KB bios code# F4 S) V# i/ v
F000:EE48 mov edi, 160000h6 \3 z% N, w) E0 l) M9 _6 P7 y
F000:EE4E mov ecx, 8000h
$ V: ]: q. s; H# |F000:EE54 cld ; Clear Direction Flag- h! G. k; |" K& ]
F000:EE55 rep movs dword ptr es:[edi], dword ptr [esi] ; move
. D+ a: u% ]& D% D/ `F000:EE55 ; 128k data to 160000h (phy addr)$ y1 ]6 ]2 M' u0 O7 N) h! J: c b& v
F000:EE59 call Leave_UnrealMode ; Call Procedure2 Z& `5 }4 T5 }. {& A! G9 @
F000:EE59 End_in_UnrealMode: O% U4 q$ [: g5 h- ~9 P9 C9 c6 B
F000:EE5C mov byte ptr [bp+214h], 0 ; mov byte ptr
! h' p- z: X& EF000:EE5C ; POST_SPEED[bp],Normal_Boot
: k# `6 e0 g+ h' T+ f4 A- }F000:EE61 mov si, 626Bh ; offset 626Bh (E000h POST tests)8 W* H2 y' j g3 T, C1 a
F000:EE64 push 0E000h ; segment E000h# ]* W; ]1 j g: @5 P
F000:EE67 push si ; next instruction offset (626Bh)+ s# P7 O( ~# [: @: N* r
F000:EE68 retf ; jmp to E000:626Bh/ E4 i# ]. R/ h, z4 P- ~9 t
________________________________________
- w$ E$ R H6 ~2 n" a. b7 g7 j# Y1 c: ~3 J
F000:7440 Enter_UnrealMode proc near ; CODE XREF: F000:EE3B; X8 `) r, x9 ?, v, A! B" r0 x1 a
F000:7440 mov ax, cs
+ _8 ]) q& b+ h# RF000:7442 mov ds, ax ; ds = cs
& y3 U: B5 a9 o6 CF000:7444 assume ds:F0009 u, b6 k% L$ n- C7 Y
F000:7444 lgdt qword ptr GDTR_F000_5504 ; Load Global Descriptor Table Register
" A% `5 D1 x$ YF000:7449 mov eax, cr0" _4 Q- T' m% C! Q7 k% O2 v
F000:744C or al, 1 ; Logical Inclusive OR
! n; f* z2 |% e9 j: e) @8 }% s3 aF000:744E mov cr0, eax5 u: K2 k! C3 L3 K
F000:7451 mov ax, 10h
4 @- v. v- N9 b7 ~3 nF000:7454 mov ds, ax ; ds = 10h (3rd entry in GDT) s- [+ ]) Z0 \9 u3 L
F000:7456 assume ds:nothing
8 t; S6 d, k* `& fF000:7456 mov ss, ax ; ss = 10h (3rd entry in GDT)
6 ^, D4 N k3 s$ M+ m" W5 UF000:7458 assume ss:nothing
" i3 V0 c$ S% r2 ?3 r! [F000:7458 retn ; Return Near from Procedure
0 `* L! z. n( C1 e. |. F% Z- GF000:7458 Enter_UnrealMode endp
+ p5 k. \$ L; ]- U: C7 t* S: p________________________________________
4 @" W! U! s1 @" K5 Y3 N# ^1 G8 O: }& V$ M8 g( S
F000:5504 GDTR_F000_5504 dw 30h ; DATA XREF: Enter_PMode+4
5 D, U* d: Q+ T/ c1 iF000:5504 ; GDT limit (6 valid desc)
) g) l5 p1 }6 ^! A2 J, E" `5 `. aF000:5506 dd 0F550Ah ; GDT phy addr (below)
, R: F; a! t! b% [F000:550A dq 0 ; null desc- x6 M* l7 y& Y _
F000:5512 dq 9F0F0000FFFFh ; code desc (08h)2 I1 p) m1 ^- [2 l+ n ~
F000:5512 ; base_addr=F0000h;seg_limit=64KB;code,execute/ReadOnly
( G3 ?$ e! y4 r# t% K7 l9 CF000:5512 ; conforming,accessed;granularity=1Byte;16-bit segment;- M! J3 s& b7 Q& c0 s
F000:5512 ; segment present,code,DPL=0
/ L+ k1 w% y3 U9 NF000:551A dq 8F93000000FFFFh ; data desc (10h)3 s' q3 N5 L1 g( l; ]
F000:551A ; base_addr=0000 0000h;seg_limit=4GB;data,R/W,accessed;
+ o* f* k8 {7 ZF000:551A ; granularity=4KB;16-bit segment; segment present,
3 G8 a! c0 }5 K! ?F000:551A ; data,DPL=0
' d' h' c% y+ j/ C ~F000:5522 dq 0FF0093FF0000FFFFh ; data desc 18h
1 [7 G7 N5 T% K8 b$ V jF000:5522 ; base_addr=FFFF0000h;seg_limit=64KB;data,R/W,accessed;
& ^7 R. U* \2 h" b/ F ?F000:5522 ; 16-bit segment,granularity = 1 byte;- t- a, k j0 g
F000:5522 ; segment present, data, DPL=0.
$ y+ L$ E4 W/ |$ U8 B7 OF000:552A dq 0FF0093FF8000FFFFh ; data desc 20h1 i; j7 U# Q4 w1 e9 H
F000:552A ; base_addr=FFFF8000h;seg_limit=64KB;data,R/W,accessed;* _7 B. H/ e. b1 g3 S% p
F000:552A ; 16-bit segment,granularity = 1 byte;/ B% y' ]' r" @6 U& {3 ]
F000:552A ; segment present, data, DPL=0.& z% k# @/ V7 R: P; F; b
F000:5532 dq 930F0000FFFFh ; data desc 28h3 k! i2 ] s! w5 k A7 W
F000:5532 ; base_addr=F0000h;seg_limit=64KB;data,R/W,accessed;
, w/ F6 w7 m" }% ZF000:5532 ; 16-bit segment,granularity = 1 byte;. W! y$ E; Q% o2 b! o2 s1 T0 M7 _
F000:5532 ; segment present, data, DPL=0.
. g3 T) R8 {8 I3 f8 N________________________________________
7 i$ V6 s7 J: X7 W- W. x8 \注意:上面的代码执行以后,这个内存地图就再改变了一次。但是这个时候,只对于压缩BIOS扩展,比如低128KB的bios代码和解压缩了的awardext.rom,在上面bootblock解释到的内存地图部分的被覆盖了。
' x) A, g, V7 ?) Q5 q- wNew Address Range in RAM Decompression State Description
* F1 G& J, P$ A) v8 b9 b6000:0000h - 6000:57C0h Decompressed This is the relocated awardext.rom
1 E6 a! G% |& T# D6 K160000h - 17FFFFh Compressed This is the relocated compressed "BIOS extension", including the compressed awardext.rom. (i.e. this is the copy of FFFC0000h - FFFDFFFF in the BIOS rom chip.
5 l. s4 @$ M, v6 e, q' _
1 G- }5 `# V: y8 k8 j- |+ {% e7.2.3. Call to the POST routine a.k.a "POST jump table execution"
1 I/ b' K8 V9 p5 P9 g+ [8 e) d/ QAddress Assembly Code. Y* \% T2 K, U- H" n1 m- t
E000:626B The last of the these POST routines starts the EISA/ISA
0 A9 Y4 m7 B6 {E000:626B section of POST and thus this call should never return.
+ Y0 G7 Z: O8 K3 H2 yE000:626B If it does, we issue a POST code and halt.# r; ~' c" h1 }8 @8 O4 }( L
E000:626B 4 [% i6 e/ u. D% U% p
E000:626B This routine called from F000:EE68h
4 L! P( q: s( U4 D- f) A- C5 rE000:626B
/ N& [' H/ W1 H/ ?( [, ?; UE000:626B sysbios_entry_point_contd a.k.a NORMAL_POST_TESTS' _: Z0 u2 p: W$ k2 P6 G
E000:626B mov cx, 3 ; mov cx,STD_POST_CODE
$ H' c( y3 c4 @- c: lE000:626E mov di, 61C2h ; mov di,offset STD_POST_TESTS
2 v7 o# D: W# C" O5 R; C2 A# JE000:6271 call RAM_POST_tests ; this won't return in normal condition
1 o: H3 i f: w+ u* hE000:6274 jmp short Halt_System ; Jump
' k( b4 e+ _5 Z/ I7 E________________________________________1 ^/ y8 S p( T8 i; L/ ]8 ^
2 F: z1 e% P, D- [5 k7 ]' W
E000:6276 ; --------------- S U B R O U T I N E ---------------------------------------+ F" `' \# \5 k. |7 p
E000:6276 2 b0 Q/ a3 {9 L+ `* K9 O; X
E000:6276 RAM_POST_tests proc near ; CODE XREF: last_E000_POST+D
& Q& e4 ?, h2 C1 y& u; F4 ]E000:6276 ; last_E000_POST+18 ...: c8 _5 c/ p$ @4 {* @
E000:6276 mov al, cl ; cl = 35 L6 N4 [, j- X( x$ l
E000:6278 out 80h, al ; manufacture's diagnostic checkpoint) l4 W6 @# i4 @; f" v) i
E000:627A push 0F000h8 R: C9 D1 v, p
E000:627D pop fs ; fs = F000h \5 M, p( {/ |' k+ K
E000:627F & v: H/ j: m+ r8 R
E000:627F ;This is the beginning of the call into E000 segment ! P8 } A) @# e; O- d
E000:627F ;POST function table
1 f- H$ {- ] h$ G, zE000:627F assume fs:F000
4 `! j, \0 x6 j1 S- ME000:627F mov ax, cs:[di] ; in the beginning :
9 F, Z; }* u9 F. M; Z! _3 kE000:627F ; di = 61C2h ; ax = cs:[di] = 154Eh; P( Q$ v) @/ {7 \& P
E000:627F ; called from E000:2489 w/ di=61FCh (dummy)
( A% P9 V" v0 W& D+ Y5 ~E000:6282 inc di ; Increment by 1+ _/ J+ \6 ~/ x* V& Y0 @
E000:6283 inc di ; di = di + 2
8 h" N/ j J/ Z9 w8 A @E000:6284 or ax, ax ; Logical Inclusive OR4 n; ^. O4 F* j' v( @4 ~9 a' Q1 B
E000:6286 jz RAM_post_return ; RAM Post Error- I& X N3 @3 M( w$ M
E000:6288 push di ; save di; A4 }* c8 G4 w5 A W8 M; l
E000:6289 push cx ; save cx
% {5 i& |3 g' H8 X, M5 kE000:628A call ax ; call 154Eh (relative call addr) ! e5 P6 v1 h, p+ X, c$ I
E000:628A ; ,one of this call 9 Q3 U( ] i+ D- `0 h& r
E000:628A ; won't return in normal condition3 L% y k# C/ I
E000:628C pop cx ; restore all% _, f; C3 q: b9 T3 y
E000:628D pop di
$ w+ R2 ?, ]+ \ {/ H+ ]1 GE000:628E jb RAM_post_return ; Jump if Below (CF=1)& Z6 i" d5 I9 w0 C" W
E000:6290 inc cx ; Increment by 1
+ o$ Y3 q9 j/ C7 b FE000:6291 jmp short RAM_POST_tests ; Jump& Y* x" f9 Z; S+ ?
E000:6293 ; ---------------------------------------------------------------------------5 v; i; m& m) L
E000:6293 # H" g- o5 I+ h& x) U) Y* d
E000:6293 RAM_post_return: ; CODE XREF: RAM_POST_tests+108 Q o$ n7 H/ l( z
E000:6293 ; RAM_POST_tests+18
+ ]/ n1 f7 @* E7 F) ]E000:6293 retn ; Return Near from Procedure; _- K9 o0 }* }
E000:6293 RAM_POST_tests endp
6 W9 Z6 F+ Y) f* r0 p________________________________________9 C8 Q4 f3 j9 p/ }# K) D$ W# t
7 r/ ]+ i& H3 x" N7 \/ T
E000:61C2 E0_POST_TESTS_TABLE:) q, W" z+ V: N# F" y3 j* h
E000:61C2 dw 154Eh ; Restore boot flag. g- O" \) ]; m* Z& Q+ I; r! `
E000:61C4 dw 156Fh ; Chk_Mem_Refrsh_Toggle
/ v5 J" K/ c8 p" I/ u: {, Z; ME000:61C6 dw 1571h ; keyboard (and its controller) POST( ^) J9 B1 Z$ Y8 ~0 B! R4 X
E000:61C8 dw 16D2h ; chksum ROM, check EEPROM
+ r9 m# k. h7 F! P: \4 @; _E000:61C8 ; on error generate spkr tone
" y0 q D9 F+ m1 e7 h% C, xE000:61CA dw 1745h ; Check CMOS circuitry- Y4 {6 ~: S0 p
E000:61CC dw 178Ah ; "chipset defaults" initialization
* z' O9 s8 ^7 O5 d+ rE000:61CE dw 1798h ; init CPU cache (both Cyrix and Intel)
- s8 v4 N& u' h1 CE000:61D0 dw 17B8h ; init interrupt vector, also initialize 7 J, l: W. k0 z9 M
E000:61D0 ; "signatures" used for Ext_BIOS components ; Q1 B- Q/ N! ^) x! M& l" ~$ b6 s
E000:61D0 ; decompression$ A/ S0 E, b2 z
E000:61D2 dw 194Bh ; Init_mainboard_equipment & CPU microcode' t9 A# d, H3 I# D8 V) `1 h* g5 n
E000:61D2 ; chk ISA CMOS chksum ?8 X, A; V: c0 b, s" O% I, Q. m" g
E000:61D4 dw 1ABCh ; Check checksum. Initialize keyboard controller( ?+ S! }- C4 d
E000:61D4 ; and set up all of the 40: area data.* } ]# L5 h: l$ ~+ R) n
E000:61D6 dw 1B08h ; Relocate extended BIOS code
- x! a. g6 G8 ^E000:61D6 ; init CPU MTRR, PCI REGs(Video BIOS ?)! _. a7 c$ L* C2 T: Q" y* `" _7 A
E000:61D8 dw 1DC8h ; Video_Init (including EPA proc)
: C" S) S1 s& B+ V& ?9 G+ \4 }+ Y8 LE000:61DA dw 2342h6 Q5 Z3 m9 R4 Z2 _; o, L, p8 x
E000:61DC dw 234Eh0 z' E. u9 q' r: g' C
E000:61DE dw 2353h ; dummy
& x4 g4 E& u/ u K& v+ YE000:61E0 dw 2355h ; dummy
2 H$ z5 A6 m% B( J. g* LE000:61E2 dw 2357h ; dummy
3 G3 m) ^# Z( ~# x4 A, z8 pE000:61E4 dw 2359h ; init Programmable Timer (PIT)
. w1 L# l" T. k! i; `; d7 _2 b9 o* u0 E9 QE000:61E6 dw 23A5h ; init PIC_1 (programmable Interrupt Ctlr)
4 r+ t& N! x1 I; S% r2 tE000:61E8 dw 23B6h ; same as above ?
, ~8 e7 X% D0 R6 SE000:61EA dw 23F9h ; dummy8 L0 p6 ?# H6 x* r, }( Y
E000:61EC dw 23FBh ; init PIC_2% [+ B) U. p1 y( u3 e
E000:61EE dw 2478h ; dummy, j8 E0 f4 A; J( E
E000:61F0 dw 247Ah ; dummy) `2 r- l6 b1 s/ u# R. y) C2 D
E000:61F2 dw 247Ah
: G- ~1 H% X% h7 W3 n4 VE000:61F4 dw 247Ah/ A7 I' u @% z( [$ b1 s' W
E000:61F6 dw 247Ah k7 C1 f" t/ o) n; \# o) k
E000:61F8 dw 247Ch ; this will call RAM_POST_tests again ( `9 H8 e4 l3 ~& W4 F
E000:61F8 ; for values below(a.k.a ISA POST)- }* |7 j+ x: c( [# d; R
E000:61FA dw 0
( P; P4 M5 A7 Q% a% A, }E000:61FA END_E0_POST_TESTS_TABLE: y: \' p9 g- T0 G3 V9 p$ L, J
________________________________________
. ~3 @% Z) l; |9 }1 i, r" n5 ?* b+ R$ S2 d5 R
E000:247C last_E000_POST proc near
! G9 N* l3 ~$ f, W, X LE000:247C cli ; Clear Interrupt Flag
e3 C0 b5 ], D& yE000:247D mov word ptr [bp+156h], 0
5 u: N; P8 K3 l4 P" [+ eE000:2483 mov cx, 30h ; '0'# C; {( J( ]* O6 c7 I
E000:2486 mov di, 61FCh ; this addr contains 0000h
5 Q _% V2 a2 f. I5 g" zE000:2489 ) O2 x8 s# U) v3 u. d" I' {
E000:2489 repeat_RAM_POST_tests: ; CODE XREF: last_E000_POST+10 N% T( K: E& l$ w3 z
E000:2489 call RAM_POST_tests ; this call immediately return
" o# I( r5 @$ k( y6 z# r( mE000:2489 ; since cs:[di]=0000h
1 J0 ~ z s; z. B- bE000:248C jb repeat_RAM_POST_tests ; jmp if CF=1; not taken) z" |: Y% l+ ]# }, p# p1 j
E000:248E mov cx, 30h ; '0'
9 o! k4 Z$ F; w* F {5 JE000:2491 mov di, 61FEh ; cs:[di] contains 249Ch3 ]4 ]) | u9 p) h% H
E000:2494
% W1 j0 E+ H- [9 u* H$ ]; {0 e& G+ zE000:2494 repeat_RAM_POST_tests_2: ; CODE XREF: last_E000_POST+1B
; g5 Q Y$ W! H: h5 ^ x* xE000:2494 call RAM_POST_tests ; this call should nvr return if- t0 p" m% F& Z, z
E000:2494 ; everything is ok, e' W- h& g' o2 Z A b
E000:2497 jb repeat_RAM_POST_tests_2 ; Jump if Below (CF=1)
, G1 E, K7 p8 i2 P. xE000:2499 jmp Halt_System ;
* U0 r3 C4 }0 c: f/ @" OE000:2499 last_E000_POST endp7 r6 h! P$ r9 P8 O" ]" t$ ?3 V. i( x
________________________________________& d5 ]6 @3 `1 u; z3 v. w
) \. Z: c8 |2 z. [5 z& Q" oE000:61FC ISA_POST_TESTS
/ F. p4 b) G( S9 ~: x$ RE000:61FC dw 0& J/ u: l* h- o" l; l8 K8 ]: I
E000:61FE dw 249Ch
/ B" o3 Z/ r& ^4 ?" OE000:6200 dw 26AFh! i. J& W7 {% ^! M o+ n! Z
E000:6202 dw 29DAh
+ c% w2 |8 H" A1 O, ^' X* I+ m TE000:6204 dw 2A54h ; dummy
7 X7 p# m" z$ ^$ I) [2 xE000:6206 dw 2A54h# p& F% e" F& A: V! Q! q6 c z
E000:6208 dw 2A54h* l8 M. e5 k& U9 f
E000:620A dw 2A54h
) V; G/ B1 X- T# S5 }5 A: d+ ]E000:620C dw 2A54h
/ n% V* b# a! P: K0 |/ M. YE000:620E dw 2A54h
9 T. n5 i' z2 \0 {E000:6210 dw 2A56h ; dummy2 a6 b* O; E3 d5 n
E000:6212 dw 2A56h) [/ z& a9 f" C7 R( u/ k9 j
E000:6214 dw 2A56h) [% K' r O, F( \. a0 b1 Z
E000:6216 dw 2A58h5 m3 t1 c8 d- `7 ?* @
E000:6218 dw 2A64h
4 M x! @% u6 j7 C5 r- u& s' p' iE000:621A dw 2B38h: O9 v9 s: a* e6 U
E000:621C dw 2B5Eh ; dummy
4 Z9 G% Y$ ~& n2 e! JE000:621E dw 2B60h ; dummy
' V# }$ }1 C p, {1 ]) {) r6 Z* [+ O$ RE000:6220 dw 2B62h
) {5 r( g% \+ o* gE000:6222 dw 2BC8h ; HD init ?/ w' X Q6 W. E5 z% e, U
E000:6224 dw 2BF0h ; game io port init ?
/ `; m' K- k) A) J" dE000:6226 dw 2BF5h ; dummy" ]8 `2 \6 _* c
E000:6228 dw 2BF7h ; FPU error interrupt related, @# F0 u$ N' S+ {9 Z" n. R3 Q
E000:622A dw 2C53h ; dummy
" V. I8 f q6 b' ME000:622C dw 2C55h
; k+ k+ p; s# E1 k2 L# sE000:622E dw 2C61h ; dummy$ w5 Y& N. s8 o7 B4 j6 g, W
E000:6230 dw 2C61h
5 Y2 g& a4 ?6 M* Q/ @$ ~* kE000:6232 dw 2C61h
) l1 j' W) n% ^9 q3 O$ W3 }; k1 AE000:6234 dw 2C61h' z5 X/ h7 v4 O& n
E000:6236 dw 2C61h
8 B) o2 z3 h K; T. A+ l" s) D7 TE000:6238 dw 2C61h4 G2 d; q9 F7 l& R
E000:623A dw 2CA6h$ }% r4 A6 m/ O. s# Y6 f
E000:623C dw 6294h ; set cursor charcteristic+ @! w; F5 \ Q2 y. ]9 E
E000:623E dw 62EAh$ z- o4 [; q- f
E000:6240 dw 6329h
$ L; H# \6 U6 @6 |: Z) WE000:6242 dw 6384h
- |0 j5 Z4 w. K) G" A5 `E000:6244 dw 64D6h ; dummy( `# z' u; K/ D" b! Z% p
E000:6246 dw 64D6h
. n9 R/ g, a+ V3 Q3 `) u7 P- {E000:6248 dw 64D6h
8 r) `8 y# k" h. N0 F, xE000:624A dw 64D6h
& x4 N5 [2 L* @ J* X! f" A$ _E000:624C dw 64D6h
5 |5 Q; a6 R; E8 V7 K" s3 @" t" a% Z$ RE000:624E dw 64D6h2 L, u+ Z5 d) f6 Q+ C
E000:6250 dw 64D6h
* v9 K( h# U; h3 ]* @* j) i9 Q2 }E000:6252 dw 64D6h6 m0 |# l3 e) y/ q/ [) P& `
E000:6254 dw 64D6h
3 _, Q) d* B0 Q; {2 V) |/ }: s# yE000:6256 dw 64D6h2 p; V+ Z2 Q! l* `1 r( V
E000:6258 dw 64D6h
4 `! O* n! g) _) O4 uE000:625A dw 64D6h
( I' b6 y. C8 Y2 O" PE000:625C dw 64D6h
7 n2 |3 o; `$ h. i4 ]1 aE000:625E dw 64D8h ; bootstrap
2 f: p3 _+ c2 `$ g1 [E000:6260 dw 66A1h {" c0 l1 V) z+ }, v
E000:6262 dw 673Ch
" U) t1 l3 @8 Q7 oE000:6264 dw 6841h ; issues int 19h (bootstrap)3 w. q" l0 R9 p6 o$ u% }
E000:6266 dw 0
I: {% v" c2 Z0 P LE000:6266 END_ISA_POST_TESTS t4 f- {0 z3 o+ Q- ]8 O
: }% C' v6 e( m. C& c" E3 A注意:) ^8 S, @9 Q: d# P
这个“POST jump table”例程在他们遇到一些执行错误的时候会设置Carry Flay(CF=1)。在POST例程返回,这个Carry Flag就要被测试,如果它被设置,然后这个“RAM_POST_TESTS”就会立刻返回,这样就会使系统崩溃,系统扬声器就会发出声音。:) |
|