⭐ 欢迎来到虫虫下载站! | 📦 资源下载 📁 资源专辑 ℹ️ 关于我们
⭐ 虫虫下载站

📄 biosdir.cls

📁 awd bios文件的修改工具
💻 CLS
📖 第 1 页 / 共 2 页
字号:
VERSION 1.0 CLASS
BEGIN
  MultiUse = -1  'True
  Persistable = 0  'NotPersistable
  DataBindingBehavior = 0  'vbNone
  DataSourceBehavior  = 0  'vbNone
  MTSTransactionMode  = 0  'NotAnMTSObject
END
Attribute VB_Name = "BIOSDir"
Attribute VB_GlobalNameSpace = False
Attribute VB_Creatable = True
Attribute VB_PredeclaredId = False
Attribute VB_Exposed = True
'AwardMod BIOS Manipulation Tool
'Copyright (C) 2001 Josef Hill
'
'This program is free software; you can redistribute it and/or
'modify it under the terms of the GNU General Public License
'as published by the Free Software Foundation; either version 2
'of the License, or any later version.
'
'This program is distributed in the hope that it will be useful,
'but WITHOUT ANY WARRANTY; without even the implied warranty of
'MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
'GNU General Public License for more details.
'
'You should have received a copy of the GNU General Public License
'along with this program; if not, write to the Free Software
'Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA  02111-1307, USA.


Private mCD As String 'Current Directory
Private mIA As Variant
Private mRB As String 'Rom BaseFile
Private mBT As Long 'Flag specifying the BIOS type
Private mR() As RomSeg



Private Type RomSeg
    RomFile_RomSeg As String
    RomBase_RomSeg As String
    RomOffset_RomSeg As String
    RomLocation_RomSeg As String
End Type

'These ALWAYS works on the currently open Directory
Public Function AddFile(FileName As String, Base As Long, Offset As Long) As Long
On Error GoTo lTest
Dim lL As Long
Dim lF As String
    ReDim Preserve mR(LBound(mR) To UBound(mR) + 1)
    If True = False Then
lTest:
        ReDim mR(0)
    End If
    lF = Trim2File(FileName)
    FileCopy FileName, mCD & "Roms\" & lF
    lL = UBound(mR)
    mR(lL).RomFile_RomSeg = lF
    mR(lL).RomBase_RomSeg = Base
    mR(lL).RomOffset_RomSeg = Offset
    AddFile = lL
    'Write Definition to Directory\BIOSDef.txt
    pWriteFile mCD & "BIOSDef.txt", pGenDef
End Function

Public Sub DelFile(iIndex As Long)
Dim lR() As RomSeg
Dim lI As Long
Dim lL As Long
    Kill mCD & "roms\" & mR(iIndex).RomFile_RomSeg
    If UBound(mR) = 0 Then
        mR = lR
        Exit Sub
    End If
        
    ReDim lR(LBound(mR) To UBound(mR) - 1)
    lL = LBound(lR)
    For lI = LBound(mR) To UBound(mR)
        If lI = iIndex Then GoTo lSkip
        lR(lL) = mR(lI)
        lL = lL + 1
lSkip:
    Next lI
    mR = lR
    'Write Definition to Directory\BIOSDef.txt
    pWriteFile mCD & "BIOSDef.txt", pGenDef
End Sub

Public Function GetDataArray() As Variant
On Error GoTo lout
Dim lR As Variant
Dim lC As Integer
Dim lA() As String
    ReDim lA(LBound(mR) To UBound(mR), 0 To 4)
    For lC = LBound(mR) To UBound(mR)
        lA(lC, 0) = lC
        lA(lC, 1) = mR(lC).RomFile_RomSeg
        lA(lC, 2) = mR(lC).RomBase_RomSeg
        lA(lC, 3) = mR(lC).RomOffset_RomSeg
        lA(lC, 4) = mR(lC).RomLocation_RomSeg
    Next lC
    GetDataArray = lA
lout:
End Function

'Load/Save Functions
Public Sub LoadFile(FileName As String)
Dim lS As String
    'test for the File
    If pTestFile(FileName) Then
        'Load BIOS into lS
        lS = pLoadFile(FileName)
        
        'Detect The BIOS Type
        mBT = pDetBIOSType(lS)
        If mBT = -1 Then Exit Sub
        
        'initialize all values
        pInit
        
        'Process Compressed Sections
        pSortBIOS lS
    End If
End Sub

Public Sub LoadDir(DirName As String)
Dim lS As String
    'test for the File
    If (pTestFile(DirName & "BIOSDEF.txt")) And (mBT <> -1) Then
        'Load the Directory
        lS = pLoadFile(DirName & "BIOSDEF.txt")
        'initialize all values
        pInit
        
        pParseDefFile lS
      
        'Save out to the Temp Directory
        pCopyDir DirName, mCD
    End If
End Sub

Public Sub SaveFile(FileName As String)
Dim lS As String
    lS = pGenBIOS
    If Len(lS) = 0 Then Exit Sub
    pWriteFile FileName, lS
End Sub

Public Sub SaveDir(DirName As String)

    pCopyDir mCD, DirName
End Sub


'Support Functions

'reads the bios file and creates a BIOS Dir in Temp
Private Sub pSortBIOS(iStr As String)
Dim lA As Variant
Dim lS As String
Dim lI As Long
    
    'Sort Compressed Sections into lA
    lA = pGetBIOSArray(iStr)
    
    'Write Definition to Directory\BIOSDef.txt
    pWriteFile mCD & "BIOSDef.txt", pGenDef
    
    'generate and Write Base File to Directory\RomBase.bin
    mRB = "RomBase.bin"
    Select Case mBT
    Case Is = 0, 4, 8
        pWriteFile mCD & "RomBase.bin", String(221184, Chr(255)) & Mid(iStr, 221185, 40960)
    Case Is = 1, 3
        pWriteFile mCD & "RomBase.bin", String(212992, Chr(255)) & Mid(iStr, 212993, 49152)
    Case Is = 2
        pWriteFile mCD & "RomBase.bin", String(106496, Chr(255)) & Mid(iStr, 106497, 24576)
    Case Is = 5
        pWriteFile mCD & "RomBase.bin", String(483328, Chr(255)) & Mid(iStr, 483329, 40960)
    Case Is = 6
        pWriteFile mCD & "RomBase.bin", String(237568, Chr(255)) & Mid(iStr, 237569, 24576)
    Case Is = 7
        pWriteFile mCD & "RomBase.bin", String(446464, Chr(255)) & Mid(iStr, 446465, 77824)
    Case Is = 9
        pWriteFile mCD & "RomBase.bin", String(204800, Chr(255)) & Mid(iStr, 204801, 57344)
    End Select
    'Write Decompressed Roms to Directory\Roms\
    For lI = LBound(lA) To UBound(lA)
        lS = lA(lI)
        pDecompress mCD & "Roms\", lS
    Next lI
End Sub

Private Function pDetBIOSType(iStr As String) As Long
Const lIDSTR = "= Award Decompression Bios ="
Const lIDSTR2 = "-lh"
Dim lL As Long
    'At Present we only know of 7 types
    '-1 = unidentified bios
    '0 = old award 4.xx bios, 256K
    '1 = New Medallion BIOS, 256K
    '2 = Old Award 4.xx bios, 128K
    '3 = Old Medallion BIOS, 256K
    '4 = Other Old Medallion BIOS, 256K
    '5 = (384K) Medallion(?) BIOS, 512K
    '6 = Other Old Medallion BIOS, 256K
    '7 = somewhat odd 512K bios
    '8 = Yet Another 256K Medallion BIOS, I need to find a better way to detect structure...
    '9 = see 8
    lL = InStr(1, iStr, lIDSTR) - 1
    Select Case lL
    Case Is = 110592
        pDetBIOSType = 2
    Case Is = 221184
        pDetBIOSType = 4
    Case Is = 212992
        lL = InStr(131072, iStr, lIDSTR2) - 1
        Select Case lL
        Case Is = 131074
            pDetBIOSType = 3
        Case Else
            pDetBIOSType = 1
        End Select
    Case Is = 225280
        pDetBIOSType = 0
    Case Is = 483328
        pDetBIOSType = 5
    Case Is = 237568
        pDetBIOSType = 6
    Case Is = 454592
        pDetBIOSType = 7
    Case Is = 226304
        pDetBIOSType = 8
    Case Is = 204800
        pDetBIOSType = 9
    Case Else
        pDetBIOSType = -1
        MsgBox "This bios is not recognised, please notify awardmod.sourceforge.net"
    End Select
End Function

Private Function pGenBIOS() As String
Dim lLHA As LHA_Handler
Dim lS As String
Dim lI As Long
Dim lN As Long 'Next Address
Dim lT As Long 'Scratch
Dim lCR As String 'Current Rom
    'Load up the Base File
    lS = pLoadFile(mCD & mRB)
    If mBT = 5 Then lN = 131072
    If mBT = 7 Then lN = 131072
    
    'Read in all of the roms and insert them into the bios
    For lI = LBound(mR) To UBound(mR)
        Set lLHA = New LHA_Handler
        lLHA.SetItem Data_eRefs, pLoadFile(mCD & "Roms\" & mR(lI).RomFile_RomSeg)
        lLHA.SetItem LoadBase_eRefs, mR(lI).RomBase_RomSeg
        lLHA.SetItem LoadOffset_eRefs, mR(lI).RomOffset_RomSeg
        lLHA.SetItem FileName_eRefs, mR(lI).RomFile_RomSeg
        lCR = lLHA.GetItem(LHA_eRefs) & Chr(0)

        Select Case mBT
        Case Is = 0, 3, 4, 6
            'Each rom does not get a tag, only the one at 20000H
            Select Case mR(lI).RomLocation_RomSeg
            Case Is = "131072"
                lT = pInsert(lS, lCR, CLng(mR(lI).RomLocation_RomSeg))
                'for the Master Rom, add the arithmetic sum to the end.
                pInsert lS, Chr(Sum8(lCR)), lT
            'in some old medallion bios' and image is at 37000
            'while in others there is an image at 34000
            Case Is = "241664", "212992"
                'This appears to be an image of some sort
                lT = pInsert(lS, lCR, CLng(mR(lI).RomLocation_RomSeg))
            Case Is = ""
                lN = pInsert(lS, lCR, lN)
            End Select
        Case Is = 1, 5, 9
            'There is no fixed location rom in the New Medallion BIOS
            'for other cases, the code may need changing
            lN = pInsert(lS, lCR, lN)
            lN = pInsert(lS, Chr(Sum8(lCR)), lN)
        Case Is = 2, 7, 8
            'There is no fixed location rom in the 128K BIOS.
            'other than perhaps the main code resides at 0, but this is not proven.
            lN = pInsert(lS, lCR, lN)
            If mR(lI).RomBase_RomSeg = 20480 Then
                lN = pInsert(lS, Chr(Sum8(lCR)), lN)
            End If
        Case Else

⌨️ 快捷键说明

复制代码 Ctrl + C
搜索代码 Ctrl + F
全屏模式 F11
切换主题 Ctrl + Shift + D
显示快捷键 ?
增大字号 Ctrl + =
减小字号 Ctrl + -