메뉴 건너뛰기

SAP 한국 커뮤니티



다이나믹 테이블

박원희 2007.05.15 05:25 조회 수 : 9164 추천:2

*&---------------------------------------------------------------------*
*& Report  Z_TEST20070214                                              *
*&                                                                     *
*&---------------------------------------------------------------------*
*&                                                                     *
*&                                                                     *
*&---------------------------------------------------------------------*


REPORT  Z_TEST20070214                .


TYPE-POOLS: rsds.


DATA: is_x030l  TYPE x030l,
      it_dfies  TYPE TABLE OF dfies,
      is_dfies  TYPE dfies,
      it_fdiff  TYPE TABLE OF field_dif,
      is_fdiff  TYPE field_dif.


DATA: w_selid   TYPE rsdynsel-selid,
      it_tables TYPE TABLE OF rsdstabs,
      is_tables TYPE rsdstabs,
      it_fields TYPE TABLE OF rsdsfields,
      it_expr   TYPE rsds_texpr,
      it_ranges TYPE rsds_trange,
      it_where  TYPE rsds_twhere,
      is_where  TYPE rsds_where,
      w_active  TYPE i.


DATA: it_content TYPE REF TO data,
      it_modif   TYPE REF TO data,
      it_fcat    TYPE lvc_t_fcat.


DATA: w_okcode   TYPE sy-ucomm.



FIELD-SYMBOLS: <itab> TYPE STANDARD TABLE,
               <ntab> TYPE STANDARD TABLE.



* Macros
DEFINE table_error.
  message e398(00) with 'Table' p_table &1.
END-OF-DEFINITION.


DEFINE fixed_val.
  is_fdiff-fieldname = is_dfies-fieldname.
  is_fdiff-fixed_val = &1.
  is_fdiff-no_input  = 'X'.
  append is_fdiff to it_fdiff.
END-OF-DEFINITION.



* Selection screen
SELECTION-SCREEN: BEGIN OF BLOCK b01 WITH FRAME.
PARAMETERS: p_table TYPE tabname OBLIGATORY                    "table
                                 MEMORY ID dtb
                                 MATCHCODE OBJECT dd_dbtb_16.
SELECTION-SCREEN: BEGIN OF LINE,
                  PUSHBUTTON 33(20) selopt USER-COMMAND sel,
                  COMMENT    55(15) selcnt,
                  END OF LINE.
SELECTION-SCREEN: SKIP.
PARAMETERS: p_rows  TYPE i.                                    "rows
SELECTION-SCREEN: END OF BLOCK b01,
                  SKIP,
                  BEGIN OF BLOCK b02 WITH FRAME.
PARAMETERS: p_displ TYPE c AS CHECKBOX.                        "display
SELECTION-SCREEN: END OF BLOCK b02.


* Initialization
INITIALIZATION.
  MOVE '@4G@ Filter records' TO selopt.


* PBO
AT SELECTION-SCREEN OUTPUT.
  IF w_active IS INITIAL.
    CLEAR: selcnt.
  ELSE.
    WRITE w_active TO selcnt LEFT-JUSTIFIED.
  ENDIF.


* PAI
AT SELECTION-SCREEN.
  IF p_table NE is_x030l-tabname.
    CALL FUNCTION 'DDIF_NAMETAB_GET'
         EXPORTING
              tabname   = p_table
         IMPORTING
              x030l_wa  = is_x030l
         TABLES
              dfies_tab = it_dfies
         EXCEPTIONS
              OTHERS    = 1.
    IF is_x030l IS INITIAL.
      table_error 'does not exist or is not active'.
    ELSEIF is_x030l-tabtype NE 'T'.
      table_error 'is not selectable'.
    ELSEIF is_x030l-align NE 0.
      table_error 'has alignment - cannot continue'.
    ENDIF.


*   Default values for system fields
    REFRESH: it_fdiff.
    is_fdiff-tabname = p_table.
    LOOP AT it_dfies INTO is_dfies.
      IF is_dfies-datatype = 'CLNT'.
        fixed_val sy-mandt.
      ELSEIF is_dfies-rollname = 'ERDAT'
          OR is_dfies-rollname = 'ERSDA'
          OR is_dfies-rollname = 'AEDAT'
          OR is_dfies-rollname = 'LAEDA'.
        fixed_val sy-datum.
      ELSEIF is_dfies-rollname = 'ERTIM'
          OR is_dfies-rollname = 'AETIM'.
        fixed_val sy-uzeit.
      ELSEIF is_dfies-rollname = 'ERNAM'
          OR is_dfies-rollname = 'AENAM'.
        fixed_val sy-uname.
      ENDIF.
    ENDLOOP.


*   Prepare free selection on table
    REFRESH it_tables.
    is_tables-prim_tab = p_table.
    APPEND is_tables TO it_tables.


    CLEAR: w_selid.
  ENDIF.


  IF sy-ucomm = 'SEL'.
    IF w_selid IS INITIAL.
*     Init free selection dialog
      CALL FUNCTION 'FREE_SELECTIONS_INIT'
           EXPORTING
                expressions  = it_expr
           IMPORTING
                selection_id = w_selid
                expressions  = it_expr
           TABLES
                tables_tab   = it_tables
           EXCEPTIONS
                OTHERS       = 1.
    ENDIF.


*   Display free selection dialog
    CALL FUNCTION 'FREE_SELECTIONS_DIALOG'
         EXPORTING
              selection_id            = w_selid
              title                   = 'Selection'
              status                  = 1
              as_window               = 'X'
         IMPORTING
              expressions             = it_expr
              field_ranges            = it_ranges
              number_of_active_fields = w_active
         TABLES
              fields_tab              = it_fields
         EXCEPTIONS
              OTHERS                  = 1.
  ENDIF.



* Start of processing
START-OF-SELECTION.


  PERFORM f_create_table USING p_table.


  PERFORM f_select_table.


  PERFORM f_display_table.



*---------------------------------------------------------------------*
*       FORM f_create_table                                           *
*---------------------------------------------------------------------*
FORM f_create_table USING in_tabname.


  FIELD-SYMBOLS: <fcat> TYPE lvc_s_fcat.


  CALL FUNCTION 'LVC_FIELDCATALOG_MERGE'
       EXPORTING
            i_structure_name = in_tabname
       CHANGING
            ct_fieldcat      = it_fcat
       EXCEPTIONS
            OTHERS           = 1.
  IF sy-subrc = 0.
*   Complete field catalog
    LOOP AT it_fcat ASSIGNING <fcat>.
      <fcat>-tabname = in_tabname.
    ENDLOOP.
    CALL FUNCTION 'LVC_FIELDCAT_COMPLETE'
         CHANGING
              ct_fieldcat = it_fcat
         EXCEPTIONS
              OTHERS      = 1.
  ELSE.
    WRITE: 'Error building field catalog'.
    STOP.
  ENDIF.


* Create dynamic table for data
  CALL METHOD cl_alv_table_create=>create_dynamic_table
    EXPORTING
      it_fieldcatalog = it_fcat
    IMPORTING
      ep_table        = it_content.
  IF sy-subrc = 0.
    ASSIGN it_content->* TO <itab>.
  ELSE.
    WRITE: 'Error creating internal table'.
    STOP.
  ENDIF.


* Create dynamic table for modif
  CALL METHOD cl_alv_table_create=>create_dynamic_table
    EXPORTING
      it_fieldcatalog = it_fcat
    IMPORTING
      ep_table        = it_modif.
  IF sy-subrc = 0.
    ASSIGN it_modif->* TO <ntab>.
  ELSE.
    WRITE: 'Error creating internal table'.
    STOP.
  ENDIF.


ENDFORM.



*---------------------------------------------------------------------*
*       FORM f_select_table                                           *
*---------------------------------------------------------------------*
FORM f_select_table.


  IF w_active = 0.
    SELECT * FROM (p_table)
             INTO CORRESPONDING FIELDS OF TABLE <itab>
            UP TO p_rows ROWS.
  ELSE.
*   Selection with parameters
    CALL FUNCTION 'FREE_SELECTIONS_RANGE_2_WHERE'
         EXPORTING
              field_ranges  = it_ranges
         IMPORTING
              where_clauses = it_where.
    READ TABLE it_where INTO is_where WITH KEY tablename = p_table.


    SELECT * FROM (p_table)
             INTO CORRESPONDING FIELDS OF TABLE <itab>
            UP TO p_rows ROWS
            WHERE (is_where-where_tab).
  ENDIF.


  IF sy-dbcnt = 0.
    WRITE: 'No record selected'.
    STOP.
  ENDIF.
ENDFORM.



*---------------------------------------------------------------------*
*       FORM f_display_table                                          *
*---------------------------------------------------------------------*
FORM f_display_table.
  DATA: l_answer TYPE c,
        l_eflag  TYPE c.


  CLEAR: w_okcode.
  REFRESH: <ntab>.
* Display table contents
  CALL FUNCTION 'STC1_FULLSCREEN_TABLE_CONTROL'
       EXPORTING
            header       = p_table
            tabname      = p_table
            display_only = p_displ
            endless      = 'X'
            no_button    = space
       IMPORTING
            okcode       = w_okcode
       TABLES
            nametab      = it_dfies
            table        = <itab>
            fielddif     = it_fdiff
            modif_table  = <ntab>
       EXCEPTIONS
            OTHERS       = 1.
  IF sy-subrc = 0.
    IF p_displ IS INITIAL AND w_okcode = 'SAVE'.
*     Confirm update
      CALL FUNCTION 'POPUP_TO_CONFIRM'
           EXPORTING
                titlebar              = p_table
                text_question         = 'Do you want to update table ?'
                default_button        = '2'
                display_cancel_button = ' '
           IMPORTING
                answer                = l_answer
           EXCEPTIONS
                OTHERS                = 1.
      IF l_answer = '1'.
*       Apply modifications
        IF NOT <ntab>[] IS INITIAL.
          PERFORM f_add_system USING space.
          MODIFY (p_table) FROM TABLE <ntab>.
          IF sy-subrc NE 0.
            l_eflag = 'X'.
          ENDIF.
        ENDIF.
*       Apply deletions
        IF l_eflag IS INITIAL.
          REFRESH: <ntab>.
          CALL FUNCTION 'STC1_GET_DATA'
               TABLES
                    deleted_data = <ntab>
               EXCEPTIONS
                    OTHERS       = 1.
          IF NOT <ntab>[] IS INITIAL.
            DELETE (p_table) FROM TABLE <ntab>.
            IF sy-subrc NE 0.
              ROLLBACK WORK.
              l_eflag = 'X'.
            ENDIF.
          ENDIF.
        ENDIF.
*       Apply creations
        IF l_eflag IS INITIAL.
          REFRESH: <ntab>.
          CALL FUNCTION 'STC1_GET_DATA'
               TABLES
                    new_data = <ntab>
               EXCEPTIONS
                    OTHERS   = 1.
          IF NOT <ntab>[] IS INITIAL.
            PERFORM f_add_system USING 'X'.
            INSERT (p_table) FROM TABLE <ntab>.
            IF sy-subrc NE 0.
              ROLLBACK WORK.
              l_eflag = 'X'.
            ENDIF.
          ENDIF.
        ENDIF.
        IF l_eflag IS INITIAL.
          COMMIT WORK.
          MESSAGE s261(53).
        ELSE.
          MESSAGE s075(3i).
          PERFORM f_select_table.
        ENDIF.
      ENDIF.
*     Display table again
      PERFORM f_display_table.
    ENDIF.
  ENDIF.


ENDFORM.



*---------------------------------------------------------------------*
*       FORM f_add_system                                             *
*---------------------------------------------------------------------*
FORM f_add_system USING new TYPE c.


  FIELD-SYMBOLS: <irec> TYPE ANY,
                 <upd>  TYPE ANY.


  LOOP AT it_fdiff INTO is_fdiff.
    READ TABLE it_dfies INTO is_dfies
                    WITH KEY fieldname = is_fdiff-fieldname.
    LOOP AT <ntab> ASSIGNING <irec>.
      ASSIGN COMPONENT is_fdiff-fieldname OF STRUCTURE <irec> TO <upd>.
      IF is_dfies-datatype = 'CLNT'.
        <upd> = sy-mandt.
      ELSE.
        CASE is_dfies-rollname.
          WHEN 'AENAM'.
            <upd> = sy-uname.
          WHEN 'AEDAT' OR 'LAEDA'.
            <upd> = sy-datum.
          WHEN 'AETIM'.
            <upd> = sy-uzeit.
          WHEN OTHERS.
        ENDCASE.
      ENDIF.
    ENDLOOP.
  ENDLOOP.


ENDFORM.

번호 제목 글쓴이 날짜 조회 수
1104 RFC OVERVIEW [3] file SARA 2007.04.25 3571
1103 LSMW [1] file SARA 2007.04.25 4642
1102 LSMW 2 [2] file SARA 2007.04.25 4619
1101 was 에서 abap에러 핸들링에 관한 문서 [1] file 도도마녀 2007.04.26 3321
1100 SAP CONNECTOR 문서 file 도도마녀 2007.04.26 3133
1099 유용한 T-Code [6] file yang 2007.04.26 3413
1098 SAPBUSINESS SYMPOSIUN07 [1] file akira 2007.04.27 3260
1097 SAPBUSINESS file SAP 2007.04.27 3422
1096 WD4A ALV관련 프로그램 방법입니다. [1] file 파워유저 2007.04.27 3402
1095 SMB 세미나 자료 입니다. file SARA 2007.04.27 3070
1094 ERP에 대한 자료 [5] file SARA 2007.04.27 3320
1093 BAPI 소개 [10] file sapjoy 2007.05.02 3241
1092 ABAP 시스템 필드(SYSTEM FIELD) file sapjoy 2007.05.02 3479
1091 중복인지 모르겠네요 QUERY사용법 메뉴얼 [4] file 싸이 2007.05.02 3422
1090 ABAP TIPS [1] file 정훈 2007.05.02 6128
1089 DB Link 만들기 [6] file dragon 2007.05.02 3946
1088 T-CODE, IMG 메뉴 엑셀로 다운받기 [21] file ccaby 2007.05.03 5190
1087 효과적인 abap 프로그래밍 [2] file 김대영 2007.05.07 3167
1086 alv help [4] file 김대영 2007.05.07 3925
1085 wd 관련 [6] file 우째 .. 2007.05.07 7835