Jumat, 25 April 2014





dari pada ane suntuk lebih baik ane share tutorial :D bener gak bro :p
nah pada masalah ini kita akan membuat taks manager dengan vb6 emang bisa ya bro ???? :p ya jelas bisa lah nama nya juga program selalu bisa :p
oke deh sekarang kita langsung aja ya lagi males ngetik ane =))
alat dan bahan :

  • 1 buah form 
  • 5 comand button
  • 1 listbox
  • 1 timer
sekarang atur masing masing sesuai selera anda ya :D =))
lihat bagian ini :

Caption name
Properties cmdProperties
Ignore Safe List cmdIgnoreSL
Move To Safe List cmdMoveSL
Terminate cmdTerminate
View Safe List cmdViewSL

pada bagian timer & listbox bagian name  lihat di sini

Caption name
timer1 tmrlist
listbox1 lstProcesses

sekarang masukan source code nya di bagian form

' visit me www.visual-basicku.blogspot.com
' free download software & source code visual basic
' add my facebook http://facebook.com/bang.hambran

Option Explicit
Const MAX_PATH& = 260
Const SNAPPROCESS As Long = 2&
Const SEE_MASK_INVOKEIDLIST = &HC
Const SEE_MASK_NOCLOSEPROCESS = &H40
Const SEE_MASK_FLAG_NO_UI = &H400
Const STANDARD_RIGHTS_REQUIRED As Long = &HF0000
Const PROCESS_TERMINATE As Long = (&H1)
Const GWL_WNDPROC = (-4)
Const PM_REMOVE = &H1
Const MOD_ALT = &H1
Const MOD_CONTROL = &H2
Const MOD_SHIFT = &H4
Const WM_HOTKEY = &H312
Private Declare Function ShellExecuteEX Lib "shell32.dll" Alias "ShellExecuteEx" (SEI As SHELLEXECUTEINFO) As Long
Private Declare Function ProcessFirst Lib "kernel32" Alias "Process32First" (ByVal hSnapshot As Long, uProcess As PROCESSENTRY) As Long
Private Declare Function ProcessNext Lib "kernel32" Alias "Process32Next" (ByVal hSnapshot As Long, uProcess As PROCESSENTRY) As Long
Private Declare Function CreateToolHelpSnapshot Lib "kernel32" Alias "CreateToolhelp32Snapshot" (ByVal lFlags As Long, lProcessID As Long) As Long
Private Declare Function CloseHandle Lib "kernel32" (ByVal hObject As Long) As Long
Private Declare Function OpenProcess Lib "kernel32.dll" (ByVal dwDesiredAccess As Long, ByVal bInheritHandle As Long, ByVal dwProcessId As Long) As Long
Private Declare Function TerminateProcess Lib "kernel32.dll" (ByVal hProcess As Long, ByVal uExitCode As Long) As Long
Private Declare Function GetAsyncKeyState Lib "user32.dll" () As Long
Private Declare Function CallWindowProc Lib "user32" Alias "CallWindowProcA" (ByVal lpPrevWndFunc As Long, ByVal hWnd As Long, ByVal MSG As Long, ByVal wParam As Long, ByVal lParam As Long) As Long
Private Declare Function RegisterHotKey Lib "user32" (ByVal hWnd As Long, ByVal id As Long, ByVal fsModifiers As Long, ByVal vk As Long) As Long
Private Declare Function UnregisterHotKey Lib "user32" (ByVal hWnd As Long, ByVal id 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 Declare Function PeekMessage Lib "user32" Alias "PeekMessageA" (lpMsg As MSG, ByVal hWnd As Long, ByVal wMsgFilterMin As Long, ByVal wMsgFilterMax As Long, ByVal wRemoveMsg As Long) As Long
Private Declare Function WaitMessage Lib "user32" () As Long
Private Type PROCESSENTRY
    Size As Long
    Usage As Long
    ProcessID As Long
    DefaultHeapID As Long
    ModuleID As Long
    Threads As Long
    ParentProcessID As Long
    PriClassBase As Long
    Flags As Long
    ExeFile As String * MAX_PATH
End Type
Private Type SHELLEXECUTEINFO
    Size As Long
    Mask As Long
    hWnd As Long
    Verb As String
    File As String
    Parameters As String
    Directory  As String
    Show  As Long
    InstApp As Long
    IDList  As Long
    Class  As String
    KeyClass As Long
    HotKey As Long
    Icon As Long
    Process  As Long
End Type
Private Type POINTAPI
    X As Long
    Y As Long
End Type
Private Type MSG
    hWnd As Long
    Message As Long
    wParam As Long
    lParam As Long
    Time As Long
    Pt As POINTAPI
End Type
Dim strstr As String
Dim SafeList() As String
Dim SLEnabled As Boolean
Dim Processing As Boolean

Private Sub cmdExit_Click()
End
End Sub
' visit me www.visual-basicku.blogspot.com
' free download software & source code visual basic
' add my facebook http://facebook.com/bang.hambran

Private Sub cmdIgnoreSL_Click()
If cmdIgnoreSL.Caption = "&Ignore Safe List" Then
    cmdIgnoreSL.Caption = "&Hide Safe List"
Else
    cmdIgnoreSL.Caption = "&Ignore Safe List"
End If
SLEnabled = Not SLEnabled
GetList
End Sub
' visit me www.visual-basicku.blogspot.com
' free download software & source code visual basic
' add my facebook http://facebook.com/bang.hambran

Private Sub cmdMoveSL_Click()
If Len(lstProcesses.Text) = 0 Then Exit Sub
ReDim Preserve SafeList(UBound(SafeList) + 1)
SafeList(UBound(SafeList)) = lstProcesses.Text
GetList
If lstProcesses.ListCount Then lstProcesses.ListIndex = 0
End Sub
' visit me www.visual-basicku.blogspot.com
' free download software & source code visual basic
' add my facebook http://facebook.com/bang.hambran

Private Sub cmdTerminate_Click()
Dim Process As PROCESSENTRY
Dim ProcessFound As Long
Dim Snapshot As Long
Dim ExeName As String
Dim AppCount As Integer
Dim NLoc As Integer
Dim CurrFile As String
Dim Count As Integer
Dim PrevProcessID As Long
Process.Size = Len(Process)
Snapshot = CreateToolHelpSnapshot(SNAPPROCESS, 0&)
ProcessFound = ProcessFirst(Snapshot, Process)
CurrFile = lstProcesses.Text
lstProcesses.Clear
Do While ProcessFound
    NLoc = InStr(1, Process.ExeFile, Chr(0))
    ExeName = LCase$(Left$(Process.ExeFile, NLoc - 1))
    ProcessFound = ProcessNext(Snapshot, Process)
    If ExeName = CurrFile Then
        KillProcess PrevProcessID
        GetList
        Exit Sub
    End If
    PrevProcessID = Process.ProcessID
Loop
If lstProcesses.ListCount Then lstProcesses.ListIndex = 0
End Sub
' visit me www.visual-basicku.blogspot.com
' free download software & source code visual basic
' add my facebook http://facebook.com/bang.hambran

Private Sub cmdViewSL_Click()
Dim Count As Integer
Dim SL As String
For Count = 0 To UBound(SafeList)
    If Len(SL) Then
        SL = SL & vbNewLine & SafeList(Count)
    Else
        SL = SafeList(Count)
    End If
Next Count
MsgBox SL
End Sub
' visit me www.visual-basicku.blogspot.com
' free download software & source code visual basic
' add my facebook http://facebook.com/bang.hambran

Private Sub Form_Load()
Dim SL As String
Dim Count As Integer, Index As Integer
Open App.Path & "/SAFELIST.dat" For Binary As #1
    SL = String(LOF(1), vbNullChar)
    Get #1, , SL
Close #1
For Count = 1 To Len(SL)
    If Mid$(SL, Count, 2) = vbNewLine Then Index = Index + 1
Next Count
ReDim SafeList(Index)
For Count = 0 To Index - 1
    SafeList(Count) = Left$(SL, InStr(1, SL, vbNewLine) - 1)
    SL = Right$(SL, Len(SL) - Len(SafeList(Count)) - 2)
Next Count
SafeList(Count) = SL
SLEnabled = True
GetList
Processing = True
RegisterHotKey Me.hWnd, &HBFFF&, MOD_CONTROL Or MOD_ALT, vbKeyP
Me.Show
ProcessMessages
End Sub
' visit me www.visual-basicku.blogspot.com
' free download software & source code visual basic
' add my facebook http://facebook.com/bang.hambran

Private Sub GetList()
Dim Process As PROCESSENTRY
Dim ProcessFound As Long
Dim Snapshot As Long
Dim ExeName As String
Dim AppCount As Integer
Dim NLoc As Integer
Dim CurrFile As String
Dim Count As Integer
Process.Size = Len(Process)
Snapshot = CreateToolHelpSnapshot(SNAPPROCESS, 0&)
ProcessFound = ProcessFirst(Snapshot, Process)
CurrFile = lstProcesses.Text
lstProcesses.Clear
Do While ProcessFound
    NLoc = InStr(1, Process.ExeFile, Chr(0))
    ExeName = LCase$(Left$(Process.ExeFile, NLoc - 1))
    ProcessFound = ProcessNext(Snapshot, Process)
    If SLEnabled Then
        For Count = 0 To UBound(SafeList)
            If SafeList(Count) = ExeName Then GoTo SkipDisp
        Next Count
    End If
    lstProcesses.AddItem ExeName
SkipDisp:
Loop
For Count = 0 To lstProcesses.ListCount - 1
    If lstProcesses.List(Count) = CurrFile Then lstProcesses.ListIndex = Count
Next Count
End Sub
' visit me www.visual-basicku.blogspot.com
' free download software & source code visual basic
' add my facebook http://facebook.com/bang.hambran
Sub ShowFileProperties(File As String)
    Dim SEI As SHELLEXECUTEINFO
    With SEI
        .Size = Len(SEI)
        .Mask = SEE_MASK_NOCLOSEPROCESS Or SEE_MASK_INVOKEIDLIST Or SEE_MASK_FLAG_NO_UI
        .Verb = "Properties"
        .File = File
    End With
    ShellExecuteEX SEI
End Sub
' visit me www.visual-basicku.blogspot.com
' free download software & source code visual basic
' add my facebook http://facebook.com/bang.hambran

Private Sub cmdProperties_Click()
If Len(lstProcesses.Text) Then ShowFileProperties lstProcesses.Text
End Sub
' visit me www.visual-basicku.blogspot.com
' free download software & source code visual basic
' add my facebook http://facebook.com/bang.hambran

Private Sub Form_Terminate()
Processing = False
UnregisterHotKey Me.hWnd, &HBFFF&
End Sub
' visit me www.visual-basicku.blogspot.com
' free download software & source code visual basic
' add my facebook http://facebook.com/bang.hambran
Private Sub Form_Unload(Cancel As Integer)
End
End Sub
' visit me www.visual-basicku.blogspot.com
' free download software & source code visual basic
' add my facebook http://facebook.com/bang.hambran
Private Sub tmrGetList_Timer()
GetList
End Sub
' visit me www.visual-basicku.blogspot.com
' free download software & source code visual basic
' add my facebook http://facebook.com/bang.hambran
Private Function KillProcess(ByVal ProcessID As Long) As Boolean
Dim Process As Long
Const RIGHTS_FLAGS = STANDARD_RIGHTS_REQUIRED Or PROCESS_TERMINATE
Process = OpenProcess(RIGHTS_FLAGS, 0&, ProcessID)
If Process Then
    If TerminateProcess(Process, 0&) Then
        KillProcess = True
    End If
    Call CloseHandle(Process)
End If
End Function
Private Sub ProcessMessages()
Dim Message As MSG
Do While Processing
    WaitMessage
    If PeekMessage(Message, Me.hWnd, WM_HOTKEY, WM_HOTKEY, PM_REMOVE) Then
        Me.Visible = True
    End If
    DoEvents
Loop
End Sub
' visit me www.visual-basicku.blogspot.com
' free download software & source code visual basic
' add my facebook http://facebook.com/bang.hambran

dan sekarang coba di jalan kan lihat hasil nya
ini contoh program ane :

bagi yang mau download source code nya :

https://www.dropbox.com/s/d3dpfr5va15kigx/taksmanager-visualbasicku.rar

 semoga bermanfaat ^_^ untuk mendapatkan tutorial terbaru bisa follow Saya :)
Categories:

0 komentar:

Posting Komentar