Enabling support for filtering options and sorting

This topic describes how to enable support for filtering options and sorting in OpenEdge.

In OpenEdge, you create one or more Business Entities as Data Object resources and generate your Data Service Catalog when you create the Data Object Service from these resources. A Business Entity is an ABL class or procedure object that implements a service interface that provides client access to data and business logic running on an OpenEdge application server. In Platform, you use the Data Service Catalog to create Platform external objects associated with OpenEdge Data Objects. You can enable support for filtering options and sorting by enhancing the Business Entity to accept a JSON object (JSON Filter Pattern) as a filter parameter.

This section describes what you must include in your Business Entity to enable sorting and filtering options in Platform.

To support sorting and filtering, you must ensure that your Business Entity and the associated include file (.i) with the schema has support for the parameters that are contained in the JSON object:

  • ablfilter — Supports filtering of records
  • id — Supports search by ID
  • top and skip — Supports paging
  • orderby — Supports sorting and grouping of records

In the include file, the temp-table definitions include the fields id and sequence (seq) to support JSON filter:

  • The id field is used to support the id parameter in the JSON filter.
  • The seq field is used to support the orderby parameter in the JSON filter.
The Read operation method method contains the code to process the JSON filter and return the corresponding records. The code uses the JSON classes in ABL to process the JSON filter. The ABL code implements the logic to handle each parameter. An AFTER-ROW-FILL method callback is used to populate the values of the id and seq fields. The local variable iSeq is used to obtain the values for the seq field.
Note: When you use the following code samples, verify that the formatting of the code is maintained. Alternatively, you can download the code samples from a Infinite Blue Community page.

The following sample include file (customer.i) illustrates a temp-table definition with id and seq fields:

/*------------------------------------------------------------------------
   File         : customer.i
   Purpose      :
   Syntax       : 
   Description  :
   Author(s)    : 
   Created      : 
   Notes        : 
 ----------------------------------------------------------------------*/
  
/* ***************************  Definitions  ************************** */
  
/* ********************  Preprocessor Definitions  ******************** */
  
/* ***************************  Main Block  *************************** */
  
/** Dynamically generated schema file **/
   
@openapi.openedge.entity.primarykey (fields="CustNum").
DEFINE TEMP-TABLE ttCustomer BEFORE-TABLE bttCustomer
FIELD id            AS CHARACTER
FIELD seq           AS INTEGER      INITIAL ?
FIELD CustNum       AS INTEGER      INITIAL "0" LABEL "Cust Num"
FIELD Name          AS CHARACTER    LABEL "Name"
FIELD Address       AS CHARACTER    LABEL "Address"
FIELD Address2      AS CHARACTER    LABEL "Address2"
FIELD Balance       AS DECIMAL      INITIAL "0" LABEL "Balance"
FIELD City          AS CHARACTER    LABEL "City"
FIELD Comments      AS CHARACTER    LABEL "Comments"
FIELD Contact       AS CHARACTER    LABEL "Contact"
FIELD Country       AS CHARACTER    INITIAL "USA" LABEL "Country"
FIELD CreditLimit   AS DECIMAL      INITIAL "1500" LABEL "Credit Limit"
FIELD Discount      AS INTEGER      INITIAL "0" LABEL "Discount"
FIELD EmailAddress  AS CHARACTER    LABEL "Email"
FIELD Fax           AS CHARACTER    LABEL "Fax"
FIELD Phone         AS CHARACTER    LABEL "Phone"
FIELD PostalCode    AS CHARACTER    LABEL "Postal Code"
FIELD SalesRep      AS CHARACTER    LABEL "Sales Rep"
FIELD State         AS CHARACTER    LABEL "State"
FIELD Terms         AS CHARACTER    INITIAL "Net30" LABEL "Terms"
INDEX seq seq
.

DEFINE DATASET dsCustomer FOR ttCustomer.

In the OpenEdge Business Entity, the code to process the JSON Filter Pattern is called from the read method and replaces the generated code for the read method as well as the private applyFillMethod() method.

The following business entity code from OpenEdge illustrates how to process the JSON Filter Pattern and enable filtering and sorting:

/*------------------------------------------------------------------------
    File        : Customer.cls
    Syntax      : 
    Author(s)   : 
    Created     : 
    Notes       : 
  ----------------------------------------------------------------------*/
    
@program FILE(name="Customer.cls", module="AppServer").
@openapi.openedge.export FILE(type="REST", executionMode="singleton", useReturnValue="false", writeDataSetBeforeImage="false").
@Progress.service.resource FILE(name="Customer", URI="/Customer", schemaName="dsCustomer", schemaFile="").

USING Progress.Lang.*.
USING Progress.Json.ObjectModel.*.


BLOCK-LEVEL ON ERROR UNDO, THROW. 

CLASS Customer:

    /*------------------------------------------------------------------------------
            Purpose:                                                                      
            Notes:                                                                        
    ------------------------------------------------------------------------------*/
     
    {"customer.i"}
                    
    DEFINE DATA-SOURCE srcCustomer  FOR Customer.
    DEFINE VARIABLE iSeq            AS INTEGER      NO-UNDO.    
    
    
    /*------------------------------------------------------------------------------
            Purpose:  Get one or more records, based on a filter string                                                                     
            Notes:                                                                        
    ------------------------------------------------------------------------------*/
    @openapi.openedge.export(type="REST", useReturnValue="false", writeDataSetBeforeImage="false").
    @Progress.service.resourceMapping(type="REST", operation="read", URI="?filter=~{filter~}", alias="", mediaType="application/json"). 
    METHOD PUBLIC VOID ReadCustomer(
            INPUT filter AS CHARACTER, 
            OUTPUT DATASET dsCustomer):

        DEFINE VARIABLE jsonParser     AS ObjectModelParser         NO-UNDO.
        DEFINE VARIABLE jsonObject     AS JsonObject                NO-UNDO.
        DEFINE VARIABLE cWhere         AS CHARACTER                 NO-UNDO.        

        DEFINE VARIABLE hQuery         AS HANDLE                    NO-UNDO.
        DEFINE VARIABLE lUseReposition AS LOGICAL                   NO-UNDO.        
        DEFINE VARIABLE iCount         AS INTEGER                   NO-UNDO.
        
        DEFINE VARIABLE ablFilter      AS CHARACTER                 NO-UNDO.
        DEFINE VARIABLE id             AS CHARACTER INITIAL ?       NO-UNDO.
        DEFINE VARIABLE iMaxRows       AS INTEGER   INITIAL ?       NO-UNDO.
        DEFINE VARIABLE iSkipRows      AS INTEGER   INITIAL ?       NO-UNDO.        
        DEFINE VARIABLE cOrderBy       AS CHARACTER INITIAL ""      NO-UNDO.                     
        
        /* The filter parameter can be:
            - a WHERE clause: if it begins with WHERE
            - a JSON object representing a query if it begins with { 
            - a free form filter specific to the business entity
        */

        MESSAGE "DEBUG: " filter.

        /* get rid of any existing data */
        EMPTY TEMP-TABLE ttCustomer.
        iSeq = 0.
                               
        IF filter BEGINS "WHERE " THEN
            cWhere = filter.
        ELSE IF filter BEGINS "~{" THEN 
        DO:        
            jsonParser  = NEW ObjectModelParser().
            jsonObject  = CAST(jsonParser:Parse(filter), jsonObject).
            iMaxRows    = jsonObject:GetInteger("top")  NO-ERROR.            
            iSkipRows   = jsonObject:GetInteger("skip") NO-ERROR.
            ablFilter   = jsonObject:GetCharacter("ablFilter") NO-ERROR.
            id          = jsonObject:GetCharacter("id") NO-ERROR.
            cOrderBy    = jsonObject:GetCharacter("orderBy") NO-ERROR.               
            cWhere      = "WHERE " + ablFilter.
            
            IF cOrderBy > "" THEN
            DO:                                
                cOrderBy = REPLACE(cOrderBy, ",", " by ").
                cOrderBy = "by " + cOrderBy + " ".                
                /* NOTE: id and seq fields should be removed from cWhere and cOrderBy */                
                cOrderBy = REPLACE(cOrderBy, "by id desc", "").
                cOrderBy = REPLACE(cOrderBy, "by id ", "").
                cOrderBy = REPLACE(cOrderBy, "by seq desc", "").
                cOrderBy = REPLACE(cOrderBy, "by seq ", "").
            END.                
            
            lUseReposition = iSkipRows <> ?.                                                 
        END.
        ELSE IF filter NE "" THEN
        DO:
            /* Use filter as WHERE clause */
            cWhere = "WHERE " + filter.            
        END.                                
                
        IF iMaxRows <> ? AND iMaxRows > 0 THEN
        DO:
            BUFFER ttCustomer:HANDLE:BATCH-SIZE = iMaxRows.
        END.
        ELSE DO:
        IF id > "" THEN
            BUFFER ttCustomer:HANDLE:BATCH-SIZE = 1.
        ELSE                                 
            BUFFER ttCustomer:HANDLE:BATCH-SIZE = 0.
        END.                        
        BUFFER ttCustomer:ATTACH-DATA-SOURCE(DATA-SOURCE srcCustomer:HANDLE).

        IF cOrderBy = ? THEN cOrderBy = "".
        cWhere = IF cWhere > "" THEN (cWhere + " " + cOrderBy) ELSE ("WHERE " + cOrderBy).                     
        MESSAGE "DEBUG: cWhere: " cWhere.
        MESSAGE "DEBUG: cOrderBy: " cOrderBy.        
        DATA-SOURCE srcCustomer:FILL-WHERE-STRING = cWhere.
            
        IF lUseReposition THEN
        DO:
            hQuery = DATA-SOURCE srcCustomer:QUERY.
            hQuery:QUERY-OPEN.
            IF id > "" AND id <> "?" THEN
            DO:
                hQuery:REPOSITION-TO-ROWID(TO-ROWID(id)).                
            END.                 
            ELSE IF iSkipRows <> ? AND iSkipRows > 0 THEN
            DO:
                hQuery:REPOSITION-TO-ROW(iSkipRows).
                IF NOT AVAILABLE Customer THEN
                    hQuery:GET-NEXT () NO-ERROR.                
            END.                
            iCount = 0.                
            REPEAT WHILE NOT hQuery:QUERY-OFF-END AND iCount < iMaxRows:
                hQuery:GET-NEXT () NO-ERROR.
                IF AVAILABLE Customer THEN
                DO:
                    CREATE ttCustomer.
                    BUFFER-COPY Customer TO ttCustomer.
                    ASSIGN  ttCustomer.id  = STRING(ROWID(Customer))
                            iSeq = iSeq + 1
                            ttCustomer.seq = iSeq.              
                END.   
                iCount = iCount + 1.                 
            END.                                 
        END.
        ELSE DO:
            IF id > "" THEN DATA-SOURCE srcCustomer:RESTART-ROWID(1) = TO-ROWID ((id)).            
            BUFFER ttCustomer:SET-CALLBACK ("AFTER-ROW-FILL", "AddIdField").                                             
            DATASET dsCustomer:FILL().
        END.            
        FINALLY:
            BUFFER ttCustomer:DETACH-DATA-SOURCE().
        END FINALLY.                
       
    END METHOD.
            
    METHOD PUBLIC VOID AddIdField (INPUT DATASET dsCustomer):        
        ASSIGN  ttCustomer.id = STRING(ROWID(Customer))
                iSeq = iSeq + 1
                ttCustomer.seq = iSeq.        
    END.                                  
      
    /*------------------------------------------------------------------------------
            Purpose: Create one or more new records                                                               
            Notes:                                                                        
    ------------------------------------------------------------------------------*/  
    @openapi.openedge.export(type="REST", useReturnValue="false", writeDataSetBeforeImage="false").
    @progress.service.resourceMapping(type="REST", operation="create", URI="", alias="", mediaType="application/json").
    METHOD PUBLIC VOID CreateCustomer(INPUT-OUTPUT DATASET dsCustomer):         
    
        THIS-OBJECT:CommitCustomer(INPUT "", INPUT ROW-CREATED).        
        RETURN.        
    END METHOD.    
    
    /*------------------------------------------------------------------------------
            Purpose:  Update one or more records                                                                  
            Notes:                                                                        
    ------------------------------------------------------------------------------*/
    @openapi.openedge.export(type="REST", useReturnValue="false", writeDataSetBeforeImage="false").
    @progress.service.resourceMapping(type="REST", operation="update", URI="", alias="", mediaType="application/json").
    METHOD PUBLIC VOID UpdateCustomer(INPUT-OUTPUT DATASET dsCustomer):         
    
        THIS-OBJECT:CommitCustomer(INPUT "", INPUT ROW-MODIFIED).
                  
    END METHOD.
    
    /*------------------------------------------------------------------------------
            Purpose:    Delete a record                                                               
            Notes:                                                                        
    ------------------------------------------------------------------------------*/
    @openapi.openedge.export(type="REST", useReturnValue="false", writeDataSetBeforeImage="false").
    @progress.service.resourceMapping(type="REST", operation="delete", URI="", alias="", mediaType="application/json").
    METHOD PUBLIC VOID DeleteCustomer(INPUT-OUTPUT DATASET dsCustomer):                    
    
        THIS-OBJECT:CommitCustomer(INPUT "", INPUT ROW-DELETED).
         
    END METHOD.
     
    /*------------------------------------------------------------------------------
            Purpose:  generic routine for creating/updating/deleting customers                                                                    
            Notes:                                                                        
    ------------------------------------------------------------------------------*/
    METHOD PRIVATE VOID commitCustomer(
                    INPUT pcFieldMapping AS CHARACTER,
                    INPUT piRowState AS INTEGER ):
        DEFINE VARIABLE Skip-list AS CHAR NO-UNDO.
        BUFFER ttCustomer:ATTACH-DATA-SOURCE (DATA-SOURCE srcCustomer:HANDLE,
                                             pcFieldMapping).
        FOR EACH ttCustomer.
            BUFFER ttCustomer:MARK-ROW-STATE (piRowState). 
        END.
        IF piRowState = ROW-CREATED THEN
            Skip-list  = "CustNum".
        FOR EACH bttCustomer:
            BUFFER bttCustomer:SAVE-ROW-CHANGES(1, Skip-list).
        END.
        FINALLY:
            BUFFER ttCustomer:DETACH-DATA-SOURCE().
            RETURN.
        END FINALLY.
    END METHOD.
              
END CLASS.

In a Business Entity from the latest release of OpenEdge, you can enable filtering and sorting by replacing the code in the Read method with the code that processes the JSON filter in a similar way to the above code, which continues to work in OpenEdge 11.3 or greater.

The following are additional annotations required for this use case in OpenEdge 11.5.1 and 11.6. They must be added manually.

@openapi.openedge.method.property(name="mappingType", value="JFP"). 
@openapi.openedge.method.property (name="capabilities", value="ablFilter,top,skip,id,orderBy").
Note: The ablFilter parameter is considered to always be supported and does not need to be listed in the values for the capabilities property.

The following is a Business Entity class file from OpenEdge that contains the code to process the JSON Filter Pattern:

 /*------------------------------------------------------------------------
    File        : Customer.cls
    Syntax      : 
    Author(s)   : 
    Created     : 
    Notes       : 
  ----------------------------------------------------------------------*/
    
@program FILE(name="Customer.cls", module="AppServer").
@openapi.openedge.export FILE(type="REST", executionMode="singleton", useReturnValue="false", writeDataSetBeforeImage="false").
@progress.service.resource FILE(name="Customer", URI="/Customer", schemaName="dsCustomer", schemaFile="Test/AppServer/customer.i").

USING OpenEdge.BusinessLogic.BusinessEntity.
USING Progress.Lang.*.
USING Progress.Json.ObjectModel.*.

BLOCK-LEVEL ON ERROR UNDO, THROW.

CLASS Customer INHERITS BusinessEntity:

    /*------------------------------------------------------------------------------
            Purpose:                                                                      
            Notes:                                                                        
    ------------------------------------------------------------------------------*/
     
    {"customer.i"}
                    
    DEFINE DATA-SOURCE srcCustomer FOR sports2000.Customer.
    DEFINE VARIABLE iSeq            AS INTEGER      NO-UNDO.           
    
    
     
    /*------------------------------------------------------------------------------
            Purpose:                                                                      
            Notes:                                                                        
    ------------------------------------------------------------------------------*/
    CONSTRUCTOR PUBLIC Customer():
        
        DEFINE VAR hDataSourceArray AS HANDLE NO-UNDO EXTENT 1.
        DEFINE VAR cSkipListArray AS CHAR NO-UNDO EXTENT 1.
        
        SUPER (DATASET dsCustomer:HANDLE).
        
        /* Data Source for each table in dataset. Should be in table order as defined 
           in DataSet */
            
        hDataSourceArray[1] =  DATA-SOURCE srcCustomer:HANDLE.
        
        
        /* Skip-list entry for each table in dataset. Should be in temp-table order 
           as defined in DataSet */
        /* Each skip-list entry is a comma-separated list of field names, to be
           ignored in create stmt */
            
        cSkipListArray[1] = "CustNum".
        
        
        THIS-OBJECT:ProDataSource = hDataSourceArray.
        THIS-OBJECT:SkipList = cSkipListArray.
                
    END CONSTRUCTOR.
    
    
    
    /*------------------------------------------------------------------------------
            Purpose:  Get one or more records, based on a filter string                                                                     
            Notes:                                                                        
    ------------------------------------------------------------------------------*/
    @openapi.openedge.export(type="REST", useReturnValue="false", writeDataSetBeforeImage="true").
    @progress.service.resourceMapping(type="REST", operation="read", URI="?filter=~{filter~}", alias="", mediaType="application/json").
    @openapi.openedge.method.property (name="capabilities", value="top,skip,id,orderBy"). 
    METHOD PUBLIC VOID ReadCustomer(
            INPUT filter AS CHARACTER, 
            OUTPUT DATASET dsCustomer):
        
        DEFINE VARIABLE jsonParser     AS ObjectModelParser         NO-UNDO.
        DEFINE VARIABLE jsonObject     AS JsonObject                NO-UNDO.
        DEFINE VARIABLE cWhere         AS CHARACTER                 NO-UNDO.        

        DEFINE VARIABLE hQuery         AS HANDLE                    NO-UNDO.
        DEFINE VARIABLE lUseReposition AS LOGICAL                   NO-UNDO.        
        DEFINE VARIABLE iCount         AS INTEGER                   NO-UNDO.
        
        DEFINE VARIABLE ablFilter      AS CHARACTER                 NO-UNDO.
        DEFINE VARIABLE id             AS CHARACTER INITIAL ?       NO-UNDO.
        DEFINE VARIABLE iMaxRows       AS INTEGER   INITIAL ?       NO-UNDO.
        DEFINE VARIABLE iSkipRows      AS INTEGER   INITIAL ?       NO-UNDO.        
        DEFINE VARIABLE cOrderBy       AS CHARACTER INITIAL ""      NO-UNDO.                     
        
        /* The filter parameter can be:
            - a WHERE clause: if it begins with WHERE
            - a JSON object representing a query if it begins with { 
            - a free form filter specific to the business entity
        */

        MESSAGE "DEBUG: " filter.

        /* get rid of any existing data */
        EMPTY TEMP-TABLE ttCustomer.
        iSeq = 0.
                               
        IF filter BEGINS "WHERE " THEN
            cWhere = filter.
        ELSE IF filter BEGINS "~{" THEN 
        DO:        
            jsonParser  = NEW ObjectModelParser().
            jsonObject  = CAST(jsonParser:Parse(filter), jsonObject).
            iMaxRows    = jsonObject:GetInteger("top")  NO-ERROR.            
            iSkipRows   = jsonObject:GetInteger("skip") NO-ERROR.
            ablFilter   = jsonObject:GetCharacter("ablFilter") NO-ERROR.
            id          = jsonObject:GetCharacter("id") NO-ERROR.
            cOrderBy    = jsonObject:GetCharacter("orderBy") NO-ERROR.               
            cWhere      = "WHERE " + ablFilter.
            
            IF cOrderBy > "" THEN
            DO:                                
                cOrderBy = REPLACE(cOrderBy, ",", " by ").
                cOrderBy = "by " + cOrderBy + " ".                
                /* NOTE: id and seq fields should be removed from cWhere and cOrderBy */                
                cOrderBy = REPLACE(cOrderBy, "by id desc", "").
                cOrderBy = REPLACE(cOrderBy, "by id ", "").
                cOrderBy = REPLACE(cOrderBy, "by seq desc", "").
                cOrderBy = REPLACE(cOrderBy, "by seq ", "").
            END.                
            
            lUseReposition = iSkipRows <> ?.                                                 
        END.
        ELSE IF filter NE "" THEN
        DO:
            /* Use filter as WHERE clause */
            cWhere = "WHERE " + filter.            
        END.                                
                
        IF iMaxRows <> ? AND iMaxRows > 0 THEN
        DO:
            BUFFER ttCustomer:HANDLE:BATCH-SIZE = iMaxRows.
        END.
        ELSE DO:
        IF id > "" THEN
            BUFFER ttCustomer:HANDLE:BATCH-SIZE = 1.
        ELSE                                 
            BUFFER ttCustomer:HANDLE:BATCH-SIZE = 0.
        END.                        
        BUFFER ttCustomer:ATTACH-DATA-SOURCE(DATA-SOURCE srcCustomer:HANDLE).

        IF cOrderBy = ? THEN cOrderBy = "".
        cWhere = IF cWhere > "" THEN (cWhere + " " + cOrderBy) ELSE ("WHERE " + cOrderBy).                     
        MESSAGE "DEBUG: cWhere: " cWhere.
        MESSAGE "DEBUG: cOrderBy: " cOrderBy.        
        DATA-SOURCE srcCustomer:FILL-WHERE-STRING = cWhere.
            
        IF lUseReposition THEN
        DO:
            hQuery = DATA-SOURCE srcCustomer:QUERY.
            hQuery:QUERY-OPEN.
            IF id > "" AND id <> "?" THEN
            DO:
                hQuery:REPOSITION-TO-ROWID(TO-ROWID(id)).                
            END.                 
            ELSE IF iSkipRows <> ? AND iSkipRows > 0 THEN
            DO:
                hQuery:REPOSITION-TO-ROW(iSkipRows).
                IF NOT AVAILABLE Customer THEN
                    hQuery:GET-NEXT () NO-ERROR.                
            END.                
            iCount = 0.                
            REPEAT WHILE NOT hQuery:QUERY-OFF-END AND iCount < iMaxRows:
                hQuery:GET-NEXT () NO-ERROR.
                IF AVAILABLE Customer THEN
                DO:
                    CREATE ttCustomer.
                    BUFFER-COPY Customer TO ttCustomer.
                    ASSIGN  ttCustomer.id  = STRING(ROWID(Customer))
                            iSeq = iSeq + 1
                            ttCustomer.seq = iSeq.              
                END.   
                iCount = iCount + 1.                 
            END.                                 
        END.
        ELSE DO:
            IF id > "" THEN DATA-SOURCE srcCustomer:RESTART-ROWID(1) = TO-ROWID ((id)).            
            BUFFER ttCustomer:SET-CALLBACK ("AFTER-ROW-FILL", "AddIdField").                                             
            DATASET dsCustomer:FILL().
        END.            
        FINALLY:
            BUFFER ttCustomer:DETACH-DATA-SOURCE().
        END FINALLY.
              
    END METHOD.
          
    METHOD PUBLIC VOID AddIdField (INPUT DATASET dsCustomer):        
        ASSIGN  ttCustomer.id = STRING(ROWID(Customer))
                iSeq = iSeq + 1
                ttCustomer.seq = iSeq.        
    END.    
          
    /*------------------------------------------------------------------------------
            Purpose: Create one or more new records                                                               
            Notes:                                                                        
    ------------------------------------------------------------------------------*/  
    @openapi.openedge.export(type="REST", useReturnValue="false", writeDataSetBeforeImage="true").
    @progress.service.resourceMapping(type="REST", operation="create", URI="", alias="", mediaType="application/json").
    METHOD PUBLIC VOID CreateCustomer(INPUT-OUTPUT DATASET dsCustomer):         
        DEFINE VAR hDataSet AS HANDLE NO-UNDO.
        hDataSet = DATASET dsCustomer:HANDLE.
       
        SUPER:CreateData(DATASET-HANDLE hDataSet BY-REFERENCE).        
    END METHOD.    
    
    /*------------------------------------------------------------------------------
            Purpose:  Update one or more records                                                                  
            Notes:                                                                        
    ------------------------------------------------------------------------------*/
    @openapi.openedge.export(type="REST", useReturnValue="false", writeDataSetBeforeImage="true").
    @progress.service.resourceMapping(type="REST", operation="update", URI="", alias="", mediaType="application/json").
    METHOD PUBLIC VOID UpdateCustomer(INPUT-OUTPUT DATASET dsCustomer):         
    
        DEFINE VAR hDataSet AS HANDLE NO-UNDO.
        hDataSet = DATASET dsCustomer:HANDLE.
       
        SUPER:UpdateData(DATASET-HANDLE hDataSet BY-REFERENCE).          
    END METHOD.
    
    /*------------------------------------------------------------------------------
            Purpose:    Delete a record                                                               
            Notes:                                                                        
    ------------------------------------------------------------------------------*/
    @openapi.openedge.export(type="REST", useReturnValue="false", writeDataSetBeforeImage="true").
    @progress.service.resourceMapping(type="REST", operation="delete", URI="", alias="", mediaType="application/json").
    METHOD PUBLIC VOID DeleteCustomer(INPUT-OUTPUT DATASET dsCustomer):                    
    
        DEFINE VAR hDataSet AS HANDLE NO-UNDO.
        hDataSet = DATASET dsCustomer:HANDLE.
       
        SUPER:DeleteData(DATASET-HANDLE hDataSet BY-REFERENCE).   
    END METHOD.
    
    /*------------------------------------------------------------------------------
            Purpose:    Submit a record                                                               
            Notes:                                                                        
    ------------------------------------------------------------------------------*/
    @openapi.openedge.export(type="REST", useReturnValue="false", writeDataSetBeforeImage="true").
    @progress.service.resourceMapping(type="REST", operation="submit", URI="/SubmitCustomer", alias="", mediaType="application/json").
    METHOD PUBLIC VOID SubmitCustomer(INPUT-OUTPUT DATASET dsCustomer):                    
    
        /* Calling extending class's CUD methods instead of SUPER:Submit() in case 
           customized functionality was added.
           Do deletes first, next modifies, and finally creates */
        THIS-OBJECT:DeleteCustomer(DATASET dsCustomer).
        THIS-OBJECT:UpdateCustomer(DATASET dsCustomer).
        THIS-OBJECT:CreateCustomer(DATASET dsCustomer).        
    END METHOD.
     
          
END CLASS.

For information about sorting and grouping, see Filtering OpenEdge Service objects by search criteria.

This topic is under revision.
Implementing the pattern filter method in the Business Entity class file OpenEdge Business entities generated from Progress Developer Studio for OpenEdge 11.3 or earlier support READ operations based on a filter. In order to support sorting and filtering capabilities, you can modify the business entity to support JSON filter pattern. The JSON filter pattern method is a model or a pattern in which the ABL filter parameter of the READ operation is used as a JSON object (a string). This JSON object must be hard-coded to include additional parameters that are required for sorting and filtering.what are the additional parameters?