0

最近几年,我在一些 VB6 程序中添加了配置表单。选项卡控件非常方便地为要管理的各种配置分组不同的类别。

我的开发 PC 是一台运行 Windows XP(32 位)Service Pack 3 的虚拟 PC。我正在使用 Visual Basic 6.0 (SP6) 进行编程。

事实证明,其他用户的 PC,不用于 VB6 编程开发和较新版本的 Windows,并不能立即理解如何处理这个“新奇的”选项卡控件。

tabctl32.ocx 是一个 ActiveX 控件模块,其中包含用于选项卡式对话框控件的 SSTab 控件。像 tabctl32.ocx 这样的非系统进程源自您安装在系统上的软件。

vb6 "regfreecom" 为 ocx 文件自动创建清单

最近,我被提醒,在过去的几年里,我制定了一个处理这个问题的过程:

  1. 创建一个简单的小程序,目的是执行相关控制。
  2. 提供所需的清单和资源文件。
  3. 编译、构建和测试程序。
  4. 构建并使用 NSIS 文件来创建 SxS 安装文件,以便在任何目标 PC 上进行测试。
  5. 使用您的原始 VB6 程序,将您的新清单文件和更改合并到其资源文件中,并继续其构建和测试。

  1. 创建一个小型测试简单程序:

    • 打开VB6【新标准EXE】
    • 在项目属性列表中提供名称:(例如:zTABCTL32)
    • 打开工具箱
    • 项目 > 组件 > [浏览]:TABCTL32.ocx [打开] [确定]
    • 单击刚刚添加到工具箱底部的项目(例如:SSTab)
    • 将 SSTab 添加到表单
    • 在表单属性列表中提供名称:(例如:frmTABCTL32)
    • 在表单属性列表中提供一个标题:(例如:TABCTL32)
    • 保存您的表单和项目(操纵和/或创建适当的文件夹)
    • 设置项目 zTABCTL32 属性 [General] > Startup Object: [Sub Main] > [ OK ]
    • 添加到项目:main_zTABCTL32.bas - (Sub Main - frmTABCTL32.show)
    • 编辑 main_zTABCTL32.bas Sub Main() 以确保正确的表单名称在 .Show 命令中
    • 添加到项目:Module1.bas -(声明)
    • 添加到项目:ReadWritePathFile.bas(读取/写入路径/文件的实用程序)
    • 将代码添加到表单 (frmzTABCTL32)
    • 运行[开始完全编译]

main_zTABCTL32.bas - 子主 - frmzTABCTL32.show ...


Attribute VB_Name = "main_zTABCTL32"
Private Type InitCommonControlsExStruct
    lngSize As Long
    lngICC As Long
End Type
Private Declare Function InitCommonControls Lib "comctl32" () As Long
Private Declare Function LoadLibrary Lib "kernel32.dll" Alias "LoadLibraryA" (ByVal lpLibFileName As String) As Long
Private Declare Function FreeLibrary Lib "kernel32.dll" (ByVal hLibModule As Long) As Long
Private Declare Function InitCommonControlsEx Lib "comctl32.dll" (iccex As InitCommonControlsExStruct) As Boolean

Private Sub Main()

    Dim iccex As InitCommonControlsExStruct, hMod As Long
    Const ICC_ALL_CLASSES As Long = &HFDFF& ' combination of all known values
    ' constant descriptions: http://msdn.microsoft.com/en-us/library/bb775507%28VS.85%29.aspx

    With iccex
       .lngSize = LenB(iccex)
       .lngICC = ICC_ALL_CLASSES    ' you really should customize this value from the available constants
    End With
    On Error Resume Next ' error? Requires IEv3 or above
    hMod = LoadLibrary("shell32.dll")
    InitCommonControlsEx iccex
    If Err Then
        InitCommonControls ' try Win9x version
        Err.Clear
    End If
    On Error GoTo 0
    '... show your main form next (i.e., Form1.Show)
    frmTABCTL32.Show
    If hMod Then FreeLibrary hMod


'** Tip 1: Avoid using VB Frames when applying XP/Vista themes
'          In place of VB Frames, use pictureboxes instead.
'** Tip 2: Avoid using Graphical Style property of buttons, checkboxes and option buttons
'          Doing so will prevent them from being themed.

End Sub

'Sub Main()
'    frmTABCTL32.Show
'End Sub

Module1.bas - 表单调整大小和图标操作


Attribute VB_Name = "Module1"
'Re:Bonnie West +vvvvvvvvvvvvvvvvvvvvv
Option Explicit

Public Const WINDOWS_ICON As Integer = 1
Public Const CHROME_ICON  As Integer = 2

Public Const HALF         As Single = 0.5!

Public Const ICON_JUMBO   As Long = 256

Public Const ICON_BIG     As Long = 1
Public Const ICON_SMALL   As Long = 0
Public Const WM_SETICON   As Long = &H80

Public Enum E_DrawIconEx_Flags
    DI_MASK = &H1
    DI_IMAGE = &H2
    DI_NORMAL = &H3
    DI_COMPAT = &H4
    DI_DEFAULTSIZE = &H8
    DI_NOMIRROR = &H10
End Enum
#If False Then
    Dim DI_MASK, DI_IMAGE, DI_NORMAL, DI_COMPAT, DI_DEFAULTSIZE, DI_NOMIRROR
#End If

Public Enum E_GetWindowLong_Index
    GWL_USERDATA = (-21&)
    GWL_EXSTYLE = (-20&)
    GWL_STYLE = (-16&)
    GWL_ID = (-12&)
    GWL_HWNDPARENT = (-8&)
    GWL_HINSTANCE = (-6&)
    GWL_WNDPROC = (-4&)
End Enum
#If False Then
    Dim GWL_USERDATA, GWL_EXSTYLE, GWL_STYLE, GWL_ID, GWL_HWNDPARENT, GWL_HINSTANCE, GWL_WNDPROC
#End If

Public Enum E_LoadImage_Type
    IMAGE_BITMAP = 0
    IMAGE_ICON = 1
    IMAGE_CURSOR = 2
End Enum
#If False Then
    Dim IMAGE_BITMAP, IMAGE_ICON, IMAGE_CURSOR
#End If

Public Enum E_LoadImage_fuLoad
    LR_DEFAULTCOLOR = &H0
    LR_MONOCHROME = &H1
    LR_LOADFROMFILE = &H10
    LR_LOADTRANSPARENT = &H20
    LR_DEFAULTSIZE = &H40
    LR_VGACOLOR = &H80
    LR_LOADMAP3DCOLORS = &H1000
    LR_CREATEDIBSECTION = &H2000
    LR_SHARED = &H8000&
End Enum
#If False Then
    Dim LR_DEFAULTCOLOR, LR_MONOCHROME, LR_LOADFROMFILE, LR_LOADTRANSPARENT, _
    LR_DEFAULTSIZE, LR_VGACOLOR, LR_LOADMAP3DCOLORS, LR_CREATEDIBSECTION, LR_SHARED
#End If

Public Type RECT
    Left   As Long
    Top    As Long
    Right  As Long
    Bottom As Long
End Type

Public Declare Function AdjustWindowRectEx Lib "user32.dll" ( _
    ByRef lpRect As RECT, _
    ByVal dwStyle As Long, _
    ByVal bMenu As Long, _
    ByVal dwExStyle As Long _
) As Long

Public Declare Function DrawIconEx Lib "user32.dll" ( _
             ByVal hDC As Long, _
             ByVal xLeft As Long, _
             ByVal yTop As Long, _
             ByVal hIcon As Long, _
    Optional ByVal cxWidth As Long, _
    Optional ByVal cyWidth As Long, _
    Optional ByVal istepIfAniCur As Long, _
    Optional ByVal hbrFlickerFreeDraw As Long, _
    Optional ByVal diFlags As E_DrawIconEx_Flags = DI_NORMAL _
) As Long

Public Declare Function GetWindowLongW Lib "user32.dll" ( _
    ByVal hWnd As Long, _
    ByVal nIndex As E_GetWindowLong_Index _
) As Long

Public Declare Function LoadImageW Lib "user32.dll" ( _
             ByVal hInst As Long, _
             ByVal lpszName As Long, _
    Optional ByVal uType As E_LoadImage_Type = IMAGE_BITMAP, _
    Optional ByVal cxDesired As Long, _
    Optional ByVal cyDesired As Long, _
    Optional ByVal fuLoad As E_LoadImage_fuLoad = LR_DEFAULTCOLOR _
) As Long

Public Declare Function SendMessageW Lib "user32.dll" ( _
    ByVal hWnd As Long, _
    ByVal uMsg As Long, _
    ByVal wParam As Long, _
    ByVal lParam As Long _
) As Long

'Private Sub Main()
'    MsgBox "Don't forget to set ""windows_perfection_logo_v2_d-bliss.ico"" as Form1's Icon!" & _
'            vbNewLine & "(Set it via the Properties Window)", vbInformation
'    Form1.Show
'    Form2.Show
'End Sub
'Re:Bonnie West +^^^^^^^^^^^^^^^^^^^^^

ReadWritePathFile.bas(读取/写入路径/文件的实用程序)


Option Explicit

Public sOutputPath As String

'Function:  AssurePathExists
'Purpose:   If the complete specified path does not exist, then create it.
'Parms:     sPathName - String - The full path to be assured e.g.:
'               D:\DIR1\DIR2\DIR3  or D:\DIR1\DIR2\DIR3\
'                   If the last character is not a "\", it will be supplied.
'Returns:   True if the path already exists or was successfully created, False if unsucessful.
Public Function AssurePathExists(ByVal sPathName As String) As Boolean
On Error GoTo Exit_AssurePathExists
Dim sTestPath As String, iPos As Integer
    AssurePathExists = False
    If IsNumeric(sPathName) Then Exit Function
    If Len(sPathName) = 0 Then Exit Function
    If Right$(sPathName, 1) <> "\" Then sPathName = sPathName & "\"
    If PathExists(sPathName) Then
        AssurePathExists = True
        Exit Function
    End If
        
    iPos = 0
    Do Until iPos = Len(sPathName)
        iPos = InStr(iPos + 1, sPathName, "\")
        sTestPath = Left$(sPathName, iPos)
        If Not PathExists(sTestPath) Then MkDir sTestPath
    Loop
    AssurePathExists = True
    
Exit_AssurePathExists:
    Exit Function
End Function


Function CloseFileOutput(ByVal iFileNumber As Integer) As Integer
    On Error Resume Next
    Close #iFileNumber
    CloseFileOutput = 0
End Function


'
'Function:  ExtractPath
'Purpose:   extract and return the path part of a full pathname.
'Parms:     FullPathName - String containing the full path name of a file.
'Returns:   String containing the path part of the specified full path file name.
Function ExtractPath(ByVal FullPathName As Variant) As String
    Dim i As String

    'Preset the returned string to an empty string.
    ExtractPath = ""
    
    'Validate input parameter.
    If (VarType(FullPathName) <> vbString) Then Exit Function
    FullPathName = Trim(FullPathName)
    If (Len(FullPathName) = 0) Then Exit Function
    If (InStr(FullPathName, "\") = 0) Then Exit Function
    
    'Find the last "\" in the full path name.
    i = InStrRev(FullPathName, "\")
    
    'Return the path part of the specified full path name.
    ExtractPath = Left$(FullPathName, i - 1)
End Function



Function OpenFileOutput(ByVal sApp_Path_OutFile As String, Optional bAppend As Boolean = False) As Integer           '04apr2011
    On Error GoTo Err_OpenFileOutput
    OpenFileOutput = 0
    If Not PathExists(ExtractPath(sApp_Path_OutFile)) Then Exit Function            '30sep2011
    OpenFileOutput = FreeFile
    If bAppend Then
        Open sApp_Path_OutFile For Append As #OpenFileOutput
    Else
        Open sApp_Path_OutFile For Output As #OpenFileOutput
    End If
Exit_OpenFileOutput:
        Exit Function
Err_OpenFileOutput:
        Select Case Err.Number
            Case 70
                MsgBox Err.Number & " " & Err.Description & vbCrLf & "File: " & sApp_Path_OutFile & " is already open" & vbCrLf & vbCrLf & "     OR  possibly ..." & vbCrLf & "Remove Redirection from command line e.g.:" & vbCrLf & "> " & sApp_Path_OutFile & vbCrLf & "Specify Output file path and name in _.INI file", , "OpenFileOutput "
                OpenFileOutput = 0
                Resume Exit_OpenFileOutput
            Case Else
                MsgBox Err.Number & " " & Err.Description, , "Error in OpenFileOutput() "
                OpenFileOutput = 0
                Resume Exit_OpenFileOutput
        End Select
End Function


'
'Function:  PathExists
'Purpose:   Determine whether or not a pathname is valid.
'Parm:      pathname - String containing a file name or path to be tested.
'Returns:   True, if the path is valid.
'           False, if path is invalid.
Function PathExists(ByVal pathname As String) As Boolean
    Dim res As Variant 'RSF 6/17/98 Declared as Variant to accept a NULL value.
    
    PathExists = False
    
    If IsNumeric(pathname) Then Exit Function                   '29sep2011
    'If input pathname is empty, it's not a valid path
    If (Len(pathname) = 0) Then Exit Function
    
    'Check for valid path. invalid path causes trappable runtime error
    On Error GoTo patherror
    res = Dir(pathname, vbDirectory)
    
    'RSF 6/17/98 Dir can return a NULL, check for a string before proceeding.
    If (VarType(res) <> vbString) Then Exit Function
    
    'If length of the result is zero, it's not a valid path
    If (Len(res) = 0) Then Exit Function
    
    PathExists = True
    Exit Function
    
patherror:
End Function



Public Function SetgsRWApp_Path() As String
On Error Resume Next
Dim sAppPath0 As String, sAppSubFolder As String, sProgramFiles As String, sProgramFilesx86 As String, sProgramData As String, sPUBLIC As String
    
    SetgsRWApp_Path = ""
    sAppPath0 = App.Path
    sProgramFiles = Environ("ProgramFiles")
    sProgramFilesx86 = Environ("ProgramFiles(x86)")
    sProgramData = Environ("ProgramData")
    sPUBLIC = Environ("PUBLIC")

    If (Len(Trim(sPUBLIC)) > 0) Then
        sPUBLIC = Left(sAppPath0, 3) & Mid(sPUBLIC, 4)
    End If
    
    If Len(Trim(sProgramFilesx86)) > 0 Then
        sProgramFilesx86 = Left(sAppPath0, 3) & Mid(sProgramFilesx86, 4)        '28aug2017
        sAppSubFolder = Mid(sAppPath0, InStr(sAppPath0, sProgramFilesx86) + Len(sProgramFilesx86))
        If (Len(Trim(sPUBLIC)) > 0) And (InStr(sAppPath0, sProgramFilesx86) > 0) Then
            SetgsRWApp_Path = sPUBLIC & sAppSubFolder
        ElseIf (Len(Trim(sProgramData)) > 0) And (InStr(sAppPath0, sProgramFilesx86) > 0) Then
            SetgsRWApp_Path = sProgramData & sAppSubFolder
        Else
            MsgBox "Cannot create Read/Write Application Path" & vbCrLf & "sAppPath0='" & sAppPath0 & "'" & vbCrLf & "sProgramFiles='" & sProgramFiles & "'" & vbCrLf & "sProgramFilesx86='" & sProgramFilesx86 & "'" & vbCrLf & "sProgramData='" & sProgramData & "'" & vbCrLf & "sPUBLIC='" & sPUBLIC & "'", vbCritical, "SetgsRWApp_Path"
        End If
    ElseIf Len(Trim(sProgramFiles)) > 0 Then
        sProgramFiles = Left(sAppPath0, 3) & Mid(sProgramFiles, 4)        '28aug2017
        sAppSubFolder = Mid(sAppPath0, InStr(sAppPath0, sProgramFiles) + Len(sProgramFiles))
        If (Len(Trim(sPUBLIC)) > 0) And (InStr(sAppPath0, sProgramFiles) > 0) Then
            SetgsRWApp_Path = sPUBLIC & sAppSubFolder
        ElseIf (Len(Trim(sProgramData)) > 0) And (InStr(sAppPath0, sProgramFiles) > 0) Then
            SetgsRWApp_Path = sProgramData & sAppSubFolder
        Else
            SetgsRWApp_Path = sAppPath0
        End If
    Else
            MsgBox "Cannot create Read/Write Application Path" & vbCrLf & "sAppPath0='" & sAppPath0 & "'" & vbCrLf & "sProgramFiles='" & sProgramFiles & "'" & vbCrLf & "sProgramFilesx86='" & sProgramFilesx86 & "'" & vbCrLf & "sProgramData='" & sProgramData & "'" & vbCrLf & "sPUBLIC='" & sPUBLIC & "'", vbCritical, "SetgsRWApp_Path"
    End If
    
    
End Function



Sub WriteFileOutput(ByVal iFileNumber As Integer, ByVal strOutput As String)
    On Error GoTo Err_WriteFileOutput
    If iFileNumber > 0 Then
        Print #iFileNumber, strOutput
    End If
Exit_WriteFileOutput:
        Exit Sub
Err_WriteFileOutput:
        Select Case Err.Number
            Case Else
                MsgBox Err.Number & " " & Err.Description, , "WriteFileOutput"
                Resume Exit_WriteFileOutput
        End Select
End Sub

将代码添加到表单 (frmzTABCTL32)


Option Explicit     'Don't forget to set the "windows_perfection_logo_v2_d-bliss.ico" icon as the MDIForm's Icon! (Set it via the Properties Window)

Private Const pbID As String = "picIcon"

Private Declare Function DestroyIcon Lib "user32.dll" (ByVal hIcon As Long) As Long
Private Declare Function FindWindowExW Lib "user32.dll" (Optional ByVal hWndParent As Long, Optional ByVal hWndChildAfter As Long, Optional ByVal lpszClass As Long, Optional ByVal lpszWindow As Long) As Long
Private Declare Function InvalidateRect Lib "user32.dll" (ByVal hWnd As Long, Optional ByVal lpRect As Long, Optional ByVal bErase As Long = -True) As Long

Private m_hIcon   As Long
Private m_hWndMC  As Long
Private m_picIcon As VB.PictureBox

Private Const lbID As String = "lblVerPathFile"
Private m_lblVPF As VB.Label
Private sCaption0 As String                                     'SSTab Test Code

Private Sub Form_Load()

    sOutputPath = SetgsRWApp_Path() & "\Data"

    AssurePathExists sOutputPath
'09jun2020 vvvvvvv
Dim strOutfile As String, iFileOutputNumber As Integer, bAppend As Boolean, strRecord As String
    strOutfile = sOutputPath & "\" & Me.Name & ".txt"
    bAppend = True
    strRecord = Me.Name & "   Form_Load() " & App.Path & "  " & strOutfile
    iFileOutputNumber = OpenFileOutput(strOutfile, bAppend)
    WriteFileOutput iFileOutputNumber, strRecord
    CloseFileOutput iFileOutputNumber
'09jun2020 ^^^^^^^
    Set m_lblVPF = Controls.Add("VB.Label", lbID)                   '03jun2020  vvv
    With m_lblVPF
        .Height = 615
        .Left = 240
        .Top = 120
        .Width = 4215
        .Caption = App.EXEName & "  " & App.Major & "." & Format(App.Minor, "00") & "." & Format(App.Revision, "0000") & vbCrLf & sOutputPath & "\" & vbCrLf & Me.Name & ".txt"
        .Visible = True
    End With                                                        '03jun2020  ^^^
    sCaption0 = m_lblVPF.Caption                                'SSTab Test Code

'Re:Bonnie West +vvvvvvvvvvvvvvvvvvvvv
    m_hWndMC = FindWindowExW(hWnd, , StrPtr("MDIClient"))

    If App.LogMode Then
        Set Icon = Nothing
        m_hIcon = LoadImageW(App.hInstance, WINDOWS_ICON, IMAGE_ICON, ICON_JUMBO, ICON_JUMBO)
        SendMessageW hWnd, WM_SETICON, ICON_BIG, LoadImageW(App.hInstance, WINDOWS_ICON, IMAGE_ICON, , , LR_DEFAULTSIZE)
        SendMessageW hWnd, WM_SETICON, ICON_SMALL, LoadImageW(App.hInstance, WINDOWS_ICON, IMAGE_ICON, 16&, 16&)
    End If

    Set m_picIcon = Controls.Add("VB.PictureBox", pbID)
    With m_picIcon
        .AutoRedraw = True
        .BackColor = BackColor
        .BorderStyle = 0
        .ClipControls = False
        .ScaleMode = vbPixels
    End With
'Re:Bonnie West +^^^^^^^^^^^^^^^^^^^^^

End Sub


Private Sub Form_Resize()

'Re:Bonnie West +vvvvvvvvvvvvvvvvvvvvv
    If WindowState <> vbMinimized Then
        With m_picIcon
            .Cls
            .Move 0!, 0!, ScaleWidth, ScaleHeight

            If m_hIcon Then
                DrawIconEx .hDC, (.ScaleWidth - ICON_JUMBO) * HALF, _
                                 (.ScaleHeight - ICON_JUMBO) * HALF, m_hIcon, ICON_JUMBO, ICON_JUMBO
            ElseIf Not Icon Is Nothing Then
               .PaintPicture Icon, (.ScaleWidth - .ScaleX(Icon.Width, vbHimetric, vbPixels)) * HALF, _
                                   (.ScaleHeight - .ScaleY(Icon.Height, vbHimetric, vbPixels)) * HALF
            End If

            Set Picture = .Image
            InvalidateRect m_hWndMC
        End With
    End If
'Re:Bonnie West +^^^^^^^^^^^^^^^^^^^^^

End Sub

Private Sub Form_Unload(Cancel As Integer)

Dim strOutfile As String, iFileOutputNumber As Integer, bAppend As Boolean, strRecord As String
    strOutfile = sOutputPath & "\" & Me.Name & ".txt"
    bAppend = True
'08jun2020    strRecord = Me.Name & vbCrLf & App.EXEName & " " & App.Major & "." & Format(App.Minor, "00") & "." & Format(App.Revision, "0000") & vbCrLf & App.Path
    strRecord = Me.Name & "   " & Format(Now, "yyyy mmm dd hh:nn am/pm") & vbCrLf & App.EXEName & " " & App.Major & "." & Format(App.Minor, "00") & "." & Format(App.Revision, "0000") & vbCrLf & App.Path  '08jun2020
    iFileOutputNumber = OpenFileOutput(strOutfile, bAppend)
    WriteFileOutput iFileOutputNumber, strRecord
    CloseFileOutput iFileOutputNumber
    
    Set m_lblVPF = Nothing
    Controls.Remove lbID

'Re:Bonnie West +vvvvvvvvvvvvvvvvvvvvv
    Set m_picIcon = Nothing
    Controls.Remove pbID

    If m_hIcon Then
        DestroyIcon m_hIcon
        DestroyIcon SendMessageW(hWnd, WM_SETICON, ICON_BIG, 0&)
        DestroyIcon SendMessageW(hWnd, WM_SETICON, ICON_SMALL, 0&)
    End If
'Re:Bonnie West +^^^^^^^^^^^^^^^^^^^^^

End Sub



Private Sub SSTab1_Click(PreviousTab As Integer)

m_lblVPF.Caption = sCaption0 & " [ " & PreviousTab & " ] "      'SSTab Test Code

End Sub

  1. 提供所需的清单和资源文件。

关闭 VB6 zTABCTL32 项目从项目中删除 zTABCTL32.RES

UMMM.ini

  • 此 .ini 文件位于 Identity 行之后,包含一个依赖文件列表。它们列在 .vbp 文件中(例如: Object={BDC217C8-ED16-11CD-956C-0000C04E4C0A}#1.1#0; TABCTL32.OCX )。

  • 您还可以在 VB6 菜单 > 项目 > 组件...

  • 在该组件表单上,您可以选择[x] Selected Items Only更轻松地查看列表。

  • 突出显示列表中的每个组件将显示如下:(e.g.: Location C:\ ... \TABCTL32.OCX )

  • 在 .ini 文件中,我指定了依赖文件的路径,因为它没有存储在本地 Project 文件夹中。


Identity zTABCTL32.exe zTABCTL32.exe "TABCTL32 Test program 1.0"  
File C:\WINDOWS\system32\TABCTL32.ocx

UMMM.bat


UMMM.exe zUMMMTabCtl32.ini .\manifest\zTABCTL32.exe.manifest

pause done?

有没有办法在 Program.exe.manifest 的 UMMM(无人参与的 Make My Manifest)创建中指定 File Name=?


zTABCTL32.exe.manifest我用记事本编辑了结果并更改了:

从: <file name="..\..\..\..\WINDOWS\system32\TABCTL32.ocx">
到: <file name="Dependencies\TABCTL32.ocx">


<?xml version="1.0" encoding="UTF-8" standalone="yes"?>
<assembly xmlns="urn:schemas-microsoft-com:asm.v1" manifestVersion="1.0" xmlns:asmv3="urn:schemas-microsoft-com:asm.v3">
    <assemblyIdentity name="zTABCTL32.exe" processorArchitecture="X86" type="win32" version="1.0.0.20" />
    <description>TABCTL32 Test program 1.0</description>
    <file name="Dependencies\TABCTL32.ocx">
        <typelib tlbid="{BDC217C8-ED16-11CD-956C-0000C04E4C0A}" version="1.1" flags="control,hasdiskimage" helpdir="" />
        <comClass clsid="{BDC217C5-ED16-11CD-956C-0000C04E4C0A}" tlbid="{BDC217C8-ED16-11CD-956C-0000C04E4C0A}" progid="TabDlg.SSTab.1" threadingModel="Apartment" miscStatus="" miscStatusContent="recomposeonresize,cantlinkinside,insideout,activatewhenvisible,simpleframe,setclientsitefirst">
            <progid>TabDlg.SSTab</progid>
        </comClass>
        <comClass clsid="{942085FD-8AEE-465F-ADD7-5E7AA28F8C14}" tlbid="{BDC217C8-ED16-11CD-956C-0000C04E4C0A}" threadingModel="Apartment" miscStatus="" miscStatusContent="recomposeonresize,cantlinkinside,insideout,activatewhenvisible,simpleframe,setclientsitefirst" />
    </file>
</assembly>

MT.bat - 这不适合我吗?
我的参考是:https ://docs.microsoft.com/en-us/windows/win32/sbscs/mt-exe


mt  -nologo -manifest .\manifest\zTABCTL32.exe.manifest -outputresource:"zTABCTL32.RES;1"

pause Done?

资源文件没有创建?我不知道 [#] Resource_ID (1) 是什么?


C:\Devlpmnt\LANG\VB6\zTABCTL32>mt  -nologo -manifest .\manifest\zTABCTL32.exe.ma
nifest -outputresource:"zTABCTL32.RES;1"

mt : general error c101008d: Failed to write the updated manifest to the resourc
e of file "zTABCTL32.RES". The system cannot find the file specified.

C:\Devlpmnt\LANG\VB6\zTABCTL32>pause Done?
Press any key to continue . . .

相反,我使用 ManifestCreatorv2.0.3

 - The Manifest > Create from Project File (vbp) zzTABCTL32.vbp
 - The Manifest > Append/Merge Manifest - From file [e.g.: .\manifest\zTABCTL32.exe.manifest]   
 - The Manifest > Export Manifest >
          [_] Indent Manifest
          [_] Do Not Use Prefixed Name Spaces
          [x] Do Not Export Empty/Blank Attributes
          Destination Resource File - save to zzTABCTL32.RES (Replace)    
 - Open VB6 zTABCTL32 Project or Add zTABCTL32.RES back into Project  


  1. 编译、构建和测试程序。

    • 在 VB6 zTABCTL32 项目中,开始完全编译:运行正常
    • 在 VB6 zTABCTL32 项目中,文件 -> 制作新的可执行文件:
    • 保存项目

在其项目文件夹中运行 zTABCTL32.exe
[Run-Error 7 out of memory?]


  1. 构建并使用 NSIS 文件来创建 SxS 安装文件,以便在任何目标 PC 上进行测试。
I adjusted the NSIS file to install only the dependency files listed in the .vbp file, the UMMM.ini file and in the resulting .exe.manifest file.    

安装在 WinXP(32) 上运行正常
安装在 Win7(64)上运行正常
在 Win10(64) 上安装运行正常


  1. 使用您的原始 VB6 程序,将您的新清单文件和更改合并到其资源文件中,并继续其构建和测试。
4

2 回答 2

0

我正在使用 UMMM 为 SSTab 控件生成一个简单的清单,它可以工作

<?xml version="1.0" encoding="UTF-8" standalone="yes"?>
<assembly xmlns="urn:schemas-microsoft-com:asm.v1" manifestVersion="1.0" xmlns:asmv3="urn:schemas-microsoft-com:asm.v3">
    <assemblyIdentity name="MyCompany.Project1" processorArchitecture="X86" type="win32" version="1.0.0.0" />
    <description>MyCompany Project1 1.0</description>
    <file name="TABCTL32.ocx">
        <typelib tlbid="{BDC217C8-ED16-11CD-956C-0000C04E4C0A}" version="1.1" flags="control,hasdiskimage" helpdir="" />
        <comClass clsid="{BDC217C5-ED16-11CD-956C-0000C04E4C0A}" tlbid="{BDC217C8-ED16-11CD-956C-0000C04E4C0A}" progid="TabDlg.SSTab.1" threadingModel="Apartment" miscStatus="" miscStatusContent="recomposeonresize,cantlinkinside,insideout,activatewhenvisible,simpleframe,setclientsitefirst">
            <progid>TabDlg.SSTab</progid>
        </comClass>
    </file>
</assembly>

在此处查看完整的测试项目。build.batin scriptsshellUmmm.exe生成Project1.ini.manifest,然后用于将此mt.exe清单嵌入到Project1.exe可执行文件中。

如果清单被一次性编译成一个RES文件并且这个Project1.res文件被添加到 VB6 项目中,那么这个批处理文件的执行可以完全跳过。

于 2020-06-09T09:40:46.327 回答
0

我已经通过这些步骤完成了我的 2 个程序,使用UMMM.exeand ManifestCreatorv2.0.3and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and and VB6and an update的更新NSIS file成功地在所有3个系统上运行:

安装在 WinXP(32) 上运行正常
安装在 Win7(64)上运行正常
在 Win10(64) 上安装运行正常

关于 UMMM.exe 和 MT.exe 还有一些我不明白的地方。
额外的理解可能有助于更好的答案。

从这个经验中得出的另一个结论是,不需要为单个依赖文件创建清单文件。

如果有人真的很好奇,我修复的 2 个免费软件程序是https://www.indra.com/~anderci/ciaartcl.htm上的 Gastro 和 QueryMgr

于 2020-06-13T17:40:16.767 回答