vb@rchiv
VB Classic
VB.NET
ADO.NET
VBA
C#
Schützen Sie Ihre Software vor Software-Piraterie - mit sevLock 1.0 DLL!  
 vb@rchiv Quick-Search: Suche startenErweiterte Suche starten   Impressum  | Datenschutz  | vb@rchiv CD Vol.6  | Shop Copyright ©2000-2024
 
zurück

 Sie sind aktuell nicht angemeldet.Funktionen: Einloggen  |  Neu registrieren  |  Suchen

Visual-Basic Einsteiger
CD-Nr und Disk-Image 
Autor: VBholic
Datum: 15.12.04 13:46

Hallo!

Ich habe da zwei Probleme, die mich beschäftigen:

1) wie kann ich die individuelle Nr. einer CD zur Identifikation ermitteln?

2) gibt es eine Möglichkeit - und wenn: wie -, von einer Diskette ein Image incl. Bootsektor zu erstellen und dieses als Datei zur Wiederverwendung zu speichern? Und wie kann man dieses Image wieder auf eine (leere) überspielen?

Wäre schön, wenn jemand Lösungen für meine Probleme hätte.

Grüße

VBholic

...enden die Fragen nie?

Themenbaum einblendenGesamtübersicht  |  Zum Thema  |  Suchen

Re: CD-Nr und Disk-Image 
Autor: Zero-G.
Datum: 15.12.04 13:51

Hey VBholic

Also zu Deiner 2. Frage: - Norton bietet das Programm Ghost für solche Fälle an. kostet 30 Euro und kann dafür alles sichern (inkl. Bootsector) auch über ein Netzwerk. - Also z.B. den Server der kein Brennlaufwerk hat - am Brennlaufwerk vom Client sichern & so.

mfg
Themenbaum einblendenGesamtübersicht  |  Zum Thema  |  Suchen

Re: CD-Nr und Disk-Image 
Autor: VBholic
Datum: 15.12.04 20:21

Hallo Null-Schwerkraft !

Jau, das weiß ich - aber ich hatte gedacht, daß es auch mit VB5-Mitteln geht.

War vielleicht zu naiv gedacht.

Trotzdem, Danke und

Grüße

VBholic
Themenbaum einblendenGesamtübersicht  |  Zum Thema  |  Suchen

Re: CD-Nr und Disk-Image 
Autor: Radeonmaster
Datum: 16.12.04 07:58

Zu 1.:
Schau dir dazu mal das an:
http://www.activevb.de/tipps/vb6tipps/tipp0059.html
Themenbaum einblendenGesamtübersicht  |  Zum Thema  |  Suchen

Re: CD-Nr und Disk-Image 
Autor: Radeonmaster
Datum: 16.12.04 07:58

Zu 2.:
Ich hab's noch nie mit Disketten probiert, muss aber ansich funktionieren.
Leider nur für NT und aufwärts.
In ein Modul:
Option Explicit
 
'*****************************************************************
' Module for performing Direct Read/Write access to disk sectors
'
' Written by Arkadiy Olovyannikov (ark@fesma.ru)
'
' formated, cutted, fixed and commented by rm_code
'*****************************************************************
 
Private Const FILE_BEGIN = 0                ' file begin at byte 0
 
'function for reading from a drive (only NT)
Public Function DirectReadDriveNT(ByVal sDrive As String, ByVal iStartSec As _
  Long, ByVal iOffset As Long, ByRef ret() As Byte, Optional ByVal cBytes As _
  Long = -1) As Boolean
    Dim hDevice As Long, nSectors As Long, nRead As Long, BytesPerSector As Long
    Dim abBuff() As Byte, abResult() As Byte
    Dim sd As SECURITY_ATTRIBUTES
 
    'get the size of a disk sector in bytes
    If Not GetSectorSize(sDrive, BytesPerSector) Then Exit Function
 
    If cBytes = -1 Or cBytes < 1 Then cBytes = BytesPerSector
 
    'get the number of sectors to read
    nSectors = Int((iOffset + cBytes - 1) / BytesPerSector) + 1
 
    'open the drive
    hDevice = CreateFile("\\.\" & UCase(Left(sDrive, 1)) & ":", _
                         GENERIC_READ Or GENERIC_WRITE, _
                         FILE_SHARE_READ Or FILE_SHARE_WRITE, _
                         sd, OPEN_EXISTING, 0&, 0&)
 
    'check for a valid drive handle
    If hDevice = INVALID_HANDLE_VALUE Then Exit Function
 
    'set the filepointer to the first sector we want to read
    SetFilePointer hDevice, iStartSec * BytesPerSector, 0, FILE_BEGIN
 
    'prepare the buffers
    ReDim abResult(cBytes - 1)
    ReDim abBuff(nSectors * BytesPerSector - 1)
 
    'read the sectors and close the handle to the drive
    ReadFile hDevice, abBuff(0), UBound(abBuff) + 1, nRead, 0&
    CloseHandle hDevice
 
    'copy the bytes from the read buffer to the result buffer...
    CopyMemory abResult(0), abBuff(iOffset), cBytes
 
    '... and return it
    ret = abResult
    DirectReadDriveNT = True
End Function
 
'function for writing to a drive (only NT)
Public Function DirectWriteDriveNT(ByVal sDrive As String, ByVal iStartSec As _
  Long, ByVal iOffset As Long, ByVal sWrite As String) As Boolean
    Dim hDevice As Long, nRead As Long, nSectors As Long, BytesPerSector As Long
    Dim sd As SECURITY_ATTRIBUTES
    Dim abBuff() As Byte, ab() As Byte
 
    'get the size of a disk sector in bytes
    If Not GetSectorSize(sDrive, BytesPerSector) Then Exit Function
 
    'get the number of sectors to read
    nSectors = Int((iOffset + Len(sWrite) - 1) / BytesPerSector) + 1
 
    'open the drive
    hDevice = CreateFile("\\.\" & UCase(Left(sDrive, 1)) & ":", _
                         GENERIC_READ Or GENERIC_WRITE, _
                         FILE_SHARE_READ Or FILE_SHARE_WRITE, _
                         sd, OPEN_EXISTING, 0&, 0&)
 
    'check for a valid drive handle
    If hDevice = INVALID_HANDLE_VALUE Then Exit Function
 
    'fill the write buffer with the data from the sectors we want to overwrite,
    'because we have the option to start writing from an offset
    DirectReadDriveNT sDrive, iStartSec, 0, abBuff, nSectors * BytesPerSector
    ab = StrConv(sWrite, vbFromUnicode)
 
    'add the data to write to the writebuffer
    CopyMemory abBuff(iOffset), ab(0), Len(sWrite)
 
    'set the filepointer to the first sector we want to write to
    SetFilePointer hDevice, iStartSec * BytesPerSector, 0, FILE_BEGIN
 
    'lock the drive for writing
    LockFile hDevice, LoWord(iStartSec * BytesPerSector), _
                      HiWord(iStartSec * BytesPerSector), _
                      LoWord(nSectors * BytesPerSector), _
                      HiWord(nSectors * BytesPerSector)
 
    'write it!
    DirectWriteDriveNT = WriteFile(hDevice, abBuff(0), UBound(abBuff) + 1, _
      nRead, 0&)
 
    'make sure everything was written
    FlushFileBuffers hDevice
 
    'unlock the drive
    UnlockFile hDevice, LoWord(iStartSec * BytesPerSector), _
                        HiWord(iStartSec * BytesPerSector), _
                        LoWord(nSectors * BytesPerSector), _
                        HiWord(nSectors * BytesPerSector)
 
    'and clean up a little bit
    CloseHandle hDevice
End Function
Themenbaum einblendenGesamtübersicht  |  Zum Thema  |  Suchen

Re: CD-Nr und Disk-Image 
Autor: Radeonmaster
Datum: 16.12.04 07:58


und dann folgende 2 Funktionen zum Lesen und Schreiben des Bootsektors:
Public Function ReadBootSector(sDrive As String, sDestFile As String) As Boolean
    On Error GoTo ErrH
 
    Dim ret() As Byte
    Dim FF As Byte: FF = FreeFile
 
    If Not DirectReadDriveNT(sDrive, 0, 1, ret) Then Exit Function
 
    Open sDestFile For Binary As #FF
        Put #FF, , ret
    Close #FF
 
    ReadBootSector = True
 
ErrH:
End Function
 
Public Function WriteBootSector(sDrive As String, sBootImage As String) As _
  Boolean
    On Error GoTo ErrH
 
    Dim FF As Byte: FF = FreeFile
    Dim sRet As String
    Dim ret() As Byte
 
    Open sBootImage For Binary As #FF
        ReDim ret(FileLen(sBootImage )) As Byte
        Get #FF, , ret
    Close #FF
 
    sRet = StrConv(ret, vbUnicode)
 
    WriteBootSector = DirectWriteDriveNT(sDrive, 0, 0, ret)
 
ErrH:
End Function
Das Lesen sollte auf jedenfall klappen, wenn das Schreiben nicht funktionieren sollte,
schau ich's mir nochmal genauer an.
Im moment hab ich leider kein Floppy
Themenbaum einblendenGesamtübersicht  |  Zum Thema  |  Suchen

Re:CD-Nr und Disk-Image 
Autor: VBholic
Datum: 16.12.04 16:29

Hallo Radeonmaster!

Whow - und Danke!

Ich habe zwar nur WIN98 mit VB5, werde mich jedoch am Wochenende intensiv mit Deinem Vorschlag beschäftigen. Rückmeldung garantiert!

Der Tipp aus "ActiveVB' ist auch super!

Danke und Grüße

VBholic

...enden die Fragen nie?

Themenbaum einblendenGesamtübersicht  |  Zum Thema  |  Suchen

Re:CD-Nr und Disk-Image 
Autor: Radeonmaster
Datum: 16.12.04 16:55

Freut mich

Hab die API Deklarationen völlig vergessen:

Option Explicit
 
Public Declare Function GetDiskFreeSpace Lib "kernel32.dll" Alias _
  "GetDiskFreeSpaceA" ( _
    ByVal lpRootPathName As String, lpSectorsPerCluster As Long, _
    lpBytesPerSector As Long, lpNumberOfFreeClusters As Long, _
    lpTotalNumberOfClusters 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, ByRef lpOverlapped As OVERLAPPED _
) As Long
 
Public Declare Function CreateFile Lib "kernel32" Alias "CreateFileA" ( _
    ByVal lpFileName As String, ByVal dwDesiredAccess As Long, _
    ByVal dwShareMode As Long, ByRef lpSecurityAttributes As _
    SECURITY_ATTRIBUTES, _
    ByVal dwCreationDisposition As Long, ByVal dwFlagsAndAttributes As Long, _
    ByVal hTemplateFile 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 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 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 Declare Function SetFilePointer Lib "kernel32" ( _
    ByVal hFile As Long, ByVal lDistanceToMove As Long, _
    lpDistanceToMoveHigh As Long, ByVal dwMoveMethod As Long _
) As Long
 
Public Declare Function GetVersionEx Lib "kernel32" Alias "GetVersionExA" ( _
        lpVersionInformation As OSVERSIONINFOEX _
) As Long
 
Public Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" ( _
    Destination As Any, Source As Any, ByVal length As Long _
)
 
Public Declare Function GetDriveType Lib "kernel32" Alias "GetDriveTypeA" ( _
    ByVal nDrive As String _
) As Long
 
Public Declare Function FlushFileBuffers Lib "kernel32" ( _
    ByVal hFile As Long _
) As Long
 
Public Declare Function CloseHandle Lib "kernel32" ( _
    ByVal hObject As Long _
) As Long
 
Public Type SECURITY_ATTRIBUTES
    nLength As Long
    lpSecurityDescriptor As Long
    bInheritHandle As Long
End Type
 
Public Type OSVERSIONINFOEX
    dwOSVersionInfoSize As Long
    dwMajorVersion As Long
    dwMinorVersion As Long
    dwBuildNumber As Long
    dwPlatformId As Long
    szCSDVersion As String * 128
End Type
 
Public Type OVERLAPPED
    Internal As Long
    InternalHigh As Long
    offset As Long
    OffsetHigh As Long
    hEvent As Long
End Type
 
Public Const VER_PLATFORM_WIN32s = 0
Public Const VER_PLATFORM_WIN32_WINDOWS = 1
Public Const VER_PLATFORM_WIN32_NT = 2
 
Public Const FILE_ATTRIBUTE_NORMAL = &H80  ' ?
Public Const GENERIC_READ = &H80000000     ' Generic read flag
Public Const GENERIC_WRITE = &H40000000    ' Generic write flag
Public Const FILE_READ_ACCESS = &H1        ' Readrights
Public Const FILE_WRITE_ACCESS = &H2       ' Writerights
Public Const FILE_SHARE_READ = &H1         ' shared read rights
Public Const FILE_SHARE_WRITE = &H2        ' shared write rights
Public Const OPEN_EXISTING = 3             ' open an existing file
Public Const INVALID_HANDLE_VALUE = -1&    ' invalid handle
 
Public Function LoWord(ByVal nDWord As Long) As Long
  LoWord = CLng("&H" & Left$(Right$("00000000" & Hex$(nDWord), 8), 4))
End Function
 
Public Function HiWord(ByVal nDWord As Long) As Long
  HiWord = CLng("&H" & Right$(Right$("00000000" & Hex$(nDWord), 8), 4))
End Function
 
Public Function GetSectorSize(ByVal drv As String, ByRef lSize As Long) As _
  Boolean
    Dim lSpC As Long, lBpS As Long, lNoFC As Long, lTNoC As Long
 
    If GetDiskFreeSpace(Left$(drv, 1) & ":", lSpC, lSize, lNoFC, lTNoC) <> 0 _
      Then _
        GetSectorSize = True
End Function
Themenbaum einblendenGesamtübersicht  |  Zum Thema  |  Suchen

Re:CD-Nr und Disk-Image 
Autor: VBholic
Datum: 18.12.04 15:47

Hallo Radeonmaster!

Wollte Dir gerade schreiben, daß ich mit dem Code leider nicht zurechtkomme.

Aber - jetzt geht's erst mal weiter

Melde mich nochmal!


Gruß BVholic
Themenbaum einblendenGesamtübersicht  |  Zum Thema  |  Suchen

Re:CD-Nr und Disk-Image 
Autor: VBholic
Datum: 19.12.04 19:14

Hallo Radeonmaster!

Das Ganze klappt auch mit den Deklarationen nicht - das Problem liegt wohl hier:

  'open the drive
  hDevice = CreateFile("\\.\" & UCase(Left(sDrive, 1)) & ":", _
            GENERIC_READ Or GENERIC_WRITE, _
            FILE_SHARE_READ Or FILE_SHARE_WRITE, _
            sd, OPEN_EXISTING, 0&, 0&)
 
  'check for a valid drive handle
  If hDevice = INVALID_HANDLE_VALUE Then Exit Function
hDevice gibt INVALID_HANDLE_VALUE zurück.

Das Floppy-LW wird angesprochen, die Sektorengröße richtig erkannt. Leider gehen meine Kenntnisse nicht weiter. Wahrscheinlich doch nur für NT!?

Schade zwar, trotzdem:

Danke für Deine Mühen!

...enden die Fragen nie?

Themenbaum einblendenGesamtübersicht  |  Zum Thema  |  Suchen

Re:CD-Nr und Disk-Image 
Autor: Radeonmaster
Datum: 20.12.04 17:23

Ich hab noch ne Windows 9x Version gefunden,
und versucht, die wieder auf die Beine zu bekommen,
aber da ich XP hab, kann ich leider das Lesen und Schreiben selbst nicht debuggen :-/
Ich hoffe, dass es trotzdem tut:
http://actorics.de/rm_code/9x.txt
Themenbaum einblendenGesamtübersicht  |  Zum Thema  |  Suchen

Sie sind nicht angemeldet!
Um auf diesen Beitrag zu antworten oder neue Beiträge schreiben zu können, müssen Sie sich zunächst anmelden.

Einloggen  |  Neu registrieren

Funktionen:  Zum Thema  |  GesamtübersichtSuchen 

nach obenzurück
 
   

Copyright ©2000-2024 vb@rchiv Dieter Otter
Alle Rechte vorbehalten.
Microsoft, Windows und Visual Basic sind entweder eingetragene Marken oder Marken der Microsoft Corporation in den USA und/oder anderen Ländern. Weitere auf dieser Homepage aufgeführten Produkt- und Firmennamen können geschützte Marken ihrer jeweiligen Inhaber sein.

Diese Seiten wurden optimiert für eine Bildschirmauflösung von mind. 1280x1024 Pixel