How to show multiple dynamic tables on a single screen?

right now im displaying alv for singlr attribute of dimension.
eg for dimension PRODUCT attribute PROFITCENTER im displaying in alv when user executes it.
but the requirement is that multiple attributes can be there so multiple tables is to be displayed on a single screen.
User basically wants to see data of all attributes. if there are 10 attributes hee wants to see 10 tables as every attribute has a different table.
what i have achieved is below in snapshots. only one attribute table PRODUCT im able to display. since i believe multiple headers cant be displyed in alv so even if i display multiple dynamically populated tables on a single screen then it will be fine.
i have also ADDED my code below: ZMDREPORT
this report is for SAP BPC.
*& Report  ZMDREPORT
REPORT  zmdreport.
TABLES /1cpmb/bfrdp3rp.
DATA: gw_datatbl TYPE tabname,
      gw_datatbl1 TYPE tabname,
      gw_descrptbl TYPE tabname,
      gw_attribute TYPE tabname.
DATA:
BEGIN OF gw_attr,
  appset_id      TYPE uja_dim_attr-appset_id,
  dimension      TYPE uja_dim_attr-dimension,
  tech_name      TYPE uja_dim_attr-tech_name,
  attribute_name TYPE uja_dim_attr-attribute_name,
  caption        TYPE uja_dim_attr-caption,
END OF gw_attr,
gt_attr          LIKE TABLE OF gw_attr.
DATA: gt_slis_fcat1 TYPE slis_t_fieldcat_alv,
      gw_slis_fcat1 LIKE LINE OF gt_slis_fcat1.
DATA : gt_except TYPE TABLE OF zbpcbt007,
       gw_except LIKE LINE OF gt_except,
          gt_except_t TYPE TABLE OF zbpcbt007,
          gt_attrib TYPE TABLE OF tabname,
          gw_attrib LIKE LINE OF gt_attrib.
DATA: gr_r_ref   TYPE  REF TO data.
DATA:BEGIN OF gw_mdr,
     appset_id     TYPE  uj_appset_id,
     dimension     TYPE uj_dim_name,
     reasoncd      TYPE zmdreason,
     refdimension  TYPE uj_dim_name,
     attrib        TYPE uj_attr_name,
     END OF gw_mdr,
     gt_mdr1 LIKE TABLE OF gw_mdr,
     gt_mdr2 LIKE TABLE OF gw_mdr,
     gt_mdtable1 TYPE zbpctt_attr,
     gt_mdtable2 TYPE zbpctt_attr,
     gw_mdtable2 LIKE LINE OF gt_mdtable2,
     gt_mdtable3 TYPE zbpctt_attr,
     gt_mdtable4 TYPE zbpctt_attr,
     gw_mdtable4 LIKE LINE OF gt_mdtable4,
      BEGIN OF gw_finalattr,
       dim(32)      TYPE c,
       END OF gw_finalattr,
       gt_finalattr LIKE TABLE OF gw_finalattr,
       gt_tab1 LIKE TABLE OF gw_finalattr,
       gw_tab1 LIKE LINE OF gt_tab1,
       gt_tab2 LIKE TABLE OF gw_finalattr,
       gw_tab2 LIKE LINE OF gt_tab2.
FIELD-SYMBOLS: <gfs_tab1>  TYPE STANDARD TABLE.
FIELD-SYMBOLS: <gfs_tab2>  TYPE STANDARD TABLE,
               <gfs_tab3>  TYPE STANDARD TABLE,
               <gfs_tab4>  TYPE STANDARD TABLE.
FIELD-SYMBOLS:<gfs_attr> TYPE any,
                          <gfs_field3> TYPE any,
                          <gfs_field4> TYPE any.
DATA: gw_sortcond TYPE string.
FIELD-SYMBOLS: <gfs_t_final>  TYPE STANDARD TABLE.
FIELD-SYMBOLS: <gfs_final>  TYPE any.
FIELD-SYMBOLS: <gfs_data> TYPE any .
SELECTION-SCREEN BEGIN OF BLOCK b1 WITH FRAME TITLE text-001.
PARAMETERS: p_env TYPE uja_dimension-appset_id OBLIGATORY.
PARAMETERS: p_dim TYPE uja_dimension-dimension OBLIGATORY.
SELECT-OPTIONS: s_member FOR /1cpmb/bfrdp3rp-mbr_name .
PARAMETERS: p_hir TYPE /1cpmb/bfrdp3rp-/cpmb/hir.
PARAMETERS:p_attr TYPE uj_attr_name MODIF ID m1.
SELECTION-SCREEN END OF BLOCK b1.
SELECTION-SCREEN BEGIN OF BLOCK b2 WITH FRAME TITLE text-002.
PARAMETERS: p_radio1 RADIOBUTTON GROUP g1 USER-COMMAND abc DEFAULT 'X',
            p_radio2 RADIOBUTTON GROUP g1.
SELECTION-SCREEN END OF BLOCK b2.
SELECTION-SCREEN BEGIN OF BLOCK b3 WITH FRAME TITLE text-003.
PARAMETERS: p_reason  TYPE zbpcbt007-reasoncd MODIF ID m1.
SELECTION-SCREEN END OF BLOCK b3.
*********************************************************************alv
DATA  :gt_fcat    TYPE lvc_t_fcat.
DATA: gw_ok_code TYPE sy-ucomm,
      gw_okcode  TYPE sy-ucomm.
DATA: go_custom_container TYPE REF TO cl_gui_custom_container,
      gw_g_container  TYPE scrfname VALUE 'CC1',
      go_grid1        TYPE REF TO cl_gui_alv_grid.
DATA:BEGIN OF gw_table,
      dimension TYPE uja_dimension-dimension,
     END OF gw_table,
     gt_tab LIKE TABLE OF gw_table ,
     BEGIN OF gw_member,
     mbr_name TYPE uj_dim_member,
       END OF gw_member ,
       gt_member LIKE TABLE OF gw_member,
       BEGIN OF gw_hir ,
       hir TYPE /1cpmb/bfrdp3rp-/cpmb/hir,
       END OF gw_hir,
       gt_hir LIKE TABLE OF gw_hir.
DATA:gt_slis_fcat2 TYPE slis_t_fieldcat_alv,
          gw_slis_fcat2 LIKE LINE OF gt_slis_fcat2 .
DATA:  lr_data    TYPE REF TO data.
DATA  :gt_fcat1   TYPE lvc_t_fcat,
       gt_fcat2   TYPE lvc_t_fcat,
       gt_fcat3   TYPE lvc_t_fcat,
       gt_fcat2_t TYPE lvc_t_fcat,
       gw_fcat    LIKE LINE OF gt_fcat2,
       gw_fcat3    LIKE LINE OF gt_fcat3.
DATA:  gt_fcat3_t LIKE gt_fcat3.
DATA:  gw_desc TYPE uj_desc.
DATA : gw_string  TYPE string,
       gw_str     TYPE string.
DATA:  gw_len TYPE string,
      BEGIN OF gw_refdim,
        dimension TYPE uja_dimension-dimension,
      END OF gw_refdim,
      gt_refdim LIKE TABLE OF gw_refdim,
      gt_refdim_t LIKE TABLE OF gw_refdim,
      BEGIN OF gw_refdata,
        data_table TYPE tabname,
         desc_table TYPE tabname,
      END OF gw_refdata,
      gt_refdata LIKE TABLE OF gw_refdata,
      BEGIN OF gw_techattr,
        tech_name TYPE uja_dim_attr-tech_name,
        END OF gw_techattr,
        gt_techattr LIKE TABLE OF gw_techattr,
        gw_cond TYPE string.
DATA:gw_hircond TYPE string.
DATA: gt_dynpread TYPE TABLE OF dynpread,
      gw_dynpread LIKE LINE OF gt_dynpread,
      gw_dynpread2 LIKE LINE OF gt_dynpread,
      gw_dim TYPE string,
      gw_env TYPE string.
FIELD-SYMBOLS: <gfs_w_tab1>      TYPE any,
               <gfs_w_tab2>      TYPE any,
               <gfs_w_tab3>      TYPE any,
               <gfs_field>       TYPE any,
               <gfs_field2>       TYPE any,
               <gfs_field_final> TYPE any,
               <gfs_s_fcat>      TYPE lvc_s_fcat,
               <gfs_s_fcat2>     TYPE lvc_s_fcat,
               <gfs_s_fcat3>     TYPE lvc_s_fcat
AT SELECTION-SCREEN ON VALUE-REQUEST FOR p_dim.
  REFRESH gt_dynpread.
  gw_dynpread-fieldname = 'P_ENV'.
  APPEND gw_dynpread TO gt_dynpread.
  CALL FUNCTION 'DYNP_VALUES_READ'
    EXPORTING
      dyname                         = sy-repid
      dynumb                         = sy-dynnr
*     TRANSLATE_TO_UPPER             = ' '
*     REQUEST                        = ' '
*     PERFORM_CONVERSION_EXITS       = ' '
*     PERFORM_INPUT_CONVERSION       = ' '
*     DETERMINE_LOOP_INDEX           = ' '
*     START_SEARCH_IN_CURRENT_SCREEN = 'X'
*     start_search_in_main_screen    = ' '
*     START_SEARCH_IN_STACKED_SCREEN = ' '
*     START_SEARCH_ON_SCR_STACKPOS   = ' '
*     SEARCH_OWN_SUBSCREENS_FIRST    = ' '
*     SEARCHPATH_OF_SUBSCREEN_AREAS  = ' '
    TABLES
      dynpfields                     = gt_dynpread
    EXCEPTIONS
      invalid_abapworkarea           = 1
      invalid_dynprofield            = 2
      invalid_dynproname             = 3
      invalid_dynpronummer           = 4
      invalid_request                = 5
      no_fielddescription            = 6
      invalid_parameter              = 7
      undefind_error                 = 8
      double_conversion              = 9
      stepl_not_found                = 10
      OTHERS                         = 11.
  IF sy-subrc EQ 0.
    READ TABLE gt_dynpread INTO gw_dynpread INDEX 1.
    IF sy-subrc EQ 0.
      TRY .
          REFRESH gt_tab.
          SELECT dimension
          FROM uja_dimension CLIENT SPECIFIED
          INTO TABLE gt_tab
          WHERE mandt EQ sy-mandt
          AND   appset_id EQ gw_dynpread-fieldvalue.
          IF sy-subrc EQ 0.
            SORT gt_tab BY dimension.
            DELETE ADJACENT DUPLICATES FROM gt_tab COMPARING dimension.
            IF gt_tab IS NOT INITIAL.
              CALL FUNCTION 'F4IF_INT_TABLE_VALUE_REQUEST' "#EC CI_SUBRC
                 EXPORTING
*           DDIC_STRUCTURE         = ''
                retfield               = 'DIMENSION'
*           PVALKEY                = ' '
                dynpprog               = sy-repid
                dynpnr                 = sy-dynnr
                dynprofield            = 'P_DIM'(004)
*           STEPL                  = 0
*           WINDOW_TITLE           =
*           VALUE                  = ' '
                value_org              = 'S'
*           MULTIPLE_CHOICE        = ' '
*           display                = ''
*           CALLBACK_PROGRAM       = ' '
*           CALLBACK_FORM          = ' '
*           CALLBACK_METHOD        =
*           MARK_TAB               =
*           IMPORTING
*           USER_RESET             =
                TABLES
                value_tab              = gt_tab
*           FIELD_TAB              =
*           RETURN_TAB             =
*           DYNPFLD_MAPPING        =
                EXCEPTIONS
                parameter_error        = 1
                no_values_found        = 2
                 OTHERS                 = 3
              IF sy-subrc NE 0.
              ENDIF.
            ENDIF.
          ENDIF.
        CATCH cx_root.
      ENDTRY.
    ENDIF.
  ENDIF.
AT SELECTION-SCREEN ON VALUE-REQUEST FOR s_member-low.
  REFRESH gt_dynpread.
  gw_dynpread-fieldname = 'P_ENV'.
  APPEND gw_dynpread TO gt_dynpread.
  gw_dynpread-fieldname = 'P_DIM'.
  APPEND gw_dynpread TO gt_dynpread.
  CALL FUNCTION 'DYNP_VALUES_READ'
    EXPORTING
      dyname                         = sy-repid
      dynumb                         = sy-dynnr
*     TRANSLATE_TO_UPPER             = ' '
*     REQUEST                        = ' '
*     PERFORM_CONVERSION_EXITS       = ' '
*     PERFORM_INPUT_CONVERSION       = ' '
*     DETERMINE_LOOP_INDEX           = ' '
*     START_SEARCH_IN_CURRENT_SCREEN = 'X'
*     start_search_in_main_screen    = ' '
*     START_SEARCH_IN_STACKED_SCREEN = ' '
*     START_SEARCH_ON_SCR_STACKPOS   = ' '
*     SEARCH_OWN_SUBSCREENS_FIRST    = ' '
*     SEARCHPATH_OF_SUBSCREEN_AREAS  = ' '
    TABLES
      dynpfields                     = gt_dynpread
    EXCEPTIONS
      invalid_abapworkarea           = 1
      invalid_dynprofield            = 2
      invalid_dynproname             = 3
      invalid_dynpronummer           = 4
      invalid_request                = 5
      no_fielddescription            = 6
      invalid_parameter              = 7
      undefind_error                 = 8
      double_conversion              = 9
      stepl_not_found                = 10
      OTHERS                         = 11.
  IF sy-subrc EQ 0.
    SORT gt_dynpread BY fieldname.
    DELETE ADJACENT DUPLICATES FROM gt_dynpread COMPARING fieldname.
    IF gt_dynpread IS NOT INITIAL.
      LOOP AT gt_dynpread INTO gw_dynpread.
        IF gw_dynpread-fieldname EQ 'P_ENV'.
          gw_env = gw_dynpread-fieldvalue.
        ELSEIF gw_dynpread-fieldname EQ 'P_DIM'.
          gw_dim = gw_dynpread-fieldvalue.
        ENDIF.
      ENDLOOP.
      IF sy-subrc EQ 0.
        CLEAR: gw_datatbl1, gt_member.
        SELECT SINGLE data_table
        INTO (gw_datatbl1)
        FROM uja_dimension CLIENT SPECIFIED
        WHERE mandt EQ sy-mandt
        AND   appset_id EQ gw_env
        AND   dimension EQ gw_dim.
        IF sy-subrc EQ 0.
          TRY .
              REFRESH gt_member.
              SELECT mbr_name
              INTO TABLE gt_member
              FROM (gw_datatbl1) CLIENT SPECIFIED
              WHERE mandt EQ sy-mandt .
              IF sy-subrc EQ 0.
                CALL FUNCTION 'F4IF_INT_TABLE_VALUE_REQUEST'
                  EXPORTING
*           DDIC_STRUCTURE         = ' '
          retfield               = 'MBR_NAME'
*        PVALKEY                = ' '
          dynpprog               = sy-repid
          dynpnr                 = sy-dynnr
          dynprofield            = 'S_MEMBER'
*        STEPL                  = 0
*        WINDOW_TITLE           =
*        VALUE                  = ' '
          value_org              = 'S'
*        MULTIPLE_CHOICE        = ' '
*        DISPLAY                = ' '
          callback_program       = sy-repid
          callback_form          = 'F4CALLBACK'
*        CALLBACK_METHOD        =
*        MARK_TAB               =
*        IMPORTING
*        USER_RESET             =
          TABLES
          value_tab              = gt_member
*        FIELD_TAB              =
*        RETURN_TAB             =
*        DYNPFLD_MAPPING        =
          EXCEPTIONS
          parameter_error        = 1
             no_values_found        = 2
             OTHERS                 = 3
                IF sy-subrc <> 0.
* Implement suitable error handling here
                ENDIF.
              ENDIF.
            CATCH cx_root.
          ENDTRY.
        ENDIF.
      ENDIF.
    ENDIF.
  ENDIF.
AT SELECTION-SCREEN ON VALUE-REQUEST FOR s_member-high.
  REFRESH gt_dynpread.
  gw_dynpread-fieldname = 'P_ENV'.
  APPEND gw_dynpread TO gt_dynpread.
  gw_dynpread-fieldname = 'P_DIM'.
  APPEND gw_dynpread TO gt_dynpread.
  CALL FUNCTION 'DYNP_VALUES_READ'
    EXPORTING
      dyname                         = sy-repid
      dynumb                         = sy-dynnr
*     TRANSLATE_TO_UPPER             = ' '
*     REQUEST                        = ' '
*     PERFORM_CONVERSION_EXITS       = ' '
*     PERFORM_INPUT_CONVERSION       = ' '
*     DETERMINE_LOOP_INDEX           = ' '
*     START_SEARCH_IN_CURRENT_SCREEN = 'X'
*     start_search_in_main_screen    = ' '
*     START_SEARCH_IN_STACKED_SCREEN = ' '
*     START_SEARCH_ON_SCR_STACKPOS   = ' '
*     SEARCH_OWN_SUBSCREENS_FIRST    = ' '
*     SEARCHPATH_OF_SUBSCREEN_AREAS  = ' '
    TABLES
      dynpfields                     = gt_dynpread
    EXCEPTIONS
      invalid_abapworkarea           = 1
      invalid_dynprofield            = 2
      invalid_dynproname             = 3
      invalid_dynpronummer           = 4
      invalid_request                = 5
      no_fielddescription            = 6
      invalid_parameter              = 7
      undefind_error                 = 8
      double_conversion              = 9
      stepl_not_found                = 10
      OTHERS                         = 11.
  IF sy-subrc EQ 0.
    SORT gt_dynpread BY fieldname.
    DELETE ADJACENT DUPLICATES FROM gt_dynpread COMPARING fieldname.
    IF gt_dynpread IS NOT INITIAL.
      LOOP AT gt_dynpread INTO gw_dynpread.
        IF gw_dynpread-fieldname EQ 'P_ENV'.
          gw_env = gw_dynpread-fieldvalue.
        ELSEIF gw_dynpread-fieldname EQ 'P_DIM'.
          gw_dim = gw_dynpread-fieldvalue.
        ENDIF.
      ENDLOOP.
      IF sy-subrc EQ 0.
        CLEAR: gw_datatbl1.
        SELECT SINGLE data_table
        INTO (gw_datatbl1)
        FROM uja_dimension CLIENT SPECIFIED
        WHERE mandt EQ sy-mandt
        AND   appset_id EQ gw_env
        AND   dimension EQ gw_dim.
        IF sy-subrc EQ 0.
          TRY .
              REFRESH gt_member.
              SELECT mbr_name
              INTO TABLE gt_member
              FROM (gw_datatbl1) CLIENT SPECIFIED
              WHERE mandt EQ sy-mandt.
              IF sy-subrc EQ 0.
                CALL FUNCTION 'F4IF_INT_TABLE_VALUE_REQUEST'
                  EXPORTING
*          DDIC_STRUCTURE         = ' '
            retfield               = 'MBR_NAME'
*          PVALKEY                = ' '
            dynpprog               = sy-repid
            dynpnr                 = sy-dynnr
            dynprofield            = 'S_MEMBER'
*          STEPL                  = 0
*          WINDOW_TITLE           =
*          VALUE                  = ' '
            value_org              = 'S'
*          MULTIPLE_CHOICE        = ' '
*          DISPLAY                = ' '
            callback_program       = sy-repid
            callback_form          = 'F4CALLBACK'
*          CALLBACK_METHOD        =
*          MARK_TAB               =
*          IMPORTING
*          USER_RESET             =
            TABLES
            value_tab              = gt_member
*          FIELD_TAB              =
*          RETURN_TAB             =
*          DYNPFLD_MAPPING        =
            EXCEPTIONS
            parameter_error        = 1
            no_values_found        = 2
            OTHERS                 = 3
                IF sy-subrc <> 0.
* Implement suitable error handling here
                ENDIF.
              ENDIF.
            CATCH cx_root.
          ENDTRY.
        ENDIF.
      ENDIF.
    ENDIF.
  ENDIF.
*&      Form  F4CALLBACK
*       text
*      -->RECORD_TAB   text
*      -->SHLP         text
*      -->CALLCONTROL  text
FORM f4callback TABLES record_tab STRUCTURE seahlpres
                CHANGING shlp TYPE shlp_descr
                         callcontrol TYPE ddshf4ctrl.
  callcontrol-no_maxdisp = ''.
ENDFORM.                    "F4CALLBACK
AT SELECTION-SCREEN ON VALUE-REQUEST FOR p_hir.
  REFRESH gt_dynpread.
  CLEAR gw_dynpread.
  gw_dynpread-fieldname = 'P_ENV'.
  APPEND gw_dynpread TO gt_dynpread.
  gw_dynpread-fieldname = 'P_DIM'.
  APPEND gw_dynpread TO gt_dynpread.
  CALL FUNCTION 'DYNP_VALUES_READ'
    EXPORTING
      dyname                         = sy-repid
      dynumb                         = sy-dynnr
*     TRANSLATE_TO_UPPER             = ' '
*     REQUEST                        = ' '
*     PERFORM_CONVERSION_EXITS       = ' '
*     PERFORM_INPUT_CONVERSION       = ' '
*     DETERMINE_LOOP_INDEX           = ' '
*     START_SEARCH_IN_CURRENT_SCREEN = 'X'
*     start_search_in_main_screen    = ' '
*     START_SEARCH_IN_STACKED_SCREEN = ' '
*     START_SEARCH_ON_SCR_STACKPOS   = ' '
*     SEARCH_OWN_SUBSCREENS_FIRST    = ' '
*     SEARCHPATH_OF_SUBSCREEN_AREAS  = ' '
    TABLES
      dynpfields                     = gt_dynpread
    EXCEPTIONS
      invalid_abapworkarea           = 1
      invalid_dynprofield            = 2
      invalid_dynproname             = 3
      invalid_dynpronummer           = 4
      invalid_request                = 5
      no_fielddescription            = 6
      invalid_parameter              = 7
      undefind_error                 = 8
      double_conversion              = 9
      stepl_not_found                = 10
      OTHERS                         = 11.
  IF sy-subrc EQ 0.
    SORT gt_dynpread BY fieldname.
    DELETE ADJACENT DUPLICATES FROM gt_dynpread COMPARING fieldname.
    LOOP AT gt_dynpread INTO gw_dynpread.
      IF gw_dynpread-fieldname EQ 'P_ENV'.
        gw_env = gw_dynpread-fieldvalue.
      ELSEIF gw_dynpread-fieldname EQ 'P_DIM'.
        gw_dim = gw_dynpread-fieldvalue.
      ENDIF.
    ENDLOOP.
    IF sy-subrc EQ 0.
      CLEAR: gw_datatbl1.
      SELECT SINGLE data_table
      INTO (gw_datatbl1)
      FROM uja_dimension CLIENT SPECIFIED
      WHERE mandt EQ sy-mandt
      AND   appset_id EQ gw_env
      AND   dimension EQ gw_dim.
      IF sy-subrc EQ 0.
        REFRESH gt_member.
        TRY .
            SELECT /cpmb/hir
            INTO TABLE gt_hir
            FROM (gw_datatbl1) CLIENT SPECIFIED
            WHERE mandt EQ sy-mandt.
            IF sy-subrc EQ 0.
              SORT gt_hir BY hir.
              DELETE ADJACENT DUPLICATES FROM gt_hir COMPARING hir.
              IF gt_hir IS NOT INITIAL.
                CALL FUNCTION 'F4IF_INT_TABLE_VALUE_REQUEST'
                               EXPORTING
*                   DDIC_STRUCTURE         = ' '
                                 retfield               = '/CPMB/HIR'
*                   PVALKEY                = ' '
                                dynpprog               = sy-repid
                                dynpnr                 = sy-dynnr
                                dynprofield            = 'P_HIR'
*                   STEPL                  = 0
*                   WINDOW_TITLE           =
*                   VALUE                  = ' '
                                value_org              = 'S'
*                   MULTIPLE_CHOICE        = ' '
*                   DISPLAY                = ' '
*                   CALLBACK_PROGRAM       = ' '
*                   CALLBACK_FORM          = ' '
*                   CALLBACK_METHOD        =
*                   MARK_TAB               =
*                 IMPORTING
*                   USER_RESET             =
                               TABLES
                                 value_tab              = gt_hir
*                   FIELD_TAB              =
*                   RETURN_TAB             =
*                   DYNPFLD_MAPPING        =
                              EXCEPTIONS
                                parameter_error        = 1
                                no_values_found        = 2
                                OTHERS                 = 3
                IF sy-subrc <> 0.
* Implement suitable error handling here
                ENDIF.
              ENDIF.
            ENDIF.
          CATCH cx_root.
        ENDTRY.
      ENDIF.
    ENDIF.
  ENDIF.
*       CLASS lcl_main DEFINITION
CLASS lcl_main DEFINITION.
  PUBLIC SECTION.
    CLASS-METHODS:
             create_alv1,
             create_alv2,
             create_alv3,
             create_fieldcatalog,
             create_dynamicalv,
             merge_tables,
             show_alv1
ENDCLASS.                    "lcl_main DEFINITION
*       CLASS lcl_main IMPLEMENTATION
CLASS lcl_main IMPLEMENTATION.
  METHOD create_fieldcatalog.
    CALL FUNCTION 'LVC_FIELDCATALOG_MERGE'                "#EC CI_SUBRC
                 EXPORTING
                   i_structure_name       = gw_datatbl
                 CHANGING
                   ct_fieldcat            = gt_fcat1
                 EXCEPTIONS
                   inconsistent_interface = 1
                   program_error          = 2
                   OTHERS                 = 3.
    IF sy-subrc <> 0.
* Implement suitable error handling here
    ENDIF.
    CALL FUNCTION 'LVC_FIELDCATALOG_MERGE'                "#EC CI_SUBRC
      EXPORTING
        i_structure_name       = gw_descrptbl
      CHANGING
        ct_fieldcat            = gt_fcat2
      EXCEPTIONS
        inconsistent_interface = 1
        program_error          = 2
        OTHERS                 = 3.
    IF sy-subrc <> 0.
* Implement suitable error handling here
    ENDIF.
  ENDMETHOD.                    "create_fieldcatalog
  METHOD create_dynamicalv.
*    DATA: lr_data    TYPE REF TO data.
    CLEAR lr_data.
    CALL METHOD cl_alv_table_create=>create_dynamic_table
                                                          "#EC CI_SUBRC
                 EXPORTING
*               i_style_table             =
                   it_fieldcatalog           = gt_fcat2
*               i_length_in_byte          =
                 IMPORTING
                   ep_table                  = lr_data
*               e_style_fname             =
                 EXCEPTIONS
                   generate_subpool_dir_full = 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.
  ENDMETHOD.                    "create_dynamicalv
  METHOD merge_tables.
    SORT gt_fcat2 BY col_pos.
    ASSIGN lr_data->* TO <gfs_t_final>.
    LOOP AT <gfs_tab1> ASSIGNING <gfs_w_tab1>.
      APPEND INITIAL LINE TO <gfs_t_final> ASSIGNING <gfs_final>.
      LOOP AT gt_fcat2 ASSIGNING <gfs_s_fcat>.           "#EC CI_NESTED
        ASSIGN COMPONENT <gfs_s_fcat>-fieldname OF STRUCTURE
        <gfs_w_tab1> TO <gfs_field>.
        IF sy-subrc EQ 0 AND <gfs_field> IS ASSIGNED.
          ASSIGN COMPONENT <gfs_s_fcat>-fieldname OF STRUCTURE
          <gfs_final> TO <gfs_field_final>.
          IF sy-subrc EQ 0 AND <gfs_field_final> IS ASSIGNED.
            <gfs_field_final> = <gfs_field>.
          ENDIF.
*** Creating dynamic where clause for the key fields
          IF <gfs_s_fcat>-key = 'X'.
            READ TABLE gt_fcat2_t ASSIGNING <gfs_s_fcat2>
            WITH KEY
            key       = abap_true
            fieldname = <gfs_s_fcat>-fieldname.
            IF sy-subrc EQ 0.
              IF gw_string IS INITIAL.
*Putting value into quotes
                CONCATENATE `'` <gfs_field> `'` INTO gw_str.
*Concatenating first field into string
                CONCATENATE <gfs_s_fcat>-fieldname '=' gw_str
                INTO gw_string SEPARATED BY space.
                CLEAR gw_str.
              ELSE.
*Concatenating rest all key fields
                CONCATENATE `'` <gfs_field> `'` INTO gw_str.
                CONCATENATE gw_string 'AND' <gfs_s_fcat>-fieldname
                '=' gw_str INTO gw_string SEPARATED BY space.
                CLEAR gw_str.
              ENDIF.
            ENDIF.
*** End of Creation
          ENDIF.
        ENDIF.
      ENDLOOP.
      IF NOT gw_string IS INITIAL.
*Concatenating sy-langu (-> always present)
        CONCATENATE gw_string 'AND LANGU = SY-LANGU'
        INTO gw_string SEPARATED BY space.
      ENDIF.
*** Filling Description field based on dynamically created where clause
      LOOP AT <gfs_tab2> ASSIGNING <gfs_w_tab2> WHERE (gw_string).
                                                         "#EC CI_NESTED
        ASSIGN COMPONENT 'TXTLG' OF STRUCTURE <gfs_w_tab2>
        TO <gfs_field>.
        IF sy-subrc EQ 0 AND <gfs_field> IS ASSIGNED.
          ASSIGN COMPONENT 'TXTLG' OF STRUCTURE <gfs_final>
          TO <gfs_field_final>.
          IF sy-subrc EQ 0 AND <gfs_field_final> IS ASSIGNED.
            <gfs_field_final> = <gfs_field>.
          ENDIF.
        ENDIF.
      ENDLOOP.
      CLEAR gw_string.
    ENDLOOP.
  ENDMETHOD.                    "merge_tables
  METHOD create_alv3.
    CREATE DATA gr_r_ref TYPE TABLE OF (gw_datatbl).
    ASSIGN gr_r_ref->* TO <gfs_tab1>.
    SELECT *
    INTO TABLE <gfs_tab1>
    FROM (gw_datatbl) CLIENT SPECIFIED
    WHERE mandt EQ sy-mandt
    AND   mbr_name IN s_member
    AND   /cpmb/calc EQ 'N'.
    IF sy-subrc EQ 0.
      IF p_hir IS NOT INITIAL.
        CLEAR gw_hircond.
        CONCATENATE '/CPMB/HIR' 'NE' 'P_HIR' INTO gw_hircond
        SEPARATED BY space.
        DELETE <gfs_tab1> WHERE (gw_hircond).
      ENDIF.
      CLEAR: gr_r_ref.
      CREATE DATA gr_r_ref TYPE TABLE OF (gw_descrptbl).
      ASSIGN gr_r_ref->* TO <gfs_tab2>.
      SELECT *
      FROM (gw_descrptbl) CLIENT SPECIFIED
      INTO TABLE <gfs_tab2>
      WHERE mandt EQ sy-mandt
      AND langu EQ sy-langu.
      IF sy-subrc EQ 0.
        READ TABLE gt_refdata INTO gw_refdata INDEX 1.
        IF sy-subrc EQ 0.
          CLEAR gr_r_ref.
          CREATE DATA gr_r_ref TYPE TABLE OF (gw_refdata-data_table).
          ASSIGN gr_r_ref->* TO <gfs_tab3>.
          SELECT *
          INTO TABLE <gfs_tab3>
          FROM (gw_refdata-data_table) CLIENT SPECIFIED
          WHERE mandt EQ sy-mandt
          AND /cpmb/calc EQ 'N'.
          IF sy-subrc EQ 0.
            CLEAR gr_r_ref.
            CREATE DATA gr_r_ref TYPE TABLE OF (gw_refdata-desc_table).
            ASSIGN gr_r_ref->* TO <gfs_tab4>.
            SELECT *
            INTO TABLE <gfs_tab4>
            FROM (gw_refdata-desc_table) CLIENT SPECIFIED
            WHERE mandt EQ sy-mandt
            AND   langu EQ sy-langu.
            lcl_main=>create_fieldcatalog( ).
            gt_fcat2_t[] = gt_fcat2[].
            DELETE gt_fcat2 WHERE fieldname NE 'TXTLG'.
            APPEND LINES OF gt_fcat1 TO gt_fcat2.
            gw_len = lines( gt_fcat2 ).
            gw_len = gw_len + 1.
            gw_fcat-fieldname = 'TXTLG1'.
            gw_fcat-reptext   = 'Attribute Description'.
            gw_fcat-col_pos   = gw_len.
            gw_fcat-outputlen = 60.
            APPEND gw_fcat TO gt_fcat2.
            SORT gt_fcat2 BY fieldname.
            READ TABLE gt_techattr INTO gw_techattr INDEX 1.
            LOOP AT gt_fcat2 INTO gw_fcat.
              READ TABLE gt_attr INTO gw_attr
              WITH KEY tech_name = gw_fcat-fieldname.
              IF sy-subrc EQ 0.
                gw_fcat-reptext = gw_attr-caption.
              ENDIF.
              IF gw_fcat-fieldname = 'TXTLG'.
                gw_fcat-outputlen = 60.
              ENDIF.
              MODIFY gt_fcat2 FROM gw_fcat TRANSPORTING
              outputlen reptext .
              IF gw_fcat-fieldname NE 'MBR_NAME'
              AND gw_fcat-fieldname NE 'TXTLG'
                AND gw_fcat-fieldname NE 'TXTLG1'
              AND gw_fcat-fieldname NE gw_techattr-tech_name."gw_attrib.
                gw_fcat-no_out = 'X'.
                MODIFY gt_fcat2 FROM gw_fcat TRANSPORTING no_out.
              ENDIF.
            ENDLOOP.
            lcl_main=>create_dynamicalv( ).
            lcl_main=>merge_tables( ).
            CLEAR gw_cond.
            READ TABLE gt_techattr INTO gw_techattr INDEX 1.
*        CONCATENATE 'MBR_NAME =' '<Gfs_field>' INTO Gw_cond
*        SEPARATED BY space.
            TRANSLATE gw_techattr-tech_name TO UPPER CASE.
            CONCATENATE `'` gw_techattr-tech_name `'`
            '=' '<Gfs_field>' INTO gw_cond
            SEPARATED BY space.
            CHECK NOT <gfs_t_final> IS INITIAL.
            SORT <gfs_t_final> BY (gw_techattr-tech_name).
            LOOP AT <gfs_tab3> ASSIGNING <gfs_w_tab3>.
              ASSIGN COMPONENT 'MBR_NAME' OF STRUCTURE <gfs_w_tab3>
              TO <gfs_field>.
              IF sy-subrc EQ 0 AND <gfs_field> IS ASSIGNED.
                DELETE <gfs_t_final> WHERE (gw_cond).
              ENDIF.
              IF <gfs_t_final> IS INITIAL.
                EXIT.
              ENDIF.
            ENDLOOP.
*adding attribute description
            DATA gw_cond1 TYPE string.
            DATA gw_cond2 TYPE string.
            CLEAR gw_cond1.
           CONCATENATE `'` gw_techattr-tech_name `'` 'eq' '<gfs_field>'
           INTO gw_cond1 SEPARATED BY space.
            CLEAR gw_cond2.
            CONCATENATE 'TXTLG1' 'eq' 'SPACE'
            INTO gw_cond2 SEPARATED BY space.
            CLEAR gw_cond.
            CONCATENATE 'TXTLG' 'NE' 'SPACE' INTO gw_cond SEPARATED BY
            space.
            gw_sortcond = 'TXTLG'.
            SORT <gfs_tab4> BY (gw_sortcond).
            LOOP AT <gfs_t_final> ASSIGNING <gfs_final> WHERE
              (gw_cond2).
              ASSIGN COMPONENT gw_techattr-tech_name OF STRUCTURE
              <gfs_final> TO <gfs_field>.
              IF sy-subrc EQ 0 AND <gfs_field> IS ASSIGNED.
                ASSIGN COMPONENT 'TXTLG1' OF STRUCTURE
                <gfs_final> TO <gfs_field4>.
                IF sy-subrc EQ 0 AND <gfs_field4> IS ASSIGNED.
                  LOOP AT <gfs_tab4> ASSIGNING <gfs_attr>
                    WHERE (gw_cond).
                    ASSIGN COMPONENT 2 OF STRUCTURE <gfs_attr> TO
                    <gfs_field2>.
                    IF sy-subrc EQ 0 AND <gfs_field2> IS ASSIGNED.
                      ASSIGN COMPONENT 5 OF STRUCTURE <gfs_attr>
                      TO <gfs_field3>.
                      IF sy-subrc EQ 0 AND <gfs_field3> IS ASSIGNED.
                        IF <gfs_field> EQ <gfs_field2>.
                          <gfs_field4> = <gfs_field3>.
                          MODIFY <gfs_t_final> FROM <gfs_final>
                          TRANSPORTING ('TXTLG1') WHERE (gw_cond1).
                          EXIT.
                        ENDIF.
                      ENDIF.
                    ENDIF.
                  ENDLOOP.
                ENDIF.
              ENDIF.
            ENDLOOP.
*            LOOP AT <gfs_tab4> ASSIGNING <gfs_attr> WHERE (gw_cond) .
*              ASSIGN COMPONENT 2 OF STRUCTURE <gfs_attr> TO
*              <gfs_field2>.
*              IF sy-subrc EQ 0 AND <gfs_field2> IS ASSIGNED.
*                ASSIGN COMPONENT 5 OF STRUCTURE <gfs_attr> TO
*                              <gfs_field3>.
*                IF sy-subrc EQ 0 AND <gfs_field3> IS ASSIGNED.
*                  LOOP AT <gfs_t_final> ASSIGNING <gfs_final>
*                    WHERE (gw_cond2).
*                    ASSIGN COMPONENT gw_techattr-tech_name OF STRUCTURE
*                    <gfs_final> TO <gfs_field>.
*                    IF sy-subrc EQ 0 AND <gfs_field> IS ASSIGNED.
*                     ASSIGN COMPONENT 'TXTLG1' OF STRUCTURE <gfs_final>
*                     TO <gfs_field4>.
*                      IF sy-subrc EQ 0 AND <gfs_field4> IS ASSIGNED.
*                        IF <gfs_field> EQ <gfs_field2>.
*                          <gfs_field4> = <gfs_field3>.
*                          MODIFY <gfs_t_final> FROM <gfs_final>
*                          TRANSPORTING ('TXTLG1') WHERE (gw_cond1).
*                          EXIT.
*                        ENDIF.
*                      ENDIF.
*                    ENDIF.
*                  ENDLOOP.
*                ENDIF.
*              ENDIF.
*            ENDLOOP.
            IF <gfs_t_final> IS NOT INITIAL.
              CALL SCREEN 9000.
            ENDIF.
          ENDIF.
        ENDIF.
      ENDIF.
    ENDIF.
  ENDMETHOD.                    "create_alv3
  METHOD create_alv2.
    READ TABLE gt_techattr INTO gw_techattr INDEX 1.
    CONCATENATE gw_techattr-tech_name 'EQ' 'space' INTO gw_cond
    SEPARATED
   BY
    space.
    CREATE DATA gr_r_ref TYPE TABLE OF (gw_datatbl).
    ASSIGN gr_r_ref->* TO <gfs_tab1>.
    SELECT *
    INTO TABLE <gfs_tab1>
    FROM (gw_datatbl) CLIENT SPECIFIED
    WHERE mandt EQ sy-mandt
    AND mbr_name IN s_member
    AND   /cpmb/calc EQ 'N'
    AND (gw_cond).
    IF sy-subrc EQ 0.
      IF p_hir IS NOT INITIAL.
        CLEAR gw_hircond.
        CONCATENATE '/CPMB/HIR' 'NE' 'P_HIR' INTO gw_hircond
              SEPARATED BY space.
        DELETE <gfs_tab1> WHERE (gw_hircond).
      ENDIF.
      CLEAR: gr_r_ref.
      CREATE DATA gr_r_ref TYPE TABLE OF (gw_descrptbl).
      ASSIGN gr_r_ref->* TO <gfs_tab2>.
      SELECT *
       FROM (gw_descrptbl) CLIENT SPECIFIED
       INTO TABLE <gfs_tab2>
       WHERE mandt EQ sy-mandt
       AND langu EQ sy-langu.
      IF sy-subrc EQ 0.
        lcl_main=>create_fieldcatalog( ).
        gt_fcat2_t[] = gt_fcat2[].
        DELETE gt_fcat2 WHERE fieldname NE 'TXTLG'.
        APPEND LINES OF gt_fcat1 TO gt_fcat2.
        SORT gt_fcat2 BY fieldname.
        LOOP AT gt_fcat2 INTO gw_fcat.
          READ TABLE gt_attr INTO gw_attr WITH KEY
              tech_name = gw_fcat-fieldname.
          IF sy-subrc EQ 0.
            gw_fcat-reptext = gw_attr-caption.
          ENDIF.
          IF gw_fcat-fieldname = 'TXTLG'.
            gw_fcat-outputlen = 60.
          ENDIF.
          MODIFY gt_fcat2 FROM gw_fcat TRANSPORTING outputlen reptext.
*      READ TABLE gt_attrib INTO gw_attrib INDEX 1.
*      IF sy-subrc EQ 0.
          IF gw_fcat-fieldname NE 'MBR_NAME'
          AND gw_fcat-fieldname NE 'TXTLG'
          AND gw_fcat-fieldname NE gw_techattr-tech_name."gw_attrib.
            gw_fcat-no_out = 'X'.
            MODIFY gt_fcat2 FROM gw_fcat TRANSPORTING no_out.
          ENDIF.
*      ENDIF.
        ENDLOOP.
        lcl_main=>create_dynamicalv( ).
        lcl_main=>merge_tables( ).
        CHECK NOT <gfs_t_final> IS INITIAL.
        SORT <gfs_t_final> BY ('MBR_NAME').
        CALL SCREEN 9000.
      ENDIF.
    ENDIF.
  ENDMETHOD.                    "create_alv2
  METHOD create_alv1.
    CREATE DATA gr_r_ref TYPE TABLE OF (gw_datatbl).
    ASSIGN gr_r_ref->* TO <gfs_tab1>.
    SELECT *
    FROM (gw_datatbl) CLIENT SPECIFIED
    INTO TABLE <gfs_tab1>
    WHERE mandt EQ sy-mandt
    AND   mbr_name IN s_member.
    IF sy-subrc EQ 0.
      IF p_hir IS NOT INITIAL.
        CLEAR gw_hircond.
        CONCATENATE '/CPMB/HIR' 'NE' 'P_HIR'
         INTO gw_hircond SEPARATED BY
           space.
        DELETE <gfs_tab1> WHERE (gw_hircond).
      ENDIF.
      CLEAR: gr_r_ref.
      CREATE DATA gr_r_ref TYPE TABLE OF (gw_descrptbl).
      ASSIGN gr_r_ref->* TO <gfs_tab2>.
      SELECT *
       FROM (gw_descrptbl) CLIENT SPECIFIED
       INTO TABLE <gfs_tab2>
       WHERE mandt EQ sy-mandt
       AND langu EQ sy-langu.
      IF sy-subrc EQ 0.
        lcl_main=>create_fieldcatalog( ).
        SORT gt_fcat2 BY col_pos fieldname.
        gt_fcat2_t[] = gt_fcat2[].
        DELETE gt_fcat2 WHERE fieldname NE 'TXTLG'.
        APPEND LINES OF gt_fcat1 TO gt_fcat2.
        SORT gt_fcat2 BY fieldname.
        SORT gt_attr BY tech_name.
        LOOP AT gt_fcat2 INTO gw_fcat .
          IF gw_fcat-reptext IS INITIAL.
            READ TABLE gt_attr INTO gw_attr
           WITH KEY tech_name = gw_fcat-fieldname BINARY SEARCH.
            IF sy-subrc EQ 0.
              gw_fcat-reptext = gw_attr-caption.
            ELSE.
              gw_fcat-reptext = gw_fcat-fieldname.
            ENDIF.
          ENDIF.
          IF gw_fcat-fieldname EQ 'OBJVERS'.
            gw_fcat-no_out = 'X'.
          ELSEIF gw_fcat-fieldname EQ 'ROWFLAG'.
            gw_fcat-no_out = 'X'.
          ELSEIF gw_fcat-fieldname EQ 'MBR_NAME'.
            gw_fcat-no_out = 'X'.
          ELSEIF gw_fcat-fieldname EQ '/CPMB/CALC'.
            gw_fcat-no_out = 'X'.
          ELSEIF gw_fcat-fieldname EQ 'TXTLG'.
            gw_fcat-outputlen = 70.
          ELSEIF gw_fcat-fieldname EQ '/CPMB/HIR'.
            gw_fcat-outputlen = 20.
          ENDIF.
          MODIFY gt_fcat2 FROM gw_fcat
          TRANSPORTING reptext no_out outputlen.
        ENDLOOP.
        lcl_main=>create_dynamicalv( ).
        lcl_main=>merge_tables( ).
        CHECK NOT <gfs_t_final> IS INITIAL.
*        SORT <gfs_t_final> BY ('TXTLG').
        CALL SCREEN 9000.
      ENDIF.
    ENDIF.
  ENDMETHOD.                    "show_alv1
  METHOD show_alv1.
    IF go_custom_container IS INITIAL.
      CREATE OBJECT go_custom_container
        EXPORTING
*          parent                      =
          container_name              = gw_g_container
*          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 OBJECT go_grid1
       EXPORTING
*          i_shellstyle      = 0
*          i_lifetime        =
         i_parent          = go_custom_container
*         i_appl_events     = 'X'
*          i_parentdbg       =
*          i_applogparent    =
*          i_graphicsparent  =
*          i_name            =
*          i_fcat_complete   = SPACE
       EXCEPTIONS
         error_cntl_create = 1
         error_cntl_init   = 2
         error_cntl_link   = 3
         error_dp_create   = 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.
      CALL METHOD go_grid1->set_table_for_first_display   "#EC CI_SUBRC
*       EXPORTING
*         i_buffer_active               =
*         i_bypassing_buffer            =
*         i_consistency_check           =
*         i_structure_name              =
*          is_variant                    =
*          i_save                        = 'X'
**         i_default                     = 'X'
*          is_layout                     =
**         is_print                      =
**         it_special_groups             =
*          it_toolbar_excluding          =
*         it_hyperlink                  =
*         it_alv_graphics               =
*         it_except_qinfo               =
*         ir_salv_adapter               =
       CHANGING
         it_outtab                     = <gfs_t_final>
         it_fieldcatalog               = gt_fcat2
*         it_sort                       =
*         it_filter                     =
       EXCEPTIONS
         invalid_parameter_combination = 1
         program_error                 = 2
         too_many_lines                = 3
         OTHERS                        = 4.
      IF sy-subrc <> 0.
*     Implement suitable error handling here
      ENDIF.
    ENDIF.
  ENDMETHOD.                    "SHOW_alv1
ENDCLASS.                    "lcl_main IMPLEMENTATION
AT SELECTION-SCREEN OUTPUT.
  IF p_radio1 EQ 'X'.
    LOOP AT SCREEN.
      IF screen-group1 = 'M1'.
        screen-active = 0.
        MODIFY SCREEN.
      ENDIF.
*      IF screen-group1 = 'M'.
*        screen-active    = 0.
*        MODIFY SCREEN.
*      ENDIF.
    ENDLOOP.
  ENDIF.
*  IF p_radio2 EQ 'X'.
*    LOOP AT SCREEN.
*      IF p_reason EQ 30.
*        IF screen-group1 = 'M2'.
*          screen-active    = 0.
*          MODIFY SCREEN.
*        ENDIF.
*      ENDIF.
*    ENDLOOP.
*  ENDIF.
START-OF-SELECTION.
  IF p_radio1 EQ 'X'.
    SELECT SINGLE data_table desc_table
    INTO (gw_datatbl , gw_descrptbl)
    FROM uja_dimension CLIENT SPECIFIED
    WHERE mandt EQ sy-mandt
    AND   appset_id EQ p_env
    AND   dimension EQ p_dim.
    IF sy-subrc EQ 0.
      SELECT appset_id dimension tech_name attribute_name caption
      INTO TABLE gt_attr
      FROM uja_dim_attr CLIENT SPECIFIED
      WHERE mandt EQ sy-mandt
      AND   appset_id EQ p_env
      AND   dimension EQ p_dim.
      IF sy-subrc EQ 0.
        lcl_main=>create_alv1( ).
      ENDIF.
    ENDIF.
  ELSE.
    IF p_reason NE 30.
      SELECT *
      INTO TABLE gt_except
      FROM zbpcbt007 CLIENT SPECIFIED
      WHERE mandt EQ sy-mandt
      AND   appset_id EQ p_env
      AND   dimension EQ p_dim
      AND   reasoncd  EQ p_reason.
      IF sy-subrc EQ 0.
        SELECT SINGLE data_table desc_table
             INTO (gw_datatbl,gw_descrptbl)
             FROM uja_dimension CLIENT SPECIFIED
             WHERE mandt EQ sy-mandt
             AND   appset_id EQ p_env
             AND   dimension EQ p_dim.
        IF sy-subrc EQ 0.
          SELECT appset_id dimension tech_name attribute_name caption
          INTO TABLE gt_attr
          FROM uja_dim_attr CLIENT SPECIFIED
          WHERE mandt EQ sy-mandt
          AND   appset_id EQ p_env
          AND   dimension EQ p_dim.
          IF sy-subrc EQ 0.
            gt_except_t[] = gt_except[].
            SORT gt_except_t.
            DELETE ADJACENT DUPLICATES FROM gt_except_t.
            IF gt_except_t IS NOT INITIAL.
              SELECT tech_name
              INTO TABLE gt_techattr
              FROM uja_dim_attr CLIENT SPECIFIED
              FOR ALL ENTRIES IN gt_except_t
              WHERE mandt EQ sy-mandt
              AND   appset_id EQ p_env
              AND   dimension EQ p_dim
              AND   attribute_name EQ gt_except_t-attrib.
              IF sy-subrc EQ 0.
                lcl_main=>create_alv2( ).
              ENDIF.
            ENDIF.
          ENDIF.
        ENDIF.
      ENDIF.
    ELSEIF p_reason EQ 30.
      SELECT SINGLE data_table desc_table
      INTO (gw_datatbl,gw_descrptbl)
      FROM uja_dimension CLIENT SPECIFIED
      WHERE mandt EQ sy-mandt
      AND   appset_id EQ p_env
      AND   dimension EQ p_dim.
      IF sy-subrc EQ 0.
*        gt_except_t[] = gt_except[].
*        SORT gt_except_t BY attrib.
*        DELETE ADJACENT DUPLICATES FROM gt_except_t COMPARING attrib.
*        IF gt_except_t IS NOT INITIAL.
        SELECT refdimension
        INTO TABLE gt_refdim
        FROM zbpcbt009 CLIENT SPECIFIED
*          FOR ALL ENTRIES IN gt_except_t
        WHERE mandt EQ sy-mandt
        AND   appset_id EQ p_env
        AND   dimension EQ p_dim
        AND   attrib EQ p_attr."gt_except_t-attrib.
        IF sy-subrc EQ 0.
          gt_refdim_t[] = gt_refdim[].
          SORT gt_refdim_t BY dimension.
          DELETE ADJACENT DUPLICATES FROM gt_refdim_t COMPARING
          dimension.
          IF gt_refdim_t IS NOT INITIAL.
            SELECT data_table desc_table
                         INTO TABLE gt_refdata
                         FROM uja_dimension CLIENT SPECIFIED
                         FOR ALL ENTRIES IN gt_refdim_t
                         WHERE mandt EQ sy-mandt
                         AND   appset_id EQ p_env
                         AND   dimension EQ gt_refdim_t-dimension.
            IF sy-subrc EQ 0.
              SELECT appset_id dimension tech_name attribute_name
              caption
              INTO TABLE gt_attr
              FROM uja_dim_attr CLIENT SPECIFIED
              WHERE mandt EQ sy-mandt
              AND   appset_id EQ p_env
              AND   dimension EQ p_dim.
              IF sy-subrc EQ 0.
                SELECT  tech_name
                INTO TABLE gt_techattr
                FROM uja_dim_attr CLIENT SPECIFIED
*                  FOR ALL ENTRIES IN gt_except_t
                WHERE mandt EQ sy-mandt
                AND   appset_id EQ p_env
                AND   dimension EQ p_dim
                  AND   attribute_name EQ p_attr."gt_except_t-attrib.
                IF sy-subrc EQ 0.
                  REFRESH: gt_refdim_t.",gt_except_t.
                  lcl_main=>create_alv3( ).
                ENDIF.
              ENDIF.
            ENDIF.
          ENDIF.
        ENDIF.
      ENDIF.
*      ENDIF.
*      ENDIF.
    ENDIF.
  ENDIF.
*&      Module  SHOW_ALV1  OUTPUT
*&-------

Yes you can, although you need to do it slightly differently, depending on what your 'original' form is doing.
You end up having to do two things:
1. In your second tabular form, you need to explicitly identify the relevant form fields using calls to the relevant APEX_ITEM functions - as well as this, you need to 'manually' specify the array number in the arguments for the function call, ensuring it doesn't overlap with your original form. Normally, this aspect is done for you.
2. Create your own custom CRUD processes, referencing the above elements. There are a few threads floating around the forum relating to how to deal with this. Do a search for "APEX_APPLICATION.G_F" or "HTMLDB_APPLICATION.G_F" for pointers.
Happy hunting!

Similar Messages

  • How to handle multiple database tables in a single UIX page?

    Hi,
    I am new to UIX & BC4J. I have to handle data from four different tables in the database. The scenario is as follows:
    The tables are
    1. user
    fields are: userid number, name varchar2
    2. business
    fields are: businessId number, name varchar2
    3. service
    fields are: serviceId number, serviceName varchar2
    4. userBusiness
    userid,businessid (both are foreign keys) & form complex primary keys.
    and userid,businessid, serviceId are primary keys.
    Now my problem is: to create a webpage where
    1. The userid is available in the httpSession Variable as string.
    2. according to the userId stored in the session variable I have to retrieve the business names and show them in a choice i.e., pull down box.
    3. I have to show the services provided by the business for the business name selected in the combo box.
    Could anyone Please help me solve this problem? Could you please give me hints? I have truncated the other fields in the tables.
    Thanking you,
    Velpandian .S

    At the moment, you can't do it declaratively. You have to do it in an event handler. Assuming you have the userid setup as a query parameter in the view object, something like this should get you started:
    public EventResult handleEvent(
    BajaContext context, Page page, PageEvent event) throws Throwable
    HttpSession session = context.getServletRequest().getSession(true);
    ViewObject view = ServletBindingUtils.getViewObject(context);
    String userid = session.getAttribute("userid");
    view.setWhereClauseParam(0, userid);
    view.executeQuery();

  • How to load multiple target tables simultaneously in single interface?

    I have a requirement where I have to load data into two target tables in single interface simultaneously. Reason is to populate parent-child relationship on target side as it is coming from the source side.
    For eg: I have 2 headers and 10 corresponding lines in source. Now I want load 2 headers into T1 and 10 lines into T2 simultaneously.
    Eg. SOURCE_TABLE
    HeaderId HeaderDesc LineId LineDesc
    1 AAA 10 QQQ
    1 AAA 20 WWW
    2 BBB 30 ZZZ
    2 BBB 10 XXX
    TARGET_TABLES:
    TARGET_HEADER
    HeaderId HeaderDesc
    1 AAA
    2 BBB
    TARGET_LINE
    HeaderId LineId LineDesc
    1 10 QQQ
    1 20 WWW
    2 30 ZZZ
    2 10 XXX
    I would appreciate if anyone can provide solution in this scenario.
    Thanks in advance.
    Giri
    Edited by: user10993896 on Apr 13, 2009 2:56 PM
    Edited by: GiriM on Apr 14, 2009 10:47 AM

    Hi Giri,
    Let me try to build an example... If I misunderstood your requirement please, let me know!
    1) Source table Tab_S
    create table Tab_S as (cs1 number, cs2 varchar2(10))
    2) Table Parent (P)
    create table Tab_P as (cp1 number, cp2 varchar2(10))
    3) Table Child (C)
    create table Tab_C as (cc1 number, cc2 varchar2(10), cp1 number)
    4) Function F$_Tab_C (create it in a ODI procedure)
    4.1 - step 1
    Create or Replace
    Function F$_Tab_C (p_cp2 varchar2, p_cc1 number,p_cc2 varchar2, cp_cp1 number) return varchar2 as
    begin
    insert into Tab_C (cc1, cc2, cp1)
    values (p_cc1, p_cc2, p_cp1);
    return p_cp2;
    end;
    associate this step to an procedure option like "Create_Function"
    4.2 - step 1
    Drop Function F$_Tab_C
    associate this step to an procedure option like "Drop_Function"
    4.3 - Step 2
    Disable the FK constraint and parent and child
    associate this step to an procedure option like "Disable_Constraint"
    4.4 - Step 3
    Enable the FK constraint
    associate this step to an procedure option like "Enable_Constraint"
    5) ODI interface:
    Source: Tab_S
    Target: Tab_P
    Mapping:
    cp1 ---> cs1
    cp2 ---> F$_Tab_C(cs2, 123, 'abc', cp1)
    6) ODI Package with all flow:
    6.1 - Drag and drop the procedure and put the options:
    "Create_Function" yes
    "Disable_Constraint" yes
    "Drop_Function" no
    "Enable_Constraint" no
    6.2 - Drag and drop the interface
    6.3 - Drag and drop the procedure (again) and put the options:
    "Create_Function" no
    "Disable_Constraint" no
    "Drop_Function" yes (optional, can let as NO if you wish)
    "Enable_Constraint" yes
    These are the necessary steps.... Maybe there is some syntax error because I build all in a notepad and do not compiled it in the DB. It is just to show you the general idea.
    Maybe you can be a little afraid about disable the FK but it is OK because you can guarantee the relationship by logic (funcion).
    The only point is that you must be the only one working at the target tables during the process.
    Make any sense in your case?

  • How to show multiple records in JDeveloper automatically

    Hi, you guys,
    May I ask you how to show multiple records, say consecutive three records, of a View object in JDeveloper?
    I know that we can just drag and drop a view object as a child (Table) of a scrollPane.
    Are there any other approaches?
    Thanks a lot for your time.
    damon

    Thanks for your reply.
    You are right.
    Table binding is the best solution for that.
    But in my mind, a record in a table is always shown in one row (or one line), am I right?
    If so, it is not convient to show records with multitple columns.
    Let's say, there are 20 columns to show for each record. Then we should display a record in, say 3 lines.
    How can we do that?
    Are there any suggestions?
    I am thinking that maybe I can use secondary row set iterators for that since we can create two or more row set iterators for the same view object.
    Assume I want to show three consecutive records. I can use attribute binding to show the current record in three lines by dragging attributes one by one from Data Control Palette to Design Window as Child | TextField;
    But I do not know how to use a secondary row set iterator for the next record. Where shall I create a secondary row set ietrator such that I can use it to create and synchronize the bindings.
    Thanks a lot
    Damon
    Message was edited by:
    user599641

  • How to create a dynamic table were the JTable columns keep varying

    How to create a dynamic table were the JTable columns keep varying based on the input to the jtable

    Oooh, I lied. DefaultTableModel has an API for adding and
    removing columns. I didn't know that. You should have read
    the API.
    As for preferring to extend AbstractTableModel rather than
    DefaultTableModel, I think it's more correct. DefaultTableModel
    is a simple implementation of Abstract for basic cases. It isn't
    intended to be extended. I figure most people extending
    DefaultTableModel are also extending JFrame, JPanel, and Thread
    instead of encapsulating the first two and implementing
    Runnable for the third.

  • How to combine multiple Unmanaged Solution to one single Managed solution

    Hi,
    How to combine multiple Unmanaged Solution to one single Managed solution.?
    There were some other third party developer have kept things lik ein UAT there are 2 release solution and both are Managed Solution.
    And in Production the changes are only deployed for release 1 and for the release 2 changes deployment needs to be done.
    But when i import that second release Managed Solution from UAT to Production then i got number of elements missing but i have checked they are already there in Soolution.
    I did some R&D on this but not much helpful.
    I thought i require to convert Unmanaged Solution of Production environment to Managed first for first release and then needs to import Managed solution of UAT to Production for second release.
    Is this the right way to overcome form this situation?
    Any help and response would be really appreciated.
    Thanks.
    If this post answers your question, please click &quot;Mark As Answer&quot; on the post and &quot;Mark as Helpful&quot;

    Hi, 
    You can prepare unmanaged solution by adding all the components from the default solution,which are there in the managed solution, If Customizatiable entity is true in  the managed solution.

  • How to include multiple image components into a single custom component???

    How to include multiple image components into a single custom component???

    Hi Marcel,
    an ABAP transaction can only run or at least be started on one single system. A portal transaction can be assigned using a URL. This doesn't need any logical component.
    Regards
    Andreas

  • Get input for 100 dynamic fields in a single screen

    Hi all
    I got one requirement wherein i need to accept input for around 100 dynamic fields in a single screen. screen can scroll down if possible.
    Can anyone tell me whether it is possible. if yes please let me have the sample code.
    Thanks
    Ravindra Suvarna

    Ravi,
    Probably a TAB STRIP might help you.
    Seggregate your 100 fields logically, say 5 groups.
    Have a TAB STRIP CONTROL, with 5 tab strips and place 20 fields in each of the tabs. Each tab strip will have a sub screen.
    Regards,
    Ravi
    Note : Please mark the helpful answers.

  • How to populate a dynamic table according to the choice of the viewer

    Hi there,
    I ran into a dead-end on my  "Events" page.
    There is a dynamic table getting the info from a database. It will initially show the Upcoming Events.
    At this point my question is this:
    *Can I populate the dynamic table based on a condition where the current date and the event date (as in the db) will be compared and if the event date is later than the current date, it will be displayed in the table. Otherwise, it won't.
    If I can do that, can someone please help me out with the code?
    Besides that, on the right side of the page there are 3 options for the viewer:
    1. View upcoming events
    2. View past events
    3. Search events by month and year
    What I want to do is that when the viewer clicks on 'past events', the table will be reset and populated with those events whose date has passed.
    When the viewer clicks on "upcoming events", the table is reset again and populated with the relevant events.
    When the viewer selects a month and a year, search the database to find the relevant records.
    Can all of this be written in php? Since I read smwhere that php doesn't work with onclick functions... i got confused. Cuz the data in my table will have to vary depending on what the viewer is clicking (upcoming events/past events/search events). I do not wish to create separate pages for each type of event.
    If anybody has a better suggestion to carry out this task, please share!
    Thanks!

    >Can I populate the dynamic table based on a condition where the current date and the event date (as in the db)
    >will be compared and if the event date is later than the current date, it will be displayed in the table. Otherwise, it won't.
    Of course. You just need to compare the date field in your database with the current date as returned by your DBMS date function. Assuming you are using MySQL, you would compare your column with the currdate() function and use the appropriate greater than/ less than operators in the SQL WHERE clause. If you don't know what a WHERE clause is then I would urge you to learn SQL as soon as possible. You can't build data driven sites without a basic understanding of SQL.
    >Since I read smwhere that php doesn't work with onclick functions..
    What this means is that php is a server side language, where user interactions always occur at the client site. But that does not mean you can't invoke a server side action from a client side event. You most certainly can and would.
    You might consider adding links to the dynamic table page that pass a querystring to the php script which determine what filter to add in the WHERE clause- greater than the current date, less than, etc.
    Also, in the future, please post these questions to the application development forum.

  • How to show data in table on the basis of click on a row of another table

    Hi All,
    I want to show two tables. In first table the main objects show in turn there is another collection in that main object for which i want to show data in separate table.
    e.g.,
    ObjectA
      have the collection of ObjectBs
    when i select ObjectA in main table then all the collection Objects of ObjectBs shows in separate table. Plz help me how to handle this case ??

    hi,
    You can create two value nodes for storing these collections. The first one would be singleton node as it is the main list. Under that create the second node with singleton = false.
    e.g.
    ---NodeA
        --attrA1
        --attrA2
        --NodeB(singleton = false)
                --attrB1
                --attrB2
    Now populate collection of object A in NodeA and after adding element in NodeA populate respective elements in NodeB.
    IPrivate<View>View.INodeANode nodeA = wdContext.NodeAnode();
    for (Iterator  it = collectionA.iterator(); it.hasNext(); )
         ObjectA objA= it.next();
         IPrivate<View>View.INodeAElement nodeAElem= nodeA.createNodeAElement();
         wdCopyservice.copy Corresponding(objA,nodeAElem);
         nodeA.addElement(nodeAElem);
         Collection collectioB =objA.getCollectionB();
         for (Iterator  it1 = collectionB.iterator(); it1.hasNext(); )
             ObjectB objB= it1.next();
            IPrivate<View>View.INodeBNode nodeB = nodeAElem.nodeBnode();
            IPrivate<View>View.INodeAElement nodeBElem= nodeB.createNodeBElement();
            wdCopyservice.copy Corresponding(objB,nodeBElem);
            nodeB.addElement(nodeBElem);
    Bind NodeA to the first table and NodeB to second one.
    After that when you select record in first table automatically its corresponding records will be populated in second table.
    Hope this helps!
    Monalisa

  • How to show data through table control

    Hi Experts,
    I have created an table control through wizard using table EKKO.
    I have to populate one internal table( type ekko ), and then show it in output  through table control.
    Please advise, how to do that and in where i have to write the codes.
    I will reward points for every suggestion
    Thanks in advance.
    regards

    hi saubrab,
                    This is kiran kumar.G.I am sending some sample code to populate data into table control check it once.
    i will give input in 100 screen. and display table control in 200 screen.check it once once ..ok....
    SE38 :(CODE)
    *& Module pool       YMODULEPOOL_TABLECONTROL1                         *
    *& DEVELOPER   : KIRAN KUMAR.G                                         *
    *& PURPOSE     : TABLE CONTROL DEMO                                    *
    *& CREATION DT : 17/12/2007                                            *
    *& T.CODE      : YMODTABLECONTROL1                                     *
    *& REQUEST     : ERPK900035                                            *
    PROGRAM  ymodulepool_tablecontrol1.
    Tables
    TABLES: yvbap,  "Sales Document: Item Data
            vbak.   "Sales Document: Header Data
    Controls
    CONTROLS: my_table TYPE TABLEVIEW USING SCREEN 200.
    Global Variables
    DATA: gv_lines    TYPE i,
          gv_lines1   type i,
          gv_temp     type i,
          gv_flag(20) TYPE c VALUE 'DISP',
          gv_mode1    TYPE c,
          gv_mode     TYPE c VALUE 'C'. " C: Change, D :Display
    Internal Table
    DATA: BEGIN OF gt_item OCCURS 0,
            vbeln LIKE vbap-vbeln,  "Sales Document Number
            posnr LIKE vbap-posnr,  "Sales Document Item
            matnr LIKE vbap-matnr,  "Material Number
            matkl LIKE vbap-matkl,  "Material Group
            arktx LIKE vbap-arktx,  "Short Text for Sales Order Item
            cflag,                  "Deletion Indicator
          END OF gt_item.
    *&      Module  STATUS_0100  OUTPUT
          text
    MODULE status_0100 OUTPUT.
      SET PF-STATUS 'ZTABLECONTROL' OF PROGRAM 'YMODULEPOOL_TABLECONTROL'.
    SET TITLEBAR 'xxx'.
    ENDMODULE.                 " STATUS_0100  OUTPUT
    *&      Module  USER_COMMAND_0100  INPUT
          text
    MODULE user_command_0100 INPUT.
      CASE sy-ucomm.
        WHEN 'DISP'.
          SELECT single vbeln
                        erdat
                        angdt
                        bnddt
                   FROM vbak
                  INTO (vbak-vbeln,vbak-erdat,
                        vbak-angdt,vbak-bnddt)
                  WHERE vbeln = vbak-vbeln.
            IF sy-subrc EQ 0.
    *Fetch the table control data and place them in Internal Table
              SELECT vbeln
                     posnr
                     matnr
                     matkl
                     arktx
                FROM yvbap
                INTO TABLE gt_item
                WHERE vbeln = vbak-vbeln.
              IF sy-subrc EQ 0.
    *NO OF line in the Internal Table
                DESCRIBE TABLE gt_item LINES gv_lines.
                my_table-lines = gv_lines + 20.
              ENDIF.
            ENDIF.
    *Call Screen 200.
            SET SCREEN 200.
          WHEN  'EXIT' OR 'BACK' OR 'CANCEL'.
    *Exit from the Program
            CALL TRANSACTION 'SESSION_MANAGER'.
        ENDCASE.
      ENDMODULE.                 " USER_COMMAND_0100  INPUT
    module STATUS_0200 output.
    SET PF-STATUS 'ZTABLECONTROL1'.
    endmodule.                 " STATUS_0200  OUTPU
    *&      Module  copy_data  OUTPUT
          text
    module copy_data output.
    *Fetch the current line data from the Table control
    read table gt_item index my_table-current_line.
    if sy-subrc eq 0.
    *Populating data into screen fields
    gt_item-vbeln = gt_item-vbeln.
    gt_item-posnr = gt_item-posnr.
    gt_item-matnr = gt_item-matnr.
    gt_item-matkl = gt_item-matkl.
    gt_item-arktx = gt_item-arktx.
    endif.
    SE51:CODE (SCREEN 100)
    PROCESS BEFORE OUTPUT.
    MODULE STATUS_0100.
    PROCESS AFTER INPUT.
    MODULE USER_COMMAND_0100.
    SE51 :CODE (SCREEN 200)
    PROCESS BEFORE OUTPUT.
    MODULE STATUS_0200.
    loop at gt_item with control my_table cursor my_table-current_line.
    module copy_data.
    endloop.
    PROCESS AFTER INPUT.
    loop at gt_item.
    MODULE USER_COMMAND_0200.
    endloop.
                             HAVE A NICE DAY..
    Award points if helpful,kiran kumar.G

  • How to create a Dynamic table without knowing fieldcat size

    Hi all, i'm trying to insert a (Jointer) of 3 selections form diffrent tables in an other dynamic table but i dont know the size of my final table, so i dont know how to create a fieldcatalog.
    Can we create an internal table with those caractiristics ????

    Hi,
    If you know which fields (ABAP Dictionary) you're selecting then you know their size; use the following FM call: DD_NAMETAB_TO_DDFIELDS
    Then you can use the following method to create your dynamic table: cl_alv_table_create=>create_dynamic_table
    Arash

  • How to decrease the dynamic table data loading time

    hi
    i have problem with dynamic table.
    when i execute the the table with passing a query , getting lot of time for loading the table data.( it takes 30sec for every 100 rows.)
    pls help me how to overcome this problem.
    thanks advance.

    Yes, This is oracle application...
    We can move into other tablespace as well. But concern is how to improve the alter table move command performance.
    Is there any specific parameter apart from the nologging and parallel server..
    If it is taking 8 hours , can some have experience that nologging will save how much time. or is there any risk in doing in production.
    Regards

  • How to add a dynamic table to a Crystal ReportViewer?

    Hi All,
    I'm trying to create my first crystal report, but I want to create the data dynamically. I want to create my table on the fly then, just dump the table into the crystal report.
    1. I'm not sure how to setup the fieldnames in the report to point to my dynamic table.
    2. How do I add the columns name in my dynamic table to my report?
            DataTable m_tExample = new DataTable();
            // Add Column Names
            m_tExample.Columns.Add("firstname", typeof (string));
            m_tExample.Columns.Add("lastname", typeof( string));
            // Add Test Data
            m_tExample.Rows.Add("MT","Long");
            m_tExample.Rows.Add("D", "Chiat");
            m_tExample.Rows.Add("Matdt", "Sdmith");
            m_tExample.Rows.Add("Kevin", "Cloley");
            m_tExample.Rows.Add("Maitt", "Diurkee");
            m_tExample.Rows.Add("Paam", "Duurkee");
            m_tExample.Rows.Add("William", "Never");
            m_tExample.Rows.Add("Tang", "Hong");
            m_tExample.Rows.Add("Mike", "Lopez");
            m_tExample.Rows.Add("Bill", "Chao");
            m_tExample.Rows.Add("Az", "Mattizra");
            m_tExample.Rows.Add("Raja", "Crash");
            m_tExample.Rows.Add("Jimmy", "Compton");
            m_tExample.Rows.Add("Ray", "Johnson");
            m_tExample.Rows.Add("Janice", "Howard");
            m_tExample.Rows.Add("Tony", "Scott");
        // Add DataSet to Viewer?
            CrystalReportViewer1.ReportSource = m_tExample.DataSet;
            CrystalReportViewer1.DataBind();
    NOTE: When I'm in the designer, I only see a text object to place in the report detail for a fieldname.
    VS 2005, Crystal Report 2008
    Thanks.

    Hello,
    Once you get the Data Set create save it as XML and then create a new report off the XML file. Then you can set the data set to the report and the XML is not required any more.
    First, to be able add fields to a report you need to use RAS. Report.Engine doesn't have the ability.
    If you search in this forum you will find lots of examples on how to...
    If you want to create the report then see these RAS samples:
    http://wiki.sdn.sap.com/wiki/display/BOBJ/NETRASSDK+Samples#NETRASSDKSamples-Exporting%2FPrinting
    Don

  • How to append to dynamic table

    hi, everyone
    I want to append some data to a dynamic internal table.
    I have some code like following:
    form dyna  using  itab.
    DATA: NEW_LINE type ref to data.
    FIELD-SYMBOLS: <FS_1> type any table,
                   <FS_2>,
                   <FS_3>.
    assign itab to <FS_1>.
    create data NEW_LINE like line of <FS_1>.
    assign NEW_LINE->*  to <FS_2>.
    assign component 1 of structure <FS_2> to <FS_3>.
    <FS_3> = 'I'.
    assign component 2 of structure <FS_2> to <FS_3>.
    <FS_3> = 'ABC'.
    then <FS_2> is the entry I want to append now
    append ???
    endform.
    What I want to know is how to append the <FS_2> to the dynamic table. I require the entry can be append, and return out of this form.
    Any suggestion and answer is welcome
    Hope your reply, thanks a lot

    Hi,
    try out like this.
    data: begin of itab occurs 0,
          val1 type c,
          val2(3) type c,
          end of itab.
    data ws_itab like itab.
    DATA: NEW_LINE type ref to data.
    FIELD-SYMBOLS: <FS_1> type standard table,
    <FS_2>,
    <FS_3>.
    assign itab[] to <FS_1>.
    create data NEW_LINE like line of <FS_1>.
    assign NEW_LINE->* to <FS_2>.
    assign component 1 of structure <FS_2> to <FS_3>.
    <FS_3> = 'I'.
    assign component 2 of structure <FS_2> to <FS_3>.
    <FS_3> = 'ABC'.
    append <FS_2> to <FS_1>.
    Regards,
    Jagath

Maybe you are looking for

  • How to recover deleted files from iPod

    All the contents of my iTunes music folder were deleted. When I connected my iPod it was autosynced with the empty iTunes music folder and everything on the iPod got deleted too. (No warning, no undo.) Does anyone know of a utility proven to recover

  • Flash Builder Integration

    Flash CS5 has the ability to integrate with Flash Builder for editing AS files but I can't find a way to make it work with existing Flash projects. The docs tell how to do it when creating new FLA/AS files but they don't say anything about existing p

  • Detail transaction

    Hello Experts, We want to know detail transaction of our revenue account. All informations including row information. In GL report, we can't see detail document e.g if there is an invoice, it must include the items in the invoice. . We use B1 2007A.P

  • Make to order - MRP

    Dear all,           MY Client doing Make to order production, finished material is assembly. all components are sent to subcontractor under 541 mvt type without reference. when the sale order came for assembly, we have to run MRP, at the time system

  • Missing parameters for L_TO_CREATE_DN (Transfer Order Creation)

    Hi,    Though i am passing T_LTAP_VB-LETYP, i am getting an error message as 'Enter the storage unit type', could you please let me know what i am missing here. I am passing the following fields to the function module (L_TO_CREATE_DN): I_LGNUM I_VBEL