I have a GridView table that I loaded data into from codebehind, and it is working, here is my GridView code:
<asp:Gridview runat="server" ID="GridView1"
style='z-index: 2; left: 0px; top: 80px; position: absolute; height: 105px; width: 1600px;'
GridLines="Both"
AllowSorting="True"
AutoGenerateEditButton="True"
OnRowEditing="GridView1_RowEditing"
OnRowCancelingEdit="GridView1_RowCancelingEdit"
onRowUpdating="GridView1_RowUpdating"
>
<HeaderStyle HorizontalAlign="Left" />
</asp:Gridview>
+++++++++++++++++++++++++++++++++++++++++++++++++++++
OnRowEditing and OnRowCanceling methods are working fine.
Here's my codebehind to load Gridview:
++++++++++++++++++++++++++++++++++++++++++++++++++++++
class-id ProductionInventory.TPR410_001_SCR_0001 is partial
inherits type System.Web.UI.Page public.
-------
working-storage section.
01 IN-MESSAGE-AREA.
03 IN-LINE-TABLE.
05 I-SCR-FAC-COMP-NUM PIC X(01).
05 I-SCR-FAC-DESC PIC X(20).
05 I-SCR-FAC-01 PIC X(06).
05 I-SCR-FAC-02 PIC X(06).
05 I-SCR-FAC-03 PIC X(06).
05 I-SCR-FAC-04 PIC X(06).
01 OUT-MESSAGE.
02 O-FILLER01 PIC X(08).
02 O-SCR-OVRDH-LINES.
05 O-SCR-OVRDH-DETAIL OCCURS 6 TIMES PIC X(39).
02 O-FILLER02 PIC X(06).
01 LINE-TABLE-DATA.
03 LINE-TABLE OCCURS 6 TIMES.
05 SCRO-FAC-COMP-NUM PIC X(01) VALUE SPACE.
05 SCRO-FAC-DESC PIC X(20) VALUE SPACES.
05 SCRO-FAC-01 PIC X(06) VALUE ZEROS.
05 SCRO-FAC-02 PIC X(06) VALUE ZEROS.
05 SCRO-FAC-03 PIC X(06) VALUE ZEROS.
01 WS-O-SUB PIC 9(02) VALUE ZERO.
01 TBL type System.Data.DataTable.
01 Col1 type System.Data.DataColumn.
01 Trow type System.Data.DataRow.
method-id. Load_Screen protected.
procedure division .
MOVE O-SCR-OVRDH-LINES TO LINE-TABLE-DATA.
set TBL to new System.Data.DataTable.
set Col1 to new System.Data.DataColumn.
set Col1::DataType to type System.Type::GetType("System.String").
set Col1::ColumnName to "FAC-COMP-NUM".
invoke TBL::Columns::Add(Col1).
set Col1 to new System.Data.DataColumn.
set Col1::DataType to type System.Type::GetType("System.String").
set Col1::ColumnName to "FAC-DESC ".
invoke TBL::Columns::Add(Col1).
set Col1 to new System.Data.DataColumn.
set Col1::DataType to type System.Type::GetType("System.String").
set Col1::ColumnName to "FAC-01 ".
invoke TBL::Columns::Add(Col1).
set Col1 to new System.Data.DataColumn.
set Col1::DataType to type System.Type::GetType("System.String").
set Col1::ColumnName to "FAC-02 ".
invoke TBL::Columns::Add(Col1).
set Col1 to new System.Data.DataColumn.
set Col1::DataType to type System.Type::GetType("System.String").
set Col1::ColumnName to "FAC-03 ".
invoke TBL::Columns::Add(Col1).
MOVE 1 TO WS-O-SUB
perform varying WS-O-SUB from 1 by 1 until WS-O-SUB > 6
set Trow to TBL::NewRow()
Invoke TBL::Rows::Add(Trow)
set Trow::Item("FAC-COMP-NUM") to SCRO-FAC-COMP-NUM(WS-O-SUB)::Trim
set Trow::Item("FAC-DESC ") to SCRO-FAC-DESC(WS-O-SUB)
set Trow::Item("FAC-01 ") to SCRO-FAC-01(WS-O-SUB)::Trim
set Trow::Item("FAC-02 ") to SCRO-FAC-02(WS-O-SUB)::Trim
set Trow::Item("FAC-03 ") to SCRO-FAC-03(WS-O-SUB)::Trim
end-perform.
invoke TBL::AcceptChanges().
set self::GridView1::DataSource to TBL.
invoke GridView1::DataBind().
set UCTSESSION::Value to THIS-SESSION-ALPHA.
set KEYPRESS::Value to " ".
end method Load_Screen.
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
In Method below, how do I get the values from the updating row?
method-id GridView1_RowUpdating protected.
procedure division using by value sender as object e as type System.Web.UI.WebControls.GridViewUpdateEventArgs.
**** I only want to get the values from that row, I will pass the values to another method for updating source table. ***
end method.