Groupes Novell - VB/VBA/VBS - Programmation
Marsh Posté le 22-09-2004 à 15:42:40
Re,
J'ai bidouillé un truc qui, à priori, fonctionne. Si ça peut éviter à quelqu'un de se prendre la tête, voilà le truc (Il y a surement mieux).
Private Declare Function RegCloseKey& Lib "advapi32.dll" (ByVal hKey& )
Private Declare Function RegOpenKeyExA& Lib "advapi32.dll" (ByVal hKey&, ByVal lpszSubKey$, dwOptions&, ByVal samDesired&, lpHKey& )
Private Declare Function RegQueryValueExA& Lib "advapi32.dll" (ByVal hKey&, ByVal lpszValueName$, ByVal lpdwRes&, lpdwType&, ByVal lpDataBuff$, nSize& )
Const HKEY_CLASSES_ROOT = &H80000000
Const HKEY_CURRENT_USER = &H80000001
Const HKEY_LOCAL_MACHINE = &H80000002
Const HKEY_USERS = &H80000003
Const ERROR_SUCCESS = 0&
Const REG_SZ = 1& ' Unicode nul terminated string
Const REG_DWORD = 4& ' 32-bit number
Const KEY_QUERY_VALUE = &H1&
Const KEY_SET_VALUE = &H2&
Const KEY_CREATE_SUB_KEY = &H4&
Const KEY_ENUMERATE_SUB_KEYS = &H8&
Const KEY_NOTIFY = &H10&
Const KEY_CREATE_LINK = &H20&
Const READ_CONTROL = &H20000
Const WRITE_DAC = &H40000
Const WRITE_OWNER = &H80000
Const SYNCHRONIZE = &H100000
Const STANDARD_RIGHTS_REQUIRED = &HF0000
Const STANDARD_RIGHTS_READ = READ_CONTROL
Const STANDARD_RIGHTS_WRITE = READ_CONTROL
Const STANDARD_RIGHTS_EXECUTE = READ_CONTROL
Const KEY_READ = STANDARD_RIGHTS_READ Or KEY_QUERY_VALUE Or KEY_ENUMERATE_SUB_KEYS Or KEY_NOTIFY
Const KEY_WRITE = STANDARD_RIGHTS_WRITE Or KEY_SET_VALUE Or KEY_CREATE_SUB_KEY
Const KEY_EXECUTE = KEY_READ
Const PROCESS_QUERY_INFORMATION = &H400
Const STATUS_PENDING = &H103&
Private Declare Function OpenProcess Lib "kernel32" _
(ByVal dwDesiredAccess As Long, _
ByVal bInheritHandle As Long, _
ByVal dwProcessId As Long) As Long
Private Declare Function GetExitCodeProcess Lib "kernel32" _
(ByVal hProcess As Long, lpExitCode As Long) As Long
Private Declare Function CloseHandle Lib "kernel32" _
(ByVal hObject As Long) As Long
Function RegGetValue$(MainKey&, SubKey$, value$)
Dim sKeyType&
Dim ret&
Dim lpHKey&
Dim lpcbData&
Dim ReturnedString$
Dim fTempDbl!
If MainKey >= &H80000000 And MainKey <= &H80000006 Then
ret = RegOpenKeyExA(MainKey, SubKey, 0&, KEY_READ, lpHKey)
If ret <> ERROR_SUCCESS Then
RegGetValue = ""
Exit Function
End If
lpcbData = 255
ReturnedString = Space$(lpcbData)
ret& = RegQueryValueExA(lpHKey, value, ByVal 0&, sKeyType, ReturnedString, lpcbData)
If ret <> ERROR_SUCCESS Then
RegGetValue = ""
Else
If sKeyType = REG_DWORD Then
ret = RegQueryValueExA(lpHKey, value, ByVal 0&, sKeyType, ReturnedLong, 4)
If ret = ERROR_SUCCESS Then RegGetValue = CStr(ReturnedLong)
Else
RegGetValue = Left$(ReturnedString, lpcbData - 1)
End If
End If
ret = RegCloseKey(lpHKey)
End If
End Function
Private Sub Form_Load()
' Recherche de l'OS Win 9x
OS = RegGetValue$(HKEY_LOCAL_MACHINE, "Software\Microsoft\Windows\CurrentVersion", "ProductName" )
' Si non trouvé, recherche Win 2k
If OS = "" Then
OS = RegGetValue$(HKEY_LOCAL_MACHINE, "Software\Microsoft\Windows NT\CurrentVersion", "ProductName" )
End If
' MsgBox OS
' Recherche du UserName
Select Case Right(OS, 2)
Case "98"
User = RegGetValue$(HKEY_LOCAL_MACHINE, "NetWork\Logon", "NetWareUsername" )
Case "XP"
User = RegGetValue$(HKEY_CURRENT_USER, "Volatile Environment", "NWUSERNAME" )
End Select
' Lecture des groupes Novell de l'utilisateur
Select Case Right(OS, 2)
Case "98"
Groupes = Shell("c:\windows\command.com /C nlist user where cn = " & Chr(34) & User & Chr(34) & " show " & Chr(34) & "group membership" & Chr(34) & " > c:\groupes.txt", 1)
Case "XP"
Groupes = Shell("c:\windows\system32\command.com /C nlist user where cn = " & Chr(34) & User & Chr(34) & " show " & Chr(34) & "group membership" & Chr(34) & " > c:\groupes.txt", 1)
End Select
'Récupérer le handler du Process obtenu
hProcess& = OpenProcess(PROCESS_QUERY_INFORMATION, False, Groupes)
'Tester si le Process est terminé
Do
Call GetExitCodeProcess(hProcess&, CodeSortie& )
DoEvents
Loop While CodeSortie& = STATUS_PENDING
Call CloseHandle(hProcess& )
' Lecture des groupes
FicSource = FreeFile
FicGroupes = "c:\groupes.txt"
Open FicGroupes For Binary Access Read Lock Read As #FicSource
Line Input #FicSource, lignesource
Line Input #FicSource, lignesource
Line Input #FicSource, lignesource
Do While Not EOF(FicSource)
On Error Resume Next
Line Input #FicSource, lignesource
If EOF(FicSource) Then
Err.Clear
Exit Do
End If
pos = InStr(lignesource, "Group Membership" ) + Len("Group Membership" ) + 2
If InStr(lignesource, "Group Membership" ) > 0 Then
Groupe = Groupe & Mid(lignesource, pos) & Chr(10)
End If
Loop
MsgBox Groupe
End Sub
Marsh Posté le 20-09-2004 à 10:52:16
Bonjour,
si quelqu'un peut m'aider : J'aurai besoin, dans un programme VB6, de lister les groupes Novell auxquels appartient l'utilisateur connecté.
Merci.