天天爱天天做天天做天天吃中文|久久综合给久合久久综合|亚洲视频一区二区三区|亚洲国产综合精品2022

  • 
    
    <delect id="ixd07"></delect>

      1. <span id="4bvar"></span>
        <table id="4bvar"></table>
        <button id="4bvar"><cite id="4bvar"></cite></button>

        汶上信息港

        標(biāo)題: About anti-SoftICE tricks [打印本頁(yè)]

        作者: hbhdgpyz    時(shí)間: 2008-9-28 16:34
        標(biāo)題: About anti-SoftICE tricks
        <TABLE width=500>, n( @# {  U% |. I( w5 N
        <TBODY>) C4 v# @# j% R* G# W8 l) `1 ?
        <TR>6 }8 F$ B) n/ `1 d% Q$ C# D
        <TD><PRE>Method 01
        ) a( N6 [0 N$ v/ J=========4 w! S3 n8 l$ s+ N# \2 p; G
        + Q- t' i0 [, Y2 m
        This method of detection of SoftICE (as well as the following one) is
        / g; v  U1 A# P8 xused by the majority of packers/encryptors found on Internet.7 x# V* K& k4 I& m, F4 r; r0 g+ D
        It seeks the signature of BoundsChecker in SoftICE0 F) f2 {, N6 e, H% X5 b- ?

        ' ?6 w9 h  S% m" [9 B$ k7 l    mov     ebp, 04243484Bh        ; 'BCHK'
        , f% M9 D; \8 E9 x- X/ [8 A    mov     ax, 04h
        ! |9 f, P% D9 w9 c/ m! A- m    int     3       2 O8 d4 b) ]9 s3 J: T5 X/ y8 c
            cmp     al,4- {# f7 z5 ?& v: C
            jnz     SoftICE_Detected7 J! |& Z# R9 Z) h6 {; b
        7 ^3 a1 [, W& k4 l0 l7 L/ R6 C0 e( u
        ___________________________________________________________________________+ o# J9 Y7 S% `, ~4 [3 E

        & o/ Q$ q8 [* d! xMethod 02" Y6 ]- _7 s( e
        =========
          ]( J# N# @% O3 R+ J
        ; ~8 j9 v- n0 {/ n2 n) c( e: MStill a method very much used (perhaps the most frequent one).  It is used
        6 G, K" p: [) ~- N, Q  M- _to get SoftICE 'Back Door commands' which gives infos on Breakpoints,2 V$ o( e3 C5 S! b6 Y$ }% E3 C
        or execute SoftICE commands...
        % ]. `. {( w7 f5 C& t* z3 QIt is also used to crash SoftICE and to force it to execute any commands
        + q$ W8 l/ B7 V( ]! @. p2 h+ ~" I(HBOOT...) :-((  : a+ `! s# `0 F, G! ^

        # m0 W0 o3 C$ B, FHere is a quick description:6 ]7 f# B( e3 `6 n- Z, N% K# U' w- P
        -AX = 0910h   (Display string in SIce windows)
        : N& W$ ]" o, f" |8 C; ~-AX = 0911h   (Execute SIce commands -command is displayed is ds:dx)
        ' ?( f7 u  V1 \6 q-AX = 0912h   (Get breakpoint infos)
        ( T! F4 S  N; @( @/ F-AX = 0913h   (Set Sice breakpoints). G$ |+ R3 Z  ~! {0 }
        -AX = 0914h   (Remove SIce breakoints)
        5 E2 D) S. H( E1 i" `7 s5 P5 G! h* }- }/ G3 j- |3 x0 t3 r1 x
        Each time you'll meet this trick, you'll see:
        . w+ d: d' E, f  b-SI = 4647h" |2 M$ q+ a6 H
        -DI = 4A4Dh: p9 M- X9 A& m* Q5 f1 H& J$ j3 e
        Which are the 'magic values' used by SoftIce.# a- n1 b2 @2 Q; a+ |- R
        For more informations, see "Ralf Brown Interrupt list" chapter int 03h.2 d. c+ [2 j* a% q2 c

        # O* O5 O  D% E- F4 U6 JHere is one example from the file "Haspinst.exe" which is the dongle HASP
        ' |4 D% v, }: M7 F5 iEnvelope utility use to protect DOS applications:
        / E) R! |; e+ E% x6 P; x  v2 Y7 C: F9 M$ f

        * r9 l! d& S* W7 X4C19:0095   MOV    AX,0911  ; execute command.
        - k7 |) ]1 A/ W* k" y& d4C19:0098   MOV    DX,[BX]  ; ds:dx point to the command (see below).
          L% x1 B2 X) H5 n- @4 l2 _9 E4C19:009A   MOV    SI,4647  ; 1st magic value.
          o7 R8 [& V) ]& p4 |8 P, B4C19:009D   MOV    DI,4A4D  ; 2nd magic value.
        5 V7 Y- j3 w& |3 u: C5 T( K4C19:00A0   INT    3        ; Int call.(if SIce is not loaded, jmp to 00AD*)
        " w- m; {5 t6 A, p2 T4C19:00A1   ADD    BX,02    ; BX+2 to point to next command to execute: B" n# M& z- I. ~  s
        4C19:00A4   INC    CX
        5 A; a" e8 j* N. C: K4C19:00A5   CMP    CX,06    ; Repeat 6 times  to execute0 a; ?' K, p' E5 [: ?4 v( M
        4C19:00A8   JB     0095     ; 6 different commands.
        8 c. L+ X! o: o! A4 x6 a2 G4C19:00AA   JMP    0002     ; Bad_Guy jmp back.) L% E; I5 R. J/ U/ q! t. Q, T
        4C19:00AD   MOV    BX,SP    ; Good_Guy go ahead :)
        ' F) y' i. S* p3 Y: y2 r. R/ d
        - \. A9 E  O% fThe program will execute 6 different SIce commands located at ds:dx, which& S% D( H9 `% K
        are: LDT, IDT, GDT, TSS, RS, and ...HBOOT.
        ! e1 l$ ~) a/ H8 Z% I. d9 k1 w
        1 W9 [3 u9 c$ ]- O* the "jmp to 00ADh" is performed via an SEH if the debugger is not loaded.( s% _3 n, A( t- a: i( C
        ___________________________________________________________________________
        % Y) a% b. O" K* n$ A' z" \' K1 o8 h3 l7 j4 l
        3 `! W& z9 B% B' ~# w! t$ b2 @# X
        Method 037 d1 o+ a' @) H$ ?% L  Z9 a
        =========6 F7 P$ \# F! g
        + v* y) h* l: Z( Y# \
        Less used method.  It seeks the ID of SoftICE VxD via the int 2Fh/1684h
        ( |  ^& v6 X: F  u6 C(API Get entry point)
        ' Y$ Q9 t/ w; l9 \) v' z- d        3 s. S$ _5 O) w1 I6 B' u5 x

        ( ~/ G0 ?' \9 C7 m1 y8 \4 p    xor     di,di
        , j. Q0 t3 B+ t( l6 o    mov     es,di
        * X8 o! A* K1 Y/ \! K0 x; s    mov     ax, 1684h       ; O) M- s/ A; G7 |( N& a8 s! h
            mov     bx, 0202h       ; VxD ID of winice
        * ]5 }8 s. N- i! v5 E    int     2Fh: L7 T& M! v9 g( t
            mov     ax, es          ; ES:DI -&gt; VxD API entry point+ y& L0 g9 V2 l$ e
            add     ax, di, @9 |7 i; u  T6 g
            test    ax,ax
        & B6 D  J5 @6 d: ^9 T+ n    jnz     SoftICE_Detected- b+ o/ |2 n0 l$ ^2 p

        $ J4 q2 s5 f/ K___________________________________________________________________________! `7 O9 x- O9 z" x

        ; Y# O: {: D7 H: {Method 04
          A' D. S- V3 E=========( C* D# l! a! J% t8 T2 v) \

        0 ]& l/ f9 {4 g! R/ FMethod identical to the preceding one except that it seeks the ID of SoftICE; f: @8 U- O) y9 z+ h! }4 @7 q( \
        GFX VxD.4 m! e, o" i; S" ~
        3 y; X, c, ?! v0 l* e) K
            xor     di,di. N5 M0 I: ~/ e2 f$ P. ]/ W
            mov     es,di, U, @# j: S# @9 A9 Q6 O
            mov     ax, 1684h      
        3 _7 a6 {# c$ d    mov     bx, 7a5Fh       ; VxD ID of SIWVID
        , q' m9 W  @: Q: t2 O9 L    int     2fh# J' n  s& c$ w% p$ t
            mov     ax, es          ; ES:DI -&gt; VxD API entry point0 o% Z  z2 M& Y9 F& L8 F: x
            add     ax, di) U5 E) n' Q$ S4 ^+ L$ ~
            test    ax,ax
        % e0 r0 y# F( Q2 Z/ j+ K0 a2 O# G    jnz     SoftICE_Detected
        / ^( q* {4 h1 L  p2 S: [# M3 A7 h4 L9 m- D- X: ^2 {0 M
        __________________________________________________________________________: }/ C( ^( F* m5 F) J
        ( r$ J5 H1 u/ _+ y" y
        ( g) _, @6 g# {1 d( P
        Method 05
        # o5 A' E5 I" [=========
        6 e+ R8 z0 ?' B4 T! e# p
        ! {% t" A2 N# f6 W- m+ bMethod seeking the 'magic number' 0F386h returned (in ax) by all system
        : M+ y; N4 |$ m. e1 Udebugger. It calls the int 41h, function 4Fh.
        7 B& {+ Z* n( Y- ?9 b2 {' q, m4 h& uThere are several alternatives.  
        - E7 d9 e) n4 W3 t! Q. v, y* i1 G2 P/ L) C9 _* k
        The following one is the simplest:7 Q4 s* ?1 Z4 y! D$ \
        4 ?9 ^' r+ n# C2 ]& j5 g
            mov     ax,4fh# d8 ?7 o7 y1 h9 l( z( B
            int     41h6 m& `$ U3 m0 S6 O5 u
            cmp     ax, 0F386
        - g& Z7 l$ O+ r6 a, t; B    jz      SoftICE_detected
        3 o/ }. ^4 a5 _% s, h9 B4 |8 W+ s5 G6 A, a% ^) t* _% C
        7 R+ s* L! x& R5 k/ N
        Next method as well as the following one are 2 examples from Stone's ! @: ~* i) r3 Z0 |; C8 y# L- E
        "stn-wid.zip" (www.cracking.net):- |7 n& h, B% T9 T

        1 v" N$ e/ K; \: G" @1 v: S    mov     bx, cs2 E# {# ]0 O' c+ ^6 x. L7 }9 ^
            lea     dx, int41handler24 Q) M. }+ |9 v3 [7 s
            xchg    dx, es:[41h*4]
        . k. ~* }* x$ C! n    xchg    bx, es:[41h*4+2]
        / R- w' n+ e) y7 q' v( Y. b! F6 g! G    mov     ax,4fh% U3 o1 x# \; @! @
            int     41h0 z1 Y3 _4 T8 G. y& k5 I4 U5 f
            xchg    dx, es:[41h*4]9 s* {9 C& ]' ]9 J7 e7 s5 B* }
            xchg    bx, es:[41h*4+2]1 j! U4 |( t* i/ x) B
            cmp     ax, 0f386h0 e) f! c- O) I  H+ n. H; j9 K
            jz      SoftICE_detected5 J4 I! P5 R# |2 j! z5 n

        , q; D! |! h! P& }& ]int41handler2 PROC& L% |+ P3 \0 T9 [* u
            iret; _. |7 p& k) q6 a4 L3 z1 q) k7 q
        int41handler2 ENDP
        ( A5 r+ C: w+ u- J8 ~5 e' f
        ! _. Z) m$ Y; e2 M
        2 O$ V- [+ t! V_________________________________________________________________________
        $ F; H, g+ D% f
        2 B, y: }( d: ]5 W8 }/ F( I
        , n) p: M* l3 f+ eMethod 06
        / d0 b! N& x' n1 h2 P0 z=========
        ( s: `" A. h0 r1 l% Z* Y; A8 y; y4 @
        3 ~  R2 E4 k0 @: x! `2 e# j+ H" T' _
        2nd method similar to the preceding one but more difficult to detect:" H) A- Z" r4 B) p
        5 O. M3 [# g- j. S' \6 O

        ! p' L* X+ g3 P3 a+ Eint41handler PROC
        7 I9 E2 n6 V1 X) s    mov     cl,al5 E6 G, p1 q$ B  |) u( t' b
            iret. u- E+ n4 ~" ~/ H+ v6 _
        int41handler ENDP
        0 B- c5 Z5 X3 I, h0 C% a2 I& h
        6 H3 `9 B5 x. I& k
        $ g) Y" T3 L2 _# H    xor     ax,ax
        / w: V4 |* j3 D2 [7 o9 `: G+ s    mov     es,ax
        ) T8 d5 b5 `2 [- ]    mov     bx, cs$ R8 D4 K6 O4 G2 l# O
            lea     dx, int41handler
        5 P, \2 j0 m0 ~% t% |    xchg    dx, es:[41h*4]
        5 K! E- u: R# d$ {4 M( I    xchg    bx, es:[41h*4+2]
        " l4 h9 l0 Z/ c- r2 ?" x3 h1 w$ F    in      al, 40h3 V9 X; c) c) M. Z" O- ~  J
            xor     cx,cx3 o" A$ m; m7 [3 L
            int     41h# H" A6 q* U: l! @! V' R  n
            xchg    dx, es:[41h*4]
        8 `: e- P8 U% H    xchg    bx, es:[41h*4+2]3 q) q: o' p1 [0 W  J2 h" o0 @
            cmp     cl,al2 z2 d$ p6 s& t' z
            jnz     SoftICE_detected
        / L7 `- z+ I8 |3 ?* C9 p9 Z$ r, n5 h( e6 }, R
        _________________________________________________________________________
        , T9 a7 ~9 q" P+ B- Q5 M
        , m* T1 @* o/ v9 v) BMethod 07
        1 g4 ?- ?1 M( f& F, A- R! E5 ?, c=========1 o. E8 O2 D' ^/ B1 \$ D

        ! z6 u/ b7 G, S, e5 KMethod of detection of the WinICE handler in the int68h (V86)
        # B6 ], _# e1 }0 R* }) F, z- h" e* {$ J! l$ _8 ]/ T
            mov     ah,43h
        " k7 F* A2 `4 F3 X5 w    int     68h
        7 O- u7 u7 ]. {- G( l    cmp     ax,0F386h
        & D( [0 a/ K6 [# A    jz      SoftICE_Detected
        % I$ R6 \7 W! e' v$ D5 N( k+ T4 ?6 N: ?, \5 D4 g( R
        " w) X- v: I" k9 ?0 C
        =&gt; it is not possible to set a BPINT 68 with softice but you can hook a 32Bit
        0 Z3 X9 m: i6 P* S7 U, ~0 K   app like this:
        : h5 _6 c  c; u& z7 v0 \
        6 V' [# s) P1 h! Q, {   BPX exec_int if ax==68: @" U, K8 x7 B7 Y" P! V
           (function called is located at byte ptr [ebp+1Dh] and client eip is5 i5 G& o# h: {$ s8 ]2 s0 l4 z
           located at [ebp+48h] for 32Bit apps)
        3 U/ P! a  q3 g! P0 E8 N& Y__________________________________________________________________________
        8 G5 @$ L9 A  x. b4 o9 W4 g& Y# Y& O( k; \

        7 C/ _) R2 ^5 I3 t4 h8 mMethod 08
        6 v3 n5 G( W) }# W+ G: y=========
        5 f6 x5 R6 a+ x5 U2 L7 j8 y+ j) M  a% m6 B1 l. z, }+ O1 Z# A
        It is not a method of detection of SoftICE but a possibility to crash the  m4 G2 v8 w- v9 i2 ~+ q! U
        system by intercepting int 01h and int 03h and redirecting them to another: l  B5 }' X( v  V1 h. U
        routine.
        + @+ u! J6 `$ q$ I9 y) M, D6 `It calls int 21h functions 25h and 35h (set/get int vector) and ds:dx points
        * f4 N! ]; O, [( f" [; d- Tto the new routine to execute (hangs computer...)
        # ]8 o/ i( i3 c9 }4 p  d
        2 s- H6 [7 l/ L' j" B9 ?) ?0 ?# h    mov     ah, 25h* t4 T1 l. o$ \% E: y
            mov     al, Int_Number (01h or 03h)
        2 i+ h( x/ w2 j0 P: [4 l5 L+ |6 W3 U    mov     dx, offset New_Int_Routine
        4 l0 G6 a' z( y) z- J4 A& o    int     21h5 j8 Q2 J0 O& H8 }- n
        6 ^+ R- m7 ]; p1 D
        __________________________________________________________________________, p+ u; h; q2 t# x& H

        9 S8 d! v/ D* u( ^Method 09
        ! {/ B) j7 p& r5 N=========% @: j( y) I" F4 n# b) T8 x& o  f
        0 b+ a* E. X  W; D8 x8 |
        This method is closed to methods 03 and 04 (int 2Fh/1684h) but it is only
        2 T, G0 {3 H( Eperformed in ring0 (VxD or a ring3 app using the VxdCall).
        ' \( S2 v6 b- T# e9 o# EThe Get_DDB service is used to determine whether or not a VxD is installed
        & }5 ]7 j. _- U: u2 qfor the specified device and returns a Device Description Block (in ecx) for
        . k1 T4 S! I& r( ?' `/ u  ~) dthat device if it is installed.1 W, n* @4 ~3 u5 z0 k  ~! |# F7 r

        9 W- T6 `- r# M1 A+ n   mov     eax, Device_ID   ; 202h for SICE or 7a5Fh for SIWVID VxD ID
        8 g; S! q6 d# q7 @4 {   mov     edi, Device_Name ; only used if no VxD ID (useless in our case ;-)
        " Y( q, C3 u' D5 h, s3 h2 W   VMMCall Get_DDB; D) f0 q6 o! q
           mov     [DDB], ecx       ; ecx=DDB or 0 if the VxD is not installed
        ' v' @% z) M  ~; `  c8 ]1 X" G, Z* K! K! A7 }& u7 c& P+ I& |
        Note as well that you can easily detect this method with SoftICE:' k# U! W! \+ q7 D! M# O7 q" {/ e3 p  v
           bpx Get_DDB if ax==0202 || ax==7a5fh1 S9 G6 ?4 m2 Y6 m# F( d

        + z1 C2 i1 Q3 M# f/ `/ S__________________________________________________________________________! X$ {0 q0 S* _( ]/ `2 w
        , F( ~0 R, O! _  B! }! T
        Method 10
        # Y! v5 `+ ?# s5 h4 @' T' }' E4 I8 Y=========
        . g9 z& C& z+ H2 d. x- W2 k
        8 N% }$ J. k4 X$ J/ A* {=&gt;Disable or clear breakpoints before using this feature. DO NOT trace with
          Z$ I$ H+ X: u% {  U  SoftICE while the option is enable!!- [3 }* |: x! [) \( v' w

        ; ]0 t/ G+ v3 T$ |4 n0 y, [. I  J6 p- bThis trick is very efficient:
        6 R0 H3 i# C% w% O- X3 m- [" hby checking the Debug Registers, you can detect if SoftICE is loaded
        0 w, y/ h0 G; \8 z" t- j(dr7=0x700 if you loaded the soft with SoftICE loader, 0x400 otherwise) or if
        % q0 h& j2 c$ f" Y7 Fthere are some memory breakpoints set (dr0 to dr3) simply by reading their8 m8 e% D  y4 x  o: }2 s
        value (in ring0 only). Values can be manipulated and or changed as well
        2 l0 _3 K. M! H4 }(clearing BPMs for instance)8 w  s0 ~6 u9 y1 I; w

        - ^) g3 h, t6 D! ^7 a* p__________________________________________________________________________
        ) Q) t% w2 e& Q3 f+ J' |6 S8 O4 v/ ~7 F" y7 K, T
        Method 11
        : h' n$ z3 D5 z1 ^8 G- }=========) C8 u# _6 k) S& ?1 R2 l- C
        + m/ k1 N# v( C: M; Z2 d
        This method is most known as 'MeltICE' because it has been freely distributed
        * {$ U7 }% n: ?" jvia www.winfiles.com. However it was first used by NuMega people to allow0 S3 ~; |: n4 ~! ^- x' H3 h
        Symbol Loader to check if SoftICE was active or not (the code is located7 f3 Z: W7 L. d  V% {: Z) K* |
        inside nmtrans.dll).
        7 h" c9 X" i7 P2 N4 P  L7 I. R! o2 E) e' w7 {( R
        The way it works is very simple:
        9 C+ o9 Q( G' V% a" BIt tries to open SoftICE drivers handles (SICE, SIWVID for Win9x, NTICE for
        5 N5 D, L7 D( y" V4 {WinNT) with the CreateFileA API.
        8 u; ?; N. R: z2 X- j: j  c. W- e
        ; |2 x; R% ~% C( i& yHere is a sample (checking for 'SICE'):
        8 A' Z3 ?1 P9 D* k; ?7 Y" w& z! u9 F$ r7 \$ j) p3 }1 P
        BOOL IsSoftIce95Loaded()
        4 X. L* T# G7 b. S7 C2 \1 m5 @{3 E# w7 J' F: v! i0 B# ~
           HANDLE hFile;  
        # u. t- z/ z. l, F   hFile = CreateFile( "\\\\.\\SICE", GENERIC_READ | GENERIC_WRITE,4 Y; X2 P; \- }/ E4 o: E7 R
                              FILE_SHARE_READ | FILE_SHARE_WRITE,8 f. W" h% |4 V9 B, H
                              NULL, OPEN_EXISTING, FILE_ATTRIBUTE_NORMAL, NULL);$ J) G( \4 M, U) z: t2 M# q! y1 B
           if( hFile != INVALID_HANDLE_VALUE )
        ( f5 H# n4 u  ?1 `: t   {1 S% q& p+ @* S
              CloseHandle(hFile);
        : g& i3 Y4 o" M5 Q      return TRUE;2 a6 h# O6 h, k/ q% u' B8 W' C6 Z
           }4 d4 m. c, q# Z6 S' w3 B
           return FALSE;
        / k0 o, Z$ E1 b}
        4 O- Z8 t, t5 q+ T9 J& j5 h' g/ Z0 c- R. w
        Although this trick calls the CreateFileA function, don't even expect to be$ v" ~% S5 G! @: Z2 K
        able to intercept it by installing a IFS hook: it will not work, no way!. i; k/ y: }% S0 J) K; o2 V& v: O( e: y; ~
        In fact, after the call to CreateFileA it will get through VWIN32 0x001F& G% j) |7 |2 Z- W
        service _VWIN32_ReleaseWin32Mutex (via Kernel32!ORD_0001/VxDCall function); [+ I2 S6 {" T/ h) g. ^: @
        and then browse the DDB list until it find the VxD and its DDB_Control_Proc  E7 G/ y( P7 P6 J  W8 R) v3 v% T
        field.) P. B6 _2 m) t. B* l" G
        In fact, its purpose is not to load/unload VxDs but only to send a ' y6 d$ m3 t9 J4 `, I
        W32_DEVICEIOCONTROL (0x23) control message (DIOC_OPEN and DIOC_CLOSEHANDLE)' l' n' p- y) |) \& G1 R9 ^
        to the VxD Control_Dispatch proc (how the hell a shareware soft could try: H* Z2 C) t2 I
        to load/unload a non-dynamically loadable driver such as SoftICE ;-).
        5 v/ ^- V+ J$ T7 V$ k6 P7 H3 E4 ]# [( tIf the VxD is loaded, it will always clear eax and the Carry flag to allow
        ' h, n8 k- H) mits handle to be opened and then, will be detected.' F' `* W2 E4 r
        You can check that simply by hooking Winice.exe control proc entry point
        ; b1 I+ x0 ^$ R" f' [: O' q3 Jwhile running MeltICE.! G0 o# O, T2 y: {5 X- O. k
        8 B( E  I; S) S8 A/ l" F
          f- Q& O5 ?6 @8 U9 W8 S% n0 S
          00401067:  push      00402025    ; \\.\SICE1 P! I5 f* j0 {& g4 s7 c8 v2 K* s; p
          0040106C:  call      CreateFileA
        4 ^& Q6 R- Q: Y" ]$ L  00401071:  cmp       eax,-001  U& M( f0 z) T7 T
          00401074:  je        004010915 Q4 k  E1 W2 l( u4 G& Z; ?) f5 @

        4 r6 _& a; R( x! z# w
        & S" K" O/ Z, b( E! L& z( f5 V% KThere could be hundreds of BPX you could use to detect this trick.
        . B; x7 p; f$ Q2 R-The most classical one is:+ e# m: D- H) G. `: L
          BPX CreateFileA if *(esp-&gt;4+4)=='SICE' || *(esp-&gt;4+4)=='SIWV' ||
        4 L+ K1 e, r# i/ t0 ~8 D    *(esp-&gt;4+4)=='NTIC'
        ' g2 S$ u/ M$ W/ U; O& S8 X* ^: n7 t: R+ D% X$ k
        -The most exotic ones (could be very slooooow :-(
        & g9 B+ v" c" v- n" s7 c% r   BPINT 30 if eax==002A001F &amp;&amp; (*edi=='SICE' || *edi=='SIWV')  
        3 A& Y+ G. ]! `. F2 N/ n     ;will break 3 times :-(
        $ E4 w% S# [- Q: y$ i% ^9 w* [1 z+ v7 M( i  d8 O
        -or (a bit) faster: ' B8 g- h# I* r1 A9 c+ b
           BPINT 30 if (*edi=='SICE' || *edi=='SIWV')! b* z7 [0 ]1 Q) C# A2 ^; H

        / d6 L1 j4 @! n, M7 D- c   BPX KERNEL32!ORD_0001 if *edi=='SICE' || *edi=='SIWV'  
        / A9 W' y& f9 S/ \     ;will break 3 times :-(9 @, b2 h  w2 Q6 j+ T

        ) S+ X9 y5 Y8 t# ]7 t" o-Much faster:2 Y8 k8 k  q3 J6 H! K( U5 P
           BPX VMM_GetDDBList if eax-&gt;3=='SICE' || eax-&gt;3=='SIWV'
        2 }4 v  ^* e4 e8 }) s$ ?* i+ j
        / I) m( W% E+ J& LNote also that some programs (like AZPR3.00) use de old 16-bit _lopen! \6 L+ M, E" l
        function to do the same job:  Q5 D0 b% W- _+ t1 a. g) H

        . z0 k5 z1 G  J9 s   push    00                        ; OF_READ5 |) j/ W0 P/ r: R
           mov     eax,[00656634]            ; '\\.\SICE',0+ q1 Q& g0 w  f$ \% X! s
           push    eax
        & {: N: r* {) e% s3 c  L   call    KERNEL32!_lopen
        % `/ V( e- [3 H( O   inc     eax
        ( b: K7 k0 u3 ]9 K   jnz     00650589                  ; detected, q2 N0 Q/ [3 V1 g8 A1 W/ m* _$ A
           push    00                        ; OF_READ
        8 B% @5 w1 M6 W) q/ J  m; `& ^   mov     eax,[00656638]            ; '\\.\SICE'" k0 N$ \  ]7 ^4 ?
           push    eax
        0 U$ L& t# v1 {% m; a! v, R6 k" }0 n   call    KERNEL32!_lopen
        + G$ R! R1 r0 {" w   inc     eax6 Z" ]2 B+ [  O1 d$ z( i) B7 J
           jz      006505ae                  ; not detected, e6 Y5 ^! f& d1 g- d% V; a
        & k- J2 m; f9 W' U6 i
        5 \, {3 S! u# T3 a
        __________________________________________________________________________
        % m$ r( m1 w% e" H" ^1 v
          D, X8 Y2 l5 u! Q( k# R8 O! AMethod 12
        : n1 F4 {) t- B# V% U3 A=========1 D+ a. R/ F" y/ W4 S0 U
        # s" R1 f' B* T: H
        This trick is similar to int41h/4fh Debugger installation check (code 053 O6 o4 v3 T5 j" P$ j
        &amp; 06) but very limited because it's only available for Win95/98 (not NT)5 K$ `4 z3 y# _4 q5 T9 Q& ^) X
        as it uses the VxDCall backdoor. This detection was found in Bleem Demo.
        2 k- l( J$ w3 ~# I
        2 C) S7 ?; L' y8 E6 P   push  0000004fh         ; function 4fh
        1 _# Q" I7 C7 U; F7 q   push  002a002ah         ; high word specifies which VxD (VWIN32)
        ! L; r/ y5 t/ k  ~: }                           ; low word specifies which service4 Y7 ~7 b2 e/ h8 K
                                     (VWIN32_Int41Dispatch)6 x5 m4 @0 R* ~# F9 D1 M" \
           call  Kernel32!ORD_001  ; VxdCall4 N" `0 G* i6 r( K8 \% d
           cmp   ax, 0f386h        ; magic number returned by system debuggers
        1 N; `+ w4 j" d) f1 u: K   jz    SoftICE_detected2 T- n' J6 k+ m8 z( t" k3 P7 N

        * ~! r! K9 ]& ~- uHere again, several ways to detect it:
        3 `/ k: z$ a$ }/ o. q
        # a- F  j5 _$ P  F9 e" f3 `    BPINT 41 if ax==4f" B- U5 ]+ A5 [; J
        * Y7 ]+ d1 P( g
            BPINT 30 if ax==0xF386   ; SoftICE must be loaded for this one/ z3 m" ]7 y3 ]3 U" W1 z

        ; v2 }' a3 Q- A3 U: v- E    BPX Exec_PM_Int if eax==41 &amp;&amp; edx-&gt;1c==4f &amp;&amp; edx-&gt;10==002A002A4 S6 L. X9 ]  E2 a+ z! ]8 ~7 x
        0 k+ _* C: R' W& W% e/ P
            BPX Kernel32!ord_0001 if esp-&gt;4==002A002A &amp;&amp; esp-&gt;8==4f   ; slooooow!
        8 z+ I3 P- O, \) B! a
          A/ u7 x8 i" \( l" J+ J__________________________________________________________________________
        " |/ U8 C9 C3 V% f
        6 v' }& x- @# i# Y4 q9 Y( ZMethod 13
        , z9 Q9 u& I6 h& x/ T* i9 [  o5 Q=========0 {/ |0 A+ P. Q# B: `) n- @

        " z* s8 Q7 B1 Z2 u& t; c2 I# W' N2 jNot a real method of detection, but a good way to know if SoftICE is
        8 s2 a, K- n2 @  U2 g2 C  Pinstalled on a computer and to locate its installation directory.# m6 c* U9 `1 f* j
        It is used by few softs which access the following registry keys (usually #2) :3 n, C- w/ x$ {/ j8 ~* `# p

        + K0 x) L! f7 Z& {-#1: HKEY_LOCAL_MACHINE\Software\Microsoft\Windows\CurrentVersion4 [- J) \* j5 W! @/ A* c2 L' Y" g
        \Uninstall\SoftICE+ @2 k, }& B8 f& P
        -#2: HKEY_LOCAL_MACHINE\Software\NuMega\SoftICE( ~! v! V: d  h( p
        -#3: HKEY_LOCAL_MACHINE\Software\Microsoft\Windows\CurrentVersion) p7 c# k# X( V( B
        \App Paths\Loader32.Exe# F5 o0 H3 {6 e+ S

        ; ^: P5 f' h8 H# L# b4 `, p* Z" P8 j+ f# z9 h8 S! j
        Note that some nasty apps could then erase all files from SoftICE directory& I+ u, {3 a9 B/ j% a
        (I faced that once :-(
        / E7 G& r" a9 d9 f7 ~
        2 F) ?* A1 @' JUseful breakpoint to detect it:
        - K7 p' z% r& x4 d# @2 H! e# E2 Y3 o  c, d" [
             BPX _regopenkey if *(esp-&gt;8+0x13)=='tICE' || *(esp-&gt;8+0x37)=='tICE'! `3 r5 K' V9 Q; }) B
        * g- W' D6 i/ F  \8 H: @! P
        __________________________________________________________________________0 q5 J% x; C" q  C
        : K. J2 S) w' N- O, j- N
        2 c3 W9 n' v5 m. _* D; L2 Q, s
        Method 14 # X  u7 ]3 q9 m' k1 ]
        =========
        2 N+ A5 [7 O& h' b4 t% ~7 H0 ]& ?! l5 x; g, w# i7 r" s$ e$ R
        A call to VMM 'Test_Debug_Installed' service. As the name says, its purpose$ U* D% R8 [! S9 b+ h9 N3 |) ~
        is to determines whether a debugger is running on your system (ring0 only).
        0 ^, r; {6 H; z% W" C, f6 v. s5 o" q- I7 ]; g
           VMMCall Test_Debug_Installed
        8 E) L" p: |  }& ?5 x. I) [   je      not_installed4 [: V7 \. \/ p+ ^
        1 a3 s1 |1 `% p1 }$ S2 g
        This service just checks a flag.
        7 |0 `5 Z: w- N7 C$ |$ Q4 e  A6 ?</PRE></TD></TR></TBODY></TABLE>




        歡迎光臨 汶上信息港 (http://vancelump.com/) Powered by Discuz! X3.5
        <label id="pgeyg"><xmp id="pgeyg">

        <span id="pgeyg"></span>
        <label id="pgeyg"><xmp id="pgeyg">
        1. <button id="pgeyg"><cite id="pgeyg"></cite></button>