Track Cyber-Hecker

* Mohon Patuhi Peraturan Forum

* Hukuman Bagi User Yang Melanggar :

* Warning 1 = Peringatan
* Warning 2 = Libur Post 1 hari
* Warning 3 = Libur Post 3 hari
* Warning 4 = Libur Post 7 hari
* Warning 5 = Ban Permanen

* Warning UP = Banned Permanent

Track Cyber-Hecker

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

Sosial Comunity

Login

Lupa password?

March 2024

MonTueWedThuFriSatSun
    123
45678910
11121314151617
18192021222324
25262728293031

Calendar Calendar


    Auto Injector (noSusped)

    VzGrey
    VzGrey
    +
                    +


    Points : 1177
    Reputation : 3
    Join date : 27.05.11
    Lokasi : Bandunk

    Auto Injector (noSusped) Empty Auto Injector (noSusped)

    Post by VzGrey Sun Jun 26, 2011 3:02 am

    kali ini saya coba shear Auto injector

    Bhan Visual basic 6

    1.Buat 1from
    -2Timer
    -1Label

    Klick Kanan From 'plih view code dan masukan SC ini


    Code:
    'By Me VzGrey
    'Special Thabk To Kress-K4 amd all N3 Snut.us
    'And Suhu Sapta_Agunk Thank for all

    Option Explicit
    Dim I As Long
    Dim merah, hijau, biru As Integer
    Dim Counter As Integer
    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 Declare Function ReleaseCapture Lib "user32" () As Long
    Private Declare Function SendMessage Lib "user32" Alias "SendMessageA" (ByVal hWnd As Long, ByVal wMsg As Long, ByVal wParam As Long, lParam As Long) As Long
    Private Declare Function CreateRoundRectRgn Lib "gdi32" (ByVal X1 As Long, ByVal Y1 As Long, ByVal X2 As Long, ByVal Y2 As Long, ByVal X3 As Long, ByVal Y3 As Long) As Long
    Private Declare Function CreateEllipticRgn Lib "gdi32" (ByVal X1 As Long, ByVal Y1 As Long, ByVal X2 As Long, ByVal Y2 As Long) As Long
    Private Declare Function SetWindowRgn Lib "user32" (ByVal hWnd As Long, ByVal hRgn As Long, ByVal bRedraw As Boolean) As Long
    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 VzGreyInjecktor()

        Me.Caption = "VzGreyInjecktor" ' nama injector pada Form
        Opacity 240, Me
        NamaDll = App.Path & "" & "Name.dll" '
        FileTarget = "PointBlank.exe"
        Timer1.Interval = 20
       

    End Sub

    'Pengaturan 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()
    Dim l As Long
    l = CreateRoundRectRgn(0, 0, Me.Width / Screen.TwipsPerPixelX, Me.Height / Screen.TwipsPerPixelY, 20, 20)
    SetWindowRgn Me.hWnd, l, True
        App.TaskVisible = True 'Menyembunyikan  aplikasi dari window taskmanager  true= untuk menampilkan /false Untuk Tidak menampilkan
                                'tetapi tidak hidden di process
                               
        'perintah menghindari aplikasi dijalankan 2 kali
        'pada saat yg bersamaan
        '----------------------------------------
        If App.PrevInstance Then
            End
        End If
        '----------------------------------------
        VzGreyInjecktor '--> memanggil perintah pada -->> Private Sub silakandiedit()

    End Sub


    Private Sub Form_MouseDown(Button As Integer, Shift As Integer, X As Single, Y As Single)
    If Button = 1 Then
    ReleaseCapture
    SendMessage Me.hWnd, &HA1, 2, 0
    End If
    End Sub



    Private Sub Label1_Click()
    'Untuk kecepatan Perubahan Warna Silakan Di Ubah Interval Pada Timer2
    'semakin Kecil intervalnya maka akan Semakin Cepat Perubahan Warnanya
    End Sub

    Private Sub Timer1_Timer()
        winHwnd = FindWindow(vbNullString, "HSUpdate")
        If Not winHwnd = 0 Then
            NTProcessList
            InjectExecute (NamaDll)
            End
        Else
            Label1.Caption = "VzGreyInjecktor Please Wait" '
        End If

    End Sub

    Private Sub Timer2_Timer()

    I = I + 1
      If I = 1000000 Then I = 0
      merah = Int(255 * Rnd)
      hijau = Int(255 * Rnd)
      biru = Int(255 * Rnd)
      Label1.ForeColor = RGB(merah, hijau, biru)
      If I Mod 2 = 0 Then
        Label1.Visible = True
      Else
        Label1.Visible = False
      End If
    End Sub
    Private Sub Form_QueryUnload(Cancel As Integer, UnloadMode As Integer)
    OpenURL "http://trackcyber-hecker.forumid.net", Me.hWnd
    End Sub


    2.Buat 2BUah Modules Dengan Name
    -1.VzGreyMain
    -2.modbrowser

    -Di Modules 1 masukan SC ini

    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
    Private Declare Function SetLayeredWindowAttributes Lib "user32" (ByVal hWnd As Long, ByVal crKey As Long, ByVal bAlpha As Byte, ByVal dwFlags As Long) As Long
    Private Declare Function UpdateLayeredWindow Lib "user32" (ByVal hWnd As Long, ByVal hdcDst As Long, pptDst As Any, psize As Any, ByVal hdcSrc As Long, pptSrc As Any, crKey As Long, ByVal pblend As Long, ByVal dwFlags As Long) As Long
    Private Declare Function GetWindowLong Lib "user32" Alias "GetWindowLongA" (ByVal hWnd As Long, ByVal nIndex As Long) As Long
    Private Declare Function SetWindowLong Lib "user32" Alias "SetWindowLongA" (ByVal hWnd As Long, ByVal nIndex As Long, ByVal dwNewLong As Long) As Long

    Private Const GWL_EXSTYLE = (-20)
    Private Const LWA_COLORKEY = &H1
    Private Const LWA_ALPHA = &H2
    Private Const ULW_COLORKEY = &H1
    Private Const ULW_ALPHA = &H2
    Private Const ULW_OPAQUE = &H4
    Private Const WS_EX_LAYERED = &H80000
        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
    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 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

    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 Injection Successful!", vbInformation, "VzGreyInjecktor"
    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
    Public Function isTransparent(ByVal hWnd As Long) As Boolean
    On Error Resume Next
    Dim Msg As Long
    Msg = GetWindowLong(hWnd, GWL_EXSTYLE)
    If (Msg And WS_EX_LAYERED) = WS_EX_LAYERED Then
      isTransparent = True
    Else
      isTransparent = False
    End If
    If Err Then
      isTransparent = False
    End If
    End Function

    Public Function MakeTransparent(ByVal hWnd As Long, Perc As Integer) As Long
    Dim Msg As Long
    On Error Resume Next
    If Perc < 0 Or Perc > 255 Then
      MakeTransparent = 1
    Else
      Msg = GetWindowLong(hWnd, GWL_EXSTYLE)
      Msg = Msg Or WS_EX_LAYERED
      SetWindowLong hWnd, GWL_EXSTYLE, Msg
      SetLayeredWindowAttributes hWnd, 0, Perc, LWA_ALPHA
      MakeTransparent = 0
    End If
    If Err Then
      MakeTransparent = 2
    End If
    End Function

    Public Function MakeOpaque(ByVal hWnd As Long) As Long
    Dim Msg As Long
    On Error Resume Next
    Msg = GetWindowLong(hWnd, GWL_EXSTYLE)
    Msg = Msg And Not WS_EX_LAYERED
    SetWindowLong hWnd, GWL_EXSTYLE, Msg
    SetLayeredWindowAttributes hWnd, 0, 0, LWA_ALPHA
    MakeOpaque = 0
    If Err Then
      MakeOpaque = 2
    End If
    End Function






    -Modules K.2 masukan SC ini
    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







    Nb: lau terjdi eror coba di cari mungkin ada yg slah tau kurang teliti
    untuk name injector mesti sama pas kalian mau MakeProject1.exe
    di Me.Caption = "harus sama dengan nma Injector"





    By Me. VzGrey
    Special Thank to:
    Kress-K4
    Sampta_agunk
    rifki

      Waktu sekarang Thu Mar 28, 2024 8:16 pm