cmonhackns.n-stars.org
Would you like to react to this message? Create an account in a few clicks or log in to continue.


Indonesian SWF Editor Community
 
HomeLatest imagesRegisterLog in
SELAMAT Datang Di Cmonhackns ===> Mulailah dari yang kecil... karena semua yang besar dulunya juga kecil..

 

 Cara Membuat Anti Virus VB 6

Go down 
5 posters
Go to page : 1, 2  Next
AuthorMessage
Ryan San Rakagi
Moderator
Moderator
Ryan San Rakagi


Jumlah posting : 260
Join date : 2011-04-19
Age : 29
Lokasi : CIREBON

Cara Membuat Anti Virus VB 6  Empty
PostSubject: Cara Membuat Anti Virus VB 6    Cara Membuat Anti Virus VB 6  Icon_minitime1Tue Dec 06, 2011 12:21 pm

1.Buka program microsoft visual basic 6.0 -> Standard EXE -> OK maka akan tampil form baru sesuai dengan gambar di bawah,desain form sesuai keinginan anda


[You must be registered and logged in to see this image.]

Beri nama form tersebut : frmUtama

2.Setelah form selesai di rubah namanya tambahkan component Mscomctl.Ocx dengan cara
Klik Project -> Components -> Microsoft Windows Common Controls 6.0 -> lalu klik OK
Contoh seperti gambar di bawah

[You must be registered and logged in to see this image.]

3.Setelah component sukses di tambahkan langkah selanjutnya adalah menambah Command Button,Textbox,Listview,Picture Box
disini saya menggunakan desain yang sangat sederhana,desain bisa anda rubah sendiri sesuai kreatifitas anda ^^

- Tambahkan Listview kedalam form dan beri nama lvScan

[You must be registered and logged in to see this image.]

yang saya lingkari merah adalah listview yang telah di tambahkan ke dalam form.

setelah itu setting listview dengan cara
Klik Listview -> Disebelah kanan bawah ada kotak properties -> Custom
lalu ikuti settingan seperti pada gambar di bawah ini

[You must be registered and logged in to see this image.]

Lalu pada tab Column Headers klik insert column
- Column 1 beri nama : Virus Name
- Column 2 beri nama : Path
- Column 3 beri nama : Checksum Virus
- Column 4 beri nama : Status Virus
lalu klik Ok

Tambahkan picture box buat picture box itu sekecil mungkin dan beri nama sIcon
Setting :
Appearance : Flat
Auto Redraw : True
Border Style : None
Visible : False

Tambahkan Textbox ke dalam form dengan nama txtPath
Setting :
Appearance : Flat
Border Style : None

Tambahkan Command Button dengan nama cmdBrowse di samping Textbox yang telah di buat tadi
Setting :
Caption : ...

Masukan Code ini ke dalam cmdBrowse

Code:
Dim Pathnya As String
Pathnya = ""
Pathnya = BrowseFolder("Pilih folder yang akan di Scan:", Me)
If Pathnya <> "" Then
txtPath.Text = Pathnya
End If


Code di atas berfungsi untuk membuka kotak dialog yang berisi path" yang ada di dalam komputer lalu mencetaknya ke dalam textbox yang bernama txtPath

Tambahkan label dengan nama default
Setting :
Caption : Dir Scanned

Tambahkan label dengan nama lblDirScan
Setting :
Caption : 0

Tambahkan label dengan nama default
Setting :
Caption : Detected

Tambahkan label dengan nama lblFileDet
Setting :
Caption : 0

Tambahkan label dengan nama default
Setting :
Caption : File Scanned

Tambahkan label dengan nama lblFileScan
Setting :
Caption : 0

Tambahkan Textbox dengan nama txtFileScan
Setting :
Multiline : True
Scroll Bar : 2-Vertical

Tambahkan Command Button dengan nama cmdScan
Setting :
Caption : &Scan

Code:
If cmdScan.Caption = "Scan" Then
Pathnya = txtPath.Text
If Mid(Pathnya, 2, 1) <> ":" Or Pathnya = "" Then
MsgBox "Direktori Tidak Ditemukan", vbCritical, "Error"
Exit Sub
Else
lvScan.Enabled = False
cmdEnable False, False, False
clear_log
cmdScan.Caption = "Stop"
StopScan = False
FindFilesEx txtPath.Text, CBool(chkSubDir.Value)
MsgBox "Scan finished !" & vbNewLine & vbNewLine & "Total Dir Scanned = " & lblDirScan.Caption & _
vbNewLine & "Total File Scanned = " & lblFileScan.Caption & vbNewLine & "Total File Detected = " & lblFileDet.Caption, vbInformation, "Finish"
If lblFileDet.Caption <> "0" Then
cmdEnable True, True, True
Else
cmdEnable False, False, True
End If
lvScan.Enabled = True
cmdScan.Caption = "Scan"
End If
Else
cmdScan.Caption = "Scan"
StopScan = True
End If

fungsi kode di atas adalah untuk memulai scan pada antivirus

Tambahkan Command Button dengan nama cmdAction
Setting :
Caption : &Delete

Tambahkan Command Button dengan nama cmdAction
Setting :
Caption : &Quarantine

Tambahkan Command Button dengan nama cmdViewQ
Setting :
Caption : &View Quarantine File

Tambahkan Command Button dengan nama cmdAction
Setting :
Caption : &Delete

Tambahkan kode ini di dalamnya

Code:
Dim DftrFile As String
DftrFile = GetSelected(lvScan)
If DftrFile = "" Then
MsgBox "No Detected File(s) Selected", vbCritical, ""
Exit Sub
End If
Select Case Index
Case 0
clean = Action(DftrFile, lvScan, "D")
MsgBox clean & " File(s) has been deleted"
Case 1
clean = Action(DftrFile, lvScan, "Q")
MsgBox clean & " File(s) has been quarantine"
End Select

Fungsi di atas adalah fungsi untuk menghapus/mengkarantina file yang terdeteksi

Tambahkan Command Button dengan nama cmdAction
Setting :
Caption : &Quarantine

Tambahkan Command Button dengan nama cmdViewQ
Setting :
Caption : &View Quarantine File

Code:
Me.hide
frmquarantine.show

Code di atas berfungsi untuk memunculkan form quarantine dan meng enabled form utama

nah selesai untuk memasukan control ke dalam formnya
contoh form yang telah selesai.

[You must be registered and logged in to see this image.]

lalu klik kanan pada form masukan kode di bawah ini

Code:
Private Sub lvScan_ItemCheck(ByVal Item As MSComctlLib.ListItem)
UnSelect lvScan, "Di Karantina"
UnSelect lvScan, "Di Hapus"
End Sub

Private Function cmdEnable(hapus As Boolean, Quarantine As Boolean, openQuarantine As Boolean)
cmdAction(0).Enabled = hapus
cmdAction(1).Enabled = Quarantine
cmdViewQ.Enabled = openQuarantine
End Function

Private Function clear_log()
lblDirScan.Caption = 0
lblFileScan.Caption = 0
lblFileDet.Caption = 0
lvScan.ListItems.Clear
jumlahDir = 0
jumlahFile = 0
jumlahVirus = 0
End Function

lalu di Form_load() masukan kode ini

Code:
On Error Resume Next
MkDir "Quarantine"
BuildDatabase

Lalu buatlah 1 module dengan nama modAPI

Lalu tambahkan code di bawah ini

Code:
Public Declare Function FindFirstFile Lib "kernel32" Alias "FindFirstFileA" (ByVal lpFileName As String, lpFindFileData As WIN32_FIND_DATA) As Long
Public Declare Function FindNextFile Lib "kernel32" Alias "FindNextFileA" (ByVal hFindFile As Long, lpFindFileData As WIN32_FIND_DATA) As Long
Public Declare Function FindClose Lib "kernel32" (ByVal hFindFile As Long) As Long
Public Declare Function PathIsDirectory Lib "shlwapi.dll" Alias "PathIsDirectoryA" (ByVal pszPath As String) As Long
Public Declare Function CopyFile Lib "kernel32.dll" Alias "CopyFileA" (ByVal lpExistingFileName As String, ByVal lpNewFileName As String, ByVal bFailIfExists As Long) As Long
Public Declare Function MoveFile Lib "kernel32.dll" Alias "MoveFileA" (ByVal lpExistingFileName As String, ByVal lpNewFileName As String) As Long
Public Declare Function DeleteFile Lib "kernel32" Alias "DeleteFileA" (ByVal lpFileName As String) As Long
Public Declare Function PathFileExists Lib "shlwapi.dll" Alias "PathFileExistsA" (ByVal pszPath As String) As Long
Public Declare Function GetSystemDirectory Lib "kernel32.dll" Alias "GetSystemDirectoryA" (ByVal lpBuffer As String, ByVal nSize As Long) As Long
Public Declare Function GetWindowsDirectory Lib "kernel32.dll" Alias "GetWindowsDirectoryA" (ByVal lpBuffer As String, ByVal nSize As Long) As Long
Public Declare Function SHGetPathFromIDList Lib "shell32.dll" Alias "SHGetPathFromIDListA" (ByVal pidl As Long, ByVal pszPath As String) As Long
Public Declare Function SHBrowseForFolder Lib "shell32.dll" Alias "SHBrowseForFolderA" (lpBrowseInfo As BROWSEINFO) As Long
Private Declare Function RealizePalette Lib "gdi32" (ByVal hDC As Long) As Long
Public Declare Function CreateFile Lib "kernel32" Alias "CreateFileA" (ByVal lpFileName As String, ByVal dwDesiredAccess As Long, ByVal dwShareMode As Long, lpSecurityAttributes As Any, ByVal dwCreationDisposition As Long, ByVal dwFlagsAndAttributes As Long, ByVal hTemplateFile As Long) As Long
Public Declare Function CloseHandle Lib "kernel32" (ByVal hObject As Long) As Long
Public Declare Function GetFileSize Lib "kernel32" (ByVal hFile As Long, lpFileSizeHigh As Long) As Long
Public Declare Function VirtualAlloc Lib "kernel32" (lpAddress As Any, ByVal dwSize As Long, ByVal flAllocationType As Long, ByVal flProtect As Long) As Long
Public Declare Function ReadFile Lib "kernel32" (ByVal hFile As Long, lpBuffer As Any, ByVal nNumberOfBytesToRead As Long, lpNumberOfBytesRead As Long, lpOverlapped As Any) As Long
Public Declare Function WriteFile Lib "kernel32" (ByVal hFile As Long, lpBuffer As Any, ByVal nNumberOfBytesToWrite As Long, lpNumberOfBytesWritten As Long, lpOverlapped As Any) As Long
Public Declare Function SetFilePointer Lib "kernel32" (ByVal hFile As Long, ByVal lDistanceToMove As Long, lpDistanceToMoveHigh As Long, ByVal dwMoveMethod As Long) As Long
Public Declare Function SetEndOfFile Lib "kernel32" (ByVal hFile As Long) As Long

Public Const GENERIC_READ = &H80000000
Public Const GENERIC_WRITE = &H40000000
Public Const FILE_SHARE_READ = &H1
Public Const OPEN_EXISTING = 3
Public Const FILE_ATTRIBUTE_NORMAL = &H80
Public Const INVALID_HANDLE_VALUE = -1
Public Const FILE_END = 2
Public Const FILE_BEGIN = 0
Public Const FILE_CURRENT = 1
Public Const LWA_COLORKEY = &H1
Public Const GWL_EXSTYLE = (-20)
Public Const WS_EX_LAYERED = &H80000
Public Const MAX_PATH = 260
Public Const SW_SHOWNORMAL = 1

Public Type FileTime
dwLowDateTime As Long
dwHighDateTime As Long
End Type

Public Type WIN32_FIND_DATA
dwFileAttributes As Long
ftCreationTime As FileTime
ftLastAccessTime As FileTime
ftLastWriteTime As FileTime
nFileSizeHigh As Long
nFileSizeLow As Long
dwReserved0 As Long
dwReserved1 As Long
cFileName As String * MAX_PATH
cAlternate As String * 14
End Type

Type BROWSEINFO
hOwner As Long
pidlRoot As Long
pszDisplayName As String
lpszTitle As String
ulFlags As Long
lpfn As Long
lParam As Long
iImage As Long
End Type

'untuk browse folder
Public Function BrowseFolder(ByVal aTitle As String, ByVal aForm As Form) As String
Dim bInfo As BROWSEINFO
Dim rtn&, pidl&, path$, pos%
Dim BrowsePath As String
bInfo.hOwner = aForm.hWnd
bInfo.lpszTitle = aTitle
bInfo.ulFlags = &H1
pidl& = SHBrowseForFolder(bInfo)
path = Space(512)
t = SHGetPathFromIDList(ByVal pidl&, ByVal path)
pos% = InStr(path$, Chr$(0))
BrowseFolder = Left(path$, pos - 1)
If Right$(Browse, 1) = "\" Then
BrowseFolder = BrowseFolder
Else
BrowseFolder = BrowseFolder + "\"
End If
If Right(BrowseFolder, 2) = "\\" Then BrowseFolder = Left(BrowseFolder, Len(BrowseFolder) - 1)
If BrowseFolder = "\" Then BrowseFolder = ""
End Function

Public Function StripNulls(ByVal OriginalStr As String) As String
If (InStr(OriginalStr, Chr$(0)) > 0) Then
OriginalStr = Left$(OriginalStr, InStr(OriginalStr, Chr(0)) - 1)
End If
StripNulls = OriginalStr
End Function

'fungsi untuk menentukan file script atau bukan
Public Function IsScript(Filename As String) As Boolean
IsScript = False
ext = Split("|vbs|vbe", "|")
For i = 1 To UBound(ext)
If LCase(Right(Filename, 3)) = LCase(ext(i)) Then IsScript = True
Next
End Function


Code di atas adalah Fungsi API yang di butuhkan untuk antivirus

Buat 1 module dengan nama modChecksum
masukan code di bawah ini.


Code:
Public Function GetChecksum(FilePath As String) As String
Dim CheckSum(1 To 2) As String
CheckSum(1) = CalcBinary(FilePath, 499, 4500)
CheckSum(2) = CalcBinary(FilePath, 499, 4000)
GetChecksum = CheckSum(1) & CheckSum(2)
End Function
Public Function CalcBinary(ByVal lpFileName As String, ByVal lpByteCount As Long, Optional ByVal StartByte As Long = 0) As String
On Error GoTo err
Dim Bin() As Byte
Dim ByteSum As Long
Dim i As Long
ReDim Bin(lpByteCount) As Byte
Open lpFileName For Binary As #1
If StartByte = 0 Then
Get #1, , Bin
Else
Get #1, StartByte, Bin
End If
Close #1
For i = 0 To lpByteCount
ByteSum = ByteSum + Bin(i) ^ 2
Next i
CalcBinary = Hex$(ByteSum)
Exit Function
err:
CalcBinary = "00"
End Function

potongan code di atas di gunakan untuk meng kalkulasi checksum

buat 1 module lagi dengan nama modDatabase
lalu tambahkan code di bawah ini.

Code:
Public VirusDB(5), IconDB(48), Bahaya(5) As String
Public Sub BuildDatabase()
Call Checksum_DB
Call IconCompare_DB
Call Script_DB
End Sub
Private Sub Checksum_DB()
VirusDB(1) = "Alman.A|8911D290F723"
VirusDB(2) = "Malingsi.A|A6292EA60230"
VirusDB(3) = "Conficker.A|9EC112ABB2F3"
VirusDB(4) = "N4B3.A|B5CCD36CDB98"
VirusDB(5) = "N4B3.B|A1FE6D6DBE07"
End Sub
Public Sub IconCompare_DB()
On Error Resume Next
IconDB(1) = "20938B2"
IconDB(2) = "19F4ED6"
IconDB(3) = "133BE0B"
IconDB(4) = "18EDEAE"
IconDB(5) = "1EF89C2"
IconDB(6) = "1C915FF"
IconDB(7) = "24563C4"
IconDB(8) = "1B2DB74"
IconDB(9) = "208EA72"
IconDB(10) = "22A064D"
IconDB(11) = "19B64EE"
IconDB(12) = "1D4B7E1"
IconDB(13) = "2087762"
IconDB(14) = "29C7258"
IconDB(15) = "1B18705"
IconDB(16) = "1B5FCAB"
IconDB(17) = "126D4CF"
IconDB(18) = "1C58E5C"
IconDB(19) = "15D7730"
IconDB(20) = "1FB82B7"
IconDB(21) = "112763E"
IconDB(22) = "2165AF9"
IconDB(23) = "25F46BE"
IconDB(24) = "206556B"
IconDB(25) = "22A8D69"
IconDB(26) = "19237F8"
IconDB(27) = "15022B4"
IconDB(28) = "1D8B4EB"
IconDB(29) = "1DBC1EA"
IconDB(30) = "2333F5D"
IconDB(31) = "1F37C2F"
IconDB(32) = "1C9CCA4"
IconDB(33) = "1DFDFB4"
IconDB(34) = "1C1283E"
IconDB(35) = "1F6598C"
IconDB(36) = "27F4C1A"
IconDB(37) = "22F92E0"
IconDB(38) = "191DBDC"
IconDB(39) = "27BFE4A"
IconDB(40) = "20E0907"
IconDB(46) = "2FA4C88"
IconDB(47) = "25AA630"
IconDB(48) = "1DE28E2"
End Sub
Public Sub Script_DB()
On Error Resume Next
Bahaya(1) = "Scripting.FileSystemObject|Wscript.ScriptFullName|WScript.Shell|.regwrite|.copy"
Bahaya(2) = "Wscript.ScriptFullName|createobject|strreverse|.regwrite"
Bahaya(3) = "createobject|Wscript.ScriptFullName|.regwrite|[autorun]"
Bahaya(4) = "createobject|Wscript.ScriptFullName|specialfolder|.regwrite"
Bahaya(5) = "chr(asc(mid(|createobject|Wscript.ScriptFullName|.GetFolder|.RegWrite"
End Sub

potongan code di atas adalah database pada antivirusnya

buat lagi 1 buah module dengan nama modQuar
masukan code yang ada di bawah ini

Code:
Option Explicit
Public Function EncodeFile(SourceFile As String, DestFile As String)
Dim ByteArray() As Byte, Filenr As Integer
Filenr = FreeFile
Open SourceFile For Binary As #Filenr
ReDim ByteArray(0 To LOF(Filenr) - 1)
Get #Filenr, , ByteArray()
Close #Filenr
Call Coder(ByteArray())
If (PathFileExists(DestFile)) <> 0 Then DeleteFile DestFile
Open DestFile For Binary As #Filenr
Put #Filenr, , ByteArray()
Close #Filenr
End Function
Public Function DecodeFile(SourceFile As String, DestFile As String)
Dim ByteArray() As Byte, Filenr As Integer
Filenr = FreeFile
Open SourceFile For Binary As #Filenr
ReDim ByteArray(0 To LOF(Filenr) - 1)
Get #Filenr, , ByteArray()
Close #Filenr
Call DeCoder(ByteArray())
If (PathFileExists(DestFile)) <> 0 Then DeleteFile DestFile
Open DestFile For Binary As #Filenr
Put #Filenr, , ByteArray()
Close #Filenr
End Function
Private Sub Coder(ByteArray() As Byte)
Dim x As Long
Dim Value As Integer
Value = 0
For x = 0 To UBound(ByteArray)
Value = Value + ByteArray(x)
If Value > 255 Then Value = Value - 256
ByteArray(x) = Value
Next
End Sub
Private Sub DeCoder(ByteArray() As Byte)
Dim x As Long
Dim Value As Integer
Dim newValue As Integer
newValue = 0
For x = 0 To UBound(ByteArray)
Value = newValue
newValue = ByteArray(x)
Value = ByteArray(x) - Value
If Value < 0 Then Value = Value + 256 ByteArray(x) = Value Next End Sub

Code di atas adalah code untuk enkripsi/dekripsi pada virus yang akan di karantina

Buat lagi 1 module dengan nama modHeuristic
lalu masukan code di bawah ini

Code:
Private Declare Function ExtractIconEx Lib "shell32.dll" Alias "ExtractIconExA" (ByVal lpszFile As String, ByVal nIconIndex As Long, ByRef phiconLarge As Long, ByRef phiconSmall As Long, ByVal nIcons As Long) As Long
Private Declare Function DestroyIcon Lib "user32.dll" (ByVal hIcon As Long) As Long
Private Declare Function DrawIconEx Lib "user32" (ByVal hDC As Long, ByVal xLeft As Long, ByVal yTop As Long, ByVal hIcon As Long, ByVal cxWidth As Long, ByVal cyWidth As Long, ByVal istepIfAniCur As Long, ByVal hbrFlickerFreeDraw As Long, ByVal diFlags As Long) As Boolean
Private Declare Function ExtractIcon Lib "shell32.dll" Alias "ExtractIconA" (ByVal hInst As Long, ByVal lpszExefileName As String, ByVal nIconIndex As Long) As Long
Private Const DI_MASK = &H1
Private Const DI_IMAGE = &H2
Private Const DI_NORMAL = &H3
Private Const DI_COMPAT = &H4
Private Const DI_DEFAULTSIZE = &H8
Private Const SHGFI_DISPLAYNAME = &H200
Private Const SHGFI_EXETYPE = &H2000
Private Const SHGFI_SYSICONINDEX = &H4000
Private Const SHGFI_LARGEICON = &H0
Private Const SHGFI_SMALLICON = &H1
Private Const ILD_TRANSPARENT = &H1
Private Const SHGFI_SHELLICONSIZE = &H4
Private Const SHGFI_TYPENAME = &H400
Private Const BASIC_SHGFI_FLAGS = SHGFI_TYPENAME Or SHGFI_SHELLICONSIZE Or SHGFI_SYSICONINDEX Or SHGFI_DISPLAYNAME Or SHGFI_EXETYPE
Private SIconInfo As SHFILEINFO
Private SectionHeaders() As IMAGE_SECTION_HEADER
Dim i As Integer
Dim j As Integer
Public Function CekHeuristic(Filename As String)
CekHeuristic = ""
On Error GoTo hError
Dim hFile As Long, bRW As Long
Dim DOSheader As IMAGE_DOS_HEADER
Dim NTHeaders As IMAGE_NT_HEADERS
Dim Filedata As String
DOS_HEADER_INFO = ""
NT_HEADERS_INFO = ""
hFile = CreateFile(Filename, ByVal (GENERIC_READ Or GENERIC_WRITE), FILE_SHARE_READ, ByVal 0&, OPEN_EXISTING, FILE_ATTRIBUTE_NORMAL, ByVal 0)
ReadFile hFile, DOSheader, Len(DOSheader), bRW, ByVal 0&
SetFilePointer hFile, DOSheader.e_lfanew, 0, 0
ReadFile hFile, NTHeaders, Len(NTHeaders), bRW, ByVal 0&
If NTHeaders.Signature <> IMAGE_NT_SIGNATURE Then
If IsScript(Filename) = True Then
Open Filename For Binary As #1
Filedata = Space$(LOF(1))
Get #1, , Filedata
Close #1
CekHeuristic = CekHeur(Filedata)
End If
Exit Function
End If
CekHeuristic = CekIconBinary(Filename)
hError:
End Function
Private Function CekHeur(Data As String)
Dim hsl, asl As Integer
strasli = LCase(Replace(Data, vbNewLine, "$"))
For i = 1 To UBound(Bahaya)
hsl = 0
strData = Split(Bahaya(i), "|")
asl = 0
For k = 0 To UBound(strData)
xxx = LCase(strData(k))
If InStr(strasli, xxx) > 0 Then hsl = hsl + 1
asl = asl + 1
Next
If hsl = asl Then
CekHeur = "Malicious-Script"
Exit Function
End If
Next
CekHeur = ""
End Function
Private Function CekIconBinary(PathFile As String)
Dim q As Integer
Dim IconIDNow As String
CekIconBinary = ""
IconIDNow = CalcIcon(PathFile)
If IconIDNow = "" Then Exit Function
For q = 1 To UBound(IconDB)
If IconDB(q) = IconIDNow Then
CekIconBinary = "Malicious-Icon"
Exit Function
End If
Next q
End Function
Private Function CalcBinary(ByVal lpFileName As String, ByVal lpByteCount As Long, Optional ByVal StartByte As Long = 0) As String
Dim Bin() As Byte
Dim ByteSum As Long
Dim i As Long
ReDim Bin(lpByteCount) As Byte
Open lpFileName For Binary As #1
If StartByte = 0 Then
Get #1, , Bin
Else
Get #1, StartByte, Bin
End If
Close #1
For i = 0 To lpByteCount
ByteSum = ByteSum + Bin(i) ^ 2
Next i
CalcBinary = Hex$(ByteSum)
End Function
Private Function CalcIcon(ByVal lpFileName As String) As String
Dim PicPath As String
Dim ByteSum As String
Dim IconExist As Long
Dim hIcon As Long
IconExist = ExtractIconEx(lpFileName, 0, ByVal 0&, hIcon, 1)
If IconExist <= 0 Then IconExist = ExtractIconEx(lpFileName, 0, hIcon, ByVal 0&, 1) If IconExist <= 0 Then Exit Function End If frmUtama.sIcon.BackColor = vbWhite DrawIconEx frmUtama.sIcon.hDC, 0, 0, hIcon, 0, 0, 0, 0, DI_NORMAL DestroyIcon hIcon PicPath = Environ$("windir") & "\tmp.tmp" SavePicture frmUtama.sIcon.Image, PicPath ByteSum = CalcBinary(PicPath, FileLen(PicPath)) DeleteFile PicPath CalcIcon = ByteSum
End Function

Fungsi di atas adalah fungsi untuk mengecek suatu file dengan metode heuristic icon + heuristic untuk virus VBS

Buat 1 module dengan nama modIconCompare
lalu masukan code di bawah ini

Code:
Option Explicit
Private Const SHGFI_DISPLAYNAME = &H200, SHGFI_EXETYPE = &H2000, SHGFI_SYSICONINDEX = &H4000, SHGFI_LARGEICON = &H0, SHGFI_SMALLICON = &H1, SHGFI_SHELLICONSIZE = &H4, SHGFI_TYPENAME = &H400, ILD_TRANSPARENT = &H1, BASIC_SHGFI_FLAGS = SHGFI_TYPENAME Or SHGFI_SHELLICONSIZE Or SHGFI_SYSICONINDEX Or SHGFI_DISPLAYNAME Or SHGFI_EXETYPE
Public Type SHFILEINFO
hIcon As Long: iIcon As Long: dwAttributes As Long: szDisplayName As String * MAX_PATH: szTypeName As String * 80
End Type
Private Declare Function SHGetFileInfo Lib "shell32.dll" Alias "SHGetFileInfoA" (ByVal pszPath As String, ByVal dwFileAttributes As Long, psfi As SHFILEINFO, ByVal cbSizeFileInfo As Long, ByVal uFlags As Long) As Long
Private Declare Function ImageList_Draw Lib "comctl32.dll" (ByVal himl As Long, ByVal i As Long, ByVal hdcDest As Long, ByVal x As Long, ByVal y As Long, ByVal flags As Long) As Long
Private shinfo As SHFILEINFO, sshinfo As SHFILEINFO
Private Declare Function DrawIconEx Lib "user32.dll" (ByVal hDC As Long, ByVal xLeft As Long, ByVal yTop As Long, ByVal hIcon As Long, ByVal cxWidth As Long, ByVal cyWidth As Long, ByVal istepIfAniCur As Long, ByVal hbrFlickerFreeDraw As Long, ByVal diFlags As Long) As Long
Private SIconInfo As SHFILEINFO

Public Enum IconRetrieve
ricnLarge = 32
ricnSmall = 16
End Enum

Public Sub RetrieveIcon(fName As String, DC As PictureBox, icnSize As IconRetrieve)
Dim hImgSmall, hImgLarge As Long
Debug.Print fName
Select Case icnSize
Case ricnSmall
hImgSmall = SHGetFileInfo(fName$, 0&, shinfo, Len(shinfo), BASIC_SHGFI_FLAGS Or SHGFI_SMALLICON)
Call ImageList_Draw(hImgSmall, shinfo.iIcon, DC.hDC, 0, 0, ILD_TRANSPARENT)
Case ricnLarge
hImgLarge& = SHGetFileInfo(fName$, 0&, shinfo, Len(shinfo), BASIC_SHGFI_FLAGS Or SHGFI_LARGEICON)
Call ImageList_Draw(hImgLarge, shinfo.iIcon, DC.hDC, 0, 0, ILD_TRANSPARENT)
End Select
End Sub
Public Function ExtractIcon(Filename As String, AddtoImageList As ImageList, PictureBox As PictureBox, PixelsXY As IconRetrieve, iKey As String) As Long
Dim SmallIcon As Long
Dim NewImage As ListImage
Dim IconIndex As Integer
On Error GoTo Load_New_Icon
If iKey <> "Application" And iKey <> "Shortcut" Then
ExtractIcon = AddtoImageList.ListImages(iKey).Index
Exit Function
End If
Load_New_Icon:
On Error GoTo Reset_Key
RetrieveIcon Filename, PictureBox, PixelsXY
IconIndex = AddtoImageList.ListImages.Count + 1
Set NewImage = AddtoImageList.ListImages.Add(IconIndex, iKey, PictureBox.Image)
ExtractIcon = IconIndex
Exit Function
Reset_Key:
iKey = ""
Resume
End Function
Public Sub GetLargeIcon(icPath$, pDisp As PictureBox)
Dim hImgLrg&: hImgLrg = SHGetFileInfo(icPath$, 0&, SIconInfo, Len(SIconInfo), BASIC_SHGFI_FLAGS Or SHGFI_LARGEICON)
ImageList_Draw hImgLrg, SIconInfo.iIcon, pDisp.hDC, 0, 0, ILD_TRANSPARENT
End Sub

kode di atas di butuhkan untuk metode heuristic icon pada antivirus

Buat 1 module dengan nama modLV
lalu masukan code di bawah ini

Code:
Public Function GetSelected(TheLV As ListView)
Dim Sel As String
For i = 1 To TheLV.ListItems.Count
If TheLV.ListItems.Item(i).Checked = True Then
Sel = Sel & "|" & TheLV.ListItems.Item(i).SubItems(1)
End If
Next
GetSelected = Sel
End Function

Public Function SelectedAll(TheLV As ListView)
For i = 1 To TheLV.ListItems.Count
TheLV.ListItems.Item(i).Checked = True
Next
End Function

Public Function SelectedNone(TheLV As ListView)
For i = 1 To TheLV.ListItems.Count
TheLV.ListItems.Item(i).Checked = False
Next
End Function

Public Function GetIndex(TheLV As ListView, Data As String) As Integer
For i = 1 To TheLV.ListItems.Count
If TheLV.ListItems.Item(i).SubItems(1) = Data Then
GetIndex = i
End If
Next
End Function

Public Function UnSelect(TheLV As ListView, Data As String)
For i = 1 To TheLV.ListItems.Count
If TheLV.ListItems.Item(i).SubItems(3) = Data Then
TheLV.ListItems.Item(i).Checked = False
End If
Next
End Function

Public Function AddDetect(TheLV As ListView, FilePath As String, VirData As String)
With TheLV
If Left(VirData, 9) <> "Malicious" Then
Set lvItm = .ListItems.Add(, , Split(VirData, "|")(0), , frmUtama.ImgSmall.ListImages(1).Index)
lvItm.SubItems(1) = FilePath
lvItm.SubItems(2) = Split(VirData, "|")(1)
lvItm.SubItems(3) = "Virus File"
Else
Set lvItm = .ListItems.Add(, , VirData, , frmUtama.ImgSmall.ListImages(1).Index)
lvItm.SubItems(1) = FilePath
lvItm.SubItems(2) = GetChecksum(FilePath)
lvItm.SubItems(3) = "Virus File"
End If
End With
End Function

Code di atas berguna untuk dengatur Listview pada saat virus terdeteksi

Buat 1 module dengan nama modPE
lalu masukan code di bawah ini

Code:
Public Type IMAGE_DOS_HEADER
e_magic As Integer
e_cblp As Integer
e_cp As Integer
e_crlc As Integer
e_cparhdr As Integer
e_minalloc As Integer
e_maxalloc As Integer
e_ss As Integer
e_sp As Integer
e_csum As Integer
e_ip As Integer
e_cs As Integer
e_lfarlc As Integer
e_ovno As Integer
e_res(1 To 4) As Integer
e_oemid As Integer
e_oeminfo As Integer
e_res2(1 To 10) As Integer
e_lfanew As Long
End Type

Public Type IMAGE_SECTION_HEADER
nameSec As String * 6
PhisicalAddress As Integer

VirtualSize As Long
VirtualAddress As Long
SizeOfRawData As Long
PointerToRawData As Long
PointerToRelocations As Long
PointerToLinenumbers As Long
NumberOfRelocations As Integer
NumberOfLinenumbers As Integer
Characteristics As Long

End Type

Public Type IMAGE_DATA_DIRECTORY
VirtualAddress As Long
size As Long
End Type

Public Type IMAGE_OPTIONAL_HEADER
Magic As Integer
MajorLinkerVersion As Byte
MinorLinkerVersion As Byte
SizeOfCode As Long
SizeOfInitializedData As Long
SizeOfUninitializedData As Long
AddressOfEntryPoint As Long
BaseOfCode As Long
BaseOfData As Long
ImageBase As Long
SectionAlignment As Long
FileAlignment As Long
MajorOperatingSystemVersion As Integer
MinorOperatingSystemVersion As Integer
MajorImageVersion As Integer
MinorImageVersion As Integer
MajorSubsystemVersion As Integer
MinorSubsystemVersion As Integer
Win32VersionValue As Long
SizeOfImage As Long
SizeOfHeaders As Long
CheckSum As Long
Subsystem As Integer
DllCharacteristics As Integer
SizeOfStackReserve As Long
SizeOfStackCommit As Long
SizeOfHeapReserve As Long
SizeOfHeapCommit As Long
LoaderFlags As Long
NumberOfRvaAndSizes As Long
DataDirectory(0 To 15) As IMAGE_DATA_DIRECTORY
End Type

Public Type IMAGE_FILE_HEADER
Machine As Integer
NumberOfSections As Integer
TimeDateStamp As Long
PointerToSymbolTable As Long
NumberOfSymbols As Long
SizeOfOptionalHeader As Integer
Characteristics As Integer
End Type

Public Type IMAGE_NT_HEADERS
Signature As Long
FileHeader As IMAGE_FILE_HEADER
OptionalHeader As IMAGE_OPTIONAL_HEADER
End Type

Public Type IMAGE_EXPORT_DIRECTORY
Characteristics As Long
TimeDateStamp As Long
MajorVersion As Integer
MinorVersion As Integer
Name As Long
Base As Long
NumberOfFunctions As Long
NumberOfNames As Long
AddressOfFunctions As Long
AddressOfNames As Long
AddressOfNameOrdinals As Long
End Type

Public Type IMAGE_IMPORT_DESCRIPTOR
OriginalFirstThunk As Long
TimeDateStamp As Long
ForwarderChain As Long
Name As Long
FirstThunk As Long
End Type

Public Type IMAGE_IMPORT_BY_NAME
Hint As Integer
Name As String * 255
End Type

Public Const IMAGE_SIZEOF_SECTION_HEADER = 40
Public Const IMAGE_DOS_SIGNATURE = &H5A4D
Public Const IMAGE_NT_SIGNATURE = &H4550
Public Const IMAGE_ORDINAL_FLAG = &H80000000

Public Enum SECTION_CHARACTERISTICS
IMAGE_SCN_LNK_NRELOC_OVFL = &H1000000 'Section contains extended relocations.
IMAGE_SCN_MEM_DISCARDABLE = &H2000000 'Section can be discarded.
IMAGE_SCN_MEM_NOT_CACHED = &H4000000 'Section is not cachable.
IMAGE_SCN_MEM_NOT_PAGED = &H8000000 'Section is not pageable.
IMAGE_SCN_MEM_SHARED = &H10000000 'Section is shareable.
IMAGE_SCN_MEM_EXECUTE = &H20000000 'Section is executable.
IMAGE_SCN_MEM_READ = &H40000000 'Section is readable.
IMAGE_SCN_MEM_WRITE = &H80000000 'Section is writeable.
End Enum

Public Enum IMAGE_DIRECTORY
IMAGE_DIRECTORY_ENTRY_EXPORT = 0 ' Export Directory
IMAGE_DIRECTORY_ENTRY_IMPORT = 1 ' Import Directory
IMAGE_DIRECTORY_ENTRY_RESOURCE = 2 ' Resource Directory
IMAGE_DIRECTORY_ENTRY_EXCEPTION = 3 ' Exception Directory
IMAGE_DIRECTORY_ENTRY_SECURITY = 4 ' Security Directory
IMAGE_DIRECTORY_ENTRY_BASERELOC = 5 ' Base Relocation Table
IMAGE_DIRECTORY_ENTRY_DEBUG = 6 ' Debug Directory
IMAGE_DIRECTORY_ENTRY_ARCHITECTURE = 7 ' Architecture Specific Data
IMAGE_DIRECTORY_ENTRY_GLOBALPTR = 8 ' RVA of GP
IMAGE_DIRECTORY_ENTRY_TLS = 9 ' TLS Directory
IMAGE_DIRECTORY_ENTRY_LOAD_CONFIG = 10 ' Load Configuration Directory
IMAGE_DIRECTORY_ENTRY_BOUND_IMPORT = 11 ' Bound Import Directory in headers
IMAGE_DIRECTORY_ENTRY_IAT = 12 ' Import Address Table
IMAGE_DIRECTORY_ENTRY_DELAY_IMPORT = 13 ' Delay Load Import Descriptors
IMAGE_DIRECTORY_ENTRY_COM_DESCRIPTOR = 14 ' COM Runtime descriptor
End Enum

code di atas berfungsi untuk pengecekan PE HEADER

buat 1 module dengan nama modScanning
lalu tambahkan code di bawah ini

Code:
Public jumlahDir As Long, jumlahFile As Long, jumlahVirus As Long
Public StopScan As Boolean

Public Function CekVirus(FilePath As String) As String
CekVirus = ""
For i = 1 To UBound(VirusDB)
If GetChecksum(FilePath) = Split(VirusDB(i), "|")(1) Then
CekVirus = VirusDB(i)
Exit Function
End If
Next
If FileLen(FilePath) / 1024 <= 512 Then CekVirus = CekHeuristic(FilePath) End If End Function Public Sub FindFilesEx(ByVal lpFolderName As String, ByVal SubDirs As Boolean) Dim i As Long Dim hSearch As Long, WFD As WIN32_FIND_DATA Dim Result As Long, CurItem As String Dim tempDir() As String, dirCount As Long Dim RealPath As String, GetViri As String GetViri = "" dirCount = -1 ScanInfo = "Scan File" If Right$(lpFolderName, 1) = "\" Then RealPath = lpFolderName Else RealPath = lpFolderName & "\" End If hSearch = FindFirstFile(RealPath & "*", WFD) If Not hSearch = INVALID_HANDLE_VALUE Then Result = True Do While Result DoEvents If StopScan = True Then Exit Do CurItem = StripNulls(WFD.cFileName) If Not CurItem = "." And Not CurItem = ".." Then If PathIsDirectory(RealPath & CurItem) <> 0 Then
jumlahDir = jumlahDir + 1
frmUtama.lblDirScan.Caption = jumlahDir
If SubDirs = True Then
dirCount = dirCount + 1
ReDim Preserve tempDir(dirCount) As String
tempDir(dirCount) = RealPath & CurItem
End If
Else
jumlahFile = jumlahFile + 1
frmUtama.lblFileScan.Caption = jumlahFile
frmUtama.txtFileScan.Text = RealPath & CurItem
frmUtama.txtFileScan.SelStart = Len(frmUtama.txtFileScan.Text)
If WFD.nFileSizeLow > 5120 Or WFD.nFileSizeHigh > 5120 Then
GetViri = CekVirus(RealPath & CurItem)
If GetViri <> "" Then
AddDetect frmUtama.lvScan, RealPath & CurItem, GetViri
jumlahVirus = jumlahVirus + 1
frmUtama.lblFileDet.Caption = jumlahVirus
End If
End If
End If
End If
Result = FindNextFile(hSearch, WFD)
Loop
FindClose hSearch

If SubDirs = True Then
If dirCount <> -1 Then
For i = 0 To dirCount
FindFilesEx tempDir(i), True
Next i
End If
End If
End If
End Sub

Code di atas adalah code untuk scan file & folder pada antivirus

buat 1 module dengan nama modEtc
masukan code di bawah ini

Code:
Public Function Action(Data As String, TheLV As ListView, Mode As String)
Dim Filedata() As String
Dim fName, tmp, Status As String
Dim y As Integer
Filedata = Split(Data, "|")
For i = 1 To UBound(Filedata)
a = a + 1
If Mode = "Q" Then
fName = GetFileName(Filedata(i))
EncodeFile Filedata(i), AppPath & "Quarantine\" & Left$(fName, Len(fName) - Len(GetExt(Filedata(i)))) & ".avq"
AddQList TheLV, Filedata(i), Left$(fName, Len(fName) - Len(GetExt(Filedata(i)))) & ".avq"
DeleteFile Filedata(i)
Status = "Di Karantina"
ElseIf Mode = "D" Then
DeleteFile Filedata(i)
Status = "Di Hapus"
End If
y = GetIndex(TheLV, Filedata(i))
With TheLV.ListItems.Item(y)
.SubItems(3) = Status
.Checked = False
.SmallIcon = frmUtama.ImgSmall.ListImages(2).Index
End With
Next
Action = a
End Function

Public Function AddQList(TheLV As ListView, FilePath As String, Source As String)
Dim Dat As String
Dat = AppPath & "Quarantine\HN.dat"
If PathFileExists(Dat) <> 0 Then
Open Dat For Input As #1
Input #1, isi
Close #1
DeleteFile Dat
Else
isi = ""
End If
namavir = TheLV.ListItems(GetIndex(TheLV, FilePath))
If InStrRev(isi, Source, , vbTextCompare) = 0 Then
Open Dat For Output As #2
Print #2, isi & "|" & namavir & "?" & FilePath & "?" & Source
Close #2
Else
Open Dat For Output As #3
Print #3, isi
Close #3
End If
End Function

Public Function GetFileName(PathFile As String) As String
Dim i As Long
Dim DirString As Long
For i = 1 To Len(PathFile)
If Mid$(PathFile, i, 1) = "\" Then DirString = i
Next i
GetFileName = Right$(PathFile, Len(PathFile) - DirString)
End Function

Public Function GetExt(ByVal lpFileName As String)
Dim sTemp As String
Dim i As Long
sTemp = GetFileName(lpFileName)
If InStr(lpFileName, ".") Then
For i = 0 To Len(sTemp) - 1
If Mid$(sTemp, Len(sTemp) - i, 1) = "." Then
GetExt = Mid$(sTemp, Len(sTemp) - i, i)
Exit Function
End If
Next i
End If
End Function

Code di atas adalah kumpulan fungsi etc untuk scanning,karantina,delete

Ini adalah tampilan antivirus setelah di berikan module

[You must be registered and logged in to see this image.]

sekarang tinggal cara membuat form quarantinenya,

caranya adalah sebagai berikut pada gambar berikut

[You must be registered and logged in to see this image.]

setelah form baru sudah di buat,lalu rubah nama formnya menjadi frmQuarantine

Tambah 1 buah listview dengan nama lvQ
lalu setting listview tersebut sesuai dengan gambar di bawah ini,cara setting listview sudah tertera diatas.

[You must be registered and logged in to see this image.]


Tambahkan 3 buah Command button dengan nama

- cmdDelete
- cmdRestore
- cmdRestore(1)

Tambahkan code di bawah ini ke dalam Command [ cmdDelete ]

Code:
If lvQ.ListItems.Count = 0 Then Exit Sub
Dim Data() As String
If PathFileExists(Dat) <> 0 Then
Open Dat For Input As #1
Input #1, isi
Close #1
DeleteFile Dat
Else
isi = ""
End If
Data = Split(isi, "|")
For i = 1 To UBound(Data)
namafile = lvQ.SelectedItem.SubItems(2)
If namafile <> Split(Data(i), "?")(1) Then
nyu = nyu & "|" & Data(i)
End If
Next
DeleteFile AppPath & "Quarantine\" & lvQ.SelectedItem.SubItems(1)
Open Dat For Output As #2
Print #2, nyu
Close #2
MsgBox "Success Deleting File !!!", vbInformation, ""
UpdateQ

code di atas berfungsi untuk menghapus file yang telah di karantina

Masukan code di bawah ini ke Command [ cmdRestore ]

Code:
If lvQ.ListItems.Count = 0 Then Exit Sub
Select Case Index
Case 0
DecodeFile AppPath & "Quarantine\" & lvQ.SelectedItem.SubItems(1), lvQ.SelectedItem.SubItems(2)
MsgBox "File Restored to " & Chr(34) & lvQ.SelectedItem.SubItems(2) & Chr(34) & " !!!", vbInformation, ""
Case 1
sTitle = "Select path:" & vbNewLine & "Select path to restore file."
ThePath = BrowseFolder(sTitle, Me)
If ThePath <> "" Then
DecodeFile AppPath & "Quarantine\" & lvQ.SelectedItem.SubItems(1), ThePath & GetFileName(lvQ.SelectedItem.SubItems(2))
MsgBox "File Restored to " & Chr(34) & ThePath & GetFileName(lvQ.SelectedItem.SubItems(2)) & Chr(34) & " !!!", vbInformation, ""
End If
End Select

Fungsi code di atas berguna untuk me restore file kembali ke asalnya.

lalu pada Form_Load() tambahkan code di bawah ini.

Code:
frmUtama.Enabled = False
Dat = AppPath & "Quarantine\HN.dat"
UpdateQ

Masukan code di bawah ini ke dalam frmQuarantine yang telah anda buat tadi.

Code:
Dim Dat As String
Private Sub UpdateQ()
lvQ.ListItems.Clear
Dim Data() As String
If PathFileExists(Dat) = 0 Then Exit Sub
Open Dat For Input As #1
Input #1, isi
Close #1
Data = Split(isi, "|")
For i = 1 To UBound(Data)
With lvQ.ListItems.Add(, , Split(Data(i), "?")(0))
.SubItems(1) = Split(Data(i), "?")(2)
.SubItems(2) = Split(Data(i), "?")(1)
End With
Next
Me.Caption = "Quarantine (" & lvQ.ListItems.Count & ")"
End Sub

Berfungsi untuk memanggil data yang ada di folder karantina.

Hanya itu ilmu yang bisa saya bagikan. sekarang kita bukan hanya sebagai pemakai atau user sekrang kita sudah bisa mmembuat antivirus.

dan ini adalah Screenshot antivirus yang kita buat tadi saat melakukan scanning.


[You must be registered and logged in to see this image.]


Note : Jika anda membaca dan mencoba dengan teliti dan seksama anda pasti berhasil.

Orang yang berhasil adalah orang yang banyak mecoba.

Untuk masalah source code anda bisa meminta kepada saya tapi dengan satu syarat, yaitu anda harus menyertakan bukti bahwa anda telah mencoba entah itu dalam bentuk screenshot atau yang lainnya.

Dan jika ada kekurang jelas'n dalam hal SS ini saya perjelas SS nya :

[You must be registered and logged in to see this image.]

Dan Jika ada kekurangan harap dimaklumi karna ane masih newbie
dan jika ada kesalahan mohon bimbingan nya untuk membenahi Cara Membuat Anti Virus VB 6  443313 Cara Membuat Anti Virus VB 6  443313

dan Jika bermanfaat tolong hargai dengan karya agan dan tidak lupa ++ seikhlas nya

Dan mohon maaf atas sebelum nya Cara Membuat Anti Virus VB 6  443313 Cara Membuat Anti Virus VB 6  443313
Back to top Go down
http://nesaz.lifeme.net
Drw123
Warga Lama
Warga Lama
Drw123


Jumlah posting : 126
Join date : 2011-07-05
Age : 26
Lokasi : Bekasi

Cara Membuat Anti Virus VB 6  Empty
PostSubject: Re: Cara Membuat Anti Virus VB 6    Cara Membuat Anti Virus VB 6  Icon_minitime1Tue Dec 06, 2011 2:36 pm

Quote :
Tambahkan Command Button dengan nama cmdAction
Setting :
Caption : &Delete

Tambahkan Command Button dengan nama cmdAction
Setting :
Caption : &Quarantine

Tambahkan Command Button dengan nama cmdViewQ
Setting :
Caption : &View Quarantine File

Tambahkan Command Button dengan nama cmdAction
Setting :
Caption : &Delete

Bukannya Kalo Sama Namenya Jadi Eror?

Quote :
- cmdRestore
- cmdRestore(1)

Kalo Pake (1) Gitu Kok Aku Gak Bisa Ya?
Back to top Go down
http://drw-lab.blogspot.com
1stKame
Sesepuh
Sesepuh
1stKame


Jumlah posting : 459
Join date : 2011-05-11

Cara Membuat Anti Virus VB 6  Empty
PostSubject: Re: Cara Membuat Anti Virus VB 6    Cara Membuat Anti Virus VB 6  Icon_minitime1Tue Dec 06, 2011 7:53 pm

gan kok pas ane ngikutin ini !
Code:
setelah itu setting listview dengan cara
Klik Listview -> Disebelah kanan bawah ada kotak properties -> Custom
lalu ikuti settingan seperti pada gambar di bawah ini

pas di klik custom ada tulisan
Code:
Class not registered.Looking for object with CLSID:{7EBDAAE1-8120-11CF-889F-00AA00688B10}

itu kenapa gan ?

dan cara ngiteminnya gimana ?
Back to top Go down
Ryan San Rakagi
Moderator
Moderator
Ryan San Rakagi


Jumlah posting : 260
Join date : 2011-04-19
Age : 29
Lokasi : CIREBON

Cara Membuat Anti Virus VB 6  Empty
PostSubject: Re: Cara Membuat Anti Virus VB 6    Cara Membuat Anti Virus VB 6  Icon_minitime1Wed Dec 07, 2011 11:25 am

Drw123 wrote:
Quote :
Tambahkan Command Button dengan nama cmdAction
Setting :
Caption : &Delete

Tambahkan Command Button dengan nama cmdAction
Setting :
Caption : &Quarantine

Tambahkan Command Button dengan nama cmdViewQ
Setting :
Caption : &View Quarantine File

Tambahkan Command Button dengan nama cmdAction
Setting :
Caption : &Delete

Bukannya Kalo Sama Namenya Jadi Eror?

Quote :
- cmdRestore
- cmdRestore(1)

Kalo Pake (1) Gitu Kok Aku Gak Bisa Ya?


Itu ane salah ketik gan

yg cmdRestore(1) di hapus aja gan

Cara Membuat Anti Virus VB 6  443313
Back to top Go down
http://nesaz.lifeme.net
Ryan San Rakagi
Moderator
Moderator
Ryan San Rakagi


Jumlah posting : 260
Join date : 2011-04-19
Age : 29
Lokasi : CIREBON

Cara Membuat Anti Virus VB 6  Empty
PostSubject: Re: Cara Membuat Anti Virus VB 6    Cara Membuat Anti Virus VB 6  Icon_minitime1Wed Dec 07, 2011 11:28 am

1stKame wrote:
gan kok pas ane ngikutin ini !
Code:
setelah itu setting listview dengan cara
Klik Listview -> Disebelah kanan bawah ada kotak properties -> Custom
lalu ikuti settingan seperti pada gambar di bawah ini

pas di klik custom ada tulisan
Code:
Class not registered.Looking for object with CLSID:{7EBDAAE1-8120-11CF-889F-00AA00688B10}

itu kenapa gan ?

dan cara ngiteminnya gimana ?


Nah agan pke vb 6 gx?

and agan nya udah selesai melakukan prosedure / component sebelum nya gx?

klo blum gx bsa gan

dan ane minta ss nya biar ane kasih solusi
Back to top Go down
http://nesaz.lifeme.net
1stKame
Sesepuh
Sesepuh
1stKame


Jumlah posting : 459
Join date : 2011-05-11

Cara Membuat Anti Virus VB 6  Empty
PostSubject: Re: Cara Membuat Anti Virus VB 6    Cara Membuat Anti Virus VB 6  Icon_minitime1Wed Dec 07, 2011 1:13 pm

Ryan San Rakagi wrote:
1stKame wrote:
gan kok pas ane ngikutin ini !
Code:
setelah itu setting listview dengan cara
Klik Listview -> Disebelah kanan bawah ada kotak properties -> Custom
lalu ikuti settingan seperti pada gambar di bawah ini

pas di klik custom ada tulisan
Code:
Class not registered.Looking for object with CLSID:{7EBDAAE1-8120-11CF-889F-00AA00688B10}

itu kenapa gan ?

dan cara ngiteminnya gimana ?


Nah agan pke vb 6 gx?

and agan nya udah selesai melakukan prosedure / component sebelum nya gx?

klo blum gx bsa gan

dan ane minta ss nya biar ane kasih solusi
ane pake VB 6 lah !
prosedure yg mana gan ?
SS ? ngapain make SS pokoknya pas di klik custom ada tulisan kayak di atas !

Tolong di reply ya gan Cara Membuat Anti Virus VB 6  443313
Back to top Go down
Ryan San Rakagi
Moderator
Moderator
Ryan San Rakagi


Jumlah posting : 260
Join date : 2011-04-19
Age : 29
Lokasi : CIREBON

Cara Membuat Anti Virus VB 6  Empty
PostSubject: Re: Cara Membuat Anti Virus VB 6    Cara Membuat Anti Virus VB 6  Icon_minitime1Thu Dec 08, 2011 1:36 pm

1stKame wrote:
Ryan San Rakagi wrote:



Nah agan pke vb 6 gx?

and agan nya udah selesai melakukan prosedure / component sebelum nya gx?

klo blum gx bsa gan

dan ane minta ss nya biar ane kasih solusi
ane pake VB 6 lah !
prosedure yg mana gan ?
SS ? ngapain make SS pokoknya pas di klik custom ada tulisan kayak di atas !

Tolong di reply ya gan Cara Membuat Anti Virus VB 6  443313



Oooh

cba langkah nya gni neh gan

Klik kanan,terus klik properties

itu cara cepat costum nya...

and apa lagi gan problem nya?
Back to top Go down
http://nesaz.lifeme.net
1stKame
Sesepuh
Sesepuh
1stKame


Jumlah posting : 459
Join date : 2011-05-11

Cara Membuat Anti Virus VB 6  Empty
PostSubject: Re: Cara Membuat Anti Virus VB 6    Cara Membuat Anti Virus VB 6  Icon_minitime1Thu Dec 08, 2011 7:51 pm

Ryan San Rakagi wrote:
1stKame wrote:

ane pake VB 6 lah !
prosedure yg mana gan ?
SS ? ngapain make SS pokoknya pas di klik custom ada tulisan kayak di atas !

Tolong di reply ya gan Cara Membuat Anti Virus VB 6  443313



Oooh

cba langkah nya gni neh gan

Klik kanan,terus klik properties

itu cara cepat costum nya...

and apa lagi gan problem nya?

tetep gk bisa gan ada tulisan yang sama ?

tolong di reply lagi ya gan !
Back to top Go down
Ryan San Rakagi
Moderator
Moderator
Ryan San Rakagi


Jumlah posting : 260
Join date : 2011-04-19
Age : 29
Lokasi : CIREBON

Cara Membuat Anti Virus VB 6  Empty
PostSubject: Re: Cara Membuat Anti Virus VB 6    Cara Membuat Anti Virus VB 6  Icon_minitime1Fri Dec 09, 2011 1:00 pm

1stKame wrote:
Ryan San Rakagi wrote:




Oooh

cba langkah nya gni neh gan

Klik kanan,terus klik properties

itu cara cepat costum nya...

and apa lagi gan problem nya?

tetep gk bisa gan ada tulisan yang sama ?

tolong di reply lagi ya gan !


Wah mungkin ada kesalaha dalam penginstalan kali gan

and agan udah masukin list view nya blum?

klo udah di klik skali trus klik kanan properties gan

and coba kirim SS ny aja gan

nanti ane kasih solusi nya Cara Membuat Anti Virus VB 6  443313 Cara Membuat Anti Virus VB 6  443313
Back to top Go down
http://nesaz.lifeme.net
1stKame
Sesepuh
Sesepuh
1stKame


Jumlah posting : 459
Join date : 2011-05-11

Cara Membuat Anti Virus VB 6  Empty
PostSubject: Re: Cara Membuat Anti Virus VB 6    Cara Membuat Anti Virus VB 6  Icon_minitime1Fri Dec 09, 2011 1:32 pm

Ryan San Rakagi wrote:
1stKame wrote:


tetep gk bisa gan ada tulisan yang sama ?

tolong di reply lagi ya gan !


Wah mungkin ada kesalaha dalam penginstalan kali gan

and agan udah masukin list view nya blum?

klo udah di klik skali trus klik kanan properties gan

and coba kirim SS ny aja gan

nanti ane kasih solusi nya Cara Membuat Anti Virus VB 6  443313 Cara Membuat Anti Virus VB 6  443313
listviewnya udh ane masukin kok !
kalo masalah penginstalan Cara Membuat Anti Virus VB 6  779629 ane coba INUL deh gan 1

semoga berhasil
Back to top Go down
Ryan San Rakagi
Moderator
Moderator
Ryan San Rakagi


Jumlah posting : 260
Join date : 2011-04-19
Age : 29
Lokasi : CIREBON

Cara Membuat Anti Virus VB 6  Empty
PostSubject: Re: Cara Membuat Anti Virus VB 6    Cara Membuat Anti Virus VB 6  Icon_minitime1Fri Dec 09, 2011 2:29 pm

1stKame wrote:
Ryan San Rakagi wrote:



Wah mungkin ada kesalaha dalam penginstalan kali gan

and agan udah masukin list view nya blum?

klo udah di klik skali trus klik kanan properties gan

and coba kirim SS ny aja gan

nanti ane kasih solusi nya Cara Membuat Anti Virus VB 6  443313 Cara Membuat Anti Virus VB 6  443313
listviewnya udh ane masukin kok !
kalo masalah penginstalan Cara Membuat Anti Virus VB 6  779629 ane coba INUL deh gan 1

semoga berhasil

OK OK gan and goog luck

and klo ada problem lagi tambahkan SS ea

and Cara Membuat Anti Virus VB 6  965962 Cara Membuat Anti Virus VB 6  399996
Back to top Go down
http://nesaz.lifeme.net
Drw123
Warga Lama
Warga Lama
Drw123


Jumlah posting : 126
Join date : 2011-07-05
Age : 26
Lokasi : Bekasi

Cara Membuat Anti Virus VB 6  Empty
PostSubject: Re: Cara Membuat Anti Virus VB 6    Cara Membuat Anti Virus VB 6  Icon_minitime1Sat Dec 10, 2011 6:54 am

Ini Copas Dari HNc Ya?
Aku Pernah Nyoba Soalnya...
Back to top Go down
http://drw-lab.blogspot.com
Ryan San Rakagi
Moderator
Moderator
Ryan San Rakagi


Jumlah posting : 260
Join date : 2011-04-19
Age : 29
Lokasi : CIREBON

Cara Membuat Anti Virus VB 6  Empty
PostSubject: Re: Cara Membuat Anti Virus VB 6    Cara Membuat Anti Virus VB 6  Icon_minitime1Sat Dec 10, 2011 11:39 am

Drw123 wrote:
Ini Copas Dari HNc Ya?
Aku Pernah Nyoba Soalnya...


Bukan Gan

klo HNC gx source code banyak yg salah
dan tutorial tidak terlalu jelas...
Back to top Go down
http://nesaz.lifeme.net
1stKame
Sesepuh
Sesepuh
1stKame


Jumlah posting : 459
Join date : 2011-05-11

Cara Membuat Anti Virus VB 6  Empty
PostSubject: Re: Cara Membuat Anti Virus VB 6    Cara Membuat Anti Virus VB 6  Icon_minitime1Sat Dec 10, 2011 11:50 am

tetep gak bisa gan !

masih ada tulisannya Cara Membuat Anti Virus VB 6  626315
Back to top Go down
Ryan San Rakagi
Moderator
Moderator
Ryan San Rakagi


Jumlah posting : 260
Join date : 2011-04-19
Age : 29
Lokasi : CIREBON

Cara Membuat Anti Virus VB 6  Empty
PostSubject: Re: Cara Membuat Anti Virus VB 6    Cara Membuat Anti Virus VB 6  Icon_minitime1Sat Dec 10, 2011 12:56 pm

1stKame wrote:
tetep gak bisa gan !

masih ada tulisannya Cara Membuat Anti Virus VB 6  626315

Cba pke yg portable aja gan!

soal'y ane sudah berkali" bkin yg baru gx ada problem gan

and tmen ane nyoba gx error gan

Mungkin ada yg blum complete dalam pembuatan nya gan...

Cara Membuat Anti Virus VB 6  443313 Cara Membuat Anti Virus VB 6  443313
Back to top Go down
http://nesaz.lifeme.net
1stKame
Sesepuh
Sesepuh
1stKame


Jumlah posting : 459
Join date : 2011-05-11

Cara Membuat Anti Virus VB 6  Empty
PostSubject: Re: Cara Membuat Anti Virus VB 6    Cara Membuat Anti Virus VB 6  Icon_minitime1Sat Dec 10, 2011 7:20 pm

Ryan San Rakagi wrote:
1stKame wrote:
tetep gak bisa gan !

masih ada tulisannya Cara Membuat Anti Virus VB 6  626315

Cba pke yg portable aja gan!

soal'y ane sudah berkali" bkin yg baru gx ada problem gan

and tmen ane nyoba gx error gan

Mungkin ada yg blum complete dalam pembuatan nya gan...

Cara Membuat Anti Virus VB 6  443313 Cara Membuat Anti Virus VB 6  443313
ane emang make yg portable gan !

yg belum complete?lah dari pertama aja udah error haha

ane googling aja dulu deh Cara Membuat Anti Virus VB 6  626315
Back to top Go down
Ryan San Rakagi
Moderator
Moderator
Ryan San Rakagi


Jumlah posting : 260
Join date : 2011-04-19
Age : 29
Lokasi : CIREBON

Cara Membuat Anti Virus VB 6  Empty
PostSubject: Re: Cara Membuat Anti Virus VB 6    Cara Membuat Anti Virus VB 6  Icon_minitime1Sun Dec 11, 2011 8:18 am

1stKame wrote:
Ryan San Rakagi wrote:


Cba pke yg portable aja gan!

soal'y ane sudah berkali" bkin yg baru gx ada problem gan

and tmen ane nyoba gx error gan

Mungkin ada yg blum complete dalam pembuatan nya gan...

Cara Membuat Anti Virus VB 6  443313 Cara Membuat Anti Virus VB 6  443313
ane emang make yg portable gan !

yg belum complete?lah dari pertama aja udah error haha

ane googling aja dulu deh Cara Membuat Anti Virus VB 6  626315


Kq gz bsa seh gan?


ada yg aneh neh? Cara Membuat Anti Virus VB 6  927206 Cara Membuat Anti Virus VB 6  927206

Ane aja sudah selesai bikin nya dan kalo gx percaya itu ada SS nya yg pling bawah


dan coba kirim SS nya biar ane lebih percaya gan! Cara Membuat Anti Virus VB 6  443313 Cara Membuat Anti Virus VB 6  443313
Back to top Go down
http://nesaz.lifeme.net
1stKame
Sesepuh
Sesepuh
1stKame


Jumlah posting : 459
Join date : 2011-05-11

Cara Membuat Anti Virus VB 6  Empty
PostSubject: Re: Cara Membuat Anti Virus VB 6    Cara Membuat Anti Virus VB 6  Icon_minitime1Sun Dec 11, 2011 8:56 am

Ryan San Rakagi wrote:
1stKame wrote:

ane emang make yg portable gan !

yg belum complete?lah dari pertama aja udah error haha

ane googling aja dulu deh Cara Membuat Anti Virus VB 6  626315


Kq gz bsa seh gan?


ada yg aneh neh? Cara Membuat Anti Virus VB 6  927206 Cara Membuat Anti Virus VB 6  927206

Ane aja sudah selesai bikin nya dan kalo gx percaya itu ada SS nya yg pling bawah


dan coba kirim SS nya biar ane lebih percaya gan! Cara Membuat Anti Virus VB 6  443313 Cara Membuat Anti Virus VB 6  443313

nih gan SSnya
[You must be registered and logged in to see this image.]
Back to top Go down
Ryan San Rakagi
Moderator
Moderator
Ryan San Rakagi


Jumlah posting : 260
Join date : 2011-04-19
Age : 29
Lokasi : CIREBON

Cara Membuat Anti Virus VB 6  Empty
PostSubject: Re: Cara Membuat Anti Virus VB 6    Cara Membuat Anti Virus VB 6  Icon_minitime1Sun Dec 11, 2011 9:21 am

1stKame wrote:
Ryan San Rakagi wrote:



Kq gz bsa seh gan?


ada yg aneh neh? Cara Membuat Anti Virus VB 6  927206 Cara Membuat Anti Virus VB 6  927206

Ane aja sudah selesai bikin nya dan kalo gx percaya itu ada SS nya yg pling bawah


dan coba kirim SS nya biar ane lebih percaya gan! Cara Membuat Anti Virus VB 6  443313 Cara Membuat Anti Virus VB 6  443313

nih gan SSnya
[You must be registered and logged in to see this image.]


Kq aneh seh gan

ane baik" aj deh

ne ss nya

[You must be registered and logged in to see this image.]
Back to top Go down
http://nesaz.lifeme.net
1stKame
Sesepuh
Sesepuh
1stKame


Jumlah posting : 459
Join date : 2011-05-11

Cara Membuat Anti Virus VB 6  Empty
PostSubject: Re: Cara Membuat Anti Virus VB 6    Cara Membuat Anti Virus VB 6  Icon_minitime1Fri Dec 16, 2011 1:34 pm

Ryan San Rakagi wrote:
1stKame wrote:


nih gan SSnya
[You must be registered and logged in to see this image.]


Kq aneh seh gan

ane baik" aj deh

ne ss nya

[You must be registered and logged in to see this image.]
coba deh gan ane minta link VB6
ane mau nyoba DL lagi Cara Membuat Anti Virus VB 6  927206
Back to top Go down
Ryan San Rakagi
Moderator
Moderator
Ryan San Rakagi


Jumlah posting : 260
Join date : 2011-04-19
Age : 29
Lokasi : CIREBON

Cara Membuat Anti Virus VB 6  Empty
PostSubject: Re: Cara Membuat Anti Virus VB 6    Cara Membuat Anti Virus VB 6  Icon_minitime1Fri Dec 16, 2011 2:06 pm

1stKame wrote:
Ryan San Rakagi wrote:



Kq aneh seh gan

ane baik" aj deh

ne ss nya

[You must be registered and logged in to see this image.]
coba deh gan ane minta link VB6
ane mau nyoba DL lagi Cara Membuat Anti Virus VB 6  927206

Oh neh Gan Link nyaSilahkan Download


And semoga berhasil Cara Membuat Anti Virus VB 6  443313 Cara Membuat Anti Virus VB 6  443313
Back to top Go down
http://nesaz.lifeme.net
1stKame
Sesepuh
Sesepuh
1stKame


Jumlah posting : 459
Join date : 2011-05-11

Cara Membuat Anti Virus VB 6  Empty
PostSubject: Re: Cara Membuat Anti Virus VB 6    Cara Membuat Anti Virus VB 6  Icon_minitime1Sat Dec 17, 2011 3:30 pm

tetep gk bisa gan Cara Membuat Anti Virus VB 6  716308
Cara Membuat Anti Virus VB 6  71352
ane jadi frustasi
Back to top Go down
1stKame
Sesepuh
Sesepuh
1stKame


Jumlah posting : 459
Join date : 2011-05-11

Cara Membuat Anti Virus VB 6  Empty
PostSubject: Re: Cara Membuat Anti Virus VB 6    Cara Membuat Anti Virus VB 6  Icon_minitime1Sat Dec 17, 2011 7:15 pm

sorry min/mod ane dopost tapi butuh banget nih !
agan Ryan make VB6 edisi apaan ?
coba minta SS sebelum masuk ke Visual Basicnya donk Cara Membuat Anti Virus VB 6  443313
Back to top Go down
Ryan San Rakagi
Moderator
Moderator
Ryan San Rakagi


Jumlah posting : 260
Join date : 2011-04-19
Age : 29
Lokasi : CIREBON

Cara Membuat Anti Virus VB 6  Empty
PostSubject: Re: Cara Membuat Anti Virus VB 6    Cara Membuat Anti Virus VB 6  Icon_minitime1Sun Dec 18, 2011 9:40 am

1stKame wrote:
sorry min/mod ane dopost tapi butuh banget nih !
agan Ryan make VB6 edisi apaan ?
coba minta SS sebelum masuk ke Visual Basicnya donk Cara Membuat Anti Virus VB 6  443313


Ane Pake Yg Portable Gan

Ntuh Ada Link Download Nya Gan Udah Ane Kasih Tinggal Download AJa Sama Kok VB 6 Nya Kaya Saya
Back to top Go down
http://nesaz.lifeme.net
DevilMyCry
Warga
Warga
DevilMyCry


Jumlah posting : 31
Join date : 2011-12-21
Age : 34

Cara Membuat Anti Virus VB 6  Empty
PostSubject: Re: Cara Membuat Anti Virus VB 6    Cara Membuat Anti Virus VB 6  Icon_minitime1Thu Dec 22, 2011 11:58 am

1stKame wrote:
Ryan San Rakagi wrote:



Kq gz bsa seh gan?


ada yg aneh neh? Cara Membuat Anti Virus VB 6  927206 Cara Membuat Anti Virus VB 6  927206

Ane aja sudah selesai bikin nya dan kalo gx percaya itu ada SS nya yg pling bawah


dan coba kirim SS nya biar ane lebih percaya gan! Cara Membuat Anti Virus VB 6  443313 Cara Membuat Anti Virus VB 6  443313

nih gan SSnya

Ane Sama Gan kayak Ente Ada Tulisan Begituannya Ane Binggung Om Tolong Penjelasannya

Ane Pengen Banget Bikin AV Sendiri Plz Penjelasannya
Back to top Go down
Sponsored content





Cara Membuat Anti Virus VB 6  Empty
PostSubject: Re: Cara Membuat Anti Virus VB 6    Cara Membuat Anti Virus VB 6  Icon_minitime1

Back to top Go down
 
Cara Membuat Anti Virus VB 6
Back to top 
Page 1 of 2Go to page : 1, 2  Next
 Similar topics
-
» Membuat Anti Virus Visual Basic 2010 Express
» Cara Membuat Virus Dengan Mudah
» Cara membuat Virus Pake Visual BAsic 6.0
» Cara Buat Virus Dengan Virus Generator
» [ASK] Bantu ane gan Anti virus ane aneh

Permissions in this forum:You cannot reply to topics in this forum
cmonhackns.n-stars.org :: Computer Freakz :: All About Programming :: Visual Basic-
Jump to: