Friday 28 April 2023

The power of dynamism and data reference in SAP ABAP

Dynamic structures and data references have been well-documented and written for more than a decade already and it’s one of the most flexible (albeit, also the most dangerous security-wise) components of SAP development. I would not be re-engineering the wheel but presenting it in different layers of a dynamic structure.

In addition, I wouldn’t include the inline declarations yet as it defeats the purpose of dynamism in the context of learning.

We’ll try to peel the onion and go from the simplest to the more complex structures using dynamic and data references. What I would try is to best explain dynamic programming to someone who is new to ABAP programming as this is a huge topic and learning it early helps develop a good framework mindset.

For those who want to create tools in the future, you must have a strong base in dynamic programming.

Disclaimer: The examples below are just simple representations and not actual codes in the system. 

Level 1. Dynamic variable. Access any variable in SAP ABAP


Strong Warning: This is highly inadvisable. This is also dangerous when used incorrectly

Usage: If you wanted to access variables in the call stack, particularly on user exits or enhancements.

SAP ABAP Career, SAP ABAP Tutorial and Materials, SAP ABAP Prep, SAP ABPA Preparation, SAP ABAP Guides, SAP ABAP Certification, SAP ABAP Learning

With great power comes great responsibility. Use it only when necessary and avoid as much as possible.

FIELD-SYMBOLS: <lfs_vkorg> TYPE vkorg.
CONSTANTS: lc_curr_vkorg TYPE objectname VALUE '(SAPMV13H)KOMGH-VKORG'.

... Do something ...

ASSIGN (lc_curr_vkorg) TO <lfs_vkorg>.
IF <lfs_vkorg> IS ASSIGNED.
   IF <lfs_vkorg> IS NOT INITIAL.

... Do something ...

   ENDIF.
ENDIF.

Level 2. Dynamic Structure


Usage: This would usually go hand in hand with Dynamic tables but if not, it gives you an opportunity to create a structure out of a name or a reference (like another variable). There are multiple ways to create a dynamic structure but one of them is below

PARAMETERS: p_tab   TYPE tabname.

  
DATA: lo_structure    TYPE REF TO cl_abap_structdescr,
        
      lr_data         TYPE REF TO data.


  

lo_structure ?= cl_abap_structdescr=>describe_by_name( p_name = p_tab ).
  
CREATE DATA lr_data TYPE HANDLE lo_structure.
  
ASSIGN lr_data->* TO FIELD-SYMBOL(<lfs_structure>).

IF <lfs_structure> IS ASSIGNED. 
" Do something
ENDIF. 

Another example is a dynamically generated structure without a “reference”. In this example, I am generating a structure with a number of standard price field based on the parameter p_cnt. It generates the structure on runtime. This is very useful in programs where it can change the output.

One common use case is generating an ALV output based on a time range like a monthly value where the number of months is variable depending on user output.

PARAMETERS: p_cnt   TYPE i.

TYPES: BEGIN OF ty_material_price,
         matnr    TYPE matnr,
         waers    TYPE waers,
       END   OF ty_material_price.

DATA: go_struc       TYPE REF TO cl_abap_structdescr,
      go_new_struc   TYPE REF TO cl_abap_structdescr,
      gr_structure   TYPE REF TO data,
      go_tabdata     TYPE REF TO data,
      go_descr       TYPE REF TO cl_abap_datadescr,
      gv_price       TYPE STPRS,
      gs_mat_price   TYPE ty_material_price.


go_struc ?= cl_abap_structdescr=>describe_by_data( gs_mat_price ).

DATA(components)  = go_struc->get_components( ).

DO p_cnt TIMES.
  go_descr ?= cl_abap_typedescr=>describe_by_data( gv_price  ).
  APPEND INITIAL LINE TO components
    ASSIGNING FIELD-SYMBOL(<component>).
  <component> = VALUE #( name = |STPRS{ sy-index }| type = go_descr  ).
ENDDO.

TRY.
  DATA(new_struc) = cl_abap_structdescr=>create( p_components = components ).             " Structure Type Object
  CREATE DATA gr_structure TYPE HANDLE new_struc.
  ASSIGN gr_structure->* TO FIELD-SYMBOL(<new_structure>).
  IF <new_structure> IS ASSIGNED. 
    " Do something
  ENDIF. 
CATCH cx_sy_struct_creation. " Exception when creating a structure description
ENDTRY.

Level 3. Dynamic Table


Most of the usage of dynamism in ABAP would revolve in dynamic tables. There are countless usages, particularly in dynamic programs that revolve in the creation of dynamic table. In fact, most framework programs would have some concept of dynamic tables in the coding.

Similar to dynamic structure, there are multiple ways to create a dynamic table but just to continue with the dynamic structure to dynamic table creation, below is a good example of how to create one.

  PARAMETERS: p_tab   TYPE tabname.

  DATA: lo_structure    TYPE REF TO cl_abap_structdescr,
        lo_table        TYPE REF TO cl_abap_tabledescr,
        lr_data         TYPE REF TO data,
        lr_table_data   TYPE REF TO data.

  FIELD-SYMBOLS: <lfs_table> TYPE STANDARD TABLE.

  lo_structure ?= cl_abap_structdescr=>describe_by_name( p_name = p_tab ).
  CREATE DATA lr_data TYPE HANDLE lo_structure.

  lo_table ?= cl_abap_tabledescr=>create(
                p_line_type  = lo_structure                   " Line Type
*                p_table_kind = tablekind_std      " Table Category (STANDARD, SORTED, HASHED)
*                p_unique     = abap_false         " Uniqueness of the Key
*                p_key        =                    " Key table
*                p_key_kind   = keydefkind_default " Key category
              ).

  CREATE DATA lr_table_data TYPE HANDLE lo_table.

  ASSIGN lr_data->* TO FIELD-SYMBOL(<lfs_structure>).
  ASSIGN lr_table_data->* TO FIELD-SYMBOL(<lfs_table_data>).

  IF <lfs_table_data> IS ASSIGNED.
    " Do something
  ENDIF.

Following the dynamic structure example #2, we can also use the structure to create an internal table out of the dynamic structure.

PARAMETERS: p_cnt   TYPE i.

TYPES: BEGIN OF ty_material_price,
         matnr    TYPE matnr,
         waers    TYPE waers,
       END   OF ty_material_price.

DATA: go_struc       TYPE REF TO cl_abap_structdescr,
      go_new_struc   TYPE REF TO cl_abap_structdescr,
      gr_structure   TYPE REF TO data,
      gr_table       TYPE REF TO data,
      go_descr       TYPE REF TO cl_abap_datadescr,
      gv_price       TYPE STPRS,
      gs_mat_price   TYPE ty_material_price.

FIELD-SYMBOLS: <new_table> TYPE STANDARD TABLE.

go_struc ?= cl_abap_structdescr=>describe_by_data( gs_mat_price ).

DATA(components)  = go_struc->get_components( ).

DO p_cnt TIMES.
  go_descr ?= cl_abap_typedescr=>describe_by_data( gv_price  ).
  APPEND INITIAL LINE TO components
    ASSIGNING FIELD-SYMBOL(<component>).
  <component> = VALUE #( name = |STPRS{ sy-index }| type = go_descr  ).
ENDDO.

TRY.
  DATA(new_struc) = cl_abap_structdescr=>create( p_components = components ).             " Structure Type Object
  CREATE DATA gr_structure TYPE HANDLE new_struc.
  ASSIGN gr_structure->* TO FIELD-SYMBOL(<new_structure>).
  IF <new_structure> IS ASSIGNED.
    " Do something
  ENDIF.

  DATA(new_table) = cl_abap_tabledescr=>create( p_line_type = new_struc  ).
  CREATE DATA gr_table TYPE HANDLE new_table.
  ASSIGN gr_table->* TO <new_table>.
  IF <new_table> IS ASSIGNED.
    " Do something
  ENDIF.

  CATCH cx_sy_table_creation. " Exception when Creating a Table Type
  CATCH cx_sy_struct_creation. " Exception when creating a structure description
ENDTRY.

Level 4. Accessing dynamic fields in the dynamic structure


The entire dynamic table is useless if you cannot access the fields in the structure. The fields from dynamic structures and tables are ambiguous on design time and can only be generated in run time.

That said, you can access them using the ASSIGN COMPONENT command or the ASSIGN command. It will try to access the field or component in run time. Both achieves the same result.

    CREATE DATA gr_structure TYPE HANDLE new_struc.
    ASSIGN gr_structure->* TO FIELD-SYMBOL(<new_structure>).
    IF <new_structure> IS ASSIGNED.

      gv_field =  |STPRS{ p_cnt }|.

      "Option 1
      ASSIGN <new_structure>-(gv_field) TO FIELD-SYMBOL(<stprs2>).
      IF <stprs2> IS ASSIGNED.
        <stprs2> = 10.  
      ENDIF.

      "Option 2
      ASSIGN COMPONENT gv_field OF STRUCTURE <new_structure> TO FIELD-SYMBOL(<stprs>).
      IF <stprs> IS ASSIGNED.
        <stprs> = 20.
        " Do something

        BREAK-POINT.

      ENDIF.
      UNASSIGN <stprs>.

      " Do something
    ENDIF.

Level 5. Dynamic SELECT statement


Continuing with the theme of the dynamic table, we can select dynamically and create dynamic tables. This can also be achieved differently but this is basically one example on how to achieve a dynamic select statement.

Strong Warning: While this is very useful, make sure that you secure your code for any injections by adding authorization checks on your dynamic programs. 

PARAMETERS: p_tab   TYPE tabname,
            p_matnr TYPE matnr.

TYPES: BEGIN OF ty_list,
         name  TYPE tabname,
         r_str TYPE REF TO data,
         r_tbl TYPE REF TO data,
       END OF ty_list.

DATA: lt_list         TYPE STANDARD TABLE OF ty_list.

DATA: lo_structure  TYPE REF TO cl_abap_structdescr,
      lo_table      TYPE REF TO cl_abap_tabledescr,
      lt_fields     TYPE STANDARD TABLE OF fieldname,
      lt_CONDTAB    TYPE STANDARD TABLE OF hrcond,
      lt_where      TYPE STANDARD TABLE OF string,
      lr_data       TYPE REF TO data,
      lr_table_data TYPE REF TO data.

FIELD-SYMBOLS: <lfs_table> TYPE STANDARD TABLE.

lo_structure ?= cl_abap_structdescr=>describe_by_name( p_name = p_tab ).
CREATE DATA lr_data TYPE HANDLE lo_structure.

lo_table ?= cl_abap_tabledescr=>create(
              p_line_type  = lo_structure                   " Line Type
*                p_table_kind = tablekind_std      " Table Category (STANDARD, SORTED, HASHED)
*                p_unique     = abap_false         " Uniqueness of the Key
*                p_key        =                    " Key table
*                p_key_kind   = keydefkind_default " Key category
            ).

CREATE DATA lr_table_data TYPE HANDLE lo_table.

ASSIGN lr_data->* TO FIELD-SYMBOL(<lfs_structure>).
ASSIGN lr_table_data->* TO FIELD-SYMBOL(<lfs_table_data>).

lt_condtab = VALUE #( ( field = 'MATNR' opera = 'EQ' low = p_matnr ) ).

IF <lfs_table_data> IS ASSIGNED.

  IF p_tab EQ 'MARA'.
    lt_fields = VALUE #( ( 'MATNR'  ) ).

    CALL FUNCTION 'RH_DYNAMIC_WHERE_BUILD'
      EXPORTING
        dbtable         = p_Tab
      TABLES
        condtab         = lt_condtab
        where_clause    = lt_where
      EXCEPTIONS
        empty_condtab   = 1
        no_db_field     = 2
        unknown_db      = 3
        wrong_condition = 4
        OTHERS          = 5.

    SELECT (lt_fields)
      FROM (p_tab)
     WHERE (lt_where)
      INTO CORRESPONDING FIELDS OF TABLE @<lfs_table_data>.

    " Do something

  ENDIF.

ENDIF.

Level 6. Reference Variables (DATA)


As you would have noticed, this has been used in the above examples already. There’s no limit on the creation of dynamic objects with the usage of data references.

For example, you can create an internal table with data references. In the sample below, you can create a typed internal table with data references to dynamic structures and tables.

  TYPES: BEGIN OF ty_list,
           name   TYPE tabname,
           r_str  TYPE REF TO data,
           r_tbl  TYPE REF TO data,
         END OF ty_list. 
         
  DATA: lt_list         TYPE STANDARD TABLE OF ty_list. 

Data references can also be passed via methods or function modules with a well-structured reference variable. If you really need to call dynamic data, the best approach is via Reference variables.

 PARAMETERS: p_tab   TYPE tabname.

 CLASS lcl_main DEFINITION.

   PUBLIC SECTION.

    CLASS-METHODS: set_data   CHANGING o_tbl   TYPE REF TO data.

 ENDCLASS.

  TYPES: BEGIN OF ty_list,
           name   TYPE tabname,
           r_str  TYPE REF TO data,
           r_tbl  TYPE REF TO data,
         END OF ty_list.

  DATA: lt_list         TYPE STANDARD TABLE OF ty_list.

  DATA: lo_structure    TYPE REF TO cl_abap_structdescr,
        lo_table        TYPE REF TO cl_abap_tabledescr,
        lr_data         TYPE REF TO data,
        lr_table_data   TYPE REF TO data.

  FIELD-SYMBOLS: <lfs_table> TYPE STANDARD TABLE.

  lo_structure ?= cl_abap_structdescr=>describe_by_name( p_name = p_tab ).
  CREATE DATA lr_data TYPE HANDLE lo_structure.

  lo_table ?= cl_abap_tabledescr=>create(
                p_line_type  = lo_structure                   " Line Type
*                p_table_kind = tablekind_std      " Table Category (STANDARD, SORTED, HASHED)
*                p_unique     = abap_false         " Uniqueness of the Key
*                p_key        =                    " Key table
*                p_key_kind   = keydefkind_default " Key category
              ).

  CREATE DATA lr_table_data TYPE HANDLE lo_table.

  ASSIGN lr_data->* TO FIELD-SYMBOL(<lfs_structure>).
  ASSIGN lr_table_data->* TO FIELD-SYMBOL(<lfs_table_data>).

  IF <lfs_table_data> IS ASSIGNED.
    lcl_main=>set_data(
      CHANGING
        o_tbl = lr_table_data
    ).
  ENDIF.

 CLASS lcl_main IMPLEMENTATION.

   METHOD set_data.
     FIELD-SYMBOLS: <lfs_data> TYPE STANDARD TABLE.

     ASSIGN o_tbl->* TO <lfs_data>.
     IF <lfs_data> IS ASSIGNED.
       " Do something
     ENDIF.

   ENDMETHOD.

 ENDCLASS.

Level 7. Dynamic Methods


One of the best ways to teach a new developer ABAP OO concepts, particularly polymorphism in some aspects, is the usage of Class Interfaces.

A good example of its usage is when you wanted to run different logic depending in configuration. For example, you have a program that can either send to excel or rest service or to flat file in the local server while making it configurable, the best practice way to standardize is the usage of Class Interfaces.

    DATA: lo_adapter    TYPE REF TO zif_adapter,
          ls_data       TYPE ty_data. 

    IF ms_adapter-s_adapter-call_class IS NOT INITIAL.
      TRY.
          CREATE OBJECT lo_adapter TYPE (ms_adapter-s_adapter-call_class).
  IF lo_adapter IS BOUND.
    lo_adapter->send( CHANGING is_data = ls_data ). 

          ENDIF. 

        CATCH cx_sy_dyn_call_illegal_method.
        CATCH cx_sy_create_object_error.
      ENDTRY.
    ENDIF. 

Classes with interfaces

" Class #1. Send via Email 
CLASS zcl_email definition
  public
  final
  create public .

   PUBLIC SECTION.
   
    INTERFACES: zif_adapter.
   
   PROTECTED SECTION. 
   PRIVATE SECTION. 

 ENDCLASS.

 CLASS lcl_main IMPLEMENTATION.
   
   METHOD zif_adapter~send. 
     " Send via email
   ENDMETHOD. 

 ENDCLASS.
 
" Class #2. Send via FTP
  CLASS zcl_ftp definition
  public
  final
  create public .

   PUBLIC SECTION.
   
    INTERFACES: zif_adapter.
   
   PROTECTED SECTION. 
   PRIVATE SECTION. 

 ENDCLASS.

 CLASS lcl_main IMPLEMENTATION.
   
   METHOD zif_adapter~send. 
     " Send to ftp server
   ENDMETHOD. 

 ENDCLASS.

No comments:

Post a Comment