Display line of total SUM at end of ALV.

How i can display it? In some ALV i've seen this line yellow colored.
Thanks for aswers.

hi,
in the fieldcat.
give <b>wa_fieldcat-do_sum = 'X'.</b>
**TABLES DECLN
TABLES: VBRK,VBRP,T001.
TYPE-POOLS: SLIS.
TYPE-POOLS: ICON.
***DATA DECLN.
DATA: V_VBELN LIKE VBRK-VBELN,
      V_MATNR LIKE VBRP-MATNR.
CONSTANTS: C_USER_COMMAND TYPE SLIS_FORMNAME VALUE 'F_USER_COMMAND',
           C_PF_STATUS TYPE SLIS_FORMNAME VALUE 'F_SET_PF_STATUS'.
**ALV RELATED TABLES.
*--Field Catalog
DATA:   IT_FIELDCAT TYPE STANDARD TABLE OF
                        SLIS_FIELDCAT_ALV  WITH HEADER LINE,
        IT_FIELDCAT1 TYPE STANDARD TABLE OF
                        SLIS_FIELDCAT_ALV WITH HEADER LINE ,
        WA_FIELDCAT TYPE SLIS_FIELDCAT_ALV,
*--Layout
       WA_LAYOUT TYPE SLIS_LAYOUT_ALV,
*--Sort
       IT_SORT TYPE SLIS_T_SORTINFO_ALV,
       WA_SORT TYPE SLIS_SORTINFO_ALV  ,
**-Structure for excluding function codes
       WA_EXTAB TYPE SLIS_EXTAB,
**-To hold function codes to be excluded in ALV toolbar
       IT_EXTAB TYPE SLIS_T_EXTAB.
***INTERNAL TABLE DECLN.
DATA: BEGIN OF IT_VBRK OCCURS 0,
      VBELN LIKE VBRK-VBELN,
      WAERK LIKE VBRK-WAERK,
      VKORG LIKE VBRK-VKORG,
      FKDAT LIKE VBRK-FKDAT,
      BUKRS LIKE VBRK-BUKRS,
      NETWR LIKE VBRK-NETWR,
      END OF IT_VBRK.
DATA: BEGIN OF ITAB OCCURS 0,
      VBELN LIKE VBRP-VBELN,
      POSNR LIKE VBRP-POSNR,
      FKIMG LIKE VBRP-FKIMG,
      VRKME LIKE VBRP-VRKME,
      NETWR LIKE VBRP-NETWR,
      MATNR LIKE VBRP-MATNR,
      ARKTX LIKE VBRP-ARKTX,
      END OF ITAB.
DATA: IT_VBRP LIKE ITAB OCCURS 0 WITH HEADER LINE.
***selection screen.
SELECTION-SCREEN: BEGIN OF BLOCK B1 WITH FRAME TITLE TEXT-001.
SELECT-OPTIONS: S_VBELN FOR VBRK-VBELN,
                S_FKDAT FOR VBRK-FKDAT OBLIGATORY,
                S_MATNR FOR VBRP-MATNR.
SELECTION-SCREEN: END OF BLOCK B1.
**INITIALIZATION.
INITIALIZATION.
  S_FKDAT-LOW = SY-DATUM - 200.
  S_FKDAT-HIGH = SY-DATUM.
  APPEND S_FKDAT.
***AT SELECTION-SCREEN.
AT SELECTION-SCREEN.
  IF NOT S_VBELN IS INITIAL.
    SELECT SINGLE VBELN FROM VBRK
           INTO V_VBELN
           WHERE VBELN IN S_VBELN.
    IF SY-SUBRC <> 0.
      MESSAGE E001(ZZ2).
    ENDIF.
  ENDIF.
  IF NOT S_MATNR IS INITIAL.
    SELECT SINGLE MATNR FROM MARA
           INTO V_MATNR
           WHERE MATNR IN S_MATNR.
    IF SY-SUBRC <> 0.
      MESSAGE E001(ZZ2).
    ENDIF.
  ENDIF.
***START-OF-SELECTION.
START-OF-SELECTION.
  PERFORM GET_DATA_VBRK.
  PERFORM GET_DATA_VBRP.
***END-OF-SELECTION.
END-OF-SELECTION.
*--Sort the Output Fields
PERFORM SORT_FIELDS.
*--Build Field catalog for the Output fields
  PERFORM GET_FIELD_CATALOG.
***MODIFY LAYOUT.
PERFORM MODIFY_LAYOUT.
*--Display ALV output
  PERFORM LIST_DISP  TABLES IT_VBRK
                           USING  C_USER_COMMAND.
*&      Form  GET_DATA_VBRK
      text
-->  p1        text
<--  p2        text
FORM GET_DATA_VBRK.
  SELECT VBELN
         WAERK
         VKORG
         FKDAT
         BUKRS
         NETWR
         INTO TABLE IT_VBRK
         FROM VBRK
         WHERE VBELN IN S_VBELN
         AND FKDAT IN S_FKDAT.
ENDFORM.                    " GET_DATA
*&      Form  GET_DATA_VBRP
      text
-->  p1        text
<--  p2        text
FORM GET_DATA_VBRP .
SELECT VBELN
        POSNR
        FKIMG
        VRKME
        NETWR
        MATNR
        ARKTX
        FROM VBRP
        INTO TABLE IT_VBRP
        FOR ALL ENTRIES IN IT_VBRK
        WHERE VBELN = IT_VBRK-VBELN.
  SELECT VBELN
         POSNR
         FKIMG
         VRKME
         NETWR
         MATNR
         ARKTX
         FROM VBRP
         INTO TABLE ITAB
         FOR ALL ENTRIES IN IT_VBRK
         WHERE VBELN = IT_VBRK-VBELN.
ENDFORM.                    " GET_DATA_VBRP
*&      Form  GET_FIELD_CATALOG
      text
-->  p1        text
<--  p2        text
FORM GET_FIELD_CATALOG .
  CALL FUNCTION 'REUSE_ALV_FIELDCATALOG_MERGE'
    EXPORTING
      I_PROGRAM_NAME         = SY-REPID
      I_INTERNAL_TABNAME     = 'IT_VBRK'
      I_INCLNAME             = SY-REPID
    CHANGING
      CT_FIELDCAT            = IT_FIELDCAT[]
    EXCEPTIONS
      INCONSISTENT_INTERFACE = 1
      PROGRAM_ERROR          = 2
      OTHERS                 = 3.
  IF SY-SUBRC <> 0.
    MESSAGE ID SY-MSGID TYPE SY-MSGTY NUMBER SY-MSGNO
            WITH SY-MSGV1 SY-MSGV2 SY-MSGV3 SY-MSGV4.
  ENDIF.
ENDFORM.                    " GET_FIELD_CATALOG
*&      Form  SORT_FIELDS
      text
-->  p1        text
<--  p2        text
FORM SORT_FIELDS .
  CLEAR WA_SORT.
  WA_SORT-SPOS = '01'.
  WA_SORT-FIELDNAME = 'VBELN' .
  WA_SORT-TABNAME   = 'IT_VBRK'.
  WA_SORT-UP        = 'X'.
  APPEND WA_SORT TO IT_SORT.
  CLEAR  WA_SORT.
  WA_SORT-SPOS = '02'.
  WA_SORT-FIELDNAME = 'POSNR' .
  WA_SORT-TABNAME   = 'IT_VBRP'.
  WA_SORT-UP        = 'X'.
  APPEND WA_SORT TO IT_SORT.
ENDFORM.                    " SORT_FIELDS
*&      Form  MODIFY_LAYOUT
      text
-->  p1        text
<--  p2        text
FORM MODIFY_LAYOUT .
  WA_LAYOUT-DEFAULT_ITEM = 'X'.
  WA_LAYOUT-ZEBRA = 'X'.
  WA_LAYOUT-EXPAND_FIELDNAME = 'EXPAND'.
  WA_layout-colwidth_optimize = 'X'.
ENDFORM.                    " MODIFY_LAYOUT
*&      Form  LIST_DISP
      text
-->  p1        text
<--  p2        text
FORM LIST_DISP  TABLES   P_IT_VBRK
                   USING    P_USER_COMMAND TYPE SLIS_FORMNAME.
*CALL FUNCTION 'REUSE_ALV_LIST_DISPLAY'
   EXPORTING
     I_CALLBACK_PROGRAM       = SY-REPID
     I_CALLBACK_PF_STATUS_SET = 'POPUP'
     I_CALLBACK_USER_COMMAND  = 'HANDLE_USER_COMMAND'
     IS_LAYOUT                = WA_LAYOUT
     IT_FIELDCAT              = IT_FIELDCAT[]
     IT_EXCLUDING             = IT_EXTAB[]
   TABLES
     T_OUTTAB                 = IT_VBRK
   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.
  CALL FUNCTION 'REUSE_ALV_GRID_DISPLAY'
    EXPORTING
      I_CALLBACK_PROGRAM       = SY-REPID
      I_CALLBACK_PF_STATUS_SET = 'POPUP'
      I_CALLBACK_USER_COMMAND  = 'HANDLE_USER_COMMAND'
      IS_LAYOUT                = WA_LAYOUT
      IT_FIELDCAT              = IT_FIELDCAT[]
    TABLES
      T_OUTTAB                 = P_IT_VBRK
    EXCEPTIONS
      PROGRAM_ERROR            = 1
      OTHERS                   = 2.
ENDFORM.                    " LIST_DISP
*&      Form  POPUP
      text
     -->P_EXTAB    text
FORM POPUP USING IT_EXTAB TYPE SLIS_T_EXTAB.
*- Pf status
  SET PF-STATUS 'POPUP'.
ENDFORM.                 " POPUP
*&      Form F_USER_COMMAND
FORM HANDLE_USER_COMMAND USING R_UCOMM     LIKE SY-UCOMM
                               RS_SELFIELD TYPE SLIS_SELFIELD.
  CASE R_UCOMM.
    WHEN '&IC1'.
        clear it_fieldcat1[].
        CLEAR IT_VBRP[].
        IF RS_SELFIELD-FIELDNAME = 'VBELN'.
        READ TABLE IT_VBRK INDEX RS_SELFIELD-TABINDEX.
        LOOP AT ITAB WHERE VBELN = IT_VBRK-VBELN.
        MOVE-CORRESPONDING ITAB TO IT_VBRP.
        APPEND IT_VBRP.
        ENDLOOP.
        PERFORM INTERACTIVE_REPORT.
        ENDIF.
  ENDCASE.
ENDFORM.                    "HANDLE_USER_COMMAND
*&      Form  INTERACTIVE_REPORT
      text
-->  p1        text
<--  p2        text
FORM INTERACTIVE_REPORT .
CALL FUNCTION 'REUSE_ALV_FIELDCATALOG_MERGE'
   EXPORTING
     I_PROGRAM_NAME         = SY-REPID
     I_INTERNAL_TABNAME     = 'ITAB'
     I_INCLNAME             = SY-REPID
   CHANGING
     CT_FIELDCAT            = IT_FIELDCAT1[]
   EXCEPTIONS
     INCONSISTENT_INTERFACE = 1
     PROGRAM_ERROR          = 2
     OTHERS                 = 3.
IF SY-SUBRC <> 0.
MESSAGE ID SY-MSGID TYPE SY-MSGTY NUMBER SY-MSGNO
        WITH SY-MSGV1 SY-MSGV2 SY-MSGV3 SY-MSGV4.
ENDIF.
  WA_FIELDCAT-FIELDNAME = 'VBELN'.
  WA_FIELDCAT-SELTEXT_L = 'BILLING DOC'.
  WA_FIELDCAT-TABNAME = 'IT_VBRP'.
  WA_FIELDCAT-COL_POS  = 1.
  APPEND WA_FIELDCAT TO IT_FIELDCAT1.
  CLEAR WA_FIELDCAT.
  WA_FIELDCAT-FIELDNAME = 'POSNR'.
  WA_FIELDCAT-SELTEXT_L = 'ITEM'.
  WA_FIELDCAT-TABNAME = 'IT_VBRP'.
  WA_FIELDCAT-COL_POS  = 2.
  APPEND WA_FIELDCAT TO IT_FIELDCAT1.
  CLEAR WA_FIELDCAT.
  WA_FIELDCAT-FIELDNAME = 'FKIMG'.
  WA_FIELDCAT-SELTEXT_M = 'INV QTY'.
  WA_FIELDCAT-TABNAME = 'IT_VBRP'.
  WA_FIELDCAT-COL_POS  = 3.
  APPEND WA_FIELDCAT TO IT_FIELDCAT1.
  CLEAR WA_FIELDCAT.
  WA_FIELDCAT-FIELDNAME = 'VRKME'.
  WA_FIELDCAT-SELTEXT_M = 'SALES UNIT'.
  WA_FIELDCAT-TABNAME = 'IT_VBRP'.
  WA_FIELDCAT-COL_POS  = 4.
  APPEND WA_FIELDCAT TO IT_FIELDCAT1.
  CLEAR WA_FIELDCAT.
  WA_FIELDCAT-FIELDNAME = 'NETWR'.
  WA_FIELDCAT-SELTEXT_M = 'NET PRICE'.
  WA_FIELDCAT-TABNAME = 'IT_VBRP'.
  WA_FIELDCAT-DO_SUM = 'X'.
  WA_FIELDCAT-COL_POS  = 5.
  APPEND WA_FIELDCAT TO IT_FIELDCAT1.
  CLEAR WA_FIELDCAT.
  WA_FIELDCAT-FIELDNAME = 'MATNR'.
  WA_FIELDCAT-SELTEXT_M = 'MATERIAL'.
  WA_FIELDCAT-TABNAME = 'IT_VBRP'.
  WA_FIELDCAT-COL_POS  = 6.
  APPEND WA_FIELDCAT TO IT_FIELDCAT1.
  CLEAR WA_FIELDCAT.
  WA_FIELDCAT-FIELDNAME = 'ARKTX'.
  WA_FIELDCAT-SELTEXT_M = 'SALES ORDER'.
  WA_FIELDCAT-TABNAME = 'IT_VBRP'.
  WA_FIELDCAT-COL_POS  = 7.
  APPEND WA_FIELDCAT TO IT_FIELDCAT1.
  CLEAR WA_FIELDCAT.
*CALL FUNCTION 'REUSE_ALV_LIST_DISPLAY'
   EXPORTING
     I_CALLBACK_PROGRAM       = SY-REPID
     IS_LAYOUT                = WA_LAYOUT
     IT_FIELDCAT              = IT_FIELDCAT1[]
     IT_SORT                  = IT_SORT
   TABLES
     T_OUTTAB                 = IT_VBRP
   EXCEPTIONS
     PROGRAM_ERROR            = 1
     OTHERS                   = 2.
  CALL FUNCTION 'REUSE_ALV_GRID_DISPLAY'
    EXPORTING
      I_CALLBACK_PROGRAM = SY-REPID
      IS_LAYOUT          = WA_LAYOUT
      IT_FIELDCAT        = IT_FIELDCAT1[]
    TABLES
      T_OUTTAB           = IT_VBRP
    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.                    " INTERACTIVE_REPORT
hope this helps,
priya.

Similar Messages

  • How to Hide rows in ALV without affecting total sum at the end of table?

    Hi,
    I need some help in hiding particular rows in an ALV Grid without affecting the total sum at the end of the table. I am trying to hide the rows that have negative quantities, but I still need those values so that the user can still compute for the total sums. Can anyone help? Thanks.
    Joseph

    Hi,
    Hopw this way you can hide the rows in the GRID.
    DATA:
      ld_column      TYPE lvc_fname,
      ld_hide          TYPE abap_bool.
    FIELD-SYMBOLS:
      <ls_entry>     TYPE any,
      <ld_fld>         TYPE any.
      ld_column = 'COL_1'.  " column which you want to suppress if everything is zero
      ld_hide     = abap_true.  " = 'X';  default hide column
      LOOP at <gt_outtab> ASSIGNING <ls_entry>.
        ASSIGN COMPONENT (ld_column) OF STRUCTURE <ls_entry> TO <ld_fld>.
        IF ( <ld_fld>   > 0 ).
          ld_hide = abap_false.  " display column because at least single value > 0
          EXIT.  " leave LOOP
        ENDIF.
      ENDLOOP.
      READ TABLE gt_fcat INTO ls_fcat
                           WITH KEY fieldname = ld_column.
      IF ( syst-subrc = 0 ).
        ls_fcat-no_out = ld_hide.
        MODIFY gt_fcat FROM ls_fcat INDEX syst-tabix.
      ENDIF.
    hop you will get the total with for those columns too.
    Regards,
    Madhavi

  • Total sum to be displayed in a table view control ?

    Hi,
      I am unable to display the total sum of a column in a table view control( using HTMLB ). How should one display the sum of a column ?
    THanks in advance,
    VaraPrasad

    Hi,
    it should work once you are restricting the capacity of the out put port then it should provide that much rows only otherwise its a Bug.
    Alternativily you are tellin to disaply using sorting then add a Sort operator to the output port and the display ur output port in down order.
    But first option should work just check it again.
    On which SP u r working?
    Regards,
    Govindu

  • Final total cannot appear when the last line item reached the page end

    Hi All,
    My report included 2 pages. Problem is the final total cannot appear when the last line item reached the page end. (page 2)
    final total will appear on the middle of last page (page 3) when i comment (type    = 'BOTTOM').
    Below is the program.
      CALL FUNCTION 'OPEN_FORM'
        EXPORTING
          device   = 'PRINTER'
          dialog   = 'X'
          form     = 'ZBOTM_VOUCHER'
          language = sy-langu.
      sort itab by vblnr.
      LOOP AT itab INTO wa_itab.
        move wa_itab-vblnr to reguh-vblnr.
        move wa_itab-lifnr to reguh-lifnr.
        move wa_itab-rbetr to reguh-rbetr.
        reguh-rbetr = reguh-rbetr * -1.
        CALL FUNCTION 'WRITE_FORM'
          EXPORTING
            window  = 'MAIN'
            element = 'DETAIL'.
        t_rbetr = reguh-rbetr + t_rbetr.
        AT LAST.
          CALL FUNCTION 'WRITE_FORM'
            EXPORTING
              window = 'LINE'.
          CALL FUNCTION 'WRITE_FORM'
            EXPORTING
              element = 'TOTAL'.
              type    = 'BOTTOM'
              WINDOW  = 'MAIN'.
        ENDAT.
    Thanks.

    Hi,
    Where should I include the code for bottom?
    How to open text editor?
    Thanks.
    Edited by: Alice8 on Feb 7, 2011 9:09 AM

  • How to display the total at the end of the column in the report.

    Hi all,
    Could any one please intimate, how to display the total at the end of the column. For example, i have a column, "sales" as the Key figure, and it has the data for all the transactions. Now, i would like to display the total at the end of the report, below the same column.
    Similarly, for all the other columns in the report, i need to display the total for all the columns in the report.
    Thanks & Regards,
    A.V.N.Rao

    Hi All,
    Thanks for many suggestions. I tried by providing the "Total" under "Calculate Results as" and also "Counter for all detailed values" under "Calcuate Single Values as", in the  "Calculations" tab of the key figure, but i am unable to get the information. Again, i am providing the requirement below:
    CHAR - A   CHAR - B   TIME CH. - 1 KF -1  KF- 2 KF - 3
    1                     RAM        2012           1         50      50
    2                     SAM         2012          2         100    200
    Result                                               3           150   250
    Assume KF -1 as  "Qty." KF-2  as "Price" KF-3 as "Sales".
    Please intimate the solution.
    Thanks & Regards,
    A.V.N.Rao.

  • Displaying a total sum value in the af:table - footer

    Hello everyone,
    I have seen various threads on how to calculate a summary column based on a af:column in an af:table. I would like the value of this column to be displayed in the af:table -> footer (right undernead the af:column)
    I'm having trouble putting together the pieces. This is the last requirement I have on this page, so hopefully I won't have to start all over.
    Here this what I have:
    I have created my page. (jspx) I did not create the page with a "backing bean". I have seen in various threads that the backing bean can be used to programmatically populate the table.
    This is what I have done so far.
    For the DataModel:
    I have created my entity object, and I have a view assigned to the object. I assigned the view to my Application Module.
    For the UserInterface:
    On the layout, I dragged the instance of the view from the page definition. I created an af:table.
    My questions/train of thought are:
    I didn't create a "backing bean" when I first created my jspx page. From the various threads that I have seen, they all reference this. Can anyone explain how I can do this when the page has already been created? I'm using jdev version 10.1.3.3
    Within the backing bean, I assume this is where I would then create a method that would do the "sum" of my column.
    To display the column:
    I would then create an af:output_text and drag it to theh table footer. The binding section
    If anyone has a prior thread that I haven't found that can point me in the right direction with what I already I would really appreciate it.
    Thanks

    Kuba,
    By creating a managed bean against the page definition, you are able to access the "iterator". The iterator is an object that is based off of hte View object (which the page is build off of)... From there, you can then loop through the rows and add them together to come up with the total sum.
    You can then reference this method in the TEST.java class since it was created as a managed bean.
    I believe I got the gist of it now... Coming from an Oracle Forms perspecitive, it is actually pretty similar. Now I understand what Managed Beans are used for. Thanks again for the great example.
    Danny

  • ABAP Dump while doing total(summing up)

    Hello Experts
    I have a report:
    This program reads Sales Order and Delivery information. When i tried to sum the Order Quantity, an ABAP Dump is coming. Can anyone help me in correcting my Code?
    Program looks like following and DUMP follows.
    Global data declaration
    TYPE-POOLS: slis.
    TABLES: vbap, vbrk, vbfa, vbak, vbrp, konv, kna1, bkpf, bsad, bkpf_bsad,
    knvv, pa0002, t005u, mvke, lips, likp, vbpa, vbep.
    DATA: BEGIN OF i_list OCCURS 0,
          vbeln LIKE vbak-vbeln,
          posnr LIKE vbap-posnr,
          etenr like vbep-etenr,
          matnr LIKE vbap-matnr,
          erdat LIKE vbap-erdat,
          mvgr1 LIKE mvke-mvgr1,
          wadat_ist LIKE likp-wadat_ist,
          days TYPE i,
          werks LIKE vbap-werks,
          lgort LIKE vbap-lgort,
          kwmeng LIKE vbap-kwmeng,"                                  CH01+
          lfimg  LIKE lips-lfimg,"                                   CH01+
          pstyv  LIKE vbap-pstyv,"                                   CH01+
          obd    LIKE lips-vbeln,"                                   CH01+
          obd_pos LIKE lips-posnr,"                                  CH01+
          soldto  LIKE vbaK-kunnr,"                                  JR+
          shipto  LIKE vbpa-kunnr,"                                  JR+
          edatu like vbep-edatu,"                                    PR+
          END OF i_list.
    DATA: i_list2 LIKE i_list OCCURS 0 WITH HEADER LINE,
          i_list3 LIKE i_list OCCURS 0 WITH HEADER LINE.
    DATA: i_list4 LIKE vbap OCCURS 0 WITH HEADER LINE.
    *ALV Output Header
    DATA: gt_list_top_of_page TYPE slis_t_listheader,
          prognm     LIKE sy-repid,
          gc_formname_top_of_page TYPE slis_formname VALUE 'TOP_OF_PAGE',
          gt_events   TYPE slis_t_event,
          is_layout TYPE slis_layout_alv,
          is_variant LIKE disvariant,
          it_sort  TYPE slis_t_sortinfo_alv WITH HEADER LINE.
    DATA:gt_fieldcat TYPE slis_t_fieldcat_alv.
    DATA:gt_outtab LIKE i_list OCCURS 0 WITH HEADER LINE.
    DATA:   g_repid LIKE sy-repid,
            g_count LIKE sy-tabix.
    SELECTION-SCREEN BEGIN OF BLOCK block0 WITH FRAME TITLE text-t01.
    SELECTION-SCREEN: BEGIN OF LINE.
    SELECTION-SCREEN COMMENT 1(79) text-t10.
    SELECTION-SCREEN: END OF LINE.
    SELECTION-SCREEN: BEGIN OF LINE.
    SELECTION-SCREEN COMMENT 1(79) text-t11.
    SELECTION-SCREEN: END OF LINE.
    SELECTION-SCREEN: BEGIN OF LINE.
    SELECTION-SCREEN COMMENT 1(79) text-t12.
    SELECTION-SCREEN: END OF LINE.
    SELECTION-SCREEN END OF BLOCK block0.
    */ Selection and Input Parameters
    SELECTION-SCREEN BEGIN OF BLOCK blocko WITH FRAME TITLE text-001.
    SELECT-OPTIONS: s_vbeln FOR vbap-vbeln, "SO
                    s_auart FOR vbak-auart DEFAULT 'KB' OBLIGATORY,
                    s_matnr FOR vbap-matnr," obligatory,
                    s_mvgr1 FOR mvke-mvgr1,
                    s_erdat FOR vbap-erdat OBLIGATORY,
                    s_werks FOR vbap-werks,
                    s_lgort FOR vbap-lgort,
                    s_edatu FOR vbep-edatu.
    PARAMETERS:     p_vkorg LIKE vbak-vkorg DEFAULT '5010'.
    SELECTION-SCREEN SKIP 2.
    +EC1
    Addition                                                          +EC1
    +EC1
    PARAMETERS: p_vari LIKE disvariant-variant.
    +EC1
    End Addition                                                      +EC1
    +EC1
    SELECTION-SCREEN END OF BLOCK blocko.
    +EC1
    Addition                                                          +EC1
    +EC1
    DATA:   g_save(1) TYPE c,
           g_default(1) TYPE c,
            g_exit(1) TYPE c,
            gx_variant LIKE disvariant,
            g_variant LIKE disvariant.
    +EC1
    End Addition                                                      +EC1
    +EC1
    Initialization fieldcatalog
    INITIALIZATION.
    PERFORM clear_tables.
      g_repid = sy-repid.
      PERFORM fieldcat_init USING gt_fieldcat[].
    +EC1
    Addition                                                          +EC1
    +EC1
      g_save = 'A'.
      PERFORM variant_init.
    Get default variant
      gx_variant = g_variant.
      CALL FUNCTION 'REUSE_ALV_VARIANT_DEFAULT_GET'
           EXPORTING
                i_save     = g_save
           CHANGING
                cs_variant = gx_variant
           EXCEPTIONS
                not_found  = 2.
      IF sy-subrc = 0.
        p_vari = gx_variant-variant.
      ENDIF.
    AT SELECTION-SCREEN ON VALUE-REQUEST FOR p_vari.
      PERFORM f4_for_variant.
    AT SELECTION-SCREEN.
      PERFORM auth_check.  "+ESC
      PERFORM pai_of_selection_screen.
    +EC1
    End Addition                                                      +EC1
    +EC1
    START-OF-SELECTION.
      PERFORM get_data.
      PERFORM alv.
    END-OF-SELECTION.
          FORM get_data                                                 *
    FORM get_data.
    *CH01 - Added kwmeng(order qty) to selection, excluded rejects
    *JR -added soldto and shipto code
      SELECT avbeln aposnr amatnr aerdat awerks algort
             akwmeng apstyv bkunnr cedatu
    CH01+
      INTO
    (i_list-vbeln, i_list-posnr, i_list-matnr, i_list-erdat, i_list-werks,
    i_list-lgort,
    i_list-kwmeng , i_list-pstyv, i_list-soldto,i_list-edatu)
           CH01+
      FROM vbap AS a INNER JOIN vbak AS b ON avbeln = bvbeln
                     INNER JOIN vbep AS c ON avbeln = cvbeln
      WHERE b~vkorg = p_vkorg
      AND   a~werks IN s_werks
      AND   a~lgort IN s_lgort
      AND   b~auart IN s_auart
      AND   a~vbeln IN s_vbeln
      AND   a~erdat IN s_erdat
      AND   a~abgru = ''"                                            CH01+
      AND   a~matnr IN s_matnr
      AND   c~edatu IN s_edatu.
        APPEND i_list.
      ENDSELECT.
      COMMIT WORK AND WAIT.
    SORT i_list BY VBELN POSNR EDATU.
    DELETE ADJACENT DUPLICATES FROM i_list COMPARING vbeln posnr.
      LOOP AT i_list.
        SELECT SINGLE mvgr1 INTO i_list-mvgr1 FROM mvke
        WHERE matnr = i_list-matnr.
        MODIFY i_list.
        CLEAR: i_list.
      ENDLOOP.
      COMMIT WORK AND WAIT.
      LOOP AT i_list.
        IF i_list-mvgr1 IN s_mvgr1.
          CONTINUE.
        ELSE.
          DELETE i_list.
          COMMIT WORK AND WAIT.
        ENDIF.
      ENDLOOP.
    CH01 - commented these lines out and redid logic below
    LOOP AT i_list.
       select single vbeln into lips-vbeln from lips
       where vgbel = i_list-vbeln
       and   vgpos = i_list-posnr.
       select single wadat_ist into i_list-wadat_ist from likp
       where vbeln = lips-vbeln.
       SELECT b~wadat_ist  INTO i_list-wadat_ist
       FROM lips AS a INNER JOIN
       likp AS b ON avbeln = bvbeln WHERE a~vgbel = i_list-vbeln
                                      AND   a~vgpos = i_list-posnr.
         MODIFY i_list.
         CLEAR: i_list, lips-vbeln.
       ENDSELECT.
    ENDLOOP.
    CH01 - Changed to select multiple delivery lines & del qty
    summing the total deliveries per OBD# and date
      LOOP AT i_list.
        SELECT avbeln   sum( alfimg ) b~wadat_ist
        INTO (i_list-obd , i_list-lfimg , i_list-wadat_ist)
        FROM lips AS a INNER JOIN
        likp AS b ON avbeln = bvbeln WHERE a~vgbel = i_list-vbeln
                                       AND   a~vgpos = i_list-posnr
                                       AND   a~pstyv = i_list-pstyv
          group by avbeln bwadat_ist.
          i_list2 = i_list.
          APPEND i_list2.
        ENDSELECT.
        IF sy-subrc <> 0.
          i_list2 = i_list.
          APPEND i_list2.
        ENDIF.
      ENDLOOP.
      i_list[] = i_list2[].
    *End CH01
      COMMIT WORK AND WAIT.
      LOOP AT i_list.
        IF  i_list-wadat_ist IS INITIAL.
          CONTINUE.
        ELSE.
          i_list-days = i_list-wadat_ist - i_list-erdat.
        ENDIF.
        MODIFY i_list.
        CLEAR: i_list.
        COMMIT WORK AND WAIT.
      ENDLOOP.
      COMMIT WORK AND WAIT.
      LOOP AT i_list.
        IF i_list-vbeln IS INITIAL.
          DELETE i_list.
        ENDIF.
      ENDLOOP.
      COMMIT WORK AND WAIT.
    *JR
      LOOP AT i_list.
        SELECT SINGLE KUNNR INTO i_list-shipto FROM vbpa
        WHERE vbeln = i_list-vbeln
         AND parvw = 'WE'.
        MODIFY i_list.
      ENDLOOP.
    *END JR
      gt_outtab[] = i_list[].
      COMMIT WORK AND WAIT.
    ENDFORM.
          FORM alv                                                      *
    FORM alv.
      PERFORM e03_eventtab_build USING gt_events[].             "+EC1
      PERFORM e04_comment_build  USING gt_list_top_of_page[].   "+EC1
      prognm = sy-repid.                                        "+EC1
      CALL FUNCTION 'REUSE_ALV_GRID_DISPLAY'
          EXPORTING
               i_callback_user_command = 'USER_COMMAND'
               i_callback_program      = g_repid
               it_fieldcat             = gt_fieldcat[]
               it_events               = gt_events[]    "+ESC
               it_sort                 = it_sort[]
    +EC1
    Addition                                                          +EC1
    +EC1
               is_variant              = g_variant
               i_save                  = g_save
    +EC1
    End Addition                                                      +EC1
    +EC1
          TABLES
               t_outtab                = gt_outtab.
      COMMIT WORK AND WAIT.
    ENDFORM.
          FORM fieldcat_init                                            *
    -->  I_FIELDCAT                                                    *
    FORM fieldcat_init
          USING i_fieldcat TYPE slis_t_fieldcat_alv.
      DATA: ls_fieldcat TYPE slis_fieldcat_alv.
      DATA: pos TYPE i VALUE 1.
      CLEAR ls_fieldcat.
      pos = pos + 1.
      ls_fieldcat-col_pos       =  pos.
      ls_fieldcat-fieldname     = 'VBELN'.
      ls_fieldcat-ref_tabname   = 'VBAK'.
      ls_fieldcat-key           = 'X'.
      APPEND ls_fieldcat TO i_fieldcat.
      CLEAR ls_fieldcat.
      pos = pos + 1.
      ls_fieldcat-col_pos       =  pos.
      ls_fieldcat-fieldname     = 'POSNR'.
      ls_fieldcat-ref_tabname   = 'VBAP'.
      ls_fieldcat-key           = 'X'.
      APPEND ls_fieldcat TO i_fieldcat.
      CLEAR ls_fieldcat.
      pos = pos + 1.
      ls_fieldcat-col_pos       =  pos.
      ls_fieldcat-fieldname     = 'MATNR'.
      ls_fieldcat-ref_tabname   = 'VBAP'.
      ls_fieldcat-key           = 'X'.
      APPEND ls_fieldcat TO i_fieldcat.
      CLEAR ls_fieldcat.
      pos = pos + 1.
      ls_fieldcat-col_pos       =  pos.
      ls_fieldcat-fieldname     = 'MVGR1'.
      ls_fieldcat-ref_tabname   = 'MVKE'.
      ls_fieldcat-key           = 'X'.
      APPEND ls_fieldcat TO i_fieldcat.
      CLEAR ls_fieldcat.
      pos = pos + 1.
      ls_fieldcat-col_pos       =  pos.
      ls_fieldcat-fieldname     = 'WERKS'.
      ls_fieldcat-ref_tabname   = 'VBAP'.
    ls_fieldcat-key           = 'X'.
      APPEND ls_fieldcat TO i_fieldcat.
      CLEAR ls_fieldcat.
      pos = pos + 1.
      ls_fieldcat-col_pos       =  pos.
      ls_fieldcat-fieldname     = 'LGORT'.
      ls_fieldcat-ref_tabname   = 'VBAP'.
    ls_fieldcat-key           = 'X'.
      APPEND ls_fieldcat TO i_fieldcat.
      CLEAR ls_fieldcat.
      pos = pos + 1.
      ls_fieldcat-col_pos       =  pos.
      ls_fieldcat-fieldname     = 'ERDAT'.
      ls_fieldcat-ref_tabname   = 'VBAP'.
    ls_fieldcat-key           = 'X'.
      APPEND ls_fieldcat TO i_fieldcat.
      CLEAR ls_fieldcat.
      pos = pos + 1.
      ls_fieldcat-col_pos       =  pos.
      ls_fieldcat-fieldname     = 'WADAT_IST'.
      ls_fieldcat-ref_tabname   = 'LIKP'.
    ls_fieldcat-key           = 'X'.
      APPEND ls_fieldcat TO i_fieldcat.
      CLEAR ls_fieldcat.
      pos = pos + 1.
      ls_fieldcat-col_pos       =  pos.
      ls_fieldcat-fieldname     = 'DAYS'.
      ls_fieldcat-ref_fieldname = 'DAYS'.
      ls_fieldcat-seltext_s     = '# Of Days'.
      ls_fieldcat-seltext_m     = '# Of Days'.
      ls_fieldcat-seltext_l     = '# Of Days'.
      APPEND ls_fieldcat TO i_fieldcat.
      CLEAR ls_fieldcat.
    *Begin CH01
      pos = pos + 1.
      ls_fieldcat-col_pos       =  pos.
      ls_fieldcat-fieldname     = 'KWMENG'.
      ls_fieldcat-ref_tabname   = 'VBAP'.
      ls_fieldcat-outputlen     = 7.
      APPEND ls_fieldcat TO i_fieldcat.
      CLEAR ls_fieldcat.
      pos = pos + 1.
      ls_fieldcat-col_pos       =  pos.
      ls_fieldcat-fieldname     = 'LFIMG'.
      ls_fieldcat-ref_tabname   = 'LIPS'.
      ls_fieldcat-outputlen     = 7.
      APPEND ls_fieldcat TO i_fieldcat.
      CLEAR ls_fieldcat.
      pos = pos + 1.
      ls_fieldcat-col_pos       =  pos.
      ls_fieldcat-fieldname     = 'OBD'.
      ls_fieldcat-seltext_s     = 'OBD'.
      ls_fieldcat-seltext_m     = 'Outbound Del'.
      ls_fieldcat-seltext_l     = 'Outbound Delivery'.
      ls_fieldcat-outputlen     = 10.
      APPEND ls_fieldcat TO i_fieldcat.
      CLEAR ls_fieldcat.
    ls_fieldcat-col_pos       =  pos.
    ls_fieldcat-fieldname     = 'OBD_POS'.
    ls_fieldcat-seltext_s     = 'OBD Ln'.
    ls_fieldcat-seltext_m     = 'Outbound Del Ln'.
    ls_fieldcat-seltext_l     = 'Outbound Del Line'.
    ls_fieldcat-outputlen     = 10.
    APPEND ls_fieldcat TO i_fieldcat.
    CLEAR ls_fieldcat.
    *End CH01
    *JR
      pos = pos + 1.
      ls_fieldcat-col_pos       =  pos.
      ls_fieldcat-fieldname     = 'SOLDTO'.
      ls_fieldcat-ref_tabname   = 'VBAP'.
      ls_fieldcat-seltext_m     = 'Sold To'.
      ls_fieldcat-seltext_l     = 'Sold To'.
      ls_fieldcat-outputlen     = 10.
      APPEND ls_fieldcat TO i_fieldcat.
      CLEAR ls_fieldcat.
      pos = pos + 1.
      ls_fieldcat-col_pos       =  pos.
      ls_fieldcat-fieldname     = 'SHIPTO'.
      ls_fieldcat-ref_tabname   = 'VBPA'.
      ls_fieldcat-seltext_m     = 'Ship To'.
      ls_fieldcat-seltext_l     = 'Ship To'.
      ls_fieldcat-outputlen     = 10.
      APPEND ls_fieldcat TO i_fieldcat.
      CLEAR ls_fieldcat.
      pos = pos + 1.
      ls_fieldcat-col_pos = pos.
      ls_fieldcat-fieldname = 'ETERN'.
      ls_fieldcat-ref_tabname = 'VBEP'.
      ls_fieldcat-seltext_m     = 'Schedule line number'.
      ls_fieldcat-seltext_l     = 'Schedule line number'.
    ls_fieldcat-key = 'Schedule line number'.
      APPEND ls_fieldcat TO i_fieldcat.
      CLEAR ls_fieldcat.
    *END JR
    pos = pos + 1.
    ls_fieldcat-col_pos = pos.
    ls_fieldcat-fieldname = 'EDATU'.
    ls_fieldcat-ref_tabname = 'VBEP'.
    ls_fieldcat-seltext_m = 'Requested Delivery date'.
    ls_fieldcat-seltext_l = 'Requested Delivery date'.
    ls_fieldcat-outputlen = 20.
    APPEND ls_fieldcat TO i_fieldcat.
    CLEAR ls_fieldcat.
    *FOR ALV SORT & SUBTOTAL
      CLEAR it_sort.
      it_sort-spos = '0'.
      it_sort-fieldname = 'VBELN'.
      it_sort-tabname = 'GT_OUTTAB'.
      it_sort-up = 'X'.
    it_sort-subtot = 'X'.
      APPEND it_sort.
      CLEAR it_sort.
      it_sort-spos = '1'.
      it_sort-fieldname = 'POSNR'.
      it_sort-tabname = 'GT_OUTTAB'.
      it_sort-up = 'X'.
      it_sort-subtot = 'X'.
    it_sort-subtot = 'X'.
      APPEND it_sort.
      CLEAR it_sort.
      it_sort-spos = '2'.
      it_sort-fieldname = 'MATNR'.
      it_sort-tabname = 'GT_OUTTAB'.
      it_sort-up = 'X'.
    it_sort-subtot = 'X'.
      APPEND it_sort.
      CLEAR it_sort.
      it_sort-spos = '3'.
      it_sort-fieldname = 'MVGR1'.
      it_sort-tabname = 'GT_OUTTAB'.
      it_sort-up = 'X'.
    it_sort-subtot = 'X'.
      APPEND it_sort.
      CLEAR it_sort.
      it_sort-spos = '4'.
      it_sort-fieldname = 'ERDAT'.
      it_sort-tabname = 'GT_OUTTAB'.
      it_sort-up = 'X'.
    it_sort-subtot = 'X'.
      APPEND it_sort.
      CLEAR it_sort.
      it_sort-spos = '5'.
      it_sort-fieldname = 'WADAT_IST'.
      it_sort-tabname = 'GT_OUTTAB'.
      it_sort-down = 'X'.
    it_sort-subtot = 'X'.
      APPEND it_sort.
    CLEAR it_sort.
    it_sort-spos = '6'.
    it_sort-fieldname = 'PERNR'.
    it_sort-tabname = 'GT_OUTTAB'.
    it_sort-up = 'X'.
    it_sort-subtot = 'X'.
    APPEND it_sort.
    CLEAR it_sort.
    it_sort-spos = '7'.
    it_sort-fieldname = 'VORNA'.
    it_sort-tabname = 'GT_OUTTAB'.
    it_sort-up = 'X'.
    it_sort-subtot = 'X'.
    APPEND it_sort.
    CLEAR it_sort.
    it_sort-spos = '8'.
    it_sort-fieldname = 'NACHN'.
    it_sort-tabname = 'GT_OUTTAB'.
    it_sort-up = 'X'.
    it_sort-subtot = 'X'.
    APPEND it_sort.
    CLEAR it_sort.
    it_sort-spos = '9'.
    it_sort-fieldname = 'VKGRP'.
    it_sort-tabname = 'GT_OUTTAB'.
    it_sort-up = 'X'.
    it_sort-subtot = 'X'.
    APPEND it_sort.
    CLEAR it_sort.
    it_sort-spos = '10'.
    it_sort-fieldname = 'VBELN'.
    it_sort-tabname = 'GT_OUTTAB'.
    it_sort-up = 'X'.
    it_sort-subtot = 'X'.
    APPEND it_sort.
    CLEAR it_sort.
    it_sort-spos = '11'.
    it_sort-fieldname = 'ERDAT'.
    it_sort-tabname = 'GT_OUTTAB'.
    it_sort-up = 'X'.
    it_sort-subtot = 'X'.
    APPEND it_sort.
    CLEAR it_sort.
    it_sort-spos = '12'.
    it_sort-fieldname = 'BEZEI'.
    it_sort-tabname = 'GT_OUTTAB'.
    it_sort-up = 'X'.
    it_sort-subtot = 'X'.
    APPEND it_sort.
    clear it_sort.
    it_sort-spos = '1'.
    it_sort-fieldname = 'BELNR'.
    it_sort-tabname = 'GT_OUTTAB'.
    it_sort-up = 'X'.
    append it_sort.
    ENDFORM.
    +EC1
    Addition                                                          +EC1
    +EC1
    *&      Form  VARIANT_INIT
          text
    -->  p1        text
    <--  p2        text
    FORM variant_init.
      CLEAR g_variant.
      g_variant-report = g_repid.
    ENDFORM.                               " VARIANT_INIT
          FORM f4_for_variant                                           *
    FORM f4_for_variant.
      CALL FUNCTION 'REUSE_ALV_VARIANT_F4'
           EXPORTING
                is_variant          = g_variant
                i_save              = g_save
              it_default_fieldcat =
           IMPORTING
                e_exit              = g_exit
                es_variant          = gx_variant
           EXCEPTIONS
                not_found = 2.
      IF sy-subrc = 2.
        MESSAGE ID sy-msgid TYPE 'S'      NUMBER sy-msgno
                WITH sy-msgv1 sy-msgv2 sy-msgv3 sy-msgv4.
      ELSE.
        IF g_exit = space.
          p_vari = gx_variant-variant.
        ENDIF.
      ENDIF.
    ENDFORM.
    *&      Form  PAI_OF_SELECTION_SCREEN
          text
    FORM pai_of_selection_screen.
      IF NOT p_vari IS INITIAL.
        MOVE g_variant TO gx_variant.
        MOVE p_vari TO gx_variant-variant.
        CALL FUNCTION 'REUSE_ALV_VARIANT_EXISTENCE'
             EXPORTING
                  i_save     = g_save
             CHANGING
                  cs_variant = gx_variant.
        g_variant = gx_variant.
      ELSE.
        PERFORM variant_init.
      ENDIF.
    ENDFORM.                               " PAI_OF_SELECTION_SCREEN
    +EC1
    End Addition                                                      +EC1
    +EC1
          FORM e03_eventtab_build                                       *
    -->  E03_LT_EVENTS                                                 *
    FORM e03_eventtab_build USING e03_lt_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   = e03_lt_events.
      READ TABLE e03_lt_events WITH KEY name =  slis_ev_top_of_page
                               INTO ls_event.
      IF sy-subrc = 0.
        MOVE gc_formname_top_of_page TO ls_event-form.
        APPEND ls_event TO e03_lt_events.
      ENDIF.
    ENDFORM.
          FORM e04_comment_build                                        *
    -->  E04_LT_TOP_OF_PAGE                                            *
    FORM e04_comment_build USING e04_lt_top_of_page TYPE slis_t_listheader.
      DATA: ls_line TYPE slis_listheader.
    *Report Title
      CLEAR ls_line.
      ls_line-typ  = 'H'.
      ls_line-info = text-007.
      APPEND ls_line TO e04_lt_top_of_page.
    **Doc Type Desc.
    clear ls_line.
    ls_line-typ  = 'S'.
    ls_line-key = text-008.
    ls_line-info = p_matnr.
    append ls_line to e04_lt_top_of_page.
    clear ls_line.
    ls_line-typ  = 'S'.
    ls_line-key  = text-009.
    ls_line-info = p_werks.
    append ls_line to e04_lt_top_of_page.
    clear ls_line.
    ls_line-typ  = 'S'.
    ls_line-key = text-010.
    ls_line-info = p_stlan.
    append ls_line to e04_lt_top_of_page.
    clear ls_line.
    ls_line-typ  = 'S'.
    ls_line-key = text-011.
    ls_line-info = p_stlal.
    append ls_line to e04_lt_top_of_page.
    clear ls_line.
    ls_line-typ  = 'S'.
    ls_line-key = text-012.
    ls_line-info = p_stlal.
    append ls_line to e04_lt_top_of_page.
    ENDFORM.
          FORM top_of_page                                              *
    FORM top_of_page.
      CALL FUNCTION 'REUSE_ALV_COMMENTARY_WRITE'
           EXPORTING
                it_list_commentary = gt_list_top_of_page.
    ENDFORM.
          FORM auth_check                                               *
    FORM auth_check.
      AUTHORITY-CHECK OBJECT 'V_VBAK_VKO'
                      ID 'VKORG' FIELD p_vkorg.
      IF sy-subrc NE 0.
        MESSAGE e054 WITH p_vkorg.
      ENDIF.
    ENDFORM.                    " auth_check
    *&      Form  USER_COMMAND
    FORM user_command  USING r_ucomm LIKE sy-ucomm
                             rs_selfield TYPE slis_selfield.
      CASE r_ucomm.
        WHEN '&IC1'.
          PERFORM display_so_order USING r_ucomm
                                        rs_selfield.
      ENDCASE.
    ENDFORM.
    *&      Form  display_sales_order
          text
         -->P_R_UCOMM  text
         -->P_RS_SELFIELD  text
    FORM display_so_order USING    r_ucomm LIKE sy-ucomm
                                             rs_selfield TYPE slis_selfield.
      CASE rs_selfield-sel_tab_field.
        WHEN '1-VBELN'.
          SET PARAMETER ID 'AUN' FIELD rs_selfield-value.
          CALL TRANSACTION 'VA03' AND SKIP FIRST SCREEN.
        WHEN '1-MATNR'.
          SET PARAMETER ID 'MAT' FIELD rs_selfield-value.
          CALL TRANSACTION 'MM03' AND SKIP FIRST SCREEN.
        WHEN '1-OBD'.
          SET PARAMETER ID 'VL' FIELD rs_selfield-value.
          CALL TRANSACTION 'VL03N' AND SKIP FIRST SCREEN.
        WHEN OTHERS.
          MESSAGE i000(z1) WITH 'Please Click on the Valid Selection'.
          EXIT.
      ENDCASE.
    ENDFORM.                    " display_sales_order
          FORM EDit_table                                               *
    -do_sum = 'C'.     
    009350   *     save the actual grouplevel information                        
    009360         gs_grouplevels = rs_grouplevels.                              
    009370         clear g_lines.                                                
    009380                                                                       
    009390   *     get number of lines of the collect table                      
    009400         describe table rt_data lines g_lines.                         
    009410   *     if there is only one line or the field has no references so   
    009420   *     that only the first line has to be considered                                                                               
    Contents of system fields                                                                               
    SY field contents..................... SY field contents.....................                                                                               
    SY-SUBRC 4                             SY-INDEX 1                                      
    SY-TABIX 15                            SY-DBCNT 1                                      
    SY-FDPOS 1                             SY-LSIND 0                                      
    SY-PAGNO 0                             SY-LINNO 1            
    SY-COLNO 1                                                                               
    Chosen variables                                                                               
    Name.......................... Contents.1........2........3....+....4                                                                               
    %_ARCHIVE                                                                               
    4444444444444444444444444444444444444444            
                                   0000000000000000000000000000000000000000            
    ... +  40                                                                               
    4444444444444444444444444444444444444444            
                                   0000000000000000000000000000000000000000            
    ... +  80                                                                               
    4444444444444444444444444444444444444444            
                                   0000000000000000000000000000000000000000            
    ... + 120                                                                               
    44444444                                            
                                   0000000                                             
    -FIELDNAME        ETERN                                                                               
    CECDD4444444444444444444444444                       
                                  535950000000000000000000000000                       
    T_DATA                        00004082920002000000                  00             
                                  FFFFFFFFFFFFFFFFFFFF444444444444444444FF             
                                  0000408292000200000000000000000000000000             
    .. +  40                      000000   00000000#######        ########             
                                  FFFFFF444FFFFFFFF00000004444444400000000             
                                  000000000000000000000000000000000000000C             
    .. +  80                      #######              000000                          
                                  000000044444444444444FFFFFF4444444444444             
                                  000000C000000000000000000000000000000000             
    .. + 120                             00000000#                                     
                                  4444444F                                             
                                  0000000                                              
    S_DRAGDROP                                                    ####                 
                                  444444444444444444444444444444440000                 
                                  000000000000000000000000000000000000
                                   000000000000000000000000000000000000             
    SY-SUBRC                       4                                                                               
    0000                                             
                                   0004                                             
    SY-XPROG                       SAPCNVE                                          
                                   ECDCDEC444444444444444444444444444444444         
                                   2173555000000000000000000000000000000000         
    %_SPACE                                                                               
    0                                                                               
    0                                                
    SY-MSGID                       0K                                                                               
    FD444444444444444444                             
                                   02000000000000000000                             
    %_PRINT                            000                                          
                                   4444FFF444444444444444444444444444444444         
                                   0000000000000000000000000000000000000000         
    ... +  40                                                                               
    4444444444444444444444444444444444444444         
                                   0000000000000000000000000000000000000000         
    ... +  80                                0 ########                             
                                   4444444444F40000000044444444444444444444         
                                   0000000000000000000000000000000000000000         
    ... + 120                                                                               
    44444444                                         
                                   0000000                                          
    SY-MSGNO                       000                                              
                                   FFF                                              
                                   000
                                   000                                                   
    %_ITAB_MODIFY_LIST             ###########################ø##Èø########              
                                   0000000000000000000000000007007700000000              
                                   0000000000000000000000004000004000000000              
    ... +  40                      ###################################Ø#²#0              
                                   0001000100010000FFFF00000000020000083E0F              
                                   0009000900090000FFFF04000002900000000A50              
    ... +  80                      ########################################              
                                   0000000000000000000000000000000000000000              
                                   0000000000000000000000000000000000000000              
    ... + 120                      ################################                      
                                   00000000                                              
                                   0000000                                               
    SY-MSGV1                                                                               
    4444444444444444444444444444444444444444              
                                   0000000000000000000000000000000000000000              
    ... +  40                                                                               
    4444444444                                            
                                   0000000000                                            
    SY-MSGV2                                                                               
    4444444444444444444444444444444444444444              
                                   0000000000000000000000000000000000000000              
    ... +  40                                                                               
    4444444444                                            
                                   0000000000                                            
    SY-MSGV3                                                                               
    4444444444444444444444444444444444444444              
                                   0000000000000000000000000000000000000000
                                   0000000000000000000000000000000000000000          
    ... +  40                                                                               
    4444444444                                        
                                

    Hi Experts,
    I tried with  OUTPUT length, still Dump Persists, Any Ideas??
    <b>Source code extract on the dump is:</b>
    Thanks
    SP
                                                                                    008930         gs_roid-row_id = rs_row-index * -1.        
    008940       endif.                                                                               
    008950       gs_roid-sub_row_id = rs_row-rowtype+7(10).   
    008960       gs_poid-row_id = gs_roid-row_id.             
    008970       gs_poid-sub_row_id = gs_roid-sub_row_id.     
    008980       gs_poid-rowtype    = rs_row-rowtype.         
    008990       gs_poid-index      = rs_row-index.           
    009000       insert gs_poid into table rt_poid.           
    009010     endif.                                                                               
    009020     append gs_roid to rt_roid.                     
    009030                                                                               
    009040     loop at rt_fieldcat assigning <ls_fieldcat>
    where tech ne 'X' and                    
    009050                                                    
      no_out ne 'X'.                     
    009060                                                                               
    009070       if gflg_invisible = 'X'.                     
    009080         if <ls_fieldcat>-do_sum is initial.        
    009090           clear gflg_invisible.                    
    009100           continue.                                
    009110         else.                                                                               
    009120           clear g_col_counter.                     
    009130           clear gflg_invisible.                    
    009140         endif.                                                                               
    009150       endif.                                                                               
    009160                                                                               
    009170       clear gs_lvc_data.                           
    009180       clear g_style.                               
    009190                                                                               
    009200       assign component                             
    009200       assign component                             
    009210              <ls_fieldcat>-fieldname of structure
    rt_data to <g_field>.                        
    009220       if sy-subrc ne 0.                                                                               
    >         message x000(0k).                          
    009240       endif.                                                                               
    009250                                                                               
    009260       g_col_counter = g_col_counter + 1.           
    009270                                                                               
    009280       gs_lvc_data-row_pos = r_row_counter.         
    009290       gs_lvc_data-col_pos = g_col_counter.         
    009300       gs_lvc_data-row_id  = gs_roid-row_id.        
    009310       gs_lvc_data-sub_row_id = gs_roid-sub_row_id. 
    009320                                                                               
    009330   *   Endtotal and average                         
    009340       if rs_row-rowtype(1) ca 'T' and
    <ls_fieldcat>-do_sum = 'C'.                              
    009350   *     save the actual grouplevel information     
    009360         gs_grouplevels = rs_grouplevels.           
    009370         clear g_lines.                             
    009380                                                                               
    009390   *     get number of lines of the collect table   
    009400         describe table rt_data lines g_lines.      
    009410   *     if there is only one line or the field has
    no references so                            
    009420   *     that only the first line has to be
    considered

  • How to get total sum of big filtered table?

    Hello
    I'm using JDeveloper 11.1.1.3.0
    I have an af:table with big data source (100 000 rows). The table have filters.
    I want to display total count of the filtered rows and total sum by the one of column of the filtered rows in the footer of the table.
    In my backing bean I can get a Map with all filter values:
    Map<String, Object> filters = ((FilterableQueryDescriptor)table.getFilterModel()).getFilterCriteria();And, in this case, I may create the method for getting sum I need on my own.
    In this method I may create SQL Query dynamically, because I have to process all filter values with different types
    It is possible, but, maybe, there is a more easy way to do it?
    Anatolii

    Hi, sanchezis
    Code example.
    In the jsp:
                    <af:column sortProperty="Sumv" sortable="true" filterable="false" align="end" width="125px"
                               headerText="#{bindings.TransactionView1.hints.Sumv.label}" id="c16">
                      <af:outputText value="#{row.Sumv}" id="qt4">
                        <af:convertNumber maxFractionDigits="2" minFractionDigits="2"/>
                      </af:outputText>
                      <f:facet name="footer">
                          <af:panelGroupLayout id="pg41" halign="right"
                                               layout="vertical">             
                        <af:outputText value="#{backing_reptransactions.tableTransactionTotalSumV}" id="ot44">
                          <af:convertNumber maxFractionDigits="2" minFractionDigits="2"/>
                        </af:outputText>
                        </af:panelGroupLayout>
                      </f:facet>
                    </af:column>In the backing bean:
        public double getTableTransactionTotalSumV() {
            DCIteratorBinding iter =
                binding.findIteratorBinding("TransactionView1Iterator");
            TransactionViewImpl vo = (TransactionViewImpl)iter.getViewObject();
            return vo.getFilteredTotalSumV();
        }In the ViewImpl (TransactionViewImpl) class.
        public double getFilteredTotalSumV() {
            double sumV = 0d;
            DBTransaction dbTransaction = getDBTransaction();
            ResultSet rs = null;
            String query = "SELECT SUM(SumV) sumvtotal FROM (" + getQuery() + ")";
            String str1 = "WHERE ROWNUM < :Bind_RangePage_High";
            String str2 = "WHERE Z_R_N > :Bind_RangePage_Low";
            int i = query.indexOf(str1);
            if (i > 0) {
                query = query.substring(0, i) + " " + query.substring(i + str1.length());
            i = query.indexOf(str2);
            if (i > 0) {
                query = query.substring(0, i) + " " + query.substring(i + str2.length());
            PreparedStatement st = dbTransaction.createPreparedStatement(query, 0);
            try {
                Object[] params = this.getWhereClauseParams();
                int index = 0;
                for (Object avalue : params) {
                    String key = (String)((Object[])avalue)[0];
                    if ((!key.equals("Bind_RangePage_High")) &&
                        (!key.equals("Bind_RangePage_Low"))) {
                        Object value = ((Object[])avalue)[1];
                        index++;
                        if (value instanceof Integer) {
                            st.setInt(index, (Integer)value);
                        } else if (value instanceof oracle.jbo.domain.Date) {
                            st.setDate(index,
                                       ((oracle.jbo.domain.Date)value).dateValue());
                        } else if (value instanceof java.sql.Date) {
                            st.setDate(index, (Date)value);
                        } else {
                            st.setString(index, (String)value);
                rs = st.executeQuery();
                if (rs.next()) {
                    sumV = rs.getDouble("sumvtotal");
            } catch (SQLException e) {
                throw new JboException(e);
            } finally {
                if (st != null) {
                    try {
                        st.close();
                    } catch (SQLException e) {
            return sumV;
        public long getFilteredTotalCount() {
            return this.getEstimatedRowCount();
        }But, you need to know that in the TransactionView in the "General" - "Tuning" I set up next values:
    "All rows",
    "As needed",
    "Fill Last Page of Rows when Paging through Rowset",
    "Passivate State(..."
    Access Mode - "Range Paging Incremental"
    Range Size - 160
    Range Paging Cache Factor - 3
    If you have other values, then your SQL request may be different, so, you will have to rewrite it.
    I talk about
    "WHERE ROWNUM < :Bind_RangePage_High",
    "WHERE Z_R_N > :Bind_RangePage_Low",
                    if ((!key.equals("Bind_RangePage_High")) &&
                        (!key.equals("Bind_RangePage_Low")))If you have other solution, please, tell me.
    Anatolii

  • How to add a total at the end of a characteristic column

    Hi All,
    There is a report where sales document number(0doc_number)is displayed in one of the columns,
    now There is a requirement where I need to add a total count of those doc numbers at the end of that column.
    I am not able to find a suitable way to do that.
    I tried exception aggregation for taking a count of doc numbers but that will be another column then while I need the total at the end of the same
    column which already exists.
    Please assist.
    Thanks,
    Dolly

    Hi Suman,
    A part of the report is :
    I need a count as 2 in above example at the bottom of sales document column.
    Dolly

  • Difference between cumulative balance and line items total in FS10N

    hi,
    when I am executing FS10n, I observed that the cumulative balance amount is not equal to line items total .  This is due to some amounts in previous years are varying from the line ltem totals in those periods of previous years.
    This is not happening with QA server only Prdn server is facing this problem.  Can anybody provide me a way to solve this..!?
    Regards,
    AJo
    I have checked the master data for the GL and the check box for line item display is selected. It has not been changed for years.
    Edited by: Anil Jonnalagadda on Oct 22, 2008 10:57 AM

    Hi Anil,
    The reason for the differences that you are viewing can be various. As the differences are found in the cummulative balance then it means that the differences might have occurred in previous fiscal years. The first stetp is to find when these differences were originated: You can run report SAPF190 (in se38) for previous fiscal years, and company code in question- This report should show the differences with message "Errors" in the log. If differences are found then you have to creeate a message and send it to SAP for further analysis and corrections.(only SAP experts can do this kind of corrections - component FI-GL-GL-X)
    Also bear in mind that if you did archiving in previous fiscal years then this would not be an error:
    If you already did archiving and secondary index deletion on this accounts with SAPF048I. So this explains why line items balance and GL summary balance differ ! There is no programm error.
    See consulting note 81489 which describes this issue:
    The balance of an account results from the balance of the open items. In
    connection with an archiving that has been carried out, the line item
    display - used with cleared items - must not therefore be interpreted as
    a balance display. For the balance display, there are separate
    correspond to the display balance of the open items from the line item
    display.
    Having archived and deleted secondary indexes ( with SAPF048I )
    for an account you can not use line item drill down as a balance
    display any more for a line item managed account.
    ( as not all line items are existing any more in table BSIS ! )
    The transactions meant to display the binding balances are  FS10N,
    FK10N and FD10N.
    They also give you the line items details, but only of those line
    items not yet deleted ( by SAPF048I ).
    kind regards,
    Oscar Diaz

  • FS10N balance not tie with FBl3N line item totals

    Hi
    I searched the forum for posting on FS10N and FBL3N incorrect balances and I did not any post appropriate for my issue. Hence I am posting my issue here.
    For a particular month, say 072010, FS10N GL balance does not tie with FBL3N line item totals. I am not sure why. In our case, we did not archive any line items and this is not related to year end carry forward. Year beginning GL balances look fine. We dont have any negative postings. Only few GL balances are off. We are using 4.7 version.
    Do you know why this inconsistency and how to rectify it? Is there any program which I run apart from Yead End carry forward?
    any ideas really appreciated.
    Thanks

    Hello
    We have already this trouble.
    To correct it you need to proceed like this (when NewGL is not activate, with new Gl there is one new programm)
    Without newGL
    - Block account to be posted (transaction FS00 Block for posting in the company view)
    - Delete open item, by using the programm RFSEPA03 (you need to adapt it by a copy because if you don't you can't run it), also this programm will unflag your account in the company view
    - Delete line item by the standrd program RFSEPA04
    - Create the line item by the standard program RFSEPA01
    - if this account is managed by open item, run the programm RFSEPA02 (you need to do the same adjustement of the RFSEPA03)
    With NewGL, there is something new. the program RFSEPA02 is linked with a new transaction and you don't have to adjust it FAGL_ACTIVATE_OP. The difference is when you create the open item, you have to define the default profit center and default value depending of the customizing of the leading ledger.
    BBest regards
    Philippe,
    Thanks for the rewards.

  • Decode function... total at the end

    Hi,
    I am using following query to show results...
    Select
    ACCOUNT_CONSULTANT,
    max((DECODE (SALES_STAGE, 'MEETING', Opportunities, NULL)
    )) MEETING,
    max((DECODE (SALES_STAGE, 'CLOSED', Opportunities, NULL)
    )) CLOSED,
    max((DECODE (SALES_STAGE, '', Opportunities, NULL)
    )) TBD
    From
    select
    ACCOUNT_CONSULTANT,
    SALES_STAGE,
    count(PROSPECT_NAME) as Opportunities
    from Table_A
    group by
    ACCOUNT_CONSULTANT,
    SALES_STAGE
    group by
    ACCOUNT_CONSULTANT
    order by
    ACCOUNT_CONSULTANT
    results appear as follows
    Acct_Conslt Meeting Closed TBD
    Sales RepA 6 1 11
    what I want is the total at the end, something like this
    Acct_Conslt Meeting Closed TBD Total
    Sales RepA 6 1 11 18
    Please advice

    Hi,
    Assuming your present query is getting the right results, you can make it a sub-query. Just copy the whole query (except the ORDER BY clause) into a WITH clause or an in-line view. Then, in the main query, you can reference the computed columns meeting, closed and tbd, like this:
    WITH     got_aggregates     AS
         Select
         ACCOUNT_CONSULTANT,
         max((DECODE (SALES_STAGE, 'MEETING', Opportunities, NULL)
         )) MEETING,
         max((DECODE (SALES_STAGE, 'CLOSED', Opportunities, NULL)
         )) CLOSED,
         max((DECODE (SALES_STAGE, '', Opportunities, NULL)
         )) TBD
         From
         select
         ACCOUNT_CONSULTANT,
         SALES_STAGE,
         count(PROSPECT_NAME) as Opportunities
         from Table_A
         group by
         ACCOUNT_CONSULTANT,
         SALES_STAGE
         group by
         ACCOUNT_CONSULTANT
    SELECT       a.*
    ,       meeting + closed + tbd          AS total
    FROM       got_aggregates   a
    ORDER BY  account_consultant
    ;If the components of total can be NULL, then you'd better compute total like this:
    ,       NVL (meeting, 0) +
           NVL (closed,     0) +
           NVL (tbd,     0)          AS totalEdited by: Frank Kulash on Jun 3, 2010 5:39 PM
    Fixed typo.

  • Suppressing a line if the sum of a value = 0 in a group footer

    How do i suppress a line if the sum of a value = 0 in a group footer
    I have tried this this formula in the section expert - Sum ({RM_INV.QUANTITY}) = 0
    will not work.

    Hi Dana, 
    The sum function needs to include the group you have your total in like: 
    Sum ({table.FIELD1}, {RM_INV.QUANTITY}) = 0
    {table.FIELD1} would be the field you are grouping on.  Your formula was summing the grand total for RM_INV.QUANTITY. 
    Thanks,
    Brian

  • Currency conversion - Line item total does not tally with account balance

    hi guys!
    we are currently going through currency conversion in Zimbabwe and we are at preparation stage. i have got 3 issues:
    1. while trying to run program RFSEPA02 the following error is appearing-
       -Line item total does not tally with account balance
    2. i might need to retrieve some FI documents whic were archived. how do i retrieve archived documents
    3. i might also be required to delete(if its an option) some records so tha line item total will tally with account balance

    put a break-point @
    if t_balance_items_hw[] <> t_balance_account_hw[] or
         t_balance_items_tw[] <> t_balance_account_tw[].
        perform dequeue_account.
        message e099.
    *   Summe der Einzelposten stimmt nicht mit Kontensaldo überein. ->
      endif.
    endform.                               " CHECK_ACCOUNT_BALANCE_2
    and debug y it is getting the error.
    Short text
    Switch On Open Item Management by Changing Master Record
    Description
    This program activates open item (OI) management for a G/L account and makes the necessary changes to documents already posted. These are then displayed afterwards as open items. It does not process the open items any further. In reversed documents especially, it does not reenter clearing data in the document.
    Requirements
    No items can already be archived from this account.
    Caution: Company policy must be in place to ensure that this does not happen.
    Some G/L accounts cannot be managed on an open item basis, especially G/L accounts that are used in account determination for automatic transactions (for example, accounts set up for transactions MVA or VVA, or accounts which are posted to using posting keys set up for account type M).
    Caution: Before making any changes, check that the G/L account can really be managed on an open item basis. If necessary, contact your SAP consultant.
    The account must be blocked from posting since any new documents posted at the same time as converting documents and postings for this account would not be entered.
    Output
    When using the list log, each document that was changed is listed. In addition, the total of the changed BSIS/BSAS entries and the total of the changed documents is listed.
    Regards
    Prabhu
    Message was edited by: Prabhu Peram

  • How to print a window (ex:total)only after end of main window in SAP Script

    How to print a window(ex: total) only after end of main window in SAP Script
    Thank you.

    Create a total window and place it after your main window, get the number of lines in your main window and place counter
    Ex,&SAPSCRIPT-COUNTER_1(+)&,
    IF SAPSCRIPT-COUNTER_1& EQ <number of lines in main window>
    **print total
    ENDIF.
    Regards,
    Sairam

Maybe you are looking for

  • GL Clearing

    Hello, We are in process of finalization of our books of accounts. We have different profit center in our company and we are doing inter profit clearing. Now for some gl overall balance is Zero. But If we see Profit center wise then there it shows ba

  • Itunes 10.5 won't back up for both ipad and iphone

    after uninstalling and installing several times itunes 10.5 won't back up any apple device and stallked on back up process for several hours and won't close untill ending process by task manager I'm using windows 7 I have iphone 4 and iphone 3gs and

  • What can I do if I receive a broken EE Power Bar from the store?

    I got an EE Power Bar yesterday (Sat 27) and it was only half full. I tried to charge it when I got home, but it won't light up the top two lights. Whats more, when I try and use the torch it takes more than two presses of the button to turn it on, a

  • Computer keeps freeing up and have to unload battery to restart it

    Hi, this is happening all the time now, my computer locks up/freezes, my start and wireless buttons flash and the only way to restart the computer is to unplug everything and pop out the battery. Any idea why this is happening, the computer is only 6

  • SP10 - multiple approver problem with CUP

    We have SP10 (patch 1) in our development system and cannot move forward to production because of a real show stopper.  I have currently reported this to SAP thru an OSS message (and it is in development) but would like to know if anyone else is havi