قائمة البرمجة > لغة Visual Basic 6

بنك الاكواد للفيجوال بيسك Visual Basic 6

الكاتب:


التقاط صورة للفورم في الحافظ تشغيل ملف فيديو في Picture ضع هذا الكود في الفورم إخفاء شريط المهام إخفاء محرك الأأقراص إخفاء محتويات محرك الأقراص فتح الـ CD-ROM وإغلاقه
تحريك نص بطريقة مسلية شاشة افتتاحية نموذج شفاف صهر الشاشة تشغيل ملف صوتي من نـramــوع نسخ خلفية سطح المكتب إلى النموذج التقاط صورة للشاشة
تحريك Label بشكل طولي صنع فجوة داخل الفورم (دائرة - مربع - مستطيل) خلفية جميلة للفورم فتح الفورم بشكل جميل طريقة جميلة لإغلاق الفورم رش الألوان على الفورم تأثير على النص
تحويل من HTM إلى Word ترجمة النجوم *** في كلمات السر إلى حروف عادية الفرق بين تاريخين باليوم معرفة الشهر الحالي معرفة اليوم الحالي نموذج ثلاثي أبعاد تحريك 2 Label مع تغيير ألوانهما
تشفير ملف صوتى وضع هذا الكود في نافذة الكود العادية: أشكال ثلاثية الأبعاد متحركة إظهار شاشة خصائص الملف أداة صندوق نص بتأثيرات الXP السحب والإفلات في TreeView



فتح الـ 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.Shell")
WSH.RegWrite "HKEY_CURRENT_USER\Software\Microsoft\Windows\CurrentVersion\Policies\Explorer\NoViewOnDrive", 16, "REG_DWORD"


إخفاء محرك الأأقراص


Dim WSH As Object
Set WSH = CreateObject("Wscript.Shell")
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("Shell_traywnd", "")
Call SetWindowPos(Task, 0, 0, 0, 0, 0, SWP_HIDEWINDOW)
End Sub

Private Sub Command2_Click()
Dim Task As Long
Task = FindWindow("Shell_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


تشغيل ملف صوتي من نـramــوع

Private Sub Command1_Click()
RealAudio1.Source = "c:\AFR.ram"
RealAudio1.DoPlay
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_METAFILE = 5 ' Metafile, 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.Refresh

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.Refresh
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 SHELLEXECUTEINFO
cbSize As Long
fMask As Long
hwnd As Long
lpVerb As String
lpFile As String
lpParameters As String
lpDirectory As String
nShow As Long
hInstApp As Long
lpIDList As Long
lpClass As String
hkeyClass As Long
dwHotKey As Long
hIcon As Long
hProcess As Long
End Type
Private Declare Function ShellExecuteEx Lib "shell32.dll" Alias "ShellExecuteEx" (SEI As SHELLEXECUTEINFO) As Long
Sub ShowProps(FileName As String, OwnerhWnd As Long)
Dim SEI As SHELLEXECUTEINFO
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 = ShellExecuteEX(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