Application Development Discussions
Join the discussions or start your own on all things application development, including tools and APIs, programming models, and keeping your skills sharp.
cancel
Showing results for 
Search instead for 
Did you mean: 

please give me some sample program releated BOM

Former Member
0 Kudos

please give me some sample program releated BOM

3 REPLIES 3

Former Member
0 Kudos

Hi,

*& Module : PP |

*& Application : The program loads the Bill of Material |

*& |

----


*| Modification Log |

*| -


|

*| Programmer |

*| Change |

*| -


-


-


-


-


|

REPORT zpp0120 NO STANDARD PAGE HEADING

MESSAGE-ID z0

LINE-SIZE 132

LINE-COUNT 65(2).

----


  • Internal Tables *

----


*Internal table for the BOM file.

DATA: BEGIN OF i_bom OCCURS 0,

matnr(18),

werks(4),

stlan(1),

stlal(2),

stktx(40),

bmeng(16),

menge(16),

posnr(4),

postp(1),

meins(3),

datuv(10),

fmeng(1),

idnrk(18),

potx1(40),

ausch(7),

END OF i_bom.

  • Extracting Document and Doc type for POSTP = D.

DATA : BEGIN OF i_stpo OCCURS 1,

doknr(25),

dokar(3),

posnr(4),

stlnr LIKE mast-stlnr,

END OF i_stpo.

  • Local work area

DATA: g_my_rec_in LIKE i_bom.

    • Declare internal table for Call Transaction and BDC Session

DATA: i_bdc_table LIKE bdcdata OCCURS 0 WITH HEADER LINE.

----


  • Global Variables *

----


DATA: g_counter(2) TYPE n,

g_field_name(18) TYPE c,

zc_yes TYPE syftype VALUE 'X'.

----


  • Selection Screen *

----


SELECTION-SCREEN BEGIN OF BLOCK a WITH FRAME TITLE text-001.

PARAMETERS: p_fname1 TYPE localfile .

SELECTION-SCREEN SKIP 1.

SELECTION-SCREEN BEGIN OF BLOCK b WITH FRAME TITLE text-002.

PARAMETERS: p_rloc1 AS CHECKBOX DEFAULT 'X'.

SELECTION-SCREEN BEGIN OF BLOCK c WITH FRAME TITLE text-005.

PARAMETERS p_group(12) OBLIGATORY DEFAULT 'ZBOM'.

SELECTION-SCREEN END OF BLOCK c.

SELECTION-SCREEN END OF BLOCK b.

SELECTION-SCREEN END OF BLOCK a.

**WRITE the report header

TOP-OF-PAGE.

INCLUDE zheading.

----


  • Start of selection *

----


START-OF-SELECTION.

  • Load Input file

PERFORM f_load_input_file.

  • Create BDC records.

PERFORM create_bdc_records .

&----


*& Form Create_BDC_records

&----


  • text:* perform the BDC for the records in the internal table

----


  • --> p1 text

  • <-- p2 text

----


FORM create_bdc_records .

DATA: v_stlnr LIKE mast-stlnr.

DATA: v_postp(1) VALUE 'D'.

IF NOT i_bom[] IS INITIAL.

    • Open BDC session

PERFORM open_bdc_session.

SORT i_bom BY matnr werks posnr.

SELECT SINGLE stlnr INTO v_stlnr

FROM mast

WHERE matnr = i_bom-matnr

AND werks = i_bom-werks.

SELECT doknr dokar posnr stlnr

INTO TABLE i_stpo

FROM stpo

FOR ALL ENTRIES IN i_bom

WHERE postp = v_postp

AND posnr = i_bom-posnr

AND stlnr = v_stlnr.

SORT i_stpo BY posnr stlnr.

LOOP AT i_bom.

g_my_rec_in = i_bom.

READ TABLE i_stpo WITH KEY posnr = i_bom-posnr

stlnr = v_stlnr

BINARY SEARCH.

AT NEW matnr.

CLEAR i_bdc_table[].

PERFORM insert_screen_header.

ENDAT.

  • Setting up counter for 20 line items

IF g_counter = 20.

g_counter = 1.

ENDIF.

PERFORM bdc_field USING 'BDC_OKCODE'

'/00'.

*next screen

PERFORM bdc_dynpro USING 'SAPLCSDI' '0140'.

PERFORM bdc_field USING 'BDC_CURSOR' 'RC29P-FMENG(01)'.

PERFORM bdc_field USING 'BDC_OKCODE' '/00'.

CONCATENATE 'RC29P-POSNR(' g_counter ')' INTO g_field_name.

PERFORM bdc_field USING g_field_name i_bom-posnr.

CONCATENATE 'RC29P-IDNRK(' g_counter ')' INTO g_field_name.

PERFORM bdc_field USING g_field_name i_bom-idnrk.

CONCATENATE 'RC29P-MENGE(' g_counter ')' INTO g_field_name.

PERFORM bdc_field USING g_field_name i_bom-menge.

CONCATENATE 'RC29P-MEINS(' g_counter ')' INTO g_field_name.

PERFORM bdc_field USING g_field_name i_bom-meins.

CONCATENATE 'RC29P-POSTP(' g_counter ')' INTO g_field_name.

PERFORM bdc_field USING g_field_name i_bom-postp.

CONCATENATE 'RC29P-FMENG(' g_counter ')' INTO g_field_name.

PERFORM bdc_field USING g_field_name i_bom-fmeng.

*next screen

PERFORM bdc_dynpro USING 'SAPLCSDI' '0130'.

PERFORM bdc_field USING 'BDC_OKCODE' '/00'.

  • Check the Item category to direct the screen flow accordingly.

CASE i_bom-postp.

WHEN 'B'.

PERFORM item_text_insert.

WHEN 'Z'.

PERFORM item_text_insert.

WHEN 'T'.

PERFORM item_text_insert.

WHEN 'N'.

PERFORM bdc_field USING 'BDC_CURSOR' 'RC29P-AUSCH'.

PERFORM bdc_field USING 'RC29P-AUSCH' i_bom-ausch.

  • next screen

PERFORM item_text_insert.

*next screen

PERFORM bdc_dynpro USING 'SAPLCSDI' '0133'.

PERFORM bdc_field USING 'BDC_OKCODE' '/00'.

PERFORM bdc_field USING 'RC29P-EKORG' ' '.

WHEN 'D'.

PERFORM bdc_field USING 'RC29P-DOKNR' i_stpo-doknr.

PERFORM bdc_field USING 'RC29P-DOKAR' i_stpo-dokar.

  • next screen

PERFORM item_text_insert.

  • When POSTP = X, L.

WHEN OTHERS.

PERFORM bdc_field USING 'BDC_CURSOR' 'RC29P-AUSCH'.

PERFORM bdc_field USING 'RC29P-AUSCH' i_bom-ausch.

  • next screen

PERFORM item_text_insert.

ENDCASE.

g_counter = g_counter + 1.

  • next screen

PERFORM bdc_dynpro USING 'SAPLCSDI' '0140'.

PERFORM bdc_field USING 'BDC_CURSOR' 'RC29P-POSNR(01)'.

PERFORM bdc_field USING 'BDC_OKCODE' '=FCBU'.

AT END OF matnr.

PERFORM insert_bdc_new.

ENDAT.

ENDLOOP.

CLEAR i_bom[].

PERFORM close_bdc_session.

    • Release the BDC sessions created

PERFORM release_bdc.

ENDIF.

ENDFORM. " open_group

&----


*& Form bdc_dynpro_start

&----


  • Initialize the screen

----


  • -->P_G_PROGRAM_1

  • -->P_G_SCREEN

----


FORM bdc_dynpro USING p_g_program_1

p_g_screen.

CLEAR i_bdc_table.

i_bdc_table-program = p_g_program_1.

i_bdc_table-dynpro = p_g_screen.

i_bdc_table-dynbegin = 'X'.

APPEND i_bdc_table.

ENDFORM. " bdc_dynpro_start

&----


*& Form bdc_field

----


  • Insert field *

----


FORM bdc_field USING f_name f_value.

CLEAR i_bdc_table.

i_bdc_table-fnam = f_name.

i_bdc_table-fval = f_value.

APPEND i_bdc_table.

ENDFORM. "bdc_insert_field

&----


*& Form open_bdc_session

&----


  • Open the BDC session

----


FORM open_bdc_session .

    • Open BDC session and creat and update condition records

CALL FUNCTION 'BDC_OPEN_GROUP'

EXPORTING

client = sy-mandt

  • DEST = FILLER8

group = p_group

  • HOLDDATE = FILLER8

keep = 'X'

user = sy-uname

  • RECORD = FILLER1

  • PROG = SY-CPROG

  • IMPORTING

  • QID =

EXCEPTIONS

client_invalid = 1

destination_invalid = 2

group_invalid = 3

group_is_locked = 4

holddate_invalid = 5

internal_error = 6

queue_error = 7

running = 8

system_lock_error = 9

user_invalid = 10

OTHERS = 11

.

IF sy-subrc <> 0.

MESSAGE ID sy-msgid TYPE sy-msgty NUMBER sy-msgno

WITH sy-msgv1 sy-msgv2 sy-msgv3 sy-msgv4.

ENDIF.

ENDFORM. " create_bdc_session

&----


*& Form insert_screen_header

&----


  • Insert the Header data into the screens

----


FORM insert_screen_header .

g_counter = 1.

PERFORM bdc_dynpro USING 'SAPLCSDI' '0100'.

PERFORM bdc_field USING 'BDC_CURSOR' 'RC29N-STLAL'.

PERFORM bdc_field USING 'BDC_OKCODE' '/00'.

PERFORM bdc_field USING 'RC29N-MATNR' g_my_rec_in-matnr.

PERFORM bdc_field USING 'RC29N-WERKS' g_my_rec_in-werks.

PERFORM bdc_field USING 'RC29N-STLAN' g_my_rec_in-stlan.

PERFORM bdc_field USING 'RC29N-STLAL' g_my_rec_in-stlal.

PERFORM bdc_field USING 'RC29N-DATUV' g_my_rec_in-datuv.

  • next screen

PERFORM bdc_dynpro USING 'SAPLCSDI' '0110'.

PERFORM bdc_field USING 'BDC_CURSOR' 'RC29K-BMENG'.

PERFORM bdc_field USING 'BDC_OKCODE' '/00'.

PERFORM bdc_field USING 'RC29K-STKTX' g_my_rec_in-stktx.

PERFORM bdc_field USING 'RC29K-BMENG' g_my_rec_in-bmeng.

*next screen

PERFORM bdc_dynpro USING 'SAPLCSDI' '0111'.

PERFORM bdc_field USING 'BDC_CURSOR' 'RC29K-LABOR'.

ENDFORM. " insert_screen_header

&----


*& Form insert_bdc

&----


  • Insert the BDC session

----


FORM insert_bdc_new .

CALL FUNCTION 'BDC_INSERT'

EXPORTING

tcode = 'CS01'

  • POST_LOCAL = NOVBLOCAL

  • PRINTING = NOPRINT

  • SIMUBATCH = ' '

  • CTUPARAMS = ' '

TABLES

dynprotab = i_bdc_table

EXCEPTIONS

internal_error = 1

not_open = 2

queue_error = 3

tcode_invalid = 4

printing_invalid = 5

posting_invalid = 6

OTHERS = 7

.

IF sy-subrc <> 0.

MESSAGE ID sy-msgid TYPE sy-msgty NUMBER sy-msgno

WITH sy-msgv1 sy-msgv2 sy-msgv3 sy-msgv4.

ENDIF.

CLEAR i_bdc_table[].

ENDFORM. " insert_bdc

&----


*& Form close_bdc_session

&----


  • Close the BDC session

----


FORM close_bdc_session .

CALL FUNCTION 'BDC_CLOSE_GROUP'

EXCEPTIONS

not_open = 1

queue_error = 2

OTHERS = 3.

IF sy-subrc <> 0.

MESSAGE ID sy-msgid TYPE sy-msgty NUMBER sy-msgno

WITH sy-msgv1 sy-msgv2 sy-msgv3 sy-msgv4.

ENDIF.

ENDFORM. " close_bdc_session

&----


*& Form f_load_input_file

&----


  • Load the file into the Internal table

----


FORM f_load_input_file.

IF p_rloc1 = zc_yes.

CALL FUNCTION 'WS_UPLOAD'

EXPORTING

filename = p_fname1

filetype = 'DAT'

TABLES

data_tab = i_bom

EXCEPTIONS

conversion_error = 1

file_open_error = 2

file_read_error = 3

invalid_type = 4

no_batch = 5

unknown_error = 6

invalid_table_width = 7

gui_refuse_filetransfer = 8

customer_error = 9

OTHERS = 10.

IF sy-subrc <> 0.

MESSAGE ID sy-msgid TYPE sy-msgty NUMBER sy-msgno

WITH sy-msgv1 sy-msgv2 sy-msgv3 sy-msgv4.

STOP.

ENDIF.

ENDIF.

ENDFORM. " f_load_input_file

&----


*& Form release_bdc

&----


  • Release BDC session

----


FORM release_bdc.

SUBMIT rsbdcsub WITH mappe EQ p_group

WITH von EQ sy-datum

WITH bis EQ sy-datum

WITH fehler EQ '.'

EXPORTING LIST TO MEMORY

AND RETURN.

ENDFORM. " release_bdc

&----


*& Form item_text_insert

&----


  • Repetitive code in the screen flow

----


FORM item_text_insert.

PERFORM bdc_dynpro USING 'SAPLCSDI' '0131'.

PERFORM bdc_field USING 'BDC_OKCODE' '/00'.

PERFORM bdc_field USING 'BDC_CURSOR' 'RC29P-POTX1'.

PERFORM bdc_field USING 'RC29P-POTX1' i_bom-potx1.

ENDFORM. " item_text_insert

Former Member
0 Kudos

Hello Kannan,

check out the following program

BCALV_TREE_DEMO

Former Member
0 Kudos
*&---------------------------------------------------------------------*
*& Report  ZPPSV_BOMDETAILS                                            *
*&                                                                     *
*&---------------------------------------------------------------------*
*&                                                                     *
*&                                                                     *
*&---------------------------------------------------------------------*

report  zppsv_bomdetails no standard page heading line-count 55(1)
line-size 292.

tables : mara, mast, stko,makt, t001w, mbew, marc, keko, t023t, cskt.

data : begin of itab occurs 0,
           matnr like mast-matnr,
           werks like mast-werks,
           meins like mara-meins,
           kalnr like keko-kalnr,
           kadky like keko-kadky,
           tvers like keko-tvers,
           klvar like keko-klvar,
       end of itab.

types: begin of ck_strukturtab_typ,
       stufe type i,                          "Aufloesungstufe
       losgr like keko-losgr,                 "Losgroesse bei Mat.
       meins like keko-meins,                 "Mengeneinheit Losgroesse
       kurst like keko-kurst,                 "Kurstyp,      "P40K059138
       asl   like keko-asl,                   "ASL-Kalkulation "E40CROB
       arbpl like rcr01-arbpl,                "Arbeitsplatz bei Eigenl.
       baltkz like keko-baltkz,               "Kz. Beschaffungsaltern.
       klvar like keko-klvar,                 "KalkVariante  "P30K129325
       no_itemization type c,                 "Kz. 'Mat. ohne Einzeln.'
       no_authority type c,                   "keine Anz.Berecht. E40ROB
       no_cumulation type c,                  "Kz. 'nicht kumulieren'
       recosted type c,                       "nachträgl. kalk. "ALR99
       type like keko-type,                   "Konf.tes Material
       maxmsg like keko-maxmsg.               "Max. Meldungstyp "ALR99
       include structure ckkalktab.
types: recursion type c,                      "note499629
       end of ck_strukturtab_typ.
types ck_strukturtab type ck_strukturtab_typ occurs 0.

data : itstpox  like stpox occurs 0 with header line,
       itcscmat like cscmat occurs 0 with header line,
       it1 type ck_strukturtab.

data : mstufe like stpox-stufe,
       j(3) type c,
       i(1)  type n,
       fdate type d,
       tdate type d,
       x(10) type c,
       mtext(20) type c,
       mtext1(5) type c,
       mebeln like ekko-ebeln,
       cv like cki64a-klvar.

selection-screen begin of block b2 with frame.
parameters : mb radiobutton group radi default 'X', "Material Bom
             cb radiobutton group radi. "Costed Bom
selection-screen end of block b2.
selection-screen begin of block b1 with frame title text-001.
select-options : matnr for mara-matnr obligatory,
                 werks for mast-werks.
parameters     : mtart like mara-mtart obligatory default 'FERT'.
select-options : mmatnr for mara-matnr.
selection-screen begin of line.
selection-screen comment (27) text-002.
selection-screen position 32.
selection-screen comment  (5) text-003.
selection-screen position 38.
parameter fmonth(2) type n obligatory.
selection-screen comment (4) text-004.
selection-screen position 47.
parameter fyear(4) type n obligatory.
selection-screen end of line.
selection-screen end of block b1.
at selection-screen output.
  if cb = 'X'.
   loop at screen.
     if screen-name = 'FMONTH' or screen-name = 'FYEAR'.
        screen-input = 1.
        modify screen.
     endif.
   endloop.
 elseif mb = 'X'.
   loop at screen.
    if screen-name = 'FMONTH' or screen-name = 'FYEAR'.
       screen-input = 0.
       modify screen.
    endif.
   endloop.
 endif.
start-of-selection.
if cb = 'X'.
   fdate+6(2) = '01'.
   fdate+4(2) = fmonth.
   fdate+0(4) = fyear.
   call function 'ZLAST_DATE'
     exporting
      v_date          = fdate
    importing
      v_last_dt       =  tdate.
endif.
*  SELECT * INTO CORRESPONDING FIELDS OF TABLE ITAB FROM MARD
*                WHERE MATNR IN MATNR AND MTART = 'FERT'.
 select a~matnr a~meins b~werks into corresponding fields of table itab
      from mara as a inner join marc as b on a~matnr eq b~matnr
           where a~matnr in matnr and a~mtart = mtart "'FERT'
             and b~werks in werks.

  loop at itab.
    select single * from mast where matnr = itab-matnr
                                and werks = itab-werks.
    if sy-subrc ne 0.
      delete itab. continue.
    else.
      select single * from stko where stlnr = mast-stlnr
                                  and stlst = 1.
      if sy-subrc ne 0.
        delete itab. continue.
      endif.
    endif.
    if cb = 'X'.
       select single * from keko where bzobj = '0' and
                                       kadky ge fdate and
                                       kadky le tdate and
                                       matnr = itab-matnr and
                                       werks = itab-werks and
                                       feh_sta = 'FR'.
       if sy-subrc ne 0.
          delete itab.
          continue.
       endif.
       itab-kalnr = keko-kalnr.
       itab-kadky = keko-kadky.
       itab-tvers = keko-tvers.
       itab-klvar = keko-klvar.
       modify itab.
    endif.
  endloop.

  loop at itab.
    if mb = 'X'.
    call function 'CS_BOM_EXPL_MAT_V2'
  exporting
*   FTREL                       = ' '
*   ALEKZ                       = ' '
*   ALTVO                       = ' '
*   AUFSW                       = ' '
*   AUMGB                       = ' '
*   AUMNG                       = 0
*   AUSKZ                       = ' '
*   AMIND                       = ' '
*   BAGRP                       = ' '
*   BEIKZ                       = ' '
*   BESSL                       = ' '
*   BGIXO                       = ' '
*   BREMS                       = 'X' "Commented for All the level
    capid                       = 'PP01'
*   CHLST                       = ' '
*   COSPR                       = ' '
*   CUOBJ                       = 000000000000000
*   CUOVS                       = 0
*   CUOLS                       = ' '
    datuv                       = sy-datum                  "mdate1
*   DELNL                       = ' '
*   DRLDT                       = ' '
*   EHNDL                       = ' '
*   EMENG                       = 0
*   ERSKZ                       = ' '
*   ERSSL                       = ' '
*   FBSTP                       = ' '
*   KNFBA                       = ' '
*   KSBVO                       = ' '
*   MBWLS                       = ' '
    mktls                       = ' '
*   MDMPS                       = ' '
    mehrs                       = 'X'
*   MKMAT                       = ' '
*   MMAPS                       = ' '
*   SALWW                       = ' '
*   SPLWW                       = ' '
    mmory                       = '1'
    mtnrv                       = itab-matnr
*   NLINK                       = ' '
*   POSTP                       = ' '
*   RNDKZ                       = ' '
*   RVREL                       = ' '
*   SANFR                       = ' '
*   SANIN                       = ' '
*   SANKA                       = ' '
*   SANKO                       = ' '
*   SANVS                       = ' '
*   SCHGT                       = ' '
*   STKKZ                       = ' '
*   STLAL                       = ' '
*   STLAN                       = ' '
*   STPST                       = 0
*   SVWVO                       = ' '
    werks                       = itab-werks
*   NORVL                       = ' '
*   MDNOT                       = ' '
*   PANOT                       = ' '
*   QVERW                       = ' '
*   VERID                       = ' '
*   VRSVO                       = ' '
* IMPORTING
*   TOPMAT                      =
*   DSTST                       =
   tables
     stb                         = itstpox
     matcat                      = itcscmat
  exceptions
    alt_not_found               = 1
    call_invalid                = 2
    material_not_found          = 3
    missing_authorization       = 4
    no_bom_found                = 5
    no_plant_data               = 6
    no_suitable_bom_found       = 7
    conversion_error            = 8
    others                      = 9.
    if sy-subrc <> 0.
* MESSAGE ID SY-MSGID TYPE SY-MSGTY NUMBER SY-MSGNO
*         WITH SY-MSGV1 SY-MSGV2 SY-MSGV3 SY-MSGV4.
    endif.
    if not ( itstpox[] is initial ).
      perform prnt_dtl.
    endif.
  elseif cb = 'X'.
         concatenate itab-kadky+6(2) '.' itab-kadky+4(2) '.'
         itab-kadky+0(4) into x.
         cv = 'PPC1'.
     call function 'CK_F_CSTG_STRUCTURE_EXPLOSION'
       exporting
         klvar                       = cv
         kalnr                       = itab-kalnr
         kadky                       = itab-kadky
         tvers                       = itab-tvers
         werk                        = itab-werks
*        SICHT                       = '01'
*        S_LOSGR                     = ' '
*        S_BEZUGSMENGE               =
*        S_BEZUGSMENGENEINHEIT       =
*        S_ACCEPT_NULLMENGE          = ' '
*        S_AUFLOESUNGSTIEFE          =
*        S_READ_ONLY_DB              = 'X'
*        S_ONLY_MAT_POS              = ' '
*        S_EXPLODE_KF_TOO            = ' '
*        S_EXPLODE_RAW               = ' '
*        S_SKIP_TOTALS               = 'X'
*        S_USE_KKE3_CACHE            = ' '
*        S_EXPLODE_BPO               = ' '
*        S_VUC_READ_ONLY_DB          = ' '
*      IMPORTING
*        F_KEKO                      =
*        F_HEADER_MAT                =
*        S_AUFL_UNVOLLSTAENDIG       =
       tables
         strukturtabelle             = it1
*        T_KEKO_IMP                  =
      exceptions
        invalid_bzobj               = 1
        keko_not_found              = 2
        meta_model_error            = 3
        ckhs_not_found              = 4
        others                      = 5.
     if sy-subrc <> 0.
* MESSAGE ID SY-MSGID TYPE SY-MSGTY NUMBER SY-MSGNO
*         WITH SY-MSGV1 SY-MSGV2 SY-MSGV3 SY-MSGV4.
     endif.
     if not ( it1[] is initial ).
        perform prnt_dtl1.
     endif.
  endif.
    uline.
  endloop.

top-of-page.
if mb = 'X'.
   new-page line-size 206.
endif.
  write :/1 'TAFE Ltd'.
  if mb = 'X'.
     write : 10(130) 'BOM Details ' centered.
  elseif cb = 'X'.
     write : 10(130) 'COSTED BOM Details ' centered.
  endif.
  write : /1 'Run Date : ',sy-datum,120 'Page : ',sy-pagno.
  if mb = 'X'.
     uline at 1(106).
  else.
     uline.
  endif.
*  WRITE : /1 'Material',44 SY-VLINE,
*          45 'Description',75 SY-VLINE,
*          76 'Quantity',89 SY-VLINE,'UOM',100 SY-VLINE.
  write :/1 sy-vline,
          2 'PLANT',7 sy-vline,
          8(18)  'MODEL',27 sy-vline,
          28(18) 'MATERIAL',47 sy-vline,
          48(30) 'DESCRIPTION',79 sy-vline,
          80(12) 'QUANTITY' centered,93 sy-vline,
          94(5)  'UOM',100 sy-vline,
          101(7)  'PR CTRL',109 sy-vline,
        110(13)  'PRICE' centered,124 sy-vline,
        125(10)  'PROC TYPE',136 sy-vline,
        137(10)  'SPL PROC',148 sy-vline,
        149(14) 'Standard cost',164 sy-vline.
if mb = 'X'.
   write : 165(13) 'ECM No',179 sy-vline,
        180(10) 'ECM Date',191 sy-vline,
        192(14) 'A/C View Ind',206 sy-vline.
elseif cb = 'X'.
       write : 165(9) 'Matl.GRP',175 sy-vline,176(20) 'Matl.GRP Description',197 sy-vline,
            198(10) 'Act.Typ',209 sy-vline, 210(10) 'Cost Center',221 sy-vline,
            222(20) 'Cost Center Desc.',243 sy-vline,244(20) 'Text',265 sy-vline,
            266(5) 'PO ind',272 sy-vline,273(18) 'Output Material',292 sy-vline.
endif.
if mb = 'X'.
   uline at 1(206).
else.
  uline.
endif.
*&---------------------------------------------------------------------*
*&      Form  GET_COLOR_RESET
*&---------------------------------------------------------------------*
*       text
*----------------------------------------------------------------------*
*  -->  p1        text
*  <--  p2        text
*----------------------------------------------------------------------*
*FORM GET_COLOR_RESET .
**IF ITSTPOX-STUFE > 7 .
**  I = 1.
**ENDIF.
*IF ITSTPOX-STUFE  = 1 OR ITSTPOX-STUFE > 7.
*  FORMAT RESET. FORMAT COLOR 1 INVERSE ON.
*ELSEIF ITSTPOX-STUFE = 2.
*  FORMAT RESET. FORMAT COLOR 2 INVERSE ON.
*ELSEIF ITSTPOX-STUFE = 3.
*  FORMAT RESET. FORMAT COLOR 3 INVERSE ON.
*ELSEIF ITSTPOX-STUFE = 4.
*  FORMAT RESET. FORMAT COLOR 4 INVERSE ON.
*ELSEIF ITSTPOX-STUFE = 5.
*  FORMAT RESET. FORMAT COLOR 5 INVERSE ON.
*ELSEIF ITSTPOX-STUFE = 6.
*  FORMAT RESET. FORMAT COLOR 6 INVERSE ON.
*ELSEIF ITSTPOX-STUFE = 7.
*  FORMAT RESET. FORMAT COLOR 7 INVERSE ON.
*ENDIF.
*ENDFORM.                    " GET_COLOR_RESET
*
*END-OF-PAGE.
*ULINE.
*&---------------------------------------------------------------------*
*&      Form  PRNT_DTL
*&---------------------------------------------------------------------*
*       text
*----------------------------------------------------------------------*
*  -->  p1        text
*  <--  p2        text
*----------------------------------------------------------------------*
form prnt_dtl .
  loop at itstpox where idnrk in mmatnr.
    set left scroll-boundary column 79.
    select single * from makt where matnr = itstpox-idnrk.
    select single * from mbew where matnr = itstpox-idnrk
                                and bwkey = itab-werks.
    select single * from marc where matnr = itstpox-idnrk
                                and werks = itab-werks.
    write :/1 sy-vline,
            2(4) itab-werks,7 sy-vline,
            8(18) itab-matnr,27 sy-vline,
            28(18) itstpox-idnrk,47 sy-vline,
            48(30) makt-maktx+0(30),79 sy-vline,
            80(12) itstpox-menge,93 sy-vline,
            94(5) itstpox-meins,100 sy-vline,
            101(7) mbew-vprsv centered,109 sy-vline.
    if mbew-vprsv = 'V'.
      write : 110(13) mbew-verpr,124 sy-vline.
    else.
      write : 110(13) mbew-stprs,124 sy-vline.
    endif.
    write : 125(10) marc-beskz centered,136 sy-vline,
            137(10) marc-sobsl centered,148 sy-vline,
*included by Karhi as per mr Velu as on 25.5.2006 starts.
            149(14) mbew-stprs,164 sy-vline,
            165(13) itstpox-aennr,179 sy-vline,
            180 itstpox-datuv,191 sy-vline.
       if mbew-lplpr = 0 and mbew-stprs = 0 and mbew-vprsv = 'V'.
         write:192(14) 'X'.
       endif.
       write : 206 sy-vline.
*included by Karhi as per mr Velu as on 25.5.2006 ends.
  endloop.
endform.                    " PRNT_DTL

end-of-page.
  uline.
*&---------------------------------------------------------------------*
*&      Form  prnt_dtl1
*&---------------------------------------------------------------------*
*       text
*----------------------------------------------------------------------*
*  -->  p1        text
*  <--  p2        text
*----------------------------------------------------------------------*
form prnt_dtl1 .
data : wa type ck_strukturtab_typ,
       stprs like mbew-stprs.    "Incl By G.Balakumar 30.08.2006
data : begin of irec occurs 0,
          ikalka like keko-kalka,
          ikalnr like keko-kalnr,
          imatnr like keko-matnr,
          omatnr like keko-matnr,
       end of irec.
data : begin of it2 occurs 0,
         kalka like keko-kalka,
         kalnr like keko-kalnr,
         matnr like keko-matnr,
       end of it2.
  loop at it1 into wa where matnr in mmatnr.
    clear it2.
    move wa-kalka to it2-kalka.
    move wa-kalnr to it2-kalnr.
    move wa-matnr to it2-matnr.
    append it2.
  endloop.
  loop at it1 into wa where matnr in mmatnr. " assigning <f1>.
    select single * from makt where matnr = wa-matnr.
    if sy-subrc ne 0.
       move space to makt-maktx.
    endif.
    select single * from mara where matnr = wa-matnr.
    if sy-subrc ne 0.
       move space to mara-matkl.
    endif.
    select single * from mbew where matnr = wa-matnr
                                and bwkey = itab-werks.
    if sy-subrc ne 0.
       clear : mbew-vprsv, mbew-verpr, mbew-stprs.
    endif.
    select single * from marc where matnr = wa-matnr
                                and werks = itab-werks.
    if sy-subrc ne 0.
       clear : marc-beskz, marc-sobsl.
    endif.
    select single * from t023t where matkl = mara-matkl.
    if sy-subrc ne 0.
       move space to t023t-wgbez.
    endif.
    select single * from cskt where spras = 'EN' and
                                    kokrs = 'TAFE' and
                                    kostl = wa-kostl.
    if sy-subrc ne 0.
       move space to cskt-ktext.
    endif.
    clear : mebeln, mtext1.
    if marc-beskz = 'F' or marc-beskz = 'X'.
       if not ( marc-sobsl is initial ).
          read table it2 with key kalnr = wa-ukaln
                                  kalka = wa-ukalka.
          if sy-subrc eq 0.
             clear irec.
             move it2-kalka to irec-ikalka.
             move it2-kalnr to irec-ikalnr.
             move it2-matnr to irec-imatnr.
             move wa-matnr to  irec-omatnr.
             append irec.
          endif.
       endif.
       select single a~ebeln into mebeln from ( ekko as a inner join ekpo as b
                                  on a~ebeln = b~ebeln ) where a~kdatb le tdate and
                                                               a~kdate ge tdate and
                                                               b~matnr = wa-matnr and
                                                               b~werks in werks.
    endif.
   if mebeln = 0.
      mtext1 = 'No PO'.
   endif.
   if wa-matnr is initial.
      clear mtext1.
   endif.
*    if wa-meins ne space.
       read table irec with key ikalka = wa-kalka
                                ikalnr = wa-kalnr
                                imatnr = wa-matnr.
       if sy-subrc ne 0.
          move space to irec-omatnr.
       endif.
*    endif.
    set left scroll-boundary column 79.
    write :/1 sy-vline,
            2 itab-werks,7 sy-vline,
            8(18) itab-matnr,27 sy-vline,
            28(18) wa-matnr,47 sy-vline,
            48(30) makt-maktx+0(30),79 sy-vline,
            80(12) wa-menge,93 sy-vline,
            94(5) wa-meins,100 sy-vline,
            101(7) mbew-vprsv centered,109 sy-vline.
    if wa-meins = space.
       clear : mbew-verpr, mbew-stprs.
    endif.
    if mbew-vprsv = 'V'.
      write : 110(13) mbew-verpr,124 sy-vline.
    else.
      write : 110(13) mbew-stprs,124 sy-vline.
    endif.
*Incl By G.Balakumar to avoid Misposting of Standard Cost in Printing
**Date : 30.08.2006**
     stprs = wa-wrtfw_kpf.
     if wa-baugr eq 'X'.
        clear stprs.
     endif.
**End of Incl by G.Balakumar - 20.08.2006***
    clear mtext.
    if wa-strat = 3.
       mtext = 'Moving Average Price'.
    elseif wa-strat = 4.
           mtext = 'Planned Price 1'.
    endif.
    write : 125(10) marc-beskz centered,136 sy-vline,
            137(10) marc-sobsl centered,148 sy-vline,
*included by Karhi as per mr Velu as on 25.5.2006 starts.
            149(14) stprs,164 sy-vline, "mbew-stprs,
            165(9)  mara-matkl,175 sy-vline,176(20) t023t-wgbez,197 sy-vline,
            198(10) wa-lstar,209 sy-vline, 210(10) wa-kostl,221 sy-vline,
            222(20) cskt-ktext,243 sy-vline,244(20) mtext,265 sy-vline,
            266(5) mtext1,272 sy-vline,273(18) irec-omatnr,292 sy-vline.
*included by Karhi as per mr Velu as on 25.5.2006 ends.
    clear : stprs.
  endloop.
endform.                    " prnt_dtl1

Reward if usefull