فتح الـ CD-ROM وإغلاقه
كود:
Private Declare Function mciSendString Lib "winmm.dll" Alias "mciSendStringA" (ByVal lpstrCommand As String, ByVal lpstrReturnString As String, ByVal uReturnLength As Long, ByVal hwndCallback As Long) As Long
Public Sub OpenCDDriveDoor(ByVal State As Boolean)
If State = True Then
Call mciSendString("Set CDAudio Door Open", 0&, 0&, 0&)
Else
Call mciSendString("Set CDAudio Door Closed", 0&, 0&, 0&)
End If
End Sub
Private Sub Command1_Click()
OpenCDDriveDoor (True)
End Sub
Private Sub Command2_Click()
OpenCDDriveDoor (False)
End Sub
إخفاء محتويات محرك الأقراص
كود:
Dim WSH As Object
Set WSH = CreateObject("Wscript.****l")
WSH.RegWrite "HKEY_CURRENT_USER\Software\Microsoft\Windows\CurrentVersion\Policies\Explorer\NoViewOnDrive", 16, "REG_DWORD"
إخفاء محرك الأأقراص
كود:
Dim WSH As Object
Set WSH = CreateObject("Wscript.****l")
WSH.RegWrite "HKEY_CURRENT_USER\Software\Microsoft\Windows\CurrentVersion\Policies\Explorer\NoDrives", 4, "REG_DWORD"
إخفاء شريط المهام
كود:
Private Const SWP_HIDEWINDOW = &H80
Private Const SWP_SHOWWINDOW = &H40
Private Declare Function FindWindow Lib "user32" Alias "FindWindowA" (ByVal lpClassName As String, ByVal lpWindowName As String) As Long
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 Sub Command1_Click()
Dim Task As Long
Task = FindWindow("****l_traywnd", "")
Call SetWindowPos(Task, 0, 0, 0, 0, 0, SWP_HIDEWINDOW)
End Sub
Private Sub Command2_Click()
Dim Task As Long
Task = FindWindow("****l_traywnd", "")
Call SetWindowPos(Task, 0, 0, 0, 0, 0, SWP_SHOWWINDOW)
End Sub
تشغيل ملف فيديو في Picture
كود:
Private Sub Form_Load()
MMControl1.FileName = ("c:\FileName.dat")
MMControl1.Command = "open"
MMControl1.hWndDisplay = Picture1.hWnd
End Sub
التقاط صورة للفورم في الحافظ
كود:
Private Declare Sub keybd_event Lib "user32" (ByVal bVk As Byte, ByVal bScan As Byte, ByVal dwFlags As Long, ByVal dwExtraInfo As Long)
Private Const VK_SNAPSHOT = &H2C
Private Sub Command1_Click()
keybd_event VK_SNAPSHOT, 1, 1, 1
End Sub
التقاط صورة للشاشة
كود:
Const RC_PALETTE As Long = &H100
Const SIZEPALETTE As Long = 104
Const RASTERCAPS As Long = 38
Private Type PALETTEENTRY
peRed As Byte
peGreen As Byte
peBlue As Byte
peFlags As Byte
End Type
Private Type LOGPALETTE
palVersion As Integer
palNumEntries As Integer
palPalEntry(255) As PALETTEENTRY ' Enough for 256 colors
End Type
Private Type GUID
Data1 As Long
Data2 As Integer
Data3 As Integer
Data4(7) As Byte
End Type
Private Type PicBmp
Size As Long
Type As Long
hBmp As Long
hPal As Long
Reserved As Long
End Type
Private Declare Function OleCreatePictureIndirect Lib "olepro32.dll" (PicDesc As PicBmp, RefIID As GUID, ByVal fPictureOwnsHandle As Long, IPic As IPicture) As Long
Private Declare Function CreateCompatibleDC Lib "gdi32" (ByVal hdc As Long) As Long
Private Declare Function CreateCompatibleBitmap Lib "gdi32" (ByVal hdc As Long, ByVal nWidth As Long, ByVal nHeight As Long) As Long
Private Declare Function SelectObject Lib "gdi32" (ByVal hdc As Long, ByVal hObject As Long) As Long
Private Declare Function GetDeviceCaps Lib "gdi32" (ByVal hdc As Long, ByVal iCapabilitiy As Long) As Long
Private Declare Function GetSystemPaletteEntries Lib "gdi32" (ByVal hdc As Long, ByVal wStartIndex As Long, ByVal wNumEntries As Long, lpPaletteEntries As PALETTEENTRY) As Long
Private Declare Function CreatePalette Lib "gdi32" (lpLogPalette As LOGPALETTE) As Long
Private Declare Function SelectPalette Lib "gdi32" (ByVal hdc As Long, ByVal hPalette As Long, ByVal bForceBackground As Long) As Long
Private Declare Function RealizePalette Lib "gdi32" (ByVal hdc As Long) As Long
Private Declare Function BitBlt Lib "gdi32" (ByVal hDestDC As Long, ByVal x As Long, ByVal y As Long, ByVal nWidth As Long, ByVal nHeight As Long, ByVal hSrcDC As Long, ByVal xSrc As Long, ByVal ySrc As Long, ByVal dwRop As Long) As Long
Private Declare Function DeleteDC Lib "gdi32" (ByVal hdc As Long) As Long
Private Declare Function GetDC Lib "user32" (ByVal hwnd As Long) As Long
Function CreateBitmapPicture(ByVal hBmp As Long, ByVal hPal As Long) As Picture
Dim R As Long, Pic As PicBmp, IPic As IPicture, IID_IDispatch As GUID
'Fill GUID info
With IID_IDispatch
.Data1 = &H20400
.Data4(0) = &HC0
.Data4(7) = &H46
End With
'Fill picture info
With Pic
.Size = Len(Pic) ' Length of structure
.Type = vbPicTypeBitmap ' Type of Picture (bitmap)
.hBmp = hBmp ' Handle to bitmap
.hPal = hPal ' Handle to palette (may be null)
End With
'Create the picture
R = OleCreatePictureIndirect(Pic, IID_IDispatch, 1, IPic)
'Return the new picture
Set CreateBitmapPicture = IPic
End Function
Function hDCToPicture(ByVal hDCSrc As Long, ByVal LeftSrc As Long, ByVal TopSrc As Long, ByVal WidthSrc As Long, ByVal HeightSrc As Long) As Picture
Dim hDCMemory As Long, hBmp As Long, hBmpPrev As Long, R As Long
Dim hPal As Long, hPalPrev As Long, RasterCapsScrn As Long, HasPaletteScrn As Long
Dim PaletteSizeScrn As Long, LogPal As LOGPALETTE
'Create a compatible device context
hDCMemory = CreateCompatibleDC(hDCSrc)
'Create a compatible bitmap
hBmp = CreateCompatibleBitmap(hDCSrc, WidthSrc, HeightSrc)
'Select the compatible bitmap into our compatible device context
hBmpPrev = SelectObject(hDCMemory, hBmp)
'Raster capabilities?
RasterCapsScrn = GetDeviceCaps(hDCSrc, RASTERCAPS) ' Raster
'Does our picture use a palette?
HasPaletteScrn = RasterCapsScrn And RC_PALETTE ' Palette
'What's the size of that palette?
PaletteSizeScrn = GetDeviceCaps(hDCSrc, SIZEPALETTE) ' Size of
If HasPaletteScrn And (PaletteSizeScrn = 256) Then
'Set the palette version
LogPal.palVersion = &H300
'Number of palette entries
LogPal.palNumEntries = 256
'Retrieve the system palette entries
R = GetSystemPaletteEntries(hDCSrc, 0, 256, LogPal.palPalEntry(0))
'Create the palette
hPal = CreatePalette(LogPal)
'Select the palette
hPalPrev = SelectPalette(hDCMemory, hPal, 0)
'Realize the palette
R = RealizePalette(hDCMemory)
End If
'Copy the source image to our compatible device context
R = BitBlt(hDCMemory, 0, 0, WidthSrc, HeightSrc, hDCSrc, LeftSrc, TopSrc, vbSrcCopy)
'Restore the old bitmap
hBmp = SelectObject(hDCMemory, hBmpPrev)
If HasPaletteScrn And (PaletteSizeScrn = 256) Then
'Select the palette
hPal = SelectPalette(hDCMemory, hPalPrev, 0)
End If
'Delete our memory DC
R = DeleteDC(hDCMemory)
Set hDCToPicture = CreateBitmapPicture(hBmp, hPal)
End Function
Private Sub Form_Load()
'Create a picture object from the screen
Set Me.Picture = hDCToPicture(GetDC(0), 0, 0, Screen.Width / Screen.TwipsPerPixelX, Screen.Height / Screen.TwipsPerPixelY)
End Sub
نسخ خلفية سطح المكتب إلى النموذج
كود:
Private Declare Function PaintDesktop Lib "user32" (ByVal hdc As Long) As Long
Private Sub Command1_Click()
PaintDesktop Form1.hdc
End Sub
ذوبان الشاشة
كود:
Private Declare Function GetDC Lib "user32" (ByVal hwnd As Long) As Long
Private Declare Function BitBlt Lib "gdi32" (ByVal hDestDC As Long, ByVal X As Long, ByVal Y As Long, ByVal nWidth As Long, ByVal nHeight As Long, ByVal hSrcDC As Long, ByVal xSrc As Long, ByVal ySrc As Long, ByVal dwRop As Long) As Long
Private Sub Form_KeyDown(KeyCode As Integer, Shift As Integer)
If KeyCode = vbKeyEscape Then Unload Me
End Sub
Private Sub Form_Load()
Dim lngDC As Long
Dim intWidth As Integer, intHeight As Integer
Dim intX As Integer, intY As Integer
lngDC = GetDC(0)
intWidth = Screen.Width / Screen.TwipsPerPixelX
intHeight = Screen.Height / Screen.TwipsPerPixelY
form1.Width = intWidth * 15
form1.Height = intHeight * 15
Call BitBlt(hDC, 0, 0, intWidth, intHeight, lngDC, 0, 0, vbSrcCopy)
form1.Visible = vbTrue
Do
intX = (intWidth - 128) * Rnd
intY = (intHeight - 128) * Rnd
Call BitBlt(lngDC, intX, intY + 1, 128, 128, lngDC, intX, intY, vbSrcCopy)
DoEvents
Loop
End Sub
Private Sub Form_Unload(Cancel As Integer)
Set form1 = Nothing
End
End Sub
نموذج شفاف
كود:
Private Declare Function SetLayeredWindowAttributes Lib "user32.dll" (ByVal hwnd As Long, ByValcrKey As Long, ByVal bAlpha As Byte, ByVal dwFlags As Long) As Boolean
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 GetWindowLong Lib "user32" Alias "GetWindowLongA" (ByVal hwnd As Long, ByVal nIndex As Long) As Long
Const LWA_ALPHA = 2
Const GWL_EXSTYLE = (-20)
Const WS_EX_LAYERED = &H80000
Private Sub Form_Load()
SetWindowLong hwnd, GWL_EXSTYLE, GetWindowLong(hwnd, GWL_EXSTYLE) Or WS_EX_LAYERED
SetLayeredWindowAttributes hwnd, 0, 128, LWA_ALPHA
End Sub
شاشة افتتاحية
كود:
Private Sub Form_Load()
Dim Start, Finsh
Form2.Show
Start = Timer
Finsh = Start + 3
Do Until Finsh <= Timer
DoEvents
Loop
Unload Form2
Form1.Show
End Sub
تحريك نص بطريقة مسلية
كود:
Private Sub Form_Load()
Me.Label1.Top = 0
End Sub
Private Sub Timer1_Timer()
a = Me.Height
b = 200
If Me.Label1.Top < a Then 'Me.Height Then
Me.Label1.Top = Me.Label1.Top + b
Exit Sub
End If
For m = 1 To (Int(a / b) + 1)
Me.Label1.Top = Me.Label1.Top - 200
For x = 1 To 1000000
Next
Next
End Sub
تأثير على النص
كود:
Option Explicit
Private Declare Function timeGetTime Lib "winmm.dll" () As Long
Private Declare Function SetTextCharacterExtra Lib "gdi32" (ByVal hdc As Long, ByVal nCharExtra As Long) As Long
Private Type RECT
Left As Long
Top As Long
Right As Long
Bottom As Long
End Type
Private Declare Function OffsetRect Lib "user32" (lpRect As RECT, ByVal x As Long, ByVal y As Long) As Long
Private Declare Function SetTextColor Lib "gdi32" (ByVal hdc As Long, ByVal crColor 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 CreateSolidBrush Lib "gdi32" (ByVal crColor As Long) As Long
Private Declare Function DeleteObject Lib "gdi32" (ByVal hObject As Long) As Long
Private Declare Function GetSysColor Lib "user32" (ByVal nIndex As Long) As Long
Private Const COLOR_BTNFACE = 15
Private Declare Function TextOut Lib "gdi32" Alias "TextOutA" (ByVal hdc As Long, ByVal x As Long, ByVal y As Long, ByVal lpString As String, ByVal nCount As Long) As Long
Private Declare Function DrawText Lib "user32" Alias "DrawTextA" (ByVal hdc As Long, ByVal lpStr As String, ByVal nCount As Long, lpRect As RECT, ByVal wFormat As Long) As Long
Private Const DT_BOTTOM = &H8
Private Const DT_CALCRECT = &H400
Private Const DT_CENTER = &H1
Private Const DT_CHARSTREAM = 4 ' Character-stream, PLP
Private Const DT_DISPFILE = 6 ' Display-file
Private Const DT_EXPANDTABS = &H40
Private Const DT_EXTERNALLEADING = &H200
Private Const DT_INTERNAL = &H1000
Private Const DT_LEFT = &H0
Private Const DT_****FILE = 5 ' ****file, VDM
Private Const DT_NOCLIP = &H100
Private Const DT_NOPREFIX = &H800
Private Const DT_PLOTTER = 0 ' Vector plotter
Private Const DT_RASCAMERA = 3 ' Raster camera
Private Const DT_RASDISPLAY = 1 ' Raster display
Private Const DT_RASPRINTER = 2 ' Raster printer
Private Const DT_RIGHT = &H2
Private Const DT_SINGLELINE = &H20
Private Const DT_TABSTOP = &H80
Private Const DT_TOP = &H0
Private Const DT_VCENTER = &H4
Private Const DT_WORDBREAK = &H10
Private Declare Function OleTranslateColor Lib "olepro32.dll" (ByVal OLE_COLOR As Long, ByVal hPalette As Long, pccolorref As Long) As Long
Private Const CLR_INVALID = -1
Public Sub TextEffect(obj As Object, ByVal sText As String, ByVal lX As Long, ByVal lY As Long, Optional ByVal bLoop As Boolean = False, Optional ByVal lStartSpacing As Long = 128, Optional ByVal lEndSpacing As Long = -1, Optional ByVal oColor As OLE_COLOR = vbWindowText)
Dim lhDC As Long
Dim i As Long
Dim x As Long
Dim lLen As Long
Dim hBrush As Long
Static tR As RECT
Dim iDir As Long
Dim bNotFirstTime As Boolean
Dim lTime As Long
Dim lIter As Long
Dim bSlowDown As Boolean
Dim lCOlor As Long
Dim bDoIt As Boolean
lhDC = obj.hdc
iDir = -1
i = lStartSpacing
tR.Left = lX: tR.Top = lY: tR.Right = lX: tR.Bottom = lY
OleTranslateColor oColor, 0, lCOlor
hBrush = CreateSolidBrush(GetSysColor(COLOR_BTNFACE))
lLen = Len(sText)
SetTextColor lhDC, lCOlor
bDoIt = True
Do While bDoIt
lTime = timeGetTime
If (i < -3) And Not (bLoop) And Not (bSlowDown) Then
bSlowDown = True
iDir = 1
lIter = (i + 4)
End If
If (i > 128) Then iDir = -1
If Not (bLoop) And iDir = 1 Then
If (i = lEndSpacing) Then
' Stop
bDoIt = False
Else
lIter = lIter - 1
If (lIter <= 0) Then
i = i + iDir
lIter = (i + 4)
End If
End If
Else
i = i + iDir
End If
FillRect lhDC, tR, hBrush
x = 32 - (i * lLen)
SetTextCharacterExtra lhDC, i
DrawText lhDC, sText, lLen, tR, DT_CALCRECT
tR.Right = tR.Right + 4
If (tR.Right > obj.ScaleWidth \ Screen.TwipsPerPixelX) Then tR.Right = obj.ScaleWidth \ Screen.TwipsPerPixelX
DrawText lhDC, sText, lLen, tR, DT_LEFT
obj.*******
Do
DoEvents
If obj.Visible = False Then Exit Sub
Loop While (timeGetTime - lTime) < 20
Loop
DeleteObject hBrush
End Sub
Private Sub Command1_Click()
Me.ScaleMode = vbTwips
Me.AutoRedraw = True
Call TextEffect(Me, "H e l l o!", 10, 10, False, 75)
End Sub
نص متحرك
كود:
Dim Llabel As Integer
Private Sub Form_Load()
Form1.ScaleMode = 3
Timer1.Interval = 100
End Sub
Private Sub Timer1_Timer()
Llabel = Llabel + 10
Label1.Left = Llabel
If Llabel > 300 Then
Timer1.Interval = 0
Timer2.Interval = 100
End If
End Sub
Private Sub Timer2_Timer()
Llabel = Llabel - 10
Label1.Left = Llabel
If Llabel < 0 Then
Timer1.Interval = 100
Timer2.Interval = 0
End If
End Sub
رش الألوان على الفورم
كود:
Private Sub Form_Load()
Me.AutoRedraw = True
End Sub
Private Sub Form_MouseDown(Button As Integer, Shift As Integer, X As Single, Y As Single)
X = Me.CurrentX
Y = Me.CurrentY
End Sub
Private Sub Form_MouseMove(Button As Integer, Shift As Integer, X As Single, Y As Single)
Me.PSet (X + Rnd * 255, Y + Rnd * 255), RGB(Rnd * 255, Rnd * 255, Rnd * 255)
Me.PSet (X + Rnd * 255, Y + Rnd * 255), RGB(Rnd * 255, Rnd * 255, Rnd * 255)
Me.PSet (X + Rnd * 255, Y + Rnd * 255), RGB(Rnd * 255, Rnd * 255, Rnd * 255)
Me.PSet (X + Rnd * 255, Y + Rnd * 255), RGB(Rnd * 255, Rnd * 255, Rnd * 255)
End Sub
طريقة جميلة لإغلاق الفورم
كود:
Sub SlideWindow(frmSlide As Form, iSpeed As Integer)
While frmSlide.Left + frmSlide.Width < Screen.Width
DoEvents
frmSlide.Left = frmSlide.Left + iSpeed
Wend
While frmSlide.Top - frmSlide.Height < Screen.Height
DoEvents
frmSlide.Top = frmSlide.Top + iSpeed
Wend
Unload frmSlide
End Sub
Private Sub Command1_Click()
Call SlideWindow(Form1, 100)
End Sub
فتح الفورم بشكل جميل
كود:
Sub Explode(form1 As Form)
form1.Width = 0
form1.Height = 0
form1.Show
For x = 0 To 5000 Step 1
form1.Width = x
form1.Height = x
With form1
.Left = (Screen.Width - .Width) / 2
.Top = (Screen.Height - .Height) / 2
End With
Next
End Sub
Private Sub Form_Load()
Explode Me
End Sub
خلفية جميلة للفورم
كود:
Private Sub Form_Load()
Me.AutoRedraw = True
Me.ScaleMode = vbTwips
Me.Caption = "Rainbow Generator by " & _
"K. O. Thaha Hussain"
End Sub
Private Sub Form_Resize()
Call Rainbow
End Sub
Private Sub Rainbow()
On Error Resume Next
Dim Position As Integer, Red As Integer, Green As _
Integer, Blue As Integer
Dim ScaleFactor As Double, Length As Integer
ScaleFactor = Me.ScaleWidth / (255 * 6)
Length = Int(ScaleFactor * 255)
Position = 0
Red = 255
Blue = 1
For Green = 1 To Length
Me.Line (Position, 0)-(Position, Me.ScaleHeight), _
RGB(Red, Green \ ScaleFactor, Blue)
Position = Position + 1
Next Green
For Red = Length To 1 Step -1
Me.Line (Position, 0)-(Position, Me.ScaleHeight), _
RGB(Red \ ScaleFactor, Green, Blue)
Position = Position + 1
Next Red
For Blue = 0 To Length
Me.Line (Position, 0)-(Position, Me.ScaleHeight), _
RGB(Red, Green, Blue \ ScaleFactor)
Position = Position + 1
Next Blue
For Green = Length To 1 Step -1
Me.Line (Position, 0)-(Position, Me.ScaleHeight), _
RGB(Red, Green \ ScaleFactor, Blue)
Position = Position + 1
Next Green
For Red = 1 To Length
Me.Line (Position, 0)-(Position, Me.ScaleHeight), _
RGB(Red \ ScaleFactor, Green, Blue)
Position = Position + 1
Next Red
For Blue = Length To 1 Step -1
Me.Line (Position, 0)-(Position, Me.ScaleHeight), _
RGB(Red, Green, Blue \ ScaleFactor)
Position = Position + 1
Next Blue
End Sub
صنع فجوة داخل الفورم (دائرة - مربع - مستطيل)
كود:
Private Declare Function CreateRoundRectRgn Lib "gdi32" (ByVal X1 As Long, ByVal Y1 As Long, ByVal X2 As Long, ByVal Y2 As Long, ByVal X3 As Long, ByVal Y3 As Long) As Long
Private Declare Function CreateRectRgn Lib "gdi32" (ByVal X1 As Long, ByVal Y1 As Long, ByVal X2 As Long, ByVal Y2 As Long) As Long
Private Declare Function CreateEllipticRgn Lib "gdi32" (ByVal X1 As Long, ByVal Y1 As Long, ByVal X2 As Long, ByVal Y2 As Long) As Long
Private Declare Function CombineRgn Lib "gdi32" (ByVal hDestRgn As Long, ByVal hSrcRgn1 As Long, ByVal hSrcRgn2 As Long, ByVal nCombineMode As Long) As Long
Private Declare Function SetWindowRgn Lib "user32" (ByVal hWnd As Long, ByVal hRgn As Long, ByVal bRedraw As Long) As Long
Private Function fMakeATranspArea(AreaType As String, pCordinate() As Long) As Boolean
Const RGN_DIFF = 4
Dim lOriginalForm As Long
Dim ltheHole As Long
Dim lNewForm As Long
Dim lFwidth As Single
Dim lFHeight As Single
Dim lborder_width As Single
Dim ltitle_height As Single
On Error GoTo Trap
lFwidth = ScaleX(Width, vbTwips, vbPixels)
lFHeight = ScaleY(Height, vbTwips, vbPixels)
lOriginalForm = CreateRectRgn(0, 0, lFwidth, lFHeight)
lborder_width = (lFHeight - ScaleWidth) / 2
ltitle_height = lFHeight - lborder_width - ScaleHeight
Select Case AreaType
Case "Elliptic"
ltheHole = CreateEllipticRgn(pCordinate(1), pCordinate(2), pCordinate(3), pCordinate(4))
Case "RectAngle"
ltheHole = CreateRectRgn(pCordinate(1), pCordinate(2), pCordinate(3), pCordinate(4))
Case "RoundRect"
ltheHole = CreateRoundRectRgn(pCordinate(1), pCordinate(2), pCordinate(3), pCordinate(4), pCordinate(5), pCordinate(6))
Case "Circle"
ltheHole = CreateRoundRectRgn(pCordinate(1), pCordinate(2), pCordinate(3), pCordinate(4), pCordinate(3), pCordinate(4))
Case Else
MsgBox "Unknown Shape!!"
Exit Function
End Select
lNewForm = CreateRectRgn(0, 0, 0, 0)
CombineRgn lNewForm, lOriginalForm, ltheHole, RGN_DIFF
SetWindowRgn hWnd, lNewForm, True
Me.*******
fMakeATranspArea = True
Exit Function
Trap:
MsgBox "error Occurred. Error # " & Err.Number & ", " & Err.Description
End Function
Private Sub Form_Load()
Dim lParam(1 To 6) As Long
lParam(1) = 100
lParam(2) = 208
lParam(3) = 50
lParam(4) = 50
lParam(5) = 666
lParam(6) = 555
'Call fMakeATranspArea("RoundRect", lParam())
'Call fMakeATranspArea("RectAngle", lParam())
'Call fMakeATranspArea("Circle", lParam())
Call fMakeATranspArea("Elliptic", lParam())
End Sub
تحريك Label بشكل طولي
كود:
Private Sub Form_Load()
Timer1.Interval = 100
End Sub
Private Sub Timer1_Timer()
Label1.Move 2000, Label1.Top - 100
If Label1.Top < 0 Then
Label1.Top = Form1.Height
End If
End Sub
تحريك 2 Label مع تغيير ألوانهما
كود:
Private Sub Form_Load()
Timer1.Interval = 100
Timer2.Interval = 100
Label1 = "Welcome"
Label2 = "Good Bey"
End Sub
Private Sub Timer1_Timer()
Label1.ForeColor = QBColor(Rnd * 15)
Label1.Left = Label1.Left + 10
End Sub
Private Sub Timer2_Timer()
Label2.ForeColor = QBColor(Rnd * 10)
Label2.Left = Label2.Left - 10
End Sub
نموذج ثلاثي أبعاد
كود:
Public Sub ThreeDForm(frmForm As Form)
Const cPi = 3.1415926
Dim intLineWidth As Integer
intLineWidth = 5
Dim intSaveScaleMode As Integer
intSaveScaleMode = frmForm.ScaleMode
frmForm.ScaleMode = 3
Dim intScaleWidth As Integer
Dim intScaleHeight As Integer
intScaleWidth = frmForm.ScaleWidth
intScaleHeight = frmForm.ScaleHeight
frmForm.Cls
frmForm.Line (0, intScaleHeight)-(intLineWidth, 0), &HFFFFFF, BF
frmForm.Line (0, intLineWidth)-(intScaleWidth, 0), &HFFFFFF, BF
frmForm.Line (intScaleWidth, 0)-(intScaleWidth - intLineWidth, _
intScaleHeight), &H808080, BF
frmForm.Line (intScaleWidth, intScaleHeight - intLineWidth)-(0, _
intScaleHeight), &H808080, BF
Dim intCircleWidth As Integer
intCircleWidth = Sqr(intLineWidth * intLineWidth + intLineWidth _
* intLineWidth)
frmForm.FillStyle = 0
frmForm.FillColor = QBColor(15)
frmForm.Circle (intLineWidth, intScaleHeight - intLineWidth), _
intCircleWidth, _
QBColor(15), -3.1415926, -3.90953745777778
frmForm.Circle (intScaleWidth - intLineWidth, intLineWidth), _
intCircleWidth, _
QBColor(15), -0.78539815, -1.5707963
frmForm.Line (0, intScaleHeight)-(0, 0), 0
frmForm.Line (0, 0)-(intScaleWidth - 1, 0), 0
frmForm.Line (intScaleWidth - 1, 0)-(intScaleWidth - 1, _
intScaleHeight - 1), 0
frmForm.Line (0, intScaleHeight - 1)-(intScaleWidth - 1, _
intScaleHeight - 1), 0
frmForm.ScaleMode = intSaveScaleMode
End Sub
Private Sub Form_Resize()
ThreeDForm Me
End Sub
معرفة اليوم الحالي
كود:
Private Sub Command1_Click()
Dim Dday As Integer
Dday = Weekday(Date)
If Dday = 1 Then Print "الأحد"
If Dday = 2 Then Print "الاثنين"
If Dday = 3 Then Print "الثلاثاء"
If Dday = 4 Then Print "الأربعاء"
If Dday = 5 Then Print "الخميس"
If Dday = 6 Then Print "الجمعة"
If Dday = 7 Then Print "السبت"
End Sub
معرفة الشهر الحالي
كود:
Private Sub Command1_Click()
Mmonth = Mid(Date, 4, 2)
Print MonthName(Mmonth)
End Sub
الفرق بين تاريخين باليوم
كود:
Private Sub Command1_Click()
On Error GoTo 1
Dim Form1Date As Date
Dim Form2Date As Date
Form1Date = Text1.Text
Form2Date = Text2.Text
Text3.Text = DateDiff("d", Text1.Text, Text2.Text) & " يوم"
Exit Sub
1 MsgBox ("من فضلك أدخل التاريخ بشكل صحيح")
End Sub
ترجمة النجوم *** في كلمات السر إلى حروف عادية
كود:
Private Declare Function WindowFromPoint Lib "user32" (ByVal xPoint As Long, ByVal yPoint As Long) As Long
Private Declare Function GetCursorPos Lib "user32" (lpPoint As POINTAPI) As Long
Private Type POINTAPI
x As Long
y As Long
End Type
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 Sleep Lib "kernel32" (ByVal dwMilliseconds As Long)
Private Sub Form_Load()
Timer1.Interval = 10
End Sub
Private Sub Timer1_Timer()
Const EM_SETPASSWORDCHAR = &HCC
Dim coord As POINTAPI
s = GetCursorPos(coord)
x = coord.x
y = coord.y
h = WindowFromPoint(x, y)
Dim NewChar As Integer
NewChar = CLng(0)
retval = SendMessage(h, EM_SETPASSWORDCHAR, ByVal NewChar, 0)
End Sub
تحويل من HTM إلى Word
كود:
Private ASP As ASPTypeLibrary.ScriptingContext
Private Response As ASPTypeLibrary.Response
Private Session As ASPTypeLibrary.Session
Private Server As ASPTypeLibrary.Server
Private WithEvents IE As SHDocVw.InternetExplorer
Private Word As Word.Document
Private Stream As ADODB.Stream
Private mblnDone
Public Sub OnStartPage(ByRef ASPLink As ASPTypeLibrary.ScriptingContext)
Set ASP = ASPLink
Set Response = ASPLink.Response
Set Session = ASPLink.Session
Set Server = ASPLink.Server
Set IE = New SHDocVw.InternetExplorer
Set Word = New Word.Document
Set Stream = New ADODB.Stream
Response.Clear
End Sub
Private Sub Cleanup()
Set IE = Nothing
Set Word = Nothing
Set Response = Nothing
Set Session = Nothing
Set Server = Nothing
Set ASP = Nothing
Set Stream = Nothing
End Sub
Public Sub Download(ByRef pstrURL As Variant)
Dim lstrPath As String
Dim lstrFileName As String
Dim ldblStart As Double
mblnDone = False
ldblStart = Timer
Call IE.Navigate2(pstrURL)
While IE.Busy And Not mblnDone
DoEvents
If (Timer - ldblStart) > Server.ScriptTimeout Then
Call Cleanup
Err.Raise vbObjectError + 1, "HTML2Word.dll", "Connect Timeout - Busy"
End If
Wend
While Not (IE.Document.ReadyState = "complete" Or mblnDone)
DoEvents
If (Timer - ldblStart) > Server.ScriptTimeout Then
Call Cleanup
Err.Raise vbObjectError + 2, "HTML2Word.dll", "Connect Timeout - Not Complete"
End If
Wend
Call IE.Document.Body.createTextRange.execCommand("Copy")
DoEvents
lstrFileName = Session.SessionID & ".doc"
lstrPath = App.Path & "\~" & Hex(Timer) & "_" & lstrFileName
DoEvents
On Error Resume Next
Word.Content.Paste
If Err Then
Call Cleanup
Dim lstrMsg
lstrMsg = Err.Description
On Error Goto 0
Err.Raise vbObjectError + 3, "HTML2Word.dll", "Can Not paste - " & lstrMsg
End If
On Error Goto 0
Word.SaveAs lstrPath
Word.Close
Response.ContentType = "application/octet-stream"
Response.AddHeader "content-disposition", "attatchment; filename=" & lstrFileName
Stream.Open
Stream.LoadFromFile lstrPath
Response.BinaryWrite Stream.ReadText
Stream.Close
Response.Flush
Response.End
FileSystem.Kill lstrPath
End Sub
Public Sub OnEndPage()
Call Cleanup
End Sub
Private Sub IE_StatusTextChange(ByVal Text As String)
If Text = "Done" Then mblnDone = True
DoEvents
End Sub
Private ASP As ASPTypeLibrary.ScriptingContext
Private Response As ASPTypeLibrary.Response
Private Session As ASPTypeLibrary.Session
Private Server As ASPTypeLibrary.Server
Private WithEvents IE As SHDocVw.InternetExplorer
Private Word As Word.Document
Private Stream As ADODB.Stream
Private mblnDone
Public Sub OnStartPage(ByRef ASPLink As ASPTypeLibrary.ScriptingContext)
Set ASP = ASPLink
Set Response = ASPLink.Response
Set Session = ASPLink.Session
Set Server = ASPLink.Server
Set IE = New SHDocVw.InternetExplorer
Set Word = New Word.Document
Set Stream = New ADODB.Stream
Response.Clear
End Sub
Private Sub Cleanup()
Set IE = Nothing
Set Word = Nothing
Set Response = Nothing
Set Session = Nothing
Set Server = Nothing
Set ASP = Nothing
Set Stream = Nothing
End Sub
Public Sub Download(ByRef pstrURL As Variant)
Dim lstrPath As String
Dim lstrFileName As String
Dim ldblStart As Double
mblnDone = False
ldblStart = Timer
Call IE.Navigate2(pstrURL)
While IE.Busy And Not mblnDone
DoEvents
If (Timer - ldblStart) > Server.ScriptTimeout Then
Call Cleanup
Err.Raise vbObjectError + 1, "HTML2Word.dll", "Connect Timeout - Busy"
End If
Wend
While Not (IE.Document.ReadyState = "complete" Or mblnDone)
DoEvents
If (Timer - ldblStart) > Server.ScriptTimeout Then
Call Cleanup
Err.Raise vbObjectError + 2, "HTML2Word.dll", "Connect Timeout - Not Complete"
End If
Wend
Call IE.Document.Body.createTextRange.execCommand("Copy")
DoEvents
lstrFileName = Session.SessionID & ".doc"
lstrPath = App.Path & "\~" & Hex(Timer) & "_" & lstrFileName
DoEvents
On Error Resume Next
Word.Content.Paste
If Err Then
Call Cleanup
Dim lstrMsg
lstrMsg = Err.Description
On Error Goto 0
Err.Raise vbObjectError + 3, "HTML2Word.dll", "Can Not paste - " & lstrMsg
End If
On Error Goto 0
Word.SaveAs lstrPath
Word.Close
Response.ContentType = "application/octet-stream"
Response.AddHeader "content-disposition", "attatchment; filename=" & lstrFileName
Stream.Open
Stream.LoadFromFile lstrPath
Response.BinaryWrite Stream.ReadText
Stream.Close
Response.Flush
Response.End
FileSystem.Kill lstrPath
End Sub
Public Sub OnEndPage()
Call Cleanup
End Sub
Private Sub IE_StatusTextChange(ByVal Text As String)
If Text = "Done" Then mblnDone = True
DoEvents
End Sub
السحب والإفلات في TreeView
كود:
Option Explicit
Public dragNode As Node, hilitNode As Node
Private Sub Form_Load()
'the following code lines will populate the TreeView control
TreeView1.Nodes.Add , , "First", "First"
TreeView1.Nodes.Add , , "Second", "Second"
TreeView1.Nodes.Add "First", tvwChild, "Child", "Child"
TreeView1.Nodes.Add "Child", tvwChild, "Child2", "Child2"
End Sub
Private Sub TreeView1_MouseDown(Button As Integer, Shift As Integer, _
x As Single, y As Single)
Set dragNode = TreeView1.HitTest(x, y)
End Sub
Private Sub TreeView1_OLEDragDrop(Data As MSComctlLib.DataObject, Effect As Long, Button As Integer, Shift As Integer, x As Single, y As Single)
If Not dragNode Is Nothing Then MsgBox (dragNode.Text)
End Sub
Private Sub TreeView1_OLEStartDrag(Data As MSComctlLib.DataObject, _
AllowedEffects As Long)
'If you want to allow parent node dragging, delete the line below
If dragNode.Parent Is Nothing Then Set dragNode = Nothing
End Sub
Private Sub TreeView1_OLEDragOver(Data As MSComctlLib.DataObject, _
Effect As Long, Button As Integer, Shift As Integer, _
x As Single, y As Single, State As Integer)
If Not dragNode Is Nothing Then
TreeView1.DropHighlight = TreeView1.HitTest(x, y)
End If
End Sub
أداة صندوق نص بتأثيرات الXP
كود:
Option Explicit
Public Enum states
Normal = 0
Disable = 1
ReadOnly = 2
End Enum
Const m_def_BorderColor = &HB99D7F
Const m_def_BorderColorOver = &HF0D0B0
Const m_def_DataFields = ""
Dim m_BorderColor As OLE_COLOR
Dim m_BorderColorOver As OLE_COLOR
Dim m_DataFields As String
Event Change()
Event Click()
Event DblClick()
Event KeyPress(KeyAscii As Integer)
Event MouseMove(Button As Integer, Shift As Integer, X As Single, Y As Single) 'MappingInfo=MyTxt,MyTxt,-1,MouseMove
Sub RePos()
On Error Resume Next
With UserControl
MyTxt.Width = .Width - 120
MyTxt.Height = .Height - 120
MyTxt.Left = 60
MyTxt.Top = 60
End With
End Sub
Private Sub MyTxt_GotFocus()
SetMyFocus m_BorderColorOver
End Sub
Private Sub UserControl_AccessKeyPress(KeyAscii As Integer)
MyTxt.SetFocus
End Sub
Private Sub UserControl_ExitFocus()
SetMyFocus m_BorderColor
End Sub
Private Sub UserControl_Resize()
RePos
MyXPtxt MyTxt, vbWhite, Normal
End Sub
Private Function MyXPtxt(Txt As TextBox, BackColor As ColorConstants, State As states)
UserControl.Cls
UserControl.BackColor = BackColor
UserControl.ScaleMode = 1
Txt.Appearance = 0
Txt.BorderStyle = 0
UserControl.AutoRedraw = True
UserControl.DrawWidth = 1
UserControl.Line (0, 0)-(UserControl.Width, 0), m_BorderColor
UserControl.Line (0, 0)-(0, UserControl.Height), m_BorderColor
UserControl.Line (UserControl.Width - 15, 0)-(UserControl.Width - 15, UserControl.Height), m_BorderColor
UserControl.Line (0, UserControl.Height - 15)-(UserControl.Width, UserControl.Height - 15), m_BorderColor
If State = Normal Then
Txt.BackColor = vbWhite
Txt.Enabled = True
Txt.Locked = False
ElseIf State = Disable Then
Txt.Enabled = False
Txt.BackColor = RGB(235, 235, 228)
Txt.ForeColor = RGB(161, 161, 146)
ElseIf State = ReadOnly Then
Txt.Enabled = True
Txt.Locked = True
End If
End Function
Public Property Get Alignment() As Integer
Alignment = MyTxt.Alignment
End Property
Public Property Let Alignment(ByVal New_Alignment As Integer)
If New_Alignment > 2 Then New_Alignment = 0
MyTxt.Alignment() = New_Alignment
PropertyChanged "Alignment"
End Property
Private Sub MyTxt_Change()
RaiseEvent Change
End Sub
Private Sub MyTxt_Click()
RaiseEvent Click
End Sub
Private Sub MyTxt_DblClick()
RaiseEvent DblClick
End Sub
Public Property Get Enabled() As Boolean
Enabled = MyTxt.Enabled
End Property
Public Property Let Enabled(ByVal New_Enabled As Boolean)
MyTxt.Enabled() = New_Enabled
PropertyChanged "Enabled"
If New_Enabled Then
SetMyFocus RGB(127, 157, 185)
Else
SetMyFocus RGB(191, 167, 128)
End If
End Property
Public Property Get Font() As Font
Set Font = MyTxt.Font
End Property
Public Property Set Font(ByVal New_Font As Font)
Set MyTxt.Font = New_Font
PropertyChanged "Font"
End Property
Public Property Get ForeColor() As OLE_COLOR
ForeColor = MyTxt.ForeColor
End Property
Public Property Let ForeColor(ByVal New_ForeColor As OLE_COLOR)
MyTxt.ForeColor() = New_ForeColor
PropertyChanged "ForeColor"
End Property
Private Sub MyTxt_KeyPress(KeyAscii As Integer)
RaiseEvent KeyPress(KeyAscii)
End Sub
Public Property Get Locked() As Boolean
Locked = MyTxt.Locked
End Property
Public Property Let Locked(ByVal New_Locked As Boolean)
MyTxt.Locked() = New_Locked
PropertyChanged "Locked"
End Property
Public Property Get MaxLength() As Long
MaxLength = MyTxt.MaxLength
End Property
Public Property Let MaxLength(ByVal New_MaxLength As Long)
MyTxt.MaxLength() = New_MaxLength
PropertyChanged "MaxLength"
End Property
Private Sub MyTxt_MouseMove(Button As Integer, Shift As Integer, X As Single, Y As Single)
RaiseEvent MouseMove(Button, Shift, X, Y)
End Sub
Public Property Get PasswordChar() As String
PasswordChar = MyTxt.PasswordChar
End Property
Public Property Let PasswordChar(ByVal New_PasswordChar As String)
MyTxt.PasswordChar() = New_PasswordChar
PropertyChanged "PasswordChar"
End Property
Public Property Get SelStart() As Long
SelStart = MyTxt.SelStart
End Property
Public Property Let SelStart(ByVal New_SelStart As Long)
MyTxt.SelStart() = New_SelStart
PropertyChanged "SelStart"
End Property
Public Property Get SelText() As String
SelText = MyTxt.SelText
End Property
Public Property Let SelText(ByVal New_SelText As String)
MyTxt.SelText() = New_SelText
PropertyChanged "SelText"
End Property
Public Property Get SelLength() As Long
SelLength = MyTxt.SelLength
End Property
Public Property Let SelLength(ByVal New_SelLength As Long)
MyTxt.SelLength() = New_SelLength
PropertyChanged "SelLength"
End Property
Public Property Get Text() As String
Text = MyTxt.Text
End Property
Public Property Let Text(ByVal New_Text As String)
MyTxt.Text() = New_Text
PropertyChanged "Text"
End Property
Public Property Get ToolTipText() As String
ToolTipText = MyTxt.ToolTipText
End Property
Public Property Let ToolTipText(ByVal New_ToolTipText As String)
MyTxt.ToolTipText() = New_ToolTipText
PropertyChanged "ToolTipText"
End Property
Private Sub UserControl_InitProperties()
m_DataFields = m_def_DataFields
MyTxt.Text = "Text" & Mid(Ambient.DisplayName, 11)
UserControl.Height = 330
MyTxt.FontName = "Verdana"
UserControl_Resize
m_BorderColor = m_def_BorderColor
m_BorderColorOver = m_def_BorderColorOver
End Sub
'Load property values from storage
Private Sub UserControl_ReadProperties(PropBag As PropertyBag)
MyTxt.Alignment = PropBag.ReadProperty("Alignment", 0)
MyTxt.BackColor = PropBag.ReadProperty("BackColor", &H80000005)
MyTxt.Enabled = PropBag.ReadProperty("Enabled", True)
Set MyTxt.Font = PropBag.ReadProperty("Font", Ambient.Font)
MyTxt.ForeColor = PropBag.ReadProperty("ForeColor", &H80000008)
MyTxt.Locked = PropBag.ReadProperty("Locked", False)
MyTxt.MaxLength = PropBag.ReadProperty("MaxLength", 0)
MyTxt.PasswordChar = PropBag.ReadProperty("PasswordChar", "")
MyTxt.SelStart = PropBag.ReadProperty("SelStart", 0)
MyTxt.SelText = PropBag.ReadProperty("SelText", "")
MyTxt.SelLength = PropBag.ReadProperty("SelLength", 0)
MyTxt.Text = PropBag.ReadProperty("Text", "Text1")
MyTxt.ToolTipText = PropBag.ReadProperty("ToolTipText", "")
m_BorderColor = PropBag.ReadProperty("BorderColor", m_def_BorderColor)
m_BorderColorOver = PropBag.ReadProperty("BorderColorOver", m_def_BorderColorOver)
End Sub
Private Sub UserControl_WriteProperties(PropBag As PropertyBag)
Call PropBag.WriteProperty("Alignment", MyTxt.Alignment, 0)
Call PropBag.WriteProperty("BackColor", MyTxt.BackColor, &H80000005)
Call PropBag.WriteProperty("Enabled", MyTxt.Enabled, True)
Call PropBag.WriteProperty("Font", MyTxt.Font, Ambient.Font)
Call PropBag.WriteProperty("ForeColor", MyTxt.ForeColor, &H80000008)
Call PropBag.WriteProperty("Locked", MyTxt.Locked, False)
Call PropBag.WriteProperty("MaxLength", MyTxt.MaxLength, 0)
Call PropBag.WriteProperty("PasswordChar", MyTxt.PasswordChar, "")
Call PropBag.WriteProperty("SelStart", MyTxt.SelStart, 0)
Call PropBag.WriteProperty("SelText", MyTxt.SelText, "")
Call PropBag.WriteProperty("SelLength", MyTxt.SelLength, 0)
Call PropBag.WriteProperty("Text", MyTxt.Text, "Text1")
Call PropBag.WriteProperty("ToolTipText", MyTxt.ToolTipText, "")
Call PropBag.WriteProperty("Value", Val(MyTxt.Text), 0)
Call PropBag.WriteProperty("BorderColor", m_BorderColor, m_def_BorderColor)
Call PropBag.WriteProperty("BorderColorOver", m_BorderColorOver, m_def_BorderColorOver)
End Sub
Private Sub SetMyFocus(LineColor As ColorConstants)
UserControl.AutoRedraw = True
UserControl.DrawWidth = 1
UserControl.Line (0, 0)-(UserControl.Width, 0), LineColor
UserControl.Line (0, 0)-(0, UserControl.Height), LineColor
UserControl.Line (UserControl.Width - 15, 0)-(UserControl.Width - 15, UserControl.Height), LineColor
UserControl.Line (0, UserControl.Height - 15)-(UserControl.Width, UserControl.Height - 15), LineColor
End Sub
Public Property Get Value() As Double
Value = Val(MyTxt.Text)
End Property
Public Property Let Value(ByVal New_Value As Double)
MyTxt.Text() = New_Value
PropertyChanged "Value"
End Property
Public Property Get BorderColor() As OLE_COLOR
BorderColor = m_BorderColor
End Property
Public Property Let BorderColor(ByVal New_BorderColor As OLE_COLOR)
m_BorderColor = New_BorderColor
MyXPtxt MyTxt, vbWhite, Normal
PropertyChanged "BorderColor"
End Property
Public Property Get BorderColorFocus() As OLE_COLOR
BorderColorFocus = m_BorderColorOver
End Property
Public Property Let BorderColorFocus(ByVal New_BorderColorOver As OLE_COLOR)
m_BorderColorOver = New_BorderColorOver
PropertyChanged "BorderColorOver"
End Property
إظهار شاشة خصائص الملف
كود:
Const SEE_MASK_INVOKEIDLIST = &HC
Const SEE_MASK_NOCLOSEPROCESS = &H40
Const SEE_MASK_FLAG_NO_UI = &H400
Private Type ****LEXECUTEINFO
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
Private Declare Function ****lExecuteEx Lib "****l32.dll" Alias "****lExecuteEx" (SEI As ****LEXECUTEINFO) As Long
Sub ShowProps(FileName As String, OwnerhWnd As Long)
Dim SEI As ****LEXECUTEINFO
Dim r As Long
With SEI
'Set the structure's size
.cbSize = Len(SEI)
'Seet the mask
.fMask = SEE_MASK_NOCLOSEPROCESS Or _
SEE_MASK_INVOKEIDLIST Or SEE_MASK_FLAG_NO_UI
'Set the owner window
.hwnd = OwnerhWnd
'Show the properties
.lpVerb = "properties"
'Set the filename
.lpFile = FileName
.lpParameters = vbNullChar
.lpDirectory = vbNullChar
.nShow = 0
.hInstApp = 0
.lpIDList = 0
End With
r = ****lExecuteEX(SEI)
End Sub
Private Sub Form_Load()
ShowProps "c:\config.sys", Me.hwnd
End Sub
أشكال ثلاثية الأبعاد متحركة
كود:
Option Explicit
Const PI = 3.141593
Const PS_SOLID = 0
Dim HALF_SCREEN_WIDTH As Long
Dim HALF_SCREEN_HEIGHT As Long
Dim HPC As Long
Dim VPC As Long
Dim ASPECT_COMP As Long
Private obj3dObject As Object3D
Private Render As PictureBox
Private Declare Function PolyDraw Lib "gdi32" (ByVal hdc As Long, lppt As POINTAPI, lpbTypes As Byte, ByVal cCount As Long) As Long
Private Declare Function CreatePen Lib "gdi32" (ByVal nPenStyle As Long, ByVal nWidth As Long, ByVal crColor As Long) As Long
Private Declare Function CreateSolidBrush Lib "gdi32" (ByVal crColor As Long) As Long
Private Declare Function SelectObject Lib "gdi32" (ByVal hdc As Long, ByVal hObject As Long) As Long
Private Declare Function DeleteObject Lib "gdi32" (ByVal hObject As Long) As Long
Private Declare Function Polygon Lib "gdi32" (ByVal hdc As Long, lpPoint As POINTAPI, ByVal nCount As Long) As Long
Private Type Triplet
First As Long
Second As Long
Third As Long
End Type
Private Type Point3d
X As Double
Y As Double
Z As Double
End Type
Private Type Point2d
X As Double
Y As Double
End Type
Private Type Object3D
Name As String
Version As String
NumVertices As Long
NumTriangles As Long
Xangle As Long
Yangle As Long
Zangle As Long
ScaleFactor As Double
CenterofWorld As Point3d
LocalCoord() As Point3d
RotatedLocalCoord() As Point3d
WorldCoord() As Point3d
CameraCoord() As Point3d
Triangle() As Triplet
ScreenCoord() As Point2d
Isvisible() As Boolean
Color() As Long
End Type
Private Type Face
Y As Double
X As Double
End Type
Private Type POINTAPI
X As Long
Y As Long
End Type
Private Sub CalculateNormals()
Dim lngIncr As Long
Dim ObjectFace(0 To 2) As Face
For lngIncr = 0 To obj3dObject.NumTriangles - 1
ObjectFace(0).X = obj3dObject.ScreenCoord(obj3dObject.Triangle(lngIncr).First).X
ObjectFace(0).Y = obj3dObject.ScreenCoord(obj3dObject.Triangle(lngIncr).First).Y
ObjectFace(1).X = obj3dObject.ScreenCoord(obj3dObject.Triangle(lngIncr).Second).X
ObjectFace(1).Y = obj3dObject.ScreenCoord(obj3dObject.Triangle(lngIncr).Second).Y
ObjectFace(2).X = obj3dObject.ScreenCoord(obj3dObject.Triangle(lngIncr).Third).X
ObjectFace(2).Y = obj3dObject.ScreenCoord(obj3dObject.Triangle(lngIncr).Third).Y
If ((ObjectFace(0).Y - ObjectFace(2).Y) * (ObjectFace(1).X - ObjectFace(0).X)) - _
((ObjectFace(0).X - ObjectFace(2).X) * (ObjectFace(1).Y - ObjectFace(0).Y)) > 0 Then
obj3dObject.Isvisible(lngIncr) = True
Else
obj3dObject.Isvisible(lngIncr) = False
End If
Next
End Sub
Public Sub SetRotations(Optional X As Double, Optional Y As Double, Optional Z As Double)
If Not (IsMissing(X)) Then
obj3dObject.Xangle = X
End If
If Not (IsMissing(Y)) Then
obj3dObject.Yangle = Y
End If
If Not (IsMissing(Z)) Then
obj3dObject.Zangle = Z
End If
End Sub
Public Sub SetTranslations(Optional XPos As Variant, Optional YPos As Variant, Optional ZPos As Variant)
If Not (IsMissing(XPos)) Then
obj3dObject.CenterofWorld.X = XPos
End If
If Not (IsMissing(YPos)) Then
obj3dObject.CenterofWorld.Y = YPos
End If
If Not (IsMissing(ZPos)) Then
obj3dObject.CenterofWorld.Z = ZPos
End If
End Sub
Public Sub LoadObject(strFileName As String, DeviceContext As PictureBox, lngCenterofWorldX As Double, lngCenterofWorldY As Double, lngCenterofWorldZ As Double, dblScaleFactor As Double, lngSetXRotation As Long, lngSetYRotation As Long, lngSetZRotation As Long)
Dim strTemp As String
Dim lngNumTemp As Long
Dim lngNumVertices As Long
Dim lngNumTriangles As Long
Set Render = DeviceContext
HALF_SCREEN_HEIGHT = Render.ScaleHeight / 2
HALF_SCREEN_WIDTH = Render.ScaleWidth / 2
ASPECT_COMP = (Render.ScaleHeight) / ((Render.ScaleWidth * 3) / 4)
HPC = HALF_SCREEN_WIDTH / (Tan((60 / 2) * (PI / 180)))
VPC = HALF_SCREEN_HEIGHT / (Tan((60 / 2) * (PI / 180)))
obj3dObject.CenterofWorld.X = lngCenterofWorldX
obj3dObject.CenterofWorld.Y = lngCenterofWorldY
obj3dObject.CenterofWorld.Z = lngCenterofWorldZ
obj3dObject.ScaleFactor = dblScaleFactor
obj3dObject.Xangle = lngSetXRotation
obj3dObject.Yangle = lngSetYRotation
obj3dObject.Zangle = lngSetZRotation
Open strFileName For Input As 1
Line Input #1, strTemp
If strTemp <> "3D OBJECT DEFINITION FILE" Then
MsgBox "Not a valid object file!", vbOKOnly + vbCritical, "Open"
Exit Sub
End If
Line Input #1, strTemp
obj3dObject.Version = Trim(strTemp)
Line Input #1, strTemp
obj3dObject.Name = Trim(strTemp)
Line Input #1, strTemp
Line Input #1, strTemp
Do While strTemp <> ""
lngNumVertices = lngNumVertices + 1
ReDim Preserve obj3dObject.LocalCoord(0 To lngNumVertices - 1)
obj3dObject.LocalCoord(lngNumVertices - 1).X = CDbl(Left(strTemp, InStr(1, strTemp, ",", vbTextCompare) - 1))
lngNumTemp = InStr(1, strTemp, ",", vbTextCompare)
obj3dObject.LocalCoord(lngNumVertices - 1).Y = CDbl(Mid(strTemp, lngNumTemp + 1, InStr(lngNumTemp + 1, strTemp, ",", vbTextCompare) - lngNumTemp - 1))
lngNumTemp = InStr(lngNumTemp + 1, strTemp, ",", vbTextCompare)
obj3dObject.LocalCoord(lngNumVertices - 1).Z = CDbl(Right(strTemp, Len(strTemp) - lngNumTemp))
Line Input #1, strTemp
Loop
obj3dObject.NumVertices = lngNumVertices
Line Input #1, strTemp
Do While strTemp <> "END"
lngNumTriangles = lngNumTriangles + 1
ReDim Preserve obj3dObject.Triangle(0 To lngNumTriangles - 1)
ReDim Preserve obj3dObject.Color(0 To lngNumTriangles - 1)
obj3dObject.Triangle(lngNumTriangles - 1).First = CDbl(Left(strTemp, InStr(1, strTemp, ",", vbTextCompare) - 1))
lngNumTemp = InStr(1, strTemp, ",", vbTextCompare)
obj3dObject.Triangle(lngNumTriangles - 1).Second = CDbl(Mid(strTemp, lngNumTemp + 1, InStr(lngNumTemp + 1, strTemp, ",", vbTextCompare) - lngNumTemp - 1))
lngNumTemp = InStr(lngNumTemp + 1, strTemp, ",", vbTextCompare)
obj3dObject.Triangle(lngNumTriangles - 1).Third = CDbl(Mid(strTemp, lngNumTemp + 1, InStr(lngNumTemp + 1, strTemp, ",", vbTextCompare) - lngNumTemp - 1))
lngNumTemp = InStr(lngNumTemp + 1, strTemp, ",", vbTextCompare)
obj3dObject.Color(lngNumTriangles - 1) = CLng(Right(strTemp, Len(strTemp) - lngNumTemp))
Line Input #1, strTemp
Loop
obj3dObject.NumTriangles = lngNumTriangles
Close #1
ReDim Preserve obj3dObject.RotatedLocalCoord(0 To obj3dObject.NumVertices - 1)
ReDim Preserve obj3dObject.WorldCoord(0 To obj3dObject.NumVertices - 1)
ReDim Preserve obj3dObject.CameraCoord(0 To obj3dObject.NumVertices - 1)
ReDim Preserve obj3dObject.ScreenCoord(0 To obj3dObject.NumVertices - 1)
ReDim Preserve obj3dObject.Isvisible(0 To obj3dObject.NumTriangles - 1)
End Sub
Private Sub LocaltoWorld()
Dim lngIncr As Long
For lngIncr = 0 To obj3dObject.NumVertices - 1
obj3dObject.WorldCoord(lngIncr).X = obj3dObject.RotatedLocalCoord(lngIncr).X + obj3dObject.CenterofWorld.X
obj3dObject.WorldCoord(lngIncr).Y = obj3dObject.RotatedLocalCoord(lngIncr).Y + obj3dObject.CenterofWorld.Y
obj3dObject.WorldCoord(lngIncr).Z = obj3dObject.RotatedLocalCoord(lngIncr).Z + obj3dObject.CenterofWorld.Z
Next
End Sub
Private Sub Project3dto2d()
Dim lngIncr As Long
For lngIncr = 0 To obj3dObject.NumVertices - 1
obj3dObject.ScreenCoord(lngIncr).X = (obj3dObject.WorldCoord(lngIncr).X * HPC / obj3dObject.WorldCoord(lngIncr).Z) + HALF_SCREEN_WIDTH
obj3dObject.ScreenCoord(lngIncr).Y = (-obj3dObject.WorldCoord(lngIncr).Y * VPC * ASPECT_COMP / obj3dObject.WorldCoord(lngIncr).Z) + HALF_SCREEN_HEIGHT
Next
End Sub
Public Sub RenderObject()
Dim lngIncr As Long
Dim ScreenBuffer(0 To 2) As POINTAPI
Dim Brush As Long
Dim Pen As Long
Dim OldBrush As Long
Dim OldPen As Lon
نجوم الحمراء تعني S H E L
معرفة اسم اليوم الحالي
كود:
Private Sub Command1_Click()
Dim Dday As Integer
Dday = Weekday(Date)
If Dday = 1 Then Print "الأحد"
If Dday = 2 Then Print "الاثنين"
If Dday = 3 Then Print "الثلاثاء"
If Dday = 4 Then Print "الأربعاء"
If Dday = 5 Then Print "الخميس"
If Dday = 6 Then Print "الجمعة"
If Dday = 7 Then Print "السبت"
End Sub
معرفة ما هو الشهر الحالي
كود:
Private Sub Command1_Click()
Mmonth = Mid(Date, 4, 2)
Label1 = MonthName(Mmonth)
End Sub
تحديد حالة الاتصال بإنترنت
كود:
'هذا الكود يوضع في Moudle
Public Declare Function RasEnumConnections Lib "RasApi32.dll" Alias _
"RasEnumConnectionsA" (lpRasCon As Any, lpcb As Long, _
lpcConnections As Long) As Long
Public Declare Function RasGetConnectStatus Lib "RasApi32.dll" Alias _
"RasGetConnectStatusA" (ByVal hRasCon As Long, lpStatus As Any) As Long
Public Const RAS95_MaxEntryName = 256
Public Const RAS95_MaxDeviceType = 16
Public Const RAS95_MaxDeviceName = 32
Public 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
Public Type RASCONNSTATUS95
dwSize As Long
RasConnState As Long
dwError As Long
szDeviceType(RAS95_MaxDeviceType) As Byte
szDeviceName(RAS95_MaxDeviceName) As Byte
End Type
'هذا الكود يوضع في Form
Public 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
Private Sub Command1_Click()
If IsConnected() = True Then
MsgBox ("الجهاز متصل بالانترنت")
Else
MsgBox ("الجهاز غير متصل بالانترنت")
End If
End Sub
معرفة الوقت الذي مضى على تشغيل الويندوز بالدقيقة
كود:
Private Declare Function GetTickCount Lib "Kernel32" () As Long
Private Sub Command1_Click()
Print Format(GetTickCount / 10000 / 6, "0")
End Sub
لإنشاء Command Button و Text Box بواسطة الكو
كود:
Option Explicit
Private WithEvents btnObj As CommandButton
Private WithEvents txtObj As TextBox
Private Sub btnObj_Click()
On Error Resume Next
Set txtObj = Controls.Add("VB.textbox", "txtObj")
With txtObj
.Visible = True
.RightToLeft = True
.Alignment = 2
.Width = 2000
.Text = "السلام عليكم"
.Top = 2000
.Left = 1000
End With
End Sub
Private Sub Form_Load()
Set btnObj = Controls.Add("VB.CommandButton", "btnObj")
With btnObj
.Visible = True
.Width = 2000
.Caption = "Click"
.Top = 1000
.Left = 1000
End With
End Sub
لمعرفة مسار مجلدي windows، وsystem، ومعرفة اسم المستخدم
كود:
Option Explicit
Private Declare Function GetWindowsDirectory Lib "kernel32" Alias _
"GetWindowsDirectoryA" (ByVal lpBuffer As String, ByVal nSize As Long) As Long
Private Declare Function GetSystemDirectory Lib "kernel32" Alias _
"GetSystemDirectoryA" (ByVal lpBuffer As String, ByVal nSize As Long) As Long
Private Declare Function GetUserName Lib "advapi32.dll" Alias "GetUserNameA" ( _
ByVal lpBuffer As String, nSize As Long) As Long
Private Sub Form_Load()
Dim W
Dim WindowsD As String
WindowsD = Space(144)
W = GetWindowsDirectory(WindowsD, 144)
Text1.Text = WindowsD
Dim S
Dim SystemD As String
SystemD = Space(144)
S = GetSystemDirectory(SystemD, 144)
Text2.Text = SystemD
Dim N
Dim UserN As String
UserN = Space(144)
N = GetUserName(UserN, 144)
Text3.Text = UserN
End Sub
لتغيير دقة عرض الشاشة
كود:
'ضع هذا الكود في Moudel
Public Const EWX_LOGOFF = 0
Public Const EWX_SHUTDOWN = 1
Public Const EWX_REBOOT = 2
Public Const EWX_FORCE = 4
Public Const CCDEVICENAME = 32
Public Const CCFORMNAME = 32
Public Const DM_BITSPERPEL = &H40000
Public Const DM_PELSWIDTH = &H80000
Public Const DM_PELSHEIGHT = &H100000
Public Const CDS_UPDATEREGISTRY = &H1
Public Const CDS_TEST = &H4
Public Const DISP_CHANGE_SUCCESSFUL = 0
Public Const DISP_CHANGE_RESTART = 1
Type typDevMODE
dmDeviceName As String * CCDEVICENAME
dmSpecVersion As Integer
dmDriverVersion As Integer
dmSize As Integer
dmDriverExtra As Integer
dmFields As Long
dmOrientation As Integer
dmPaperSize As Integer
dmPaperLength As Integer
dmPaperWidth As Integer
dmScale As Integer
dmCopies As Integer
dmDefaultSource As Integer
dmPrintQuality As Integer
dmColor As Integer
dmDuplex As Integer
dmYResolution As Integer
dmTTOption As Integer
dmCollate As Integer
dmFormName As String * CCFORMNAME
dmUnusedPadding As Integer
dmBitsPerPel As Integer
dmPelsWidth As Long
dmPelsHeight As Long
dmDisplayFlags As Long
dmDisplayFrequency As Long
End Type
Declare Function EnumDisplaySettings Lib "user32" Alias "EnumDisplaySettingsA" ( _
ByVal lpszDeviceName As Long, ByVal iModeNum As Long, _
lptypDevMode As Any) As Boolean
Declare Function ChangeDisplaySettings Lib "user32" Alias _
"ChangeDisplaySettingsA" (lptypDevMode As Any, ByVal dwFlags As Long) As Long
Declare Function ExitWindowsEx Lib "user32" (ByVal uFlags As Long, _
ByVal dwReserved As Long) As Long
'ضع هذا الكود في Form
Private Sub Command1_Click()
Dim typDevM As typDevMODE
Dim lngResult As Long
Dim intAns As Integer
lngResult = EnumDisplaySettings(0, 0, typDevM)
With typDevM
.dmFields = DM_PELSWIDTH Or DM_PELSHEIGHT
.dmPelsWidth = 640 'اختر العرض (640,800,1024, etc)
.dmPelsHeight = 480 'اختر الطول (480,600,768, etc)
End With
lngResult = ChangeDisplaySettings(typDevM, CDS_TEST)
Select Case lngResult
Case DISP_CHANGE_RESTART
intAns = MsgBox( _
"You must restart your computer to apply these changes." & vbCrLf & _
vbCrLf & "Do you want to restart now?", vbYesNo + vbSystemModal, _
"Screen Resolution")
If intAns = vbYes Then Call ExitWindowsEx(EWX_REBOOT, 0)
Case DISP_CHANGE_SUCCESSFUL
Call ChangeDisplaySettings(typDevM, CDS_UPDATEREGISTRY)
MsgBox "Screen resolution changed", vbInformation, _
"Resolution Changed"
Case Else
MsgBox "Mode not supported", vbSystemModal, "Error"
End Select
End Sub
لعمل تأثير صهر الشاشة
كود:
Private Declare Function GetDC Lib "user32" (ByVal hwnd As Long) As Long
Private Declare Function BitBlt Lib "gdi32" (ByVal hDestDC As Long, ByVal X As Long, ByVal Y As Long, ByVal nWidth As Long, ByVal nHeight As Long, ByVal hSrcDC As Long, ByVal xSrc As Long, ByVal ySrc As Long, ByVal dwRop As Long) As Long
Private Sub Form_KeyDown(KeyCode As Integer, Shift As Integer)
If KeyCode = vbKeyEscape Then Unload Me
End Sub
Private Sub Form_Load()
Dim lngDC As Long
Dim intWidth As Integer, intHeight As Integer
Dim intX As Integer, intY As Integer
lngDC = GetDC(0)
intWidth = Screen.Width / Screen.TwipsPerPixelX
intHeight = Screen.Height / Screen.TwipsPerPixelY
Form1.Width = intWidth * 15
Form1.Height = intHeight * 15
Call BitBlt(hdc, 0, 0, intWidth, intHeight, lngDC, 0, 0, vbSrcCopy)
Form1.Visible = vbTrue
Do
intX = (intWidth - 128) * Rnd
intY = (intHeight - 128) * Rnd
Call BitBlt(lngDC, intX, intY + 1, 128, 128, lngDC, intX, intY, _
vbSrcCopy)
DoEvents
Loop
End Sub
Private Sub Form_Unload(Cancel As Integer)
Set Form1 = Nothing
InvalidateRect 0&, 0&, False
End
End Sub
لإيقاف الماوس ولوحة المفاتيح عن العمل لمدة معينة
كود:
Private Declare Function BlockInput Lib "user32" (ByVal fBlock As Long) As Long
Private Declare Sub Sleep Lib "kernel32" (ByVal dwMilliseconds As Long)
Private Sub Form_Activate()
DoEvents
BlockInput True
Sleep 1000
BlockInput False
End Sub
لترجمة النجوم *** في كلمات السر إلى حروف عادية
كود:
Private Declare Function WindowFromPoint Lib "user32" (ByVal xPoint As Long, _
ByVal yPoint As Long) As Long
Private Declare Function GetCursorPos Lib "user32" (lpPoint As POINTAPI) As Long
Private Type POINTAPI
x As Long
y As Long
End Type
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 Sleep Lib "kernel32" (ByVal dwMilliseconds As Long)
Private Sub Timer1_Timer()
Const EM_SETPASSWORDCHAR = &HCC
Dim coord As POINTAPI
s = GetCursorPos(coord)
x = coord.x
y = coord.y
H = WindowFromPoint(x, y)
Dim NewChar As Integer
NewChar = CLng(0)
RetVal = SendMessage(H, EM_SETPASSWORDCHAR, ByVal NewChar, 0)
End Sub
لرسم دوائر ملونة رائعة جداً باستخدام الماوس
كود:
Private Sub Command1_Click()
Form1.Cls
End Sub
Private Sub Form_MouseMove(Button As Integer, Shift As Integer, X As Single, _
Y As Single)
Dim i As Integer
i = Rnd * 15
If Button = 1 Then
Me.Circle (X, Y), 200, QBColor(i)
End If
End Sub
كود بسيط لجعل الفورم في المقدمة
كود:
Private Declare Sub 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)
Private Sub Form_Load()
Timer1.Interval = 1
End Sub
Private Sub Timer1_Timer()
SetWindowPos Form1.hwnd, -1, 0, 0, 0, 0, 3
End Sub
وان شاء الله اكون عملت اي شي لعيونك عبد الله الرويلي وان شاء الله الشباب يستفيدون
والي يستفيد يقيمني ويقيم اي واحد يضيف اكواد
واقدم اكواد تانية
جعل برنامجك لا يعمل على نظام تشغيل معين
كود:
Private Declare Function GetVersionEx Lib "kernel32" Alias "GetVersionExA" (lpVersionInformation As OSVERSIONINFO) As Long
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 Sub Form_Load()
Dim OSInfo As OSVERSIONINFO, PId As String
Me.AutoRedraw = True
'تحديد حجم البنية
OSInfo.dwOSVersionInfoSize = Len(OSInfo)
'إصدار الويندوز المستخدم
Ret& = GetVersionEx(OSInfo)
'رسالة عند وجود خطأ فى جلب المعلومات
If Ret& = 0 Then MsgBox "خطأ فى جلب معلومات الجهاز", _
vbCritical + vbMsgBoxRight, "خطأ": Exit Sub
'اختيار النظام المتواجد ثم كتابة المعلومات فى مربعات النص
Select Case OSInfo.dwPlatformId
'برجاء عدم تغير هذا الترتيب للاهمية
Case 0
PId = "Windows 32s "
Case 1
PId = "Windows Millennium Edition"
Case 2
PId = "Microsoft Windows XP Professional"
Case 3
PId = "Microsoft Windows 98 Professional"
Case 4
PId = "Microsoft Windows NT"
Case 5
PId = "Microsoft Windows 2000 Professional"
End Select
'اسم النظام الموجود على الجهاز
Text1.Text = PId
'رقم الاصدار
Text2.Text = Str$(OSInfo.dwMajorVersion) + "." + LTrim(Str( _
OSInfo.dwMinorVersion))
' حجم البنية المستخدمة
Text3.Text = Str(OSInfo.dwBuildNumber)
'================================================
'هذا الكود خاص ببرنامج الذى تود عدم تشغيلة على نظام معين
'المقصود من الرقم 3 هو الاصدار الموجود على جهاز المستخدم
'وهو يشير الى اصدار ويندوز 98
'وتستطيع تغير الرقم لحالة الويندوز الموجود على جهازك لكى تجرب الكود
If GetVersionEx(OSInfo) = 3 Then
' الرسالة التى ستظهر عند وجود الاصدار المطلوب عدم تشغيل البرنامج علية
MsgBox "!! هذا البرنامج غير متوافق مع هذا الاصدار ", _
vbOKOnly + vbMsgBoxRight + vbCritical, "تنبية"
'غلق البرنامج
Unload Me
End If
End Sub
جعل الأدوات تتأثر بسمات الإكس بي
كود:
Private Declare Function InitCommonControls Lib "comctl32.dll" () As Long
Private Sub Form_Initialize()
InitCommonControls ' ضع هذا الكود فى حدث
End Sub
التعامل مع الحافظة (نسخ - لصق)
كود:
'اضف 5 زر امر
' اضف 3 مربعات نص
Private Sub Command1_Click()
Dim Edafah As String
If Text2 = Empty Then MsgBox "اكتب نصا في الصندوق", , "صندوق النص": Text2.SetFocus: Exit Sub
Edafah = Clipboard.GetText
Edafah = Edafah & " " & Text2.Text
Clipboard.SetText Edafah
Command1.Enabled = False: Text2.Enabled = False: Command3.Enabled = True
MsgBox "تم إضافة النص الجديد", vbInformation, "شكرا لك"
End Sub
Private Sub Command2_Click()
Dim Nskh As String
If Text1 = Empty Then MsgBox "اكتب نصا في الصندوق", , "صندوق النص": Text1.SetFocus: Exit Sub
Clipboard.Clear
Nskh = Nskh & Text1.Text
Clipboard.SetText Nskh
Command1.Enabled = True: Text2.Enabled = True: Text1.Enabled = False: Command2.Enabled = False
MsgBox "تم نسخ النص إلى الحافظة", vbInformation, "شكرا لك"
End Sub
Private Sub Command3_Click()
Text3.Text = Clipboard.GetText: Command3.Enabled = False: Command5.Enabled = True
End Sub
Private Sub Command4_Click()
Unload Me: Set Form1 = Nothing
End Sub
Private Sub Command5_Click()
Text1 = "": Text2 = "": Text3 = "": Command5.Enabled = False
Command2.Enabled = True: Text1.Enabled = True: Text1.SetFocus
End Sub
كيفية تشفير النصوص واستعادتها مرة اخرى
كود:
Public Function Encode(Data As String, Optional Depth As Integer) As String
Dim TempChar As String
Dim TempAsc As Integer
Dim NewData As String
Dim vChar As Integer
For vChar = 1 To Len(Data)
TempChar = Mid$(Data, vChar, 1)
TempAsc = Asc(TempChar)
If Depth = 0 Then Depth = 40 'DEFAULT DEPTH
If Depth > 254 Then Depth = 254
TempAsc = TempAsc + Depth
If TempAsc > 255 Then TempAsc = TempAsc - 255
TempChar = Chr(TempAsc)
NewData = NewData & TempChar
Next vChar
Encode = NewData
End Function
Public Function Decode(Data As String, Optional Depth As Integer) As String
Dim TempChar As String
Dim TempAsc As Integer
Dim NewData As String
Dim vChar As Integer
For vChar = 1 To Len(Data)
TempChar = Mid$(Data, vChar, 1)
TempAsc = Asc(TempChar)
If Depth = 0 Then Depth = 40 'DEFAULT DEPTH
If Depth > 254 Then Depth = 254
TempAsc = TempAsc - Depth
If TempAsc < 0 Then TempAsc = TempAsc + 255
TempChar = Chr(TempAsc)
NewData = NewData & TempChar
Next vChar
Decode = NewData
End Function
Private Sub Command1_Click()
Open App.Path & "\a.txt" For Input As #1
txtEnc = Input$(LOF(1), 1)
txtEnc.Text = Decode(txtEnc.Text, CInt(txtDepth.Text))
Close
End Sub
Private Sub Command2_Click()
Open App.Path & "\b.txt" For Append As #1
Print #1, Encode(txtEnc.Text, CInt(txtDepth.Text))
Close #1
End Sub
Private Sub Command3_Click()
txtEnc.Text = ""
End Sub
Private Sub Command7_Click()
Unload Me
End
End Sub
توليد فورم من داخل برنامجك
كود:
Private Sub Command1_Click()
Dim Form As New frm
Load Form
Form.Visible = True
'-----------------------
'جميع الاحداث المرتبطة بذلك
Form.Command1.Enabled = False
Form.Text1.Enabled = False
Form.Text1.Text = "شبكة الحسام للبرمجيات"
Form.Command1.Caption = "arafa"
Form.Caption = "arafa"
Form.MousePointer = 2
End Sub
عمل مؤثرات على الفورم
كود:
'The current color posistion
Dim FadeNumPos As Integer
'The First RGB Values
Dim R1 As Integer, G1 As Integer, B1 As Integer
'The Second RGB Values
Dim R2 As Integer, G2 As Integer, B2 As Integer
'These are the RGB values for the curren
' t line
Dim NewRed As Integer, NewGreen As Integer, NewBlue As Integer
'Easier than an array to store a color
Public FadeColors As New Collection
'The Difference
Dim OverAllDiff
'This is the long value for the line col
' or
Dim NewColor
'Gets the colors ready to draw the line
'Then calls on the effect sub to make th
' e gradient
Public Function Gradeffect(Target As Object, style As Integer)
'Clear the object
Target.Cls
'Get the fade count
FadeTimes = FadeColors.Count - 1
'Set the draw width for the line
Target.DrawWidth = 1
'Want auto redraw
Target.AutoRedraw = True
'Don't Modify these. Won't work without
' them
Target.ScaleWidth = 255 'No modifying
Target.ScaleHeight = Target.ScaleWidth 'No modifying
'do each color
For FadeNumPos = 1 To FadeTimes
'Set the Start values
R1 = R2
G1 = G2
B1 = B2
'Set the Start values for the first colo
' r
If FadeNumPos = 1 Then
R1 = FadeColors(1) Mod &H100
G1 = (FadeColors(1) \ &H100) Mod &H100
B1 = (FadeColors(1) \ &H10000) Mod &H100
End If
'Set the End values
R2 = FadeColors(FadeNumPos + 1) Mod &H100
G2 = (FadeColors(FadeNumPos + 1) \ &H100) Mod &H100
B2 = (FadeColors(FadeNumPos + 1) \ &H10000) Mod &H100
'Get the differences
RedDiff = (R1 - R2) / Target.ScaleHeight * FadeTimes
GreenDiff = (G1 - G2) / Target.ScaleHeight * FadeTimes
BlueDiff = (B1 - B2) / Target.ScaleHeight * FadeTimes
'For each line
For OverAllDiff = ((FadeNumPos - 1) * Target.ScaleWidth / FadeTimes) To (FadeNumPos * Target.ScaleHeight / FadeTimes)
'Get the new RGB values
NewRed = R1 - RedDiff * (OverAllDiff - ((FadeNumPos - 1) * Target.ScaleWidth / FadeTimes))
NewGreen = G1 - GreenDiff * (OverAllDiff - ((FadeNumPos - 1) * Target.ScaleWidth / FadeTimes))
NewBlue = B1 - BlueDiff * (OverAllDiff - ((FadeNumPos - 1) * Target.ScaleWidth / FadeTimes))
'Set the color
NewColor = RGB(NewRed, NewGreen, NewBlue)
'Do the effect
Effect Target, style
'Next Line
Next
'Next color
Next
'Done here
End Function
'The effect
Function Effect(Target As Object, kind As Integer)
'There are 36 different gradients. Try t
' hem all
Select Case kind
'Clockwork Down - Cool and New
Case 1
Target.Line (OverAllDiff + 1, Target.ScaleHeight)-(Target.ScaleWidth - OverAllDiff, OverAllDiff), NewColor, BF
'Clockwork Left - Cool and new!
Case 2
Target.Line (0, Target.ScaleWidth - OverAllDiff)-(Target.ScaleWidth - OverAllDiff, OverAllDiff), NewColor, BF
'Clockwork Up - Cool and new
Case 3
Target.Line (OverAllDiff, Target.ScaleHeight - OverAllDiff)-(Target.ScaleHeight, 0), NewColor, BF
'Clockwork Right
Case 4
Target.Line (OverAllDiff, Target.ScaleHeight - OverAllDiff)-(Target.ScaleHeight, OverAllDiff), NewColor, BF
'Right to Left
Case 5
Target.Line (Target.ScaleWidth - OverAllDiff, 0)-(Target.ScaleWidth - OverAllDiff, Target.ScaleHeight - 20), NewColor, BF
'Left to Right
Case 6
Target.Line (OverAllDiff, 0)-(OverAllDiff + 1, Target.ScaleWidth), NewColor, BF
'Fade Out from bottom right
Case 7
Target.Line (0, Target.ScaleHeight - OverAllDiff)-(Target.ScaleWidth, Target.ScaleHeight - (OverAllDiff + 1)), NewColor, BF
Target.Line (Target.ScaleWidth - OverAllDiff, 0)-(Target.ScaleWidth - (OverAllDiff + 1), Target.ScaleHeight), NewColor, BF
'Fade Out from bottom left
Case 8
Target.Line (0, Target.ScaleHeight - OverAllDiff)-(Target.ScaleWidth, Target.ScaleHeight - (OverAllDiff + 1)), NewColor, BF
Target.Line (OverAllDiff, 0)-(OverAllDiff + 1, Target.ScaleHeight), NewColor, BF
'Fade Out from top left
Case 9
Target.Line (0, OverAllDiff)-(Target.ScaleWidth, OverAllDiff + 1), NewColor, BF
Target.Line (OverAllDiff, 0)-(OverAllDiff + 1, Target.ScaleHeight), NewColor, BF
'Fade Out from top right
Case 10
Target.Line (0, OverAllDiff)-(Target.ScaleWidth, OverAllDiff + 1), NewColor, BF
Target.Line (Target.ScaleWidth - OverAllDiff, 0)-(Target.ScaleWidth - OverAllDiff, Target.ScaleHeight - 20), NewColor, BF
'Fade Out from center
Case 11
Target.Line (Int(Target.ScaleWidth / 2 - OverAllDiff / 2), Int(Target.ScaleHeight / 2 - OverAllDiff / 2))-(Target.ScaleWidth / 2 + OverAllDiff / 2, Target.ScaleHeight / 2 + OverAllDiff / 2), NewColor, B
'Fade In from bottom right
Case 12
Target.Line (OverAllDiff, Target.ScaleWidth)-(Target.ScaleWidph, OverAllDiff + 1), NewColor, BF
'Fade In from bottom left
Case 13
Target.Line (0, Target.ScaleHeight)-(Target.ScaleWidth - OverAllDiff, OverAllDiff), NewColor, BF
'Fade In from top left
Case 14
Target.Line (0, 0)-(Target.ScaleWidth - OverAllDiff, Target.ScaleHeight - OverAllDiff), NewColor, BF
'Fade In from top right
Case 15
Target.Line (Target.ScaleWidth, 0)-(OverAllDiff, Target.ScaleHeight - OverAllDiff), NewColor, BF
'Boxes 1
Case 16
Target.Line (Target.ScaleWidth, 0)-(OverAllDiff, Target.ScaleHeight - OverAllDiff), NewColor, BF
Target.Line (0, Target.ScaleHeight)-(Target.ScaleWidth - OverAllDiff, OverAllDiff), NewColor, BF
'Boxes 2
Case 17
Target.Line (Target.ScaleWidth, 0)-(OverAllDiff, Target.ScaleHeight - OverAllDiff), NewColor, BF
Target.Line (OverAllDiff, Target.ScaleWidth)-(Target.ScaleWidth, OverAllDiff + 1), NewColor, BF
'Boxes 3
Case 18
Target.Line (Target.ScaleWidth, 0)-(OverAllDiff, Target.ScaleHeight - OverAllDiff), NewColor, BF
Target.Line (0, Target.ScaleHeight)-(Target.ScaleWidth - OverAllDiff, OverAllDiff), NewColor, BF
Target.Line (OverAllDiff, Target.ScaleWidth)-(Target.ScaleWidth, OverAllDiff + 1), NewColor, BF
'Boxes 4
Case 19
Target.Line (0, Target.ScaleHeight)-(Target.ScaleWidth - OverAllDiff, OverAllDiff), NewColor, BF
Target.Line (OverAllDiff, Target.ScaleWidth)-(Target.ScaleWidth, OverAllDiff + 1), NewColor, BF
'Boxes 5
Case 20
Target.Line (Target.ScaleWidth, 0)-(OverAllDiff, Target.ScaleHeight - OverAllDiff), NewColor, BF
Target.Line (0, 0)-(Target.ScaleWidth - OverAllDiff, Target.ScaleHeight - OverAllDiff), NewColor, BF
'Boxes 6
Case 21
Target.Line (0, Target.ScaleHeight)-(Target.ScaleWidth - OverAllDiff, OverAllDiff), NewColor, BF
Target.Line (0, 0)-(Target.ScaleWidth - OverAllDiff, Target.ScaleHeight - OverAllDiff), NewColor, BF
'Boxes 7
Case 22
Target.Line (OverAllDiff, Target.ScaleWidth)-(Target.ScaleWidth, OverAllDiff + 1), NewColor, BF
Target.Line (0, 0)-(Target.ScaleWidth - OverAllDiff, Target.ScaleHeight - OverAllDiff), NewColor, BF
'Boxes 8
Case 23
Target.Line (0, 0)-(Target.ScaleWidth - OverAllDiff, Target.ScaleHeight - OverAllDiff), NewColor, BF
Target.Line (Target.ScaleWidth, 0)-(OverAllDiff, Target.ScaleHeight - OverAllDiff), NewColor, BF
Target.Line (0, Target.ScaleHeight)-(Target.ScaleWidth - OverAllDiff, OverAllDiff), NewColor, BF
Target.Line (OverAllDiff, Target.ScaleWidth)-(Target.ScaleWidth, OverAllDiff + 1), NewColor, BF
'Top to Bottom
Case 24
Target.Line (0, OverAllDiff)-(Target.ScaleWidth, OverAllDiff + 1), NewColor, BF
'Bottom to Top
Case 25
Target.Line (0, 0)-(Target.ScaleWidth, Target.ScaleHeight - OverAllDiff), NewColor, BF
'Refraction
Case 26
Target.Line (Target.ScaleWidth - OverAllDiff, OverAllDiff)-(Target.ScaleWidth - OverAllDiff, Target.ScaleHeight), NewColor, BF
Target.Line (OverAllDiff, Target.ScaleHeight - OverAllDiff)-(Target.ScaleHeight, OverAllDiff), NewColor, BF
'Line through middle
Case 27
Target.Line ((Target.ScaleWidth / 2) - (OverAllDiff / 2), 0)-((Target.ScaleWidth / 2) - (OverAllDiff / 2), Target.ScaleHeight), NewColor, BF
Target.Line ((Target.ScaleWidth / 2) + (OverAllDiff / 2), 0)-((Target.ScaleWidth / 2) + (OverAllDiff / 2), Target.ScaleHeight), NewColor, BF
'Exploded
Case 28
Target.Line (Target.ScaleWidth, OverAllDiff / 2)-(OverAllDiff, Target.ScaleHeight - OverAllDiff), NewColor, BF
Target.Line (0, Target.ScaleHeight)-(Target.ScaleWidth - OverAllDiff, OverAllDiff), NewColor, BF
'Pouring
Case 29
Target.Line (Target.ScaleWidth, 0)-(OverAllDiff, Target.ScaleHeight), NewColor, BF
Target.Line (0, Target.ScaleHeight)-(Target.ScaleWidth - OverAllDiff, OverAllDiff), NewColor, BF
'lighthouse
Case 30
Target.Line (Target.ScaleWidth, OverAllDiff / 2)-(OverAllDiff, Target.ScaleHeight - OverAllDiff), NewColor, BF
'Square
Case 31
Target.Line (OverAllDiff / 2, Target.ScaleWidth)-(Target.ScaleWidth, OverAllDiff + 1), NewColor, BF
'Ripped
Case 32
Target.Line ((Target.ScaleHeight * OverAllDiff), OverAllDiff)-(OverAllDiff, Target.ScaleWidth + OverAllDiff), NewColor, BF
'Prism
Case 33
Target.Line (Target.ScaleWidth - OverAllDiff, OverAllDiff)-(Target.ScaleWidth - OverAllDiff, Target.ScaleHeight), NewColor, BF
Target.Line (OverAllDiff, Target.ScaleHeight - OverAllDiff)-(Target.ScaleHeight - OverAllDiff, 0), NewColor, BF
'Top left to bottom right
Case 34
Target.Line (0, OverAllDiff * 2)-(OverAllDiff * 2, 0), NewColor
'Fade to center from top right and botto
' m left
Case 35
Target.AutoRedraw = False
Target.Line (0, Target.ScaleHeight - OverAllDiff)-(OverAllDiff, Target.ScaleHeight), NewColor
Target.Line (Target.ScaleWidth - OverAllDiff, 0)-(Target.ScaleWidth, OverAllDiff), NewColor
'Fade to center from top left and bottom
' right
Case 36
Target.Line (Target.ScaleWidth, Target.ScaleHeight - OverAllDiff)-(Target.ScaleWidth - OverAllDiff, Target.ScaleHeight), NewColor
Target.Line (0, OverAllDiff)-(OverAllDiff, 0), NewColor
'Wow I'm finally done!
End Select
End Function
Function nolic(Target As Object)
Target.FontSize = 10
Target.ForeColor = vbBlack
Target.CurrentY = 0
Target.CurrentX = 2
Target.Print "Created With a SpiderTek Product"
Target.ForeColor = vbWhite
Target.CurrentY = 0
Target.CurrentX = 3
Target.Print "Created With a SpiderTek Product"
End Function
Private Sub Form_Click()
Static x As Integer
If x = 36 Then x = 0
x = x + 1
Gradeffect Me, x
Me.CurrentY = 200
Me.CurrentX = 3
Me.Print "You are at """ & x & """ of 36 total effects."
nolic Me
End Sub
Private Sub Form_Load()
FadeColors.Add vbBlack
FadeColors.Add vbRed
FadeColors.Add vbYellow
FadeColors.Add vbWhite
Gradeffect Me, 1
End Sub
Private Sub Form_Resize()
Gradeffect Me, 1
End Sub
لوضع البرنامج داخل صينية المهام
كود:
'ضع هذا الكود في ملف Modules
Option Explicit
'تعريف الدالة
Declare Function ****l_notifyicon Lib "****l32.dll" Alias _
"****l_NotifyIconA" (ByVal dwMessage As Long, lpData As NOTIFYICONDATA) As Long
Public Const WM_LBUTTONDBLCLK = &H203
Public Const WM_MBUTTONDBLCLK = &H209
Public Const WM_MBUTTONDOWN = &H207
Public Const WM_LBUTTONUP = &H202
Public Const WM_LBUTTONDOWN = &H201
Public Const WM_RBUTTONDBLCLK = &H206
Public Const WM_RBUTTONDOWN = &H204
Public Const WM_RBUTTONUP = &H205
Public Const WM_MOUSEMOVE = &H200
Public Const NIF_ICON = &H2
Public Const WM_COMMNOTIFY = &H44
Public Const NIF_MESSAGE = &H1
Public Const NIF_TIP = &H4
Public Const NIM_ADD = &H0
Public Const NIM_DELETE = &H2
Public Const MAX_TOOLTIP As Integer = 64
Type NOTIFYICONDATA
cbsize As Long
hwind As Long
uID As Long
uFlags As Long
uCallbackMessage As Long
hIcon As Long
szTip As String * MAX_TOOLTIP
End Type
' ضع هذا الكود في ملف تموذج
Dim nfIconData As NOTIFYICONDATA
Private Sub Form_Load()
'سيتم اضافة الصورة في صينية النظام
With nfIconData
'مقبض النافذة لتقبل الاحداث
.hwind = Form1.hWnd
'الايقونة التي سوف تضع
.uID = Form1.Icon
'اعطاء الثوابت للاظهار
.uFlags = NIF_ICON Or NIF_MESSAGE Or NIF_TIP
'تتبع احداث الفارة في حدث التحرك للفارة
.uCallbackMessage = WM_MOUSEMOVE
'مقبض الايقون
.hIcon = Form1.Icon.Handle
'النص المنبثق الذي سيطهر عند توقف المؤشر
.szTip = "برنامج صينية النظام" & Chr$(0)
.cbsize = Len(nfIconData)
End With
'استدعاء الدالة
Call ****l_notifyicon(NIM_ADD, nfIconData)
End Sub
Private Sub Form_MouseMove(Button As Integer, Shift As Integer, X As Single, Y As Single)
'سيتم تتبع احداث الفارة هنا
Select Case (X \ Screen.TwipsPerPixelX)
'عند تحرك الفارة فوقها
Case &H200
'Caption = Val(Caption) + 1
'عند النقر عليها بالفارة
Case &H203
Me.Visible = True
Me.WindowState = vbNormal
'النقر بالزر الايمن
Case &H205
PopupMenu Mnu_File
End Select
End Sub
Private Sub Form_Resize()
If WindowState = vbMinimized Then Me.Visible = False
End Sub
Private Sub Form_Unload(Cancel As Integer)
'تنظيف المقابض بعد الاغق واخفاء الايقونة
Call ****l_notifyicon(NIM_DELETE, nfIconData)
End Sub
Private Sub Mnu_File_Close_Click()
Unload Me
End Sub
Private Sub Mnu_File_Max_Click()
Me.Visible = True
Me.WindowState = vbNormal
End Sub
Private Sub Mnu_File_Min_Click()
WindowState = vbMinimized
End Sub
إظهار معلومات القرص المحدد
كود:
'===================================================
'Sub: GetDiskInfo
'Description: Gets information for a specified disk drive.
' (The name of the Disk, Serial Number, Maximum Component length,
' File System Flags, and File System Type)
'Where to place code: Module
'Notes: Call this function with a root path as its' parimeter (ie, GetDiskInfo "c:\").
' The function will then load the public variables with the correct values for the
' disk.
'
'http://www.littleguru.com
'==================================================
Public Declare Function GetVolumeInformation& Lib "kernel32" Alias "GetVolumeInformationA" (ByVal lpRootPathName As String, ByVal lpVolumeNameBuffer As String, ByVal nVolumeNameSize As Long, lpVolumeSerialNumber As Long, lpMaximumComponentLength As Long, lpFileSystemFlags As Long, ByVal lpFileSystemNameBuffer As String, ByVal nFileSystemNameSize As Long)
Public strDiskName As String ' Disk Name
Public lngSerialNumber As Long ' Disk Serial Number
Public lngMaxComLength As Long ' Maximum Component Length
Public lngFileSystemFlags As Long ' File System Flags
Public strFileSystem As String ' File System Type
Public Sub GetDiskInfo(strRootPath As String)
Dim lngTemp As Long
Dim strTemp1 As String * 255
Dim strTemp2 As String * 10
If GetVolumeInformation(strRootPath, strTemp1, 255, lngSerialNumber, lngMaxComLength, lngFileSystemFlags, strTemp2, 10) = 0 Then
' Insert Error Handling code here
End If
If Len(strTemp1) > 0 Then
lngTemp = InStr(strTemp1, vbNullChar)
strDiskName = Left(strTemp1, lngTemp - 1)
End If
If Len(strTemp2) > 0 Then
lngTemp = InStr(strTemp2, vbNullChar)
strFileSystem = Left(strTemp2, lngTemp - 1)
End If
End Sub
إيقاف البرنامج لفترة معينة
كود:
'===================================================
'Sub: AppSleep
'Description: Suspends operation of your program for the specified time
'Where to place code: Module
'Notes: Set lngMilliSeconds to the time in milliseconds your app will be suspended
'
'http://www.littleguru.com
'==================================================
Public Declare Sub Sleep Lib "kernel32" (ByVal dwMilliseconds As Long)
Public Sub AppSleep(lngMilliSeconds As Long)
Sleep lngMilliSeconds
End Sub
إضافة نص في موضع معين من نص آخر
كود:
'===================================================
'Function: InsertString
'Description: Inserts a string into another at the specified position
'Where to place code: Module
'Notes: Set lngPosition to the position in the original string you want the new string to be inserted at
' Set strString1 to the original string
' Set strString2 to the string you want inserted in the original string
'
'http://www.littleguru.com
'==================================================
Public Function InsertString(lngPosition, strString1, strString2)
Dim strTemp As String
Dim strTemp2 As String
strTemp = Left(strString1, lngPosition)
strTemp2 = Right(strString1, Len(strString1) - lngPosition)
InsertString = strTemp + strString2 + strTemp2
End Function
معرفة ما إذا كان البرنامج يعمل بالفعل أم لا
كود:
'===================================================
'Sub: IsAppAlreadyRunning
'Description: Determines if your application is already running
'Where to place code: Module
'Notes: It would be a good idea to change the MsgBox and End code
' to something more professional
'
'http://www.littleguru.com
'==================================================
Public Sub IsAppRunning()
If App.PrevInstance = True Then
MsgBox "MyApp is already running",vbOkOnly,"MyApp"
End
End If
End Sub
عمل البرنامج مع بدأ تشغيل الويندوز
كود:
'===================================================
'Function: RunNextBoot
'Description: Sets a key in the registry to have your app run the next time Windows is rebooted,
' or everytime Windows is rebooted.
'Where to place code: Module
'Notes: Set AppName to the name of your application
' Set CmdLine to the path of you application with any other arguments following
' Set ThisUserOnly to true if the application should only be run when the current user reboots
' Set RunEveryBoot to true if the application should run every reboot, instead of just the next time
'
'Author: Karl E. Peterson of VBPJ
'Author's ***site: http://www.vbpj.com
'Magazine: Visual Basic Programmer's Journal, March 1999, Vol. 9, No. 3, pg. 93
'http://www.littleguru.com
'==================================================
Public Declare Function RegCreateKeyEx& Lib "advapi32.dll" Alias "RegCreateKeyExA" (ByVal hKey As Long, ByVal lpSubKey As String, ByVal Reserved As Long, ByVal lpClass As String, ByVal dwOptions As Long, ByVal samDesired As Long, lpSecurityAttributes As Any, phkResult As Long, lpdwDisposition As Long)
Public 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)
Public Declare Function RegCloseKey& Lib "advapi32.dll" (ByVal hKey As Long)
Public Const HKEY_CURRENT_USER = &H80000001
Public Const HKEY_LOCAL_MACHINE = &H80000002
Public Const REG_OPTION_NON_VOLATILE = 0
Public Const SYNCHRONIZE = &H100000
Public Const STANDARD_RIGHTS_ALL = &H1F0000
Public Const KEY_QUERY_VALUE = &H1
Public Const KEY_SET_VALUE = &H2
Public Const KEY_CREATE_SUB_KEY = &H4
Public Const KEY_ENUMERATE_SUB_KEYS = &H8
Public Const KEY_NOTIFY = &H10
Public Const KEY_CREATE_LINK = &H20
Public Const KEY_ALL_ACCESS = ((STANDARD_RIGHTS_ALL Or KEY_QUERY_VALUE Or KEY_SET_VALUE Or KEY_CREATE_SUB_KEY Or KEY_ENUMERATE_SUB_KEYS Or KEY_NOTIFY Or KEY_CREATE_LINK) And (Not SYNCHRONIZE))
Public Const ERROR_SUCCESS = 0&
Public Const REG_SZ = 1
Public Function RunNextBoot(ByVal AppName As String, ByVal CmdLine As String, Optional ThisUserOnly As Boolean = False, Optional RunEveryBoot As Boolean = False)
Dim TopKey As Long
Dim SubKey As String
Dim nRet As Long
Dim hKey As Long
Dim nResult As Long
If RunEveryBoot Then
SubKey = "SOFTWARE\Microsoft\Windows\CurrentVersion\Run"
Else
SubKey = "SOFTWARE\Microsoft\Windows\CurrentVersion\RunOnce"
End If
If ThisUserOnly Then
TopKey = HKEY_CURRENT_USER
Else
TopKey = HKEY_LOCAL_MACHINE
End If
nRet = RegCreateKeyEx(TopKey, SubKey, 0&, vbNullString, REG_OPTION_NON_VOLATILE, KEY_ALL_ACCESS, ByVal 0&, hKey, nResult)
If nRet = ERROR_SUCCESS Then
nRet = RegSetValueEx(hKey, AppName, 0&, REG_SZ, ByVal CmdLine, Len(CmdLine))
Call RegCloseKey(hKey)
End If
RunNextBoot = (nRet = ERROR_SUCCESS)
End Function
