Tek-Tips is the largest IT community on the Internet today!

Members share and learn making Tek-Tips Forums the best source of peer-reviewed technical information on the Internet!

  • Congratulations SkipVought on being selected by the Tek-Tips community for having the most helpful posts in the forums last week. Way to Go!

How to insert/update/delete records using MSHFlexGrid control in VB 6

Status
Not open for further replies.

psharma1

Programmer
Nov 16, 2009
10
0
0
US
I'm having problem in my project where I've to display a data grid based on a Master/Child relationship where the Master Data is entered as a value by the user in a text box and the data from the Child table is displayed in a grid. I'm able to accomplish this much using the MSHFLEXGRID control. My problem now is how to give control to the user to insert new record in the child table using the grid, modify the data or even delete records from this datagrid. Please let me know if using a MSHFLEXGRID is a good choice for this kind of scenario or is there any better control to acheive this and how.

Thank you in advance!

PS
 

MSHFLEXGRID control is not designed for insert / update / delete. It is for display only (as far as I know)

In my opinion you have at least 2 choices (unbound flex grid):
1. Overlay a text box over your MSHFLEXGRID control, make it look the same size, font and text of a cell from the grid. This will allow user to modify / enter new information which you will transfer back to the grid.

2. When user selects any row in your grid, highligh the row and transfer the data from that row into several text boxes that user can modify. This way you can also allow user to delete highlighted row. User can also enter information into the text boxes and hit "New" or "Insert" command button.

I have done both ways of dealing with this kind of situations.

Have fun.

---- Andy
 
Hi Andrzejek,

Thanks for your response. I like the 2nd option better, but since I'm just a beginner at VB programming, would you please help me little more with the code to make the grid work like that. Can I use the MSFLEXGRID for the 2nd option above and if so what property I need to set to make it clickable. Can you help me with the code or point me in the right direction. This part is something that I'm not able to find much about on the Internet.

Thanks a lot!
PS
 

No problem, I can help you.
First, show me the code where you populate the flex grid. This way I will know a lot of what you have as far as data in your grid.

Have fun.

---- Andy
 

Just as a sample of work:
On top of empty Form place 4 text boxes:[tt]
Text1 Text2 Text3 Text 4[/tt]

And a MSFlexGrid1 control
Code:
Option Explicit
Dim intRow As Integer
Dim intCol As Integer

Private Sub Form_Load()

Call MakeTextBoxesEmpty

With MSFlexGrid1
    .Clear
    .HighLight = flexHighlightNever
    .AllowUserResizing = flexResizeColumns
    .Cols = 5
    .Rows = 7
    [green]'Symbols ^ < > align headers[/green]
    .FormatString = "^Col 0|^Col 1|<Col 2|>Col 3|<Col 4|>Col 5"
    
    For intCol = 0 To .Cols - 1
        For intRow = 1 To .Rows - 1
            .TextMatrix(intRow, intCol) = "Col " & intCol & " - Row " & intRow
        Next intRow
    Next intCol
    
    .ColWidth(0) = .Width / .Cols
    .ColWidth(1) = .Width / .Cols
    .ColWidth(2) = .Width / .Cols
    .ColWidth(3) = .Width / .Cols
    .ColWidth(4) = .Width / .Cols
    .ColWidth(5) = .Width / .Cols
End With

End Sub

Private Sub MSFlexGrid1_Click()

With MSFlexGrid1
    [green]'Make all cells White[/green]
    For intCol = 1 To .Cols - 1
        .Col = intCol
        For intRow = 1 To .Rows - 1
            .Row = intRow
            .CellBackColor = vbWhite
        Next intRow
    Next intCol
    [green]'Highlight selected Row in Yellow[/green]
    If .MouseRow > 0 Then
        .Row = .MouseRow
        For intCol = 1 To .Cols - 1
            .Col = intCol
            .CellBackColor = vbYellow
        Next intCol
        Text1.Text = .TextMatrix(.Row, 1)
        Text2.Text = .TextMatrix(.Row, 2)
        Text3.Text = .TextMatrix(.Row, 3)
        Text4.Text = .TextMatrix(.Row, 4)
    Else
        [green]'.MouseRow = 0 ' this is a header row[/green]
        Call MakeTextBoxesEmpty
    End If
End With

End Sub

Private Sub MakeTextBoxesEmpty()
Dim cntr As Control
[green]
'Make all text boxes empty[/green]
For Each cntr In Me.Controls
    If TypeOf cntr Is TextBox Then
        cntr.Text = ""
    End If
Next cntr

End Sub

Have fun.

---- Andy
 
You might also look at faq222-3262 (about half way down) which shows how to get the appearance of editing a flexgrid.

If you want the best response to a question, please check out FAQ222-2244 first.
'If we're supposed to work in Hex, why have we only got A fingers?'
Drive a Steam Roller
 
Hey Strongm,

I started with the DataGrid, but my problem is that I don't want to use the ADODC control to dump the whole table into the Grid and then move from one record to another. Since I wanted the results in the grid to appear based on the user entered key, I'm not sure how I can use my own code to control how my grid should get populated.

With MSFLEXGRID I used the following code to popluate my grid. Hey Andrjezek - This what you were also asking me, right? I've looked at your code yet, but I'll and respond back to you.

This part for populating the FLEXGRID is working fine for me.

Private Sub cmdNext_Click()
On Error GoTo errHandler

Dim Con As New ADODB.Connection
Dim rs As New ADODB.Recordset
Dim sQuery As String
Dim vbResult As Integer


Con.Open DB_CONN, DB_USER, DB_PASS

sQuery = "select c1, d1 from <Table1>
where c1 = '" & Trim(txtC1Num.Text) & "'"

Set rs = Con.Execute(sQuery)

If Not rs.EOF Then
Call SelectRecordDC(rs)

Else
MsgBox "There are no records that match your search", vbExclamation

Exit Sub
End If

rs.Close
Set rs = Nothing
Con.Close
Set Con = Nothing
Exit Sub


Function SelectRecordDC(ByVal rs As Recordset) As Boolean
Dim sColumns(2) As String
Dim n As Integer

sColumns(0) = "County Precinct"
sColumns(1) = "District Combo"

Dim nRow As Integer
Dim nCol As Integer
Dim nField As Integer

MSHFDistrictCombo.Cols = 2

nRow = 0
nCol = 0

MSHFDistrictCombo.Row = nRow
For n = 0 To 1
MSHFDistrictCombo.Col = n
MSHFDistrictCombo.Text = sColumns(n)
Select Case n
Case 0
MSHFDistrictCombo.ColWidth(n) = 1250
Case 1
MSHFDistrictCombo.ColWidth(n) = 1200
End Select
Next n


Do While Not rs.EOF

nRow = nRow + 1
MSHFDistrictCombo.Rows = nRow + 1

nCol = 0
MSHFDistrictCombo.Row = nRow
MSHFDistrictCombo.Col = nCol


MSHFDistrictCombo.Text = nRow

For nCol = 1 To MSHFDistrictCombo.Cols Step 1
MSHFDistrictCombo.Col = (nCol - 1)
MSHFDistrictCombo.Text = IIf(IsNull(rs(nCol - 1)), "", rs(nCol - 1))
Next
rs.MoveNext
Loop
SelectRecord = True
End Function



Thanks,
PS
 
> I don't want to use the ADODC control

Um - you don't have to. The datasource can quite happily be an ADO recordset.

Here's a full example that demonstrates your master child relationship as you have described, plus allowing adding new records, deleting records, modifying records ... You simply need a form with a textbox and a datagrid control, and a reference to ADO. I've tried reuse as much of your flexgrid code as possible:
Code:
[blue]Option Explicit
Public rs As Recordset

Private Sub Form_Load()
    Dim Con As New Connection
    Dim sQuery As String
    Dim DB_CONN As String
    
    [green]' Your connection string would go here ...[/green]
    DB_CONN = "Provider=Microsoft.Jet.OLEDB.4.0;Data Source=\\tsclient\C\Users\Mike\Documents\mike1.mdb;Persist Security Info=False"
    Con.Open DB_CONN [green]', DB_USER, DB_PASS[/green]
    
    Set rs = New Recordset
    
    [green]' All following settings required to achieve full functionality[/green]
    rs.LockType = adLockOptimistic
    rs.CursorType = adOpenKeyset
    rs.CursorLocation = adUseClient
    
    rs.ActiveConnection = Con
    sQuery = "SELECT c1, d1 FROM Table1" 
    [green]'WHERE statement is more conveniently done with a filter    
    ' where c1 = '" & Trim(txtC1Num.Text) & "'"[/green]
    
    rs.Open sQuery
    
    [green]' Change defaults[/green]
    DataGrid1.AllowAddNew = True
    DataGrid1.AllowDelete = True
    
    Set DataGrid1.DataSource = rs
    DataGrid1.Columns(0).Caption = "County Precinct"
    DataGrid1.Columns(0).Width = 1250
    DataGrid1.Columns(1).Caption = "District Combo"
    DataGrid1.Columns(1).Width = 1200
    
    txtC1Num.Text = "1" [green]' force a txtC1Num change event[/green]
End Sub

Private Sub txtC1Num_Change()
    [green]' Simplistic approach ...[/green]
    On Error Resume Next
        rs.Filter = "c1=" & Trim$(txtC1Num.Text)
    On Error GoTo 0
End Sub[/blue]
 
Something(s) seem funny here.

First, you make the user type in this "County Precinct" value instead of using some form of dropdown list preloaded from the master table?

Then even stranger looking, you have a grid with two columns yet one column is exactly the value already entered in the textbox? Perhaps this is a foreign key value, in which case I'd hide the column to avoid unexpected changes to it.

Speaking of foreign keys, I don't see a parent and child table above, just what looks like a single unnormalized table.


How about using two tables, call them Precincts and Combos. Prestore all the Precincts table records. Then instead of a textbox use a DataCombo linked to a DataGrid by using the Data Shaping Service and the data binding properties?

So imagine three controls:
[ul]
[li]Label - lblPrecincts[/li]
[li]DataCombo - dbcPrecincts (Style set to dbcDropdownList)[/li]
[li]DataGrid - dbgrdCombos[/li]
[/ul]

For testing we'll create a dummy database, using a Const (DATABASE) here to define its location and a Public Function OpenDB() to create the database if not present and return an open Connection using the Data Shape Provider in general:

LGDB.bas
Code:
Option Explicit

Private Const CONNWG As String = "Provider=Microsoft.Jet.OLEDB.4.0;" _
                               & "Jet OLEDB:Engine Type=5;" _
                               & "Jet OLEDB:Create System Database=True;" _
                               & "Data Source='$DB$.mdw';"
Private Const CONNDB As String = "Provider=Microsoft.Jet.OLEDB.4.0;" _
                               & "Jet OLEDB:Engine Type=5;" _
                               & "Jet OLEDB:System Database='$DB$.mdw';" _
                               & "Data Source='$DB$.mdb';"
Private Const CONNSHAPEPREF As String = "Provider=MSDataShape;Data "
Private Const DATABASE As String = "Database"

Private Sub CreateDB()
    Dim catData As Object 'Don't early-bind ADOX objects.
    Dim cnData As ADODB.Connection
    
    Set catData = CreateObject("ADOX.Catalog")
    With catData
        .Create Replace$(CONNWG, "$DB$", DATABASE)
        .Create Replace$(CONNDB, "$DB$", DATABASE)
        Set cnData = .ActiveConnection
    End With
    Set catData = Nothing
    With cnData
        .Execute "CREATE TABLE [Precincts](" _
               & "[ID] IDENTITY CONSTRAINT [PK_ID] PRIMARY KEY," _
               & "[Precinct] TEXT(35) WITH COMPRESSION NOT NULL)", , _
                 adCmdText
        .Execute "CREATE TABLE [Combos] (" _
               & "[ID] IDENTITY NOT NULL CONSTRAINT [PK_ID] PRIMARY KEY," _
               & "[Combo] TEXT(35) WITH COMPRESSION NOT NULL," _
               & "[PrecinctID] INTEGER NOT NULL CONSTRAINT [FK_PrecinctID] " _
               & "REFERENCES [Precincts] ([ID]))", , _
                 adCmdText
        .Execute "CREATE PROCEDURE [InsertPrecinct]" _
               & "([NewPrecinct] TEXT(35)) AS " _
               & "INSERT INTO [Precincts] ([Precinct]) VALUES ([NewPrecinct])", , _
                 adCmdText
        .Execute "CREATE PROCEDURE [InsertCombo]" _
               & "([PrecinctName] TEXT(35), [NewCombo] TEXT(35)) AS " _
               & "INSERT INTO [Combos] ([Combo], [PrecinctID]) " _
               & "SELECT [NewCombo], [Precincts].[ID] FROM [Precincts] " _
               & "WHERE [Precinct] = [PrecinctName]", , _
                 adCmdText
        'Predefine the Precincts.
        .InsertPrecinct "1st"
        .InsertPrecinct "3rd"
        .InsertPrecinct "25th"
        .InsertPrecinct "26th"
        'Some initial Precinct Combo values just for fun - er, whatever a Combo is
        .InsertCombo "1st", "fudge"
        .InsertCombo "3rd", "nuts"
        .InsertCombo "25th", "chips"
        .InsertCombo "26th", "gum"
        .Close
    End With
End Sub

Public Function OpenDB() As ADODB.Connection
    On Error Resume Next
    GetAttr DATABASE & ".mdb"
    If Err Then
        On Error GoTo 0
        CreateDB
    End If
    On Error GoTo 0
    Set OpenDB = New ADODB.Connection
    OpenDB.Open CONNSHAPEPREF & Replace$(CONNDB, "$DB$", DATABASE)
End Function

Then we'll need our Form:

LGForm.frm
Code:
Option Explicit

Private cnDB As ADODB.Connection
Private rsPrecincts As ADODB.Recordset

Private Sub dbcPrecincts_Change()
    'Follow the value selected in the Combo.
    rsPrecincts.Bookmark = dbcPrecincts.SelectedItem
End Sub

Private Sub dbgrdCombos_BeforeColUpdate(ByVal ColIndex As Integer, OldValue As Variant, Cancel As Integer)
    'Catch illegal Null entry here.
    If ColIndex = 1 Then
        'This is [Combo], which can't be Null.
        With dbgrdCombos.Columns(ColIndex)
            If Len(.Text) < 1 Then
                Cancel = True
                MsgBox "Must enter a value for " & .Caption, vbOKOnly, Caption
            End If
        End With
    End If
End Sub

Private Sub dbgrdCombos_KeyPress(KeyAscii As Integer)
    'Treat Enter as Update.
    If KeyAscii = vbKeyReturn Then
        dbgrdCombos.Bookmark = dbgrdCombos.Bookmark
    End If
End Sub

Private Sub Form_Load()
    Set cnDB = OpenDB()
    Set rsPrecincts = New ADODB.Recordset
    rsPrecincts.CursorLocation = adUseServer
    rsPrecincts.Open "SHAPE {SELECT * FROM [Precincts]} " _
                 & "APPEND ({SELECT [PrecinctID], [Combo] " _
                 & "FROM [Combos]} AS [ChpCombos] " _
                 & "RELATE [ID] TO [PrecinctID])", _
                   cnDB, adOpenDynamic, adLockOptimistic, adCmdText
    lblPrecincts.Caption = "County Precinct"
    With dbcPrecincts
        'Style set to dbcDropdownList at design-time.
        Set .RowSource = rsPrecincts
        .BoundColumn = "ID"
        .ListField = "Precinct"
        .Text = rsPrecincts(.ListField).Value
    End With
    With dbgrdCombos
        Set .DataSource = rsPrecincts!ChpCombos.Value
        .Columns(0).Visible = False 'Hide the foreign key column.
        .Columns(1).Caption = "District Combos"
        .AllowAddNew = True
        .AllowDelete = True
        .AllowArrows = True
        .WrapCellPointer = True
        .TabAction = dbgGridNavigation
    End With
End Sub

Private Sub Form_Unload(Cancel As Integer)
    dbgrdCombos.EditActive = False 'Cancel any pending change left hanging.
    rsPrecincts.Close
    cnDB.Close
End Sub
 
>since I'm just a beginner at VB programming ...

... might explain it.
 
Hi Dilettante,

Thanks for providing a detailed code. My point behind providing the end-user with a text box to enter the Precinct value is that there are a total of 160 Precincts here and it doesn't seems okay to provide a drop down for 160 values and let the user scroll thru (and also to make this form consistent with other forms in the app). Since the users are pretty familiar with their data they can simply enter the value they are interested in, in the text box and search for the districtcombos attached with that precinct in the District_Combo table.

I understand the fact that the County_Precinct values that I'm showing in the data grid should be non-editable, but instead of hiding it, I'd like to show it, just make it non-editable. Is it possible to do that?
Here again with the insert button, I'd like to have the option of precinct column getting auto-filled and the cursor can move to the Districtcombo column for the user to enter value and save.

I still have to try out your code to see how the functions AllowAddNew, AllowDelete, AllowArrows works.

Please pardon me if I mentioned something that doesn't make any sense in VB, but as I said before, I'm just a beginner at VB and been asked to make this 1 enhancement to this already existing contractor developed application.

Thanks,
PS

 
You could modify the example by replacing the DataCombo with a TextBox, then in Form_Load initialize it with something like:
Code:
:
:
    lblPrecincts.Caption = "County Precinct"
    With txtPrecincts
        .Tag = "Precinct"
        .Text = rsPrecincts(.Tag).Value
    End With
    With dbgrdCombos
:
:
The tear out the dbcPrecincts_Change() event handler and replace it by something like:
Code:
Private Sub txtPrecincts_GotFocus()
    With txtPrecincts
        .SelStart = 0
        .SelLength = Len(.Text)
    End With
End Sub

Private Sub txtPrecincts_Validate(Cancel As Boolean)
    With txtPrecincts
        rsPrecincts.Find .Tag & " = '" & .Text & "'", , adSearchForward, adBookmarkFirst
        If rsPrecincts.EOF Then
            MsgBox "No such " & lblPrecincts.Caption, vbOKOnly, App.Title
            Cancel = True
            txtPrecincts_GotFocus
        End If
    End With
End Sub

There is no support for "uneditable" columns in a DataGrid. I suppose you might be able to write code to respond to change events and cancel them on unrecognised columns though.

Perhaps in Form_Load don't make Columns(0) invisible, set your column headings:
Code:
:
:
    With dbgrdCombos
        Set .DataSource = rsPrecincts!ChpCombos.Value
        With .Columns(0)
            .Caption = "County Precinct ID"
            .Width = TextWidth(" " & .Caption & " ")
        End With
        With .Columns(1)
            .Caption = "District Combos"
            .Width = TextWidth(" " & .Caption & " ")
        End With
        .AllowAddNew = True
:
:

Then change the dbgrdCombos_BeforeColUpdate() event handler:
Code:
Private Sub dbgrdCombos_BeforeColUpdate( _
    ByVal ColIndex As Integer, _
    OldValue As Variant, _
    Cancel As Integer)
    If ColIndex = 0 Then
        'Disallow changes to [PrecinctID].
        Cancel = True
    ElseIf ColIndex = 1 Then
        'This is [Combo], which can't be Null.
        With dbgrdCombos.Columns(ColIndex)
            If Len(.Text) < 1 Then
                Cancel = True
                MsgBox "Must enter a value for " & .Caption, vbOKOnly, Caption
            End If
        End With
    End If
End Sub
This displays the PrecinctID in Columns(0) though.

To get the Precinct (name) instead might be easier using a flat Recordset and applying a Filter on it. But in the end we can only show you so much here. There are lots of options to decide among.
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top