+ Reply to Thread
Results 1 to 7 of 7

Need Help with Inserting in SQL

  1. #1
    Livin
    Guest

    Need Help with Inserting in SQL

    This is code I had working a few years back in Excel 2000 & XP using SQL
    2000. Now I'm needing the code again but using SQL Express 2005 and with
    Excel 2003 and it seems to have broken, I think.

    I've setup SQL Express 2005 with the Table "Logos" with Columns imgLogo &
    txtLogo

    I'm trying to take files from a folder and place the text name and the image
    itself into the database.

    I was doing this with CopyLogosToDataBase() - but this seems to fail to get
    the file names at all now - i.e. it returns no files in the search... it
    worked perfecting in Excel 2000 (a few years back).

    I have replaced CopyLogosToDataBase() with GetAllFiles() &
    GetAllFilesInDir() & InsertLogoToDataBase() - they run in this order. The
    new GetAllFiles* functions get the file names properly and the Insert
    function is the core of the CopyLogos sub which inserts into the SQL DB.

    Any help you guru's can give a born-again noobie is highly appreciated!

    thanks,
    Aaron

    MODULE...

    Public cnnODBC, cnnDatabase, cnnTable, cnnUserID, cnnPassword As String
    Public cnn1 As ADODB.Connection
    Public logoTable As String
    Public rsUnit As ADODB.Recordset

    Sub Aaron()
    cnnODBC = "r2\sqlexpress" 'Server Name
    cnnDatabase = "lrhist" 'Database Name
    cnnTable = "tbLrmstr" 'Table Name
    cnnUserID = "sa" 'Database User ID
    cnnPassword = "sa" 'Database User Password
    logoTable = "Logos" 'Table with Logo data

    End Sub

    Sub OpenSQLDB()
    Dim strCnn As String
    Dim logoTable As String

    Call Aaron 'Change to function for specific settings (above)

    Set cnn1 = New ADODB.Connection

    ' Open connection
    strCnn = "Provider=sqloledb;Data Source=" & cnnODBC & ";Initial
    Catalog=" & cnnDatabase & _
    ";User Id=" & cnnUserID & ";Password=" & cnnPassword & ""

    cnn1.Open strCnn
    End Sub

    Sub SetFirstTime()
    Range("isFirstTime") = True
    End Sub

    Function InsertLogoToDataBase(ByVal FileName As String) As Variant

    If Right(FileName, 4) = ".bmp" Then

    Dim strStream As ADODB.stream
    Call OpenSQLDB
    Set strStream = New ADODB.stream
    strStream.Type = adTypeBinary
    strStream.Open

    Set rsUnit = New ADODB.Recordset

    rsUnit.Open logoTable, cnn1, adOpenStatic, adLockPessimistic

    If Range("isFirstTime") = True Then
    rsUnit.AddNew
    Else
    rsUnit.MoveFirst
    End If

    FileName = Left(FileName, Len(FileName) - 4)
    v = InStrRev(FileName, "\")
    FileName = Right(FileName, Len(FileName) - v)
    rsUnit.Fields("txtLogo") = FileName
    strStream.LoadFromFile ActiveWorkbook.Path & "\" & FileName & ".BMP"
    rsUnit.Fields("imgLogo").Value = strStream.Read
    rsUnit.Update
    If Range("isFirstTime") = True Then
    rsUnit.AddNew
    Else
    rsUnit.MoveNext
    End If

    Range("isFirstTime") = False

    End If

    End Function

    Sub GetAllFiles()
    Dim varFileArray As Variant
    Dim lngI As Long
    Dim strDirName As String

    Const NO_FILES_IN_DIR As Long = 9
    Const INVALID_DIR As Long = 13

    On Error GoTo Test_Err

    strDirName = ActiveWorkbook.Path
    varFileArray = GetAllFilesInDir(strDirName)
    For lngI = 0 To UBound(varFileArray)
    'MsgBox varFileArray(lngI)
    InsertLogoToDataBase (varFileArray(lngI))
    Next lngI

    Test_Err:
    Select Case Err.Number
    Case NO_FILES_IN_DIR
    MsgBox "The directory named '" & strDirName _
    & "' contains no files."
    Case INVALID_DIR
    MsgBox "'" & strDirName & "' is not a valid directory."
    Case 0
    Case Else
    MsgBox "Error #" & Err.Number & " - " & Err.Description
    End Select
    End Sub

    Function GetAllFilesInDir(ByVal strDirPath As String) As Variant
    ' Loop through the directory specified in strDirPath and save each
    ' file name in an array, then return that array to the calling
    ' procedure.
    ' Return False if strDirPath is not a valid directory.
    Dim strTempName As String
    Dim varFiles() As Variant
    Dim lngFileCount As Long

    On Error GoTo GetAllFiles_Err

    ' Make sure that strDirPath ends with a "\" character.
    If Right$(strDirPath, 1) <> "\" Then
    strDirPath = strDirPath & "\"
    End If

    ' Make sure strDirPath is a directory.
    If GetAttr(strDirPath) = vbDirectory Then
    strTempName = Dir(strDirPath, vbDirectory)
    Do Until Len(strTempName) = 0
    ' Exclude ".", "..".
    If (strTempName <> ".") And (strTempName <> "..") Then
    ' Make sure we do not have a sub-directory name.
    If (GetAttr(strDirPath & strTempName) _
    And vbDirectory) <> vbDirectory Then
    ' Increase the size of the array
    ' to accommodate the found filename
    ' and add the filename to the array.
    ReDim Preserve varFiles(lngFileCount)
    varFiles(lngFileCount) = strTempName
    lngFileCount = lngFileCount + 1
    End If
    End If
    ' Use the Dir function to find the next filename.
    strTempName = Dir()
    Loop
    ' Return the array of found files.
    GetAllFilesInDir = varFiles
    End If
    GetAllFiles_End:
    Exit Function
    GetAllFiles_Err:
    GetAllFilesInDir = False
    Resume GetAllFiles_End
    End Function

    Sub CopyLogosToDataBase()
    'OLD CODE
    Dim strStream As ADODB.stream
    Call OpenSQLDB
    Set strStream = New ADODB.stream
    strStream.Type = adTypeBinary
    strStream.Open

    Set rsUnit = New ADODB.Recordset

    rsUnit.Open logoTable, cnn1, adOpenStatic, adLockPessimistic

    If Range("isFirstTime") = True Then
    rsUnit.AddNew
    Else
    rsUnit.MoveFirst
    End If

    Dim lngCount As Long
    Dim FileName As String
    With Application.FileSearch
    .NewSearch
    .FileType = msoFileTypeAllFiles
    .LookIn = ActiveWorkbook.Path
    .FileName = "*.bmp"

    If .Execute(SortBy:=msoSortByFileName, _
    SortOrder:=msoSortOrderAscending) > 0 Then
    MsgBox "There were " & .FoundFiles.Count & _
    " files found."

    For lngCount = 1 To .FoundFiles.Count
    FileName = .FoundFiles.Item(lngCount)
    If Right(FileName, 4) = ".bmp" Then
    FileName = Left(FileName, Len(FileName) - 4)
    v = InStrRev(FileName, "\")
    FileName = Right(FileName, Len(FileName) - v)
    MsgBox FileName, vbOKOnly, "Adding Logo Name"
    rsUnit.Fields("txtLogo") = FileName
    strStream.LoadFromFile ActiveWorkbook.Path & "\" &
    FileName & ".BMP"
    rsUnit.Fields("imgLogo").Value = strStream.Read
    rsUnit.Update
    If Range("isFirstTime") = True Then
    rsUnit.AddNew
    Else
    rsUnit.MoveNext
    End If
    End If
    Next lngCount
    End If
    End With
    Range("isFirstTime") = False
    End Sub



  2. #2
    Dave Patrick
    Guest

    Re: Need Help with Inserting in SQL

    What error? What line?

    --

    Regards,

    Dave Patrick ....Please no email replies - reply in newsgroup.
    Microsoft Certified Professional
    Microsoft MVP [Windows]
    http://www.microsoft.com/protect

    "Livin" wrote:
    | This is code I had working a few years back in Excel 2000 & XP using SQL
    | 2000. Now I'm needing the code again but using SQL Express 2005 and with
    | Excel 2003 and it seems to have broken, I think.
    |
    | I've setup SQL Express 2005 with the Table "Logos" with Columns imgLogo &
    | txtLogo
    |
    | I'm trying to take files from a folder and place the text name and the
    image
    | itself into the database.
    |
    | I was doing this with CopyLogosToDataBase() - but this seems to fail to
    get
    | the file names at all now - i.e. it returns no files in the search... it
    | worked perfecting in Excel 2000 (a few years back).
    |
    | I have replaced CopyLogosToDataBase() with GetAllFiles() &
    | GetAllFilesInDir() & InsertLogoToDataBase() - they run in this order. The
    | new GetAllFiles* functions get the file names properly and the Insert
    | function is the core of the CopyLogos sub which inserts into the SQL DB.
    |
    | Any help you guru's can give a born-again noobie is highly appreciated!
    |
    | thanks,
    | Aaron
    |
    | MODULE...
    |
    | Public cnnODBC, cnnDatabase, cnnTable, cnnUserID, cnnPassword As String
    | Public cnn1 As ADODB.Connection
    | Public logoTable As String
    | Public rsUnit As ADODB.Recordset
    |
    | Sub Aaron()
    | cnnODBC = "r2\sqlexpress" 'Server Name
    | cnnDatabase = "lrhist" 'Database Name
    | cnnTable = "tbLrmstr" 'Table Name
    | cnnUserID = "sa" 'Database User ID
    | cnnPassword = "sa" 'Database User Password
    | logoTable = "Logos" 'Table with Logo data
    |
    | End Sub
    |
    | Sub OpenSQLDB()
    | Dim strCnn As String
    | Dim logoTable As String
    |
    | Call Aaron 'Change to function for specific settings (above)
    |
    | Set cnn1 = New ADODB.Connection
    |
    | ' Open connection
    | strCnn = "Provider=sqloledb;Data Source=" & cnnODBC & ";Initial
    | Catalog=" & cnnDatabase & _
    | ";User Id=" & cnnUserID & ";Password=" & cnnPassword & ""
    |
    | cnn1.Open strCnn
    | End Sub
    |
    | Sub SetFirstTime()
    | Range("isFirstTime") = True
    | End Sub
    |
    | Function InsertLogoToDataBase(ByVal FileName As String) As Variant
    |
    | If Right(FileName, 4) = ".bmp" Then
    |
    | Dim strStream As ADODB.stream
    | Call OpenSQLDB
    | Set strStream = New ADODB.stream
    | strStream.Type = adTypeBinary
    | strStream.Open
    |
    | Set rsUnit = New ADODB.Recordset
    |
    | rsUnit.Open logoTable, cnn1, adOpenStatic, adLockPessimistic
    |
    | If Range("isFirstTime") = True Then
    | rsUnit.AddNew
    | Else
    | rsUnit.MoveFirst
    | End If
    |
    | FileName = Left(FileName, Len(FileName) - 4)
    | v = InStrRev(FileName, "\")
    | FileName = Right(FileName, Len(FileName) - v)
    | rsUnit.Fields("txtLogo") = FileName
    | strStream.LoadFromFile ActiveWorkbook.Path & "\" & FileName &
    ".BMP"
    | rsUnit.Fields("imgLogo").Value = strStream.Read
    | rsUnit.Update
    | If Range("isFirstTime") = True Then
    | rsUnit.AddNew
    | Else
    | rsUnit.MoveNext
    | End If
    |
    | Range("isFirstTime") = False
    |
    | End If
    |
    | End Function
    |
    | Sub GetAllFiles()
    | Dim varFileArray As Variant
    | Dim lngI As Long
    | Dim strDirName As String
    |
    | Const NO_FILES_IN_DIR As Long = 9
    | Const INVALID_DIR As Long = 13
    |
    | On Error GoTo Test_Err
    |
    | strDirName = ActiveWorkbook.Path
    | varFileArray = GetAllFilesInDir(strDirName)
    | For lngI = 0 To UBound(varFileArray)
    | 'MsgBox varFileArray(lngI)
    | InsertLogoToDataBase (varFileArray(lngI))
    | Next lngI
    |
    | Test_Err:
    | Select Case Err.Number
    | Case NO_FILES_IN_DIR
    | MsgBox "The directory named '" & strDirName _
    | & "' contains no files."
    | Case INVALID_DIR
    | MsgBox "'" & strDirName & "' is not a valid directory."
    | Case 0
    | Case Else
    | MsgBox "Error #" & Err.Number & " - " & Err.Description
    | End Select
    | End Sub
    |
    | Function GetAllFilesInDir(ByVal strDirPath As String) As Variant
    | ' Loop through the directory specified in strDirPath and save each
    | ' file name in an array, then return that array to the calling
    | ' procedure.
    | ' Return False if strDirPath is not a valid directory.
    | Dim strTempName As String
    | Dim varFiles() As Variant
    | Dim lngFileCount As Long
    |
    | On Error GoTo GetAllFiles_Err
    |
    | ' Make sure that strDirPath ends with a "\" character.
    | If Right$(strDirPath, 1) <> "\" Then
    | strDirPath = strDirPath & "\"
    | End If
    |
    | ' Make sure strDirPath is a directory.
    | If GetAttr(strDirPath) = vbDirectory Then
    | strTempName = Dir(strDirPath, vbDirectory)
    | Do Until Len(strTempName) = 0
    | ' Exclude ".", "..".
    | If (strTempName <> ".") And (strTempName <> "..") Then
    | ' Make sure we do not have a sub-directory name.
    | If (GetAttr(strDirPath & strTempName) _
    | And vbDirectory) <> vbDirectory Then
    | ' Increase the size of the array
    | ' to accommodate the found filename
    | ' and add the filename to the array.
    | ReDim Preserve varFiles(lngFileCount)
    | varFiles(lngFileCount) = strTempName
    | lngFileCount = lngFileCount + 1
    | End If
    | End If
    | ' Use the Dir function to find the next filename.
    | strTempName = Dir()
    | Loop
    | ' Return the array of found files.
    | GetAllFilesInDir = varFiles
    | End If
    | GetAllFiles_End:
    | Exit Function
    | GetAllFiles_Err:
    | GetAllFilesInDir = False
    | Resume GetAllFiles_End
    | End Function
    |
    | Sub CopyLogosToDataBase()
    | 'OLD CODE
    | Dim strStream As ADODB.stream
    | Call OpenSQLDB
    | Set strStream = New ADODB.stream
    | strStream.Type = adTypeBinary
    | strStream.Open
    |
    | Set rsUnit = New ADODB.Recordset
    |
    | rsUnit.Open logoTable, cnn1, adOpenStatic, adLockPessimistic
    |
    | If Range("isFirstTime") = True Then
    | rsUnit.AddNew
    | Else
    | rsUnit.MoveFirst
    | End If
    |
    | Dim lngCount As Long
    | Dim FileName As String
    | With Application.FileSearch
    | .NewSearch
    | .FileType = msoFileTypeAllFiles
    | .LookIn = ActiveWorkbook.Path
    | .FileName = "*.bmp"
    |
    | If .Execute(SortBy:=msoSortByFileName, _
    | SortOrder:=msoSortOrderAscending) > 0 Then
    | MsgBox "There were " & .FoundFiles.Count & _
    | " files found."
    |
    | For lngCount = 1 To .FoundFiles.Count
    | FileName = .FoundFiles.Item(lngCount)
    | If Right(FileName, 4) = ".bmp" Then
    | FileName = Left(FileName, Len(FileName) - 4)
    | v = InStrRev(FileName, "\")
    | FileName = Right(FileName, Len(FileName) - v)
    | MsgBox FileName, vbOKOnly, "Adding Logo Name"
    | rsUnit.Fields("txtLogo") = FileName
    | strStream.LoadFromFile ActiveWorkbook.Path & "\" &
    | FileName & ".BMP"
    | rsUnit.Fields("imgLogo").Value = strStream.Read
    | rsUnit.Update
    | If Range("isFirstTime") = True Then
    | rsUnit.AddNew
    | Else
    | rsUnit.MoveNext
    | End If
    | End If
    | Next lngCount
    | End If
    | End With
    | Range("isFirstTime") = False
    | End Sub
    |
    |



  3. #3
    Livin
    Guest

    Re: Need Help with Inserting in SQL

    I do not get an error, that is the problem. If I did it would be easier for
    me to troubleshoot. If you can help in putting some error trapping in the
    rsUnit areas where the text and image are put into the DB that might help
    see if SQL if returning something. I put some error trapping on the cnn1
    (the connection) and it shows err 0 so that seems fine.

    thanks for helping!


    "Dave Patrick" <[email protected]> wrote in message
    news:[email protected]...
    > What error? What line?
    >
    > --
    >
    > Regards,
    >
    > Dave Patrick ....Please no email replies - reply in newsgroup.
    > Microsoft Certified Professional
    > Microsoft MVP [Windows]
    > http://www.microsoft.com/protect
    >
    > "Livin" wrote:
    > | This is code I had working a few years back in Excel 2000 & XP using SQL
    > | 2000. Now I'm needing the code again but using SQL Express 2005 and with
    > | Excel 2003 and it seems to have broken, I think.
    > |
    > | I've setup SQL Express 2005 with the Table "Logos" with Columns imgLogo
    > &
    > | txtLogo
    > |
    > | I'm trying to take files from a folder and place the text name and the
    > image
    > | itself into the database.
    > |
    > | I was doing this with CopyLogosToDataBase() - but this seems to fail to
    > get
    > | the file names at all now - i.e. it returns no files in the search... it
    > | worked perfecting in Excel 2000 (a few years back).
    > |
    > | I have replaced CopyLogosToDataBase() with GetAllFiles() &
    > | GetAllFilesInDir() & InsertLogoToDataBase() - they run in this order.
    > The
    > | new GetAllFiles* functions get the file names properly and the Insert
    > | function is the core of the CopyLogos sub which inserts into the SQL DB.
    > |
    > | Any help you guru's can give a born-again noobie is highly appreciated!
    > |
    > | thanks,
    > | Aaron
    > |
    > | MODULE...
    > |
    > | Public cnnODBC, cnnDatabase, cnnTable, cnnUserID, cnnPassword As
    > String
    > | Public cnn1 As ADODB.Connection
    > | Public logoTable As String
    > | Public rsUnit As ADODB.Recordset
    > |
    > | Sub Aaron()
    > | cnnODBC = "r2\sqlexpress" 'Server Name
    > | cnnDatabase = "lrhist" 'Database Name
    > | cnnTable = "tbLrmstr" 'Table Name
    > | cnnUserID = "sa" 'Database User ID
    > | cnnPassword = "sa" 'Database User Password
    > | logoTable = "Logos" 'Table with Logo data
    > |
    > | End Sub
    > |
    > | Sub OpenSQLDB()
    > | Dim strCnn As String
    > | Dim logoTable As String
    > |
    > | Call Aaron 'Change to function for specific settings (above)
    > |
    > | Set cnn1 = New ADODB.Connection
    > |
    > | ' Open connection
    > | strCnn = "Provider=sqloledb;Data Source=" & cnnODBC & ";Initial
    > | Catalog=" & cnnDatabase & _
    > | ";User Id=" & cnnUserID & ";Password=" & cnnPassword & ""
    > |
    > | cnn1.Open strCnn
    > | End Sub
    > |
    > | Sub SetFirstTime()
    > | Range("isFirstTime") = True
    > | End Sub
    > |
    > | Function InsertLogoToDataBase(ByVal FileName As String) As Variant
    > |
    > | If Right(FileName, 4) = ".bmp" Then
    > |
    > | Dim strStream As ADODB.stream
    > | Call OpenSQLDB
    > | Set strStream = New ADODB.stream
    > | strStream.Type = adTypeBinary
    > | strStream.Open
    > |
    > | Set rsUnit = New ADODB.Recordset
    > |
    > | rsUnit.Open logoTable, cnn1, adOpenStatic, adLockPessimistic
    > |
    > | If Range("isFirstTime") = True Then
    > | rsUnit.AddNew
    > | Else
    > | rsUnit.MoveFirst
    > | End If
    > |
    > | FileName = Left(FileName, Len(FileName) - 4)
    > | v = InStrRev(FileName, "\")
    > | FileName = Right(FileName, Len(FileName) - v)
    > | rsUnit.Fields("txtLogo") = FileName
    > | strStream.LoadFromFile ActiveWorkbook.Path & "\" & FileName &
    > ".BMP"
    > | rsUnit.Fields("imgLogo").Value = strStream.Read
    > | rsUnit.Update
    > | If Range("isFirstTime") = True Then
    > | rsUnit.AddNew
    > | Else
    > | rsUnit.MoveNext
    > | End If
    > |
    > | Range("isFirstTime") = False
    > |
    > | End If
    > |
    > | End Function
    > |
    > | Sub GetAllFiles()
    > | Dim varFileArray As Variant
    > | Dim lngI As Long
    > | Dim strDirName As String
    > |
    > | Const NO_FILES_IN_DIR As Long = 9
    > | Const INVALID_DIR As Long = 13
    > |
    > | On Error GoTo Test_Err
    > |
    > | strDirName = ActiveWorkbook.Path
    > | varFileArray = GetAllFilesInDir(strDirName)
    > | For lngI = 0 To UBound(varFileArray)
    > | 'MsgBox varFileArray(lngI)
    > | InsertLogoToDataBase (varFileArray(lngI))
    > | Next lngI
    > |
    > | Test_Err:
    > | Select Case Err.Number
    > | Case NO_FILES_IN_DIR
    > | MsgBox "The directory named '" & strDirName _
    > | & "' contains no files."
    > | Case INVALID_DIR
    > | MsgBox "'" & strDirName & "' is not a valid directory."
    > | Case 0
    > | Case Else
    > | MsgBox "Error #" & Err.Number & " - " & Err.Description
    > | End Select
    > | End Sub
    > |
    > | Function GetAllFilesInDir(ByVal strDirPath As String) As Variant
    > | ' Loop through the directory specified in strDirPath and save each
    > | ' file name in an array, then return that array to the calling
    > | ' procedure.
    > | ' Return False if strDirPath is not a valid directory.
    > | Dim strTempName As String
    > | Dim varFiles() As Variant
    > | Dim lngFileCount As Long
    > |
    > | On Error GoTo GetAllFiles_Err
    > |
    > | ' Make sure that strDirPath ends with a "\" character.
    > | If Right$(strDirPath, 1) <> "\" Then
    > | strDirPath = strDirPath & "\"
    > | End If
    > |
    > | ' Make sure strDirPath is a directory.
    > | If GetAttr(strDirPath) = vbDirectory Then
    > | strTempName = Dir(strDirPath, vbDirectory)
    > | Do Until Len(strTempName) = 0
    > | ' Exclude ".", "..".
    > | If (strTempName <> ".") And (strTempName <> "..") Then
    > | ' Make sure we do not have a sub-directory name.
    > | If (GetAttr(strDirPath & strTempName) _
    > | And vbDirectory) <> vbDirectory Then
    > | ' Increase the size of the array
    > | ' to accommodate the found filename
    > | ' and add the filename to the array.
    > | ReDim Preserve varFiles(lngFileCount)
    > | varFiles(lngFileCount) = strTempName
    > | lngFileCount = lngFileCount + 1
    > | End If
    > | End If
    > | ' Use the Dir function to find the next filename.
    > | strTempName = Dir()
    > | Loop
    > | ' Return the array of found files.
    > | GetAllFilesInDir = varFiles
    > | End If
    > | GetAllFiles_End:
    > | Exit Function
    > | GetAllFiles_Err:
    > | GetAllFilesInDir = False
    > | Resume GetAllFiles_End
    > | End Function
    > |
    > | Sub CopyLogosToDataBase()
    > | 'OLD CODE
    > | Dim strStream As ADODB.stream
    > | Call OpenSQLDB
    > | Set strStream = New ADODB.stream
    > | strStream.Type = adTypeBinary
    > | strStream.Open
    > |
    > | Set rsUnit = New ADODB.Recordset
    > |
    > | rsUnit.Open logoTable, cnn1, adOpenStatic, adLockPessimistic
    > |
    > | If Range("isFirstTime") = True Then
    > | rsUnit.AddNew
    > | Else
    > | rsUnit.MoveFirst
    > | End If
    > |
    > | Dim lngCount As Long
    > | Dim FileName As String
    > | With Application.FileSearch
    > | .NewSearch
    > | .FileType = msoFileTypeAllFiles
    > | .LookIn = ActiveWorkbook.Path
    > | .FileName = "*.bmp"
    > |
    > | If .Execute(SortBy:=msoSortByFileName, _
    > | SortOrder:=msoSortOrderAscending) > 0 Then
    > | MsgBox "There were " & .FoundFiles.Count & _
    > | " files found."
    > |
    > | For lngCount = 1 To .FoundFiles.Count
    > | FileName = .FoundFiles.Item(lngCount)
    > | If Right(FileName, 4) = ".bmp" Then
    > | FileName = Left(FileName, Len(FileName) - 4)
    > | v = InStrRev(FileName, "\")
    > | FileName = Right(FileName, Len(FileName) - v)
    > | MsgBox FileName, vbOKOnly, "Adding Logo Name"
    > | rsUnit.Fields("txtLogo") = FileName
    > | strStream.LoadFromFile ActiveWorkbook.Path & "\" &
    > | FileName & ".BMP"
    > | rsUnit.Fields("imgLogo").Value = strStream.Read
    > | rsUnit.Update
    > | If Range("isFirstTime") = True Then
    > | rsUnit.AddNew
    > | Else
    > | rsUnit.MoveNext
    > | End If
    > | End If
    > | Next lngCount
    > | End If
    > | End With
    > | Range("isFirstTime") = False
    > | End Sub
    > |
    > |
    >
    >




  4. #4
    Dave Patrick
    Guest

    Re: Need Help with Inserting in SQL

    If you don't get an error then it sounds like the code works. Generally
    speaking I'd throw in some MsgBox's at various points to see where you're
    getting the unexpected result.


    Not sure why you need this in Function InsertLogoToDataBase twice but
    somewhere after you'll want to rsUnit.Update

    If Range("isFirstTime") = True Then
    rsUnit.AddNew
    Else
    rsUnit.MoveNext
    End If

    --

    Regards,

    Dave Patrick ....Please no email replies - reply in newsgroup.
    Microsoft Certified Professional
    Microsoft MVP [Windows]
    http://www.microsoft.com/protect

    "Livin" wrote:
    |I do not get an error, that is the problem. If I did it would be easier for
    | me to troubleshoot. If you can help in putting some error trapping in the
    | rsUnit areas where the text and image are put into the DB that might help
    | see if SQL if returning something. I put some error trapping on the cnn1
    | (the connection) and it shows err 0 so that seems fine.
    |
    | thanks for helping!



  5. #5
    Livin
    Guest

    Re: Need Help with Inserting in SQL

    Thanks for looking at it... I dug in and revamped the entire module. I never
    got the original working, it was not finding any files in the directory...
    very strange!

    So I found some rock'n code that enumerated files in a folder complete with
    error checking. I used it and then rewrote the insert code. It works
    perfectly!

    thanks again!


    "Dave Patrick" <[email protected]> wrote in message
    news:%[email protected]...
    > If you don't get an error then it sounds like the code works. Generally
    > speaking I'd throw in some MsgBox's at various points to see where you're
    > getting the unexpected result.
    >
    >
    > Not sure why you need this in Function InsertLogoToDataBase twice but
    > somewhere after you'll want to rsUnit.Update
    >
    > If Range("isFirstTime") = True Then
    > rsUnit.AddNew
    > Else
    > rsUnit.MoveNext
    > End If
    >
    > --
    >
    > Regards,
    >
    > Dave Patrick ....Please no email replies - reply in newsgroup.
    > Microsoft Certified Professional
    > Microsoft MVP [Windows]
    > http://www.microsoft.com/protect
    >
    > "Livin" wrote:
    > |I do not get an error, that is the problem. If I did it would be easier
    > for
    > | me to troubleshoot. If you can help in putting some error trapping in
    > the
    > | rsUnit areas where the text and image are put into the DB that might
    > help
    > | see if SQL if returning something. I put some error trapping on the cnn1
    > | (the connection) and it shows err 0 so that seems fine.
    > |
    > | thanks for helping!
    >
    >




  6. #6
    Livin
    Guest

    Re: Need Help with Inserting in SQL

    Thanks for looking at it... I dug in and revamped the entire module. I never
    got the original working, it was not finding any files in the directory...
    very strange!

    So I found some rock'n code that enumerated files in a folder complete with
    error checking. I used it and then rewrote the insert code. It works
    perfectly!

    thanks again!


    "Dave Patrick" <[email protected]> wrote in message
    news:%[email protected]...
    > If you don't get an error then it sounds like the code works. Generally
    > speaking I'd throw in some MsgBox's at various points to see where you're
    > getting the unexpected result.
    >
    >
    > Not sure why you need this in Function InsertLogoToDataBase twice but
    > somewhere after you'll want to rsUnit.Update
    >
    > If Range("isFirstTime") = True Then
    > rsUnit.AddNew
    > Else
    > rsUnit.MoveNext
    > End If
    >
    > --
    >
    > Regards,
    >
    > Dave Patrick ....Please no email replies - reply in newsgroup.
    > Microsoft Certified Professional
    > Microsoft MVP [Windows]
    > http://www.microsoft.com/protect
    >
    > "Livin" wrote:
    > |I do not get an error, that is the problem. If I did it would be easier
    > for
    > | me to troubleshoot. If you can help in putting some error trapping in
    > the
    > | rsUnit areas where the text and image are put into the DB that might
    > help
    > | see if SQL if returning something. I put some error trapping on the cnn1
    > | (the connection) and it shows err 0 so that seems fine.
    > |
    > | thanks for helping!
    >
    >





  7. #7
    Dave Patrick
    Guest

    Re: Need Help with Inserting in SQL

    Glad to hear you sorted it.

    --

    Regards,

    Dave Patrick ....Please no email replies - reply in newsgroup.
    Microsoft Certified Professional
    Microsoft MVP [Windows]
    http://www.microsoft.com/protect

    "Livin" wrote:
    | Thanks for looking at it... I dug in and revamped the entire module. I
    never
    | got the original working, it was not finding any files in the directory...
    | very strange!
    |
    | So I found some rock'n code that enumerated files in a folder complete
    with
    | error checking. I used it and then rewrote the insert code. It works
    | perfectly!
    |
    | thanks again!



+ Reply to Thread

Thread Information

Users Browsing this Thread

There are currently 1 users browsing this thread. (0 members and 1 guests)

Bookmarks

Posting Permissions

  • You may not post new threads
  • You may not post replies
  • You may not post attachments
  • You may not edit your posts

Search Engine Friendly URLs by vBSEO 3.6.0 RC 1