Tuesday, December 22, 2009

WebDynpro: Transfer data between screens

If you want to capture data in one screen and then displaying it or use that data in the next screen then the following way can be applied. We have a simple example where we take customer number and description and then display it on the next screen.

image

This is done without writing any code. We create a context in the component controller and then map this context to the two screens. So the data gets captured from the first screen in the context and then gets referred in the second screen.

image

In the first screen the input fields refer to its local context and in the second screen the output field refer to its local context respectively but since they are mapped to the same component controller context they have access to the same data.

If you are getting the error ‘The lead selection has not been set’ when testing, make sure that you have ‘Cardinality’ set to 1:1 and ‘Initialization Lead Selection’ property checked for the context.

image

When you use the context for referring them on the screen as masking variable that is required.

Monday, December 14, 2009

Utility: Find similar strings using Levenshtein distance

This posting is basically to show the Levenshtein distance implementation in ABAP. This implementation was created to find if there is already a similar name of a given name. For example if you are searching for ‘John’ then ‘Johnny’ could also be presented in the search.

The Levenshtein distance gives the difference of characters between two strings. So in the case of ‘John’ and ‘Johnny’ the distance would be 2. The implementation is done using a class-method. The method accepts string1 and string2 and returns the distance. The program calling the method can then decided if the distance is acceptable or not.

image

METHOD get_levenshtein_distance.
  DATA lt_matrix TYPE REF TO data.
  DATA lst_matrix TYPE REF TO data.
  DATA l_str_len1 TYPE i.
  DATA l_str_len1_tmp TYPE i.
  DATA l_str_len2 TYPE i.
  DATA l_str_len2_tmp TYPE i.
  DATA l_count1 TYPE i.
  DATA l_count2 TYPE i.
  DATA l_i TYPE i.
  DATA l_j TYPE i.
  DATA l_i_1 TYPE i.
  DATA l_j_1 TYPE i.
  DATA l_field_value TYPE i.
  DATA lo_cl_abap_datadescr.
  DATA l_col_name TYPE string.
  DATA l_n_index(3) TYPE n.
  DATA lt_abap_component_tab TYPE abap_component_tab.
  DATA lst_abap_component TYPE abap_componentdescr.
  DATA lo_abap_datadescr TYPE REF TO cl_abap_datadescr.
  DATA lo_abap_structdescr TYPE REF TO cl_abap_structdescr.
  DATA lo_abap_tabledescr TYPE REF TO cl_abap_tabledescr.
  DATA lt_number TYPE TABLE OF i.
  FIELD-SYMBOLS <lt_matrix> TYPE table.
  FIELD-SYMBOLS <lst_matrix> TYPE data.
  FIELD-SYMBOLS <l_field> TYPE data.
  FIELD-SYMBOLS <l_field2> TYPE data.
* Create data type of number
  lo_abap_datadescr ?= cl_abap_datadescr=>describe_by_data( 1 ).
* Get the string lengths
  l_str_len1 = STRLEN( i_string1 ).
  l_str_len2 = STRLEN( i_string2 ).
* Create (l_str_len2 + 1) number of columns
  l_str_len2_tmp = l_str_len2 + 1.
  DO l_str_len2_tmp TIMES.
    l_n_index = sy-index.
    CONCATENATE 'COL' l_n_index INTO l_col_name.
    lst_abap_component-name = l_col_name.
    lst_abap_component-type = lo_abap_datadescr.
    APPEND lst_abap_component TO lt_abap_component_tab.
  ENDDO.
  lo_abap_structdescr = cl_abap_structdescr=>create( p_components = lt_abap_component_tab ).
  lo_abap_tabledescr = cl_abap_tabledescr=>create( p_line_type = lo_abap_structdescr ).
  CREATE DATA lt_matrix TYPE HANDLE lo_abap_tabledescr.
  ASSIGN lt_matrix->* TO <lt_matrix>.
  CREATE DATA lst_matrix TYPE HANDLE lo_abap_structdescr.
  ASSIGN lst_matrix->* TO <lst_matrix>.
* Initialise first row
  WHILE sy-subrc IS INITIAL.
    ASSIGN COMPONENT sy-index OF STRUCTURE <lst_matrix> TO <l_field>.
    IF sy-subrc IS NOT INITIAL.
      EXIT.
    ENDIF.
    <l_field> = sy-index - 1.
  ENDWHILE.
  APPEND <lst_matrix> TO <lt_matrix>.
* Create (l_str_len1 + 1) number of rows
* First row is already created
  DO l_str_len1 TIMES.
    CLEAR <lst_matrix>.
    ASSIGN COMPONENT 1 OF STRUCTURE <lst_matrix> TO <l_field>.
    <l_field> = sy-index.
    APPEND <lst_matrix> TO <lt_matrix>.
  ENDDO.
  l_j = 2. " Column
  DO l_str_len2 TIMES.
    CLEAR l_count1.
    l_i = 2. " Row
    DO l_str_len1 TIMES.
* i - 1
      l_i_1 = l_i - 1.
* j - 1
      l_j_1 = l_j - 1.
* Get d[i, j]
      READ TABLE <lt_matrix> INDEX l_i ASSIGNING <lst_matrix>.
      ASSIGN COMPONENT l_j OF STRUCTURE <lst_matrix> TO <l_field2>.
      IF i_string1+l_count1(1) = i_string2+l_count2(1).
* Get d[i-1, j-1]
        READ TABLE <lt_matrix> INDEX l_i_1 ASSIGNING <lst_matrix>.
        ASSIGN COMPONENT l_j_1 OF STRUCTURE <lst_matrix> TO <l_field>.
*         d[i, j] := d[i-1, j-1]
        <l_field2> = <l_field>.
      ELSE.
        CLEAR lt_number[].
*                      d[i-1, j] + 1,  // deletion
        UNASSIGN <l_field>.
        READ TABLE <lt_matrix> INDEX l_i_1 ASSIGNING <lst_matrix>.
        ASSIGN COMPONENT l_j OF STRUCTURE <lst_matrix> TO <l_field>.
        l_field_value = <l_field> + 1.
        APPEND l_field_value TO lt_number.
*                      d[i, j-1] + 1,  // insertion
        UNASSIGN <l_field>.
        READ TABLE <lt_matrix> INDEX l_i ASSIGNING <lst_matrix>.
        ASSIGN COMPONENT l_j_1 OF STRUCTURE <lst_matrix> TO <l_field>.
        l_field_value = <l_field> + 1.
        APPEND l_field_value TO lt_number.
*                      d[i-1, j-1] + 1 // substitution
        UNASSIGN <l_field>.
        READ TABLE <lt_matrix> INDEX l_i_1 ASSIGNING <lst_matrix>.
        ASSIGN COMPONENT l_j_1 OF STRUCTURE <lst_matrix> TO <l_field>.
        l_field_value = <l_field> + 1.
        APPEND l_field_value TO lt_number.
* Get the minimum
        UNASSIGN <l_field>.
        SORT lt_number.
        READ TABLE lt_number INDEX 1 ASSIGNING <l_field>.
*         d[i, j] := minimum
        <l_field2> = <l_field>.
      ENDIF.
      l_i = l_i + 1.
      l_count1 = l_count1 + 1.
    ENDDO.
    l_j = l_j + 1.
    l_count2 = l_count2 + 1.
  ENDDO.
* Bottom right of the array lt_matrix will have the answer
  l_str_len1_tmp = l_str_len1 + 1.
  l_str_len2_tmp = l_str_len2 + 1.
  READ TABLE <lt_matrix> INDEX l_str_len1_tmp ASSIGNING <lst_matrix>.
  ASSIGN COMPONENT l_str_len2_tmp OF STRUCTURE <lst_matrix> TO <l_field>.
  r_distance = <l_field>.
ENDMETHOD.

Wednesday, October 14, 2009

Update to Upload program

Have modified the upload program to make it similar to the recent download program.

*&---------------------------------------------------------------------*
*& Report  ZUPLOAD
*&
*&---------------------------------------------------------------------*
*&
*&
*&---------------------------------------------------------------------*
REPORT ZUPLOAD MESSAGE-ID zx_message.
*----------------------------------------------------------------------*
*       CLASS upload DEFINITION
*----------------------------------------------------------------------*
*
*----------------------------------------------------------------------*
CLASS upload DEFINITION.
  PUBLIC SECTION.
    CLASS-METHODS open_file.
    METHODS start.
    METHODS end.
    METHODS free_log.
    METHODS display_output.
    METHODS display_log.
  PRIVATE SECTION.
    CONSTANTS c_max_ranges TYPE i VALUE 100.
    CONSTANTS c_seperator TYPE abap_char1 VALUE cl_abap_char_utilities=>horizontal_tab.
    DATA upload_file_tab TYPE REF TO data.
    DATA upload_file_row TYPE REF TO data.
    DATA t_tab_file TYPE TABLE OF string.
    DATA o_struc_type TYPE REF TO cl_abap_structdescr.
    DATA s_log TYPE bal_s_log.
    DATA log_handle         TYPE balloghndl.
    DATA t_log_handle       TYPE bal_t_logh.
    DATA o_ccont_display TYPE REF TO cl_gui_custom_container.
    DATA o_ccont_log TYPE REF TO cl_gui_custom_container.
    DATA dummy.
    DATA t_filecontent TYPE string_table.
    METHODS convert_file2struc IMPORTING i_header TYPE boolean
                                         i_separator TYPE c.
    METHODS create_table_and_row.
    METHODS read_file IMPORTING i_file TYPE string.
    METHODS open_log.
    METHODS add_msg.
ENDCLASS.                    "upload DEFINITION
DATA o_upload TYPE REF TO upload.
DATA s_t001 TYPE t001.
*--------------------------------------------------------------------*
* File Location
SELECTION-SCREEN BEGIN OF BLOCK file WITH FRAME TITLE text-f01.
PARAMETERS:
  p_file   TYPE rlgrap-filename OBLIGATORY,
  p_header AS CHECKBOX DEFAULT abap_true.
SELECTION-SCREEN END OF BLOCK file.
*--------------------------------------------------------------------*
* Material selection
SELECTION-SCREEN BEGIN OF BLOCK bukrs WITH FRAME TITLE text-001.
*--- company options
SELECT-OPTIONS s_bukrs FOR s_t001-bukrs.
SELECTION-SCREEN END OF BLOCK bukrs.
*--------------------------------------------------------------------*
* Defaults
SELECTION-SCREEN BEGIN OF BLOCK intr WITH FRAME TITLE text-t03.
PARAMETERS:
  p_struc TYPE strukname DEFAULT 'T001'.
SELECTION-SCREEN END OF BLOCK intr.
*--------------------------------------------------------------------*
* F4
AT SELECTION-SCREEN ON VALUE-REQUEST FOR p_file.
  upload=>open_file( ).
*--------------------------------------------------------------------*
START-OF-SELECTION.
  CREATE OBJECT o_upload.
  o_upload->start( ).
*--------------------------------------------------------------------*
END-OF-SELECTION.
  o_upload->end( ).
  CALL SCREEN 0100.
*----------------------------------------------------------------------*
*       CLASS upload IMPLEMENTATION
*----------------------------------------------------------------------*
*
*----------------------------------------------------------------------*
CLASS upload IMPLEMENTATION.
  METHOD open_file.
    DATA:
        l_t_file_table TYPE TABLE OF file_table,
        l_s_file_table TYPE file_table.
    DATA l_subrc TYPE i.
    CALL METHOD cl_gui_frontend_services=>file_open_dialog
      CHANGING
        file_table              = l_t_file_table
        rc                      = l_subrc
      EXCEPTIONS
        file_open_dialog_failed = 1
        cntl_error              = 2
        error_no_gui            = 3
        not_supported_by_gui    = 4
        OTHERS                  = 5.
    IF sy-subrc <> 0.
      MESSAGE ID sy-msgid TYPE sy-msgty NUMBER sy-msgno
                 WITH sy-msgv1 sy-msgv2 sy-msgv3 sy-msgv4.
    ENDIF.
    READ TABLE l_t_file_table INTO l_s_file_table INDEX 1.
    p_file = l_s_file_table-filename.
  ENDMETHOD.                    "open_file
  METHOD start.
    DATA l_file TYPE string.
    l_file = p_file.
    open_log( ).
    create_table_and_row( ).
    read_file( i_file = l_file ).
    convert_file2struc( i_header    = p_header
                        i_separator = c_seperator ).
  ENDMETHOD.                    "start
  METHOD create_table_and_row.
    DATA l_type TYPE string.
    DATA lo_type TYPE REF TO cl_abap_typedescr.
    DATA lo_tabletype TYPE REF TO cl_abap_tabledescr.
    l_type = p_struc.
    CALL METHOD cl_abap_structdescr=>describe_by_name
      EXPORTING
        p_name         = l_type
      RECEIVING
        p_descr_ref    = lo_type
      EXCEPTIONS
        type_not_found = 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.
    o_struc_type ?= lo_type.
    CREATE DATA upload_file_row TYPE HANDLE o_struc_type.
    TRY.
        CALL METHOD cl_abap_tabledescr=>create
          EXPORTING
            p_line_type  = o_struc_type
*    P_TABLE_KIND = TABLEKIND_STD
*    P_UNIQUE     = ABAP_FALSE
*    P_KEY        =
*    P_KEY_KIND   = KEYDEFKIND_DEFAULT
          RECEIVING
            p_result     = lo_tabletype
            .
      CATCH cx_sy_table_creation .
    ENDTRY.
    CREATE DATA upload_file_tab TYPE HANDLE lo_tabletype.
* Structure mapped successfully
    MESSAGE s181 INTO dummy.
    add_msg( ).
  ENDMETHOD.                    "create_table_and_row
  METHOD convert_file2struc.
    DATA:
      l_struc TYPE REF TO data,
      l_o_datadescr TYPE REF TO cl_abap_datadescr,
      l_o_tabledescr TYPE REF TO cl_abap_tabledescr,
      l_t_fields TYPE string_table,
      l_s_fields TYPE string.
    FIELD-SYMBOLS:
      <l_filecontent> TYPE ANY,
      <l_field> TYPE ANY,
      <l_row> TYPE ANY,
      <l_struc_content> TYPE table.
    ASSIGN upload_file_row->* TO <l_row>.
    ASSIGN upload_file_tab->* TO <l_struc_content>.
    LOOP AT t_filecontent ASSIGNING <l_filecontent>.
      IF i_separator IS INITIAL. " File is same as structure
        <l_row> = <l_filecontent>.
      ELSE.
*---split based on the separator
        SPLIT <l_filecontent> AT i_separator INTO TABLE l_t_fields.
        LOOP AT l_t_fields INTO l_s_fields.
          ASSIGN COMPONENT sy-tabix OF STRUCTURE <l_row> TO <l_field>.
          <l_field> = l_s_fields.
        ENDLOOP.
      ENDIF.
      APPEND <l_row> TO <l_struc_content>.
    ENDLOOP.
  ENDMETHOD.                    "convert_file2struc
  METHOD end.
  ENDMETHOD.                    "end
  METHOD open_log.
* create a log
    s_log-extnumber  = 'Application Log in Subscreen'(001).
    CALL FUNCTION 'BAL_LOG_CREATE'
      EXPORTING
        i_s_log      = s_log
      IMPORTING
        e_log_handle = log_handle
      EXCEPTIONS
        OTHERS       = 1.
    IF sy-subrc <> 0.
      MESSAGE ID sy-msgid TYPE sy-msgty NUMBER sy-msgno
               WITH sy-msgv1 sy-msgv2 sy-msgv3 sy-msgv4.
    ENDIF.
    INSERT log_handle INTO TABLE t_log_handle.
* Log opened successfully
    MESSAGE s180 INTO dummy.
    add_msg( ).
  ENDMETHOD.                    "open_log
  METHOD add_msg.
    DATA:
      l_s_msg   TYPE bal_s_msg.
* define data of message for Application Log
    l_s_msg-msgty     = sy-msgty.
    l_s_msg-msgid     = sy-msgid.
    l_s_msg-msgno     = sy-msgno.
    l_s_msg-msgv1     = sy-msgv1.
    l_s_msg-msgv2     = sy-msgv2.
    l_s_msg-msgv3     = sy-msgv3.
    l_s_msg-msgv4     = sy-msgv4.
* add this message to log file
    CALL FUNCTION 'BAL_LOG_MSG_ADD'
      EXPORTING
        i_log_handle = log_handle
        i_s_msg      = l_s_msg
      EXCEPTIONS
        OTHERS       = 1.
    IF sy-subrc <> 0.
      MESSAGE ID sy-msgid TYPE sy-msgty NUMBER sy-msgno
              WITH sy-msgv1 sy-msgv2 sy-msgv3 sy-msgv4.
    ENDIF.
  ENDMETHOD.                    "add_msg
  METHOD free_log.
* free all data (this must NOT be forgotten !)
    CALL FUNCTION 'BAL_DSP_OUTPUT_FREE'
      EXCEPTIONS
        OTHERS = 1.
    IF sy-subrc <> 0.
      MESSAGE ID sy-msgid TYPE sy-msgty NUMBER sy-msgno
               WITH sy-msgv1 sy-msgv2 sy-msgv3 sy-msgv4.
    ENDIF.
  ENDMETHOD.                    "free_log
  METHOD display_output.
    DATA:
      l_r_table   TYPE REF TO cl_salv_table,
*      l_r_event_handler TYPE REF TO l_cl_event_handler,
      l_r_events TYPE REF TO cl_salv_events_table,
      l_t_salv_t_int4_column TYPE salv_t_int4_column,
      l_s_salv_t_int4_column TYPE LINE OF salv_t_int4_column.
    FIELD-SYMBOLS <l_upload_file_tab> TYPE table.
    ASSIGN upload_file_tab->* TO <l_upload_file_tab>.
*--------------------------------------------------------------------*
    IF o_ccont_display IS INITIAL.
* Create holder container
      CREATE OBJECT o_ccont_display
        EXPORTING
*    PARENT                      =
          container_name              = 'CCONTROL_0101'
*    STYLE                       =
*    LIFETIME                    = lifetime_default
*    REPID                       =
*    DYNNR                       =
*    NO_AUTODEF_PROGID_DYNNR     =
        EXCEPTIONS
          cntl_error                  = 1
          cntl_system_error           = 2
          create_error                = 3
          lifetime_error              = 4
          lifetime_dynpro_dynpro_link = 5
          OTHERS                      = 6
          .
      IF sy-subrc <> 0.
        MESSAGE ID sy-msgid TYPE sy-msgty NUMBER sy-msgno
                   WITH sy-msgv1 sy-msgv2 sy-msgv3 sy-msgv4.
      ENDIF.
*--------------------------------------------------------------------*
* Create AVL table
      TRY.
          cl_salv_table=>factory(
            EXPORTING
              r_container = o_ccont_display
            IMPORTING
              r_salv_table = l_r_table
            CHANGING
              t_table      = <l_upload_file_tab> ).
        CATCH cx_salv_msg.                              "#EC NO_HANDLER
      ENDTRY.
*--------------------------------------------------------------------*
* Functions
      DATA:
        lr_functions TYPE REF TO cl_salv_functions_list.
      lr_functions = l_r_table->get_functions( ).
*  lr_functions->set_aggregation_total( abap_true ).
      lr_functions->set_default( abap_true ).
* Columns
      DATA:
        lr_columns TYPE REF TO cl_salv_columns_table,
        lr_column TYPE REF TO cl_salv_column.
      lr_columns = l_r_table->get_columns( ).
      lr_columns->set_optimize( abap_true ).
      TRY.
          CALL METHOD lr_columns->set_exception_column
            EXPORTING
              value     = 'TRAFFIC_LIGHT'
              group     = '2'
              condensed = if_salv_c_bool_sap=>false.
        CATCH cx_salv_data_error .
      ENDTRY.
      TRY.
          CALL METHOD lr_columns->set_cell_type_column
            EXPORTING
              value = 'CELL_TYPE'.
        CATCH cx_salv_data_error .
      ENDTRY.
      l_r_table->display( ).
    ENDIF.
  ENDMETHOD.                    "get_e1maktm
  METHOD display_log.
    DATA:
      l_r_table   TYPE REF TO cl_salv_table,
*      l_r_event_handler TYPE REF TO l_cl_event_handler,
      l_r_events TYPE REF TO cl_salv_events_table,
      l_t_salv_t_int4_column TYPE salv_t_int4_column,
      l_s_salv_t_int4_column TYPE LINE OF salv_t_int4_column.
    DATA ls_display_profile  TYPE bal_s_prof.
    DATA l_control_handle     TYPE balcnthndl.
    FIELD-SYMBOLS <l_upload_file_tab> TYPE table.
*--------------------------------------------------------------------*
* Create holder container
    IF o_ccont_log IS INITIAL.
      CREATE OBJECT o_ccont_log
        EXPORTING
*    PARENT                      =
          container_name              = 'CCONTROL_0102'
*    STYLE                       =
*    LIFETIME                    = lifetime_default
*    REPID                       =
*    DYNNR                       =
*    NO_AUTODEF_PROGID_DYNNR     =
        EXCEPTIONS
          cntl_error                  = 1
          cntl_system_error           = 2
          create_error                = 3
          lifetime_error              = 4
          lifetime_dynpro_dynpro_link = 5
          OTHERS                      = 6
          .
      IF sy-subrc <> 0.
        MESSAGE ID sy-msgid TYPE sy-msgty NUMBER sy-msgno
                   WITH sy-msgv1 sy-msgv2 sy-msgv3 sy-msgv4.
      ENDIF.
*       get a display profile which describes how to display messages
      CALL FUNCTION 'BAL_DSP_PROFILE_NO_TREE_GET'
        IMPORTING
          e_s_display_profile = ls_display_profile.
      ls_display_profile-no_toolbar = 'X'.
*--------------------------------------------------------------------*
*       create control to display data
      CALL FUNCTION 'BAL_CNTL_CREATE'
        EXPORTING
          i_container         = o_ccont_log
          i_s_display_profile = ls_display_profile
          i_t_log_handle      = t_log_handle
        IMPORTING
          e_control_handle    = l_control_handle
        EXCEPTIONS
          OTHERS              = 1.
      IF sy-subrc <> 0.
        MESSAGE ID sy-msgid TYPE sy-msgty NUMBER sy-msgno
                WITH sy-msgv1 sy-msgv2 sy-msgv3 sy-msgv4.
      ENDIF.
    ENDIF.
  ENDMETHOD.                    "display_log
  METHOD read_file.
    CALL METHOD cl_gui_frontend_services=>gui_upload
      EXPORTING
        filename                = i_file
*        has_field_separator     = 'X'
      CHANGING
        data_tab                = t_filecontent
      EXCEPTIONS
        file_open_error         = 1
        file_read_error         = 2
        no_batch                = 3
        gui_refuse_filetransfer = 4
        invalid_type            = 5
        no_authority            = 6
        unknown_error           = 7
        bad_data_format         = 8
        header_not_allowed      = 9
        separator_not_allowed   = 10
        header_too_long         = 11
        unknown_dp_error        = 12
        access_denied           = 13
        dp_out_of_memory        = 14
        disk_full               = 15
        dp_timeout              = 16
        not_supported_by_gui    = 17
        error_no_gui            = 18
        OTHERS                  = 19.
    IF sy-subrc <> 0.
      MESSAGE ID sy-msgid TYPE sy-msgty NUMBER sy-msgno
                 WITH sy-msgv1 sy-msgv2 sy-msgv3 sy-msgv4.
    ENDIF.
  ENDMETHOD.                    "read_file
ENDCLASS.                    "upload IMPLEMENTATION
*&---------------------------------------------------------------------*
*&      Module  status_0100  OUTPUT
*&---------------------------------------------------------------------*
*       text
*----------------------------------------------------------------------*
MODULE status_0100 OUTPUT.
* set status and title
  SET PF-STATUS 'STATUS'.
  SET TITLEBAR 'TITLE'.
* flush data to frontend
  CALL METHOD cl_gui_cfw=>flush.
ENDMODULE.                 " status_0100  OUTPUT
*&SPWIZARD: FUNCTION CODES FOR TABSTRIP 'TAB_STRIP'
CONSTANTS: BEGIN OF c_tab_strip,
             tab1 LIKE sy-ucomm VALUE 'TAB_STRIP_FC1',
             tab2 LIKE sy-ucomm VALUE 'TAB_STRIP_FC2',
           END OF c_tab_strip.
*&SPWIZARD: DATA FOR TABSTRIP 'TAB_STRIP'
CONTROLS:  tab_strip TYPE TABSTRIP.
DATA:      BEGIN OF g_tab_strip,
             subscreen   LIKE sy-dynnr,
             prog        LIKE sy-repid VALUE 'Zupload',
             pressed_tab LIKE sy-ucomm VALUE c_tab_strip-tab1,
           END OF g_tab_strip.
DATA:      ok_code LIKE sy-ucomm.
*&SPWIZARD: OUTPUT MODULE FOR TS 'TAB_STRIP'. DO NOT CHANGE THIS LINE!
*&SPWIZARD: SETS ACTIVE TAB
MODULE tab_strip_active_tab_set OUTPUT.
  tab_strip-activetab = g_tab_strip-pressed_tab.
  CASE g_tab_strip-pressed_tab.
    WHEN c_tab_strip-tab1.
      g_tab_strip-subscreen = '0101'.
    WHEN c_tab_strip-tab2.
      g_tab_strip-subscreen = '0102'.
    WHEN OTHERS.
*&SPWIZARD:      DO NOTHING
  ENDCASE.
ENDMODULE.                    "TAB_STRIP_ACTIVE_TAB_SET OUTPUT
*&SPWIZARD: INPUT MODULE FOR TS 'TAB_STRIP'. DO NOT CHANGE THIS LINE!
*&SPWIZARD: GETS ACTIVE TAB
MODULE tab_strip_active_tab_get INPUT.
  ok_code = sy-ucomm.
  CASE ok_code.
    WHEN c_tab_strip-tab1.
      g_tab_strip-pressed_tab = c_tab_strip-tab1.
    WHEN c_tab_strip-tab2.
      g_tab_strip-pressed_tab = c_tab_strip-tab2.
    WHEN OTHERS.
*&SPWIZARD:      DO NOTHING
  ENDCASE.
ENDMODULE.                    "TAB_STRIP_ACTIVE_TAB_GET INPUT
*&---------------------------------------------------------------------*
*&      Module  user_command_0100  INPUT
*&---------------------------------------------------------------------*
*       text
*----------------------------------------------------------------------*
MODULE user_command_0100 INPUT.
  CASE ok_code.
*   leave this screen
    WHEN 'ABBR' OR 'BACK' OR 'BEEN'.
      LEAVE TO SCREEN 0.
    WHEN OTHERS.
  ENDCASE.
* Delete log profile
  o_upload->free_log( ).
* call dispatch method of control framwork
  CALL METHOD cl_gui_cfw=>dispatch.
ENDMODULE.                 " user_command_0100  INPUT
*&---------------------------------------------------------------------*
*&      Module  display_output  OUTPUT
*&---------------------------------------------------------------------*
*       text
*----------------------------------------------------------------------*
MODULE display_output OUTPUT.
  o_upload->display_output( ).
ENDMODULE.                 " display_output  OUTPUT
*&---------------------------------------------------------------------*
*&      Module  display_log  OUTPUT
*&---------------------------------------------------------------------*
*       text
*----------------------------------------------------------------------*
MODULE display_log OUTPUT.
  o_upload->display_log( ).
ENDMODULE.                 " display_log  OUTPUT