Wednesday, April 19, 2017

Splitter container in full screen - two ways

The Goal

is to have fully occupied space of the screen without usage of any tool of screen painter. Just the blank screen is enough, the rest is matter of below coding. In advance let me say, the second solution is much better :)

1) Docking container


The very first way is docking container, which is able to occupy whole screen very easily. See the coding below:


  DATA:
* Reference Variable for Docking Container
  go_dock_container  TYPE REF TO cl_gui_docking_container,
  go_split_container TYPE REF TO cl_gui_splitter_container.

  CREATE OBJECT go_dock_container
    EXPORTING
      repid        sy-repid " Report Name
      dynnr        sy-dynnr " Screen Number
      side                        cl_gui_docking_container=>dock_at_bottom
      extension                   cl_gui_docking_container=>ws_maximizebox

    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_split_container
    EXPORTING
      parent            go_dock_container " Parent Container
      rows              " Number of Rows to be displayed
      columns           " Number of Columns to be Displayed
    EXCEPTIONS
      cntl_error        1
      cntl_system_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.



The disadvantage of above solution is appearance of side resizing frame border. We need to occupy whole space, split it into two parts, but nothing else. You can not easily disable resizing on docking container.





2) Direct use of Splitter container


The the good message is that by removal of docking container we reach clean fully occupied screen without side resizing frame border.





See whole PBO coding:


  DATAgo_container_top   TYPE REF TO cl_gui_splitter_container,
        go_container_cell1 TYPE REF TO cl_gui_container,
        go_container_cell2 TYPE REF TO cl_gui_container,
        go_salv1           TYPE REF TO cl_salv_table,
        go_salv2           TYPE REF TO cl_salv_table,
        gt_data            TYPE STANDARD TABLE OF tstct,
        gx_msg             TYPE REF TO cx_salv_msg.

  CREATE OBJECT go_container_top
    EXPORTING
      link_dynnr        sy-dynnr " Screen Number
      link_repid        sy-repid " Report Name
      parent            cl_gui_container=>default_screen " Parent Container
      rows              " Number of Rows to be displayed
      columns           " Number of Columns to be Displayed
    EXCEPTIONS
      cntl_error        1
      cntl_system_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.

*   get part of splitter container for 1st table
  CALL METHOD go_container_top->get_container
    EXPORTING
      row       1
      column    1
    RECEIVING
      container go_container_cell1.

*   get part of splitter container for 2nd table
  CALL METHOD go_container_top->get_container
    EXPORTING
      row       2
      column    1
    RECEIVING
      container go_container_cell2.

  SELECT FROM tstct INTO TABLE gt_data WHERE sprsl 'E'.

  TRY.
      cl_salv_table=>factory(
      EXPORTING
        r_container go_container_cell1
      IMPORTING
        r_salv_table     go_salv1
      CHANGING
        t_table      gt_data ).
    CATCH cx_salv_msg INTO gx_msg.
      MESSAGE gx_msg TYPE 'E'.
  ENDTRY.

  TRY.
      cl_salv_table=>factory(
      EXPORTING
        r_container go_container_cell2
      IMPORTING
        r_salv_table     go_salv2
      CHANGING
        t_table      gt_data ).
    CATCH cx_salv_msg INTO gx_msg.
      MESSAGE gx_msg TYPE 'E'.
  ENDTRY.

  go_salv1->display).
  go_salv2->display).



Valuable hint taken from: http://inmyitkb.blogspot.com/2012/06/container-to-occupy-whole-screen.html 





Saturday, April 15, 2017

User parameters comparison tool (USR05)

This article just offers a small fast food program comparing parameters between two users. Some transactions use bunch of these params. During a tuning of a new user or in case of troubles is handy to compare them.

I was surprised that SUIM tx. does not offer such functionality. To keep all the comparison abilities on one place, I placed there buttons calling SUIM comparison tools too.

Because we use also an other PARID/PARVA based custom table with the same structure as USR05, I placed an option also to compare such table. You can add there as much radio buttons as you want.


How does it look like?


Input screen





Result screen


  • Red - parameter exists just on one side
  • Yellow - parameter exists on both sides, but the actual value differs
  • Green - parameter exists on both sides and the value fits


Sorted by Parameter ID




Sorted by equality status 





The source code:



*&---------------------------------------------------------------------*
*& Report  Y_USER_CMP
*&
*&---------------------------------------------------------------------*
*&
*&
*&---------------------------------------------------------------------*

REPORT y_user_cmp.

TYPESBEGIN OF sty_param_both.
TYPESparid   TYPE  memoryid.   " ID line including both sides, used later for sorting
TYPESparid1  TYPE  abap_bool.
TYPESparva1  TYPE  xuvalue.
TYPESparid2  TYPE  abap_bool.  " The second id has to be stored as well because we need to distinguish the case where id is present within both tables, but empty on one side
TYPESparva2  TYPE  xuvalue.
TYPESpartext TYPE  as4text.
TYPESstatus  TYPE  LENGTH 1" S = successfull comparison, E = id not exists on both sides, W = ID exists but values differ
TYPESt_color TYPE  lvc_t_scol.
TYPESEND OF sty_param_both.

TYPEStty_param_both TYPE STANDARD TABLE OF sty_param_both.


*----------------------------------------------------------------------*
*       CLASS lcl_alv DEFINITION
*----------------------------------------------------------------------*
*
*----------------------------------------------------------------------*
CLASS lcl_alv DEFINITION.

  PUBLIC SECTION.
    METHODS:
      constructor
        IMPORTING
          iv_usr1    TYPE xubname
          iv_usr2    TYPE xubname
          iv_tabname TYPE tabname
          it_param   TYPE tty_param_both,
      generate_alv.

  PRIVATE SECTION.

    TYPESBEGIN OF gt_t_heading,
      operand(12TYPE c,
      valtyp      TYPE char30,
      client      TYPE char10,
      system      TYPE char30,
    END   OF gt_t_heading.

    DATA:   v_usr1    TYPE xubname,
            v_usr2    TYPE xubname,
            v_tabname TYPE tabname,
            t_param   TYPE tty_param_both,
            o_salv    TYPE REF TO cl_salv_table,
            o_header  TYPE REF TO cl_salv_form_layout_grid,
            o_h_label TYPE REF TO cl_salv_form_label,
            o_h_flow  TYPE REF TO cl_salv_form_layout_flow,
            o_ex      TYPE REF TO cx_root.

    METHODS:
      set_columns,
      set_header,
      set_rows_color.

ENDCLASS.                    "lcl_alv DEFINITION

*----------------------------------------------------------------------*
*       CLASS lcl_alv IMPLEMENTATION
*----------------------------------------------------------------------*
*
*----------------------------------------------------------------------*
CLASS lcl_alv IMPLEMENTATION.

  METHODconstructor.

    super->constructor).

    v_usr1     iv_usr1.
    v_usr2     iv_usr2.
    v_tabname  iv_tabname.
    t_param    it_param.

  ENDMETHOD.                    "constructor

  METHOD generate_alv.

    TRY.
        cl_salv_table=>factory(
        IMPORTING
          r_salv_table o_salv
        CHANGING
          t_table      t_param
        ).
      CATCH cx_root INTO o_ex.
        MESSAGE o_ex TYPE 'E'.
    ENDTRY.

    me->set_header).
    me->set_columns).
    me->set_rows_color).

    o_salv->display).

  ENDMETHOD.                    "constructor

  METHOD set_columns.

    DATAlo_columns TYPE REF TO cl_salv_columns_table,
          lo_column  TYPE REF TO cl_salv_column_table,
          lv_title_s TYPE scrtext_s,
          lv_title_m TYPE scrtext_m,
          lv_title_l TYPE scrtext_l.

    lo_columns o_salv->get_columns).
    lo_columns->set_optimizeabap_true ).

    TRY.

        lv_title_s v_usr1.
        CONCATENATE v_usr1 space 'value' INTO lv_title_m RESPECTING BLANKS.
        CONCATENATE v_usr1 space 'value' INTO lv_title_l RESPECTING BLANKS.
        lo_column ?= lo_columns->get_column'PARVA1' ).
        lo_column->set_short_textlv_title_s ).
        lo_column->set_medium_textlv_title_m ).
        lo_column->set_long_textlv_title_l ).

        CLEARlv_title_slv_title_mlv_title_l.
        lv_title_s v_usr2.
        CONCATENATE v_usr2 space 'value' INTO lv_title_m RESPECTING BLANKS.
        CONCATENATE v_usr2 space 'value' INTO lv_title_l RESPECTING BLANKS.
        lo_column ?= lo_columns->get_column'PARVA2' ).
        lo_column->set_short_textlv_title_s ).
        lo_column->set_medium_textlv_title_m ).
        lo_column->set_long_textlv_title_l ).

        lo_column ?= lo_columns->get_column'PARID1' ).
        lo_column->set_visibleabap_false ).

        lo_column ?= lo_columns->get_column'PARID2' ).
        lo_column->set_visibleabap_false ).

        lo_column ?= lo_columns->get_column'STATUS' ).
        lo_column->set_visibleabap_false ).

      CATCH cx_salv_not_found.                          "#EC NO_HANDLER
    ENDTRY.

  ENDMETHOD.                    "set_columns

  METHOD set_header.

    " Simplified RSUSR050 code for header

    DATAlo_grid        TYPE REF TO cl_salv_form_layout_grid,
          lo_label       TYPE REF TO cl_salv_form_label,    "#EC NEEDED
          lo_text        TYPE REF TO cl_salv_form_text,     "#EC NEEDED
          lv_row         TYPE        i,
          lv_column      TYPE        i,
          lv_title       TYPE        LENGTH 100.

    CONCATENATE 'Comparison of user parameters for table ' space v_tabname INTO lv_title RESPECTING BLANKS.

    DATAlt_heading  TYPE STANDARD TABLE OF gt_t_heading,
          ls_heading  LIKE LINE OF lt_heading,
          lv_lsind      TYPE i.

    ls_heading-operand 'User'.
    ls_heading-valtyp  'Name'.
    ls_heading-client  'Client'.
    ls_heading-system  'System'.
    APPEND ls_heading TO lt_heading.

    CLEAR ls_heading.
    ls_heading-operand 'A'.
    ls_heading-valtyp  v_usr1.
    ls_heading-client  sy-mandt.
    ls_heading-system  sy-sysid.
    APPEND ls_heading TO lt_heading.

    CLEAR ls_heading.
    ls_heading-operand 'B'.
    ls_heading-valtyp  v_usr2.
    ls_heading-client  sy-mandt.
    ls_heading-system  sy-sysid.
    APPEND ls_heading TO lt_heading.

    CLEARlv_rowlv_column.

    CREATE OBJECT lo_grid.

    lo_grid->create_header_information(
      row     1
      column  1
      colspan 20
      text    lv_title
    ).

    lo_grid->add_row).

    READ TABLE lt_heading INTO ls_heading INDEX 1.
    lv_column 11.
    lo_label lo_grid->create_labelrow    =  3
    column  =  2
    text    =  ls_heading-operand ).

    lo_label lo_grid->create_labelrow    =  3
    column  =  5
    text    =  ls_heading-valtyp ).

    lv_column lv_column + 10.
    lo_label lo_grid->create_labelrow    =  3
    column  =  lv_column
    text    =  ls_heading-client ).

    lv_column lv_column + 10.
    lo_label lo_grid->create_labelrow     =  3
    column  =  lv_column
    text    =  ls_heading-system ).

    lv_row 4.
    LOOP AT lt_heading INTO ls_heading FROM 2.
      lv_column 11.
      lo_text lo_grid->create_textrow     =  lv_row
      column  =  2
      text    =  ls_heading-operand ).

      lo_text lo_grid->create_text(   row     =  lv_row
      column  =  5
      text    =  ls_heading-valtyp ).

      lv_column lv_column + 10.
      lo_text lo_grid->create_text(   row     =  lv_row
      column  =  lv_column
      text    =  ls_heading-client ).

      lv_column lv_column + 10.
      lo_text lo_grid->create_text(   row     =  lv_row
      column  =  lv_column
      text    =  ls_heading-system ).
      lv_row  lv_row + 1.
    ENDLOOP.

    o_salv->set_top_of_listlo_grid ).

  ENDMETHOD.                    "set_header

  METHOD set_rows_color.

    DATAlo_cols_tab TYPE REF TO cl_salv_columns_table,
          lt_s_color TYPE lvc_t_scol,
          ls_s_color TYPE lvc_s_scol.

    FIELD-SYMBOLS<fs_param> LIKE LINE OF t_param.
    LOOP AT t_param ASSIGNING <fs_param>.

      IF <fs_param>-parid1 IS INITIAL OR <fs_param>-parid2 IS INITIAL ).
        ls_s_color-color-col col_negative.
      ELSE.
        IF <fs_param>-parva1 NE <fs_param>-parva2 ).
          ls_s_color-color-col 3" yellow
        ELSE.
          ls_s_color-color-col col_positive.
        ENDIF.
      ENDIF.

      ls_s_color-color-int 0.
      ls_s_color-color-inv 0.
      APPEND ls_s_color TO lt_s_color.
      CLEAR  ls_s_color.

      <fs_param>-t_color lt_s_color.
      CLEAR  lt_s_color.
    ENDLOOP.

    lo_cols_tab o_salv->get_columns).
    TRY.
        lo_cols_tab->set_color_column'T_COLOR' ).
      CATCH cx_salv_data_error.
    ENDTRY.

  ENDMETHOD.                    "set_rows_color

ENDCLASS.                    "lcl_alv IMPLEMENTATION

*----------------------------------------------------------------------*
*       CLASS lcl_user_cmp DEFINITION
*----------------------------------------------------------------------*
*
*----------------------------------------------------------------------*
CLASS lcl_user_cmp DEFINITION.

  PUBLIC SECTION.

    METHODS compare_users
              IMPORTING iv_usr1       TYPE xubname
                        iv_usr2       TYPE xubname
                        iv_tabname    TYPE tabname
                        iv_sort_parid TYPE abap_bool.

    CLASS-METHODS get_instance RETURNING value(ro_objTYPE REF TO lcl_user_cmp.
    CLASS-METHODS check_authorization.

  PRIVATE SECTION.

    TYPEStty_param      TYPE STANDARD TABLE OF usparam.

    CLASS-DATAo_user_cmp TYPE REF TO lcl_user_cmp.

    DATAo_alv TYPE REF TO lcl_alv.

    METHODS get_user_param
              IMPORTING iv_usr     TYPE xubname
              EXPORTING et_param  TYPE tty_param.

ENDCLASS.                    "lcl_user_cmp DEFINITION


*----------------------------------------------------------------------*
*       CLASS lcl_user_cmp IMPLEMENTATION
*----------------------------------------------------------------------*
*
*----------------------------------------------------------------------*
CLASS lcl_user_cmp IMPLEMENTATION.

  METHOD compare_users.

    DATAlt_param1     TYPE tty_param,
          lt_param2     TYPE tty_param,
          lt_param_both TYPE STANDARD TABLE OF sty_param_both,
          ls_param_both LIKE LINE OF lt_param_both.

    me->get_user_param(
          EXPORTING
          iv_usr    iv_usr1
          IMPORTING
            et_param lt_param1
    ).

    me->get_user_param(
          EXPORTING
            iv_usr    iv_usr2
          IMPORTING
            et_param lt_param2
    ).

    FIELD-SYMBOLS<fs_param> TYPE usparam.

    " store whole first table
    LOOP AT lt_param1 ASSIGNING <fs_param>.
      CLEAR ls_param_both.
      ls_param_both-parid   <fs_param>-parid.
      ls_param_both-parid1  abap_true.
      ls_param_both-parva1  <fs_param>-parva.
      ls_param_both-partext <fs_param>-partext.
      ls_param_both-status  'E'" ID does not fit by default
      APPEND ls_param_both TO lt_param_both.
    ENDLOOP.

    " loop over second param table
    LOOP AT lt_param2 ASSIGNING <fs_param>.

      CLEAR ls_param_both.

      READ TABLE lt_param_both INTO ls_param_both WITH KEY parid <fs_param>-parid.
      IF sy-subrc EQ 0.
        " The same ID already exists, alter existing row
        ls_param_both-parid2  abap_true.
        ls_param_both-parva2  <fs_param>-parva.

        IF ls_param_both-parva1 EQ <fs_param>-parva.
          ls_param_both-status  'S'.
        ELSE.
          ls_param_both-status  'W'.
        ENDIF.

        MODIFY lt_param_both FROM ls_param_both INDEX sy-tabix TRANSPORTING parid2 parva2 status.
      ELSE.
        " Insert complete new row
        ls_param_both-parid   <fs_param>-parid.
        ls_param_both-parid2  abap_true.
        ls_param_both-parva2  <fs_param>-parva.
        ls_param_both-partext <fs_param>-partext.
        ls_param_both-status  'E'.
        APPEND ls_param_both TO lt_param_both.
      ENDIF.
    ENDLOOP.

    IF iv_sort_parid EQ abap_true.
      SORT lt_param_both BY parid.
    ELSE.
      SORT lt_param_both BY status.
    ENDIF.

    FREE o_alv.

    CREATE OBJECT o_alv
      EXPORTING
        iv_usr1    iv_usr1
        iv_usr2    iv_usr2
        iv_tabname iv_tabname
        it_param   lt_param_both.

    o_alv->generate_alv).

  ENDMETHOD.                    "compare_users

  METHOD get_instance.

    IF o_user_cmp IS NOT BOUND.
      CREATE OBJECT o_user_cmp.
    ENDIF.

    ro_obj o_user_cmp.

  ENDMETHOD.                    "get_instance

  METHOD check_authorization.

    CLEARsy-msgidsy-msgtysy-msgnosy-msgv1sy-msgv2sy-msgv3sy-msgv4.

    CALL FUNCTION 'AUTHORITY_CHECK_TCODE'
      EXPORTING
        tcode  'SU01D'
      EXCEPTIONS
        ok     0
        not_ok 1
        OTHERS 2.

    IF sy-subrc <> 0.
      IF sy-msgid IS INITIAL OR sy-msgty IS INITIAL.
        MESSAGE i172(00DISPLAY LIKE 'I' WITH sy-tcode.
      ELSE.
        MESSAGE ID sy-msgid TYPE sy-msgty NUMBER sy-msgno
        DISPLAY LIKE sy-msgty
        WITH sy-msgv1 sy-msgv2 sy-msgv3 sy-msgv4.
      ENDIF.
      LEAVE PROGRAM.
    ENDIF.

  ENDMETHOD.                    "check_authorization

  METHOD get_user_param.

    CALL FUNCTION 'SUSR_USER_PARAMETERS_GET'
      EXPORTING
        user_name           iv_usr
        with_text           space
      TABLES
        user_parameters     et_param
      EXCEPTIONS
        user_name_not_exist 1
        OTHERS              2.

  ENDMETHOD.                    "check_authorization

ENDCLASS.                    "lcl_user_cmp IMPLEMENTATION


DATA:  go_user_cmp TYPE REF TO lcl_user_cmp,
       gv_tabname  TYPE tabname.

TABLES sscrfields.

" Usernames
SELECTION-SCREEN BEGIN OF BLOCK bl_users WITH FRAME TITLE tx_01.
SELECTION-SCREEN BEGIN OF LINE.
SELECTION-SCREEN COMMENT 1(6tx_02 FOR FIELD p_usr1.
PARAMETERS p_usr1 TYPE xubname MATCHCODE OBJECT user_addr.
SELECTION-SCREEN COMMENT 40(6tx_03 FOR FIELD p_usr2.
PARAMETERS p_usr2 TYPE xubname MATCHCODE OBJECT user_addr.
SELECTION-SCREEN END OF LINE.
SELECTION-SCREEN END OF BLOCK bl_users.

" Table choice
SELECTION-SCREEN BEGIN OF BLOCK bl_tabs WITH FRAME TITLE tx_08.
SELECTION-SCREEN BEGIN OF LINE.
PARAMETERS r_tab1 RADIOBUTTON GROUP rg1.
SELECTION-SCREEN COMMENT 4(23tx_04 FOR FIELD r_tab1.
SELECTION-SCREEN END OF LINE.
SELECTION-SCREEN BEGIN OF LINE.
PARAMETERS r_tab2 RADIOBUTTON GROUP rg1.
SELECTION-SCREEN COMMENT 4(23tx_05 FOR FIELD r_tab2.
SELECTION-SCREEN END OF LINE.
SELECTION-SCREEN END OF BLOCK bl_tabs.

" Sort choice
SELECTION-SCREEN BEGIN OF BLOCK bl_sort WITH FRAME TITLE tx_09.
SELECTION-SCREEN BEGIN OF LINE.
PARAMETERS r_sort1 RADIOBUTTON GROUP rg2.
SELECTION-SCREEN COMMENT 4(24tx_06 FOR FIELD r_sort1.
SELECTION-SCREEN END OF LINE.
SELECTION-SCREEN BEGIN OF LINE.
PARAMETERS r_sort2 RADIOBUTTON GROUP rg2.
SELECTION-SCREEN COMMENT 4(24tx_07 FOR FIELD r_sort2.
SELECTION-SCREEN END OF LINE.
SELECTION-SCREEN END OF BLOCK bl_sort.

SELECTION-SCREEN PUSHBUTTON 1(25tx_10 USER-COMMAND onli.

************************************************************************
INITIALIZATION.
************************************************************************
  " Authorization
  lcl_user_cmp=>check_authorization).

  " Get main class instance
  go_user_cmp lcl_user_cmp=>get_instance).

  " Screen buttons for SUIM comaprison programs
  SELECTION-SCREEN FUNCTION KEY 1.
  SELECTION-SCREEN FUNCTION KEY 2.
  SELECTION-SCREEN FUNCTION KEY 3.
  SELECTION-SCREEN FUNCTION KEY 4.

  " Selection screen texts
  tx_01 'Compare user parameters for:'.
  tx_02 'User A'.
  tx_03 'User B'.
  tx_04 'User parameters (USR05)'.
  tx_05 'User parameters (ZPC01)'.
  tx_06 'Sort by PARAM id (ABC)'.
  tx_07 'Sort by Differences'.
  tx_08 'Choose parameter table'.
  tx_09 'Choose sort'.
  tx_10 'Compare user parameters'.
  sscrfields-functxt_01 'Compare Users'.
  sscrfields-functxt_02 'Roles'.
  sscrfields-functxt_03 'Profiles'.
  sscrfields-functxt_04 'Authorizations'.


************************************************************************
AT SELECTION-SCREEN.
************************************************************************

  CASE sy-ucomm.
    WHEN 'FC01'.
      SUBMIT rsusr050 VIA SELECTION-SCREEN USING SELECTION-SET 'SAP&_BENUTZER' AND RETURN.
    WHEN 'FC02'.
      SUBMIT rsusr050 VIA SELECTION-SCREEN USING SELECTION-SET 'SAP&_ROLLE' AND RETURN.
    WHEN 'FC03'.
      SUBMIT rsusr050 VIA SELECTION-SCREEN USING SELECTION-SET 'SAP&_PROFILE' AND RETURN.
    WHEN 'FC04'.
      SUBMIT rsusr050 VIA SELECTION-SCREEN USING SELECTION-SET 'SAP&_BERECHTIG' AND RETURN.
    WHEN OTHERS.
      IF p_usr1 IS INITIAL OR p_usr2 IS INITIAL ).
        MESSAGE e279(01DISPLAY LIKE 'I'.
      ENDIF.
  ENDCASE.


************************************************************************
START-OF-SELECTION.
************************************************************************

  " Run comparison for table:
  CASE abap_true.
    WHEN r_tab1.
      gv_tabname 'USR05'.
    WHEN r_tab2.
      gv_tabname 'ZUSER_TAB'.
  ENDCASE.

  go_user_cmp->compare_usersiv_usr1       p_usr1
                              iv_usr2       p_usr2
                              iv_tabname    gv_tabname
                              iv_sort_parid r_sort1
                            ).

END-OF-SELECTION.