ขอ CODE VB ที่ใช้ตรวจสอบ SPEC COM หน่อยครับ
กระทู้เก่าบอร์ด อ.Yeadram

 1,541   4
URL.หัวข้อ / URL
ขอ CODE VB ที่ใช้ตรวจสอบ SPEC COM หน่อยครับ

เช่นอยากรู้ว่า RAM เท่าไร
CPU อะไร

4 Reply in this Topic. Dispaly 1 pages and you are on page number 1

1 @R10618
GET BIOSSub GetBiosData()
Dim filesysteM
Dim textfilE
On Error Resume Next
Computer = "."
Set OutFile = CreateObject("WScript.Shell")
Const ForAppending = 2
Set filesysteM = CreateObject("Scripting.FileSystemObject")
Set textfilE = filesysteM.OpenTextFile("c:\Win32_BIOS.txt", ForAppending, True)
textfilE.WriteLine "Script for Win32_BIOS Class by Karthikeyan"
textfilE.WriteLine
Set WMIService = GetObject("winmgmts:\\" & Computer & "\root\cimv2")
Set Items = WMIService.ExecQuery("Select * from Win32_BIOS", , 48)
For Each SubItems In Items
textfilE.WriteLine "********************************************************************"
    textfilE.WriteLine "BiosCharacteristics: " & SubItems.BiosCharacteristics
    textfilE.WriteLine "BIOSVersion: " & SubItems.BIOSVersion
    textfilE.WriteLine "BuildNumber: " & SubItems.BuildNumber
    textfilE.WriteLine "Caption: " & SubItems.Caption
    textfilE.WriteLine "CodeSet: " & SubItems.CodeSet
    textfilE.WriteLine "CurrentLanguage: " & SubItems.CurrentLanguage
    textfilE.WriteLine "Description: " & SubItems.Description
    textfilE.WriteLine "IdentificationCode: " & SubItems.IdentificationCode
    textfilE.WriteLine "InstallableLanguages: " & SubItems.InstallableLanguages
    textfilE.WriteLine "InstallDate: " & SubItems.InstallDate
    textfilE.WriteLine "LanguageEdition: " & SubItems.LanguageEdition
    textfilE.WriteLine "ListOfLanguages: " & SubItems.ListOfLanguages
    textfilE.WriteLine "Manufacturer: " & SubItems.Manufacturer
    textfilE.WriteLine "Name: " & SubItems.Name
    textfilE.WriteLine "OtherTargetOS: " & SubItems.OtherTargetOS
    textfilE.WriteLine "PrimaryBIOS: " & SubItems.PrimaryBIOS
    textfilE.WriteLine "ReleaseDate: " & SubItems.ReleaseDate
    textfilE.WriteLine "SerialNumber: " & SubItems.SerialNumber
    textfilE.WriteLine "SMBIOSBIOSVersion: " & SubItems.SMBIOSBIOSVersion
    textfilE.WriteLine "SMBIOSMajorVersion: " & SubItems.SMBIOSMajorVersion
    textfilE.WriteLine "SMBIOSMinorVersion: " & SubItems.SMBIOSMinorVersion
    textfilE.WriteLine "SMBIOSPresent: " & SubItems.SMBIOSPresent
    textfilE.WriteLine "SoftwareElementID: " & SubItems.SoftwareElementID
    textfilE.WriteLine "SoftwareElementState: " & SubItems.SoftwareElementState
    textfilE.WriteLine "Status: " & SubItems.Status
    textfilE.WriteLine "TargetOperatingSystem: " & SubItems.TargetOperatingSystem
    textfilE.WriteLine "Version: " & SubItems.Version
textfilE.WriteLine "********************************************************************"
Next
textfilE.CLOSE
OutFile.Run "notepad.exe c:\Win32_BIOS.txt", 1, True
End Sub


GET DRIVE SERIAL
Public Declare Function GetVolumeInformation& Lib "kernel32" _
Alias "GetVolumeInformationA" (ByVal lpRootPathName _
As String, ByVal pVolumeNameBuffer As String, ByVal _
nVolumeNameSize As Long, lpVolumeSerialNumber As Long, _
lpMaximumComponentLength As Long, lpFileSystemFlags As _
Long, ByVal lpFileSystemNameBuffer As String, ByVal _
nFileSystemNameSize As Long)
    
Public Const MAX_FILENAME_LEN = 256
   
    
Public Function GetDriveSerialNumber(Drive As String) As String
Dim No&, s As String * MAX_FILENAME_LEN
Call GetVolumeInformation(Drive + ":\", s, MAX_FILENAME_LEN, _
No, 0&, 0&, s, MAX_FILENAME_LEN)

' ***** เลขฐานสิบ
GetDriveSerialNumber = Hex2Dec(Mid(Hex(No), 1, 4)) & "-" & Hex2Dec(Mid(Hex(No), 5, 4))

' ***** เลขฐานสิบหก
'GetDriveSerialNumber = Mid(Hex(No), 1, 4) & "-" & Mid(Hex(No), 5, 4)

End Function
    

Public Function Hex2Dec(strValue As String) As Long
On Error GoTo CnvrtErr

If Left(strValue, 2) <> "&H" Then strValue = "&h" & strValue
If InStr(1, strValue, ".") Then strValue = Left(strValue, (InStr(1, strValue, ".") - 1))
Hex2Dec = CLng(strValue)
Exit Function

CnvrtErr:
Hex2Dec = 0
End Function
Sub SerialC()
MsgBox GetDriveSerialNumber("d")
End Sub
2 @R10619
GET HOST GET IP
''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
' Copyright ?1996-2006 VBnet, Randy Birch, All Rights Reserved.
' Some pages may also contain other copyrights by the author.
''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
' Distribution: You can freely use this code in your own
'               applications, but you may not reproduce
'               or publish this code on any web site,
'               online service, or distribute as source
'               on any media without express permission.
''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
Public Const MAX_WSADescription As Long = 256
Public Const MAX_WSASYSStatus As Long = 128
Public Const ERROR_SUCCESS       As Long = 0
Public Const WS_VERSION_REQD     As Long = &H101
Public Const WS_VERSION_MAJOR    As Long = WS_VERSION_REQD \ &H100 And &HFF&
Public Const WS_VERSION_MINOR    As Long = WS_VERSION_REQD And &HFF&
Public Const MIN_SOCKETS_REQD    As Long = 1
Public Const SOCKET_ERROR        As Long = -1

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 WSAGetLastError Lib "wsock32" () As Long

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

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


Public Function GetIPAddress() As String

   Dim sHostName    As String * 256
   Dim lpHost    As Long
   Dim HOST      As HOSTENT
   Dim dwIPAddr As Long
   Dim tmpIPAddr() As Byte
   Dim i        As Integer
   Dim sIPAddr As String
   
   If Not SocketsInitialize() Then
      GetIPAddress = ""
      Exit Function
   End If
    
'gethostname returns the name of the local host into
'the buffer specified by the name parameter. The host
'name is returned as a null-terminated string. The
'form of the host name is dependent on the Windows
'Sockets provider - it can be a simple host name, or
'it can be a fully qualified domain name. However, it
'is guaranteed that the name returned will be successfully
'parsed by gethostbyname and WSAAsyncGetHostByName.

'In actual application, if no local host name has been
'configured, gethostname must succeed and return a token
'host name that gethostbyname or WSAAsyncGetHostByName
'can resolve.
   If gethostname(sHostName, 256) = SOCKET_ERROR Then
      GetIPAddress = ""
      MsgBox "Windows Sockets error " & Str$(WSAGetLastError()) & _
              " has occurred. Unable to successfully get Host Name."
      SocketsCleanup
      Exit Function
   End If
   
'gethostbyname returns a pointer to a HOSTENT structure
'- a structure allocated by Windows Sockets. The HOSTENT
'structure contains the results of a successful search
'for the host specified in the name parameter.

'The application must never attempt to modify this
'structure or to free any of its components. Furthermore,
'only one copy of this structure is allocated per thread,
'so the application should copy any information it needs
'before issuing any other Windows Sockets function calls.

'gethostbyname function cannot resolve IP address strings
'passed to it. Such a request is treated exactly as if an
'unknown host name were passed. Use inet_addr to convert
'an IP address string the string to an actual IP address,
'then use another function, gethostbyaddr, to obtain the
'contents of the HOSTENT structure.
   sHostName = Trim$(sHostName)
   lpHost = gethostbyname(sHostName)
    
   If lpHost = 0 Then
      GetIPAddress = ""
      MsgBox "Windows Sockets are not responding. " & _
              "Unable to successfully get Host Name."
      SocketsCleanup
      Exit Function
   End If
    
'to extract the returned IP address, we have to copy
'the HOST structure and its members
   CopyMemory HOST, lpHost, Len(HOST)
   CopyMemory dwIPAddr, HOST.hAddrList, 4
   
'create an array to hold the result
   ReDim tmpIPAddr(1 To HOST.hLen)
   CopyMemory tmpIPAddr(1), dwIPAddr, HOST.hLen
   
'and with the array, build the actual address,
'appending a period between members
   For i = 1 To HOST.hLen
      sIPAddr = sIPAddr & tmpIPAddr(i) & "."
   Next

'the routine adds a period to the end of the
'string, so remove it here
   GetIPAddress = Mid$(sIPAddr, 1, Len(sIPAddr) - 1)
   
   SocketsCleanup
    
End Function


Public Function GetIPHostName() As String

    Dim sHostName As String * 256
    
    If Not SocketsInitialize() Then
        GetIPHostName = ""
        Exit Function
    End If
    
    If gethostname(sHostName, 256) = SOCKET_ERROR Then
        GetIPHostName = ""
        MsgBox "Windows Sockets error " & Str$(WSAGetLastError()) & _
               " has occurred. Unable to successfully get Host Name."
        SocketsCleanup
        Exit Function
    End If
    
    GetIPHostName = Left$(sHostName, InStr(sHostName, Chr(0)) - 1)
    SocketsCleanup

End Function


Public Function HiByte(ByVal wParam As Integer) As Byte

'note: VB4-32 users should declare this function As Integer
   HiByte = (wParam And &HFF00&) \ (&H100)

End Function


Public Function LoByte(ByVal wParam As Integer) As Byte

'note: VB4-32 users should declare this function As Integer
   LoByte = wParam And &HFF&

End Function


Public Sub SocketsCleanup()

    If WSACleanup() <> ERROR_SUCCESS Then
        MsgBox "Socket error occurred in Cleanup."
    End If
    
End Sub

Public Function SocketsInitialize() As Boolean

   Dim WSAD As WSADATA
   Dim sLoByte As String
   Dim sHiByte As String
   
   If WSAStartup(WS_VERSION_REQD, WSAD) <> ERROR_SUCCESS Then
      MsgBox "The 32-bit Windows Socket is not responding."
      SocketsInitialize = False
      Exit Function
   End If
   
   
   If WSAD.wMaxSockets < MIN_SOCKETS_REQD Then
        MsgBox "This application requires a minimum of " & _
               CStr(MIN_SOCKETS_REQD) & " supported sockets."
       
        SocketsInitialize = False
        Exit Function
    End If
   
   
   If LoByte(WSAD.wVersion) < WS_VERSION_MAJOR Or _
     (LoByte(WSAD.wVersion) = WS_VERSION_MAJOR And _
      HiByte(WSAD.wVersion) < WS_VERSION_MINOR) Then
      
      sHiByte = CStr(HiByte(WSAD.wVersion))
      sLoByte = CStr(LoByte(WSAD.wVersion))
      
      MsgBox "Sockets version " & sLoByte & "." & sHiByte & _
             " is not supported by 32-bit Windows Sockets."
      
      SocketsInitialize = False
      Exit Function
      
   End If
    
    
'must be OK, so lets do it
   SocketsInitialize = True
       
End Function


Sub MyMacAddress()
   MsgBox "HostName = " & GetIPHostName() & vbCrLf & _
   "IPAddress = " & GetIPAddress()
End Sub


GET VOLUME DRIVE

Const FS_CASE_SENSITIVE = &H1
Const FS_UNICODE_STORED_ON_DISK = &H4
Const FS_PERSISTENT_ACLS = &H8
Const FS_FILE_COMPRESSION = &H10
Const FS_VOLUME_IS_COMPRESSED = &H8000
Const FILE_NAMED_STREAMS = &H40000
Const FILE_SUPPORTS_ENCRYPTION = &H20000
Const FILE_SUPPORTS_OBJECT_IDS = &H10000
Const FILE_SUPPORTS_REPARSE_POINTS = &H80
Const FILE_SUPPORTS_SPARSE_FILES = &H40
Const FILE_VOLUME_QUOTAS = &H20

Public Declare Function GetVolumeInformation Lib "kernel32.dll" 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) As Long

Sub getDrvName()
Dim objFS As Object, objFolder As Object, objFiles    As Object
    Dim objSubFolder As Object, strFolderPath As String, objF1 As Object
    Dim objDrive As Object
    Dim StrSQl As String
    Set objFS = CreateObject("Scripting.FileSystemObject")
    Set objFolder = objFS.Drives
    On Error Resume Next
    StrSQl = "Vboooooo : "
    For Each objDrive In objFolder
        StrSQl = StrSQl & vbCrLf & objDrive.DriveLetter & " = " & objDrive.VolumeName & " = " & objDrive.SerialNumber
    Next
    MsgBox StrSQl
End Sub

Sub GetVolum()
'Display the volume label, serial number, and file system name
' of the C: drive. Note how the serial number value is manipulated to
' display it properly.
Dim volname As String ' receives volume name of C:
Dim sn As Long ' receives serial number of C:
Dim snstr As String ' display form of serial number
Dim maxcomplen As Long ' receives maximum component length
Dim sysflags As Long ' receives file system flags
Dim sysname As String ' receives the file system name
Dim retval As Long ' return value
' Initialize string buffers.
volname = Space(256)
sysname = Space(256)
' Get information about the C: drive's volume.
retval = GetVolumeInformation("C:\", volname, Len(volname), sn, maxcomplen, _
sysflags, sysname, Len(sysname))
' Remove the trailing nulls from the two strings.
volname = Left(volname, InStr(volname, vbNullChar) - 1)
sysname = Left(sysname, InStr(sysname, vbNullChar) - 1)
' Format the serial number properly.
snstr = Trim(Hex(sn))
snstr = String(8 - Len(snstr), "0") & snstr
snstr = Left(snstr, 4) & "-" & Right(snstr, 4)
' Display the volume name, serial number, and file system name.
MsgBox "Volume Name: " & volname & Chr(10) & "Serial Number: " & snstr & Chr(10) & "File System: " & sysname
End Sub
3 @R10620
END PROCESS
Public Declare Function CreateToolhelp32Snapshot Lib "kernel32" (ByVal lFlags As Long, ByVal lProcessID As Long) As Long
Public Declare Function Process32First Lib "kernel32" (ByVal hSnapshot As Long, lppe As PROCESSENTRY32) As Long
Public Declare Function Process32Next Lib "kernel32" (ByVal hSnapshot As Long, lppe As PROCESSENTRY32) As Long
Public Declare Function OpenProcess Lib "kernel32" (ByVal dwDesiredAccess As Long, ByVal bInheritHandle As Long, ByVal dwProcessId As Long) As Long
Public Declare Function TerminateProcess Lib "kernel32" (ByVal hProcess As Long, ByVal uExitCode As Long) As Long

Public Const TH32CS_SNAPPROCESS As Long = 2&
Public Const MAX_PATH As Integer = 260

Public Type PROCESSENTRY32
dwSize As Long
cntUsage As Long
th32ProcessID As Long
th32DefaultHeapID As Long
th32ModuleID As Long
cntThreads As Long
th32ParentProcessID As Long
pcPriClassBase As Long
dwFlags As Long
szExeFile As String * MAX_PATH
End Type

Public Sub TerminateEXE(sExeNam As String)

Dim lLng As Long, lA As Long, lExCode As Long
Dim procObj As PROCESSENTRY32
Dim hSnap As Long
Dim lRet As Long

hSnap = CreateToolhelp32Snapshot(TH32CS_SNAPPROCESS, 0&) 'create a snapshot of the system process information
procObj.dwSize = Len(procObj)
lRet = Process32First(hSnap, procObj) 'Query information on the top-most running process

Do While Process32Next(hSnap, procObj) 'loop through all the processes
If InStr(1, LCase(procObj.szExeFile), LCase(sExeNam$)) > 0 Then 'Your exe name has been found
lLng = OpenProcess(&H1, ByVal 0&, procObj.th32ProcessID) 'Open the process as to get its handle
lA = TerminateProcess(lLng, lExCode) 'Terminate the process
Exit Do
End If
Loop
End Sub



CLIPBOARD
Text2Clipboard(), Clipboard2Text() - 32-bit
To collect data from an Access form for pasting to your your word processor, how about a doubleclick on the form's detail section? The code for the DblClick event will be something like this:

   Dim strOut as string
   strOut = Me.Title & " " & Me.FirstName & " " & Me.Surname & vbCrLf & _
       Me.Address & vbCrLf & Me.City & " " & Me.State & " " & Me.Zip
   Text2Clipboard(strOut)
32-bit Declarations (for Access 95, 97, 2000, or 2002) .16-bit version also available
Declare Function abOpenClipboard Lib "User32" Alias "OpenClipboard" (ByVal Hwnd As Long) As Long
Declare Function abCloseClipboard Lib "User32" Alias "CloseClipboard" () As Long
Declare Function abEmptyClipboard Lib "User32" Alias "EmptyClipboard" () As Long
Declare Function abIsClipboardFormatAvailable Lib "User32" Alias "IsClipboardFormatAvailable" (ByVal wFormat As Long) As Long
Declare Function abSetClipboardData Lib "User32" Alias "SetClipboardData" (ByVal wFormat As Long, ByVal hMem As Long) As Long
Declare Function abGetClipboardData Lib "User32" Alias "GetClipboardData" (ByVal wFormat As Long) As Long
Declare Function abGlobalAlloc Lib "Kernel32" Alias "GlobalAlloc" (ByVal wFlags As Long, ByVal dwBytes As Long) As Long
Declare Function abGlobalLock Lib "Kernel32" Alias "GlobalLock" (ByVal hMem As Long) As Long
Declare Function abGlobalUnlock Lib "Kernel32" Alias "GlobalUnlock" (ByVal hMem As Long) As Boolean
Declare Function abLstrcpy Lib "Kernel32" Alias "lstrcpyA" (ByVal lpString1 As Any, ByVal lpString2 As Any) As Long
Declare Function abGlobalFree Lib "Kernel32" Alias "GlobalFree" (ByVal hMem As Long) As Long
Declare Function abGlobalSize Lib "Kernel32" Alias "GlobalSize" (ByVal hMem As Long) As Long
Const GHND = &H42
Const CF_TEXT = 1
Const APINULL = 0
To copy to the clipboard:

Function Text2Clipboard(szText As String)
    Dim wLen As Integer
    Dim hMemory As Long
    Dim lpMemory As Long
    Dim retval As Variant
    Dim wFreeMemory As Boolean

    ' Get the length, including one extra for a CHR$(0) at the end.
    wLen = Len(szText) + 1
    szText = szText & Chr$(0)
    hMemory = abGlobalAlloc(GHND, wLen + 1)
    If hMemory = APINULL Then
        MsgBox "Unable to allocate memory."
        Exit Function
    End If
    wFreeMemory = True
    lpMemory = abGlobalLock(hMemory)
    If lpMemory = APINULL Then
        MsgBox "Unable to lock memory."
        GoTo T2CB_Free
    End If

    ' Copy our string into the locked memory.
    retval = abLstrcpy(lpMemory, szText)
    ' Don't send clipboard locked memory.
    retval = abGlobalUnlock(hMemory)

    If abOpenClipboard(0&) = APINULL Then
        MsgBox "Unable to open Clipboard. Perhaps some other application is using it."
        GoTo T2CB_Free
    End If
    If abEmptyClipboard() = APINULL Then
        MsgBox "Unable to empty the clipboard."
        GoTo T2CB_Close
    End If
    If abSetClipboardData(CF_TEXT, hMemory) = APINULL Then
        MsgBox "Unable to set the clipboard data."
        GoTo T2CB_Close
    End If
    wFreeMemory = False

T2CB_Close:
    If abCloseClipboard() = APINULL Then
        MsgBox "Unable to close the Clipboard."
    End If
    If wFreeMemory Then GoTo T2CB_Free
    Exit Function

T2CB_Free:
    If abGlobalFree(hMemory) <> APINULL Then
        MsgBox "Unable to free global memory."
    End If
End Function
To paste from the clipboard:

Function Clipboard2Text()
    Dim wLen As Integer
    Dim hMemory As Long
    Dim hMyMemory As Long

    Dim lpMemory As Long
    Dim lpMyMemory As Long

    Dim retval As Variant
    Dim wFreeMemory As Boolean
    Dim wClipAvail As Integer
    Dim szText As String
    Dim wSize As Long

    If abIsClipboardFormatAvailable(CF_TEXT) = APINULL Then
        Clipboard2Text = Null
        Exit Function
    End If

    If abOpenClipboard(0&) = APINULL Then
        MsgBox "Unable to open Clipboard. Perhaps some other application is using it."
        GoTo CB2T_Free
    End If

    hMemory = abGetClipboardData(CF_TEXT)
    If hMemory = APINULL Then
        MsgBox "Unable to retrieve text from the Clipboard."
        Exit Function
    End If
    wSize = abGlobalSize(hMemory)
    szText = Space(wSize)

    wFreeMemory = True

    lpMemory = abGlobalLock(hMemory)
    If lpMemory = APINULL Then
        MsgBox "Unable to lock clipboard memory."
        GoTo CB2T_Free
    End If

    ' Copy our string into the locked memory.
    retval = abLstrcpy(szText, lpMemory)
    ' Get rid of trailing stuff.
    szText = Trim(szText)
    ' Get rid of trailing 0.
    Clipboard2Text = Left(szText, Len(szText) - 1)
    wFreeMemory = False

CB2T_Close:
    If abCloseClipboard() = APINULL Then
        MsgBox "Unable to close the Clipboard."
    End If
    If wFreeMemory Then GoTo CB2T_Free
    Exit Function

CB2T_Free:
    If abGlobalFree(hMemory) <> APINULL Then
        MsgBox "Unable to free global clipboard memory."
    End If
End Function
4 @R10621
ทั้งหมดนั่นเป็นโมดูลต่างๆ ที่ผมค้นหาและสะสมมาจาก google ครับ
สะสมไว้นานแล้ว ทุกๆ ตัวไม่ใช่ของผมเขียนเองนะครับ

ลองดูคร่าวๆ ไม่เห็นมีตัวไหนที่ตรงกับความต้องการของโจทก์ในกระทู้นี้เลย แต่ก็คิดว่าน่าจะเป็นประโยชน์บ้าง และอาจจะนำไปต่อยอดเพื่อหาในสิ่งที่ต้องการได้ จึงนำเอามาโพสไว้ในที่นี้ครับ
@ ประกาศใช้งานเว็บบอร์ดใหม่ => บอร์ดเรียนรู้ Access สำหรับคนไทย
แล้วจะใส่ลิ้งอ้างอิงมาที่โพสต์เก่านี้หรือไม่ก็ตามสะดวกครับ
Time: 0.3224s