Thursday, July 30, 2015

Batch Input - BDC via custom class tool set - call of LX47 example

I think, no SAP developer can avoid to touch batch input transaction calls. There is a few constantly repeated steps, which could be a bit easier if you would use some custom set of functions, the best way a custom class. So, let's take a look at my solution, maybe it becomes handy for you.

Good source to start is here.

Hot to get BDC commands?

If you are new here, definitely take a look at transaction SHDB (Batch Input Transaction Recorder). It can save you lot of pains when you would be searching for proper BDC commands. Sometime even dynamically generated screens have one dynpro number in foreground and different one in background call. It means, without tool as SHDB, you are absolutely lost.

In my case, I imitated manual usage of transaction LX47. The result of such a SHDB recording can looks like this.



Ok, we have a list of commands needed for background call. Now we can setup our tool set. There is some abstract base class suitable to be an ancestor of some real controller class.

The class definition


*----------------------------------------------------------------------*
*       CLASS lcl_ctrl_bapi DEFINITION
*----------------------------------------------------------------------*
*
*----------------------------------------------------------------------*
CLASS lcl_ctrl_base DEFINITION ABSTRACT.
  PUBLIC SECTION.
    METHODS
             bdc_call_transaction
                IMPORTING iv_transaction TYPE bdc_prog
                          iv_mode        TYPE c1
                          iv_dynrbegin   TYPE bdc_start
                RAISING lcx_msg_exception,
             bdc_add_dynpro
                IMPORTING iv_program   TYPE bdc_prog
                          iv_dynpro    TYPE bdc_dynr
                          iv_dynrbegin TYPE bdc_start,
             bdc_add_param
                IMPORTING iv_name      TYPE fnam_____4
                          iv_value     TYPE bdc_fval,
             bdc_init,
             bdc_send_enter,
             bdc_send_execute,
             bdc_send_end,
             bdc_send_update,
             bdc_send_select_all.


  PRIVATE SECTION.
    DATAt_bdcdata TYPE STANDARD TABLE OF bdcdata,
          s_bdcdata LIKE LINE OF t_bdcdata.   " Structure type of bdcdata

ENDCLASS.                    "lcl_ctrl_base DEFINITION



The class implementation


*----------------------------------------------------------------------*
*       CLASS lcl_ctrl_bapi IMPLEMENTATION
*----------------------------------------------------------------------*
*
*----------------------------------------------------------------------*
CLASS lcl_ctrl_base IMPLEMENTATION.


  METHOD bdc_call_transaction.

    DATAlt_msg TYPE TABLE OF bdcmsgcoll.   " Collecting Error messages
    FIELD-SYMBOLS<fs_msg> TYPE bdcmsgcoll.

    CALL TRANSACTION
      iv_transaction
      USING  t_bdcdata
      MODE   iv_mode
      UPDATE 'S' " Synchronous/Asynchronous/Local update task
      MESSAGES INTO lt_msg.

    IF sy-subrc NE 0.
*    Error Found - fire the first one...
      LOOP AT lt_msg INTO <fs_msg> WHERE msgtyp EQ 'E'.
        RAISE EXCEPTION TYPE lcx_msg_exception
          EXPORTING
            is_msg_bdcmsgoll <fs_msg>.
      ENDLOOP.
    ENDIF.
  ENDMETHOD.                    "bdc_call_transaction

  METHOD bdc_add_dynpro.
    CLEAR s_bdcdata.
    s_bdcdata-program  iv_program.
    s_bdcdata-dynpro   iv_dynpro.
    s_bdcdata-dynbegin iv_dynrbegin.
    APPEND s_bdcdata TO t_bdcdata.
  ENDMETHOD.                    "bdc_add_dynpro

  METHOD bdc_add_param.
    CLEAR s_bdcdata.
    s_bdcdata-fnam iv_name.
    s_bdcdata-fval iv_value.
    CONDENSE s_bdcdata-fval.
    APPEND s_bdcdata TO t_bdcdata.
  ENDMETHOD.                    "bdc_add_field

  METHOD bdc_init.
    CLEAR   s_bdcdata.
    REFRESH t_bdcdata.
  ENDMETHOD.                    "bdc_init

  METHOD bdc_send_enter.
    me->bdc_add_param(
      EXPORTING
        iv_name  'BDC_OKCODE'
        iv_value '/00').
  ENDMETHOD.                    "bdc_enter

  METHOD bdc_send_execute.
    me->bdc_add_param(
      EXPORTING
        iv_name  'BDC_OKCODE'
        iv_value '=ONLI').
  ENDMETHOD.                    "bdc_send_execute

  METHOD bdc_send_end.
    me->bdc_add_param(
      EXPORTING
        iv_name  'BDC_OKCODE'
        iv_value '/EECAN').   "iv_value = '/EENDE').
  ENDMETHOD.                    "bdc_send_end

  METHOD bdc_send_update.
    me->bdc_add_param(
      EXPORTING
        iv_name  'BDC_OKCODE'
        iv_value '=COMMIT').
  ENDMETHOD.                    "bdc_send_update

  METHOD bdc_send_select_all.
    me->bdc_add_param(
      EXPORTING
        iv_name  'BDC_OKCODE'
        "iv_value = '/EENDE').
        iv_value '=&ALL').
  ENDMETHOD.                    "bdc_send_select_all

ENDCLASS.                    "lcl_ctrl_base IMPLEMENTATION




And now, how to use it?


Imagine, you have some your own controller class inheriting from abstract base class above. So its method can looks as follows.

  METHOD bdc_call_lx47.

    " Input check
    IF iv_lgnum IS INITIAL OR iv_tanum IS INITIAL ).
      RETURN.
    ENDIF.

    DATA lv_value TYPE bdc_fval.

    me->bdc_init).

    me->bdc_add_dynpro(
      EXPORTING
        iv_program   'RLLX4700'
        iv_dynpro    '1000'
        iv_dynrbegin 'X'
      ).

    MOVE iv_lgnum TO lv_value.
    me->bdc_add_param(
      EXPORTING
        iv_name      'PV_LGNUM'     " warehouse num.
        iv_value     lv_value
      ).

    CLEAR lv_value.
    MOVE iv_tanum TO lv_value.
    me->bdc_add_param(
      EXPORTING
        iv_name      'PR_TANUM-LOW' " transfer order num.
        iv_value     lv_value
      ).

    me->bdc_add_param(
      EXPORTING
        iv_name      'PV_MARK'      " set active, the checkbox
        iv_value     'X'
      ).

    me->bdc_send_execute)" emulate click on first screen

    " Select all
    me->bdc_add_dynpro(
      EXPORTING
        iv_program   'SAPMSSY0'
        iv_dynpro    '0120'
        iv_dynrbegin 'X'
      ).
    me->bdc_send_select_all).

    " Update
    me->bdc_add_dynpro(
      EXPORTING
        iv_program   'SAPMSSY0'
        iv_dynpro    '0120'
        iv_dynrbegin 'X'
      ).
    me->bdc_send_update).

    me->bdc_call_transaction(
      EXPORTING
        iv_transaction 'LX47'
        iv_mode        'N' " A - foreground / E - errors only / N - no display
        iv_dynrbegin   abap_true
    ).

  ENDMETHOD.                    "bdc_call_lx47


To be exact in case of LX47 I had to check if any data exists before calling of second screen number 120, that why I used below check before actual BDC call. So this part is just for those who are interested in full LX47 call :)

METHOD bdc_check_call_lx47.

    " Input check
    IF iv_lgnum IS INITIAL OR iv_tanum IS INITIAL ).
      RETURN.
    ENDIF.

    " LX47 data check
    " Read data from the transfer order header table
    DATAlv_mark  TYPE lvs_selkz,
          lv_item  TYPE lvs_selkz,
          lt_ltodn TYPE STANDARD TABLE OF ltodn,
          lt_tanum TYPE STANDARD TABLE OF range_n10,
          ls_tanum LIKE LINE OF lt_tanum.

    lv_mark  abap_true.
    ls_tanum-sign   'I'.
    ls_tanum-option 'EQ'.
    ls_tanum-low   iv_tanum.
    APPEND ls_tanum TO lt_tanum.

    CALL FUNCTION 'L_TO_DN_READ'
      EXPORTING
        iv_lgnum        iv_lgnum
        iv_mark         lv_mark
        iv_item         lv_item
      TABLES
        et_ltodn        lt_ltodn
        ir_tanum        lt_tanum
                                      "ir_vbeln        = pr_vbeln
      EXCEPTIONS
        not_found       1
        not_found_to_dn 2
        not_found_dn    3.

    IF sy-subrc NE 0.
      RETURN" no data for BDC LX47 call
    ENDIF.

    me->bdc_call_lx47(
      EXPORTING
        iv_lgnum iv_lgnum
        iv_tanum iv_tanum
    ).

  ENDMETHOD.                    "bdc_check_call_lx47



Tuesday, May 19, 2015

VDA Modulus 43 method of Data Matrix ECC200

From time to time we all have to fulfill some technical norm. Concerning Data Matrix code ECC200 - VDA label norm there is no exception. Once I had to code this norm requirement, simple task to get security sign of all DMC content. So why to discover a wheel again? :) Check my approach below.

VDA requirement says

The check digit is calculated with the Modulus 43 method:
For this purpose the numeric values of all characters transferred (without control characters) are
added and the sum is divided by 43.

The remaining balance is converted into a character again and transferred in the data record as a
check digit. 

Example: the “12345ABCDE” string makes the check digit W. 1+2+3+4+5+10+11+12+13+14 = 75 
--> 75 : 43 = 1 Rest 32 -> 32 equals the W character.



I put some simple subroutine into SF to add one DataMatrix code item.



Later on subroutine for modulus 43.




The actual coding looks like this


*&---------------------------------------------------------------------*
*&      Form  get_check_code
*&---------------------------------------------------------------------*
*       get VDA security check character
*----------------------------------------------------------------------*
*      -->LV_INPUTDATA_STR  text
*      -->LV_CHECK_CHAR     text
*----------------------------------------------------------------------*
FORM get_check_code
      USING
          lv_inputdata_str TYPE string
      CHANGING
          lv_check_char    TYPE /fit/lwert.

  TYPESBEGIN OF ty_translation,
            input TYPE c1,
            value TYPE i,
         END OF ty_translation.

  DATAlt_translations TYPE STANDARD TABLE OF ty_translation,
        ls_translation LIKE LINE OF lt_translations.

  CONSTANTS cv_diviser TYPE VALUE 43.

  ls_translation-input '0'.
  ls_translation-value 0.
  APPEND ls_translation TO lt_translations.

  ls_translation-input '1'.
  ls_translation-value 1.
  APPEND ls_translation TO lt_translations.

  ls_translation-input '2'.
  ls_translation-value 2.
  APPEND ls_translation TO lt_translations.

  ls_translation-input '3'.
  ls_translation-value 3.
  APPEND ls_translation TO lt_translations.

  ls_translation-input '4'.
  ls_translation-value 4.
  APPEND ls_translation TO lt_translations.

  ls_translation-input '5'.
  ls_translation-value 5.
  APPEND ls_translation TO lt_translations.

  ls_translation-input '6'.
  ls_translation-value 6.
  APPEND ls_translation TO lt_translations.

  ls_translation-input '7'.
  ls_translation-value 7.
  APPEND ls_translation TO lt_translations.

  ls_translation-input '8'.
  ls_translation-value 8.
  APPEND ls_translation TO lt_translations.

  ls_translation-input '9'.
  ls_translation-value 9.
  APPEND ls_translation TO lt_translations.

  ls_translation-input 'A'.
  ls_translation-value 10.
  APPEND ls_translation TO lt_translations.

  ls_translation-input 'B'.
  ls_translation-value 11.
  APPEND ls_translation TO lt_translations.

  ls_translation-input 'C'.
  ls_translation-value 12.
  APPEND ls_translation TO lt_translations.

  ls_translation-input 'D'.
  ls_translation-value 13.
  APPEND ls_translation TO lt_translations.

  ls_translation-input 'E'.
  ls_translation-value 14.
  APPEND ls_translation TO lt_translations.

  ls_translation-input 'F'.
  ls_translation-value 15.
  APPEND ls_translation TO lt_translations.

  ls_translation-input 'G'.
  ls_translation-value 16.
  APPEND ls_translation TO lt_translations.

  ls_translation-input 'H'.
  ls_translation-value 17.
  APPEND ls_translation TO lt_translations.

  ls_translation-input 'I'.
  ls_translation-value 18.
  APPEND ls_translation TO lt_translations.

  ls_translation-input 'J'.
  ls_translation-value 19.
  APPEND ls_translation TO lt_translations.

  ls_translation-input 'K'.
  ls_translation-value 20.
  APPEND ls_translation TO lt_translations.

  ls_translation-input 'L'.
  ls_translation-value 21.
  APPEND ls_translation TO lt_translations.

  ls_translation-input 'M'.
  ls_translation-value 22.
  APPEND ls_translation TO lt_translations.

  ls_translation-input 'N'.
  ls_translation-value 23.
  APPEND ls_translation TO lt_translations.

  ls_translation-input 'O'.
  ls_translation-value 24.
  APPEND ls_translation TO lt_translations.

  ls_translation-input 'P'.
  ls_translation-value 25.
  APPEND ls_translation TO lt_translations.

  ls_translation-input 'Q'.
  ls_translation-value 26.
  APPEND ls_translation TO lt_translations.

  ls_translation-input 'R'.
  ls_translation-value 27.
  APPEND ls_translation TO lt_translations.

  ls_translation-input 'S'.
  ls_translation-value 28.
  APPEND ls_translation TO lt_translations.

  ls_translation-input 'T'.
  ls_translation-value 29.
  APPEND ls_translation TO lt_translations.

  ls_translation-input 'U'.
  ls_translation-value 30.
  APPEND ls_translation TO lt_translations.

  ls_translation-input 'V'.
  ls_translation-value 31.
  APPEND ls_translation TO lt_translations.

  ls_translation-input 'W'.
  ls_translation-value 32.
  APPEND ls_translation TO lt_translations.

  ls_translation-input 'X'.
  ls_translation-value 33.
  APPEND ls_translation TO lt_translations.

  ls_translation-input 'Y'.
  ls_translation-value 34.
  APPEND ls_translation TO lt_translations.

  ls_translation-input 'Z'.
  ls_translation-value 35.
  APPEND ls_translation TO lt_translations.

  ls_translation-input '-'.
  ls_translation-value 36.
  APPEND ls_translation TO lt_translations.

  ls_translation-input '.'.
  ls_translation-value 37.
  APPEND ls_translation TO lt_translations.

  ls_translation-input ' '.
  ls_translation-value 38.
  APPEND ls_translation TO lt_translations.

  ls_translation-input '$'.
  ls_translation-value 39.
  APPEND ls_translation TO lt_translations.

  ls_translation-input '/'.
  ls_translation-value 40.
  APPEND ls_translation TO lt_translations.

  ls_translation-input '+'.
  ls_translation-value 41.
  APPEND ls_translation TO lt_translations.

  ls_translation-input '%'.
  ls_translation-value 42.
  APPEND ls_translation TO lt_translations.
*
  TRANSLATE lv_inputdata_str TO UPPER CASE.

  DATAlv_char   TYPE c,
        lv_offset TYPE syindex,
        lv_sum    TYPE i,
        lv_rest   TYPE i.

  " get sum of character values
  DO strlenlv_inputdata_str TIMES.
    lv_offset sy-index 1.
    lv_char lv_inputdata_str+lv_offset.

    IF lv_char IS NOT INITIAL.
      CLEAR ls_translation.
      READ TABLE lt_translations WITH KEY input lv_char INTO ls_translation.
      IF sy-subrc EQ 0.
        lv_sum lv_sum + ls_translation-value.
      ENDIF.
    ENDIF.
  ENDDO.

  " get proper 43 return code
  IF lv_sum NE 0.
    lv_rest lv_sum MOD cv_diviser.
    CLEAR ls_translation.
    READ TABLE lt_translations WITH KEY value lv_rest INTO ls_translation.
    IF sy-subrc EQ 0.
      lv_check_char ls_translation-input.
    ENDIF.
  ENDIF.
ENDFORM.                    "get_check_code