zoukankan      html  css  js  c++  java
  • BWABAP to copy aggregates from one cube to another

    In COPA you have often a data model consisting of similar cubes but with different data.You can have e.g. a cube for data of the current year, another cube with data of the previous year and a last one with data older than 2 years. For good query performance you create aggregates. Because of the similarities between the cubes it would be nice to have a FM or ABAP that copies one aggregate from a cube to another cube. Better would be to copy all aggregates from the old to the new cubes. If you search in the repository and SDN, you will find report RSDDK_AGGRCOMP_COPY. This report copies one aggregate by its technical name or UID to the destination cube. So I played around with it and found some issues:
    1. It hasn’t any value-help for cubes – I spent times to find an error, blamed to find out I entered the wrong technical name-
    2. It doesn’t allow to copy all aggregates from source to the  target cube
    3. Texts of the copied aggregate are different from the original
    4. It terminates very hard and not user friendly if target infocube doesn’t exist
    So I took a little of my time and made a copy of this report into customer namespace and added value helps for source and destination cube as well as to copy all aggregates of a cube to another. I also moved the checks for infocube existence at the beginning. Now the report ends with an error message in the output list window. 

    The coding for the new report is now:

     

    *& Report  ZAGGR_COPY
    *&
    *&---------------------------------------------------------------------*
    *& copies aggregates from one cube to another
    *& works for real-time cubes too
    *&
    *&---------------------------------------------------------------------*

    REPORT  ZAGGR_COPY.

    TYPE-POOLS: rs, rsddk, rshi, rrsm, rrsi.

    DATA:
      l_r_aggr_collection TYPE REF TO cl_rsddk_aggregate_collection,
      l_t_aggrdir like table of rsddaggrdir,
      l_s_aggrdir like rsddaggrdir,

      l_aggruid           TYPE rsddaggruid,
      l_infocube_old      TYPE rsd_infocube,
      l_cubetype          TYPE rscubetype,
      l_no_authority      TYPE rs_bool,
      l_expert_mode       TYPE rs_bool,

      l_txtsh             TYPE rstxtsh,
      l_txtlg             TYPE rstxtlg,

      l_t_aggrt           TYPE rsddk_t_aggrt_db,
      l_s_aggrt           TYPE rsddaggrt,

      l_s_aggrcomp        TYPE rsddk_s_aggrcomp_db,
      l_t_aggrcomp        TYPE rsddk_t_aggrcomp_db,
      l_t_aggrcomp_del    TYPE rsddk_t_aggrcomp_db,
      l_t_aggrcomp_all    type rsddk_t_aggrcomp_db,
      l_t_cob_pro         TYPE rsd_t_cob_pro.

    FIELD-SYMBOLS:
      <l_s_aggrcomp>      TYPE rsddk_s_aggrcomp_db.

    * select-options:
    * aggregate to be copied
    SELECTION-SCREEN:  BEGIN OF BLOCK b1
                            WITH FRAME TITLE text-101.

    PARAMETERS:
      i_scube    TYPE rsdcube-infocube,
      i_aggr     TYPE rsd_infocube,
      i_auid     TYPE rsddaggruid.

    SELECTION-SCREEN: END OF BLOCK b1,
    * infocube to which aggregate should be copied
                      SKIP 1,
                      BEGIN OF BLOCK b2
                      WITH FRAME TITLE text-102.
    PARAMETERS:
      i_cube     TYPE rsdcube-infocube.

    SELECTION-SCREEN: END OF BLOCK b2.

    AT SELECTIOn-SCREEN ON VALUE-REQUEST FOR i_cube.
    PERFORM f_valuerequest_icube.

    AT SELECTIOn-SCREEN ON VALUE-REQUEST FOR i_scube.
    PERFORM f_valuerequest_scube.

    AT SELECTIOn-SCREEN ON VALUE-REQUEST FOR i_aggr.
    PERFORM f_valuerequest_aggr.

    END-OF-SELECTION.

    * check if target infocube exists!
    SELECT SINGLE cubetype FROM rsdcube
                    INTO l_cubetype
                    WHERE infocube = i_cube
                      AND objvers  = rs_c_objvers-active.
    IF sy-subrc <> 0 OR
       l_cubetype NE 'B'.
    *   no valid infocube selection.
      WRITE: / text-128 COLOR COL_NEGATIVE.
      EXIT.
    ENDIF.

    * check if source infocube exists!
    SELECT SINGLE cubetype FROM rsdcube
                    INTO l_cubetype
                    WHERE infocube = i_scube
                      AND objvers  = rs_c_objvers-active.
    IF sy-subrc <> 0 OR
       l_cubetype NE 'B'.
    *   no valid infocube selection.
      WRITE: / text-120 COLOR COL_NEGATIVE.
      EXIT.
    ENDIF.

    * authority check from RSDDV   ************************
    CALL FUNCTION 'RSSB_AUTHORITY_ADMWB_INFOCUBE'
      EXPORTING
        i_actvt        = 'U'
        i_infocube     = i_cube
        i_icubeobj     = rssb_c_auth_icubeobj-aggregate
        i_try_display  = rs_c_true
      IMPORTING
        e_display_only = l_no_authority.
    IF l_no_authority = rs_c_true.
      WRITE: / text-124 COLOR COL_NEGATIVE.
      EXIT.
    ENDIF.

    * check for lock and set lock for INFOPROV
    CALL METHOD cl_rsd_dta=>enqueue
      EXPORTING
        i_infoprov   = i_cube
        i_scope      = '1'
      EXCEPTIONS
        foreign_lock = 1
        sys_failure  = 2
        OTHERS       = 4.
    IF sy-subrc <> 0.
      WRITE: / text-125 COLOR COL_NEGATIVE, sy-msgv2 COLOR COL_NEGATIVE.
      EXIT.
    ENDIF.

    * cob_pro for infocube
    CALL FUNCTION 'RSD_COB_PRO_ALL_GET'
      EXPORTING
        i_infocube                = i_cube
        i_with_atr_nav            = rs_c_true
        i_objvers                 = rs_c_objvers-active
        i_bypass_buffer           = rs_c_false
      IMPORTING
        e_t_cob_pro               = l_t_cob_pro
      EXCEPTIONS
        infocube_not_found        = 1
        error_reading_infocatalog = 2
        illegal_input             = 3
        OTHERS                    = 4.
    IF sy-subrc <> 0.
      WRITE: / text-122 COLOR COL_NEGATIVE.
      EXIT.
    ENDIF.

    * get aggregate definition
    IF NOT ( i_aGGR IS INITIAL ).
      refresh l_t_aggrdir.
      SELECT *
                      FROM rsddaggrdir
                      INTO table l_T_aggrdir
    *  SELECT SINGLE aggruid infocube expertmode
    *                 FROM rsddaggrdir
    *                  INTO (l_aggruid, l_infocube_old, l_expert_mode)
                     WHERE aggrcube = i_aggr
                       AND objvers  = rs_c_objvers-modified.
      IF sy-subrc <> 0.
    *   aggregate not found
        WRITE: / text-121 COLOR COL_NEGATIVE.
        EXIT.
      ENDIF.

    ELSEIF not ( i_SCUBE is initial ).
      SELECT *
                      FROM rsddaggrdir
                      INTO table l_T_aggrdir
                     WHERE infocube = i_scube
                       AND objvers  = rs_c_objvers-modified.
    ELSE.
      l_aggruid = i_auid.
      l_s_aggrdir-aggruid = i_auid.
      append l_s_aggrdir to l_t_aggrdir.
    ENDIF.

    Loop at l_t_aggrdir into l_s_aggrdir.

      refresh l_t_aggrt.
      l_aggruid = l_S_aggrdir-aggruid.
      l_infocube_old = l_s_aggrdir-infocube.
      l_expert_mode = l_s_aggrdir-expertmode.

    SELECT * FROM rsddaggrcomp
             INTO TABLE l_t_aggrcomp
             WHERE aggruid = l_aggruid
               AND objvers = rs_c_objvers-modified.
    IF sy-subrc <> 0.
    *   aggregate not found
      WRITE: / text-121 COLOR COL_NEGATIVE.
      EXIT.
    ENDIF.

    * compare aggregate definition and cob_pro of infocube
    LOOP AT l_t_aggrcomp INTO l_s_aggrcomp.
      READ TABLE l_t_cob_pro
        TRANSPORTING NO FIELDS
        WITH KEY iobjnm = l_s_aggrcomp-iobjnm.
      IF sy-subrc <> 0.
        DELETE TABLE l_t_aggrcomp FROM l_s_aggrcomp.
        APPEND l_s_aggrcomp TO l_t_aggrcomp_del.
      ENDIF.

    ENDLOOP.

    IF l_t_aggrcomp IS INITIAL.
      WRITE: / text-123 COLOR COL_NEGATIVE.
      EXIT.
    ENDIF.
    * create new texts
    SELECT SINGLE * FROM rsddaggrt
                    INTO l_s_aggrt
                    WHERE aggruid = l_aggruid
                      AND objvers = rs_c_objvers-modified
                      AND langu   = sy-langu.

    * get new UID
    CALL FUNCTION 'RSS_SYSTEM_GET_UNIQUE_ID'
      IMPORTING
        e_uni_idc25 = l_aggruid.

    * and create new aggregate definition
    LOOP AT l_t_aggrcomp ASSIGNING <l_s_aggrcomp>.
      <l_s_aggrcomp>-aggruid = l_aggruid.
    ENDLOOP.
    l_s_aggrt-aggruid = l_aggruid.
    APPEND l_s_aggrt TO l_t_aggrt.

    * instantiate class
    CREATE OBJECT l_r_aggr_collection
      EXPORTING
        i_infoprov   = i_cube
        i_view_only  = rs_c_false.

    * set expert mode
    CALL METHOD l_r_aggr_collection->set_expert_mode
      EXPORTING
        i_expert_mode = l_expert_mode.

    * create aggregate
    CALL METHOD l_r_aggr_collection->aggregate_create
      EXPORTING
        i_t_aggrcomp  = l_t_aggrcomp
        i_t_aggrt     = l_t_aggrt
        i_aggruid     = l_aggruid
        i_expert_mode = l_expert_mode.

    * save definition
    CALL METHOD l_r_aggr_collection->save.

    * OUTPUT
    WRITE: / , text-110 COLOR COL_HEADING.
    WRITE: / , text-117 COLOR COL_POSITIVE, l_s_aggrt-txtlg .
    WRITE: / , text-111 COLOR COL_POSITIVE, l_aggruid .
    WRITE: / .
    * infoobjects that are copied
    WRITE: / , text-126 COLOR COL_POSITIVE.
    WRITE: / , text-112, text-113, text-114, text-115, text-116.
    LOOP AT l_t_aggrcomp INTO l_s_aggrcomp.
      WRITE: / ,  l_s_aggrcomp-iobjnm,  l_s_aggrcomp-aggrst,
                  l_s_aggrcomp-fixsid,  l_s_aggrcomp-hiesid,
                  l_s_aggrcomp-tlevel.
    ENDLOOP.

    WRITE: / .
    WRITE: / .
    * infoobjects that are included by the checks
    WRITE: / , text-127 COLOR COL_POSITIVE.
    WRITE: / , text-112, text-113, text-114, text-115, text-116.
    SELECT * FROM  rsddaggrcomp
             INTO  table l_t_aggrcomp_all
             WHERE aggruid = l_aggruid
               AND objvers = rs_c_objvers-modified.
      LOOP AT l_t_aggrcomp_all INTO l_s_aggrcomp.
        READ TABLE l_t_aggrcomp
             WITH KEY iobjnm = l_s_aggrcomp-iobjnm
             TRANSPORTING NO FIELDS.
        IF sy-subrc <> 0.
    *     infoobject was not in original, but included by cube-spec. checks
          WRITE: / ,  l_s_aggrcomp-iobjnm,  l_s_aggrcomp-aggrst,
                      l_s_aggrcomp-fixsid,  l_s_aggrcomp-hiesid,
                      l_s_aggrcomp-tlevel.
        ENDIF.
      ENDLOOP.


      WRITE: / .
      WRITE: / .
    * infoobjects that are not copied
      WRITE: / , text-118 COLOR COL_POSITIVE.
      WRITE: / , text-112, text-113, text-114, text-115, text-116.
      LOOP AT l_t_aggrcomp_del INTO l_s_aggrcomp.
        WRITE: / ,  l_s_aggrcomp-iobjnm,  l_s_aggrcomp-aggrst,
                    l_s_aggrcomp-fixsid,  l_s_aggrcomp-hiesid,
                    l_s_aggrcomp-tlevel.
      ENDLOOP.


    endloop. " overall aggregates of a cube

    * release lock for INFOPROV
      CALL METHOD cl_rsd_dta=>dequeue
        EXPORTING
          i_infoprov = i_cube
          i_scope    = '1'.



    *&---------------------------------------------------------------------
    *& Form f_valuerequest_icube
    *&---------------------------------------------------------------------

    FORM f_valuerequest_icube.

    DATA: BEGIN OF t_data OCCURS 1,
    data(20),
    END OF t_data.

    DATA: lwa_dfies TYPE dfies.

    data h_field_wa LIKe dfies.
    data h_field_tab like dfies occurs 0 with header line.
    data h_dselc like dselc occurs 0 with header line.
    data: ret_tab like table of ddshretval.
    data: l_rsdcube like rsdcube.

    refresh: t_data.
    SELECT infocube FROM rsdcube into l_rsdcube where objvers = 'A'.
    t_data = l_rsdcube-infocube. APPEND t_data.
    ENDSELECT.


    PERFORM f_fieldinfo_get USING 'RSDCUBE'
    'INFOCUBE'
    CHANGING h_field_wa.
    APPEND h_field_wa TO h_field_tab.

    h_dselc-fldname = 'INFOCUBE'.
    h_dselc-dyfldname = 'I_CUBE'.
    APPEND h_dselc.

    DATA: ld_repid LIKE sy-repid.
    ld_repid = sy-repid.

    CALL FUNCTION 'F4IF_INT_TABLE_VALUE_REQUEST'
    EXPORTING
    retfield = 'I_CUBE'
    dynpprog = ld_repid
    dynpnr = '1000'
    dynprofield = 'I_CUBE'

    *multiple_choice = ''
    *value_org = 'S'
    TABLES
    value_tab = t_data
    field_tab = h_field_tab
    *return_tab = ret_tab
    DYNPFLD_MAPPING = h_dselc
    EXCEPTIONS
    OTHERS = 0.

    ENDFORM. " f_valuerequest_vbeln

    FORM f_valuerequest_scube.

    DATA: BEGIN OF t_data OCCURS 1,
    data(20),
    END OF t_data.

    DATA: lwa_dfies TYPE dfies.

    data h_field_wa LIKe dfies.
    data h_field_tab like dfies occurs 0 with header line.
    data h_dselc like dselc occurs 0 with header line.
    data: l_rsdcube like rsdcube.

    SELECT * FROM rsdcube into l_rsdcube where objvers = 'A'.
    t_data = l_rsdcube-infocube. APPEND t_data.
    ENDSELECT.


    PERFORM f_fieldinfo_get USING 'RSDCUBE'
    'INFOCUBE'
    CHANGING h_field_wa.
    APPEND h_field_wa TO h_field_tab.

    h_dselc-fldname = 'INFOCUBE'.
    h_dselc-dyfldname = 'I_SCUBE'.
    APPEND h_dselc.

    DATA: ld_repid LIKE sy-repid.
    ld_repid = sy-repid.

    CALL FUNCTION 'F4IF_INT_TABLE_VALUE_REQUEST'
    EXPORTING
    retfield = 'I_SCUBE'
    dynpprog = ld_repid
    dynpnr = '1000'
    dynprofield = 'I_SCUBE'

    *multiple_choice = ''
    *value_org = 'S'
    TABLES
    value_tab = t_data
    field_tab = h_field_tab
    *return_tab = return_tab
    DYNPFLD_MAPPING = h_dselc
    EXCEPTIONS
    OTHERS = 0.

    ENDFORM. 

    FORM f_valuerequest_aggr.

    DATA: BEGIN OF t_data OCCURS 1,
    data(20),
    END OF t_data.

    DATA: lwa_dfies TYPE dfies.

    data h_field_wa LIKe dfies.
    data h_field_tab like dfies occurs 0 with header line.
    data h_dselc like dselc occurs 0 with header line.
    data: l_rsdaggr like rsddaggrdir-aggrcube.

    SELECT aggrcube FROM rsddaggrdir into l_rsdaggr where objvers = 'A'.
    t_data = l_rsdaggr. APPEND t_data.
    ENDSELECT.


    PERFORM f_fieldinfo_get USING 'RSDDAGGRDIR'
    'AGGRCUBE'
    CHANGING h_field_wa.
    APPEND h_field_wa TO h_field_tab.

    h_dselc-fldname = 'AGGRCUBE'.
    h_dselc-dyfldname = 'I_AGGR'.
    APPEND h_dselc.

    DATA: ld_repid LIKE sy-repid.
    ld_repid = sy-repid.

    CALL FUNCTION 'F4IF_INT_TABLE_VALUE_REQUEST'
    EXPORTING
    retfield = 'I_AGGR'
    dynpprog = ld_repid
    dynpnr = '1000'
    dynprofield = 'I_AGGR'

    *multiple_choice = ''
    *value_org = 'S'
    TABLES
    value_tab = t_data
    field_tab = h_field_tab
    *return_tab = return_tab
    DYNPFLD_MAPPING = h_dselc
    EXCEPTIONS
    OTHERS = 0.

    ENDFORM. 


    *&---------------------------------------------------------------------
    *& Form f_fieldinfo_get
    *&---------------------------------------------------------------------

    *text
    *----------------------------------------------------------------------

    *-->P_0079 text
    *-->P_0080 text
    *<--P_H_FIELD_WA text
    *----------------------------------------------------------------------
    FORM f_fieldinfo_get USING fu_tabname
    fu_fieldname
    CHANGING fwa_field_tab.

    CALL FUNCTION 'DDIF_FIELDINFO_GET'
    EXPORTING
    TABNAME = fu_tabname
    FIELDNAME = fu_fieldname
    LFIELDNAME = fu_fieldname
    IMPORTING
    DFIES_WA = fwa_field_tab
    EXCEPTIONS
    NOT_FOUND = 1
    INTERNAL_ERROR = 2
    OTHERS = 3
    .
    IF SY-SUBRC <> 0.
    MESSAGE ID SY-MSGID TYPE SY-MSGTY NUMBER SY-MSGNO
    WITH SY-MSGV1 SY-MSGV2 SY-MSGV3 SY-MSGV4.
    ENDIF.


    ENDFORM. " f_fieldinfo_get

     

    To work properly you need this textelements:

     

    101      Which Aggregate Definition Is To Be Copied?

     102      For Which InfoCube Is This Aggregate To Be Created?

     

    103      (Copy)

    104      Copy of Cube

    110      New Aggregate Successfully Created

    111      UID of New Aggregate:

    112      InfoObject

    113      Aggregation Level

    114      Fixed Value

    115      Hierarchy SID

    116      Hierarchy Level

    117      Name of New Aggregate:

    118      Unused InfoObjects

    120      SourceInfoCube Is Not A BasicCube. An Aggregate Cannot Be Created

    121      The Specified Aggregate Does Not Exist

    122      COB_PRO Does Not Exist For This InfoCube

    123      New Aggregate Definition Would Be Empty. Aggregate Not Created

    124      No Authorization To Create Aggregates

    125      Aggregate Cannot Be Created As Transaction Is Locked By:

    126      Transferred InfoObjects in Aggregate

    127      InfoCube-Specific InfoObjects in Aggregate

    128      TargetInfoCube Is Not A BasicCube. An Aggregate Cannot Be Created 

    source link: https://www.sdn.sap.com/irj/sdn/weblogs?blog=/pub/wlg/8352

  • 相关阅读:
    java与C#区别1
    简单解决Linq多条件组合问题<转>
    散列表(哈希表)工作原理<转>
    在Eclipse中设置中文JavaDOC<转>
    Cucumber入门之_argument
    Cucumber入门之Gherkin
    网上常用免费WebServices集合
    watir学习baidu搜索示例
    使用Cucumber的15个建议
    Cucumber入门之_World
  • 原文地址:https://www.cnblogs.com/xiaomaohai/p/6157067.html
Copyright © 2011-2022 走看看