How to use table control in bdc briefly?

how to use table control in bdc briefly in description manner ?

Hi friend,
here i am giving exm. code of table control.see if help full to u.
REPORT zxk_01
       NO STANDARD PAGE HEADING LINE-SIZE 255.
include bdcrecx1.
TYPES : BEGIN OF ty_data,
       line(100) TYPE c,
       END OF ty_data.
PARAMETERS: p_pcfile   LIKE ibipparms-path DEFAULT 'D:\NKS.TXT'.
DATA : g_filename    TYPE string.
TYPES : BEGIN OF ty_file,
        lifnr(16) TYPE c,                             " vendor
        bukrs(4)  TYPE c,                             "company code
        ktokk(4)   TYPE  c,                             " Acc grp
        anred(15) TYPE c,                             " Title
        name1(35) TYPE c,                             " name
        sortl(10) TYPE c,                             " search term
        stras(35) TYPE c,                             " street
        ort01(35) TYPE c,                             " city
        ort02(35) TYPE c,                             " district
        land1(3)  TYPE c,                              " country
        pfach(10) TYPE c,                             " PO BOx
        spras(2)  TYPE c,                             " language
        kunnr(10) TYPE c,                             " Customer
        vbund(6)  TYPE c,                              " trading partner
        banks(3) TYPE c,                              " BANK COUNTRY
        bankl(15) TYPE c,                             " BANK KEY
        bankn(18) TYPE c,                             " BANK ACC
        koinh(60) TYPE c,                             " ACC HOLDER
        bkont(2) TYPE c,                              " CK
        bvtyp(4) TYPE c,                              " BNKT
        bkref(20) TYPE c,                             " REFERENCE DETAILS
        namev(35)   TYPE c,                                 " first NAME
        name2(35)   TYPE c,                                 " NAME
        telf1(16) TYPE c,                                   " TELEPHONE
        abtnr(4)  TYPE c,                                   " DEPTT
        pafkt(2)  TYPE c,                                   " FUNCTION
        akont(10) TYPE c,                             " REC ACCOUNT
        zuawa(3)  TYPE c,                             " SORT KEY
        lnrze(10) TYPE c,                             "HEAD OFFICE
        fdgrv(10) TYPE c,                             " CASH MGMT GRP,
        frgrp(4)  TYPE c,                             " RELEASE GRP
        zterm(4)  TYPE c,                             " PAY TERMS
        togru(4)  TYPE c,                             " TOLERENCE GRP,
        reprf,                                        "CHECK DOUBLE INV
        zwels(10) TYPE c,                            " PAYMENTS METHODS
        zahls,                                       " PAYMENTS BLOCK
        hbkid(5)  TYPE c,                             " house bank
        zgrup(2)  TYPE c,                             " grouping key
        mahna(4)  TYPE c,                             " dunn procedure
        mansp,                                       "  DUNNING BLOCK'
        gmvdt(10) TYPE c,                            "  LEGAL DONE PROCEDURE
        lfrma(10) TYPE c,                            " DUNN RECEPIENT
        madat(10) TYPE c,                            " LAST DUNNED
        mahns(1)  TYPE c,                         " dunning level
        mgrup(2)  TYPE  c,                            " grouping key
        busab(2)  TYPE c,                             "dunning clerk
       END OF ty_file.
DATA : BEGIN OF it_xk01 OCCURS 0,
       lifnr(16) TYPE c,                             " vendor
       bukrs(4)  TYPE c,                             "company code
       ktokk(4)   TYPE  c,                             " Acc grp
       anred(15) TYPE c,                             " Title
       name1(35) TYPE c,                             " name
       sortl(10) TYPE c,                             " search term
       stras(35) TYPE c,                             " street
       ort01(35) TYPE c,                             " city
       ort02(35) TYPE c,                             " district
       land1(3)  TYPE c,                              " country
       pfach(10) TYPE c,                             " PO BOx
       spras(2)  TYPE c,                             " language
       kunnr(10) TYPE c,                             " Customer
       vbund(6)  TYPE c,                              " trading partner
       akont(10) TYPE c,                             " REC ACCOUNT
       zuawa(3)  TYPE c,                             " SORT KEY
       lnrze(10) TYPE c,                             "HEAD OFFICE
       fdgrv(10) TYPE c,                             " CASH MGMT GRP,
       frgrp(4)  TYPE c,                             " RELEASE GRP
       zterm(4)  TYPE c,                             " PAY TERMS
       togru(4)  TYPE c,                             " TOLERENCE GRP,
       reprf,                                        "CHECK DOUBLE INV
       zwels(10) TYPE c,                            " PAYMENTS METHODS
       zahls,                                       " PAYMENTS BLOCK
       hbkid(5)  TYPE c,                             " house bank
       zgrup(2)  TYPE c,                             " grouping key
       mahna(4)  TYPE c,                             " dunn procedure
       mansp,                                       "  DUNNING BLOCK'
       gmvdt(10) TYPE c,                            "  LEGAL DONE PROCEDURE
       lfrma(10) TYPE c,                            " DUNN RECEPIENT
       madat(10) TYPE c,                            " LAST DUNNED
       mahns(1)  TYPE c,                         " dunning level
       mgrup(2)  TYPE  c,                            " grouping key
       busab(2)  TYPE c,                             "dunning clerk
       END OF it_xk01.
     internal table  for bank detaiils
DATA : BEGIN OF it_bank OCCURS 0,
       banks(3) TYPE c,                              " BANK COUNTRY
       bankl(15) TYPE c,                             " BANK KEY
       bankn(18) TYPE c,                             " BANK ACC
       koinh(60) TYPE c,                             " ACC HOLDER
       bkont(2) TYPE c,                              " CK
       bvtyp(4) TYPE c,                              " BNKT
       bkref(20) TYPE c,                             " REFERENCE DETAILS
       lifnr(16) TYPE c,                             " vendor
      xezer,                                        " CHECK
       END OF it_bank.
INTERNAL TABLE FOR CONTACT PERSON
TYPES  : BEGIN OF ty_cust,
       lifnr(16) TYPE c,
       namev(35)   TYPE c,                                 " first NAME
       name1(35)   TYPE c,                                 " NAME
       telf1(16) TYPE c,                                   " TELEPHONE
       abtnr(4)  TYPE c,                                   " DEPTT
       pafkt(2)  TYPE c,                                   " FUNCTION
       END OF ty_cust.
INTERNAL TABLES DECLARATION
DATA : it_bdcdata LIKE bdcdata OCCURS 0 WITH HEADER LINE,
       it_bdcmsgcoll LIKE bdcmsgcoll OCCURS 0 WITH HEADER LINE,
       it_file TYPE TABLE OF ty_file,
       it_data TYPE TABLE OF ty_data,
       it_cust TYPE TABLE OF ty_cust.
   WORK AREAS FOR TYPES
DATA : wa_xk01 LIKE it_xk01,
       wa_data TYPE ty_data,
       wa_file TYPE ty_file,
       wa_bank LIKE it_bank,
       wa_cust TYPE ty_cust.
*CALL METHOD cl_gui_frontend_services=>gui_upload
   EXPORTING
     filename = lt_file
     filetype = 'ASC'
   CHANGING
     data_tab = iT_DATA.
IF sy-subrc <> 0.
ENDIF.
g_filename = p_pcfile.
CALL FUNCTION 'GUI_UPLOAD'
  EXPORTING
    filename                      =  g_filename "'D:\TESTDATA1_XK01.txt'
   filetype                      =  'TXT'
    has_field_separator           = 'X'
  HEADER_LENGTH                 = 0
   read_by_line                  = 'X'
  DAT_MODE                      = ' '
  CODEPAGE                      = ' '
  IGNORE_CERR                   = ABAP_TRUE
    replacement                   = ' '
  CHECK_BOM                     = ' '
  VIRUS_SCAN_PROFILE            =
  NO_AUTH_CHECK                 = ' '
IMPORTING
  FILELENGTH                    =
  HEADER                        =
  TABLES
    data_tab                      = it_file
EXCEPTIONS
   file_open_error               = 1
   file_read_error               = 2
   no_batch                      = 3
   gui_refuse_filetransfer       = 4
   invalid_type                  = 5
   no_authority                  = 6
   unknown_error                 = 7
   bad_data_format               = 8
   header_not_allowed            = 9
   separator_not_allowed         = 10
   header_too_long               = 11
   unknown_dp_error              = 12
   access_denied                 = 13
   dp_out_of_memory              = 14
   disk_full                     = 15
   dp_timeout                    = 16
   OTHERS                        = 17
IF sy-subrc <> 0.
MESSAGE ID SY-MSGID TYPE SY-MSGTY NUMBER SY-MSGNO
        WITH SY-MSGV1 SY-MSGV2 SY-MSGV3 SY-MSGV4.
ENDIF.
LOOP AT it_file INTO wa_file .
ON CHANGE OF WA_FILE-LIFNR.
  wa_xk01-lifnr =   wa_file-lifnr.
  wa_xk01-bukrs =   wa_file-bukrs.
  wa_xk01-ktokk =   wa_file-ktokk.
  wa_xk01-anred  = wa_file-anred.
  wa_xk01-name1  = wa_file-name1.
  wa_xk01-sortl  = wa_file-sortl.
  wa_xk01-stras =  wa_file-stras.
  wa_xk01-ort01 =  wa_file-ort01.
  wa_xk01-ort02 =  wa_file-ort02.
  wa_xk01-land1 =  wa_file-land1.
  wa_xk01-pfach =  wa_file-pfach.
  wa_xk01-spras =  wa_file-spras.
  wa_xk01-kunnr =  wa_file-kunnr.
  wa_xk01-vbund =  wa_file-vbund.
  wa_xk01-akont =  wa_file-akont.
  wa_xk01-zuawa =  wa_file-zuawa.
  wa_xk01-lnrze =  wa_file-lnrze.
  wa_xk01-fdgrv =  wa_file-fdgrv.
  wa_xk01-frgrp =  wa_file-frgrp.
  wa_xk01-zterm =  wa_file-zterm.
  wa_xk01-togru =  wa_file-togru.
  wa_xk01-reprf =  wa_file-reprf.
  wa_xk01-zwels =  wa_file-zwels.
  wa_xk01-zahls =  wa_file-zahls.
  wa_xk01-hbkid =  wa_file-hbkid.
  wa_xk01-zgrup =  wa_file-zgrup.
  wa_xk01-mahna =  wa_file-mahna.
  wa_xk01-mansp =  wa_file-mansp.
  wa_xk01-gmvdt =  wa_file-gmvdt.
  wa_xk01-lfrma =  wa_file-lfrma.
  wa_xk01-madat =  wa_file-madat.
  wa_xk01-mahns =  wa_file-mahns.
  wa_xk01-mgrup =  wa_file-mgrup.
  wa_xk01-busab =  wa_file-busab.
   APPEND wa_xk01 TO it_xk01.
   CLEAR : WA_XK01.
  CONTINUE.
   ENDON.
IF WA_FILE-BANKS NE ''.
  wa_bank-lifnr = wa_file-lifnr.
  wa_bank-banks  = wa_file-banks.
  wa_bank-bankl  = wa_file-bankl.
  wa_bank-bankn  = wa_file-bankn.
  wa_bank-koinh  = wa_file-koinh.
  wa_bank-bkont = wa_file-bkont.
  wa_bank-bvtyp  = wa_file-bvtyp.
  wa_bank-bkref  = wa_file-bkref.
  wa_cust-lifnr =  wa_file-lifnr.
  wa_cust-namev = wa_file-namev.
  wa_cust-name1 = wa_file-name2.
  wa_cust-telf1 = wa_file-telf1.
  wa_cust-abtnr =  wa_file-abtnr.
  wa_cust-pafkt =  wa_file-pafkt.
  APPEND wa_bank TO it_bank.
  APPEND wa_cust TO it_cust.
APPEND wa_xk01 TO it_xk01.
  CLEAR :  wa_bank , wa_cust.
ENDIF.
ENDLOOP.
START-OF-SELECTION.
  LOOP AT it_xk01 INTO wa_xk01.
    REFRESH it_bdcdata.
    PERFORM bdc_dynpro      USING 'SAPMF02K' '0100'.
    PERFORM bdc_field       USING 'BDC_CURSOR'
                                  'RF02K-KTOKK'.
    PERFORM bdc_field       USING 'BDC_OKCODE'
                                  '/00'.
    PERFORM bdc_field       USING 'RF02K-LIFNR'
                                   wa_xk01-lifnr.                                        " vendor
    PERFORM bdc_field       USING 'RF02K-BUKRS'
                                  wa_xk01-bukrs.                                        " company cpode
    PERFORM bdc_field       USING 'RF02K-KTOKK'
                                  wa_xk01-ktokk.                                        " Acc group
    PERFORM bdc_dynpro      USING 'SAPMF02K' '0110'.
    PERFORM bdc_field       USING 'BDC_CURSOR'
                                  'LFA1-SPRAS'.
    PERFORM bdc_field       USING 'BDC_OKCODE'
                                  '/00'.
    PERFORM bdc_field       USING 'LFA1-ANRED'
                                  wa_xk01-anred.                                          " title
    PERFORM bdc_field       USING 'LFA1-NAME1'
                                  wa_xk01-name1.                                        " name
    PERFORM bdc_field       USING 'LFA1-SORTL'
                                  wa_xk01-sortl.                                       "  ' search term'
    PERFORM bdc_field       USING 'LFA1-STRAS'
                                  wa_xk01-stras.                                    "street'
    PERFORM bdc_field       USING 'LFA1-PFACH'
                                  wa_xk01-pfach.                                     " po box
    PERFORM bdc_field       USING 'LFA1-ORT01'
                                  wa_xk01-ort01.                                  " city
    PERFORM bdc_field       USING 'LFA1-ORT02'
                                  wa_xk01-ort02.                                       " district
    PERFORM bdc_field       USING 'LFA1-LAND1'
                                  wa_xk01-land1.                                         " country
    PERFORM bdc_field       USING 'LFA1-SPRAS'
                                  wa_xk01-spras.                                         " language
    PERFORM bdc_dynpro      USING 'SAPMF02K' '0120'.
    PERFORM bdc_field       USING 'BDC_CURSOR'
                                  'LFA1-VBUND'.
    PERFORM bdc_field       USING 'BDC_OKCODE'
                                  '/00'.
    PERFORM bdc_field       USING 'LFA1-KUNNR'                                   " customer
                                  wa_xk01-kunnr.
    PERFORM bdc_field       USING 'LFA1-VBUND'
                                  wa_xk01-vbund.                                       " trading partner
    PERFORM bdc_dynpro      USING 'SAPMF02K' '0130'.
    PERFORM bdc_field       USING 'BDC_CURSOR'
                                  'LFBK-BKREF(01)'.
    PERFORM bdc_field       USING 'BDC_OKCODE'
                                  '=ENTR'.
    DATA : fnam(20) TYPE c,
           int      TYPE c.
    MOVE 1 TO int.
    CLEAR wa_bank.
    LOOP AT it_bank INTO wa_bank WHERE lifnr = wa_xk01-lifnr.
      CONCATENATE 'LFBK-BANKS(' int ')' INTO fnam.
      PERFORM bdc_field       USING fnam
                                    wa_bank-banks.                                           " city
      CONCATENATE 'LFBK-BANKL(' int ')' INTO fnam.
      PERFORM bdc_field       USING fnam
                                    wa_bank-bankl.
      CONCATENATE 'LFBK-BANKN(' int ')' INTO fnam.
      PERFORM bdc_field       USING fnam
                                    wa_bank-bankn.
      CONCATENATE 'LFBK-KOINH(' int ')' INTO fnam.
      PERFORM bdc_field       USING  fnam
                                    wa_bank-koinh.
      CONCATENATE 'LFBK-BKONT(' int ')' INTO fnam.
      PERFORM bdc_field       USING fnam
                                    wa_bank-bkont.
      CONCATENATE 'LFBK-BVTYP(' int ')' INTO fnam.
      PERFORM bdc_field       USING  fnam
                                    wa_bank-bvtyp.
      CONCATENATE 'LFBK-BKREF(' int ')' INTO fnam.
      PERFORM bdc_field       USING fnam
                                   wa_bank-bkref.
      int = int + 1.
    ENDLOOP.
    PERFORM bdc_dynpro      USING 'SAPMF02K' '0130'.
    PERFORM bdc_field       USING 'BDC_CURSOR'
                                  'LFBK-BANKS(01)'.
    PERFORM bdc_field       USING 'BDC_OKCODE'
                                  '=ENTR'.
    PERFORM bdc_dynpro      USING 'SAPMF02K' '0380'.
    PERFORM bdc_field       USING 'BDC_CURSOR'
                                  'KNVK-PAFKT(05)'.
    PERFORM bdc_field       USING 'BDC_OKCODE'
                                  '=ENTR'.
    DATA : fnam1(20) TYPE c,
           cnt.
    cnt = 1.
    CLEAR : wa_cust.
    LOOP AT it_cust INTO wa_cust WHERE lifnr = wa_xk01-lifnr.
      CONCATENATE 'KNVK-NAMEV(' cnt ')' INTO fnam1.
      PERFORM bdc_field       USING  fnam1
                                    wa_cust-namev.
      CONCATENATE 'KNVK-NAME1(' cnt ')' INTO fnam1.
      PERFORM bdc_field       USING  fnam1
                                     wa_cust-name1.
      CONCATENATE 'KNVK-TELF1(' cnt ')' INTO fnam1.
      PERFORM bdc_field       USING  fnam1
                                    wa_cust-telf1.
      CONCATENATE 'KNVK-ABTNR(' cnt ')' INTO fnam1.
      PERFORM bdc_field       USING  fnam1
                                   wa_cust-abtnr.
      CONCATENATE 'KNVK-PAFKT(' cnt ')' INTO fnam1.
      PERFORM bdc_field       USING fnam1
                                    wa_cust-pafkt.
      cnt = cnt + 1.
    ENDLOOP.
    PERFORM bdc_dynpro      USING 'SAPMF02K' '0380'.
    PERFORM bdc_field       USING 'BDC_CURSOR'
                                  'KNVK-NAMEV(01)'.
    PERFORM bdc_field       USING 'BDC_OKCODE'
                                  '=ENTR'.
    PERFORM bdc_dynpro      USING 'SAPMF02K' '0210'.
    PERFORM bdc_field       USING 'BDC_CURSOR'
                                  'LFB1-FRGRP'.
    PERFORM bdc_field       USING 'BDC_OKCODE'
                                  '/00'.
    PERFORM bdc_field       USING 'LFB1-AKONT'
                                  wa_xk01-akont.                           " REC aCC
    PERFORM bdc_field       USING 'LFB1-ZUAWA'
                                   wa_xk01-zuawa.                                " SORT KEY
    PERFORM bdc_field       USING 'LFB1-LNRZE'
                                   wa_xk01-lnrze.                            " HEAD OFFICE
    PERFORM bdc_field       USING 'LFB1-FDGRV'
                                  wa_xk01-fdgrv.                              " CASH MGMT GRP
    PERFORM bdc_field       USING 'LFB1-FRGRP'
                                  wa_xk01-frgrp.                          " RELEASE GRP
    PERFORM bdc_field       USING 'LFB1-CERDT'
    PERFORM bdc_dynpro      USING 'SAPMF02K' '0215'.
    PERFORM bdc_field       USING 'BDC_CURSOR'
                                  'LFB1-ZGRUP'.
    PERFORM bdc_field       USING 'BDC_OKCODE'
                                  '/00'.
    PERFORM bdc_field       USING 'LFB1-ZTERM'
                                  wa_xk01-zterm.                            " PAYMENT TERMS'
    PERFORM bdc_field       USING 'LFB1-TOGRU'
                                   wa_xk01-togru.                            " TOLERENCE GRP
    PERFORM bdc_field       USING 'LFB1-REPRF'
                                   wa_xk01-reprf.                                " CHECK DOUBLE INV
    PERFORM bdc_field       USING 'LFB1-ZWELS'
                                   wa_xk01-zwels.                            " PAYMENT METHOD
    PERFORM bdc_field       USING 'LFB1-ZAHLS'
                                   wa_xk01-zahls.                                " PAYMENT BLOCK
    PERFORM bdc_field       USING 'LFB1-HBKID'
                                   wa_xk01-hbkid.                             " HOUSE BANK
    PERFORM bdc_field       USING 'LFB1-ZGRUP'
                                   wa_xk01-zgrup.                              " GROUPING KEY
    PERFORM bdc_dynpro      USING 'SAPMF02K' '0220'.
    PERFORM bdc_field       USING 'BDC_CURSOR'
                                  'LFB5-BUSAB'.
    PERFORM bdc_field       USING 'BDC_OKCODE'
                                  '/00'.
    PERFORM bdc_field       USING 'LFB5-MAHNA'
                                   wa_xk01-mahna.                           " DUNN  PROCEDURE
    PERFORM bdc_field       USING 'LFB5-MANSP'
                                   wa_xk01-mansp.                              " DUNNING BLOCK
    PERFORM bdc_field       USING 'LFB5-LFRMA'
                                   wa_xk01-lfrma.                        " Dunn representative
    PERFORM bdc_field       USING 'LFB5-GMVDT'
                                   wa_xk01-gmvdt.                      " legal dunn proc
    PERFORM bdc_field       USING 'LFB5-MADAT'
                                   wa_xk01-madat.                      " last dunned
    PERFORM bdc_field       USING 'LFB5-MAHNS'
                                   wa_xk01-mahns.                               " dunn level
    PERFORM bdc_field       USING 'LFB5-BUSAB'
                                   wa_xk01-busab.                             "  dunning clerk
    PERFORM bdc_field       USING 'LFB1-MGRUP'
                                   wa_xk01-mgrup.                             " grouping key
    CALL TRANSACTION 'XK01' USING it_bdcdata
                           MODE  'A'.
  ENDLOOP.
Start new screen *
FORM bdc_dynpro USING program dynpro.
  CLEAR it_bdcdata.
  it_bdcdata-program = program.
  it_bdcdata-dynpro = dynpro.
  it_bdcdata-dynbegin = 'X'.
  APPEND it_bdcdata.
ENDFORM.                    "BDC_DYNPRO
Insert field
FORM bdc_field USING fnam fval TYPE any.
  CLEAR it_bdcdata.
  it_bdcdata-fnam = fnam.
  it_bdcdata-fval = fval.
  APPEND it_bdcdata.
ENDFORM. "bdc_field
*perform close_group.

Similar Messages

  • How to use table control in bdc, plz somebody tell me.

    Hi Gurus,
    Ples tell me
    how to use table control in bdc, plz somebody tell me.
    And send Sample CODE also. Thnaks in advance.

    hi,
    Table control / step loop in BDC
    Steploop and table contol is inevitable in certain transactions. When we run BDC for such transactions, we will face the situation: how many visible lines of steploop/tablecontrol are on the screen?
    Although we can always find certain method to deal with it, such as function code 'NP', 'POPO', considering some extreme situation: there is only one line visible one the screen, our BDC program should display an error message. (See transaction 'ME21', we you resize your screen to let only one row visible, you can not enter mutiple lines on this screen even you use 'NP')
    we can determine the number of visible lines on Transaction Screen from our Calling BDC program.
    Demo ABAP code has two purposes:
    1. how to determine number of visible lines and how to calculte page number;
    (the 'calpage' routine has been modify to meet general purpose usage)
    2. using field symbol in BDC program, please pay special attention to the difference
    in Static ASSIGN and Dynamic ASSIGN.
    Step1: go to screen painter to display the screen 121, then we can count the fixed line on this screen, there is 7 lines above the steploop and 2 lines below the steploop, so there are total 9 fixed lines on this screen. This means except these 9 lines, all the other line is for step loop.
    Then have a look at steploop itselp, one entry of it will occupy two lines.
    (Be careful, for table control, the head and the bottom scroll bar will possess another two fixed lines, and there is a maximum number for table line)
    Now we have : FixedLine = 9
    LoopLine = 2(for table control, LoopLine is always equal to 1)
    Step2: go to transaction itself(ME21) to see how it roll page, in ME21, the first line of new page is always occupied by the last line of last page, so it begin with index '02', but in some other case, fisrt line is empty and ready for input.
    Now we have: FirstLine = 0
    or FirstLine = 1 ( in our case, FirstLine is 1 because the first line of new page is fulfilled)
    Step3: write a subroutine calcalculating number of pages
    (here, the name of actual parameter is the same as formal parameter)
    global data: FixedLine type i, " number of fixed line on a certain screen
    LoopLine type i, " the number of lines occupied by one steploop item
    FirstLine type i, " possbile value 0 or 1, 0 stand for the first line of new " scrolling screen is empty, otherwise is 1
    Dataline type i, " number of items you will use in BDC, using DESCRIBE to get
    pageno type i, " you need to scroll screen how many times.
    line type i, " number of lines appears on the screen.
    index(2) type N, " the screen index for certain item
    begin type i, " from parameter of loop
    end type i. " to parameter of loop
    *in code sample, the DataTable-linindex stands for the table index number of this line
    form calpage using FixedLine type i (see step 1)
    LoopLine type i (see step 1)
    FirstLine type i (see step 2)
    DataLine type i ( this is the item number you will enter in transaction)
    changing pageno type i (return the number of page, depends on run-time visible line in table control/ Step Loop)
    changing line type i.(visible lines one the screen)
    data: midd type i,
    vline type i, "visible lines
    if DataLine eq 0.
    Message eXXX.
    endif.
    vline = ( sy-srows - FixedLine ) div LoopLine.
    *for table control, you should compare vline with maximum line of
    *table control, then take the small one that is min(vline, maximum)
    *here only illustrate step loop
    if FirstLine eq 0.
    pageno = DataLine div vline.
    if pageno eq 0.
    pageno = pageno + 1.
    endif.
    elseif FirstLine eq 1.
    pageno = ( DataLine - 1 ) div ( vline - 1 ) + 1.
    midd = ( DataLine - 1 ) mod ( vline - 1).
    if midd = 0 and DataLine gt 1.
    pageno = pageno - 1.
    endif.
    endif.
    line = vline.
    endform.
    Step4 write a subroutine to calculate the line index for each item.
    form calindex using Line type i (visible lines on the screen)
    FirstLine type i(see step 2)
    LineIndex type i(item index)
    changing Index type n. (index on the screen)
    if FirstLine = 0.
    index = LineIndex mod Line.
    if index = '00'.
    index = Line.
    endif.
    elseif FirstLine = 1.
    index = LineIndex mod ( Line - 1 ).
    if ( index between 1 and 0 ) and LineIndex gt 1.
    index = index + Line - 1.
    endif.
    if Line = 2.
    index = index + Line - 1.
    endif.
    endif.
    endform.
    Step5 write a subroutine to calculate the loop range.
    form calrange using Line type i ( visible lines on the screen)
    DataLine type i
    FirstLine type i
    loopindex like sy-index
    changing begin type i
    end type i.
    If FirstLine = 0.
    if loopindex = 1.
    begin = 1.
    if DataLine <= Line.
    end = DataLine.
    else.
    end = Line.
    endif.
    elseif loopindex gt 1.
    begin = Line * ( loopindex - 1 ) + 1.
    end = Line * loopindex.
    if end gt DataLine.
    end = DataLine.
    endif.
    endif.
    elseif FirstLine = 1.
    if loopindex = 1.
    begin = 1.
    if DataLine <= Line.
    end = DataLine.
    else.
    end = Line.
    endif.
    elseif loop index gt 1.
    begin = ( Line - 1 ) * ( loopindex - 1 ) + 2.
    end = ( Line - 1 ) * ( loopindex - 1 ) + Line.
    if end gt DataLine.
    end = DataLine.
    endif.
    endif.
    endif.
    endform.
    Step6
    using field sysbol in your BDC, for example: in ME21, but you should calculate each item will correponding to which index in steploop/Table Control
    form creat_bdc.
    field-symbols: , , .
    data: name1(14) value 'EKPO-EMATN(XX)',
    name2(14) value 'EKPO-MENGE(XX)',
    name3(15) value 'RM06E-SELKZ(XX)'.
    assign: name1 to ,
    name2 to ,
    name3 to .
    do pageno times.
    if sy-index gt 1
    *insert scroll page ok_code"
    endif.
    perform calrange using Line DataLine FirstLine sy-index
    changing begin end.
    loop at DataTable from begin to end.
    perform calindex using Line FirstLine DataTable-LineIndex changing Index.
    name1+11(2) = Index.
    name2+11(2) = Index.
    name3+12(2) = Index.
    perform bdcfield using DataTable-matnr.
    perform bdcfield using DataTable-menge.
    perform bdcfield using DataTable-indicator.
    endloop.
    enddo.
    example 1
    BDC table control is an area on the screen in which you can display data in tabular form. You process it using a loop. Table controls are comparable to step loop tables. While a table control consists of a single definition row, step loop blocks may extend over more than one row. Table controls are more flexible than step loops, and are intended to replace them
    When you need to handle a scenario like in sales order,it may contain more than one material,if you have more than one material We have to use table control,it will have number of columns and number of rows.
    Table controls allow you to enter, display, and modify tabular data easily on the screen
    Check this code,
    PARAMETERS: file1 LIKE rlgrap-filename.
    *Internal Table Declarations
    DATA: BEGIN OF itab OCCURS 0,
    matnr(18) TYPE c, "MaterialNumber
    werks(4) TYPE c, "Plant
    vdatu(10) TYPE c, "Valid From Date
    bdatu(10) TYPE c, "Valid To Date
    lifnr(10) TYPE c, "Vendor Number
    ekorg(4) TYPE c, "Purchasing Organization
    feskz TYPE c, "Fixed
    autet TYPE c, "MRP Indicator
    END OF itab.
    DATA: bdcdata LIKE TABLE OF bdcdata WITH HEADER LINE.
    *VARIABLES Declarations
    DATA: wa1 LIKE LINE OF itab. "Workarea for ITAB
    DATA: n TYPE i, "Check
    count TYPE i.
    DATA: cnt(2), "Counter
    wa(15). "Workarea to hold concatenatedvalue
    DATA v_msg(100).
    DATA: flag.
    DATA: file TYPE string.
    *Initialization event
    INITIALIZATION.
    *At-selection-screen event
    *To provide Input help for file name
    AT SELECTION-SCREEN ON VALUE-REQUEST FOR file1.
    CALL FUNCTION 'F4_FILENAME'
    EXPORTING
    program_name = syst-cprog
    dynpro_number = syst-dynnr
    IMPORTING
    file_name = file1.
    *START-OF-SELECTION EVENT
    START-OF-SELECTION.
    MOVE file1 TO file.
    CALL FUNCTION 'GUI_UPLOAD'
    EXPORTING
    filename = file
    filetype = 'ASC'
    has_field_separator = 'X'
    TABLES
    data_tab = itab
    EXCEPTIONS
    file_open_error = 1
    file_read_error = 2
    no_batch = 3
    gui_refuse_filetransfer = 4
    invalid_type = 5
    no_authority = 6
    unknown_error = 7
    bad_data_format = 8
    header_not_allowed = 9
    separator_not_allowed = 10
    header_too_long = 11
    unknown_dp_error = 12
    access_denied = 13
    dp_out_of_memory = 14
    disk_full = 15
    dp_timeout = 16
    OTHERS = 17.
    IF sy-subrc <> 0.
    MESSAGE ID sy-msgid TYPE sy-msgty NUMBER sy-msgno
    WITH sy-msgv1 sy-msgv2 sy-msgv3 sy-msgv4.
    ENDIF.
    *To populate BDCDATA and start data transfer
    LOOP AT itab .
    To validate Plant range
    IF itab-werks = '1000' OR itab-werks = '2000'
    OR itab-werks = '1008'.
    AT NEW werks.
    CLEAR: n.
    cnt = 1.
    PERFORM bdc_dynpro USING 'SAPLMEOR' '0200'.
    PERFORM bdc_field USING 'BDC_CURSOR'
    'EORD-MATNR'.
    PERFORM bdc_field USING 'BDC_OKCODE'
    '/00'.
    PERFORM bdc_field USING 'EORD-MATNR'
    itab-matnr.
    PERFORM bdc_field USING 'EORD-WERKS'
    itab-werks.
    PERFORM bdc_dynpro USING 'SAPLMEOR' '0205'.
    CONCATENATE 'EORD-EKORG(' cnt ')' INTO wa.
    PERFORM bdc_field USING 'BDC_CURSOR'
    wa.
    PERFORM bdc_field USING 'BDC_OKCODE'
    '=BU'.
    ENDAT.
    IF n = 12.
    READ TABLE bdcdata WITH KEY fval = '=BU'.
    bdcdata-fval = '=NS'.
    MODIFY bdcdata INDEX sy-tabix TRANSPORTING fval.
    PERFORM bdc_dynpro USING 'SAPLMEOR' '0205'.
    PERFORM bdc_field USING 'BDC_CURSOR'
    'EORD-VDATU(01)'.
    PERFORM bdc_field USING 'BDC_OKCODE'
    '=BU'.
    cnt = 2.
    n = 2.
    ENDIF.
    CONCATENATE 'EORD-VDATU(' cnt ')' INTO wa.
    PERFORM bdc_field USING wa
    itab-vdatu.
    CONCATENATE 'EORD-BDATU(' cnt ')' INTO wa.
    PERFORM bdc_field USING wa
    itab-bdatu.
    CONCATENATE 'EORD-LIFNR(' cnt ')' INTO wa.
    PERFORM bdc_field USING wa
    itab-lifnr.
    CONCATENATE 'EORD-EKORG(' cnt ')' INTO wa.
    PERFORM bdc_field USING wa
    itab-ekorg.
    CONCATENATE 'RM06W-FESKZ(' cnt ')' INTO wa.
    PERFORM bdc_field USING wa
    itab-feskz.
    CONCATENATE 'EORD-AUTET(' cnt ')' INTO wa.
    PERFORM bdc_field USING wa
    itab-autet.
    IF n <> 12.
    n = cnt.
    ENDIF.
    cnt = cnt + 1.
    AT END OF werks.
    CALL TRANSACTION 'ME01' USING bdcdata
    UPDATE 'S'
    MODE 'A'.
    CLEAR:bdcdata,bdcdata[].
    CALL FUNCTION 'FORMAT_MESSAGE'
    EXPORTING
    id = sy-msgid
    lang = 'EN'
    no = sy-msgno
    v1 = sy-msgv1
    v2 = sy-msgv2
    v3 = sy-msgv3
    v4 = sy-msgv4
    IMPORTING
    msg = v_msg.
    WRITE:/ v_msg.
    CLEAR: bdcdata,bdcdata[],flag.
    ENDAT.
    ENDIF.
    ENDLOOP.
    Start new screen *
    FORM bdc_dynpro USING program dynpro.
    CLEAR bdcdata.
    bdcdata-program = program.
    bdcdata-dynpro = dynpro.
    bdcdata-dynbegin = 'X'.
    APPEND bdcdata.
    ENDFORM.
    Insert field values
    FORM bdc_field USING fnam fval.
    IF NOT fval IS INITIAL.
    CLEAR bdcdata.
    bdcdata-fnam = fnam.
    bdcdata-fval = fval.
    APPEND bdcdata.
    ENDIF.
    CLEAR wa.
    ENDFORM.
    Sample code 2
    THis is example to upload the Bank details of the Vendor which has the TC.
    REPORT zprataptable2
    NO STANDARD PAGE HEADING LINE-SIZE 255.
    DATA : BEGIN OF itab OCCURS 0,
    i1 TYPE i,
    lifnr LIKE rf02k-lifnr,
    bukrs LIKE rf02k-bukrs,
    ekorg LIKE rf02k-ekorg,
    ktokk LIKE rf02k-ktokk,
    anred LIKE lfa1-anred,
    name1 LIKE lfa1-name1,
    sortl LIKE lfa1-sortl,
    land1 LIKE lfa1-land1,
    akont LIKE lfb1-akont,
    fdgrv LIKE lfb1-fdgrv,
    waers LIKE lfm1-waers,
    END OF itab.
    DATA : BEGIN OF jtab OCCURS 0,
    j1 TYPE i,
    banks LIKE lfbk-banks,
    bankl LIKE lfbk-bankl,
    bankn LIKE lfbk-bankn,
    END OF jtab.
    DATA : cnt(4) TYPE n.
    DATA : fdt(20) TYPE c.
    DATA : c TYPE i.
    INCLUDE bdcrecx1.
    START-OF-SELECTION.
    CALL FUNCTION 'WS_UPLOAD'
    EXPORTING
    filename = 'C:\first1.txt'
    filetype = 'DAT'
    TABLES
    data_tab = itab.
    CALL FUNCTION 'WS_UPLOAD'
    EXPORTING
    filename = 'C:\second.txt'
    filetype = 'DAT'
    TABLES
    data_tab = jtab.
    LOOP AT itab.
    PERFORM bdc_dynpro USING 'SAPMF02K' '0100'.
    PERFORM bdc_field USING 'BDC_CURSOR'
    'RF02K-KTOKK'.
    PERFORM bdc_field USING 'BDC_OKCODE'
    '/00'.
    PERFORM bdc_field USING 'RF02K-LIFNR'
    itab-lifnr.
    PERFORM bdc_field USING 'RF02K-BUKRS'
    itab-bukrs.
    PERFORM bdc_field USING 'RF02K-EKORG'
    itab-ekorg.
    PERFORM bdc_field USING 'RF02K-KTOKK'
    itab-ktokk.
    PERFORM bdc_dynpro USING 'SAPMF02K' '0110'.
    PERFORM bdc_field USING 'BDC_CURSOR'
    'LFA1-LAND1'.
    PERFORM bdc_field USING 'BDC_OKCODE'
    '/00'.
    PERFORM bdc_field USING 'LFA1-ANRED'
    itab-anred.
    PERFORM bdc_field USING 'LFA1-NAME1'
    itab-name1.
    PERFORM bdc_field USING 'LFA1-SORTL'
    itab-sortl.
    PERFORM bdc_field USING 'LFA1-LAND1'
    itab-land1.
    PERFORM bdc_dynpro USING 'SAPMF02K' '0120'.
    PERFORM bdc_field USING 'BDC_CURSOR'
    'LFA1-KUNNR'.
    PERFORM bdc_field USING 'BDC_OKCODE'
    '/00'.
    PERFORM bdc_dynpro USING 'SAPMF02K' '0130'.
    PERFORM bdc_field USING 'BDC_CURSOR'
    'LFBK-BANKN(01)'.
    PERFORM bdc_field USING 'BDC_OKCODE'
    '=ENTR'.
    cnt = 0.
    LOOP AT jtab WHERE j1 = itab-i1.
    cnt = cnt + 1.
    CONCATENATE 'LFBK-BANKS(' cnt ')' INTO fdt.
    PERFORM bdc_field USING fdt jtab-banks.
    CONCATENATE 'LFBK-BANKL(' cnt ')' INTO fdt.
    PERFORM bdc_field USING fdt jtab-bankl.
    CONCATENATE 'LFBK-BANKN(' cnt ')' INTO fdt.
    PERFORM bdc_field USING fdt jtab-bankn.
    IF cnt = 5.
    cnt = 0.
    PERFORM bdc_dynpro USING 'SAPMF02K' '0130'.
    PERFORM bdc_field USING 'BDC_CURSOR'
    'LFBK-BANKS(01)'.
    PERFORM bdc_field USING 'BDC_OKCODE'
    '=P+'.
    PERFORM bdc_dynpro USING 'SAPMF02K' '0130'.
    PERFORM bdc_field USING 'BDC_CURSOR'
    'LFBK-BANKN(02)'.
    PERFORM bdc_field USING 'BDC_OKCODE'
    '=ENTR'.
    ENDIF.
    ENDLOOP.
    PERFORM bdc_dynpro USING 'SAPMF02K' '0130'.
    PERFORM bdc_field USING 'BDC_CURSOR'
    'LFBK-BANKS(01)'.
    PERFORM bdc_field USING 'BDC_OKCODE'
    '=ENTR'.
    PERFORM bdc_dynpro USING 'SAPMF02K' '0210'.
    PERFORM bdc_field USING 'BDC_CURSOR'
    'LFB1-FDGRV'.
    PERFORM bdc_field USING 'BDC_OKCODE'
    '/00'.
    PERFORM bdc_field USING 'LFB1-AKONT'
    itab-akont.
    PERFORM bdc_field USING 'LFB1-FDGRV'
    itab-fdgrv.
    PERFORM bdc_dynpro USING 'SAPMF02K' '0215'.
    PERFORM bdc_field USING 'BDC_CURSOR'
    'LFB1-ZTERM'.
    PERFORM bdc_field USING 'BDC_OKCODE'
    '/00'.
    PERFORM bdc_dynpro USING 'SAPMF02K' '0220'.
    PERFORM bdc_field USING 'BDC_CURSOR'
    'LFB5-MAHNA'.
    PERFORM bdc_field USING 'BDC_OKCODE'
    '/00'.
    PERFORM bdc_dynpro USING 'SAPMF02K' '0310'.
    PERFORM bdc_field USING 'BDC_CURSOR'
    'LFM1-WAERS'.
    PERFORM bdc_field USING 'BDC_OKCODE'
    '/00'.
    PERFORM bdc_field USING 'LFM1-WAERS'
    itab-waers.
    PERFORM bdc_dynpro USING 'SAPMF02K' '0320'.
    PERFORM bdc_field USING 'BDC_CURSOR'
    'RF02K-LIFNR'.
    PERFORM bdc_field USING 'BDC_OKCODE'
    '=ENTR'.
    PERFORM bdc_dynpro USING 'SAPLSPO1' '0300'.
    PERFORM bdc_field USING 'BDC_OKCODE'
    '=YES'.
    PERFORM bdc_transaction USING 'XK01'.
    ENDLOOP.
    PERFORM close_group.
    Header file:
    1 63190 0001 0001 0001 mr bal188 b in 31000 a1 inr
    2 63191 0001 0001 0001 mr bal189 b in 31000 a1 inr
    TC file:
    1 in sb 11000
    1 in sb 12000
    1 in sb 13000
    1 in sb 14000
    1 in sb 15000
    1 in sb 16000
    1 in sb 17000
    1 in sb 18000
    1 in sb 19000
    1 in sb 20000
    1 in sb 21000
    1 in sb 22000
    2 in sb 21000
    2 in sb 22000
    Regards

  • How can we use TABLE CONTROL in BDC and WORK FLOW of ABAP.

    how can we use TABLE CONTROL in BDC and WORK FLOW of ABAP.?
    please explain the important questions.

    How to deal with table control / step loop in BDC
    Steploop and table contol is inevitable in certain transactions. When we run BDC for such transactions, we will face the situation: how many visible lines of steploop/tablecontrol are on the screen? Although we can always find certain method to deal with it, such as function code 'NP', 'POPO', considering some extreme situation: there is only one line visible one the screen, our BDC program should display an error message. (See transaction 'ME21', we you resize your screen to let only one row visible, you can not enter mutiple lines on this screen even you use 'NP')
    Now with the help of Poonam on sapfans.com developement forum, I find a method with which we can determine the number of visible lines on Transaction Screen from our Calling BDC program. Maybe it is useless to you, but I think it will give your some idea.
    Demo ABAP code has two purposes:
    1. how to determine number of visible lines and how to calculte page number;
    (the 'calpage' routine has been modify to meet general purpose usage)
    2. using field symbol in BDC program, please pay special attention to the difference in Static ASSIGN and Dynamic ASSIGN.
    Now I begin to describe the step to implement my method:
    (I use transaction 'ME21', screen 121 for sample,
    the method using is Call Transation Using..)
    Step1: go to screen painter to display the screen 121, then we can count the fixed line on this screen, there is 7 lines above the steploop and 2 lines below the steploop, so there are total 9 fixed lines on this screen. This means except these 9 lines, all the other line is for step loop. Then have a look at steploop itselp, one entry of it will occupy two lines.
    (Be careful, for table control, the head and the bottom scroll bar will possess another two fixed lines, and there is a maximum number for table line)
    Now we have : FixedLine = 9
                  LoopLine  = 2(for table control, LoopLine is always equal to 1)
    Step2: go to transaction itself(ME21) to see how it roll page, in ME21, the first line of new page is always occupied by the last line of last page, so it begin with index '02', but in some other case, fisrt line is empty and ready for input.
    Now we have: FirstLine = 0
              or FirstLine = 1 ( in our case, FirstLine is 1 because the first line of new page is fulfilled)
    Step3: write a subroutine calcalculating number of pages
    (here, the name of actual parameter is the same as formal parameter)
    global data:    FixedLine type i, " number of fixed line on a certain screen
                    LoopLine  type i, " the number of lines occupied by one steploop item
                    FirstLine type i, " possbile value 0 or 1, 0 stand for the first line of new                                                               " scrolling screen is empty, otherwise is 1
                    Dataline  type i, " number of items you will use in BDC, using DESCRIBE to get
                    pageno    type i, " you need to scroll screen how many times.
                    line      type i, " number of lines appears on the screen.
                    index(2)  type N, " the screen index for certain item
                    begin     type i, " from parameter of loop
                    end       type i. " to parameter of loop
    *in code sample, the DataTable-linindex stands for the table index number of this line
    form calpage using FixedLine type i (see step 1)
                       LoopLine  type i (see step 1)
                       FirstLine type i (see step 2)
                       DataLine  type i ( this is the item number you will enter in transaction)
              changing pageno    type i (return the number of page, depends on run-time visible                                                                             line in table control/ Step Loop)
              changing line      type i.(visible lines one the screen)
    data: midd type i,
          vline type i, "visible lines
    if DataLine eq 0.
       Message eXXX.
    endif.
    vline = ( sy-srows - FixedLine ) div LoopLine.
    *for table control, you should compare vline with maximum line of
    *table control, then take the small one that is min(vline, maximum)
    *here only illustrate step loop
    if FirstLine eq 0.
            pageno = DataLine div vline.
            if pageno eq 0.
               pageno = pageno + 1.
            endif.
    elseif FirstLine eq 1.
            pageno = ( DataLine - 1 ) div ( vline - 1 ) + 1.
            midd = ( DataLine - 1 ) mod ( vline - 1).
            if midd = 0 and DataLine gt 1.
                    pageno = pageno - 1.
            endif.
    endif.
    line = vline.
    endform.
    Step4 write a subroutine to calculate the line index for each item.
    form calindex using Line type i (visible lines on the screen)
                        FirstLine type i(see step 2)
                        LineIndex type i(item index)
              changing  Index type n.    (index on the screen)
      if  FirstLine = 0.
            index = LineIndex mod Line.
            if index = '00'.
                    index = Line.
            endif.
      elseif FirstLine = 1.
            index = LineIndex mod ( Line - 1 ).
            if ( index between 1 and 0 ) and LineIndex gt 1.
                    index = index + Line - 1.
            endif.
            if Line = 2.
                    index = index + Line - 1.
            endif.
    endif.
    endform.
    Step5 write a subroutine to calculate the loop range.
    form calrange using Line type i ( visible lines on the screen)
                        DataLine type i
                        FirstLine type i
                        loopindex like sy-index
            changing    begin type i
                        end type i.
    If FirstLine = 0.
       if loopindex = 1.
            begin = 1.
            if DataLine <= Line.
                    end = DataLine.
            else.
                    end = Line.
            endif.
       elseif loopindex gt 1.
            begin = Line * ( loopindex - 1 ) + 1.
            end   = Line * loopindex.
            if end gt DataLine.
               end = DataLine.
            endif.
       endif.
    elseif FirstLine = 1.
      if loopindex = 1.
            begin = 1.
            if DataLine <= Line.
                    end = DataLine.
            else.
                    end = Line.
            endif.
      elseif loop index gt 1.
            begin = ( Line - 1 ) * ( loopindex - 1 ) + 2.
            end =   ( Line - 1 ) * ( loopindex - 1 ) + Line.
            if end gt DataLine.
                    end = DataLine.
            endif.
      endif.
    endif.
    endform.
    Step6 using field sysbol in your BDC, for example: in ME21, but you should calculate each item will correponding to which index in steploop/Table Control
    form creat_bdc.
    field-symbols: <material>, <quan>, <indicator>.
    data: name1(14) value 'EKPO-EMATN(XX)',
          name2(14) value 'EKPO-MENGE(XX)',
          name3(15) value 'RM06E-SELKZ(XX)'.
    assign:         name1 to <material>,
                    name2 to <quan>,
                    name3 to <indicator>.
    do pageno times.
    if sy-index gt 1
    *insert scroll page ok_code"
    endif.
            perform calrange using Line DataLine FirstLine sy-index
                             changing begin end.
    loop at DataTable from begin to end.
            perform calindex using Line FirstLine DataTable-LineIndex changing Index.
            name1+11(2) = Index.
            name2+11(2) = Index.
            name3+12(2) = Index.
            perform bdcfield using <material> DataTable-matnr.
            perform bdcfield using <quan>     DataTable-menge.
            perform bdcfield using <indicator> DataTable-indicator.
    endloop.
    enddo.
    An example abap program of handling Table Control during bdc programming.
    REPORT zmm_bdcp_purchaseorderkb02
           NO STANDARD PAGE HEADING LINE-SIZE 255.
                    Declaring internal tables                            *
    *-----Declaring line structure
    DATA : BEGIN OF it_dummy OCCURS 0,
             dummy(255) TYPE c,
           END OF it_dummy.
    *-----Internal table for line items
    DATA :  BEGIN OF it_idata OCCURS 0,
              ematn(18),      "Material Number.
              menge(13),      "Qyantity.
              netpr(11),      "Net Price.
              werks(4),       "Plant.
              ebelp(5),       "Item Number.
            END OF it_idata.
    *-----Deep structure for header data and line items
    DATA  :  BEGIN OF it_me21 OCCURS 0,
               lifnr(10),      "Vendor A/c No.
               bsart(4),       "A/c Type.
               bedat(8),       "Date of creation of PO.
               ekorg(4),       "Purchasing Organisation.
               ekgrp(3),       "Purchasing Group.
               x_data LIKE TABLE OF it_idata,
             END OF it_me21.
    DATA  :  x_idata LIKE LINE OF it_idata.
    DATA  :  v_delimit VALUE ','.
    DATA  :  v_indx(3) TYPE n.
    DATA  :  v_fnam(30) TYPE c.
    DATA  :  v_count TYPE n.
    DATA  :  v_ne TYPE i.
    DATA  :  v_ns TYPE i.
    *include bdcrecx1.
    INCLUDE zmm_incl_purchaseorderkb01.
                    Search help for file                                 *
    AT SELECTION-SCREEN ON VALUE-REQUEST FOR p_file.
      CALL FUNCTION 'F4_FILENAME'
        EXPORTING
          program_name  = syst-cprog
          dynpro_number = syst-dynnr
        IMPORTING
          file_name     = p_file.
    START-OF-SELECTION.
           To upload the data into line structure                        *
      CALL FUNCTION 'WS_UPLOAD'
        EXPORTING
          filename = p_file
          filetype = 'DAT'
        TABLES
          data_tab = it_dummy.
        Processing the data from line structure to internal tables       *
      REFRESH:it_me21.
      CLEAR  :it_me21.
      LOOP AT it_dummy.
        IF it_dummy-dummy+0(01) = 'H'.
          v_indx = v_indx + 1.
          CLEAR   it_idata.
          REFRESH it_idata.
          CLEAR   it_me21-x_data.
          REFRESH it_me21-x_data.
          SHIFT it_dummy.
          SPLIT it_dummy AT v_delimit INTO it_me21-lifnr
                                           it_me21-bsart
                                           it_me21-bedat
                                           it_me21-ekorg
                                           it_me21-ekgrp.
          APPEND it_me21.
        ELSEIF it_dummy-dummy+0(01) = 'L'.
          SHIFT it_dummy.
          SPLIT it_dummy AT v_delimit INTO it_idata-ematn
                                           it_idata-menge
                                           it_idata-netpr
                                           it_idata-werks
                                           it_idata-ebelp.
          APPEND it_idata TO it_me21-x_data.
          MODIFY it_me21 INDEX v_indx.
        ENDIF.
      ENDLOOP.
                    To open the group                                    *
      PERFORM open_group.
            To populate the bdcdata table for header data                *
      LOOP AT it_me21.
        v_count = v_count + 1.
        REFRESH it_bdcdata.
        PERFORM subr_bdc_table USING:   'X' 'SAPMM06E'    '0100',
                                        ' ' 'BDC_CURSOR'  'EKKO-LIFNR',
                                        ' ' 'BDC_OKCODE'  '/00',
                                        ' ' 'EKKO-LIFNR'  it_me21-lifnr,
                                        ' ' 'RM06E-BSART' it_me21-bsart,
                                        ' ' 'RM06E-BEDAT' it_me21-bedat,
                                        ' ' 'EKKO-EKORG'  it_me21-ekorg,
                                        ' ' 'EKKO-EKGRP'  it_me21-ekgrp,
                                        ' ' 'RM06E-LPEIN' 'T'.
        PERFORM subr_bdc_table USING:   'X' 'SAPMM06E'    '0120',
                                        ' ' 'BDC_CURSOR'  'RM06E-EBELP',
                                        ' ' 'BDC_OKCODE'  '/00'.
        MOVE 1 TO v_indx.
    *-----To populate the bdcdata table for line item data
        LOOP AT it_me21-x_data INTO x_idata.
          CONCATENATE 'EKPO-EMATN(' v_indx ')'  INTO v_fnam.
          PERFORM  subr_bdc_table USING ' ' v_fnam x_idata-ematn.
          CONCATENATE 'EKPO-MENGE(' v_indx ')'  INTO v_fnam.
          PERFORM  subr_bdc_table USING ' ' v_fnam x_idata-menge.
          CONCATENATE 'EKPO-NETPR(' v_indx ')'  INTO v_fnam.
          PERFORM  subr_bdc_table USING ' ' v_fnam x_idata-netpr.
          CONCATENATE 'EKPO-WERKS(' v_indx ')'  INTO v_fnam.
          PERFORM  subr_bdc_table USING ' ' v_fnam x_idata-werks.
          v_indx = v_indx + 1.
          PERFORM subr_bdc_table USING:  'X' 'SAPMM06E'    '0120',
                                         ' ' 'BDC_CURSOR'  'RM06E-EBELP',
                                         ' ' 'BDC_OKCODE'  '/00'.
        ENDLOOP.
        PERFORM subr_bdc_table USING:    'X' 'SAPMM06E'    '0120',
                                         ' ' 'BDC_CURSOR'  'RM06E-EBELP',
                                         ' ' 'BDC_OKCODE'  '=BU'.
        PERFORM bdc_transaction USING 'ME21'.
      ENDLOOP.
      PERFORM close_group.
                      End of selection event                             *
    END-OF-SELECTION.
      IF session NE 'X'.
    *-----To display the successful records
        WRITE :/10  text-001.          "Sucess records
        WRITE :/10  SY-ULINE(20).
        SKIP.
        IF it_sucess IS INITIAL.
          WRITE :/  text-002.
        ELSE.
          WRITE :/   text-008,          "Total number of Succesful records
                  35 v_ns.
          SKIP.
          WRITE:/   text-003,          "Vendor Number
                 17 text-004,          "Record number
                 30 text-005.          "Message
        ENDIF.
        LOOP AT it_sucess.
          WRITE:/4  it_sucess-lifnr,
                 17 it_sucess-tabix CENTERED,
                 30 it_sucess-sucess_rec.
        ENDLOOP.
        SKIP.
    *-----To display the erroneous records
        WRITE:/10   text-006.          "Error Records
        WRITE:/10   SY-ULINE(17).
        SKIP.
        IF it_error IS INITIAL.
          WRITE:/   text-007.          "No error records
        ELSE.
          WRITE:/   text-009,          "Total number of erroneous records
                 35 v_ne.
          SKIP.
          WRITE:/   text-003,          "Vendor Number
                 17 text-004,          "Record number
                 30 text-005.          "Message
        ENDIF.
        LOOP AT it_error.
          WRITE:/4  it_error-lifnr,
                 17 it_error-tabix CENTERED,
                 30 it_error-error_rec.
        ENDLOOP.
        REFRESH it_sucess.
        REFRESH it_error.
      ENDIF.
    CODE IN INCLUDE.
    Include           ZMM_INCL_PURCHASEORDERKB01
    DATA:   it_BDCDATA LIKE BDCDATA    OCCURS 0 WITH HEADER LINE.
    DATA:   it_MESSTAB LIKE BDCMSGCOLL OCCURS 0 WITH HEADER LINE.
    DATA:   E_GROUP_OPENED.
    *-----Internal table to store sucess records
    DATA:BEGIN OF it_sucess OCCURS 0,
           msgtyp(1)   TYPE c,
           lifnr  LIKE  ekko-lifnr,
           tabix  LIKE  sy-tabix,
           sucess_rec(125),
         END OF it_sucess.
    DATA: g_mess(125) type c.
    *-----Internal table to store error records
    DATA:BEGIN OF it_error OCCURS 0,
           msgtyp(1)   TYPE c,
           lifnr  LIKE  ekko-lifnr,
           tabix  LIKE  sy-tabix,
           error_rec(125),
         END OF it_error.
           Selection screen
    SELECTION-SCREEN BEGIN OF LINE.
    PARAMETERS session RADIOBUTTON GROUP ctu.  "create session
    SELECTION-SCREEN COMMENT 3(20) text-s07 FOR FIELD session.
    SELECTION-SCREEN POSITION 45.
    PARAMETERS ctu RADIOBUTTON GROUP ctu.     "call transaction
    SELECTION-SCREEN COMMENT 48(20) text-s08 FOR FIELD ctu.
    SELECTION-SCREEN END OF LINE.
    SELECTION-SCREEN BEGIN OF LINE.
    SELECTION-SCREEN COMMENT 3(20) text-s01 FOR FIELD group.
    SELECTION-SCREEN POSITION 25.
    PARAMETERS group(12).                      "group name of session
    SELECTION-SCREEN COMMENT 48(20) text-s05 FOR FIELD ctumode.
    SELECTION-SCREEN POSITION 70.
    PARAMETERS ctumode LIKE ctu_params-dismode DEFAULT 'N'.
    "A: show all dynpros
    "E: show dynpro on error only
    "N: do not display dynpro
    SELECTION-SCREEN END OF LINE.
    SELECTION-SCREEN BEGIN OF LINE.
    SELECTION-SCREEN COMMENT 48(20) text-s06 FOR FIELD cupdate.
    SELECTION-SCREEN POSITION 70.
    PARAMETERS cupdate LIKE ctu_params-updmode DEFAULT 'L'.
    SELECTION-SCREEN END OF LINE.
    SELECTION-SCREEN BEGIN OF LINE.
    SELECTION-SCREEN COMMENT 3(20) text-s03 FOR FIELD keep.
    SELECTION-SCREEN POSITION 25.
    PARAMETERS: keep AS CHECKBOX.       "' ' = delete session if finished
    "'X' = keep   session if finished
    SELECTION-SCREEN COMMENT 48(20) text-s09 FOR FIELD e_group.
    SELECTION-SCREEN POSITION 70.
    PARAMETERS e_group(12).             "group name of error-session
    SELECTION-SCREEN END OF LINE.
    SELECTION-SCREEN BEGIN OF LINE.
    SELECTION-SCREEN COMMENT 51(17) text-s03 FOR FIELD e_keep.
    SELECTION-SCREEN POSITION 70.
    PARAMETERS: e_keep AS CHECKBOX.     "' ' = delete session if finished
    "'X' = keep   session if finished
    SELECTION-SCREEN END OF LINE.
    PARAMETERS:p_file LIKE rlgrap-filename.
      at selection screen                                                *
    AT SELECTION-SCREEN.
    group and user must be filled for create session
      IF SESSION = 'X' AND
         GROUP = SPACE. "OR USER = SPACE.
        MESSAGE E613(MS).
      ENDIF.
      create batchinput session                                          *
    FORM OPEN_GROUP.
      IF SESSION = 'X'.
        SKIP.
        WRITE: /(20) 'Create group'(I01), GROUP.
        SKIP.
    *----open batchinput group
        CALL FUNCTION 'BDC_OPEN_GROUP'
          EXPORTING
            CLIENT = SY-MANDT
            GROUP  = GROUP
            USER   = sy-uname.
        WRITE:/(30) 'BDC_OPEN_GROUP'(I02),
                (12) 'returncode:'(I05),
                     SY-SUBRC.
      ENDIF.
    ENDFORM.                    "OPEN_GROUP
      end batchinput session                                             *
    FORM CLOSE_GROUP.
      IF SESSION = 'X'.
    *------close batchinput group
        CALL FUNCTION 'BDC_CLOSE_GROUP'.
        WRITE: /(30) 'BDC_CLOSE_GROUP'(I04),
                (12) 'returncode:'(I05),
                     SY-SUBRC.
      ELSE.
        IF E_GROUP_OPENED = 'X'.
          CALL FUNCTION 'BDC_CLOSE_GROUP'.
          WRITE: /.
          WRITE: /(30) 'Fehlermappe wurde erzeugt'(I06).
        ENDIF.
      ENDIF.
    ENDFORM.                    "CLOSE_GROUP
           Start new transaction according to parameters                 *
    FORM BDC_TRANSACTION USING TCODE TYPE ANY.
      DATA: L_SUBRC LIKE SY-SUBRC.
    *------batch input session
      IF SESSION = 'X'.
        CALL FUNCTION 'BDC_INSERT'
          EXPORTING
            TCODE     = TCODE
          TABLES
            DYNPROTAB = it_BDCDATA.
        WRITE: / 'BDC_INSERT'(I03),
                 TCODE,
                 'returncode:'(I05),
                 SY-SUBRC,
                 'RECORD:',
                 SY-INDEX.
      ELSE.
        REFRESH it_MESSTAB.
        CALL TRANSACTION TCODE USING it_BDCDATA
                         MODE   CTUMODE
                         UPDATE CUPDATE
                         MESSAGES INTO it_MESSTAB.
        L_SUBRC = SY-SUBRC.
        WRITE: / 'CALL_TRANSACTION',
                 TCODE,
                 'returncode:'(I05),
                 L_SUBRC,
                 'RECORD:',
                 SY-INDEX.
      ENDIF.
      Message handling for Call Transaction                              *
      perform subr_mess_hand using g_mess.
    *-----Erzeugen fehlermappe
      IF L_SUBRC <> 0 AND E_GROUP <> SPACE.
        IF E_GROUP_OPENED = ' '.
          CALL FUNCTION 'BDC_OPEN_GROUP'
            EXPORTING
              CLIENT = SY-MANDT
              GROUP  = E_GROUP
              USER   = sy-uname
              KEEP   = E_KEEP.
          E_GROUP_OPENED = 'X'.
        ENDIF.
        CALL FUNCTION 'BDC_INSERT'
          EXPORTING
            TCODE     = TCODE
          TABLES
            DYNPROTAB = it_BDCDATA.
      ENDIF.
      REFRESH it_BDCDATA.
    ENDFORM.                    "BDC_TRANSACTION
         Form  subr_bdc_table                                            *
          text
         -->P_0220   text                                                *
         -->P_0221   text                                                *
         -->P_0222   text                                                *
    FORM subr_bdc_table  USING      VALUE(P_0220) TYPE ANY
                                    VALUE(P_0221) TYPE ANY
                                    VALUE(P_0222) TYPE ANY.
      CLEAR it_bdcdata.
      IF P_0220 = ' '.
        CLEAR it_bdcdata.
        it_bdcdata-fnam     = P_0221.
        it_bdcdata-fval     = P_0222.
        APPEND it_bdcdata.
      ELSE.
        it_bdcdata-dynbegin = P_0220.
        it_bdcdata-program  = P_0221.
        it_bdcdata-dynpro   = P_0222.
        APPEND it_bdcdata.
      ENDIF.
    ENDFORM.                    " subr_bdc_table
         Form  subr_mess_hand                                            *
          text                                                           *
         -->P_G_MESS  text                                               *
    FORM subr_mess_hand USING  P_G_MESS TYPE ANY.
      LOOP AT IT_MESSTAB.
        CALL FUNCTION 'FORMAT_MESSAGE'
          EXPORTING
            ID     = it_messtab-msgid
            LANG   = it_messtab-msgspra
            NO     = it_messtab-msgnr
            v1     = it_messtab-msgv1
            v2     = it_messtab-msgv2
          IMPORTING
            MSG    = P_G_MESS
          EXCEPTIONS
            OTHERS = 0.
        CASE it_messtab-msgtyp.
          when 'E'.
            it_error-error_rec   =  P_G_MESS.
            it_error-lifnr       =  it_me21-lifnr.
            it_error-tabix       =  v_count.
            APPEND IT_ERROR.
          when 'S'.
            it_sucess-sucess_rec =  P_G_MESS.
            it_sucess-lifnr      =  it_me21-lifnr.
            it_sucess-tabix      =  v_count.
            APPEND IT_SUCESS.
        endcase.
      ENDLOOP.
      Describe table it_sucess lines v_ns.
      Describe table it_error  lines v_ne.
    ENDFORM.                    " subr_mess_hand
    Also refer
    http://sap.ittoolbox.com/groups/technical-functional/sap-dev/bdc-table-control-668404
    and
    http://www.sap-img.com/abap/bdc-example-using-table-control-in-bdc.htm
    Regards,
    srinivas
    <b>*reward for useful answers*</b>

  • Hi abapers how to handle table control in bdc

    hi experts please guide me
    how to handle table control in bdc? could u please explain me briefly  
    thanks and regards

    sayeed,
    Go thru this code it may help you. check bold code for the table control..
    report zsunil_bdc
    no standard page heading line-size 255.
    INTERNAL TABLES *
    DATA: BEGIN OF IT_KNA1 OCCURS 0,
    CUSTOMER LIKE RF02D-KUNNR,
    COMPANY_CODE LIKE RF02D-BUKRS,
    ACCOUNT_GROUP LIKE RF02D-KTOKD,
    TITLE LIKE KNA1-ANRED,
    NAME LIKE KNA1-NAME1,
    SEARCH_TERM LIKE KNA1-SORTL,
    STREET LIKE KNA1-STRAS,
    CITY LIKE KNA1-ORT01,
    POSTAL_CODE LIKE KNA1-PSTLZ,
    COUNTRY LIKE KNA1-LAND1,
    LANGUAGE_KEY LIKE KNA1-SPRAS,
    CNTRY LIKE KNBK-BANKS,
    BANK_KEY LIKE KNBK-BANKL,
    BANK_ACCOUNT LIKE KNBK-BANKN,
    REC_ACCOUNT LIKE KNB1-AKONT,
    END OF IT_KNA1.
    DATA: IT_BDCDATA TYPE BDCDATA OCCURS 0 WITH HEADER LINE.
    DATA: IT_MESSAGES TYPE BDCMSGCOLL OCCURS 0 WITH HEADER LINE.
    SELECTION SCREEN *
    SELECTION-SCREEN BEGIN OF BLOCK B1 WITH FRAME TITLE TEXT-001.
    PARAMETER P_FILE TYPE RLGRAP-FILENAME DEFAULT 'C:\CUSTOMER.TXT'
    OBLIGATORY.
    SELECTION-SCREEN END OF BLOCK B1.
    AT SELECTION SCREEN *
    AT SELECTION-SCREEN ON VALUE-REQUEST FOR P_FILE.
    PERFORM HELP_FILE USING P_FILE.
    START OF SELECTION *
    START-OF-SELECTION.
    *UPLOADING THE FILE FROM WORKSTATION
    PERFORM UPLOAD_FILE USING P_FILE.
    *POPULATING DATA.
    PERFORM POPULATE_FILE.
    *& Form HELP_FILE
    text
    -->P_P_FILE text
    form HELP_FILE using p_p_file.
    DATA: L_FILE TYPE IBIPPARMS-PATH.
    CALL FUNCTION 'F4_FILENAME'
    EXPORTING
    PROGRAM_NAME = SYST-CPROG
    DYNPRO_NUMBER = SYST-DYNNR
    FIELD_NAME = ' '
    IMPORTING
    FILE_NAME = L_FILE.
    P_P_FILE = L_FILE.
    endform. " HELP_FILE
    *& Form UPLOAD_FILE
    text
    -->P_P_FILE text
    form UPLOAD_FILE using p_p_file.
    CALL FUNCTION 'UPLOAD'
    EXPORTING
    CODEPAGE = ' '
    FILENAME = 'P_P_FILE'
    FILETYPE = 'DAT'
    ITEM = ' '
    FILEMASK_MASK = ' '
    FILEMASK_TEXT = ' '
    FILETYPE_NO_CHANGE = ' '
    FILEMASK_ALL = ' '
    FILETYPE_NO_SHOW = ' '
    LINE_EXIT = ' '
    USER_FORM = ' '
    USER_PROG = ' '
    SILENT = 'S'
    IMPORTING
    FILESIZE =
    CANCEL =
    ACT_FILENAME =
    ACT_FILETYPE =
    TABLES
    data_tab = IT_KNA1
    EXCEPTIONS
    CONVERSION_ERROR = 1
    INVALID_TABLE_WIDTH = 2
    INVALID_TYPE = 3
    NO_BATCH = 4
    UNKNOWN_ERROR = 5
    GUI_REFUSE_FILETRANSFER = 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.
    endform. " UPLOAD_FILE
    *& Form POPULATE_FILE
    text
    --> p1 text
    <-- p2 text
    form POPULATE_FILE .
    DATA: L_STRING TYPE STRING,
    L_COUNTER(2) TYPE N,
    V_INDEX TYPE SY-TABIX.
    LOOP AT IT_KNA1.
    V_INDEX = SY-TABIX.
    AT NEW CUSTOMER.
    READ TABLE IT_KNA1 INDEX V_INDEX.
    IF SY-SUBRC = 0.
    perform bdc_dynpro using 'SAPMF02D' '0105'.
    perform bdc_field using 'BDC_CURSOR'
    'RF02D-KTOKD'.
    perform bdc_field using 'BDC_OKCODE'
    '/00'.
    perform bdc_field using 'RF02D-KUNNR'
    IT_KNA1-CUSTOMER.
    perform bdc_field using 'RF02D-BUKRS'
    IT_KNA1-COMPANY_CODE.
    perform bdc_field using 'RF02D-KTOKD'
    IT_KNA1-ACCOUNT_GROUP.
    *PERFORM BDC_FIELD USING 'RF02D-D0130'
    'X'.
    perform bdc_dynpro using 'SAPMF02D' '0110'.
    perform bdc_field using 'BDC_CURSOR'
    'KNA1-SPRAS'.
    perform bdc_field using 'BDC_OKCODE'
    '/00'.
    perform bdc_field using 'KNA1-ANRED'
    IT_KNA1-TITLE.
    perform bdc_field using 'KNA1-NAME1'
    IT_KNA1-NAME.
    perform bdc_field using 'KNA1-SORTL'
    IT_KNA1-SEARCH_TERM.
    perform bdc_field using 'KNA1-STRAS'
    IT_KNA1-STREET.
    perform bdc_field using 'KNA1-ORT01'
    IT_KNA1-CITY.
    perform bdc_field using 'KNA1-PSTLZ'
    IT_KNA1-POSTAL_CODE.
    perform bdc_field using 'KNA1-LAND1'
    IT_KNA1-COUNTRY.
    perform bdc_field using 'KNA1-SPRAS'
    IT_KNA1-LANGUAGE_KEY.
    perform bdc_dynpro using 'SAPMF02D' '0120'.
    perform bdc_field using 'BDC_CURSOR'
    'KNA1-LIFNR'.
    perform bdc_field using 'BDC_OKCODE'
    '/00'.
    perform bdc_dynpro using 'SAPMF02D' '0130'.
    PERFORM BDC_FIELD USING 'RF02D-D0130'
    'X'.
    perform bdc_field using 'BDC_CURSOR'
    'KNBK-BANKN(01)'.
    perform bdc_field using 'BDC_OKCODE'
    '=ENTR'.
    perform bdc_dynpro using 'SAPMF02D' '0210'.
    perform bdc_field using 'BDC_CURSOR'
    'KNB1-AKONT'.
    perform bdc_field using 'BDC_OKCODE'
    '=UPDA'.
    perform bdc_field using 'KNB1-AKONT'
    IT_KNA1-REC_ACCOUNT.
    perform bdc_dynpro using 'SAPLRSFH' '0100'.
    perform bdc_field using 'BDC_OKCODE'
    '/EBACK'.
    perform bdc_field using 'BDC_CURSOR'
    'RSIODYNP4-LOW(01)'.
    ENDIF.
    ENDAT.
    L_COUNTER = L_COUNTER + 1.
    CLEAR L_STRING.
    CONCATENATE 'KNBK-BANKS(' L_COUNTER ')' INTO L_STRING.
    PERFORM BDC_FIELD USING L_STRING
    IT_KNA1-CNTRY.
    CLEAR L_STRING.
    CONCATENATE 'KNBK-BANKL(' L_COUNTER ')' INTO L_STRING.
    PERFORM BDC_FIELD USING L_STRING
    IT_KNA1-BANK_KEY.
    CLEAR L_STRING.
    CONCATENATE 'KNBK-BANKN(' L_COUNTER ')' INTO L_STRING.
    PERFORM BDC_FIELD USING L_STRING
    IT_KNA1-BANK_ACCOUNT.
    AT END OF CUSTOMER.
    READ TABLE IT_KNA1 INDEX V_INDEX.
    IF SY-SUBRC = 0.
    CALL TRANSACTION 'FD01' USING IT_BDCDATA MODE 'A' UPDATE 'S' MESSAGES
    INTO IT_MESSAGES.
    IF SY-SUBRC <> 0.
    PERFORM EMPLOYEEID_ERROR.
    *ELSE.
    ENDIF.
    WRITE: SY-SUBRC.
    perform message_format_write.
    *ENDIF.
    *WRITE: SY-SUBRC.
    CLEAR IT_BDCDATA.
    REFRESH IT_BDCDATA.
    ENDIF.
    ENDAT.
    ENDLOOP.
    endform. " POPULATE_FILE
    *& Form bdc_dynpro
    text
    -->P_0224 text
    -->P_0225 text
    form bdc_dynpro using value(p_0224)
    value(p_0225).
    IT_BDCDATA-PROGRAM = P_0224.
    IT_BDCDATA-DYNPRO = P_0225.
    IT_BDCDATA-DYNBEGIN = 'X'.
    APPEND IT_BDCDATA.
    CLEAR IT_BDCDATA.
    endform. " bdc_dynpro
    *& Form bdc_field
    text
    -->P_0229 text
    -->P_0230 text
    form bdc_field using value(p_0229)
    value(p_0230).
    IT_BDCDATA-FNAM = P_0229.
    IT_BDCDATA-FVAL = P_0230.
    APPEND IT_BDCDATA.
    CLEAR IT_BDCDATA.
    endform. " bdc_field
    *& Form EMPLOYEEID_ERROR
    text
    --> p1 text
    <-- p2 text
    form EMPLOYEEID_ERROR .
    CALL FUNCTION 'BDC_OPEN_GROUP'
    EXPORTING
    CLIENT = SY-MANDT
    DEST = FILLER8
    GROUP = 'Z50583_REC1'
    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.
    CALL FUNCTION 'BDC_INSERT'
    EXPORTING
    TCODE = 'FD01'
    POST_LOCAL = NOVBLOCAL
    PRINTING = NOPRINT
    SIMUBATCH = ' '
    CTUPARAMS = ' '
    TABLES
    dynprotab = IT_BDCDATA
    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.
    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. " EMPLOYEEID_ERROR
    *& Form message_format_write
    text
    --> p1 text
    <-- p2 text
    form message_format_write .
    DATA: L_MSG(200).
    CALL FUNCTION 'FORMAT_MESSAGE'
    EXPORTING
    ID = SY-MSGID
    LANG = SY-LANGU
    NO = SY-MSGNO
    V1 = SY-MSGV1
    V2 = SY-MSGV2
    V3 = SY-MSGV3
    V4 = SY-MSGV4
    IMPORTING
    MSG = L_MSG
    EXCEPTIONS
    NOT_FOUND = 1
    OTHERS = 2.
    WRITE: / L_MSG.
    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. " message_format_write
    ~~Guduri

  • How to handle table control in BDC while uploading item details for anorder

    How to handle table control in BDC while uploading item details for an order?
    What is the use of CTU_PARAMS structure in BDC?
    In Finance I have done some changes to the layout set by coping to a zscript(duning letter) and how can assign the print program?
    What is the process to test the finance script?
    How can I see the print preview whether it is coming correctly or not?
    Thanks in advance.
    Regards.
    Abhilash.

    hi,
    for the bdc control refer the following link:
    http://www.sap-img.com/abap/bdc-example-using-table-control-in-bdc.htm
    ctu_params:
    refer to the link
    https://www.sdn.sap.com/irj/sdn/wiki?path=/display/abap/dataTransfers-LSMW%2CALE%2C+BDC
    reward if useful,
    thanks and regards

  • How to handle Table control in BDC

    How to handle Table control in BDC

    HI,
    Table Control in BDC
    HI,
    Refer the link:
    http://www.sap-img.com/abap/bdc-example-using-table-control-in-bdc.htm
    The concept is easy: it has to indicate the index of the table control in the field name, so if you have to populate the first record of table control:
    BDC-FIELDNAME = <FIELDNAME>(01).
    If you fill the second row:
    BDC-FIELDNAME = <FIELDNAME>(02).
    and so....
    Now the problem is usually on how many records you have to load, because u can fill only the rows of table control available in the screen, If you have more records than it can be displayed yuo have to simulate the command to go next page.
    The number of recod can be displayed can depend on pc resolution and many program haven't command to go to next page (in this case it could be impossible create a BDC program9.
    A way to create a bdc program resolution indipendent is to work on the first and second row.
    - Place the first hit in the first row of bdc;
    - Place the second insert in the second row of bdc;
    - Place the last hit to the top of table control;
    - Place the next hit in the second row;
    - Place the last hit to the top of table control;
    - Place the next hit in the second row;
    - .... and so
    For more info: Search in SDN with TABLE CONTROL IN BDC.
    Will get a lot of related links.
    <b>Reward points if this Helps.
    Manish</b>

  • How to use table control in LSMW

    Hello All,
    I have requirement to use LSMW , in my using transaction have table control ,I need to pass values in table control . how to use table control in LSMW .Can any one give me the solution for this.
    Best regards,
    Satya.

    Note: The recording function records a fixed screen sequence. It cannot be used for migrating data containing a variable number of items or for transactions with dynamic screen sequences!
    Tip: It is possible to create a recording via SHDB, generate a program out of this recording, and adopt the program to your needs and registrate the program to be able to use it in LSMW.
    That’s means, for creation of project and WBS Elements is not possible through
    1. LSMW-BDC (For both CJ01 and CJ20n)
    2. LSMW-BAPI (Method: Maintain is not listed )
    3. LSME-Standard Batch Direct Input.
    It’s possible through programmatically(SE38.) either using BAPI Or BDC.
    Thanks,

  • How to handle Table control in BDC? Difference between BDC & LSMW?

    Hi
    How to handle Table control in BDC? Difference between BDC & LSMW?
    Regards,
    Raghu

    Hi ,
    the diff b/w normal BDC and with table control is that with table control u can enter as many lineitems as u want..so during recording if u r entering 3 line items..then the program will show (1), (2) and (3) with that.
    chane that fixed no to variable.
    check that sample code.
    in this for new customer...any no of items can be entered.
    LOOP AT t_cusdata.
        REFRESH t_bdcdata.
        ON CHANGE OF t_cusdata-kunnr.
    initial screen.
          PERFORM bdc_dynpro      USING 'SAPMV10A' '0100'.
          PERFORM bdc_field       USING 'BDC_CURSOR'
                                  'MV10A-VTWEG'.
          PERFORM bdc_field       USING 'BDC_OKCODE'
                                  '/00'.
          PERFORM bdc_field       USING 'MV10A-KUNNR'
                                  t_cusdata-kunnr.
          PERFORM bdc_field      USING 'MV10A-VKORG'
                                  t_cusdata-vkorg.     "'HCL'.
          PERFORM bdc_field       USING 'MV10A-VTWEG'
                                  t_cusdata-vtweg.     "'HL'.
          DATA: fnam(20) TYPE c,
                fnam1(20) TYPE c,
                idx(2) TYPE c.
          MOVE 1 TO idx.
          LOOP AT t_matdata WHERE kunnr = t_cusdata-kunnr.
            PERFORM bdc_dynpro      USING 'SAPMV10A' '0200'.
            CONCATENATE 'MV10A-KDMAT(' idx ')' INTO fnam.
            PERFORM bdc_field       USING 'BDC_CURSOR'
                                          fnam.
            PERFORM bdc_field       USING 'BDC_OKCODE'
                                           '/00'.
            CONCATENATE 'MV10A-MATNR(' idx ')' INTO fnam1.
            PERFORM bdc_field       USING fnam1
                                          t_matdata-matnr.      "'FIN50'.
            PERFORM bdc_field       USING fnam
                                          t_matdata-kdmat.  "'ABCD'.
            idx = idx + 1.
          ENDLOOP.
          PERFORM bdc_dynpro      USING 'SAPMV10A' '0200'.
          PERFORM bdc_field       USING 'BDC_CURSOR'
                                  'MV10A-MATNR(01)'.
          PERFORM bdc_field       USING 'BDC_OKCODE'
                                  '=SICH'.
          CALL TRANSACTION 'VD51' USING t_bdcdata MODE 'A' .
                                        UPDATE 'S' MESSAGES INTO t_err_mes.
    Regards,
    Sonika

  • How  to handle table controls in BDC

    Hi All,
    Can u please help me out in my BDC program which involves header data and the item data which is to be filled in a Table Control of a particular transaction .If anyone can send me already existing code it would be of great help..
    Thanks in Advance
    Kishore

    Hi Kishore
    http://www.sap-img.com/abap/bdc-example-using-table-control-in-bdc.htm
    regards
    SAmeer

  • How to use Table Control?

    Hi,
    I am working on dialog programming and am using a TABLE control for data entry.
    How do I transport records from database table to screen and insert / update / delete records from the screen table which should get reflected in database table.
    Kindly help.

    Hi,
    fill an internal table with the data you want to manage from the standard table.
    Create the table control referred to the internal table filled with insert and delete button.
    Every change has done on the table control, change your internal table.
    After you finish changing the data, link the SAVE button with MODIFY standard_table FROM TABLE internal_table and you'll pass the chages to your DB table.
    Be carefull when deleting....you have to save the data deleted in an internal table of deletion or you won't delete the corresponding raws.
    Regards
    Edited by: anna pozzi on Sep 4, 2008 12:37 PM

  • How to use table control wizard using standard SAP structure.

    Hi ,
    I'm working on one project...
    I have created my own program, where we generate sequence of numbers. This output is displayed in the table control and when i save it saves in my user defined database table.
    Now i'm trying and using standard structure in table control wizard to view the data... Table control wizard is not working if we define structure..
    Please help me out with the solution.
    Thanks and Regards in advance.
    A. Rafique

    Please explain as to what u mean by standard structure in the table control, when u r trying to view the data, are u trying to populate the internal table that you are feeding to the screen structure with the entries that you want to display?

  • How to use table control in module pool programming

    Hi
    I want to use a table control to fetch some data from mara table.
    Please guide me with the procedure and the steps which I can follow to complete my program correctly.
    thanks
    Lalit Gupta

    As [vinraaj|http://forums.sdn.sap.com/profile.jspa?userID=3968041] wrote, call transaction SE51, there is a Wizard to help you generate the table control, it will create the table control and some includes with PBO/PAI modules > Read [Using the Table Control Wizard|http://help.sap.com/saphelp_bw/helpdata/en/6d/150d67da1011d3963800a0c94260a5/frameset.htm]
    Also there is a tutorial in the wiki, read [Learn Making First Table Control |http://wiki.sdn.sap.com/wiki/display/ABAP/LearnMakingFirstTableControl] by [Krishna Chauhan|http://wiki.sdn.sap.com/wiki/display/~nc0euof]
    Regards,
    Raymond

  • How to transfer data in table control in bdc

    hi
    how to transfer data in table control in bdc . I need the theory regarding this
    bye

    Hi,
    just check in the forum , there is many threads available to ur questions.
    Table control in BDC
    http://www.sap-img.com/abap/bdc-example-using-table-control-in-bdc.htm
    You can even refer to these related threads
    bdc table control
    Re: table control in bdc
    table control in BDC
    Reward if helpful.
    Thanks
    Naveen khan

  • How can we handle table control in BDC?

    Hi,
    How can we handle table control in BDC?
    regards
    eswar

    hi,
    check this example:
    http://www.sap-img.com/abap/bdc-example-using-table-control-in-bdc.htm
    ex:
    *& Report  ZSR_BDC_TBCTRL
    REPORT  ZSR_BDC_TBCTRL
            NO STANDARD PAGE HEADING LINE-SIZE 255.
    TABLES : RF02K,LFA1,LFBK.
    DATA : BEGIN OF IT_VEN OCCURS 0,
          LIFNR LIKE RF02K-LIFNR,
          KTOKK LIKE RF02K-KTOKK,
          NAME1 LIKE LFA1-NAME1,
          SORTL LIKE LFA1-SORTL,
          LAND1 LIKE LFA1-LAND1,
          SPRAS LIKE LFA1-SPRAS,
          BANKS(6) TYPE C,
          BANKL(17) TYPE C,
          BANKN(19) TYPE C,
          END OF IT_VEN.
    DATA : BEGIN OF BANKS OCCURS 0,
           BANKS LIKE LFBK-BANKS,
           END OF BANKS,
           BEGIN OF BANKL OCCURS 0,
           BANKL LIKE LFBK-BANKL,
           END OF BANKL,
           BEGIN OF BANKN OCCURS 0,
           BANKN LIKE LFBK-BANKN,
           END OF BANKN.
    DATA : FLD(20) TYPE C,
           CNT(2) TYPE N.
    DATA : BDCTAB LIKE BDCDATA OCCURS 0 WITH HEADER LINE.
    INCLUDE BDCRECX1.
    START-OF-SELECTION.
    CALL FUNCTION 'GUI_UPLOAD'
      EXPORTING
        FILENAME                      = 'Z:\sr.TXT'
       FILETYPE                      = 'ASC'
       HAS_FIELD_SEPARATOR           = 'X'
      HEADER_LENGTH                 = 0
      READ_BY_LINE                  = 'X'
      DAT_MODE                      = ' '
      CODEPAGE                      = ' '
      IGNORE_CERR                   = ABAP_TRUE
      REPLACEMENT                   = '#'
      CHECK_BOM                     = ' '
    IMPORTING
      FILELENGTH                    =
      HEADER                        =
      TABLES
        DATA_TAB                      = IT_VEN
    EXCEPTIONS
      FILE_OPEN_ERROR               = 1
      FILE_READ_ERROR               = 2
      NO_BATCH                      = 3
      GUI_REFUSE_FILETRANSFER       = 4
      INVALID_TYPE                  = 5
      NO_AUTHORITY                  = 6
      UNKNOWN_ERROR                 = 7
      BAD_DATA_FORMAT               = 8
      HEADER_NOT_ALLOWED            = 9
      SEPARATOR_NOT_ALLOWED         = 10
      HEADER_TOO_LONG               = 11
      UNKNOWN_DP_ERROR              = 12
      ACCESS_DENIED                 = 13
      DP_OUT_OF_MEMORY              = 14
      DISK_FULL                     = 15
      DP_TIMEOUT                    = 16
      OTHERS                        = 17
    IF SY-SUBRC <> 0.
    MESSAGE ID SY-MSGID TYPE SY-MSGTY NUMBER SY-MSGNO
            WITH SY-MSGV1 SY-MSGV2 SY-MSGV3 SY-MSGV4.
    ENDIF.
    PERFORM OPEN_GROUP.
    LOOP AT IT_VEN.
        REFRESH BDCDATA.
        REFRESH : BANKS,BANKL,BANKN..
        SPLIT IT_VEN-BANKS AT ',' INTO TABLE BANKS.
        SPLIT IT_VEN-BANKL AT ',' INTO TABLE BANKL.
        SPLIT IT_VEN-BANKN AT ',' INTO TABLE BANKN.
    PERFORM BDC_DYNPRO      USING 'SAPMF02K' '0100'.
    PERFORM BDC_FIELD       USING 'BDC_CURSOR'
                                  'RF02K-KTOKK'.
    PERFORM BDC_FIELD       USING 'BDC_OKCODE'
                                  '/00'.
    PERFORM BDC_FIELD       USING 'RF02K-LIFNR'
                                  IT_VEN-LIFNR.
    PERFORM BDC_FIELD       USING 'RF02K-KTOKK'
                                  IT_VEN-KTOKK.
    PERFORM BDC_DYNPRO      USING 'SAPMF02K' '0110'.
    PERFORM BDC_FIELD       USING 'BDC_CURSOR'
                                  'LFA1-SPRAS'.
    PERFORM BDC_FIELD       USING 'BDC_OKCODE'
                                  '/00'.
    PERFORM BDC_FIELD       USING 'LFA1-NAME1'
                                  IT_VEN-NAME1.
    PERFORM BDC_FIELD       USING 'LFA1-SORTL'
                                  IT_VEN-SORTL.
    PERFORM BDC_FIELD       USING 'LFA1-LAND1'
                                  IT_VEN-LAND1.
    PERFORM BDC_FIELD       USING 'LFA1-SPRAS'
                                  IT_VEN-SPRAS.
    PERFORM BDC_DYNPRO      USING 'SAPMF02K' '0120'.
    PERFORM BDC_FIELD       USING 'BDC_CURSOR'
                                  'LFA1-KUNNR'.
    PERFORM BDC_FIELD       USING 'BDC_OKCODE'
                                  '/00'.
    PERFORM BDC_DYNPRO      USING 'SAPMF02K' '0130'.
    PERFORM BDC_FIELD       USING 'BDC_CURSOR'
                                  'LFBK-BANKN(02)'.
    PERFORM BDC_FIELD       USING 'BDC_OKCODE'
                                  '=ENTR'.
    *perform bdc_field       using 'LFBK-BANKS(01)'
                                 'DE'.
    *perform bdc_field       using 'LFBK-BANKS(02)'
                                 'DE'.
    *perform bdc_field       using 'LFBK-BANKL(01)'
                                 '10020030'.
    *perform bdc_field       using 'LFBK-BANKL(02)'
                                 '67270003'.
    *perform bdc_field       using 'LFBK-BANKN(01)'
                                 '12345'.
    *perform bdc_field       using 'LFBK-BANKN(02)'
                                 '66666'.
    MOVE 1 TO CNT.
        LOOP AT BANKS.
          CONCATENATE 'LFBK-BANKS(' CNT ') ' INTO FLD.
          PERFORM BDC_FIELD USING FLD BANKS-BANKS.
          CNT = CNT + 1.
        ENDLOOP.
        MOVE 1 TO CNT.
        LOOP AT BANKL.
          CONCATENATE 'LFBK-BANKL(' CNT ') ' INTO FLD.
          PERFORM BDC_FIELD USING FLD BANKL-BANKL.
          CNT = CNT + 1.
        ENDLOOP.
        MOVE 1 TO CNT.
        LOOP AT BANKN.
          CONCATENATE 'LFBK-BANKN(' CNT ') ' INTO FLD.
          PERFORM BDC_FIELD USING FLD BANKN-BANKN.
          CNT = CNT + 1.
        ENDLOOP.
    PERFORM BDC_DYNPRO      USING 'SAPMF02K' '0130'.
    PERFORM BDC_FIELD       USING 'BDC_CURSOR'
                                  'LFBK-BANKS(01)'.
    PERFORM BDC_FIELD       USING 'BDC_OKCODE'
                                  '=ENTR'.
    PERFORM BDC_DYNPRO      USING 'SAPLSPO1' '0300'.
    PERFORM BDC_FIELD       USING 'BDC_OKCODE'
                                  '=YES'.
    PERFORM BDC_TRANSACTION USING 'XK01'.
    ENDLOOP.
    PERFORM CLOSE_GROUP.

  • Hi All, How we can handle a table control in bdc - in detail its urgent pls

    Hi All, How we can handle a table control in bdc - in detail its urgent. Please send me the explanation in detail.
    Thanks&regards.
    Bharat

    hi,
    Create Table Control
    • Step 1 (Create new structure for table control)
    Type is name of structure (ZTC_EKKO) and press create
    • Step 2 (Create Program)
    Goto transaction SE80(Object Navigator) -> Repository Browser -> Program.
    Enter your program name, please ensure that is begins with SAPMZ…… as this is a module pool (dialog program).
    Press enter to create, and press yes!
    Ensure that you create a top include, and press Enter.
    Accept the name created for the top include.
    Press Enter.
    Press Save
    • Step 3 (Create TOP include)
    Double click on the top include and enter following ABAP code:
    Tables: ZTC_EKKO.
    controls: tc100 type tableview using screen 100.
    data: ok_code type sy-ucomm.
    data: it_ekko type standard
    table of ZTC_EKKO initial size 0,
    wa_ekko type ZTC_EKKO.
    data: ok_code type sy-ucomm.
    Press Save and Activate
    • Step 4 (Create screen)
    Right click the program to create a screen 100 for the dialog. Enter Short description, set screen type to Normal and enter 0 or blank into Next screen. Then move to Element List tab and enter the OK code as OK_CODE (i.e. the same as what you declared in the top include with data: ok_code type sy-ucomm).
    • Step 5 (Create table control)
    Press the Layout button to bring up the screen painter editor.
    Press table control button and drag it on to the screen, enter the name of table control created in TOP include (TC100). Now press the yellow button for attributes and set the table control as below options
    • Step 6 (Populate table control )
    Press the orange button (Fields). On the next screen enter ZTC_EKKO and press the ‘Get from Dict’ button. Select the fields you want (all) and press enter. Now drag them onto your Table Control.
    Below is the result, there will been syntax errors if we check now! So Save and go back into the flow logic tab.
    • Step 7 (Create flow control )
    Within the flow logic of screen 100 and create two modules, one to select the data from the database and the other to move the selected fields into the table control. Also insert the two loop statements to populate and retrieve the lines of the table control.
    PROCESS BEFORE OUTPUT.
    MODULE STATUS_0100.
    module data_retrieval.
    loop at it_ekko into wa_ekko with control TC100.
    module populate_screen.
    endloop.
    PROCESS AFTER INPUT.
    loop at it_ekko.
    endloop.
    MODULE USER_COMMAND_0100.
    Double click the module data_retrieval to create and click yes to get past the popup. Ensure that a new include is created to hold all the PBO modules (default). Press enter.
    Select 10 rows of data from the EKKO table and load into the internal table it_ekko. Go back to the flow logic to load this data into the Table Control.
    check this one
    REPORT ZCALL_TRANS_TAB1 .
    TABLES: LFA1,LFBK,lfb1.
    data: BEGIN OF it_vendor occurs 0,
    LIFNR LIKE LFA1-LIFNR,
    bukrs like lfb1-bukrs,
    END OF it_vendor.
    DATA: BEGIN OF IT_BANK occurs 0,
    LIFNR LIKE LFA1-LIFNR,
    BANKS LIKE LFBK-BANKS,
    BANKL LIKE LFBK-BANKL,
    BANKN LIKE LFBK-BANKN,
    koinh like lfbk-koinh,
    END OF IT_BANK.
    data: it_bdcdata like bdcdata occurs 0 with header line.
    data: it_messages like bdcmsgcoll occurs 0 with header line.
    *selection screen.
    selection-screen: begin of block b1 with frame.
    parameters: p_file like rlgrap-filename default 'c:/vendor.txt'
    obligatory.
    parameters: p_file1 like rlgrap-filename default 'c:/xyz.txt'
    obligatory.
    selection-screen: end of block b1.
    *at selection screen.
    at selection-screen on value-request for p_file.
    perform f4_help using p_file.
    at selection-screen on value-request for p_file1.
    perform f4_help1 using p_file1.
    *start of selection
    start-of-selection.
    *******uploading file
    perform upload_file using p_file P_FILE1.
    ******open session.
    perform populate_data.
    *& Form f4_help
    form f4_help using p_p_file.
    data: l_file type ibipparms-path.
    call function 'F4_FILENAME'
    importing
    file_name = l_file.
    p_file = l_file.
    endform. " f4_help
    *& Form POPULATE_DATA
    form populate_data .
    DATA: L_STRING TYPE STRing.
    DATA: L_COUNTER(2) TYPE n.
    loop at it_vendor.
    perform bdc_dynpro using 'SAPMF02K' '0106'.
    perform bdc_field using 'BDC_CURSOR'
    'RF02K-D0130'.
    perform bdc_field using 'BDC_OKCODE'
    '/00'.
    perform bdc_field using 'RF02K-LIFNR'
    it_vendor-lifnr.
    perform bdc_field using 'RF02K-BUKRS'
    it_vendor-bukrs.
    perform bdc_field using 'RF02K-D0130'
    'X'.
    perform bdc_dynpro using 'SAPMF02K' '0130'.
    perform bdc_field using 'BDC_CURSOR'
    'LFBK-bankn(03)'.
    perform bdc_field using 'BDC_OKCODE'
    '=UPDA'.
    *********bank details
    CLEAR l_COUNTER.
    LOOP AT IT_BANK WHERE LIFNR = IT_VENDOR-LIFNR.
    l_COUNTER = l_COUNTER + 1.
    clear l_string.
    CONCATENATE 'lfbk-banks(' l_counter ')' into l_string.
    perform bdc_field using l_string
    it_bank-banks.
    clear l_string.
    CONCATENATE 'lfbk-bankl(' l_counter ')' into l_string.
    perform bdc_field using l_string
    it_bank-bankl.
    clear l_string.
    CONCATENATE 'lfbk-bankn(' l_counter ')' into l_string.
    perform bdc_field using l_string
    it_bank-bankn.
    endloop.
    ******CALL TRANSACTION.
    call transaction 'FK02' using it_bdcdata mode 'A'
    messages into it_messages.
    write:/ sy-subrc.
    perform format_messages.
    clear it_bdcdata.
    refresh it_bdcdata.
    endloop.
    endform. " POPULATE_DATA
    *& Form FORMAT_MESSAGES
    form format_messages .
    data: l_msg(100).
    loop at it_messages.
    call function 'FORMAT_MESSAGE'
    exporting
    id = it_messages-msgid
    lang = sy-langu
    no = it_messages-msgnr
    v1 = it_messages-msgv1
    v2 = it_messages-msgv2
    v3 = it_messages-msgv3
    v4 = it_messages-msgv4
    importing
    msg = l_msg
    exceptions
    not_found = 1
    others = 2
    write:/ l_msg.
    endloop.
    endform. " FORMAT_MESSAGES
    *& Form bdc_dynpro
    form bdc_dynpro using value(p_program)
    value(p_screen).
    it_bdcdata-program = p_program.
    it_bdcdata-dynpro = p_screen.
    it_bdcdata-dynbegin = 'X'.
    append it_bdcdata.
    clear it_bdcdata.
    endform. " bdc_dynpro
    *& Form bdc_field
    form bdc_field using value(p_fnam)
    value(p_fval).
    it_bdcdata-fnam = p_fnam.
    it_bdcdata-fval = p_fval.
    append it_bdcdata.
    clear it_bdcdata.
    endform. " bdc_field
    *& Form upload_file
    form upload_file using p_p_file
    p_p_file1.
    CALL FUNCTION 'WS_UPLOAD'
    EXPORTING
    CODEPAGE = ' '
    FILENAME = P_P_FILE
    FILETYPE = 'DAT'
    HEADLEN = ' '
    LINE_EXIT = ' '
    TRUNCLEN = ' '
    USER_FORM = ' '
    USER_PROG = ' '
    DAT_D_FORMAT = ' '
    IMPORTING
    FILELENGTH =
    TABLES
    data_tab = IT_VENDOR
    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
    NO_AUTHORITY = 10
    OTHERS = 11
    IF sy-subrc <> 0.
    MESSAGE I000(ZZ) WITH 'UNABLE TO UPLOAD'.
    STOP.
    ENDIF.
    *******UPLOADING BANK DETAILS
    CALL FUNCTION 'WS_UPLOAD'
    EXPORTING
    CODEPAGE = ' '
    FILENAME = P_P_FILE1
    FILETYPE = 'DAT'
    HEADLEN = ' '
    LINE_EXIT = ' '
    TRUNCLEN = ' '
    USER_FORM = ' '
    USER_PROG = ' '
    DAT_D_FORMAT = ' '
    IMPORTING
    FILELENGTH =
    TABLES
    data_tab = IT_BANK
    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
    NO_AUTHORITY = 10
    OTHERS = 11
    IF sy-subrc <> 0.
    MESSAGE I000(ZZ) WITH 'UNABLE TO UPLOAD'.
    STOP.
    ENDIF.
    endform. " upload_file
    *& Form f4_help1
    -->P_P_FILE1 text
    form f4_help1 using p_p_file1.
    data:l_file1 type ibipparms-path.
    CALL FUNCTION 'F4_FILENAME'
    IMPORTING
    FILE_NAME = l_file1.
    p_file1 = l_file1.
    endform. " f4_help1
    http://sap-img.com/abap/bdc-example-using-table-control-in-bdc.htm
    Regards,
    Sankar

Maybe you are looking for

  • Problem in Concatenate Statement

    hello Friends,   I have to concatenate  Four variables A B C and D.In this four variables three of them are Characters.The last one is currency field.I am not able to concatenate this field.for this I declared one variable in character fomat and i mo

  • Javax.mail.NoSuchProviderException: No provider for SMTP

    whats the meaning of the following exception javax.mail.NoSuchProviderException: No provider for SMTP can any one help. thanks and regards.

  • Doubt on Prepared statement

    Hi, If i have a collection of string, and i want to use the strings in that collection for my IN parameters ( inside the query ), then which is the preferred method to follow among the below mentioned two ways.. 1) I am iterating the collection and c

  • Commissioning a new CAS server in existing Exchange 2013 org

    I have a question about why my Outlook client would connect to a newly Exchange 2013 CAS server although not a lot of configuration has been done on it? Also, the existing CAS servers are configured with a third party load balancer and the new server

  • How to start Weblogic 10.3.5 managed server on port 80

    Hello, We're trying to understand how to start Weblogic as root so we can start on port 80 on Linux. We understand that we'll use the post bind UID to run as a non-priv user. Right now in the Admin console under the managed server, Server Start prope