zoukankan      html  css  js  c++  java
  • SAP Container Controls(容器)

    BC_CONTROLS_TUTORIAL

    效果

     代码

    REPORT bc_controls_tutorial.
    *--------------------------------------------------------------
    * This report is the result of all exercises described in the
    * "Controls Tutorial".
    *--------------------------------------------------------------
    *
    
    
    *( Code added in: Lesson 1, Exercise 2
    DATA: custom_container TYPE REF TO cl_gui_custom_container,
          editor TYPE REF TO cl_gui_textedit,
          repid LIKE sy-repid.
    CONSTANTS: line_length TYPE i VALUE 256.
    *)
    
    *( Code added in: Lesson 3, Exercise 4
    DATA: scratch TYPE REF TO cl_gui_textedit,
         custom_container2 TYPE REF TO cl_gui_custom_container.
    *)
    
    *( Code added in: Lesson 1, Exercise 3
    TYPES: BEGIN OF mytable_line,
              line(line_length) TYPE c,
              END OF mytable_line.
    DATA: mytable TYPE TABLE OF mytable_line,
          textstruct TYPE mytable_line,
          g_loaded TYPE c.
    *)
    
    *( Code added in: Lesson 2, Exercise 2
    DATA events TYPE cntl_simple_events.
    DATA wa_events TYPE cntl_simple_event.
    *)
    
    *( Code added in: Lesson 2, Exercise 1
    DATA: event_type(20) TYPE c.
    *---------------------------------------------------------------------*
    *       CLASS lcl_event_handler DEFINITION
    *---------------------------------------------------------------------*
    *       ........                                                      *
    *---------------------------------------------------------------------*
    CLASS lcl_event_handler DEFINITION.
    
      PUBLIC SECTION.
        CLASS-METHODS: catch_dblclick
                           FOR EVENT dblclick OF cl_gui_textedit
                           IMPORTING sender.
    ENDCLASS.
    
    DATA: event_handler TYPE REF TO lcl_event_handler.
    
    *---------------------------------------------------------------------*
    *       CLASS lcl_event_handler IMPLEMENTATION
    *---------------------------------------------------------------------*
    *       ........                                                      *
    *---------------------------------------------------------------------*
    CLASS lcl_event_handler IMPLEMENTATION.
      METHOD catch_dblclick.
    
    *( Code added in: Lesson 2, Exercise 4
        DATA: from_line TYPE i,
               from_pos TYPE i,
               to_line TYPE i,
               to_pos TYPE i.
        CALL METHOD sender->get_selection_pos
            IMPORTING
                    from_line = from_line
                    from_pos = from_pos
                    to_line = to_line
                    to_pos = to_pos.
    
        IF not g_loaded is initial.
          CALL METHOD sender->get_text_as_r3table
            IMPORTING
                   table = mytable.
        ENDIF.
    
        READ TABLE mytable INDEX from_line INTO textstruct.
        IF sy-subrc = 0.
          IF textstruct+0(1) cs '*'.
            SHIFT textstruct.
          ELSEIF textstruct+0(1) ns '*'.
            SHIFT textstruct RIGHT.
            textstruct+0(1) = '*'.
          ENDIF.
    
          MODIFY mytable FROM textstruct INDEX from_line.
          CALL METHOD sender->set_text_as_r3table
             EXPORTING table = mytable
          EXCEPTIONS
             OTHERS = 1.
        ENDIF.
    
        CALL METHOD cl_gui_cfw=>flush.
        IF sy-subrc ne 0.
          CALL FUNCTION 'POPUP_TO_INFORM'
               EXPORTING
                    titel = repid
                    txt2  = sy-subrc
                    txt1  = 'Method CATCH_DBLCLICK: Error in Flush!'(602).
        ENDIF.
    *)
    
    *( Code changed in Lesson 2, Exercise 3
    * (event_type is set at PAI time now!)
    *    event_type = text-002.
    
    * (added)
        CALL METHOD cl_gui_cfw=>set_new_ok_code
             EXPORTING new_code = 'SHOW'.
    *)
    
      ENDMETHOD.
    ENDCLASS.
    *)
    
    
    *( Code added in: Lesson 1, Exercise 1
    DATA  ok_code LIKE sy-ucomm.
    
    START-OF-SELECTION.
      SET SCREEN '100'.
    *)
    
    
    *&---------------------------------------------------------------------*
    *&      Module  USER_COMMAND_0100  INPUT
    *&---------------------------------------------------------------------*
    *       text
    *----------------------------------------------------------------------*
    
    *( Code added in: Lesson 1, Exercise 1
    MODULE user_command_0100 INPUT.
    
      CASE ok_code.
        WHEN 'EXIT'.
          LEAVE TO SCREEN 0.
    *( Code added in: Lesson 1, Exercise 3
        WHEN 'IMP'.
          PERFORM load_tab.
    *)
    
    *( Code added in: Lesson 2, Exercise 3
        WHEN 'SHOW'.
          event_type = 'Doubleclick'(555).
    *)
    
    *( Code added in: Lesson 3, Exercise 1
        WHEN 'PROTECT'.
          DATA: from_idx TYPE i,
                to_idx TYPE i,
                index TYPE i.
    *( Code added in: Lesson 3, Exercise 3
    * remark: In this exercise, the calls GET_SELECTION_POS and
    *         GET_FIRST_VISIBLE LINE are copied to Form GET_LINES.
          PERFORM get_lines CHANGING from_idx to_idx index.
    *### Note: There is no Flush call in form GET_LINES!
    *)
    
    *(
    * Code added in: Lesson 3, Exercise 2
          CALL METHOD cl_gui_cfw=>flush.
          IF sy-subrc ne 0.
            CALL FUNCTION 'POPUP_TO_INFORM'
                 EXPORTING
                      titel = repid
                      txt2  = sy-subrc
                      txt1 =
                         'PAI USER_COMMAND_100(1): Error in Flush!'(603).
          ENDIF.
          IF from_idx = index.
            MESSAGE i208(00) WITH text-003.
            EXIT.
          ENDIF.
    *)
    
          LOOP AT mytable INTO textstruct.
            IF ( sy-tabix >= from_idx and sy-tabix <= to_idx ).
              index = sy-tabix.
              CALL METHOD editor->protect_lines
                      EXPORTING from_line = index
                                to_line   = index.
            ENDIF.
          ENDLOOP.
          CALL METHOD cl_gui_cfw=>flush.
          IF sy-subrc ne 0.
            CALL FUNCTION 'POPUP_TO_INFORM'
                 EXPORTING
                      titel = repid
                      txt2  = sy-subrc
                      txt1 =
                         'PAI USER_COMMAND_100(2): Error in Flush!'(604).
          ENDIF.
    *)
    
    *( Code added in: Lesson 2, Exercise 2
        WHEN OTHERS.
    *(
    * The following line was commented out in Lesson 2, Exercise 3
    * (DISPATCH is not needed when using system events only)
    *      CALL METHOD cl_gui_cfw=>dispatch.
    *)
    
      ENDCASE.
    *)
    ENDMODULE.                             " USER_COMMAND_0100  INPUT
    *&---------------------------------------------------------------------*
    *&      Module  STATUS_0100  OUTPUT
    *&---------------------------------------------------------------------*
    *       text
    *----------------------------------------------------------------------*
    MODULE status_0100 OUTPUT.
    *  SET PF-STATUS 'xxxxxxxx'.
    *  SET TITLEBAR 'xxx'.
    *( Code added in: Lesson 1, Exercise 2
      IF editor is initial.
        repid = sy-repid.
        CREATE OBJECT custom_container
           EXPORTING
              container_name = 'MYCONTAINER1'
           EXCEPTIONS
              cntl_error = 1
              cntl_system_error = 2
              create_error = 3
              lifetime_error = 4
              lifetime_dynpro_dynpro_link = 5.
    
        CREATE OBJECT editor
           EXPORTING
              parent = custom_container
              wordwrap_mode = cl_gui_textedit=>wordwrap_at_fixed_position
              wordwrap_position = line_length
              wordwrap_to_linebreak_mode = cl_gui_textedit=>true.
    
    * ( Code added in: Lesson 2, Exercise 2
        wa_events-eventid = cl_gui_textedit=>event_double_click.
    
    *( Code changed in: Lesson 2, Exercise 3
    *   wa_events-appl_event = 'X'.
        wa_events-appl_event = space.
    *)
        APPEND wa_events TO events.
        CALL METHOD editor->set_registered_events
              EXPORTING events = events.
    * )
    
    *( Code added in: Lesson 1, Exercise 1
        SET HANDLER event_handler->catch_dblclick FOR editor.
    *)
    
    *( Code added in: Lesson 3, Exercise 4
        CREATE OBJECT custom_container2
              EXPORTING
                 container_name = 'MYCONTAINER2'
              EXCEPTIONS
                 cntl_error = 1
                 cntl_system_error = 2
                 create_error = 3
                 lifetime_error = 4
                 lifetime_dynpro_dynpro_link = 5.
    
    
        CREATE OBJECT scratch
           EXPORTING
              parent = custom_container2
              wordwrap_mode = cl_gui_textedit=>wordwrap_at_windowborder
              wordwrap_to_linebreak_mode = cl_gui_textedit=>true.
        CALL METHOD scratch->set_statusbar_mode
           EXPORTING
              statusbar_mode = cl_gui_textedit=>false.
    *)
    
    *( Code added in: Lesson 1, Exercise 3
        DO 20 TIMES.
          WRITE text-001 TO textstruct-line.
          APPEND textstruct TO mytable.
        ENDDO.
    *)
      ENDIF.                               "editor is initial
    *)
    
    
    
    
    
    ENDMODULE.                             " STATUS_0100  OUTPUT
    *&---------------------------------------------------------------------*
    *&      Form  load_tab
    *&---------------------------------------------------------------------*
    *       text
    *----------------------------------------------------------------------*
    *  -->  p1        text
    *  <--  p2        text
    *----------------------------------------------------------------------*
    FORM load_tab.
    *( Code added in: Lesson 1, Exercise 3
      CALL METHOD editor->set_text_as_r3table
                EXPORTING table = mytable
         EXCEPTIONS
             OTHERS = 1.
      IF sy-subrc ne 0.
        CALL FUNCTION 'POPUP_TO_INFORM'
             EXPORTING
                  titel = repid
                  txt2  = ' '
                  txt1  = 'Error in set_text_as_r3table'(600).
      ELSE.
        g_loaded = 'X'.
      ENDIF.
      CALL METHOD cl_gui_cfw=>flush.
      IF sy-subrc ne 0.
        CALL FUNCTION 'POPUP_TO_INFORM'
             EXPORTING
                  titel = repid
                  txt2  = sy-subrc
                  txt1  = 'Form LOAD_TAB: Error in FLUSH'(601).
      ENDIF.
    *)
    
    ENDFORM.                               " load_tab
    *&---------------------------------------------------------------------*
    *&      Form  GET_LINES
    *&---------------------------------------------------------------------*
    *       text
    *----------------------------------------------------------------------*
    *      <--P_FROM_IDX  text
    *      <--P_TO_IDX  text
    *      <--P_INDEX  text
    *----------------------------------------------------------------------*
    FORM get_lines CHANGING from_idx TYPE i
                            to_idx   TYPE i
                            index    TYPE i.
    *###(
    *### The following code block has been moved from PAI to form GET_LINES
    *### in Lesson 3, Exercise 3
      CALL METHOD editor->get_selection_pos
             IMPORTING
                from_line = from_idx
                to_line = to_idx
      EXCEPTIONS
                error_cntl_call_method = 1.
    *( Code added in: Lesson 3, Exercise 2
      CALL METHOD editor->get_first_visible_line
               IMPORTING
                   line = index
               EXCEPTIONS
                   error_cntl_call_method = 1.
    *)
    * Note: The flush is made after returning from this form!
    
    ENDFORM.                               " GET_LINES

    Customer container

    效果

    *&---------------------------------------------------------------------*
    *& Report  RSDEMO_CUSTOM_CONTROL                                       *
    *&                                                                     *
    *&---------------------------------------------------------------------*
    *&                                                                     *
    *&                                                                     *
    *&---------------------------------------------------------------------*
    
    REPORT  rsdemo_custom_control         .
    DATA  url(132).
    
    TYPE-POOLS cndp.
    * custom container
    DATA container TYPE REF TO cl_gui_custom_container.
    * picture Control.
    DATA picture TYPE REF TO cl_gui_picture.
    * Definition of Control Framework
    CLASS cl_gui_cfw DEFINITION LOAD.
    
    DATA  init.
    DATA ok_code TYPE sy-ucomm.
    
    CALL SCREEN 100.
    
    *&---------------------------------------------------------------------*
    *&      Module  STATUS_0100  OUTPUT
    *&---------------------------------------------------------------------*
    *       text
    *----------------------------------------------------------------------*
    MODULE status_0100 OUTPUT.
      SET PF-STATUS 'STATUS'.
    *  SET TITLEBAR 'xxx'.
      IF init is initial.
    * create the custom container
        CREATE OBJECT container
                      EXPORTING container_name = 'CUSTOM'.
    * create the picture control
        CREATE OBJECT picture
                      EXPORTING parent = container.
    
    * Request an URL from the data provider by exporting the pic_data.
    
        CLEAR URL.
        PERFORM LOAD_PIC_FROM_DB CHANGING URL.
    
    * load picture
        CALL METHOD picture->load_picture_from_url
            EXPORTING url = url.
        init = 'X'.
    
        CALL METHOD cl_gui_cfw=>flush
             EXCEPTIONS cntl_system_error = 1
                        cntl_error = 2.
        IF sy-subrc <> 0.
    * error handling
        ENDIF.
      ENDIF.
    ENDMODULE.                             " STATUS_0100  OUTPUT
    
    *&---------------------------------------------------------------------*
    *&      Module  EXIT  INPUT
    *&---------------------------------------------------------------------*
    *       text
    *----------------------------------------------------------------------*
    MODULE exit INPUT.
      CALL METHOD picture->free.
      CALL METHOD container->free.
      FREE picture.
      FREE container.
      LEAVE PROGRAM.
    ENDMODULE.                             " EXIT  INPUT
    *&---------------------------------------------------------------------*
    *&      Form  LOAD_PIC_FROM_DB
    *&---------------------------------------------------------------------*
    *       text
    *----------------------------------------------------------------------*
    *
    *----------------------------------------------------------------------*
    FORM LOAD_PIC_FROM_DB CHANGING URL.
      DATA QUERY_TABLE LIKE W3QUERY OCCURS 1 WITH HEADER LINE.
      DATA HTML_TABLE LIKE W3HTML OCCURS 1.
      DATA RETURN_CODE LIKE  W3PARAM-RET_CODE.
      DATA CONTENT_TYPE LIKE  W3PARAM-CONT_TYPE.
      DATA CONTENT_LENGTH LIKE  W3PARAM-CONT_LEN.
      DATA PIC_DATA LIKE W3MIME OCCURS 0.
      DATA PIC_SIZE TYPE I.
    
      REFRESH QUERY_TABLE.
      QUERY_TABLE-NAME = '_OBJECT_ID'.
      QUERY_TABLE-VALUE = 'ENJOYSAP_LOGO'.
      APPEND QUERY_TABLE.
    
      CALL FUNCTION 'WWW_GET_MIME_OBJECT'
           TABLES
                QUERY_STRING        = QUERY_TABLE
                HTML                = HTML_TABLE
                MIME                = PIC_DATA
           CHANGING
                RETURN_CODE         = RETURN_CODE
                CONTENT_TYPE        = CONTENT_TYPE
                CONTENT_LENGTH      = CONTENT_LENGTH
           EXCEPTIONS
                OBJECT_NOT_FOUND    = 1
                PARAMETER_NOT_FOUND = 2
                OTHERS              = 3.
      if sy-subrc = 0.
        PIC_SIZE = CONTENT_LENGTH.
      endif.
    
    CALL FUNCTION 'DP_CREATE_URL'
             EXPORTING
                  TYPE     = 'image'
                  SUBTYPE  = cndp_sap_tab_unknown
                  SIZE     = PIC_SIZE
                  lifetime = cndp_lifetime_transaction
             TABLES
                  DATA     = PIC_DATA
             CHANGING
                  URL      = URL
             EXCEPTIONS
                  others   = 1.
    
    
    ENDFORM.                    " LOAD_PIC_FROM_DB

    Docking container

    效果

    *&---------------------------------------------------------------------*
    *& Report  RSDEMO_DOCKING_CONTROL                                      *
    *&                                                                     *
    *&---------------------------------------------------------------------*
    *&                                                                     *
    *&                                                                     *
    *&---------------------------------------------------------------------*
    
    REPORT  rsdemo_docking_control         .
    
    * Docking Container
    DATA docking TYPE REF TO cl_gui_docking_container.
    * Picture Control
    DATA picture TYPE REF TO cl_gui_picture.
    * Definition of Control Framework
    TYPE-POOLS cndp.
    
    DATA  init.
    DATA ok_code TYPE sy-ucomm.
    DATA repid TYPE sy-repid.
    DATA dynnr TYPE sy-dynnr.
    
    CALL SCREEN 100.
    
    *&---------------------------------------------------------------------*
    *&      Module  STATUS_0100  OUTPUT
    *&---------------------------------------------------------------------*
    *       text
    *----------------------------------------------------------------------*
    MODULE status_0100 OUTPUT.
      SET PF-STATUS 'STATUS'.
    *  SET TITLEBAR 'xxx'.
      IF init is initial.
        repid = sy-repid.
        dynnr = sy-dynnr.
    * create the docking container
        CREATE OBJECT docking
                      EXPORTING repid     = repid
                                dynnr     = dynnr
                                side      = docking->dock_at_left
                                extension = 180.
    * create the picture container
        CREATE OBJECT picture
                      EXPORTING parent = docking.
    
    * Request an URL from the data provider by exporting the pic_data.
        DATA url(255).
        CLEAR url.
        PERFORM load_pic_from_db CHANGING url.
    
    * load picture
        CALL METHOD picture->load_picture_from_url
            EXPORTING url = url.
        init = 'X'.
    
      ENDIF.
    ENDMODULE.                             " STATUS_0100  OUTPUT
    
    *&---------------------------------------------------------------------*
    *&      Module  EXIT  INPUT
    *&---------------------------------------------------------------------*
    *       text
    *----------------------------------------------------------------------*
    MODULE exit INPUT.
      CALL METHOD docking->free.
      LEAVE PROGRAM.
    ENDMODULE.                             " EXIT  INPUT
    
    *&---------------------------------------------------------------------*
    *&      Form  LOAD_PIC_FROM_DB
    *&---------------------------------------------------------------------*
    *       text
    *----------------------------------------------------------------------*
    *
    *----------------------------------------------------------------------*
    FORM load_pic_from_db CHANGING url.
      DATA query_table LIKE w3query OCCURS 1 WITH HEADER LINE.
      DATA html_table LIKE w3html OCCURS 1.
      DATA return_code LIKE  w3param-ret_code.
      DATA content_type LIKE  w3param-cont_type.
      DATA content_length LIKE  w3param-cont_len.
      DATA pic_data LIKE w3mime OCCURS 0.
      DATA pic_size TYPE i.
    
      REFRESH query_table.
      query_table-name = '_OBJECT_ID'.
      query_table-value = 'ENJOYSAP_LOGO'.
      APPEND query_table.
    
      CALL FUNCTION 'WWW_GET_MIME_OBJECT'
           TABLES
                query_string        = query_table
                html                = html_table
                mime                = pic_data
           CHANGING
                return_code         = return_code
                content_type        = content_type
                content_length      = content_length
           EXCEPTIONS
                OBJECT_NOT_FOUND    = 1
                parameter_not_found = 2
                OTHERS              = 3.
      IF sy-subrc = 0.
        pic_size = content_length.
      ENDIF.
    
      CALL FUNCTION 'DP_CREATE_URL'
           EXPORTING
                type     = 'image'
                subtype  = cndp_sap_tab_unknown
                size     = pic_size
                lifetime = cndp_lifetime_transaction
           TABLES
                data     = pic_data
           CHANGING
                url      = url
           EXCEPTIONS
                OTHERS   = 1.
    
    
    ENDFORM.                               " LOAD_PIC_FROM_DB

    Spliter container

    效果

    *&---------------------------------------------------------------------*
    *& Report  RSDEMO_SPLITTER_CONTROL                                     *
    *&                                                                     *
    *&---------------------------------------------------------------------*
    *&                                                                     *
    *&                                                                     *
    *&---------------------------------------------------------------------*
    
    REPORT  rsdemo_splitter_control         .
    DATA  url(132).
    
    DATA splitter TYPE REF TO cl_gui_splitter_container.
    DATA container TYPE REF TO cl_gui_custom_container.
    DATA container_1 TYPE REF TO cl_gui_container.
    DATA container_2 TYPE REF TO cl_gui_container.
    DATA picture_1 TYPE REF TO cl_gui_picture.
    DATA picture_2 TYPE REF TO cl_gui_picture.
    DATA  init.
    DATA ok_code TYPE sy-ucomm.
    
    TYPE-POOLS cndp.
    
    
    CALL SCREEN 100.
    
    *&---------------------------------------------------------------------*
    *&      Module  STATUS_0100  OUTPUT
    *&---------------------------------------------------------------------*
    *       text
    *----------------------------------------------------------------------*
    MODULE status_0100 OUTPUT.
      SET PF-STATUS 'STATUS'.
      IF init is initial.
        CREATE OBJECT container
                      EXPORTING container_name = 'CUSTOM'.
        CREATE OBJECT splitter
                      EXPORTING parent = container
                                rows    = 1
                                columns = 2.
        CALL METHOD splitter->get_container
                          EXPORTING row      = 1
                                    column   = 1
                          RECEIVING container = container_1.
        CALL METHOD splitter->get_container
                      EXPORTING row      = 1
                                column   = 2
                      RECEIVING container = container_2.
    
        CREATE OBJECT picture_1
                      EXPORTING parent  = container_1.
    
    
        CREATE OBJECT picture_2
                      EXPORTING parent  = container_2.
    
    * Request an URL from the data provider by exporting the pic_data.
        CLEAR url.
        PERFORM load_pic_from_db CHANGING url.
    
    * load picture
        CALL METHOD picture_1->load_picture_from_url
            EXPORTING url = url.
    
        CALL METHOD picture_2->load_picture_from_url
            EXPORTING url = url.
    
        init = 'X'.
    
        CALL METHOD cl_gui_cfw=>flush
             EXCEPTIONS cntl_system_error = 1
                        cntl_error = 2.
        IF sy-subrc <> 0.
    * error handling
        ENDIF.
      ENDIF.
    ENDMODULE.                             " STATUS_0100  OUTPUT
    
    *&---------------------------------------------------------------------*
    *&      Module  EXIT  INPUT
    *&---------------------------------------------------------------------*
    *       text
    *----------------------------------------------------------------------*
    MODULE exit INPUT.
      CALL METHOD container->free.
      LEAVE PROGRAM.
    ENDMODULE.                             " EXIT  INPUT
    
    *&---------------------------------------------------------------------*
    *&      Form  LOAD_PIC_FROM_DB
    *&---------------------------------------------------------------------*
    *       text
    *----------------------------------------------------------------------*
    *
    *----------------------------------------------------------------------*
    FORM load_pic_from_db CHANGING url.
      DATA query_table LIKE w3query OCCURS 1 WITH HEADER LINE.
      DATA html_table LIKE w3html OCCURS 1.
      DATA return_code LIKE  w3param-ret_code.
      DATA content_type LIKE  w3param-cont_type.
      DATA content_length LIKE  w3param-cont_len.
      DATA pic_data LIKE w3mime OCCURS 0.
      DATA pic_size TYPE i.
    
      REFRESH query_table.
      query_table-name = '_OBJECT_ID'.
      query_table-value = 'ENJOYSAP_LOGO'.
      APPEND query_table.
    
      CALL FUNCTION 'WWW_GET_MIME_OBJECT'
           TABLES
                query_string        = query_table
                html                = html_table
                mime                = pic_data
           CHANGING
                return_code         = return_code
                content_type        = content_type
                content_length      = content_length
           EXCEPTIONS
                OBJECT_NOT_FOUND    = 1
                parameter_not_found = 2
                OTHERS              = 3.
      IF sy-subrc = 0.
        pic_size = content_length.
      ENDIF.
    
      CALL FUNCTION 'DP_CREATE_URL'
           EXPORTING
                type     = 'image'
                subtype  = cndp_sap_tab_unknown
                size     = pic_size
                lifetime = cndp_lifetime_transaction
           TABLES
                data     = pic_data
           CHANGING
                url      = url
           EXCEPTIONS
                OTHERS   = 1.
    
    endform.

    Easy spliter container

    效果

    *&---------------------------------------------------------------------*
    *& Report  RSDEMO_EASY_SPLITTER_CONTROL                                *
    *&                                                                     *
    *&---------------------------------------------------------------------*
    *&                                                                     *
    *&                                                                     *
    *&---------------------------------------------------------------------*
    
    REPORT  rsdemo_easy_splitter_control         .
    
    * splitter control
    DATA splitter TYPE REF TO cl_gui_easy_splitter_container.
    * container for the splitter control
    DATA container TYPE REF TO cl_gui_custom_container.
    * containers created by the splitter control
    DATA container_1 TYPE REF TO cl_gui_container.
    DATA container_2 TYPE REF TO cl_gui_container.
    * picture controls
    DATA picture_1 TYPE REF TO cl_gui_picture.
    DATA picture_2 TYPE REF TO cl_gui_picture.
    * load control framework definition
    TYPE-POOLS cndp.
    
    DATA  init.
    DATA ok_code TYPE sy-ucomm.
    
    CALL SCREEN 100.
    
    *&---------------------------------------------------------------------*
    *&      Module  STATUS_0100  OUTPUT
    *&---------------------------------------------------------------------*
    *       text
    *----------------------------------------------------------------------*
    MODULE status_0100 OUTPUT.
      SET PF-STATUS 'STATUS'.
      IF init is initial.
    * create a container for the splitter control
        CREATE OBJECT container
                      EXPORTING container_name = 'CUSTOM'.
    * create the splitter control
        CREATE OBJECT splitter
                      EXPORTING parent = container
                                orientation    = 1.
    * get the containers of the splitter control
        container_1 = splitter->top_left_container.
        container_2 = splitter->bottom_right_container.
    * create the picture controls inside the containers of the splitter
        CREATE OBJECT picture_1
                      EXPORTING parent  = container_1.
    
        CREATE OBJECT picture_2
                      EXPORTING parent  = container_2.
    * Request an URL from the data provider by exporting the pic_data.
        DATA url(255).
        CLEAR url.
        PERFORM load_pic_from_db CHANGING url.
    
    * load picture
        CALL METHOD picture_1->load_picture_from_url
            EXPORTING url = url.
    
        CALL METHOD picture_2->load_picture_from_url
            EXPORTING url = url.
    
        init = 'X'.
    
        CALL METHOD cl_gui_cfw=>flush
             EXCEPTIONS cntl_system_error = 1
                        cntl_error = 2.
        IF sy-subrc <> 0.
    * error handling
        ENDIF.
      ENDIF.
    ENDMODULE.                             " STATUS_0100  OUTPUT
    
    *&---------------------------------------------------------------------*
    *&      Module  EXIT  INPUT
    *&---------------------------------------------------------------------*
    *       text
    *----------------------------------------------------------------------*
    MODULE exit INPUT.
      CALL METHOD container->free.
      LEAVE PROGRAM.
    ENDMODULE.                             " EXIT  INPUT
    
    *&---------------------------------------------------------------------*
    *&      Form  LOAD_PIC_FROM_DB
    *&---------------------------------------------------------------------*
    *       text
    *----------------------------------------------------------------------*
    *
    *----------------------------------------------------------------------*
    FORM load_pic_from_db CHANGING url.
      DATA query_table LIKE w3query OCCURS 1 WITH HEADER LINE.
      DATA html_table LIKE w3html OCCURS 1.
      DATA return_code LIKE  w3param-ret_code.
      DATA content_type LIKE  w3param-cont_type.
      DATA content_length LIKE  w3param-cont_len.
      DATA pic_data LIKE w3mime OCCURS 0.
      DATA pic_size TYPE i.
    
      REFRESH query_table.
      query_table-name = '_OBJECT_ID'.
      query_table-value = 'ENJOYSAP_LOGO'.
      APPEND query_table.
    
      CALL FUNCTION 'WWW_GET_MIME_OBJECT'
           TABLES
                query_string        = query_table
                html                = html_table
                mime                = pic_data
           CHANGING
                return_code         = return_code
                content_type        = content_type
                content_length      = content_length
           EXCEPTIONS
                OBJECT_NOT_FOUND    = 1
                parameter_not_found = 2
                OTHERS              = 3.
      IF sy-subrc = 0.
        pic_size = content_length.
      ENDIF.
    
      CALL FUNCTION 'DP_CREATE_URL'
           EXPORTING
                type     = 'image'
                subtype  = cndp_sap_tab_unknown
                size     = pic_size
                lifetime = cndp_lifetime_transaction
           TABLES
                data     = pic_data
           CHANGING
                url      = url
           EXCEPTIONS
                OTHERS   = 1.
    
    
    ENDFORM.                               " LOAD_PIC_FROM_DB

    Dialog box container

    效果

    *&---------------------------------------------------------------------*
    *& Report  RSDEMO_DIALOGBOX_CONTROL                                    *
    *&                                                                     *
    *&---------------------------------------------------------------------*
    *&                                                                     *
    *&                                                                     *
    *&---------------------------------------------------------------------*
    
    REPORT  rsdemo_dialogbox_control         .
    DATA repid TYPE sy-repid.
    DATA dynnr TYPE sy-dynnr.
    DATA  init.
    DATA ok_code TYPE sy-ucomm.
    TYPE-POOLS cndp.
    
    * dialogbox Container
    DATA dialogbox TYPE REF TO cl_gui_dialogbox_container.
    * picture Control
    DATA picture TYPE REF TO cl_gui_picture.
    * Definition of Control Framework
    CLASS cl_gui_cfw DEFINITION LOAD.
    
    
    CALL SCREEN 100.
    
    *&---------------------------------------------------------------------*
    *&      Module  STATUS_0100  OUTPUT
    *&---------------------------------------------------------------------*
    *       text
    *----------------------------------------------------------------------*
    MODULE status_0100 OUTPUT.
      SET PF-STATUS 'STATUS'.
    *  SET TITLEBAR 'xxx'.
      IF init IS INITIAL.
        repid = sy-repid.
        dynnr = sy-dynnr.
        CREATE OBJECT dialogbox
                      EXPORTING
                               width    = 540
                               height   = 100
                               top      = 150
                               left     = 150
                               repid    = repid
                               dynnr    = dynnr.
    
        CREATE OBJECT picture
                      EXPORTING parent = dialogbox.
    
    * Request an URL from the data provider by exporting the pic_data.
        DATA url(255).
        CLEAR url.
        PERFORM load_pic_from_db CHANGING url.
    
    * load picture
        CALL METHOD picture->load_picture_from_url
            EXPORTING url = url.
        init = 'X'.
    
        CALL METHOD cl_gui_cfw=>flush
             EXCEPTIONS cntl_system_error = 1
                        cntl_error = 2.
        IF sy-subrc <> 0.
    * error handling
        ENDIF.
      ENDIF.
    ENDMODULE.                             " STATUS_0100  OUTPUT
    
    *&---------------------------------------------------------------------*
    *&      Module  EXIT  INPUT
    *&---------------------------------------------------------------------*
    *       text
    *----------------------------------------------------------------------*
    MODULE exit INPUT.
      CALL METHOD dialogbox->free.
      LEAVE PROGRAM.
    ENDMODULE.                             " EXIT  INPUT
    *&---------------------------------------------------------------------*
    *&      Form  LOAD_PIC_FROM_DB
    *&---------------------------------------------------------------------*
    *       text
    *----------------------------------------------------------------------*
    *
    *----------------------------------------------------------------------*
    FORM load_pic_from_db CHANGING url.
      DATA query_table LIKE w3query OCCURS 1 WITH HEADER LINE.
      DATA html_table LIKE w3html OCCURS 1.
      DATA return_code LIKE  w3param-ret_code.
      DATA content_type LIKE  w3param-cont_type.
      DATA content_length LIKE  w3param-cont_len.
      DATA pic_data LIKE w3mime OCCURS 0.
      DATA pic_size TYPE i.
    
      REFRESH query_table.
      query_table-name = '_OBJECT_ID'.
      query_table-value = 'ENJOYSAP_LOGO'.
      APPEND query_table.
    
      CALL FUNCTION 'WWW_GET_MIME_OBJECT'
           TABLES
                query_string        = query_table
                html                = html_table
                mime                = pic_data
           CHANGING
                return_code         = return_code
                content_type        = content_type
                content_length      = content_length
           EXCEPTIONS
                OBJECT_NOT_FOUND    = 1
                parameter_not_found = 2
                OTHERS              = 3.
      IF sy-subrc = 0.
        pic_size = content_length.
      ENDIF.
    
      CALL FUNCTION 'DP_CREATE_URL'
           EXPORTING
                type     = 'image'
                subtype  = cndp_sap_tab_unknown
                size     = pic_size
                lifetime = cndp_lifetime_transaction
           TABLES
                data     = pic_data
           CHANGING
                url      = url
           EXCEPTIONS
                OTHERS   = 1.
    
    
    ENDFORM.                               " LOAD_PIC_FROM_DB
  • 相关阅读:
    XPath使用示例
    CSS3中的弹性布局——"em"的用法
    Sublime Text3快捷键实用总结
    学习笔记——关于HTML(含HTML5)的块级元素和行级(内联)元素总结
    JavaScript中的伪数组理解
    深入理解浏览器兼容性模式
    javascript 中使用instanceof需要注意的一点
    用人工智能学习,凡亿推出PCB问题解答智能搜索机器人:pcb助手
    Altium中坐标的导出及利用坐标快速布局
    Altium中Logo的导入方法及大小调整
  • 原文地址:https://www.cnblogs.com/JackeyLove/p/13650219.html
Copyright © 2011-2022 走看看