Multiple line selection in report list

HI All,
I have a requirment to display multiple line items with a checkbox prefixed, and i should be able to select multiple line items with the checkbox provided and should keep the selectd line items in an internal table(note the list is not ALG LIST or GRID)
can anybody please tell me how to select multiple line items and and keep the selected items in a  in a normal report list.
Regards

Hii,
  Have a look at this sample code
Report z_sdn.
*" Data declarations...................................................
* Work variables                                                      *
DATA:
  BEGIN OF fs_spfli,
    carrid   LIKE spfli-carrid,        " Airline Code
    connid   LIKE spfli-connid,        " Flight Connection Number
    airpfrom LIKE spfli-airpfrom,      " Departure airport
    airpto   LIKE spfli-airpto,        " Destination airport
    deptime  LIKE spfli-deptime,       " Departure time
    arrtime  LIKE spfli-arrtime,       " Arrival time
  END OF fs_spfli,
  BEGIN OF fs_sflight,
    carrid   LIKE sflight-carrid,       " Airline Code
    connid   LIKE sflight-connid,       " Flight Connection Number
    fldate   LIKE sflight-fldate,       " Flight date
    seatsmax LIKE sflight-seatsmax,     " Maximum seats in economy class
    seatsocc LIKE sflight-seatsocc,     " Occupied seats in economyclass
  END OF fs_sflight,
  w_checkbox TYPE c,                    " Variable for checkbox
  w_currentline TYPE i,                 " Variable to display current
                                        " line
  w_lines TYPE i,
  w_read TYPE c .
* Internal Table to hold flight schedule information                  *
DATA:
  t_spfli LIKE
    TABLE OF
          fs_spfli.
* Internal Table to hold flight information                           *
DATA:
  t_sflight LIKE
      TABLE OF
            fs_sflight,
  t_sflight1 LIKE t_sflight.
*    START-OF-SELECTION Event                                         *
START-OF-SELECTION.
  PERFORM get_data_spfli.
*    END-OF-SELECTION Event                                           *
END-OF-SELECTION.
  SET PF-STATUS 'MENU'.
  PERFORM display_data_spfli.
*    TOP-OF-PAGE Event                                                *
TOP-OF-PAGE.
  PERFORM header_table_spfli.
*    AT LINE-SELECTION EVENT                                          *
AT LINE-SELECTION.
  SET PF-STATUS space.
  IF sy-lsind EQ 1 AND sy-lilli GE 4.
    PERFORM get_data_sflight.
    PERFORM display_data_sflight.
    PERFORM flag_line.
  ENDIF.                               " IF sy-lsind EQ 1..
*    AT USER-COMMAND                                                  *
AT USER-COMMAND.
  IF sy-lsind EQ 1.
    SET PF-STATUS space.
    CASE sy-ucomm.
      WHEN 'DISPLAY'.
        PERFORM get_data_sflight1.
        PERFORM display_data_sflight.
      WHEN 'SELECTALL'.
        PERFORM select_all.
        PERFORM flag_line.
      WHEN 'DESELECTAL'.
        PERFORM deselect_all.
        PERFORM flag_line.
    ENDCASE.                           " CASE sy-ucomm
  ENDIF.                               " IF sy-lsind EQ 1
*    TOP-OF-PAGE DURING LINE-SELECTION                                *
TOP-OF-PAGE DURING LINE-SELECTION.
  PERFORM sec_list_heading.
*&      Form  get_data_spfli
*  This subroutine fetches the data from SPFLI
* This subroutine does not have parameters to pass
FORM get_data_spfli .
  SELECT carrid                        " Airline Code
         connid                        " Flight Connection Number
         airpfrom                      " Departure airport
         airpto                        " Destination airport
         deptime                       " Departure time
         arrtime                       " Arrival time
    FROM spfli
    INTO TABLE t_spfli.
ENDFORM.                               " GET_DATA_SPFLI
*&      Form  display_data_spfli
* This subroutine displays the data of SPFLI
* This subroutine does not have parameters to pass
FORM display_data_spfli .
  LOOP AT t_spfli INTO fs_spfli.
    WRITE: /02 w_checkbox AS CHECKBOX,
            05 w_read,
               fs_spfli-carrid UNDER text-001,
               fs_spfli-connid UNDER text-002,
               fs_spfli-airpfrom UNDER text-003,
               fs_spfli-airpto UNDER text-004,
               fs_spfli-deptime UNDER text-005,
               fs_spfli-arrtime UNDER text-006.
    HIDE:
      fs_spfli-carrid,
      fs_spfli-connid.
  ENDLOOP.                             " LOOP AT t_spfli..
ENDFORM.                               " DISPLAY_DATA_SPFLI
*&      Form  header_table_spfli
* This subroutine diplays the headings of table spfli
* This subroutine does not have parameters to pass
FORM header_table_spfli .
  WRITE: /10 text-001 COLOR 4,
          25 text-002 COLOR 4,
          40 text-003 COLOR 4,
          55 text-004 COLOR 4,
          70 text-005 COLOR 4,
          85 text-006 COLOR 4.
ENDFORM.                               " HEADER_TABLE
*&      Form  get_data_sflight
* This subroutine fetches the data from SFLIGHT
* This subroutine does not have interface parameters to pass
FORM get_data_sflight .
  SELECT carrid                        " Airline Code
         connid                        " Flight Connection Number
         fldate                        " Flight date
         seatsmax                      " Maximum seats in economy class
         seatsocc                      " Occupied seats in economyclass
    FROM sflight
    INTO TABLE t_sflight
   WHERE carrid EQ fs_spfli-carrid
     AND connid EQ fs_spfli-connid.
ENDFORM.                               " GET_DATA_SFLIGHT
*&      Form  display_data_sflight
* This subroutine displays the SFLIGHT data
* This subroutine does not have interface parameters to pass
FORM display_data_sflight .
  LOOP AT t_sflight INTO fs_sflight.
    WRITE: / fs_sflight-carrid UNDER text-001,
             fs_sflight-connid UNDER text-002,
             fs_sflight-fldate UNDER text-007,
             fs_sflight-seatsmax UNDER text-008 LEFT-JUSTIFIED,
             fs_sflight-seatsocc UNDER text-009 LEFT-JUSTIFIED.
  ENDLOOP.
    CLEAR: fs_sflight.
ENDFORM.                               " DISPLAY_DATA_sflight
*&      Form  sec_list_heading
*  This subroutine diplays the headings of table spfli
* This subroutine does not have interface parameters to pass
FORM sec_list_heading .
  WRITE: /2 text-001 COLOR 4,
         15 text-002 COLOR 4,
         33 text-007 COLOR 4,
         45 text-008 COLOR 4,
         60 text-009 COLOR 4.
ENDFORM.                               " SEC_LIST_HEADING
*&      Form  get_data_sflight1
* This subroutine displays the data from SFLIGHT according to checkbox
* clicked.
* This subroutine does not have interface parameters to pass
FORM get_data_sflight1 .
  DATA:
    lw_checkbox TYPE c.
  DESCRIBE TABLE t_spfli LINES w_lines.
  DO w_lines TIMES.
    w_currentline = 3 + sy-index.
    CLEAR:
      w_checkbox,
      fs_spfli.
    READ LINE w_currentline FIELD VALUE
      w_checkbox INTO lw_checkbox
      fs_spfli-carrid INTO fs_spfli-carrid
      fs_spfli-connid INTO fs_spfli-connid.
    IF sy-subrc EQ 0.
      IF lw_checkbox EQ 'X'.
        SELECT carrid                  " Airline Code
               connid                  " Flight Connection Number
               fldate                  " Flight Date
               seatsmax                " Max Seats
               seatsocc                " Occupied Seats
          FROM sflight
          INTO TABLE t_sflight1
         WHERE carrid EQ fs_spfli-carrid
           AND connid EQ fs_spfli-connid.
        IF sy-subrc EQ 0.
          APPEND LINES OF t_sflight1 TO t_sflight.
        ENDIF.                         " IF sy-subrc EQ 0.
      ENDIF.                           " IF lw_checkbox EQ 'X'
    ENDIF.                             " IF sy-subrc EQ 0.
  ENDDO.                               " DO w_lines TIMES
ENDFORM.                               " GET_DATA_SFLIGHT1
*&      Form  select_all
* This subroutine selects all the records of SPFLI
* This subroutine does not have interface parameters to pass
FORM select_all .
  DESCRIBE TABLE t_spfli LINES w_lines.
  DO w_lines TIMES.
    w_currentline = sy-index + 3.
    READ LINE w_currentline FIELD VALUE
    w_checkbox INTO w_checkbox.
    IF sy-subrc = 0.
      MODIFY LINE w_currentline FIELD VALUE
      w_checkbox FROM 'X'.
    ENDIF.                             " IF sy-subrc = 0.
  ENDDO.                               " DO lw_line TIMES.
ENDFORM.                               " SELECT_ALL
*&      Form  deselect_all
* This subroutine deselects all the records of SPFLI
* This subroutine does not have interface parameters to pass
FORM deselect_all .
  DESCRIBE TABLE t_spfli LINES w_lines.
  DO w_lines TIMES.
    w_currentline = sy-index + 3.
    READ LINE w_currentline FIELD VALUE
    w_checkbox INTO w_checkbox.
    IF sy-subrc = 0.
      MODIFY LINE w_currentline FIELD VALUE
      w_checkbox FROM ' '.
    ENDIF.                             " IF sy-subrc = 0.
  ENDDO.                               " DO lw_line TIMES.
ENDFORM.                               " DESELECT_ALL
*&      Form  flag_line
* This subroutine flags the line which has been read
* This subroutine does not have interface parameters to pass
FORM flag_line .
  DESCRIBE TABLE t_spfli LINES w_lines.
  DO w_lines TIMES.
    w_checkbox = 'X'.
    READ LINE sy-lilli FIELD VALUE
      w_read INTO w_read
      w_checkbox INTO w_checkbox.
    IF sy-subrc EQ 0.
      MODIFY CURRENT LINE
      FIELD FORMAT w_checkbox INPUT OFF
      FIELD VALUE w_read FROM '*'.
    ENDIF.                             " IF sy-subrc EQ 0
  ENDDO.                               " DO w_lines TIMES
ENDFORM.                               " FLAG_LINE
Regards
Abhijeet

Similar Messages

  • Multiple line selection in basic list

    Hi,
    I have a report output with a Check Box being the first column.
    How can we process multiple lines by selecting  multiple check boxes, i.e if the user checks few check boxes and clicks on the user menu button something should be processed further.
    Now can someone suggest how to update the internal table once the user checks more than one check boxes in the list output.
    looking forward to ur valuable replies.
    MS
    Message was edited by: Mahesh Sahu
    Message was edited by: Mahesh Sahu

    Hi,
    You will have to read the content on the list using the READ LINE statement. Here's a short sample program that I have just written. See if you are able to understand the logic.
    REPORT  zlist_test no standard page heading.
    data: list_line(72),
          begin of itab occurs 0,
            box type c,
            num type i,
          end of itab.
    start-of-selection.
    do 10 times.
      move sy-index to itab-num.
      append itab.
    enddo.
    loop at itab.
      write : / itab-box as checkbox,
                itab-num.
    endloop.
    at user-command.
    if sy-ucomm NE space.
      write 'The following lines were checked'.
      do.
        read line sy-index line value into list_line.
        if sy-subrc ne 0.
          exit.
        endif.
        if list_line(1) eq 'X'.
          read table itab index sy-index.
    * Here you can also modify the internal table with the value of the checkbox.
          write : / itab-num.
        endif.
      enddo.
    endif.
    Regards,
    Anand Mandalika.

  • How to select multiple lines in ALV report

    hi gurus,
    I am working on an interactive ALV report where i have to select multiple lines from the basic list into an internal table, based on check box clicks. Using RS_SELFIELD i can select only 1 row. The coding has been done based on Call Function. Can u please suggest some way.
    Regards,
    Satyajit

    hi,
    try like this
    TABLES:     ekko.
    TYPE-POOLS: slis.                                 "ALV Declarations
    TYPES: BEGIN OF t_ekko,
      sel,                         "stores which row user has selected
      ebeln TYPE ekpo-ebeln,
      ebelp TYPE ekpo-ebelp,
      statu TYPE ekpo-statu,
      aedat TYPE ekpo-aedat,
      matnr TYPE ekpo-matnr,
      menge TYPE ekpo-menge,
      meins TYPE ekpo-meins,
      netpr TYPE ekpo-netpr,
      peinh TYPE ekpo-peinh,
    END OF t_ekko.
    DATA: it_ekko TYPE STANDARD TABLE OF t_ekko INITIAL SIZE 0,
          wa_ekko TYPE t_ekko.
    DATA: fieldcatalog TYPE slis_t_fieldcat_alv WITH HEADER LINE,
          fieldcatalog1 TYPE slis_t_fieldcat_alv WITH HEADER LINE,
          gd_tab_group TYPE slis_t_sp_group_alv,
          gd_layout    TYPE slis_layout_alv,
          gd_repid     LIKE sy-repid.
    DATA : BEGIN OF det_tab OCCURS 0,
            ebeln LIKE ekpo-ebeln,
           END OF det_tab.
    START-OF-SELECTION.
      PERFORM data_retrieval.
      PERFORM build_fieldcatalog.
      PERFORM build_layout.
      PERFORM display_alv_report.
    *&      Form  BUILD_FIELDCATALOG
    *       Build Fieldcatalog for ALV Report
    FORM build_fieldcatalog.
      fieldcatalog-fieldname   = 'EBELN'.
      fieldcatalog-seltext_m   = 'Purchase Order'.
      fieldcatalog-outputlen   = 10.
      fieldcatalog-emphasize   = 'X'.
      fieldcatalog-key         = 'X'.
      APPEND fieldcatalog TO fieldcatalog.
      CLEAR  fieldcatalog.
      fieldcatalog-fieldname   = 'EBELP'.
      fieldcatalog-seltext_m   = 'PO Item'.
      APPEND fieldcatalog TO fieldcatalog.
      CLEAR  fieldcatalog.
      fieldcatalog-fieldname   = 'STATU'.
      fieldcatalog-seltext_m   = 'Status'.
      APPEND fieldcatalog TO fieldcatalog.
      CLEAR  fieldcatalog.
      fieldcatalog-fieldname   = 'AEDAT'.
      fieldcatalog-seltext_m   = 'Item change date'.
      APPEND fieldcatalog TO fieldcatalog.
      CLEAR  fieldcatalog.
      fieldcatalog-fieldname   = 'MATNR'.
      fieldcatalog-seltext_m   = 'Material Number'.
      APPEND fieldcatalog TO fieldcatalog.
      CLEAR  fieldcatalog.
      fieldcatalog-fieldname   = 'MENGE'.
      fieldcatalog-seltext_m   = 'PO quantity'.
      APPEND fieldcatalog TO fieldcatalog.
      CLEAR  fieldcatalog.
      fieldcatalog-fieldname   = 'MEINS'.
      fieldcatalog-seltext_m   = 'Order Unit'.
      APPEND fieldcatalog TO fieldcatalog.
      CLEAR  fieldcatalog.
      fieldcatalog-fieldname   = 'NETPR'.
      fieldcatalog-seltext_m   = 'Net Price'.
      fieldcatalog-outputlen   = 15.
      fieldcatalog-do_sum      = 'X'.        "Display column total
      fieldcatalog-datatype     = 'CURR'.
      APPEND fieldcatalog TO fieldcatalog.
      CLEAR  fieldcatalog.
      fieldcatalog-fieldname   = 'PEINH'.
      fieldcatalog-seltext_m   = 'Price Unit'.
      APPEND fieldcatalog TO fieldcatalog.
      CLEAR  fieldcatalog.
    ENDFORM.                    " BUILD_FIELDCATALOG
    *&      Form  BUILD_LAYOUT
    *       Build layout for ALV grid report
    FORM build_layout.
      gd_layout-box_fieldname     = 'SEL'.
      "set field name to store row selection
      gd_layout-edit              = 'X'. "makes whole ALV table editable
      gd_layout-zebra             = 'X'.
    ENDFORM.                    " BUILD_LAYOUT
    *&      Form  DISPLAY_ALV_REPORT
    *       Display report using ALV grid
    FORM display_alv_report.
      gd_repid = sy-repid.
      CALL FUNCTION 'REUSE_ALV_GRID_DISPLAY'
        EXPORTING
          i_callback_program       = gd_repid
          i_callback_user_command  = 'USER_COMMAND'
          i_callback_pf_status_set = 'SET_STAT'
          is_layout                = gd_layout
          it_fieldcat              = fieldcatalog[]
          i_save                   = 'X'
        TABLES
          t_outtab                 = it_ekko
        EXCEPTIONS
          program_error            = 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.
    ENDFORM.                    " DISPLAY_ALV_REPORT
    *&      Form  DATA_RETRIEVAL
    *       Retrieve data form EKPO table and populate itab it_ekko
    FORM data_retrieval.
      SELECT ebeln ebelp statu aedat matnr menge meins netpr peinh
       UP TO 10 ROWS
        FROM ekpo
        INTO CORRESPONDING FIELDS OF TABLE it_ekko.
    ENDFORM.                    " DATA_RETRIEVAL
    *       FORM USER_COMMAND                                          *
    *       --> R_UCOMM                                                *
    *       --> RS_SELFIELD                                            *
    FORM user_command USING r_ucomm LIKE sy-ucomm
                      rs_selfield TYPE slis_selfield.
    * Check function code
      CASE r_ucomm.
        WHEN '&IC1'.
          IF rs_selfield-fieldname = 'EBELN'.
            READ TABLE it_ekko INTO wa_ekko INDEX rs_selfield-tabindex.
            SET PARAMETER ID 'BES' FIELD wa_ekko-ebeln.
            CALL TRANSACTION 'ME23N' AND SKIP FIRST SCREEN.
          ENDIF.
        WHEN 'DET'.  "button add by me
          CLEAR det_tab.
          REFRESH det_tab.
          LOOP AT it_ekko INTO wa_ekko WHERE sel = 'X'.
            MOVE-CORRESPONDING wa_ekko TO det_tab.
            APPEND det_tab.
          ENDLOOP.
          PERFORM build_cat.
          PERFORM dis_data.
      ENDCASE.
    ENDFORM.                    "user_command
    *&      Form  set_stat
    *       text
    *      -->RT_EXTAB   text
    FORM set_stat USING rt_extab TYPE slis_t_extab.
      SET PF-STATUS 'ZSTAT' EXCLUDING rt_extab.
    ENDFORM.                    "set_stat
    *&      Form  build_cat
    *       text
    FORM build_cat.
      CLEAR fieldcatalog1.
      REFRESH fieldcatalog1.
      fieldcatalog1-fieldname = 'EBELN'.
      fieldcatalog1-tabname = 'DET_TAB'.
      fieldcatalog1-seltext_m = 'Order No.'.
      fieldcatalog1-outputlen = 10.
      APPEND fieldcatalog1 TO fieldcatalog1.
      CLEAR fieldcatalog1.
    ENDFORM.                    "build_cat
    *&      Form  dis_data
    *       text
    FORM dis_data.
      CALL FUNCTION 'REUSE_ALV_GRID_DISPLAY'
        EXPORTING
          i_callback_program = 'ZTEST_DS'
          it_fieldcat        = fieldcatalog1[]
          i_save             = 'X'
        TABLES
          t_outtab           = det_tab.
    ENDFORM.                    "dis_data
    here i have copied standard gui status of ALV into my z status ZSTAT and add one button DET......
    here u can select morethan one line using control(ctrl)
    reward if usefull...

  • Multiple line selection and then capturing the selected values

    Dear all
      in my alv program ,i need to capture multiple line selections  using checkboxes.
    I have appended check boxes by adding it in the internal table  & filling in field catalog.
    but problem is i'm not able to capture multiple selected check boxes dynamically,
    i could capture only the last selected check box,
    option i found was to use class method get-selected-rows,but i'm unable to use it properly, could anyone explain in detail
    i have already gone through the various examples in sdn but i am not able to work out.
    like using parameters etc....
    CAN ANY ONE HELP ME WITH THE CODE
    help reqired  immediately,
    Thanks in advance.

    Hi Ankur,
    In the PAI, just after the selection of your user event, button or menu,
    add this code before getting the selected records.
    <b>CALL METHOD grid1->check_changed_data
                 IMPORTING
                   e_valid = ws_x.</b>
    where    grid1  TYPE REF TO cl_gui_alv_grid,
    Now fetch the selected records.
    Check this code for reference
                C O M P A N Y   C O N F I D E N T I A L                **
           Care should be taken to prevent its unauthorized use.       **
    REPORT zfipost MESSAGE-ID f4 NO STANDARD PAGE HEADING .
    AUTHOR   : Susmitha Susan Thomas
    DATE     : August 18, 2005
    *Abridged Version : This report generates a list in Abap List Viewer of
                      all the selected records in VBKPF/VBSEG. * *
                      (TRANSACTION ZPPD:Modified from transaction FBV0)
    -- Class definition--
    CLASS lcl_event_receiver DEFINITION DEFERRED.
    --Tables--
    TABLES:  vbkpf. " Belegkopf
    TABLES: tsp1d, pri_params, spopli.
    TYPE-POOLS slis.
    ---- Global Variables -
    DATA:    anzkr(6)     TYPE n,
             lsind        LIKE sy-lsind,
             no_output(1) TYPE c,
             records(1) TYPE c,
             xpick(1)     TYPE c,
             xpickc(1)    TYPE c,
             xbinp(1)     TYPE c,
             rc           LIKE syst-subrc,
             ok_code LIKE sy-ucomm,
             index TYPE i,
             char_x(1)    TYPE c VALUE 'X',
             post         TYPE c,
             ans          TYPE n,
             user(40) TYPE c.
    DATA :BEGIN OF i_doctype OCCURS 0,
             blart LIKE vbkpf-blart,
          END OF i_doctype.
    --AlV Initialization--
    DATA:  gs_layout TYPE lvc_s_layo,
           gt_fieldcat TYPE lvc_t_fcat,
           gs_fieldcat TYPE lvc_s_fcat,
           gs_index_rows TYPE lvc_t_row,
           l_layout TYPE disvariant,
           g_repid LIKE sy-repid,
           g_max TYPE i VALUE 100,
           ws_row_idx TYPE lvc_t_row ,
           ws_row_no TYPE lvc_t_roid,
           i_excl_func TYPE ui_functions,
           ls_prnt TYPE lvc_s_prnt,
           refresh TYPE c,
           i_fieldcat  TYPE lvc_t_fcat,
          post(1) TYPE c,
           accr_def(1) TYPE c,
           rev_cd(3) TYPE c,
           ch(1) TYPE c.
    DATA: list_index LIKE sy-lsind,
          flag TYPE n VALUE 0,
          fl TYPE n VALUE 0,
          g_container TYPE scrfname VALUE 'GRID_CONTAINER',
          grid_container TYPE REF TO cl_gui_docking_container,
          grid1  TYPE REF TO cl_gui_alv_grid,
          custom_container1 TYPE REF TO cl_gui_custom_container,
          event_receiver TYPE REF TO lcl_event_receiver,
          gt_vbkpf1 TYPE STANDARD TABLE OF vbkpf WITH HEADER LINE,
          i_vbkpf TYPE  TABLE OF vbkpf WITH HEADER LINE,
          i_ws_row_idx LIKE ws_row_idx WITH HEADER LINE.
    ---Internal table containing details of selected documents--
    DATA : BEGIN OF gt_vbkpf OCCURS 0,
             xpick(1) TYPE c,
             belnr LIKE vbkpf-belnr,
             gjahr LIKE vbkpf-gjahr,
             bukrs LIKE vbkpf-bukrs,
             blart LIKE vbkpf-blart,
             budat LIKE vbkpf-budat,
             bldat LIKE vbkpf-bldat,
             bktxt LIKE vbkpf-bktxt,
             waers LIKE vbkpf-waers,
             usnam LIKE vbkpf-usnam,
             xblnr LIKE vbkpf-xblnr,
             rev_code(3) TYPE c,
             rev_rsn(15) TYPE c,
             rev_date(10) TYPE c,
             linecolor(4) TYPE c,
           END OF gt_vbkpf.
    --Table to store long text--
    DATA : BEGIN OF inline OCCURS 0,
    tdformat TYPE tdformat,
    tdline TYPE tdline,
    END OF inline.
    DATA: thead LIKE thead OCCURS 0 WITH HEADER LINE.
    -- Records to be posted--
    DATA:   BEGIN OF tbkpf OCCURS 5.
            INCLUDE STRUCTURE vbkpf.
    DATA:   END   OF tbkpf.
    ---- Constants -
    CONSTANTS: awtyp_bkpf TYPE awtyp VALUE 'BKPF '.
    CONSTANTS: awtyp_space TYPE awtyp VALUE '     '.
    Selection Screen
    PARAMETER: funcl   LIKE t020-funcl NO-DISPLAY.   "P(ost),D(isplay),U(pd)
    SELECTION-SCREEN SKIP 2.
    SELECT-OPTIONS:
             p_bukrs     FOR  vbkpf-bukrs,
             p_belnr     FOR  vbkpf-belnr,
             p_gjahr     FOR  vbkpf-gjahr,
             p_budat     FOR  vbkpf-budat,
             p_bldat     FOR  vbkpf-bldat,
             p_blart     FOR  vbkpf-blart,
             p_xblnr     FOR  vbkpf-xblnr,
             p_bktxt     FOR  vbkpf-bktxt,
             p_usnam     FOR  vbkpf-usnam.
    SELECTION-SCREEN SKIP 1.
    SELECTION-SCREEN BEGIN OF BLOCK blk
                WITH FRAME TITLE text-010 NO INTERVALS.
    SELECTION-SCREEN BEGIN OF LINE.
    SELECTION-SCREEN COMMENT 1(35) text-002.
    PARAMETER norm_doc    TYPE c
              RADIOBUTTON GROUP doc DEFAULT 'X' .
    SELECTION-SCREEN END OF LINE.
    SELECTION-SCREEN BEGIN OF LINE.
    SELECTION-SCREEN COMMENT 1(35) text-001.
    PARAMETER ad_doc       TYPE c
               RADIOBUTTON GROUP doc .
    SELECTION-SCREEN END OF LINE.
    SELECTION-SCREEN BEGIN OF LINE.
    SELECTION-SCREEN COMMENT 1(35) text-003.
    PARAMETER all_doc       TYPE c
                RADIOBUTTON GROUP doc .
    SELECTION-SCREEN END OF LINE.
    SELECTION-SCREEN END OF BLOCK blk.
          CLASS lcl_event_receiver DEFINITION
          For capturing events on the ALV                               *
    CLASS lcl_event_receiver DEFINITION.
      PUBLIC SECTION.
        METHODS:
    to capture all recently changed data.
          handle_data_changed      FOR EVENT data_changed OF
                                           cl_gui_alv_grid
                                           IMPORTING er_data_changed,
    for hot spot
          handle_hotspot           FOR EVENT hotspot_click OF
                                           cl_gui_alv_grid
                                           IMPORTING e_column_id e_row_id.
    ENDCLASS.   " lcl_event_receiver (Definition)
          CLASS lcl_event_receiver (Implementation)
          For capturing events on the ALV                               *
    CLASS lcl_event_receiver IMPLEMENTATION.
      METHOD handle_data_changed.
        PERFORM f2200_handle_data_changed USING er_data_changed.
      ENDMETHOD.
      METHOD handle_hotspot.
        PERFORM f2201_handle_hotspot USING e_column_id e_row_id .
      ENDMETHOD.
    ENDCLASS.  " lcl_event_receiver (Implementation)
    AT SELECTION-SCREEN
    AT SELECTION-SCREEN.
    START-OF-SELECTION
    START-OF-SELECTION.
    ---- Colors -
      FORMAT COLOR COL_NORMAL INTENSIFIED OFF.
    -------------------- Status und Title Bar----------------------------*
      SET PF-STATUS funcl.
      SET TITLEBAR  funcl.
    -- Read Records--
      SELECT * FROM vbkpf INTO TABLE gt_vbkpf1
          WHERE bukrs IN p_bukrs
            AND ausbk IN p_bukrs
            AND belnr IN p_belnr
            AND gjahr IN p_gjahr
            AND budat IN p_budat
            AND bldat IN p_bldat
            AND blart IN p_blart
            AND bktxt IN p_bktxt
            AND xblnr IN p_xblnr
            AND usnam IN p_usnam
            AND bstat EQ 'V'
          AND ( awtyp IN (awtyp_bkpf, awtyp_space) OR
                awtyp IS null )
          ORDER BY PRIMARY KEY.
    ----Call the ALV Screen -
      PERFORM alv_display.
    END-OF-SELECTION.
                         FORM BELEG_PICKUP                              *
          Indicate changing of the selected external record             *
    FORM beleg_pickup.
      SET PARAMETER ID 'BUK' FIELD vbkpf-bukrs.
      SET PARAMETER ID 'GJR' FIELD vbkpf-gjahr.
      SET PARAMETER ID 'BLP' FIELD vbkpf-belnr.
      CASE funcl.
         WHEN 'P'.
          IF anzkr IS INITIAL.
            CALL FUNCTION 'ZPRELIMINARY_POSTING_POST_D'
                 EXPORTING
                      bukrs = vbkpf-bukrs
                      belnr = vbkpf-belnr
                      gjahr = vbkpf-gjahr.
          ELSE.
            IF sy-ucomm EQ 'BUCH'.
              CALL FUNCTION 'ZPRELIMINARY_POSTING_POST_ALL'
                   EXPORTING
                        synch   = char_x
                        bupbi   = xbinp
                   TABLES
                        t_vbkpf = tbkpf.
            ELSE.
              CALL FUNCTION 'ZPRELIMINARY_POSTING_POST_ALL'
                   EXPORTING
                        bupbi   = xbinp
                   TABLES
                        t_vbkpf = tbkpf.
             wait up to 3 seconds.
             commit work.
            ENDIF.
          ENDIF.
        WHEN OTHERS.
          IF sy-tcode = 'ZPPD'.
            funcl = 'P'.
          ENDIF.
          CALL FUNCTION 'ZPRELIMINARY_POSTING_DISPLAY'
               EXPORTING
                    bukrs = vbkpf-bukrs
                    belnr = vbkpf-belnr
                    gjahr = vbkpf-gjahr.
      ENDCASE.
    ENDFORM.
                        FORM TBKPF_FUELLEN                              *
                Include  records for posting in TBKPF                   *
    FORM tbkpf_fuellen.
      records = 'X'.
      LOOP AT gt_vbkpf.
        IF gt_vbkpf-xpick = 'X'.
          CLEAR anzkr.
          CLEAR records.
          IF sy-subrc = 0.
            anzkr = anzkr + 1.
            MOVE-CORRESPONDING gt_vbkpf TO tbkpf.
            APPEND tbkpf.
          ELSE.
            EXIT.
          ENDIF.
        ENDIF.
      ENDLOOP.
    ENDFORM.
                              FORM MALL                                 *
                         Select All documents                           *
    FORM mall.
      LOOP AT gt_vbkpf.
        gt_vbkpf-xpick = 'X'.
        MODIFY gt_vbkpf.
      ENDLOOP.
      refresh = 'X'.
      CALL METHOD grid1->refresh_table_display.
    ENDFORM.
                             FORM EMAL                                  *
                       Unselect all documents                           *
    FORM emal.
      LOOP AT gt_vbkpf.
        gt_vbkpf-xpick = ' '.
        MODIFY gt_vbkpf.
      ENDLOOP.
      refresh = 'X'.
      CALL METHOD grid1->refresh_table_display.
    ENDFORM.
                         Form  alv_display                               *
                  To display the details on an ALV.                      *
    FORM alv_display.
      CALL SCREEN 100.
    ENDFORM.                    " alv_display
    *&      Module  PB0_100  OUTPUT
    MODULE pb0_100 OUTPUT.
      SET PF-STATUS 'MAIN100'.
      SET TITLEBAR 'POSTDOC'.
    --To verify that posting is complete.--
    ---- Setting the layout -
      IF grid1 IS INITIAL.
        PERFORM fill_table.
    -- Initializing the field catalog--
        PERFORM fieldcat_init CHANGING i_fieldcat.
    -- Initializing the ALV GRID and CONTAINER--
        CLEAR gs_layout.
        gs_layout-info_fname = 'linecolor'.
        gs_layout-grid_title = 'Parked Documents'(100).
        gs_layout-zebra               = 'X'.
        gs_layout-cwidth_opt   = 'X'.
        gs_layout-sel_mode = 'A'.
        gs_layout-edit                = 'X'.
        l_layout-report = sy-repid.
    ------ Create a custom container control for ALV Control----
        IF cl_gui_alv_grid=>offline( ) IS INITIAL.
          CREATE OBJECT grid_container
             EXPORTING
               dynnr                     = '100'
               ratio                     = '100'
            EXCEPTIONS
             cntl_error                  = 1
             cntl_system_error           = 2
             create_error                = 3
             lifetime_error              = 4
             lifetime_dynpro_dynpro_link = 5
             others                      = 6.
          IF sy-subrc NE 0.
         MESSAGE i000 WITH text-007.  " Error in object creation
            LEAVE LIST-PROCESSING.
          ENDIF.
    -- Create an instance of alv control--
          CREATE OBJECT grid1
                 EXPORTING
                    i_lifetime = 1
                    i_parent = grid_container.
    ---- Disable all unwanted button in the ALV grid -
          PERFORM disable_functions TABLES i_excl_func.
    ---- Call the display function of ALV grid -
          CALL METHOD grid1->set_table_for_first_display
               EXPORTING
                         is_variant       = l_layout
                         i_save           = 'A'
                         is_layout        = gs_layout
                         is_print         = ls_prnt
                         it_toolbar_excluding          = i_excl_func
               CHANGING  it_outtab        = gt_vbkpf[]
                         it_fieldcatalog  = i_fieldcat.
        ENDIF.                  "  IF cl_gui_alv_grid=>offline IS INITIAL
        CALL METHOD grid1->register_edit_event
            EXPORTING
             i_event_id = cl_gui_alv_grid=>mc_evt_enter.
        CALL METHOD grid1->register_edit_event
          EXPORTING
            i_event_id = cl_gui_alv_grid=>mc_evt_modified.
    ---- Create a reciever object to handle events -
        CREATE OBJECT event_receiver.
        SET HANDLER event_receiver->handle_data_changed FOR grid1.
        SET HANDLER event_receiver->handle_hotspot FOR grid1.
        CALL METHOD cl_gui_control=>set_focus EXPORTING control = grid1.
      ENDIF.                   " IF grid1 IS INITIAL.
    ENDMODULE.                 " PB0_100  OUTPUT
    *&      Form  fill_table
         Fills the data table to be passed to the ALV grid.
    FORM fill_table.
      LOOP AT gt_vbkpf1.
        MOVE-CORRESPONDING gt_vbkpf1 TO gt_vbkpf.
        IF ad_doc = 'X' OR all_doc = 'X'.
          thead-tdobject = 'BELEG'.
          CONCATENATE gt_vbkpf1-bukrs
                      gt_vbkpf1-belnr
                      gt_vbkpf1-gjahr INTO thead-tdname.
          thead-tdspras = sy-langu.
          thead-tdid = '0004'.
          PERFORM read_text.
          READ TABLE inline INDEX 1.
          gt_vbkpf-rev_code =  inline-tdline.
          REFRESH inline.
          CLEAR inline.
          thead-tdid = '0005'.
          PERFORM read_text.
          READ TABLE inline INDEX 1.
          gt_vbkpf-rev_rsn =  inline-tdline.
          REFRESH inline.
          CLEAR inline.
          thead-tdid = '0006'.
          PERFORM read_text.
          READ TABLE inline INDEX 1.
          gt_vbkpf-rev_date =  inline-tdline.
          REFRESH inline.
          CLEAR inline.
          REFRESH inline.
          CLEAR inline.
        ENDIF.
        APPEND gt_vbkpf.
        CLEAR gt_vbkpf.
    ENDLOOP.
      ENDLOOP.
    ENDFORM.
    *&      Form  fieldcat_init
         Initialize the field catalog
    FORM fieldcat_init CHANGING i_fieldcat TYPE lvc_t_fcat.
      DATA: i_fldcat TYPE lvc_t_fcat WITH HEADER LINE.
    CHECKBOX
      CLEAR i_fldcat.
      i_fldcat-fieldname = 'XPICK'.
      i_fldcat-checkbox  = 'X'.
    i_fldcat-key       = 'X'.
      i_fldcat-tabname   = 'GT_VBKPF'.
      i_fldcat-outputlen   =  '4'.
      i_fldcat-scrtext_l =  'ChkB'.
       APPEND i_fldcat TO i_fieldcat.
      CLEAR i_fldcat.
      i_fldcat-fieldname = 'BELNR'.
      i_fldcat-tabname   = 'GT_VBKPF'.
    i_fldcat-key       = 'X'.
      i_fldcat-hotspot   = 'X'.
      i_fldcat-outputlen   =  '15'.
      i_fldcat-scrtext_l =  'Document Number'.
      APPEND i_fldcat TO i_fieldcat.
      CLEAR i_fldcat.
      i_fldcat-fieldname = 'GJAHR'.
      i_fldcat-tabname   = 'GT_VBKPF'.
    i_fldcat-key       = 'X'.
      i_fldcat-scrtext_l = 'FYear'.
      i_fldcat-outputlen   = '5'.
      APPEND i_fldcat TO i_fieldcat.
      CLEAR i_fldcat.
      i_fldcat-fieldname = 'BUKRS'.
      i_fldcat-tabname   = 'GT_VBKPF'.
    i_fldcat-key       = 'X'.
      i_fldcat-scrtext_l = 'CCode'.
      i_fldcat-outputlen   =  '5'.
      APPEND i_fldcat TO i_fieldcat.
      CLEAR i_fldcat.
      i_fldcat-fieldname = 'BLART'.
      i_fldcat-tabname   = 'GT_VBKPF'.
    i_fldcat-key       = 'X'.
      i_fldcat-scrtext_l = 'Type'.
      i_fldcat-outputlen   =  '6'.
      APPEND i_fldcat TO i_fieldcat.
      CLEAR i_fldcat.
      i_fldcat-fieldname = 'BLDAT'.
      i_fldcat-tabname  = 'GT_VBKPF'.
    i_fldcat-key      = 'X'.
      i_fldcat-scrtext_l = 'Doc Date'.
      i_fldcat-outputlen   =  '12'.
      APPEND i_fldcat TO i_fieldcat.
      CLEAR i_fldcat.
      i_fldcat-fieldname = 'BUDAT'.
      i_fldcat-tabname  = 'GT_VBKPF'.
    i_fldcat-key      = 'X'.
      i_fldcat-scrtext_l = 'Park Date'.
      i_fldcat-outputlen   =  '12'.
      APPEND i_fldcat TO i_fieldcat.
      CLEAR i_fldcat.
      i_fldcat-fieldname = 'BKTXT'.
      i_fldcat-tabname  = 'GT_VBKPF'.
    i_fldcat-key      = 'X'.
      i_fldcat-scrtext_l = 'Document Header Text'.
      i_fldcat-outputlen   =  '25'.
      APPEND i_fldcat TO i_fieldcat.
      CLEAR i_fldcat.
      i_fldcat-fieldname = 'WAERS'.
      i_fldcat-tabname  = 'GT_VBKPF'.
    i_fldcat-key      = 'X'.
      i_fldcat-scrtext_l = 'Curr'.
      i_fldcat-outputlen   =  '7'.
      APPEND i_fldcat TO i_fieldcat.
      CLEAR i_fldcat.
      i_fldcat-fieldname = 'USNAM'.
      i_fldcat-tabname   = 'GT_VBKPF'.
    i_fldcat-key       = 'X'.
      i_fldcat-scrtext_l = 'Parked By'.
      i_fldcat-outputlen   =  '13'.
      APPEND i_fldcat TO i_fieldcat.
      CLEAR i_fldcat.
      i_fldcat-fieldname = 'XBLNR'.
      i_fldcat-tabname   = 'GT_VBKPF'.
    i_fldcat-key       = 'X'.
      i_fldcat-scrtext_l = 'Reference Text'.
      i_fldcat-outputlen   =  '19'.
      APPEND i_fldcat TO i_fieldcat.
      IF ad_doc = 'X' OR all_doc = 'X'.
        CLEAR i_fldcat.
        i_fldcat-fieldname = 'REV_CODE'.
        i_fldcat-tabname   = 'GT_VBKPF'.
       i_fldcat-key       = 'X'.
        i_fldcat-scrtext_l = 'RC'.
        i_fldcat-outputlen   =  '2'.
        APPEND i_fldcat TO i_fieldcat.
        CLEAR i_fldcat.
        i_fldcat-fieldname = 'REV_RSN'.
        i_fldcat-tabname   = 'GT_VBKPF'.
       i_fldcat-key       = 'X'.
        i_fldcat-scrtext_l = 'Rev Reason'.
        i_fldcat-outputlen   =  '15'.
        APPEND i_fldcat TO i_fieldcat.
        CLEAR i_fldcat.
        i_fldcat-fieldname = 'REV_DATE'.
        i_fldcat-tabname   = 'GT_VBKPF'.
       i_fldcat-key       = 'X'.
        i_fldcat-scrtext_l = 'Rev Date'.
        i_fldcat-outputlen   =  '10'.
        APPEND i_fldcat TO i_fieldcat.
      ENDIF.
    ENDFORM.                    " fieldcat_init
    *&      Module  PAI_100  INPUT
    MODULE pai_100 INPUT.
      CASE ok_code.
        WHEN 'BACK'.
          IF sy-dynnr = '1000'.
            PERFORM exit_program.
          ELSEIF sy-dynnr = '0100'.
            LEAVE TO TRANSACTION 'ZPPD'.
          ENDIF.
        WHEN 'EXIT'.
          IF sy-dynnr = '1000'.
            PERFORM exit_program.
          ELSEIF sy-dynnr = '0100'.
            LEAVE TO TRANSACTION 'ZPPD'.
          ENDIF.
        WHEN '%EX'.
          IF sy-dynnr = '1000'.
            PERFORM exit_program.
          ELSEIF sy-dynnr = '0100'.
            LEAVE TO TRANSACTION 'ZPPD'.
          ENDIF.
        WHEN 'BINP'.
          DATA : ws_x TYPE c VALUE 'X'.
          CALL FUNCTION 'POPUP_TO_CONFIRM'
              EXPORTING
                   titlebar      = 'Posting Documents Via Batch Input'
                   text_question =
               'Are you sure you want to post all the selected documents?'
                   text_button_1 = 'Yes'
                   text_button_2 = 'No'
                   start_column  = 25
                   start_row     = 6
              IMPORTING
                   answer        = ans.
          IF ans = '1'.
            CALL METHOD grid1->check_changed_data
                 IMPORTING
                   e_valid = ws_x.
            xbinp = 'X'.
            PERFORM tbkpf_fuellen.
            IF records = 'X'.
              MESSAGE s999(zv) WITH text-007.
            ELSE.
              PERFORM beleg_pickup.
            ENDIF.
          ENDIF.
        WHEN 'MALL'.
          PERFORM mall.
        WHEN 'EMAL'.
          PERFORM emal.
        WHEN 'RW'.
          IF sy-dynnr = '1000'.
            PERFORM exit_program.
          ELSEIF sy-dynnr = '0100'.
            LEAVE TO TRANSACTION 'ZPPD'.
          ENDIF.
        WHEN 'BUCH'.
          CALL FUNCTION 'POPUP_TO_CONFIRM'
               EXPORTING
                    titlebar      = 'Posting Document'
                    text_question =
                'Are you sure you want to post all documents selected?'
                    text_button_1 = 'Yes'
                    text_button_2 = 'No'
                    start_column  = 25
                    start_row     = 6
               IMPORTING
                    answer        = ans.
          IF ans = '1'.
            CALL METHOD grid1->check_changed_data
              IMPORTING
                e_valid = ws_x.
                perform tbkpf_fuellen.
            IF records = 'X'.
              MESSAGE s999(zv) WITH text-007.
            ELSE.
              PERFORM beleg_pickup.
            ENDIF.
          ENDIF.
        WHEN 'PICK'.
          DATA : check TYPE n,
                 no_rec TYPE c.
          check = 0.
          no_rec = 'X'.
          CALL METHOD grid1->check_changed_data
            IMPORTING
              e_valid = ws_x.
          index = 0.
          LOOP AT gt_vbkpf.
            funcl = 'D'.
            index = index + 1.
            IF gt_vbkpf-xpick = 'X'.
              check = 1.
              CLEAR no_rec.
              READ TABLE gt_vbkpf1 INDEX index INTO vbkpf.
              PERFORM beleg_pickup.
            ENDIF.
          ENDLOOP.
          IF check = 0.
            CALL METHOD grid1->get_selected_rows
              IMPORTING
                et_index_rows = ws_row_idx.
            IF NOT ws_row_idx IS INITIAL.
              CLEAR no_rec.
            ENDIF.
            LOOP AT ws_row_idx INTO i_ws_row_idx.
              READ TABLE gt_vbkpf1 INDEX i_ws_row_idx-index INTO vbkpf.
              PERFORM beleg_pickup.
            ENDLOOP.
            IF no_rec = 'X'.
              MESSAGE s999(zv) WITH text-007.
            ENDIF.
          ENDIF.
        WHEN '&RNT_PREV'.
          CALL METHOD grid1->set_function_code
          CHANGING c_ucomm = ok_code.
        WHEN '&RNT'.
          CALL METHOD grid1->set_function_code
          CHANGING c_ucomm = ok_code.
        WHEN '%SC'.
          CALL METHOD grid1->set_function_code
          CHANGING c_ucomm = ok_code.
        WHEN '&OL0'.
          CALL METHOD grid1->set_function_code
         CHANGING c_ucomm = ok_code.
        WHEN '&OAD'.
          CALL METHOD grid1->set_function_code
          CHANGING c_ucomm = ok_code.
        WHEN '&AVE'.
          CALL METHOD grid1->set_function_code
         CHANGING c_ucomm = ok_code.
        WHEN '&AQW'.
          CALL METHOD grid1->set_function_code
         CHANGING c_ucomm = ok_code.
        WHEN '&XXL'.
          CALL METHOD grid1->set_function_code
         CHANGING c_ucomm = ok_code.
        WHEN '%PC'.
          CALL METHOD grid1->set_function_code
         CHANGING c_ucomm = ok_code.
        WHEN '&CRTEMPL'.
          CALL METHOD grid1->set_function_code
         CHANGING c_ucomm = ok_code.
        WHEN OTHERS.
         do nothing.
      ENDCASE.
      CLEAR ok_code.
    ENDMODULE.                 " PAI_100  INPUT
    *&      Form  exit_program
         Exits from the program after freeing the grid and container     *
    FORM exit_program.
      IF NOT grid_container IS INITIAL.
        CALL METHOD grid_container->free.
      ENDIF.
      IF NOT grid1 IS INITIAL.
        CALL METHOD grid1->free
           EXCEPTIONS
             cntl_error        = 1
             cntl_system_error = 2
             OTHERS            = 3.
      ENDIF.
      LEAVE PROGRAM.
    ENDFORM.                    " exit_program
    *&      Form  f2200_handle_data_changed
          To handle event of change in data in ALV.
         -->P_ER_DATA_CHANGED  text
    FORM f2200_handle_data_changed USING    ir_data_changed
                                             TYPE REF TO
                                             cl_alv_changed_data_protocol.
      DATA : ls_mod_cell TYPE lvc_s_modi ,
             lv_value TYPE lvc_value,
             lflg_check TYPE i.
      DATA : wa_vbkpf LIKE LINE OF gt_vbkpf.
      SORT ir_data_changed->mt_mod_cells BY row_id .
      LOOP AT ir_data_changed->mt_mod_cells
                         INTO ls_mod_cell
                         WHERE fieldname = 'I_PICK'.
        IF NOT ls_mod_cell-value IS INITIAL .
          CALL METHOD ir_data_changed->modify_cell
            EXPORTING
              i_row_id    = ls_mod_cell-row_id
              i_fieldname = ls_mod_cell-fieldname
              i_value     = ls_mod_cell-value.
          READ TABLE gt_vbkpf INTO wa_vbkpf
                     INDEX ls_mod_cell-row_id.
          IF ls_mod_cell-fieldname = 'I_PICK'.
            wa_vbkpf-xpick = ls_mod_cell-value.
          ENDIF.
          MODIFY gt_vbkpf  FROM wa_vbkpf
                              INDEX ls_mod_cell-row_id.
        ENDIF .
      ENDLOOP .
    ENDFORM.                    " f2200_handle_data_changed
    *&      Form  f2201_handle_hotspot
                To handle event of clicking on hyperlink
         -->P_E_COLUMN_ID  text
    FORM f2201_handle_hotspot USING    p_e_column_id  p_e_row_id.
      READ TABLE gt_vbkpf1 INDEX p_e_row_id INTO vbkpf.
      funcl = 'D'.
      PERFORM beleg_pickup.
      PERFORM exit_program.
    ENDFORM.                    " f2201_handle_hotspot
    Regards,
    Susmitha
    Dont forget to reward points for useful answers

  • F-44  ZBAPI MULTIPLE LINE SELECTIONS FOR WEB SERVICES

    HI TO ALL,
              I HAVE WRITTEN ZBAPI FOR POSTING MULTIPLE LINE SELECTIONS FOR TCODE F-44, THE ZBAPI  CONSIST OF BDC PROGRAM, WHICH IS WORKING IN SAP SYSTEM PERFECTLY BUT WHEN I AM USING IT IN WEB SERVICES IT IS THROWING A  ERROR MESSAGE.
                     PLEASE CAN ANY ONE TELL ME DOES THIS PROCESS WILL WORK OR NOT, IF YES HOW IS IT POSSIBLE

    Hi Gabriel,
    Let me try to answer some of your questions:
    1) The "Requires Secure Access" attribute of a resource handler controls whether this handler must be accessed/consumed only over SSL (HTTPS). Oracle Database Cloud Schema Service is only offered over SSL, so this attribute does not have any effect on RESTful services deployed in this environment (because secure access is always required and there is no other way). That said, if you want to access such web service from your own APEX instance, your instance must have Oracle Wallet configured with appropriate SSL certificate.
    2) The URI parameters are not required. If your web service returns data for many entities (for example, list of employees in employees/), you may not need a parameter. If your web service returns data for one specific entity (for example, details of one employee in employees/{id}), you may want to identify that entity with a URI parameter.
    3) You can have many URI parameters, for example: customers/{id}/orders/{order_id}.
    4) Yes, these are the same HTTP methods/verbs you would use from PHP.
    5) If you are trying this POST example from your own APEX instance (not Oracle Database Cloud Schema Service) and you are trying to access a web service over SSL, then it is likely that the Oracle Wallet used by your instance does not include the required SSL certificate(s), or the Oracle Wallet is not configured at all.
    6) I recommend to check RESTful Web Services for the Oracle Database Cloud white paper and Oracle REST Data Services Developers Guide. Oracle REST Data Services is the technology that enables RESTful services in the Oracle Database Cloud Schema Service.
    You can certainly create your own web services in the Oracle Database Cloud Schema Service and consume them from the same environment.
    Vlad

  • Multiple line selection for RRI  in WAD

    Is it possible to select multiple lines from 1 query and do a RRI to the receiver query. Eg : Select multiple POs and then go to PO details query which shows PO details of multiple POs in WAD and both the results shown in the same web report?
    I tried the below solution, but all I get is the display of the entire Master data dump and not the filtered values. Any suggestion?????
    Rao  
    Posts: 135
    Registered: 6/24/04
    Forum Points: 8 
       Re: Multiple line selection for RRI   
    Posted: Feb 4, 2008 2:22 PM    in response to: LAKSHMI HARINDRAN           Reply 
    Yes. You can do this. You create web template with ANALYSIS web item. In the item parameters of ANALYSIS web item, you can set a property, single line or multiple for the runtime selection. Once you do this, you create a button option or context selection menu option to jump target. In the button (RRI button) in the command sequence, the first command should be SET_SELECTION_STATE_BY_BINDING and then, the RRI command to jump to the target. Hope it will help.
    Venny.

    Hi, Do you have any solution on this. please suggest. Thanks

  • DYNP_VALUES_READ Limitations for multiple lines select options

    Hi all !
       First post here, but a tough one I think. Here is my inquiry :
       I have worked on an specific abap function used in many long abap list reports. Theses reports are launched in background processing. The aim of this routine is to stop the report execution if a background job with the same selection parameters is already launched for the current user (to Prevent useless several launch of a time-expensive program).
        Because this routine is dynamic, I read the selection screen of the current report with the function 'DYNP_VALUES_READ'. And I compare the result with the variant of the backgroung job (read with function 'RS_VARIANT_CONTENTS').
        The real problem is that function "DYNP_VALUES_READ" only extract the first line of select-options. I found an alternative solution to extract the select options values (a dynamic assign with field symbols), but external conversions (for WBS elements for example ) are lost, so the comparison detects differences between the background job's variant values and the current selection screen values.
        Does anybody know a way to get entire select options values from a selection screen just as they are displayed on screen ?
    Thanks for reading my message
    Message was edited by: Thomas BRICOUT

    Thomas,
    Perhaps the following code will help you.  A function module in the code captures everything on the selection screen into an internal table.  It doesn't actually capture the information the way you want it, but I believe you will be able to work with it to achieve your desired result.  If it doesn't meet your needs, it is still useful for printing selection screen fields and their values.
    Bruce
    report zybttes2.
    tables: zf137,   " 137 General Ledger Document Details Table
            zf137a.  " 137 General Ledger Document Details Table, Archive
    selection-screen begin of block b1 with frame title text-004." BCT003
    parameters: p_zf137   radiobutton group xxx,                " BCT003
                p_zf137a  radiobutton group xxx.                " BCT003
    selection-screen end of block b1.                           " BCT003
    selection-screen begin of block parameter with frame title text-001.
    selection-screen skip 1.
    select-options: s_date for zf137-zzpostdat.
    selection-screen skip 1.
    selection-screen begin of line.
    selection-screen comment 3(6) text-002.
    selection-screen end of line.
    selection-screen skip 1.
    select-options: s_loan for zf137-zzloan.
    selection-screen skip 1.
    selection-screen begin of line.
    selection-screen comment 3(6) text-003.
    selection-screen end of line.
    selection-screen skip 1.
    select-options: s_ccentr for zf137-zzcostctr.
    selection-screen skip 1.
    selection-screen end of block parameter.
    data: ww(3) type n.
    data: zz(3) type c.
    data: c1(1) type c value '0'.
    do 2 times.
      ww = ww + 1.
      zz = ww.  shift zz left  deleting leading  c1.
      write: / zz.
    enddo.
      Capture and then print the selection screen fields and their values
    data: begin of i_info occurs 20,
            flag,
            olength type x,
            line  like raldb-infoline,
          end of i_info.
    call function 'PRINT_SELECTIONS'
      exporting
        mode      = 'TABLE'
        rname     = sy-cprog
        rvariante = sy-slset
      tables
        infotab   = i_info.
    loop at   i_info.
      write: / i_info-line.
    endloop.
    write:  / 'end'.

  • Multiple line selection for RRI

    Is it possible to select multiple lines  from 1 query and do a RRI to the receiver query. Eg : Select multiple POs and then go to PO details query which shows PO details of multiple POs.
    Also when you do a RRI from 1 q to other , does the filter criteria of 2nd query pop up to the user ?
    thanks in advance ,
    LH

    Hi Lakshmi,
    Yes, it is possible to select multiple lines from one query. It means as you said, if you select multiple PO's i.e., Po's belong to a customer. If 10 PO's belong to single customer, then if you select that customer and Goto RRI in the report, you will get the details of all those 10 PO's in the RRI report. This is done in RSBBS tcode>After creating RRI>Assignment details-->Map the required fields of sender to the reciever queries according to the need.
    When you use RRI, the reciver query, i.e., the second query will contain the filter selection as usual in the normal report when executed.
    Hope this helps u...
    Regards,
    KK.

  • How to capture indexes of multiple rows selected in Advance list

    Hi,
    - I have a prefilled advance list with multiselection enabled.
    - There is a button, associated with an action,which is bind to a eventHandler,that event Handler has script operation which conains the ruby scrpt code.
    - Now when i select multiple rows of that advance list and click on the action,I want to capture the indexes of all the selected rows.
    I tried using following ruby code:
    lead=$data.datalist.LeadSelectedIndex
    But it returns index of only first row selected out of various rows selected.
    So please anyone help me on that.
    Regards ,
    Saurabh Sharma.

    In FP2.6 there is no chance from SDK to have a mass enabled Action and bind to a mulli selection list as a BO Action in the UI Designer, as multiplicity will always be single and only lead selection would be selected.
    this feature comes only in FP3.0.
    So i am not sure what excatly Saurabh wants to do : maybe do some calculations based on multi seletions then i would do the following as also what Christian mentioned
    multiSelect =  ($data.DataList.GetSelectedRowsCount() > 1);
    NoOfRowsSelected = $data.DataList.GetSelectedRowsCount();
    SummationField = 0;
    if ( multiSelect )
       LeadSelection = $data.DataList.LeadSelectedIndex;
       RequiredDataField = $data.DataList.Get(LeadSelection).AnydataField;
       for i in 0..(NoOfRowsSelected - 1)
         currentRow = LeadSelection + i;
          RequiredDataField = $data.DataList.Get(currentRow).AnydataField;
    // imagine this is just add values of the RequiredDataField
         SummationField = SummationField +   RequiredDataField
       end
    end
    So i have not tried this directly - but i hope i make the idea clear.
    Regards,
    Nitesh Pai

  • Multiple line selection in BPS web layout

    Hello experts
    I know there is a "row/column" option for layout in WIB, but it only provides the "radiobutton" but not "checkbox", hence I only can select single line in the layout but not the multiple lines.
    anybody has idea to solve the problem?
    Thanks  Patrick

    Patrick, it's quite difficult to explain it, if you are not familiar with BSP
    I can show only direction for you in such case, because whole implementation is quite hard and depends of you requirements.
    In short, you should generate your application in WIB with "Generate class" set true and keep "Name of generated class" filled.
    Then, you should go to se80, select BSP appication, enter name of your application, then, you will have layout2.htm in Views. This page implements web-layout. You should change HTML and ABAP coding for this page to put checkboxes and write some code to implement your business logic.

  • Hierarchial list display- multiple line selection

    hi all,
        In my program I have multiple item field records under a header field.When I select some of the item record line and press a button on application tool bar the control should be transferred to a transaction code.
        how can I accomplish this in hierarchial sequential list display.
      The code I used is:
    CALL FUNCTION 'REUSE_ALV_HIERSEQ_LIST_DISPLAY'
      EXPORTING
      I_INTERFACE_CHECK              = ' '
       I_CALLBACK_PROGRAM             = GV_PROGNAME
       I_CALLBACK_PF_STATUS_SET       = 'ORDERS'
       I_CALLBACK_USER_COMMAND        = 'USER_COMMAND'
       IS_LAYOUT                      = X_LAYOUT
       IT_FIELDCAT                    = I_FCAT
      IT_EXCLUDING                   =
      IT_SPECIAL_GROUPS              =
       IT_SORT                        = LT_SORT
      IT_FILTER                      =
      IS_SEL_HIDE                    =
      I_SCREEN_START_COLUMN          = 0
      I_SCREEN_START_LINE            = 0
      I_SCREEN_END_COLUMN            = 0
      I_SCREEN_END_LINE              = 0
      I_DEFAULT                      = 'X'
      I_SAVE                         = ' '
      IS_VARIANT                     =
      IT_EVENTS                      =
      IT_EVENT_EXIT                  =
        i_tabname_header               = I_TAB_HEAD
        i_tabname_item                 = I_TAB_ITEM
      I_STRUCTURE_NAME_HEADER        =
      I_STRUCTURE_NAME_ITEM          =
        is_keyinfo                     = IKEYINFO
      IS_PRINT                       =
      IS_REPREP_ID                   =
      I_BYPASSING_BUFFER             =
      I_BUFFER_ACTIVE                =
      IR_SALV_HIERSEQ_ADAPTER        =
      IT_EXCEPT_QINFO                =
      I_SUPPRESS_EMPTY_DATA          = ABAP_FALSE
    IMPORTING
      E_EXIT_CAUSED_BY_CALLER        =
      ES_EXIT_CAUSED_BY_USER         =
      tables
        t_outtab_header                = I_HEADER
        t_outtab_item                  = I_ITEM
    EXCEPTIONS
      PROGRAM_ERROR                  = 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.
    endform.                    " ALV_DISPLAY
    form USER_COMMAND USING r_ucomm LIKE sy-ucomm
                 rs_selfield TYPE slis_selfield.
    *at user-command.
    case r_ucomm.
    when 'SEL'.
    *IF sy-lsind = 1 .
        DO.
          CLEAR wa_item-chk.
          READ LINE sy-index FIELD VALUE wa_item-chk.
          IF sy-subrc <> 0.
            EXIT.
          ELSE.
            CHECK wa_item-chk = 'X'.
            IF rs_selfield-tabindex <> '0'. "CHECKS IF A VALID IS SELECTED OR NOT.
            CHECK i_item IS NOT INITIAL.
            READ TABLE i_item INTO wa_item INDEX rs_selfield-tabindex.
           SET PARAMETER ID 'VST' FIELD wa_item-vstel.
           call transaction 'VL03N' and skip first screen.
           endif.
           endif.
           enddo.
    endcase.
    endform.
                Please help me out with a solution.
                          Thanks in advance.

    hi,
    if u want to go to different transactions according to different fields u have selected than there is one field u can check that
    <b>selfield-fieldname</b>
    IF <b>selfield-fieldname</b> = 'VBELN'.
       SET PARAMETER ID 'VF' FIELD itab-vbeln.
      CALL TRANSACTION 'VF03' AND SKIP FIRST SCREEN.
    ELSEIF <b>selfield-fieldname</b> = 'MATNR'.
      SET PARAMETER ID 'MAT' FIELD t_mat.
      CALL TRANSACTION 'MM03' AND SKIP FIRST SCREEN.
    ENDIF.

  • Multiple line select in TableView

    Hello all!
    I have this problem while working with Tableview. I have to delete multiple rows at a time but not able to.
    I created an instance(<b>lr_tableview</b>) of the class <b>cl_htmlb_tableview</b>. Although the instance is getting loaded correctly, but the selection is not transferred to the server.
    Therefore the attribute
    <b>lr_table_view->data->prevselectedrowindextable is not</b> getting populated with the indices of the selected rows.It is INITIAL all the time.
    Look forward to have some suggestions on how to solve this.
    Thanks and regards,
    Sukanya.

    HI
    GOOD
    GO THROUGH THESE LINKS ,I HOPE YOU WILL GET SOME SOLUTIONS.
    http://help.sap.com/saphelp_nw2004s/helpdata/en/fd/003a3c00b96951e10000000a11405a/content.htm
    http://help.sap.com/saphelp_nw04/helpdata/en/e2/5c3d651ae911d6b1d100508b6b8b11/content.htm
    http://help.sap.com/saphelp_nw04/helpdata/en/d3/4017d9b90afe4999dbf8792638b291/content.htm
    THANKS
    MRUTYUN

  • Multiple Line selection in ALV

    Hi All,
    I have an alv report. In which, i have to get the selected row index values in return. Those selected row index will be used for further processing. I do not need check box selection, as ALV provide that inbuilt facility. Please tell me the parameter name.
    It is urgent.
    Regards
    Gajendra

    Hi,
    Your Call to ALV
    CALL FUNCTION 'REUSE_ALV_GRID_DISPLAY'
    EXPORTING
    I_CALLBACK_PROGRAM = sy-cprog
    I_CALLBACK_USER_COMMAND = 'USER_COMMAND1'
    I_CALLBACK_TOP_OF_PAGE = 'TOP_OF_PAGE'
    IS_LAYOUT = wa_layout
    IT_FIELDCAT = it_fieldcat
    T_OUTTAB = it_rfq
    EXCEPTIONS
    PROGRAM_ERROR = 1
    OTHERS = 2
    Implement a Form Routine with the name you gave for the I_CALLBACK_USER_COMMAND
    eg.,
    FORM user_command1 using ucomm type sy-ucomm
    selfield type slis_selfield.
    case ucomm.
    when '&IC1'.
    read table it_rfq into wa_rfq index selfield-tabindex.
    if sy-subrc eq 0.
    if selfield-fieldname = 'EBELN' " EBELN is the fieldname in Fieldcat
    Do the necessary coding to call the screen here
    endif.
    endif.
    ENDFORM.
    regards,
    Omkar.

  • How to select multiple lines in reports

    Hi,
    how to select multiple lines in a reports and process those selected lines to other activities like BDC.
    Please paste sample report here. or any demo examples . (don't paste ALV report , paste only classical report)
    suppose there are 10 records in output, i want to select 3 records and process other activities like bdc.
    Point will awarded.

    Hi ,
    the o/p in ur case will be a basic list output with a check box enabled in the left .
    Now say there are 10 records in the list output and i have checked 3 of them where checkboxes are enabled .
    And i press a button to submit this to the BDC .
    Here u need to make use of
    READ LINE statement to read the records from the list output and then pass them to the BDC .
    The code would be something like this
    DO .
    Read line index <field> where checkbox <> ' '.
    ENDO.
    You can have a look at the F1 help on read line . This will mkae u clear .
    Hope this gives u an idea.
    Regards,
    Vijay.

  • How to display TEXT more than 500 char in a report as multiple lines.

    Hi Friends,
    i have a requirement like i should display Texts of length more than 500 Characters in a report( ALV LIST) as multiple lines
    I am fetching the data Using FM READ_TEXT
    the output im currently geeting with 150 Char in lenth as a single line
    How we can split the text into multiple lines in a report
    first i would like to know is it possible? if possible please give your valuable suggitions if not is there any alternative way to do this task.
    Thanks & regards
    kumar.

    Hi,
    This is possible but the Solution might not look Standard/Appropriate to you.
    In ALV, you can have Multiple Line Output...There is a Field in the Field Catalogue..called as Row_position...this is by default 0...which means Single row/Line ALV output....You can have this Value in the Range of 0 to 3.......A ALV field with row_position 1, will be displayed in the second line for every record...i.e. you will have multiple line for a single record of ALV.
    In your case......you can use this but you need to split your field in two fields.....but you may end up spliting a single word....but for that also you can design the logic of splitting the Fiel value at SPACE only......
    This may work.......and Sorry if not work......

Maybe you are looking for

  • General questions on IDOCs and IDOCs for 2 Accounting Interface BAPIs

    This post involves several questions pertaining to the topic of IDOC creation. I downloaded a couple of PDFs and tried googling for material on that, but things are far from being clear in my mind. I tried to put my questions in some order, so we can

  • How to connect hdmi

    I have a MacBook Pro and a HDMI cable which once did work, but no longer. Did  software change, did my luck run out?  What can I do to make HDMI cable work again?

  • Dreamweaver Templates

    I have been using a template, creating new pages. All of the sudden when I create a new page, I get the template page, and I cannot edit in the editable regions. What did I do?

  • MDM 5.5 SP05 installation - Anyone installed it on SUSE Linux?

    In accordance to my previous post, I will give the whole story of my installation in order to make it clear. It is about a test server , running Linux SUSE LES 9.3. We want to install on it MDM5.5 (without NetWeaver -stand alone installation) and ORA

  • Inclusion of query in the role?

    Hi, i had created a new query , which does not have any role so far! Now i was asked to include this query in a role! But when i check role button in query designer it says :"you are not assigned to any role" What can be done to include the new query