📄 mdirectrw.bas
字号:
Attribute VB_Name = "mDirectRW"
'*****************************************************************
' Module for performing Direct Read/Write access to disk sectors
'
' Written by Arkadiy Olovyannikov (ark@fesma.ru)
' Copyright 2001 by Arkadiy Olovyannikov
'
' This software is FREEWARE. You may use it as you see fit for
' your own projects but you may not re-sell the original or the
' source code.
'
' No warranty express or implied, is given as to the use of this
' program. Use at your own risk.
'*****************************************************************
Option Explicit
Public Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (Destination As Any, Source As Any, ByVal Length As Long)
Public Declare Sub Sleep Lib "kernel32" (ByVal dwMilliseconds As Long)
'*************Win9x direct Read/Write Staff**********
Public Enum FAT_WRITE_AREA_CODE
FAT_AREA = &H2001
ROOT_DIR_AREA = &H4001
DATA_AREA = &H6001
End Enum
Public Type DISK_IO
dwStartSector As Long
wSectors As Integer
dwBuffer As Long
End Type
Public Type DIOC_REGISTER
reg_EBX As Long
reg_EDX As Long
reg_ECX As Long
reg_EAX As Long
reg_EDI As Long
reg_ESI As Long
reg_Flags As Long
End Type
Public Const VWIN32_DIOC_DOS_IOCTL = 1& 'Int13 - 440X functions
Public Const VWIN32_DIOC_DOS_INT25 = 2& 'Int25 - Direct Read Command
Public Const VWIN32_DIOC_DOS_INT26 = 3& 'Int26 - Direct Write Command
Public Const VWIN32_DIOC_DOS_DRIVEINFO = 6& 'Extended Int 21h function 7305h
Public Const FILE_DEVICE_FILE_SYSTEM = &H9&
Public Const FILE_ANY_ACCESS = 0
Public Const FILE_READ_ACCESS = &H1
Public Const FILE_WRITE_ACCESS = &H2
Public Const GENERIC_READ = &H80000000
Public Const GENERIC_WRITE = &H40000000
Public Const FILE_SHARE_READ = &H1
Public Const FILE_SHARE_WRITE = &H2
Public Const OPEN_EXISTING = 3
Public Const INVALID_HANDLE_VALUE = -1&
Public Declare Function CreateFile Lib "kernel32" Alias "CreateFileA" (ByVal lpFileName As String, ByVal dwDesiredAccess As Long, ByVal dwShareMode As Long, ByVal lpSecurityAttributes As Long, ByVal dwCreationDisposition As Long, ByVal dwFlagsAndAttributes As Long, ByVal hTemplateFile As Long) As Long
Public Declare Function CloseHandle Lib "kernel32" (ByVal hObject As Long) As Long
Public Declare Function DeviceIoControl Lib "kernel32" (ByVal hDevice As Long, ByVal dwIoControlCode As Long, ByRef lpInBuffer As Any, ByVal nInBufferSize As Long, ByRef lpOutBuffer As Any, ByVal nOutBufferSize As Long, ByRef lpBytesReturned As Long, ByVal lpOverlapped As Long) As Long
'
'****************** NT direct Read/Write staff**************************************************
Public Declare Function SetFilePointer Lib "kernel32.dll" (ByVal hFile As Long, ByVal lDistanceToMove As Long, lpDistanceToMoveHigh As Long, ByVal dwMoveMethod As Long) As Long
Public Declare Function ReadFile Lib "kernel32" (ByVal hFile As Long, lpBuffer As Any, ByVal nNumberOfBytesToRead As Long, lpNumberOfBytesRead As Long, ByVal lpOverlapped As Long) As Long
Public Declare Function WriteFile Lib "kernel32" (ByVal hFile As Long, lpBuffer As Any, ByVal nNumberOfBytesToWrite As Long, lpNumberOfBytesWritten As Long, ByVal lpOverlapped As Long) As Long
Public Declare Function FlushFileBuffers Lib "kernel32" (ByVal hFile As Long) As Long
Public Declare Function LockFile Lib "kernel32" (ByVal hFile As Long, ByVal dwFileOffsetLow As Long, ByVal dwFileOffsetHigh As Long, ByVal nNumberOfBytesToLockLow As Long, ByVal nNumberOfBytesToLockHigh As Long) As Long
Public Declare Function UnlockFile Lib "kernel32" (ByVal hFile As Long, ByVal dwFileOffsetLow As Long, ByVal dwFileOffsetHigh As Long, ByVal nNumberOfBytesToUnlockLow As Long, ByVal nNumberOfBytesToUnlockHigh As Long) As Long
Public Const FILE_BEGIN = 0
Public Function DirectReadDrive(ByVal sDrive As String, ByVal iStartSec As Long, ByVal iOffset As Long, ByVal cBytes As Long) As Variant
If IsWindowsNT Then
DirectReadDrive = DirectReadDriveNT(sDrive, iStartSec, iOffset, cBytes)
Else
If FSName = "FAT12" Or FSName = "FAT16" Then
DirectReadDrive = DirectReadFloppy9x(sDrive, iStartSec, iOffset, cBytes)
Else
DirectReadDrive = DirectReadDrive9x(sDrive, iStartSec, iOffset, cBytes)
End If
End If
End Function
Public Function DirectWriteDrive(ByVal sDrive As String, ByVal iStartSec As Long, ByVal iOffset As Long, ByVal sWrite As String, Optional AreaCode As FAT_WRITE_AREA_CODE = DATA_AREA) As Boolean
If IsWindowsNT Then
DirectWriteDrive = DirectWriteDriveNT(sDrive, iStartSec, iOffset, sWrite)
Else
If FSName = "FAT12" Or FSName = "FAT16" Then
DirectWriteDrive = DirectWriteFloppy9x(sDrive, iStartSec, iOffset, sWrite)
Else
DirectWriteDrive = DirectWriteDrive9x(sDrive, iStartSec, iOffset, sWrite, AreaCode)
End If
End If
End Function
'===Direct Read/Write floppy using Int25/26===
'Works only for FAT12/16 systems, but much more quicker
'Then Int21 7305 function
Public Function DirectReadFloppy9x(ByVal sDrive As String, ByVal iStartSec As Long, ByVal iOffset As Long, ByVal cBytes As Long) As Variant
Dim hDevice As Long
Dim reg As DIOC_REGISTER
Dim nSectors As Long
Dim aOutBuff() As Byte
Dim abResult() As Byte
Dim nRead As Long
nSectors = Int((iOffset + cBytes - 1) / BytesPerSector) + 1
ReDim aOutBuff(nSectors * BytesPerSector)
ReDim abResult(cBytes - 1) As Byte
With reg
.reg_EAX = Asc(UCase(sDrive)) - Asc("A")
.reg_ESI = &H6000
.reg_ECX = nSectors
.reg_EBX = VarPtr(aOutBuff(0))
.reg_EDX = iStartSec
End With
hDevice = CreateFile("\\.\VWIN32", GENERIC_READ, FILE_SHARE_READ Or FILE_SHARE_WRITE, 0&, OPEN_EXISTING, 0&, 0&)
If hDevice = INVALID_HANDLE_VALUE Then Exit Function
Call DeviceIoControl(hDevice, VWIN32_DIOC_DOS_INT25, reg, Len(reg), reg, Len(reg), nRead, 0&)
CloseHandle hDevice
CopyMemory abResult(0), aOutBuff(iOffset), cBytes
DirectReadFloppy9x = abResult
End Function
Public Function DirectWriteFloppy9x(ByVal sDrive As String, ByVal iStartSec As Long, ByVal iOffset As Long, ByVal sWrite As String) As Boolean
Dim hDevice As Long
Dim reg As DIOC_REGISTER
Dim nSectors As Long
Dim abBuff() As Byte
Dim ab() As Byte
Dim nRead As Long
nSectors = Int((iOffset + Len(sWrite) - 1) / BytesPerSector) + 1
abBuff = DirectReadFloppy9x(sDrive, iStartSec, 0, nSectors * BytesPerSector)
ab = StrConv(sWrite, vbFromUnicode)
CopyMemory abBuff(iOffset), ab(0), Len(sWrite)
With reg
.reg_EAX = Asc(UCase(sDrive)) - Asc("A")
.reg_ESI = &H6000
.reg_ECX = nSectors
.reg_EBX = VarPtr(abBuff(0))
.reg_EDX = iStartSec
End With
hDevice = CreateFile("\\.\VWIN32", GENERIC_READ, FILE_SHARE_READ Or FILE_SHARE_WRITE, 0&, OPEN_EXISTING, 0&, 0&)
If hDevice = INVALID_HANDLE_VALUE Then Exit Function
DirectWriteFloppy9x = DeviceIoControl(hDevice, VWIN32_DIOC_DOS_INT26, reg, Len(reg), reg, Len(reg), nRead, 0&) And Not (reg.reg_Flags And 1)
CloseHandle hDevice
End Function
'====Direct Read/Write drive using Int21 function 7305h====
'works with FAT12/16/32
Public Function DirectReadDrive9x(ByVal sDrive As String, ByVal iStartSec As Long, ByVal iOffset As Long, ByVal cBytes As Long) As Variant
Dim hDevice As Long
Dim reg As DIOC_REGISTER
Dim dio As DISK_IO
Dim abDioBuff() As Byte
Dim nSectors As Long
Dim aOutBuff() As Byte
Dim abResult() As Byte
Dim nRead As Long
nSectors = Int((iOffset + cBytes - 1) / BytesPerSector) + 1
ReDim abResult(cBytes - 1) As Byte
ReDim aOutBuff(nSectors * BytesPerSector - 1)
With dio
.dwStartSector = iStartSec
.wSectors = CInt(nSectors)
.dwBuffer = VarPtr(aOutBuff(0))
End With
ReDim abDioBuff(LenB(dio) - 1)
⌨️ 快捷键说明
复制代码
Ctrl + C
搜索代码
Ctrl + F
全屏模式
F11
切换主题
Ctrl + Shift + D
显示快捷键
?
增大字号
Ctrl + =
减小字号
Ctrl + -