Technology Blog Posts by Members
cancel
Showing results for 
Search instead for 
Did you mean: 
Discoverer
Explorer
2,220

Hi Community,
In this blog, we’ll explore how to build a custom ABAP utility that enables Excel-based upload and download functionality for Z-tables, with real-time validation against check table entries. This solution allows users to generate Excel templates, validate input data during upload, and update custom tables dynamically all from a single report.

Introduction

In many SAP projects, business users request Excel-based upload and download features for ease of data entry and mass maintenance. However, ensuring data integrity during uploads—especially for custom tables with check table dependencies—is crucial.
This blog showcases a utility report in ABAP that enables:

  • Downloading a Z-table structure into Excel from Se16N

  • Uploading Excel data back into SAP

  • Validating data against defined check tables

  • Updating the custom table only if validation passes

Let’s walk through the solution with modular includes, class-based design, and user-friendly error handling via SALV.

Solution Overview

The solution is built using:

  • Modular Includes: Top declarations, selection screens, class definitions, and implementations are separated for clarity.

  • Dynamic Programming: Internal tables and field symbols are generated at runtime based on the table name.

  • SOI Interface: SAP Office Integration is used to parse Excel.

  • Check Table Validation: All dependent fields are validated using metadata (from DDIF_FIELDINFO_GET).

  • Error Handling: Errors are displayed using SALV with row indicators.

Selection Screen Design

Two main modes:

  • Export: Generates an Excel template based on a selected custom table and navigates to SE16N.

  • Import: Reads and uploads validated Excel content into the corresponding Z-table.

 

Below is the Report Program zcustom_excel

REPORT zcustom_excel.
INCLUDE zcust_excel_top.
INCLUDE zcust_excel_sel.
INCLUDE zcust_excel_cls_dfn.
INCLUDE zcust_excel_cls_dec.
INITIALIZATION.
  CLEAR: go_ref.
  go_ref = NEW lcl_header_values( ).
  go_ref->initialize( ).
AT SELECTION-SCREEN OUTPUT.
  LOOP AT SCREEN INTO DATA(ls_screen).
    IF ls_screen-name CS 'PATH'.
      ls_screen-active = COND #( WHEN rb_exp = abap_true THEN 0 ELSE 1 ).
      MODIFY SCREEN FROM ls_screen.
    ENDIF.
  ENDLOOP.
AT SELECTION-SCREEN.
  go_ref->file_import( ).
AT SELECTION-SCREEN ON VALUE-REQUEST FOR p_path.
  go_ref->pop_up_dialogue( ).
START-OF-SELECTION.
  go_ref->operation( ).
​

Top Declaration is done in INCLUDE zcust_excel_top. 

TYPES:BEGIN OF gty_msg, 
         lights(4) TYPE c, 
         row       TYPE i, 
         message   TYPE tdline, 
       END OF gty_msg. 
 DATA:gs_msg          TYPE gty_msg, 
      gt_msg          TYPE TABLE OF gty_msg, 
      gv_wtitle       TYPE string , 
      gv_format       TYPE string, 
      gt_dyn_tab      TYPE REF TO data, 
      gt_dyn_tab1     TYPE REF TO data, 
      go_salv         TYPE REF TO cl_salv_table, 
 ##NEEDED      gv_msg          TYPE REF TO cx_salv_msg, 
      gt_table_filds  TYPE TABLE OF dfies, 
      gt_table_filds1 TYPE TABLE OF dfies, 
      gs_dyn_tab      TYPE REF TO data, 
      gv_auth_result  TYPE c LENGTH 1. 
 FIELD-SYMBOLS:<fs_val>       TYPE any, 
               <fs_dyn>       TYPE STANDARD TABLE, 
               <fs_dyn1>      TYPE STANDARD TABLE, 
               <fs_dyns>      TYPE any, 
               <fs_dyn_field> TYPE any. 



Parameter declaration is done in include ZCUST_EXCEL_SEL 

PARAMETERS:p_tab TYPE zch_de_tabname OBLIGATORY. 
 SELECTION-SCREEN BEGIN OF BLOCK b1 WITH FRAME TITLE TEXT-006. 
   PARAMETERS:rb_exp RADIOBUTTON GROUP grp MODIF ID rb1 DEFAULT 'X' USER-COMMAND rb, 
              rb_imp RADIOBUTTON GROUP grp  MODIF ID rb2. 
  
SELECTION-SCREEN END OF BLOCK b1. 
 SELECTION-SCREEN BEGIN OF BLOCK b3 WITH FRAME TITLE TEXT-007. 
   PARAMETERS: p_path TYPE ibipparms-path MODIF ID fil. 
 SELECTION-SCREEN END OF BLOCK b3. ​

Class Definition is done in the include INCLUDE zcust_excel_cls_dfn. 

CLASS  lcl_header_values DEFINITION. 
   PUBLIC SECTION. 
     METHODS: file_import, 
       operation, 
       pop_up_dialogue, 
       initialize. 
  
ENDCLASS. 
 DATA go_ref TYPE REF TO  lcl_header_values. 

 

Class Implementation is done in include INCLUDE zcust_excel_cls_dec 

 CLASS lcl_header_values IMPLEMENTATION.
 
"File_import method is used to do the validation based on Input table name in "selection screen.  
METHOD file_import.
 
    SELECT low FROM tvarvc WHERE name = 'ZCUST_TAB_TVARVC' AND low = @p_tab INTO TABLE (lt_tvarvc).
 
    CASE sy-ucomm.
 
      WHEN  'ONLI'.
 
        IF p_tab+0(1) <> 'Z'.
 
          MESSAGE 'Given table is not a custom table' TYPE 'E'.
 
        ELSEIF p_tab IS NOT INITIAL.
 
          SELECT tabname  FROM dd02l WHERE tabname LIKE 'Z%' AND tabclass = 'TRANSP'  AND    ##NEEDED
 
          tabname = @p_tab INTO TABLE (lt_tabname).
 
          IF sy-subrc NE 0.
 
            MESSAGE 'Given table is not existing in the system' TYPE 'E' .
 
          ENDIF.
 
        ENDIF.
 

    
 
        IF p_path IS INITIAL AND rb_imp EQ abap_true.
 
          MESSAGE 'table name Filed can''t be empty' TYPE 'E'.
 
        ENDIF.
 
    ENDCASE.
 

  ENDMETHOD.
 
  METHOD operation.
 
    DATA:lt_excel    TYPE TABLE OF alsmex_tabline,
 
         lv_col      TYPE i,
 
         lv_flag     TYPE abap_bool,
 
         lo_cols     TYPE REF TO cl_salv_columns_table,
 
         lo_column   TYPE REF TO cl_salv_column,
 
         lv_table    TYPE char50,
 
         lv_field    TYPE char50,
 
         lv_clause   TYPE char200,
 
         lt_tab      TYPE string_table,
 
       ##NEEDED ls_tab      LIKE LINE OF lt_tab,
 
         lv_transaction TYPE tstc-tcode VALUE 'SE16N',
 
         lv_count    TYPE i VALUE 0.
TYPES: BEGIN OF hex_record,
 
                 myhex TYPE x LENGTH 1024,
 
               END OF hex_record.
 
        DATA lt_upload     TYPE STANDARD TABLE OF hex_record.
 
        DATA lv_filelength TYPE i.
 
        DATA:gv_filename TYPE string.

 
"Based on custom table name it will navigate to se16n screen 
    IF rb_exp EQ abap_true.
 
      SET PARAMETER ID 'DTB' FIELD p_tab.
"Providing Authorization 
      AUTHORITY-CHECK OBJECT 'S_TCODE'
 
               ID 'TCD' FIELD 'SE16N'.
 
      IF sy-subrc EQ 0.
 
        CALL TRANSACTION  lv_transaction.
 
      ELSE.
 
        MESSAGE 'User dont have authorization for SE16N T-Code' TYPE 'E'.
 
      ENDIF.
 
    ELSEIF rb_imp EQ abap_true.
 "Here we are mainataining some custom table that supposed to insert the data 
      SELECT low FROM tvarvc WHERE name = 'ZCUST_TAB_TVARVC' AND low = @p_tab INTO TABLE (lt_tvarvc).
 
      IF lt_tvarvc IS NOT INITIAL.
 
"Here we are Creating the dynamic internal table based on the table we have "provided in the selection screen
        CREATE DATA gt_dyn_tab TYPE  TABLE OF (p_tab).
 
        CREATE DATA gs_dyn_tab TYPE (p_tab).
 
        CREATE DATA gt_dyn_tab1 TYPE  TABLE OF (p_tab).
 
        ASSIGN gt_dyn_tab->* TO <fs_dyn>.
 
        ASSIGN gt_dyn_tab1->* TO <fs_dyn1>.
 
        ASSIGN gs_dyn_tab->* TO <fs_dyns>.
 
        
 
        gv_filename = p_path.
 


        cl_sovy_container_control=>get_container_control(
 
          EXPORTING
 
            office_integration_mode = cl_sovy_container_control=>soi_mode_import
 
*           config                  = VALUE #( enforce_new_integration = enforce )
 
          IMPORTING
 
            control                 = DATA(control) ).
 
        DATA(container) = NEW cl_gui_custom_container( container_name = 'CONTAINER' ).
 
        control->init_control( r3_application_name = 'SHEET_IMPORT'
 
                               parent              = container ).
 
        control->get_document_proxy( EXPORTING document_type  = 'Excel.Sheet'
 
                                     IMPORTING document_proxy = DATA(document_proxy) ).
 
        CALL FUNCTION 'GUI_UPLOAD'
           EXPORTING
             filename   = gv_filename
             filetype   = 'BIN'
           IMPORTING
             filelength = lv_filelength
           TABLES
             data_tab   = lt_upload.
 

        document_proxy->open_document_from_table( document_size  = lv_filelength
 
                                                 document_table = lt_upload ).
 
        document_proxy->get_spreadsheet_interface( IMPORTING sheet_interface = DATA(sheet) ).
 
        DATA sheetname TYPE soi_field_name.
 
        sheetname = 'Sheet1'.
 
        sheet->get_active_sheet( IMPORTING sheetname = sheetname ).
 
        DATA(rangesdef) = VALUE soi_dimension_table( ( row     = 1
 
                                                    column  = 1
 
                                                    rows    = 1000
 
                                                    columns = 20 ) ).
 
        DATA ranges   TYPE soi_range_list.
 
        DATA : contents TYPE soi_generic_table,
 
               ls_data  TYPE soi_generic_item.
 
        sheet->get_ranges_data( EXPORTING rangesdef = rangesdef
 
                                IMPORTING contents  = contents
 
                                CHANGING  ranges    = ranges ).
 
        IF sy-subrc EQ 0.
 
*** --- Sort
 
          SORT lt_excel BY row.
 

*          LOOP AT lt_excel INTO DATA(ls_excel).
 
          LOOP AT contents INTO ls_data.
 
*** --- Adding count to skip the mapping for MANDT field
 
*            lv_col = ls_excel-col + 1.
 
            lv_col = ls_data-column + 1.
 

            ASSIGN COMPONENT lv_col OF STRUCTURE <fs_dyns> TO <fs_dyn_field>.
 
            IF sy-subrc = 0.
 
***-- Compare Excel sheet column data and Dynamic table fields
 
*              IF ls_excel-row = 1.
 
              IF ls_data-row = 1.
 
                CALL FUNCTION 'DDIF_FIELDINFO_GET'      "#EC CI_SUBRC
                   EXPORTING
                     tabname        = p_tab
                   TABLES
                     dfies_tab      = gt_table_filds
                   EXCEPTIONS ##FM_SUBRC_OK
                     not_found      = 1
                     internal_error = 2
                     OTHERS         = 3.
 
                IF sy-subrc IS NOT INITIAL.
 
                  MESSAGE ID sy-msgid TYPE sy-msgty NUMBER sy-msgno
 
                          WITH sy-msgv1 sy-msgv2 sy-msgv3 sy-msgv4.
 
                ENDIF.
 
                READ TABLE gt_table_filds INTO DATA(ls_table_fields) INDEX lv_col.
 
                IF sy-subrc = 0.
 

                  IF ls_table_fields-scrtext_m EQ ls_data-value OR ls_table_fields-scrtext_l EQ ls_data-value  .
 
                  ELSE.
 
                    MESSAGE 'Provided table is not matching with the Excel data ' TYPE 'E'.
 
                    LEAVE SCREEN.
 
                  ENDIF.
 
                ENDIF.
 
              ELSE.
 
*                <fs_dyn_field> = ls_excel-value.
                 <fs_dyn_field> = ls_data-value.
 
              ENDIF.
 
            ENDIF.
 
*            IF ls_excel-row GT 1.
 
            DATA(lv_val) = ls_data-value.
 
            IF ls_data-row GT 1.
 
              AT NEW row.
 
                IF lv_val IS INITIAL .
 
                  EXIT.
 
                ENDIF.
 
              ENDAT .
 
              AT END OF row.
 
                IF <fs_dyns>  IS ASSIGNED AND  <fs_dyn> IS ASSIGNED.
 
                  APPEND <fs_dyns> TO <fs_dyn>.
 
                ENDIF.
 
                CLEAR <fs_dyns>.
 
              ENDAT.
 
            ENDIF.
 
*            NEW
 
*            ENDIF.
 
*            end
 
          ENDLOOP.
 
        ENDIF.
 


        "Excel data to validate
 
        LOOP AT <fs_dyn> ASSIGNING FIELD-SYMBOL(<lfs_dn1>).
 
          lv_count =  lv_count + 1.
 
          CLEAR:lv_flag.
 
          "Checking for any custom table is linked with Check table
 
          LOOP AT gt_table_filds ASSIGNING FIELD-SYMBOL(<lfs_tab>) WHERE checktable IS NOT INITIAL. "#EC CI_NESTED
 
            "To fetch the Check table information
 
            ASSIGN COMPONENT <lfs_tab>-fieldname OF STRUCTURE <lfs_dn1> TO  <fs_val>.
 
            IF <fs_val> IS ASSIGNED AND <fs_val> IS NOT INITIAL.
 
              IF <lfs_tab>-fieldname EQ 'MATNR'.
 
                CALL FUNCTION 'CONVERSION_EXIT_MATN1_INPUT'     "#EC CI_SUBRC
                   EXPORTING
                     input        = <fs_val>
                   IMPORTING
                     output       = <fs_val>
                   EXCEPTIONS
                     length_error = 1
                     OTHERS       = 2.
 
                IF sy-subrc <> 0.
 
                  MESSAGE ID sy-msgid TYPE sy-msgty NUMBER sy-msgno
 
                          WITH sy-msgv1 sy-msgv2 sy-msgv3 sy-msgv4.
 
                ENDIF.
 
              ELSE.
                 <fs_val> = |{ <fs_val> ALPHA = IN }|.
 
              ENDIF.
 
              CALL FUNCTION 'DDIF_FIELDINFO_GET'  "#EC CI_SUBRC
                 EXPORTING
                   tabname        = <lfs_tab>-checktable
                 TABLES
                   dfies_tab      = gt_table_filds1
                 EXCEPTIONS
                   not_found      = 1
                   internal_error = 2
                   OTHERS         = 3.
 
              IF sy-subrc IS NOT INITIAL.
 
                MESSAGE ID sy-msgid TYPE sy-msgty NUMBER sy-msgno
 
                        WITH sy-msgv1 sy-msgv2 sy-msgv3 sy-msgv4.
 
              ENDIF.
 
              READ TABLE gt_table_filds1  INTO DATA(ls_fields1) WITH KEY domname = <lfs_tab>-domname."Reading the Check table field
 
              IF sy-subrc EQ 0.
 
                lv_field = ls_fields1-fieldname.   "check table field
 
                lv_table = <lfs_tab>-checktable.  "check table name
 
                "Comparing each Excel data with the check table value if it is exist or not
 
                lv_clause = |{ lv_field }| && | = | && |'| && |{ <fs_val> }| && |'| .
 
                SELECT SINGLE (lv_field)  FROM (lv_table) INTO ls_tab WHERE (lv_clause). "#EC CI_SUBRC
 
                CLEAR :ls_tab.
 
                IF sy-subrc NE 0.
 
                  gs_msg-message = TEXT-010. "text-010(Data has not updated)
 
                  gs_msg-row = lv_count.
 
                  gs_msg-lights = 1.
 
                  APPEND gs_msg TO gt_msg.
 
                  CLEAR:gs_msg.
 
                  lv_flag = abap_true.
 
                ENDIF.
 
              ENDIF.
 
            ENDIF.
 
          ENDLOOP.
 
*        IF sy-subrc NE 0.
 
          IF lv_flag EQ abap_false.
 
            gs_msg-message = TEXT-011 .
 
            gs_msg-row = lv_count.
 
            gs_msg-lights = 3.
 
            APPEND gs_msg TO gt_msg.
 
            CLEAR:gs_msg.
 
            APPEND <lfs_dn1> TO <fs_dyn1>.
 
            CLEAR: <lfs_dn1>.
 
          ENDIF.
 
        ENDLOOP.
//Locking the table.
        IF <fs_dyn1> IS ASSIGNED AND <fs_dyn1> IS NOT INITIAL.
 
          CALL FUNCTION 'ENQUEUE_E_TABLE'
             EXPORTING
               mode_rstable   = 'E'
               tabname        = p_tab
             EXCEPTIONS
               foreign_lock   = 1
               system_failure = 2
               OTHERS         = 3.
 
          IF sy-subrc EQ 0.
 
            MODIFY (p_tab) FROM TABLE <fs_dyn1>.
 
            IF sy-subrc EQ 0.
 
              COMMIT WORK.
 
            ELSE.
 
              ROLLBACK WORK.
 
            ENDIF.
 
            CALL FUNCTION 'DEQUEUE_E_TABLE'
               EXPORTING
                 mode_rstable = 'E'
                 tabname      = p_tab.
 
          ENDIF.
 
                                                          "#EC CI_SUBRC
 
        ENDIF.
 
*Data is updated succussfully without any interruption then display's below message
 
        IF gt_msg IS INITIAL.
 
          MESSAGE TEXT-008 TYPE 'S'.  "text-008(Data is Updated succussfully)
 
        ENDIF.
 
        IF gt_msg IS NOT INITIAL.
 
          TRY.
 
              cl_salv_table=>factory(
 
                IMPORTING
 
                  r_salv_table = go_salv                       " Basis Class Simple ALV Tables
 
                CHANGING
 
                  t_table      = gt_msg
 
              ).
 
            ##NO_HANDLER            CATCH cx_salv_msg INTO gv_msg.
 
          ENDTRY.
 
          TRY.
 
              lo_cols = go_salv->get_columns( ).
 
              lo_cols->set_exception_column(
 
                value = 'LIGHTS' ).
 
            ##NO_HANDLER  CATCH cx_salv_data_error.
 
          ENDTRY.
 
          TRY.
 
              lo_column = lo_cols->get_column( columnname = 'ROW' ).
 
              lo_column->set_long_text( ‘Row' ).
 
              lo_column->set_medium_text( 'Row’ ).
 
              lo_column->set_short_text( ‘Row’ ).
 
              lo_column->set_output_length( 6 ).
 

              lo_column = lo_cols->get_column( columnname = 'MESSAGE' ).
 
              lo_column->set_long_text( ‘Message’ ).
 
              lo_column->set_medium_text( ‘Message’ ).
 
              lo_column->set_short_text( ‘Message' ).
 
              lo_column->set_output_length( 15 ).
 
            ##NO_HANDLER           CATCH cx_salv_not_found.
 
          ENDTRY.
 

**Displaying the Error mesage in ouput
 
          go_salv->display( ).
 
          CLEAR:gt_msg.
 
        ENDIF.
 
      ELSE.
 
        MESSAGE e242(zotc_r1_message) WITH p_tab.
 
      ENDIF.
 
    ENDIF.
 

  ENDMETHOD.
 
  METHOD pop_up_dialogue.
 
    DATA:lv_rc   TYPE i,
 
         lt_file TYPE TABLE OF file_table.
 
    TRY.
 
        gv_wtitle = ‘Please Select the file'.
 
        cl_gui_frontend_services=>file_open_dialog(       "#EC CI_SUBRC
 
          EXPORTING
 
            window_title            = gv_wtitle                 " Title Of File Open Dialog
 
            default_filename        = gv_format                 " Default File Name
 
            file_filter             = cl_gui_frontend_services=>filetype_excel                 " File Extension Filter String
 
          CHANGING
 
            file_table              = lt_file                 " Table Holding Selected Files
 
            rc                      = lv_rc              " Return Code, Number of Files or -1 If Error Occurred
 
          EXCEPTIONS
 
            file_open_dialog_failed = 1                " "Open File" dialog failed
 
            cntl_error              = 2                " Control error
 
            error_no_gui            = 3                " No GUI available
 
            not_supported_by_gui    = 4                " GUI does not support this
 
            OTHERS                  = 5
 
        ).
 

        IF sy-subrc <> 0.
 
          CASE sy-subrc.
 
            WHEN 1.
 
              MESSAGE ‘file_openDialog_failed’ TYPE 'E'.
 
            WHEN 2.
 
              MESSAGE ‘Control_Error' TYPE 'E'.
 
            WHEN 3.
 
              MESSAGE ‘Error_no_gui’ TYPE 'E'.
 
            WHEN 4.
 
              MESSAGE ‘Not supported by GUI’ TYPE 'E'.
 
            WHEN OTHERS.
 
              MESSAGE ‘Other issue’ TYPE 'E'.
 
          ENDCASE.
 
        ENDIF.
 
      CATCH cx_root INTO DATA(lx_error).
 
        MESSAGE lx_error->get_text( ) TYPE 'E'.
 
    ENDTRY.
 


    IF lt_file IS NOT INITIAL.
 
      p_path = lt_file[ 1 ]-filename.
 
    ENDIF.
 
  ENDMETHOD.
 
  METHOD initialize.
 
    CLEAR: gs_msg, gt_msg, gv_wtitle       ,
 
     gv_format       ,
 
     gt_dyn_tab      ,
 
     gt_dyn_tab1     ,
 
     go_salv         ,
 
     gv_msg          ,
 
     gt_table_filds  ,
 
     gt_table_filds1 ,
 
     gs_dyn_tab    ,
 
     gv_auth_result.
 
  ENDMETHOD.
 
ENDCLASS.

So ,The output Screen will be as below 
Screenshots / Walkthrough

Export Mode (SE16N)

Enter a valid custom table name
Select Export → Runs SE16N for the table


select.png

Download the Table Data

Download data as Excel from SE16N and fill in the template
Downloading SE16N to Local system.png

Import Mode

Select Import, provide the Excel path
The report validates each entry and updates records

Example:

  • Mismatch in fields shows error in SALV

  • Valid data gets inserted, shown in success message table


Selection_screen.png

If there is mismatch between the table fields and excel fields we will get some validation error or else the data will be inserted & the output will be showed as below.


Sucuess_full_update_output.png

 

Important Notes

  • This report is built to work only with custom transparent tables (Z-tables)

  • Validation is driven by check tables defined in the Data Dictionary

  • DDIF_FIELDINFO_GET is used to fetch metadata dynamically


Conclusion

This utility provides a robust, flexible, and reusable solution for Excel-based data uploads and downloads involving custom Z-tables. By validating data against check tables and dynamically creating data structures, the tool ensures that only clean, consistent data is written to the database.

Such a tool not only simplifies end-user data entry but also reduces manual effort and errors significantly.



2 Comments
Jelena_Perfiljeva
Active Contributor

My learned friend, please take a look at ABAP2XLSX: https://github.com/abap2xlsx/abap2xlsx

It's been around for over a decade. 

Discoverer
Explorer
0 Kudos

Hi @Jelena_Perfiljeva 

Thank you for your feedback.

The scenario covered in this blog differs slightly. While we do use a standard class for reading Excel data, the key focus here is on validating the entries against check tables based on the values entered in the Excel file. The validation logic dynamically checks whether the referenced entries exist in the corresponding check tables before allowing the data update.

You can see this validation logic implemented starting from line 199 and line 306 in the code.

Appreciate your time in reviewing the blog, and happy to hear your further thoughts.