Tek-Tips is the largest IT community on the Internet today!

Members share and learn making Tek-Tips Forums the best source of peer-reviewed technical information on the Internet!

  • Congratulations gkittelson on being selected by the Tek-Tips community for having the most helpful posts in the forums last week. Way to Go!

Services API

Status
Not open for further replies.

foxylady

Programmer
Jan 19, 2001
14
US
Does anyone know how to return the User name that a service runs under?
 
QueryServiceConfig provides the information through the lpServiceStartName member of the QUERY_SERVICE_CONFIG structure/UDT.

You will need to use OpenSCManager to get a handle to the Service Control Manager and then OpenService to get a handle to the service you want to know about.

Take Care

Matt
If at first you don't succeed, skydiving is not for you.
 
Here's some code you can put into a module to do what you're looking for. The function returns a Long type return code, and uses a ByRef parameter to pass the username. If the return code is 0, everything worked and you can use the username from the ByRef variables. I know there's some overkill with the constants, but I figured if you're working with services having some extras in there wouldn't hurt (this is a function I stripped out of a module I've created to do a lot of service manipulation). Hope this helps.

=============================================

' Force declaration of all variables
Option Explicit

' Declare APIs
Private Declare Function OpenSCManager Lib "advapi32.dll" Alias "OpenSCManagerA" (ByVal lpMachineName As String, ByVal lpDatabaseName As String, ByVal dwDesiredAccess As Long) As Long
Private Declare Function OpenService Lib "advapi32.dll" Alias "OpenServiceA" (ByVal lngSCManager As Long, ByVal lpServiceName As String, ByVal dwDesiredAccess As Long) As Long
Private Declare Function CloseServiceHandle Lib "advapi32.dll" (ByVal hSCObject As Long) As Long
Private Declare Function QueryServiceConfig Lib "advapi32.dll" Alias "QueryServiceConfigA" (ByVal hService As Long, lpServiceConfig As Byte, ByVal cbBufSize As Long, pcbBytesNeeded As Long) As Long
Private Declare Function lstrcpy Lib "kernel32.dll" Alias "lstrcpyA" (szDest As String, szcSource As Long) As Long
Private Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (Destination As Any, Source As Any, ByVal Length As Long)

' Define constants
Private Const SERVICES_ACTIVE_DATABASE = "ServicesActive"
Private Const STANDARD_RIGHTS_REQUIRED = &HF0000
Private Const SC_MANAGER_CONNECT = &H1
Private Const SC_MANAGER_CREATE_SERVICE = &H2
Private Const SC_MANAGER_ENUMERATE_SERVICE = &H4
Private Const SC_MANAGER_LOCK = &H8
Private Const SC_MANAGER_QUERY_LOCK_STATUS = &H10
Private Const SC_MANAGER_MODIFY_BOOT_CONFIG = &H20
Private Const SC_MANAGER_ALL_ACCESS = (STANDARD_RIGHTS_REQUIRED Or SC_MANAGER_CONNECT Or SC_MANAGER_CREATE_SERVICE Or SC_MANAGER_ENUMERATE_SERVICE Or SC_MANAGER_LOCK Or SC_MANAGER_QUERY_LOCK_STATUS Or SC_MANAGER_MODIFY_BOOT_CONFIG)
Private Const SERVICE_QUERY_CONFIG = &H1
Private Const SERVICE_CHANGE_CONFIG = &H2
Private Const SERVICE_QUERY_STATUS = &H4
Private Const SERVICE_ENUMERATE_DEPENDENTS = &H8
Private Const SERVICE_START = &H10
Private Const SERVICE_STOP = &H20
Private Const SERVICE_PAUSE_CONTINUE = &H40
Private Const SERVICE_INTERROGATE = &H80
Private Const SERVICE_USER_DEFINED_CONTROL = &H100
Private Const SERVICE_ALL_ACCESS = (STANDARD_RIGHTS_REQUIRED Or SERVICE_QUERY_CONFIG Or SERVICE_CHANGE_CONFIG Or SERVICE_QUERY_STATUS Or SERVICE_ENUMERATE_DEPENDENTS Or SERVICE_START Or SERVICE_STOP Or SERVICE_PAUSE_CONTINUE Or SERVICE_INTERROGATE Or SERVICE_USER_DEFINED_CONTROL)
Private Const SERVICE_WIN32_OWN_PROCESS As Long = &H10
Private Const SERVICE_WIN32_SHARE_PROCESS As Long = &H20
Private Const SERVICE_WIN32 As Long = SERVICE_WIN32_OWN_PROCESS + SERVICE_WIN32_SHARE_PROCESS
Private Const GENERIC_READ = &H80000000
Private Const SERVICE_DEMAND_START As Long = &H3
Private Const SERVICE_ERROR_NORMAL As Long = &H1
Private Const ERROR_MORE_DATA = 234
Private Const ERROR_INSUFFICIENT_BUFFER = 122
Private Const ERROR_DUP_NAME = 52&
Private Const ERROR_SERVICE_EXISTS = 1073&

' Define UDTs
Private Type QUERY_SERVICE_CONFIG
dwServiceType As Long
dwStartType As Long
dwErrorControl As Long
lpBinaryPathName As Long
lpLoadOrderGroup As Long
dwTagId As Long
lpDependencies As Long
lpServiceStartName As Long
lpDisplayName As Long
End Type

Public Function getServiceUser(strServerName As String, strServiceName As String, ByRef strUserName As String) As Long

' Declare local variable(s)
Dim udtServiceConfig As QUERY_SERVICE_CONFIG
Dim lngServiceManagerHandle As Long
Dim lngServiceHandle As Long
Dim strNullString As String
Dim strTempString As String
Dim lngReturnCode As Long
Dim lngBufferSize As Long
Dim lngAPIReturn As Long
Dim bytBuffer() As Byte

' Initialize variable(s)
strUserName = ""
lngReturnCode = 0
strNullString = vbNullChar

' Open the computer Service Manager
lngServiceManagerHandle = OpenSCManager(strServerName, SERVICES_ACTIVE_DATABASE, SC_MANAGER_ALL_ACCESS)

' If we successfully opened the service manager, attempt to get
' the service config for the specified service
If lngServiceManagerHandle <> 0 Then
lngServiceHandle = OpenService(lngServiceManagerHandle, strServiceName, SERVICE_ALL_ACCESS)
If lngServiceHandle = 0 Then
CloseServiceHandle lngServiceManagerHandle
lngReturnCode = 9992 ' Unable to open service
GoTo getServiceUser_Finalize
End If

' ReDim the buffer to 1 byte so we can call QueryServiceConfig to
' get the needed buffer size
ReDim bytBuffer(0) As Byte
lngAPIReturn = QueryServiceConfig(lngServiceHandle, 0&, 0, lngBufferSize)
If (lngAPIReturn = 0) And (Err.LastDllError <> ERROR_INSUFFICIENT_BUFFER) Then
lngReturnCode = Err.LastDllError
CloseServiceHandle lngServiceManagerHandle
GoTo getServiceUser_Finalize
End If

' ReDim the buffer and call QueryServiceConfig again to get
' the service configuration
ReDim bytBuffer(lngBufferSize) As Byte
lngAPIReturn = QueryServiceConfig(lngServiceHandle, bytBuffer(0), lngBufferSize, lngBufferSize)
If lngAPIReturn = 0 Then
lngReturnCode = Err.LastDllError
CloseServiceHandle lngServiceManagerHandle
GoTo getServiceUser_Finalize
End If

' Copy the buffer to the service config UDT
CopyMemory udtServiceConfig, bytBuffer(0), Len(udtServiceConfig)

' Close the service handle for the service now that
' we've got the information we need
CloseServiceHandle lngServiceHandle

' Allocate space for the temp string to grab the user name
strTempString = Space(255)

' Populate the temp string using the string pointer in the
' service config UDT
lngAPIReturn = lstrcpy(ByVal strTempString, ByVal udtServiceConfig.lpServiceStartName)

' Get the string up to the first null char as the user
strUserName = Left(strTempString, InStr(1, strTempString, Chr(0)) - 1)

CloseServiceHandle lngServiceManagerHandle
Else
lngReturnCode = 9991 ' Unable to open service manager
End If

getServiceUser_Finalize:

' Return the appropriate return code
getServiceUser = lngReturnCode

End Function
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top