Wednesday, October 7, 2020

BAPI_MATERIAL_SAVEDATA Use For Material Extension Full Program Example in SAP ABAP

Material Extension  Full Program Example in SAP ABAP.


BAPI_MATERIAL_SAVEDATA Use For Material Extension in SAP ABAP.

REPORT zrmm_material_master_upld.
INCLUDE zrmm_material_master_upld_top.
INCLUDE zrmm_material_master_upld_ss.
INCLUDE zrmm_material_master_upld_sub.

******************  I  N I T I A L I Z A T I O N   *************
INITIALIZATION.

AT SELECTION-SCREEN ON VALUE-REQUEST FOR p_path.
  
PERFORM f4_help.

START-OF-SELECTION.
PERFORM get_data.

  
IF r_int abap_true.
    
PERFORM f_fill_matnr.
  
ELSEIF r_ext abap_true.
    gt_final[] 
gt_final_ext[].
  
ENDIF.

  
IF gt_final[] IS NOT INITIAL.
    
PERFORM f_create_material_master.

***** MSG Handling
    
PERFORM f_build_header,
              f_download_msg
.
  
ENDIF.
**&---------------------------------------------------------------------*
**& Form F4_HELP
**&---------------------------------------------------------------------*
**& text
**&---------------------------------------------------------------------*
**& -->  p1        text
**& <--  p2        text
**&---------------------------------------------------------------------*
FORM f4_help .
  
CALL FUNCTION 'F4_FILENAME'
    
EXPORTING
      program_name  
syst-cprog
      dynpro_number 
syst-dynnr
    
IMPORTING
      file_name     
p_path.
ENDFORM.

================================================================

TABLES:bapimathead,
       bapi_makt
,
       bapi_mara
,
       bapi_marax
,
       bapi_marc
,
       bapi_marcx
,
       bapi_mard
,
       bapi_mardx
,
       bapi_mpop
,
       bapi_mpopx
,
       bapi_mbew
,
       bapi_mbewx
,
       bapi_mvke
,
       bapi_mvkex
,
       bapi_mlgt
,
       bapi_mlgtx
,
       bapi_mpgd
,
       bapi_mpgdx 
.

TYPES BEGIN OF ty_ext_final,
          matnr
(40),
          mtart
(4),
          werks
(4),
          lgort
(4),
          vkorg
(4),
          vtweg
(2),
          maktx
(40),
          meins
(3),
          matkl
(9),
          bismt
(40),   """"
          spart
(2),
          mtpos_mara
(4),
          brgew
(17),
*          gewei(3),
          ntgew
(13),
          taxkm
(1),
          taxkm1
(1),
          taxkm2
(1),
          taxkm3
(1),
          taxkm4
(1),
          ktgrm
(2),
          mtpos
(4),
***          New ADD
*          MVGR1(3),
*          MVGR2(3),
*          MVGR3(3),
*          MVGR4(3),
*          MVGR5(3),
****          New ADD
****      new add
          mtbfp
(2),
          xchpf
(1),
*          kautb(1),
****
          tragr
(4),
          ladgr
(4),
          prctr
(10),
          steuc
(16),
          ekgrp
(3),
          vabme
(1),
          taxim
(1),
          disgr
(4),
          dismm
(2),
          minbe
(10),             "New added
          dispo
(3),
          mabst
(17),
          disls
(2),
          beskz
(1),
          dzeit
(3),
          plifz
(3),
          webaz
(3),
*          perkz(1),
*          strgr(2),
*          mtvfp(2),
*          sbdkz(1),
*          prmod(1),
*          peran(3),
*          anzpr(3),
*          kzini(1),
*          siggr(9),
*          modav(1),
          fevor
(3),
          sfcpf
(6),
          mhdrz
(4),
          mhdhb
(4),
          iprkz
(1),
*
          sled_bbd
(1),
          sernp
(4),
          bwtty
(1),
          bklas
(4),
          mlast
(1),
*          stprs_1(14),
          peinh_1
(5),
          vprsv_1
(1),

          losgr
(17),
**          vprsv(1),
**          peinh(5),
**          stprs(14),
          umren2_1
(5),
          umren3_1
(5),
          umren4_1
(5),
          meinh2_1
(3),

          umren2_2
(5),
          umren3_2
(5),
          umren4_2
(5),
          meinh2_2
(3),

*          umren2_3(5),
*          umren3_3(5),
*          umren4_3(5),
*          meinh2_3(3),

          
"po_text(250),
          po_text1
(50),
          po_text2
(50),
          po_text3
(50),
          po_text4
(50),
          po_text5
(50),

        
END OF ty_ext_final,

        
BEGIN OF ty_int_final,
          mtart
(4),
          werks
(4),
          lgort
(4),
          vkorg
(4),
          vtweg
(2),
          maktx
(40),
          meins
(3),
          matkl
(9),
          bismt
(40),   """"
          spart
(2),
          mtpos_mara
(4),
          brgew
(17),
*          gewei(3),
          ntgew
(13),
          taxkm
(1),
          taxkm1
(1),
          taxkm2
(1),
          taxkm3
(1),
          taxkm4
(1),
          ktgrm
(2),
          mtpos
(4),
***          New ADD
*          MVGR1(3),
*          MVGR2(3),
*          MVGR3(3),
*          MVGR4(3),
*          MVGR5(3),
****          New ADD

****      new add
          mtbfp
(2),
          xchpf
(1),
*          kautb(1),
****
          tragr
(4),
          ladgr
(4),
          prctr
(10),
          steuc
(16),
          ekgrp
(3),
          vabme
(1),
          taxim
(1),
          disgr
(4),
          dismm
(2),
          minbe
(10),             "New added
          dispo
(3),
          mabst
(17),
          disls
(2),
          beskz
(1),
          dzeit
(3),
          plifz
(3),
          webaz
(3),
*          perkz(1),
*          strgr(2),
*          mtvfp(2),
*          sbdkz(1),
*          prmod(1),
*          peran(3),
*          anzpr(3),
*          kzini(1),
*          siggr(9),
*          modav(1),
          fevor
(3),
          sfcpf
(6),
          mhdrz
(4),
          mhdhb
(4),
          iprkz
(1),

          sled_bbd
(1),
          sernp
(4),
          bwtty
(1),
          bklas
(4),
          mlast
(1),
*          stprs_1(14),
          peinh_1
(5),
          vprsv_1
(1),

          losgr
(17),
**          vprsv(1),
**          peinh(5),
**          stprs(14),
          umren2_1
(5),
          umren3_1
(5),
          umren4_1
(5),
          meinh2_1
(3),

          umren2_2
(5),
          umren3_2
(5),
          umren4_2
(5),
          meinh2_2
(3),

*          umren2_3(5),
*          umren3_3(5),
*          umren4_3(5),
*          meinh2_3(3),
          po_text1 
TYPE TDLINE "(50),
          po_text2
(50),
          po_text3
(50),
          po_text4
(50),
          po_text5
(50),
        
END OF ty_int_final.


DATA gt_final     TYPE STANDARD TABLE OF ty_ext_final,
       gs_final     
TYPE ty_ext_final,

       gt_final_ext 
TYPE STANDARD TABLE OF ty_ext_final,
       gs_final_ext 
TYPE ty_ext_final,

       gt_final_int 
TYPE STANDARD TABLE OF ty_int_final,
       gs_final_int 
TYPE ty_int_final.

DATAgt_file_data  TYPE truxs_t_text_data.


DATA it_mlan  TYPE STANDARD TABLE OF bapi_mlan,
       wa_mlan  
TYPE bapi_mlan,

       it_marm  
TYPE STANDARD TABLE OF bapi_marm,
       it_marmx 
TYPE STANDARD TABLE OF bapi_marmx,

       it_makt  
TYPE STANDARD TABLE OF bapi_makt,
       wa_makt  
TYPE bapi_makt,

       wa_marm  
TYPE bapi_marm,
       wa_marmx 
TYPE bapi_marmx.

DATA it_return LIKE bapiret2,
       wa_return 
TYPE bapiret2.



DATA :it_excel TYPE STANDARD TABLE OF alsmex_tabline,
      wa_excel 
TYPE                   alsmex_tabline.
FIELD-SYMBOLS<fs>.

TYPES BEGIN OF ty_header,
          f_name 
TYPE char75,
        
END OF ty_header,

        
BEGIN OF msg,
          
line       TYPE i,
          
type       TYPE char10,
          message_v1 
TYPE symsgv,
          maktx      
TYPE makt-maktx,
          
message    TYPE bapi_msg,
        
END OF msg.


DATA lv_desktop TYPE string,
       lv_line    
TYPE i.

DATAlt_header TYPE STANDARD TABLE OF ty_header,
      ls_header 
TYPE ty_header,

      it_msg    
TYPE STANDARD TABLE OF msg,
      wa_msg    
TYPE msg.

=======================================================================================

SELECTION-SCREEN BEGIN OF BLOCK B1 WITH FRAME TITLE TEXT-001.
PARAMETERS P_PATH LIKE RLGRAP-FILENAME OBLIGATORY,
             P_STROW 
TYPE I OBLIGATORY,
             P_EDROW 
TYPE I OBLIGATORY.

SELECTION-SCREEN SKIP 1.

SELECTION-SCREEN END OF BLOCK B1.

SELECTION-SCREEN BEGIN OF BLOCK b2 WITH FRAME title text-002.
  
PARAMETERS r_int RADIOBUTTON GROUP rd1 DEFAULT 'X',
               r_ext 
RADIOBUTTON GROUP rd1.
  
SELECTION-SCREEN end of BLOCK b2.

======================================================================================


*&---------------------------------------------------------------------*
*&---------------------------------------------------------------------*
*& Form GET_DATA
*&---------------------------------------------------------------------*
*& text
*&---------------------------------------------------------------------*
*& -->  p1        text
*& <--  p2        text
*&---------------------------------------------------------------------*
FORM get_data .
  
DATA index    TYPE i.
  
IF r_ext abap_true.

    
CALL FUNCTION 'ALSM_EXCEL_TO_INTERNAL_TABLE'
      
EXPORTING
        filename                
p_path
        i_begin_col             
1
        i_begin_row             
p_strow
        i_end_col               
100
        i_end_row               
p_edrow
      
TABLES
        intern                  
it_excel
      
EXCEPTIONS
        inconsistent_parameters 
1
        upload_ole              
2
        
OTHERS                  3.
    
IF sy-subrc <> 0.
      
MESSAGE 'ERROR OCCUR IN READING THE EXCEL FILE' TYPE 'I'.
      
STOP.
    
ENDIF.

    
LOOP AT it_excel INTO wa_excel.
      
index wa_excel-col.
      
ASSIGN COMPONENT index OF STRUCTURE gs_final_ext TO <fs>.
      <fs> 
wa_excel-value.
      
AT END OF row.
*      APPEND wa_final TO it_final.
        
APPEND gs_final_ext TO gt_final_ext.
        
CLEAR gs_final_ext.
      
ENDAT.
    
ENDLOOP.

*    CALL FUNCTION 'TEXT_CONVERT_XLS_TO_SAP'
*      EXPORTING
*        i_line_header        = abap_true
*        i_tab_raw_data       = gt_file_data
*        i_filename           = p_file
*      TABLES
*        i_tab_converted_data = gt_final_ext[]
*      EXCEPTIONS
*        conversion_failed    = 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.
*    SORT gt_final_ext BY matnr.
  
ELSEIF r_int abap_true.


    
CALL FUNCTION 'ALSM_EXCEL_TO_INTERNAL_TABLE'
      
EXPORTING
        filename                
p_path
        i_begin_col             
1
        i_begin_row             
p_strow
        i_end_col               
100
        i_end_row               
p_edrow
      
TABLES
        intern                  
it_excel
      
EXCEPTIONS
        inconsistent_parameters 
1
        upload_ole              
2
        
OTHERS                  3.
    
IF sy-subrc <> 0.
      
MESSAGE 'ERROR OCCUR IN READING THE EXCEL FILE' TYPE 'I'.
      
STOP.
    
ENDIF.

    
LOOP AT it_excel INTO wa_excel.
      
index wa_excel-col.
      
ASSIGN COMPONENT index OF STRUCTURE gs_final_int TO <fs>.
      <fs> 
wa_excel-value.
      
AT END OF row.
*      APPEND wa_final TO it_final.
        
APPEND gs_final_int TO gt_final_int.
        
CLEAR gs_final_int.
      
ENDAT.
    
ENDLOOP.

*   BREAK-POINT.

*    CALL FUNCTION 'TEXT_CONVERT_XLS_TO_SAP'
*      EXPORTING
*        i_line_header        = abap_true
*        i_tab_raw_data       = gt_file_data
*        i_filename           = p_file
*      TABLES
*        i_tab_converted_data = gt_final_int[]
*      EXCEPTIONS
*        conversion_failed    = 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.
  
ENDIF.

*  BREAK-POINT.
ENDFORM.
*&---------------------------------------------------------------------*
*& Form UPLOAD_DATA
*&---------------------------------------------------------------------*
*& text
*&---------------------------------------------------------------------*
*& -->  p1        text
*& <--  p2        text
*&---------------------------------------------------------------------*
FORM f_fill_matnr .

  
DATA lv_lines TYPE i.
  
DATA :lv_new_mat_total TYPE bapimatall-req_numbers,
        required_numbers 
LIKE  bapimatall-req_numbers,
        lt_material      
TYPE STANDARD TABLE OF  bapimatinr,
        lt_material1     
TYPE STANDARD TABLE OF  bapimatinr,
        ls_material      
TYPE bapimatinr,
        material_type    
LIKE  bapimatdoa-matl_type.


  
DESCRIBE TABLE gt_final_int LINES lv_lines.

  
IF lv_lines > 255 .
    
MESSAGE 'For Internal material Number range only 255 line is allowed.' TYPE 'E'.
  
ENDIF.
  
DESCRIBE TABLE gt_final_int LINES lv_new_mat_total ."lv_lines.


  
READ TABLE gt_final_int INTO DATA(ls_f_intINDEX 1.

  
CALL FUNCTION 'BAPI_MATERIAL_GETINTNUMBER'
    
EXPORTING
      material_type    
ls_f_int-mtart "'ZROH'
*     INDUSTRY_SECTOR  = ' '
      required_numbers 
lv_new_mat_total
* IMPORTING
*     RETURN           =
    
TABLES
      material_number  
lt_material.



  
LOOP AT gt_final_int INTO gs_final_int.
    
MOVE-CORRESPONDING gs_final_int TO gs_final_ext.
    
READ TABLE lt_material INTO ls_material INDEX 1.
    
IF sy-subrc 0.
      gs_final_ext
-matnr ls_material-material.
    
ENDIF.
    
APPEND gs_final_ext TO gt_final.
    
DELETE lt_material WHERE material ls_material-material.
    
CLEAR gs_final_int ,gs_final_ext ls_material.
  
ENDLOOP.

*  BREAK-POINT.
ENDFORM.
**&---------------------------------------------------------------------*
**& Form F_CREATE_MATERIAL_MASTER
**&---------------------------------------------------------------------*
**& text
**&---------------------------------------------------------------------*
**& -->  p1        text
**& <--  p2        text
**&---------------------------------------------------------------------*
FORM f_create_material_master .
  
DATAls_header LIKE thead,
        lt_lines  
TYPE STANDARD TABLE OF tline WITH HEADER LINE.

  lv_line 
p_strow.
  
LOOP AT gt_final INTO gs_final.
    
CLEAR bapimathead bapi_mara bapi_marax bapi_maktbapi_marcbapi_marcx,
            bapi_mard
bapi_mardxbapi_mpopbapi_mpopxbapi_mbewbapi_mbewx,
            bapi_mvke
bapi_mvkexbapi_mlgtbapi_mlgtxbapi_mpgdbapi_mpgdx.
****************  Feeling Header data
    
IF r_ext abap_true .
      
CALL FUNCTION 'CONVERSION_EXIT_MATN1_INPUT'
        
EXPORTING
          
input  gs_final-matnr
        
IMPORTING
          
output gs_final-matnr
*     EXCEPTIONS
*         LENGTH_ERROR       = 1
*         OTHERS = 2
        
.
      
IF sy-subrc <> 0.
* Implement suitable error handling here
      
ENDIF.
    
ENDIF .
    bapimathead
-material gs_final-matnr.
    bapimathead
-material_long gs_final-matnr.
    bapimathead
-matl_type gs_final-mtart.
    bapimathead
-ind_sector 'S'.
    bapimathead
-basic_view 'X'.
    bapimathead
-sales_view 'X'.
    bapimathead
-purchase_view 'X'.
    bapimathead
-forecast_view 'X'.
    bapimathead
-storage_view 'X'.
    bapimathead
-account_view 'X'.
    bapimathead
-cost_view 'X'.
    bapimathead
-mrp_view 'X'.
    bapimathead
-work_sched_view 'X'.
    bapimathead
-quality_view 'X'.
**************  End of header data

**************  Feeling Material description : MAKT
    
REFRESH it_makt.
    wa_makt
-langu 'E'.
    wa_makt
-langu_iso 'EN'.
    wa_makt
-matl_desc gs_final-maktx.
    
APPEND wa_makt TO it_makt.
************** ENd of material description

**************  Feelinf material data : MARA
    bapi_mara
-matl_group gs_final-matkl.
    
CALL FUNCTION 'CONVERSION_EXIT_CUNIT_INPUT'
      
EXPORTING
        
input          gs_final-meins
        
language       sy-langu
      
IMPORTING
        
output         gs_final-meins
      
EXCEPTIONS
        unit_not_found 
1
        
OTHERS         2.
    
IF sy-subrc <> 0.
* Implement suitable error handling here
    
ENDIF.

    bapi_mara
-base_uom gs_final-meins.
    bapi_mara
-old_mat_no gs_final-bismt.
*BAPI_MARA- = gs_final-brgew.
    
IF gs_final-ntgew IS NOT INITIAL.
      bapi_mara
-net_weight gs_final-ntgew.

      bapi_mara
-unit_of_wt 'KG'             ." Joy gs_final-gewei.
    
ENDIF.

    bapi_mara
-division gs_final-spart.
    bapi_mara
-item_cat gs_final-mtpos_mara.
    bapi_mara
-trans_grp gs_final-tragr.
*    bapi_mara-minremlife = gs_final-mhdrz.
*    bapi_mara-shelf_life = gs_final-mhdhb.
*    bapi_mara-sled_bbd = gs_final-sled_bbd.
    bapi_mara
-var_ord_un gs_final-vabme.

*    CALL FUNCTION 'CONVERSION_EXIT_PERKZ_INPUT'
*      EXPORTING
*        input  = gs_final-iprkz
*      IMPORTING
*        output = bapi_mara-period_ind_expiration_date.

*    bapi_mara-period_ind_expiration_date = gs_final-iprkz.
    bapi_mara
-batch_mgmt gs_final-xchpf.


    bapi_marax
-matl_group =  'X'.
    bapi_marax
-base_uom =    'X'.
*    bapi_marax-old_mat_no =  'X'.
*BAPI_MARA- = gs_final-brgew.'X'.
    
IF gs_final-ntgew IS NOT INITIAL.
      bapi_marax
-net_weight =  'X'.
      bapi_marax
-unit_of_wt =  'X'.
    
ENDIF.
    bapi_marax
-division =    'X'.
    bapi_marax
-item_cat =    'X'.
    bapi_marax
-trans_grp =   'X'.
    bapi_marax
-minremlife =  'X'.
    bapi_marax
-shelf_life =  'X'.
    bapi_marax
-sled_bbd =    'X'.
    bapi_marax
-var_ord_un 'X'.
    bapi_marax
-period_ind_expiration_date 'X'.
    bapi_marax
-batch_mgmt 'X'.
    bapi_marax
-old_mat_no gs_final-bismt.



*********** Material Data at plant level  : MARC
    bapi_marc
-plant   gs_final-werks.
    bapi_marc
-ctrl_code   gs_final-steuc.
    bapi_marc
-pur_group   gs_final-ekgrp.
*    bapi_marc-profit_ctr   = gs_final-prctr.
    
CALL FUNCTION 'CONVERSION_EXIT_ALPHA_INPUT'
      
EXPORTING
        
input  gs_final-prctr
      
IMPORTING
        
output bapi_marc-profit_ctr.

    
IF gs_final-dismm 'PD' OR gs_final-dismm 'VB'.
      bapi_marc
-mrp_group   gs_final-disgr.
      bapi_marc
-mrp_type   gs_final-dismm.
      bapi_marc
-mrp_ctrler   gs_final-dispo.
      bapi_marc
-max_stock   gs_final-mabst.
      bapi_marc
-lotsizekey   gs_final-disls.
      bapi_marc
-proc_type   gs_final-beskz.
      bapi_marc
-inhseprodt   gs_final-dzeit.
    
ELSE.
      bapi_marc
-mrp_type   gs_final-dismm.
    
ENDIF.
    bapi_marc
-loadinggrp   gs_final-ladgr.

    bapi_marc
-serno_prof   gs_final-sernp.
    bapi_marc
-plnd_delry   gs_final-plifz.
    bapi_marc
-gr_pr_time   gs_final-webaz.
*    bapi_marc-period_ind   = gs_final-perkz.
*    bapi_marc-plan_strgp   = gs_final-strgr.
    bapi_marc
-availcheck   '02'."gs_final-mtvfp.
*    bapi_marc-dep_req_id   = gs_final-sbdkz.
    bapi_marc
-production_scheduler   gs_final-fevor.
    bapi_marc
-lot_size   gs_final-losgr.
*    bapi_marc-auto_p_ord   = gs_final-kautb.
    bapi_marc
-prodprof   gs_final-sfcpf.
*BAPI_MARC-   = gs_final-
*BAPI_MARC-   = gs_final-



*BAPI_MARCx-  = ='X'.
*BAPI_MARCx-  = ='X'.
*BAPI_MARCx-  = ='X'.



    bapi_marcx
-plant  gs_final-werks."'X'.
    bapi_marcx
-ctrl_code  'X'.
    bapi_marcx
-pur_group  'X'.
    bapi_marcx
-profit_ctr  'X'.
    bapi_marcx
-loadinggrp  'X'.

    
IF gs_final-dismm 'PD' OR gs_final-dismm 'VB'.
      bapi_marcx
-mrp_group  'X'.
      bapi_marcx
-mrp_type  'X'.
      bapi_marcx
-mrp_ctrler  'X'.
      bapi_marcx
-max_stock   'X'.
      bapi_marcx
-lotsizekey  'X'.
      bapi_marcx
-proc_type  'X'.
      bapi_marcx
-inhseprodt  'X'.
      bapi_marcx
-serno_prof 'X' .
    
ELSE.
      bapi_marcx
-mrp_type  'X'.
    
ENDIF.

    bapi_marcx
-plnd_delry  'X'.
    bapi_marcx
-gr_pr_time  'X'.
    bapi_marcx
-period_ind  'X'.
    bapi_marcx
-plan_strgp  'X'.
    bapi_marcx
-availcheck  'X'.
    bapi_marcx
-dep_req_id  'X'.
    bapi_marcx
-lot_size   'X'.
    bapi_marcx
-production_scheduler  'X'.
    bapi_marcx
-prodprof   'X'.
    bapi_marcx
-auto_p_ord   'X'.


    
IF gs_final-dismm 'VB'.
      bapi_marc
-reorder_pt   gs_final-minbe.
      bapi_marcx
-reorder_pt  'X'.
    
ENDIF.

************* End of Material Data at plant level  : MARC



************* Material Data at Storage Location Level : MARD
    
IF gs_final-mtart NE 'ZSRV'.
      bapi_mard
-plant  gs_final-werks.
      bapi_mard
-stge_loc  gs_final-lgort.
      bapi_mardx
-plant gs_final-werks ."'X'.
      bapi_mardx
-stge_loc gs_final-lgort ."'X'.
    
ENDIF.

************* End of Material Data at Storage Location Level : MARD

************* Forecast Parameters : MPOP
    bapi_mpop
-plant gs_final-werks.
*    bapi_mpop-fore_model = gs_final-prmod.
*    bapi_mpop-hist_vals = gs_final-peran.
*    bapi_mpop-fore_pds = gs_final-anzpr.
*    bapi_mpop-initialize = gs_final-kzini.
*    bapi_mpop-tracklimit = gs_final-siggr.
*    bapi_mpop-model_sp = gs_final-modav.

    bapi_mpopx
-plant gs_final-werks.
    bapi_mpopx
-fore_model 'X'.
    bapi_mpopx
-hist_vals 'X'.
    bapi_mpopx
-fore_pds 'X'.
    bapi_mpopx
-initialize 'X'.
    bapi_mpopx
-tracklimit 'X'.
    bapi_mpopx
-model_sp 'X'.
************* End of  Forecast Parameters : MPOP


************* TAX Data
    
REFRESH it_mlan.
    
CLEAR wa_mlan.
    wa_mlan
-depcountry 'IN'.
    wa_mlan
-depcountry_iso 'IN'.
    wa_mlan
-tax_type_1 'JOSG'.
    wa_mlan
-taxclass_1 gs_final-taxkm.
    wa_mlan
-tax_ind gs_final-taxim.
    
APPEND wa_mlan TO it_mlan.

    wa_mlan
-depcountry 'IN'.
    wa_mlan
-depcountry_iso 'IN'.
    wa_mlan
-tax_type_1 'JOCG'.
    wa_mlan
-taxclass_1 gs_final-taxkm1.
    wa_mlan
-tax_ind gs_final-taxim.
    
APPEND wa_mlan TO it_mlan.

    wa_mlan
-depcountry 'IN'.
    wa_mlan
-depcountry_iso 'IN'.
    wa_mlan
-tax_type_1 'JOIG'.
    wa_mlan
-taxclass_1 gs_final-taxkm2.
    wa_mlan
-tax_ind gs_final-taxim.
    
APPEND wa_mlan TO it_mlan.

    wa_mlan
-depcountry 'IN'.
    wa_mlan
-depcountry_iso 'IN'.
    wa_mlan
-tax_type_1 'JOUG'.
    wa_mlan
-taxclass_1 gs_final-taxkm3.
    wa_mlan
-tax_ind gs_final-taxim.
    
APPEND wa_mlan TO it_mlan.


    wa_mlan
-depcountry 'IN'.
    wa_mlan
-depcountry_iso 'IN'.
    wa_mlan
-tax_type_1 'JTC1'.
    wa_mlan
-taxclass_1 gs_final-taxkm4.
    wa_mlan
-tax_ind gs_final-taxim.
    
APPEND wa_mlan TO it_mlan.
*    wa_mlan-taxclass_2 = gs_final-taxkm1.
*    wa_mlan-taxclass_3 = gs_final-taxkm2.
*    wa_mlan-taxclass_4 = gs_final-taxkm3.


************* End of TAX Data

************* Sales Data : MVKE
    bapi_mvke
-sales_org gs_final-vkorg.
    bapi_mvke
-distr_chan gs_final-vtweg.
    bapi_mvke
-acct_assgt gs_final-ktgrm.
    bapi_mvke
-item_cat gs_final-mtpos.

    
IF r_ext abap_true.
*      bapi_mvke-matl_grp_1 = gs_final-mvgr1.
*      bapi_mvke-matl_grp_2 = gs_final-mvgr2.
*      bapi_mvke-matl_grp_3 = gs_final-mvgr3.
*      bapi_mvke-matl_grp_4 = gs_final-mvgr4.
*      bapi_mvke-matl_grp_5 = gs_final-mvgr5.
    
ENDIF.
    bapi_mvkex
-sales_org gs_final-vkorg.
    bapi_mvkex
-distr_chan gs_final-vtweg.
    bapi_mvkex
-acct_assgt  'X'.
    bapi_mvkex
-item_cat 'X'.

    
IF r_ext abap_true.

      bapi_mvkex
-matl_grp_1 'X'.
      bapi_mvkex
-matl_grp_2 'X'.
      bapi_mvkex
-matl_grp_3 'X'.
      bapi_mvkex
-matl_grp_4 'X'.
      bapi_mvkex
-matl_grp_5 'X'.
    
ENDIF.
************* End of Sales Data : MVKE


************* Valuation Area : MBEW
    bapi_mbew
-val_area gs_final-werks.
    bapi_mbew
-val_class gs_final-bklas.
    bapi_mbew
-price_ctrl gs_final-vprsv_1.
    bapi_mbew
-price_unit gs_final-peinh_1.
    bapi_mbew
-val_cat gs_final-bwtty.
*    bapi_mbew-std_price = gs_final-stprs.
    bapi_mbew
-ml_settle gs_final-mlast.
*BAPI_MBEW- = gs_final-
    bapi_mbewx
-val_area gs_final-werks.
    bapi_mbewx
-val_class 'X'.
    bapi_mbewx
-price_ctrl 'X'.
    bapi_mbewx
-price_unit 'X'.
    bapi_mbewx
-std_price 'X'.
    bapi_mbewx
-val_cat   'X'.
    bapi_mbewx
-ml_settle 'X'.

    
IF gs_final-mtart 'ZSRV'.
      bapi_mbew
-pr_ctrl_pp    'V'.
      bapi_mbewx
-pr_ctrl_pp   'X'.

      bapi_mbew
-price_ctrl    'V'.
      bapi_mbewx
-price_ctrl   'X'.

      bapi_mbew
-pr_ctrl_py    'V'.
      bapi_mbewx
-pr_ctrl_py   'X'.
    
ENDIF.

*BAPI_MBEWX- = 'X'.
************* END of Valuation Area : MBEW

************* Unit of measure
    
REFRESH it_marm it_marmx.
    
CLEAR wa_marm.

*     bapi_mara-base_uom

****     Gross weight
    wa_marm
-unit_of_wt 'KG'.  "bapi_mara-base_uom.
    wa_marm
-alt_unit bapi_mara-base_uom."'KG'.   "bapi_mara-base_uom.
    wa_marm
-gross_wt gs_final-brgew.
    
APPEND wa_marm TO it_marm.

    wa_marmx
-unit_of_wt 'KG'"bapi_mara-base_uom.
    wa_marmx
-alt_unit bapi_mara-base_uom.
    wa_marmx
-gross_wt 'X'."gs_final-brgew.
    
APPEND wa_marmx TO it_marmx.
***
*    CLEAR : wa_marm , wa_marmx.
    
IF gs_final-umren2_1 IS NOT INITIAL AND gs_final-umren3_1 IS NOT INITIAL
      
AND gs_final-umren4_1 IS NOT INITIAL AND gs_final-meinh2_1 IS NOT INITIAL.
      wa_marm
-denominatr gs_final-umren2_1.
      wa_marm
-alt_unit gs_final-umren3_1.
      wa_marm
-numerator gs_final-umren4_1.
      wa_marm
-alt_unit_iso gs_final-meinh2_1.
      
APPEND wa_marm TO it_marm.

      wa_marmx
-denominatr  'X'.
      wa_marmx
-numerator  'X'.
      wa_marmx
-alt_unit gs_final-umren3_1 .
      wa_marmx
-alt_unit_iso gs_final-meinh2_1.
      
APPEND wa_marmx TO it_marmx.
    
ELSE.
*      REFRESH: it_marm , it_marmx.
    
ENDIF.

*    wa_marm-denominatr = gs_final-umren3.
*    wa_marm-numerator = gs_final-umrez3.
*    APPEND wa_marm TO it_marm.
*
*    wa_marm-denominatr = gs_final-umren4.
*    wa_marm-numerator = gs_final-umrez4.
*    APPEND wa_marm TO it_marm.
*    wa_marm-denominatr = gs_final-.
*    APPEND wa_marm TO it_marm.


*************
    
CALL FUNCTION 'BAPI_MATERIAL_SAVEDATA'
      
EXPORTING
        headdata             
bapimathead
        clientdata           
bapi_mara
        clientdatax          
bapi_marax
        plantdata            
bapi_marc
        plantdatax           
bapi_marcx
        forecastparameters   
bapi_mpop
        forecastparametersx  
bapi_mpopx
*       PLANNINGDATA         =
*       PLANNINGDATAX        =
        storagelocationdata  
bapi_mard
        storagelocationdatax 
bapi_mardx
        valuationdata        
bapi_mbew
        valuationdatax       
bapi_mbewx
*       WAREHOUSENUMBERDATA  =
*       WAREHOUSENUMBERDATAX =
        salesdata            
bapi_mvke
        salesdatax           
bapi_mvkex
        storagetypedata      
bapi_mlgt
        storagetypedatax     
bapi_mlgtx
*       FLAG_ONLINE          = ' '
*       FLAG_CAD_CALL        = ' '
*       NO_DEQUEUE           = ' '
*       NO_ROLLBACK_WORK     = ' '
*       CLIENTDATACWM        =
*       CLIENTDATACWMX       =
*       VALUATIONDATACWM     =
*       VALUATIONDATACWMX    =
      
IMPORTING
        
return               it_return
      
TABLES
        materialdescription  
it_makt
        unitsofmeasure       
it_marm
        unitsofmeasurex      
it_marmx
*       INTERNATIONALARTNOS  =
*       MATERIALLONGTEXT     =
        taxclassifications   
it_mlan
*       RETURNMESSAGES       =
*       PRTDATA              =
*       PRTDATAX             =
*       EXTENSIONIN          =
*       EXTENSIONINX         =
*       UNITSOFMEASURECWM    =
*       UNITSOFMEASURECWMX   =
      
.

    
IF it_return-type NE 'E' .
      
CALL FUNCTION 'BAPI_TRANSACTION_COMMIT'
* EXPORTING
*   WAIT          =
* IMPORTING
*   RETURN        =
        
.
      wa_msg
-line lv_line.
      wa_msg
-message it_return-message.
      wa_msg
-message_v1 it_return-message_v1.
      wa_msg
-maktx     gs_final-maktx.
      wa_msg
-type it_return-type.

      
APPEND wa_msg TO it_msg.

      
IF gs_final-po_text1 IS NOT INITIAL.
        
CLEARls_header  .
        
REFRESH lt_lines.

        ls_header
-tdobject  'MATERIAL'.
        ls_header
-tdname    gs_final-matnr.
        ls_header
-tdid      'BEST'.
        ls_header
-tdspras   sy-langu.


        
CONCATENATE gs_final-po_text1 ' '
                   
INTO DATA(lv_textSEPARATED BY space .
        lt_lines
-tdline lv_text ."gs_final-po_text.
        
APPEND lt_lines.

        
CLEAR lv_text.
        
CONCATENATE  gs_final-po_text2 ' '
                    
INTO lv_text SEPARATED BY space .
        lt_lines
-tdline lv_text ."gs_final-po_text.
        
APPEND lt_lines.

        
CLEAR lv_text.
        
CONCATENATE  gs_final-po_text3 ' '
                  
INTO lv_text SEPARATED BY space .
        lt_lines
-tdline lv_text ."gs_final-po_text.
        
APPEND lt_lines.

        
CLEAR lv_text.
        
CONCATENATE  gs_final-po_text4 ' '
                  
INTO lv_text SEPARATED BY space .
        lt_lines
-tdline lv_text ."gs_final-po_text.
        
APPEND lt_lines.

        
CLEAR lv_text.
        
CONCATENATE  gs_final-po_text5 ' '
                  
INTO lv_text SEPARATED BY space .
        lt_lines
-tdline lv_text ."gs_final-po_text.
        
APPEND lt_lines.


        
CALL FUNCTION 'SAVE_TEXT'
          
EXPORTING
            
client          sy-mandt
            
header          ls_header
            savemode_direct 
'X'
          
TABLES
            
lines           lt_lines
          
EXCEPTIONS
            
OTHERS          1.
*    REFRESH :lt_lines.
*   CONCATENATE  gs_final-po_text3 gs_final-po_text4
*               INTO DATA(lv_text1) SEPARATED BY space .
*        lt_lines-tdline = lv_text1 ."gs_final-po_text.
*        APPEND lt_lines.
*
*        CALL FUNCTION 'SAVE_TEXT'
*          EXPORTING
*            client          = sy-mandt
*            header          = ls_header
*            savemode_direct = 'X'
*          TABLES
*            lines           = lt_lines
*          EXCEPTIONS
*            OTHERS          = 1.
      
ENDIF.
    
ELSE.
      
CALL FUNCTION 'BAPI_TRANSACTION_ROLLBACK'
*   IMPORTING
*     RETURN        =
        
.

      wa_msg
-line lv_line.
      wa_msg
-message it_return-message.
      wa_msg
-message_v1 it_return-message_v1.
      wa_msg
-type it_return-type.
      
APPEND wa_msg TO it_msg.
    
ENDIF.
*    BREAK-POINT.

    lv_line 
lv_line + 1.
  
ENDLOOP.
ENDFORM.

*&---------------------------------------------------------------------*
*& Form F_BUILD_HEADER
*&---------------------------------------------------------------------*
*& text
*&---------------------------------------------------------------------*
*& -->  p1        text
*& <--  p2        text
*&---------------------------------------------------------------------*
FORM f_build_header .
  ls_header
-f_name 'Line Number'.
  
APPEND ls_header TO lt_header.
  
CLEAR ls_header.

  ls_header
-f_name 'Type'.
  
APPEND ls_header TO lt_header.
  
CLEAR ls_header.

  ls_header
-f_name 'Material Number'.
  
APPEND ls_header TO lt_header.
  
CLEAR ls_header.

  ls_header
-f_name 'Material Desc'.
  
APPEND ls_header TO lt_header.
  
CLEAR ls_header.

  ls_header
-f_name 'Message'.
  
APPEND ls_header TO lt_header.
  
CLEAR ls_header.

  ls_header
-f_name ''.
  
APPEND ls_header TO lt_header.
  
CLEAR ls_header.
ENDFORM.
*&---------------------------------------------------------------------*
*& Form F_DOWNLOAD_MSG
*&---------------------------------------------------------------------*
*& text
*&---------------------------------------------------------------------*
*& -->  p1        text
*& <--  p2        text
*&---------------------------------------------------------------------*
FORM f_download_msg .

  
CALL METHOD cl_gui_frontend_services=>get_desktop_directory
    
CHANGING
      desktop_directory 
lv_desktop
    
EXCEPTIONS
      cntl_error        
1.
  
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 METHOD cl_gui_cfw=>update_view.


  
CONCATENATE lv_desktop '\Shakambari' '\Material Master' '\Material Upload' '_' sy-datum '_' sy-uzeit '.xls' INTO lv_desktop.
*BREAK-POINT.
  
CALL FUNCTION 'GUI_DOWNLOAD'
    
EXPORTING
*     BIN_FILESIZE            =
      filename                
lv_desktop
      filetype                
'DAT'
*     APPEND                  = 'X'
      write_field_separator   
'X'
    
TABLES
      data_tab                
it_msg
      fieldnames              
lt_header
    
EXCEPTIONS
      file_write_error        
1
      no_batch                
2
      gui_refuse_filetransfer 
3
      invalid_type            
4
      no_authority            
5
      unknown_error           
6
      header_not_allowed      
7
      separator_not_allowed   
8
      filesize_not_allowed    
9
      header_too_long         
10
      dp_error_create         
11
      dp_error_send           
12
      dp_error_write          
13
      unknown_dp_error        
14
      access_denied           
15
      dp_out_of_memory        
16
      disk_full               
17
      dp_timeout              
18
      file_not_found          
19
      dataprovider_exception  
20
      control_flush_error     
21
      
OTHERS                  22.
  
IF sy-subrc <> 0.
* Implement suitable error handling here
  
ENDIF.


ENDFORM.


Tuesday, October 6, 2020

Technical Settings While Creating A Table In ABAP Dictionary.

What Is The Importance Of Technical Settings While Creating A Table In ABAP Dictionary?

Technical settings allow you to optimize the storage requirements and table access behaviorof database tables. Technical Setting comprises of the following components:

Data Class: Designates the table to an area in the physical database where similar tables are grouped.

Size Category: Identifies the amount of disk space that will be required to hold the data records for a table in the database.

Buffering: Determines whether table records will be accessed directly from the database server or from global memory.

Logging: Creates before and after images of changes to the table of contents. Logging must be activated by the profile when the system is started.

 

Delivery Class In SAP ABAP.

What Is A Delivery Class?


Delivery Class In SAP ABAP.

Delivery Class manages the transport of table data when installing or upgrading in a client copy when transporting between customer systems. Different delivery classes available are:

  C - Customizing table, maintenance only by customer not SAP import.

 Example: Common Address Data (Country: T005)

E - Control table, SAP and customer have separate key areas, defined in TRESC

 Example: Messages (T100)

G - Customizing table, protected against SAP Upgrade

 Example: Communication: country dialing code (T005K)

L - Table for storing temporary data, delivered empty

 Example: Lock Arguments (E070USE)

S - System table maintenance only by SAP.

 Example: Language Key (T002)

A - Application table (master and transaction data)

 Example: Personal Address Data, Username (USR01)

W - System table, contents transportable via separate TR objects.

 Example: Transport (E070), Tables (DD02L) 

Differences Between Database View & Projection View in SAP ABAP.

 Database View & Projection View in SAP ABAP.



· Database view can built over many tables whereas projection view can be built over a single table only.

 Database view can be updated if the view is built over a single table whereas in projection view data can be updated.

 In case of database view, data updates can use open SQL or native SQL whereas in case of projection view, data updates must use open SQL.

 Database view can be buffered whereas Projection view cannot be buffered. 

Views In SAP ABAP.

What Are The Different Types Of Views In SAP?

Views In SAP

In SAP, you have total four types of views. Based on the way in which the view is implemented and the methods that are permitted for accessing the view data they are divided into Database View, Projection View, Maintenance View and Help View. Database views implement an Inner Join whereas Projection View, Maintenance View and Help View implement an Outer Join. There are 4 Different types of

 Views in SAP. They are:

 Maintenance View

 Database View

 Projection View

 Help View

Differences Between Transparent Tables, Pooled Tables & Cluster Tables.

What Are The Differences Between Transparent Tables, Pooled Tables & Cluster Tables?



Differences between transparent, pooled and cluster tables are:

 Transparent tables have a one to one relationship with a physical table in an underlying database where as pooled tables and cluster tables have many to one relationship with a physical table in the underlying database (Relationship between tables in ABAP Dictionary & Underlying database).

 For each transparent table there will be exactly only one table in the underlying database whereas many pooled tables are stored in a single table in an underlying database called table pool. Similarly many cluster tables are stored in a single table in the database called a table cluster

 In case of transparent tables, the underlying database table will have the same name, same number of fields and the fields will also have the same names as defined in ABAP Dictionary whereas for pooled tables and cluster tables the underlying database table will have different name, different number of fields and fields will have different names from what has been defined in ABAP Dictionary.

 Transparent tables can have one or more primary key Whereas Primary key of each pooled table of a table pool need not be same whereas Primary key of each cluster table of a table cluster should have at least one key in common.

 Secondary indexes can be created for transparent tables, but for pooled and cluster tables we cannot create any secondary index.

 Transparent tables can be accessed via both Native and Open SQL whereas pooled and cluster table can be accessed by Open SQL only.

 Transparent tables are used to hold application data which includes both master data as well as transaction data. Pooled tables reduce the amount of database resources needed when many small tables have to be opened at the same time. Cluster tables are used when the tables have primary key in common and data in these tables are all accessed simultaneously.

Cluster Tables In SAP ABAP.

What Do You Mean By Cluster Tables In SAP ABAP? Also Explain What Do You Mean By Table Cluster?



Cluster Tables In SAP ABAP.

 A cluster table is similar to a Pooled table. It has a many to one relationship with a table in an underlying database. Many cluster tables are stored in a single table in an underlying database called a table cluster.

So table cluster is similar to pooled table pool. A table cluster holds only cluster table within it.

Table clusters store data from several cluster tables based on the primary key fields that they have in common.

Rows from the cluster tables are combined into a single row in the table cluster. The rows are combined based on the part of the primary key they have in common.

The biggest advantage of cluster table and pooled table is they reduce the number of database reads and thereby improve performance.

 Tables CDPOS and CDHDR are Cluster tables in SAP ABAP Dictionary and CDCLS is the table cluster that exist in the underlying database. CDCLS table contains or hold data of both tables CDPOS and CDHDR in the underlying database.


Thursday, October 1, 2020

Remote Function Call (RFC) & types of RFC’s in SAP ABAP.

 What is Remote Function Call (RFC) & types of RFC’s?



Ans:

Ø  It is a SAP specific protocol to provide communication between different systems.

Ø  It is the process of calling Function modules from another system.

Ø  SAP Uses CPIC (Common Programming Interface for Communication) Protocol to transfer data between Systems.

                Types:

                1. Synchronous RFC: In case of this RFC both the Sender/Source and Receiver/Target                      systems should be available while distributing the data. The next part of calling program     isn’t continued until call function is completed.

            2. Asynchronous RFC: In case of this RFC both the Sender/Source and Receiver/Target                    systems should not be available while distributing the data. The next part of calling                            program is continued without completing call function.

            3. Transactional RFC (TRFC): It is almost similar to Asynchronous RFC. The Transactional              RFC is executed only once in an RFC server & save the corresponding data under unique                transaction ID in the Database.

            4. Queued RFC: In case of this RFC the multiple transactional RFC’s are serialized in the                                sequence using the Function module ‘TRFC_SET_QUEUE_NAME’.

Ø  An additional statement ‘Destination’ is used while calling Remote Enabled Functions.

What are the Enhancement Spots in SAP ABAP.

What are the Enhancement Spots?

Ans :-

Ø  The enhancement spots are used to manage explicit enhancement options that means you can add your code in standard ABAP code without need of access key, which implies that the standard code is not disturbed.

Ø  Enhancement spots specify the places where we can add our code in standard SAP.

Ø  Each enhancement spot element definition must be assigned to at least one enhancement spot.

Ø  Enhancement spots carry information about the positions at which enhancement options were created. One enhancement spot can manage several enhancement options of a Repository object. Conversely, several enhancement spots can be assigned to one enhancement option.

What are the differences between Classic (Old) BADI and New (Kernel) BADI?

 

What are the differences between Classic (Old) BADI and New (Kernel) BADI?



Ans :-

Classic or Old BADI

New or Kernel BADI

1. The standard method GET_INSTANCE of the standard class CL_EXIT_HANDLER is used to call

1. The ABAP statements GET BADI & CALL BADI are used to work with New BADI’s.

2. An interface of a BADI referred to create the Reference object

2. The definition of a BADI is referred to create the Reference object

3. It is not faster as like the Kernel BADI

3. It is faster than the Classic BADI 

4. It can be a multiple use BADI

4. It must be a single use BADI

5. The Fall back class can’t be defined

5. The Fall back class can be defined

6. It can be a Filter Dependent BADI

6. It is not possible to maintain the Filter values

What are the ways to find BADIs

 What are the ways to find BADIs.



How to find BADIs in SAP ABAP.

Ans :-

ü  Most of the Standard BADI’s are classic BADI’s.

ü  They are used to add the additional customer specific functionality/business logic to the standard programs/T-codes.

ü  There are 4 ways to find the BADI’s

                      I.        Using the standard class CL_EXITHANDLER

Ø  Execute the T-code: SE24 to maintain the global class.

Ø  Enter the standard class name CL_EXITHANDLER

Ø  Click on display button.

Ø  Double click on the method GET_INSTANCE

Ø  Set a session break point on the method GET_CLASS_NAME_BY_INTERFACE

Ø  Execute the required functional T-code Ex: MM02

Ø  Perform the required action Ex: save material

Ø  Double click on a passing parameter (EXT_NAME) to list out the corresponding BADI. Ex: BADI_MATERAIL_CHECK

                    II.        Using the T-code SE84

                   III.        Using the T-code ST05 (SQL Tracer)

                  IV.        Using the T-code SPRO

Details About BADI's in SAP ABAP.

Details About BADI's in SAP ABAP.

What are the Transaction Codes associated with BADIs?

Ans :-

           T-code SE18 & SE19: are used to work with the BADI’s

           T-code SE18: used to define the BADI’s

           T-code SE19: used to implement the BADI’


What are the types & sub types of BADIs and explain about them?

Ans :- It is used to add the additional customer specific business logic to the standard programs.

1.    Classic/Old BADI: These are mostly used in the functional areas like SD, MM, FI/CO. The standard method “GET_INSTANCE” of the standard class “CL_EXIT_HANDLER” is used to work with the classic BADI’s.

2.    Kernel/New BADI: The ABAP statements “GET BADI & CALL BADI” are used to work with New BADI’s. It is faster than Classical BADI’s.

GET BADI: This statement is used to generate a New BADI object & sets the BADI reference to the objects in the BADI reference variables.

CALL BADI: This statement is used to call the Methods of the New BADI’s.

         Subtypes:

a.    Single use BADI: The single use BADI can’t be implemented for multiple times. This BADI can have only one implementation.

b.    Multiple use BADI: The multiple use BADI’s can’t be implemented for the multiple times.

c.    Filter Dependent BADI: It is used to control the BADI implementation based on the specified filter value. The system generates an Import parameter ‘FLT_VAL’ to pass the filter values for controlling the business logic of the BADI implementation.

What are the ways to find the Exits in SAP.

 What are the ways to find the Exits?


How to find the Exits in SAP.

                      I.        Using the Package name of the applications

                    II.        Using the T-code SE84

Ø  Find the package name of the required T-code.

Ø  Execute the T-code SE84.

Ø  Expand Enhancement folder

Ø  Double click on enhancements

Ø  Enter the required package name/Exit name

Ø  Click on execute icon

                   III.        Using the Find function in standard programs.

                  IV.        Using the standard Tables  MODSAP & MODACT.