Wednesday, April 7, 2010

Parse HTML Code Untuk Postingan

Fasilitas di bawah ini adalah untuk mengkonversi kode HTML yang diperuntukan untuk postingan, sehingga tampil sesuai dengan yang diharapkan.


Jika Anda ingin memasangnya di blog Anda sendiri, di bawah ini adalah kodenya, kopi dan pastekan:
<script src="http://www.gmodules.com/ig/ifr?url=http://hosting.gmodules.com/ig/gadgets/file/102462998830435293579/post-Code.xml&amp;up_grows=10&amp;up_conv1=1&amp;up_conv2=1&amp;up_conv3=1&amp;up_conv4=1&amp;up_conv5=1&amp;synd=open&amp;w=520&amp;h=500&amp;title=Post-Code%3A+code+converter&amp;border=%23ffffff%5C0px%2C1px+solid+%23595959%5C0px%2C1px+solid+%23797979%7C0px%2C2px+solid+%23898989&amp;output=js"></script>
READ MORE - Parse HTML Code Untuk Postingan

Kode Kerangka Untuk Template Blogspot

<html>
<head>
<title>Skeleton of a 2 Column Blogger Template</title>
<style type='text/css'>
body
{
 font-family:Arial;
}
#outer-wrapper
{
 width: 682px;
 border: 1px dotted;
 background: #dddddd;
 margin:0px auto 0;
 padding:10px;
}
#header-wrapper
{
 width:660px;
 height: 100px;
 border: 1px dotted;
 background: #fefe99;
 margin-bottom: 10px;
 padding:10px;
}
#content-wrapper
{
 width: 660px;
 height: 280px;
 border: 1px dotted;
 background: #fefe99;
 margin-bottom: 10px;
 padding:10px;
}
#main-wrapper
{
 width: 410px;
 height: 200px;
 border: 1px dotted;
 background: #a0cffd;
 float: left;
}
#sidebar-wrapper
{
 width: 220px;
 height: 250px;
 border: 1px dotted;
 background: #a0cffd;
 float: right;
}
#footer-wrapper
{
 width: 660px;
 height: 50px;
 border: 1px dotted;
 background: #fefe99;
 padding:10px;
}
</style>
</head>
<body>
<div id='outer-wrapper'>
  <div id='header-wrapper'>
   <p>Header</p>
   </div>
  <div id='content-wrapper'>
   <div id='main-wrapper'>
    <p>Main</p>
   </div>
   <div id='sidebar-wrapper'>
    <p>Side Bar</p>
   </div>
   </div>
  <div id='footer-wrapper'>
   <p>Footer</p>
  </div> 
</div>
</body>
</html>
READ MORE - Kode Kerangka Untuk Template Blogspot

Sunday, April 4, 2010

VB6 Code - Apakah SoundCard Ada?

Di bawah ini merupakan fungsi VB6 untuk mengetahui apakah komputer memiliki souncard atau tidak.
Option Explicit

Private Declare Function waveOutGetNumDevs Lib "winmm.dll" () As Long

Public Function IsExistSoundCard() As Boolean
Dim I As Integer
I = waveOutGetNumDevs()
IsExistSoundCard = (I > 0)
End Function
Contoh penggunaan fungsi memeriksa keberadaan sound card pada komputer
Private Sub Command1_Click()
MsgBox IsExistSoundCard
End Sub
READ MORE - VB6 Code - Apakah SoundCard Ada?

VB6 Code - Membuat Kata Secara Acak (Random)

Di bawah ini merupakan fungsi VB6 code untuk membuat sebuah kata secara acak.
Option Explicit

Public Function RandomString(Optional Max As Integer = 5) As String

Dim sAlpha As String
Dim iLoop As Integer
Dim iRandNum As Integer
Dim sMatch As String
Dim str As String
sAlpha = "abcdefghijklmnopqrstuvwxyz"

Randomize

For iLoop = 1 To Max
iRandNum = Int((26 - 1 + 1) * Rnd + 1)
sMatch = Mid(sAlpha, iRandNum, 1)
str = str & sMatch
Next iLoop

RandomString = str

End Function
Contoh penggunaan fungsi menampilkan kata secara acak
Private Sub Command1_Click()
MsgBox RandomString 10
End Sub
READ MORE - VB6 Code - Membuat Kata Secara Acak (Random)

VB6 Code - Fungsi Untuk Menjadikan Blank Layar Komputer

Di bawah ini merupakan fungsi VB6 untuk mematikan layar monitor.
Option Explicit

Private Declare Function SendMessage Lib "user32" Alias "SendMessageA" (ByVal hwnd As Long, ByVal wMsg As Long, ByVal wParam As Long, lParam As Any) As Long

Private Const MONITOR_ON = -1&
Private Const MONITOR_LOWPOWER = 1&
Private Const MONITOR_OFF = 2&
Private Const SC_MONITORPOWER = &HF170&
Private Const WM_SYSCOMMAND = &H112

Public Function TurnOnMonitor(hwnd As Long, bFlag As Boolean) As Boolean
If bFlag Then
Call SendMessage(hwnd, WM_SYSCOMMAND, SC_MONITORPOWER, ByVal MONITOR_ON)
Else
Call SendMessage(hwnd, WM_SYSCOMMAND, SC_MONITORPOWER, ByVal MONITOR_OFF)
End If
End Function
Contoh penggunaan kode di atas:
Option Explicit

Private Sub Command1_Click()
TurnOnMonitor Me.hwnd, False
End Sub
READ MORE - VB6 Code - Fungsi Untuk Menjadikan Blank Layar Komputer

VB6 Code - Informasi Mengenai Printer Yang Terinstall

Di bawah ini merupakan cara memperoleh/mengetahui informasi mengenai printer yang terinstall.
Option Explicit

Public Function ListAllPrinters(lst As Control)
Dim oPrint As Object
For Each oPrint In Printers
List1.AddItem oPrint.DeviceName
Next
End Function
Contoh penggunaan mengenai printer yang terinstall
Private Sub Form_Load()
ListAllPrinters List1
End Sub
READ MORE - VB6 Code - Informasi Mengenai Printer Yang Terinstall

VB6 Code - Fungsi Untuk Mengetahui Default Printer

Di bawah ini merupakan fungsi untuk mengetahui default printer yang sedang digunakan menggunakan kode VB6:
Option Explicit

Function DefPrintName() As String
DefPrintName = Printer.DeviceName
End Function
Contoh penggunaan kode di atas
Private Sub Command1_Click()
MsgBox DefPrintName, vbInformation, "Default Printer"
End Sub
READ MORE - VB6 Code - Fungsi Untuk Mengetahui Default Printer

VB6 Code - Mendownload Sebuah URL

Di bawah ini merupakan fungsi VB6 untuk mendownload sebuah URL. Adapun kode VB6 untuk mendownload sebuah URL adalah sebagai berikut:
Option Explicit

Private Function DownloadFile(ByVal sFileSource As String, ByVal sDestFile As String) As Boolean
Dim bytes() As Byte
Dim fnum As Integer
bytes() = Inet1.OpenUrl(sFileSource, icByteArray)
fnum = FreeFile

Open sDestFile For Binary Access Write As #fnum
Put #fnum, , bytes()
Close #fnum

DownloadFile = True
End Function
Contoh penggunaan fungsi di atas:
Private Sub Command1_Click()
Call DownloadFile("http://4basic-vb.blogspot.com", "C:\download.html")
End Sub
Demikian kode VB6 untuk mendownload sebuah URL. Semoga bermanfaat.
READ MORE - VB6 Code - Mendownload Sebuah URL

VB6 Code - Memeriksa Apakah Komputer Terhubung Ke Internet

Di bawah ini merupakan fungsi VB6 untuk memeriksa sebuah komputer terhubung ke internet atau tidak?. Adapun kode VB6 untuk memeriksa sebuah komputer apakah terhubung ke internet adalah sebagai berikut:
Option Explicit

Private Declare Function RasEnumConnections Lib "RasApi32.dll" Alias "RasEnumConnectionsA" (lpRasCon As Any, lpcb As Long, lpcConnections As Long) As Long
Private Declare Function RasGetConnectStatus Lib "RasApi32.dll" Alias "RasGetConnectStatusA" (ByVal hRasCon As Long, lpStatus As Any) As Long
'
Const RAS95_MaxEntryName = 256
Const RAS95_MaxDeviceType = 16
Const RAS95_MaxDeviceName = 32
'
Private Type RASCONN95
dwSize As Long
hRasCon As Long
szEntryName(RAS95_MaxEntryName) As Byte
szDeviceType(RAS95_MaxDeviceType) As Byte
szDeviceName(RAS95_MaxDeviceName) As Byte
End Type
'
Private Type RASCONNSTATUS95
dwSize As Long
RasConnState As Long
dwError As Long
szDeviceType(RAS95_MaxDeviceType) As Byte
szDeviceName(RAS95_MaxDeviceName) As Byte
End Type

Private Function IsConnected() As Boolean
'
Dim TRasCon(255) As RASCONN95
Dim lg As Long
Dim lpcon As Long
Dim RetVal As Long
Dim Tstatus As RASCONNSTATUS95
'
TRasCon(0).dwSize = 412
lg = 256 * TRasCon(0).dwSize
'
RetVal = RasEnumConnections(TRasCon(0), lg, lpcon)
If RetVal <> 0 Then
MsgBox "ERROR "
Exit Function
End If
'
Tstatus.dwSize = 160
RetVal = RasGetConnectStatus(TRasCon(0).hRasCon, Tstatus)
If Tstatus.RasConnState = &H2000 Then
IsConnected = True
Else
IsConnected = False
End If
End Function
Contoh penggunaan fungsi VB6 di atas:
Private Sub Command1_Click()
MsgBox IsConnected
End Sub
Demikian mengenai fungsi VB6 untuk memeriksa apakah sebuah komputer terhubung ke internet?
READ MORE - VB6 Code - Memeriksa Apakah Komputer Terhubung Ke Internet

VB6 Code - Membuat Label Yang Berkedip-kedip

Bagaimana cara membuat label yang berkedip-kedip, simak kodenya di bawah ini:
Private Sub Form_Load()
Label1.Caption = "http://4basic-vb.blogspot.com"
Timer1.Interval = 300
End Sub

Private Sub Timer1_Timer()
Label1.Visible = Not Label1.Visible
End Sub
READ MORE - VB6 Code - Membuat Label Yang Berkedip-kedip

VB6 Code - Baca Tulis INI File

Di bawah ini merupakan fungsi untuk baca tulis file .INI. menggunakan Visual Basic 6:
Option Explicit

Private Declare Function WriteProfileString Lib "kernel32" Alias "WriteProfileStringA" (ByVal lpszSection As String, ByVal lpszKeyName As String, ByVal lpszString As String) As Long
Private Declare Function GetProfileString Lib "kernel32" Alias "GetProfileStringA" (ByVal lpAppName As String, ByVal lpKeyName As String, ByVal lpDefault As String, ByVal lpReturnedString As String, ByVal nSize As Long) As Long
Private Declare Function WritePrivateProfileString Lib "kernel32" Alias "WritePrivateProfileStringA" (ByVal lpApplicationName As String, ByVal lpKeyName As Any, ByVal lpString As Any, ByVal lpFileName As String) As Long
Private Declare Function GetPrivateProfileString Lib "kernel32" Alias "GetPrivateProfileStringA" (ByVal lpApplicationName As String, ByVal lpKeyName As Any, ByVal lpDefault As String, ByVal lpReturnedString As String, ByVal nSize As Long, ByVal lpFileName As String) As Long

Public Function ReadIni(ByVal strSection As String, ByVal strKey As String, ByVal strDefault As String, ByVal strFileName As String) As String
Dim intRes As Integer, strRet As String
strRet = Space$(32400)
intRes = GetPrivateProfileString(strSection, strKey, strDefault, strRet, Len(strRet), strFileName)
ReadIni = Left$(strRet, intRes)
End Function

Public Sub WriteIni(ByVal strSection As String, ByVal strKey As String, ByVal strSetting As Variant, ByVal strFileName As String)
WritePrivateProfileString strSection, strKey, CStr(strSetting), strFileName
End Sub

Public Function ReadWinIni(strSection As String, strKey As String) As String
Dim Result As String * 128
Dim Temp As Integer
Temp = GetProfileString(strSection, strKey, "", Result, Len(Result))
ReadWinIni = Left$(Result, Temp)
End Function

Public Sub WriteWinIni(strSection As String, strKey As String, strSetting As String)
WriteProfileString strSection, strKey, strSetting
End Sub


READ MORE - VB6 Code - Baca Tulis INI File

VB6 Code - Memilih Item Listbox Secara Otomatis

Bagaimana cara memilih item yang terdapat pada ListBox secara otomatis pada saat mouse berada di atasnya menggunakan kode Visual Basic 6?
Option Explicit

Private Declare Function ClientToScreen Lib "user32" (ByVal hwnd As Long, lpPoint As POINTAPI) As Long
Private Declare Function LBItemFromPt Lib "COMCTL32.DLL" (ByVal hLB As Long, ByVal ptX As Long, ByVal ptY As Long, ByVal bAutoScroll As Long) 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 Const LB_SETCURSEL = &H186
Private Const LB_GETCURSEL = &H188

Private Type POINTAPI
X As Long
Y As Long
End Type

Private Sub HightLightListBox(ByVal hwndLB As Long, ByVal X As Single, ByVal Y As Single)

Dim IndexItem As Long
Dim Point As POINTAPI

Point.X = X \ Screen.TwipsPerPixelX
Point.Y = Y \ Screen.TwipsPerPixelY

Call ClientToScreen(hwndLB, Point)

IndexItem = LBItemFromPt(hwndLB, Point.X, Point.Y, False)

If IndexItem <> SendMessage(hwndLB, LB_GETCURSEL, 0, 0) Then
Call SendMessage(hwndLB, LB_SETCURSEL, IndexItem, 0)
End If

End Sub
READ MORE - VB6 Code - Memilih Item Listbox Secara Otomatis

VB6 Code - Encrypt Dan Decrypt Sederhana


Di bawah ini merupakan fungsi VB6 untuk melakukan encrypt dan decrypt string secara sederhana, adapun kode VB6 untuk melakukan encrypt dan decrypt string secara sederhana adalah sebagai berikut:
Option Explicit

Public Function Encrypt(sText As String) As String
Dim i As Integer
Dim msg As String
For i = 1 To Len(sText)
msg = msg & Chr(Asc(Mid(sText, i, 1)) + 9)
Next
Encrypt = msg
End Function

Public Function Decrypt(sText As String) As String
Dim i As Integer
Dim msg As String
For i = 1 To Len(sText)
msg = msg & Chr(Asc(Mid(sText, i, 1)) - 9)
Next
Decrypt = msg
End Function
Contoh penggunaan fungsi encrypt dan decrypt sederhana
Private Sub Command1_Click()
Text2.Text = Encrypt(Text1.Text)
End Sub

Private Sub Command2_Click()
Text3.Text = Decrypt(Text2.Text)
End Sub
READ MORE - VB6 Code - Encrypt Dan Decrypt Sederhana

VB6 Code - Mengetahui Bilangan Apakah Ganjil Atau Genap?

Di bawah ini merupakan fungsi VB6 yang sangat sederhana untuk mengetahui sebuah bilangan, apakah ia genap atau ganjil?
Option Explicit

Public Function IsEven(Number As Double) As Boolean
IsEven = IIf(Number Mod 2 = 0, True, False)
End Function
Contoh penggunakan kode VB6 di atas:
Private Sub Command1_Click()
MsgBox IsEven(20) 'return true
End Sub

Private Sub Command1_Click()
MsgBox IsEven(21) 'return false
End Sub
READ MORE - VB6 Code - Mengetahui Bilangan Apakah Ganjil Atau Genap?

VB6 Code - Konfirmasi Sebelum Keluar Dari Aplikasi

Di bawah ini merupakan fungsi VB6 untuk melakukan konfirmasi sebelum keluar dari aplikasi. Mengapa dibuat menjadi fungsi? agar memiliki sifat mudah digunakan kembali, karena hampir tiap software yang dibuat, memerlukan fungsi di bawah ini:
Option Explicit

Public Function ConfirmExit(Optional Title As String = "Konfirmasi") As Boolean
If MsgBox("Are you sure want to exit?", vbQuestion + vbYesNo, Title) = vbYes Then
ConfirmExit = ConfirmExit
Else
ConfirmExit = True
End If
End Function
Contoh penggunaan fungsi di atas:
Private Sub Form_QueryUnload(Cancel As Integer, UnloadMode As Integer)
Cancel = ConfirmExit
End Sub
Penggunaan fungsi di atas dapat kita tempatkan pada event Unload ataupun QueryUnload.
READ MORE - VB6 Code - Konfirmasi Sebelum Keluar Dari Aplikasi

VB6 Code - Memeriksa Bahasa dari Keyboard Digunakan

Di bawah ini merupakan procedure VB6 untuk mengetahui bahasa dari keyboard yang sedang digunakan.
Option Explicit

Private Declare Function GetKeyboardLayout Lib "user32" (ByVal dwLayout As Long) As Long
Private Declare Function GetWindowThreadProcessId Lib "user32" (ByVal hwnd As Long, lpdwProcessId As Long) As Long

Public Sub KeyBoardLanguage()

Dim TheardId As Long
Dim TheardLang As Long
Dim processid As Long

TheardId = GetWindowThreadProcessId(hwnd, processid)
TheardLang = GetKeyboardLayout(ByVal TheardId)
TheardLang = TheardLang Mod 10000

Select Case TheardLang
Case "9721"
MsgBox "English"
Case "5425"
MsgBox "Arabic"
Case Else
MsgBox "I don't know atuh, cari weh ku anjeun sorangan", vbInformation, "Don't Know"
End Select

End Sub
Contoh penggunaan procedure VB6 di atas:
Private Sub  Command1_Click()
KeyBoardLanguage
End Sub
Demikian kode VB6 untuk memmeriksa bahasa dari keyboard yang sedang digunakan. Semoga bermanfaat.
READ MORE - VB6 Code - Memeriksa Bahasa dari Keyboard Digunakan

VB6 Code - Menjadikan Form Semi Transparan

Bagaimana cara membuat form semi transparan menggunakan Visual Basic 6.0?. Simaklah kode VB6 di bawah ini:
Option Explicit

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 Declare Function SetLayeredWindowAttributes Lib "user32" (ByVal hWnd As Long, ByVal color As Long, ByVal x As Byte, ByVal alpha As Long) As Boolean

Const LWA_BOTH = 3
Const LWA_ALPHA = 2
Const LWA_COLORKEY = 1
Const GWL_EXSTYLE = -20
Const WS_EX_LAYERED = &H80000

Dim iTransparant As Integer

Sub MakeTransparan(hWndBro As Long, iTransp As Integer)
On Error Resume Next

Dim ret As Long
ret = GetWindowLong(hWndBro, GWL_EXSTYLE)

SetWindowLong hWndBro, GWL_EXSTYLE, ret Or WS_EX_LAYERED
SetLayeredWindowAttributes hWndBro, RGB(255, 255, 0), iTransp, LWA_ALPHA
Exit Sub

End Sub
Contoh penggunaan fungsi VB6 di atas:
Option Explicit

Private Sub Form_Load()
On Error Resume Next
MakeTransparan Me.hWnd, 75
End Sub
Demikian mengenai cara membuat form menjadi semi transparant menggunakan VB6. Semoga bermanfaat.
READ MORE - VB6 Code - Menjadikan Form Semi Transparan

VB6 Code - Generate Nomor Secara Unik

Di bawah ini merupakan fungsi VB6 yang berlaku sebagai sebuah generator agar menampilkan nomor secara unik (tidak ada yang sama satu dengan yang lainnya). Adapun kode VB6 untuk melakukannya adalah sebagai berikut:
Option Explicit

Private Function GenRanUnix(MIN As Integer, MAX As Integer) As Collection

Dim iMax As Integer
Dim iRan As Integer
Dim g As Integer
Dim y As Integer
Dim c As New Collection
Dim k As New Collection
Dim f As Integer
Dim x As Integer

For f = MIN To MAX
c.Add f
Next

y = c.Count
Randomize

For x = 1 To y
g = Int(y * Rnd + 1)
k.Add c.Item(g)
c.Remove g
y = c.Count
Next

Set GenRanUnix = k

End Function
Contoh penggunaan fungsi VB6 di atas:
Private Sub Command1_Click()
Dim b As New Collection
Dim i As Integer
Dim msg As String
List1.Clear
Set b = GenRanUnix(0, 100)
For i = 1 To b.Count
List1.AddItem b.Item(i)
Next
End Sub
Demikian mengenai cara membuat fungsi VB6 untuk men-generate nomor secara unik.
READ MORE - VB6 Code - Generate Nomor Secara Unik

VB6 Code - Menjadikan Form Berada Paling Depan

Fungsi VB6 di bawah ini merupakana cara menampilkan form agar berada paling depan (Form On Top/Top Most). Adapun kode VB6 untuk melakukan hal tersebut adalah sebagai berikut:
Option Explicit

Public Declare Function SetWindowPos Lib "user32" (ByVal hWnd As Long, ByVal hWndInsertAfter As Long, ByVal X As Long, ByVal y As Long, ByVal cx As Long, ByVal cy As Long, ByVal wFlags As Long) As Long

Public Const HWND_TOPMOST = -1
Public Const HWND_NOTOPMOST = -2
Public Const SWP_NOMOVE = &H2
Public Const SWP_NOSIZE = &H1
Public Const SWP_NOACTIVATE = &H10
Public Const SWP_SHOWWINDOW = &H40
Public Const FLAGS = SWP_NOMOVE Or SWP_NOSIZE

Public Function TopMost(frm As Form, bTopMost As Boolean)
If bTopMost Then
Call SetWindowPos(frm.hWnd, HWND_TOPMOST, 0, 0, 0, 0, FLAGS)
Else
Call SetWindowPos(frm.hWnd, HWND_NOTOPMOST, 0, 0, 0, 0, FLAGS)
End If
End Function
Contoh penggunaan menjadikan form berada paling depan menggunakan VB6:
Private Sub Form_Load()
TopMost Me, True
End Sub
Demikian mengenai cara membuat fungsi VB6 (fungsi API) agar menjadikan sebuah form paling depan.
READ MORE - VB6 Code - Menjadikan Form Berada Paling Depan

VB6 Code - Membuat Efek Fade Pada Form

Di bawah ini merupakan fungsi VB6 untuk membuat efek fade pada sebuah form. Adapun kode VB6 untuk membuat efek fade pada sebuah form yang ditampilkan adalah sebagai berikut:
Option Explicit
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 Declare Function SetLayeredWindowAttributes Lib "user32" (ByVal hWnd As Long, ByVal color As Long, ByVal x As Byte, ByVal alpha As Long) As Boolean

Const LWA_BOTH = 3
Const LWA_ALPHA = 2
Const LWA_COLORKEY = 1
Const GWL_EXSTYLE = -20
Const WS_EX_LAYERED = &H80000

Dim iTransparant As Integer

Sub MakeTransparan(hWndBro As Long, iTransp As Integer)
On Error Resume Next

Dim ret As Long
ret = GetWindowLong(hWndBro, GWL_EXSTYLE)

SetWindowLong hWndBro, GWL_EXSTYLE, ret Or WS_EX_LAYERED
SetLayeredWindowAttributes hWndBro, RGB(255, 255, 0), iTransp, LWA_ALPHA
Exit Sub
End Sub

Private Sub Command1_Click()
Unload Me
End Sub


Private Sub Form_Load()
Timer1.Enabled = False
Timer2.Enabled = False
Timer1.Interval = 1
Timer2.Interval = 1
Me.Visible = False
Timer1.Enabled = True
End Sub

Private Sub Form_Unload(Cancel As Integer)
Cancel = 1
Timer1.Enabled = False
Timer2.Enabled = True
End Sub

Private Sub Timer1_Timer()
On Error Resume Next
iTransparant = iTransparant + 5
If iTransparant > 255 Then
iTransparant = 255
Timer1.Enabled = False
End If
MakeTransparan Me.hWnd, iTransparant
Me.Show
End Sub

Private Sub Timer2_Timer()
On Error Resume Next
iTransparant = iTransparant - 5
If iTransparant < 0 Then
iTransparant = 0
Timer2.Enabled = False
End
End If
MakeTransparan Me.hWnd, iTransparant
End Sub
Demikian kode VB6 untuk membuat efek fade pada sebuah form.
READ MORE - VB6 Code - Membuat Efek Fade Pada Form

VB6 Code - Membuat Explode Effect Pada Form

Membuat efek/animasi blow/explode pada sebuah form menggunakan kode VB6. Adapun cara membut efek animasi blow/explode dengan menggunakan VB6 adalah sebagai berikut:
Option Explicit

Type RECT
Left As Long
Top As Long
Right As Long
Bottom As Long
End Type

Declare Function GetWindowRect Lib "user32" (ByVal hwnd As Long, lpRect As RECT) As Long
Declare Function GetDC Lib "user32" (ByVal hwnd As Long) As Long
Declare Function ReleaseDC Lib "user32" (ByVal hwnd As Long, ByVal hdc As Long) As Long
Declare Function SetBkColor Lib "gdi32" (ByVal hdc As Long, ByVal crColor As Long) As Long
Declare Function Rectangle Lib "gdi32" (ByVal hdc As Long, ByVal X1 As Long, ByVal Y1 As Long, ByVal X2 As Long, ByVal Y2 As Long) As Long
Declare Function CreateSolidBrush Lib "gdi32" (ByVal crColor As Long) As Long
Declare Function SelectObject Lib "user32" (ByVal hdc As Long, ByVal hObject As Long) As Long
Declare Function DeleteObject Lib "gdi32" (ByVal hObject As Long) As Long

Public Const IMPLODE_EXPLODE_VALUE = 1500 'you can change the value

Sub ExplodeForm(f As Form, Movement As Integer)
Dim myRect As RECT
Dim formWidth%, formHeight%, i%, X%, Y%, Cx%, Cy%
Dim TheScreen As Long
Dim Brush As Long
GetWindowRect f.hwnd, myRect
formWidth = (myRect.Right - myRect.Left)
formHeight = myRect.Bottom - myRect.Top
TheScreen = GetDC(0)
Brush = CreateSolidBrush(f.BackColor)
For i = 1 To Movement
Cx = formWidth * (i / Movement)
Cy = formHeight * (i / Movement)
X = myRect.Left + (formWidth - Cx) / 2
Y = myRect.Top + (formHeight - Cy) / 2
Rectangle TheScreen, X, Y, X + Cx, Y + Cy
Next i
X = ReleaseDC(0, TheScreen)
DeleteObject (Brush)
End Sub

Public Sub ImplodeForm(f As Form, Movement As Integer)
Dim myRect As RECT
Dim formWidth%, formHeight%, i%, X%, Y%, Cx%, Cy%
Dim TheScreen As Long
Dim Brush As Long
GetWindowRect f.hwnd, myRect
formWidth = (myRect.Right - myRect.Left)
formHeight = myRect.Bottom - myRect.Top
TheScreen = GetDC(0)
Brush = CreateSolidBrush(f.BackColor)
For i = Movement To 1 Step -1
Cx = formWidth * (i / Movement)
Cy = formHeight * (i / Movement)
X = myRect.Left + (formWidth - Cx) / 2
Y = myRect.Top + (formHeight - Cy) / 2
Rectangle TheScreen, X, Y, X + Cx, Y + Cy
Next i
X = ReleaseDC(0, TheScreen)
DeleteObject (Brush)
End Sub
Contoh penggunaan membuat efek ledakan pada form:
Private Sub Command1_Click()
Call ImplodeForm(Me, IMPLODE_EXPLODE_VALUE)
End
Set Form1 = Nothing
End Sub

Private Sub Form_Load()
Call ExplodeForm(Me, IMPLODE_EXPLODE_VALUE)
End Sub
Demikian mengenai cara membuat efek ledakan (blow/explode) dengan menggunakan kode VB6. Semoga bermanfaat.
READ MORE - VB6 Code - Membuat Explode Effect Pada Form

VB6 Code - Menutup Seluruh Form For...each

Di bawah ini merupakan procedure VB6 untuk menutup seluruh form dengan menggunakan for...each.
Option Explicit

Public Sub CloseAllForm()
Dim frm As Form
For Each frm In Forms
Unload frm
Next
End Sub
Contoh penggunaan procedure di atas:
Private Sub Form_Unload(Cancel As Integer)
CloseAllForm
End Sub
Demikian contoh kode VB6 untuk menutup seluruh form menggunakan for .. each. Semoga bermanfaat.
READ MORE - VB6 Code - Menutup Seluruh Form For...each

VB6 Code - Membuat Form Yang Berbentuk Lingkaran

Mengenai cara membuat form yang berbentuk lingkarang menggunakan VB6 - Adapun cara membuat form berbentuk lingkaran menggunakan VB6 adalah sebagai berikut:
Option Explicit

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

Function CutCirCle(frm As Form, Left, Top, Fat, Tall)
With frm
.Width = (Fat + 10) * 15
.Height = (Tall + 10) * 15
End With
SetWindowRgn frm.hWnd, CreateEllipticRgn(Left, Top, Fat, Tall), True
End Function
Contoh penggunaan kode VB6 di atas:
Private Sub Command1_Click()
Call CutCirCle(Me, 0, 0, 600, 600)
End Sub

Private Sub Form_Resize()
Command1.Left = ((610 * 15) / 2) - (Command1.Width / 2)
End Sub
Demikian kode VB6 untuk membuat form yang berbentuk lingkaran. Semoga bermanfaat.
READ MORE - VB6 Code - Membuat Form Yang Berbentuk Lingkaran

VB6 Code - Menyimpan Form Di Tengah Layar (screen)

Di bawah ini merupkan procedure VB6 untuk menyimpan/memindahkan form tepat di tengah layar.
Option Explicit

Private Sub CenterForm(frmIn As Object)

Dim iTop As Integer, ileft As Integer

If frmIn.WindowState <> 0 Then
'prevent if form maximized or minimized
'the form must in normal condition
Exit Sub
End If

ileft = (Screen.Width - frmIn.Width) \ 2
iTop = (Screen.Height - frmIn.Height) \ 2
frmIn.Move ileft, iTop

End Sub
Cara penggunaan kode VB6 di atas:
Private Sub Form_Load()
Form_Resize
End Sub

Private Sub Form_Resize()
CenterForm Me
End Sub
READ MORE - VB6 Code - Menyimpan Form Di Tengah Layar (screen)

VB6 Code - Membuat Form Yang Berbentuk Elips

Bagaimanakah cara membuat form yang berbentuk elips menggunakan kode Vb6? tentu saja untuk keperluan ini kita harus memanggil beberapa fungsi API. Bagaimana kode lengkap dari VB6 tersebut \? simaklah di bawah ini:
Option Explicit

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
Contoh penggunaan fungsi API agar form berbentuk Elips
Private Sub Form_Click()
Unload Me
End Sub

Private Sub Form_Load()
SetWindowRgn hWnd, CreateEllipticRgn(0, 0, 299, 200), True
End Sub
Demikian kode VB6 untuk membuat form yang berbentuk lingkaran.
READ MORE - VB6 Code - Membuat Form Yang Berbentuk Elips

VB6 Code - Menampilkan Dialog Properties Sebuah File

Di bawah ini merupakan fungsi VB6 untuk menampilkan kotak dialog properties sebuah file.
Option Explicit

Type SHELLEXECUTEINFO
cbSize As Long
fMask As Long
hwnd As Long
lpVerb As String
lpFile As String
lpParameters As String
lpDirectory As String
nShow As Long
hInstApp As Long
lpIDList As Long
lpClass As String
hkeyClass As Long
dwHotKey As Long
hIcon As Long
hProcess As Long
End Type

Public Const SEE_MASK_INVOKEIDLIST = &HC
Public Const SEE_MASK_NOCLOSEPROCESS = &H40
Public Const SEE_MASK_FLAG_NO_UI = &H400

Declare Function ShellExecuteEX Lib "shell32.dll" Alias "ShellExecuteEx" (SEI As SHELLEXECUTEINFO) As Long

Public Sub ShowProps(FileName As String, OwnerhWnd As Long)

Dim SEI As SHELLEXECUTEINFO
Dim lngReturn As Long

With SEI
.cbSize = Len(SEI)
.fMask = SEE_MASK_NOCLOSEPROCESS Or _
SEE_MASK_INVOKEIDLIST Or SEE_MASK_FLAG_NO_UI
.hwnd = OwnerhWnd
.lpVerb = "properties"
.lpFile = FileName
.lpParameters = vbNullChar
.lpDirectory = vbNullChar
.nShow = 0
.hInstApp = 0
.lpIDList = 0
End With

lngReturn = ShellExecuteEX(SEI)

End Sub
Contoh menggunakan dialog properties sebuah file
Option Explicit

Private Sub Command1_Click()
Call ShowProps("C:\boot.ini", Me.hwnd)
End Sub
READ MORE - VB6 Code - Menampilkan Dialog Properties Sebuah File

VB6 Code - Fungsi API Untuk Browse For Folder

Mengenai fungsi-fungsi API untuk menampilkan dialog browse for folder dengan menggunakan kode-kode VB6:
Option Explicit

Private Const BIF_RETURNONLYFSDIRS = 1
Private Const BIF_DONTGOBELOWDOMAIN = 2
Private Const MAX_PATH = 260

Private Declare Function SHBrowseForFolder Lib "shell32" (lpbi As BrowseInfo) As Long
Private Declare Function SHGetPathFromIDList Lib "shell32" (ByVal pidList As Long, ByVal lpBuffer As String) As Long
Private Declare Function lstrcat Lib "kernel32" Alias "lstrcatA" (ByVal lpString1 As String, ByVal lpString2 As String) As Long

Public Type BrowseInfo
hWndOwner As Long
pIDLRoot As Long
pszDisplayName As Long
lpszTitle As Long
ulFlags As Long
lpfnCallback As Long
lParam As Long
iImage As Long
End Type

Public Function BrowseForFolder(hwnd As Long, Optional Title As String = "Browse For Folder") As String
Dim lpIDList As Long
Dim sBuffer As String
Dim szTitle As String
Dim tBrowseInfo As BrowseInfo
szTitle = "This Is My Title"
With tBrowseInfo
.hWndOwner = Me.hwnd
.lpszTitle = lstrcat(szTitle, "")
.ulFlags = BIF_RETURNONLYFSDIRS + BIF_DONTGOBELOWDOMAIN
End With
lpIDList = SHBrowseForFolder(tBrowseInfo)
If (lpIDList) Then
sBuffer = Space(MAX_PATH)
SHGetPathFromIDList lpIDList, sBuffer
sBuffer = Left(sBuffer, InStr(sBuffer, vbNullChar) - 1)
BrowseForFolder = sBuffer
End If
End Function
Adapun contoh untuk fungsi API diatas:

Private Sub Command1_Click()
Text1.Text = BrowseForFolder(Me.hwnd)
End Sub
READ MORE - VB6 Code - Fungsi API Untuk Browse For Folder

VB6 Code - Horizontal Scrollbar Pada Listbox

Di bawah ini merupakan procedure VB6 untuk menambah ScrollBar pada objek ListBox. Seperti yang kita ketahui, ListBox tidak memiliki properties horizontal scroll bar akan tetapi dengan memanggil beberapa fungsi API hal tersebut mungkin untuk dilakukan.
Option Explicit

Private Declare Function SendMessageByNum Lib "user32" Alias "SendMessageA" (ByVal hwnd As Long, ByVal wMsg As Long, ByVal wParam As Long, ByVal lParam As Long) As Long
Private Const LB_SETHORIZONTALEXTENT = &H194

Public Sub AddHSBToListBox(sText As String, lst As ListBox)
Static x As Long
lst.AddItem sText
If x < TextWidth(sText & " ") Then
x = TextWidth(sText & " ")
End If
If ScaleMode = vbTwips Then
x = x / Screen.TwipsPerPixelX
SendMessageByNum lst.hwnd, LB_SETHORIZONTALEXTENT, x, 0
End If
End Sub
Contoh penggunaan menambah horizontal scrollbar pada listbox
Private Sub  Command1_Click()
Dim sText As String
sText = ("This is a sample of long text, if the text longer than listbox, it will be create horizontal scrollbar automatically")
AddHSBToListBox sText, List1
End Sub
READ MORE - VB6 Code - Horizontal Scrollbar Pada Listbox

VB6 Code - Horizontal Scrollbar Pada Richtextbox

Di bawah ini merupakan kode VB6 mengenai cara menambah horizontal scrollbar pada objek richtextbox.
Option Explicit

Private Sub Form_Load()
With RichTextBox1
.Text = "Visual Basic :: Horizontal Scroll Position In A Richtextbox, you must set the scrollbar properties to 1 or 3"
.RightMargin = RichTextBox1.Width + 600
End With
End Sub
READ MORE - VB6 Code - Horizontal Scrollbar Pada Richtextbox

VB6 Code - Procedure Auto Drop Down Pada Combobox

Di bawah ini merupakan procedure VB6 yang digunakan untuk membuat auto drop down pada objek ComboBox standar. Maksudnya, drop down otomatis apabila mouse berada di atasnya tanpa harus mengkliknya terlebih dahulu.
Option Explicit

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
Const CB_SHOWDROPDOWN = &H14F

Public Sub AutoDropDown(cmb As ComboBox)
Call SendMessage(cmb.hwnd, CB_SHOWDROPDOWN, 1, ByVal 0&)
If cmb.ListIndex = -1 Then cmb.ListIndex = 0
End Sub
Contoh penggunaan proceder auto drop down pada combobox
Private Sub Combo1_GotFocus()
AutoDropDown Combo1
End Sub

Private Sub Form_Load()
With Combo1
.AddItem "asep hibban"
.AddItem "fahmi nurul anwar"
.AddItem "mohammad galbi"
.AddItem "karim wafi"
End With
End Sub
READ MORE - VB6 Code - Procedure Auto Drop Down Pada Combobox

VB6 Code - Memperoleh Nilai Maksimal Dari Sebuah Array

Di bawah ini merupakan fungsi VB6 untuk memperoleh nilai maksimal dari sebuah array.
Option Explicit

Public Function MAX(ByRef Number() As Double) As Double
Dim iMaxNum As Double
Dim i As Integer
iMaxNum = Number(LBound(Number))
For i = LBound(Number) To UBound(Number)
If Number(i) > iMaxNum Then
iMaxNum = Number(i)
Else
iMaxNum = iMaxNum
End If
Next i
MAX = iMaxNum
End Function
Contoh penggunaan fungsi untuk memperoleh nilai maksimal dari sebuah array
Private Sub Command1_Click()
Dim iArray(3) As Double
iArray(0) = 588
iArray(1) = 67
iArray(2) = 66
iArray(3) = 4
MsgBox "The max number is: " & MAX(iArray)
End Sub
READ MORE - VB6 Code - Memperoleh Nilai Maksimal Dari Sebuah Array

VB6 Code - Memperoleh Nilai Minimal Dari Sebuah Array

Di bawah ini merupakan fungsi VB6 untuk mencari nilai minimal dari sebuah array.
Option Explicit

Public Function MIN(ByRef Number() As Double) As Double
Dim iMaxNum As Double
iMaxNum = Number(LBound(Number))
Dim i As Integer
For i = LBound(Number) To UBound(Number)
If Number(i) < iMaxNum Then
iMaxNum = Number(i)
Else
iMaxNum = iMaxNum
End If
Next i
MIN = iMaxNum
End Function
Contoh fungsi untuk memperoleh nilai minimal dari sebuah array
Private Sub Command1_Click()
Dim iArray(3) As Double
iArray(0) = 588
iArray(1) = 67
iArray(2) = 66
iArray(3) = 4
MsgBox "The min number is: " & MIN(iArray)
End Sub
READ MORE - VB6 Code - Memperoleh Nilai Minimal Dari Sebuah Array

VB6 Code - Memeriksa Apakah Screen Saver Enable

Di bawah ini merupakan fungsi VB6 untuk memeriksa apakah screen saver enable atau disable? enable return true dan jika disable, apalagi jika bukan return false.
Option Explicit

Private Declare Function SystemParametersInfo Lib "user32" Alias "SystemParametersInfoA" (ByVal uAction As Long, ByVal uParam As Long, lpvParam As Any, ByVal fuWinIni As Long) As Long
Private Const SPI_GETSCREENSAVEACTIVE = 16

Private Function IsScreenSaverEnable() As Boolean
Dim bReturn As Boolean
Dim bActive As Boolean
Call SystemParametersInfo(SPI_GETSCREENSAVEACTIVE, vbNull, bReturn, 0)
IsScreenSaverEnable = bReturn
End Function
Contoh penggunaan fungsi untuk memeriksa apakah screen saver enable
Private Sub Command1_Click()
MsgBox IsScreenSaverEnable
End Sub
READ MORE - VB6 Code - Memeriksa Apakah Screen Saver Enable

VB6 Code - Memperoleh Nilai Rata-rata Dari Sebuah Array

Di bawah ini merupakan fungsi VB6 untuk memperoleh nilai rata-rata dari sebuah array.
Option Explicit

Function AVERAGE(ByRef Number() As Double) As Double
Dim iMaxNum As Double, i As Integer
For i = LBound(Number) To UBound(Number)
iMaxNum = iMaxNum + Number(i)
Next i
AVERAGE = iMaxNum / (UBound(Number) + 1)
End Function
Contoh penggunaan fungsi untuk memperoleh nilai rata-rata dari sebuah array
Private Sub Command1_Click()
Dim iArray(3) As Double
iArray(0) = 588
iArray(1) = 67
iArray(2) = 66
iArray(3) = 4
MsgBox "The Average is: " & AVERAGE(iArray)
End Sub
READ MORE - VB6 Code - Memperoleh Nilai Rata-rata Dari Sebuah Array

VB6 Code - Mencari Dengan Cepat Pada Listbox (Fungsi Api)

Di bawah ini merupakan fungsi VB6 yang digunakan untuk mencari sebuah item yang terdapat dalam objek ListBox dengan cepat.
Option Explicit

Private Declare Function SendMessage Lib "User32" Alias "SendMessageA" (ByVal hWnd As Long, ByVal wMsg As Integer, ByVal wParam As Integer, lParam As Any) As Long
Private Const LB_FINDSTRING = &H18F

Public Function SearchInList(sText As String, lst As ListBox)
On Error Resume Next
lst.ListIndex = SendMessage(lst.hWnd, LB_FINDSTRING, -1, ByVal sText)
lst.TopIndex = List1.ListIndex - 1
End Function
Contoh penggunaan mencari dengan cepat menggunakan fungsi API
Private Sub Form_Load()
With List1
.AddItem "Bandung"
.AddItem "Jakarta"
.AddItem "Garut"
.AddItem "Surabaya"
.AddItem "New York"
.AddItem "Khoiriyyah"
End With
End Sub

Private Sub Text1_Change()
SearchInList Text1.Text, List1
End Sub
READ MORE - VB6 Code - Mencari Dengan Cepat Pada Listbox (Fungsi Api)

VB6 Code - Menjalankan Screen Saver

Di bawah ini merupakan fungsi uVB6 ntuk menjalankan screen saver melalui pemrograman.
Option Explicit

Private Declare Function SendMessage Lib "user32" Alias "SendMessageA" (ByVal hWnd As Long, ByVal wMsg As Long, ByVal wParam As Long, ByVal lParam As Long) As Long

Private Const WM_SYSCOMMAND = &H112&
Private Const SC_SCREENSAVER = &HF140&

Public Sub RunScreenSaver()
Call SendMessage(Me.hWnd, WM_SYSCOMMAND, SC_SCREENSAVER, 0&)
End Sub
Contoh penggunaan menjalankan screen saver
Private Sub Command1_Click()
RunScreenSaver
End Sub
READ MORE - VB6 Code - Menjalankan Screen Saver

VB6 Code - Memperoleh Waktu Double Klik Pada Mouse

Source code VB6 di bawah ini berguna untuk memperoleh waktu double klik pada mouse dengan menggunakan fungsi API GetDoubleClick.
Option Explicit

Private Declare Function GetDoubleClickTime Lib "user32" () As Long

Private Sub Command1_Click()
Dim ret As Long
ret = GetDoubleClickTime
Text1.Text = ret & " milliseconds"
End Sub
READ MORE - VB6 Code - Memperoleh Waktu Double Klik Pada Mouse

VB6 Code - Menjalankan Aplikasi Pada Start Up

Di bawah ini merupakan cara yang mudah untuk menjalankan aplikasi pada saat startup menggunakan kode VB6. Pada dasarnya fungsi startup, hanyalah fungsi baca dan tulis ke dalam registy. Kodenya pendek, karena ia meminjam ActiveX Windows Script Host Object Model atau yang lebih dikenal dengan nama WSHOM.OCX.
Option Explicit

Dim oWSHShell As New WshShell

Private Function RegWrite(sKey As String, sFilepath As String)
oWSHShell.RegWrite sKey, sFilepath
End Function

Private Function RegDelete(sKey As String)
oWSHShell.RegDelete sKey
End Function
Contoh penggunaan fungsi di atas yang digunakan untuk menulis ke dalam registry
Private Sub Command1_Click()
RegWrite "HKEY_CURRENT_USER\Software\Microsoft\Windows\CurrentVersion\Run\" & _
App.EXEName, App.Path & "\" & App.EXEName & ".exe"
End Sub
Contoh penggunaan fungsi di atas yang digunakan untuk menghapus entry yang terdapat dalam registry
Private Sub Command2_Click()
RegDelete "HKEY_CURRENT_USER\Software\Microsoft\Windows\CurrentVersion\Run\" & App.EXEName
End Sub
READ MORE - VB6 Code - Menjalankan Aplikasi Pada Start Up

VB6 Code - Animasi Ketikan Tanpa Flicker

Fungsi VB6 di bawah ini digunakan untuk animasi yang menyerupai text yang sedang di ketik. Animasinya sangat halus nyaris tanpa kedipan.
Option Explicit

Dim sAnimation As String

Private Sub Form_Load()
sAnimation = "Asep Hibban : http://4basic-vb.blogspot.com"
End Sub

Private Sub Timer1_Timer()
Dim sToAnimate As String
Static iAnimation As Integer
Dim c As Integer
iAnimation = iAnimation + 1

sToAnimate = Mid(sAnimation, 1, iAnimation)
With Picture1
.Cls
.CurrentX = 25
.CurrentY = 100
Picture1.Print sToAnimate
End With
If iAnimation >= Len(sAnimation) Then
iAnimation = 0
End If
End Sub
READ MORE - VB6 Code - Animasi Ketikan Tanpa Flicker

VB6 Code - Menjalankan File .mp3

Di bawah ini merupakan contoh menggunakan Microsoft Multimedia Control yang digunakan untuk menjalankan file .mp3 menggunakan VB6.
Option Explicit

Private Sub Command1_Click()
MMC.FileName = OpenFile
Me.Caption = MMC.FileName
MMC.Command = "open"
MMC.Command = "play"
End Sub

Private Function OpenFile() As String
With CommonDialog1
.FileName = ""
.DialogTitle = "Open Files"
.InitDir = "C:\My Documents"
.Filter = "MP3 File (*.MP3)|*.MP3"
.ShowOpen
If .FileName = "" Then Exit Function
MMC.Command = "stop"
OpenFile = .FileName
End With
End Function

Private Sub Command2_Click()
MMC.Command = "stop"
End Sub
READ MORE - VB6 Code - Menjalankan File .mp3

VB6 Code - Menghapus Spasi Rangkap

Di bawah ini merupakan fungsi VB6 untuk menghapus/menghilangkan spasi yang tidak diperlukan (spasi rangkap).
Option Explicit

Private Function DelJunkSpace(str As String) As String
Do While (InStr(str, " ") > 0)
str = Replace(str, " ", " ")
Loop
DelJunkSpace = str
End Function
Contoh penggunaan fungsi di atas
Private Sub Form_Load()
Dim str As String
str = "Asep Hibban http://4basic-vb.blogspot.com"
'menjadi = "Asep Hibban http://4basic-vb.blogspot.com"
Text1.Text = str
End Sub
READ MORE - VB6 Code - Menghapus Spasi Rangkap

VB6 Code - Menjadikan Input Textbox Kapital

Di bawah ini merupakan kode VB6 untuk menjadikan text yang terdapat pada textbox menjadi kapital. Kode yang ditrigger pada saat penekanan tombol.
Option Explicit

'This one line code makes the contents of text box in capital. As you keep in typing it. Just copy this code keypress
Private Sub Text1_KeyPress(KeyAscii As Integer)
KeyAscii = Asc(UCase(Chr(KeyAscii)))
End Sub
READ MORE - VB6 Code - Menjadikan Input Textbox Kapital

VB6 Code - Memperoleh Jumlah Baris TextBox

Di bawah ini merupakan fungsi VB6 untuk memperoleh/mengetahui jumlah jajaran dalam sebuah textboxt. Fungsi tersebut menggunakan fungsi API SendMessageLong.
Option Explicit

Private Declare Function SendMessageLong Lib "user32" Alias "SendMessageA" (ByVal hwnd As Long, ByVal wMsg As Long, ByVal wParam As Long, ByVal lParam As Long) As Long
Private Const EM_GETLINECOUNT = &HBA

Public Function GetLineCount(Txt As TextBox)
Dim lngLineCount As Long
On Error Resume Next
lngLineCount = SendMessageLong(Txt.hwnd, EM_GETLINECOUNT, 0&, 0&)
GetLineCount = Format$(lngLineCount, "##,###")
End Function
Contoh penggunaan fungsi VB6 di atas:
Private Sub Command1_Click()
MsgBox GetLineCount(Text1)
End Sub
READ MORE - VB6 Code - Memperoleh Jumlah Baris TextBox

VB6 Code - Menghapus Isi Textbox Dengan Cepat

Di bawah ini merupakan procedure VB6 untuk menghapus isi/text yang terdapat dalam textbox dengan cepat. Kami buat menjadi procedure agar mudah dalam penggunaan dan memiliki sifat mudah digunakan kembali (reusability)
Option Explicit

Public Sub ClearAllTextBoxes(frmClearMe As Form)
Dim txt As Control
For Each txt In frmClearMe
If TypeOf txt Is TextBox Then txt.Text = ""
Next
End Sub
Contoh penggunaan/pemanggilan procedure di atas
Private Sub Command1_Click()
ClearAllTextBoxes Me
End Sub
READ MORE - VB6 Code - Menghapus Isi Textbox Dengan Cepat

VB6 Code - Fungsi Shutdown, Restart, Log-off

Di bawah ini merupakan fungsi untuk men-shutdown, restart, log-off sebuah komputer.
Option Explicit

Private Declare Function ExitWindowsEx Lib "user32" (ByVal uFlags As Long, ByVal dwReserved As Long) As Long
Private Const ENDSESSION_LOGOFF As Long = &H80000000

Public Enum EShutDownTypes
[_First] = 0
EWX_LOGOFF = 0
EWX_SHUTDOWN = 1&
EWX_REBOOT = 2&
EWX_FORCELOGOFF = 4&
EWX_FORCESHUTDOWN = 5&
EWX_FORCEREBOOT = 6&
EWX_POWEROFF = 8&
EWX_FORCEIFHUNG = 10& ' NT5 only
[_Last] = &H20& - 1
End Enum

Public Enum EShutDownErrorBaseConstant
eeSSDErrorBase = vbObjectError Or (1048 + &H210)
End Enum

Private Type OSVERSIONINFO
dwOSVersionInfoSize As Long
dwMajorVersion As Long
dwMinorVersion As Long
dwBuildNumber As Long
dwPlatformId As Long
szCSDVersion As String * 128
End Type

Private Declare Function GetVersionEx Lib "kernel32" Alias "GetVersionExA" (lpVersionInformation As OSVERSIONINFO) As Long

Private Const VER_PLATFORM_WIN32_NT = 2
Private Const VER_PLATFORM_WIN32_WINDOWS = 1
Private Const VER_PLATFORM_WIN32s = 0

Private Const FORMAT_MESSAGE_ALLOCATE_BUFFER = &H100
Private Const FORMAT_MESSAGE_ARGUMENT_ARRAY = &H2000
Private Const FORMAT_MESSAGE_FROM_HMODULE = &H800
Private Const FORMAT_MESSAGE_FROM_STRING = &H400
Private Const FORMAT_MESSAGE_FROM_SYSTEM = &H1000
Private Const FORMAT_MESSAGE_IGNORE_INSERTS = &H200
Private Const FORMAT_MESSAGE_MAX_WIDTH_MASK = &HFF

Private Declare Function FormatMessage Lib "kernel32" Alias "FormatMessageA" (ByVal dwFlags As Long, lpSource As Any, ByVal dwMessageId As Long, _
ByVal dwLanguageId As Long, ByVal lpBuffer As String, ByVal nSize As Long, Arguments As Long) As Long

Private Type LARGE_INTEGER
LowPart As Long
HighPart As Long
End Type

Private Type LUID
LowPart As Long
HighPart As Long
End Type

Private Type LUID_AND_ATTRIBUTES
pLuid As LUID
Attributes As Long
End Type

Private Type TOKEN_PRIVILEGES
PrivilegeCount As Long
Privileges(0 To 0) As LUID_AND_ATTRIBUTES
End Type

Private Declare Function GetCurrentProcess Lib "kernel32" () As Long
Private Declare Function OpenProcessToken Lib "advapi32.dll" (ByVal ProcessHandle As Long, ByVal DesiredAccess As Long, TokenHandle As Long) As Long
Private Declare Function CloseHandle Lib "kernel32" (ByVal hObject As Long) As Long
Private Declare Function GetTokenInformation Lib "advapi32.dll" (ByVal TokenHandle As Long, TokenInformationClass As Integer, TokenInformation As Any, ByVal TokenInformationLength As Long, ReturnLength As Long) As Long
Private Declare Function AdjustTokenPrivileges Lib "advapi32.dll" (ByVal TokenHandle As Long, ByVal DisableAllPrivileges As Long, NewState As TOKEN_PRIVILEGES, ByVal BufferLength As Long, PreviousState As TOKEN_PRIVILEGES, ReturnLength As Long) As Long
Private Declare Function LookupPrivilegeValue Lib "advapi32.dll" Alias "LookupPrivilegeValueA" (ByVal lpSystemName As String, ByVal lpName As String, lpLuid As LUID) As Long

Private Const SE_SHUTDOWN_NAME = "SeShutdownPrivilege"
Private Const SE_PRIVILEGE_ENABLED = &H2

Private Const READ_CONTROL = &H20000
Private Const STANDARD_RIGHTS_ALL = &H1F0000
Private Const STANDARD_RIGHTS_EXECUTE = (READ_CONTROL)
Private Const STANDARD_RIGHTS_READ = (READ_CONTROL)
Private Const STANDARD_RIGHTS_REQUIRED = &HF0000
Private Const STANDARD_RIGHTS_WRITE = (READ_CONTROL)

Private Const TOKEN_ASSIGN_PRIMARY = &H1
Private Const TOKEN_DUPLICATE = (&H2)
Private Const TOKEN_IMPERSONATE = (&H4)
Private Const TOKEN_QUERY = (&H8)
Private Const TOKEN_QUERY_SOURCE = (&H10)
Private Const TOKEN_ADJUST_PRIVILEGES = (&H20)
Private Const TOKEN_ADJUST_GROUPS = (&H40)
Private Const TOKEN_ADJUST_DEFAULT = (&H80)
Private Const TOKEN_ALL_ACCESS = (STANDARD_RIGHTS_REQUIRED Or TOKEN_ASSIGN_PRIMARY Or _
TOKEN_DUPLICATE Or TOKEN_IMPERSONATE Or TOKEN_QUERY Or TOKEN_QUERY_SOURCE Or TOKEN_ADJUST_PRIVILEGES Or TOKEN_ADJUST_GROUPS Or TOKEN_ADJUST_DEFAULT)
Private Const TOKEN_READ = (STANDARD_RIGHTS_READ Or TOKEN_QUERY)
Private Const TOKEN_WRITE = (STANDARD_RIGHTS_WRITE Or TOKEN_ADJUST_PRIVILEGES Or TOKEN_ADJUST_GROUPS Or TOKEN_ADJUST_DEFAULT)
Private Const TOKEN_EXECUTE = (STANDARD_RIGHTS_EXECUTE)
Private Const TokenImpersonationLevel = 9
Private Const TokenOwner = 4
Private Const TokenUser = 1
Private Const TokenPrimaryGroup = 5
Private Const TokenStatistics = 10
Private Const TokenType = 8
Private Const TokenPrivileges = 3
Private Const TokenSource = 7
Private Const TokenDefaultDacl = 6
Private Const TokenGroups = 2

Public Function WinError(ByVal lLastDLLError As Long) As String

Dim sBuff As String
Dim lCount As Long

sBuff = Space(255)
lCount = FormatMessage(FORMAT_MESSAGE_FROM_SYSTEM Or FORMAT_MESSAGE_IGNORE_INSERTS, 0, lLastDLLError, 0&, sBuff, Len(sBuff), ByVal 0)

If lCount Then
WinError = Left(sBuff, lCount)
End If

End Function

Public Function IsNT() As Boolean

Static bOnce As Boolean
Static bValue As Boolean

If Not (bOnce) Then
Dim tVI As OSVERSIONINFO

tVI.dwOSVersionInfoSize = Len(tVI)

If (GetVersionEx(tVI) <> 0) Then
bValue = (tVI.dwPlatformId = VER_PLATFORM_WIN32_NT)
bOnce = True
End If
End If

IsNT = bValue

End Function

Private Function NTEnableShutDown(ByRef sMsg As String) As Boolean

Dim tLUID As LUID
Dim hProcess As Long
Dim hToken As Long
Dim tTP As TOKEN_PRIVILEGES
Dim tTPOld As TOKEN_PRIVILEGES
Dim lTpOld As Long
Dim lR As Long

lR = LookupPrivilegeValue(vbNullString, SE_SHUTDOWN_NAME, tLUID)

If (lR <> 0) Then

hProcess = GetCurrentProcess()
If (hProcess <> 0) Then
lR = OpenProcessToken(hProcess, TOKEN_ADJUST_PRIVILEGES Or TOKEN_QUERY, hToken)
If (lR <> 0) Then

With tTP
.PrivilegeCount = 1
With .Privileges(0)
.Attributes = SE_PRIVILEGE_ENABLED
.pLuid.HighPart = tLUID.HighPart
.pLuid.LowPart = tLUID.LowPart
End With
End With

lR = AdjustTokenPrivileges(hToken, 0, tTP, Len(tTP), tTPOld, lTpOld)

If (lR <> 0) Then
NTEnableShutDown = True
Else
Err.Raise eeSSDErrorBase + 6, App.EXEName & ".mShutDown", "Can't enable shutdown: You do not have the privileges to " & "shutdown this system. [" & WinError(Err.LastDllError) & "]"
End If

CloseHandle hToken
Else
Err.Raise eeSSDErrorBase + 6, App.EXEName & ".mShutDown", "Can't enable shutdown: You do not have the privileges to " & "shutdown this system. [" & WinError(Err.LastDllError) & "]"
End If
Else
Err.Raise eeSSDErrorBase + 5, App.EXEName & ".mShutDown", "Can't enable shutdown: Can't determine the current process. [" & WinError(Err.LastDllError) & "]"
End If
Else
Err.Raise eeSSDErrorBase + 4, App.EXEName & ".mShutDown", _
"Can't enable shutdown: Can't find the SE_SHUTDOWN_NAME privilege value. [" & _
WinError(Err.LastDllError) & "]"
End If

End Function

Public Function ShutdownSystem(Optional ByVal eType As EShutDownTypes = EWX_SHUTDOWN) As Boolean

Dim yesno As Integer

Dim lR As Long
Dim sMsg As String

If (eType < EShutDownTypes.[_First] And eType > EShutDownTypes.[_Last]) Then
Err.Raise eeSSDErrorBase + 7, App.EXEName & ".mShutDown", "Invalid parameter to ShutdownSystem: " & eType, vbInformation
Exit Function
End If

If (IsNT) Then
If Not (NTEnableShutDown(sMsg)) Then
Exit Function
End If
End If

lR = ExitWindowsEx(eType, &HFFFFFFFF)

If (lR = 0) Then
Err.Raise eeSSDErrorBase + 3, App.EXEName & ".mShutDown", "ShutdownSystem failed: " & WinError(Err.LastDllError)
Else
ShutdownSystem = True
End If

End Function
Contoh penggunaan fungsi di atas -shutdown
Private Sub Command1_Click()
ShutdownSystem EWX_FORCESHUTDOWN
End Sub
Contoh penggunaan fungsi di atas -restart
Private Sub Command2_Click()
ShutdownSystem EWX_FORCEREBOOT
End Sub
Contoh penggunaan fungsi di atas -log-off
Private Sub Command3_Click()
ShutdownSystem EWX_FORCELOGOFF
End Sub
READ MORE - VB6 Code - Fungsi Shutdown, Restart, Log-off

VB6 Code - Mengetahui Lama Windows Dijalankan

Fungsi VB6 untuk mengetahui berapa lama windows telah dijalankan.
Option Explicit

Private Declare Function GetTickCount Lib "Kernel32" () As Long

Private Sub Timer1_Timer()
Text1.Text = Format(GetTickCount, "0") & " milisceconds"
Text2.Text = Format(GetTickCount / 60000, "0") & " minutes"
End Sub
READ MORE - VB6 Code - Mengetahui Lama Windows Dijalankan

VB6 Code - Memperoleh Time Out Screen Saver

Di bawah ini merupakan fungsi VB6 untuk memperoleh/mengetahui time out screen saver. Adapun kodenya di bawah ini:
Option Explicit

Private Declare Function SystemParametersInfo Lib "user32" Alias "SystemParametersInfoA" (ByVal uAction As Long, ByVal uParam As Long, lpvParam As Any, ByVal fuWinIni As Long) As Long
Private Const SPI_GETSCREENSAVETIMEOUT = 14

Function ScrTimeOut() As Integer
Dim intValue As Integer
Call SystemParametersInfo(SPI_GETSCREENSAVETIMEOUT, vbNull, intValue, 0)
ScrTimeOut = intValue
End Function
Contoh penggunaan fungsi di atas:
Private Sub Command1_Click()
MsgBox ("Screen saver time-out value: " & ScrTimeOut & " seconds.")
End Sub
READ MORE - VB6 Code - Memperoleh Time Out Screen Saver

Saturday, April 3, 2010

VB6 Code - Fungsi Untuk Merubah Desktop Wallpaper

Di bawah ini merupakan fungsi VB6 untuk merubah desktop wallpaper. Bagaimana implementasinya dalam Visual Basic 6.0?
Option Explicit

Private Declare Function SystemParametersInfo Lib "user32" Alias "SystemParametersInfoA" (ByVal uAction As Long, ByVal uParam As Long, ByVal lpvParam As Any, ByVal fuWinIni As Long) As Long

Private Const SPIF_SENDWININICHANGE = &H2
Private Const SPIF_UPDATEINIFILE = &H1
Private Const SPIF_SETDESKWALLPAPER = 20

Public Function ChangeWallPaper(imgFile As String)
Call SystemParametersInfo(SPIF_SETDESKWALLPAPER, 0&, imgFile, SPIF_UPDATEINIFILE Or SPIF_SENDWININICHANGE)
End Function
Contoh penggunaan kode di atas
Private Sub Command1_Click()
Call ChangeWallPaper("C:\Windows\Blue.bmp")
End Sub
READ MORE - VB6 Code - Fungsi Untuk Merubah Desktop Wallpaper

VB6 - Menyembunyikan Dan Menampilkan Windows Taskbar

Di bawah ini merupakan contoh standar untuk menyembunyikan dan menampilkan windows taskbar menggunakan Visual Basic 6.
Option Explicit

Private Declare Function SetWindowPos Lib "user32" (ByVal hWnd As Long, ByVal hWndInsertAfter As Long, ByVal X As Long, ByVal y As Long, ByVal cx As Long, ByVal cy As Long, ByVal wFlags As Long) As Long
Private Declare Function FindWindow Lib "user32" Alias "FindWindowA" (ByVal lpClassName As String, ByVal lpWindowName As String) As Long

Const SWP_HIDEWINDOW = &H80
Const SWP_SHOWWINDOW = &H40

Public Sub HideTaskBar()
Dim hWnd1 As Long
hWnd1 = FindWindow("Shell_traywnd", "")
Call SetWindowPos(hWnd1, 0, 0, 0, 0, 0, SWP_HIDEWINDOW)
End Sub

Public Sub ShowTaskBar()
Dim hWnd1 As Long
hWnd1 = FindWindow("Shell_traywnd", "")
Call SetWindowPos(hWnd1, 0, 0, 0, 0, 0, SWP_SHOWWINDOW)
End Sub
Contoh penggunaan untuk menyembunyikan windows taskbar
Private Sub  Command1_Click()
HideTaskBar
End Sub
Contoh penggunaan untuk menampilkan windows taskbar
Private Sub Command2_Click()
ShowTaskBar
End Sub
Demikian mengenai cara menampilkan dan menyembunyikan windows taskbar menggunakan Visual Basic 6.
READ MORE - VB6 - Menyembunyikan Dan Menampilkan Windows Taskbar

VB6 Code - Menampilkan Kotak Dialog Shutdown

Di bawah ini merupakan fungsi API untuk menampilkan kotak dialog shutdown menggunakan kode VB6. Fungsi yang digunakan adalah SHShutDownDialog yang terdapat pada Shell32.dll.
Option Explicit

Private Declare Function SHShutDownDialog Lib "shell32" Alias "#60" (ByVal sParam As Long) As Long
Contoh penggunaan fungsi API di atas:
Private Sub Command1_Click()
SHShutDownDialog 0
End Sub
READ MORE - VB6 Code - Menampilkan Kotak Dialog Shutdown

VB6 Code - Fungsi Untuk Memeriksa Resolusi Screen

Di bawah ini merupakan fungsi VB6 untuk mengetahui resolusi screen. Bagaimana implementasinya dalam Visual Basic 6.0? bisa kita simak kodenya di bawah ini:
Option Explicit
Public Function ScreenResolution(iWidth, iHeight) As String
iWidth = Screen.Width \ Screen.TwipsPerPixelX
iHeight = Screen.Height \ Screen.TwipsPerPixelY
ScreenResolution = "Screen Resolution:" + vbCrLf + vbCrLf + Str$(iWidth) + " x" + Str$(iHeight)
End Function
Contoh penggunaan fungsi di atas:
Private Sub Command1_Click()
Dim intWidth As Integer
Dim intHeight As Integer
MsgBox ScreenResolution(intWidth, intHeight)
MsgBox intWidth
MsgBox intHeight
End Sub
READ MORE - VB6 Code - Fungsi Untuk Memeriksa Resolusi Screen

VB6 Code - Drag Form Yang Tidak Memiliki Controlbox

Di bawah ini merupakan fungsi VB6 (menggunakan fungsi API) untuk men-drag form yang tidak memiliki Control Box.
Option Explicit

Private Declare Function SendMessage Lib "User32" Alias "SendMessageA" (ByVal hWnd As Long, ByVal wMsg As Long, ByVal wParam As Long, lParam As Any) As Long
Private Declare Sub ReleaseCapture Lib "User32" ()

Const WM_NCLBUTTONDOWN = &HA1
Const HTCAPTION = 2

Public Sub DragForm(frm As Form)
Dim lngReturnValue As Long
Call ReleaseCapture
lngReturnValue = SendMessage(frm.hWnd, WM_NCLBUTTONDOWN, HTCAPTION, 0&)
End Sub
Contoh penggunaan drag form yang tidak memiliki controlbox
Private Sub Form_MouseMove(Button As Integer, Shift As Integer, X As Single, Y As Single)
DragForm Me
End Sub
READ MORE - VB6 Code - Drag Form Yang Tidak Memiliki Controlbox

VB6 Code - Mencari Aplikasi Asosiasi Sebuah File

Di bawah ini merupakan fungsi VB6 untuk mencari aplikasi yang diasosiasikan terhadap sebuah file. Bingung? misalnya kita double klik file berektensi .ini maka aplikasinya notepad.exe, double klik file berektensi .doc maka aplikasinya Microsoft Word, dst.
Option Explicit

Private Declare Function FindExecutableA Lib "shell32.dll" (ByVal lpFile As String, ByVal lpdirectory As String, ByVal lpResult As String) As Long
Private Const MAX_FILENAME_LEN = 256

Public Function FindExecutable(FileName As String) As String
Dim iReturn As Integer
Dim sResults As String

sResults = String(MAX_FILENAME_LEN, 32) & Chr$(0)

iReturn = FindExecutableA(FileName & Chr$(0), vbNullString, sResults)

If iReturn > 32 Then
FindExecutable = Left$(sResults, InStr(sResults, Chr$(0)) - 1)
Else
FindExecutable = ""
End If
End Function
Contoh penggunaan fungsi untuk mencari assosiasi sebuah file
Private Sub Form_Load()
MsgBox FindExecutable("c:\boot.ini")
End Sub
READ MORE - VB6 Code - Mencari Aplikasi Asosiasi Sebuah File

VB Code - Mengubah Object LeftToRight Menjadi RighToLeft

Di bawah ini merupakan fungsi VB6 untuk mengubah objek yang tidak memiliki properties LeftToRight agar seolah-olah memiliki properties tersebut. Melalui akal-akalan fungsi API, hal tersebut mungkin untuk dilakukan.
Option Explicit

Private Declare Function SetWindowLong Lib "user32" Alias "SetWindowLongA" (ByVal hWnd As Long, ByVal nIndex As Long, ByVal dwNewLong As Long) As Long 'TreeView1 RightToLeft True

Private Const WS_EX_LAYOUTRTL = 4194304
Private Const GWL_EXSTYLE = -20

Public Sub ctlRightToLeft(ctl As Control)
SetWindowLong ctl.hWnd, GWL_EXSTYLE, WS_EX_LAYOUTRTL
End Sub
Contoh penggunaan fungsi VB6 di atas:
Private Sub Command1_Click()
ctlRightToLeft TreeView1
TreeView1.Appearance = cc3D
TreeView1.BorderStyle = ccFixedSingle
TreeView1.Refresh
End Sub
Coba Anda ganti objeknya misalnya menggunakan Progress Bar, kemudian lihat apa yang terjadi?
READ MORE - VB Code - Mengubah Object LeftToRight Menjadi RighToLeft

VB6 Code - Download File Menggunakan IE

Di bawah ini merupakan procedure VB6 untuk mendownload sebuah file dengan memanfaatkan file bawaan IE (internet explorer) hdocvw.dll. Bagaimana implementasinya dalam Visual Basic 6.0? bisa Anda simak kodenya di bawah ini:
Option Explicit

Private Declare Function DoFileDownload Lib "shdocvw.dll" (ByVal lpszFile As String) As Long

Public Sub DownloadFile(URL As String)
Dim sDownload As String
sDownload = StrConv(Text1.Text, vbUnicode)
Call DoFileDownload(sDownload)
End Sub
Contoh penggunaan procedure VB6 di atas:
Private Sub Command1_Click()
DownloadFile "http://google.co.id"
End Sub
READ MORE - VB6 Code - Download File Menggunakan IE

VB6 Code - Apakah Aplikasi Masih Dalam IDE VB6

Ini merupakan cara yang cerdik untuk mengetahui apakah sebuah aplikasi masih dalam IDE Visual Basic 6.0 ataukah sudah dicompile. Procedurenya sangat sederhana sekali yakni dengan memanfaatkan handle error.
Public Function IsIDE() As Boolean
On Error GoTo ErrHandler
Debug.Print 1 / 0
ErrHandler:
IsIDE = Err
End Function
Contoh penggunaan kode VB6 di atas:
Private Sub Form_Load()
If IsIDE Then
MsgBox "Jalankan aplikasi ini dari file .EXE", vbInformation, "Message"
End If
End Sub

READ MORE - VB6 Code - Apakah Aplikasi Masih Dalam IDE VB6

VB6 Code - Memindahkan File Ke Recycle Bin

Di bawah ini merupakan procedure VB6 untuk memindahkan/menghapus file ke dalam recycle bin. Bagaimana kodenya dalam Visual Basic 6.0? bisa kita simak di bawah ini:
Option Explicit

Private Declare Function SHFileOperation Lib "shell32.dll" Alias "SHFileOperationA" (lpFileOp As SHFILEOPSTRUCT) As Long

Private Type SHFILEOPSTRUCT
hwnd As Long
wFunc As Long
pFrom As String
pTo As String
fFlags As Integer
fAnyOperationsAborted As Long
hNameMappings As Long
lpszProgressTitle As Long
End Type

Private Const FO_DELETE = &H3
Private Const FOF_ALLOWUNDO = &H40
Private Const FOF_NOCONFIRMATION = &H10
Private Const FOF_SILENT = &H4

Public Sub SendFileToRecycleBin(FileName As String, Optional Confirm As Boolean = True, Optional Silent As Boolean = False)
Dim FileOp As SHFILEOPSTRUCT

With FileOp
.wFunc = FO_DELETE
.pFrom = FileName
fFlags = FOF_ALLOWUNDO
If Not Confirm Then .fFlags = .fFlags + FOF_NOCONFIRMATION
If Silent Then .fFlags = .fFlags + FOF_SILENT
End With
SHFileOperation FileOp
End Sub
Contoh penggunaan procedure VB6 di atas:
Private Sub Command1_Click()
SendFileToRecycleBin "c:\42.tmp", True, False
End Sub
READ MORE - VB6 Code - Memindahkan File Ke Recycle Bin

VB6 Code - Menghapus Seluruh File Recycle Bin

Di bawah ini merupakan fungsi VB6 untuk menghapus seluruh file yang terdapat pada recycle bin. Bagaimana implementasinya dalam Visual Basic 6.0? bisa Anda simak kodenya di bawah ini
Option Explicit

Private Declare Function SHEmptyRecycleBin Lib "shell32.dll" Alias "SHEmptyRecycleBinA" (ByVal hWnd As Long, ByVal pszRootPath As String, ByVal dwFlags As Long) As Long
Const SHERB_NOCONFIRMATION = &H1
Const SHERB_NOPROGRESSUI = &H2
Const SHERB_NOSOUND = &H4

Public Sub EmptyRecycleBin(frm As Form)
Dim RetVal
RetVal = SHEmptyRecycleBin(frm.hWnd, "", SHERB_NOPROGRESSUI + SHERB_NOCONFIRMATION)
End Sub
Contoh pengunaan procedure VB6 di atas
Private Sub Command1_Click()
EmptyRecycleBin Me
End Sub
READ MORE - VB6 Code - Menghapus Seluruh File Recycle Bin

VB6 Code - Apakah Recycle Bin Kosong?

Di bawah ini merupakan fungsi VB6 untuk memeriksa apakah recycle bin kosong? Bagaimana implementasinya dalam Visual Basic 6.0? bisa Anda simak kodenya dibawah ini:
Option Explicit

Private Type SHQUERYRBINFO
cbSize As Long
i64SizeLo As Long
i64SizeHi As Long
i64NumItemsLo As Long
i64NumItemsHi As Long
End Type

Private Declare Function SHQueryRecycleBin Lib "shell32" Alias "SHQueryRecycleBinA" (ByVal pszRootPath As String, pSHQueryRBInfo As SHQUERYRBINFO) As Long

Function IsEmptyRecycle() As Boolean
Dim RB As SHQUERYRBINFO
RB.cbSize = Len(RB)
Call SHQueryRecycleBin("C:\", RB)
IsEmptyRecycle = (RB.i64NumItemsLo = 0)
End Function
Contoh penggunaan fungsi VB6 di atas:
Private Sub Command1_Click()
MsgBox IsEmptyRecycle
End Sub
READ MORE - VB6 Code - Apakah Recycle Bin Kosong?

VB6 Code - Menghapus Seluruh File Recent Document

Di bawah ini merupakan procedure VB6 untuk menghapus seluruh yang terdapat pada recent document. Untuk keperluan ini digunakan satu fungsi API yakni SHAddToRecentDocs yang terdapat pada shell32.dll.
Option Explicit

Private Declare Sub SHAddToRecentDocs Lib "shell32.dll" (ByVal uFlags As Long, ByVal pv As Any)

Sub EmptyRecentDocument()
SHAddToRecentDocs 0, CLng(0)
End Sub
Contoh penggunaan procedure VB6 di atas:
Private Sub Command1_Click()
EmptyRecentDocument
End Sub
READ MORE - VB6 Code - Menghapus Seluruh File Recent Document

VB6 Code - Membuat Efek Bayangan Pada Objek

Di bawah ini merupakan fungsi VB6 untuk membuat efek bayangan pada sebuah objek. Bagaimana implementasi dalam Visual Basic 6.0? bisa Anda simak kodenya di bawah ini:
Option Explicit

Public Function Shadow(frm As Form, ctl As Control, Optional shWidth = 3, Optional Color = vbGrayed)
Dim oldWidth As Integer
Dim oldScale As Integer

With frm
oldWidth = .DrawWidth
oldScale = .ScaleMode
.ScaleMode = 3
.DrawWidth = 1
frm.Line (ctl.Left + shWidth, ctl.Top + shWidth)-Step(ctl.Width - 1, ctl.Height - 1), Color, BF
.DrawWidth = oldWidth
.ScaleMode = oldScale
End With

End Function
Contoh penggunaan fungsi membuat efek bayangan pada objek:
Private Sub Command1_Click()
Shadow Me, Command1, 2, vbBlack
End Sub

Anda dapat menggunakannya pada objek secara bulk dengan menggunakan for...each.
READ MORE - VB6 Code - Membuat Efek Bayangan Pada Objek

VB6 Code - Menambahkan File Ke Recent Document

Di bawah ini merupakan fungsi VB6 (API) untuk menambahkan file ke recent document. Untuk keperluan ini digunakan satu fungsi API yakni SHAddToRecentDocs yang terdapat pada shell32.dll.
Option Explicit

Private Declare Sub SHAddToRecentDocs Lib "shell32.dll" (ByVal uFlags As Long, ByVal pv As String)

Public Function AddToRecentDocument(FileName As String)
Call SHAddToRecentDocs(3, FileName)
End Function
Cara menggunakan fungsi VB6 di atas:
Private Sub Command1_Click()
AddToRecentDocument "C:\boot.ini"
End Sub
READ MORE - VB6 Code - Menambahkan File Ke Recent Document

VB6 Code - Class Untuk Mengetahui Crc32 Dari Sebuah File

Di bawah ini merupakan class VB6 untuk mengetahui CRC32 dari sebuah file. Untuk keperluan ini copy dan pastekan kode di bawah ini ke dalam class, kemudian ganti nama kelasnya menjadi clsCRC.
Option Explicit

Private crcTable(0 To 255) As Long 'crc32

Private Function CRC32(ByRef bArrayIn() As Byte, ByVal lLen As Long, Optional ByVal lcrc As Long = 0) As Long

Dim lCurPos As Long
Dim lTemp As Long

If lLen = 0 Then Exit Function 'In case of empty file
lTemp = lcrc Xor &HFFFFFFFF 'lcrc is for current value from partial check on the partial array

For lCurPos = 0 To lLen
lTemp = (((lTemp And &HFFFFFF00) \ &H100) And &HFFFFFF) Xor (crcTable((lTemp And 255) Xor bArrayIn(lCurPos)))
Next lCurPos

CRC32 = lTemp Xor &HFFFFFFFF

End Function

Private Function BuildTable() As Boolean

Dim I As Long, x As Long, crc As Long
Const Limit = &HEDB88320 'usally its shown backward, cant remember what it was.

For I = 0 To 255
crc = I
For x = 0 To 7
If crc And 1 Then
crc = (((crc And &HFFFFFFFE) \ 2) And &H7FFFFFFF) Xor Limit
Else
crc = ((crc And &HFFFFFFFE) \ 2) And &H7FFFFFFF
End If
Next x
crcTable(I) = crc
Next I

End Function

Private Sub Class_Initialize()
BuildTable
End Sub

Public Function CekCRC32(FileName As String) As String

Dim lngCrc As Long
Dim sCrc As Long

On Error GoTo ErrHandler

Open FileName For Binary Access Read As #1
ReDim tmp(LOF(1)) As Byte
Get #1, , tmp()
Close #1

lngCrc = UBound(tmp)
lngCrc = CRC32(tmp, lngCrc)
CekCRC32 = Hex(lngCrc)

Exit Function

ErrHandler:

MsgBox Err.Description, vbCritical, "Error"

End Function
Contoh penggunaan Class CRC32
Option  Explicit

Private Sub Form_Load()
Dim crc As New clsCRC
MsgBox crc.CekCRC32("C:\boot.ini")
End Sub
READ MORE - VB6 Code - Class Untuk Mengetahui Crc32 Dari Sebuah File

VB6 Code - Mencegah Aplikasi Dijalankan Dua Kali - Part-2

Di bawah ini merupakan prosedure VB6 kedua masih mengenai cara mencegah aplikasi dijalankan dua kali. Bagaimana implementasinya dalam Visual Basic 6.0? bisa Anda simak kodenya di bawah ini:
Option Explicit

Declare Function OpenIcon Lib "user32" (ByVal hWnd As Long) As Long
Declare Function FindWindow Lib "user32" Alias "FindWindowA" (ByVal lpClassName As String, ByVal lpWindowName As String) As Long
Declare Function GetWindow Lib "user32" (ByVal hWnd As Long, ByVal wCmd As Long) As Long
Declare Function SetForegroundWindow Lib "user32" (ByVal hWnd As Long) As Long

Public Const GW_HWNDPREV = 3

Sub ActivatePrevInstance()

Dim AppTitle As String
Dim PrevHndl As Long
Dim result As Long

AppTitle = App.Title
App.Title = "unwanted instance"

If PrevHndl = 0 Then
PrevHndl = FindWindow("ThunderRT6Main", AppTitle)
If PrevHndl <> 0 Then
PrevHndl = GetWindow(PrevHndl, GW_HWNDPREV)
result = OpenIcon(PrevHndl)
result = SetForegroundWindow(PrevHndl)
End
End If
End If

End Sub
Contoh penggunaan prosedure VB6 di atas:
Private Sub Form_Load()
If App.PrevInstance Then ActivatePrevInstance
End Sub
READ MORE - VB6 Code - Mencegah Aplikasi Dijalankan Dua Kali - Part-2

VB6 Code - Mengetahui Jumlah Tombol Yang Terdapat Pada Mouse

Di bawah ini merupakan fungsi VB6 untuk mengetahui jumlah tombol yang terdapat pada mouse.
Option Explicit

Private Declare Function GetSystemMetrics Lib "user32" (ByVal nIndex As Long) As Long
Private Const SM_CMOUSEBUTTONS As Long = 43

Public Function ButtonMouse()
ButtonMouse = GetSystemMetrics(SM_CMOUSEBUTTONS)
End Function
Contoh penggunaan fungsi VB6 di atas:
Private Sub Command1_Click()
MsgBox ButtonMouse
End Sub
READ MORE - VB6 Code - Mengetahui Jumlah Tombol Yang Terdapat Pada Mouse

VB6 Code - Apakah Mouse Terinstall Pada Komputer Anda?

Di bawah ini merupakan fungsi VB6 untuk memeriksa apakah mouse terinstall pada komputer Anda. Bagaimana implementasinya dalam Visual Basic 6.0? simaklah kodenya di bawah ini.
Option Explicit

Private Const SM_CMOUSEBUTTONS = 43
Private Declare Function GetSystemMetrics Lib "user32" (ByVal nIndex As Long) As Long

Public Function IsMousePresent() As Boolean
IsMousePresent = (GetSystemMetrics(SM_CMOUSEBUTTONS) > 0)
End Function
Contoh penggunaan fungsi VB6 di atas:
Private Sub Command1_Click()
MsgBox IsMousePresent
End Sub
READ MORE - VB6 Code - Apakah Mouse Terinstall Pada Komputer Anda?

VB6 Code - Merubah Waktu Double Klik Pada Mouse

Di bawah ini merupakan fungsi VB6 untuk merubah waktu double klik pada mouse. Bagaimana implementasinya dalam Visual Basic 6.0? Simaklah kodenya di bawah ini.
Option Explicit

Private Declare Function SetDoubleClickTime Lib "user32" (ByVal wCount As Long) As Long

Public Function ChangeDBClkTime(Time As Integer)
SetDoubleClickTime (Time)
End Function
Contoh penggunaan fungsi VB6 di atas:
Private Sub Command1_Click()
Call ChangeDBClkTime(1000)
End Sub
READ MORE - VB6 Code - Merubah Waktu Double Klik Pada Mouse

VB6 Code - Mencegah Aplikasi Dijalankan Dua Kali

Di bawah ini merupakan cara termudah untuk mencegah sebuah aplikasi dijalankan dua kali (double instance) menggunakan VB6. Bagaimana implementasinya dalam Visual Basic 6.0? Simaklah kodenya di bawah ini.
Option Explicit

Private Sub ActivatePrevInstance()
AppActivate App.Title
SendKeys "+", True
End
End Sub
Contoh penggunaan procedure VB6 di atas:
Private Sub Form_Load()
If App.PrevInstance Then ActivatePrevInstance
End Sub
READ MORE - VB6 Code - Mencegah Aplikasi Dijalankan Dua Kali

VB6 Code - Memindahkan Seluruh File Dalam Satu Directory

Di bawah ini merupakan fungsi VB6 untuk memindahkan seluruh file dari satu directory tertentu. Untuk keperluan ini Anda harus mereferensi pada objek Microsoft Scripting Runtime atau scrun.dll.
Option Explicit

Public Function MoveAllFiles()
Dim fso As New FileSystemObject
Call fso.MoveFolder(Source, Destination)
Set fso = Nothing
End Function
Contoh penggunaan fungsi VB6 di atas:
Private Sub Command1_Click()
Call MoveAllFiles("C:\djview", "D:\djview")
End Sub
READ MORE - VB6 Code - Memindahkan Seluruh File Dalam Satu Directory

VB6 Code - Mengcopy Seluruh File Dalam Satu Directory

Di bawah ini merupakan fungsi VB6 untuk meng-copy seluruh file dari satu directory tertentu. Untuk keperluan ini Anda harus mereferensi pada objek Microsoft Scripting Runtime atau scrun.dll.
Option Explicit

Public Function CopyAllFiles(Source As String, Destination As String)
Dim fso As New FileSystemObject
Call fso.CopyFolder(Source, Destination)
Set fso = Nothing
End Function
Contoh penggunaan fungsi di atas:
Private Sub Command1_Click()
Call CopyAllFiles("C:\djview", "D:\djview")
End Sub
READ MORE - VB6 Code - Mengcopy Seluruh File Dalam Satu Directory

VB6 Code Konversi Warna Dari Qbcolor Ke RGB

Di bawah ini merupakan fungsi VB6 untuk meng-konversi warna dari QBColor ke RGB. Bagaimana implementasinya dalam Visual Basic 6.0? simak kodenya di bawah ini:
Public Sub QBColorToRGB(QBColorValue As Integer)
QBColorToRGB = LongToRGB(QBColor(QBColorValue))
End Sub
READ MORE - VB6 Code Konversi Warna Dari Qbcolor Ke RGB

VB6 Code - Konversi Warna Dari Rgb Ke Long

Di bawah ini merupakan fungsi VB6 untuk meng-konversi warna dari RGB(red, green, blue) ke Long. Bagaimana implementasinya dalam Visual Basic 6.0? simak kodenya di bawah ini:
Public Function RGBToLong(Red As Integer, Green As Integer, Blue As Integer)
RGBToLong = RGB(Red, Green, Blue)
End Function
Contoh penggunaan fungsi konversi warna dari RGB ke Long
Private Sub Command1_Click()
MsgBox RGB(8, 12, 254)
End Sub
READ MORE - VB6 Code - Konversi Warna Dari Rgb Ke Long

VB6 Code - Konversi Warna Long Ke RGB

Di bawah ini merupakan fungsi VB6 untuk meng-konversi warna dari long ke rgb (red, green, blue). Bagaimana implementasinya dalam Visual Basic 6.0? simak kodenya di bawah ini:
Public Sub LongToRGB(Color As Long, Red, Green, Blue)
Blue = Color \ 65536
Green = (Color - Blue * 65536) \ 256
Red = Color - (Blue * 65536) - (Green * 256)
End Sub
Contoh penggunaan fungsi VB6 di atas:
Private Sub Command1_Click()
Dim red
Dim green
Dim blue
Call LongToRGB(CLng("23489"), red, green, blue)
MsgBox red & "," & green & "," & blue
End Sub
READ MORE - VB6 Code - Konversi Warna Long Ke RGB

VB6 Code - Konversi Warna Dari RGB Ke Hex

Di bawah ini merupakan fungsi VB6 untuk meng-konversi warna dari rgb (red, green, blue) ke Hex. Bagaimana implementasinya dalam Visual Basic 6.0? simak kodenya di bawah ini:
Public Function RGBToHex(Red As Integer, Green As Integer, Blue As Integer)
RGBToHex = Right(0 & Hex(Red), 2) & Right(0 & Hex(Green), 2) & Right(0 & Hex(Blue), 2)
End Function
Contoh penggunaan fungsi konversi warna dari RGB ke HEX
Private Sub Command1_Click()
MsgBox RGBToHex(0, 0, 12)
End Sub
READ MORE - VB6 Code - Konversi Warna Dari RGB Ke Hex

VB6 Code - Konversi Angka Dari Hexa Ke Decimal

Di bawah ini merupakan fungsi VB6 untuk mengkonversi angka dari hexadecimal ke decimal dan sebaliknya. Adapun kode untuk mengkonversi angka dari hexa ke decimal dan sebaliknya menggunakan VB6 adalah sebagai berikut:
Option Explicit

Public Function DecToHex(DecNumber)
DecToHex = Hex(DecNumber)
End Function

Public Function HexToDec(HexNumber)
HexToDec = Val("&H" & HexNumber)
End Function
Contoh penggunaan Konversi angka dari decimal ke hexa
Private Sub Form_Load()
MsgBox DecToHex(120000)
End Sub
Contoh penggunaan konversi angka dari hexa ke decimal
Private Sub Form_Load()
MsgBox HexToDec(120000)
End Sub
READ MORE - VB6 Code - Konversi Angka Dari Hexa Ke Decimal

VB6 Code - Menyembunyikan Dan Menampilkan Pointer Mouse

Di bawah ini merupakan procedure VB6 untuk menyembunyikan dan menampilkan pointer mouse. Bagaimana implementasinya dalam Visual Basic 6.0, simaklah kodenya di bawah ini:
Option Explicit

Private Declare Function ShowCursor Lib "user32" (ByVal bShow As Long) As Long

Sub ShowMouseCursor(bShow As Boolean)
ShowCursor bShow
End Sub
Dua contoh penggunaan menyembunyikan dan menampilkan pointer mouse
Private Sub Check1_MouseUp(Button As Integer, Shift As Integer, X As Single, Y As Single)
ShowMouseCursor (Check1.Value = 0)
End Sub

Private Sub Command1_Click()
ShowMouseCursor True
End Sub

READ MORE - VB6 Code - Menyembunyikan Dan Menampilkan Pointer Mouse

VB6 Code - Vertical Scrollbar Textbox Pada Saat Runtime

Di bawah ini merupakan fungsi VB6 untuk menampilkan Vertical ScrollBar pada TextBox.
Option Explicit

Private Declare Function ShowScrollBar Lib "user32" (ByVal hwnd As Long, ByVal wBar As Long, ByVal bShow As Long) As Long

Public Function ShowScroll(obj As Control, bShow As Boolean)
ShowScrollBar obj.hwnd, 1, bShow
obj.Refresh
End Function
Contoh penggunaan kode VB6 di atas:
Public Sub Command1_Click()
ShowScroll Text1, True
End Sub
READ MORE - VB6 Code - Vertical Scrollbar Textbox Pada Saat Runtime

VB6 Code - Fungsi Untuk Membentuk Form Dari Huruf

Di bawah ini merupakan fungsi VB6 untuk membentuk form dari sebuah huruf, kata, atau kalimat. Untuk keperluan ini Anda dapat memodifikasi besar serta jenis hurufnya. Untuk keperluan-keperluan yang seperti ini, kita tidak bisa memprogramnya secara langsung akan tetapi harus melewati fungsi-fungsi API. Bagaimana implementasinya dalam Visual Basic 6.0? bisa Anda simak implementasinya di bawah ini:
Option Explicit

Private Declare Function SelectClipPath Lib "gdi32" (ByVal hDC As Long, ByVal iMode As Long) As Long
Private Declare Function BeginPath Lib "gdi32" (ByVal hDC As Long) As Long
Private Declare Function EndPath Lib "gdi32" (ByVal hDC As Long) As Long
Private Declare Function PathToRegion Lib "gdi32" (ByVal hDC 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 Const txt = "ASEP" & vbCrLf & "HIBBAN"

Public Function MakeFormChar(frm As Form)
Dim hRgn As Long

With frm.Font
.Name = "Comic Sans MS"
.Bold = True
.Size = 100
End With

With frm
.Width = frm.TextWidth(txt)
.Height = frm.TextHeight(txt)
BeginPath .hDC
.CurrentX = 0
.CurrentY = 0
frm.Print txt
EndPath .hDC
hRgn = PathToRegion(.hDC)
SetWindowRgn .hwnd, hRgn, False
.Move (Screen.Width - .Width) / 2, (Screen.Height - .Height) / 2
End With

End Function
READ MORE - VB6 Code - Fungsi Untuk Membentuk Form Dari Huruf

VB6 Code - Fungsi Untuk Menghancurkan File

Di bawah ini merupakan fungsi VB6 untuk menghancurkan file. Maksud dari fungsi ini, agar file yang sudah dihapus/dihancurkan, tidak dapat direcover dengan software-software recovery.
Core function dari fungsi penghancur file ini hanyalah 3 line code, yaitu:
Open Filename For Output As #1
Print #1, "Sorry, destroyed....."
Close #1
Adapun fungsi lengkapnya serta cara penggunaannya:
Option Explicit

Public Function DestroyFile(Filename As String)
Open Filename For Output As #1
Print #1, "Sorry, destroyed....."
Close #1
End Function
Cara penggunaan Fungsi Untuk Menghancurkan File
Private Sub Command1_Click()
Call DestroyFile("C:\hancur.jpg")
End Sub
Di atas merupakan cara penggunaan yang sederhana, dalam kenyataannya Anda dapat memodifikasi penggunaan, sehingga bisa digunakan untuk bulk files destroyer.
READ MORE - VB6 Code - Fungsi Untuk Menghancurkan File

VB6 Code - Procedure Membatasi Pointer Mouse

Di bawah ini merupakan procedure VB6 untuk membatasi gerak pointer mouse pada objek tertentu yang memilliki hwnd (handle window).
Option Explicit

Private Declare Sub ClipCursor Lib "user32" (lpRect As Any)
Private Declare Sub GetClientRect Lib "user32" (ByVal hWnd As Long, lpRect As RECT)
Private Declare Sub ClientToScreen Lib "user32" (ByVal hWnd As Long, lpPoint As POINT)
Private Declare Sub OffsetRect Lib "user32" (lpRect As RECT, ByVal x As Long, ByVal y As Long)

Private Type RECT
left As Integer
top As Integer
right As Integer
bottom As Integer
End Type

Private Type POINT
x As Long
y As Long
End Type

Public Sub LimitCursorMovement(ctl As Object)

Dim client As RECT
Dim upperleft As POINT
Dim lHwnd As Long

On Error Resume Next

lHwnd = ctl.hWnd
If lHwnd = 0 Then Exit Sub

GetClientRect ctl.hWnd, client
upperleft.x = client.left
upperleft.y = client.top
ClientToScreen ctl.hWnd, upperleft
OffsetRect client, upperleft.x, upperleft.y
ClipCursor client

End Sub

Public Sub ReleaseLimit()
ClipCursor ByVal 0&
End Sub
Contoh penggunaan procedureVB6  membatasi pointer mouse
Private Sub Command1_Click()
Command1.Caption = IIf(Command1.Caption = "Set Limit", "Release", "Set Limit")
If Command1.Caption = "Set Limit" Then
ReleaseLimit
Else
LimitCursorMovement Command1
End If
End Sub

Private Sub Form_Load()
Command1.Caption = "Set Limit"
End Sub
READ MORE - VB6 Code - Procedure Membatasi Pointer Mouse

VB Code - Menukarkan Tombol Mouse

Di bawah ini merupakan procedure VB6 untuk menukarkan tombol mouse, dari kiri ke kanan dan sebaliknya. Bagaimana implementasinya dalam Visual Basic 6.0, simaklah kodenya di bawah ini:
Option Explicit

Private Declare Function SwapMouseButton Lib "user32" (ByVal bSwap As Long) As Long

Public Sub SwapMouse(bSwap As Boolean)
SwapMouseButton bSwap
End Sub
Dua contoh penggunaan menukarkan tombol mouse
Private Sub Check1_MouseUp(Button As Integer, Shift As Integer, X As Single, Y As Single)
SwapMouse (Check1.Value=0)
End Sub

Private Sub Command1_Click()
SwapMouse True
End Sub
READ MORE - VB Code - Menukarkan Tombol Mouse

VB6 Code - Menggerakan Pointer Mouse Satu Koordinat

Di bawah ini merupakan fungsi VB6 untuk menggerakan pointer mouse pada koordinat tertentu.
Private Declare Function SetCursorPos Lib "User32" (ByVal X As Long, ByVal Y As Long) As Long
Contoh penggunaan code untuk menggerakan pointer mouse pada koordinat tertentu
Private Sub Command1_Click()
Call SetCursorPos(100, 200)
End Sub
READ MORE - VB6 Code - Menggerakan Pointer Mouse Satu Koordinat

VB6 Code - Menutup Seluruh Aplikasi Yang Sedang Berjalan

Di bawah ini merupakan fungsi VB6 untuk menutup seluruh aplikasi yang sedang berjalan. Mengapa seluruh aplikasi yang sedang berjalan tersebut harus ditutup? contoh kecilnya dalam pembuatan billing warnet. Misalnya A (user) log-out, kemudian datang B (user baru) log-in, B tidak akan melihat aplikasi-aplikasi yang masih terbuka (kemungkinan lupa ditutup oleh A), karena seluruh aplikasi yang sedang berjalan telah ditutup secara otomatis dengan fungsi di bawah ini.
Mungkin ada pertanyaan, Apakah ditutup dengan software billing warnetnya juga? ya, boleh jika kita mau, bahkan sekalian di shutdown pula.
Option Explicit

Public Declare Function SendMessageTimeout Lib "user32" Alias "SendMessageTimeoutA" (ByVal hwnd As Long, ByVal msg As Long, ByVal wParam As Long, _
ByVal lParam As Long, ByVal fuFlags As Long, ByVal uTimeout As Long, lpdwResult As Long) As Long
Public Declare Function IsWindowVisible& Lib "user32" (ByVal hwnd As Long)
Public Declare Function IsWindow Lib "user32" (ByVal hwnd As Long) As Long
Public Declare Function EnumWindows Lib "user32.dll" (ByVal lpEnumFunc As Long, ByVal lParam As Long) As Long
Public Declare Function FindWindowEx Lib "user32" Alias "FindWindowExA" (ByVal hWnd1 As Long, ByVal hWnd2 As Long, ByVal lpsz1 As String, ByVal lpsz2 As String) As Long
Public Declare Function OpenProcess Lib "kernel32" (ByVal dwDesiredAccess As Long, ByVal bInheritHandle As Long, ByVal dwProcessId As Long) As Long
Public Declare Function TerminateProcess& Lib "kernel32" (ByVal hProcess As Long, ByVal uExitCode As Long)
Public Declare Function GetWindowThreadProcessId Lib "user32" (ByVal hwnd As Long, lpdwProcessId As Long) As Long
Public Declare Function CloseHandle Lib "kernel32" (ByVal hObject As Long) As Long

Public Const SMTO_BLOCK = &H1
Public Const SMTO_ABORTIFHUNG = &H2
Public Const SC_CLOSE = &HF060&
Public Const WM_SYSCOMMAND = &H112
Public Const WM_NULL = &H0
Public Const PROCESS_ALL_ACCESS = &H1F0FFF

Public HWND_Taskbar As Long
Public HWND_Desktop As Long
Public HWND_ExplorerW As Long

Public Function EnumWindowsProc(ByVal hwnd As Long, ByVal lParam As Long) As Long

Dim lThreadID As Long
Dim lPid As Long
Dim lHp As Long

If hwnd <> HWND_Taskbar And hwnd <> HWND_Desktop And hwnd <> HWND_ExplorerW Then
lThreadID = GetWindowThreadProcessId(hwnd, lPid)
If lThreadID <> App.ThreadID Then
If IsWindowVisible(hwnd) Then
SendMessageTimeout hwnd, WM_SYSCOMMAND, SC_CLOSE, 0, 0, 500, 0
If IsWindow(hwnd) Then
lHp = OpenProcess(PROCESS_ALL_ACCESS, 0&, lPid)
TerminateProcess lHp&, 0&
CloseHandle lHp
End If
End If
End If
End If

EnumWindowsProc = 1

End Function

Public Sub CloseAllRuning()
HWND_Desktop = FindWindowEx(0&, 0&, "Progman", vbNullString)
HWND_Taskbar = FindWindowEx(0&, 0&, "Shell_TrayWnd", vbNullString)
EnumWindows AddressOf EnumWindowsProc, 0&
End Sub
Contoh Penggunaan fungsi untuk menutup seluruh aplikasi menggunakan VB6:
Sub Main()
Call CloseAllRuning
End Sub
READ MORE - VB6 Code - Menutup Seluruh Aplikasi Yang Sedang Berjalan

VB Code - Meng-capture Screen .bmp Atau .jpg (Ezcapture.dll)

Di bawah ini merupakan fungsi VB6 untuk meng-capture (mengambil) gambar screen dalam format .bmp atau format .jpg dengan menggunakan ActiveX ezCapture.dll. Untuk keperluan ini tentu saja Anda harus memiliki dll ezCapture.dll kemudian mereferensikan project Anda terhadapnya. Mengenai ezCapture.dll bisa Anda download di sini.

Fungsi VB6 untuk meng-Capture screen dalam format .bmp

Option Explicit

Sub CaptureScreenBMP()
Dim ezCapture As New CaptureScreen
On Error Resume Next
With ezCapture
.CaptureFullScreen "C:\screen.bmp"
End With
End Sub

Fungsi VB6 untuk meng-Capture screen dalam format .jpg
Sub CaptureScreenJPG()
Dim ezCapture As New CaptureScreen
With ezCapture
.CaptureFullScreen "C:\screen.jpg"
End With
End Sub

Contoh penggunaan fungsi capture screen .bmp
Private Sub Command1_Click()
CaptureScreenBMP
End Sub

Contoh penggunaan fungsi capture screen .jpg.
Untuk keperluan ini Anda membutuhkan satu file lagi yakni "ijl11.dll"
Private Sub Command2_Click()
CaptureScreenJPG
End Sub
READ MORE - VB Code - Meng-capture Screen .bmp Atau .jpg (Ezcapture.dll)

VB6 Code - Menjalankan File .wav Menggunakan Visual Basic

Di bawah ini merupakan fungsi VB6 untuk menjalankan file .wav dengan menggunakan Visual Basic 6.0 disertai dengan beberapa argumen yang dibutuhkan.
Option Explicit

Public Declare Function sndPlaySound Lib "winmm.dll" Alias "sndPlaySoundA" (ByVal lpszSoundName As String, ByVal uFlags As Long) As Long

Public Enum SoundOption
SND_SYNC = &H0
SND_ASYNC = &H1
SND_NODEFAULT = &H2
SND_LOOP = &H8
SND_NOSTOP = &H10
End Enum

Public Sub PlaySound(Filename As String, Optional OpsiSound As SoundOption = SND_ASYNC Or SND_NODEFAULT)
Dim sThewavsound As String, ret As Long
sThewavsound = Filename
ret = sndPlaySound(sThewavsound, OpsiSound)
End Sub
Contoh Penggunaan fungsi menjalankan file .wav menggunakan visual basic 6.0
Private Sub Command1_Click()
PlaySound Text1.Text, SND_ASYNC
End Sub
READ MORE - VB6 Code - Menjalankan File .wav Menggunakan Visual Basic

VB6 Code - Mendapatkan Source Html Dari URLTertentu

Di bawah ini merupakan fungsi VB6 untuk mendapatkan source code HTML dari URL tertentu.
Option Explicit

Function GetSource(ByVal URL As String) As String

MousePointer = vbHourglass

Dim Data() As Byte
Dim sText As String
Dim i As Long

Data() = Inet1.OpenURL(URL)

sText = Data()
GetSource = sText

MousePointer = vbDefault

End Function
Cara penggunaan fungsi VB6 di atas:
Private Sub Command1_Click()
Dim sUrl As String
sUrl = Text1.Text
Text2.Text = GetSource(sUrl)
End Sub

Untuk tujuan tertentu, maka dengan sedikit modifikasi tentu saja Anda dapat menyimpannya ke dalam hardisk Anda.
READ MORE - VB6 Code - Mendapatkan Source Html Dari URLTertentu

VB Code - Menghapus Seluruh Komentar Visual Basic 6.0

Di bawah ini merupakan fungsi VB6 untuk menghapus seluruh komentar yang terdapat dalam source code Visual Basic 6.0. Kami membuatnya menjadi dua fungsi, fungsi pertama untuk menghapus seluruh komentar sedangkan fungsi yang kedua untuk menghapus seluruh line kosong. Berikut kodenya di bawah ini:
Di bawah ini merupakan fungsi untuk menghapus seluruh komentar yang terdapat dalam Visual Basic 6.0:
Option Explicit

Function DeleteAllComment(sText As String) As String

Dim str As String
Dim vArray As Variant
Dim g As String
Dim i As Integer
Dim x As Integer
Dim w As Integer
Dim u As String
Dim y As Integer

str = sText
vArray = Split(str, vbCrLf)

For i = LBound(vArray) To UBound(vArray)

If Trim(Right(vArray(i), 1)) = "_" Then

Do While Trim(Right(vArray(i + w), 1)) = "_"

If w > 0 Then
vArray(i) = vArray(i) & Left(vArray(i + w), Len(vArray(i + w)) - 1) & " "
vArray(i + w) = "'"
Else
vArray(i) = Left(vArray(i), Len(vArray(i)) - 1)
End If

w = w + 1

Loop

vArray(i) = vArray(i) & Left(vArray(i + w), Len(vArray(i + w))) & " "
vArray(i + w) = "'"

End If

w = 0

y = InStr(1, vArray(i), Chr(34) & "'" & Chr(34))
x = InStr(1, vArray(i), "'")

If x > 0 Then

If (y = 0) Then

If Right(vArray(i), 1) = "_" Then
Do While Right(vArray(i + w), 1) = "_"
If w > 0 Then vArray(i + w) = "'"
w = w + 1
Loop
vArray(i + w) = "'"
End If

If Trim(Mid(vArray(i), 1, x)) <> "'" Then

If Right(Mid(vArray(i), 1, x), 1) = "'" Then
g = g & Left(Mid(vArray(i), 1, x), Len(Mid(vArray(i), 1, x)) - 1) & vbCrLf
Else
g = g & Mid(vArray(i), 1, x) & vbCrLf
End If

End If

Else
g = g & vArray(i) & vbCrLf
End If
Else
g = g & vArray(i) & vbCrLf
End If

Next

DeleteAllComment = g

End Function

Di bawah ini merupakan fungsi untuk menghapus seluruh jajaran kosong (blank line)
Function DeleteBlankLine(sText As String) As String

Dim str As String
Dim vArray As Variant
Dim i As Integer
Dim g As String

str = sText
vArray = Split(sText, vbCrLf)

For i = LBound(vArray) To UBound(vArray)

If Trim(vArray(i)) <> "" Then
g = g & vArray(i) & vbCrLf
End If

Next

DeleteBlankLine = g

End Function

Cara penggunaan:
Option Explicit

Private Sub Command1_Click()
Dim str As String
str = DeleteAllComment(Text1.Text)
Text2.Text = DeleteBlankLine(str)
End Sub
READ MORE - VB Code - Menghapus Seluruh Komentar Visual Basic 6.0

VB Code - Fungsi Personal Editor Html Unordering List [ ul ]

Ini merupakan fungsi VB6 yang digunakan untuk membuat personal editor. Tag yang akan kita modifikasi adalah tag UL (Unordering List).
Option Explicit

Function UL(strText As String) As String
Dim sText As String
Dim aText() As String
Dim i As Integer
sText = strText
aText = Split(sText, vbCrLf)
For i = LBound(aText) To UBound(aText)
Select Case i
Case LBound(aText)
sText = "<ul>" & "<li>" & aText(i) & "</li>" & vbCrLf
Case UBound(aText)
sText = sText & "<li>" & aText(i) & "</li>" & "</ul>"
Case Else
sText = sText & "<li>" & aText(i) & "</li>" & vbCrLf
End Select
Next
UL = sText
End Function
Cara penggunaan Fungsi Personal Editor HTML Unordering List <UL>
Private Sub Command1_Click()
Text1.SelText = UL(Text1.SelText)
End Sub
READ MORE - VB Code - Fungsi Personal Editor Html Unordering List [ ul ]

VB6 Code - Fungsi Encode Dan Decode Tag HTML

Mengenai Fungsi VB6 untuk meng-encode dan decode tag HTML - Kode HTML yang dituliskan dalam sebuah tulisan/postingan tentu saja tidak dapat ditulis secara langsung tetapi harus dikonversi terlebih dahulu agar format tulisannya sesuai dengan apa yang diharapkan. Perlu kita ketahui bahwa mesin penerjemah (compiler) akan menganggap tulisannya merupakan kode HTML dan menerjemahkannya, padahal yang kita maksud adalah tulisan, tulisan yang mengandung kode HTML . Dibawah ini merupakan fungsi encode dan decode tag HTML yang bisa Anda gunakan ketika membuat tulisan/postingan yang melibatkan banyak kode/tag HTML.
Option Explicit

Dim EncodeTag() As String
Dim DecodeTag() As String

Enum eType
Decode
Encode
End Enum

Public Function EncDecTag(strText As String, EncDec As eType) As String
Dim i As Integer
InitTagArray
For i = LBound(EncodeTag) To UBound(EncodeTag)
If EncDec = Encode Then
strText = Replace(strText, EncodeTag(i), DecodeTag(i), , , vbTextCompare)
Else
strText = Replace(strText, DecodeTag(i), EncodeTag(i), , , vbTextCompare)
End If
Next
EncDecTag = strText
End Function

Private Function InitTagArray()
Dim EncTag As String
Dim DecTag As String
EncTag = "&,<,>," & Chr(34) & ",±"
DecTag = "&amp;,&lt;,&gt;,&quot;,&plusmn;"
EncodeTag = Split(EncTag, ",")
DecodeTag = Split(LCase(DecTag), ",")
End Function
Cara Penggunaan Fungsi Encode dan Decode Tag HTML
Private Sub Command1_Click()
Text1.SelText = EncDecTag(Text1.SelText, Decode)
End Sub

Private Sub Command2_Click()
Text1.SelText = EncDecTag(Text1.SelText, Encode)
End Sub
READ MORE - VB6 Code - Fungsi Encode Dan Decode Tag HTML

VB6 Code - Fungsi Personal Editor HTML Ordering List [ ol ]

Ini merupakan fungsi VB6 yang digunakan untuk membuat personal editor. Tag yang akan kita modifikasi adalah tag OL (Ordering List).
Option Explicit

Function OL(strText As String) As String
Dim sText As String
Dim aText() As String
Dim i As Integer
sText = strText
aText = Split(sText, vbCrLf)
For i = LBound(aText) To UBound(aText)
Select Case i
Case LBound(aText)
sText = "<ol>" & "<li>" & aText(i) & "</li>" & vbCrLf
Case UBound(aText)
sText = sText & "<li>" & aText(i) & "</li>" & "</ol>"
Case Else
sText = sText & "<li>" & aText(i) & "</li>" & vbCrLf
End Select
Next
OL = sText
End Function

Cara penggunaan Fungsi Personal Editor HTML Ordering List <OL>
Private Sub Command1_Click()
Text1.SelText = OL(Text1.SelText)
End Sub
READ MORE - VB6 Code - Fungsi Personal Editor HTML Ordering List [ ol ]