Jump to content

FileDisk virtual disk driver for Windows NT/2K/X


Recommended Posts

I needed soething like this for cdfs, so i guess there is no way for me...

Actually there is something like that, it only applies to files, it is used widely in Microsoft distribution CDs, and implemented in their "internal use only" CDIMAGE.

The purpose is, if you have the SAME file in ore than one directory, all occurrences of the file but one are sustituted by a link pointing to the remaining file.

If I recall correctly, this feature is present in mkisofs windows port too:

http://www.bootcd.us/Mkisofs_options.htm

(you might need some search to find the full man page)

Cannot say if this is what you are looking for, though.

jaclaz

Link to comment
Share on other sites


Yes,

what you need is something more like the good old "SUBST" DOS command.

I don't think such a file/directory redirector exists, or at least I was never been able to find it.

There are two softwares that ( I suppose) use something like this, Rescue 1.2 is now released as freeware (the one for Win98) whilst rescue 2 & 3 (for NT based systems) are Commercial:

http://www.qualystem.com/en/download.html

The other one is this:

http://www.apct.net/en/index.html

(site seems abandoned since 2002 i.e. before they made the XP version, but it is possible to download the demo version for Win2k up to SP2, free registration required)

jaclaz

Link to comment
Share on other sites

  • 3 weeks later...

Bilou and all, I'm actually looking at this for a slightly different application (putting game installs on DVDs).

I want to (without pre-installing a package like Daemontools) mount 2 ISO images, know WHICH drive letters they are and call an installer from the virtual drives.

Is there such a util? In the "old" DOS days I would have used CDEmu or FakeCD (IIRC)...

After install my script can install a noCD patch and unload the ISOs.

ANy ideas gents?

Link to comment
Share on other sites

  • 2 months later...

According to the AUTHOR you have to load the device driver and boot again before loading disk images. I need something I can load, mount image, install from image and (possibly) unload.

As it was I solved the need for that one title I was doing but I'd still like to know IF there is a util that does what I want!

Link to comment
Share on other sites

  • 5 months later...

Here's the vb6 code that shows you how to register FileDisk.sys as a system service and start it without a need to reboot. Just add this module to your project and use RegSVC, StartSVC, StopSVC and UnRegSVC to register, start, stop and unregister FileDisk.sys as a system service. This code assumes that FileDisk.sys is in the same directory.

' Use "RegSVC, StartSVC, StopSVC and UnRegSVC

Option Explicit

Private Type OSVERSIONINFO
dwOSVersionInfoSize As Long
dwMajorVersion As Long
dwMinorVersion As Long
dwBuildNumber As Long
dwPlatformId As Long
szCSDVersion(1 To 128) As Byte
End Type
Private Const VER_PLATFORM_WIN32_NT = 2&

Private Declare Function GetVersionEx Lib "kernel32" Alias "GetVersionExA" (lpVersionInformation As OSVERSIONINFO) As Long

Private Declare Function ShellExecute Lib "shell32" Alias "ShellExecuteA" (ByVal hwnd As Long, ByVal lpOperation As String, ByVal lpFile As String, ByVal lpParameters As String, ByVal lpDirectory As String, ByVal nShowCmd As Long) As Long

Private Const SW_SHOWNORMAL = 1&
Dim ServState As SERVICE_STATE, Installed As Boolean

Private Const ERROR_SERVICE_DOES_NOT_EXIST = 1060&
Private Const SERVICE_WIN32_OWN_PROCESS = &H10&
Private Const SERVICE_KERNEL_DRIVER = &H1&
Private Const SERVICE_WIN32_SHARE_PROCESS = &H20&
Private Const SERVICE_WIN32 = SERVICE_WIN32_OWN_PROCESS + _
SERVICE_WIN32_SHARE_PROCESS
Private Const SERVICE_FILE_SYSTEM_DRIVER = &H2&
Private Const SERVICE_ACCEPT_STOP = &H1
Private Const SERVICE_ACCEPT_PAUSE_CONTINUE = &H2
Private Const SERVICE_ACCEPT_SHUTDOWN = &H4
Private Const SC_MANAGER_CONNECT = &H1&
Private Const SC_MANAGER_CREATE_SERVICE = &H2&
Private Const SC_MANAGER_ENUMERATE_SERVICE = &H4
'Private Const SC_MANAGER_LOCK = &H8
'Private Const SC_MANAGER_QUERY_LOCK_STATUS = &H10
'Private Const SC_MANAGER_MODIFY_BOOT_CONFIG = &H20
Private Const STANDARD_RIGHTS_REQUIRED = &HF0000
Private Const SERVICE_QUERY_CONFIG = &H1&
Private Const SERVICE_CHANGE_CONFIG = &H2&
Private Const SERVICE_QUERY_STATUS = &H4&
Private Const SERVICE_ENUMERATE_DEPENDENTS = &H8&
Private Const SERVICE_START = &H10&
Private Const SERVICE_STOP = &H20&
Private Const SERVICE_PAUSE_CONTINUE = &H40&
Private Const SERVICE_INTERROGATE = &H80&
Private Const SERVICE_USER_DEFINED_CONTROL = &H100&
Private Const SERVICE_ALL_ACCESS = (STANDARD_RIGHTS_REQUIRED Or _
SERVICE_QUERY_CONFIG Or _
SERVICE_CHANGE_CONFIG Or _
SERVICE_QUERY_STATUS Or _
SERVICE_ENUMERATE_DEPENDENTS Or _
SERVICE_START Or _
SERVICE_STOP Or _
SERVICE_PAUSE_CONTINUE Or _
SERVICE_INTERROGATE Or _
SERVICE_USER_DEFINED_CONTROL)
Private Const SERVICE_AUTO_START As Long = 2
Private Const SERVICE_DEMAND_START As Long = 3
Private Const SERVICE_ERROR_NORMAL As Long = 1
Private Const ERROR_INSUFFICIENT_BUFFER = 122&
Private Enum SERVICE_CONTROL
SERVICE_CONTROL_STOP = 1&
SERVICE_CONTROL_PAUSE = 2&
SERVICE_CONTROL_CONTINUE = 3&
SERVICE_CONTROL_INTERROGATE = 4&
SERVICE_CONTROL_SHUTDOWN = 5&
End Enum
Public Enum SERVICE_STATE
SERVICE_STOPPED = &H1
SERVICE_START_PENDING = &H2
SERVICE_STOP_PENDING = &H3
SERVICE_RUNNING = &H4
SERVICE_CONTINUE_PENDING = &H5
SERVICE_PAUSE_PENDING = &H6
SERVICE_PAUSED = &H7
End Enum
Private Type SERVICE_STATUS
dwServiceType As Long
dwCurrentState As Long
dwControlsAccepted As Long
dwWin32ExitCode As Long
dwServiceSpecificExitCode As Long
dwCheckPoint As Long
dwWaitHint As Long
End Type
Private Type QUERY_SERVICE_CONFIG
dwServiceType As Long
dwStartType As Long
dwErrorControl As Long
lpBinaryPathName As Long
lpLoadOrderGroup As Long
dwTagId As Long
lpDependencies As Long
lpServiceStartName As Long
lpDisplayName As Long
End Type
Private Declare Function OpenSCManager _
Lib "advapi32" Alias "OpenSCManagerA" _
(ByVal lpMachineName As String, ByVal lpDatabaseName As String, _
ByVal dwDesiredAccess As Long) As Long
Private Declare Function CreateService _
Lib "advapi32" Alias "CreateServiceA" _
(ByVal hSCManager As Long, ByVal lpServiceName As String, _
ByVal lpDisplayName As String, ByVal dwDesiredAccess As Long, _
ByVal dwServiceType As Long, ByVal dwStartType As Long, _
ByVal dwErrorControl As Long, ByVal lpBinaryPathName As String, _
ByVal lpLoadOrderGroup As String, ByVal lpdwTagId As String, _
ByVal lpDependencies As String, ByVal lp As String, _
ByVal lpPassword As String) As Long
Private Declare Function DeleteService _
Lib "advapi32" (ByVal hService As Long) As Long
Private Declare Function CloseServiceHandle _
Lib "advapi32" (ByVal hSCObject As Long) As Long
Private Declare Function OpenService _
Lib "advapi32" Alias "OpenServiceA" _
(ByVal hSCManager As Long, ByVal lpServiceName As String, _
ByVal dwDesiredAccess As Long) As Long '** Change SERVICE_NAME as needed
Private Declare Function QueryServiceConfig Lib "advapi32" _
Alias "QueryServiceConfigA" (ByVal hService As Long, _
lpServiceConfig As QUERY_SERVICE_CONFIG, _
ByVal cbBufSize As Long, pcbBytesNeeded As Long) As Long
Private Declare Function QueryServiceStatus Lib "advapi32" _
(ByVal hService As Long, lpServiceStatus As SERVICE_STATUS) As Long
Private Declare Function ControlService Lib "advapi32" _
(ByVal hService As Long, ByVal dwControl As SERVICE_CONTROL, _
lpServiceStatus As SERVICE_STATUS) As Long
Private Declare Function StartService Lib "advapi32" _
Alias "StartServiceA" (ByVal hService As Long, _
ByVal dwNumServiceArgs As Long, ByVal lpServiceArgVectors As Long) As Long
Private Declare Function NetWkstaUserGetInfo Lib "Netapi32" (ByVal reserved As Any, ByVal Level As Long, lpBuffer As Any) As Long
Private Declare Function NetApiBufferFree Lib "Netapi32" (ByVal lpBuffer As Long) As Long

Private Declare Function lstrcpy Lib "kernel32" Alias "lstrcpyA" (ByVal lpString1 As Any, ByVal lpString2 As Any) As Long
Private Declare Function lstrlen Lib "kernel32" Alias "lstrlenA" (ByVal lpString As Any) As Long
Private Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (Destination As Any, Source As Any, ByVal Length As Long)
Private Declare Function lstrlenW Lib "kernel32" (ByVal lpString As Long) As Long

Private Const SERVICE_NAME As String = "FileDisk"
Private Const Service_Display_Name As String = "FileDisk"
Private Const Service_File_Name As String = "filedisk.sys"

Public AppPath As String

' This function returns current service status
' or 0 on error
Public Function GetServiceStatus() As SERVICE_STATE
Dim hSCManager As Long, hService As Long, Status As SERVICE_STATUS
hSCManager = OpenSCManager(vbNullString, vbNullString, _
SC_MANAGER_CONNECT)
If hSCManager <> 0 Then
hService = OpenService(hSCManager, SERVICE_NAME, SERVICE_QUERY_STATUS)
If hService <> 0 Then
If QueryServiceStatus(hService, Status) Then
GetServiceStatus = Status.dwCurrentState
End If
CloseServiceHandle hService
End If
CloseServiceHandle hSCManager
End If
End Function

' This function fills Service Account field in form.
' It returns nonzero value on error

Public Function GetServiceConfig() As Long
Dim hSCManager As Long, hService As Long
Dim r As Long, SCfg() As QUERY_SERVICE_CONFIG, r1 As Long, s As String

hSCManager = OpenSCManager(vbNullString, vbNullString, _
SC_MANAGER_CONNECT)
If hSCManager <> 0 Then
hService = OpenService(hSCManager, SERVICE_NAME, SERVICE_QUERY_CONFIG)
If hService <> 0 Then
ReDim SCfg(1 To 1)
If QueryServiceConfig(hService, SCfg(1), 36, r) = 0 Then
If Err.LastDllError = ERROR_INSUFFICIENT_BUFFER Then
r1 = r \ 36 + 1
ReDim SCfg(1 To r1)
If QueryServiceConfig(hService, SCfg(1), r1 * 36, r) <> 0 Then
s = Space$(255)
lstrcpy s, SCfg(1).lpServiceStartName
s = left$(s, lstrlen(s))
Else
GetServiceConfig = Err.LastDllError
End If
Else
GetServiceConfig = Err.LastDllError
End If
End If
CloseServiceHandle hService
Else
GetServiceConfig = Err.LastDllError
End If
CloseServiceHandle hSCManager
Else
GetServiceConfig = Err.LastDllError
End If
End Function

' This function installs service on local computer
' It returns nonzero value on error
Public Function SetNTService() As Long
Dim hSCManager As Long
Dim hService As Long, DomainName As String

hSCManager = OpenSCManager(vbNullString, vbNullString, _
SC_MANAGER_CREATE_SERVICE)
If hSCManager <> 0 Then
' Install service to manual start. To set service to autostart
' replace SERVICE_DEMAND_START to SERVICE_AUTO_START
hService = CreateService(hSCManager, SERVICE_NAME, _
Service_Display_Name, SERVICE_ALL_ACCESS, _
SERVICE_KERNEL_DRIVER, _
SERVICE_DEMAND_START, SERVICE_ERROR_NORMAL, _
App.Path & "\" & Service_File_Name, vbNullString, _
vbNullString, vbNullString, vbNullString, _
vbNullString)

If hService <> 0 Then
CloseServiceHandle hService
Else
SetNTService = Err.LastDllError
End If
CloseServiceHandle hSCManager
Else
SetNTService = Err.LastDllError
End If
End Function

' This function uninstalls service
' It returns nonzero value on error
Public Function DeleteNTService() As Long
Dim hSCManager As Long
Dim hService As Long, Status As SERVICE_STATUS

hSCManager = OpenSCManager(vbNullString, vbNullString, _
SC_MANAGER_CONNECT)
If hSCManager <> 0 Then
hService = OpenService(hSCManager, SERVICE_NAME, _
SERVICE_ALL_ACCESS)
If hService <> 0 Then
' Stop service if it is running
ControlService hService, SERVICE_CONTROL_STOP, Status
If DeleteService(hService) = 0 Then
DeleteNTService = Err.LastDllError
End If
CloseServiceHandle hService
Else
DeleteNTService = Err.LastDllError
End If
CloseServiceHandle hSCManager
Else
DeleteNTService = Err.LastDllError
End If

End Function

' This function returns local network domain name
' or zero-length string on error
Public Function GetDomainName() As String
Dim lpBuffer As Long, l As Long, p As Long
If NetWkstaUserGetInfo(0&, 1&, lpBuffer) = 0 Then
CopyMemory p, ByVal lpBuffer + 4, 4
l = lstrlenW(p)
If l > 0 Then
GetDomainName = Space$(l)
CopyMemory ByVal StrPtr(GetDomainName), ByVal p, l * 2
End If
NetApiBufferFree lpBuffer
End If
End Function

' This function starts service
' It returns nonzero value on error
Public Function StartNTService() As Long
Dim hSCManager As Long, hService As Long
hSCManager = OpenSCManager(vbNullString, vbNullString, _
SC_MANAGER_CONNECT)
If hSCManager <> 0 Then
hService = OpenService(hSCManager, SERVICE_NAME, SERVICE_START)
If hService <> 0 Then
If StartService(hService, 0, 0) = 0 Then
StartNTService = Err.LastDllError
End If
CloseServiceHandle hService
Else
StartNTService = Err.LastDllError
End If
CloseServiceHandle hSCManager
Else
StartNTService = Err.LastDllError
End If
End Function

' This function stops service
' It returns nonzero value on error
Public Function StopNTService() As Long
Dim hSCManager As Long, hService As Long, Status As SERVICE_STATUS
hSCManager = OpenSCManager(vbNullString, vbNullString, _
SC_MANAGER_CONNECT)
If hSCManager <> 0 Then
hService = OpenService(hSCManager, SERVICE_NAME, SERVICE_STOP)
If hService <> 0 Then
If ControlService(hService, SERVICE_CONTROL_STOP, Status) = 0 Then
StopNTService = Err.LastDllError
End If
CloseServiceHandle hService
Else
StopNTService = Err.LastDllError
End If
CloseServiceHandle hSCManager
Else
StopNTService = Err.LastDllError
End If
End Function

' change this to "Public Sub Main ()" if you don't need a form
Public Sub DoService()
RegSVC
StartSVC
'add your code here

StopSVC
UnRegSVC
End
End Sub

Private Sub CheckService()
If GetServiceConfig() = 0 Then
Installed = True
ServState = GetServiceStatus()
Select Case ServState
Case SERVICE_RUNNING
Case SERVICE_STOPPED
Case Else
End Select
Else
Installed = False
End If
End Sub

Public Sub RegSVC()
CheckService
If Not Installed Then
SetNTService
End If
CheckService
'MsgBox ("It's installed")
End Sub

Public Sub UnRegSVC()
CheckService
If Installed Then
DeleteNTService
End If
'MsgBox ("Now it's uninstalled")
End Sub

Public Sub StartSVC()
CheckService
If ServState = SERVICE_STOPPED Then
StartNTService
End If
CheckService
'MsgBox ("Now it's Started")
End Sub

Public Sub StopSVC()
CheckService
If ServState = SERVICE_RUNNING Then
StopNTService
End If
CheckService
'MsgBox ("Now it's Stopped")
End Sub

Here's the thread that explains why I needed this module

http://www.ubcd4win.com/forum/index.php?showtopic=3271&st=15

Edited by pcuser_tom
Link to comment
Share on other sites

  • 8 months later...
  • 3 weeks later...

This guy jeffothy has put 'em all together:

http://www.jeffothy.com/weblog/filedisk-iso-mounter/

check this also:

http://www.benlaufer.com/2006/04/24/filedisk-ua/

“FileDisk uA” is a WinRAR SFX that silently copies filedisk.exe and filedisk.sys to the correct directories and adds appropriate registry keys. It will also associate FileDisk with .iso files so you can mount them by just double clicking on the iso files. It will also add Mount/Unmount on First Device to the context menu for .iso files.

jaclaz

Edited by jaclaz
Link to comment
Share on other sites

  • 3 years later...

is there a amd64 build of the filedisk.exe anywhere? Is it possible to use the sourcecode to build a amd64? I need that for my 64bit winpe to mount images of 64bit windows setups. The driver is available in amd64 yet. Anybody can help to get a filedisk amd64 exe?

Thanks

Link to comment
Share on other sites

Create an account or sign in to comment

You need to be a member in order to leave a comment

Create an account

Sign up for a new account in our community. It's easy!

Register a new account

Sign in

Already have an account? Sign in here.

Sign In Now
  • Recently Browsing   0 members

    • No registered users viewing this page.
×
×
  • Create New...