Cyber Stars
Would you like to react to this message? Create an account in a few clicks or log in to continue.


™†|-Welcome To Forum-Cyber-Stars-|†™
 

IndeksPortalLatest imagesPendaftaranLoginV.I.P CheatPatnerWelcome To Info Cyber StarsINFO CHEAT
Login
Username:
Password:
Login otomatis: 
:: Lupa password?
Latest topics
» Soucer Code Multi Inject Game
[TUTORIAL] Create Injector Automatic EmptyThu Jul 21, 2016 1:29 pm by [C][S]Admin

» Cheat PointBlank Garena Simple Fitur HOT++
[TUTORIAL] Create Injector Automatic EmptyThu Aug 06, 2015 6:08 am by [C][S]Admin

» Cheat Pointblank Auto Headshot , Auto VK, WallHack 11-12 APRIL 2014
[TUTORIAL] Create Injector Automatic EmptySun Jun 28, 2015 7:20 pm by topik

» ++Cheat G-Cash Generator[Work 2014]++
[TUTORIAL] Create Injector Automatic EmptySat Apr 18, 2015 3:55 am by taufik hidayat

» CHEAT POINT BLANK 2014 EXP POINT BLANK 5 MENIT JADI BINTANG + MASMED TERSERAH ANDA MAU DI STOP DI PANGKAT APA
[TUTORIAL] Create Injector Automatic EmptySun Mar 22, 2015 8:24 am by fenoputra

» Point Blank aplikasi bobol email pertama 2014
[TUTORIAL] Create Injector Automatic EmptyWed Feb 18, 2015 11:35 am by fhaydodol

» YNG MAU CHEATER POINTBLANK ADD FB GWE ..BOLEH TUKAR CHAR SMA CHEAT >>>https://www.facebook.com/
[TUTORIAL] Create Injector Automatic EmptyMon Jan 05, 2015 2:57 pm by idarian

» YNG MAU CHEATER POINTBLANK ...HWID >> https://www.facebook.com/
[TUTORIAL] Create Injector Automatic EmptyMon Jan 05, 2015 2:46 pm by idarian

» CHEAT PB HACK PANGKAT POINT BLANK 2014 Terbaru Hott Anti Baned
[TUTORIAL] Create Injector Automatic EmptyTue Dec 30, 2014 8:32 am by jelsi88

May 2024
MonTueWedThuFriSatSun
  12345
6789101112
13141516171819
20212223242526
2728293031  
CalendarCalendar
Twitter Cyber Stars
Keywords
Top posting users this week
No user

 

 [TUTORIAL] Create Injector Automatic

Go down 
PengirimMessage
[C][S]VIP E999Cheaters
V.I.P [Cyeber Stars]
V.I.P [Cyeber Stars]
[C][S]VIP E999Cheaters


Jumlah posting : 10
Join date : 28.10.13

[TUTORIAL] Create Injector Automatic Empty
301013
Post[TUTORIAL] Create Injector Automatic

1. Siapkan VB 6
2. 1 BackGround Buat Injectornya Dan 1 Icon Buat Injectornya
3. Kesabaran

Biar Lebih Mudah, saya siapkan SC dari agan rifqi@N3 dan saya edit sedikit :

Untuk Link Download : Ada SC

Tutorialnya dengan Video, Bisa Didownload :

Downloadnya : VIDEO

Kreasikan Injector agan beserta DLLnya, Perhatikan Videonya Baik-Baik, Bila ada Masalah atau Tambahan silahkan Comment Post diBawah, No Junk, Sara. Cuma Diskusi .

From1
Code:

Option Explicit
'Created Date: 16 November 2013 And Edited 30 Desember 2013
'Form1 Universal Injector by www.cyber-stars.forumid.net and Edited By Cyber-Stars
Private Const GWL_EXSTYLE As Long = (-20)
Private Const WS_EX_LAYERED As Long = &H80000
Private Const LWA_ALPHA As Long = &H2
Private winHwnd As Long
Private NamaDll As String
Private NamaDll1 As String
Private Declare Function GetWindowLongA Lib "USER32" (ByVal hwnd As Long, _
ByVal nIndex As Long) As Long
Private Declare Function SetWindowLongA Lib "USER32" (ByVal hwnd As Long, _
ByVal nIndex As Long, _
ByVal dwNewLong As Long) As Long
Private Declare Function SetLayeredWindowAttributes Lib "USER32" (ByVal hwnd As Long, _
ByVal crey As Byte, _
ByVal bAlpha As Byte, _
ByVal dwFlags As Long) As Long

Private Sub silakandiedit()

'---------------------------------------------------------------
' silakan diedit bagian kode dibawah ini
'---------------------------------------------------------------
Dim Welcome As String
Welcome = MsgBox("Welcome To My Injector", vbInformation, "NStars Injector")
Welcome = MsgBox("Edit Sendiri Ya Gan", vbInformation, "NStars.Net")
Me.Caption = "Nama Injectornya Gan .." 'pengaturan caption atau nama injector
Opacity 150, Me 'pengaturan transparent form MinVal = 20: MaxVal = 255
NamaDll = App.Path & "\" & "NAMA DLL AGAN.dll" 'isikan nama library, contoh: wallshot.dll
NamaDll1 = App.Path & "\" & "NAMA DLL AGAN.dll"
FileTarget = "PointBlank.exe"
Timer1.Interval = 200 'interval untuk timer
Timer2.Interval = 20
Timer2.Enabled = True
WindowsMediaPlayer1.URL = App.Path & "MP3 AGAN.mp3" 'Audio Untuk Injectornya Gan
'----------------------------------------------------------------

End Sub

'fungsi transparent form
Private Sub Opacity(Value As Byte, _
Frm As Form)


Dim MaxVal As Byte
Dim MinVal As Byte

On Error GoTo ErrorHandler
MinVal = 20
MaxVal = 255
If Value > MaxVal Then
Value = MaxVal
End If
If Value < MinVal Then
Value = MinVal
End If
SetWindowLongA Frm.hwnd, GWL_EXSTYLE, GetWindowLongA(Frm.hwnd, GWL_EXSTYLE) Or WS_EX_LAYERED
SetLayeredWindowAttributes Frm.hwnd, 0, Value, LWA_ALPHA
ErrorHandler:

Exit Sub

End Sub

Private Sub Form_Load()

App.TaskVisible = False 'hidden aplikasi dari window taskmanager terserah mau true/false
'tetapi tidak hidden di process

'perintah menghindari aplikasi dijalankan 2 kali
'pada saat yg bersamaan
'----------------------------------------
If App.PrevInstance Then
End
End If
'----------------------------------------
silakandiedit '--> memanggil perintah pada -->> Private Sub silakandiedit()

End Sub


Private Sub Timer1_Timer()

winHwnd = FindWindow(vbNullString, "HSUpdate") 'mencari jendela hsupdate
If Not winHwnd = 0 Then 'jika ditemukan
NTProcessList 'deteksi process pointblank
InjectExecute (NamaDll) 'inject library
InjectExecute (NamaDll1)
End 'tutup otomatis injector
Else 'jika tidak
Label1.Caption = Mid(Label1.Caption, 2, Len(Label1.Caption) - 1) + Mid(Label1.Caption, 1, 1)
End If

End Sub
Private Sub Timer2_Timer()

WindowsMediaPlayer1.Controls.play

End Sub

Private Sub Form_QueryUnload(Cancel As Integer, UnloadMode As Integer)
OpenURL "http://cyber-stars.forumid.net", Me.hwnd
End Sub
ModInjector
Code:

Option Explicit
Private Declare Function GetProcAddress Lib "kernel32" (ByVal hModule As Long, _
ByVal lpProcName As String) As Long
Private Declare Function GetModuleHandle Lib "kernel32" Alias "GetModuleHandleA" (ByVal lpModuleName As String) As Long
Private Declare Function LoadLibrary Lib "kernel32" Alias "LoadLibraryA" (ByVal lpLibFileName As String) As Long
Private Declare Function VirtualAllocEx Lib "kernel32" (ByVal hProcess As Long, _
lpAddress As Any, _
ByVal dwSize As Long, _
ByVal fAllocType As Long, _
flProtect As Long) As Long
Private Declare Function WriteProcessMemory Lib "kernel32" (ByVal hProcess As Long, _
ByVal lpBaseAddress As Any, _
lpBuffer As Any, _
ByVal nSize As Long, _
lpNumberOfBytesWritten As Long) As Long
Private Declare Function CreateRemoteThread Lib "kernel32" (ByVal ProcessHandle As Long, _
lpThreadAttributes As Long, _
ByVal dwStackSize As Long, _
ByVal lpStartAddress As Any, _
ByVal lpParameter As Any, _
ByVal dwCreationFlags As Long, _
lpThreadID As Long) As Long
Private Declare Sub Sleep Lib "kernel32" (ByVal dwMilliseconds As Long)


Public Sub InjectDll(DllPath As String, _
ProsH As Long)


Dim DLLVirtLoc As Long
Dim DllLength As Long

Dim inject As Long
Dim LibAddress As Long
Dim CreateThread As Long
Dim ThreadID As Long
Dim Bla As VbMsgBoxResult
g_loadlibary:
LibAddress = GetProcAddress(GetModuleHandle("kernel32.dll"), "LoadLibraryA")
If LibAddress = 0 Then
Bla = MsgBox("Can't find LoadLibrary API from kernel32.dll", vbYesNo, "ERROR")
If Bla = vbYes Then
GoTo g_loadlibary
Else 'NOT BLA...
Exit Sub
End If
End If
g_virutalallocex:
DllLength = Len(DllPath)
DLLVirtLoc = VirtualAllocEx(ProsH, 0, DllLength, &H1000, ByVal &H4)
If DLLVirtLoc = 0 Then
Bla = MsgBox("VirtualAllocEx API failed! - try again?", vbYesNo, "ERROR")
If Bla = vbYes Then
GoTo g_virutalallocex
Else 'NOT BLA...
Exit Sub
End If
End If
g_writepmemory:
inject = WriteProcessMemory(ProsH, ByVal DLLVirtLoc, ByVal DllPath, DllLength, vbNull)
If inject = 0 Then
Bla = MsgBox("Failed to Write DLL to Process! - try again?", vbYesNo, "ERROR")
If Bla = vbYes Then
GoTo g_writepmemory
Else 'NOT BLA...
Exit Sub
End If
End If
g_creatthread:
CreateThread = CreateRemoteThread(ProsH, ByVal 0, 0, ByVal LibAddress, ByVal DLLVirtLoc, 0, ThreadID)
If CreateThread = 0 Then
Bla = MsgBox("Failed to Create Thead! - try again?", vbYesNo, "ERROR")
If Bla = vbYes Then
GoTo g_creatthread
Else 'NOT BLA...
Exit Sub
End If
End If

MsgBox "Dll Has Been Inject...", vbInformation, "NStars.Net"
End Sub

Public Sub InjectExecute(ByVal sFlDLL As String)

Dim lProcInject As Long

lProcInject = OpenProcess(PROCESS_ALL_ACCESS, 0, IdTargetOne)
If lProcInject > "0" Then
Call InjectDll(sFlDLL, lProcInject)

End If
Call CloseHandle(lProcInject)

End Sub
ModProcess
Code:

Option Explicit
Public FileTarget As String
Public sFlDLL As String
Public IdTargetOne As Long
Private Const TH32CS_SNAPHEAPLIST As Long = &H1
Private Const TH32CS_SNAPPROCESS As Long = &H2
Private Const TH32CS_SNAPTHREAD As Long = &H4
Private Const TH32CS_SNAPMODULE As Long = &H8
Private Const TH32CS_SNAPALL As Double = (TH32CS_SNAPHEAPLIST Or TH32CS_SNAPPROCESS Or TH32CS_SNAPTHREAD Or TH32CS_SNAPMODULE)
Private Const MAX_PATH As Integer = 260
Public Const PROCESS_ALL_ACCESS As Long = &H1F0FFF
Private Type PROCESSENTRY32
dwSize As Long
cntUsage As Long
th32ProcessID As Long
th32DefaultHeapID As Long
th32ModuleID As Long
cntThreads As Long
th32ParentProcessID As Long
pcPriClassBase As Long
dwFlags As Long
szExeFile As String * MAX_PATH
End Type
Private Type MODULEENTRY32
dwSize As Long
th32ModuleID As Long
th32ProcessID As Long
GlblcntUsage As Long
ProccntUsage As Long
modBaseAddr As Long
modBaseSize As Long
hModule As Long
szModule As String * 256
szExePath As String * 260
End Type
Private Type THREADENTRY32
dwSize As Long
cntUsage As Long
th32ThreadID As Long
th32OwnerProcessID As Long
tpBasePri As Long
tpDeltaPri As Long
dwFlags As Long
End Type
Private Const THREAD_SUSPEND_RESUME As Long = &H2
Private hThread As Long
Private Declare Function CreateToolhelp32Snapshot Lib "kernel32" (ByVal lFlags As Long, _
ByVal lProcessID As Long) As Long
Private Declare Function Module32First Lib "kernel32" (ByVal hSnapShot As Long, _
uProcess As MODULEENTRY32) As Long
Private Declare Function lstrlen Lib "kernel32" Alias "lstrlenA" (ByVal lpString As String) As Long
Private Declare Function GetFileTitle Lib "COMDLG32.DLL" Alias "GetFileTitleA" (ByVal lpszFile As String, _
ByVal lpszTitle As String, _
ByVal cbBuf As Integer) As Integer
Private Declare Function Thread32First Lib "kernel32.dll" (ByVal hSnapShot As Long, _
ByRef lpte As THREADENTRY32) As Boolean
Private Declare Function Thread32Next Lib "kernel32.dll" (ByVal hSnapShot As Long, _
ByRef lpte As THREADENTRY32) As Boolean
Public Declare Function OpenProcess Lib "kernel32" (ByVal dwDesiredAccess As Long, _
ByVal bInheritHandle As Long, _
ByVal dwProcessId As Long) As Long
Private Declare Function TerminateProcess Lib "kernel32" (ByVal hProcess As Long, _
ByVal uExitCode As Long) As Long
Public Declare Function FindWindow Lib "USER32" Alias "FindWindowA" (ByVal Classname As String, _
ByVal WindowName As String) As Long
Private Declare Function PostMessage Lib "USER32" Alias "PostMessageA" (ByVal hwnd As Long, _
ByVal wMsg As Long, _
ByVal wParam As Long, _
lParam As Any) As Long
Private Declare Function Process32First Lib "kernel32" (ByVal hSnapShot As Long, _
uProcess As PROCESSENTRY32) As Long
Private Declare Function Process32Next Lib "kernel32" (ByVal hSnapShot As Long, _
uProcess As PROCESSENTRY32) As Long
Public Declare Function CloseHandle Lib "kernel32" (ByVal hObject As Long) As Long
Private Declare Function OpenThread Lib "kernel32.dll" (ByVal dwDesiredAccess As Long, _
ByVal bInheritHandle As Boolean, _
ByVal dwThreadId As Long) As Long
Private Declare Function ResumeThread Lib "kernel32.dll" (ByVal hThread As Long) As Long
Private Declare Function SuspendThread Lib "kernel32.dll" (ByVal hThread As Long) As Long

Public Function NTProcessList() As Long

Dim FileName As String

Dim ExePath As String
Dim hProcSnap As Long
Dim hModuleSnap As Long
Dim lProc As Long
Dim uProcess As PROCESSENTRY32
Dim uModule As MODULEENTRY32
On Error Resume Next
hProcSnap = CreateToolhelp32Snapshot(TH32CS_SNAPALL, 0&)
uProcess.dwSize = Len(uProcess)
lProc = Process32First(hProcSnap, uProcess)
Do While lProc
If uProcess.th32ProcessID <> 0 Then
hModuleSnap = CreateToolhelp32Snapshot(TH32CS_SNAPALL, uProcess.th32ProcessID)
uModule.dwSize = Len(uModule)
Module32First hModuleSnap, uModule
If hModuleSnap > 0 Then
ExePath = StripNulls(uModule.szExePath)
FileName = GetFName(ExePath)
If FileTarget = FileName Then
IdTargetOne = uProcess.th32ProcessID
End If
End If
End If
lProc = Process32Next(hProcSnap, uProcess)
Loop
Call CloseHandle(hProcSnap)
Call CloseHandle(lProc)
On Error GoTo 0

End Function

Private Function StripNulls(ByVal sStr As String) As String


StripNulls = Left$(sStr, lstrlen(sStr))

End Function

Public Function GetFName(fn) As String
Dim f%, n%
GetFName = fn
f% = InStr(fn, "\")
Do While f%
n% = f%
f% = InStr(n% + 1, fn, "\")
Loop
If n% > 0 Then GetFName = Mid$(fn, n% + 1)
End Function

Private Function Thread32Enum(ByRef Thread() As THREADENTRY32, _
ByVal lProcessID As Long) As Long

Dim THREADENTRY32 As THREADENTRY32
Dim hThreadSnap As Long
Dim lThread As Long

On Error Resume Next
ReDim Thread(0) As THREADENTRY32
hThreadSnap = CreateToolhelp32Snapshot(TH32CS_SNAPTHREAD, lProcessID)
THREADENTRY32.dwSize = Len(THREADENTRY32)
If Thread32First(hThreadSnap, THREADENTRY32) = False Then
Thread32Enum = -1
Exit Function
Else
ReDim Thread(lThread) As THREADENTRY32
Thread(lThread) = THREADENTRY32
End If
Do
If Thread32Next(hThreadSnap, THREADENTRY32) = False Then
Exit Do
Else
lThread = lThread + 1
ReDim Preserve Thread(lThread)
Thread(lThread) = THREADENTRY32
End If
Loop
Thread32Enum = lThread
Call CloseHandle(hThreadSnap)
On Error GoTo 0

End Function

ModBrowser
Code:

'modul buka browser
Public Declare Function ShellExecute Lib "shell32.dll" Alias "ShellExecuteA" _
(ByVal hwnd As Long, _
ByVal lpOperation As String, _
ByVal lpFile As String, _
ByVal lpParameters As String, _
ByVal lpDirectory As String, _
ByVal nShowCmd As Long) As Long

Public Sub OpenURL(situs As String, sourceHWND As Long)
Call ShellExecute(sourceHWND, vbNullString, situs, vbNullString, vbNullString, 1)
End Sub
Klo Dah DiBuat Jangan Lupa Untuk Kreditnya ....


Klo Berguna Jangan Lupa:+: 
Cendol Cendol 
Kembali Ke Atas Go down
Share this post on: reddit

[TUTORIAL] Create Injector Automatic :: Comments

avatar
Re: [TUTORIAL] Create Injector Automatic
Post Mon Dec 23, 2013 5:41 pm by ghaina11
dll nya gak ke inject gan, knapa yahhhh Smile 
avatar
Re: [TUTORIAL] Create Injector Automatic
Post Mon Jan 06, 2014 9:48 am by mrsloli48
Option Explicit
'Created Date: 16 November 2013 And Edited 30 Desember 2013
'Form1 Universal Injector by www.cyber-stars.forumid.net and Edited By Cyber-Stars
Private Const GWL_EXSTYLE As Long = (-20)
Private Const WS_EX_LAYERED As Long = &H80000
Private Const LWA_ALPHA As Long = &H2
Private winHwnd As Long
Private NamaDll As String
Private NamaDll1 As String
Private Declare Function GetWindowLongA Lib "USER32" (ByVal hwnd As Long, _
ByVal nIndex As Long) As Long
Private Declare Function SetWindowLongA Lib "USER32" (ByVal hwnd As Long, _
ByVal nIndex As Long, _
ByVal dwNewLong As Long) As Long
Private Declare Function SetLayeredWindowAttributes Lib "USER32" (ByVal hwnd As Long, _
ByVal crey As Byte, _
ByVal bAlpha As Byte, _
ByVal dwFlags As Long) As Long

Private Sub silakandiedit()

'---------------------------------------------------------------
' silakan diedit bagian kode dibawah ini
'---------------------------------------------------------------
Dim Welcome As String
Welcome = MsgBox("Welcome To My Injector", vbInformation, "NStars Injector")
Welcome = MsgBox("Edit Sendiri Ya Gan", vbInformation, "NStars.Net")
Me.Caption = "Nama Injectornya Gan .." 'pengaturan caption atau nama injector
Opacity 150, Me 'pengaturan transparent form MinVal = 20: MaxVal = 255
NamaDll = App.Path & "\" & "NAMA DLL AGAN.dll" 'isikan nama library, contoh: wallshot.dll
NamaDll1 = App.Path & "\" & "NAMA DLL AGAN.dll"
FileTarget = "PointBlank.exe"
Timer1.Interval = 200 'interval untuk timer
Timer2.Interval = 20
Timer2.Enabled = True
WindowsMediaPlayer1.URL = App.Path & "MP3 AGAN.mp3" 'Audio Untuk Injectornya Gan
'----------------------------------------------------------------

End Sub

'fungsi transparent form
Private Sub Opacity(Value As Byte, _
Frm As Form)


Dim MaxVal As Byte
Dim MinVal As Byte

On Error GoTo ErrorHandler
MinVal = 20
MaxVal = 255
If Value > MaxVal Then
Value = MaxVal
End If
If Value < MinVal Then
Value = MinVal
End If
SetWindowLongA Frm.hwnd, GWL_EXSTYLE, GetWindowLongA(Frm.hwnd, GWL_EXSTYLE) Or WS_EX_LAYERED
SetLayeredWindowAttributes Frm.hwnd, 0, Value, LWA_ALPHA
ErrorHandler:

Exit Sub

End Sub

Private Sub Form_Load()

App.TaskVisible = False 'hidden aplikasi dari window taskmanager terserah mau true/false
'tetapi tidak hidden di process

'perintah menghindari aplikasi dijalankan 2 kali
'pada saat yg bersamaan
'----------------------------------------
If App.PrevInstance Then
End
End If
'----------------------------------------
silakandiedit '--> memanggil perintah pada -->> Private Sub silakandiedit()

End Sub


Private Sub Timer1_Timer()

winHwnd = FindWindow(vbNullString, "HSUpdate") 'mencari jendela hsupdate
If Not winHwnd = 0 Then 'jika ditemukan
NTProcessList 'deteksi process pointblank
InjectExecute (NamaDll) 'inject library
InjectExecute (NamaDll1)
End 'tutup otomatis injector
Else 'jika tidak
Label1.Caption = Mid(Label1.Caption, 2, Len(Label1.Caption) - 1) + Mid(Label1.Caption, 1, 1)
End If

End Sub
Private Sub Timer2_Timer()

WindowsMediaPlayer1.Controls.play

End Sub

Private Sub Form_QueryUnload(Cancel As Integer, UnloadMode As Integer)
OpenURL "https://cyber-stars.forumid.net", Me.hwnd
End Sub
avatar
Re: [TUTORIAL] Create Injector Automatic
Post Mon Jan 06, 2014 9:49 am by mrsloli48
Option Explicit
'Created Date: 16 November 2013 And Edited 30 Desember 2013
'Form1 Universal Injector by www.cyber-stars.forumid.net and Edited By Cyber-Stars
Private Const GWL_EXSTYLE As Long = (-20)
Private Const WS_EX_LAYERED As Long = &H80000
Private Const LWA_ALPHA As Long = &H2
Private winHwnd As Long
Private NamaDll As String
Private NamaDll1 As String
Private Declare Function GetWindowLongA Lib "USER32" (ByVal hwnd As Long, _
ByVal nIndex As Long) As Long
Private Declare Function SetWindowLongA Lib "USER32" (ByVal hwnd As Long, _
ByVal nIndex As Long, _
ByVal dwNewLong As Long) As Long
Private Declare Function SetLayeredWindowAttributes Lib "USER32" (ByVal hwnd As Long, _
ByVal crey As Byte, _
ByVal bAlpha As Byte, _
ByVal dwFlags As Long) As Long

Private Sub silakandiedit()

'---------------------------------------------------------------
' silakan diedit bagian kode dibawah ini
'---------------------------------------------------------------
Dim Welcome As String
Welcome = MsgBox("Welcome To My Injector", vbInformation, "NStars Injector")
Welcome = MsgBox("Edit Sendiri Ya Gan", vbInformation, "NStars.Net")
Me.Caption = "Nama Injectornya Gan .." 'pengaturan caption atau nama injector
Opacity 150, Me 'pengaturan transparent form MinVal = 20: MaxVal = 255
NamaDll = App.Path & "\" & "NAMA DLL AGAN.dll" 'isikan nama library, contoh: wallshot.dll
NamaDll1 = App.Path & "\" & "NAMA DLL AGAN.dll"
FileTarget = "PointBlank.exe"
Timer1.Interval = 200 'interval untuk timer
Timer2.Interval = 20
Timer2.Enabled = True
WindowsMediaPlayer1.URL = App.Path & "MP3 AGAN.mp3" 'Audio Untuk Injectornya Gan
'----------------------------------------------------------------

End Sub

'fungsi transparent form
Private Sub Opacity(Value As Byte, _
Frm As Form)


Dim MaxVal As Byte
Dim MinVal As Byte

On Error GoTo ErrorHandler
MinVal = 20
MaxVal = 255
If Value > MaxVal Then
Value = MaxVal
End If
If Value < MinVal Then
Value = MinVal
End If
SetWindowLongA Frm.hwnd, GWL_EXSTYLE, GetWindowLongA(Frm.hwnd, GWL_EXSTYLE) Or WS_EX_LAYERED
SetLayeredWindowAttributes Frm.hwnd, 0, Value, LWA_ALPHA
ErrorHandler:

Exit Sub

End Sub

Private Sub Form_Load()

App.TaskVisible = False 'hidden aplikasi dari window taskmanager terserah mau true/false
'tetapi tidak hidden di process

'perintah menghindari aplikasi dijalankan 2 kali
'pada saat yg bersamaan
'----------------------------------------
If App.PrevInstance Then
End
End If
'----------------------------------------
silakandiedit '--> memanggil perintah pada -->> Private Sub silakandiedit()

End Sub


Private Sub Timer1_Timer()

winHwnd = FindWindow(vbNullString, "HSUpdate") 'mencari jendela hsupdate
If Not winHwnd = 0 Then 'jika ditemukan
NTProcessList 'deteksi process pointblank
InjectExecute (NamaDll) 'inject library
InjectExecute (NamaDll1)
End 'tutup otomatis injector
Else 'jika tidak
Label1.Caption = Mid(Label1.Caption, 2, Len(Label1.Caption) - 1) + Mid(Label1.Caption, 1, 1)
End If

End Sub
Private Sub Timer2_Timer()

WindowsMediaPlayer1.Controls.play

End Sub

Private Sub Form_QueryUnload(Cancel As Integer, UnloadMode As Integer)
OpenURL "https://cyber-stars.forumid.net", Me.hwnd
End Sub
 

[TUTORIAL] Create Injector Automatic

Kembali Ke Atas 

Halaman 1 dari 1

 Similar topics

-
»  Memasukan File Mp3 ke dalam Injector
» New Update Cheat LS NO Delay | 1 Hit Crusade NO DC New Tutorial Work All Win 100 %

Permissions in this forum:Anda tidak dapat menjawab topik
Cyber Stars :: Programing :: Virsual Basic-
Navigasi: