where AccountName is any user or group account name, and AccessMask is any of the generic or object-specific access masks. All the access mask constants for any securable object are defined in the sample code. AceFlags and AceType structure members have the same values as documented in the ACE_HEADER data structure in the Microsoft Platform SDK.
As demonstrated in some of the code samples available through the preceding link, the caller can specify an array of AccountPerm structures to either construct a new security descriptor or add to an existing security descriptor of any securable object. If the caller wants to pass a well known SID, the caller can allocate the SID by using the AllocateAndInitializeSid() function and then specify it in the pSid structure member, with SidPassedByCaller set to True.
Step-By-Step Example
- First step to test this example is create 3 User accounts (User1, User2 and User3) as shown below
- Create a standard exe project - Add a module to the project - Place one textbox, 1 combobox and one command button on the form1 - Place the following code in form1 code window
Form1.frm |
- Place the following code in Module1
Module1.bas |
Click here to copy the following block | Option Explicit
Private Const LMEM_FIXED = &H0 Private Const LMEM_ZEROINIT = &H40 Private Const LPTR = (LMEM_FIXED + LMEM_ZEROINIT)
Public Const GENERIC_ALL = &H10000000 Public Const GENERIC_READ = &H80000000 Public Const GENERIC_EXECUTE = &H20000000 Public Const GENERIC_WRITE = &H40000000
Public Const DELETE = &H10000 Public Const READ_CONTROL = &H20000 Public Const WRITE_DAC = &H40000 Public Const WRITE_OWNER = &H80000 Public Const SYNCHRONIZE = &H100000 Public Const STANDARD_RIGHTS_REQUIRED = &HF0000 Public Const STANDARD_RIGHTS_READ = READ_CONTROL Public Const STANDARD_RIGHTS_WRITE = READ_CONTROL Public Const STANDARD_RIGHTS_EXECUTE = READ_CONTROL Public Const STANDARD_RIGHTS_ALL = &H1F0000 Public Const SPECIFIC_RIGHTS_ALL = &HFFFF& Public Const ACCESS_SYSTEM_SECURITY = &H1000000 Public Const MAXIMUM_ALLOWED = &H2000000
Private Const DACL_SECURITY_INFORMATION = &H4 Private Const SECURITY_DESCRIPTOR_REVISION = 1 Private Const SECURITY_DESCRIPTOR_MIN_LENGTH = 20 Private Const SD_SIZE = (65536 + SECURITY_DESCRIPTOR_MIN_LENGTH) Private Const ACL_REVISION2 = 2 Private Const ACL_REVISION = 2 Private Const MAXDWORD = &HFFFFFFFF Private Const SidTypeUser = 1 Private Const AclSizeInformation = 2
Public Const OBJECT_INHERIT_ACE = &H1 Public Const CONTAINER_INHERIT_ACE = &H2 Public Const NO_PROPAGATE_INHERIT_ACE = &H4 Public Const INHERIT_ONLY_ACE = &H8 Public Const INHERITED_ACE = &H10 Public Const VALID_INHERIT_FLAGS = &H1F
Private Const SE_DACL_AUTO_INHERIT_REQ = &H100 Private Const SE_SACL_AUTO_INHERIT_REQ = &H200 Private Const SE_DACL_AUTO_INHERITED = &H400 Private Const SE_SACL_AUTO_INHERITED = &H800 Private Const SE_DACL_PROTECTED = &H1000 Private Const SE_SACL_PROTECTED = &H2000
Public Const ACCESS_ALLOWED_ACE_TYPE = 0 Public Const ACCESS_DENIED_ACE_TYPE = 1
Public Const SECURITY_WORLD_SID_AUTHORITY = &H1 Public Const SECURITY_NT_AUTHORITY = &H5
Public Const SECURITY_BUILTIN_DOMAIN_RID = &H20& Public Const DOMAIN_ALIAS_RID_ADMINS = &H220& Public Const DOMAIN_ALIAS_RID_USERS = &H221& Public Const SECURITY_LOCAL_SYSTEM_RID = &H12 Public Const SECURITY_WORLD_RID = &H0
Public Const DOMAIN_USER_RID_ADMIN = &H1F4 Public Const DOMAIN_USER_RID_GUEST = &H1F5
Public Const DOMAIN_GROUP_RID_ADMINS = &H200
Public Const INVALID_HANDLE_VALUE = -1 Public Const OPEN_EXISTING = 3 Public Const FILE_FLAG_BACKUP_SEMANTICS = &H2000000
Public Const KEY_QUERY_VALUE = &H1 Public Const KEY_SET_VALUE = &H2 Public Const KEY_CREATE_SUB_KEY = &H4 Public Const KEY_ENUMERATE_SUB_KEYS = &H8 Public Const KEY_NOTIFY = &H10 Public Const KEY_CREATE_LINK = &H20 Public Const KEY_WOW64_32KEY = &H200 Public Const KEY_WOW64_64KEY = &H100
Public Const KEY_READ = ((STANDARD_RIGHTS_READ Or _ KEY_QUERY_VALUE Or _ KEY_ENUMERATE_SUB_KEYS Or _ KEY_NOTIFY) _ And (Not SYNCHRONIZE)) Public Const KEY_WRITE = ((STANDARD_RIGHTS_WRITE Or _ KEY_SET_VALUE Or _ KEY_CREATE_SUB_KEY) _ And (Not SYNCHRONIZE)) Public Const KEY_EXECUTE = ((KEY_READ) And (Not SYNCHRONIZE)) Public Const KEY_ALL_ACCESS = ((STANDARD_RIGHTS_ALL Or _ KEY_QUERY_VALUE Or _ KEY_SET_VALUE Or _ KEY_CREATE_SUB_KEY Or _ KEY_ENUMERATE_SUB_KEYS Or _ KEY_NOTIFY Or _ KEY_CREATE_LINK) _ And (Not SYNCHRONIZE))
Public Const HKEY_CLASSES_ROOT = &H80000000 Public Const HKEY_CURRENT_USER = &H80000001 Public Const HKEY_LOCAL_MACHINE = &H80000002 Public Const HKEY_USERS = &H80000003
Public Const ERROR_SUCCESS = 0& Public Const NERR_Success = 0&
Private Const VER_PLATFORM_WIN32_NT = &H2
Private Type ACL AclRevision As Byte Sbz1 As Byte AclSize As Integer AceCount As Integer Sbz2 As Integer End Type
Private Type ACL_SIZE_INFORMATION AceCount As Long AclBytesInUse As Long AclBytesFree As Long End Type
Private Type ACE_HEADER AceType As Byte AceFlags As Byte AceSize As Integer End Type
Private Type ACE Header As ACE_HEADER Mask As Long SidStart As Long End Type
Private Type SECURITY_ATTRIBUTES Length As Long SecurityDescriptor As Long InheritHandle As Long End Type
Private Type SID_IDENTIFIER_AUTHORITY Value(6) As Byte End Type
Private Type OSVERSIONINFO dwOSVersionInfoSize As Long dwMajorVersion As Long dwMinorVersion As Long dwBuildNumber As Long dwPlatformId As Long szCSDVersion As String * 128 End Type
Public Type AccountPerm AccountName As String AccessMask As Long AceFlags As Byte AceType As Byte pSid As Long SidPassedByCaller As Boolean End Type
Private Type SDMemInfo pSD As Long pAcl As Long End Type
Private Declare Function LocalAlloc Lib "kernel32.dll" _ (ByVal wFlags As Long, ByVal wBytes As Long) As Long
Private Declare Function LocalFree Lib "kernel32.dll" _ (ByVal hMem As Long) As Long
Private Declare Sub CopyMemory Lib "kernel32.dll" Alias "RtlMoveMemory" _ (hpvDest As Any, ByVal hpvSource As Long, _ ByVal cbCopy As Long)
Private Declare Function InitializeSecurityDescriptor Lib "advapi32.dll" _ (ByVal pSecurityDescriptor As Long, _ ByVal dwRevision As Long) As Long
Private Declare Function LookupAccountName Lib "advapi32.dll" Alias _ "LookupAccountNameA" (ByVal lpSystemName As Long, _ ByVal lpAccountName As String, _ ByVal Sid As Long, _ cbSid As Long, _ ByVal ReferencedDomainName As String, _ cbReferencedDomainName As Long, _ peUse As Long) As Long
Private Declare Function GetLengthSid Lib "advapi32.dll" _ (ByVal pSid As Long) As Long
Private Declare Function InitializeAcl Lib "advapi32.dll" _ (ByVal pAcl As Long, ByVal nAclLength As Long, _ ByVal dwAclRevision As Long) As Long
Private Declare Function SetSecurityDescriptorDacl Lib "advapi32.dll" _ (ByVal pSecurityDescriptor As Long, ByVal bDaclPresent As Long, _ ByVal pDacl As Long, ByVal bDaclDefaulted As Long) As Long
Private Declare Function GetAce Lib "advapi32.dll" _ (ByVal pAcl As Long, ByVal dwAceIndex As Long, pACE As Long) As Long
Private Declare Function GetSecurityDescriptorDacl Lib "advapi32.dll" _ (ByVal pSecurityDescriptor As Long, lpbDaclPresent As Long, _ pDacl As Long, lpbDaclDefaulted As Long) As Long
Private Declare Function GetAclInformation Lib "advapi32.dll" _ (ByVal pAcl As Long, pAclInformation As Any, _ ByVal nAclInformationLength As Long, _ ByVal dwAclInformationClass As Long) As Long
Private Declare Function GetSecurityDescriptorControl Lib "advapi32.dll" _ (ByVal pSecurityDescriptor As Long, _ pControl As Long, lpdwRevision As Long) As Long
Private Declare Function SetSecurityDescriptorControl Lib "advapi32.dll" _ (ByVal pSecurityDescriptor As Long, _ ByVal controlBitsOfInterest As Long, _ ByVal controlBitsToSet As Long) As Long
Private Declare Function EqualSid Lib "advapi32.dll" _ (ByVal pSid1 As Long, ByVal pSid2 As Long) As Long
Private Declare Function AddAce Lib "advapi32.dll" (ByVal pAcl As Long, _ ByVal dwAceRevision As Long, ByVal dwStartingAceIndex As Long, _ ByVal pAceList As Long, ByVal nAceListLength As Long) As Long
Private Declare Function AllocateAndInitializeSid Lib "advapi32.dll" _ (pIdentifierAuthority As SID_IDENTIFIER_AUTHORITY, _ ByVal nSubAuthorityCount As Byte, ByVal nSubAuthority0 As Long, _ ByVal nSubAuthority1 As Long, ByVal nSubAuthority2 As Long, _ ByVal nSubAuthority3 As Long, ByVal nSubAuthority4 As Long, _ ByVal nSubAuthority5 As Long, ByVal nSubAuthority6 As Long, _ ByVal nSubAuthority7 As Long, lpPSid As Long) As Long
Private Declare Sub FreeSid Lib "advapi32.dll" (ByVal pSid As Long)
Private 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
Private Declare Function RegCloseKey Lib "advapi32.dll" _ (ByVal hKey As Long) As Long
Private Declare Function RegGetKeySecurity Lib "advapi32.dll" _ (ByVal hKey As Long, _ ByVal SecurityInformation As Long, _ ByVal pSecurityDescriptor As Long, _ lpcbSecurityDescriptor As Long) As Long
Private Declare Function RegSetKeySecurity Lib "advapi32.dll" _ (ByVal hKey As Long, _ ByVal SecurityInformation As Long, _ ByVal pSecurityDescriptor As Long) As Long
Private Declare Function GetVersionExA Lib "kernel32.dll" _ (lpVersionInformation As OSVERSIONINFO) As Integer
Private Function IsEqual(Accounts() As AccountPerm, pSid As Long) As Boolean Dim nEntries As Long Dim nIndex As Long
nEntries = UBound(Accounts) For nIndex = 0 To nEntries If (EqualSid(Accounts(nIndex).pSid, pSid)) Then IsEqual = True Exit Function End If Next IsEqual = False End Function
Private Function ConstructAndAddAce( _ ByVal pNewACL As Long, _ ByVal AceType As Byte, _ ByVal AceFlags As Byte, _ ByVal AccessMask As Long, _ ByVal pSid As Long) As Long Dim fResult As Long
Dim dwNewACESize As Long Dim dwSidLen As Long Dim tempAce As ACE Dim pACE As Long
fResult = 0 On Error GoTo Label1
dwSidLen = GetLengthSid(pSid) dwNewACESize = Len(tempAce) + dwSidLen - 4
pACE = LocalAlloc(LPTR, dwNewACESize) If pACE = 0 Then Err.Raise 0
tempAce.Header.AceType = AceType tempAce.Header.AceFlags = AceFlags tempAce.Header.AceSize = dwNewACESize tempAce.Mask = AccessMask
CopyMemory ByVal pACE, VarPtr(tempAce), LenB(tempAce) CopyMemory ByVal pACE + 8, pSid, dwSidLen
fResult = AddAce(pNewACL, ACL_REVISION, _ MAXDWORD, _ pACE, _ dwNewACESize) LocalFree pACE Label1: ConstructAndAddAce = fResult End Function
Private Function AddSecurityDescriptor(ByVal pOldSD As Long, _ Accounts() As AccountPerm, _ sdInfo As SDMemInfo) As Long
Dim pNewACL As Long Dim dwNewACLSize As Long Dim dwTotalDACLSize As Long Dim szDomainName As String Dim cbDomainName As Long Dim nSidSize As Long Dim I As Long, n As Long Dim eUse As Long Dim fReturn As Long Dim fResult As Long Dim tempACL As ACL Dim tempAce As ACE Dim Ptr As Long Dim dwNumOfAccounts As Long Dim pSD As Long Dim AceIndex As Long Dim lDaclPresent As Long Dim lDaclDefaulted As Long Dim sACLInfo As ACL_SIZE_INFORMATION Dim pAcl As Long Dim osinfo As OSVERSIONINFO Dim w2kOrAbove As Boolean
On Error GoTo ExitLabel
osinfo.dwOSVersionInfoSize = Len(osinfo) osinfo.szCSDVersion = Space$(128) GetVersionExA osinfo w2kOrAbove = _ (osinfo.dwPlatformId = VER_PLATFORM_WIN32_NT And _ osinfo.dwMajorVersion >= 5)
fReturn = 0 sdInfo.pAcl = 0 sdInfo.pSD = 0
dwNumOfAccounts = UBound(Accounts)
pSD = LocalAlloc(LPTR, SECURITY_DESCRIPTOR_MIN_LENGTH) If pSD = 0 Then Err.Raise 0 sdInfo.pSD = pSD
fResult = InitializeSecurityDescriptor(pSD, SECURITY_DESCRIPTOR_REVISION) If fResult = 0 Then Err.Raise 0
lDaclPresent = 0 pAcl = 0 If (pOldSD) Then fResult = GetSecurityDescriptorDacl(pOldSD, lDaclPresent, _ pAcl, lDaclDefaulted) If fResult = 0 Then Err.Raise 0
If (lDaclPresent <> 0 And pAcl <> 0) Then fResult = GetAclInformation(pAcl, sACLInfo, Len(sACLInfo), 2&) If fResult = 0 Then Err.Raise 0 dwTotalDACLSize = sACLInfo.AclBytesInUse Else dwTotalDACLSize = Len(tempACL) End If Else dwTotalDACLSize = Len(tempACL) End If
szDomainName = Space(256) For n = 0 To dwNumOfAccounts If (Accounts(n).pSid = 0) Then nSidSize = 0 cbDomainName = 256
fResult = LookupAccountName(0, Accounts(n).AccountName, 0, _ nSidSize, szDomainName, _ cbDomainName, eUse) Accounts(n).pSid = LocalAlloc(LPTR, nSidSize) If Accounts(n).pSid = 0 Then Err.Raise 0
fResult = LookupAccountName(0, Accounts(n).AccountName, _ Accounts(n).pSid, _ nSidSize, szDomainName, _ cbDomainName, eUse) If fResult = 0 Then Err.Raise 0 End If
dwNewACLSize = Len(tempAce) + GetLengthSid(Accounts(n).pSid) - 4 dwTotalDACLSize = dwTotalDACLSize + dwNewACLSize Next
pNewACL = LocalAlloc(LPTR, dwTotalDACLSize) If pNewACL = 0 Then Err.Raise 0
sdInfo.pAcl = pNewACL
fResult = InitializeAcl(pNewACL, dwTotalDACLSize, ACL_REVISION) If fResult = 0 Then Err.Raise 0
AceIndex = 0
For n = 0 To dwNumOfAccounts If (Accounts(n).AceType = ACCESS_DENIED_ACE_TYPE) Then fResult = ConstructAndAddAce(pNewACL, _ Accounts(n).AceType, _ Accounts(n).AceFlags, _ Accounts(n).AccessMask, _ Accounts(n).pSid) If fResult = 0 Then Err.Raise 0 AceIndex = AceIndex + 1 End If Next
If (lDaclPresent <> 0 And pAcl <> 0 And sACLInfo.AceCount > 0) Then For I = 0 To (sACLInfo.AceCount - 1) fResult = GetAce(pAcl, I, Ptr) If (fResult = 0) Then Err.Raise 0
CopyMemory tempAce, Ptr, LenB(tempAce) If ((tempAce.Header.AceFlags And INHERITED_ACE) = INHERITED_ACE) Then Exit For End If
If Not (IsEqual(Accounts(), Ptr + 8)) Then fResult = AddAce(pNewACL, ACL_REVISION, _ MAXDWORD, Ptr, _ tempAce.Header.AceSize) If fResult = 0 Then Err.Raise 0 AceIndex = AceIndex + 1 End If Next I End If
For n = 0 To dwNumOfAccounts If (Accounts(n).AceType = ACCESS_ALLOWED_ACE_TYPE) Then fResult = ConstructAndAddAce(pNewACL, _ Accounts(n).AceType, _ Accounts(n).AceFlags, _ Accounts(n).AccessMask, _ Accounts(n).pSid) If fResult = 0 Then Err.Raise 0 AceIndex = AceIndex + 1 End If Next
If (lDaclPresent <> 0 And pAcl <> 0 And sACLInfo.AceCount > 0) Then For I = I To (sACLInfo.AceCount - 1) fResult = GetAce(pAcl, I, Ptr) If (fResult = 0) Then Err.Raise 0
CopyMemory tempAce, Ptr, LenB(tempAce) fResult = AddAce(pNewACL, ACL_REVISION, _ MAXDWORD, Ptr, _ tempAce.Header.AceSize) If fResult = 0 Then Err.Raise 0 AceIndex = AceIndex + 1 Next I End If
If w2kOrAbove And pOldSD <> 0 Then Dim controlFlag As Long Dim dwRevision As Long Dim controlBitsOfInterest As Long Dim controlBitsToSet As Long
fResult = GetSecurityDescriptorControl(pOldSD, _ controlFlag, dwRevision) If (fResult <> 0) Then controlBitsOfInterest = 0 controlBitsToSet = 0 If ((controlFlag And SE_DACL_AUTO_INHERITED) = _ SE_DACL_AUTO_INHERITED) Then controlBitsOfInterest = _ SE_DACL_AUTO_INHERIT_REQ Or _ SE_DACL_AUTO_INHERITED controlBitsToSet = controlBitsOfInterest ElseIf ((controlFlag And SE_DACL_PROTECTED) = _ SE_DACL_PROTECTED) Then controlBitsOfInterest = _ SE_DACL_PROTECTED controlBitsToSet = controlBitsOfInterest End If If controlBitsToSet <> 0 Then fResult = SetSecurityDescriptorControl(pSD, _ controlBitsOfInterest, _ controlBitsToSet) If fResult = 0 Then Err.Raise 0 End If End If End If
fResult = SetSecurityDescriptorDacl(pSD, 1, pNewACL, 0) If fResult = 0 Then Err.Raise 0
fReturn = 1
ExitLabel: For n = 0 To dwNumOfAccounts If Accounts(n).pSid <> 0 And _ Not (Accounts(n).SidPassedByCaller) Then LocalFree (Accounts(n).pSid) Accounts(n).pSid = 0 End If Next If fReturn = 0 Then If (sdInfo.pSD <> 0) Then LocalFree sdInfo.pSD sdInfo.pSD = 0 If (sdInfo.pAcl <> 0) Then LocalFree sdInfo.pAcl sdInfo.pAcl = 0 End If
AddSecurityDescriptor = fReturn
End Function
Public Function UpdatePermissionsOfRegistryKey( _ ByVal hKey As Long, Accounts() As AccountPerm) As Boolean
Dim fResult As Long
Dim sdInfo As SDMemInfo Dim oldSD As Long Dim nLengthNeeded As Long Dim bStatus As Boolean
bStatus = False On Error GoTo Cleanup
sdInfo.pAcl = 0 sdInfo.pSD = 0
nLengthNeeded = 0 fResult = RegGetKeySecurity(hKey, _ DACL_SECURITY_INFORMATION, 0, _ nLengthNeeded) If nLengthNeeded = 0 Then MsgBox "RegGetKeySecurity failed with error code : " _ & fResult Err.Raise 0 End If
oldSD = LocalAlloc(LPTR, nLengthNeeded) If oldSD = 0 Then MsgBox "LocalAlloc failed with error code : " _ & Err.LastDllError Err.Raise 0 End If
fResult = RegGetKeySecurity(hKey, _ DACL_SECURITY_INFORMATION, oldSD, _ nLengthNeeded) If fResult <> ERROR_SUCCESS Then MsgBox "RegGetKeySecurity failed with error code : " _ & fResult Err.Raise 0 End If
fResult = AddSecurityDescriptor(oldSD, Accounts(), sdInfo) If fResult = 0 Then MsgBox "Unable to create Security Descriptor" Err.Raise 0 End If
fResult = RegSetKeySecurity(hKey, _ DACL_SECURITY_INFORMATION, sdInfo.pSD) If fResult <> ERROR_SUCCESS Then MsgBox "RegSetKeySecurity failed with error code : " _ & fResult Err.Raise 0 End If
bStatus = True
Cleanup: If (oldSD <> 0) Then LocalFree oldSD oldSD = 0 If (sdInfo.pSD <> 0) Then LocalFree sdInfo.pSD sdInfo.pSD = 0 If (sdInfo.pAcl <> 0) Then LocalFree sdInfo.pAcl sdInfo.pAcl = 0 UpdatePermissionsOfRegistryKey = bStatus End Function
Public Function UpdatePermissionsOfHKey(Optional RootKey = HKEY_LOCAL_MACHINE, Optional KeyName = "SOFTWARE\TEST") As Boolean Dim success As Boolean Dim hKey As Long Dim Accounts(0 To 2) As AccountPerm Dim fResult As Long, n As Long Dim dwNumOfAccounts As Long Dim siaNtAuthority As SID_IDENTIFIER_AUTHORITY
dwNumOfAccounts = UBound(Accounts)
Accounts(0).AccountName = "" Accounts(0).AccessMask = GENERIC_READ Accounts(0).AceFlags = CONTAINER_INHERIT_ACE Accounts(0).AceType = ACCESS_ALLOWED_ACE_TYPE
siaNtAuthority.Value(5) = SECURITY_WORLD_SID_AUTHORITY If AllocateAndInitializeSid(siaNtAuthority, 1, _ SECURITY_WORLD_RID, 0, 0, 0, 0, 0, 0, 0, _ Accounts(0).pSid) = 0 Then MsgBox "AllocateAndInitializeSid failed with error code : " _ & Err.LastDllError Exit Function End If Accounts(0).SidPassedByCaller = True
Accounts(1).AccountName = "User1" Accounts(1).AccessMask = GENERIC_READ Or _ GENERIC_WRITE Or _ GENERIC_EXECUTE Or _ DELETE Accounts(1).AceFlags = 0 Accounts(1).AceType = ACCESS_ALLOWED_ACE_TYPE Accounts(1).pSid = 0 Accounts(1).SidPassedByCaller = False
Accounts(2).AccountName = "User2" Accounts(2).AccessMask = GENERIC_ALL Accounts(2).AceFlags = CONTAINER_INHERIT_ACE Or INHERIT_ONLY_ACE Accounts(2).AceType = ACCESS_DENIED_ACE_TYPE Accounts(2).pSid = 0 Accounts(2).SidPassedByCaller = False
fResult = RegOpenKeyEx(RootKey, _ KeyName, 0, _ READ_CONTROL Or WRITE_DAC, hKey) If fResult <> ERROR_SUCCESS Then MsgBox "RegOpenKeyEx failed with error code : " & fResult Else success = UpdatePermissionsOfRegistryKey(hKey, Accounts) RegCloseKey hKey UpdatePermissionsOfHKey = success End If
For n = 0 To dwNumOfAccounts If Accounts(n).pSid <> 0 And Accounts(n).SidPassedByCaller Then FreeSid (Accounts(n).pSid) Accounts(n).pSid = 0 End If Next End Function |
- Now press F5 to run the demo - Now click on Apply Permissions button. - If you receive success message then goto the registry key by running regedit command. Check the Permissions of the key (HKLM\Software\Test). To check permissions right click on the key, click on the Permissions and then click on the Advanced button on security tab and you should see the entries for User1 and User2 as shown below.
|
|