Report code with ALV

Hi
Can any body provide me the code for report with selection screen using ALV.
Thanks in advance
Prasanna Kumar

Hi Prasanna,
Below is an example of ALV reporting.
*& Report  ZVVF_MR028_STOCKLEDGER                                      *
REPORT  ZVVF_MR028_STOCKLEDGER                  .
*       Tables
TABLES:      EKKO,    "PURCHASING DOC. HEADER
             EKPO,    "PURCHASING DOC. ITEM
             MAKT,    "MATERIAL DISCRIPTION
             LFA1,    "VENDOR MASTER
             RSEG,    "DOC. ITEM - INCOMING INVOICE
             KONV,    "CONDITION (TRANSECTION DATA - CLUSTER TABLE)
             EKPA,    "Partner Roles in Purchasing
             MSEG,
             t247,
             mardh,
             mara.
*       Types                    Begin with TY_
TYPE-POOLS slis.
TYPES  :  BEGIN OF ty_head,
              p_date TYPE dats,
              matnr LIKE mseg-matnr,
              maktx LIKE makt-maktx,
              openbal LIKE mardh-labst,
              r_po LIKE mseg-menge,
              r_prodord LIKE mseg-menge,
              r_byprod LIKE mseg-menge,
              r_others LIKE mseg-menge,
              R_TOTAL TYPE mseg-menge,
              i_prod LIKE mseg-menge,
              i_cust LIKE mseg-menge,
              i_costcen LIKE mseg-menge,
              i_scrapping LIKE mseg-menge,
              i_subcontractor LIKE mseg-menge,
              i_sampling LIKE mseg-menge,
              purret LIKE mseg-menge,
              i_total like mseg-menge,
              stock_out LIKE mseg-menge,
              stock_in LIKE mseg-menge,
              stock_transit LIKE mseg-menge,
              m_to_m_transit  LIKE mseg-menge,
              phy_loss LIKE mseg-menge,
              phy_gain LIKE mseg-menge,
              closing_bal LIKE mseg-menge,
              current_bal LIKE mseg-menge,
              bwart like mseg-bwart,
              werks like mseg-werks,
          END OF ty_head.
types :  begin of ty_docs,
         matnr like mseg-matnr,  "Material
         budat like mkpf-budat,  "Posting date
         menge like mseg-menge,  "Qty
         xblnr like mkpf-xblnr,  "Ref doc
         end of ty_docs.
data : w_cnt type I.
data : w_chk type i.
TYPES: BEGIN OF TY_KONV,
             KNUMV LIKE KONV-KNUMV,
             KBETR LIKE KONV-KBETR,
             KSCHL LIKE KONV-KSCHL,
             KWERT LIKE KONV-KAWRT,
       END OF TY_KONV.
TYPES: BEGIN OF TY_KBETR,
*              KBETR LIKE KONV-KBETR,
              KWERT LIKE KONV-KWERT,
          END OF TY_KBETR.
TYPES: BEGIN OF TY_RSEG,
              EBELN LIKE RSEG-EBELN,
              MATNR LIKE RSEG-MATNR,
              WRBTR LIKE RSEG-WRBTR,
              KSCHL LIKE RSEG-KSCHL,
              LIFNR LIKE RSEG-LIFNR,
          END OF TY_RSEG.
TYPES: BEGIN OF TY_NAME1,
              NAME1 LIKE LFA1-NAME1,
       END OF TY_NAME1.
** Each Condition and their values w.r.t different docu types
*data: begin of temp_head occurs 0,
*        kschl  like  konv-kschl,  " Condition type
*        kwert  like  konv-kwert,  " Condition value
*      end of temp_head.
*       Constants                Begin with C_
CONSTANTS: st_formname_top_of_page TYPE slis_formname
                              VALUE 'TOP_OF_PAGE-ALV'.
*       Data                     Begin with W_
*-------- Declarations for ALV Grid.
DATA:   it_st_list_top_of_page TYPE slis_t_listheader,
        it_st_fieldcat TYPE slis_t_fieldcat_alv,
        it_st_events   TYPE slis_t_event,
        st_layout   TYPE slis_layout_alv,
        s_status TYPE slis_formname VALUE 'STANDARD_ST01',
        s_user_command TYPE slis_formname VALUE 'USER_COMMAND-ALV',
        s_repid LIKE sy-repid,
        s_save(1) TYPE c,
        s_variant LIKE disvariant,
        code LIKE disvariant-handle.
data : begin of it_stockclose occurs 0,
       werks like s031-werks,   "Plant
       matnr like mara-matnr,   "Material
       lgort like mard-lgort,   "Storage Loc
       labst like mardh-labst,  "Unrestricted Stock
       insme like mardh-insme,  "Inspection Stock
       speme like mardh-speme,  "Safety stock
       einme like mardh-einme,  "Total stock of rest batches
       retme like mardh-retme,  "Blocked stock returns
       end of it_stockclose.
data : begin of it_finalstock occurs 0,
       werks like mseg-werks,   "Plant
       matnr like mseg-matnr,   "Material code
       lgort like mard-lgort,   "Sto Loc
       menge like mseg-menge,   "Qty
*       budat like mkpf-budat,   "Posting Date
       end of it_finalstock.
data : begin of it_docs occurs 0,
       matnr like mseg-matnr,   "Material code
       budat like mkpf-budat,   "Posting date
       bwart like mseg-bwart,   "Movement type
       menge like mseg-menge,   "Quantity
       werks like mseg-werks,   "Plant
       shkzg like mseg-shkzg,   "Credit/debit
       lgort like mseg-lgort,   "Sto Loc
       maktx like makt-maktx,   "Material Discription
       end of it_docs.
data : begin of it_mkpf occurs 0,
       budat like mkpf-budat,   "Posting date
       mblnr like mkpf-mblnr,   "Material Doc
       xblnr like mkpf-xblnr,   "Delivery ref no
       mjahr like mkpf-mjahr,   "Fiscal yr
       cpudt like mkpf-cpudt,
       end of it_mkpf.
data : begin of it_mseg occurs 0,
       matnr like mseg-matnr,   "Material
       bwart like mseg-bwart,   "Movement type
       menge like mseg-menge,   "Qty
       werks like mseg-werks,   "Plant
       mjahr like mseg-mjahr,   "Fiscal yr
       shkzg like mseg-shkzg,   "Credit/Debit Indicator
       lgort like mard-lgort,   "Sto loc
       budat like mkpf-budat,   "Posting date
       xblnr like mkpf-xblnr,   "Delivery ref
       cpudt like mkpf-cpudt,
       end of it_mseg.
data : begin of it_matnr occurs 0,
       matnr like mara-matnr,   "Material
       end of it_matnr.
data : w_monat  type monat.    "Month number
data : w_gjahr like sy-datum,    "Date
       w_date_fiscal(4) type n,  "Year
       w_date like sy-datum,     "Date
       w_buper like t009b-poper, "Posting period
       w_year like t009b-bdatj,  "Posting date
       w_datum(2) type n.        "Date
*       Internal tables          Begin with IT_
DATA    :  IT_HEAD TYPE STANDARD TABLE OF TY_HEAD WITH HEADER LINE.
***Issues and receipts
data : it_issue type ty_docs occurs 0 with header line,
       it_receipt type ty_docs occurs 0 with header line,
       it_issue_date type ty_docs occurs 0 with header line,
       it_receipt_date type ty_docs occurs 0 with header line.
data:   w_dval like mseg-menge,
        w_opbal like mseg-menge.
**  WORK AREAS: Begin with WA_
*DATA: wa_HEAD type TY_HEAD.
*data: w_tkwert    type p decimals 2 value 0,
*      grmenge     like ekpo-menge,
*      w_tot_kwert type p decimals 2 value 0,
*      w_tmp_kwert type p decimals 2 value 0,
*      w_finalsum  type p decimals 2 value 0,                "#EC *
*      w_finalrate type p decimals 4 value 0.                "#EC *
*       R A N G E S
ranges: r_loekz  for  ekko-loekz.  " Deletion Indicator
ranges : r_movtype for mseg-bwart,   "Movement type
         r_date for sy-datum.        "Date
*       Select Options          Begin with SO_
SELECTION-SCREEN BEGIN OF BLOCK MAIN WITH FRAME TITLE TEXT-001.
SELECTION-SCREEN SKIP 2.
*SELECT-OPTIONS : SO_LIFNR FOR EKKO-LIFNR.
*SELECT-OPTIONS : SO_EKORG FOR EKKO-EKORG .
*SELECT-OPTIONS : SO_WERKS FOR MSEG-WERKS .
*SELECT-OPTIONS : SO_EBELN FOR EKKO-EBELN.
*SELECT-OPTIONS : SO_DATE for sy-datum obligatory no-extension.
*SELECT-OPTIONS : SO_EKGRP FOR EKKO-EKGRP.
*SELECT-OPTIONS : SO_BSART FOR EKKO-BSART DEFAULT 'NB'.
*SELECT-OPTIONS : SO_MATKL FOR EKPO-MATKL.
*SELECT-OPTIONS : SO_MATNR FOR MSEG-MATNR.
select-options   : so_werks for mseg-werks default 'P001'. "Plant
select-options   : so_lgort for mseg-lgort. " Sto. Location
select-options   : so_matnr for mseg-matnr obligatory. "Material code
select-options   : so_mtart for mara-mtart. "Material type
SELECT-OPTIONS   : SO_MATKL FOR EKPO-MATKL. "Material Group
select-options   : so_date for sy-datum obligatory no-extension.
SELECTION-SCREEN SKIP 2.
selection-screen: skip,
                  begin of line,
                  comment (15) text-034.
parameters:     p_all    radiobutton group del.
selection-screen comment 25(9) for field p_all.
parameters:     p_del    radiobutton group del.
selection-screen comment 45(12) for field p_del.
parameters:     p_undel  radiobutton group del default 'X'.
selection-screen comment 65(14) for field p_undel.
selection-screen end of line.
SELECTION-SCREEN SKIP 2.
SELECTION-SCREEN END OF BLOCK MAIN.
*       Parameters              Begin with PR_
*       Initialisation
INITIALIZATION.
  s_repid = sy-repid.
  s_save = 'A'.
  perform f000_initialize_mov_type changing r_movtype[].
  PERFORM eventtab_build USING it_st_events[].
  PERFORM variant_init.
*       S T A R T   O F   S E L E C T I O N
START-OF-SELECTION.
  PERFORM initialize.
  perform f001_determine_fiscal_period.
  perform f002_determine_closing_stock changing it_stockclose[].
  if not so_date-low+6(2) eq '01'.
    perform f003_change_closing_stock changing  it_stockclose[].
  endif.
  perform f004_determine_mat_docs changing it_mkpf[]
                                             it_mseg[].
  perform f005_receipts_issues using    it_mseg[]
                                 changing it_issue[]
                                          it_receipt[]
                                          it_matnr[].
*---alv
  PERFORM comment_build USING it_st_list_top_of_page[].
  PERFORM fieldcat USING it_st_fieldcat[].
  PERFORM layout_build USING st_layout.
  PERFORM reuse_alv_list_display.
END-OF-SELECTION.
form initialize.
  clear:   r_loekz.
  refresh: r_loekz.
*--- Deleted PO's only
  if p_del = 'X'.
    r_loekz-sign   = 'I'.
    r_loekz-option = 'EQ'.
    r_loekz-low    = 'L'.
    append r_loekz.
  endif.
*--- UnDeleted PO's only
  if p_undel = 'X'.
    r_loekz-sign   = 'E'.
    r_loekz-option = 'EQ'.
    r_loekz-low    = ' '.
    append r_loekz.
  endif.
endform.                    "initialize
*&      Form  f000_initialize_mov_type
*       Desc : Initialization of movement types
form f000_initialize_mov_type  changing p_r_movtype like r_movtype[].
  data : lwa_movtype like line of p_r_movtype.
  lwa_movtype-sign = 'I'.
  lwa_movtype-option = 'EQ'.
  lwa_movtype-low = '101'.
  append lwa_movtype to p_r_movtype.
  lwa_movtype-low = '102'.
  append lwa_movtype to p_r_movtype.
* Additional changes done for other movement types--> by deepak
  lwa_movtype-low = '103'.
  append lwa_movtype to p_r_movtype.
  lwa_movtype-low = '104'.
  append lwa_movtype to p_r_movtype.
  lwa_movtype-low = '105'.
  append lwa_movtype to p_r_movtype.
  lwa_movtype-low = '106'.
  append lwa_movtype to p_r_movtype.
  lwa_movtype-low = '122'.
  append lwa_movtype to p_r_movtype.
  lwa_movtype-low = '123'.
  append lwa_movtype to p_r_movtype.
  lwa_movtype-low = '161'.
  append lwa_movtype to p_r_movtype.
  lwa_movtype-low = '162'.
  append lwa_movtype to p_r_movtype.
  lwa_movtype-low = '201'.
  append lwa_movtype to p_r_movtype.
  lwa_movtype-low = '202'.
  append lwa_movtype to p_r_movtype.
  lwa_movtype-low = '261'.
  append lwa_movtype to p_r_movtype.
  lwa_movtype-low = '262'.
  append lwa_movtype to p_r_movtype.
  lwa_movtype-low = '301'.
  append lwa_movtype to p_r_movtype.
  lwa_movtype-low = '302'.
  append lwa_movtype to p_r_movtype.
  lwa_movtype-low = '303'.
  append lwa_movtype to p_r_movtype.
  lwa_movtype-low = '304'.
  append lwa_movtype to p_r_movtype.
  lwa_movtype-low = '305'.
  append lwa_movtype to p_r_movtype.
  lwa_movtype-low = '306'.
  append lwa_movtype to p_r_movtype.
  lwa_movtype-low = '309'.
  append lwa_movtype to p_r_movtype.
  lwa_movtype-low = '310'.
  append lwa_movtype to p_r_movtype.
  lwa_movtype-low = '331'.
  append lwa_movtype to p_r_movtype.
  lwa_movtype-low = '332'.
  append lwa_movtype to p_r_movtype.
  lwa_movtype-low = '333'.
  append lwa_movtype to p_r_movtype.
  lwa_movtype-low = '334'.
  append lwa_movtype to p_r_movtype.
  lwa_movtype-low = '335'.
  append lwa_movtype to p_r_movtype.
  lwa_movtype-low = '336'.
  append lwa_movtype to p_r_movtype.
  lwa_movtype-low = '511'.
  append lwa_movtype to p_r_movtype.
  lwa_movtype-low = '512'.
  append lwa_movtype to p_r_movtype.
  lwa_movtype-low = '531'.
  append lwa_movtype to p_r_movtype.
  lwa_movtype-low = '532'.
  append lwa_movtype to p_r_movtype.
  lwa_movtype-low = '541'.
  append lwa_movtype to p_r_movtype.
  lwa_movtype-low = '542'.
  append lwa_movtype to p_r_movtype.
  lwa_movtype-low = '561'.
  append lwa_movtype to p_r_movtype.
  lwa_movtype-low = '562'.
  append lwa_movtype to p_r_movtype.
  lwa_movtype-low = '601'.
  append lwa_movtype to p_r_movtype.
  lwa_movtype-low = '602'.
  append lwa_movtype to p_r_movtype.
  lwa_movtype-low = '641'.
  append lwa_movtype to p_r_movtype.
  lwa_movtype-low = '642'.
  append lwa_movtype to p_r_movtype.
  lwa_movtype-low = '643'.
  append lwa_movtype to p_r_movtype.
  lwa_movtype-low = '644'.
  append lwa_movtype to p_r_movtype.
  lwa_movtype-low = '701'.
  append lwa_movtype to p_r_movtype.
  lwa_movtype-low = '702'.
  append lwa_movtype to p_r_movtype.
  lwa_movtype-low = '909'.
  append lwa_movtype to p_r_movtype.
  lwa_movtype-low = '910'.
  append lwa_movtype to p_r_movtype.
endform.                    " f000_initialize_mov_type
*&      Form  f001_determine_fiscal_period
*       Desc  Determination of fiscal period
form f001_determine_fiscal_period .
  clear : w_monat,
          w_gjahr,
          w_date,
          w_buper,
          w_year.
  w_monat = so_date-low+4(2).
  if w_monat = '01'.
    w_monat = '12'.
    w_gjahr = so_date-low+0(4).
    w_date_fiscal = w_gjahr+0(4) - 1.
    w_gjahr = w_date_fiscal.
  else.
    w_monat = w_monat - 1.
    w_gjahr = so_date-low+0(4).
  endif.
  concatenate w_gjahr w_monat '01'  into w_gjahr.
*****Determines Fiscal yr and period
  call function 'DATE_TO_PERIOD_CONVERT'
    EXPORTING
      i_date  = w_gjahr
      i_periv = 'V3'
    IMPORTING
      e_buper = w_buper
      e_gjahr = w_year.
  if sy-subrc <> 0.
  endif.
  w_datum = w_buper+1(2).
**Month text
  select single ltx from t247 into t247-ltx
         where spras = 'E'
         and   mnr   = so_date-low+4(2).
endform.                    " f001_determine_fiscal_period
*&      Form  f001_determine_closing_stock
*       Desc : Determination of closing stock
form f002_determine_closing_stock
                   changing p_it_stockclose like it_stockclose[].
  data : lw_recs type i,
         w_dval like mseg-menge,
         w_opbal like mseg-menge.
  data : begin of lit_stockclose occurs 0,
         lfgja like mardh-lfgja,   "Fiscal yr
         lfmon like mardh-lfmon,   "Period
         werks like s031-werks,   "Plant
         matnr like mara-matnr,   "Material
         lgort like mseg-lgort,   "Storage Loc
         labst like mardh-labst,  "Unrestricted Stock
       end of lit_stockclose.
  data : begin of lit_mard occurs 0,
         matnr like mara-matnr,
         werks like mseg-werks,
         lgort like mseg-lgort,
         end of lit_mard.
  data : lwa_stockclose like line of p_it_stockclose.
  select matnr werks lgort from mard
  into corresponding fields of table lit_mard
  where matnr in so_matnr
  and werks in so_werks.
  refresh it_stockclose.
  clear   it_stockclose.
*****Fetch Closing stock
*If the entry is found in MARD then consider the same
*else fetch the closing stock from MARDH.
  loop at lit_mard.
    refresh lit_stockclose.
    clear   lit_stockclose.
    select werks matnr lgort labst
          insme speme einme retme
          lfgja lfmon
           into corresponding fields of
            table lit_stockclose
           from mard
    where   lfmon = w_datum
    and     lfgja = w_year
    and     werks = lit_mard-werks
    and     matnr = lit_mard-matnr
    and     lgort = lit_mard-lgort.
    clear lw_recs.
    describe table lit_stockclose lines lw_recs.
*If no entry in MARD fetch from MARDH.
    if lw_recs = 0.
      select werks matnr lgort labst
            insme speme einme retme
            lfgja lfmon
             into corresponding fields of
            table lit_stockclose
            from mardh
     where   lfmon = w_datum
     and     lfgja = w_year
     and     werks = lit_mard-werks
     and     matnr = lit_mard-matnr
     and     lgort = lit_mard-lgort.
    endif.
    sort lit_stockclose by lfgja lfmon descending.
    read table lit_stockclose index 1.
    if sy-subrc eq 0.
      move-corresponding lit_stockclose to lwa_stockclose.
      append  lwa_stockclose to p_it_stockclose.
      clear  lwa_stockclose.
    endif.
  endloop.
endform.                    " f001_determine_closing_stock
*&      Form   f003_change_closing_stock
*       Desc : Selection of the mat docs for the intermediate
*              days if the selection begin date is not from
*              first date of the corresponding month.
form f003_change_closing_stock changing
                                   p_it_stockclose like it_stockclose[].
  data : lwa_stockclose like line of p_it_stockclose[].
  refresh : r_date,
            it_docs,
            it_finalstock.
  clear : r_date,
          lwa_stockclose.
  r_date-sign = 'I'.
  r_date-option = 'BT'.
  concatenate so_date-low+0(4)
              so_date-low+4(2)
              '01'
              into r_date-low.
  r_date-high = so_date-low - 1.
  append r_date.
  clear r_date.
read table r_loekz index 1.
  select mkpf~budat
         mseg~matnr
         mseg~bwart
         mseg~menge
         mseg~werks
         mseg~shkzg
         mseg~lgort
         makt~maktx
         into corresponding
         fields of
         table it_docs
         from mkpf as mkpf inner join mseg as mseg
         on mkpf~mandt = mseg~mandt and
            mkpf~mblnr = mseg~mblnr and
            mkpf~mjahr = mseg~mjahr
         inner join makt as makt
           on mseg~matnr = makt~matnr
         where
            mseg~werks IN SO_WERKS and
            mseg~matnr in so_matnr and
            mkpf~budat in r_date and
            mseg~bwart in r_movtype.
  Clear it_docs.
  loop at it_docs.
    if it_docs-shkzg = 'H'.
      it_docs-menge = - ( it_docs-menge ).
      modify it_docs.
    endif.
    move-corresponding it_docs to it_finalstock.
    collect it_finalstock.
    clear   it_finalstock.
    move it_docs-maktx to it_head-maktx.
  endloop.
  loop at p_it_stockclose into lwa_stockclose.
    read table it_finalstock with key
                       matnr = lwa_stockclose-matnr
                       werks = lwa_stockclose-werks
                       lgort = lwa_stockclose-lgort.
    if sy-subrc eq 0.
      lwa_stockclose-labst = lwa_stockclose-labst +
                             it_finalstock-menge.
      modify p_it_stockclose from lwa_stockclose.
      read table p_it_stockclose into lwa_stockclose index 1.
      "with key matnr = wa_head-matnr.
      "budat = wa_head-p_date.
      if sy-subrc = 0.
        w_dval = lwa_stockclose-labst.
      ENDIF.
      clear lwa_stockclose.
    endif.
  endloop.
endform.                    " f003_change_closing_stock
*&      Form  f004_determine_mat_docs
*       DEsc : Determination of Receipts and Issues
form f004_determine_mat_docs  changing p_it_mkpf like it_mkpf[]
                                       p_it_mseg like it_mseg[].
  data : lwa_mkpf like line of p_it_mkpf[],
         lwa_mseg like line of p_it_mseg[],
          ls_quantity   type mseg-menge,
          sum_issue type mseg-menge,
          sum_receipt type mseg-menge,
          sum_531 type mseg-menge,
          sum_541 type mseg-menge,
          sum_101  type mseg-menge,
          sum_511  type mseg-menge,
          sum_261  type mseg-menge,
          sum_601  type mseg-menge,
          sum_201 type mseg-menge,
          sum_641 type mseg-menge,
          sum_po  type mseg-menge,
          sum_551  type mseg-menge,
          sum_331  type mseg-menge,
          sum_161  type mseg-menge,
          sum_305  type mseg-menge,
          sum_309  type mseg-menge,
          sum_701  type mseg-menge,
          sum_702  type mseg-menge.
***Determination of Mat Docs
  select mblnr xblnr budat mjahr cpudt from mkpf
         into corresponding fields
         of table it_mkpf
         where budat in so_date.
***Determination of Receipts and issues
*  loop at p_it_mkpf into lwa_mkpf.
*    select mblnr matnr bwart menge werks mjahr shkzg lgort
*          from mseg into corresponding
*          fields of lwa_mseg
*          where mblnr = lwa_mkpf-mblnr
*          and   mjahr = lwa_mkpf-mjahr
*          and   werks in so_werks
*          and   matnr in so_matnr
*          and   bwart in r_movtype.
*      if lwa_mseg-shkzg = 'H'.
*        lwa_mseg-menge = - ( lwa_mseg-menge ).
*      endif.
*      move : lwa_mkpf-budat to lwa_mseg-budat,
*             lwa_mkpf-xblnr to lwa_mseg-xblnr,
*             lwa_mkpf-cpudt to lwa_mseg-cpudt.
*      append lwa_mseg to p_it_mseg.
*      move lwa_mseg-matnr to it_head-matnr.
*      move lwa_mseg-budat to it_head-p_date.
*      move lwa_mseg-bwart to it_head-bwart.
*      append it_head.
*      clear it_head.
*      clear lwa_mseg.
*    endselect.
*  endloop.
  sort it_mkpf by budat cpudt .
  loop at it_mkpf.
    at new budat.
      if w_opbal = SPACE.
        it_head-openbal = w_dval.
        w_chk = 1.
      else.
        it_head-openbal = w_opbal.
        w_chk = 2.
      endif.
    endat.
    if w_chk = 1.
      it_head-openbal = w_dval.
    elseif w_chk = 2.
      it_head-openbal = w_opbal.
    endif.
    select  Single *
          from mseg
          where mblnr = it_mkpf-mblnr
          and   mjahr = it_mkpf-mjahr
          and   werks in so_werks
          and   matnr in so_matnr
          and   bwart in r_movtype.
    if mseg-matnr ne SPACE.
      move mseg-mblnr to it_mseg-xblnr.
      move mseg-matnr to it_mseg-matnr.
      move mseg-bwart to IT_mseg-bwart.
      move mseg-menge to it_mseg-menge.
      move mseg-werks to it_mseg-werks.
      move mseg-mjahr to it_mseg-mjahr.
      move mseg-shkzg to it_mseg-shkzg.
      move mseg-lgort to it_mseg-lgort.
      if it_mseg-shkzg = 'H'.
        it_mseg-menge = - ( lwa_mseg-menge ).
      endif.
      move : it_mkpf-budat to it_mseg-budat,
             it_mkpf-xblnr to it_mseg-xblnr,
             it_mkpf-cpudt to it_mseg-cpudt.
*      append lwa_mseg to p_it_mseg.
      append it_mseg.
*  it_head-R_PO = it_head-r_po + ls_quantity.
      if ( it_mseg-bwart eq '101'
         or   it_mseg-bwart eq '102'
         or   it_mseg-bwart eq '103'
         or   it_mseg-bwart eq '104'
         or   it_mseg-bwart eq '105'
         or  it_mseg-bwart eq '106'
         or  it_mseg-bwart eq '161'
         or  it_mseg-bwart eq '162'
         or  it_mseg-bwart eq '122'
         or  it_mseg-bwart eq '123'
         or  it_mseg-bwart eq '511'
         or  it_mseg-bwart eq '512'
         or  it_mseg-bwart eq '531'
         or  it_mseg-bwart eq '532'
         or  it_mseg-bwart eq '561'
         or  it_mseg-bwart eq '562'
         or  it_mseg-bwart eq '305'
         or  it_mseg-bwart eq '306'
         or  it_mseg-bwart eq '702') and it_mseg-shkzg = 'S'.
        move it_mseg-menge to ls_quantity.
        sum_receipt = sum_receipt + ls_quantity.
      elseif
       ( it_mseg-bwart eq '261'
         or   it_mseg-bwart eq '262'
         or   it_mseg-bwart eq '601'
         or   it_mseg-bwart eq '602'
         or   it_mseg-bwart eq '201'
         or  it_mseg-bwart eq '202'
         or  it_mseg-bwart eq '551'
         or  it_mseg-bwart eq '552'
         or  it_mseg-bwart eq '541'
         or  it_mseg-bwart eq '542'
         or  it_mseg-bwart eq '331'
         or  it_mseg-bwart eq '332'
         or  it_mseg-bwart eq '333'
         or  it_mseg-bwart eq '334'
         or  it_mseg-bwart eq '335'
         or  it_mseg-bwart eq '336'
         or  it_mseg-bwart eq '641'
         or  it_mseg-bwart eq '642'
         or  it_mseg-bwart eq '643'
         or  it_mseg-bwart eq '644'
         or  it_mseg-bwart eq '351'
         or  it_mseg-bwart eq '352'
         or  it_mseg-bwart eq '301'
         or  it_mseg-bwart eq '302'
         or  it_mseg-bwart eq '303'
         or  it_mseg-bwart eq '304'
         or  it_mseg-bwart eq '309'
         or  it_mseg-bwart eq '310'
         or  it_mseg-bwart eq '909'
         or  it_mseg-bwart eq '910'
         or  it_mseg-bwart eq '701')  and it_mseg-shkzg = 'S'.
         move it_mseg-menge to ls_quantity.
        sum_issue = sum_issue + ls_quantity.
      endif.
    if ( it_mseg-bwart eq '101' or it_mseg-bwart eq '102'
        or it_mseg-bwart eq '103' or it_mseg-bwart eq '104'
        or it_mseg-bwart eq '105' or it_mseg-bwart eq '106')
        And it_mseg-shkzg = 'S'.
        move it_mseg-menge to ls_quantity.
        sum_po = sum_po + ls_quantity.
      endif.
      if ( it_mseg-bwart eq '531'
         or it_mseg-bwart eq '532') and it_mseg-shkzg = 'S'.
        move it_mseg-menge to ls_quantity.
        sum_531 = sum_531 + ls_quantity.
      endif.
      if ( it_mseg-bwart eq '541' or it_mseg-bwart eq '542' ).
        move it_mseg-menge to ls_quantity.
        sum_541 = sum_541 + ls_quantity.
      endif.
      if ( it_mseg-bwart eq '102' or it_mseg-bwart eq '102' ).
        move it_mseg-menge to ls_quantity.
        sum_101 = sum_101 + ls_quantity.
      endif.
      if ( it_mseg-bwart eq '561' or it_mseg-bwart eq '562'
          OR IT_MSEG-BWART EQ '511' OR it_mseg-bwart eq '512').
        move it_mseg-menge to ls_quantity.
        sum_511 = sum_511 + ls_quantity.
      endif.
      if ( it_mseg-bwart eq '261' or it_mseg-bwart eq '262').
        move it_mseg-menge to ls_quantity.
        sum_261 = sum_261 + ls_quantity.
      endif.
      if ( it_mseg-bwart eq '601' or it_mseg-bwart eq '602').
        move it_mseg-menge to ls_quantity.
        sum_601 = sum_601 + ls_quantity.
      endif.
      if ( it_mseg-bwart eq '201' or it_mseg-bwart eq '202').
        move it_mseg-menge to ls_quantity.
        sum_201 = sum_201 + ls_quantity.
      endif.
    if ( it_mseg-bwart eq '551' or it_mseg-bwart eq '552').
        move it_mseg-menge to ls_quantity.
        sum_551 = sum_551 + ls_quantity.
      endif.
    if ( it_mseg-bwart eq '331' or it_mseg-bwart eq '332'
          or it_mseg-bwart eq '333' or it_mseg-bwart eq '334'
          or it_mseg-bwart eq '335' or it_mseg-bwart eq '336').
        move it_mseg-menge to ls_quantity.
        sum_331 = sum_331 + ls_quantity.
      endif.
    if ( it_mseg-bwart eq '161' or it_mseg-bwart eq '162'
          or it_mseg-bwart eq '123' or it_mseg-bwart eq '122').
        move it_mseg-menge to ls_quantity.
        sum_161 = sum_161 + ls_quantity.
      endif.
    if ( it_mseg-bwart eq '641' or it_mseg-bwart eq '642'
          or it_mseg-bwart eq '643' or it_mseg-bwart eq '644'
          or it_mseg-bwart eq '351' or it_mseg-bwart eq '352'
          or it_mseg-bwart eq '301' or it_mseg-bwart eq '302'
          or it_mseg-bwart eq '303' or it_mseg-bwart eq '304').
        move it_mseg-menge to ls_quantity.
        sum_641 = sum_641 + ls_quantity.
      endif.
  if ( it_mseg-bwart eq '305' or it_mseg-bwart eq '306').
        move it_mseg-menge to ls_quantity.
        sum_305 = sum_305 + ls_quantity.
      endif.
  if ( it_mseg-bwart eq '309' or it_mseg-bwart eq '310'
     or it_mseg-bwart eq '909' or it_mseg-bwart eq '910').
        move it_mseg-menge to ls_quantity.
        sum_309 = sum_309 + ls_quantity.
      endif.
if ( it_mseg-bwart eq '701').
        move it_mseg-menge to ls_quantity.
        sum_701 = sum_701 + ls_quantity.
      endif.
if ( it_mseg-bwart eq '702').
        move it_mseg-menge to ls_quantity.
        sum_702 = sum_702 + ls_quantity.
      endif.
      at end of budat.
    it_head-closing_bal = ( it_head-openbal + sum_receipt ) - sum_issue.
        w_opbal = it_head-closing_bal.
        move it_mseg-matnr to it_head-matnr.
        move it_mseg-budat to it_head-p_date.
        move it_mseg-bwart to it_head-bwart.
        move sum_po  to it_head-R_po.
        move sum_101  to it_head-R_ProdOrd.
        move sum_531 to it_head-R_ByProd.
        move sum_511  to it_head-R_OTHERS.
        move sum_receipt to it_head-r_total.
        move sum_261  to it_head-I_Prod.
        move sum_601  to it_head-I_cust.
        move sum_201  to it_head-I_CostCen.
        move sum_551  to it_head-I_Scrapping.
        move sum_541 to it_head-I_subcontractor.
        move sum_331  to it_head-I_Sampling.
        move sum_issue   to it_head-i_total.
        move sum_161  to it_head-PurRet.
        move sum_641  to it_head-stock_out.
        move sum_305  to it_head-stock_in.
        move sum_309  to it_head-M_to_M_transit.
        move sum_701  to it_head-phy_loss.
        move sum_702  to it_head-phy_gain.
        append it_head.
        w_chk = 0.
        sum_issue = 0.
        sum_receipt = 0.
        sum_531 = 0.
        sum_541 = 0.
        sum_101 = 0.
        SUM_511 = 0.
        sum_261 = 0.
        sum_601 = 0.
        sum_201 = 0.
        sum_po = 0.
        sum_551 = 0.
        sum_641 = 0.
        sum_701 = 0.
        sum_702 = 0.
      endat.
      clear it_head.
      clear it_mseg.
    endif.
endloop.
  sort it_mseg by matnr budat bwart.
  sort it_head by matnr p_date bwart.
  delete ADJACENT duplicates from it_head.
endform.                    " f004_determine_mat_docs
*&      Form  f005_receipts_issues
*       Desc
form f005_receipts_issues  using    p_it_mseg  like it_mseg[]
                           changing p_it_issue like it_issue[]
                                    p_it_receipt like it_receipt[]
                                    p_it_matnr like it_matnr[].
  data : lwa_mseg like line of p_it_mseg[],
         lwa_issue like line of p_it_issue[],
         lwa_receipt like line of p_it_receipt[],
         lwa_matnr like line of p_it_matnr[],
         ls_quantity   type mseg-menge,
         wa_head type ty_head,
         lwa_stockclose like line of it_stockclose[].
*  sort it_head by bwart p_date matnr.
*  loop at it_head into wa_head.
*    read table p_it_mseg into lwa_mseg with key bwart = wa_head-bwart.
*    if sy-subrc = 0.
*      if ( lwa_mseg-bwart eq '101'
*          or   lwa_mseg-bwart eq '102'
*          or   lwa_mseg-bwart eq '103'
*          or   lwa_mseg-bwart eq '104'
*          or   lwa_mseg-bwart eq '105'
*          or  lwa_mseg-bwart eq '106') and lwa_mseg-shkzg = 'S'.
*        loop at p_it_mseg into lwa_mseg where matnr = wa_head-matnr
*                                        and   budat = wa_head-p_date
*                                        and   bwart = wa_head-bwart.
*          move lwa_mseg-menge to ls_quantity.
*          wa_head-R_PO = ls_quantity + wa_head-R_PO.
*          modify it_head from wa_head.
*        endloop.
*        clear ls_quantity .
*      endif.
*      if ( lwa_mseg-bwart eq '641'
*       and lwa_mseg-shkzg = 'S' ).
*        loop at p_it_mseg into lwa_mseg where matnr = wa_head-matnr
*                                        and   budat = wa_head-p_date
*                                        and   bwart = wa_head-bwart.
*          IF SY-SUBRC = 0 .
*            move lwa_mseg-menge to ls_quantity.
*            wa_head-stock_out = ls_quantity + wa_head-stock_out.
*            modify it_head from wa_head.
*          ENDIF.
*        endloop.
*        clear ls_quantity .
*      endif.
*      read table it_stockclose into lwa_stockclose
*         with key matnr = wa_head-matnr.
*                  "budat = wa_head-p_date.
*      if sy-subrc = 0.
*        wa_head-openbal = lwa_stockclose-labst.
*        modify it_head from wa_head.
*      ENDIF.
*    endif.
*  endloop.
*  sort it_head by bwart p_date matnr.
*  loop at it_head into wa_head.
*    read table it_mseg into lwa_mseg with key bwart = wa_head-bwart.
*    if sy-subrc = 0.
*      if ( lwa_mseg-bwart eq '101'
*          or   lwa_mseg-bwart eq '102'
*          or   lwa_mseg-bwart eq '103'
*          or   lwa_mseg-bwart eq '104'
*          or   lwa_mseg-bwart eq '105'
*          or  lwa_mseg-bwart eq '106') and lwa_mseg-shkzg = 'S'.
*        loop at it_mseg into lwa_mseg where matnr = wa_head-matnr
*                                        and   budat = wa_head-p_date
*                                        and   bwart = wa_head-bwart.
*          move lwa_mseg-menge to ls_quantity.
*          wa_head-R_PO = ls_quantity + wa_head-R_PO.
*          modify it_head from wa_head.
*        endloop.
*        clear ls_quantity .
*      endif.
*      if ( lwa_mseg-bwart eq '641'
*       and lwa_mseg-shkzg = 'S' ).
*        loop at it_mseg into lwa_mseg where matnr = wa_head-matnr
*                                        and   budat = wa_head-p_date
*                                        and   bwart = wa_head-bwart.
*          IF SY-SUBRC = 0 .
*            move lwa_mseg-menge to ls_quantity.
*            wa_head-stock_out = ls_quantity + wa_head-stock_out.
*            modify it_head from wa_head.
*          ENDIF.
*        endloop.
*        clear ls_quantity .
*      endif.
*      read table it_stockclose into lwa_stockclose
*         with key matnr = wa_head-matnr.
*                  "budat = wa_head-p_date.
*      if sy-subrc = 0.
*        wa_head-openbal = lwa_stockclose-labst.
*        modify it_head from wa_head.
*      ENDIF.
*    endif.
*  endloop.
endform.                    " f005_receipts_issues
*&      Form  COMMENT_BUILD
*       text
*  -->  p1        text
*  <--  p2        text
FORM comment_build USING p_it_st_list_top_of_page TYPE slis_t_listheader
  DATA: ls_line TYPE slis_listheader.
  REFRESH p_it_st_list_top_of_page.
  CLEAR ls_line.
  ls_line-typ  = 'H'.
  ls_line-info  = 'Details of Stock Ledger'.
  APPEND ls_line TO p_it_st_list_top_of_page.
ENDFORM.                    " COMMENT_BUILD
*&      Form  TOP_OF_PAGE-ALV
*       text
FORM top_of_page-alv.
  CALL FUNCTION 'REUSE_ALV_COMMENTARY_WRITE'
    EXPORTING
      it_list_commentary = it_st_list_top_of_page.
ENDFORM.                    "TOP_OF_PAGE-ALV
*&      Form  FIELDCAT
*      -->P_IT_ST_FIELDCAT[]  text
FORM fieldcat  USING p_it_st_fieldcat TYPE slis_t_fieldcat_alv.
  DATA: ls_fieldcat TYPE slis_fieldcat_alv.
  CLEAR ls_fieldcat.
  ls_fieldcat-fieldname  = 'P_DATE'.
  ls_fieldcat-datatype   = 'P_DATE'.
  ls_fieldcat-outputlen  = 18.
  ls_fieldcat-seltext_m  = text-002 .
*  ls_fieldcat-rollname   = 'MATNR'.
  ls_fieldcat-key         = 'X'.
  APPEND ls_fieldcat TO p_it_st_fieldcat.
  CLEAR ls_fieldcat.
  ls_fieldcat-fieldname   = 'MATNR'.
  ls_fieldcat-rollname    = 'MATNR'.
  ls_fieldcat-ddictxt     = 'L'.
  ls_fieldcat-outputlen  = 18.
  APPEND ls_fieldcat TO p_it_st_fieldcat.
  CLEAR ls_fieldcat.
  ls_fieldcat-fieldname   = 'MAKTX'.
  ls_fieldcat-rollname    = 'MAKTX'.
  ls_fieldcat-ddictxt     = 'L'.
    ls_fieldcat-outputlen  = 40.
  APPEND ls_fieldcat TO p_it_st_fieldcat.
*  CLEAR ls_fieldcat.
*  ls_fieldcat-fieldname   = 'BWART'.
*  ls_fieldcat-rollname    = 'BWART'.
*  ls_fieldcat-ddictxt     = 'L'.
*  APPEND ls_fieldcat TO p_it_st_fieldcat.
  CLEAR ls_fieldcat.
  ls_fieldcat-fieldname   = 'OPENBAL'.
  ls_fieldcat-rollname    = 'OPENBAL'.
  ls_fieldcat-ddictxt     = 'L'.
  ls_fieldcat-seltext_m  = text-003 .
  APPEND ls_fieldcat TO p_it_st_fieldcat.
  CLEAR ls_fieldcat.
  ls_fieldcat-fieldname   = 'R_PO'.
  ls_fieldcat-rollname    = 'R_PO'.
  ls_fieldcat-ddictxt     = 'L'.
  ls_fieldcat-seltext_m  = text-004 .
  APPEND ls_fieldcat TO p_it_st_fieldcat.
  CLEAR ls_fieldcat.
  ls_fieldcat-fieldname   = 'R_PRODORD'.
  ls_fieldcat-rollname    = 'R_PRODORD'.
  ls_fieldcat-ddictxt     = 'L'.
  ls_fieldcat-seltext_m  = text-005 .
  APPEND ls_fieldcat TO p_it_st_fieldcat.
  CLEAR ls_fieldcat.
  ls_fieldcat-fieldname   = 'R_BYPROD'.
  ls_fieldcat-rollname    = 'R_BYPROD'.
  ls_fieldcat-ddictxt     = 'L'.
  ls_fieldcat-seltext_m  = text-006 .
  APPEND ls_fieldcat TO p_it_st_fieldcat.
  CLEAR ls_fieldcat.
  ls_fieldcat-fieldname   = 'R_OTHERS'.
  ls_fieldcat-rollname    = 'R_OTHERS'.
  ls_fieldcat-ddictxt     = 'L'.
  ls_fieldcat-seltext_m  = text-007 .
  APPEND ls_fieldcat TO p_it_st_fieldcat.
  CLEAR ls_fieldcat.
  ls_fieldcat-fieldname   = 'R_TOTAL'.
  ls_fieldcat-rollname    = 'R_TOTAL'.
  ls_fieldcat-ddictxt     = 'L'.
  ls_fieldcat-seltext_m  = text-008 .
  APPEND ls_fieldcat TO p_it_st_fieldcat.
  CLEAR ls_fieldcat.
  ls_fieldcat-fieldname   = 'I_PROD'.
  ls_fieldcat-rollname    = 'I_PROD'.
  ls_fieldcat-ddictxt     = 'L'.
  ls_fieldcat-seltext_m  = text-009 .
  APPEND ls_fieldcat TO p_it_st_fieldcat.
  CLEAR ls_fieldcat.
  ls_fieldcat-fieldname   = 'I_CUST'.
  ls_fieldcat-rollname    = 'I_CUST'.
  ls_fieldcat-ddictxt     = 'L'.
  ls_fieldcat-seltext_m  = text-010 .
  APPEND ls_fieldcat TO p_it_st_fieldcat.
  CLEAR ls_fieldcat.
  ls_fieldcat-fieldname   = 'I_COSTCEN'.
  ls_fieldcat-rollname    = 'I_COSTCEN'.
  ls_fieldcat-ddictxt     = 'L'.
  ls_fieldcat-seltext_m  = text-011 .
  APPEND ls_fieldcat TO p_it_st_fieldcat.
  CLEAR ls_fieldcat.
  ls_fieldcat-fieldname   = 'I_SCRAPPING'.
  ls_fieldcat-rollname    = 'I_SCRAPPING'.
  ls_fieldcat-ddictxt     = 'L'.
  ls_fieldcat-seltext_m  = text-012 .
  APPEND ls_fieldcat TO p_it_st_fieldcat.
  CLEAR ls_fieldcat.
  ls_fieldcat-fieldname   = 'I_SUBCONTRACTOR'.
  ls_fieldcat-rollname    = 'I_SUBCONTRACTOR'.
  ls_fieldcat-ddictxt     = 'L'.
  ls_fieldcat-seltext_m  = text-013 .
  APPEND ls_fieldcat TO p_it_st_fieldcat.
  CLEAR ls_fieldcat.
  ls_fieldcat-fieldname   = 'I_SAMPLING'.
  ls_fieldcat-rollname    = 'I_SAMPLING'.
  ls_fieldcat-ddictxt     = 'L'.
  ls_fieldcat-seltext_m  = text-014 .
  APPEND ls_fieldcat TO p_it_st_fieldcat.
  CLEAR ls_fieldcat.
  ls_fieldcat-fieldname   = 'I_TOTAL'.
  ls_fieldcat-rollname    = 'I_TOTAL'.
  ls_fieldcat-ddictxt     = 'L'.
  ls_fieldcat-seltext_m  = text-015 .
  APPEND ls_fieldcat TO p_it_st_fieldcat.
  CLEAR ls_fieldcat.
  ls_fieldcat-fieldname   = 'PURRET'.
  ls_fieldcat-rollname    = 'PURRET'.
  ls_fieldcat-ddictxt     = 'L'.
  ls_fieldcat-seltext_m  = text-016 .
  APPEND ls_fieldcat TO p_it_st_fieldcat.
  CLEAR ls_fieldcat.
  ls_fieldcat-fieldname   = 'STOCK_OUT'.
  ls_fieldcat-rollname    = 'STOCK_OUT'.
  ls_fieldcat-ddictxt     = 'L'.
  ls_fieldcat-seltext_m  = text-017 .
  APPEND ls_fieldcat TO p_it_st_fieldcat.
  CLEAR ls_fieldcat.
  ls_fieldcat-fieldname   = 'STOCK_IN'.
  ls_fieldcat-rollname    = 'STOCK_IN'.
  ls_fieldcat-ddictxt     = 'L'.
  ls_fieldcat-seltext_m  = text-018 .
  APPEND ls_fieldcat TO p_it_st_fieldcat.
  CLEAR ls_fieldcat.
  ls_fieldcat-fieldname   = 'STOCK_TRANSIT'.
  ls_fieldcat-rollname    = 'STOCK_TRANSIT'.
  ls_fieldcat-ddictxt     = 'L'.
  ls_fieldcat-seltext_m  = text-019 .
  APPEND ls_fieldcat TO p_it_st_fieldcat.
  CLEAR ls_fieldcat.
  ls_fieldcat-fieldname   = 'M_TO_M_TRANSIT'.
  ls_fieldcat-rollname    = 'M_TO_M_TRANSIT'.
  ls_fieldcat-ddictxt     = 'L'.
  ls_fieldcat-seltext_m  = text-020 .
  APPEND ls_fieldcat TO p_it_st_fieldcat.
  CLEAR ls_fieldcat.
  ls_fieldcat-fieldname   = 'PHY_LOSS'.
  ls_fieldcat-rollname    = 'PHY_LOSS'.
  ls_fieldcat-ddictxt     = 'L'.
  ls_fieldcat-seltext_m  = text-021 .
  APPEND ls_fieldcat TO p_it_st_fieldcat.
  CLEAR ls_fieldcat.
  ls_fieldcat-fieldname   = 'PHY_GAIN'.
  ls_fieldcat-rollname    = 'PHY_GAIN'.
  ls_fieldcat-ddictxt     = 'L'.
  ls_fieldcat-seltext_m  = text-022 .
  APPEND ls_fieldcat TO p_it_st_fieldcat.
  CLEAR ls_fieldcat.
  ls_fieldcat-fieldname   = 'CLOSING_BAL'.
  ls_fieldcat-rollname    = 'CLOSING_BAL'.
  ls_fieldcat-ddictxt     = 'L'.
  ls_fieldcat-seltext_m  = text-023 .
  APPEND ls_fieldcat TO p_it_st_fieldcat.
ENDFORM.                    " FIELDCAT
*&      Form  LAYOUT_BUILD
*       text
*      -->P_ST_LAYOUT  text
FORM layout_build  USING    p_st_layout TYPE slis_layout_alv.
  p_st_layout-box_fieldname       = 'SELK'.  " Checkbox
  p_st_layout-get_selinfos        = 'X'.
  p_st_layout-f2code              =  'PICK' .  " Doppelklickfunktion
  p_st_layout-confirmation_prompt = 'X'.       "Sicherheitsabfrage
  p_st_layout-key_hotspot         = 'X'.       "Schlüssel als Hotspot
  p_st_layout-info_fieldname      = 'COL'.     "Zeilenfarbe
ENDFORM.                    " LAYOUT_BUILD
*&      Form  REUSE_ALV_LIST_DISPLAY
*       text
FORM reuse_alv_list_display .
  CALL FUNCTION 'REUSE_ALV_GRID_DISPLAY'
       EXPORTING
             i_background_id          = 'ALV_BACKGROUND'
             i_callback_program       = s_repid
*            I_CALLBACK_PF_STATUS_SET = S_STATUS
*            I_CALLBACK_USER_COMMAND     = S_USER_COMMAND
*            I_STRUCTURE_NAME         = ''
*            IS_LAYOUT                = ST_LAYOUT
             it_fieldcat              = it_st_fieldcat[]
*            IT_EXCLUDING             =
*            IT_SPECIAL_GROUPS        = ST_SP_GROUP
*            IT_SORT                  =
*            IT_FILTER                =
*            IS_SEL_HIDE              =
*            I_DEFAULT                = 'X'
*            I_SAVE                   = S_SAVE
*            IS_VARIANT               = S_VARIANT
            IT_EVENTS                = IT_ST_EVENTS[]
*            IT_EVENT_EXIT            =
*            IS_PRINT                 =
*            IS_REPREP_ID             =
*            I_SCREEN_START_COLUMN    = 0
*            I_SCREEN_START_LINE      = 0
*            I_SCREEN_END_COLUMN      = 0
*            I_SCREEN_END_LINE        = 0
*     IMPORTING
*           E_EXIT_CAUSED_BY_CALLER   =
*           ES_EXIT_CAUSED_BY_USER    =
       TABLES
            t_outtab                  =  it_head.
ENDFORM.                    " REUSE_ALV_LIST_DISPLAY
*&      Form  EVENTTAB_BUILD
*       text
*      -->P_IT_ST_EVENTS[]  text
FORM eventtab_build  USING    p_st_events  TYPE slis_t_event .
  DATA: ls_event TYPE slis_alv_event.
  CALL FUNCTION 'REUSE_ALV_EVENTS_GET'
    EXPORTING
      i_list_type = 0
    IMPORTING
      et_events   = p_st_events.
  READ TABLE p_st_events WITH KEY name = slis_ev_top_of_page
                           INTO ls_event.
  IF sy-subrc = 0.
    MOVE st_formname_top_of_page TO ls_event-form.
    APPEND ls_event TO p_st_events.
  ENDIF.
  READ TABLE p_st_events WITH KEY name = slis_ev_user_command
                           INTO ls_event.
  IF sy-subrc = 0.
    MOVE s_user_command TO ls_event-form.
    APPEND ls_event TO p_st_events.
  ENDIF.
*  READ TABLE p_st_events WITH KEY name = slis_ev_pf_status_set
*                         INTO ls_event.
*  IF sy-subrc = 0.
*    MOVE s_status TO ls_event-form.
*    APPEND ls_event TO p_st_events.
*  ENDIF.
ENDFORM.                    " EVENTTAB_BUILD
*&      Form  VARIANT_INIT
*       text
*  -->  p1        text
*  <--  p2        text
FORM variant_init .
  CLEAR s_variant.
  s_variant-report = s_repid.
  s_variant-handle = code.
ENDFORM.                    " VARIANT_INIT

Similar Messages

  • GR/IR clearing report code with gl a/c

    hi experts,
    anyone have gr/ir clearing report code with gl a/c
    Moderator message - Please ask a specific question. Don't just post vague requirements hoping that someone will take care of them for you - post locked
    Edited by: Rob Burbank on May 22, 2009 9:37 AM

    go throw below link
    Re: gr/ir clearing account?

  • Printing logo with ALV report output?

    Hi all,
    I have written a sinple program to display a report output in ALV grid format and inserted a logo in it usingh standrad FM. Though the logo is inserted successfully displaying with list ,  but  when i am clicking on print preview the logo is missing.
    Please help me on how to print the logo with the list?
    Thanks,
    Vamshi.

    Hi Krishna,
    -->Firstly go to T-Code OAER.
    -->Give Class Name as PICTURES
    -->Give Class Type as OT
    -->Give Object Key as(watever the name you wish to give)
    -->Example key 1000
    -->Click on Execute.
    Here you will get Standard Document Types.
    Select which ever you want i.e., Attachment,Screen,Template ,etc.
    Double click on Attchment it will ask you the File on the Desktop.
    Upload the image.
    Now you can see the Image in the Folder PICTURES.
    Now go to the Report.
    Function Module 'REUSE_ALV_COMMENTARY_WRITE'.
                             i_logo = '1000'.
    Hope this will Help you.
    With Regards,
    Sharmishta.

  • PO receiver report with ALV GRID

    Hello abpers,
    Can anyone gimme some guidance or sample code how to generate the PO receiver report with alv.... 
    input fields include..
    Vendor number, material number, PO number, Purchasing group/Buyer, PO creation date, PO delivery date, PO created by
    I should get the out put with the fields....
    PO, PO date, PO group/buyer, purchasing org, vendor, PO line, order quantity, Unit, Material, Description, ST LOC SHELF BIN, ST LOCBULK BIN, QTY TO BE RECV, QTY RECEVED.
    Thanks alot for your anticipation....
    SRI

    Here is a very simple ALV program which shows a basic skeleton of an ALV program,  you simply get the data from the database(usually passed on some parameters from the selection screen) and build the FC, then call the function module.
    report zrich_0003 .
    * Global ALV Data Declarations
    type-pools: slis.
    * Internal Tables
    data: begin of ialv occurs 0,
          test1(10) type c,
          test2(10) type c,
          end of ialv.
    data: fieldcat  type slis_t_fieldcat_alv.
    start-of-selection.
      perform get_data.
      perform call_alv.
    *      Form  GET_DATA
    form get_data.
      ialv-test1 = 'ABC'.
      ialv-test2 = 'DEF'.
      append ialv.
      ialv-test1 = 'GHI'.
      ialv-test2 = 'JKL'.
      append ialv.
      ialv-test1 = '123'.
      ialv-test2 = '456'.
      append ialv.
    endform.                    "GET_DATA
    *  CALL_ALV
    form call_alv.
      perform build_field_catalog.
    * Call ABAP List Viewer (ALV)
      call function 'REUSE_ALV_GRID_DISPLAY'
        exporting
          it_fieldcat  = fieldcat
        tables
          t_outtab     = ialv.
    endform.                    "CALL_ALV
    * BUILD_FIELD_CATALOG
    form build_field_catalog.
      clear fieldcat. refresh fieldcat.
      data: tmp_fc type slis_fieldcat_alv.
      clear tmp_fc.
      tmp_fc-reptext_ddic = 'Test1'.
      tmp_fc-fieldname    = 'TEST1'.
      tmp_fc-tabname      = 'IALV'.
      tmp_fc-outputlen    = '10'.
      append tmp_fc to fieldcat.
      clear tmp_fc.
      tmp_fc-reptext_ddic = 'Test2'.
      tmp_fc-fieldname    = 'TEST2'.
      tmp_fc-tabname      = 'IALV'.
      tmp_fc-outputlen    = '10'.
      append tmp_fc to fieldcat.
    endform.                    "BUILD_FIELD_CATALOG
    The use of selection screen is not use in this program, I assume that you know how to do that.
    Regards,
    Rich Heilman

  • IDOC with ALV report

    Hi All,
    i written a program for IDOC its generating idoc succesfully,
    now my requirement is to create an IDOC with ALV report.
    this is new to me, so pls kindly give some sample code to generate an IDOC with ALV report.
    regards,
    Msrinu.

    Hi ,
    this is my outpt internal table, from this i want idoc no,cust no,cust name,EAN,net price,guebg,currrency thsese fields i want to produce as ALV report. this is i written in se38 as standlone program for generating an idoc.
    BEGIN OF gt_output,
            idoc       LIKE edidc-docnum,           "M01
            kunnr(10)        TYPE c, "Customer Number 1
            addrnumber(10)   TYPE c, " Address No
            name1(40)        TYPE c, " Customer Name
            name2(40)        TYPE c, " Customer Name
            street(60)       TYPE c, " Street
            str_suppl2(40)   TYPE c, " Address
            str_suppl3(40)   TYPE c, " Address
            city1(40)        TYPE c, " City
            post_code1(10)   TYPE c, " Postal Code
            region(3)        TYPE c, " Code identifying County
            country(3)       TYPE c, " Code identifying County
            tel_number(30)   TYPE c, " Telephone
            matnr(18)        TYPE c, " Material no.
            werks(4)         TYPE c, " Werks
            netpr(11)        TYPE c, " Net price
            waerk(5)         TYPE c, " Document Currency
            vbeln(10)        TYPE c, " Sales Document No
            knumh(10)        TYPE c, " Condition record number
            kopos(2)         TYPE c, " Sequential number of the condition
            konwa(5)         TYPE c, " Rate unit (currency or percentage)
            kbetr(11)        TYPE c, " Rate
            kpein(5)         TYPE c, " Condition pricing unit
            kmein(3)         TYPE c, " Condition unit
            ean11(18)        TYPE c, " International Article Number (EAN/UPC)
            kdmat(35)        TYPE c, " Material Number Used by Customer
            kappl(2)         TYPE c, " Application
            kschl(4)         TYPE c, " Condition  type
            datbi(8)         TYPE c, " Validity end date of the condition record
            datab(8)         TYPE c, " Validity start date of the condition record
            guebg(8)         TYPE c, " Valid-from date
            gueen(8)         TYPE c, " ValiD-to date
            eikto(12)        TYPE c, " Supplier number
            cunit(5)         TYPE c, " Consumer unit
         END OF gt_output,
    regards,
    msrinu.

  • GL Account analysis report with ALV Grid control

    Hi Everyone,
    I am looking for a GL Account analysis report with ALV Grid Control.
    Can I get sample code for this report.
    Thank you
    Prasad

    Hi Rob,
    Actually, I am searching for a Report which gives GL account analysis.
    If anybody can throw more light on this ...it would be great.
    Which Tables and fields i should refer for this report.
    Thanks

  • ALV report code dumping

    Hello gurus,
    I am trying to write a simple ALV report code. I pasted the code below.
    The program is getting dumped. I am unable to find where the error is.
    Please help me out.
    Thanks in advance.
    Regards,
    Balu
    REPORT  YBP_ALV1                                .
    TABLES  : MARA.
    DATA    : BEGIN OF itab OCCURS 500,
              matnr LIKE mara-matnr,
              ersda LIKE mara-ersda,
              ernam LIKE mara-ernam,
              END OF itab.
    DATA i_repid LIKE sy-repid.
    DATA i_lines LIKE sy-tabix.
    TYPE-POOLS  : slis.
    DATA int_fcat TYPE SLIS_T_FIELDCAT_ALV.
    SELECT-OPTIONS  : s_matnr for mara-matnr matchcode object mat1.
    START-OF-SELECTION.
    select * FROM mara into CORRESPONDING FIELDS OF itab WHERE  matnr in s_matnr.
    ENDSELECT.
    end-of-SELECTION.
    i_repid = sy-repid.
    CALL FUNCTION 'REUSE_ALV_FIELDCATALOG_MERGE'
    EXPORTING
    I_PROGRAM_NAME               = i_repid
    I_INTERNAL_TABNAME           = 'ITAB'
    I_INCLNAME                   = i_repid
    CHANGING
    CT_FIELDCAT                  = int_fcat
    EXCEPTIONS
    INCONSISTENT_INTERFACE       = 1
    PROGRAM_ERROR                = 2
    OTHERS                       = 3.
    IF SY-SUBRC <> 0.
      WRITE: / 'RETURNCODE', sy-subrc, 'from function reuse_alv_fieldcatalog_merge'.
    ENDIF.
    CALL FUNCTION 'REUSE_ALV_LIST_DISPLAY'
    EXPORTING
    I_CALLBACK_PROGRAM  = i_repid
    IT_FIELDCAT                    = int_fcat
    I_SAVE                         = 'A'
    TABLES
    T_OUTTAB                       = itab
    EXCEPTIONS
    PROGRAM_ERROR                  = 1
    OTHERS                         = 2.
    IF SY-SUBRC <> 0.
      WRITE :/ 'Returncode', sy-subrc, 'from function reuse_alv_list_display'.
    ENDIF.
    Edited by: Balu on Jan 3, 2008 12:27 PM

    Rich,
    my code after the suggested changes -
    REPORT  YBP_ALV1                                .
    TABLES  : MARA.
    DATA    : BEGIN OF xtab,
              matnr LIKE mara-matnr,
              ersda LIKE mara-ersda,
              ernam LIKE mara-ernam,
              END OF xtab,
              itab LIKE STANDARD TABLE OF xtab WITH HEADER LINE.
    DATA i_repid LIKE sy-repid.
    DATA i_lines LIKE sy-tabix.
    TYPE-POOLS  : slis.
    DATA int_fcat TYPE SLIS_T_FIELDCAT_ALV.
    SELECT-OPTIONS  : s_matnr for mara-matnr matchcode object mat1.
    START-OF-SELECTION.
    select * FROM mara into CORRESPONDING FIELDS OF itab WHERE
      matnr in s_matnr.
    ENDSELECT.
    describe TABLE itab LINES i_lines.
    *if i_lines lt 1.
    write: / 'no material found'.
    exit.
    *endif.
    *clear i_lines.
    end-of-SELECTION.
    i_repid = sy-repid.
    CALL FUNCTION 'REUSE_ALV_FIELDCATALOG_MERGE'
    EXPORTING
       I_PROGRAM_NAME               = i_repid
       I_INTERNAL_TABNAME           = 'XTAB'
       I_INCLNAME                   = i_repid
      CHANGING
        CT_FIELDCAT                  = int_fcat
    EXCEPTIONS
       INCONSISTENT_INTERFACE       = 1
       PROGRAM_ERROR                = 2
       OTHERS                       = 3.
    IF SY-SUBRC <> 0.
      WRITE: / 'RETURNCODE', sy-subrc, 'from function reuse_alv_fieldcatalog_merge'.
    ENDIF.
    CALL FUNCTION 'REUSE_ALV_LIST_DISPLAY'
    EXPORTING
       I_CALLBACK_PROGRAM             = i_repid
       IT_FIELDCAT                    = int_fcat
       I_SAVE                         = 'A'
      TABLES
        T_OUTTAB                       = itab
    EXCEPTIONS
       PROGRAM_ERROR                  = 1
       OTHERS                         = 2.
    IF SY-SUBRC <> 0.
      WRITE : / 'Returncode', sy-subrc, 'from function reuse_alv_list_display'.
    ENDIF.
    The dump analysis is as below. Sorry I pasted the wrong analysis before -
    An exception occurred. This exception is dealt with in more detail below
    . The exception, which is assigned to the class 'CX_SY_READ_SRC_LINE_TOO_LONG',
    was neither
    caught nor passed along using a RAISING clause, in the procedure
    "K_KKB_FIELDCAT_MERGE" "(FUNCTION)"
    Since the caller of the procedure could not have expected this exception
    to occur, the running program was terminated.
    The reason for the exception is:
    You tried to read the program "YBP_ALV1" from the database. The READ REPORT
    statement allows you to copy a program's source code into an internal
    table. The lines of source code must not be longer than the width of the
    internal table. The internal table is 72 characters wide. The source
    code line is 80 wide.
    Regards,
    Balu

  • Stock variance report Crashes with error code REP-56048

    SR : 6990718.992
    gtcr : http://qmon.oraclecorp.com/qmon3/quickpicks.pl?t=t&q=6990718.992
    Problem Statement : When the user is trying to generate report for Stock variance report from Oracle Retail Merchandising System the report crashes with error code REP-56048.
    The steps to reproduce are specific to Oracle Retail Merchandising system application and hence I have not mentioned here.
    The REP-56048 error seems to be generic. Could you please advise me on this issue.
    Thanks & Regards,
    Sameer

    You can review the following Oracle Metalink Document;
    Comprehensive REP-56048 Troubleshooting and Overview Guide: Doc ID: Note:285281.1
    https://metalink.oracle.com/metalink/plsql/f?p=130:14:88153902823984055::::p14_database_id,p14_docid,p14_show_header,p14_show_help,p14_black_frame,p14_font:NOT,285281.1,1,1,1,helvetica
    Hope it would be useful.
    Adith

  • Report with ALV tree and ALV list?

    I need to create a report with layout as same as this one
    [http://trangiegie.com/MyFile/output.JPG]
    It looks like a report with combination of ALV tree and list. The tree works like a navigation bar. Wonder if there are any demo programs like this. Will appreciate any help.

    For Tree alone - You can check program : BCALV_TREE_02
    Program Name                   Report title
    BCALV_GRID_DND_TREE            ALV Grid: Drag and Drop with ALV Tree
    BCALV_GRID_DND_TREE_SIMPLE     ALV GRID: Drag and drop with ALV tree (simple)
    BCALV_TEST_COLUMN_TREE         Program BCALV_TEST_COLUMN_TREE
    BCALV_TEST_SIMPLE_TREE         Program BCALV_TEST_SIMPLE_TREE
    BCALV_TREE_01                  ALV Tree Control: Build Up the Hierarchy Tree
    BCALV_TREE_02                  ALV Tree Control: Event Handling
    BCALV_TREE_03                  ALV Tree Control: Use an Own Context Menu
    BCALV_TREE_04                  ALV Tree Control: Add a Button to the Toolbar
    BCALV_TREE_05                  ALV Tree Control: Add a Menu to the Toolbar
    BCALV_TREE_06                  ALV tree control: Icon column and icon for nodes/items
    BCALV_TREE_DEMO                Demo for ALV tree control
    BCALV_TREE_DND                 ALV tree control: Drag & Drop within a hierarchy tree
    BCALV_TREE_DND_MULTIPLE        ALV tree control: Drag & Drop within a hierarchy tree
    BCALV_TREE_EVENT_RECEIVER      Include BCALV_TREE_EVENT_RECEIVER
    BCALV_TREE_EVENT_RECEIVER01
    BCALV_TREE_ITEMLAYOUT          ALV Tree: Change Item Layouts at Runtime
    BCALV_TREE_MOVE_NODE_TEST      Demo for ALV tree control
    BCALV_TREE_SIMPLE_DEMO         Program BCALV_TREE_SIMPLE_DEMO
    BCALV_TREE_VERIFY              Verifier for ALV Tree and Simple ALV Tree

  • COPA Report Layout with Object List (ALV)

    Hi,
    I have question about the COPA report layout with object list (ALV). Everytime I executed the report with ALV format, the amount for quantity column always shows with 3 decimal number, menwhile for amount column always follow by 2 decimal number.
    Can anyone help me regarding this matter? I do not know how to turn off the decimal number to be 0 in this type of layout, although in the form itself I already put 0 decimal number.
    Thanks.

    Hi,
    Better to raise this issue in CO Forum. You can expect some solution.
    regards

  • How to create 2 transaction codes for same report program with diff title

    Hi All -
      I have created report program and create 2 transaction codes with different short description. I want to display the Tcodes decriptions instead of program attributes title.
    Can anyone pls tell me how to do this?
    Thanks,
    Kannan

    Hi Kannan,
    define 2 titlebars t1 and t2 for the report. In report initialization,
    IF sy-tcode = 't1'
      SET TITLE t1.
    ELSE.
      SET TITLE t2.
    ENDIF.
    Regards,
    Clemens

  • Normal report with ALV's

    Hello Experts,
    i had one new development from Scratch
    one thing is that object already developed, but the customer not intrested that output,
    he want the output to be changed.it is normal report with ALV's.
    main task of this object is to change the visibility.
    Present output is in Tree structure mode..

    Hi
    Well u can use the Fm REUSE_ALV_HIERSEQ_LIST_DISPLAY
    Or go to tx se38 and search programs with BCALVTREE
    you can find some examples.
    Look the tx DWDM.
    Regards
    Gregory

  • Printing with ALV Grid

    Hi,
    I am using ALV List and ALV grid in one of my custom reports.
    There is no issue with ALV List when I print the report after running the program.
    But when I use ALV Grid , the report runs good and when I try to print the report I get short dump "OBJECTS_NOT_CHARLIKE" in program "LKKBLF99" of the main program "SAPLKKBL".
    I am using the function module "REUSE_ALV_GRID_DISPLAY" to run the report using ALV Grid and I get the above short dump when I try to print the report.
    Can anyone help me please?
    Thanks,
    Ashok.

    Hai Ashok
    Try with the following Code
    *& Report  ZALV_GRID                                           *
    REPORT  ZALV_GRID .
    TABLES: MARA.
    TYPE-POOLS : SLIS.
    Data declaration
    DATA: BEGIN OF I_MARA OCCURS 0.
            INCLUDE STRUCTURE MARA.
    DATA: END OF I_MARA.
    DATA: V_REPID LIKE SY-REPID.
    selection-screen
    SELECTION-SCREEN BEGIN OF BLOCK B1 WITH FRAME.
      SELECT-OPTIONS : S_MATNR FOR MARA-MATNR.
      PARAMETERS: P_MTART LIKE MARA-MTART DEFAULT 'ROH'.
    SELECTION-SCREEN END OF BLOCK B1.
    initialisation
    INITIALIZATION.
    S_MATNR-LOW = '1400'.
    S_MATNR-HIGH = '1500'.
    APPEND S_MATNR.
    V_REPID = SY-REPID.
    start-of-selection
    START-OF-SELECTION.
    SELECT * FROM MARA
        INTO TABLE I_MARA
        WHERE MATNR IN S_MATNR AND
              MTART = P_MTART.
      CHECK SY-SUBRC = 0.
    end of selection
    END-OF-SELECTION.
    CALL FUNCTION 'REUSE_ALV_GRID_DISPLAY'
    EXPORTING
      I_INTERFACE_CHECK              = ' '
      I_BYPASSING_BUFFER             =
      I_BUFFER_ACTIVE                = ' '
      I_CALLBACK_PROGRAM             = ' '
      I_CALLBACK_PF_STATUS_SET       = ' '
      I_CALLBACK_USER_COMMAND        = ' '
       I_STRUCTURE_NAME               = 'MARA'
      IS_LAYOUT                      =
      IT_FIELDCAT                    =
      IT_EXCLUDING                   =
      IT_SPECIAL_GROUPS              =
      IT_SORT                        =
      IT_FILTER                      =
      IS_SEL_HIDE                    =
      I_DEFAULT                      = 'X'
      I_SAVE                         = ' '
      IS_VARIANT                     =
      IT_EVENTS                      =
      IT_EVENT_EXIT                  =
      IS_PRINT                       =
      IS_REPREP_ID                   =
      I_SCREEN_START_COLUMN          = 0
      I_SCREEN_START_LINE            = 0
      I_SCREEN_END_COLUMN            = 0
      I_SCREEN_END_LINE              = 0
    IMPORTING
      E_EXIT_CAUSED_BY_CALLER        =
      ES_EXIT_CAUSED_BY_USER         =
      TABLES
        T_OUTTAB                       = I_MARA
    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.
    Thanks & Regards
    Sreenivasulu P

  • How to implement classes with alv's

    hi
    how to implement classes with alv's

    Hi Jyotsna,
    check this example codes.
    *"Table declarations...................................................
    TABLES:
    EKKO, " Purchasing Document Header
    CDHDR, " Change document header
    SSCRFIELDS. " Fields on selection screens
    *"Selection screen elements............................................
    SELECT-OPTIONS:
    S_EBELN FOR EKKO-EBELN, " Purchasing Document Number
    S_LIFNR FOR EKKO-LIFNR, " Vendor's account number
    S_EKGRP FOR EKKO-EKGRP, " Purchasing group
    S_BEDAT FOR EKKO-BEDAT, " Purchasing Document Date
    S_UDATE FOR CDHDR-UDATE. " Creation date of the change
    " document
    *" Data declarations...................................................
    Field String to hold Purchase Document Number *
    DATA:
    BEGIN OF FS_EBELN,
    EBELN(90) TYPE C, " Purchase Document Number
    ERNAM TYPE EKKO-ERNAM, " Name of Person who Created
    " the Object
    LIFNR TYPE EKKO-LIFNR, " Vendor's account number
    EKGRP TYPE EKKO-EKGRP, " Purchasing group
    BEDAT TYPE EKKO-BEDAT, " Purchasing Document Date
    END OF FS_EBELN,
    Field String to hold Purchase Document Header *
    BEGIN OF FS_EKKO,
    EBELN TYPE EKKO-EBELN, " Purchasing Document Number
    ERNAM TYPE EKKO-ERNAM, " Name of Person who Created the
    " Object
    LIFNR TYPE EKKO-LIFNR, " Vendor's account number
    EKGRP TYPE EKKO-EKGRP, " Purchasing group
    BEDAT TYPE EKKO-BEDAT, " Purchasing Document Date
    END OF FS_EKKO,
    Field String to hold Account Number and name of the Vendor *
    BEGIN OF FS_LFA1,
    LIFNR TYPE LFA1-LIFNR, " Account Number of Vendor
    NAME1 TYPE LFA1-NAME1, " Name1
    END OF FS_LFA1,
    Field String to hold Change date and the name of the user *
    BEGIN OF FS_CDHDR,
    OBJECTCLAS TYPE CDHDR-OBJECTCLAS, " Object Class
    OBJECTID TYPE CDHDR-OBJECTID, " Object value
    CHANGENR TYPE CDHDR-CHANGENR, " Document change number
    USERNAME TYPE CDHDR-USERNAME, " User name
    UDATE TYPE CDHDR-UDATE, " Creation date of the change
    " document
    END OF FS_CDHDR,
    Field String to hold Change document items *
    BEGIN OF FS_CDPOS,
    OBJECTCLAS TYPE CDPOS-OBJECTCLAS," Object class
    OBJECTID(10) TYPE C, " Object Value
    CHANGENR TYPE CDPOS-CHANGENR, " Document change number
    TABNAME TYPE CDPOS-TABNAME, " Table Name
    FNAME TYPE CDPOS-FNAME, " Field Name
    VALUE_NEW TYPE CDPOS-VALUE_NEW, " New contents of changed field
    VALUE_OLD TYPE CDPOS-VALUE_OLD, " Old contents of changed field
    END OF FS_CDPOS,
    Field String to hold Date Element Name *
    BEGIN OF FS_DATAELE,
    TABNAME TYPE DD03L-TABNAME, " Table Name
    FIELDNAME TYPE DD03L-FIELDNAME, " Field Name
    ROLLNAME TYPE DD03L-ROLLNAME, " Data element (semantic domain)
    END OF FS_DATAELE,
    Field String to hold Short Text of the Date Element *
    BEGIN OF FS_TEXT,
    ROLLNAME TYPE DD04T-ROLLNAME, " Data element (semantic domain)
    DDTEXT TYPE DD04T-DDTEXT, " Short Text Describing R/3
    " Repository Objects
    END OF FS_TEXT,
    Field String to hold data to be displayed on the ALV grid *
    BEGIN OF FS_OUTTAB,
    EBELN TYPE EKKO-EBELN, " Purchasing Document Number
    ERNAM TYPE EKKO-ERNAM, " Name of Person who Created the
    " Object
    LIFNR TYPE EKKO-LIFNR, " Vendor's account number
    EKGRP TYPE EKKO-EKGRP, " Purchasing group
    BEDAT TYPE EKKO-BEDAT, " Purchasing Document Date
    WERKS TYPE LFA1-WERKS, " Plant
    NAME1 TYPE LFA1-NAME1, " Name1
    USERNAME TYPE CDHDR-USERNAME, " User name
    UDATE TYPE CDHDR-UDATE, " Creation date of the change
    " document
    DDTEXT TYPE DD04T-DDTEXT, " Short Text Describing R/3
    " Repository Objects
    VALUE_NEW TYPE CDPOS-VALUE_NEW, " New contents of changed field
    VALUE_OLD TYPE CDPOS-VALUE_OLD, " Old contents of changed field
    END OF FS_OUTTAB,
    Internal table to hold Purchase Document Number *
    T_EBELN LIKE STANDARD TABLE
    OF FS_EBELN,
    Internal table to hold Purchase Document Header *
    T_EKKO LIKE STANDARD TABLE
    OF FS_EKKO,
    Temp Internal table to hold Purchase Document Header *
    T_EKKO_TEMP LIKE STANDARD TABLE
    OF FS_EKKO,
    Internal table to hold Account number and Name of the Vendor *
    T_LFA1 LIKE STANDARD TABLE
    OF FS_LFA1,
    Internal Table to hold Change date and the name of the user *
    T_CDHDR LIKE STANDARD TABLE
    OF FS_CDHDR,
    Internal Table to hold Change document items *
    T_CDPOS LIKE STANDARD TABLE
    OF FS_CDPOS,
    Temp. Internal Table to hold Change document items *
    T_CDPOS_TEMP LIKE STANDARD TABLE
    OF FS_CDPOS,
    Internal Table to hold Data Element Name *
    T_DATAELE LIKE STANDARD TABLE
    OF FS_DATAELE,
    Temp. Internal Table to hold Data Element Name *
    T_DATAELE_TEMP LIKE STANDARD TABLE
    OF FS_DATAELE,
    Internal Table to hold Short Text of the Date Element *
    T_TEXT LIKE STANDARD TABLE
    OF FS_TEXT,
    Internal Table to hold data to be displayed on the ALV grid *
    T_OUTTAB LIKE STANDARD TABLE
    OF FS_OUTTAB.
    C L A S S D E F I N I T I O N *
    CLASS LCL_EVENT_HANDLER DEFINITION DEFERRED.
    *" Data declarations...................................................
    Work variables *
    DATA:
    W_EBELN TYPE EKKO-EBELN, " Purchasing Document Number
    W_LIFNR TYPE EKKO-LIFNR, " Vendor's account number
    W_EKGRP TYPE EKKO-EKGRP, " Purchasing group
    W_VALUE TYPE EKKO-EBELN, " Reflected Value
    W_SPACE VALUE ' ', " Space
    W_FLAG TYPE I, " Flag Variable
    W_VARIANT TYPE DISVARIANT, " Variant
    ALV Grid
    W_GRID TYPE REF TO CL_GUI_ALV_GRID,
    Event Handler
    W_EVENT_CLICK TYPE REF TO LCL_EVENT_HANDLER,
    Field catalog table
    T_FIELDCAT TYPE LVC_T_FCAT.
    AT SELECTION-SCREEN EVENT *
    AT SELECTION-SCREEN ON S_EBELN.
    Subroutine to validate Purchase Document Number.
    PERFORM VALIDATE_PD_NUM.
    AT SELECTION-SCREEN ON S_LIFNR.
    Subroutine to validate Vendor Number.
    PERFORM VALIDATE_VEN_NUM.
    AT SELECTION-SCREEN ON S_EKGRP.
    Subroutine to validate Purchase Group.
    PERFORM VALIDATE_PUR_GRP.
    START-OF-SELECTION EVENT *
    START-OF-SELECTION.
    Subroutine to select all Purchase orders.
    PERFORM SELECT_PO.
    CHECK W_FLAG EQ 0.
    Subroutine to select Object values.
    PERFORM SELECT_OBJ_ID.
    CHECK W_FLAG EQ 0.
    Subroutine to select Changed values.
    PERFORM SELECT_CHANGED_VALUE.
    CHECK W_FLAG EQ 0.
    Subroutine to Select Purchase Orders.
    PERFORM SELECT_PUR_DOC.
    Subroutine to select Vendor Details.
    PERFORM SELECT_VENDOR.
    Subroutine to select Text for the Changed values.
    PERFORM DESCRIPTION.
    END-OF-SELECTION EVENT *
    END-OF-SELECTION.
    IF NOT T_EKKO IS INITIAL.
    Subroutine to populate the Output Table.
    PERFORM FILL_OUTTAB.
    Subroutine to build Field Catalog.
    PERFORM PREPARE_FIELD_CATALOG CHANGING T_FIELDCAT.
    CALL SCREEN 100.
    ENDIF. " IF NOT T_EKKO...
    CLASS LCL_EVENT_HANDLER DEFINITION
    Defining Class which handles events
    CLASS LCL_EVENT_HANDLER DEFINITION .
    PUBLIC SECTION .
    METHODS:
    HANDLE_HOTSPOT_CLICK
    FOR EVENT HOTSPOT_CLICK OF CL_GUI_ALV_GRID
    IMPORTING E_ROW_ID E_COLUMN_ID.
    ENDCLASS. " LCL_EVENT_HANDLER DEFINITION
    CLASS LCL_EVENT_HANDLER IMPLEMENTATION
    Implementing the Class which can handle events
    CLASS LCL_EVENT_HANDLER IMPLEMENTATION .
    *---Handle Double Click
    METHOD HANDLE_HOTSPOT_CLICK .
    Subroutine to get the HotSpot Cell information.
    PERFORM GET_CELL_INFO.
    SET PARAMETER ID 'BES' FIELD W_VALUE.
    CALL TRANSACTION 'ME23N'.
    ENDMETHOD. " HANDLE_HOTSPOT_CLICK
    ENDCLASS. " LCL_EVENT_HANDLER
    *& Module STATUS_0100 OUTPUT
    PBO Event
    MODULE STATUS_0100 OUTPUT.
    SET PF-STATUS 'OOPS'.
    SET TITLEBAR 'TIT'.
    Subroutine to fill the Variant Structure
    PERFORM FILL_VARIANT.
    IF W_GRID IS INITIAL.
    CREATE OBJECT W_GRID
    EXPORTING
    I_SHELLSTYLE = 0
    I_LIFETIME =
    I_PARENT = CL_GUI_CONTAINER=>SCREEN0
    I_APPL_EVENTS =
    I_PARENTDBG =
    I_APPLOGPARENT =
    I_GRAPHICSPARENT =
    I_NAME =
    I_FCAT_COMPLETE = SPACE
    EXCEPTIONS
    ERROR_CNTL_CREATE = 1
    ERROR_CNTL_INIT = 2
    ERROR_CNTL_LINK = 3
    ERROR_DP_CREATE = 4
    OTHERS = 5.
    IF SY-SUBRC 0.
    MESSAGE ID SY-MSGID TYPE SY-MSGTY NUMBER SY-MSGNO
    WITH SY-MSGV1 SY-MSGV2 SY-MSGV3 SY-MSGV4.
    ENDIF. " IF SY-SUBRC 0
    CALL METHOD W_GRID->SET_TABLE_FOR_FIRST_DISPLAY
    EXPORTING
    I_BUFFER_ACTIVE =
    I_BYPASSING_BUFFER =
    I_CONSISTENCY_CHECK =
    I_STRUCTURE_NAME =
    IS_VARIANT = W_VARIANT
    I_SAVE = 'A'
    I_DEFAULT = 'X'
    IS_LAYOUT =
    IS_PRINT =
    IT_SPECIAL_GROUPS =
    IT_TOOLBAR_EXCLUDING =
    IT_HYPERLINK =
    IT_ALV_GRAPHICS =
    IT_EXCEPT_QINFO =
    IR_SALV_ADAPTER =
    CHANGING
    IT_OUTTAB = T_OUTTAB
    IT_FIELDCATALOG = T_FIELDCAT
    IT_SORT =
    IT_FILTER =
    EXCEPTIONS
    INVALID_PARAMETER_COMBINATION = 1
    PROGRAM_ERROR = 2
    TOO_MANY_LINES = 3
    OTHERS = 4
    IF SY-SUBRC 0.
    MESSAGE ID SY-MSGID TYPE SY-MSGTY NUMBER SY-MSGNO
    WITH SY-MSGV1 SY-MSGV2 SY-MSGV3 SY-MSGV4.
    ENDIF. " IF SY-SUBRC 0.
    ENDIF. " IF W_GRID IS INITIAL
    CREATE OBJECT W_EVENT_CLICK.
    SET HANDLER W_EVENT_CLICK->HANDLE_HOTSPOT_CLICK FOR W_GRID.
    ENDMODULE. " STATUS_0100 OUTPUT
    *& Module USER_COMMAND_0100 INPUT
    PAI Event
    MODULE USER_COMMAND_0100 INPUT.
    CASE SY-UCOMM.
    WHEN 'BACK'.
    LEAVE TO SCREEN 0.
    WHEN 'EXIT'.
    LEAVE PROGRAM.
    WHEN 'CANCEL'.
    LEAVE TO SCREEN 0.
    ENDCASE.
    ENDMODULE. " USER_COMMAND_0100 INPUT
    *& Form PREPARE_FIELD_CATALOG
    Subroutine to build the Field catalog
    <--P_T_FIELDCAT Field Catalog Table
    FORM PREPARE_FIELD_CATALOG CHANGING PT_FIELDCAT TYPE LVC_T_FCAT .
    DATA LS_FCAT TYPE LVC_S_FCAT.
    Purchasing group...
    LS_FCAT-FIELDNAME = 'EKGRP'.
    LS_FCAT-REF_TABLE = 'EKKO'.
    LS_FCAT-INTTYPE = 'C'.
    LS_FCAT-OUTPUTLEN = '10'.
    APPEND LS_FCAT TO PT_FIELDCAT.
    CLEAR LS_FCAT.
    Purchasing Document Number...
    LS_FCAT-FIELDNAME = 'EBELN'.
    LS_FCAT-REF_TABLE = 'EKKO' .
    LS_FCAT-EMPHASIZE = 'C411'.
    LS_FCAT-INTTYPE = 'C'.
    LS_FCAT-OUTPUTLEN = '10'.
    LS_FCAT-HOTSPOT = 'X'.
    APPEND LS_FCAT TO PT_FIELDCAT .
    CLEAR LS_FCAT .
    Name of Person who Created the Object...
    LS_FCAT-FIELDNAME = 'ERNAM'.
    LS_FCAT-REF_TABLE = 'EKKO'.
    LS_FCAT-OUTPUTLEN = '15' .
    APPEND LS_FCAT TO PT_FIELDCAT.
    CLEAR LS_FCAT.
    Purchasing Document Date...
    LS_FCAT-FIELDNAME = 'BEDAT'.
    LS_FCAT-REF_TABLE = 'EKKO'.
    LS_FCAT-INTTYPE = 'C'.
    LS_FCAT-OUTPUTLEN = '10'.
    APPEND LS_FCAT TO PT_FIELDCAT.
    CLEAR LS_FCAT.
    Vendor's account number...
    LS_FCAT-FIELDNAME = 'LIFNR'.
    LS_FCAT-REF_TABLE = 'EKKO'.
    LS_FCAT-INTTYPE = 'C'.
    LS_FCAT-OUTPUTLEN = '10'.
    APPEND LS_FCAT TO PT_FIELDCAT.
    CLEAR LS_FCAT.
    Account Number of Vendor or Creditor...
    LS_FCAT-FIELDNAME = 'NAME1'.
    LS_FCAT-REF_TABLE = 'LFA1'.
    LS_FCAT-INTTYPE = 'C'.
    LS_FCAT-OUTPUTLEN = '10'.
    LS_FCAT-COLTEXT = 'Vendor Name'(001).
    LS_FCAT-SELTEXT = 'Vendor Name'(001).
    APPEND LS_FCAT TO PT_FIELDCAT.
    CLEAR LS_FCAT.
    Creation date of the change document...
    LS_FCAT-FIELDNAME = 'UDATE'.
    LS_FCAT-REF_TABLE = 'CDHDR'.
    LS_FCAT-INTTYPE = 'C'.
    LS_FCAT-OUTPUTLEN = '10'.
    LS_FCAT-COLTEXT = 'Change Date'(002).
    LS_FCAT-SELTEXT = 'Change Date'(002).
    APPEND LS_FCAT TO PT_FIELDCAT.
    CLEAR LS_FCAT.
    User name of the person responsible in change document...
    LS_FCAT-FIELDNAME = 'USERNAME'.
    LS_FCAT-REF_TABLE = 'CDHDR'.
    LS_FCAT-INTTYPE = 'C'.
    LS_FCAT-OUTPUTLEN = '10'.
    LS_FCAT-COLTEXT = 'Modified by'(003).
    LS_FCAT-SELTEXT = 'Modified by'(003).
    APPEND LS_FCAT TO PT_FIELDCAT.
    CLEAR LS_FCAT.
    Short Text Describing R/3 Repository Objects...
    LS_FCAT-FIELDNAME = 'DDTEXT'.
    LS_FCAT-REF_TABLE = 'DD04T'.
    LS_FCAT-INTTYPE = 'C'.
    LS_FCAT-OUTPUTLEN = '15'.
    APPEND LS_FCAT TO PT_FIELDCAT.
    CLEAR LS_FCAT.
    Old contents of changed field...
    LS_FCAT-FIELDNAME = 'VALUE_OLD'.
    LS_FCAT-REF_TABLE = 'CDPOS'.
    LS_FCAT-INTTYPE = 'C'.
    LS_FCAT-OUTPUTLEN = '12'.
    APPEND LS_FCAT TO PT_FIELDCAT.
    CLEAR LS_FCAT.
    New contents of changed field...
    LS_FCAT-FIELDNAME = 'VALUE_NEW'.
    LS_FCAT-REF_TABLE = 'CDPOS'.
    LS_FCAT-INTTYPE = 'C'.
    LS_FCAT-OUTPUTLEN = '12'.
    APPEND LS_FCAT TO PT_FIELDCAT.
    CLEAR LS_FCAT.
    ENDFORM. " PREPARE_FIELD_CATALOG
    *& Form SELECT_PO
    Subroutine to select all the Purchase Orders
    There are no interface parameters to be passed to this subroutine.
    FORM SELECT_PO .
    SELECT EBELN " Purchasing Document Number
    ERNAM " Name of Person who Created
    " the Object
    LIFNR " Vendor's account number
    EKGRP " Purchasing group
    BEDAT " Purchasing Document Date
    FROM EKKO
    PACKAGE SIZE 10000
    APPENDING TABLE T_EBELN
    WHERE EBELN IN S_EBELN
    AND BEDAT IN S_BEDAT.
    ENDSELECT.
    IF SY-SUBRC NE 0.
    W_FLAG = 1.
    MESSAGE S401(M8).
    ENDIF. " IF SY-SUBRC NE 0
    ENDFORM. " SELECT_PO
    *& Form SELECT_OBJ_ID
    Subroutine to select Object ID
    There are no interface parameters to be passed to this subroutine.
    FORM SELECT_OBJ_ID .
    IF NOT T_EBELN IS INITIAL.
    SELECT OBJECTCLAS " Object Class
    OBJECTID " Object value
    CHANGENR " Document change number
    USERNAME " User name
    UDATE " Creation date
    FROM CDHDR
    INTO TABLE T_CDHDR
    FOR ALL ENTRIES IN T_EBELN
    WHERE OBJECTID EQ T_EBELN-EBELN
    AND UDATE IN S_UDATE
    AND TCODE IN ('ME21N','ME22N','ME23N').
    ENDSELECT.
    IF SY-SUBRC NE 0.
    W_FLAG = 1.
    MESSAGE S833(M8) WITH 'Header Not Found'(031).
    ENDIF. " IF SY-SUBRC NE 0.
    ENDIF. " IF NOT T_EBELN IS INITIAL
    ENDFORM. " SELECT_OBJ_ID
    *& Form SELECT_CHANGED_VALUE
    Subroutine to select Changed Values
    There are no interface parameters to be passed to this subroutine.
    FORM SELECT_CHANGED_VALUE .
    IF NOT T_CDHDR IS INITIAL.
    SELECT OBJECTCLAS " Object class
    OBJECTID " Object value
    CHANGENR " Document change number
    TABNAME " Table Name
    FNAME " Field Name
    VALUE_NEW " New contents of changed field
    VALUE_OLD " Old contents of changed field
    FROM CDPOS
    PACKAGE SIZE 10000
    APPENDING TABLE T_CDPOS
    FOR ALL ENTRIES IN T_CDHDR
    WHERE OBJECTCLAS EQ T_CDHDR-OBJECTCLAS
    AND OBJECTID EQ T_CDHDR-OBJECTID
    AND CHANGENR EQ T_CDHDR-CHANGENR.
    ENDSELECT.
    IF SY-SUBRC NE 0.
    W_FLAG = 1.
    MESSAGE S833(M8) WITH 'Item Not Found'(032).
    ENDIF. " IF SY-SUBRC NE 0.
    ENDIF. " IF NOT T_CDHDR IS INITIAL
    T_CDPOS_TEMP] = T_CDPOS[.
    ENDFORM. " SELECT_CHANGED_VALUE
    *& Form SELECT_PUR_DOC
    Subroutine to select Purchase Order Details
    There are no interface parameters to be passed to this subroutine.
    FORM SELECT_PUR_DOC .
    IF NOT T_CDPOS IS INITIAL.
    SORT T_EBELN BY EBELN.
    LOOP AT T_CDPOS INTO FS_CDPOS.
    READ TABLE T_EBELN INTO FS_EBELN WITH KEY EBELN =
    FS_CDPOS-OBJECTID BINARY SEARCH.
    IF SY-SUBRC NE 0.
    DELETE TABLE T_EBELN FROM FS_EBELN.
    ENDIF. " IF SY-SUBRC NE 0.
    ENDLOOP. " LOOP AT T_CDPOS...
    LOOP AT T_EBELN INTO FS_EBELN.
    MOVE FS_EBELN-EBELN TO FS_EKKO-EBELN.
    MOVE FS_EBELN-ERNAM TO FS_EKKO-ERNAM.
    MOVE FS_EBELN-LIFNR TO FS_EKKO-LIFNR.
    MOVE FS_EBELN-EKGRP TO FS_EKKO-EKGRP.
    MOVE FS_EBELN-BEDAT TO FS_EKKO-BEDAT.
    APPEND FS_EKKO TO T_EKKO.
    ENDLOOP. " LOOP AT T_EBELN...
    T_EKKO_TEMP] = T_EKKO[.
    ENDIF. " IF NOT T_CDPOS IS INITIAL
    ENDFORM. " SELECT_PUR_DOC
    *& Form SELECT_VENDOR
    Subroutine to select Vendor details
    There are no interface parameters to be passed to this subroutine.
    FORM SELECT_VENDOR .
    IF NOT T_EKKO IS INITIAL.
    SORT T_EKKO_TEMP BY LIFNR.
    DELETE ADJACENT DUPLICATES FROM T_EKKO_TEMP COMPARING LIFNR.
    SELECT LIFNR " Account Number of Vendor or
    " Creditor
    NAME1 " Name 1
    FROM LFA1
    INTO TABLE T_LFA1
    FOR ALL ENTRIES IN T_EKKO_TEMP
    WHERE LIFNR EQ T_EKKO_TEMP-LIFNR.
    IF SY-SUBRC NE 0.
    MESSAGE S002(M8) WITH 'Master Details'(033).
    ENDIF. " IF SY-SUBRC NE 0.
    ENDIF. " IF NOT T_EKKO IS INITIAL
    ENDFORM. " SELECT_VENDOR
    *& Form DESCRIPTION
    Subroutine to get the description
    There are no interface parameters to be passed to this subroutine.
    FORM DESCRIPTION .
    IF NOT T_CDPOS IS INITIAL.
    SORT T_CDPOS_TEMP BY TABNAME FNAME.
    DELETE ADJACENT DUPLICATES FROM T_CDPOS_TEMP COMPARING TABNAME FNAME
    SELECT TABNAME " Table Name
    FIELDNAME " Field Name
    ROLLNAME " Data element
    FROM DD03L
    INTO TABLE T_DATAELE
    FOR ALL ENTRIES IN T_CDPOS_TEMP
    WHERE TABNAME EQ T_CDPOS_TEMP-TABNAME
    AND FIELDNAME EQ T_CDPOS_TEMP-FNAME.
    IF NOT T_DATAELE IS INITIAL.
    T_DATAELE_TEMP] = T_DATAELE[.
    SORT T_DATAELE_TEMP BY ROLLNAME.
    DELETE ADJACENT DUPLICATES FROM T_DATAELE_TEMP COMPARING ROLLNAME.
    SELECT ROLLNAME " Data element
    DDTEXT " Short Text Describing R/3
    " Repository Objects
    FROM DD04T
    INTO TABLE T_TEXT
    FOR ALL ENTRIES IN T_DATAELE_TEMP
    WHERE ROLLNAME EQ T_DATAELE_TEMP-ROLLNAME
    AND DDLANGUAGE EQ SY-LANGU.
    IF SY-SUBRC NE 0.
    EXIT.
    ENDIF. " IF SY-SUBRC NE 0.
    ENDIF. " IF NOT T_DATAELE IS INITIAL.
    ENDIF. " IF NOT T_CDPOS IS INITIAL.
    ENDFORM. " DESCRIPTION
    *& Form FILL_OUTTAB
    Subroutine to populate the Outtab
    There are no interface parameters to be passed to this subroutine.
    FORM FILL_OUTTAB .
    SORT T_CDHDR BY OBJECTCLAS OBJECTID CHANGENR.
    SORT T_EKKO BY EBELN.
    SORT T_LFA1 BY LIFNR.
    SORT T_DATAELE BY TABNAME FIELDNAME.
    SORT T_TEXT BY ROLLNAME.
    LOOP AT T_CDPOS INTO FS_CDPOS.
    READ TABLE T_CDHDR INTO FS_CDHDR WITH KEY
    OBJECTCLAS = FS_CDPOS-OBJECTCLAS
    OBJECTID = FS_CDPOS-OBJECTID
    CHANGENR = FS_CDPOS-CHANGENR
    BINARY SEARCH.
    IF SY-SUBRC EQ 0.
    MOVE FS_CDHDR-USERNAME TO FS_OUTTAB-USERNAME.
    MOVE FS_CDHDR-UDATE TO FS_OUTTAB-UDATE.
    READ TABLE T_EKKO INTO FS_EKKO WITH KEY
    EBELN = FS_CDHDR-OBJECTID
    BINARY SEARCH.
    IF SY-SUBRC EQ 0.
    MOVE FS_EKKO-EBELN TO FS_OUTTAB-EBELN.
    MOVE FS_EKKO-ERNAM TO FS_OUTTAB-ERNAM.
    MOVE FS_EKKO-LIFNR TO FS_OUTTAB-LIFNR.
    MOVE FS_EKKO-EKGRP TO FS_OUTTAB-EKGRP.
    MOVE FS_EKKO-BEDAT TO FS_OUTTAB-BEDAT.
    READ TABLE T_LFA1 INTO FS_LFA1 WITH KEY
    LIFNR = FS_EKKO-LIFNR
    BINARY SEARCH.
    IF SY-SUBRC EQ 0.
    MOVE FS_LFA1-NAME1 TO FS_OUTTAB-NAME1.
    ENDIF. " IF SY-SUBRC EQ 0.
    ENDIF. " IF SY-SUBRC EQ 0.
    ENDIF. " IF SY-SUBRC EQ 0.
    MOVE FS_CDPOS-VALUE_NEW TO FS_OUTTAB-VALUE_NEW.
    MOVE FS_CDPOS-VALUE_OLD TO FS_OUTTAB-VALUE_OLD.
    READ TABLE T_DATAELE INTO FS_DATAELE WITH KEY
    TABNAME = FS_CDPOS-TABNAME
    FIELDNAME = FS_CDPOS-FNAME
    BINARY SEARCH.
    IF SY-SUBRC EQ 0.
    READ TABLE T_TEXT INTO FS_TEXT WITH KEY
    ROLLNAME = FS_DATAELE-ROLLNAME
    BINARY SEARCH.
    IF SY-SUBRC EQ 0.
    MOVE FS_TEXT-DDTEXT TO FS_OUTTAB-DDTEXT.
    ENDIF. " IF SY-SUBRC EQ 0.
    ENDIF. " IF SY-SUBRC EQ 0.
    APPEND FS_OUTTAB TO T_OUTTAB.
    CLEAR FS_OUTTAB.
    ENDLOOP.
    ENDFORM. " FILL_OUTTAB
    *& Form GET_CELL_INFO
    Subroutine to get the Cell Information
    --> W_VALUE Holds the value of Hotspot clicked
    FORM GET_CELL_INFO .
    CALL METHOD W_GRID->GET_CURRENT_CELL
    IMPORTING
    E_ROW =
    E_VALUE = W_VALUE
    E_COL =
    ES_ROW_ID =
    ES_COL_ID =
    ES_ROW_NO =
    ENDFORM. " GET_CELL_INFO
    *& Form VALIDATE_PD_NUM
    Subroutine to validate Purchase Document Number
    There are no interface parameters to be passed to this subroutine.
    FORM VALIDATE_PD_NUM .
    IF NOT S_EBELN[] IS INITIAL.
    SELECT EBELN " Purchase Document Number
    FROM EKKO
    INTO W_EBELN
    UP TO 1 ROWS
    WHERE EBELN IN S_EBELN.
    ENDSELECT.
    IF SY-SUBRC NE 0.
    CLEAR SSCRFIELDS-UCOMM.
    MESSAGE E717(M8).
    ENDIF. " IF SY-SUBRC NE 0
    ENDIF. " IF NOT S_EBELN[]...
    ENDFORM. " VALIDATE_PD_NUM
    *& Form VALIDATE_VEN_NUM
    Subroutine to validate Vendor Number
    There are no interface parameters to be passed to this subroutine.
    FORM VALIDATE_VEN_NUM .
    IF NOT S_LIFNR[] IS INITIAL.
    SELECT LIFNR " Vendor Number
    FROM LFA1
    INTO W_LIFNR
    UP TO 1 ROWS
    WHERE LIFNR IN S_LIFNR.
    ENDSELECT.
    IF SY-SUBRC NE 0.
    CLEAR SSCRFIELDS-UCOMM.
    MESSAGE E002(M8) WITH W_SPACE.
    ENDIF. " IF SY-SUBRC NE 0
    ENDIF. " IF NOT S_LIFNR[]...
    ENDFORM. " VALIDATE_VEN_NUM
    *& Form VALIDATE_PUR_GRP
    Subroutine to validate the Purchase Group
    There are no interface parameters to be passed to this subroutine.
    FORM VALIDATE_PUR_GRP .
    IF NOT S_EKGRP[] IS INITIAL.
    SELECT EKGRP " Purchase Group
    FROM T024
    INTO W_EKGRP
    UP TO 1 ROWS
    WHERE EKGRP IN S_EKGRP.
    ENDSELECT.
    IF SY-SUBRC NE 0.
    CLEAR SSCRFIELDS-UCOMM.
    MESSAGE E622(M8) WITH W_SPACE.
    ENDIF. " IF SY-SUBRC NE 0
    ENDIF. " IF NOT S_EKFRP[]...
    ENDFORM. " VALIDATE_PUR_GRP
    *& Form FILL_VARIANT
    Subroutine to fill the Variant Structure
    There are no interface parameters to be passed to this subroutine
    FORM FILL_VARIANT .
    Filling the Variant structure
    W_VARIANT-REPORT = SY-REPID.
    W_VARIANT-USERNAME = SY-UNAME.
    ENDFORM. " FILL_VARIANT
    REPORT YMS_HIERSEQLISTDISPLAY .
    Program with FM REUSE_ALV_HIERSEQ_LIST_DISPLAY *
    Author : Michel PIOUD *
    Email : mpioudyahoo.fr HomePage : http://www.geocities.com/mpioud *
    TYPE-POOLS: slis. " ALV Global types
    CONSTANTS :
    c_x VALUE 'X',
    c_gt_vbap TYPE SLIS_TABNAME VALUE 'GT_VBAP',
    c_gt_vbak TYPE SLIS_TABNAME VALUE 'GT_VBAK'.
    SELECTION-SCREEN :
    SKIP, BEGIN OF LINE,COMMENT 5(27) v_1 FOR FIELD p_max. "#EC NEEDED
    PARAMETERS p_max(02) TYPE n DEFAULT '10' OBLIGATORY.
    SELECTION-SCREEN END OF LINE.
    SELECTION-SCREEN :
    SKIP, BEGIN OF LINE,COMMENT 5(27) v_2 FOR FIELD p_expand. "#EC NEEDED
    PARAMETERS p_expand AS CHECKBOX DEFAULT c_x.
    SELECTION-SCREEN END OF LINE.
    TYPES :
    1st Table
    BEGIN OF ty_vbak,
    vbeln TYPE vbak-vbeln, " Sales document
    kunnr TYPE vbak-kunnr, " Sold-to party
    netwr TYPE vbak-netwr, " Net Value of the Sales Order
    erdat TYPE vbak-erdat, " Creation date
    waerk TYPE vbak-waerk, " SD document currency
    expand TYPE xfeld,
    END OF ty_vbak,
    2nd Table
    BEGIN OF ty_vbap,
    vbeln TYPE vbap-vbeln, " Sales document
    posnr TYPE vbap-posnr, " Sales document
    matnr TYPE vbap-matnr, " Material number
    netwr TYPE vbap-netwr, " Net Value of the Sales Order
    waerk TYPE vbap-waerk, " SD document currency
    END OF ty_vbap.
    DATA :
    1st Table
    gt_vbak TYPE TABLE OF ty_vbak,
    2nd Table
    gt_vbap TYPE TABLE OF ty_vbap.
    INITIALIZATION.
    v_1 = 'Maximum of records to read'.
    v_2 = 'With ''EXPAND'' field'.
    START-OF-SELECTION.
    Read Sales Document: Header Data
    SELECT vbeln kunnr netwr waerk erdat
    FROM vbak
    UP TO p_max ROWS
    INTO CORRESPONDING FIELDS OF TABLE gt_vbak.
    IF NOT gt_vbak[] IS INITIAL.
    Read Sales Document: Item Data
    SELECT vbeln posnr matnr netwr waerk
    FROM vbap
    INTO CORRESPONDING FIELDS OF TABLE gt_vbap
    FOR ALL ENTRIES IN gt_vbak
    WHERE vbeln = gt_vbak-vbeln.
    ENDIF.
    PERFORM f_display.
    Form F_DISPLAY
    FORM f_display.
    Macro definition
    DEFINE m_fieldcat.
    ls_fieldcat-tabname = &1.
    ls_fieldcat-fieldname = &2.
    ls_fieldcat-ref_tabname = &3.
    ls_fieldcat-cfieldname = &4. " Field with currency unit
    append ls_fieldcat to lt_fieldcat.
    END-OF-DEFINITION.
    DEFINE m_sort.
    ls_sort-tabname = &1.
    ls_sort-fieldname = &2.
    ls_sort-up = c_x.
    append ls_sort to lt_sort.
    END-OF-DEFINITION.
    DATA:
    ls_layout TYPE slis_layout_alv,
    ls_keyinfo TYPE slis_keyinfo_alv,
    ls_sort TYPE slis_sortinfo_alv,
    lt_sort TYPE slis_t_sortinfo_alv," Sort table
    ls_fieldcat TYPE slis_fieldcat_alv,
    lt_fieldcat TYPE slis_t_fieldcat_alv." Field catalog
    ls_layout-group_change_edit = c_x.
    ls_layout-colwidth_optimize = c_x.
    ls_layout-zebra = c_x.
    ls_layout-detail_popup = c_x.
    ls_layout-get_selinfos = c_x.
    IF p_expand = c_x.
    ls_layout-expand_fieldname = 'EXPAND'.
    ENDIF.
    Build field catalog and sort table
    m_fieldcat c_gt_vbak 'VBELN' 'VBAK' ''.
    m_fieldcat c_gt_vbak 'KUNNR' 'VBAK' ''.
    m_fieldcat c_gt_vbak 'NETWR' 'VBAK' 'WAERK'.
    m_fieldcat c_gt_vbak 'WAERK' 'VBAK' ''.
    m_fieldcat c_gt_vbak 'ERDAT' 'VBAK' ''.
    m_fieldcat c_gt_vbap 'POSNR' 'VBAP' ''.
    m_fieldcat c_gt_vbap 'MATNR' 'VBAP' ''.
    m_fieldcat c_gt_vbap 'NETWR' 'VBAP' 'WAERK'.
    m_fieldcat c_gt_vbap 'WAERK' 'VBAP' ''.
    m_sort c_gt_vbak 'KUNNR'.
    m_sort c_gt_vbap 'NETWR'.
    ls_keyinfo-header01 = 'VBELN'.
    ls_keyinfo-item01 = 'VBELN'.
    ls_keyinfo-item02 = 'POSNR'.
    Dipslay Hierarchical list
    CALL FUNCTION 'REUSE_ALV_HIERSEQ_LIST_DISPLAY'
    EXPORTING
    i_callback_program = sy-cprog
    i_callback_user_command = 'USER_COMMAND'
    is_layout = ls_layout
    it_fieldcat = lt_fieldcat
    it_sort = lt_sort
    i_tabname_header = c_gt_vbak
    i_tabname_item = c_gt_vbap
    is_keyinfo = ls_keyinfo
    TABLES
    t_outtab_header = gt_vbak
    t_outtab_item = gt_vbap
    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. " F_LIST_DISPLAY
    Form USER_COMMAND *
    FORM user_command USING i_ucomm TYPE sy-ucomm
    is_selfield TYPE slis_selfield. "#EC CALLED
    DATA ls_vbak TYPE ty_vbak.
    CASE i_ucomm.
    WHEN '&IC1'. " Pick
    CASE is_selfield-tabname.
    WHEN c_gt_vbap.
    WHEN c_gt_vbak.
    READ TABLE gt_vbak INDEX is_selfield-tabindex INTO ls_vbak.
    IF sy-subrc EQ 0.
    Sales order number
    SET PARAMETER ID 'AUN' FIELD ls_vbak-vbeln.
    Display Sales Order
    CALL TRANSACTION 'VA03' AND SKIP FIRST SCREEN.
    ENDIF.
    ENDCASE.
    ENDCASE.
    ENDFORM. " USER_COMMAND
    Kindly Reward Points If You Found The Reply Helpful,
    Cheers,
    Chaitanya.

  • Running report and get the report result with coding

    Hi all,
    In our R/3 system, there is a custom sales report.
    My question is: is there possibility to get data by running this report and grab it the result with code and store it in internal table?
    Sorry if my question too basic because I am not abaper
    I am just wondering to find new solution for my project.
    Regards,
    Steph

    My requirement is: I want to get the result from this report
    (rather than try to get the data from SAP original table, because this report is very complicated with a lot of selection data) and use it this result into my new program.
    The mechanism that I want is pull the result from the current report, not to add some code in current report to push into new program, to avoid changed the report.
    Btw, the output of this report not only the excel file, we can also run this report on foreground mode and see the result.
    The report is not ALV report.
    Regards,
    Steph

Maybe you are looking for

  • ITunes disappears when i turn off computer-help please

    I have always used itunes just fine, but recently I mapped 2 itunes on 2 different computers to my itune library on my nas and they work fine but whenever I turn a computer off and then back on i try to open itunes but it says the folder containing i

  • Need to know the fax number for bt customer servic...

    Ive been trying to apply for a phone & broadband package for over a week now and been called twice from bt asking me to send them some proof of ID and proof of tenancy for my current address so they can go ahead with my order.. The first person who c

  • How to take Backup of Emails and Logs?

    i)How should i take the backup of emails sent and received? ii) Where should i check for email sent and received along with sender/recipient and body of the message, i have checked log in um_system\smpt_in\<process_id>.log, but information is not in

  • Audio Levels on Playback

    Whenever I create a slideshow in iDVD or iPhoto, and then burn to a DVD in iDVD the volume levels are incredibly loud on playback on my television or stand alone DVD player. I can see the sliders to adjust the volume for playback on my computer when

  • .Jsp file Registration

    Hi All, I Have developed on .jsp screen using jdeveloper and adf , now i need to register this file in oracle apps , can you please help the process to register it , i mean where this file i need to place do i need to place any support files also apa