Today, I came across an interesting question regarding SALV OM Model. The query was regarding to show the count of displayed rows on the screen. Initially we think it is very easy – just use DESCRIBE
table, get count and show. But we need to also remember that users can use the Filters. Users can also start with saved ALV Layout which could have filters and that will change the number of rows to be displayed on the screen.
SAP doesn’t directly prepare the Data Table which it needs to display. It uses Data Provider (DP) to determine the display records from the Data table. This makes the task little bit harder to find out the Count of Displayed Rows.
What we need to do to achieve this:
We’ll catch the event AFTER_SALV_FUNCTION
. In the event handler, we need to determine the count. We need to apply the filter on each column of the temporary table. Here are the steps:
- Catch the event
AFTER_SALV_FUNCTION
- Get all Columns
- For each column, get the filter object
- Get the select option range
- Delete the records from table which are not in the range
- Get the number of rows to display
SAP doesn’t support the Dynamic WHERE
condition in DELETE
statement (till 701). So, we need to do some trick to get around this. We’ll generate a dynamic subroutine pool using GENERATE SUBROUTINE POOL
which will have form for each field. This subroutine would have only one DELETE
statement. We can also write CASE statement but we like Dynamic Programming 🙂
Code snippet to show Count of Displayed Rows:
PROGRAM zsalv_num_display_rows.
CLASS lcl_report DEFINITION.
PUBLIC SECTION.
* Final output table
TYPES: BEGIN OF ty_vbak,
vbeln TYPE vbak-vbeln,
erdat TYPE erdat,
auart TYPE auart,
kunnr TYPE kunnr,
netwr TYPE netwr,
END OF ty_vbak.
TYPES: ty_t_vbak TYPE STANDARD TABLE OF ty_vbak.
DATA: t_vbak TYPE STANDARD TABLE OF ty_vbak.
* ALV reference
DATA: o_alv TYPE REF TO cl_salv_table.
METHODS:
get_data, " Data selection
generate_output. " Generate Output
PRIVATE SECTION.
METHODS:
set_pf_status, " PF Status
set_filters, " Apply Filters
set_after_events " After Event
FOR EVENT after_salv_function OF cl_salv_events_table
IMPORTING
e_salv_function,
determine_displayed_rows, " Get number of rows
set_rows, " Set Number of rows
generate_report. " Generate Report
DATA: v_rows TYPE i. " Rows
DATA: v_prog TYPE string. " Dynamic Prog
ENDCLASS. "lcl_report DEFINITION
START-OF-SELECTION.
DATA: lo_report TYPE REF TO lcl_report.
CREATE OBJECT lo_report.
lo_report->get_data( ).
lo_report->generate_output( ).
*
CLASS lcl_report IMPLEMENTATION.
METHOD get_data.
* data selection
SELECT vbeln erdat auart kunnr netwr
INTO CORRESPONDING FIELDS OF TABLE t_vbak
FROM vbak
UP TO 100 ROWS
WHERE erdat GE '20090101'.
ENDMETHOD. "get_data
METHOD generate_output.
* New ALV instance
* We are calling the static Factory method which will give back
* the ALV object reference.
*
* exception class
DATA: lx_msg TYPE REF TO cx_salv_msg.
TRY.
cl_salv_table=>factory(
IMPORTING
r_salv_table = o_alv
CHANGING
t_table = t_vbak ).
CATCH cx_salv_msg INTO lx_msg.
ENDTRY.
*...Set default PF status
me->set_pf_status( ).
*...Set Filters
me->set_filters( ).
*...Events
DATA: lo_events TYPE REF TO cl_salv_events_table.
lo_events = o_alv->get_event( ).
SET HANDLER me->set_after_events FOR lo_events.
*.. Determine the number of displayed rows
me->determine_displayed_rows( ).
*...get display object
me->set_rows( ).
* Displaying the ALV
* Here we will call the DISPLAY method to get the output on the screen
o_alv->display( ).
ENDMETHOD. "generate_output
METHOD set_pf_status.
DATA: lo_functions TYPE REF TO cl_salv_functions_list.
lo_functions = me->o_alv->get_functions( ).
lo_functions->set_default( abap_true ).
ENDMETHOD. "set_pf_status
METHOD set_filters.
DATA: lo_filters TYPE REF TO cl_salv_filters.
lo_filters = o_alv->get_filters( ).
*
* Set the filter for the column ERDAT
* the filter criteria works exactly same as any
* RANGE or SELECT-OPTIONS works.
TRY.
CALL METHOD lo_filters->add_filter
EXPORTING
columnname = 'ERDAT'
sign = 'I'
option = 'EQ'
low = '20091214'
* high =
.
CATCH cx_salv_not_found . "#EC NO_HANDLER
CATCH cx_salv_data_error . "#EC NO_HANDLER
CATCH cx_salv_existing . "#EC NO_HANDLER
ENDTRY.
*
ENDMETHOD. "set_filters
METHOD determine_displayed_rows.
* 1. Get All the Columns
* 2. For Each column, get the filter
* 2.1 Get the filter value for each column
* 2.2 Call the subroutine to delete the records
* which are not in range
* 2.3 Determine the number of rows
DATA: lo_filters TYPE REF TO cl_salv_filters.
DATA: lo_filter TYPE REF TO cl_salv_filter.
DATA: lv_filter_val TYPE salv_t_selopt_ref.
DATA: lo_selopt TYPE REF TO cl_salv_selopt.
DATA: lr_range TYPE RANGE OF char80.
DATA: lwa_range LIKE LINE OF lr_range.
DATA: lt_data TYPE ty_t_vbak.
DATA: lo_cols TYPE REF TO cl_salv_columns.
DATA: lo_cols_tab TYPE salv_t_column_ref.
DATA: lo_col LIKE LINE OF lo_cols_tab.
data: lf_form type string.
lt_data = me->t_vbak.
* Columns and Filters
lo_cols = o_alv->get_columns( ).
lo_cols_tab = lo_cols->get( ).
lo_filters = o_alv->get_filters( ).
* dynamic subroutine pool
me->generate_report( ).
LOOP AT lo_cols_tab INTO lo_col.
CLEAR: lr_range.
TRY.
* Get Filter for the column. No filter will raise exception
lo_filter = lo_filters->get_filter( lo_col-columnname ).
lv_filter_val = lo_filter->get( ).
LOOP AT lv_filter_val INTO lo_selopt.
lwa_range-sign = lo_selopt->get_sign( ).
lwa_range-option = lo_selopt->get_option( ).
lwa_range-low = lo_selopt->get_low( ).
lwa_range-high = lo_selopt->get_high( ).
APPEND lwa_range TO lr_range.
CLEAR lwa_range.
ENDLOOP.
* Dynamic Subrotine call to overcome the Restriction
* of dynamic WHERE clause
CONCATENATE 'DEL_' lo_col-columnname into lf_form.
PERFORM (lf_form) IN PROGRAM (v_prog) IF FOUND
using lr_range
CHANGING lt_data.
* No data, exist
IF lt_data IS INITIAL.
EXIT.
ENDIF.
CATCH cx_salv_not_found.
ENDTRY.
ENDLOOP.
* recount the rows
v_rows = LINES( lt_data ).
ENDMETHOD. "determine_displayed_rows
METHOD generate_report.
DATA:
tab TYPE STANDARD TABLE OF string,
mess TYPE string,
sid TYPE string,
lf_string TYPE string,
lf_form TYPE string.
CHECK v_prog IS INITIAL.
APPEND 'PROGRAM subpool.' TO tab.
DATA: lo_cols TYPE REF TO cl_salv_columns.
DATA: lo_cols_tab TYPE salv_t_column_ref.
DATA: lo_col LIKE LINE OF lo_cols_tab.
lo_cols = o_alv->get_columns( ).
lo_cols_tab = lo_cols->get( ).
APPEND 'TYPES: ty_range type range of char80.' TO tab.
APPEND 'TYPES: BEGIN OF ty_vbak,' to tab.
APPEND 'vbeln TYPE vbak-vbeln,' to tab.
APPEND 'erdat TYPE erdat,' to tab.
APPEND 'auart TYPE auart,' to tab.
APPEND 'kunnr TYPE kunnr,' to tab.
APPEND 'netwr TYPE netwr,' to tab.
APPEND 'END OF ty_vbak.' to tab.
APPEND 'TYPES: ty_t_vbak TYPE STANDARD TABLE OF ty_vbak.' to tab.
LOOP AT lo_cols_tab INTO lo_col.
CONCATENATE 'DEL_' lo_col-columnname INTO lf_form.
CONCATENATE 'FORM ' lf_form
'using lr_range type ty_range changing ct_data type ty_t_vbak.'
INTO lf_string SEPARATED BY space.
APPEND lf_string TO tab.
CLEAR lf_string.
CONCATENATE ' DELETE ct_Data where not' lo_col-columnname
'in lr_range.' INTO lf_string SEPARATED BY space.
APPEND lf_string TO tab.
CLEAR lf_string.
APPEND 'ENDFORM. ' TO tab.
ENDLOOP.
v_prog = ''.
GENERATE SUBROUTINE POOL tab NAME v_prog
MESSAGE mess
SHORTDUMP-ID sid.
IF sy-subrc = 0.
ELSEIF sy-subrc = 4.
MESSAGE mess TYPE 'I'.
ELSEIF sy-subrc = 8.
MESSAGE sid TYPE 'I'.
ENDIF.
ENDMETHOD. "generate_report
METHOD set_after_events.
check e_salv_function eq '&ILT' " Apply Filter
or e_salv_function eq '&ILD'. " Delete Filter
me->determine_displayed_rows( ).
me->set_rows( ).
ENDMETHOD. "set_after_evnets
method set_rows.
* get display object
DATA: lo_display TYPE REF TO cl_salv_display_settings.
DATA: lv_string TYPE lvc_title.
lo_display = o_alv->get_display_settings( ).
lv_string = v_rows.
CONDENSE lv_string.
CONCATENATE 'Number of Displayed Rows: ' lv_string into
lv_string SEPARATED BY space.
lo_display->set_list_header( lv_string ).
ENDMETHOD.
ENDCLASS. "lcl_report IMPLEMENTATION
The output is something like this:
- Without any record
- With 3 records
- With all records
Share you thoughts on this via comments ..!
Thank you for this!
the only thing I wonder about is the statement “but we like Dynamic Programming” and then in the code lines I see ‘hard-coded’ field names as in “APPEND ‘vbeln TYPE vbak-vbeln,’ to tab.”. Ok maybe you forgot to remove this from test version.
A bit confusing is the naming lr_ for a range table as lr_ is frequently used for local ref to data, but…
I think, GENERATE SUBROUTINE POOL can be avoided by looping at the display table, inside the loop loop over filtered columns until you found one that’s column matches the filter conditions, count line as filtered and go to next one.
symbolic:
loop at diaplay table assigning .
loop at filter table assigning .
assign field -fieldname of structure to .
check IN ->range.
add 1 to count_filtered.
exit.
endloop.
endloop.
That may be even faster because filters must be applied/checkd only until you find a filtered value.
Regards
Clemens
Hello Clemens,
Glad to see your comment.. Yes you are right, I didn’t pay very much attention while declaring the internal table for the subroutine pool. I’ll fix it.
Probably LOOP over LOOP could be faster than Generate subroutine pool, I need to try that out.
For code formatting: we are working on something which can format the code.
Regards,
Naimesh Patel
sorry, no code tags or other formatting means visible here.
Hi Naimesh, Clemens
Working with both of your inputs I’ve worked the solution as follows, it uses the original proposal as above to determine the filters and then the LOOP within LOOP to determine the number of rows displayed in the TopOfList. Rather than using the generate subroutine the class cl_abap_typedescr is used to determine the internal structure and hence the field position in the data structure of the filters. Caching the filters allows for efficient processing of the filters, only processing the filters that are effective at that time.
One thing that I’ve had to work around is the triggering of the event to refresh the top of list when a filter is applied. I’ve had to add a button to the report and trigger the top of page method to refresh the row count displayed.
DATA: lv_text TYPE string,
lv_count(5) TYPE c,
lt_listoutput_cpy type ty_listoutput_tab.
DATA: lr_header TYPE REF TO cl_salv_form_header_info.
DATA: lo_cols TYPE REF TO cl_salv_columns.
DATA: lo_cols_tab TYPE salv_t_column_ref.
DATA: lo_col LIKE LINE OF lo_cols_tab.
DATA: lo_filters TYPE REF TO cl_salv_filters.
DATA: lo_filter TYPE REF TO cl_salv_filter.
DATA: lv_filter_val TYPE salv_t_selopt_ref.
DATA: lo_selopt TYPE REF TO cl_salv_selopt.
DATA: lr_range TYPE RANGE OF char80.
DATA: lwa_range LIKE LINE OF lr_range.
data: lv_index type sytabix.
types: BEGIN OF ty_filters,
index type sytabix,
fname type NAME_KOMP,
range LIKE lr_range,
end of ty_filters.
data: lt_filters type sorted TABLE OF ty_filters WITH NON-UNIQUE key index,
ls_filters type ty_filters.
FIELD-SYMBOLS: like line of gt_listoutput,
TYPE ANY.
DATA : lt_comp_details TYPE abap_compdescr_tab,
ls_comp_details TYPE abap_compdescr.
DATA : ref_descr TYPE REF TO cl_abap_structdescr.
* Get the internal table definition for tha list structure as passed to the ALV
ref_descr ?= cl_abap_typedescr=>describe_by_name( ‘TY_LISTOUTPUT’ ).
lt_comp_details[] = ref_descr->components[].
* Make a local copy for calculation of the display rows
lt_listoutput_cpy[] = gt_listoutput[].
try.
* Columns and Filters
lo_cols = gr_table->get_columns( ).
lo_cols_tab = lo_cols->get( ).
lo_filters = gr_table->get_filters( ).
loop at lt_listoutput_cpy ASSIGNING .
at first.
loop at lt_comp_details into ls_comp_details.
CLEAR: lr_range, lr_range[].
lv_index = sy-tabix.
TRY.
* Get Filter for the column. No filter will raise exception
lo_filter = lo_filters->get_filter( ls_comp_details-name ).
lv_filter_val = lo_filter->get( ). “exception raised if filter not existing.
LOOP AT lv_filter_val INTO lo_selopt.
lwa_range-sign = lo_selopt->get_sign( ).
lwa_range-option = lo_selopt->get_option( ).
lwa_range-low = lo_selopt->get_low( ).
lwa_range-high = lo_selopt->get_high( ).
ls_filters-fname = ls_comp_details-name.
ls_filters-index = lv_index.
APPEND lwa_range to lr_range.
ls_filters-range = lr_range.
insert ls_filters into table lt_filters.
CLEAR: lwa_range.
ENDLOOP.
CATCH cx_salv_not_found.
endtry.
ENDLOOP.
endat.
loop at lt_filters into ls_filters.
assign COMPONENT ls_filters-index of STRUCTURE to .
if NOT in ls_filters-range.
delete lt_listoutput_cpy. ” Delete he row if it would not be displated in a filter
exit. ” At least onefilter applicable
endif.
endloop.
endloop.
catch CX_SY_REF_IS_INITIAL.
endtry.
DESCRIBE TABLE lt_listoutput_cpy lines lv_count.
MOVE: text-m01 TO lv_text.
CONDENSE lv_count NO-GAPS.
REPLACE ALL OCCURRENCES OF ‘&’
IN lv_text
WITH lv_count.
CREATE OBJECT lr_header
EXPORTING
text = lv_text.
gr_table->set_top_of_list( lr_header ).
Hello Alan,
I am glad that the previous discussion between myself & Clemens helped you solve your problem efficiently.
When I tried the first time, I tried using the HEADER, but SALV only sets the header once and doesn’t allow us to refresh unless we try to explicitly refresh it. Due to this fact, I used the title to display number of records.
Regards,
Naimesh Patel
Another solution for this is to use the ‘count column’ field of the ALV class. If you combine this with the setting that totals must be shown above the data then the result is almost the same with much lesser code.
Use method SET_COUNT_COLUMN of class CL_SALV_COLUMNS_LIST to identify the count column, the colum nitself can be left empty.