Права на файли и папки

Язык Visual Basic на платформе .NET.

Модераторы: Ramzes, Sebas

Blaser1976
Начинающий
Начинающий
 
Сообщения: 7
Зарегистрирован: 26.05.2003 (Пн) 12:18

Права на файли и папки

Сообщение Blaser1976 » 26.05.2003 (Пн) 12:25

Подскажите какими средствами можно изменять права на файли и папки. Если у кого есть конкрутные примеры, буду очень благодарен.

Cyrax
Cyberninja
Cyberninja
Аватара пользователя
 
Сообщения: 891
Зарегистрирован: 25.04.2002 (Чт) 21:20
Откуда: Magnitogorsk, Russia

Сообщение Cyrax » 26.05.2003 (Пн) 13:31

из API-Guide:

Declare Function SetFileAttributes Lib "kernel32" Alias "SetFileAttributesA" (ByVal lpFileName As String, ByVal dwFileAttributes As Long) As Long

Description:
The SetFileAttributes function sets a file’s attributes.

Parameters:
· lpFileName
Points to a string that specifies the name of the file whose attributes are to be set.
Windows 95: This string must not exceed MAX_PATH characters.
Windows NT: There is a default string size limit for paths of MAX_PATH characters. This limit is related to how the SetFileAttributes function parses paths. An application can transcend this limit and send in paths longer than MAX_PATH characters by calling the wide (W) version of SetFileAttributes and prepending “\\?\” to the path. The “\\?\” tells the function to turn off path parsing; it lets paths longer than MAX_PATH be used with SetFileAttributesW. This also works with UNC names. The “\\?\” is ignored as part of the path. For example, “\\?\C:\myworld\private” is seen as “C:\myworld\private”, and “\\?\UNC\wow\hotstuff\coolapps” is seen as “\\wow\hotstuff\coolapps”.

· dwFileAttributes
Specifies the file attributes to set for the file. This parameter can be a combination of the following values. However, all other values override FILE_ATTRIBUTE_NORMAL.
FILE_ATTRIBUTE_ARCHIVE
The file is an archive file. Applications use this value to mark files for backup or removal.
FILE_ATTRIBUTE_HIDDEN
The file is hidden. It is not included in an ordinary directory listing.
FILE_ATTRIBUTE_NORMAL
The file has no other attributes set. This value is valid only if used alone.
FILE_ATTRIBUTE_OFFLINE
The data of the file is not immediately available. Indicates that the file data has been physically moved to offline storage.
FILE_ATTRIBUTE_READONLY
The file is read-only. Applications can read the file but cannot write to it or delete it.
FILE_ATTRIBUTE_SYSTEM
The file is part of the operating system or is used exclusively by it.
FILE_ATTRIBUTE_TEMPORARY
The file is being used for temporary storage. File systems attempt to keep all of the data in memory for quicker access rather than flushing the data back to mass storage. A temporary file should be deleted by the application as soon as it is no longer needed.


Constants:
Код: Выделить всё
Public Const FILE_ATTRIBUTE_ARCHIVE = &H20
Public Const FILE_ATTRIBUTE_COMPRESSED = &H800
Public Const FILE_ATTRIBUTE_DIRECTORY = &H10
Public Const FILE_ATTRIBUTE_HIDDEN = &H2
Public Const FILE_ATTRIBUTE_NORMAL = &H80
Public Const FILE_ATTRIBUTE_READONLY = &H1
Public Const FILE_ATTRIBUTE_SYSTEM = &H4
Public Const FILE_ATTRIBUTE_TEMPORARY = &H100
Ты это ему расскажи. Я уже пять болтов отвинтил, и конца не видно... (озадаченно) А это в какую сторону тянуть? Ну-ка... Ага, этот был лишний, этот вообще не отсюда, и этот... Точно, два болта.

Welcome to IRC

Blaser1976
Начинающий
Начинающий
 
Сообщения: 7
Зарегистрирован: 26.05.2003 (Пн) 12:18

Сообщение Blaser1976 » 26.05.2003 (Пн) 18:04

Description:
The SetFileAttributes function sets a file’s attributes.

Прошу не путать права (permissions) со с свойствами (properties).

Cyrax
Cyberninja
Cyberninja
Аватара пользователя
 
Сообщения: 891
Зарегистрирован: 25.04.2002 (Чт) 21:20
Откуда: Magnitogorsk, Russia

Сообщение Cyrax » 27.05.2003 (Вт) 5:33

упс. прощю прощения.... чей-то меня сглючило :)

вот держи. из того же API-Guide'а. правда только для NTFS томов.

The SetFileSecurity function sets the security of a file or directory object. Windows NT 4.0 and later: You can use the SetNamedSecurityInfo function.


Код: Выделить всё
Declare Function SetFileSecurity Lib "advapi32.dll" Alias "SetFileSecurityA" (ByVal lpFileName As String, ByVal SecurityInformation As Long, pSecurityDescriptor As SECURITY_DESCRIPTOR) As Long


· lpFileName
[in] Pointer to a null-terminated string specifying the file or directory for which security is set. Note that security applied to a directory is not inherited by its children.

· SecurityInformation
[in] Specifies a SECURITY_INFORMATION structure identifying the contents of the security descriptor pointed to by the pSecurityDescriptor parameter.

· pSecurityDescriptor
[in] Pointer to a SECURITY_DESCRIPTOR structure.


The SetSecurityDescriptorDacl function sets information in a discretionary access-control list (ACL). If a discretionary ACL is already present in the security descriptor, it is replaced.


Код: Выделить всё
Declare Function SetSecurityDescriptorDacl Lib "advapi32.dll" (pSecurityDescriptor As SECURITY_DESCRIPTOR, ByVal bDaclPresent As Long, pDacl As Byte, ByVal bDaclDefaulted As Long) As Long


· pSecurityDescriptor
[in/out] Pointer to the SECURITY_DESCRIPTOR structure to which the function adds the discretionary ACL. This security descriptor must be in absolute format, meaning that its members must be pointers to other structures, rather than offsets to contiguous data.

· bDaclPresent
[in] Specifies a flag indicating the presence of a discretionary ACL in the security descriptor. If this parameter is TRUE, the function sets the SE_DACL_PRESENT flag in the SECURITY_DESCRIPTOR_CONTROL structure and uses the values in the pDacl and bDaclDefaulted parameters. If it is FALSE, the function clears the SE_DACL_PRESENT flag, and pDacl and bDaclDefaulted are ignored.

· pDacl
[in] Pointer to an ACL structure specifying the discretionary ACL for the security descriptor. If this parameter is NULL, a NULL discretionary ACL is assigned to the security descriptor, allowing all access to the object. The discretionary ACL is referenced by, not copied into, the security descriptor.

· bDaclDefaulted
[in] Specifies a flag indicating the source of the discretionary ACL. If this flag is TRUE, the discretionary ACL has been retrieved by some default mechanism. If FALSE, the discretionary ACL has been explicitly specified by a user. The function stores this value in the SE_DACL_DEFAULTED flag of the SECURITY_DESCRIPTOR_CONTROL structure. If this parameter is not specified, the SE_DACL_DEFAULTED flag is cleared.


Код: Выделить всё
'Example from MSDN (Q240176)
'The following code changes permissions on a folder to Add & Read or Change.
'The folder needs to be created on an NTFS partition.
'You need to be an Administrator on the machine in question and have read/write
'(READ_CONTROL and WRITE_DAC) access to the file or directory.

'1. Create a Standard EXE project in Visual Basic. Form1 is created by default.
'2. Add two Textboxes (Text1 and Text2) and two CommandButtons (Command1 and Command2) to Form1.
'3. Add the following code to the form and the module
'4. Run the application.
'5. In the Test1 TextBox, enter the name of the folder you want to change permissions on. (D:\test is entered by default.)
'    In the Test2 Textbox, enter the name of the user you want to give these permissions to.
'6. Click the Add & Read permissions button to give Add & Read permissions to the folder, or click the Change Permissions
'    button to give Change permissions to the folder.
'7. To check the permissions on the folder, right-click Explorer. Select the Properties menu item, and click the Security
'    Tab of the Properties dialog box. On the Security tab, click the Permissions button. The specific account should say
'    Add & Read or Change depending on which button you clicked in the preceding sample.

'Add this code to the form
Private Sub Command1_Click()
    Dim sUserName As String
    Dim sFolderName As String
    sUserName = Trim$(CStr(Text2.Text))
    sFolderName = Trim$(CStr(Text1.Text))
    SetAccess sUserName, sFolderName, GENERIC_READ Or GENERIC_EXECUTE Or DELETE Or GENERIC_WRITE
End Sub
Private Sub Command2_Click()
    Dim sUserName As String
    Dim sFolderName As String
    sUserName = Trim$(Text2.Text)
    sFolderName = Trim$(Text1.Text)
    SetAccess sUserName, sFolderName, GENERIC_EXECUTE Or GENERIC_READ
End Sub
Private Sub Form_Load()
    Text1.Text = "enter folder name"
    Text2.Text = "enter username"
    Command1.Caption = "Change"
    Command2.Caption = "Read && Add"
End Sub

'Add this code to a module

' Constants used within our API calls. Refer to the MSDN for more
' information on how/what these constants are used for.

' Memory constants used through various memory API calls.
Public Const GMEM_MOVEABLE = &H2
Public Const LMEM_FIXED = &H0
Public Const LMEM_ZEROINIT = &H40
Public Const LPTR = (LMEM_FIXED + LMEM_ZEROINIT)
Public Const GENERIC_READ = &H80000000
Public Const GENERIC_ALL = &H10000000
Public Const GENERIC_EXECUTE = &H20000000
Public Const GENERIC_WRITE = &H40000000

' The file/security API call constants.
' Refer to the MSDN for more information on how/what these constants
' are used for.
Public Const DACL_SECURITY_INFORMATION = &H4
Public Const SECURITY_DESCRIPTOR_REVISION = 1
Public Const SECURITY_DESCRIPTOR_MIN_LENGTH = 20
Public Const SD_SIZE = (65536 + SECURITY_DESCRIPTOR_MIN_LENGTH)
Public Const ACL_REVISION2 = 2
Public Const ACL_REVISION = 2
Public Const MAXDWORD = &HFFFFFFFF
Public Const SidTypeUser = 1
Public Const AclSizeInformation = 2

'  The following are the inherit flags that go into the AceFlags field
'  of an Ace header.

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
Public Const DELETE = &H10000

' Structures used by our API calls.
' Refer to the MSDN for more information on how/what these
' structures are used for.
Type ACE_HEADER
   AceType As Byte
   AceFlags As Byte
   AceSize As Integer
End Type


Public Type ACCESS_DENIED_ACE
  Header As ACE_HEADER
  Mask As Long
  SidStart As Long
End Type

Type ACCESS_ALLOWED_ACE
   Header As ACE_HEADER
   Mask As Long
   SidStart As Long
End Type

Type ACL
   AclRevision As Byte
   Sbz1 As Byte
   AclSize As Integer
   AceCount As Integer
   Sbz2 As Integer
End Type

Type ACL_SIZE_INFORMATION
   AceCount As Long
   AclBytesInUse As Long
   AclBytesFree As Long
End Type

Type SECURITY_DESCRIPTOR
   Revision As Byte
   Sbz1 As Byte
   Control As Long
   Owner As Long
   Group As Long
   sACL As ACL
   Dacl As ACL
End Type

' API calls used within this sample. Refer to the MSDN for more
' information on how/what these APIs do.

Declare Function GetComputerName Lib "kernel32" Alias "GetComputerNameA" (ByVal lpBuffer As String, nSize As Long) As Long
Declare Function GetUserName Lib "advapi32.dll" Alias "GetUserNameA" (ByVal lpBuffer As String, nSize As Long) As Long
Declare Function LookupAccountName Lib "advapi32.dll" Alias "LookupAccountNameA" (lpSystemName As String, ByVal lpAccountName As String, sid As Any, cbSid As Long, ByVal ReferencedDomainName As String, cbReferencedDomainName As Long, peUse As Long) As Long
Declare Function InitializeSecurityDescriptor Lib "advapi32.dll" (pSecurityDescriptor As SECURITY_DESCRIPTOR, ByVal dwRevision As Long) As Long
Declare Function GetSecurityDescriptorDacl Lib "advapi32.dll" (pSecurityDescriptor As Byte, lpbDaclPresent As Long, pDacl As Long, lpbDaclDefaulted As Long) As Long
Declare Function GetFileSecurityN Lib "advapi32.dll" Alias "GetFileSecurityA" (ByVal lpFileName As String, ByVal RequestedInformation As Long, ByVal pSecurityDescriptor As Long, ByVal nLength As Long, lpnLengthNeeded As Long) As Long
Declare Function GetFileSecurity Lib "advapi32.dll" Alias "GetFileSecurityA" (ByVal lpFileName As String, ByVal RequestedInformation As Long, pSecurityDescriptor As Byte, ByVal nLength As Long, lpnLengthNeeded As Long) As Long
Declare Function GetAclInformation Lib "advapi32.dll" (ByVal pAcl As Long, pAclInformation As Any, ByVal nAclInformationLength As Long, ByVal dwAclInformationClass As Long) As Long
Public Declare Function EqualSid Lib "advapi32.dll" (pSid1 As Byte, ByVal pSid2 As Long) As Long
Declare Function GetLengthSid Lib "advapi32.dll" (pSid As Any) As Long
Declare Function InitializeAcl Lib "advapi32.dll" (pAcl As Byte, ByVal nAclLength As Long, ByVal dwAclRevision As Long) As Long
Declare Function GetAce Lib "advapi32.dll" (ByVal pAcl As Long, ByVal dwAceIndex As Long, pace As Any) As Long
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
Declare Function AddAccessAllowedAce Lib "advapi32.dll" (pAcl As Byte, ByVal dwAceRevision As Long, ByVal AccessMask As Long, pSid As Byte) As Long
Public Declare Function AddAccessDeniedAce Lib "advapi32.dll" (pAcl As Byte, ByVal dwAceRevision As Long, ByVal AccessMask As Long, pSid As Byte) As Long
Declare Function SetSecurityDescriptorDacl Lib "advapi32.dll" (pSecurityDescriptor As SECURITY_DESCRIPTOR, ByVal bDaclPresent As Long, pDacl As Byte, ByVal bDaclDefaulted As Long) As Long
Declare Function SetFileSecurity Lib "advapi32.dll" Alias "SetFileSecurityA" (ByVal lpFileName As String, ByVal SecurityInformation As Long, pSecurityDescriptor As SECURITY_DESCRIPTOR) As Long
Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (hpvDest As Any, ByVal hpvSource As Long, ByVal cbCopy As Long)
Public Sub SetAccess(sUserName As String, sFileName As String, lMask As Long)
   Dim lResult As Long            ' Result of various API calls.
   Dim I As Integer               ' Used in looping.
   Dim bUserSid(255) As Byte      ' This will contain your SID.
   Dim bTempSid(255) As Byte      ' This will contain the Sid of each ACE in the ACL .
   Dim sSystemName As String      ' Name of this computer system.

   Dim lSystemNameLength As Long  ' Length of string that contains
                                  ' the name of this system.

   Dim lLengthUserName As Long    ' Max length of user name.

   'Dim sUserName As String * 255  ' String to hold the current user
                                  ' name.


   Dim lUserSID As Long           ' Used to hold the SID of the
                                  ' current user.

   Dim lTempSid As Long            ' Used to hold the SID of each ACE in the ACL
   Dim lUserSIDSize As Long          ' Size of the SID.
   Dim sDomainName As String * 255   ' Domain the user belongs to.
   Dim lDomainNameLength As Long     ' Length of domain name needed.

   Dim lSIDType As Long              ' The type of SID info we are
                                     ' getting back.

   Dim sFileSD As SECURITY_DESCRIPTOR   ' SD of the file we want.

   Dim bSDBuf() As Byte           ' Buffer that holds the security
                                  ' descriptor for this file.

   Dim lFileSDSize As Long           ' Size of the File SD.
   Dim lSizeNeeded As Long           ' Size needed for SD for file.


   Dim sNewSD As SECURITY_DESCRIPTOR ' New security descriptor.

   Dim sACL As ACL                   ' Used in grabbing the DACL from
                                     ' the File SD.

   Dim lDaclPresent As Long          ' Used in grabbing the DACL from
                                     ' the File SD.

   Dim lDaclDefaulted As Long        ' Used in grabbing the DACL from
                                     ' the File SD.

   Dim sACLInfo As ACL_SIZE_INFORMATION  ' Used in grabbing the ACL
                                         ' from the File SD.

   Dim lACLSize As Long           ' Size of the ACL structure used
                                  ' to get the ACL from the File SD.

   Dim pAcl As Long               ' Current ACL for this file.
   Dim lNewACLSize As Long        ' Size of new ACL to create.
   Dim bNewACL() As Byte          ' Buffer to hold new ACL.

   Dim sCurrentACE As ACCESS_ALLOWED_ACE    ' Current ACE.
   Dim pCurrentAce As Long                  ' Our current ACE.

   Dim nRecordNumber As Long

   ' Get the SID of the user. (Refer to the MSDN for more information on SIDs
   ' and their function/purpose in the operating system.) Get the SID of this
   ' user by using the LookupAccountName API. In order to use the SID
   ' of the current user account, call the LookupAccountName API
   ' twice. The first time is to get the required sizes of the SID
   ' and the DomainName string. The second call is to actually get
   ' the desired information.

   lResult = LookupAccountName(vbNullString, sUserName, _
      bUserSid(0), 255, sDomainName, lDomainNameLength, _
      lSIDType)

   ' Now set the sDomainName string buffer to its proper size before
   ' calling the API again.
   sDomainName = Space(lDomainNameLength)

   ' Call the LookupAccountName again to get the actual SID for user.
   lResult = LookupAccountName(vbNullString, sUserName, _
      bUserSid(0), 255, sDomainName, lDomainNameLength, _
      lSIDType)

   ' Return value of zero means the call to LookupAccountName failed;
   ' test for this before you continue.
     If (lResult = 0) Then
        MsgBox "Error: Unable to Lookup the Current User Account: " _
           & sUserName
        Exit Sub
     End If

   ' You now have the SID for the user who is logged on.
   ' The SID is of interest since it will get the security descriptor
   ' for the file that the user is interested in.
   ' The GetFileSecurity API will retrieve the Security Descriptor
   ' for the file. However, you must call this API twice: once to get
   ' the proper size for the Security Descriptor and once to get the
   ' actual Security Descriptor information.

   lResult = GetFileSecurityN(sFileName, DACL_SECURITY_INFORMATION, _
      0, 0, lSizeNeeded)

   ' Redimension the Security Descriptor buffer to the proper size.
   ReDim bSDBuf(lSizeNeeded)

   ' Now get the actual Security Descriptor for the file.
   lResult = GetFileSecurity(sFileName, DACL_SECURITY_INFORMATION, _
      bSDBuf(0), lSizeNeeded, lSizeNeeded)

   ' A return code of zero means the call failed; test for this
   ' before continuing.
   If (lResult = 0) Then
      MsgBox "Error: Unable to Get the File Security Descriptor"
      Exit Sub
   End If

   ' Call InitializeSecurityDescriptor to build a new SD for the
   ' file.
   lResult = InitializeSecurityDescriptor(sNewSD, _
      SECURITY_DESCRIPTOR_REVISION)

   ' A return code of zero means the call failed; test for this
   ' before continuing.
   If (lResult = 0) Then
      MsgBox "Error: Unable to Initialize New Security Descriptor"
      Exit Sub
   End If

   ' You now have the file's SD and a new Security Descriptor
   ' that will replace the current one. Next, pull the DACL from
   ' the SD. To do so, call the GetSecurityDescriptorDacl API
   ' function.

   lResult = GetSecurityDescriptorDacl(bSDBuf(0), lDaclPresent, _
      pAcl, lDaclDefaulted)

   ' A return code of zero means the call failed; test for this
   ' before continuing.
   If (lResult = 0) Then
      MsgBox "Error: Unable to Get DACL from File Security " _
         & "Descriptor"
      Exit Sub
   End If

   ' You have the file's SD, and want to now pull the ACL from the
   ' SD. To do so, call the GetACLInformation API function.
   ' See if ACL exists for this file before getting the ACL
   ' information.
   If (lDaclPresent = False) Then
      MsgBox "Error: No ACL Information Available for this File"
      Exit Sub
   End If

   ' Attempt to get the ACL from the file's Security Descriptor.
   lResult = GetAclInformation(pAcl, sACLInfo, Len(sACLInfo), 2&)

   ' A return code of zero means the call failed; test for this
   ' before continuing.
   If (lResult = 0) Then
      MsgBox "Error: Unable to Get ACL from File Security Descriptor"
      Exit Sub
   End If

   ' Now that you have the ACL information, compute the new ACL size
   ' requirements.
   lNewACLSize = sACLInfo.AclBytesInUse + (Len(sCurrentACE) + _
      GetLengthSid(bUserSid(0))) * 2 - 4

   ' Resize our new ACL buffer to its proper size.
   ReDim bNewACL(lNewACLSize)

   ' Use the InitializeAcl API function call to initialize the new
   ' ACL.
   lResult = InitializeAcl(bNewACL(0), lNewACLSize, ACL_REVISION)

   ' A return code of zero means the call failed; test for this
   ' before continuing.
   If (lResult = 0) Then
      MsgBox "Error: Unable to Initialize New ACL"
      Exit Sub
   End If

   ' If a DACL is present, copy it to a new DACL.
   If (lDaclPresent) Then

      ' Copy the ACEs from the file to the new ACL.
      If (sACLInfo.AceCount > 0) Then

         ' Grab each ACE and stuff them into the new ACL.
         nRecordNumber = 0
         For I = 0 To (sACLInfo.AceCount - 1)

            ' Attempt to grab the next ACE.
            lResult = GetAce(pAcl, I, pCurrentAce)

            ' Make sure you have the current ACE under question.
            If (lResult = 0) Then
               MsgBox "Error: Unable to Obtain ACE (" & I & ")"
               Exit Sub
            End If

            ' You have a pointer to the ACE. Place it
            ' into a structure, so you can get at its size.
            CopyMemory sCurrentACE, pCurrentAce, LenB(sCurrentACE)

            'Skip adding the ACE to the ACL if this is same usersid
            lTempSid = pCurrentAce + 8
            If EqualSid(bUserSid(0), lTempSid) = 0 Then

                ' Now that you have the ACE, add it to the new ACL.
                lResult = AddAce(VarPtr(bNewACL(0)), ACL_REVISION, _
                  MAXDWORD, pCurrentAce, _
                  sCurrentACE.Header.AceSize)

                 ' Make sure you have the current ACE under question.
                 If (lResult = 0) Then
                   MsgBox "Error: Unable to Add ACE to New ACL"
                    Exit Sub
                 End If
                 nRecordNumber = nRecordNumber + 1
            End If

         Next I

         ' You have now rebuilt a new ACL and want to add it to
         ' the newly created DACL.
         lResult = AddAccessAllowedAce(bNewACL(0), ACL_REVISION, _
            lMask, bUserSid(0))

         ' Make sure added the ACL to the DACL.
         If (lResult = 0) Then
            MsgBox "Error: Unable to Add ACL to DACL"
            Exit Sub
         End If

         'If it's directory, we need to add inheritance staff.
         If GetAttr(sFileName) And vbDirectory Then

            ' Attempt to grab the next ACE which is what we just added.
            lResult = GetAce(VarPtr(bNewACL(0)), nRecordNumber, pCurrentAce)

            ' Make sure you have the current ACE under question.
            If (lResult = 0) Then
               MsgBox "Error: Unable to Obtain ACE (" & I & ")"
               Exit Sub
            End If
            ' You have a pointer to the ACE. Place it
            ' into a structure, so you can get at its size.
            CopyMemory sCurrentACE, pCurrentAce, LenB(sCurrentACE)
            sCurrentACE.Header.AceFlags = OBJECT_INHERIT_ACE + INHERIT_ONLY_ACE
            CopyMemory ByVal pCurrentAce, VarPtr(sCurrentACE), LenB(sCurrentACE)

            'add another ACE for files
            lResult = AddAccessAllowedAce(bNewACL(0), ACL_REVISION, _
               lMask, bUserSid(0))

            ' Make sure added the ACL to the DACL.
            If (lResult = 0) Then
               MsgBox "Error: Unable to Add ACL to DACL"
               Exit Sub
            End If

            ' Attempt to grab the next ACE.
            lResult = GetAce(VarPtr(bNewACL(0)), nRecordNumber + 1, pCurrentAce)

            ' Make sure you have the current ACE under question.
            If (lResult = 0) Then
               MsgBox "Error: Unable to Obtain ACE (" & I & ")"
               Exit Sub
            End If

            CopyMemory sCurrentACE, pCurrentAce, LenB(sCurrentACE)
            sCurrentACE.Header.AceFlags = CONTAINER_INHERIT_ACE
            CopyMemory ByVal pCurrentAce, VarPtr(sCurrentACE), LenB(sCurrentACE)
        End If


         ' Set the file's Security Descriptor to the new DACL.
         lResult = SetSecurityDescriptorDacl(sNewSD, 1, _
            bNewACL(0), 0)

         ' Make sure you set the SD to the new DACL.
         If (lResult = 0) Then
            MsgBox "Error: " & _
                "Unable to Set New DACL to Security Descriptor"
            Exit Sub
         End If

         ' The final step is to add the Security Descriptor back to
         ' the file!
         lResult = SetFileSecurity(sFileName, _
            DACL_SECURITY_INFORMATION, sNewSD)

         ' Make sure you added the Security Descriptor to the file!
         If (lResult = 0) Then
            MsgBox "Error: Unable to Set New Security Descriptor " _
               & " to File : " & sFileName
            MsgBox Err.LastDllError
         Else
            MsgBox "Updated Security Descriptor on File: " _
               & sFileName
         End If

      End If

   End If

End Sub
Ты это ему расскажи. Я уже пять болтов отвинтил, и конца не видно... (озадаченно) А это в какую сторону тянуть? Ну-ка... Ага, этот был лишний, этот вообще не отсюда, и этот... Точно, два болта.

Welcome to IRC

CREATOR
Новичок
Новичок
 
Сообщения: 29
Зарегистрирован: 26.03.2003 (Ср) 12:32

Сообщение CREATOR » 27.05.2003 (Вт) 11:30

:D Странно в пространстве имён :arrow: System.IO вроде всё есть т.е. типа FileInfo.Attributes или FileSystemInfo.Attributes


Вернуться в Visual Basic .NET

Кто сейчас на конференции

Сейчас этот форум просматривают: Yandex-бот и гости: 67

    TopList