MS Access VBA Error: Run time error '70' Permission Denied
MS Access VBA Error: Run time error '70' Permission Denied
我认为这个问题是最近更新 MS Office/Access 或 Windows 10 的结果。当我 运行 此代码时:
Dim s As String
With CreateObject("Scriptlet.TypeLib")
s = Left(.Guid, 9)
newguidx = Right(s, 8)
End With
我收到错误消息:对 With 语句的权限被拒绝。这是新的,只有在我的管理员更新我们的系统后才会出现。我没有回滚更新的选项。有人遇到过这个问题并解决了吗?
OS:Windows 7 家企业
访问版本:2010
谢谢
This issue is by design, as of the July security updates. This control is blocked as a security measure to help prevent malicious code from running in Office applications. We are working on getting a knowledgebase article out with the recommended method. Until that KB is ready, I'll post the content here:
Workaround
The preferred method is to change the code to use Windows API CoCreateGuid (https://msdn.microsoft.com/en-us/library/windows/desktop/ms688568(v=vs.85).aspx) instead of CreateObject("Scriptlet.TypeLib").Guid
' No VT_GUID available so must declare type GUID
Private Type GUID_TYPE
Data1 As Long
Data2 As Integer
Data3 As Integer
Data4(7) As Byte
End Type
Private Declare PtrSafe Function CoCreateGuid Lib "ole32.dll" (Guid As GUID_TYPE) As LongPtr
Private Declare PtrSafe Function StringFromGUID2 Lib "ole32.dll" (Guid As GUID_TYPE, ByVal lpStrGuid As LongPtr, ByVal cbMax As Long) As LongPtr
Function CreateGuidString()
Dim guid As GUID_TYPE
Dim strGuid As String
Dim retValue As LongPtr
Const guidLength As Long = 39 'registry GUID format with null terminator {xxxxxxxx-xxxx-xxxx-xxxx-xxxxxxxxxxxx}
retValue = CoCreateGuid(guid)
If retValue = 0 Then
strGuid = String$(guidLength, vbNullChar)
retValue = StringFromGUID2(guid, StrPtr(strGuid), guidLength)
If retValue = guidLength Then
' valid GUID as a string
CreateGuidString = strGuid
End If
End if
End Function
Alternate Workaround
This will allow you to use CreateObject("Scriptlet.TypeLib")
however it will lessen the security protection added by the Office July 2017 security update.
You can set a registry key that will allow Scriptlet.TypeLib
to instantiate inside of Office applications. When this registry key is set, Office will not block any use of this COM control.
- Open Registry Editor.
- Go to: Computer\HKEY_LOCAL_MACHINE\SOFTWARE\Microsoft\Office.0\Common\COM Compatibility{06290BD5-48AA-11D2-8432-006008C3FBFC}
- Note: you may need to search the registry to find the correct location under HKEY_LOCAL_MACHINE based on your installed Office version.
- Add ActivationFilterOverride
- Set DWORD: 1
Detailed Instructions:
- Click Start, click Run, type regedit in the Open box, and then click OK.
Locate and then click the following key in the registry:
HKEY_LOCAL_MACHINE
- On the Edit menu, point to Find, and then enter the following in the Find What: text box:
COM Compatibility
- Ensure Keys is selected, and Values and Data are deselected. Next select Match whole string only, click Find Next
Locate and then click the following key:
{06290BD5-48AA-11D2-8432-006008C3FBFC} Note: if the key is not present you will need to add it. On the Edit menu, point to New, and then click Key. Type in {06290BD5-48AA-11D2-8432-006008C3FBFC}
- On the Edit menu, point to New, and then click DWORD (32-bit) Value
- Type ActivationFilterOverride for the name of the DWORD, and then press Enter.
- Right-click ActivationFilterOverride, and then click Modify.
- In the Value data box, type 1 to enable the registry entry, and then click OK.
- Note to disable the ActivationFilterOverride setting, type 0 (zero), and then click OK.
- Exit Registry Editor, and then restart any open Office application.
由于 windows 更新已取出 "Scriptlet.TypeLib",请尝试以下操作:-
Declare Function CoCreateGuid Lib "ole32" (ByRef GUID As Byte) As Long
Public Function GenerateGUID() As String
Dim ID(0 To 15) As Byte
Dim N As Long
Dim GUID As String
Dim Res As Long
Res = CoCreateGuid(ID(0))
For N = 0 To 15
GUID = GUID & IIf(ID(N) < 16, "0", "") & Hex$(ID(N))
If Len(GUID) = 8 Or Len(GUID) = 13 Or Len(GUID) = 18 Or Len(GUID) = 23 Then
GUID = GUID & "-"
End If
Next N
GenerateGUID = GUID
End Function
或者,
如果您要连接到 SQL Server 2008 或更高版本,请尝试改用 SQL NEWID() 函数。
在 Access 中,我们可以使用这个非常短的函数来生成 GUID,方法是利用 Application.StringFromGUID
将字节转换为 GUID。不过,它会生成非常冗长的 GUID,格式为 {guid {00000000-0000-0000-0000-000000000000}}
。
Declare PtrSafe Sub CoCreateGuid Lib "ole32" (ByVal GUID As LongPtr)
Public Function NewGUID() As String
Dim b(15) As Byte
CoCreateGUID VarPtr(b(0))
NewGUID = Application.StringFromGUID(b)
End Function
您可以删除不需要的字符,例如将此函数的最后一行替换为 NewGUID = Mid(Application.StringFromGUID(b), 8, 36)
。然后,格式将是 00000000-0000-0000-0000-000000000000
我认为这个问题是最近更新 MS Office/Access 或 Windows 10 的结果。当我 运行 此代码时:
Dim s As String
With CreateObject("Scriptlet.TypeLib")
s = Left(.Guid, 9)
newguidx = Right(s, 8)
End With
我收到错误消息:对 With 语句的权限被拒绝。这是新的,只有在我的管理员更新我们的系统后才会出现。我没有回滚更新的选项。有人遇到过这个问题并解决了吗?
OS:Windows 7 家企业 访问版本:2010
谢谢
This issue is by design, as of the July security updates. This control is blocked as a security measure to help prevent malicious code from running in Office applications. We are working on getting a knowledgebase article out with the recommended method. Until that KB is ready, I'll post the content here:
Workaround The preferred method is to change the code to use Windows API CoCreateGuid (https://msdn.microsoft.com/en-us/library/windows/desktop/ms688568(v=vs.85).aspx) instead of
CreateObject("Scriptlet.TypeLib").Guid
' No VT_GUID available so must declare type GUID
Private Type GUID_TYPE
Data1 As Long
Data2 As Integer
Data3 As Integer
Data4(7) As Byte
End Type
Private Declare PtrSafe Function CoCreateGuid Lib "ole32.dll" (Guid As GUID_TYPE) As LongPtr
Private Declare PtrSafe Function StringFromGUID2 Lib "ole32.dll" (Guid As GUID_TYPE, ByVal lpStrGuid As LongPtr, ByVal cbMax As Long) As LongPtr
Function CreateGuidString()
Dim guid As GUID_TYPE
Dim strGuid As String
Dim retValue As LongPtr
Const guidLength As Long = 39 'registry GUID format with null terminator {xxxxxxxx-xxxx-xxxx-xxxx-xxxxxxxxxxxx}
retValue = CoCreateGuid(guid)
If retValue = 0 Then
strGuid = String$(guidLength, vbNullChar)
retValue = StringFromGUID2(guid, StrPtr(strGuid), guidLength)
If retValue = guidLength Then
' valid GUID as a string
CreateGuidString = strGuid
End If
End if
End Function
Alternate Workaround
This will allow you to use
CreateObject("Scriptlet.TypeLib")
however it will lessen the security protection added by the Office July 2017 security update. You can set a registry key that will allowScriptlet.TypeLib
to instantiate inside of Office applications. When this registry key is set, Office will not block any use of this COM control.
- Open Registry Editor.
- Go to: Computer\HKEY_LOCAL_MACHINE\SOFTWARE\Microsoft\Office.0\Common\COM Compatibility{06290BD5-48AA-11D2-8432-006008C3FBFC}
- Note: you may need to search the registry to find the correct location under HKEY_LOCAL_MACHINE based on your installed Office version.
- Add ActivationFilterOverride
- Set DWORD: 1
Detailed Instructions:
- Click Start, click Run, type regedit in the Open box, and then click OK. Locate and then click the following key in the registry: HKEY_LOCAL_MACHINE
- On the Edit menu, point to Find, and then enter the following in the Find What: text box: COM Compatibility
- Ensure Keys is selected, and Values and Data are deselected. Next select Match whole string only, click Find Next Locate and then click the following key: {06290BD5-48AA-11D2-8432-006008C3FBFC} Note: if the key is not present you will need to add it. On the Edit menu, point to New, and then click Key. Type in {06290BD5-48AA-11D2-8432-006008C3FBFC}
- On the Edit menu, point to New, and then click DWORD (32-bit) Value
- Type ActivationFilterOverride for the name of the DWORD, and then press Enter.
- Right-click ActivationFilterOverride, and then click Modify.
- In the Value data box, type 1 to enable the registry entry, and then click OK.
- Note to disable the ActivationFilterOverride setting, type 0 (zero), and then click OK.
- Exit Registry Editor, and then restart any open Office application.
由于 windows 更新已取出 "Scriptlet.TypeLib",请尝试以下操作:-
Declare Function CoCreateGuid Lib "ole32" (ByRef GUID As Byte) As Long
Public Function GenerateGUID() As String
Dim ID(0 To 15) As Byte
Dim N As Long
Dim GUID As String
Dim Res As Long
Res = CoCreateGuid(ID(0))
For N = 0 To 15
GUID = GUID & IIf(ID(N) < 16, "0", "") & Hex$(ID(N))
If Len(GUID) = 8 Or Len(GUID) = 13 Or Len(GUID) = 18 Or Len(GUID) = 23 Then
GUID = GUID & "-"
End If
Next N
GenerateGUID = GUID
End Function
或者, 如果您要连接到 SQL Server 2008 或更高版本,请尝试改用 SQL NEWID() 函数。
在 Access 中,我们可以使用这个非常短的函数来生成 GUID,方法是利用 Application.StringFromGUID
将字节转换为 GUID。不过,它会生成非常冗长的 GUID,格式为 {guid {00000000-0000-0000-0000-000000000000}}
。
Declare PtrSafe Sub CoCreateGuid Lib "ole32" (ByVal GUID As LongPtr)
Public Function NewGUID() As String
Dim b(15) As Byte
CoCreateGUID VarPtr(b(0))
NewGUID = Application.StringFromGUID(b)
End Function
您可以删除不需要的字符,例如将此函数的最后一行替换为 NewGUID = Mid(Application.StringFromGUID(b), 8, 36)
。然后,格式将是 00000000-0000-0000-0000-000000000000