Bruce Bruen
bbruen at bigpond.com
Thu Jun 19 18:31:57 CDT 2003
Jim,
The following is a quick hack of some AllAPI (R.I.P.) code you could use
as a starting point.
==================================START
Option Compare Database
Option Explicit
Private Declare Function InternetAttemptConnect Lib "wininet" ( _
ByVal dwReserved As Long) As Long
'Add this code to a module and set the Project's Startup Object to 'Sub
Main'
' (-> Project Menu -> Project Properties -> General Tab)
Private Const RESOURCE_CONNECTED As Long = &H1&
Private Const RESOURCE_GLOBALNET As Long = &H2&
Private Const RESOURCE_REMEMBERED As Long = &H3&
Private Const RESOURCEDISPLAYTYPE_DIRECTORY& = &H9
Private Const RESOURCEDISPLAYTYPE_DOMAIN& = &H1
Private Const RESOURCEDISPLAYTYPE_FILE& = &H4
Private Const RESOURCEDISPLAYTYPE_GENERIC& = &H0
Private Const RESOURCEDISPLAYTYPE_GROUP& = &H5
Private Const RESOURCEDISPLAYTYPE_NETWORK& = &H6
Private Const RESOURCEDISPLAYTYPE_ROOT& = &H7
Private Const RESOURCEDISPLAYTYPE_SERVER& = &H2
Private Const RESOURCEDISPLAYTYPE_SHARE& = &H3
Private Const RESOURCEDISPLAYTYPE_SHAREADMIN& = &H8
Private Const RESOURCETYPE_ANY As Long = &H0&
Private Const RESOURCETYPE_DISK As Long = &H1&
Private Const RESOURCETYPE_PRINT As Long = &H2&
Private Const RESOURCETYPE_UNKNOWN As Long = &HFFFF&
Private Const RESOURCEUSAGE_ALL As Long = &H0&
Private Const RESOURCEUSAGE_CONNECTABLE As Long = &H1&
Private Const RESOURCEUSAGE_CONTAINER As Long = &H2&
Private Const RESOURCEUSAGE_RESERVED As Long = &H80000000
Private Const NO_ERROR = 0
Private Const ERROR_MORE_DATA = 234 'L //
dderror
Private Const RESOURCE_ENUM_ALL As Long = &HFFFF
Private Type NETRESOURCE
dwScope As Long
dwType As Long
dwDisplayType As Long
dwUsage As Long
pLocalName As Long
pRemoteName As Long
pComment As Long
pProvider As Long
End Type
Private Type NETRESOURCE_REAL
dwScope As Long
dwType As Long
dwDisplayType As Long
dwUsage As Long
sLocalName As String
sRemoteName As String
sComment As String
sProvider As String
End Type
Private Declare Function WNetAddConnection2 Lib "mpr.dll" Alias
"WNetAddConnection2A" (lpNetResource As NETRESOURCE, ByVal lpPassword As
String, ByVal lpUserName As String, ByVal dwFlags As Long) As Long
Private Declare Function WNetOpenEnum Lib "mpr.dll" Alias
"WNetOpenEnumA" (ByVal dwScope As Long, ByVal dwType As Long, ByVal
dwUsage As Long, lpNetResource As Any, lphEnum As Long) As Long
Private Declare Function WNetEnumResource Lib "mpr.dll" Alias
"WNetEnumResourceA" (ByVal hEnum As Long, lpcCount As Long, lpBuffer As
NETRESOURCE, lpBufferSize As Long) As Long
Private Declare Function WNetCloseEnum Lib "mpr.dll" (ByVal hEnum As
Long) As Long
Private Declare Function VarPtrAny Lib "vb40032.dll" Alias "VarPtr"
(lpObject As Any) As Long
Private Declare Sub CopyMem Lib "kernel32" Alias "RtlMoveMemory" (lpTo
As Any, lpFrom As Any, ByVal lLen As Long)
Private Declare Sub CopyMemByPtr Lib "kernel32" Alias "RtlMoveMemory"
(ByVal lpTo As Long, ByVal lpFrom As Long, ByVal lLen As Long)
Private Declare Function lstrcpy Lib "kernel32" Alias "lstrcpyA" (ByVal
lpString1 As String, ByVal lpString2 As Any) As Long
Private Declare Function lstrlen Lib "kernel32" Alias "lstrlenA" (ByVal
lpString As Any) As Long
Private Declare Function getusername Lib "advapi32.dll" Alias
"GetUserNameA" (ByVal lpBuffer As String, nSize As Long) As Long
Private Declare Function GetComputerName Lib "kernel32" Alias
"GetComputerNameA" (ByVal lpBuffer As String, nSize As Long) As Long
Public strUserName As String
Public strMachinerName As String
Public Function IsWebConnected() As Boolean
'-----------------------------------------------------------------------
----------------
'
' Description / Purpose :-
' Quick test to see if there is an available internet connection
'
' Parameters:-
' PARAMETER TYPE COMMENTS
' none
'
' Return Value:-
' true if there is an available connection
'
' Notes:-
'
'------------------------------------------------------------
' Version Dated Author Comment
' 1.0 19-Jun-03 (c) 2003 Sargasso Pty Ltd Original.
'============================================================
On Error GoTo IsWebConnected_ERR
IsWebConnected = (InternetAttemptConnect(ByVal 0&) = 0)
IsWebConnected_EXIT:
On Error GoTo 0
Exit Function
IsWebConnected_ERR:
Dim pname As String
pname = "IsWebConnected"
Select Case Err.Number
Case Else
MsgBox "Error " & Err.Number & " (" & Err.Description & ")
in procedure pname of Module Internet Handlers"
End Select
GoTo IsWebConnected_EXIT
End Function
Public Function AreWeConnected() As Boolean
'-----------------------------------------------------------------------
----------------
'
' Description / Purpose :-
' Quick hack of the AllAPI code for Jim
'
' Parameters:-
' PARAMETER TYPE COMMENTS
' none
'
' Return Value:-
' true if some code is added to detect what you want
'
' Notes:-
'
'------------------------------------------------------------
' Version Dated Author Comment
' 1.0 20-Jun-03 (c) 2003 Sargasso Pty Ltd Original by
AllAPI as per comments.
'============================================================
Dim blnResult As Boolean
On Error GoTo AreWeConnected_ERR
'KPD-Team 2000
'URL: http://www.allapi.net/
'E-Mail: KPDTeam at Allapi.net
'-> This sample was created by Donald Grover
Const MAX_RESOURCES = 256
Const NOT_A_CONTAINER = -1
Dim bFirstTime As Boolean
Dim lReturn As Long
Dim hEnum As Long
Dim lCount As Long
Dim lMin As Long
Dim lLength As Long
Dim l As Long
Dim lBufferSize As Long
Dim lLastIndex As Long
Dim uNetApi(0 To MAX_RESOURCES) As NETRESOURCE
Dim uNet() As NETRESOURCE_REAL
bFirstTime = True
Do
If bFirstTime Then
lReturn = WNetOpenEnum(RESOURCE_GLOBALNET, RESOURCETYPE_ANY,
RESOURCEUSAGE_ALL, ByVal 0&, hEnum)
bFirstTime = False
Else
If uNet(lLastIndex).dwUsage And RESOURCEUSAGE_CONTAINER Then
lReturn = WNetOpenEnum(RESOURCE_GLOBALNET,
RESOURCETYPE_ANY, RESOURCEUSAGE_ALL, uNet(lLastIndex), hEnum)
Else
lReturn = NOT_A_CONTAINER
hEnum = 0
End If
lLastIndex = lLastIndex + 1
End If
If lReturn = NO_ERROR Then
lCount = RESOURCE_ENUM_ALL
Do
lBufferSize = UBound(uNetApi) * Len(uNetApi(0)) / 2
lReturn = WNetEnumResource(hEnum, lCount, uNetApi(0),
lBufferSize)
If lCount > 0 Then
ReDim Preserve uNet(0 To lMin + lCount - 1) As
NETRESOURCE_REAL
For l = 0 To lCount - 1
'Each Resource will appear here as uNet(i)
uNet(lMin + l).dwScope = uNetApi(l).dwScope
uNet(lMin + l).dwType = uNetApi(l).dwType
uNet(lMin + l).dwDisplayType =
uNetApi(l).dwDisplayType
uNet(lMin + l).dwUsage = uNetApi(l).dwUsage
If uNetApi(l).pLocalName Then
lLength = lstrlen(uNetApi(l).pLocalName)
uNet(lMin + l).sLocalName = Space$(lLength)
CopyMem ByVal uNet(lMin + l).sLocalName,
ByVal uNetApi(l).pLocalName, lLength
End If
If uNetApi(l).pRemoteName Then
lLength = lstrlen(uNetApi(l).pRemoteName)
uNet(lMin + l).sRemoteName = Space$(lLength)
CopyMem ByVal uNet(lMin + l).sRemoteName,
ByVal uNetApi(l).pRemoteName, lLength
End If
If uNetApi(l).pComment Then
lLength = lstrlen(uNetApi(l).pComment)
uNet(lMin + l).sComment = Space$(lLength)
CopyMem ByVal uNet(lMin + l).sComment, ByVal
uNetApi(l).pComment, lLength
End If
If uNetApi(l).pProvider Then
lLength = lstrlen(uNetApi(l).pProvider)
uNet(lMin + l).sProvider = Space$(lLength)
CopyMem ByVal uNet(lMin + l).sProvider,
ByVal uNetApi(l).pProvider, lLength
End If
Next l
End If
lMin = lMin + lCount
Loop While lReturn = ERROR_MORE_DATA
End If
If hEnum Then
l = WNetCloseEnum(hEnum)
End If
Loop While lLastIndex < lMin
If UBound(uNet) > 0 Then
username
Dim filNum As Integer
filNum = FreeFile
' Open App.Path & "\" & LCase(App.EXEName) & ".txt" For Output
Shared As #filNum
'Open "d:\" & App.EXEName & ".txt" For Output Shared As #filNum
Debug.Print "Date: " & Format(Now, "Long date")
Debug.Print ""
Debug.Print "UserName: " & strUserName
Debug.Print "Computer Name: " & strMachinerName
For l = 0 To UBound(uNet)
Select Case uNet(l).dwDisplayType
Case RESOURCEDISPLAYTYPE_DIRECTORY&
Debug.Print "Directory...",
Debug.Print "Directory...",
Case RESOURCEDISPLAYTYPE_DOMAIN
Debug.Print "Domain...",
Debug.Print "Domain...",
Case RESOURCEDISPLAYTYPE_FILE
Debug.Print "File...",
' Print #filNum, "File...",
Case RESOURCEDISPLAYTYPE_GENERIC
Debug.Print "Generic...",
' Print #filNum, "Generic...",
Case RESOURCEDISPLAYTYPE_GROUP
Debug.Print "Group...",
' Print #filNum, "Group...",
Case RESOURCEDISPLAYTYPE_NETWORK&
Debug.Print "Network...",
' Print #filNum, "Network...",
Case RESOURCEDISPLAYTYPE_ROOT&
Debug.Print "Root...",
' Print #filNum, "Root...",
Case RESOURCEDISPLAYTYPE_SERVER
Debug.Print "Server...",
' Print #filNum, "Server...",
Case RESOURCEDISPLAYTYPE_SHARE
Debug.Print "Share...",
' Print #filNum, "Share...",
Case RESOURCEDISPLAYTYPE_SHAREADMIN&
Debug.Print "ShareAdmin...",
' Print #filNum, "ShareAdmin...",
End Select
Debug.Print uNet(l).sRemoteName, uNet(l).sComment
' Print #filNum, uNet(l).sRemoteName, uNet(l).sComment
Next l
End If
Close #filNum
' MsgBox "File " + App.Path & "\" & LCase(App.EXEName) & ".txt
created" + vbCrLf + "Open it in a text editor to see the results",
vbInformation
AreWeConnected = <some form of blnResult that you have hacked into
the above>
AreWeConnected_TIDYUP:
' Close any open recordsets, destroy local objects
AreWeConnected_EXIT:
On Error GoTo 0
Exit Function
AreWeConnected_ERR:
Dim pname As String
pname = "AreWeConnected"
Select Case Err.Number
Case Else
MsgBox "Error " & Err.Number & " (" & Err.Description & ")
in procedure pname of Module Internet Handlers"
Stop
Resume
End Select
GoTo AreWeConnected_EXIT
End Function
Private Sub username()
On Error Resume Next
'Create a buffer
strUserName = String(255, Chr$(0))
'Get the username
getusername strUserName, 255
'strip the rest of the buffer
strUserName = Left$(strUserName, InStr(strUserName, Chr$(0)) - 1)
'Create a buffer
strMachinerName = String(255, Chr$(0))
GetComputerName strMachinerName, 255
'remove the unnecessary chr$(0)'s
strMachinerName = Left$(strMachinerName, InStr(1, strMachinerName,
Chr$(0)) - 1)
End Sub
==========================================END
Hth, Im in a bit of a rush
Bruce
-----Original Message-----
From: accessd-bounces at databaseadvisors.com
[mailto:accessd-bounces at databaseadvisors.com] On Behalf Of Jim DeMarco
Sent: Friday, June 20, 2003 12:01 AM
To: accessd at databaseadvisors.com
Subject: RE: [AccessD] detect network
Bruce,
I'm not familiar with network APIs. Can you point me to any reference
material? Someone suggested pinging the server but I'm not sure how to
do that in VB/VBA.
Thanks,
Jim DeMarco
-----Original Message-----
From: Bruce Bruen [mailto:bbruen at bigpond.com]
Sent: Thursday, June 19, 2003 9:35 AM
To: accessd at databaseadvisors.com
Subject: RE: [AccessD] detect network
You could either use the network API calls to get the network connection
information or presumably when they are connected there will be a
network path name you could try to access to see if its connected.
The network path is probably the QAD method.
Hth
Bruce
-----Original Message-----
From: accessd-bounces at databaseadvisors.com
[mailto:accessd-bounces at databaseadvisors.com] On Behalf Of Jim DeMarco
Sent: Thursday, June 19, 2003 10:33 PM
To: AccessD (E-mail)
Subject: [AccessD] detect network
We've got a data collection application that will be run on disconnected
laptops. At least once a week the laptop users will come in to the home
office to dump the data they've collected into our central SQL database.
Does anyone have any code that will detect that the laptop is connected
to our network so we can point their connection to the central DB (as
opposed to their local DB)? Or should we just try to hit the central DB
at app start and trap the error? I don't want to generate an error if I
don't have to.
Thanks,
Jim DeMarco
Director of Product Development
HealthSource/Hudson Health Plan
************************************************************************
***********
"This electronic message is intended to be for the use only of the named
recipient, and may contain information from Hudson Health Plan (HHP)
that is confidential or privileged. If you are not the intended
recipient, you are hereby notified that any disclosure, copying,
distribution or use of the contents of this message is strictly
prohibited. If you have received this message in error or are not the
named recipient, please notify us immediately, either by contacting the
sender at the electronic mail address noted above or calling HHP at
(914) 631-1611. If you are not the intended recipient, please do not
forward this email to anyone, and delete and destroy all copies of this
message. Thank You".
************************************************************************
***********
_______________________________________________
AccessD mailing list
AccessD at databaseadvisors.com
http://databaseadvisors.com/mailman/listinfo/accessd
Website: http://www.databaseadvisors.com
_______________________________________________
AccessD mailing list
AccessD at databaseadvisors.com
http://databaseadvisors.com/mailman/listinfo/accessd
Website: http://www.databaseadvisors.com
************************************************************************
***********
"This electronic message is intended to be for the use only of the named
recipient, and may contain information from Hudson Health Plan (HHP)
that is confidential or privileged. If you are not the intended
recipient, you are hereby notified that any disclosure, copying,
distribution or use of the contents of this message is strictly
prohibited. If you have received this message in error or are not the
named recipient, please notify us immediately, either by contacting the
sender at the electronic mail address noted above or calling HHP at
(914) 631-1611. If you are not the intended recipient, please do not
forward this email to anyone, and delete and destroy all copies of this
message. Thank You".
************************************************************************
***********
_______________________________________________
AccessD mailing list
AccessD at databaseadvisors.com
http://databaseadvisors.com/mailman/listinfo/accessd
Website: http://www.databaseadvisors.com