Skip to Content
Technical Articles
Author's profile photo Bärbel Winkler

Adapting CODE_SCANNER to fit our needs

At a guess, many of you will have had reasons to use the SAP standard transaction CODE_SCANNER to search through ABAP code in order to find a specified string. I hadn’t known about this old transaction until happening upon the blog post by arghadip kar in 2021 and have been using it regularly since then. It’s a great way to quickly search through all ABAP-code in Z* packages (just not in enhancements unfortunately).

We are currently in the process to identify Z-code which is still using checks on SY-UNAME instead of proper authority-checks or other “sub-optimal” checking logic based on the content of SY-UNAME. We want to use the results to show a warning message whenever impacted ABAP code is opened, also asking to get it fixed as quickly as possible. Our initial idea was to simply run CODE_SCANNER, dump the results into a spreadsheet and then fill a Z-table with the program names in order to trigger the message via available exits in SE38 and SE37 (yes, we are still mostly working in the GUI and not Eclipse).

Unfortunately, the CODE_SCANNER results were not quite up to the task as they included a lot of false hits, where SY-UNAME is for example used in field assignements, a perfectly legitimate use of course:

Many hits were also in Includes belonging to a function module. There, it’s rather unlikely that the code will be directly accessed via SE38 based on the include name and much more likely to go via SE37 and the function module name. I thought that it would also be nice to show at least one of the master programs an include was used in and to provide the short descriptions for the program and/or function module as additional information.

Long story short, I suggested going against our coding guidelines – which I’m responsible for! – and to create a Z-copy of the CODE_SCANNER program in order to make it better fit our needs. After that was approved, I went to work and will use the rest of the blog post to highlight some of the logic I added to the copied code.

Additional fields for scan results

TYPES: BEGIN OF t_str_lines,
         devclass LIKE tadir-devclass,
         progname LIKE rs38m-programm,
         inakt    LIKE zbc_inaktiv-inakt,                 "001+
         linno    LIKE trans_err-line, "sy-tabix,
         line     LIKE abapsource-line,
         pgmid    LIKE tadir-pgmid,                       "001+
         object   LIKE tadir-object,                      "001+
         master   LIKE d010inc-master,                    "001+
         repti    LIKE rs38m-repti,                       "001+
         funcname LIKE tfdir-funcname,                    "001+
         funcdesc LIKE tftit-stext,                       "001+
         sysid    LIKE sy-sysid,                          "001+
       END   OF t_str_lines.

DATA: BEGIN OF g_tab_lines OCCURS 0,
        devclass LIKE tadir-devclass,
        progname LIKE rs38m-programm,
        inakt    LIKE zbc_inaktiv-inakt,                 "001+
        linno    LIKE trans_err-line,  "sy-tabix,
        line     LIKE abapsource-line,
        pgmid    LIKE tadir-pgmid,                       "001+
        object   LIKE tadir-object,                      "001+
        master   LIKE d010inc-master,                    "001+
        repti    LIKE rs38m-repti,                       "001+
        funcname LIKE tfdir-funcname,                    "001+
        funcdesc LIKE tftit-stext,                       "001+
        sysid    LIKE sy-sysid,                          "001+
      END   OF g_tab_lines.

*                                                         "001 Begin
TYPES: BEGIN OF ty_objects,
         mandt      TYPE mandt,
         obj_name   TYPE sobj_name,
         field      TYPE z_field,
         credat     TYPE creationdt,
         created_by TYPE uname,
         ignore_obj TYPE check_1,
         comments   TYPE z_comment,
       END OF   ty_objects.

DATA:  g_tab_objects TYPE SORTED TABLE OF ty_objects
                          WITH UNIQUE KEY obj_name field.
*                                                         "001 End

 

Filling the fields – logic called after scan complete and before results are displayed

  "**************end package structure explosion
  "Process packages
  l_tabix = 0.
  LOOP AT l_tab_tadir INTO l_str_tadir.
    l_tabix = l_tabix + 1.
    l_devclass = l_str_tadir-obj_name.
    PERFORM scan_devc USING l_devclass l_tabix l_cnt p_lrng.
  ENDLOOP.

  "Process local package $TMP
  IF l_flg_process_tmp = con_true.
    l_tabix = l_tabix + 1.
    PERFORM scan_devc USING c_devc_tmp l_tabix l_cnt p_lrng.
  ENDIF.

  "Get addition data from D010INC for master program   "001+
  "and TFDIR for function module
  PERFORM get_additional_data.

  "If requested refresh table ZBC_OBJECTS_WARN         "001+
  IF p_del EQ abap_true OR
     p_ins EQ abap_true.
    PERFORM update_objects_table.
  ENDIF.

  "Display scan result data
  PERFORM scan_result_display.

ENDFORM.                    "process_devc
*&---------------------------------------------------------------------*
*&      Form  get_additional_data
*&---------------------------------------------------------------------*
FORM get_additional_data.

  "Determine distinct programs/includes
  DATA(distinct_prognames) = g_tab_lines[].
  SORT distinct_prognames BY progname.
  DELETE ADJACENT DUPLICATES FROM distinct_prognames COMPARING progname.

  IF distinct_prognames[] IS NOT INITIAL.

    SELECT include, master
      FROM d010inc
      INTO TABLE @DATA(master_programs)
       FOR ALL ENTRIES IN @distinct_prognames
     WHERE include EQ @distinct_prognames-progname.

     DATA(cnt_master_programs) = lines( master_programs ).
     SORT master_programs BY include master.

    SELECT repid, inakt
      FROM zbc_inaktiv
      INTO TABLE @DATA(inactive_programs)
       FOR ALL ENTRIES IN @distinct_prognames
     WHERE repid EQ @distinct_prognames-progname.

     DATA(cnt_inactive_programs) = lines( inactive_programs ).
     SORT inactive_programs BY repid.


    IF cnt_master_programs GT 0 OR cnt_inactive_programs GT 0.

      LOOP AT g_tab_lines[] INTO DATA(line).

        READ TABLE master_programs INTO DATA(master_program)
                                    WITH KEY include = line-progname
                                      BINARY SEARCH.
        IF sy-subrc EQ 0.
          line-master = master_program-master.
          "Determine title of master program
          PERFORM determine_program_title USING line-master
                                       CHANGING line-repti.
          MODIFY g_tab_lines[] FROM line TRANSPORTING master repti.
        ELSE.
          PERFORM determine_program_title USING line-progname
                                       CHANGING line-repti.
          MODIFY g_tab_lines[] FROM line TRANSPORTING repti.
        ENDIF.

        READ TABLE inactive_programs INTO DATA(inactive_program)
                                      WITH KEY repid = line-progname
                                        BINARY SEARCH.
        IF sy-subrc EQ 0.
          line-inakt = inactive_program-inakt.
        ELSE.
          clear line-inakt.
        ENDIF.
        MODIFY g_tab_lines[] FROM line TRANSPORTING inakt.

      ENDLOOP.

    ENDIF.

  ENDIF.

  "Determine distinct includes to determine function modules
  DATA(distinct_includes) = g_tab_lines[].
  SORT distinct_includes BY progname.
  DELETE distinct_includes WHERE master EQ space.
  DELETE ADJACENT DUPLICATES FROM distinct_includes COMPARING progname.

  IF distinct_includes[] IS NOT INITIAL.

    SELECT d~pname, d~include, d~funcname, t~stext AS funcdesc
      FROM tfdir AS d
      LEFT OUTER JOIN tftit AS t
                   ON d~funcname EQ t~funcname
                  AND ( t~spras EQ 'D' OR
                        t~spras EQ 'E')
      INTO TABLE @DATA(function_modules)
       FOR ALL ENTRIES IN @distinct_includes
     WHERE d~pname EQ @distinct_includes-master.

    IF sy-subrc EQ 0.

      SORT function_modules BY pname include.

      LOOP AT g_tab_lines[] INTO DATA(line_for_fm).

        DATA(num_of_char) = numofchar( line_for_fm-progname ).
        DATA(pos)         = num_of_char - 2.
        DATA(include_no)  = line_for_fm-progname+pos(2).

        READ TABLE function_modules INTO DATA(function_module)
                                    WITH KEY pname = line_for_fm-master
                                             include = include_no
                                      BINARY SEARCH.
        IF sy-subrc EQ 0.
          line_for_fm-funcname = function_module-funcname.
          line_for_fm-funcdesc = function_module-funcdesc.
          MODIFY g_tab_lines[] FROM line_for_fm
                               TRANSPORTING funcname funcdesc.
        ENDIF.

      ENDLOOP.

    ENDIF.

  ENDIF.

  g_cnt_hits = lines( g_tab_lines ).

ENDFORM.

 

Add program title

*&---------------------------------------------------------------------*
*&      Form  determine_program_title
*&---------------------------------------------------------------------*
FORM determine_program_title USING u_progname TYPE programm
                          CHANGING c_repti    LIKE rs38m-repti.

  TYPES:  ty_text    LIKE textpool.
  DATA:   prog_texts TYPE ty_text OCCURS 0 WITH HEADER LINE.

  CLEAR:  prog_texts,
          c_repti.
  REFRESH prog_texts.

  READ TEXTPOOL u_progname INTO prog_texts LANGUAGE 'E'.

  IF sy-subrc EQ 0.
    READ TABLE prog_texts WITH KEY id = 'R'.
    IF sy-subrc EQ 0.
    ELSE.
      prog_texts-entry = ' '.
    ENDIF.

  ELSE.
    "2nd try with German
    READ TEXTPOOL u_progname INTO prog_texts LANGUAGE 'D'.

    IF sy-subrc EQ 0.
      READ TABLE prog_texts WITH KEY id = 'R'.
      IF sy-subrc EQ 0.
      ELSE.
        prog_texts-entry = ' '.
      ENDIF.

    ENDIF.

  ENDIF.

  c_repti = prog_texts-entry.

ENDFORM.

Eliminate more false hits

Switched from three paramaters on the selection screen to one select-option:

SELECTION-SCREEN: BEGIN OF BLOCK b WITH FRAME TITLE TEXT-002.
SELECT-OPTIONS: s_excl FOR zmmllakte_text-text NO INTERVALS.  "001+
SELECTION-SCREEN:   SKIP.
PARAMETERS:         p_lrng(2)    TYPE n OBLIGATORY DEFAULT '01'.
SELECTION-SCREEN:   SKIP.
PARAMETERS: p_excomm AS CHECKBOX DEFAULT con_false,
            p_nohits AS CHECKBOX DEFAULT con_false,
            p_edit   AS CHECKBOX DEFAULT space.
SELECTION-SCREEN: END   OF BLOCK b.

 

Adapted scan-logic to make use of new select-option:

*&---------------------------------------------------------------------*
*&      Form  scan_prog
*&---------------------------------------------------------------------*
FORM scan_prog USING    i_devclass   TYPE devclass
                        i_objname    TYPE sobj_name
                        i_cnt_line   TYPE n
                        i_pgmid      TYPE tadir-pgmid
                        i_object     TYPE tadir-object
               CHANGING i_tab_source TYPE t_tab_long_lines.
  DATA: l_str_source TYPE t_abapsource_long,
*        l_line         TYPE sytabix,
*        l_out_progname TYPE xfeld,   "EC NEEDED
        l_flg_found  TYPE xfeld,
        l_flg_write  TYPE xfeld,
        l_cnt_line   TYPE i,
*        l_modulo       TYPE i,
        l_str_lines  TYPE t_str_lines.

* Initialization
*  CLEAR l_out_progname.
  CLEAR l_flg_found.
  g_line_object = i_objname.
  l_cnt_line = 1000.

  CLEAR l_str_lines.
  l_str_lines-devclass = i_devclass.
  l_str_lines-progname = i_objname.
  l_str_lines-object   = i_object.                        "001+
  l_str_lines-pgmid    = i_pgmid.                         "001+
  l_str_lines-sysid    = sy-sysid.                        "001+

  "Search source for selection criteria
  LOOP AT i_tab_source INTO l_str_source.
    g_line_number = sy-tabix.
    CLEAR l_flg_write.
    IF l_str_source-line CS p_strg1 AND
       ( p_strg2 IS INITIAL         OR
         l_str_source-line CS p_strg2 ).
*                                                         "001 Begin
      "Search string is found in line of code
      "Check if none of the search terms to exclude is found. This is
      "to avoid too many false hits and was changed from several
      "parameter fields to a select-option so that it can be easily
      "maintained in a variant regardless of how many terms should
      "be excluded.
      DATA(cnt_excl) = lines( s_excl ).
      LOOP AT s_excl INTO DATA(excluded).
        IF NOT l_str_source-line CS excluded-low.
          cnt_excl = cnt_excl - 1.
        ENDIF.
      ENDLOOP.
      IF cnt_excl LE 0 AND
         ( p_excomm IS INITIAL OR
           l_str_source-line(1) <> '*' ).
        l_flg_write = con_true.
        l_cnt_line  = 0.
      ENDIF.
*                                                         "001 End
    ENDIF.

    IF l_flg_write = con_true OR l_cnt_line < i_cnt_line.
      l_cnt_line  = l_cnt_line + 1.
      l_flg_found = con_true.
      l_str_lines-linno = g_line_number.
      l_str_lines-line  = l_str_source-line.
      APPEND l_str_lines TO g_tab_lines.
    ENDIF.

  ENDLOOP.

* No hits found
  IF p_nohits = con_true AND l_flg_found IS INITIAL.
    l_str_lines-linno = 1.
    l_str_lines-line  = 'No Hits'(014).
    APPEND l_str_lines TO g_tab_lines.
  ENDIF.

ENDFORM.                    " scan_prog

Saving the scan results in a Z-table

While working on the logic to add the fields, we decided to also add an option to the program to directly store the scan results in a new Z-table. That would spare us the tedious task to get and “massage” the results in a spreadsheet and then – with another program – upload them into the table.

New definition:

*                                                         "001 Begin
TYPES: BEGIN OF ty_objects,
         mandt      TYPE mandt,
         obj_name   TYPE sobj_name,
         field      TYPE z_field,
         credat     TYPE creationdt,
         created_by TYPE uname,
         ignore_obj TYPE check_1,
         comments   TYPE z_comment,
       END OF   ty_objects.

DATA:  g_tab_objects TYPE SORTED TABLE OF ty_objects
                          WITH UNIQUE KEY obj_name field.
*                                                         "001 End

 

New block on the selection-screen:

SELECTION-SCREEN BEGIN OF BLOCK d WITH FRAME TITLE TEXT-s04.
PARAMETERS: p_del   AS CHECKBOX DEFAULT con_false MODIF ID tab,
            p_ins   AS CHECKBOX DEFAULT con_false MODIF ID tab,
            p_field TYPE z_field                  MODIF ID tab.
SELECTION-SCREEN END OF BLOCK d.

 

Refresh Z-Table:

*&---------------------------------------------------------------------*
*&      Form  update_objects_table
*&---------------------------------------------------------------------*
FORM update_objects_table.

  DATA answer(1) TYPE c.

  "Only proceed if no restrictions on objectname is entered and a term
  "is specified in P_FIELD
  IF s_rest[] IS INITIAL AND
     p_field  IS NOT INITIAL.

    IF sy-batch EQ abap_false.
      CALL FUNCTION 'POPUP_TO_CONFIRM'
        EXPORTING
          text_question = 'Update table ZBC_OBJECTS_WARN?'(a01)
        IMPORTING
          answer        = answer.
      "Only continue if update confirmed
      CHECK answer EQ '1'.
    ENDIF.

    LOOP AT g_tab_lines INTO DATA(line).

      IF line_exists( g_tab_objects[ obj_name = line-progname
                                     field    = p_field ] ).
        "Don't do anything if line already exists
      ELSE.
        "Add progname to internal table of objects
        g_tab_objects[] = VALUE #( BASE g_tab_objects
                                   ( mandt      = sy-mandt
                                     obj_name   = line-progname
                                     field      = p_field
                                     credat     = sy-datum
                                     created_by = sy-uname ) ).
      ENDIF.

      IF line-master IS NOT INITIAL.

        IF line_exists( g_tab_objects[ obj_name = line-master
                                       field    = p_field ] ).
          "Don't do anything if line already exists
        ELSE.
          "Add progname to internal table of objects
          g_tab_objects[] = VALUE #( BASE g_tab_objects
                                     ( mandt      = sy-mandt
                                       obj_name   = line-master
                                       field      = p_field
                                       credat     = sy-datum
                                       created_by = sy-uname ) ).
        ENDIF.
      ENDIF.

      IF line-funcname IS NOT INITIAL.

        IF line_exists( g_tab_objects[ obj_name = line-funcname
                                       field    = p_field ] ).
          "Don't do anything if line already exists
        ELSE.
          "Add progname to internal table of objects
          g_tab_objects[] = VALUE #( BASE g_tab_objects
                                     ( mandt      = sy-mandt
                                       obj_name   = line-funcname
                                       field      = p_field
                                       credat     = sy-datum
                                       created_by = sy-uname ) ).
        ENDIF.
      ENDIF.

    ENDLOOP.

    IF p_del EQ abap_true.

      DELETE FROM zbc_objects_warn
       WHERE field EQ p_field
         AND ignore_obj EQ space.

      g_cnt_del = sy-dbcnt.

      IF sy-subrc EQ 0.
        MESSAGE i000(38) WITH sy-dbcnt
                        ' entries deleted from ZBC_OBJECTS_WARN'(a02).
      ENDIF.

    ENDIF.

    IF p_ins EQ abap_true.

      INSERT zbc_objects_warn
        FROM TABLE g_tab_objects ACCEPTING DUPLICATE KEYS.

      g_cnt_ins = sy-dbcnt.

      IF sy-subrc EQ 0.
        MESSAGE i000(38) WITH sy-dbcnt
                        ' entries inserted into ZBC_OBJECTS_WARN'(a03).
      ENDIF.

    ENDIF.

  ENDIF.

ENDFORM.

We plan to set up a job refreshing the Z-table in each relevant system once per month. Over time – as code gets fixed – we hope to see a decline in table entries, but only time will tell how effective this will be!

The code I now have is working well on a NW750-system with SP25 and EHP8 and scans our many Z-objects in about 5 minutes.

Additional musings

I was thinking about utilizing REGEX to more easily eliminate false hits. Right now, only exact hits are excluded, so I’d theoretically have to add multiple entries in the select-options to find all versions for “field_a = sy-uname” regardless of the number of spaces there are before and after “=”. I briefly tried but didn’t get it to work and abandoned the effort in the interest of time. So, if anybody has suggestions of how to improve the exclusion logic with the help of – simple – REGEX – I’m all ears!

Assigned Tags

      4 Comments
      You must be Logged on to comment or reply to a post.
      Author's profile photo Michał Badura
      Michał Badura

      Hi Bärbel Winkler, thank You for Your blog post! I always enjoy Your writings and Your approch to getting things done. 🙂

       

      If You'd like to search for a regex pattern, to also find lines where multiple spaces are used, You could change the line, where You're comparing the code line to parameters p_strg1 and p_strg2, to something like this:

      IF matches( val = l_str_source-line  regex = p_strg1  case = abap_false ) AND
         ( p_strg2 IS INITIAL OR matches( val = l_str_source-line  regex = p_strg2  case = abap_false ) ).

      and populate them on selection-screen with something like this:

      sy-uname\s+=\s+'(?:[^']|''){1,12}'

      Here I'm looking for this pattern:

      • fix: sy-uname
      • any number (greater than 0) of white signs
      • fix: =
      • any number (greater than 0) of white signs
      • fix: '
      • 1 to 12 signs which are no ' or escaped ' (double '') - this is needed, because ' could be part of the user name
      • fix: '

      But how do You search for this lines anyway? It's not sufficient to look for text field literals, You'd also have to search for text string literals:

      sy-uname\s+=\s+`(?:[^`|``){1,12}`

      unfortunately, I don't know any good way to combine the two conditions, except for this:

      sy-uname\s+=\s+'(?:[^']|''){1,12}'|sy-uname\s+=\s+`(?:[^`|``){1,12}`

      and, I don't know, whether it can be recognized, but yes, I'm still using the meanwhile obsolete POSIX standard.

      But even this wouldn't be sufficient - what about string templates?

      IF sy-uname = |USER_\|NAME|.

      What about the inverted order?

      IF 'USER_NAME' = sy-uname.

      Or putting sy-uname in the string template?

      IF |{ sy-uname }| = 'USER_NAME'. "(*)

      Using cl_abap_syst (which You should, according to SAP Press book Besseres ABAP)?

      IF cl_abap_syst=>get_user_name( ) = 'USER_NAME'.

      Or just comparing it with a variable, expression, method call, ... ?

      IF sy-uname = user_name.
      IF sy-uname SWITCH #( flag WHEN abap_true THEN user_name1 ELSE user_name2 ).
      DATA(resultCOND #WHEN sy-uname = user_name THEN abap_true ELSE abap_false ). "(*)
      IF sy-uname lcl=>get_user_name).

      Concatenations?

      IF sy-uname = 'USER_' && 'NAME'.
      IF sy-uname = 'USER_' & 'NAME'.

       

      On the other hand - there is already a check, which is looking for comparisions on sy-uname, which covers all of the above cases, except those with (*) in comment. (One should also check other variants, like ELSEIF, CASE and so on).

      You can find it in extended check (SLIN) or use it with Your ATC / Code Inspector: Syntax Check/Generation --> Extended Program Check (SLIN) --> Selected single checks --> Superfluous Statements.

      Why is it hidden there, it is indeed a superfluous statement, but not in technical meaning? Anyway, this check reports also other superfluous statements, so perhaps You'd get more hits. Two examples:

      • executable statements after RETURN
      • uncalled procedures

      But maybe You could copy the logic for this check to Your own Code Inspector check class, and sort the other hits out? By the way, I think Your guidelines are very rigoros - You're making a copy of SAP standard not for the daily business of Your company, but to implement a tool for Your developers. A tool, which doesn't have to be transported from Your development system to the following systems. In other words: what happens in development, stays in development. 😉

       

      There is also a check from akquinet enterprise solutions (/SAST/ namespace) for looking up sy-uname comparisions, but I don't know what are the pros and cons compared to SAP standard.

       

      Do You also know the other code scanner - report RS_ABAP_SOURCE_SCAN?

       

      Greetings!

      Michał

      Author's profile photo Bärbel Winkler
      Bärbel Winkler
      Blog Post Author

      Michał Badura

      Hi Michał,

      thanks for your feedback and detailed information! I'll have to explore the REGEX option when time allows. And also thanks a lot for the tip with SLIN! I may just be adding that one particular and "interestingly" named check for "superfluous statements" to our default check.

      Cheers

      Bärbel

      Author's profile photo Edo von Glan
      Edo von Glan

      Hi Bärbel,

      we also use the alternative, report RS_ABAP_SOURCE_SCAN,

      and have extended it via modifications as described here: https://blogs.sap.com/2018/09/19/code-search-in-modifications-and-enhancements/.

      (Some Russian developers also made that available as a standalone Z report)

      Once you have a HANA database, the Eclipse-based full text search has the advantage of being blindingly fast, but the search algorithm has some quirks.

      Greetings,

      Edo

      Author's profile photo Bärbel Winkler
      Bärbel Winkler
      Blog Post Author

      Edo von Glan

      Hi Edo,

      thanks for your feedback! Yes, I'm using RS_ABAP_SOURCE_SCAN as well but for what I wanted to do, CODE_SCANNER was the easier basis, i.e. just a fairly simple report program. I haven't tried Eclipse-based full text search yet as we only have DEV-systems connected but I wanted to execute the enhanced scan in TEST and PROD as well. Oh, and Eclipse-based search wouldn't work with a regular batch job to refresh the Z-table either.

      We have been on a HANA-DB for a few years and I had noticed that either scanner has been much faster running than before, when I wouldn't "dare" run a scan of all code in Z* packages.

      Cheers

      Bärbel