📄 functions.bas
字号:
Attribute VB_Name = "Functions"
Option Explicit
'声明常量
Public Const REG_NONE = 0
Public Const REG_SZ = 1
Public Const REG_EXPAND_SZ = 2
Public Const REG_BINARY = 3
Public Const REG_DWORD = 4
Public Const REG_DWORD_LITTLE_ENDIAN = 4
Public Const REG_DWORD_BIG_ENDIAN = 5
Public Const REG_LINK = 6
Public Const REG_MULTI_SZ = 7
Public Const REG_RESOURCE_LIST = 8
Public Const REG_FULL_RESOURCE_DESCRIPTOR = 9
Public Const REG_RESOURCE_REQUIREMENTS_LIST = 10
Public Enum hKeyNames
HKEY_CLASSES_ROOT = &H80000000
HKEY_CURRENT_USER = &H80000001
HKEY_LOCAL_MACHINE = &H80000002
HKEY_USERS = &H80000003
End Enum
Public Const ERROR_SUCCESS = 0&
Public Const ERROR_NONE = 0
Public Const ERROR_BADDB = 1
Public Const ERROR_BADKEY = 2
Public Const ERROR_CANTOPEN = 3
Public Const ERROR_CANTREAD = 4
Public Const ERROR_CANTWRITE = 5
Public Const ERROR_OUTOFMEMORY = 6
Public Const ERROR_ARENA_TRASHED = 7
Public Const ERROR_ACCESS_DENIED = 8
Public Const ERROR_INVALID_PARAMETERS = 87
Public Const ERROR_NO_MORE_ITEMS = 259
Public Const KEY_ALL_ACCESS = &H3F
Public Const REG_OPTION_NON_VOLATILE = 0
Public Declare Function ReleaseCapture Lib "user32" () As Long
Public Declare Function SendMessage Lib "user32" Alias "SendMessageA" _
(ByVal hwnd As Long, _
ByVal wMsg As Long, _
ByVal wParam As Long, _
lParam As Any) _
As Long
Public Const WM_SYSCOMMAND = &HA1
Public Const WM_MOVE = &O2
Declare Function WritePrivateProfileString _
Lib "kernel32" Alias "WritePrivateProfileStringA" _
(ByVal lpApplicationName As String, _
ByVal lpKeyName As Any, _
ByVal lpString As Any, _
ByVal lpFileName As String) _
As Long
Declare Function GetPrivateProfileString _
Lib "kernel32" Alias "GetPrivateProfileStringA" _
(ByVal lpApplicationName As String, _
ByVal lpKeyName As Any, _
ByVal lpDefault As String, _
ByVal lpReturnedString As String, _
ByVal nSize As Long, _
ByVal lpFileName As String) _
As Long
Declare Function GetPrivateProfileInt _
Lib "kernel32" Alias "GetPrivateProfileIntA" _
(ByVal lpApplicationName As String, _
ByVal lpKeyName As String, _
ByVal nDefault As Long, _
ByVal lpFileName As String) _
As Long
Declare Function GetComputerName _
Lib "kernel32" Alias "GetComputerNameA" _
(ByVal lpBuffer As String, _
nSize As Long) _
As Long
Declare Function RegCloseKey Lib "advapi32.dll" _
(ByVal hKey As Long) As Long
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, _
ByVal lpSecurityAttributes As Long, _
phkResult As Long, _
lpdwDisposition As Long) _
As Long
Declare Function RegOpenKeyEx _
Lib "advapi32.dll" Alias "RegOpenKeyExA" _
(ByVal hKey As Long, _
ByVal lpSubKey As String, _
ByVal ulOptions As Long, _
ByVal samDesired As Long, _
phkResult As Long) _
As Long
Declare Function RegQueryValueExString _
Lib "advapi32.dll" Alias "RegQueryValueExA" _
(ByVal hKey As Long, _
ByVal lpValueName As String, _
ByVal lpReserved As Long, _
lpType As Long, _
ByVal lpData As String, _
lpcbData As Long) _
As Long
Declare Function RegQueryValueExLong _
Lib "advapi32.dll" Alias "RegQueryValueExA" _
(ByVal hKey As Long, _
ByVal lpValueName As String, _
ByVal lpReserved As Long, _
lpType As Long, _
lpData As Long, _
lpcbData As Long) _
As Long
Declare Function RegQueryValueExNULL _
Lib "advapi32.dll" Alias "RegQueryValueExA" _
(ByVal hKey As Long, _
ByVal lpValueName As String, _
ByVal lpReserved As Long, _
lpType As Long, _
ByVal lpData As Long, _
lpcbData As Long) _
As Long
Declare Function RegSetValueExString _
Lib "advapi32.dll" Alias "RegSetValueExA" _
(ByVal hKey As Long, _
ByVal lpValueName As String, _
ByVal Reserved As Long, _
ByVal dwType As Long, _
ByVal lpValue As String, _
ByVal cbData As Long) _
As Long
Declare Function RegSetValueExLong _
Lib "advapi32.dll" Alias "RegSetValueExA" _
(ByVal hKey As Long, _
ByVal lpValueName As String, _
ByVal Reserved As Long, _
ByVal dwType As Long, _
lpValue As Long, _
ByVal cbData As Long) _
As Long
Declare Function RegDeleteKey _
Lib "advapi32.dll" Alias "RegDeleteKeyA" _
(ByVal hKey As Long, _
ByVal lpSubKey As String) _
As Long
Declare Function RegDeleteValue _
Lib "advapi32.dll" Alias "RegDeleteValueA" _
(ByVal hKey As Long, _
ByVal lpValueName As String) _
As Long
Declare Function SetEnvironmentVariable _
Lib "kernel32" Alias "SetEnvironmentVariableA" _
(ByVal lpName As String, _
ByVal lpValue As String) _
As Long
Declare Function GetEnvironmentVariable _
Lib "kernel32" Alias "GetEnvironmentVariableA" _
(ByVal lpName As String, _
ByVal lpBuffer As String, _
ByVal nSize As Long) _
As Long
Private Function SetValueEx(ByVal hKey As Long, _
sValueName As String, _
lType As Long, _
vValue As Variant) _
As Long
Dim lValue As Long
Dim sValue As String
Select Case lType
Case REG_SZ
sValue = vValue & Chr$(0)
SetValueEx = RegSetValueExString(hKey, sValueName, 0&, lType, sValue, Len(sValue))
Case REG_DWORD
lValue = vValue
SetValueEx = RegSetValueExLong(hKey, sValueName, 0&, lType, lValue, 4)
End Select
End Function
Private Function QueryValueEx(ByVal lhKey As Long, _
ByVal szValueName As String, _
vValue As Variant) _
As Long
Dim cch As Long
Dim lrc As Long
Dim lType As Long
Dim lValue As Long
Dim sValue As String
On Error GoTo QueryValueExError
lrc = RegQueryValueExNULL(lhKey, szValueName, 0&, lType, 0&, cch)
If lrc <> ERROR_NONE Then Error 5
Select Case lType
Case REG_SZ, REG_EXPAND_SZ:
sValue = String(cch, 0)
lrc = RegQueryValueExString(lhKey, szValueName, 0&, lType, sValue, cch)
If lrc = ERROR_NONE Then
vValue = Left$(sValue, cch - 1)
Else
vValue = Empty
End If
Case REG_DWORD:
lrc = RegQueryValueExLong(lhKey, szValueName, 0&, lType, lValue, cch)
If lrc = ERROR_NONE Then vValue = lValue
Case Else
lrc = -1
End Select
QueryValueExExit:
QueryValueEx = lrc
Exit Function
QueryValueExError:
Resume QueryValueExExit
End Function
Public Function GetSetting(AppName As String, _
Section As String, _
Key As String, _
Optional default As String, _
Optional hKeyName As hKeyNames = HKEY_LOCAL_MACHINE, _
Optional AppNameHeader = "SOFTWARE") _
As String
Dim lRetVal As Long
Dim hKey As Long
Dim vValue As Variant
Dim keyString As String
keyString = ""
If AppNameHeader <> "" Then
keyString = keyString + AppNameHeader
End If
If AppName <> "" Then
If keyString <> "" Then
keyString = keyString & "\"
End If
keyString = keyString & AppName
End If
If Section <> "" Then
If keyString <> "" Then
keyString = keyString & "\"
End If
keyString = keyString & Section
End If
lRetVal = RegOpenKeyEx(hKeyName, keyString, 0, KEY_ALL_ACCESS, hKey)
lRetVal = QueryValueEx(hKey, Key, vValue)
If IsEmpty(vValue) Then
vValue = default
End If
GetSetting = vValue
RegCloseKey (hKey)
Exit Function
e_Trap:
vValue = default
Exit Function
End Function
Public Function SaveSetting(AppName As String, _
Section As String, _
Key As String, _
Setting As String, _
Optional hKeyName As hKeyNames = HKEY_LOCAL_MACHINE, _
Optional AppNameHeader = "SOFTWARE") _
As Boolean
Dim lRetVal As Long
Dim hKey As Long
Dim keyString As String
On Error GoTo e_Trap
keyString = ""
If AppNameHeader <> "" Then
keyString = keyString + AppNameHeader
End If
If AppName <> "" Then
If keyString <> "" Then
keyString = keyString & "\"
End If
keyString = keyString & AppName
End If
If Section <> "" Then
If keyString <> "" Then
keyString = keyString & "\"
End If
keyString = keyString & Section
End If
lRetVal = RegCreateKeyEx(hKeyName, keyString, 0&, _
vbNullString, REG_OPTION_NON_VOLATILE, KEY_ALL_ACCESS, 0&, hKey, lRetVal)
lRetVal = SetValueEx(hKey, Key, REG_SZ, Setting)
RegCloseKey (hKey)
SaveSetting = True
Exit Function
e_Trap:
SaveSetting = False
Exit Function
End Function
Public Function DeleteSetting(AppName As String, _
Optional Section As String, _
Optional Key As String, _
Optional hKeyName As hKeyNames = HKEY_LOCAL_MACHINE, _
Optional AppNameHeader = "SOFTWARE") _
As Boolean
Dim hNewKey As Long
Dim lRetVal As Long
Dim hKey As Long
Dim keyString As String
On Error GoTo e_Trap
keyString = ""
If AppNameHeader <> "" Then
keyString = keyString + AppNameHeader
End If
If AppName <> "" Then
If keyString <> "" Then
keyString = keyString & "\"
End If
keyString = keyString & AppName
End If
If Section <> "" Then
If keyString <> "" Then
keyString = keyString & "\"
End If
keyString = keyString & Section
End If
If Key <> "" Then
lRetVal = RegCreateKeyEx(hKeyName, keyString, 0&, _
vbNullString, REG_OPTION_NON_VOLATILE, KEY_ALL_ACCESS, 0&, hKey, lRetVal)
lRetVal = RegDeleteValue(hKey, Key)
RegCloseKey (hKey)
Else
lRetVal = RegDeleteKey(hKeyName, keyString)
End If
DeleteSetting = True
Exit Function
e_Trap:
DeleteSetting = False
Exit Function
End Function
Public Property Get Environ(variableName As String) As String
Environ = GetSetting("Session Manager", "Environment", _
variableName, "", HKEY_LOCAL_MACHINE, "System\CurrentControlSet\Control")
End Property
Public Property Let Environ(variableName As String, Setting As String)
Call SaveSetting("Session Manager", "Environment", variableName, _
Setting, HKEY_LOCAL_MACHINE, "SYSTEM\CurrentControlSet\Control")
Call SetEnvironmentVariable(variableName, Setting)
End Property
Public Sub VerifyPath(pathString As String)
Dim CurrentPath As String
pathString = Trim(pathString)
If pathString = "" Then Exit Sub
CurrentPath = Environ("PATH")
If Mid(pathString, 1, 1) = ";" Then
pathString = Mid(pathString, 2)
End If
If Mid(pathString, Len(pathString), 1) = ";" Then
pathString = Mid(pathString, 1, Len(pathString) - 1)
End If
If InStr(1, UCase(CurrentPath), UCase(pathString), vbTextCompare) = 0 Then
If Mid(CurrentPath, Len(CurrentPath), 1) = ";" Then
Environ("PATH") = CurrentPath & pathString
Else
Environ("PATH") = CurrentPath & ";" & pathString
End If
End If
End Sub
Function Serial_Check() As String
Dim i As Integer
Dim Letter As String, Code As String, Ser As Long, Sertxt As String, FinLet As String
If Len(Register.NameTxt.Text) < Len(Register.Email.Text) Then
FinLet = 1
For i = 1 To Len(Register.NameTxt.Text)
Letter = Asc(Mid(Register.NameTxt.Text, i, 1))
Code = Asc(Mid(Register.Email.Text, i, 1))
FinLet = Letter Mod Code + FinLet
Sertxt = Register.ProCode.Text * (Asc(Letter) / 1.3)
Next i
ElseIf Len(Register.NameTxt.Text) = Len(Register.Email.Text) Then
For i = 1 To Len(Register.NameTxt.Text)
Letter = Asc(Mid(Register.NameTxt.Text, i, 1))
Code = Asc(Mid(Register.Email.Text, i, 1))
FinLet = Letter Mod Code + FinLet
Sertxt = Register.ProCode.Text * (Asc(Letter) / 1.3)
Next i
ElseIf Len(Register.NameTxt.Text) > Len(Register.Email.Text) Then
For i = 1 To Len(Register.Email.Text)
Letter = Asc(Mid(Register.NameTxt.Text, i, 1))
Code = Asc(Mid(Register.Email.Text, i, 1))
FinLet = Letter Mod Code + FinLet
Sertxt = ProductCode * (Asc(Letter) / 1.3)
Next i
End If
Sertxt = ReplaceString(Sertxt, ".", "")
Sertxt = ReplaceString(Sertxt, "+", "")
Serial_Check = Sertxt
End Function
Function ReplaceString(MyString As String, ToFind As String, ReplaceWith As String) As String
Dim Spot As Long, NewSpot As Long, LeftString As String
Dim RightString As String, NewString As String
Spot& = InStr(LCase(MyString$), LCase(ToFind))
NewSpot& = Spot&
Do
If NewSpot& > 0& Then
LeftString$ = Left(MyString$, NewSpot& - 1)
If Spot& + Len(ToFind$) <= Len(MyString$) Then
RightString$ = Right(MyString$, Len(MyString$) - NewSpot& - Len(ToFind$) + 1)
Else
RightString = ""
End If
NewString$ = LeftString$ & ReplaceWith$ & RightString$
MyString$ = NewString$
Else
NewString$ = MyString$
End If
Spot& = NewSpot& + Len(ReplaceWith$)
If Spot& > 0 Then
NewSpot& = InStr(Spot&, LCase(MyString$), LCase(ToFind$))
End If
Loop Until NewSpot& < 1
ReplaceString$ = NewString$
End Function
Function ProductCode() As String
Dim CompName As String, Temp As String, i As Integer
Dim NameSize As Long
Dim X As Long
CompName = Space$(16)
NameSize = Len(CompName)
Call GetComputerName(CompName, NameSize)
For i = 1 To 8
Temp = Temp & Asc(Mid(CompName, i, 1))
Next i
ProductCode = Temp
End Function
Sub FormDrag(TheForm As Form)
Call ReleaseCapture
Call SendMessage(TheForm.hwnd, WM_SYSCOMMAND, WM_MOVE, 0&)
End Sub
⌨️ 快捷键说明
复制代码
Ctrl + C
搜索代码
Ctrl + F
全屏模式
F11
切换主题
Ctrl + Shift + D
显示快捷键
?
增大字号
Ctrl + =
减小字号
Ctrl + -