Try OpenEdge Now
skip to main content
GUI for .NET Programming
Binding ABL Data to .NET Controls : Example of an updatable grid : Internal procedures and functions
 

Internal procedures and functions

The CreateRow event handler, BindSCreateRow, gets the BufferName from the CreateRowEventArgs class instance. Before attempting to create the new record, the handler ensures that the Created property is FALSE. The handler calls the CreateRow function, which returns zero if the create operation fails. If the create operation succeeds, the handler adds the new record to the result list for the appropriate query in the ProBindingSource. Finally, the handler sets the Created property to TRUE to signal the creation succeeded.
/* Internal Procedures */

PROCEDURE cleanup:

/* Cleanup ProDataSet resources */

  rBindS:Dispose( ).

END PROCEDURE.

/* BindingSource event procedures */

PROCEDURE BindSCreateRow:
  DEFINE INPUT PARAMETER rSender AS System.Object                    NO-UNDO.
  DEFINE INPUT PARAMETER rArgs   AS Progress.Data.CreateRowEventArgs NO-UNDO.

  DEFINE VARIABLE hQuery AS HANDLE NO-UNDO.

  /* Set Created to FALSE until we are sure the record has been created. */
  rArgs:Created = FALSE.

  CreateBlock:
  DO ON ERROR UNDO, LEAVE:
    IF CreateRow(INPUT rArgs:BufferName) > 0 THEN
      LEAVE CreateBlock.
    hQuery = GetCurrentQuery(INPUT rArgs:BufferName).
    hQuery:CREATE-RESULT-LIST-ENTRY().
    rArgs:Created = TRUE.
  END.

END PROCEDURE.
The CancelCreateRow event handler, BindSCancelCreateRow, gets the BufferName from the CancelCreateRowEventArgs class instance. The handler finds the correct query in the ProBindingSource with the GetCurrentQuery function. Then, the handler deletes the record from the appropriate temp-table, raising a warning message if the record cannot be deleted.
PROCEDURE BindSCancelCreateRow:
  DEFINE INPUT PARAMETER rSender AS System.Object NO-UNDO.
  DEFINE INPUT PARAMETER rArgs
    AS Progress.Data.CancelCreateRowEventArgs     NO-UNDO.

  DEFINE VARIABLE cBufferName AS CHARACTER        NO-UNDO.
  DEFINE VARIABLE hQuery      AS HANDLE           NO-UNDO.

  cBufferName = rArgs:BufferName.

  DO TRANSACTION:
    hQuery = GetCurrentQuery(INPUT cBufferName).
    hQuery:GET-CURRENT(EXCLUSIVE-LOCK).

    CASE cBufferName:
      WHEN "ttCustomer" THEN
        DELETE ttCustomer NO-ERROR.
      WHEN "ttOrder" THEN
        DELETE ttOrder NO-ERROR.
      WHEN "ttOrderLine" THEN
        DELETE ttOrderLine NO-ERROR.
    END CASE.

    IF ERROR-STATUS:ERROR THEN
      MESSAGE "New" cBufferName "record cannot be deleted."
        VIEW-AS ALERT-BOX WARNING.
    ELSE hQuery:DELETE-RESULT-LIST-ENTRY().

  END. /* transaction */

END PROCEDURE.
The grid's BeforeRowUpdate event fires when an action occurs that should result in any changed screen values being written to the data source object. However, the event does not indicate that the screen values have in fact changed. So, the sample procedure needs to verify that there are changes and then write those changes to the ProDataSet.
In the UltraGrid, each row belongs to a band which represents a specific level in the hierarchical grid. The event handler, gridBeforeRowUpdate, determines the correct buffer name for a row by retrieving the UltraGridBand class' Key property. The handler uses the RowModified property to verify that the current row in the ProBindingSource is being edited. The handler then uses the ASSIGN( ) method to update the ProDataSet, raising an error if it fails. The handler calls the ProcessRowChanges function to write the changes in the ProDataSet back to the database.
Note: Combining the logic for updating the data source object and the database in the same procedure is done for convenience in this example. If you were building an OpenEdge Reference Architecture-compliant application, you would separate these functions into the correct layers of your application.
PROCEDURE gridBeforeRowUpdate:
  DEFINE INPUT PARAMETER rSender AS System.Object          NO-UNDO.
  DEFINE INPUT PARAMETER rArgs   AS CancelableRowEventArgs NO-UNDO.

  DEFINE VARIABLE cBufferName AS CHARACTER                 NO-UNDO.
  DEFINE VARIABLE lResult     AS LOGICAL                   NO-UNDO.

  cBufferName = rArgs:Row:Band:Key.

  IF rBindS:RowModified THEN
  DO TRANSACTION:
    lResult = rBindS:Assign().

    IF NOT lResult THEN
    /* Error assigning changes from grid to dataset */
    DO:
      rArgs:Cancel = TRUE.
      LEAVE.
    END.

    /* Any necessary validation logic goes here. */

    IF NOT ProcessRowChanges(INPUT cBufferName) THEN
    /* Error assigning changes from dataset to database */
    DO:
      rArgs:Cancel = TRUE.
      LEAVE.
    END.
  END.    /* transaction  */

END PROCEDURE.
The grid's BeforeRowsDeleted event fires before any rows are deleted. The BeforeRowsDeletedEventArgs class stores the selected rows in the Rows property. The event handler, gridBeforeRowsDeleted, determines the number of rows from the Length property. Note that the Rows property is a 0-based array, so the REPEAT block counts up from zero. The handler then calls the DeleteRow function to delete each row in turn.
To refresh the grid properly, the handler turns off the ProBindingSource's AutoSync property at the start. If only a single row is deleted, the handler removes that row directly from the current query's result list. Otherwise, the handler reopens the query. The handler then reactivates the AutoSync property before leaving.
PROCEDURE gridBeforeRowsDeleted:
  DEFINE INPUT PARAMETER rSender AS System.Object              NO-UNDO.
  DEFINE INPUT PARAMETER rArgs   AS BeforeRowsDeletedEventArgs NO-UNDO.

  DEFINE VARIABLE rCurrentRow AS UltraGridRow                  NO-UNDO.
  DEFINE VARIABLE cBufferName AS CHARACTER                     NO-UNDO.
  DEFINE VARIABLE hQuery      AS HANDLE                        NO-UNDO.
  DEFINE VARIABLE rRows       AS System.Array                  NO-UNDO.
  DEFINE VARIABLE iNumRows    AS INTEGER                       NO-UNDO.
  DEFINE VARIABLE idx         AS INTEGER                       NO-UNDO.
  DEFINE VARIABLE iStatus     AS INTEGER                       NO-UNDO.
  DEFINE VARIABLE cPromptText AS CHARACTER                     NO-UNDO.

  iNumRows        = rArgs:Rows:Length.
  rRows           = rArgs:Rows.
  rBindS:AutoSync = FALSE. /* query-open should not force a refresh */

  /* Suppress Infragistics default prompt. We need to do this because the
     prompt appears after this procedure has completed - when the records
     have already been deleted. Our own prompt is substituted below. */
  rArgs:DisplayPromptMsg = FALSE.

  /* Prompt for confirmation */
  IF iNumRows > 1 THEN
    cPromptText = "Are you sure you want to delete the "
                + STRING(iNumRows)
                + " selected records?".
  ELSE cPromptText = "Are you sure
you want to delete the selected record?".

  MESSAGE cPromptText VIEW-AS ALERT-BOX QUESTION
    BUTTONS YES-NO
    UPDATE lConfirmDelete AS LOGICAL.

  IF NOT lConfirmDelete THEN
    rArgs:Cancel = TRUE.
  ELSE
  deleteTransaction:
  DO TRANSACTION:
    REPEAT idx = 0 TO iNumRows - 1 WHILE rArgs:Cancel = FALSE:
      rCurrentRow = CAST(rRows:GetValue(idx), UltraGridRow).
      cBufferName = rCurrentRow:Band:Key.
      hQuery      = GetCurrentQuery(INPUT cBufferName).

      iStatus     = DeleteRow(INPUT cBufferName, INPUT hQuery,
                              INPUT rCurrentRow).

      IF iStatus > 0 THEN
      DO:
        rArgs:Cancel = TRUE.
        UNDO deleteTransaction, LEAVE deleteTransaction.
      END.

      ELSE DO:
        /*If only deleting one record, use DELETE-RESULT-LIST-ENTRY.*/
        IF iNumRows = 1 THEN
        hQuery:DELETE-RESULT-LIST-ENTRY().
      END.
    END.   /* END REPEAT */

    /* If deleting multiple records, reopen query now. */
    IF iNumRows > 1 THEN
      hQuery:QUERY-OPEN.
  END. /* transaction */

  rBindS:AutoSync = TRUE.

END PROCEDURE.
The ProcessRowChanges function uses the ProDataSet SAVE-ROW-CHANGES( ) and ACCEPT-ROW-CHANGES( ) methods to write the changes from the ProDataSet back to the database.
Note: Combining the logic for updating the data source object and the database in the same procedure is done for convenience in this example. If you were building an OpenEdge Reference Architecture-compliant application, you would separate these functions into the correct layers of your application.
FUNCTION ProcessRowChanges RETURNS LOGICAL (INPUT cBufferName AS CHARACTER).
  DEFINE VARIABLE hQuery        AS HANDLE NO-UNDO.
  DEFINE VARIABLE hBeforeBuffer AS HANDLE NO-UNDO.
  DEFINE VARIABLE hAfterBuffer  AS HANDLE NO-UNDO.
  DEFINE VARIABLE lResult       AS LOGICAL NO-UNDO.

  hBeforeBuffer = ?.

  CASE cBufferName:
    WHEN "ttCustomer" THEN
    DO:
      hAfterBuffer  = BUFFER ttCustomer:HANDLE.
      hBeforeBuffer = hAfterBuffer:BEFORE-BUFFER.
    END.
    WHEN "ttOrder" THEN
    DO:
      hAfterBuffer  = BUFFER ttOrder:HANDLE.
      hBeforeBuffer = hAfterBuffer:BEFORE-BUFFER.
    END.
    WHEN "ttOrderLine" THEN
    DO:
      hAfterBuffer  = BUFFER ttOrderLine:HANDLE.
      hBeforeBuffer = hAfterBuffer:BEFORE-BUFFER.
    END.
  END CASE.

  /* Save-Row-Changes causes db triggers to fire. */
  lResult = hBeforeBuffer:SAVE-ROW-CHANGES() NO-ERROR.
  IF NOT lResult THEN
    DO:
      hBeforeBuffer:REJECT-ROW-CHANGES().
      RETURN FALSE.
    END.

  IF NOT hBeforeBuffer:ACCEPT-ROW-CHANGES() THEN
    RETURN FALSE.

  RETURN TRUE.

END FUNCTION.
The CreateRow function creates a new record in the appropriate temp-table and sets some initial properties. Note the use of the CATCH block here. The ProBindingSource ensures that the parent record is in the buffer by this point. So, the function uses the structured error handlings approach.
FUNCTION CreateRow RETURNS INTEGER (INPUT cBufferName AS CHARACTER).

  DO TRANSACTION ON ERROR UNDO, LEAVE:

    CASE cBufferName:
      WHEN "ttCustomer" THEN DO:
        CREATE ttCustomer.
        ASSIGN
          ttCustomer.Custnum = NEXT-VALUE(NextCustNum, sports2000)
          ttCustomer.Name    = "default".
      END.
      WHEN "ttOrder" THEN DO:
        CREATE ttOrder.
        ASSIGN
          ttOrder.OrderNum = NEXT-VALUE(NextOrdNum, sports2000)
          ttOrder.CustNum  = ttCustomer.CustNum.
      END.
      WHEN "ttOrderLine" THEN DO:
        CREATE ttOrderLine.
        ASSIGN
          ttOrderLine.Ordernum = ttOrder.OrderNum.
      END.
    END CASE.

    CATCH rAssignError AS Progress.Lang.Syserror:

      /* Trap any error so we can return a status of 1. */
        MESSAGE rAssignError:GETMESSAGE(1) VIEW-AS ALERT-BOX ERROR.
    END.

  END. /* transaction */

  IF VALID-OBJECT(rAssignError) THEN
  DO:
    RETURN 1.
  END.

  RETURN 0.

END FUNCTION.
For more information on CATCH blocks and structured error handling, see the section on error handling enhancements in OpenEdge Getting Started: New and Revised Features.
The DeleteRow function finds the cell in the input UltraGridRow that corresponds to the primary index for each of the temp-tables in the ProDataSet. Using that cell's value, the function finds the ROWID for the passed in row. The handler then repositions to that row and deletes the row from the temp-table. The handler then calls the ProcessRowChanges function to write the changes from the ProDataSet to the database.
Note: Combining the logic for updating the data source object and the database in the same procedure is done for convenience in this example. If you were building an OpenEdge Reference Architecture-compliant application, you would separate these functions into the correct layers of your application.
FUNCTION DeleteRow RETURNS INTEGER (INPUT cBufferName AS CHARACTER,
  INPUT hQuery AS HANDLE, INPUT rCurrentRow AS UltraGridRow).

  DEFINE VARIABLE rCells        AS CellsCollection NO-UNDO.
  DEFINE VARIABLE rCell0        AS UltraGridCell   NO-UNDO.
  DEFINE VARIABLE rCell1        AS UltraGridCell   NO-UNDO.
  DEFINE VARIABLE iNum          AS INTEGER         NO-UNDO.
  DEFINE VARIABLE iLineNum      AS INTEGER         NO-UNDO.
  DEFINE VARIABLE rRowID        AS ROWID           NO-UNDO.
  DEFINE VARIABLE cErrorMessage AS CHARACTER       NO-UNDO.

  rCells = rCurrentRow:Cells.
  rCell0 = rCells[0].

  CASE cBufferName:
    WHEN "ttCustomer" THEN DO:    
      iNum = INTEGER(rCell0:Text).  /* CustNum */
      FIND ttCustomer WHERE ttCustomer.CustNum = iNum.
      rRowID = ROWID(ttCustomer).
    END.
    WHEN "ttOrder" THEN DO:
      iNum = INTEGER(rCell0:Text).  /* OrderNum */
      FIND ttOrder WHERE ttOrder.OrderNum = iNum.
      rRowID = ROWID(ttOrder).
    END.
    WHEN "ttOrderLine" THEN DO:
      rCell1 = rCells[1].
      iNum = INTEGER(rCell0:Text).  /* OrderNum */
      iLineNum = INTEGER(rCell1:Text).  /* LineNum */
      FIND ttOrderLine WHERE ttOrderLine.OrderNum = iNum
                       AND   ttOrderLine.LineNum = iLineNum.
      rRowID = ROWID(ttOrderLine).
    END.
  END CASE.

  IF rRowID = ? THEN
    RETURN 1.

  CASE cBufferName:
    WHEN "ttCustomer" THEN
      DELETE ttCustomer NO-ERROR.
    WHEN "ttOrder" THEN
      DO:
        /* First, delete the OrderLines of the Order */
        DEFINE VARIABLE hOrderLineQuery AS HANDLE NO-UNDO.
        hOrderLineQuery = GetCurrentQuery(INPUT "ttOrderLine").
        FOR EACH ttOrderLine OF ttOrder:
          DELETE ttOrderline NO-ERROR.
          IF ERROR-STATUS:ERROR THEN
            DO:
              IF ERROR-STATUS:NUM-MESSAGES > 0 THEN
                cErrorMessage = ERROR-STATUS:GET-MESSAGE(1).
              ELSE
                cErrorMessage = "Error deleting temp-table record for
                                 Orderline "
                              + STRING(ttOrderLine.OrderNum)
                              + "/"
                              + STRING(ttOrderLine.LineNum).
                MESSAGE cErrorMessage VIEW-AS ALERT-BOX ERROR.
            RETURN 1.
            END.
          IF ProcessRowChanges(INPUT "ttOrderLine") = FALSE THEN
          RETURN 1.
      END.
      DELETE ttOrder NO-ERROR.
    END.
    WHEN "ttOrderLine" THEN
      DELETE ttOrderLine NO-ERROR.
  END CASE.

  IF ERROR-STATUS:ERROR THEN
  DO:
    IF ERROR-STATUS:NUM-MESSAGES > 0 THEN
      cErrorMessage = ERROR-STATUS:GET-MESSAGE(1).
    ELSE cErrorMessage = "Temp-table record delete failed.".

    MESSAGE cErrorMessage VIEW-AS ALERT-BOX ERROR.

    RETURN 1.
  END.

  IF ProcessRowChanges(INPUT cBufferName) = TRUE THEN
    RETURN 0.

  ELSE RETURN 1.

END FUNCTION.
The GetCurrentQuery function determines the correct query to use in the ProBindingSource.
FUNCTION GetCurrentQuery RETURNS HANDLE (INPUT cBufferName AS CHARACTER).
  DEFINE VARIABLE hDataSet  AS HANDLE NO-UNDO.
  DEFINE VARIABLE hRelation AS HANDLE NO-UNDO.
  DEFINE VARIABLE hQuery    AS HANDLE NO-UNDO.

  hDataSet = DATASET dsCustOrder:HANDLE.

  CASE cBufferName:
    WHEN "ttCustomer" THEN
      hQuery = hTopQuery.
    WHEN "ttOrder" THEN DO:
      hRelation = hDataSet:GET-RELATION(1).
      hQuery = hRelation:CURRENT-QUERY().
    END.
    WHEN "ttOrderLine" THEN DO:
      hRelation = hDataSet:GET-RELATION(2).
      hQuery = hRelation:CURRENT-QUERY().
    END.
    OTHERWISE
      hQuery = ?.
  END CASE.

  RETURN hQuery.

END FUNCTION.