| 123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543 |
- .286
- decoder segment
- assume cs:decoder, ds:decoder, es:decoder
-
- jumps
- cMAX_FILE equ 10
- cNAME_LEN equ 12
- cPASS_LEN equ 20
- cBUF_SIZE equ 300
-
- start:
-
- push ds ;save PSP address
- ; Check command line
- cmp byte ptr ds:[80h], 0
- je install
- cmp word ptr ds:[82h], 'u/'
- je remove
- install:
- push cs cs
- pop ds es
-
- mov ax,0DEADh ;our decoder residency check
- int 21h ;
- cmp bx,0CAFEh ;>CAFE :o)
- je already_resident ;its already resident
- ;----------------
- ; Read files&passwords
- mov ax, 3d00h
- mov dx, offset fname
- int 21h
- jc exit_prog
- xchg bx, ax
- mov ah, 3fh
- mov cx, cMAX_FILE*cNAME_LEN
- mov dx, offset files
- int 21h
- mov ah, 3eh
- int 21h
-
- mov ax, 3d00h
- mov dx, offset pname
- int 21h
- jc exit_prog
- xchg bx, ax
- mov ah, 3fh
- mov cx, cMAX_FILE*cPASS_LEN
- mov dx, offset passwords
- int 21h
- mov ah, 3eh
- int 21h
-
- pop ds
- push ds ;PSP address back into DS
- ;--------------------------------------------------
- mov ax,ds ;MCB residency
- dec ax
- mov ds,ax
-
- sub word ptr ds:[3],80h ; Decrease the size of Memory Block by 2Kb
- sub word ptr ds:[12h],80h ; Same, but in PSP
-
- xor ax,ax
- mov ds,ax
- mov ax, 2
- sub word ptr ds:[413h], ax ; Decrease BIOS data's free space by 2Kb
-
- mov ax,word ptr ds:[413h] ; Calculate page number of free 2Kb of space
- shl ax,6
-
- mov es,ax
-
- push cs
- pop ds
-
- lea si, [RES_BEG] ; Copy our prog there
- xor di,di
- mov cx, the_end - RES_BEG ; Size of interrupt handlers
- rep movsb
- ;--------------------------------------------------
- xor ax,ax ;Setting of interrupts
- mov ds,ax
-
- mov ax,es
- mov bx,0 ; Offset to interrupt in new address
- cli
- xchg bx,word ptr ds:[21h*4]
- xchg ax,word ptr ds:[21h*4+2]
- mov word ptr es:[old_int21h-RES_BEG],bx
- mov word ptr es:[old_int21h+2-RES_BEG],ax
- sti
- ;--------------------------------------------------
- push cs cs
- pop ds es
-
- mov ah,9 ; Installed OK message
- lea dx,[message]
- int 21h
- exit_prog:
- pop ds ;Restore PSP in DS
- mov ax,4c00h ;Request terminate program
- int 21h
- ;-----------------------------------------------------------------
- ; Resident begins here
- RES_BEG:
- new_int21h: ;our int 21h handler
- pushf ;push the flags
- cmp ax,0DEADh ;residency check
- jne no_install_check
- mov bx,0CAFEh ;already resident
- popf ;restore all flags
- iret ;return
- no_install_check:
- cmp ax, 0DEDDh
- je uninstall
- cmp ah, 4bh ;check if execute
- je infect
- cmp ah, 4ch ;check if terminate
- je terminate
- return:
- popf ;restore all flags
- db 0eah ;jmp to orig int 21h
- old_int21h dd ?
- ;--------------------------------
- uninstall:
- pusha ;only 286, saves all gen reg
- push ds
- push es
- push cs
- pop es
- xor ax,ax
- mov ds,ax
-
- inc word ptr ds:[413h] ;Increase BIOS data's free space by 1Kb
- cli
- xchg bx,word ptr es:[old_int21h-RES_BEG]
- xchg ax,word ptr es:[old_int21h+2-RES_BEG]
-
- mov word ptr ds:[21h*4],bx
- mov word ptr ds:[21h*4+2],ax
- sti
- pop es
- pop ds
- popa
- popf ;restore all flags
- iret ;return
- ;-------------------------------
- infect:
- pusha ;only 286, saves all gen reg
- push ds
- push es
- call tsr_delta
- tsr_delta:
- pop bp ;a tsr delta offset %-)
- sub bp, offset tsr_delta
- push ds
- push dx
- ; Test, if currently opening file is in database
- mov di, dx
- call SeekZ
- push di
- std
- mov al, '\'
- repnz scasb
- cld
- jnz $+3
- inc di
- inc di
- pop cx
- sub cx, di
- push cx
- push di
- mov dx, 12
- push cs
- pop es
- lea di, es:[bp+files]
- searchloop:
- pop si
- pop cx
- push cx
- push si
- push di
- mov al, es:[di]
- jz not_found
- repz cmpsb
- jz found
- pop di
- add di, dx
- jmp searchloop
- found:
- pop di
- pop si
- pop cx
- ; Calculate offset to password
- ; Get number of file in table
- lea si, es:[bp+files]
- sub di, si
- mov ax, di
- mov bx, cNAME_LEN
- xor dx, dx
- div bx
- mov bx, cPASS_LEN
- mul bx
- lea di, es:[bp+passwords]
- add di, bx
- mov es:[bp+pass], di
- push cs
- pop ds
- mov cx, cPASS_LEN
- mov al, ' '
- repnz scasb
- jnz $+3
- inc cx
- sub cx, cPASS_LEN
- neg cx
- mov es:[bp+pass_len], cx
- pop dx
- pop ds
- jmp decode_file
- not_found:
- pop di
- pop si
- pop cx
- pop dx
- pop ds
- jmp exit
- ;------------------------------------
- decode_file:
- mov ax,3d02h ;open file in DS:DX
- int 21h
- jc exit
-
- xchg ax,bx ;file handle to bx
- mov cs:[bp+handle], ax
-
- push cs cs
- pop ds es
-
- mov ah,3fh ;Read the target header
- lea dx,[bp+header] ;into our buffer
- mov cx,1ch
- int 21h
- mov ax, word ptr [bp+header+12h] ; Test if program is our coded prog
- cmp ax, 'CD'
- jnz close
- ;-------------------------
- ; Decode all the file
- ;-------------------------
- ; Calculate count of encode bytes
- mov ax, 4202h
- xor cx, cx
- xor dx, dx
- int 21h
- mov cx, dx ; Hi part
- mov dx, ax ; Lo part
- mov bx, word ptr [bp+header+8]
- mov ax, bx
- shr ax, 12
- push ax
- shl bx, 4
- sub cx, ax
- sub dx, bx
- push dx
- mov cx, ax
- mov bx, [bp+handle]
- mov ax, 4200h
- int 21h
- pop dx
- pop cx
- buf_loop:
- push cx
- push dx
- sub dx, cBUF_SIZE
- sbb cx, 0
- jle last_buf
- begins:
- mov ah, 3Fh ; Read full buffer of
- mov cx, cBUF_SIZE ; EXECing file
- lea dx, [bp+buffer]
- int 21h
- mov cx, ax
- dec cx
- lea di, [bp+buffer]
- call decode
- lea di, [bp+buffer]
- call submagic
- mov ax, 4201h
- mov dx, cBUF_SIZE
- neg dx
- xor cx, cx
- int 21h
- mov ah, 40h ; Write segment to
- mov cx, cBUF_SIZE ; the input file
- lea dx, [bp+buffer]
- int 21h ;
- pop dx
- pop cx
- sub dx, cBUF_SIZE
- sbb cx, 0
- jmp buf_loop
- last_buf:
- pop cx
- pop dx
- mov ah, 3Fh ; Read data of
- push cx
- lea dx, [bp+buffer]
- int 21h ;
- lea di, [bp+buffer]
- pop cx
- push cx
- dec cx
- lea di, [bp+buffer]
- call decode
- lea di, [bp+buffer]
- call submagic
- mov ax, 4201h
- pop dx
- push dx
- neg dx
- xor cx, cx
- int 21h
- mov ah, 40h ; Write segment to
- pop cx
- lea dx, [bp+buffer]
- int 21h ;
- ;- Done
-
- close:
- mov ah,3eh ;close file
- int 21h
-
- exit:
- pop es
- pop ds
- popa
- jmp return
- terminate:
- jmp return
-
-
- pass_len dw 0
- pass dw 0
- header db 1ch dup(?) ;Buffer for header
- handle dw 0
- passwords db (cPASS_LEN*cMAX_FILE) dup (0)
- db 0
- files db (cNAME_LEN*cMAX_FILE) dup (0)
- db ' '
- buffer db cBUF_SIZE dup (?)
- test_pass db 10, 12, 15, 17, -20, -13, 05, -30, 55, -51
- ;-----------------------
- SeekZ proc near
- mov al, 0
- mov cx, 0ffffh
- repnz scasb
- neg cx
- dec cx
- dec di
- ret
- endp
- ;------------------
- ; es:di - what to decode
- ; cx - length
- decode proc near
- push si
- push ax
- push cx
- push dx
- mov dx, ds:[bp+pass_len]
- loops2: mov si, ds:[bp+pass]
- cmp cx, dx
- jb lasts2
- push cx
- mov cx, dx
- addmag2: mov al, ds:[si]
- xor es:[di], al
- inc si
- inc di
- loop addmag2
- pop cx
- sub cx, dx
- jmp loops2
- lasts2: inc cx
- lasts3: mov al, ds:[si]
- xor es:[di], al
- inc si
- inc di
- loop lasts3
- pop dx
- pop cx
- pop ax
- pop si
- ret
- endp
- submagic proc near
- push si
- push ax
- push cx
- loops: lea si, ds:[bp+test_pass]
- cmp cx, 10
- jb lasts
- push cx
- mov cx, 10
- addmag: mov al, ds:[si]
- sub es:[di], al
- inc si
- inc di
- loop addmag
- pop cx
- sub cx, 10
- jmp loops
- lasts: inc cx
- lasts0: mov al, ds:[si]
- sub es:[di], al
- inc si
- inc di
- loop lasts0
- pop cx
- pop ax
- pop si
- ret
- endp
- ;------------------
- the_end:
- message db 10,13,10,13
- db '- Decoder of encrypted files successfully installed -',10,13
- db ' - Copyright Enikeew I.R. 2084/1 -',10,13,'$'
- msg_already db 10, 13
- db '- Decoder already installed - ', 10, 13
- db ' - Copyright Enikeew I.R. 2084/1 -',10,13,'$'
- msg_not db 10, 13
- db '- Decoder isn''t installed !- ', 10, 13
- db ' - Copyright Enikeew I.R. 2084/1 -',10,13,'$'
- msg_un db 10,13,10,13
- db '- Decoder were successfully removed -',10,13
- db ' - Copyright Enikeew I.R. 2084/1 -',10,13,'$'
- fname db 'files.txt',0
- pname db 'pass.txt', 0
- already_resident:
- mov ah,9 ; Installed OK message
- lea dx,[msg_already]
- int 21h
- jmp exit_prog
- not_installed:
- mov ah,9 ; Installed OK message
- lea dx,[msg_not]
- int 21h
- jmp exit_prog
- remove:
- push cs cs
- pop ds es
-
- mov ax,0DEADh ;our decoder residency check
- int 21h ;
- cmp bx,0CAFEh ;>CAFE :o)
- jne not_installed ;it isn't resident
- mov ax, 0DEDDh
- int 21h
- mov ah,9 ; Installed OK message
- lea dx,[msg_un]
- int 21h
- jmp exit_prog
- decoder ends
- end start
|