entering pictures into a table

  • Hi,

    I'm currently working on a database application sql2k back end with vb6 front end. One of the tables will store pictures along with other data fields and I'm not sure how to do that. The tasks are adding, editing, and deleting. I'd appreciate your help. Thank you.

    Dong

  • Check BOL topics

    "Managing ntext, text, and image Data"

    "Modifying ntext, text, or image Values"

    MohammedU
    Microsoft SQL Server MVP

  • The key in your VB6 app will be to convert the image to byte data array, use ADO recordsets for data access, and use GetChunk and AppendChunk to read/write the binary data to a varbinary column.

    Hope this helps



    Mark

  • There is a neat little program called Textcopy.exe, installed together with SQL server 2000, which gives you a way to read the contents of any file into a text, ntext or other 'blob' column.  There are plenty of scripts around that allow you to invoke this tool server-side, so your vb program can handle native files, whithout having to bother with the nitty-gritty of handling the data client-side.

    The bonus is ... a respectable performance-gain !!!

    Try it and find out !

    Frans H.

  • I have had bad (performance) experiences with actually storing pictures IN the database. Although most DB manufacturers claim it can be done, my option of choice is still to store links to the pictures in the database and store the pictures themselves outside the database.

  • My preference would be to keep them in the database - neater and no risk of broken links.  However, zip them up on the client side first (I have used Dynazip in the past) to keep the size and the network load down.  You can keep just the pictures and an id in a separate table on a separate physical drive if you need to.

  • I have to very strongly disagree.  Storing files outside of the database invariably leads to lost files, unauthorized or inappropriate access of the files, and eventual data integrity issues (broken links, moved directories, server access). 

    If the data is part of the application, it should be in the database, whether it is data elements or data files.  Then it is controlled, consistent, backed up, and recoverable.

    Dong Lee; one item I had forgot to mention.  There is an issue with GetChunk/AppendChunk in VB/ADO (not in VB.Net/ADO.net).  Make sure your query has only one text or image field, and it is the last field referenced in the query.  I do remember that at one time, there was a data corruption issue. I think it was fixed in a later VB service pack or MDAC release, but it would be safe to still follow this practice.



    Mark

  • Agree with Mark regarding 'last referenced field'. It's a bug somewhere in the ADO and/or MDAC layer.

    The attached VBScript code should get you in the right direction especially in regards to the routines BlobToFile and FileToBlob. This particulare script's job was to unload all blobs from a table.

    ' unloads all blobs in one or more tables to folder %TEMP%\name;

    ' based on a query returning the following column names:

    ' id - a numeric id value

    ' filename - contains a valid windows file name

    ' blobcontents - contents of blob column

    ' the windows file name is the 6 digit id followed by a dash followed by the file name

    Option Explicit

    Const strScriptname = "UnloadBlobs"

    Dim objConn

    Dim s

    Dim strConnect

    ' used for logging by Log subroutine

    Dim objFso

    Dim strLogfile

    strLogfile = strScriptname & ".log"

    Set objFso = CreateObject("Scripting.FileSystemObject")

    If objFso.FileExists(strLogfile) Then objFso.DeleteFile strLogfile

    Log strScriptname & ".vbs started"

    Log ""

    ' open database

    strConnect = "PROVIDER=SQLOLEDB;DSN=127.0.0.1;DATABASE=ACLATINA;UID=ACLATINA;PWD=ACLATINA"

    'strConnect = "DSN=ACLATINA;UID=ACLATINA;PWD=ACLATINA"

    'strConnect = "PROVIDER=oraoledb.oracle;DATA SOURCE=orcl;USER ID=TRITON;PASSWORD=TRITON"

    'strConnect = "DSN=ORACLE;UID=TRITON;PWD=TRITON"

    Set objConn = CreateObject("ADODB.Connection")

    objConn.Open strConnect

    Log "Connected to database"

    ' repeat this for each table containing blobs which you want to unload

    ' WARNING: it appears that the blobcontents column must be specified as the last column in the select clause

    '          otherwise the ADODB.Stream Write method fails

    s = ""

    s = s & "select l.linkheaderid id,h.originalfilename filename,l.filecontents blobcontents "

    s = s & "from tr_link l "

    s = s & "  join tr_linkheader h on l.linkheaderid=h.linkheaderid "

    DumpBlobs s, "tr_link"

    objConn.Close

    Set objConn = Nothing

    Log ""

    Log "Connection to database closed"

    Log ""

    Log strScriptname & ".vbs ended"

    Sub DumpBlobs(strQuery, strName)

    Dim objRs

    Dim strTempSubDir

    Dim strFilename

    Dim lngRows

    Dim lngTotRows

    ' create destination folder %TEMP%\name

    Set objFso = CreateObject("Scripting.FileSystemObject")

    strTempSubDir = "C:\" & objFso.GetSpecialFolder(2).Name & "\" & strName ' SpecialFolder=TemporaryFolder=2

    If objFso.FolderExists(strTempSubDir) Then objFso.DeleteFolder strTempSubDir, True ' Force=True

    objFso.CreateFolder strTempSubDir

    Log ""

    Log "Dumping blobs to " & strTempSubDir

    ' open recordset

    Set objRs = CreateObject("ADODB.Recordset")

    objRs.Open "select * from (" & strQuery & ") t order by id", objConn, 0, 1 ' CursorType=adOpenForwardOnly=0, LockType=adoLockReadOnly=1

    lngTotRows = RecordCount(objConn, "select count(*) from (" & strQuery & ") t")

    lngRows = 0

    ' loop through recordset rows

    While Not objRs.EOF

      strFilename = strTempSubDir & "\" & Right(CStr(CLng(objRs.Fields("id").Value)+1000000),6) & "-" & objRs.Fields("filename").Value

      ' remove 'bad' characters from file name otherwise ADODB.Stream Write method fails

      strFilename = RemoveBadChar(strFilename)

      BlobToFile objRs.Fields("blobcontents"), strFilename

      lngRows = lngRows + 1

      Log CStr(lngRows) & " of " & CStr(lngTotRows) & " - " & CStr(objRs.Fields("id").Value) & ":" & strFilename

      objRs.MoveNext

    Wend

    objRs.Close

    Set objRs = Nothing

    End Sub

    Sub BlobToFile(adoField, strFilename)

    Dim objStream

    If objFso.FileExists(strFilename) Then objFso.DeleteFile strFilename, True ' Force=True

    Set objStream = CreateObject("ADODB.Stream")

    objStream.Type = 1 ' adTypeBinary

    objStream.Open

    objStream.Write adoField.Value

    objStream.SaveToFile strFilename, 1 ' Options=adSaveCreateNotExist=1

    objStream.Close

    Set objStream = Nothing

       

    End Sub

    Sub FileToBlob(adoField, strFilename)

    Dim objStream

    If Not objFso.FileExists(strFilename) Then Exit Sub

    Set objStream = CreateObject("ADODB.Stream")

    objStream.Type = 1 ' adTypeBinary

    objStream.Open

    objStream.LoadFromFile strFilename

    adoField.Value = objStream.Read

    objStream.Close

    Set objStream = Nothing

    End Sub

    Function RecordCount(objConn, strQuery)

    ' assumes a select count(*) query

    Dim objRs

    Set objRs = CreateObject("ADODB.Recordset")

    objRs.Open strQuery, objConn, 0, 1 ' CursorType=adOpenForwardOnly=0, LockType=adoLockReadOnly=1

    RecordCount = objRs.Fields(0).Value

    objRs.Close

    Set objRs = Nothing

    End Function

    Function RemoveBadChar(strS)

    ' replaces characters less than ascii 32 with the tilde character

    Dim intC

    Dim strS2

    Dim strChar

    Dim lngChar

    strS2 = ""

    If Len(strS) > 0 Then

      For intC = 1 to Len(strS)

        strChar = Mid(strS, intC, 1)

        lngChar = Asc(strChar)

        If lngChar < 32 Then

          strS2 = strS2 & Chr(126) ' ~ tilde character

        Else

          strS2 = strS2 & strChar

        End If

      Next

    End If

    RemoveBadChar = strS2

    End Function

    Sub Log(strText)

    Dim objLogFile

    On Error Resume Next

    WScript.Echo LTrim(Ts() & " " & strText)

    Set objLogfile = objFso.OpenTextFile(strLogfile, 8, True) ' 8=append, True=create if it does not exist

    objLogFile.WriteLine LTrim(Ts() & " " & strText)

    objLogFile.Close

    End Sub

    Function Ts()

    Dim datD

    datD=Now

    Ts = CStr(Year(datD)) & "-" & _

         Mid(CStr(Month(datD)+100), 2) & "-" & _

         Mid(CStr(Day(datD)+100), 2) & " " & _

         Mid(CStr(Hour(datD)+100), 2) & ":" & _

         Mid(CStr(Minute(datD)+100), 2) & ":" & _

         Mid(CStr(Second(datD)+100), 2)

    ' comment this if you want a timestamp in the logging output

    Ts = ""

    End Function

     

  • Thank you all for the replies. I appreciate that.

    With your information I created a form with a text box and a picture box on it, and loaded a picture in the picture box. I'm trying to save that picture into a table. It has become a vb6 question, but does anyone know how to solve the problem? All I found was copying an image from one table to another. ADO provides actualsize, but the picture box does not. Should I use a different control?

    Dong

  • I think the key is to go via a file. The FileToBlob routine can then be used to get it into a table. It is VB6 compatible.

    The VB6 Picture control permits the LoadPicture method to load an image at run time. I know of no way to get the image in a Picture control to a file.

    Thus I presume your problem is that a graphic is generated dynamically in the Picture control through its various drawing and paint methods and you then want to save it into a table. Maybe your better off with another graphics control.

  • Here is a code snippet from an old project I had on my archives.  I don't have VB6 loaded to test this to make sure (I thought it was a little more complicated than this, involving some calls to CopyMemory).  If this does not work, I suggest googling on the terms {byte array picture vb6}.

    'Create a new project, add a command button and a picture box to the project, load a picture into the picture box.
    'Paste this code into Form1
    Private Type BITMAP
        bmType As Long
        bmWidth As Long
        bmHeight As Long
        bmWidthBytes As Long
        bmPlanes As Integer
        bmBitsPixel As Integer
        bmBits As Long
    End Type
    Private Declare Function GetObject Lib "gdi32" Alias "GetObjectA" (ByVal hObject As Long, ByVal nCount As Long, lpObject As Any) As Long
    Private Declare Function GetBitmapBits Lib "gdi32" (ByVal hBitmap As Long, ByVal dwCount As Long, lpBits As Any) As Long
    Private Declare Function SetBitmapBits Lib "gdi32" (ByVal hBitmap As Long, ByVal dwCount As Long, lpBits As Any) As Long
    Dim PicBits() As Byte, PicInfo As BITMAP
    Dim Cnt As Long, BytesPerLine as Long
    Private Sub PictureToByteArray()
        'Get information (such as height and width) about the picturebox
        GetObject Picture1.Image, Len(PicInfo), PicInfo
        'reallocate storage space
        BytesPerLine = (PicInfo.bmWidth * 3 + 3) And &HFFFFFFFC
        ReDim PicBits(1 To BytesPerLine * PicInfo.bmHeight * 3) As Byte
        'Copy the bitmapbits to the array
        GetBitmapBits Picture1.Image, UBound(PicBits), PicBits(1)
        'Invert the bits
        For Cnt = 1 To UBound(PicBits)
            PicBits(Cnt) = 255 - PicBits(Cnt)
        Next Cnt
    End Sub
    Private Sub ByteArrayToPicture()
        'Set the bits back to the picture
        SetBitmapBits Picture1.Image, UBound(PicBits), PicBits(1)
        'refresh
        Picture1.Refresh
    End Sub

    In .Net, it's easier because you can create a MemoryStream and load a picture box from that. See http://support.microsoft.com/kb/317670

    Hope this helps



    Mark

Viewing 11 posts - 1 through 10 (of 10 total)

You must be logged in to reply to this topic. Login to reply