Wednesday, April 29, 2009

WinHelp

'WinHelp


Const HELP_COMMAND = &H102&

Const HELP_CONTENTS = &H3&

Const HELP_CONTEXT = &H1

Const HELP_CONTEXTPOPUP = &H8&

Const HELP_FORCEFILE = &H9&

Const HELP_HELPONHELP = &H4

Const HELP_INDEX = &H3

Const HELP_KEY = &H101

Const HELP_MULTIKEY = &H201&

Const HELP_PARTIALKEY = &H105&

Const HELP_QUIT = &H2

Const HELP_SETCONTENTS = &H5&

Const HELP_SETINDEX = &H5

Const HELP_SETWINPOS = &H203&



Private Declare Function WinHelp
Lib "user32.dll"
Alias _

"WinHelpA" (ByVal hWndMain
As Long, ByVal lpHelpFile
As String, _

ByVal uCommand As Long, dwData
As Any) As Long


Private Sub Form_Load()

WinHelp Me.hWnd, "C:\Windows\help\display.hlp", _

HELP_CONTENTS, ByVal 0
End Sub

 

Execute by WinExec

'Execute by WinExec

Private Declare Function WinExec
Lib "kernel32" _

(ByVal lpCmdLine As String,
ByVal nCmdShow As Long)
As Long


Private Sub Form_Load()

'Execute explorer.exe

WinExec "Explorer.exe c:\", 10

End Sub



 

Upper-Lower Case

'UPPER-lower case



Private Declare Function CharLower
Lib "user32" Alias "CharLowerA" (ByVal lpsz
As String) As Long

Private Declare Function CharUpper
Lib "user32" Alias "CharUpperA" (ByVal lpsz
As String) As Long



Private Sub Form_Load()

Dim strSave As String, Upper
As String, Lower As String

'Set the Autoredraw property (set to Persistent Graphic)

Me.AutoRedraw = True

'This is the string we're going to use

strSave = "RockessAlpha.blogspot.com"

'Print it to the form

Me.Print "Original : " + strSave

'Convert all the characters to uppercase (like the UCase$-function from VB)

CharUpper strSave

Me.Print "Upper Case : " +  strSave

'Convert all the characters to lowercase (like the LCase$-function from VB)

CharLower strSave

Me.Print "Lower Case : " +  strSave

End Sub

Turn-Off Win NT

'Turn off Win NT
'Needs 1 module and 3 common button


'In a module


Private Const EWX_LOGOFF = 0

Private Const EWX_SHUTDOWN = 1

Private Const EWX_REBOOT = 2

Private Const EWX_FORCE = 4

Private Const TOKEN_ADJUST_PRIVILEGES = &H20

Private Const TOKEN_QUERY = &H8

Private Const SE_PRIVILEGE_ENABLED = &H2

Private Const ANYSIZE_ARRAY = 1

Private Const VER_PLATFORM_WIN32_NT = 2



Type OSVERSIONINFO

   
dwOSVersionInfoSize As Long

   
dwMajorVersion As Long

   
dwMinorVersion As Long

   
dwBuildNumber As Long

   
dwPlatformId As Long

   
szCSDVersion As String * 128

End Type



Type LUID

   
LowPart As Long

   
HighPart As Long

End Type



Type LUID_AND_ATTRIBUTES

   
pLuid As LUID

   
Attributes As Long

End Type



Type TOKEN_PRIVILEGES

   
PrivilegeCount As Long

   
Privileges(ANYSIZE_ARRAY) As LUID_AND_ATTRIBUTES

End Type



Private Declare Function GetCurrentProcess
Lib "kernel32" ()
As Long

Private Declare Function OpenProcessToken
Lib "advapi32" _

(ByVal ProcessHandle As Long,
ByVal DesiredAccess As Long, _

TokenHandle As Long) As Long

Private Declare Function LookupPrivilegeValue
Lib "advapi32"
Alias _

"LookupPrivilegeValueA" (ByVal lpSystemName
As String, _

ByVal lpName As String, lpLuid
As LUID) As Long

Private Declare Function AdjustTokenPrivileges
Lib "advapi32" _

(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 ExitWindowsEx Lib "user32" (ByVal uFlags
As Long, _

ByVal dwReserved As Long)
As Long

Private Declare Function GetVersionEx Lib "kernel32"
Alias "GetVersionExA" _

(ByRef lpVersionInformation As
OSVERSIONINFO) As Long



'Detect if the program is running under Windows NT

Public Function IsWinNT()
As Boolean

    Dim myOS As
OSVERSIONINFO

   
myOS.dwOSVersionInfoSize = Len(myOS)

   
GetVersionEx myOS

    IsWinNT = (myOS.dwPlatformId = VER_PLATFORM_WIN32_NT)

End Function



'set the shut down privilege for the current application

Private Sub EnableShutDown()

    Dim hProc, hToken
As Long

    Dim mLUID As
LUID

    Dim mPriv, mNewPriv
As TOKEN_PRIVILEGES

   
hProc = GetCurrentProcess()

   
OpenProcessToken hProc, TOKEN_ADJUST_PRIVILEGES + _

   
TOKEN_QUERY, hToken

   
LookupPrivilegeValue "", "SeShutdownPrivilege", mLUID

   
mPriv.PrivilegeCount = 1

   
mPriv.Privileges(0).Attributes = SE_PRIVILEGE_ENABLED

   
mPriv.Privileges(0).pLuid = mLUID

   
' enable shutdown privilege for the current application


   
AdjustTokenPrivileges hToken, False, mPriv, 4 + (12 * mPriv.PrivilegeCount), _

   
mNewPriv, 4 + (12 * mNewPriv.PrivilegeCount)

End Sub



' Shut Down NT

Public Sub ShutDownNT(Force
As Boolean)

   
Dim
ret , Flags As Long

   
Flags = EWX_SHUTDOWN

   
If
Force Then Flags = Flags + EWX_FORCE

   
If
IsWinNT Then EnableShutDown

   
ExitWindowsEx Flags, 0

End Sub



'Restart NT

Public Sub RebootNT(Force
As Boolean)

    Dim ret , Flags
As Long

   
Flags = EWX_REBOOT

   
If
Force Then Flags = Flags + EWX_FORCE

   
If
IsWinNT Then EnableShutDown

   
ExitWindowsEx Flags, 0

End Sub



'Log off the current user

Public Sub LogOffNT(Force As Boolean)

    Dim ret , Flags
As Long

   
Flags = EWX_LOGOFF

   
If
Force Then Flags = Flags + EWX_FORCE

If IsWinNT Then EnableShutDown

   
ExitWindowsEx Flags, 0

End Sub



'In a form

Private Sub Command1_Click()

   
LogOffNT True

End Sub



Private Sub Command2_Click()

   
RebootNT True

End Sub



Private Sub Command3_Click()

   
ShutDownNT True

End Sub



Private Sub Form_Load()

   
Command1.Caption = "Log Off NT"

   
Command2.Caption = "Reboot NT"

   
Command3.Caption = "Shutdown NT"

End Sub

 

Translate Background Color

'Translate Background Color



Private Declare Function TranslateColor
Lib "olepro32.dll"
Alias _

"OleTranslateColor" (ByVal clr
As OLE_COLOR, ByVal palet
As Long, _

col As Long) As Long



Private Sub Form_Load()

Dim RealColor As Long

'You can change me.backcolor

Me.BackColor = vbGreen

'Convert OLE colors to RGB colors

TranslateColor Me.BackColor, 0, RealColor

'show the result

MsgBox "The backcolor of this form is R=" + _

CStr(RealColor And &HFF&) + " G=" + _

CStr((RealColor And &HFF00&) / 2 ^ 8) + " B=" + _

CStr((RealColor And &HFF0000) / 2 ^ 16), vbOKOnly, "RockessAlpha"

End Sub



 

Thread Time

'Thread Time



Private Type FILETIME

    dwLowDateTime As Long

    dwHighDateTime As Long

End Type



Private Type SYSTEMTIME

    wYear As Integer

    wMonth As Integer

    wDayOfWeek As Integer

    wDay As Integer

    wHour As Integer

    wMinute As Integer

    wSecond As Integer

    wMilliseconds As Integer

End Type



Private Declare Function GetThreadTimes
Lib "kernel32" _

(ByVal hThread As Long, lpCreationTime As FILETIME, _

lpExitTime As FILETIME, lpKernelTime As FILETIME, _

lpUserTime As FILETIME) As Long



Private Declare Function FileTimeToLocalFileTime
Lib "kernel32" _

(lpFileTime As FILETIME, lpLocalFileTime As FILETIME) As Long

Private Declare Function FileTimeToSystemTime
Lib "kernel32" _

(lpFileTime As FILETIME, lpSystemTime
As SYSTEMTIME) As Long



Private Declare Function
GetCurrentThread Lib "kernel32" () As Long


Private Sub Form_Load()

Dim FT0 As FILETIME, FT1
As FILETIME, ST As
SYSTEMTIME
GetThreadTimes GetCurrentThread, FT1, FT0, FT0, FT0
FileTimeToLocalFileTime FT1, FT1

FileTimeToSystemTime FT1, ST

MsgBox "This thread was started at " + CStr(ST.wHour) + ":" _

+ CStr(ST.wMinute) + "." +
CStr(ST.wSecond) + " on " + _

CStr(ST.wMonth) + "/" +
CStr(ST.wDay) + "/" +
CStr(ST.wYear)

End Sub



 

Tab Text

'Tab Text

Private Declare Function TabbedTextOut
Lib "user32" Alias _

"TabbedTextOutA" (ByVal hdc
As Long, ByVal x
As Long, _

ByVal y As Long,
ByVal lpString As String,
ByVal nCount As Long, _

ByVal nTabPositions As Long, lpnTabStopPositions
As Long, _

ByVal nTabOrigin As Long)
As Long



Private Sub Form_Paint()

Dim TbSP(0 To 2) As Long, TbO(0
To 2) As Long

Dim mStr As String



'set the form's scalemode to Pixels

Me.ScaleMode = vbPixels



'Set the tabstops

TbSP(0) = 100

TbSP(1) = 200

TbSP(2) = 300

TbO(0) = 0

TbO(1) = 100

TbO(2) = 200



'print first string

mStr = "Rockess" + Chr$(9) + "Alpha" + Chr$(9) + "!"

TabbedTextOut Me.hdc, 0, 0, mStr, Len(mStr), 3, TbSP(0), TbO(0)



'print second string

mStr = "Visit" + Chr$(9) + "My" + Chr$(9) + "Blog"

TabbedTextOut Me.hdc, 0, Me.TextHeight(mStr), mStr, Len(mStr), 3, _

TbSP(0), TbO(0)

End Sub



 

System Color

'System Colors



Private Declare Function SetSysColors
Lib "user32" _

(ByVal nChanges As Long, lpSysColor As Long, lpColorValues As Long) As Long

Private Declare Function GetSysColor
Lib "user32" _

(ByVal nIndex As Long) As Long



Const COLOR_SCROLLBAR = 0            
'The Scrollbar colour

Const COLOR_BACKGROUND = 1        'Colour of the background with no wallpaper

Const COLOR_ACTIVECAPTION = 2    
'Caption of Active Window

Const COLOR_INACTIVECAPTION = 3
'Caption of Inactive window

Const COLOR_MENU = 4                        
'Menu

Const COLOR_WINDOW = 5                  
'Windows background

Const COLOR_WINDOWFRAME = 6     
'Window frame

Const COLOR_MENUTEXT = 7               
'Window Text

Const COLOR_WINDOWTEXT = 8         
'3D dark shadow (Win95)

Const COLOR_CAPTIONTEXT = 9          'Text in window caption

Const COLOR_ACTIVEBORDER = 10     
'Border of active window

Const COLOR_INACTIVEBORDER = 11          
'Border of inactive window

Const COLOR_APPWORKSPACE = 12            
'Background of MDI desktop

Const COLOR_HIGHLIGHT = 13                       
'Selected item background

Const COLOR_HIGHLIGHTTEXT = 14              
'Selected menu item

Const COLOR_BTNFACE = 15                           
'Button

Const COLOR_BTNSHADOW = 16                    
'3D shading of button

Const COLOR_GRAYTEXT = 17                          'Grey text, of zero if dithering is used

Const COLOR_BTNTEXT = 18                            
'Button text

Const COLOR_INACTIVECAPTIONTEXT = 19
'Text of inactive window

Const COLOR_BTNHIGHLIGHT = 20                '3D highlight of button

Const COLOR_2NDACTIVECAPTION = 27    
'Win98 only: 2nd active window color

Const COLOR_2NDINACTIVECAPTION = 28
'Win98 only: 2nd inactive window color



Private Sub Form_Load()

col& = GetSysColor(COLOR_ACTIVECAPTION)

'Change the active caption's color to red

t& = SetSysColors(1, COLOR_ACTIVECAPTION, RGB(255, 0, 0))

MsgBox "The old title bar color was" + Str$(col&) + " and is now" +
_

Str$(GetSysColor(COLOR_ACTIVECAPTION))

End Sub



 

Sound Beep

'Sound Beep

Private Declare Function Beep
Lib "kernel32" _

(ByVal dwFreq As Long,
ByVal dwDuration As Long)
As Long



Private Sub Form_Activate()

    Dim Cnt As Long

    For Cnt = 0 To
5000 Step 10

        'play a tone of Cnt Hertz, for 10 milliseconds

        Beep Cnt, 10

        Me.Caption = Cnt

        DoEvents

    Next Cnt

End Sub



'Sound Message Beep

Private Declare Function MessageBeep
Lib "user32" _

(ByVal wType As Long)
As Long

 

Private Sub Form_Load()

    Dim Cnt As Byte

    'Beep 100 times

    For Cnt = 1 To 100

        MessageBeep 0

    Next Cnt

End Sub

Sleep

'Sleep



Private Declare Sub Sleep
Lib "kernel32" (ByVal dwMilliseconds As Long)



Private Sub Form_Load()

'sleep for 10 second

Sleep 10000

End Sub



Private Declare Function SleepEx
Lib "kernel32" _

(ByVal dwMilliseconds As Long,
ByVal bAlertable As Long) As Long



Private Sub Form_Load()

'Sleep 3 seconds

SleepEx 3000, False

End Sub



 

Shell Execute

'Shell Execute

Private Declare Function ShellExecute
Lib "shell32.dll"
Alias _

"ShellExecuteA" (ByVal hwnd
As Long, ByVal lpOperation
As String, _

ByVal lpFile As String,
ByVal lpParameters As String, _

ByVal lpDirectory As String,
ByVal nShowCmd As Long)
As Long



Const SW_SHOWNORMAL = 1



Private Sub Form_Load()

'Visit my Blog

ShellExecute Me.hwnd, vbNullString, "http:\\RockessAlpha.blogspot.com", _

vbNullString, "C:\", SW_SHOWNORMAL

End Sub



 

Shell About Me

'About ME



Private Declare Function ShellAbout
Lib "shell32.dll" Alias
_

"ShellAboutA" (ByVal hWnd As Long, ByVal szApp
As String, _

ByVal szOtherStuff As String, ByVal hIcon As Long) As Long



Private Sub Form_Load()

'Show an about window

ShellAbout Me.hWnd, "About RockessAlpha.blogspot.com", _

"Created by Rockess Alpha", ByVal 0&

End Sub



 

Get System Time Adjustment

'Get System Time Adjustment



Private Declare Function GetSystemTimeAdjustment
Lib "kernel32" _

(lpTimeAdjustment As Long, lpTimeIncrement As Long, _

lpTimeAdjustmentDisabled As Boolean) As Long



Private Sub Form_Load()

Dim RetAdd As Long, RetInterval As Long, RetAdjust
As Boolean

GetSystemTimeAdjustment RetAdd, RetInterval, RetAdjust



If RetAdjust Then

MsgBox "Periodic time adjustment is disabled!", _

vbInformation

Else

MsgBox "Every " + CStr(RetInterval) + _

"x100 nanoseconds, the computer adds " + CStr(RetAdd) + _

"x100 nanoseconds to your time-of-day clock.", _

vbInformation

End If



End Sub



 

Set Time

'Set Time



Private Declare Sub SetSystemTime
Lib "kernel32" _

(lpSystemTime As SYSTEMTIME)



Private Type SYSTEMTIME

    wYear As Integer

    wMonth As Integer

    wDayOfWeek As Integer

    wDay As Integer

    wHour As Integer

    wMinute As Integer

    wSecond As Integer

    wMilliseconds As Integer

End Type



Private Sub Form_Load()

Dim lpSystemTime As
SYSTEMTIME


lpSystemTime.wYear = 2009

lpSystemTime.wMonth = 1

lpSystemTime.wDayOfWeek = -1

lpSystemTime.wDay = 13

lpSystemTime.wHour = 8

lpSystemTime.wMinute = 13

lpSystemTime.wSecond = 8

lpSystemTime.wMilliseconds = 0

'set the new time

SetSystemTime lpSystemTime

End Sub

 

Registry Simple

'REGISTRY



'This program needs 3 Command Buttons


Const REG_SZ = 1

Const REG_EXPAND_SZ = 2

Const REG_BINARY = 3

Const REG_DWORD = 4

Const REG_DWORD_BIG = 5

Const REG_LINK = 6

Const REG_MULTI_SZ = 7



Enum Key_Reg

HKEY_CLASSES_ROOT = &H80000000

HKEY_CURRENT_USER = &H80000001

HKEY_LOCAL_MACHINE = &H80000002

HKEY_USERS = &H80000003

HKEY_CURRENT_CONFIG = &H80000005

End Enum



Private Declare Function RegCloseKey Lib "advapi32.dll" _

(ByVal hKey As Long) As Long

Private Declare Function RegCreateKey Lib "advapi32.dll" Alias _

"RegCreateKeyA" (ByVal hKey As Long, ByVal lpSubKey As String, _

phkResult As Long) As Long



Private Declare Function RegDeleteValue Lib "advapi32.dll" Alias _

"RegDeleteValueA" (ByVal hKey As Long, _

ByVal lpValueName As String) As Long

Private Declare Function RegOpenKey Lib "advapi32.dll" Alias _

"RegOpenKeyA" (ByVal hKey As Long, ByVal lpSubKey As String, _

phkResult As Long) As Long



Private Declare Function RegQueryValueEx Lib "advapi32.dll" Alias _

"RegQueryValueExA" (ByVal hKey As Long, _

ByVal lpValueName As String, ByVal lpReserved As Long, _

lpType As Long, lpData As Any, lpcbData As Long) As Long



Private Declare Function RegSetValueEx Lib "advapi32.dll" Alias _

"RegSetValueExA" (ByVal hKey As Long, ByVal lpValueName As String, _

ByVal Reserved As Long, ByVal dwType As Long, lpData
As Any, _

ByVal cbData As Long) As Long



Function RegQueryStringValue(ByVal hKey As
Key_Reg, _

ByVal strValueName As String) As String

Dim lResult, lValueType, lDataBufSize As Long

Dim strBuf As String



'retrieve nformation about the key

lResult = RegQueryValueEx(hKey, strValueName, 0, _

lValueType, ByVal 0, lDataBufSize)

If lResult = 0 Then

If lValueType = REG_SZ Then

'Create a buffer

strBuf = String(lDataBufSize, Chr$(0))

'retrieve the key's content

lResult = RegQueryValueEx(hKey, strValueName, _

0, 0, ByVal strBuf, lDataBufSize)



If lResult = 0 Then

'Remove the unnecessary chr$(0)'s

RegQueryStringValue = Left$(strBuf, _

InStr(1, strBuf, Chr$(0)) - 1)

End If



ElseIf lValueType = REG_BINARY Then

Dim strData As Integer

'retrieve the key's value

lResult = RegQueryValueEx(hKey, strValueName, _

0, 0, strData, lDataBufSize)



If lResult = 0 Then

RegQueryStringValue = strData

End If



End If

End If

End Function




Function GetString(hKey As
Key_Reg, strPath As String, _

strValue As String)

Dim Ret

'Open the key

RegOpenKey hKey, strPath, Ret

'Get the key's content

GetString = RegQueryStringValue(Ret, strValue)

'Close the key

RegCloseKey Ret

End Function



Sub SaveString(hKey As
Key_Reg, strPath As String, _

strValue As String, strData As String)

Dim Ret

'Create a new key

RegCreateKey hKey, strPath, Ret

'Save a string to the key

RegSetValueEx Ret, strValue, 0, REG_SZ, _

ByVal strData, Len(strData)

'close the key

RegCloseKey Ret

End Sub



Sub SaveStringLong(hKey As
Key_Reg, strPath As String, _

strValue As String, strData As String)

Dim Ret

'Create a new key

RegCreateKey hKey, strPath, Ret

'Set the key's value

RegSetValueEx Ret, strValue, 0, REG_SZ, _

CByte(strData), 4

'close the key

RegCloseKey Ret

End Sub



Sub DelSetting(hKey As Key_Reg, strPath As String, _

strValue As String)

Dim Ret

'Create a new key

RegCreateKey hKey, strPath, Ret

'Delete the key's value

RegDeleteValue Ret, strValue

'close the key

RegCloseKey Ret

End Sub



Private Sub Command1_Click()

'Save the value to the registry

SaveStringLong HKEY_CURRENT_USER, "RockessAlpha", "StringValue", _

CByte("123")

End Sub



Private Sub Command2_Click()

'Get a string from the registry

Ret = GetString(HKEY_CURRENT_USER, "RockessAlpha", "StringValue")

If Ret = "" Then MsgBox "No value found !", _

vbExclamation + vbOKOnly, "RockessAlpha.blogspot.com":
Exit Sub

MsgBox "The value is  " + Ret, _

vbOKOnly + vbInformation, "RockessAlpha.blogspot.com"

End Sub



Private Sub Command3_Click()

'Delete the setting from the registry

DelSetting HKEY_CURRENT_USER, "RockessAlpha", "StringValue"

MsgBox "The value was deleted ...", _

vbInformation + vbOKOnly, "RockessAlpha.blogspot.com"

End Sub



Private Sub Form_Load()

Command1.Caption = "Set Value"

Command2.Caption = "Get Value"

Command3.Caption = "Delete Value"

End Sub



 

Rectangle Any Color

'Rectangle Any Color


Const RDW_INVALIDATE = &H1

Const BS_HATCHED = 2

Const HS_CROSS = 4



Private Type LOGBRUSH

    lbStyle As Long

    lbColor As Long

    lbHatch As Long

End Type



Private Type RECT

    Left As Long

    Top As Long

    Right As Long

    Bottom As Long

End Type



Private Declare Function CreateBrushIndirect Lib "gdi32" _

(lpLogBrush As LOGBRUSH) As Long

Private Declare Function CreateRectRgn Lib "gdi32" _

(ByVal X1 As Long, ByVal Y1 As Long, ByVal X2 As Long, _

ByVal Y2 As Long) As Long



Private Declare Function IsWindow Lib "user32" _

(ByVal hwnd As Long) As Long

Private Declare Function SetRectEmpty Lib "user32" _

(lpRect As RECT) As Long



Private Declare Function SetRect Lib "user32" _

(lpRect As RECT, ByVal X1 As Long, ByVal Y1 As Long, _

ByVal X2 As Long, ByVal Y2 As Long) As Long

Private Declare Function IsRectEmpty Lib "user32" _

(lpRect As RECT) As Long



Private Declare Function IntersectRect Lib "user32" _

(lpDestRect As RECT, lpSrc1Rect
As RECT, lpSrc2Rect As
RECT) As Long

Private Declare Function RedrawWindow Lib "user32" _

(ByVal hwnd As Long, lprcUpdate
As Any, ByVal hrgnUpdate As Long, _

ByVal fuRedraw As Long) As Long



Private Declare Function GetRgnBox Lib "gdi32" _

(ByVal hRgn As Long, lpRect
As RECT) As Long

Private Declare Function DeleteObject Lib "gdi32" _

(ByVal hObject As Long) As Long



Private Declare Function FillRect Lib "user32" _

(ByVal hdc As Long, lpRect
As RECT, ByVal hBrush As Long) As Long



Private Sub Form_Load()

Me.Caption = "Click for Change Color"

'Check if this window is a window

If IsWindow(Me.hwnd) = 0 Then

MsgBox "Hmm.. I hope you altered the code," _

& "or else your system is meeting with difficulties!", _

vbInformation

End If

'API uses pixels

Me.ScaleMode = vbPixels

End Sub



Private Sub Form_MouseDown(Button As Integer, Shift As Integer, _

X As Single, Y As Single)

'Redraw this window (invoke a Paint-event)

RedrawWindow Me.hwnd, ByVal 0&, ByVal 0&, RDW_INVALIDATE

End Sub



Private Sub Form_Paint()

Dim LB As LOGBRUSH, R
As RECT, Rgn As Long, RgnRect
As RECT, _

hBrush As Long



'randomize

Randomize Timer

LB.lbColor = RGB(Int(Rnd * 256), Int(Rnd * 256), Int(Rnd * 256))

LB.lbStyle = BS_HATCHED

LB.lbHatch = HS_CROSS



'Create a new brush

hBrush = CreateBrushIndirect(LB)

'Set the rectangle's values

SetRect R, 0, 0, 200, 200

'Create a rectangle region

Rgn = CreateRectRgn(100, 50, 300, 10)

'Get the region box

GetRgnBox Rgn, RgnRect

'calculate the intersection of two rectangles

IntersectRect R, RgnRect, R

'Empty the rectangle

SetRectEmpty RgnRect

'Fill our rectangle

FillRect Me.hdc, R, hBrush

'delete our brush

DeleteObject hBrush

'Check if the rectangle is empty

If IsRectEmpty(RgnRect) <> 0 Then SetRectEmpty RgnRect



End Sub



 

Play WAV

'Play WAV



Private Const SND_APPLICATION = &H80

Private Const SND_ALIAS = &H10000

Private Const SND_ALIAS_ID = &H110000

Private Const SND_ASYNC = &H1

Private Const SND_FILENAME = &H20000

Private Const SND_LOOP = &H8

Private Const SND_MEMORY = &H4

Private Const SND_NODEFAULT = &H2

Private Const SND_NOSTOP = &H10

Private Const SND_NOWAIT = &H2000

Private Const SND_PURGE = &H40

Private Const SND_RESOURCE = &H40004

Private Const SND_SYNC = &H0



Private Declare Function PlaySound
Lib "winmm.dll"
Alias _

"PlaySoundA" (ByVal lpszName
As String, ByVal hModule As Long, _

ByVal dwFlags As Long) As Long



Private Sub Form_Load()

PlaySound "C:\WINDOWS\MEDIA\TADA.WAV", ByVal 0&, _

SND_FILENAME Or SND_ASYNC

End Sub



 

Pattern Brush

'Pattern Brush

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


Private Declare Function CreatePatternBrush Lib "gdi32" _
(ByVal hBitmap
As Long) As Long

Private Declare Function FillRect Lib "user32" _
(ByVal hdc
As Long, lpRect As RECT, ByVal hBrush
As Long) As Long

Private Declare Function SetRect Lib "user32" _
(lpRect
As RECT,
ByVal X1 As Long,
ByVal Y1 As Long, _

ByVal X2 As Long,
ByVal Y2 As Long)
As Long
Private Declare Function
DeleteObject Lib "gdi32" _
(ByVal hObject
As Long) As Long

Private Declare Function CreateBitmap Lib "gdi32" _
(ByVal nWidth
As Long, ByVal nHeight
As Long, _
ByVal nPlanes
As Long, ByVal nBitCount
As Long, lpBits As Integer) As Long


Dim bBytes(1 To 8)
As Integer

Private Sub Form_Paint()

Dim R As RECT, mBrush
As Long, hBitmap As Long


For mBrush = 1 To 8
Step 2
bBytes(mBrush) = 170    
'170 = 10101010
bBytes(mBrush + 1) = 85
'85 = 01010101
Next


'Create a memory bitmap
hBitmap = CreateBitmap(8, 8, 1, 1, bBytes(1))

'Create the pattern brush
mBrush = CreatePatternBrush(hBitmap)
SetRect R, 0, 0, Me.ScaleWidth, Me.ScaleHeight

'Fill the form
FillRect Me.hdc, R, mBrush

'Clean up
DeleteObject mBrush
DeleteObject hBitmap

End Sub
 

Mouse Capture

'Mouse Capture



Private Type POINTAPI

X As Long

Y As Long

End Type



Private Declare Function SetCapture
Lib "user32" _

(ByVal hwnd As Long) As Long

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

Private Declare Function GetCursorPos
Lib "user32" _

(lpPoint As POINTAPI) As Long



Dim Pt As POINTAPI



Private Sub Form_Load()

'redirect all mouse input to this form

   
SetCapture Me.hwnd

End Sub



Private Sub Form_MouseDown(Button As Integer, _

Shift As Integer, X As Single, Y As Single)

ReleaseCapture

SetCapture Me.hwnd

End Sub



Private Sub Form_MouseMove(Button As Integer, _

Shift As Integer, X As Single, Y As Single)

'Get the current cursor position

GetCursorPos Pt

Me.CurrentX = 0

Me.CurrentY = 0

'Clear the screen

Me.Cls

Me.Print "Cursor position:"

'Print the mouse coördinates to the form

Me.Print "X:" + Str$(Pt.X) + " Y:" + Str$(Pt.Y)

Me.Print " (Press ALT-F4 to EXIT)"

SetCapture Me.hwnd

End Sub



Private Sub Form_MouseUp(Button As Integer, _

Shift As Integer, X As Single, Y As Single)

ReleaseCapture

SetCapture Me.hwnd

End Sub









 

Load BITMAP

'Load BITMAP



Const LR_LOADFROMFILE = &H10

Const IMAGE_BITMAP = 0

Const IMAGE_ICON = 1

Const IMAGE_CURSOR = 2

Const IMAGE_ENHMETAFILE = 3

Const CF_BITMAP = 2



Private Declare Function LoadImage Lib "user32"
Alias "LoadImageA" _

(ByVal hInst As Long, ByVal lpsz
As String, _

ByVal dwImageType As Long, ByVal dwDesiredWidth As Long, _

ByVal dwDesiredHeight As Long, ByVal dwFlags As Long) As Long



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

Private Declare Function OpenClipboard Lib "user32" _

(ByVal hwnd As Long) As Long



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

Private Declare Function SetClipboardData Lib "user32" _

(ByVal wFormat As Long, ByVal hMem As Long) As Long



Private Declare Function IsClipboardFormatAvailable Lib "user32" _

(ByVal wFormat As Long) As Long



Private Sub Form_Load()

Dim hDC As Long, hBitmap As Long

'Load the bitmap into the memory

hBitmap = LoadImage(App.hInstance, "C:\WINDOWS\Web\Wallpaper\bliss.bmp", _

IMAGE_BITMAP, 320, 200, LR_LOADFROMFILE)

If hBitmap = 0 Then

MsgBox "There was an error while loading the bitmap"

Exit Sub

End If




'open the clipboard

OpenClipboard Me.hwnd

'Clear the clipboard

EmptyClipboard

'Put our bitmap onto the clipboard

SetClipboardData CF_BITMAP, hBitmap

'Check if there's a bitmap on the clipboard



If IsClipboardFormatAvailable(CF_BITMAP) = 0 Then

MsgBox "Error, no BITMAP!!!"

End If



'Close the clipboard

CloseClipboard

'Get the picture from the clipboard

Me.Picture = Clipboard.GetData(vbCFBitmap)

End Sub



 

HTML Help

'HTML Help



Const HH_DISPLAY_TOPIC = &H0

Const HH_SET_WIN_TYPE = &H4

Const HH_GET_WIN_TYPE = &H5

Const HH_GET_WIN_HANDLE = &H6

Const HH_DISPLAY_TEXT_POPUP = &HE

Const HH_HELP_CONTEXT = &HF

Const HH_TP_HELP_CONTEXTMENU = &H10

Const HH_TP_HELP_WM_HELP = &H11

Const HH_CLOSE_ALL = &H12



Private Declare Function HtmlHelp
Lib "hhctrl.ocx"
Alias _

"HtmlHelpA" (ByVal hwndCaller As Long,
ByVal pszFile As String, _

ByVal uCommand As Long,
ByVal dwData As Long) As Long



Private Sub Form_Load()

Dim hwndHelp As Long

'Please placed readme.chm in 1 folder

hwndHelp = HtmlHelp(hWnd, "readme.chm", HH_DISPLAY_TOPIC, 0)

End Sub



Private Sub Form_Unload(Cancel As Integer)

HtmlHelp Me.hWnd, "", HH_CLOSE_ALL, 0

End Sub



 

Get Version Windows

'Get Version Windows



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 Sub Form_Load()

Dim OSInfo As OSVERSIONINFO, PId
As String

'Set the graphical mode to persistent

Me.AutoRedraw = True

'Set the structure size

OSInfo.dwOSVersionInfoSize = Len(OSInfo)

'Get the Windows version

Ret& = GetVersionEx(OSInfo)

'Check for errors

If Ret& = 0 Then MsgBox "Error Getting Version Information":
Exit Sub

'Print the information to the form



Select Case OSInfo.dwPlatformId

Case 0

PId = "Windows 32s "

Case 1

PId = "Windows 95/98"

Case 2

PId = "Windows NT"

End Select



Print "OS: " + PId

Print "Win version:" + Str$(OSInfo.dwMajorVersion) + "." + _

LTrim(Str(OSInfo.dwMinorVersion))

Print "Build: " + Str(OSInfo.dwBuildNumber)

End Sub



 

Get Tick Count

'Get TickCount



Private Declare Function GetTickCount&
Lib "kernel32" ()



Private Sub Form_Load()

ret& = GetTickCount&

MsgBox Str$(ret& / 60000) + " minutes."

End Sub



 

Get System Time

'Get System Time



Private Declare Sub GetSystemTime
Lib "kernel32" _

(lpSystemTime As SYSTEMTIME)



Private Type SYSTEMTIME

    wYear As Integer

    wMonth As Integer

    wDayOfWeek As Integer

    wDay As Integer

    wHour As Integer

    wMinute As Integer

    wSecond As Integer

    wMilliseconds As Integer

End Type



Private Sub Form_Load()

Dim SysTime As SYSTEMTIME

'Set the graphical mode to persistent

Me.AutoRedraw = True

'Get the system time

GetSystemTime SysTime

'Print it to the form

Me.Print "The Local Date is:" & SysTime.wMonth & "-" & _

SysTime.wDay & "-" & SysTime.wYear

Me.Print "The Local Time is:" & SysTime.wHour & ":" & _

SysTime.wMinute & ":" & SysTime.wSecond

End Sub

Get System Information

'GET System Information



Private Type SYSTEM_INFO

   
dwOemID As Long

   
dwPageSize As Long

   
lpMinimumApplicationAddress As Long

   
lpMaximumApplicationAddress As Long

   
dwActiveProcessorMask As Long

   
dwNumberOrfProcessors As Long

   
dwProcessorType As Long

   
dwAllocationGranularity As Long

   
dwReserved As Long

End Type



Private Declare Sub GetSystemInfo
Lib "kernel32" _

(lpSystemInfo As SYSTEM_INFO)



Private Sub Form_Load()

Dim SInfo As SYSTEM_INFO

'Set the graphical mode to persistent

Me.AutoRedraw = True

'Get the system information

GetSystemInfo SInfo

'Print it to the form

Me.Print "Number of procesor:" + Str$(SInfo.dwNumberOrfProcessors)

Me.Print "Processor:" + Str$(SInfo.dwProcessorType)

Me.Print "Low memory address:" + Str$(SInfo.lpMinimumApplicationAddress)

Me.Print "High memory address:" + Str$(SInfo.lpMaximumApplicationAddress)

End Sub



 

Get Special Folder

'Get Special Folder


Enum FOLDER

CSIDL_DESKTOP = &H0

CSIDL_ALLPROGRAMS = &H2

CSIDL_CONTROLS = &H3

CSIDL_PRINTERS = &H4

CSIDL_DOCUMENT = &H5

CSIDL_FAVORITES = &H6

CSIDL_STARTUP = &H7

CSIDL_RECENT = &H8

CSIDL_SENDTO = &H9

CSIDL_BITBUCKET = &HA

CSIDL_STARTMENU = &HB

CSIDL_MUSIC = &HD

CSIDL_VIDEO = &HE

CSIDL_DESKTOPDIRECTORY = &H10

CSIDL_DRIVES = &H11

CSIDL_NETWORK = &H12

CSIDL_NETHOOD = &H13

CSIDL_FONTS = &H14

CSIDL_TEMPLATES = &H15

CSIDL_ALLUSERSTARTMENU = &H16

CSIDL_ALLUSERALLPROGRAMS=&H17

CSIDL_ALLUSERSTARTUP=&H18

CSIDL_ALLUSERDESKTOP=&H19

CSIDL_ APPDATA=&H1A

CSIDL_PRINTHOOD=&H1B

CSIDL_LOCALSETTAPPDATA=&H1C

CSIDL_TEMP_INTERNET=&H20

CSIDL_COOKIES=&H21

CSIDL_HISTORY=&H22

CSIDL_ALLUSERAPPDATA=&H23

CSIDL_WINDOWS = &H24

CSIDL_SYSTEM = &H25

CSIDL_PROGRAMFILES=&H26

CSIDL_PICTURE=&H27

CSIDL_USER=&H28

CSIDL_COMMON=&H2B

CSIDL_ALLUSERTEMPLATE=&H2D

CSIDL_ALLUSERDOCUMENT=&H2E

CSIDL_ALLUSERADMTOOLS=&H2F

CSIDL_ADMTOOLS=&H30

CSIDL_ALLUSERMUSIC=&H35

CSIDL_ALLUSERPICTURE=&H36

CSIDL_ALLUSERVIDEO=&H37

CSIDL_RESOURCES=&H38

CSIDL_CDBURNING=&H3A

End Enum



Private Type SHITEMID

cb As Long

abID As Byte

End Type



Private Type ITEMIDLIST

myID As SHITEMID

End Type



Private Declare Function SHGetSpecialFolderLocation
Lib "shell32.dll" _

(ByVal hwndOwner As Long, ByVal nFolder As Long, pidl
As ITEMIDLIST) As Long

Private Declare Function SHGetPathFromIDList
Lib "shell32.dll"
Alias _

"SHGetPathFromIDListA" (ByVal pidl As Long, ByVal pszPath
As String) As Long



Private Sub Form_Load()



'Set the graphical mode to persistent

Me.AutoRedraw = True

'Print the folders to the form

Me.Print "Start Up folder : " + GetSpecialfolder(CSIDL_STARTUP)

Me.Print "Application Data  folder: " + GetSpecialfolder(CSIDL_ APPDATA)

Me.Print "Windows folder : " + GetSpecialfolder(CSIDL_WINDOWS)

Me.Print "Desktop folder : " + GetSpecialfolder(CSIDL_DESKTOP)

End Sub



Private Function GetSpecialfolder(CSIDL
As FOLDER) As String

Dim r As Long

Dim IDL As ITEMIDLIST

'Get the special folder

r = SHGetSpecialFolderLocation(100, CSIDL, IDL)

If r = NOERROR Then

'Create a buffer

Path$ = Space$(512)

'Get the path from the IDList

r = SHGetPathFromIDList(ByVal IDL.myID.cb, ByVal Path$)

'Remove the unnecessary chr$(0)'s

GetSpecialfolder = Left$(Path, InStr(Path, Chr$(0)) - 1)

Exit Function

End If

GetSpecialfolder = ""

End Function

 

Get Power Status

'Get Power Status



Private Type SYSTEM_POWER_STATUS

   
ACLineStatus As Byte

   
BatteryFlag As Byte

   
BatteryLifePercent As Byte

   
Reserved1 As Byte

   
BatteryLifeTime As Long

   
BatteryFullLifeTime As Long

End Type



Private Declare Function GetSystemPowerStatus
Lib "kernel32" _

(lpSystemPowerStatus As SYSTEM_POWER_STATUS) As Long



Private Sub Form_Paint()

Dim SPS As SYSTEM_POWER_STATUS

'get the battery power status

GetSystemPowerStatus SPS

Me.AutoRedraw = True


'show some information


Select Case SPS.ACLineStatus

Case 0

Me.Print "AC power status: Off Line"

Case 1

Me.Print "AC power status: On Line"

Case 2

Me.Print "AC power status: Unknown"

End Select


Select Case SPS.BatteryFlag

Case 1

Me.Print "Battery charge status: High"

Case 2

Me.Print "Battery charge status: Low"

Case 4

Me.Print "Battery charge status: Critical"

Case 8

Me.Print "Battery charge status: Charging"

Case 128

Me.Print "Battery charge status: No System Battery"

Case 255

Me.Print "Battery charge status: Unknown Status"

End Select

End Sub



 

Get Number Format

'Get Number Format



Private Type NUMBERFMT

   
NumDigits As Long         
'number of decimal digits

   
LeadingZero As Long      
'if leading zero in decimal fields

   
Grouping As Long            'group size left of decimal

   
lpDecimalSep As String   
'ptr to decimal separator string

   
lpThousandSep As String  'ptr to thousand separator string

   
NegativeOrder As Long    'negative number ordering

End Type



Private Declare Function GetNumberFormat
Lib "kernel32" Alias _

"GetNumberFormatA" (ByVal Locale As Long, ByVal dwFlags As Long, _

ByVal lpValue As String, lpFormat
As NUMBERFMT, _

ByVal lpNumberStr As String, ByVal cchNumber As Long) As Long



Private Sub Form_Load()

Dim Buffer As String, NF
As NUMBERFMT

Buffer = String(255, 0)


NF.NumDigits = 1

NF.Grouping = 2

NF.lpDecimalSep = "."

NF.lpThousandSep = ""

NF.NegativeOrder = 0



GetNumberFormat ByVal 0&, 0, "300243.24", NF, Buffer, Len(Buffer)

MsgBox Buffer

End Sub



 

Get Local Time

'Get Local Time



Private Declare Sub GetLocalTime
Lib "kernel32" _

(lpSystemTime As SYSTEMTIME)



Private Type SYSTEMTIME

    wYear As Integer

    wMonth As Integer

    wDayOfWeek As Integer

    wDay As Integer

    wHour As Integer

    wMinute As Integer

    wSecond As Integer

    wMilliseconds As Integer

End Type



Private Sub Form_Load()

Dim MyTime As SYSTEMTIME

'Set the graphical mode to persistent

Me.AutoRedraw = True

'Get the local time

GetLocalTime MyTime

'Print it to the form

Me.Print "The Local Date is:" & MyTime.wMonth & "-" & _

MyTime.wDay & "-" & MyTime.wYear

Me.Print "The Local Time is:" & MyTime.wHour & ":" & _

MyTime.wMinute & ":" & MyTime.wSecond

End Sub



 

Get IP Address

'Get IP Address

'need 1 module And 1 form




'in form

Private Sub Form_Load()

MsgBox "IP-address: " + GetIPAddress, vbOKOnly, "RockessAlpha.blogspot.com"

End Sub



'In module

Public Const MIN_SOCKETS_REQD As Long = 1

Public Const WS_VERSION_REQD As Long = &H101

Public Const WS_VERSION_MAJOR As Long = WS_VERSION_REQD \ _

&H100 And &HFF&

Public Const WS_VERSION_MINOR As Long = WS_VERSION_REQD And _

&HFF&



Public Const SOCKET_ERROR As Long = -1

Public Const WSADESCRIPTION_LEN = 257

Public Const WSASYS_STATUS_LEN = 129

Public Const MAX_WSADescription = 256

Public Const MAX_WSASYSStatus = 128



Public Type WSAData

   
wVersion As Integer

   
wHighVersion As Integer

   
szDescription(0 To MAX_WSADescription) As Byte

   
szSystemStatus(0 To MAX_WSASYSStatus) As Byte

   
wMaxSockets As Integer

   
wMaxUDPDG As Integer

   
dwVendorInfo As Long

End Type



Type WSADataInfo

   
wVersion As Integer

   
wHighVersion As Integer

   
szDescription As String * WSADESCRIPTION_LEN

   
szSystemStatus As String * WSASYS_STATUS_LEN

   
iMaxSockets As Integer

   
iMaxUdpDg As Integer

   
lpVendorInfo As String

End Type



Public Type HOSTENT

   
hName As Long

   
hAliases As Long

   
hAddrType As Integer

   
hLen As Integer

   
hAddrList As Long

End Type



Declare Function WSAStartupInfo Lib "WSOCK32" Alias "WSAStartup" _

(ByVal wVersionRequested As Integer, lpWSADATA
As WSADataInfo) _

As Long

Declare Function WSACleanup Lib "WSOCK32" () As Long

Declare Function WSAGetLastError Lib "WSOCK32" () As Long

Declare Function WSAStartup Lib "WSOCK32" _

(ByVal wVersionRequired As Long, lpWSADATA
As WSAData) As Long

Declare Function GetHostName Lib "WSOCK32" _

(ByVal szHost As String, ByVal dwHostLen As Long) As Long

Declare Function GetHostbyName Lib "WSOCK32" _

(ByVal szHost As String) As Long

Declare Sub CopyMemoryIP Lib "kernel32" Alias "RtlMoveMemory" _

(hpvDest As Any, ByVal hpvSource As Long, ByVal cbCopy As Long)



Public Function GetIPAddress() As String

Dim sHostName As String * 256

Dim lpHost As Long

Dim HOST As HOSTENT

Dim dwIPAddr As Long

Dim tmpIPAddr() As Byte

Dim I As Integer

Dim sIPAddr As String



If Not SocketsInitialize() Then

GetIPAddress = ""

Exit Function

End If



If gethostname(sHostName, 256) = SOCKET_ERROR Then

GetIPAddress = ""

MsgBox "Windows Sockets error " & Str$(WSAGetLastError()) & _

" has occurred. Unable To successfully get Host Name."

SocketsCleanup

Exit Function

End If



sHostName = Trim$(sHostName)

lpHost = gethostbyname(sHostName)



If lpHost = 0 Then

GetIPAddress = ""

MsgBox "Windows Sockets are not responding. " & "Unable To successfully get Host
Name."

SocketsCleanup

Exit Function

End If



CopyMemoryIP HOST, lpHost, Len(HOST)

CopyMemoryIP dwIPAddr, HOST.hAddrList, 4

ReDim tmpIPAddr(1 To HOST.hLen)

CopyMemoryIP tmpIPAddr(1), dwIPAddr, HOST.hLen



For I = 1 To HOST.hLen

sIPAddr = sIPAddr & tmpIPAddr(I) & "."

Next



GetIPAddress = Mid$(sIPAddr, 1, Len(sIPAddr) - 1)

SocketsCleanup

End Function



Public Function GetIPHostName() As String

Dim sHostName As String * 256



If Not SocketsInitialize() Then

GetIPHostName = ""

Exit Function

End If



If gethostname(sHostName, 256) = SOCKET_ERROR Then

GetIPHostName = ""

MsgBox "Windows Sockets error " & Str$(WSAGetLastError()) _

& " has occurred. Unable To successfully get Host Name."

SocketsCleanup

Exit Function

End If



GetIPHostName = Left$(sHostName, InStr(sHostName, Chr(0)) - 1)

SocketsCleanup

End Function



Public Function HiByte(ByVal wParam As Integer)

HiByte = wParam \ &H100 And &HFF&

End Function



Public Function LoByte(ByVal wParam As Integer)

LoByte = wParam And &HFF&

End Function



Public Sub SocketsCleanup()

If WSACleanup() <> ERROR_SUCCESS Then

MsgBox "Socket error occurred in Cleanup."

End If

End Sub



Public Function SocketsInitialize()
As Boolean

Dim WSAD As WSAData

Dim sLoByte As String

Dim sHiByte As String



If WSAStartup(WS_VERSION_REQD, WSAD) <> ERROR_SUCCESS Then

MsgBox "The 32-bit Windows Socket is not responding."

SocketsInitialize = False

Exit Function

End If



If WSAD.wMaxSockets < MIN_SOCKETS_REQD Then

MsgBox "This application requires a minimum of " & _

CStr(MIN_SOCKETS_REQD) & " supported sockets."

SocketsInitialize = False

Exit Function

End If



If LoByte(WSAD.wVersion) < WS_VERSION_MAJOR Or _

(LoByte(WSAD.wVersion) = WS_VERSION_MAJOR And _

HiByte(WSAD.wVersion) < WS_VERSION_MINOR) Then

sHiByte = CStr(HiByte(WSAD.wVersion))

sLoByte = CStr(LoByte(WSAD.wVersion))

MsgBox "Sockets version " & sLoByte & "." & sHiByte & _

" is not supported by 32-bit Windows Sockets."

SocketsInitialize = False

Exit Function

End If



'must be OK, so lets do it

SocketsInitialize = True

End Function