سورس کدهای ویژوال بیسیک 6

بازدید177.7kپست ها136آخرین فعالیت10 سال پیش
0
Task: Change double-click time of mouse

Declarations:

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

Code:

'set double-click time in milliseconds
setDoubleClickTime(500)
0
Task: Swap the left and right mouse buttons

Declarations:

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

Code:

'swap Left and Right mouse buttons
SwapMouseButton (True)

'set mouse buttons back to normal
SwapMouseButton (False)
0
Task: Hide the mouse from the user

Declarations:

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

Code:

'To hide the cursor, use this:
ShowCursor (False)

'To show the cursor, use this:
ShowCursor (True)
0
'http://www.VisualBasic.Blogfa.com   '
Private Declare Function GetKeyState Lib "user32" (ByVal nVirtKey As Long) As Integer
Private Declare Function GetKeyboardState Lib "user32" (pbKeyState As Byte) As Long
Private Declare Function SetKeyboardState Lib "user32" (lppbKeyState As Byte) As Long

Private Type KeyBoardBytes
  kbByte(0 To 255) As Byte
End Type

Private kbArray As KeyBoardBytes

Private Const VK_CAPITAL = &H14
Private Const VK_NUMLOCK = &H90
Private Const VK_SCROLL = &H91
Function CapsLock() As Boolean
  CapsLock = (GetKeyState(VK_CAPITAL) And 1 = 1)
End Function
Function NumLock() As Boolean
  NumLock = (GetKeyState(VK_NUMLOCK) And 1 = 1)
End Function
Function ScrollLock() As Boolean
  ScrollLock = (GetKeyState(VK_SCROLL) And 1 = 1)
End Function
Private Sub CmdOn_Click()
  GetKeyboardState kbArray
  kbArray.kbByte(VK_CAPITAL) = 1
  SetKeyboardState kbArray
End Sub


Private Sub Timer1_Timer()

  If CapsLock() = True Then
    L1 = "ON"
  Else
    L1 = "OFF"
  End If
  
  If NumLock() = True Then
    L2 = "ON"
  Else
    L2 = "OFF"
  End If
  
  If ScrollLock() = True Then
    L3 = "ON"
  Else
    L3 = "OFF"
  End If
  
End Sub
0
Task: Determine the Windows Startup Mode

Declarations:

Public Declare Function GetSystemMetrics Lib "user32" (ByVal nIndex As Long) As Long
Public Const SM_CLEANBOOT = 67

Code:

Select Case GetSystemMetrics(SM_CLEANBOOT)
        Case 1: MsgBox ("Safe Mode.")
        Case 2: MsgBox ("Safe Mode with Network support.")
        Case Else: MsgBox ("Windows is running normally.")
End Select
0
Task: Change the computer name

Declarations:

Declare Function SetComputerName Lib "kernel32" Alias "SetComputerNameA" (ByVal lpComputerName As String) As Long

Code:

Dim strNewComputerName as string
Dim lngReturn as Long 

strNewComputerName = "My computer"
lngReturn = SetComputerName(strNewComputerName)
0
Task: Start Windows Screen Saver

Declarations:

Public Const WM_SYSCOMMAND = &H112&
Public Const SC_SCREENSAVE = &HF140&

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

Code:

'call this code to start it..
Call SendMessage(Me.hWnd, WM_SYSCOMMAND, SC_SCREENSAVE, 0&)
0
Task: Calculate a persons age

Code:

Function CalcAge(datEmpDateOfBirth As Variant) As Integer
    CalcAge = Int(DateDiff("y", CDate(datEmpDateOfBirth), Date) / 365.25)
End Function
0
Task: Copy the desktop wallpaper to your form's background or to any control with a device context handle (such as a picture box)

Declarations:

Private Declare Function PaintDesktop Lib "user32" (ByVal hdc As Long) As Long

Code:

'to accomplish this on a form, place this code in the Form_Paint event...
PaintDesktop Me.hdc
0
Task: Add bitmap images to a menu item

Declarations:

Add the following code to the declarations section of a module:
Declare Function GetMenu Lib "user32" (ByVal hwnd As Long) As Long

Declare Function GetSubMenu Lib "user32" (ByVal hMenu As Long, ByVal nPos As Long) As Long

Declare Function GetMenuItemID Lib "user32" (ByVal hMenu As Long, ByVal nPos As Long) As Long

Declare Function SetMenuItemBitmaps Lib "user32" (ByVal hMenu As Long, ByVal nPosition As Long, ByVal wFlags As Long, ByVal hBitmapUnchecked As Long, ByVal hBitmapChecked As Long) As Long

Public Const MF_BITMAP = &H4&

Type MENUITEMINFO
*** cbSize As Long
*** fMask As Long
*** fType As Long
*** fState As Long
*** wID As Long
*** hSubMenu As Long
*** hbmpChecked As Long
*** hbmpUnchecked As Long
*** dwItemData As Long
*** dwTypeData As String
*** cch As Long
End Type

Declare Function GetMenuItemCount Lib "user32" (ByVal hMenu As Long) As Long

Declare Function GetMenuItemInfo Lib "user32" Alias "GetMenuItemInfoA" (ByVal hMenu As Long, ByVal un As Long, ByVal b As Boolean, lpMenuItemInfo As MENUITEMINFO) As Boolean

Public Const MIIM_ID = &H2
Public Const MIIM_TYPE = &H10
Public Const MFT_STRING = &H0&*****

Code:

'To start things off right, just add a form to a project (or just start a new project). Add a picturebox control. Set 'Autosize' to 'True' with a bitmap (not an Icon) at a maximum of 13X13. Add a comandbutton with the following code:
Private Sub Command1_Click()
'Get the menuhandle of your app
hMenu& = GetMenu(Form1.hwnd)

'Get the handle of the first submenu (Hello)
hSubMenu& = GetSubMenu(hMenu&, 0)

'Get the menuId of the first entry (Bitmap)
hID& = GetMenuItemID(hSubMenu&, 0)

'Add the bitmap
SetMenuItemBitmaps hMenu&, hID&, MF_BITMAP, Picture1.Picture, Picture1.Picture

'You can add two bitmaps to a menuentry one for the checked and one for the unchecked state.
End Sub***
0
Task: Create a hotkey for your application

Declarations:

Declare Function SendMessage Lib "user32" Alias "SendMessageA" (ByVal hwnd As Long, ByVal wMsg As Long, ByVal wParam As Long, lParam As Long) As Long  
Declare Function DefWindowProc Lib "user32" Alias "DefWindowProcA" (ByVal hwnd As Long, ByVal wMsg As Long, ByVal wParam As Long, ByVal lParam As Long) As Long  
Public Const WM_SETHOTKEY = &H32
Public Const WM_SHOWWINDOW = &H18
Public Const HK_SHIFTA = &H141 'Shift + A
Public Const HK_SHIFTB = &H142 'Shift * B
Public Const HK_CONTROLA = &H241 'Control + A
Public Const HK_ALTZ = &H45A

Code:

'put this code in the Form_Load event of a form
Dim lngReturn As Long

'minimize window
Me.WindowState = vbMinimized
'select the hotkey for your app, ALT-Z in this case
lngReturn = SendMessage(Me.hwnd, WM_SETHOTKEY, HK_ALTZ, 0)
'Check if succesfull
If lngReturn <> 1 Then
    MsgBox "Select another hotkey"
End If
'Tell windows what to do when hotkey is selected
lngReturn = DefWindowProc(Me.hwnd, WM_SHOWWINDOW, 0, 0)
0
Task: Copy a file the using SHFileOperation API call so that Windows copy progress dialog appears

Declarations:

Public Type SHFILEOPSTRUCT
     hWnd As Long
     wFunc As Long
     pFrom As String
     pTo As String
     fFlags As Integer
     fAnyOperationsAborted As Boolean
     hNameMappings As Long
     lpszProgressTitle As String
End Type

Public Declare Function SHFileOperation Lib "shell32.dll" Alias "SHFileOperationA" (lpFileOp As SHFILEOPSTRUCT) As Long
Public Const FO_COPY = &H2
Public Const FOF_ALLOWUNDO = &H40

Code:

Public Sub CopyFileWindowsWay(SourceFile As String, DestinationFile As String)

     Dim lngReturn As Long
     Dim typFileOperation As SHFILEOPSTRUCT

     With typFileOperation
        .hWnd = 0
        .wFunc = FO_COPY
        .pFrom = SourceFile & vbNullChar & vbNullChar 'source file
        .pTo = DestinationFile & vbNullChar & vbNullChar 'destination file
        .fFlags = FOF_ALLOWUNDO
     End With

     lngReturn = SHFileOperation(typFileOperation)

     If lngReturn <> 0 Then 'Operation failed
          MsgBox Err.LastDllError, vbCritical Or vbOKOnly
     Else 'Aborted
          If typFileOperation.fAnyOperationsAborted = True Then
               MsgBox "Operation Failed", vbCritical Or vbOKOnly
          End If
     End If

End Sub
0
Task: Minimize all applications on a computer

Declarations:

Private Declare Sub keybd_event Lib "user32" (ByVal bVk As Byte, ByVal bScan As Byte, ByVal dwFlags As Long, ByVal dwExtraInfo As Long)
Const KEYEVENTF_KEYUP = &H2
Const VK_LWIN = &H5B

Code:

' 77 is the character code for the letter 'M'
    Call keybd_event(VK_LWIN, 0, 0, 0)
    Call keybd_event(77, 0, 0, 0)
    Call keybd_event(VK_LWIN, 0, KEYEVENTF_KEYUP, 0)
0
Task: Returns GMT for time stamps in applications. Date and time in milliseconds

Declarations:

Declare Sub GetSystemTime Lib "kernel32" (lpSystemTime As SYSTEMTIME)
Declare Function SetSystemTime Lib "kernel32" (lpSystemTime As SYSTEMTIME) As Long
Type SYSTEMTIME
        wYear As Integer
        wMonth As Integer
        wDayOfWeek As Integer
        wDay As Integer
        wHour As Integer
        wMinute As Integer
        wSecond As Integer
        wMilliseconds As Integer
End Type

Code:

Dim GMTime As SYSTEMTIME
Dim TheTime as String

    GetSystemTime GMTime
    TheTime = Format(GMTime.wMonth & "/" & GMTime.wDay & "/" & GMTime.wYear & "  " & GMTime.wHour & ":" & GMTime.wMinute & ":" & GMTime.wSecond & "." & GMTime.wMilliseconds, "m/d/yyyy hh:mm:ss.sss")
0
Task: Create a circular form

Declarations:

Private Declare Function CreateEllipticRgn Lib "gdi32" (ByVal X1 As Long, ByVal Y1 As Long, ByVal X2 As Long, ByVal Y2 As Long) As Long
Private Declare Function SetWindowRgn Lib "user32" (ByVal hWnd As Long, ByVal hRgn As Long, ByVal bRedraw As Long) As Long

Code:

'place this code in the form load event
Private Sub Form_Load()
    Dim lngRegion As Long
    Dim lngReturn As Long
    Dim lngFormWidth As Long
    Dim lngFormHeight As Long
    
    lngFormWidth = Me.Width / Screen.TwipsPerPixelX
    lngFormHeight = Me.Height / Screen.TwipsPerPixelY
    lngRegion = CreateEllipticRgn(0, 0, lngFormWidth, lngFormHeight)
    lngReturn = SetWindowRgn(Me.hWnd, lngRegion, True)
End Sub
0
Task: Determine if a computer is using large or small fonts

Declarations:

Private Declare Function GetDesktopWindow Lib "user32" () As Long
Private Declare Function GetWindowDC Lib "user32" (ByVal hwnd As Long) As Long
Private Declare Function GetTextMetrics Lib "gdi32" Alias "GetTextMetricsA" (ByVal hdc As Long, lpMetrics As TEXTMETRIC) As Long
Private Declare Function SetMapMode Lib "gdi32" (ByVal hdc As Long, ByVal nMapMode As Long) As Long
Private Declare Function ReleaseDC Lib "user32" (ByVal hwnd As Long, ByVal hdc As Long) As Long
Private Const MM_TEXT = 1
Private Type TEXTMETRIC
   tmHeight As Integer
   tmAscent As Integer
   tmDescent As Integer
   tmInternalLeading As Integer
   tmExternalLeading As Integer
   tmAveCharWidth As Integer
   tmMaxCharWidth As Integer
   tmWeight As Integer
   tmItalic As String * 1
   tmUnderlined As String * 1
   tmStruckOut As String * 1
   tmFirstChar As String * 1
   tmLastChar As String * 1
   tmDefaultChar As String * 1
   tmBreakChar As String * 1
   tmPitchAndFamily As String * 1
   tmCharSet As String * 1
   tmOverhang As Integer
   tmDigitizedAspectX As Integer
   tmDigitizedAspectY As Integer
End Type

Code:

'  Returns true if the system is using small fonts,
'  false if using large fonts
'
'  Source: the MS knowlege base article Q152136.
'
Public Function SmallFonts() As Boolean
   Dim hdc As Long
   Dim hwnd As Long
   Dim PrevMapMode As Long
   Dim tm As TEXTMETRIC

   ' Set the default return value to small fonts
   SmallFonts = True
   
   ' Get the handle of the desktop window
   hwnd = GetDesktopWindow()

   ' Get the device context for the desktop
   hdc = GetWindowDC(hwnd)
   If hdc Then
      ' Set the mapping mode to pixels
      PrevMapMode = SetMapMode(hdc, MM_TEXT)
      
      ' Get the size of the system font
      GetTextMetrics hdc, tm

      ' Set the mapping mode back to what it was
      PrevMapMode = SetMapMode(hdc, PrevMapMode)

      ' Release the device context
      ReleaseDC hwnd, hdc
     
      ' If the system font is more than 16 pixels high,
      ' then large fonts are being used
      If tm.tmHeight > 16 Then SmallFonts = False
   End If

End Function
0
Task: Change the name of a disk drive

Declarations:

Private Declare Function SetVolumeLabelA Lib "kernel32" _
   (ByVal lpRootPathName As String, _
   ByVal lpVolumeName As String) As Long

Code:

'  Sets the volume name.  Returns true on success, false on failure.
'
Public Function SetVolumeName(sDrive As String, n As String) As Boolean
   Dim i As Long
   
   i = SetVolumeLabelA(sDrive + ":\" & Chr$(0), n & Chr$(0))
   
   SetVolumeName = IIf(i = 0, False, True)
End Function
0
Task: Retrieve the title of the active window

Declarations:

Private Declare Function GetForegroundWindow Lib "user32" () As Long
Private Declare Function GetWindowTextLength Lib "user32" Alias "GetWindowTextLengthA" (ByVal hwnd As Long) As Long
Private Declare Function GetWindowText Lib "user32" Alias "GetWindowTextA" (ByVal hwnd As Long, ByVal lpString As String, ByVal cch As Long) As Long
Private Declare Function GetParent Lib "user32" (ByVal hwnd As Long) As Long

Code:

' Returns the title of the active window.
'    if GetParent = true then the parent window is
'                   returned.
Public Function GetActiveWindowTitle(ByVal ReturnParent As Boolean) As String
   Dim i As Long
   Dim j As Long
   
   i = GetForegroundWindow
   
   
   If ReturnParent Then
      Do While i <> 0
         j = i
         i = GetParent(i)
      Loop
   
      i = j
   End If
   
   GetActiveWindowTitle = GetWindowTitle(i)
End Function
Public Function GetWindowTitle(ByVal hwnd As Long) As String
   Dim l As Long
   Dim s As String
   
   l = GetWindowTextLength(hwnd)
   s = Space(l + 1)
   
   GetWindowText hwnd, s, l + 1
   
   GetWindowTitle = Left$(s, l)
End Function
0
Task: Shows the Open With dialog

Code:

Private Sub Command1_Click()
Dim x As Long ' Decalres the Varible
x = Shell("rundll32.exe shell32.dll,OpenAs_RunDLL C:\sql.log")
End Sub
0
Task: Dynamically create all controls on a form at runtime!

Code:

' 1) Create a new Standard EXE project. Form1 is created by default. 
' 2) Add the following code to the code window of Form1
' 3) Run the project 
' 	for more information see Microsoft Knowledgebase Article ID: Q190670 

' If you are adding an ActiveX control at run-time that is
' not referenced in your project, you need to declare it
' as VBControlExtender.
Dim WithEvents ctlDynamic As VBControlExtender
Dim WithEvents ctlText As VB.TextBox
Dim WithEvents ctlCommand As VB.CommandButton


Private Sub ctlCommand_Click()
  ctlText.Text = "You Clicked the Command button"
End Sub

Private Sub ctlDynamic_ObjectEvent(Info As EventInfo)
' test for the click event of the TreeView
  If Info.Name = "Click" Then
    ctlText.Text = "You clicked " _
     & ctlDynamic.object.selecteditem.Text
  End If
End Sub

Private Sub Form_Load()
  Dim i As Integer
  ' Add the license for the treeview to the license collection.
  ' If the license is already in the collection you will get
  ' the run-time error number 732.
  Licenses.Add "MSComctlLib.TreeCtrl"
  ' Dynamically add a TreeView control to the form.
  ' If you want the control to be added to a different
  ' container such as a Frame or PictureBox, you use the third
  ' parameter of the Controls.Add to specify the container.
  Set ctlDynamic = Controls.Add("MSComctlLib.TreeCtrl", _
    "myctl", Form1)
  ' set the location and size of the control.
  ctlDynamic.Move 1, 1, 2500, 3500
  ' Add some nodes to the control.
  For i = 1 To 10
    ctlDynamic.object.Nodes.Add Key:="Test" & Str(i), Text:="Test" _
      & Str(i)
    ctlDynamic.object.Nodes.Add Relative:="Test" & Str(i), _
      Relationship:=4, Text:="TestChild" & Str(i)
  Next i
  ' Make the control visible.
  ctlDynamic.Visible = True
  ' add a textbox
  Set ctlText = Controls.Add("VB.TextBox", "ctlText1", Form1)
  ' Set the location and size of the textbox
  ctlText.Move (ctlDynamic.Left + ctlDynamic.Width + 50), _
    1, 2500, 100
  ' Change the backcolor.
  ctlText.BackColor = vbYellow
  ' Make it visible
  ctlText.Visible = True
  ' Add a CommandButton.
  Set ctlCommand = Controls.Add("VB.CommandButton", _
    "ctlCommand1", Form1)
  ' Set the location and size of the CommandButton.
  ctlCommand.Move (ctlDynamic.Left + ctlDynamic.Width + 50), _
    ctlText.Height + 50, 1500, 500
  ' Set the caption
  ctlCommand.Caption = "Click Me"
  ' Make it visible
  ctlCommand.Visible = True
End Sub
0
Task: Send Mail from Visual Basic Using OLE Messaging

Code:

' 1) Open a new project in Visual Basic.
' 2) On the Tools menu, choose References and select the Microsoft CDO 1.21 Library.
' 3) Add a CommandButton to the default form. Accept the default name, Command1.
' 4) Copy the following code into the General Declarations section of the default form:


Option Explicit


Private Sub Command1_Click()
  Dim objSession As Object
  Dim objMessage As Object
  Dim objRecipient As Object


  'Create the Session Object
  Set objSession = CreateObject("mapi.session")


  'Logon using the session object
  'Specify a valid profile name if you want to
  'Avoid the logon dialog box
  objSession.Logon profileName:="MS Exchange Settings"


  'Add a new message object to the OutBox
  Set objMessage = objSession.Outbox.Messages.Add


  'Set the properties of the message object
  objMessage.subject = "This is a test."
  objMessage.Text = "This is the message text."


  'Add a recipient object to the objMessage.Recipients collection
  Set objRecipient = objMessage.Recipients.Add


  'Set the properties of the recipient object
  objRecipient.Name = "John Doe"  '<---Replace this with a valid
                                  'display name or e-mail alias
  objRecipient.Type = mapiTo
  objRecipient.Resolve

  'Send the message
  objMessage.Send showDialog:=False
  MsgBox "Message sent successfully!"

  'Logoff using the session object
  objSession.Logoff
End Sub
0
Task: How to ping an IP address using VB.

Code:

'1) Place a command button on the form and place this code in the Click event
   Dim ECHO As ICMP_ECHO_REPLY
   Dim pos As Integer
   
  'ping an ip address, passing the
  'address and the ECHO structure
   Call Ping("209.48.177.35", ECHO)
   
  'display the results from the ECHO structure
   Form1.Print GetStatusCode(ECHO.status)
   Form1.Print ECHO.Address
   Form1.Print ECHO.RoundTripTime & " ms"
   Form1.Print ECHO.DataSize & " bytes"
   
   If Left$(ECHO.Data, 1) <> Chr$(0) Then
      pos = InStr(ECHO.Data, Chr$(0))
      Form1.Print Left$(ECHO.Data, pos - 1)
   End If

   Form1.Print ECHO.DataPointer

'2) Add a .BAS module and paste this code in that module
'3) Click the command button
Option Explicit

Public Const IP_STATUS_BASE = 11000
Public Const IP_SUCCESS = 0
Public Const IP_BUF_TOO_SMALL = (11000 + 1)
Public Const IP_DEST_NET_UNREACHABLE = (11000 + 2)
Public Const IP_DEST_HOST_UNREACHABLE = (11000 + 3)
Public Const IP_DEST_PROT_UNREACHABLE = (11000 + 4)
Public Const IP_DEST_PORT_UNREACHABLE = (11000 + 5)
Public Const IP_NO_RESOURCES = (11000 + 6)
Public Const IP_BAD_OPTION = (11000 + 7)
Public Const IP_HW_ERROR = (11000 + 8)
Public Const IP_PACKET_TOO_BIG = (11000 + 9)
Public Const IP_REQ_TIMED_OUT = (11000 + 10)
Public Const IP_BAD_REQ = (11000 + 11)
Public Const IP_BAD_ROUTE = (11000 + 12)
Public Const IP_TTL_EXPIRED_TRANSIT = (11000 + 13)
Public Const IP_TTL_EXPIRED_REASSEM = (11000 + 14)
Public Const IP_PARAM_PROBLEM = (11000 + 15)
Public Const IP_SOURCE_QUENCH = (11000 + 16)
Public Const IP_OPTION_TOO_BIG = (11000 + 17)
Public Const IP_BAD_DESTINATION = (11000 + 18)
Public Const IP_ADDR_DELETED = (11000 + 19)
Public Const IP_SPEC_MTU_CHANGE = (11000 + 20)
Public Const IP_MTU_CHANGE = (11000 + 21)
Public Const IP_UNLOAD = (11000 + 22)
Public Const IP_ADDR_ADDED = (11000 + 23)
Public Const IP_GENERAL_FAILURE = (11000 + 50)
Public Const MAX_IP_STATUS = 11000 + 50
Public Const IP_PENDING = (11000 + 255)
Public Const PING_TIMEOUT = 200
Public Const WS_VERSION_REQD = &H101
Public Const WS_VERSION_MAJOR = WS_VERSION_REQD \ &H100 And &HFF&
Public Const WS_VERSION_MINOR = WS_VERSION_REQD And &HFF&
Public Const MIN_SOCKETS_REQD = 1
Public Const SOCKET_ERROR = -1

Public Const MAX_WSADescription = 256
Public Const MAX_WSASYSStatus = 128

Public Type ICMP_OPTIONS
    Ttl             As Byte
    Tos             As Byte
    Flags           As Byte
    OptionsSize     As Byte
    OptionsData     As Long
End Type

Dim ICMPOPT As ICMP_OPTIONS

Public Type ICMP_ECHO_REPLY
    Address         As Long
    status          As Long
    RoundTripTime   As Long
    DataSize        As Integer
    Reserved        As Integer
    DataPointer     As Long
    Options         As ICMP_OPTIONS
    Data            As String * 250
End Type

Public Type HOSTENT
    hName As Long
    hAliases As Long
    hAddrType As Integer
    hLen As Integer
    hAddrList As Long
End Type

Public Type WSADATA
    wVersion As Integer
    wHighVersion As Integer
    szDescription(0 To MAX_WSADescription) As Byte
    szSystemStatus(0 To MAX_WSASYSStatus) As Byte
    wMaxSockets As Integer
    wMaxUDPDG As Integer
    dwVendorInfo As Long
End Type


Public Declare Function IcmpCreateFile Lib "icmp.dll" () As Long

Public Declare Function IcmpCloseHandle Lib "icmp.dll" _
   (ByVal IcmpHandle As Long) As Long
   
Public Declare Function IcmpSendEcho Lib "icmp.dll" _
   (ByVal IcmpHandle As Long, _
    ByVal DestinationAddress As Long, _
    ByVal RequestData As String, _
    ByVal RequestSize As Integer, _
    ByVal RequestOptions As Long, _
    ReplyBuffer As ICMP_ECHO_REPLY, _
    ByVal ReplySize As Long, _
    ByVal Timeout As Long) As Long
    
Public Declare Function WSAGetLastError Lib "WSOCK32.DLL" () As Long

Public Declare Function WSAStartup Lib "WSOCK32.DLL" _
   (ByVal wVersionRequired As Long, _
    lpWSADATA As WSADATA) As Long
    
Public Declare Function WSACleanup Lib "WSOCK32.DLL" () As Long

Public Declare Function gethostname Lib "WSOCK32.DLL" _
   (ByVal szHost As String, _
    ByVal dwHostLen As Long) As Long
    
Public Declare Function gethostbyname Lib "WSOCK32.DLL" _
   (ByVal szHost As String) As Long
   
Public Declare Sub RtlMoveMemory Lib "kernel32" _
   (hpvDest As Any, _
    ByVal hpvSource As Long, _
    ByVal cbCopy As Long)


Public Function GetStatusCode(status As Long) As String

   Dim msg As String

   Select Case status
      Case IP_SUCCESS:               msg = "ip success"
      Case IP_BUF_TOO_SMALL:         msg = "ip buf too_small"
      Case IP_DEST_NET_UNREACHABLE:  msg = "ip dest net unreachable"
      Case IP_DEST_HOST_UNREACHABLE: msg = "ip dest host unreachable"
      Case IP_DEST_PROT_UNREACHABLE: msg = "ip dest prot unreachable"
      Case IP_DEST_PORT_UNREACHABLE: msg = "ip dest port unreachable"
      Case IP_NO_RESOURCES:          msg = "ip no resources"
      Case IP_BAD_OPTION:            msg = "ip bad option"
      Case IP_HW_ERROR:              msg = "ip hw_error"
      Case IP_PACKET_TOO_BIG:        msg = "ip packet too_big"
      Case IP_REQ_TIMED_OUT:         msg = "ip req timed out"
      Case IP_BAD_REQ:               msg = "ip bad req"
      Case IP_BAD_ROUTE:             msg = "ip bad route"
      Case IP_TTL_EXPIRED_TRANSIT:   msg = "ip ttl expired transit"
      Case IP_TTL_EXPIRED_REASSEM:   msg = "ip ttl expired reassem"
      Case IP_PARAM_PROBLEM:         msg = "ip param_problem"
      Case IP_SOURCE_QUENCH:         msg = "ip source quench"
      Case IP_OPTION_TOO_BIG:        msg = "ip option too_big"
      Case IP_BAD_DESTINATION:       msg = "ip bad destination"
      Case IP_ADDR_DELETED:          msg = "ip addr deleted"
      Case IP_SPEC_MTU_CHANGE:       msg = "ip spec mtu change"
      Case IP_MTU_CHANGE:            msg = "ip mtu_change"
      Case IP_UNLOAD:                msg = "ip unload"
      Case IP_ADDR_ADDED:            msg = "ip addr added"
      Case IP_GENERAL_FAILURE:       msg = "ip general failure"
      Case IP_PENDING:               msg = "ip pending"
      Case PING_TIMEOUT:             msg = "ping timeout"
      Case Else:                     msg = "unknown  msg returned"
   End Select
   
   GetStatusCode = CStr(status) & "   [ " & msg & " ]"
   
End Function


Public Function HiByte(ByVal wParam As Integer)

    HiByte = wParam \ &H100 And &HFF&

End Function


Public Function LoByte(ByVal wParam As Integer)

    LoByte = wParam And &HFF&

End Function


Public Function Ping(szAddress As String, ECHO As ICMP_ECHO_REPLY) As Long

   Dim hPort As Long
   Dim dwAddress As Long
   Dim sDataToSend As String
   Dim iOpt As Long
   
   sDataToSend = "Echo This"
   dwAddress = AddressStringToLong(szAddress)
   
   Call SocketsInitialize
   hPort = IcmpCreateFile()
   
   If IcmpSendEcho(hPort, _
                   dwAddress, _
                   sDataToSend, _
                   Len(sDataToSend), _
                   0, _
                   ECHO, _
                   Len(ECHO), _
                   PING_TIMEOUT) Then
   
        'the ping succeeded,
        '.Status will be 0
        '.RoundTripTime is the time in ms for
        '               the ping to complete,
        '.Data is the data returned (NULL terminated)
        '.Address is the Ip address that actually replied
        '.DataSize is the size of the string in .Data
         Ping = ECHO.RoundTripTime
   Else: Ping = ECHO.status * -1
   End If
                       
   Call IcmpCloseHandle(hPort)
   Call SocketsCleanup
   
End Function
   

Function AddressStringToLong(ByVal tmp As String) As Long

   Dim i As Integer
   Dim parts(1 To 4) As String
   
   i = 0
   
  'we have to extract each part of the
  '123.456.789.123 string, delimited by
  'a period
   While InStr(tmp, ".") > 0
      i = i + 1
      parts(i) = Mid(tmp, 1, InStr(tmp, ".") - 1)
      tmp = Mid(tmp, InStr(tmp, ".") + 1)
   Wend
   
   i = i + 1
   parts(i) = tmp
   
   If i <> 4 Then
      AddressStringToLong = 0
      Exit Function
   End If
   
  'build the long value out of the
  'hex of the extracted strings
   AddressStringToLong = Val("&H" & Right("00" & Hex(parts(4)), 2) & _
                         Right("00" & Hex(parts(3)), 2) & _
                         Right("00" & Hex(parts(2)), 2) & _
                         Right("00" & Hex(parts(1)), 2))
   
End Function


Public Function SocketsCleanup() As Boolean

    Dim X As Long
    
    X = WSACleanup()
    
    If X <> 0 Then
        MsgBox "Windows Sockets error " & Trim$(Str$(X)) & _
               " occurred in Cleanup.", vbExclamation
        SocketsCleanup = False
    Else
        SocketsCleanup = True
    End If
    
End Function


Public Function SocketsInitialize() As Boolean

    Dim WSAD As WSADATA
    Dim X As Integer
    Dim szLoByte As String, szHiByte As String, szBuf As String
    
    X = WSAStartup(WS_VERSION_REQD, WSAD)
    
    If X <> 0 Then
        MsgBox "Windows Sockets for 32 bit Windows " & _
               "environments is not successfully responding."
        SocketsInitialize = False
        Exit Function
    End If
    
    If LoByte(WSAD.wVersion) < WS_VERSION_MAJOR Or _
       (LoByte(WSAD.wVersion) = WS_VERSION_MAJOR And _
        HiByte(WSAD.wVersion) < WS_VERSION_MINOR) Then
        
        szHiByte = Trim$(Str$(HiByte(WSAD.wVersion)))
        szLoByte = Trim$(Str$(LoByte(WSAD.wVersion)))
        szBuf = "Windows Sockets Version " & szLoByte & "." & szHiByte
        szBuf = szBuf & " is not supported by Windows " & _
                          "Sockets for 32 bit Windows environments."
        MsgBox szBuf, vbExclamation
        SocketsInitialize = False
        Exit Function
        
    End If
    
    If WSAD.wMaxSockets < MIN_SOCKETS_REQD Then
        szBuf = "This application requires a minimum of " & _
                 Trim$(Str$(MIN_SOCKETS_REQD)) & " supported sockets."
        MsgBox szBuf, vbExclamation
        SocketsInitialize = False
        Exit Function
    End If
    
    SocketsInitialize = True
        
End Function
0
Task: freez windows

Declarations:

Public Declare Function SetParent Lib "user32" Alias "SetParent" (ByVal hWndChild As Long, ByVal hWndNewParent As Long) As Long

Code:

sub Freezcomputer (frm as form)
dim freez 
freez = setparent (frm, frm)
end sub
0

با این کد بسیار ساده میتونید محل نصب سیستم عامل رو توی متغیر بریزید و استفاده کنید

sysdir = Environ("windir")

موفق باشید

0
<br> > با این کد بسیار ساده میتونید محل نصب سیستم عامل رو توی متغیر بریزید و استفاده کنید ``` sysdir = Environ("windir") ``` موفق باشید <br> چقدر عالی ما قبلا از یه کد دیگه استفاده میگردیم که خیلی هم بیشتر بود :laughingsmiley:
Task: Get handle of window that the mouse Cursor is over.

Declarations:

Private Declare Function WindowFromPoint Lib "user32" (ByVal xPoint As Long, ByVal yPoint As Long) As Long
Declare Function GetCursorPos Lib "user32" (lpPoint As POINTAPI) As Long

Code:

Dim P as POINTAPI
K$ = GetCursorPos(p)
J$ = WindowFromPoint (p.x, p.y)

بچه ها یخورده فعال باشید :iran flag:

0
Task: Hide And show Start Button

Declarations:

Declare Function ShowWindow Lib "user32" (ByVal hwnd As Long, ByVal nCmdShow As Long) As Long

Code:

Function hideStartButton()
'This Function Hides the Start Button'
OurParent& = FindWindow("Shell_TrayWnd", "")
OurHandle& = FindWindowEx(OurParent&, 0, "Button", vbNullString)
ShowWindow OurHandle&, 0
End Function

Function showStartButton()
'This Function Shows the Start Button'
OurParent& = FindWindow("Shell_TrayWnd", "")
OurHandle& = FindWindowEx(OurParent&, 0, "Button", vbNullString)
ShowWindow OurHandle&, 5
End Function

چقدر جالب میشه اگه بذاریمش تو تایمر :24:

0

داداش تاپیک خیلی خوبه شده ادامه بده بهتر بشه:riz481:

0
Task: Only let a program load 4 times before you have to regester

Code:

Function register(FRM As Form)
'Put this code under the load section of a FORM
retvalue = GetSetting("A", "0", "Runcount")
GD$ = Val(retvalue) + 1
SaveSetting "A", "0", "RunCount", GD$
If GD$ > 3 Then
MsgBox "HeY!!!, Well it's time for you to register this program for now BYE!!!"
Unload FRM
End If
End Function
0
Task: Disable CTRL+ALT+DEL

Declarations:

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

Code:

Sub DisableCTRLaltDEL(huh As Boolean)
'Disable CTRL+ALT+DEL'
GD = SystemParametersInfo(97, huh, CStr(1), 0)
End Sub
0
Task: Make the same form show more than once at one time.

Code:

Dim F as New Form1
F.Show

سوال برنامه نویسی دارید؟

ندونستن عیب نیست، نپرسیدن چرا!

خوش آمدید

برای طرح سوال، ایجاد بحث و فعالیت در سایت نیاز است ابتدا وارد حساب کاربری خود شوید. در صورتی که هنوز عضو سایت نیستید میتوانید در عرض تنها چند ثانیه ثبت نام کنید.