How to DOWNLOAD  a whole module pool program????

Hi..
can anybody tell me how to download a <b>whole module pool program</b> into my desktop with .sap extension???
Actually i want to download a whole module pool program from a server so that i can upload the same program into another sap server instead of writing the whole code.
Thanx in advance......

the program is exits..
i don't y it is not for ur.....
i am sending d code for the same....
create a program and check...
*& Report  REPTRAN                                                     *
*& This report allows to display and save complete programs and        *
*& function modules.                                                   *
*& This report was originally written by Frank Wolf, Xaption GmbH.     *
*& Its original name was ZREPTRAN (see www.abaps.de).                  *
REPORT  reptran LINE-SIZE 170      .
TABLES: d010inc, trdir, eudb, title, d020t, trkey, tfdir, tmdir, tadir,
        seoclass,  seoclassdf, seoclassex, seoclasstx, seometarel,
        seocompo,  seocompodf, seocompoex, seocompotx, seoimplrel,
        seomapatt, seomapcls,  seoredef,   seofriends, seotypepls,
        seosubco,  seosubcodf, seosubcoex, seosubcotx.
TYPES: abapline(255).
TYPES: BEGIN OF ty_tit,
        code TYPE rsoldleng-title,
        text TYPE title-text_line,
       END OF ty_tit.
TYPES: BEGIN OF ty_reptxt,
        id TYPE textpool-id,
        key TYPE textpool-key,
        entry TYPE textpool-entry,
        length(4) TYPE n,
       END OF ty_reptxt.
TYPES: BEGIN OF ty_d020t,
        prog TYPE d020t-prog,
        dynr TYPE d020t-dynr,
        dtxt TYPE d020t-dtxt,
       END OF ty_d020t.
TYPES: BEGIN OF dynp_rel_type,         "Dynpro-Releases
        rel(1),
        dot(1),
        version(2),
       END OF dynp_rel_type.
TYPES: BEGIN OF ty_seocompodf_t.
        INCLUDE STRUCTURE seocmpkey.
TYPES:  version TYPE seocompodf-version,
        alias TYPE seocompodf-alias,
        redefin TYPE seocompodf-redefin,
        exposure TYPE seocompodf-exposure,
        state TYPE seocompodf-state,
        editorder(4) TYPE n,
        locked TYPE seocompodf-locked,
        dispid(4) TYPE n.
        INCLUDE STRUCTURE seochange.
        INCLUDE STRUCTURE seomtdapx.
        INCLUDE STRUCTURE seoevtapx.
        INCLUDE STRUCTURE seotypapx.
TYPES:  typtype TYPE seocompodf-typtype,
        type TYPE seocompodf-type,
        tableof TYPE seocompodf-tableof,
        srcrow1(4) TYPE n,
        srccolumn1(2) TYPE n,
        srcrow2(4) TYPE n,
        srccolumn2(2) TYPE n.
        INCLUDE STRUCTURE seocmpref.
TYPES: END OF ty_seocompodf_t.
TYPES: BEGIN OF ty_seosubcodf_t.
        INCLUDE STRUCTURE seoscokey.
TYPES:  version TYPE seosubcodf-version,
        editorder(4) TYPE n,
        dispid(4) TYPE n.
        INCLUDE STRUCTURE seochange.
TYPES:  pardecltyp TYPE seosubcodf-pardecltyp,
        parpasstyp TYPE seosubcodf-parpasstyp,
        typtype TYPE seosubcodf-typtype,
        type TYPE seosubcodf-type,
        tableof TYPE seosubcodf-tableof,
        srcrow1(4) TYPE n,
        srccolumn1(2) TYPE n,
        srcrow2(4) TYPE n,
        srccolumn2(2) TYPE n,
        parvalue TYPE seosubcodf-parvalue,
        paroptionl TYPE seosubcodf-paroptionl.
        INCLUDE STRUCTURE seoexcapx.
TYPES: END OF ty_seosubcodf_t.
Release bis 3.1
*INCLUDE mseuxcom.
DATA: eu_key TYPE rseu1_key.
    Titel
DATA: tit    TYPE STANDARD TABLE OF ty_tit     WITH HEADER LINE.
Release from 4.6
DATA: fun4   TYPE STANDARD TABLE OF rsmpe_funt WITH HEADER LINE.
DATA: ctx4   TYPE STANDARD TABLE OF rsmpe_ctx  WITH HEADER LINE.
DATA: mtx4   TYPE STANDARD TABLE OF rsmpe_mnlt WITH HEADER LINE.
DATA: men4   TYPE STANDARD TABLE OF rsmpe_men  WITH HEADER LINE.
DATA: act4   TYPE STANDARD TABLE OF rsmpe_act  WITH HEADER LINE.
DATA: doc4   TYPE STANDARD TABLE OF rsmpe_atrt WITH HEADER LINE.
DATA: sta4   TYPE STANDARD TABLE OF rsmpe_stat WITH HEADER LINE.
DATA: set4   TYPE STANDARD TABLE OF rsmpe_staf WITH HEADER LINE.
DATA: pfk4   TYPE STANDARD TABLE OF rsmpe_pfk  WITH HEADER LINE.
DATA: but4   TYPE STANDARD TABLE OF rsmpe_but  WITH HEADER LINE.
DATA: tit4   TYPE STANDARD TABLE OF rsmpe_titt WITH HEADER LINE.
DATA: stx4   TYPE STANDARD TABLE OF rsmptexts  WITH HEADER LINE.
DATA: adm4   TYPE rsmpe_adm.
Release from 4.6c
DATA: biv46c TYPE STANDARD TABLE OF rsmpe_buts WITH HEADER LINE.
DATA: reports    TYPE STANDARD TABLE OF trdir-name WITH HEADER LINE,
      reportname TYPE string.
DATA: i_repsrc TYPE STANDARD TABLE OF abapline   WITH HEADER LINE.
DATA: i_reptx  TYPE STANDARD TABLE OF textpool   WITH HEADER LINE.
DATA: i_reptxt TYPE STANDARD TABLE OF ty_reptxt  WITH HEADER LINE.
DATA: i_adm4 TYPE STANDARD TABLE OF rsmpe_adm    WITH HEADER LINE.
DATA: i_tmd TYPE STANDARD TABLE OF tmdir.
DATA: i_tfd TYPE STANDARD TABLE OF tfdir.
DATA: i_cls TYPE STANDARD TABLE OF seoclass.
DATA: i_cdf TYPE STANDARD TABLE OF seoclassdf.
DATA: i_clx TYPE STANDARD TABLE OF seoclassex.
DATA: i_clt TYPE STANDARD TABLE OF seoclasstx.
DATA: i_cmr TYPE STANDARD TABLE OF seometarel.
DATA: i_cmp TYPE STANDARD TABLE OF seocompo.
DATA: i_cmd TYPE STANDARD TABLE OF seocompodf WITH HEADER LINE.
DATA: i_cmd_t TYPE STANDARD TABLE OF ty_seocompodf_t WITH HEADER LINE.
DATA: i_cmx TYPE STANDARD TABLE OF seocompoex.
DATA: i_cmt TYPE STANDARD TABLE OF seocompotx.
DATA: i_irl TYPE STANDARD TABLE OF seoimplrel.
DATA: i_mat TYPE STANDARD TABLE OF seomapatt.
DATA: i_mac TYPE STANDARD TABLE OF seomapcls.
DATA: i_red TYPE STANDARD TABLE OF seoredef.
DATA: i_frd TYPE STANDARD TABLE OF seofriends.
DATA: i_tpl TYPE STANDARD TABLE OF seotypepls.
DATA: i_sco TYPE STANDARD TABLE OF seosubco.
DATA: i_scd TYPE STANDARD TABLE OF seosubcodf WITH HEADER LINE.
DATA: i_scd_t TYPE STANDARD TABLE OF ty_seosubcodf_t WITH HEADER LINE.
DATA: i_scx TYPE STANDARD TABLE OF seosubcoex.
DATA: i_sct TYPE STANDARD TABLE OF seosubcotx.
DATA: i_inc TYPE STANDARD TABLE OF d010inc-include WITH HEADER LINE.
DATA: i_d020t TYPE STANDARD TABLE OF ty_d020t WITH HEADER LINE.
DATA: hdr TYPE d020s,
      fld TYPE STANDARD TABLE OF d021s WITH HEADER LINE,
      src TYPE STANDARD TABLE OF d022s WITH HEADER LINE,
      mat TYPE STANDARD TABLE OF d023s WITH HEADER LINE.
CONSTANTS:
           stars(64)          VALUE
                                                            "#EC NOTEXT
           comment1(64)       VALUE
'*   THIS FILE IS GENERATED BY THE SCREEN PAINTER.              *',
                                                            "#EC NOTEXT
           comment2(64)       VALUE
'*   NEVER CHANGE IT MANUALLY, PLEASE !                         *',
                                                            "#EC NOTEXT
           dynpro_text(8)     VALUE '%_DYNPRO',             "#EC NOTEXT
           header_text(8)     VALUE '%_HEADER',             "#EC NOTEXT
           params_text(8)     VALUE '%_PARAMS',             "#EC NOTEXT
           descript_text(13)  VALUE '%_DESCRIPTION',        "#EC NOTEXT
           fields_text(8)     VALUE '%_FIELDS',             "#EC NOTEXT
           kreuz(1)           VALUE 'x',                    "#EC NOTEXT
           flowlogic_text(11) VALUE '%_FLOWLOGIC'.          "#EC NOTEXT
DATA: header_char TYPE scr_chhead.
DATA: fields_char TYPE STANDARD TABLE OF scr_chfld WITH HEADER LINE.
DATA: dynp_char TYPE STANDARD TABLE OF scr_chfld WITH HEADER LINE.
DATA: prog_len     TYPE p.
DATA: BEGIN OF dynp,
        prog TYPE d020s-prog,
        dnum TYPE d020s-dnum,
      END OF dynp.
DATA:
    scrp_rel  TYPE dynp_rel_type VALUE '4.02'.  "Rel. Scrp. 4.02
      scrp_rel  TYPE dynp_rel_type VALUE '4.60'.  "Rel. Scrp. 4.6A
DATA  dynp_rel  TYPE dynp_rel_type.    "akt. Rel. Dynpro
DATA: dynpro_rel(4).
DATA  status.
DATA  prog_len_akt TYPE p.
DATA  release.
DATA  rows  LIKE sy-curow.
DATA  lines LIKE sy-cucol.
DATA: filename TYPE string.
DATA: subrc LIKE sy-subrc.
DATA: os(10).
DATA: delux VALUE '/'.
DATA: delwn VALUE '\'.
DATA: delim.
DATA: dirux(250) VALUE '-l>dir.tmp'.
DATA: dirwn(250) VALUE '/Q /Cdir>dir.tmp'.
DATA: command(250).
DATA: shellux(250) VALUE 'bash'.
DATA: shellwn(250) VALUE 'cmd.exe'.
DATA: shell(250).
DATA: file      TYPE rlgrap-filename.
DATA: answer.
DATA: incname   TYPE d010inc-include.
DATA: repname   TYPE d010inc-include.
DATA: rest1     TYPE d010inc-include.
DATA: rest2     TYPE d010inc-include.
DATA: kz_renam.
DATA: classname TYPE seoclsname.
DATA: classtype(2).
DATA: offset  TYPE i.
DATA: savepath(250).
SELECT-OPTIONS:   report   FOR trdir-name.
SELECTION-SCREEN: SKIP.
SELECT-OPTIONS:   cnam     FOR trdir-cnam MATCHCODE OBJECT user_addr,
                  unam     FOR trdir-unam MATCHCODE OBJECT user_addr,
                  devclass FOR tadir-devclass,
                  subc     FOR trdir-subc,
                  rstat    FOR trdir-rstat,
                  cdat     FOR trdir-cdat,
                  udat   FOR trdir-udat.
SELECTION-SCREEN: SKIP.
PARAMETERS:       path(250).
SELECTION-SCREEN: SKIP.
PARAMETERS:       display  RADIOBUTTON GROUP func,
                  save     RADIOBUTTON GROUP func,
                  savedspl RADIOBUTTON GROUP func.
SELECTION-SCREEN: SKIP.
PARAMETERS:       codeonly AS CHECKBOX.
SELECTION-SCREEN: SKIP.
*PARAMETERS:       suffix(80) LOWER CASE.
DATA:             suffix(80) TYPE c.
LOAD-OF-PROGRAM.
  AUTHORITY-CHECK OBJECT 'S_DEVELOP'
      ID 'DEVCLASS' DUMMY
      ID 'OBJTYPE'  FIELD 'PROG'
      ID 'OBJNAME'  FIELD 'REPTRAN'
      ID 'PGROUP'   DUMMY
      ID 'ACTVT'    FIELD '03'.
  IF sy-subrc <> 0.
    MESSAGE e059(EU) WITH 'REPTRAN'.
  ENDIF.
INITIALIZATION.
  GET PARAMETER ID 'REPTRAN_PATH' FIELD path.
  IF path IS INITIAL.
    path = 'C:\ABAPS\'.
  ENDIF.
  save = 'X'.
  codeonly = 'X'.
  CALL FUNCTION 'WS_QUERY'
       EXPORTING
          ENVIRONMENT    = ' '
          FILENAME       = ' '
            query          = 'OS'
          WINID          = ' '
       IMPORTING
            return         = os
       EXCEPTIONS
            inv_query      = 1
            no_batch       = 2
            frontend_error = 3
            OTHERS         = 4.
  IF sy-subrc = 0 AND
     ( os CS 'OS2' OR os CS 'DOS' OR os CS 'NT' ).
    delim = delwn.
    command = dirwn.
    shell = shellwn.
  ELSE.
    delim = delux.
    command = dirux.
    shell = shellux.
  ENDIF.
AT SELECTION-SCREEN ON VALUE-REQUEST FOR path.
  GET CURSOR FIELD path VALUE path.
  filename = path.
  PERFORM fileselector.
AT SELECTION-SCREEN.
  IF report[] IS INITIAL.
    IF NOT reports[] IS INITIAL.
      report = 'IEQ'.
      report-low = reports.
      APPEND report.
      MESSAGE i208(00)
         WITH 'Report/BSP application was also identified'(009).
    ELSE.
      MESSAGE e208(00)
         WITH 'Enter report or BSP application or enter path'(011).
    ENDIF.
  ENDIF.
START-OF-SELECTION.
  offset = strlen( path ) - 1.
  IF path+offset(1) <> '\'.
    CONCATENATE path '\' INTO path.
  ENDIF.
  SET PARAMETER ID 'REPTRAN_PATH' FIELD path.
  FORMAT COLOR COL_BACKGROUND INTENSIFIED OFF.
  eu_key-sprsl = sy-langu.
  IF NOT save     IS INITIAL OR
     NOT display  IS INITIAL OR
     NOT savedspl IS INITIAL.
  DOWNLOAD PROGRAMS
    SELECT name  FROM trdir
           INTO  TABLE reports
           WHERE name IN report
           AND   cnam IN cnam
           AND   unam IN unam
           AND   subc IN subc
           AND   rstat IN rstat
           AND   cdat IN cdat
           AND   udat IN udat.
    IF sy-subrc <> 0.
      LOOP AT report.
        CONCATENATE report(3) 'SAPL' report+3 INTO report.
        MODIFY report.
      ENDLOOP.
      SELECT name  FROM trdir
             INTO  TABLE reports
             WHERE name IN report
             AND   cnam IN cnam
             AND   unam IN unam
             AND   subc IN subc
             AND   rstat IN rstat
             AND   cdat IN cdat
             AND   udat IN udat.
    ENDIF.
    IF sy-subrc <> 0.
      MESSAGE i208(00)
         WITH 'The program/function name entered does not exist!'(082).
    ENDIF.
    LOOP AT reports.
Check if report is in development class
      classtype = reports+30.
      IF reports(5) NE 'CL_O2'.
        IF classtype = 'CP'.
          tadir-obj_name = reports.
          SHIFT tadir-obj_name RIGHT DELETING TRAILING space.
          SHIFT tadir-obj_name RIGHT BY 2 PLACES.
          SHIFT tadir-obj_name RIGHT DELETING TRAILING '='.
          SHIFT tadir-obj_name LEFT DELETING LEADING space.
          SELECT SINGLE * FROM  tadir
                 WHERE  pgmid     = 'R3TR'
                 AND    object    = 'CLAS'
                 AND    obj_name  = tadir-obj_name
                 AND    devclass  IN devclass.
        ENDIF.
        IF classtype <> 'CP' OR sy-subrc <> 0.
          SELECT SINGLE * FROM  tadir
                 WHERE  pgmid     = 'R3TR'
                 AND    object    = 'PROG'
                 AND    obj_name  = reports
                 AND    devclass  IN devclass.
          IF sy-subrc <> 0.
            SELECT SINGLE * FROM  tadir
                   WHERE  pgmid     = 'R3TR'
                   AND    object    = 'FUGR'
                   AND    obj_name  = reports
                   AND    devclass  IN devclass.
          ENDIF.
          IF sy-subrc <> 0 AND
             ( reports(4) = 'SAPL' OR reports(4) = 'sapl' ).
            reportname = reports+4.
            SELECT SINGLE * FROM  tadir
                   WHERE  pgmid     = 'R3TR'
                   AND    object    = 'FUGR'
                   AND    obj_name  = reportname
                   AND    devclass  IN devclass.
          ENDIF.
        ENDIF.
        IF sy-subrc <> 0.
          CONTINUE.
        ENDIF.
      ENDIF.
      reportname = reports.
      PERFORM makepath USING    reportname
                                path
                       CHANGING savepath.
      PERFORM writeinfo  USING reportname
                               savepath.
      REFRESH: i_repsrc, i_reptx, i_reptxt, i_inc,
               sta4, ctx4, fun4, mtx4, doc4, tit4, men4, act4, but4,
               pfk4, set4, stx4, biv46c,
               i_d020t, i_adm4,
               i_tmd, i_tfd, i_cls, i_cdf, i_clx, i_clt, i_cmr, i_cmp,
               i_cmd, i_cmx, i_cmt, i_irl, i_mat, i_mac, i_red, i_frd,
               i_tpl, i_sco, i_scd, i_scx, i_sct, i_cmd_t, i_scd_t.
      CLEAR: adm4.
      eu_key-name  = reports.
      READ REPORT reports INTO i_repsrc.
      IF codeonly <> 'X'.
        READ TEXTPOOL reports INTO i_reptx.
      ENDIF.
      LOOP AT i_reptx.
        MOVE-CORRESPONDING i_reptx TO i_reptxt.
        APPEND i_reptxt.
      ENDLOOP.
      IF NOT display  IS INITIAL OR
         NOT savedspl IS INITIAL.
        PERFORM show_rep.
      ENDIF.
      IF classtype = 'CP' OR classtype = 'IP'.
        classname = reports(30).
        TRANSLATE classname USING '= '.
        SELECT * FROM tmdir INTO TABLE i_tmd
               WHERE classname = classname.
        SELECT * FROM seoclass   INTO TABLE i_cls
               WHERE clsname = classname.
        SELECT * FROM seoclassdf INTO TABLE i_cdf
               WHERE clsname = classname.
        SELECT * FROM seoclassex INTO TABLE i_clx
               WHERE clsname = classname.
        SELECT * FROM seoclasstx INTO TABLE i_clt
               WHERE clsname = classname.
        SELECT * FROM seometarel INTO TABLE i_cmr
               WHERE clsname = classname.
        SELECT * FROM seocompo   INTO TABLE i_cmp
               WHERE clsname = classname.
        SELECT * FROM seocompodf INTO TABLE i_cmd
               WHERE clsname = classname.
        LOOP AT i_cmd.
          MOVE-CORRESPONDING i_cmd TO i_cmd_t.
          APPEND i_cmd_t.
        ENDLOOP.
        SELECT * FROM seocompoex INTO TABLE i_cmx
               WHERE clsname = classname.
        SELECT * FROM seocompotx INTO TABLE i_cmt
               WHERE clsname = classname.
        SELECT * FROM seoimplrel INTO TABLE i_irl
               WHERE clsname = classname.
        SELECT * FROM seomapatt  INTO TABLE i_mat
               WHERE clsname = classname.
        SELECT * FROM seomapcls  INTO TABLE i_mac
               WHERE clsname = classname.
        SELECT * FROM seoredef   INTO TABLE i_red
               WHERE clsname = classname.
        SELECT * FROM seofriends INTO TABLE i_frd
               WHERE clsname = classname.
        SELECT * FROM seotypepls INTO TABLE i_tpl
               WHERE clsname = classname.
        SELECT * FROM seosubco   INTO TABLE i_sco
               WHERE clsname = classname.
        SELECT * FROM seosubcodf INTO TABLE i_scd
               WHERE clsname = classname.
        LOOP AT i_scd.
          MOVE-CORRESPONDING i_scd TO i_scd_t.
          APPEND i_scd_t.
        ENDLOOP.
        SELECT * FROM seosubcoex INTO TABLE i_scx
               WHERE clsname = classname.
        SELECT * FROM seosubcotx INTO TABLE i_sct
               WHERE clsname = classname.
      ELSE.
        CLEAR classtype.
      ENDIF.
      IF codeonly <> 'X'.
        SELECT * FROM tfdir INTO TABLE i_tfd
               WHERE pname = reports.
        CALL FUNCTION 'RS_CUA_INTERNAL_FETCH'
             EXPORTING
                  program         = reports
                LANGUAGE        =
                STATE           = 'A'
             IMPORTING
                  adm             = adm4
                LANGU           =
                AUTHOR          =
                DATE            =
                TIME            =
                CAUTHOR         =
                CDATE           =
                CTIME           =
                GDATE           =
                GTIME           =
             TABLES
                  sta             = sta4
                  fun             = fun4
                  men             = men4
                  mtx             = mtx4
                  act             = act4
                  but             = but4
                  pfk             = pfk4
                  set             = set4
                  doc             = doc4
                  tit             = tit4
                  biv             = biv46c
             EXCEPTIONS
                  not_found       = 1
                  unknown_version = 2
                  OTHERS          = 3.
        SELECT ddnr text_line FROM title INTO TABLE tit
               WHERE ddlanguage = eu_key-sprsl AND
                     progname   = eu_key-name.
        SELECT * FROM rsmptexts INTO TABLE stx4
               WHERE progname   = eu_key-name AND
                     sprsl = eu_key-sprsl.
        SELECT prog dynr dtxt FROM d020t INTO TABLE i_d020t
               WHERE prog = reports AND
                     NOT dtxt LIKE 'SEL_SCREEN%'.
      ENDIF.
      IF NOT classtype IS INITIAL.
        reports = classname.
      ENDIF.
      TRANSLATE reports TO LOWER CASE.
      TRANSLATE reports USING '/.'.
      IF NOT save     IS INITIAL OR
         NOT savedspl IS INITIAL.
        CONCATENATE savepath reports suffix '.txt' INTO filename.
        PERFORM download TABLES i_repsrc USING filename
                         'Source'(003).
        IF NOT i_reptxt[] IS INITIAL.
          CONCATENATE savepath reports suffix '_txt.txt' INTO filename.
          PERFORM download TABLES i_reptxt USING filename
                           'Text elements'(004).
        ENDIF.
      ENDIF.
      SELECT include FROM d010inc INTO TABLE i_inc
             WHERE master = eu_key-name.
      DELETE i_inc WHERE table_line(1) = '<'.
      DELETE i_inc WHERE table_line(1) = '>'.
      DELETE i_inc WHERE table_line = 'DB__SSEL'.
      IF ( NOT save     IS INITIAL OR
           NOT savedspl IS INITIAL ) AND
           NOT i_inc[]  IS INITIAL.
        CONCATENATE savepath reports suffix '_inc.txt' INTO filename.
        PERFORM download TABLES i_inc USING filename
                         'Include List'(033).
      ENDIF.
      IF ( NOT save     IS INITIAL OR
           NOT savedspl IS INITIAL ) AND
           NOT i_tmd[]  IS INITIAL.
        CONCATENATE savepath reports suffix '_tmd.txt' INTO filename.
        PERFORM download TABLES i_tmd USING filename
                         'Methods List'(048).
      ENDIF.
      IF ( NOT save     IS INITIAL OR
           NOT savedspl IS INITIAL ) AND
           NOT i_cls[]  IS INITIAL.
        CONCATENATE savepath reports suffix '_cls.txt' INTO filename.
        PERFORM download TABLES i_cls USING filename
                         'Class Entry'(050).
      ENDIF.
      IF ( NOT save     IS INITIAL OR
           NOT savedspl IS INITIAL ) AND
           NOT i_cdf[]  IS INITIAL.
        CONCATENATE savepath reports suffix '_cdf.txt' INTO filename.
        PERFORM download TABLES i_cdf USING filename
                         'Class Definition'(051).
      ENDIF.
      IF ( NOT save     IS INITIAL OR
           NOT savedspl IS INITIAL ) AND
           NOT i_clx[]  IS INITIAL.
        CONCATENATE savepath reports suffix '_clx.txt' INTO filename.
        PERFORM download TABLES i_clx USING filename
                         'Class Remote Info'(052).
      ENDIF.
      IF ( NOT save     IS INITIAL OR
           NOT savedspl IS INITIAL ) AND
           NOT i_clt[]  IS INITIAL.
        CONCATENATE savepath reports suffix '_clt.txt' INTO filename.
        PERFORM download TABLES i_clt USING filename
                         'Class Description'(053).
      ENDIF.
      IF ( NOT save     IS INITIAL OR
           NOT savedspl IS INITIAL ) AND
           NOT i_cmr[]  IS INITIAL.
        CONCATENATE savepath reports suffix '_cmr.txt' INTO filename.
        PERFORM download TABLES i_cmr USING filename
                         'Class Meta Relations'(054).
      ENDIF.
      IF ( NOT save     IS INITIAL OR
           NOT savedspl IS INITIAL ) AND
           NOT i_cmp[]  IS INITIAL.
        CONCATENATE savepath reports suffix '_cmp.txt' INTO filename.
        PERFORM download TABLES i_cmp USING filename
                         'Class Components'(055).
      ENDIF.
      IF ( NOT save      IS INITIAL OR
           NOT savedspl  IS INITIAL ) AND
           NOT i_cmd_t[] IS INITIAL.
        CONCATENATE savepath reports suffix '_cmd.txt' INTO filename.
        PERFORM download TABLES i_cmd_t USING filename
                         'Class Components Definitions'(056).
      ENDIF.
      IF ( NOT save     IS INITIAL OR
           NOT savedspl IS INITIAL ) AND
           NOT i_cmx[]  IS INITIAL.
        CONCATENATE savepath reports suffix '_cmx.txt' INTO filename.
        PERFORM download TABLES i_cmx USING filename
                         'Class Components Remote Infos'(057).
      ENDIF.
      IF ( NOT save     IS INITIAL OR
           NOT savedspl IS INITIAL ) AND
           NOT i_cmt[]  IS INITIAL.
        CONCATENATE savepath reports suffix '_cmt.txt' INTO filename.
        PERFORM download TABLES i_cmt USING filename
                         'Class Components Descriptions'(058).
      ENDIF.
      IF ( NOT save     IS INITIAL OR
           NOT savedspl IS INITIAL ) AND
           NOT i_irl[]  IS INITIAL.
        CONCATENATE savepath reports suffix '_irl.txt' INTO filename.
        PERFORM download TABLES i_irl USING filename
                         'Class Components Relation Types'(059).
      ENDIF.
      IF ( NOT save     IS INITIAL OR
           NOT savedspl IS INITIAL ) AND
           NOT i_mat[]  IS INITIAL.
        CONCATENATE savepath reports suffix '_mat.txt' INTO filename.
        PERFORM download TABLES i_mat USING filename
                         'Class Mapping Attributes'(060).
      ENDIF.
      IF ( NOT save     IS INITIAL OR
           NOT savedspl IS INITIAL ) AND
           NOT i_mac[]  IS INITIAL.
        CONCATENATE savepath reports suffix '_mac.txt' INTO filename.
        PERFORM download TABLES i_mac USING filename
                         'Class Mapping Classes'(061).
      ENDIF.
      IF ( NOT save     IS INITIAL OR
           NOT savedspl IS INITIAL ) AND
           NOT i_red[]  IS INITIAL.
        CONCATENATE savepath reports suffix '_red.txt' INTO filename.
        PERFORM download TABLES i_red USING filename
                         'Class Redefinitions'(062).
      ENDIF.
      IF ( NOT save     IS INITIAL OR
           NOT savedspl IS INITIAL ) AND
           NOT i_frd[]  IS INITIAL.
        CONCATENATE savepath reports suffix '_frd.txt' INTO filename.
        PERFORM download TABLES i_frd USING filename
                         'Class Friends'(063).
      ENDIF.
      IF ( NOT save     IS INITIAL OR
           NOT savedspl IS INITIAL ) AND
           NOT i_tpl[]  IS INITIAL.
        CONCATENATE savepath reports suffix '_tpl.txt' INTO filename.
        PERFORM download TABLES i_tpl USING filename
                         'Class Type-Pools'(064).
      ENDIF.
      IF ( NOT save     IS INITIAL OR
           NOT savedspl IS INITIAL ) AND
           NOT i_sco[]  IS INITIAL.
        CONCATENATE savepath reports suffix '_sco.txt' INTO filename.
        PERFORM download TABLES i_sco USING filename
                         'Class Sub Components'(065).
      ENDIF.
      IF ( NOT save      IS INITIAL OR
           NOT savedspl  IS INITIAL ) AND
           NOT i_scd_t[] IS INITIAL.
        CONCATENATE savepath reports suffix '_scd.txt' INTO filename.
        PERFORM download TABLES i_scd_t USING filename
                         'Class Sub Components Definitions'(066).
      ENDIF.
      IF ( NOT save     IS INITIAL OR
           NOT savedspl IS INITIAL ) AND
           NOT i_scx[]  IS INITIAL.
        CONCATENATE savepath reports suffix '_scx.txt' INTO filename.
        PERFORM download TABLES i_scx USING filename
                         'Class Sub Components Remote Infos'(067).
      ENDIF.
      IF ( NOT save     IS INITIAL OR
           NOT savedspl IS INITIAL ) AND
           NOT i_sct[]  IS INITIAL.
        CONCATENATE savepath reports suffix '_sct.txt' INTO filename.
        PERFORM download TABLES i_sct USING filename
                         'Class Sub Components Descriptions'(068).
      ENDIF.
      IF ( NOT save     IS INITIAL OR
           NOT savedspl IS INITIAL ) AND
           NOT i_tfd[]  IS INITIAL.
        CONCATENATE savepath reports suffix '_tfd.txt' INTO filename.
        PERFORM download TABLES i_tfd USING filename
                         'Function List'(049).
      ENDIF.
      IF NOT i_inc[] IS INITIAL.
        LOOP AT i_inc.
          REFRESH: i_reptx, i_reptxt.
          READ REPORT i_inc INTO i_repsrc.
          IF codeonly <> 'X'.
            READ TEXTPOOL i_inc INTO i_reptx.
          ENDIF.
          LOOP AT i_reptx.
            MOVE-CORRESPONDING i_reptx TO i_reptxt.
            APPEND i_reptxt.
          ENDLOOP.
          IF NOT display IS INITIAL OR
            NOT savedspl IS INITIAL.
            PERFORM show_inc.
          ENDIF.
          TRANSLATE i_inc TO LOWER CASE.
          TRANSLATE i_inc USING '/.'.
          IF NOT save     IS INITIAL OR
             NOT savedspl IS INITIAL.
            CONCATENATE savepath i_inc suffix '.txt' INTO filename.
            PERFORM download TABLES i_repsrc USING filename
                             'Include Source'(032).
            IF NOT i_reptxt[] IS INITIAL.
              CONCATENATE savepath i_inc suffix '_txt.txt'
                          INTO filename.
              PERFORM download TABLES i_reptxt USING filename
                               'Text elements'(004).
            ENDIF.
          ENDIF.
        ENDLOOP.
      ENDIF.
      IF NOT i_d020t[] IS INITIAL.
        LOOP AT i_d020t.
          IMPORT DYNPRO hdr fld src mat ID i_d020t.
          CALL FUNCTION 'RS_SCRP_UPGRADE_DYNPRO'
               TABLES
                    f = fld
                    m = mat
               CHANGING
                    h = hdr.
          IF src[] IS INITIAL.
            DELETE i_d020t.
            CONTINUE.
          ENDIF.
          CLEAR src.
          READ TABLE src INDEX 1.
          IF src-line CS 'Do not change'.
            DELETE i_d020t.
            CONTINUE.
          ENDIF.
          CALL FUNCTION 'RS_SCRP_GET_SCREEN_INFOS'
               EXPORTING
                    dynnr                 = hdr-dnum
                    progname              = hdr-prog
                    with_fieldlist        = 'X'
               IMPORTING
                    lines                 = lines
                    columns               = rows
               TABLES
                    fieldlist             = fld
               EXCEPTIONS
                    dynpro_does_not_exist = 01
                    no_field_list         = 02.
          hdr-bzmx = lines.
          hdr-bzbr = rows.
          IF NOT display  IS INITIAL OR
             NOT savedspl IS INITIAL.
            PERFORM show_dyn.
          ENDIF.
          IF NOT save     IS INITIAL OR
             NOT savedspl IS INITIAL.
            PERFORM dynpro_download.
          ENDIF.
        ENDLOOP.
        IF ( NOT save     IS INITIAL OR
             NOT savedspl IS INITIAL ) AND
           NOT i_d020t[] IS INITIAL.
          CONCATENATE savepath reports suffix '_dyn.txt' INTO filename.
          PERFORM download TABLES i_d020t USING filename
                           'Dynpro List'(040).
        ENDIF.
      ENDIF.
      IF NOT save     IS INITIAL OR
         NOT savedspl IS INITIAL.
        IF NOT sta4[] IS INITIAL.
          CONCATENATE savepath reports suffix '_sta.txt' INTO filename.
          PERFORM download TABLES sta4 USING filename
                           'GUI Status'(013).
        ENDIF.
        IF NOT ctx4[] IS INITIAL.
          CONCATENATE savepath reports suffix '_ctx.txt' INTO filename.
          PERFORM download TABLES ctx4 USING filename
                           'Object Codes'(045).
        ENDIF.
        IF NOT fun4[] IS INITIAL.
          CONCATENATE savepath reports suffix '_fun.txt' INTO filename.
          PERFORM download TABLES fun4 USING filename
                           'Function Texts'(014).
        ENDIF.
        IF NOT men4[] IS INITIAL.
          CONCATENATE savepath reports suffix '_men.txt' INTO filename.
          PERFORM download TABLES men4 USING filename
                           'Menus'(015).
        ENDIF.
        IF NOT tit4[] IS INITIAL.
          CONCATENATE savepath reports suffix '_sti.txt' INTO filename.
          PERFORM download TABLES tit4 USING filename
                           'Title Codes'(042).
        ENDIF.
        IF NOT mtx4[] IS INITIAL.
          CONCATENATE savepath reports suffix '_mtx.txt' INTO filename.
          PERFORM download TABLES mtx4 USING filename
                           'Menu Texts'(016).
        ENDIF.
        IF NOT act4[] IS INITIAL.
          CONCATENATE savepath reports suffix '_act.txt' INTO filename.
          PERFORM download TABLES act4 USING filename
                           'Menu Bars'(047).
        ENDIF.
        IF NOT but4[] IS INITIAL.
          CONCATENATE savepath reports suffix '_but.txt' INTO filename.
          PERFORM download TABLES but4 USING filename
                           'Push Buttons'(018).
        ENDIF.
        IF NOT pfk4[] IS INITIAL.
          CONCATENATE savepath reports suffix '_pfk.txt' INTO filename.
          PERFORM download TABLES pfk4 USING filename
                           'PF Keys'(019).
        ENDIF.
        IF NOT adm4 IS INITIAL.
          APPEND adm4 TO i_adm4.
          CONCATENATE savepath reports suffix '_adm.txt' INTO filename.
          PERFORM download TABLES i_adm4 USING filename
                           'Management Information'(043).
        ENDIF.
        IF NOT set4[] IS INITIAL.
          CONCATENATE savepath reports suffix '_set.txt' INTO filename.
          PERFORM download TABLES set4 USING filename
                           'Function Sets'(020).
        ENDIF.
        IF NOT stx4[] IS INITIAL.
          CONCATENATE savepath reports suffix '_stx.txt' INTO filename.
          PERFORM download TABLES stx4 USING filename
                           'Status Texts'(023).
        ENDIF.
        IF NOT doc4[] IS INITIAL.
          CONCATENATE savepath reports suffix '_doc.txt' INTO filename.
          PERFORM download TABLES doc4 USING filename
                           'Status Short Texts'(024).
        ENDIF.
        IF NOT biv46c[] IS INITIAL.
          CONCATENATE savepath reports suffix '_biv.txt' INTO filename.
          PERFORM download TABLES biv46c USING filename
                           'Invariant Functions'(048).
        ENDIF.
        IF NOT tit[] IS INITIAL.
          CONCATENATE savepath reports suffix '_tit.txt' INTO filename.
          PERFORM download TABLES tit USING filename
                           'Title Bars'(030).
        ENDIF.
      ENDIF.
      ULINE.
    ENDLOOP.
  ENDIF.
  REFRESH reports.
*&      Form  DOWNLOAD
FORM download TABLES   tabelle
              USING    value(filename)
                       component.
  CALL FUNCTION 'GUI_DOWNLOAD'
       EXPORTING
          BIN_FILESIZE            = ' '
            filename                = filename
            filetype                = 'ASC'
     IMPORTING
          FILELENGTH              =
       TABLES
            data_tab                = tabelle
       EXCEPTIONS
            file_write_error        = 1
            no_batch                = 2
            gui_refuse_filetransfer = 3
            invalid_type            = 4
            OTHERS                  = 5.
IF reports IS INITIAL.
   WRITE: / appls.
ELSE.
   WRITE: / reports.
ENDIF.
  WRITE: /(20) component.
  IF sy-subrc = 0.
    WRITE: 'successfully downloaded'(001).
    PERFORM getfilename USING    filename
                        CHANGING filename.
    WRITE: '->', filename.
  ELSE.
    WRITE: 'not downloaded,  RC ='(002), sy-subrc.
  ENDIF.
ENDFORM.                                                    " DOWNLOAD
*&      Form  FILESELECTOR
FORM fileselector.
  DATA: repname(250).
  DATA: fdpos(2) TYPE p.
  CALL FUNCTION 'WS_FILENAME_GET'
       EXPORTING
          DEF_FILENAME     = ' '
            def_path         = path
            mask             = ',.txt,.txt.'
            mode             = 'O'
          TITLE            = ' '
       IMPORTING
            filename         = file
          RC               =
       EXCEPTIONS
            inv_winsys       = 1
            no_batch         = 2
            selection_cancel = 3
            selection_error  = 4
            OTHERS           = 5.
  subrc = sy-subrc.
  path = file.
  CLEAR: sy-fdpos, sy-subrc.
  fdpos = 1.
  WHILE sy-subrc = 0.
    fdpos = fdpos + sy-fdpos + 1.
    SEARCH path FOR delim STARTING AT fdpos.
  ENDWHILE.
  fdpos = fdpos - 1.
  path = path(fdpos).
  repname = file.
  CLEAR sy-subrc.
  WHILE sy-subrc = 0.
    SHIFT repname LEFT.
    SHIFT repname LEFT UP TO delim.
  ENDWHILE.
  SHIFT repname RIGHT UP TO '.'.
  SHIFT repname RIGHT.
  SHIFT repname LEFT DELETING LEADING space.
  TRANSLATE repname TO UPPER CASE.
  reports = repname.
  APPEND reports.
ENDFORM.                               " FILESELECTOR
*&      Form  LS
FORM ls.
  TYPES: c80(80).
  DATA: dirtab TYPE STANDARD TABLE OF c80 WITH HEADER LINE.
  DATA: datei TYPE string.
  DATA: i LIKE sy-tabix.
  DATA: endtime LIKE sy-uzeit.
  CALL FUNCTION 'WS_EXECUTE'
       EXPORTING
          DOCUMENT       = ' '
            cd             = path
            commandline    = command
          INFORM         = ' '
            program        = shell
          STAT           = ' '
          WINID          = ' '
          OSMAC_SCRIPT   = ' '
          OSMAC_CREATOR  = ' '
          WIN16_EXT      = ' '
          EXEC_RC        = ' '
     IMPORTING
          RBUFF          =
       EXCEPTIONS
            frontend_error = 1
            no_batch       = 2
            prog_not_found = 3
            illegal_option = 4
            OTHERS         = 5.
  IF sy-subrc NE 0.
    MESSAGE e001(pc).
  Error when executing the WS program
  ENDIF.
  CONCATENATE path 'dir.tmp'  INTO datei.
  GET TIME.
  endtime = sy-uzeit + 3.
  WHILE sy-uzeit < endtime.
    GET TIME.
  ENDWHILE.
  CALL FUNCTION 'GUI_UPLOAD'
       EXPORTING
            filename                = datei
            filetype                = 'ASC'
     IMPORTING
          FILELENGTH              =
       TABLES
            data_tab                = dirtab
       EXCEPTIONS
            file_read_error         = 1
            no_batch                = 2
            gui_refuse_filetransfer = 3
            invalid_type            = 4
            OTHERS                  = 5.
  IF sy-subrc NE 0.
    MESSAGE e001(pc).
  Error when executing the WS program
  ENDIF.
  REFRESH reports.
  i = 1.
  DO.
    SEARCH dirtab FOR '.txt' STARTING AT i.
    IF sy-subrc NE 0.
      EXIT.
    ENDIF.
    READ TABLE dirtab INDEX sy-tabix.
    i = sy-tabix + 1.
    CHECK dirtab NS 'txt_.txt'.
    SHIFT dirtab LEFT UP TO space.
    SHIFT dirtab LEFT DELETING LEADING space.
    SHIFT dirtab LEFT UP TO space.
    SHIFT dirtab LEFT DELETING LEADING space.
    SHIFT dirtab LEFT UP TO space.
    SHIFT dirtab RIGHT UP TO '.'.
    SHIFT dirtab RIGHT.
    SHIFT dirtab LEFT DELETING LEADING space.
    IF NOT dirtab IS INITIAL.
      TRANSLATE dirtab TO LOWER CASE.
      APPEND dirtab TO reports.
    ENDIF.
  ENDDO.
  SORT reports.
  DELETE ADJACENT DUPLICATES FROM reports.
ENDFORM.                                                    " LS
*&      Form  SHOW_DYN
FORM show_dyn.
Printing Dynpro data
Header for Dynpro
  FORMAT COLOR COL_TOTAL.
  WRITE: / 'Dynpro header', AT sy-linsz ''.
  FORMAT COLOR COL_NORMAL.
  WRITE: / 'Program:',    30 hdr-prog, AT sy-linsz '',
         / 'Dynpro:',      30 hdr-dnum, AT sy-linsz '',
         / 'Follow-up dynpro:', 30 hdr-fnum, AT sy-linsz ''.
  ULINE.
Print field list
  FORMAT COLOR COL_TOTAL.
  WRITE:  / 'Field list'  COLOR COL_TOTAL, AT sy-linsz ''.
  FORMAT COLOR COL_HEADING.
  WRITE:  / 'Field',
         25 'Line',
         30 'Column',
         37 'TYPE',
         42 'LOOPTyp',
         50 'DDIC',
         55 'FormByte', AT sy-linsz ''.
  CALL FUNCTION 'RS_SCRP_FIELDS_RAW_TO_CHAR'
       TABLES
            fields_int  = fld
            fields_char = fields_char
       EXCEPTIONS
            OTHERS      = 1.
  FORMAT COLOR COL_NORMAL.
  LOOP AT fields_char.
    WRITE: /(24) fields_char-feldname,
              25 fields_char-line,
              30 fields_char-coln,
              37 fields_char-feldformat,
              42 fields_char-looptype,
              50 fields_char-inttyp,
              55 fields_char-fmb1,
              58 fields_char-fmb2.
  ENDLOOP.
  ULINE.
Display logic
  FORMAT COLOR COL_TOTAL.
  WRITE: / 'Logic', AT sy-linsz ''.
  FORMAT COLOR COL_NORMAL.
  LOOP AT src.
    WRITE: / src-line.
  ENDLOOP.
  ULINE.
  SKIP.
Display matchcode data
  FORMAT COLOR COL_TOTAL.
  WRITE: / 'Matchcode data', AT sy-linsz ''.
  FORMAT COLOR COL_NORMAL.
  LOOP AT mat.
    WRITE: /(80) mat.
  ENDLOOP.
  IF sy-subrc NE 0.
    WRITE / ' no matchcode files available ' COLOR COL_NEGATIVE.
  ENDIF.
  NEW-PAGE.
ENDFORM.                                                    " SHOW_DYN
*&      Form  SHOW_REP
FORM show_rep.
  FORMAT COLOR COL_TOTAL.
  WRITE: / 'Program:', reports, AT sy-linsz ''.
  FORMAT COLOR COL_BACKGROUND.
  LOOP AT i_repsrc.
    WRITE: / i_repsrc.
  ENDLOOP.
  ULINE.
  FORMAT COLOR COL_TOTAL.
  WRITE: / 'Text elements for program:', reports, AT sy-linsz ''.
  FORMAT COLOR COL_HEADING.
  WRITE:  / 'Type',
          5 'Key',
         20 'Length',
         30 'Text', AT sy-linsz ''.
  FORMAT COLOR COL_NORMAL.
  LOOP AT i_reptxt.
    WRITE: / i_reptxt-id,
           5 i_reptxt-key,
       20(4) i_reptxt-length,
      30(80) i_reptxt-entry.
  ENDLOOP.
  NEW-PAGE.
ENDFORM.                                                    " SHOW_REP
*&      Form  SHOW_INC
FORM show_inc.
  FORMAT COLOR COL_TOTAL.
  WRITE: / 'Include:', i_inc, AT sy-linsz ''.
  FORMAT COLOR COL_BACKGROUND.
  LOOP AT i_repsrc.
    WRITE: / i_repsrc.
  ENDLOOP.
  ULINE.
  FORMAT COLOR COL_TOTAL.
  WRITE: / 'Text elements for include:', i_inc, AT sy-linsz ''.
  FORMAT COLOR COL_HEADING.
  WRITE:  / 'Type',
          5 'Key',
         20 'Length',
         30 'Text', AT sy-linsz ''.
  FORMAT COLOR COL_NORMAL.
  LOOP AT i_reptxt.
    WRITE: / i_reptxt-id,
           5 i_reptxt-key,
       20(4) i_reptxt-length,
      30(80) i_reptxt-entry.
  ENDLOOP.
  NEW-PAGE.
ENDFORM.                                                    " SHOW_INC
*&      Form  DYNPRO_DOWNLOAD
&

Similar Messages

  • How to insert Logo in module pool programming

    Plz any one can explain me that  how we will inseart Logo on screens by using module pool programming (in GUI programming) .

    Hello.
    I'll give you an example of inserting a personal photo in UI programming. Hope it helps you.
    First of all, in your screen (painter), insert a custom control and give it a name (PHOTO in my example).
    Then, in your screen PBO, insert a coding like this:
    CLEAR handle.
    CALL FUNCTION 'HR_IMAGE_INIT'
        EXPORTING
          p_pernr        = pernr
          p_tclas        = 'A'
          container      = 'PHOTO'
        IMPORTING
          handle         = handle
        EXCEPTIONS
          no_document    = 1
          internal_error = 2
          OTHERS         = 3.
      CALL FUNCTION 'HR_IMAGE_SHOW'
        EXPORTING
          p_pernr        = pernr
          p_tclas        = 'A'
          handle         = handle
        EXCEPTIONS
          invalid_handle = 1
          no_document    = 2
          internal_error = 3
          OTHERS         = 4.
    Regards.
    Valter Oliveira.

  • How to conduct training for Module Pool Programming

    Hi everybody
    I am going to conduct 5 days training for module pool programming.
    Can you please provide me some suggestion about how to start & what r the steps?
    Please provide suggestion for following
    1) From where should I start
    2) What should be the first step & subsequent steps
    3) how should I get documentation & sample programs
    thanks

    Hello,
    You can start the training by first explaining what is Module Pool programming, and why is it needed, how is it different from other forms of programming , like reports(SE38).
    Then go on to explain how to create a MPP , i.e this you can do by giving the demo online, like:-
    Goto SE80
    Create a new program, and so on.
    Talk about the various elements of MPP, such as the scree(which is also known as Dynpro), text elements, pushbuttons, tabstrips, etc, and how to use them in the program.
    For sample programs and documentation, you can refer to help.sap.com, and search the documnetation for Module Pool Programming.
    Thanks and regards,
    Prerna

  • How to down load the Module pool program from sap

    hi friends,
    i am having the Module pool program in one server
    it consists of 1 screen.
    now i want to down load the Module pool program into another server.
    those two server are not linked.
    is there any way to copy from one server to another server.
    like what we do in smartfroms,that is downloading form and uploading the form.

    Hi,
    You can down load code from source system and u can upload those in your destination system. You can down load  Code as normally like    execute SE38 > enter ur program name> click on change button> Utilities(in menu bar)->more utilities>upload/down load>down load  in source system & Just use same path with upload instead of down load. So this will help u to transfer code from one system to other.
    Screens transfer: SE51> enter ur program name & screen no> click on change button> click on Layout button> Utilities(m)>upload/download>download for down loading a screen from source system.
             And follow the same procedure in destination system also just use up load instead of download. to upload a screen in destination system.
    Hope useful.
    Regards,
    BBR.

  • How to call a "Z"module pool program in a "z"report

    Hi Guys,
    I have two reports .
    1. Report : uploads a tab delimited " .Txt1" file and update the "z1" table
        ".TXT1" : File contains 4 fields
    2. Module pool. :Uploads a a tab delimited " .Txt2" file and update another "z2" table
        ".TXT2" file contains  the 4 fileds of ".TXT1" and also 2 extra fields.
    I want to merge (call) the module pool program in the Report and perform the upload function using only one ".TXT" file.Please do guide me precisely .
    *Report:*
    REPORT zrswbgcs009 NO STANDARD PAGE HEADING MESSAGE-ID zwb
                         LINE-SIZE 185.
    TABLES:  zgcs_foc.      "FOC Parts Table
    *data count buffer
    DATA:    read_cnt(6)    TYPE p,        "Find read record
             update_cnt(6)  TYPE p,        "OK record
             error_cnt(6)   TYPE p.        "Error record
    *file buffer(FOC)
    DATA: BEGIN OF FOC_inrec  OCCURS  0,
            CUSTOMER(10),      "Customer
            PART_CODE(18),     "Parts Code
            REF_NO(35),        "Ref No.
            REF_DATE(10),      "Ref Date
            QTY(12),           "Parts Qty
            TEXT(100),         "Remark
          END OF FOC_inrec.
    *file buffer
    DATA: BEGIN OF inrec  OCCURS  0,
            CUSTOMER(10),      "Customer
            PART_CODE(18),     "Parts Code
            REF_NO(35),        "Ref No.
            REF_DATE(10),      "Ref Date
            QTY(12),           "Parts Qty
            PRICE(15),         "Parts Price
            WAERK(5),          "Parts Currency
            TEXT(100),         "Remark
          END OF inrec.
    DATA : v_file      LIKE rlgrap-filename.
    DATA gt_zgcs_foc LIKE zgcs_foc OCCURS 0 WITH HEADER LINE.
    DATA gs_zgcs_foc LIKE zgcs_foc.
    *File name ACCEPT--------------------------------------------------
    SELECTION-SCREEN SKIP 1.
    SELECTION-SCREEN  BEGIN OF BLOCK b1 WITH FRAME TITLE text-001.
    *Company code
    PARAMETERS:  p_comp LIKE zgcs_imei-company OBLIGATORY.
    PARAMETERS:  pcfile LIKE rlgrap-filename OBLIGATORY LOWER CASE.
    SELECTION-SCREEN BEGIN OF LINE.
    SELECTION-SCREEN POSITION 1.
    PARAMETERS: HQfile  RADIOBUTTON GROUP b2.
    SELECTION-SCREEN COMMENT 7(20)  text-101 FOR FIELD HQfile.
    SELECTION-SCREEN POSITION 31.
    PARAMETERS: SUBfile RADIOBUTTON GROUP b2.
    SELECTION-SCREEN COMMENT 37(20) text-102 FOR FIELD SUBfile.
    SELECTION-SCREEN END OF LINE.
    SELECTION-SCREEN  END   OF BLOCK b1.
    SELECTION-SCREEN SKIP 1.
    SELECTION-SCREEN BEGIN OF BLOCK box WITH FRAME.
    SELECTION-SCREEN: COMMENT /2(40) text-011, COMMENT  42(40) text-001,
                      ULINE,
                      COMMENT /2(40) text-012, COMMENT  42(40) text-002,
                      COMMENT /2(40) text-013, COMMENT  42(40) text-003,
                      COMMENT /2(40) text-014, COMMENT  42(40) text-004,
                      COMMENT /2(40) text-015, COMMENT  42(40) text-005,
                      COMMENT /2(40) text-016, COMMENT  42(40) text-006,
                      COMMENT /2(40) text-017, COMMENT  42(40) text-007,
                      COMMENT /2(40) text-018, COMMENT  42(40) text-008,
                                               COMMENT /42(40) text-009.
    SELECTION-SCREEN END OF BLOCK box.
    * -- AT SELECTION SCREEN ON
    AT SELECTION-SCREEN ON VALUE-REQUEST FOR pcfile.
      CALL FUNCTION 'WS_FILENAME_GET'
           EXPORTING
                def_filename     = space
                def_path         = 'C:\'
                mask             = ',*.txt,*.TXT.'
                mode             = 'O'
                title            = ' '
           IMPORTING
                filename         = pcfile
           EXCEPTIONS
                inv_winsys       = 1
                no_batch         = 2
                selection_cancel = 3
                selection_error  = 4
                OTHERS           = 5.
    *-----------------------------start--------------------------------
    START-OF-SELECTION.
      CLEAR: read_cnt, update_cnt, error_cnt.
      REFRESH gt_zgcs_foc.        CLEAR gs_zgcs_foc.
      PERFORM file_upload_from_pc.
      SORT gt_zgcs_foc.
      DELETE ADJACENT DUPLICATES FROM gt_zgcs_foc
             COMPARING COMPANY CUSTOMER PART_CODE REF_NO REF_DATE.
    *// customer code check
      DATA: LT_ZESTD LIKE ZESTD OCCURS 0 WITH HEADER LINE.
      IF NOT gt_zgcs_foc[] IS INITIAL.
        SELECT COMPANY CUSTOMER CURRENCY
          INTO CORRESPONDING FIELDS OF TABLE LT_ZESTD
          FROM ZESTD
           FOR ALL ENTRIES IN gt_zgcs_foc
         WHERE COMPANY  = gt_zgcs_foc-COMPANY
           AND CUSTOMER = gt_zgcs_foc-CUSTOMER.
      ENDIF.
      SORT LT_ZESTD BY COMPANY CUSTOMER.
    *// part code check
      DATA: LT_MARA LIKE MARA OCCURS 0 WITH HEADER LINE.
      IF NOT gt_zgcs_foc[] IS INITIAL.
        SELECT *
          INTO TABLE LT_MARA
          FROM MARA
           FOR ALL ENTRIES IN gt_zgcs_foc
         WHERE MATNR = gt_zgcs_foc-PART_CODE.
      ENDIF.
      SORT LT_MARA BY MATNR.
      LOOP AT gt_zgcs_foc.
    *// customer code check
        READ TABLE LT_ZESTD WITH KEY
                COMPANY  = gt_zgcs_foc-COMPANY
                CUSTOMER = gt_zgcs_foc-CUSTOMER.
        IF SY-SUBRC <> 0.
          WRITE:/'Invalid Customer code ',
             gt_zgcs_foc-COMPANY, ' ',
             gt_zgcs_foc-CUSTOMER.
          STOP.
        ENDIF.
    *// part code check
        READ TABLE LT_MARA WITH KEY MATNR = gt_zgcs_foc-PART_CODE
          BINARY SEARCH.
        IF SY-SUBRC <> 0.
          WRITE:/ 'Invalid part code ', gt_zgcs_foc-PART_CODE.
          STOP.
        ENDIF.
    *// REF_NO
        TRANSLATE gt_zgcs_foc-REF_NO     TO UPPER CASE.
        SHIFT gt_zgcs_foc-REF_NO     LEFT DELETING LEADING SPACE.
        IF gt_zgcs_foc-REF_NO = SPACE.
          WRITE:/'Ref No. is blank'.
          STOP.
        ENDIF.
    *// REF_DATE
        IF gt_zgcs_foc-REF_DATE = 0.
          WRITE:/'Invalid Ref Date'.
          STOP.
        ENDIF.
    *// QTY
    *    IF gt_zgcs_foc-QTY CO ' 0123456789'.
    *    ELSE.
    *      WRITE:/ gt_zgcs_foc-QTY, ' Invalid Qty value'.
    *      STOP.
    *    ENDIF.
      ENDLOOP.
    * Insert/Update table
    *  MODIFY zgcs_foc FROM TABLE gt_zgcs_foc.
      INSERT zgcs_foc FROM TABLE gt_zgcs_foc.
      IF sy-subrc EQ 0.
        COMMIT WORK.
        DESCRIBE TABLE gt_zgcs_foc LINES update_cnt.
        error_cnt = read_cnt - update_cnt.
      ELSE.
        ROLLBACK WORK.
        error_cnt = read_cnt - update_cnt.
      ENDIF.
      ULINE.
      FORMAT COLOR 3.
      WRITE: / 'Read count                :', read_cnt.
      WRITE: / 'Insert/Update count       :', update_cnt.
      WRITE: / 'Error count               :', error_cnt.
      FORMAT COLOR OFF.
    *end-of-selection--------------------------------------------------
    END-OF-SELECTION.
    *&      Form FILE_UPLOAD_FROM_PC
    FORM file_upload_from_pc.
      IF pcfile IS INITIAL.
        WRITE: / 'SELECT UPLOAD FILE !'.
      ELSE.
        MOVE pcfile TO v_file.
    * HQ file upload
        IF HQfile EQ 'X'.
          CALL FUNCTION 'WS_UPLOAD'
               EXPORTING
                    filename                = v_file
                    filetype                = 'DAT'
               TABLES
                    data_tab                = FOC_inrec
               EXCEPTIONS
                    conversion_error        = 1
                    file_open_error         = 2
                    file_read_error         = 3
                    invalid_type            = 4
                    no_batch                = 5
                    unknown_error           = 6
                    invalid_table_width     = 7
                    gui_refuse_filetransfer = 8
                    customer_error          = 9
                    OTHERS                  = 10.
          IF sy-subrc <> 0.
            WRITE: / 'FILE UPLOAD                :', sy-subrc.
          ENDIF.
          LOOP AT FOC_inrec.
            ADD 1 TO read_cnt.
            call function 'CONVERSION_EXIT_ALPHA_INPUT'
                 exporting
                      input  = FOC_inrec-customer
                 importing
                      output = FOC_inrec-customer.
            call function 'CONVERSION_EXIT_ALPHA_INPUT'
                 exporting
                      input  = FOC_inrec-part_code
                 importing
                      output = FOC_inrec-part_code.
            MOVE-CORRESPONDING FOC_inrec TO gs_zgcs_foc.
            MOVE p_comp          TO gs_zgcs_foc-company.
            MOVE gs_zgcs_foc-qty TO gs_zgcs_foc-balan.
            MOVE sy-uname        TO gs_zgcs_foc-ERNAM.
            MOVE sy-datum        TO gs_zgcs_foc-ERDAT.
            MOVE sy-UZEIT        TO gs_zgcs_foc-ERZET.
    * Source(1:HQ,2:SUB,0:Etc)
            MOVE '1'             TO gs_zgcs_foc-source.
            APPEND gs_zgcs_foc TO gt_zgcs_foc.
          ENDLOOP.
    * SGE file upload
        ELSE.
          CALL FUNCTION 'WS_UPLOAD'
               EXPORTING
                    filename                = v_file
                    filetype                = 'DAT'
               TABLES
                    data_tab                = inrec
               EXCEPTIONS
                    conversion_error        = 1
                    file_open_error         = 2
                    file_read_error         = 3
                    invalid_type            = 4
                    no_batch                = 5
                    unknown_error           = 6
                    invalid_table_width     = 7
                    gui_refuse_filetransfer = 8
                    customer_error          = 9
                    OTHERS                  = 10.
          IF sy-subrc <> 0.
            WRITE: / 'FILE UPLOAD                :', sy-subrc.
          ENDIF.
          LOOP AT inrec.
            ADD 1 TO read_cnt.
            call function 'CONVERSION_EXIT_ALPHA_INPUT'
                 exporting
                      input  = inrec-customer
                 importing
                      output = inrec-customer.
            call function 'CONVERSION_EXIT_ALPHA_INPUT'
                 exporting
                      input  = FOC_inrec-part_code
                 importing
                      output = FOC_inrec-part_code.
            MOVE-CORRESPONDING inrec TO gs_zgcs_foc.
            MOVE p_comp          TO gs_zgcs_foc-company.
            MOVE gs_zgcs_foc-qty TO gs_zgcs_foc-balan.
            MOVE sy-uname        TO gs_zgcs_foc-ERNAM.
            MOVE sy-datum        TO gs_zgcs_foc-ERDAT.
            MOVE sy-UZEIT        TO gs_zgcs_foc-ERZET.
    * Source(1:HQ,2:SUB,0:Etc)
            MOVE '2'             TO gs_zgcs_foc-source.
            APPEND gs_zgcs_foc TO gt_zgcs_foc.
          ENDLOOP.
        ENDIF.
      ENDIF.
    ENDFORM.
    *MODULE POOL::*
    *& Module Name      : Warranty Bill
    *& Sub-Module       : W/B
    *& Description      : Parts Q'ty Adjust(Sales & Warranty)
    *& Program Name     : ZRSWBP004
    *& History
    *& Date             Author            Reason
    *& 2007.05.08       Song, Ji-Hyun     Initial Coding     Req.by WH.Song
    *& Logic Process
    *  - CONDITIONS
    *    Company, Customer, Material
    *  - PROCESS
    *    Display,Insert,Update data in the T/B ZESP04
    REPORT  zrswbp004 NO STANDARD PAGE HEADING
                      MESSAGE-ID 00
                      LINE-SIZE  250
                      LINE-COUNT 50.
    *               G L O B A L    V A R I A B L E S                       *
    TABLES : zesp04.
    DATA : BEGIN OF itab_list OCCURS 0,
            company       LIKE zesp04-company,
            customer      LIKE zesp04-customer,
            material      LIKE zesp04-material,
            adj_date      LIKE zesp04-adj_date,
            adjust        LIKE zesp04-adjust,
            reason        LIKE zesp04-reason,
            reason_code   LIKE zesp04-reason_code,
            doc_no        LIKE zesp04-doc_no,
            in_date       LIKE zesp04-in_date,
            create_id     LIKE zesp04-create_id,
          END OF itab_list.
    DATA : itab_upload LIKE TABLE OF zesp04 WITH HEADER LINE.
    DATA : s_mode(10).
    DATA : table_name(10) VALUE 'ZESP04'.
    DATA : tot_cnt TYPE i.
    DATA : ref_flag(1).
    *               M A C R O    D E F I N E                               *
    DEFINE conversion_kunnr.
      call function 'CONVERSION_EXIT_ALPHA_INPUT'
           exporting
                input  = &1
           importing
                output = &1.
    END-OF-DEFINITION.
    DEFINE conversion_material.
      call function 'CONVERSION_EXIT_MATN1_INPUT'
           exporting
                input  = &1
           importing
                output = &1.
    END-OF-DEFINITION.
    *               S E L E C T I O N   S C R E E N                        *
    SELECTION-SCREEN BEGIN OF BLOCK b1 WITH FRAME  TITLE title1.
    PARAMETERS     : company LIKE zesp04-company MEMORY ID buk MODIF ID v1
                     OBLIGATORY.
    SELECT-OPTIONS : customer   FOR zesp04-customer MEMORY ID kun
                                                    MODIF ID v1.
    SELECT-OPTIONS : material   FOR zesp04-material MEMORY ID mat
                                                    MODIF ID v1.
    SELECTION-SCREEN SKIP.
    SELECTION-SCREEN BEGIN OF LINE.
    SELECTION-SCREEN POSITION 3.
    SELECTION-SCREEN COMMENT 3(12) text-002 MODIF ID v2.
    PARAMETERS : up_flag AS CHECKBOX MODIF ID v2.
    SELECTION-SCREEN END OF LINE.
    SELECTION-SCREEN BEGIN OF LINE.
    SELECTION-SCREEN COMMENT 3(12) text-001 MODIF ID v2.
    PARAMETERS : p_fname(300) LOWER CASE MODIF ID v2.
    SELECTION-SCREEN END OF LINE.
    SELECTION-SCREEN END OF BLOCK b1.
    SELECTION-SCREEN BEGIN OF BLOCK b2 WITH FRAME  TITLE title2.
    SELECTION-SCREEN BEGIN OF LINE.
    SELECTION-SCREEN COMMENT 3(53) text-003 MODIF ID v2.
    SELECTION-SCREEN END OF LINE.
    SELECTION-SCREEN BEGIN OF LINE.
    SELECTION-SCREEN COMMENT 5(10) text-004 MODIF ID v2.
    SELECTION-SCREEN END OF LINE.
    SELECTION-SCREEN BEGIN OF LINE.
    SELECTION-SCREEN COMMENT 5(12) text-005 MODIF ID v2.
    SELECTION-SCREEN END OF LINE.
    SELECTION-SCREEN BEGIN OF LINE.
    SELECTION-SCREEN COMMENT 5(12) text-006 MODIF ID v2.
    SELECTION-SCREEN END OF LINE.
    SELECTION-SCREEN BEGIN OF LINE.
    SELECTION-SCREEN COMMENT 5(15) text-007 MODIF ID v2.
    PARAMETERS : df1 TYPE c RADIOBUTTON GROUP grp1.
    SELECTION-SCREEN COMMENT 24(13) text-012 MODIF ID v2.
    PARAMETERS : df2 TYPE c RADIOBUTTON GROUP grp1.
    SELECTION-SCREEN COMMENT 41(11) text-013 MODIF ID v2.
    SELECTION-SCREEN END OF LINE.
    SELECTION-SCREEN BEGIN OF LINE.
    SELECTION-SCREEN COMMENT 5(14) text-008 MODIF ID v2.
    SELECTION-SCREEN END OF LINE.
    SELECTION-SCREEN BEGIN OF LINE.
    SELECTION-SCREEN COMMENT 5(11) text-009 MODIF ID v2.
    SELECTION-SCREEN END OF LINE.
    SELECTION-SCREEN BEGIN OF LINE.
    SELECTION-SCREEN COMMENT 5(14) text-010 MODIF ID v2.
    SELECTION-SCREEN END OF LINE.
    SELECTION-SCREEN BEGIN OF LINE.
    SELECTION-SCREEN COMMENT 5(10) text-011 MODIF ID v2.
    SELECTION-SCREEN END OF LINE.
    SELECTION-SCREEN END OF BLOCK b2.
    INCLUDE zrswbp004_pbo.
    INCLUDE zrswbp004_pai.
    INITIALIZATION.
      title1 = ' Parts Quantity Adjustment '.
      title2 = ' Text File Layout '.
    *            S T A R T   O F   S E L E C T I O N                       *
    TOP-OF-PAGE.
      PERFORM write_header.
    TOP-OF-PAGE DURING LINE-SELECTION.
      PERFORM write_header.
    START-OF-SELECTION.
      IF up_flag = 'X'.
        PERFORM upload_data.
      ELSE.
        PERFORM select_data.
        SET PF-STATUS 'PF01' EXCLUDING 'SAVE'.
        PERFORM display_data.
      ENDIF.
    AT USER-COMMAND.
      PERFORM user_command.
    AT SELECTION-SCREEN ON VALUE-REQUEST FOR p_fname.
      PERFORM get_filename.
    *&      Form  SELECT_DATA
    *       Select Data for Display
    FORM select_data.
      SELECT * FROM (table_name)
        INTO CORRESPONDING FIELDS OF TABLE itab_list
       WHERE company = company
         AND customer IN customer
         AND material IN material.
      CHECK sy-subrc <> 0.
      WRITE: 'No data found with your option.'.
    ENDFORM.                    " SELECT_DATA
    *&      Form  DISPLAY_DATA
    *       Display Data following Condition
    FORM display_data.
      LOOP AT itab_list.
        FORMAT COLOR 2 INTENSIFIED.
        WRITE : / '|' NO-GAP.
        WRITE :  (07) itab_list-company    CENTERED   NO-GAP, '|' NO-GAP,
                 (10) itab_list-customer   CENTERED   NO-GAP, '|' NO-GAP,
                 (20) itab_list-material   CENTERED   NO-GAP, '|' NO-GAP,
                 (10) itab_list-adj_date   CENTERED   NO-GAP, '|' NO-GAP,
                 (15) itab_list-adjust  RIGHT-JUSTIFIED  NO-GAP, '|'
    NO-GAP,
                 (55) itab_list-reason LEFT-JUSTIFIED NO-GAP, '|' NO-GAP,
                 (11) itab_list-reason_code CENTERED  NO-GAP, '|' NO-GAP,
                 (10) itab_list-doc_no      CENTERED  NO-GAP, '|' NO-GAP,
                 (10) itab_list-in_date  CENTERED   NO-GAP, '|' NO-GAP,
                 (12) itab_list-create_id  CENTERED   NO-GAP, '|' NO-GAP.
        FORMAT INTENSIFIED OFF.
        HIDE itab_list.
      ENDLOOP.
      WRITE : / sy-uline(171).
    ENDFORM.                    " DISPLAY_DATA
    *&      Form  WRITE_HEADER
    *       Write Report Header
    FORM write_header.
      DATA : line(1024).
      CLEAR line WITH '-'.
      DESCRIBE TABLE itab_list LINES tot_cnt.
      FORMAT INTENSIFIED ON.
      WRITE : 15 'Parts Quantity Adjustment'.
      SKIP.
      WRITE : / 'Total Count : ', tot_cnt.
      WRITE : /.
      WRITE : (171) sy-uline.
      WRITE : / '|' NO-GAP.
      WRITE : (07) 'Company'  CENTERED   NO-GAP, '|' NO-GAP,
              (10) 'Customer' CENTERED   NO-GAP, '|' NO-GAP,
              (20) 'Material' CENTERED   NO-GAP, '|' NO-GAP,
              (10) 'Adj. Date' CENTERED   NO-GAP, '|' NO-GAP,
              (15) 'Adjust' CENTERED   NO-GAP, '|' NO-GAP,
              (55) 'Reason' CENTERED   NO-GAP, '|' NO-GAP,
              (11) 'Reason Code' CENTERED   NO-GAP, '|' NO-GAP,
              (10) 'Doc No' CENTERED   NO-GAP, '|' NO-GAP,
              (10) 'IN DATE' CENTERED   NO-GAP, '|' NO-GAP,
              (12) 'CREATE ID' CENTERED   NO-GAP, '|' NO-GAP.
      WRITE : /(171) sy-uline.
      FORMAT INTENSIFIED OFF.
    ENDFORM.                    " WRITE_HEADER
    *&      Form  UPLOAD_DATA
    *       Data Upload from File
    FORM upload_data.
      DATA : l_filename LIKE rlgrap-filename,
             temp_dateformat TYPE dateformat.
      IF df1 = 'X'.
        temp_dateformat = 'YYYY.MM.DD'.
      ELSE.
        temp_dateformat = 'DD.MM.YYYY'.
      ENDIF.
      MOVE p_fname TO l_filename.
      CHECK l_filename NE space.
      CALL FUNCTION 'WS_UPLOAD'
           EXPORTING
                filename                = l_filename
                filetype                = 'DAT'
                dat_d_format            = temp_dateformat
           TABLES
                data_tab                = itab_list
           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.
      IF sy-subrc NE 0.
        MESSAGE s000 WITH 'File upload is failed!'.
        STOP.
      ELSE.
        CLEAR : itab_upload, itab_upload[].
        LOOP AT itab_list.
          MOVE-CORRESPONDING itab_list TO itab_upload.
          conversion_kunnr    itab_upload-customer.
          conversion_material itab_upload-material.
          itab_upload-mandt     = sy-mandt.
          itab_upload-in_date   = sy-datum.
          itab_upload-create_id = sy-uname.
    *>>>>Insert by GSCHOI 2007.11.08
          IF itab_list-adj_date+0(6) NE sy-datum+0(6).
            MESSAGE i368 WITH 'Adjust month must same as current month!'.
            ROLLBACK WORK.
            STOP.
          ENDIF.
    *<<<<End
          APPEND itab_upload.
          INSERT INTO (table_name) VALUES itab_upload.
          IF sy-subrc EQ 0.
            CONTINUE.
          ELSEIF sy-subrc EQ 4.
            MESSAGE s368 WITH 'Duplicated Data Error!'.
            ROLLBACK WORK.
            STOP.
          ELSE.
            MESSAGE s368 WITH 'File Error!'.
            ROLLBACK WORK.
            STOP.
          ENDIF.
        ENDLOOP.
      ENDIF.
      IF sy-subrc EQ 0.
        MESSAGE s368 WITH 'Uploaded Successfully!'.
      ENDIF.
    ENDFORM.                    " UPLOAD_DATA
    *&      Form  USER_COMMAND
    *       User Command Execution in Screen 1000
    FORM user_command.
      MOVE-CORRESPONDING itab_list TO zesp04.
      CASE sy-ucomm.
        WHEN 'INSERT'.
          PERFORM insert_item.
        WHEN 'UPDATE'.
          PERFORM update_item.
        WHEN 'DISPLAY'.
          PERFORM display_item.
        WHEN 'REFRESH'.
          PERFORM refresh_list.
      ENDCASE.
      IF ref_flag = 'Y'.
        PERFORM refresh_list.
        CLEAR ref_flag.
      ENDIF.
    ENDFORM.                    " USER_COMMAND
    *&      Form  INSERT_ITEM
    *       When Clicking Insert Button
    FORM insert_item.
      CLEAR : s_mode.
      CLEAR : zesp04.
      s_mode = 'INSERT'.
      CALL SCREEN '100'.
    ENDFORM.                    " INSERT_ITEM
    *&      Form  UPDATE_ITEM
    *       When Clicking Update Button
    FORM update_item.
      CLEAR : s_mode.
      s_mode = 'UPDATE'.
      CALL SCREEN '100'.
    ENDFORM.                    " UPDATE_ITEM
    *&      Form  DISPLAY_ITEM
    *       When Clicking Display Button
    FORM display_item.
      CLEAR : s_mode.
      s_mode = 'DISPLAY'.
      CALL SCREEN '100'.
    ENDFORM.                    " DISPLAY_ITEM
    *&      Form  REFRESH_LIST
    *       When Clicking Refresh Button or Returning Display Screen
    FORM refresh_list.
      CLEAR : itab_list, itab_list[].
      PERFORM select_data.
      sy-lsind = sy-lsind - 1.
      PERFORM display_data.
    ENDFORM.                    " REFRESH_LIST
    *&      Form  GET_FILENAME
    *       Get Filename
    FORM get_filename.
      DATA: l_fname LIKE ibipparms-path .
      DATA : p_name LIKE sy-repid.
      p_name = sy-repid.
      CALL FUNCTION 'F4_FILENAME'
           EXPORTING
                program_name  = p_name
                dynpro_number = sy-dynnr
                field_name    = ''
           IMPORTING
                file_name     = l_fname.
      p_fname = l_fname.
    ENDFORM.                    " GET_FILENAME
    Edited by: Matt on Nov 24, 2008 11:24 AM - surrounded the ABAP with  tags

    Hi,
        Use SUBMIT statement in your first Report zrswbgcs009 at the end, to call the Modulepool program zrswbp004.
    do a search in SDN you will get lot of threads on SUBMIT statement with selection screen.
    SUBMIT... [VIA SELECTION-SCREEN]
               [USING SELECTION-SET <var>]
               [WITH <sel> <criterion>]
               [WITH FREE SELECTIONS <freesel>]
               [WITH SELECTION-TABLE <rspar>].
    http://help.sap.com/saphelp_nw04/Helpdata/EN/9f/dba51a35c111d1829f0000e829fbfe/content.htm
    Regards
    Bala Krishna

  • How to download ABAP(report,module pool...etc) source code to client PC?

    hi guys,
    please advise how can i download/export ABAP(report,module pool...etc) source code to client PC?
    thanks.

    hi
    this report is to export to another server...
    PROGRAM ZDOWNLOAD_SAP
    LINE-SIZE 132
    LINE-COUNT 62
    NO STANDARD PAGE HEADING.
    This program up / downloads from / to a local dataset
    all the components of an ABAP - i.e TEXTS, the entire CUA
    including statuses and menus, DYNPROS and source code.
    Program documentation and variants are not handled.
    INCLUDED programs are automatically handled both on upload
    or download. INCLUDE selection can be excluded or generic
    e.g only handle INCLUDES starting with ZIN*
    INCLUDES within INCLUDES alos handled.
    The only restriction is on UPLOAD the INCLUDED programs must come
    from the same directory as the main program.
    On Download of course the ABAP must exist in the library.
    Note for LINUX and BATCH users
    This program was originally designed as a one off tool for
    getting ABAPS etc from a SAP R2 (IBM MVS mainframe system) into
    an R3 test system minimising the need for a large amount of
    mainframe sysprogs (anybody remember what they were !!) time
    and support to say nothing of access problems from TSO /JES2 /
    SAP R2. At that time network connections were patchy and the
    transport systems largely incompatable and not very reliable.
    This program was originally designed as a one off tool for
    Must run on Windows front end ---- If you are running SAP with
    LINUX on your work station you will have to change the WS_UPLOAD
    and WS_DOWNLOAD functions to reflect the Linux file system. The
    contents of the data sets themseleves do not need to be changed
    Program can easily be modified to run in batch and store
    the data on a UNIX host. Change the WS_UPLOAD and WS_DOWNLOAD
    to read from and write to UNIX data sets (OPEN FILE etc).
    You will also need to modify the parts of the program that get
    the DOS directory and display the Windows file paths.
    The actual abap data sets do not need to be changed.
    Rel 4.0 names can now be up to 40 bytes long
    Dynpros and CUA have changed from rel 3.1
    Tabstrips now loaded and unloaded in dynpros
    Please note restriction on 4.6 systems for users who
    have ABAP names which include '/'s in their names.
    Rel 4.6b, 4.6c Abap names can include the '/' in their names
    e.g /CUST1/CUST2/ORDER
    This causes problems when storing to a local file.
    a solution is to change the name to %CUST1%CUST2%ORDER i.e / will
    be changed to %. On upload the % should be changed back to /
    again. This change still needs to be implemented.
    If you don't use the / in the abap name then this is not a problem.
    If file to be uploaded is in rel 3 format then names are only 8
    bytes long.
    program uses 3 datasets per abap
    1) abapname.eee source, dynpr logic, texts, CUA stuff
    2) abapname.hhh dynpr header
    3) abapname.fff dynpro fields.
    because of varying lengths and contents 3 data sets are used. The
    complexity of combining all these to 1 data set would make the
    program far too complex.
    NOTE: This version of the program can only be used on
    release 4.0 or higher. Once an ABAP has been converted
    to rel 4.0 it cannot be converted back to rel 3.0
    on a release 3/3.1 system. Release 4 CUA tables
    are different. Use release 3 version of this program
    for releases 3.0 and 3.1. Available on SAPFANS website.
    Note that data to be uploaded must have been previously downloaded
    by this program (any version since rel 2.0) - except for Initial
    Load -- see end of these comments.
    Dynpros and CUA statuses have changed since rel 3.1
    This program will handle rel 3.1 format on upload but will
    download in rel 4.0 format. To upload 3.1 format specify an 'X'
    in the rel3 parameter.
    If you have downloaded components in rel 4.0 format and you
    want to re-load to a 3.1 system you will have to load
    the source via standard upload and re-create dynpros and the CUA
    manually.
    As names can now be longer than 8 characters you can only
    use this program if the SAP front end (SAPGUI) supports
    long file names (WIN 95/98 or WIN NT). Windows 3.x will not
    work as the underlying DOS system cannot handle long file names.
    UPLOAD function and DOS directory.
    When an ABAP is selected for UPLOAD then the DOS
    directory is read into a table. A file called ABAP.BAT is created,
    and down loaded to the 'C' drive and executed.
    This file executes a DOS DIR command and pipes the output
    into a dataset which is then uploaded into an internal
    table on SAP.
    Note on running DOS commands from ABAP
    The first time this procedure is executed you will see a DOS window
    which you will have to close manually. To get round this
    use windows explorer to select the file ABAP.BAT and then
    right mouse click on the file name. Select the
    properties window. From this click the CLOSE on EXIT box. This
    will then automatically close the DOS function after it has
    executed. (Windows restriction).
    The DOS function has not been tested using Windows 2000 so
    it might not work. OK on W95,W98,WME and Windows NT (No Thanks)
    If INCLUDE programs are wanted on UPLOAD only the specified
    directory is searched.
    Instead of entering path name manually you can click on
    the path parameter. Because of Windows restriction you will
    have to select ANY file in the relevant directory.
    The path will then be copied on to the selection screen.
    To do still : Merge 3 files to one and compress output to .ZIP file
    fix 4.5 4.6 problem of abaps containing '/' in the name
    possibility to automatically up / download referenced
    function modules with selection criteria like INCLUDES
    To load the ist time into a system.
    Create program with ABAP editor and Upload the .EEE file.
    Delete ist line (????SRCE) in the ABAP EDITOR --NOT THE DISK FILE
    Delete all the source from the line that starts ????TEXT (towards
    the end file) till the end so the last line in your source is ENDFORM.
    DO NOT ALTER THE DISK FILE. DO THESE CHANGES IN THE ABAP EDITOR.
    Save file and execute
    Use following parameters (Note the ist time you won't get proper
    text on the selection screen).
    Function U
    Path full dos path containing source e.g c:\abaps\
    NOTE YOU MUST ENTER THE FINAL \ as above.
    REPID the program name. e.g ZZJIMHXX
    note that on the DISK you will see 3 files
    ZZJIMHXX.EEE, ZZJIMHXX.FFF, ZZJIMHXX.HHH
    just use the name before the dos qualifier - the
    program will do the rest
    ignore other parameters
    The program will then load itself with all the texts etc.
    It should now be ready for use.
    Macros
    DEFINE DEFINE_TABLE.
    DATA: &1 LIKE &2 OCCURS &3 WITH HEADER LINE.
    END-OF-DEFINITION.
    DEFINE CLS.
    REFRESH &1.
    CLEAR &1.
    END-OF-DEFINITION.
    DEFINE INIT.
    IF &1 NE SPACE.
    SEARCH &1 FOR '. .'.
    IF SY-SUBRC = 0.
    WRITE '*' TO &1+SY-FDPOS(1).
    ENDIF.
    TRANSLATE &1 USING '*%'.
    ELSE.
    MOVE '%' TO &1.
    ENDIF.
    END-OF-DEFINITION.
    end of macros
    / SAP standard tables */
    TABLES: D020S, "Dynpro header
    D020T, "Dynpro title
    D021T, "Screen field keyword texts
    TRDIR, "Attribute table
    TADIR, "Dev. class etc.
    EUDB, "CUA data
    TSTC, "transaction data
    TITLE, "CUA titles
    RSMPTEXTS. "Function texts (rel 4.0)
    / Work tables to hold ABAP source etc, and dynpro */
    / contents. */
    DATA: BEGIN OF H. "Header
    INCLUDE STRUCTURE D020S.
    DATA: END OF H.
    DATA: BEGIN OF H1 OCCURS 10, "Header
    NAME(40) TYPE C, "rel 4
    NUMBER(4) TYPE N.
    INCLUDE STRUCTURE D020S.
    DATA: END OF H1.
    DATA: BEGIN OF H2 OCCURS 0, "Rel 3 dynp. header
    CNAME(8) TYPE C,
    CNUM(4) TYPE C,
    NNAME(8) TYPE C,
    NNUM(4) TYPE C,
    FILL(51) TYPE C,
    CDAT(6) TYPE C,
    CTIM(6) TYPE C,
    END OF H2.
    DATA: BEGIN OF F OCCURS 250. "Dynpro Fields
    INCLUDE STRUCTURE D021S.
    DATA: END OF F.
    DATA: BEGIN OF F1 OCCURS 500, "Dynpro Fields
    NAME(40) TYPE C, "rel 4
    NUMBER(4) TYPE N.
    INCLUDE STRUCTURE D021S.
    DATA: END OF F1.
    DATA: BEGIN OF OLD_F1 OCCURS 0, "Dynpro Fields (rel 3)
    NAME(8) TYPE C,
    NUMBER(4) TYPE C.
    INCLUDE STRUCTURE D021SE_OLD.
    DATA: END OF OLD_F1.
    DATA: BEGIN OF F2 OCCURS 0, "Dynpro Fields (rel 3)
    TFIL(284) TYPE C,
    END OF F2.
    DATA: BEGIN OF M OCCURS 3. "Match codes (if any)
    INCLUDE STRUCTURE D023S.
    DATA: END OF M.
    DATA: BEGIN OF E OCCURS 0. "Dynpro Logic
    INCLUDE STRUCTURE D022S.
    DATA: END OF E.
    DATA: BEGIN OF E1 OCCURS 0, "Dynpro Logic
    NAME(40) TYPE C, "rel 4
    NUMBER(4) TYPE N.
    INCLUDE STRUCTURE D022S.
    DATA: END OF E1.
    DATA: BEGIN OF T OCCURS 0, "prog name and dynpro nrs
    NAME(40) TYPE C, "rel 4
    NUMBER(4) TYPE N,
    END OF T.
    DATA: BEGIN OF R OCCURS 56, "prog name and language
    NAME(40) TYPE C, "rel 4
    LANGUAGE(1) TYPE C,
    END OF R.
    DATA: BEGIN OF S OCCURS 3000,
    TXT(180) TYPE C, "rel 4 was 132
    END OF S.
    DATA: BEGIN OF R1 OCCURS 50, "for include programs
    NAME(40) TYPE C, "rel 4
    INSTANCE(3) TYPE P,
    END OF R1.
    DATA: BEGIN OF S1 OCCURS 3000,
    TXT(180) TYPE C, " rel 4 was 132
    END OF S1.
    DATA: BEGIN OF U OCCURS 100, "Text elements
    TXT(180) TYPE C, " rel 4 was 132
    END OF U.
    DATA: BEGIN OF DIR. "ABAP Attributes
    INCLUDE STRUCTURE TRDIR.
    DATA: END OF DIR.
    DATA: BEGIN OF DTXT. "Dynpro field keyword texts
    INCLUDE STRUCTURE D021T.
    DATA: END OF DTXT.
    / This data contains all the components of the */
    / CUA such as menus, statuses, Pfkeys */
    / As from rel 4.5 Tabstrips are automatically copied as well */
    / The rel3 parameter must be set however to load the */
    / correct version of the CUA tables if uploading rel 3 */
    / data to a rel 4 system. */
    / Rel 4.0B can convert 3.1 and earlier CUA's */
    / This could change later however. */
    CUA Tables.
    Key of CUA tables in EUDB data set. Name is len 40 in rel 4.0
    DATA BEGIN OF EU_KEY.
    INCLUDE STRUCTURE RSEU1_KEY.
    DATA END OF EU_KEY.
    Status
    DATA BEGIN OF STA OCCURS 0.
    INCLUDE STRUCTURE RSMPE_STAT. " rel 4
    DATA END OF STA.
    Functions
    DATA BEGIN OF FUN OCCURS 0.
    INCLUDE STRUCTURE RSMPE_FUNT. "rel 4
    DATA END OF FUN.
    Menus
    DATA BEGIN OF MEN OCCURS 0.
    INCLUDE STRUCTURE RSMPE_MEN. "rel 4.0
    DATA END OF MEN.
    Menus (texts)
    DATA BEGIN OF MTX OCCURS 0.
    INCLUDE STRUCTURE RSMPE_MNLT. "rel 4.0
    DATA END OF MTX.
    Action Bar
    DATA BEGIN OF ACT OCCURS 0.
    INCLUDE STRUCTURE RSMPE_ACT. "rel 4.0
    DATA END OF ACT.
    Push Buttons
    DATA BEGIN OF BUT OCCURS 0.
    INCLUDE STRUCTURE RSMPE_BUT. "rel 4.0
    DATA END OF BUT.
    PF-Keys
    DATA BEGIN OF PFK OCCURS 0.
    INCLUDE STRUCTURE RSMPE_PFK. "rel 4.0
    DATA END OF PFK.
    Function sets
    DATA BEGIN OF SET OCCURS 0.
    INCLUDE STRUCTURE RSMPE_STAF. "rel 4.0
    DATA END OF SET.
    Documentation
    DATA BEGIN OF DOC OCCURS 0.
    INCLUDE STRUCTURE RSMPE_ATRT. "rel 4.0
    DATA END OF DOC.
    Title codes with text
    DATA: BEGIN OF TIT OCCURS 0.
    INCLUDE STRUCTURE RSMPE_TITT. "rel 4.0
    DATA: END OF TIT.
    DATA BEGIN OF FTX OCCURS 0. "rel 4.0
    INCLUDE STRUCTURE RSMPTEXTS.
    DATA END OF FTX.
    rel 3.1 CUA components.
    Status
    DATA BEGIN OF OLD_STA OCCURS 0.
    INCLUDE STRUCTURE RSEU1_GEN. " rel 3.1
    DATA END OF OLD_STA.
    Functions
    DATA BEGIN OF OLD_FUN OCCURS 0.
    INCLUDE STRUCTURE RSEU1_FUN. "rel 3.1
    DATA END OF OLD_FUN.
    Menus
    DATA BEGIN OF OLD_MEN OCCURS 0.
    INCLUDE STRUCTURE RSEU1_MEN. "rel 3.1
    DATA END OF OLD_MEN.
    Menus (texts)
    DATA BEGIN OF OLD_MTX OCCURS 0.
    INCLUDE STRUCTURE RSEU1_TXM. "rel 3.1
    DATA END OF OLD_MTX.
    Action Bar
    DATA BEGIN OF OLD_ACT OCCURS 0.
    INCLUDE STRUCTURE RSEU1_ACT. "rel 3.1
    DATA END OF OLD_ACT.
    Push Buttons
    DATA BEGIN OF OLD_BUT OCCURS 0.
    INCLUDE STRUCTURE RSEU1_BUT. "rel 3.1
    DATA END OF OLD_BUT.
    PF-Keys
    DATA BEGIN OF OLD_PFK OCCURS 0.
    INCLUDE STRUCTURE RSEU1_PFK. "rel 3.1
    DATA END OF OLD_PFK.
    Function sets
    DATA BEGIN OF OLD_SET OCCURS 0.
    INCLUDE STRUCTURE RSEU1_SET. "rel 3.1
    DATA END OF OLD_SET.
    Documentation
    DATA BEGIN OF OLD_DOC OCCURS 0.
    INCLUDE STRUCTURE RSEU1_ETM. "rel 3.1
    DATA END OF OLD_DOC.
    Title codes with text
    DATA: BEGIN OF OLD_TIT OCCURS 0.
    INCLUDE STRUCTURE TITLE. "rel 3.1
    DATA: END OF OLD_TIT.
    dynamic function text
    DATA BEGIN OF FDN OCCURS 1.
    INCLUDE STRUCTURE RSEU1_FDYN. "not req for rel 4.
    DATA END OF FDN.
    Icons
    DATA BEGIN OF FIN OCCURS 1.
    INCLUDE STRUCTURE RSEU1_ICON. "not req for rel 4
    DATA END OF FIN.
    dynamic menu texts
    DATA BEGIN OF MDN OCCURS 1.
    INCLUDE STRUCTURE RSEU1_MDYN. "not req for rel 4.
    DATA END OF MDN.
    Symbol list
    DATA BEGIN OF SYM OCCURS 0.
    INCLUDE STRUCTURE RSEU1_SYMB.
    DATA END OF SYM.
    Status Short text
    DATA BEGIN OF STX OCCURS 0.
    INCLUDE STRUCTURE RSEU1_CTX.
    DATA END OF STX.
    Attributes for function key settings (menu bars) Rel 3.0
    DATA BEGIN OF ATT OCCURS 0.
    INCLUDE STRUCTURE RSEU1_HAT.
    DATA END OF ATT.
    Include-Menus
    DATA BEGIN OF INC OCCURS 3.
    INCLUDE STRUCTURE RSEU1_INC.
    DATA END OF INC.
    Last used numbers
    DATA BEGIN OF LAST.
    INCLUDE STRUCTURE RSEU1_LST.
    DATA END OF LAST.
    data for call transaction (SE41 to re-generate the CUA)
    DATA: BEGIN OF T_BDC_TAB OCCURS 0.
    INCLUDE STRUCTURE BDCDATA. "BDC data
    DATA: END OF T_BDC_TAB.
    DATA: BEGIN OF T_MESSTAB OCCURS 0.
    INCLUDE STRUCTURE BDCDATA.
    DATA: END OF T_MESSTAB.
    / Program data */
    DATA: NUMBER(4) TYPE N,
    OLDNUM(4) TYPE N,
    FILESIZE TYPE I,
    NR_OF_BYTES TYPE I,
    I(3) TYPE P,
    IX(3) TYPE P,
    J(3) TYPE P,
    L(3) TYPE P,
    CUA-FLAG(1) TYPE C,
    CUA_RETURN(10) TYPE C,
    DYNPRO_MESSAGE(160) TYPE C,
    DYNPRO_LINE TYPE P,
    DYNPRO_WORD(30) TYPE C,
    NUM(3) TYPE N,
    DYNNAME(44) TYPE C,
    FN1(128) TYPE C,
    FN2(128) TYPE C,
    FN3(128) TYPE C,
    W_ITERATE(1) TYPE C,
    MAIN(1) TYPE C,
    FUNC(1) TYPE C,
    OLDNAME(40) TYPE C,
    OLD-FUNC(8) TYPE C,
    NEW-FUNC(8) TYPE C,
    FOUND(1) TYPE C,
    LANGUAGE LIKE SY-LANGU,
    FIRST-TIME(1) TYPE C VALUE 'Y',
    OK-CODE(5) TYPE C,
    NAME(40) TYPE C, "rel 4
    TXLINE(70) TYPE C,
    LINE(132) TYPE C.
    DATA:
    UL_FILE(128) TYPE C,
    DL_FILE(128) TYPE C,
    DOSLINE(72) TYPE C.
    DATA: BEGIN OF DOSDIR OCCURS 0,
    TEXT(72),
    END OF DOSDIR.
    DATA: BEGIN OF I_PROG OCCURS 0,
    NAME(40),
    END OF I_PROG.
    DATA: BEGIN OF I_PROGT OCCURS 0,
    NAME(40),
    END OF I_PROGT.
    DATA: BEGIN OF I_INCLUDE OCCURS 0,
    NAME(40),
    HANDLED(1) TYPE C,
    END OF I_INCLUDE.
    DATA: BEGIN OF I_INCL OCCURS 0,
    NAME(40),
    END OF I_INCL.
    DATA: BUFFER(1024).
    DATA: WINSYS(3).
    DATA: GLOBAL_FILEMASK_MASK(20), GLOBAL_FILEMASK_TEXT(20).
    DATA: GLOBAL_FILEMASK_ALL(80).
    DATA: T_FILENAME(128),
    TMP_FILENAME(128),
    T_MODE(1),
    FIELDLN TYPE I.
    DEFINE_TABLE I_DYNPFIELDS DYNPREAD 0. "dynpro fields to be updated
    DATA: I_FLDS LIKE HELP_VALUE OCCURS 0 WITH HEADER LINE.
    FIELD-SYMBOLS: <F>.
    / Parameters */
    SELECTION-SCREEN BEGIN OF BLOCK A1 WITH FRAME TITLE TEXT-001.
    SELECTION-SCREEN SKIP 1.
    SELECT-OPTIONS REPID FOR TRDIR-NAME OBLIGATORY .
    PARAMETERS:
    FUNCTION(1) TYPE C OBLIGATORY, "Function
    DSNAME(40) TYPE C, "Data set name
    INCLUDES(1) TYPE C DEFAULT 'N', "Resolve Includes
    IMASK(40) TYPE C, "Include Mask
    CLASS LIKE TRDIR-CLAS,
    AUTHOR LIKE TRDIR-CNAM, "Author
    APPL LIKE TRDIR-APPL,
    PATH(88) TYPE C DEFAULT 'A:\',
    REL3(1) TYPE C.
    SELECTION-SCREEN SKIP 1.
    SELECTION-SCREEN BEGIN OF LINE.
    SELECTION-SCREEN COMMENT 1(70) TEXT-004.
    SELECTION-SCREEN END OF LINE.
    SELECTION-SCREEN BEGIN OF LINE.
    SELECTION-SCREEN COMMENT 1(70) TEXT-005.
    SELECTION-SCREEN END OF LINE.
    SELECTION-SCREEN SKIP 1.
    SELECTION-SCREEN BEGIN OF LINE.
    SELECTION-SCREEN COMMENT 1(70) TEXT-002.
    SELECTION-SCREEN END OF LINE.
    SELECTION-SCREEN BEGIN OF LINE.
    SELECTION-SCREEN COMMENT 1(70) TEXT-003.
    SELECTION-SCREEN END OF LINE.
    SELECTION-SCREEN END OF BLOCK A1.
    / Check users workstation is running WINDOWS, */
    / WINDOWS 95, or WINDOWS NT. OS/2 no good for */
    / this application. */
    CALL FUNCTION 'WS_QUERY'
    EXPORTING
    QUERY = 'WS'
    IMPORTING
    RETURN = WINSYS.
    IF WINSYS(2) NE 'WN'. "Win 3.X no good either
    WRITE: / 'Windows NT or Windows 95/98 is required'.
    EXIT.
    ENDIF.
    / Get names of programs to be handled. */
    / Name can be a single value, many values or ranges */
    / as per standard SELECT-OPTIONS on selection screen */
    / On Download read TRDIR and store program names in a table */
    / as per selection options. */
    / On upload read the specified directory for all files of */
    / type .EEE from specified directory */
    / compare file names with selection criteria */
    MOVE FUNCTION TO FUNC.
    MOVE 'Y' TO MAIN.
    CASE FUNC.
    WHEN 'U'. "Upload required
    PERFORM READ_DOS_DIRECTORY.
    PERFORM GET_RANGE_UL. "Get list of progs to process
    WHEN 'D'. "Download required
    PERFORM GET_RANGE_DL. "Get list of progs to process
    WHEN OTHERS.
    WRITE: / 'Function not performed due to user request'.
    EXIT.
    ENDCASE.
    SORT I_PROG.
    DELETE ADJACENT DUPLICATES FROM I_PROG.
    For download INCLUDE handling can be resolved via function
    module call.
    All Includes within Includes are also resolved by the function
    module call.
    Note that this method does not work if program itself is of type
    I (it's an include)
    In this case we can still search the source.
    IF FUNC = 'D'.
    IF INCLUDES = 'Y'.
    PERFORM GET_INCLUDES_DL.
    PERFORM PROCESS_INCLUDES_DL.
    ENDIF.
    ENDIF.
    Program list from selection criteria i.e excluding INCLUDES found
    LOOP AT I_PROG.
    MOVE I_PROG-NAME TO R1-NAME.
    APPEND R1.
    DESCRIBE TABLE R1 LINES I.
    WHILE I NE 0.
    PERFORM EXECUTE-FUNCTION.
    ENDWHILE.
    REFRESH R1.
    ENDLOOP.
    We need to check now for INCLUDES on DOWNLOAD when the INCLUDE
    program itself is of type I. In this case the function call
    will not return the INCLUDES. For example we could be
    downloading ZTESTTOP (an Include itself) which as an include
    ZTEST01.
    The process fortunately is the same as the UPLOAD function
    except of course we need to read the library instead of the
    DOS directory
    process INCLUDE modules for Upload
    On upload the procedure is more complex as Includes within
    Includes can only be resolved by scanning the code and
    searching if the program exists in the directory.
    To get all INCLUDES within INCLUDES entries in table I_INCL
    that do not exist in I_INCLUDE are copied to table I_INCLUDE
    after each entire pass of table i_INCLUDE and table is then
    re-looped through. Programs in table I_INCLUDE that have already
    been processed have a "Y" indicator set in I_INCLUDE-AVAIL.
    if func = 'U'.
    IF INCLUDES = 'Y'.
    DESCRIBE TABLE I_INCL LINES I.
    IF I > 0.
    W_ITERATE = 'Y'.
    ELSE.
    W_ITERATE = ' '.
    ENDIF.
    WHILE W_ITERATE = 'Y'.
    PERFORM PROCESS_INCLUDES_UL.
    PERFORM LOOP_THROUGH.
    DESCRIBE TABLE I_INCL LINES I.
    IF I > 0.
    W_ITERATE = 'Y'.
    ELSE.
    W_ITERATE = ' '.
    ENDIF.
    ENDWHILE.
    endif.
    ENDIF.
    DESCRIBE TABLE I_INCLUDE LINES I.
    IF I > 0.
    SKIP 1.
    WRITE: / ' Included Programs found'.
    SKIP 1.
    LOOP AT I_INCLUDE.
    WRITE I_INCLUDE-NAME TO LINE(40).
    CONDENSE LINE.
    WRITE: / LINE(80).
    ENDLOOP.
    ENDIF.
    / Table R contains ABAP names to up / download. */
    / Loop through table R and perform up / download */
    / for each program. */
    / Table R1 contains INCLUDE names found (if any) */
    / As each */
    FORM EXECUTE-FUNCTION.
    LOOP AT R1.
    MOVE-CORRESPONDING R1 TO R.
    APPEND R.
    ENDLOOP.
    REFRESH R1.
    LOOP AT R.
    REFRESH : T, E1, H1, F1, S, U.
    PERFORM PROCESS.
    MOVE 'N' TO MAIN.
    ENDLOOP.
    REFRESH R.
    DESCRIBE TABLE R1 LINES I.
    ENDFORM.
    / Build file names for UP/DOWNLOAD */
    / 3 files are generated per ABAP. */
    / 1) ABAP Path\PROGNAME.EEE (ABAP, Attr,Texts) */
    / Logic Path\PROGNAME.EEE (Dynpro Source Logic) */
    / CUA Path\PROGNAME.EEE (CUA components - keys etc) */
    / 2) Header Path\PROGNAME.HHH (Dynpro Header) */
    / 3) Fields Path\PROGNAME.FFF (Dynpro Field definitions )*/
    / ( If alternate file name specified -DSNAME- this will */
    / be used instead. This is only valid for the main program. */
    / INCLUDED programs will have file names as specified */
    / above). */
    / By using this scheme it saves the user from having to */
    / be prompted for 3 file names. */
    / If you want multiple copies / versions on disk either */
    / rename the old versions or specify a different directory in */
    / the path parameter. */
    FORM PROCESS.
    MOVE PATH TO FN1.
    CASE MAIN.
    WHEN 'Y'.
    IF DSNAME NE SPACE.
    WRITE DSNAME TO FN1+66. "rel 4
    ELSE.
    WRITE R-NAME TO FN1+66. "rel 4
    ENDIF.
    WHEN OTHERS.
    WRITE R-NAME TO FN1+66. "rel 4
    ENDCASE.
    MOVE FN1 TO FN2.
    MOVE FN1 TO FN3.
    WRITE '.HHH' TO FN1+124(4). "rel 4
    WRITE '.FFF' TO FN2+124(4). "rel 4
    WRITE '.EEE' TO FN3+124(4). "rel 4
    CONDENSE FN1 NO-GAPS.
    CONDENSE FN2 NO-GAPS.
    CONDENSE FN3 NO-GAPS.
    NAME = R-NAME.
    CASE FUNC.
    WHEN 'D'.
    PERFORM DOWNLOAD_OBJECTS.
    CLEAR LINE.
    WRITE : 'ABAP : ' TO LINE.
    WRITE R-NAME TO LINE+8.
    WRITE 'has been unloaded' TO LINE+55.
    CONDENSE LINE.
    WRITE: / LINE.
    DESCRIBE TABLE T LINES I.
    IF I = 0.
    WRITE: / 'No Dynpros were found for unload function'.
    ELSE.
    WRITE: / 'The following Dynpros have been unloaded : '.
    PERFORM LOOP_THROUGH_T.
    ENDIF.
    WHEN 'U'.
    PERFORM UPLOAD_OBJECTS.
    DESCRIBE TABLE T LINES I.
    CASE I.
    WHEN 0.
    WRITE: / 'No Dynpros were found for restore function'.
    WHEN OTHERS.
    WRITE: / 'The following Dynpros have been restored : '.
    PERFORM LOOP_THROUGH_T.
    ENDCASE.
    IF MAIN EQ 'Y'.
    CASE OLDNAME.
    WHEN SPACE.
    CLEAR LINE.
    WRITE : 'ABAP : ' TO LINE.
    WRITE R-NAME TO LINE+8.
    WRITE 'has been restored' TO LINE+55.
    CONDENSE LINE.
    WRITE: / LINE.
    WHEN OTHERS.
    CLEAR LINE.
    WRITE : 'ABAP : ' TO LINE.
    WRITE R-NAME TO LINE+8.
    WRITE 'has been restored - original name :'
    TO LINE+55.
    WRITE OLDNAME TO LINE+92.
    CONDENSE LINE.
    WRITE: / LINE.
    ENDCASE.
    ELSE.
    CLEAR LINE.
    WRITE : 'ABAP : ' TO LINE.
    WRITE R-NAME TO LINE+8.
    WRITE 'has been restored' TO LINE+55.
    CONDENSE LINE.
    WRITE: / LINE.
    ENDIF.
    ENDCASE.
    ENDFORM.
    / print progname + dynpro nrs that have been processed. */
    FORM LOOP_THROUGH_T.
    LOOP AT T.
    CLEAR LINE.
    WRITE R-NAME TO LINE.
    WRITE T-NUMBER TO LINE+50.
    CONDENSE LINE.
    WRITE: / LINE.
    ENDLOOP.
    ENDFORM.
    / Download Objects */
    FORM DOWNLOAD_OBJECTS.
    PERFORM UNLOAD_ABAP. "ABAP source, texts, attr
    SELECT SINGLE * FROM TRDIR
    WHERE NAME EQ R-NAME.
    IF TRDIR-SUBC = 'I'.
    CASE INCLUDES. "Included file wanted
    WHEN 'Y'.
    PERFORM SCAN4-INCLUDES.
    ENDCASE.
    ENDIF.
    PERFORM UNLOAD_CUA. "CUA stuff
    PERFORM DOWNLOAD_DATA. "Download EEE file to PC
    PERFORM BUILD_T. "Build table of all dynpros in ABAP
    DESCRIBE TABLE T LINES I.
    CASE I.
    WHEN 0. "if no dynpros exist then cannot download any
    PERFORM DOWNLOAD_DATA. "Download EEE file to PC
    WHEN OTHERS.
    PERFORM UNLOAD_DYNPROS. "Get Raw dynpros from SAP
    PERFORM UNLOAD_DYNPRO_COMPONENTS."Convert to table
    PERFORM DOWNLOAD_DATA. "Download ABAP etc. to PC
    PERFORM DOWNLOAD_BIN_H1. "Download dynpro header
    PERFORM DOWNLOAD_BIN_F1. "Download dynpro fields
    ENDCASE.
    ENDFORM.
    / Split ABAP up into its component parts */
    / A) Program source (72) */
    / B) Texts (132) */
    / C) Attributes (117) */
    / D) CUA stuff (Various) */
    FORM UNLOAD_ABAP.
    / Get ABAP language. Only required on download. */
    SELECT SINGLE * FROM TRDIR
    WHERE NAME EQ R-NAME.
    MOVE TRDIR-RLOAD TO R-LANGUAGE.
    READ REPORT R-NAME INTO S. "Get source into table S
    MOVE '????SRCE' TO S-TXT.
    INSERT S INDEX 1.
    / Text elements, Numbered texts, headings, selection texts */
    / Read text elements with logon language. If they don't */
    / exist read with the value taken from TRDIR. */
    READ TEXTPOOL R-NAME INTO U LANGUAGE SY-LANGU.
    IF SY-SUBRC NE 0.
    READ TEXTPOOL R-NAME INTO U LANGUAGE R-LANGUAGE.
    ENDIF.
    DESCRIBE TABLE U LINES I.
    CASE I.
    WHEN 0.
    WHEN OTHERS.
    MOVE '????TEXT' TO S-TXT.
    APPEND S.
    LOOP AT U.
    MOVE U-TXT TO S-TXT.
    APPEND S.
    DELETE U.
    ENDLOOP.
    ENDCASE.
    / Retrieve Attributes from TRDIR and add to table S */
    / Change language to logged on language */
    MOVE '????ATTR' TO S-TXT.
    APPEND S.
    SELECT SINGLE * FROM TRDIR
    WHERE NAME EQ R-NAME.
    MOVE SY-LANGU TO TRDIR-RLOAD.
    MOVE-CORRESPONDING TRDIR TO DIR.
    MOVE DIR TO S-TXT.
    APPEND S.
    ENDFORM.
    / retrieve CUA stuff and append to table S. */
    FORM UNLOAD_CUA.
    MOVE R-NAME TO EU_KEY-NAME. "Program name for CUA
    MOVE 'D' TO EU_KEY-SPRSL. "CUA seems to want D as lang
    MOVE R-LANGUAGE TO EU_KEY-SPRSL. "Language "rel 2.2
    IMPORT STA FUN MEN MTX ACT BUT PFK SET LAST INC STX DOC "rel 2.2
    IMPORT STA STX FUN MEN MTX ACT BUT PFK SET LAST INC DOC "rel 3.0
    ATT FDN MDN SYM FIN "rel 3.0
    FROM DATABASE EUDB(CU) ID EU_KEY.
    IF SY-SUBRC NE 0. "No statuses
    EXIT.
    ENDIF.
    read titles in logged on language. If not present use
    language from TRDIR.
    CASE REL3.
    WHEN SPACE. "(rel 4)
    SELECT * FROM RSMPTEXTS WHERE PROGNAME EQ R-NAME
    AND SPRSL = SY-LANGU.
    MOVE-CORRESPONDING RSMPTEXTS TO FTX.
    APPEND FTX.
    ENDSELECT.
    IF SY-SUBRC NE 0.
    SELECT * FROM RSMPTEXTS WHERE PROGNAME EQ R-NAME
    AND SPRSL = R-LANGUAGE.
    MOVE-CORRESPONDING RSMPTEXTS TO FTX.
    APPEND FTX.
    ENDSELECT.
    ENDIF.
    DESCRIBE TABLE FTX LINES I.
    IF I > 0.
    MOVE '????FTXT' TO S-TXT.
    APPEND S.
    LOOP AT FTX.
    MOVE FTX TO S-TXT.
    APPEND S.
    ENDLOOP.
    ENDIF.
    WHEN OTHERS.
    SELECT * FROM TITLE WHERE PROGNAME EQ R-NAME
    AND DDLANGUAGE EQ SY-LANGU.
    MOVE-CORRESPONDING TITLE TO TIT.
    APPEND TIT.
    ENDSELECT.
    IF SY-SUBRC NE 0.
    SELECT * FROM TITLE WHERE PROGNAME EQ R-NAME
    AND DDLANGUAGE EQ R-LANGUAGE.
    MOVE-CORRESPONDING TITLE TO TIT.
    APPEND TIT.
    ENDSELECT.
    ENDIF.
    ENDCASE.
    DESCRIBE TABLE STA LINES I.
    IF I > 0.
    MOVE '????STAT' TO S-TXT.
    APPEND S.
    LOOP AT STA.
    MOVE STA TO S-TXT.
    APPEND S.
    ENDLOOP.
    ENDIF.
    DESCRIBE TABLE FUN LINES I.
    IF I > 0.
    MOVE '????FUNC' TO S-TXT.
    APPEND S.
    LOOP AT FUN.
    MOVE FUN TO S-TXT.
    APPEND S.
    ENDLOOP.
    ENDIF.
    DESCRIBE TABLE MEN LINES I.
    IF I > 0.
    MOVE '????MEN1' TO S-TXT.
    APPEND S.
    LOOP AT MEN.
    MOVE MEN TO S-TXT.
    APPEND S.
    ENDLOOP.
    ENDIF.
    DESCRIBE TABLE MTX LINES I.
    IF I > 0.
    MOVE '????MTX1' TO S-TXT.
    APPEND S.
    LOOP AT MTX.
    MOVE MTX TO S-TXT.
    APPEND S.
    ENDLOOP.
    ENDIF.
    DESCRIBE TABLE ACT LINES I.
    IF I > 0.
    MOVE '????ACTN' TO S-TXT.
    APPEND S.
    LOOP AT ACT.
    MOVE ACT TO S-TXT.
    APPEND S.
    ENDLOOP.
    ENDIF.
    DESCRIBE TABLE BUT LINES I.
    IF I > 0.
    MOVE '????BUTN' TO S-TXT.
    APPEND S.
    LOOP AT BUT.
    MOVE BUT TO S-TXT.
    APPEND S.
    ENDLOOP.
    ENDIF.
    DESCRIBE TABLE PFK LINES I.
    IF I > 0.
    MOVE '????PFKY' TO S-TXT.
    APPEND S.
    LOOP AT PFK.
    MOVE PFK TO S-TXT.
    APPEND S.
    ENDLOOP.
    ENDIF.
    DESCRIBE TABLE SET LINES I.
    IF I > 0.
    MOVE '????SETS' TO S-TXT.
    APPEND S.
    LOOP AT SET.
    MOVE SET TO S-TXT.
    APPEND S.
    ENDLOOP.
    ENDIF.
    IF LAST NE SPACE.
    MOVE '????LIST' TO S-TXT.
    APPEND S.
    MOVE LAST TO S-TXT.
    APPEND S.
    ENDIF.
    DESCRIBE TABLE INC LINES I.
    IF I > 0.
    MOVE '????INCL' TO S-TXT.
    APPEND S.
    LOOP AT INC.
    MOVE INC TO S-TXT.
    APPEND S.
    ENDLOOP.
    ENDIF.
    DESCRIBE TABLE STX LINES I.
    IF I > 0.
    MOVE '????STXT' TO S-TXT.
    APPEND S.
    LOOP AT STX.
    MOVE STX TO S-TXT.
    APPEND S.
    ENDLOOP.
    ENDIF.
    DESCRIBE TABLE DOC LINES I.
    IF I > 0.
    MOVE '????DOCN' TO S-TXT.
    APPEND S.
    LOOP AT DOC.
    MOVE DOC TO S-TXT.
    APPEND S.
    ENDLOOP.
    ENDIF.
    DESCRIBE TABLE TIT LINES I.
    IF I > 0.
    MOVE '????TITL' TO S-TXT.
    APPEND S.
    LOOP AT TIT.
    MOVE TIT TO S-TXT.
    APPEND S.
    ENDLOOP.
    ENDIF.
    Next 5 tables are rel 3.0 specific (ATT, FDN, MDN, SYM, FIN)
    DESCRIBE TABLE ATT LINES I.
    IF I > 0.
    MOVE '????VATT' TO S-TXT.
    APPEND S.
    LOOP AT ATT.
    MOVE ATT TO S-TXT.
    APPEND S.
    ENDLOOP.
    ENDIF.
    DESCRIBE TABLE FDN LINES I.
    IF I > 0.
    MOVE '????VFDN' TO S-TXT.
    APPEND S.
    LOOP AT FDN.
    MOVE FDN TO S-TXT.
    APPEND S.
    ENDLOOP.
    ENDIF.
    DESCRIBE TABLE MDN LINES I.
    IF I > 0.
    MOVE '????VMDN' TO S-TXT.
    APPEND S.
    LOOP AT MDN.
    MOVE MDN TO S-TXT.
    APPEND S.
    ENDLOOP.
    ENDIF.
    DESCRIBE TABLE SYM LINES I.
    IF I > 0.
    MOVE '????VSYM' TO S-TXT.
    APPEND S.
    LOOP AT SYM.
    MOVE SYM TO S-TXT.
    APPEND S.
    ENDLOOP.
    ENDIF.
    DESCRIBE TABLE FIN LINES I.
    IF I > 0.
    MOVE '????VFIN' TO S-TXT.
    APPEND S.
    LOOP AT FIN.
    MOVE FIN TO S-TXT.
    APPEND S.
    ENDLOOP.
    ENDIF.
    ENDFORM.
    / Upload Objects. */
    FORM UPLOAD_OBJECTS.
    PERFORM UPLOAD_EEE. "ABAP,texts,attr dynpro logic
    DESCRIBE TABLE E1 LINES I.
    IF I > 0. "Do dynpro components exist
    PERFORM UPLOAD_HHH. "dynpro header
    PERFORM UPLOAD_FFF. "dynpro fields.
    PERFORM RECONSTRUCT_DYNPROS. "load + gen dynpros
    ENDIF.
    ENDFORM.
    / Build table containing dynpro names and numbers */
    FORM BUILD_T.
    SELECT * FROM D020S WHERE PROG EQ R-NAME.
    T-NUMBER = D020S-DNUM.
    T-NAME = D020S-PROG.
    APPEND T.
    ENDSELECT.
    ENDFORM.
    / Split dynpros into constituent parts. */
    FORM UNLOAD_DYNPROS.
    MOVE 'Y' TO FIRST-TIME.
    LOOP AT T.
    REFRESH: F, E.
    CLEAR: H, F, E.
    PERFORM BUILD_HHH. "Dynpro Header
    PERFORM BUILD_FFF. "Dynpro Fields
    PERFORM BUILD_EEE_DYNP. "Dynpro Logic
    ENDLOOP.
    ENDFORM.
    / Header H length 284. */
    FORM BUILD_HHH.
    MOVE T-NAME TO DYNNAME(40). "rel 4.
    MOVE T-NUMBER TO DYNNAME+40(4). "rel 4.
    IMPORT DYNPRO H F E M ID DYNNAME.
    MOVE T-NAME TO H1-NAME.
    MOVE T-NUMBER TO H1-NUMBER.
    MOVE-CORRESPONDING H TO H1.
    APPEND H1.
    ENDFORM.
    / Fields D021S Len 87. */
    FORM BUILD_FFF.
    MOVE T-NAME TO F1-NAME.
    MOVE T-NUMBER TO F1-NUMBER.
    LOOP AT F.
    MOVE-CORRESPONDING F TO F1.
    APPEND F1.
    DELETE F.
    ENDLOOP.
    ENDFORM.
    / Dynpro Logic D022S E */
    FORM BUILD_EEE_DYNP.
    MOVE T-NAME TO E1-NAME.
    MOVE T-NUMBER TO E1-NUMBER.
    LOOP AT E.
    MOVE-CORRESPONDING E TO E1.
    APPEND E1.
    DELETE E.
    ENDLOOP.
    ENDFORM.
    / Unload Constituent parts of dynpro. */
    FORM UNLOAD_DYNPRO_COMPONENTS.
    MOVE '????LOGC' TO S-TXT.
    APPEND S.
    LOOP AT E1.
    MOVE E1 TO S-TXT.
    APPEND S.
    DELETE E1.
    ENDLOOP.
    FREE E1.
    LOOP AT T.
    MOVE 'N' TO FOUND.
    SELECT SINGLE * FROM D020T "use logged on language
    WHERE PROG EQ T-NAME
    AND DYNR EQ T-NUMBER
    AND LANG EQ SY-LANGU.
    IF SY-SUBRC NE 0. "try original language.
    SELECT SINGLE * FROM D020T
    WHERE PROG EQ T-NAME
    AND DYNR EQ T-NUMBER
    AND LANG EQ R-LANGUAGE.
    ENDIF.
    IF SY-SUBRC EQ 0.
    IF FOUND = 'N'.
    MOVE '????DTIT' TO S-TXT.
    APPEND S.
    MOVE 'Y' TO FOUND.
    ENDIF.
    MOVE T-NAME TO S-TXT.
    WRITE T-NUMBER TO S-TXT+8(4).
    WRITE D020T-DTXT TO S-TXT+12(60).
    APPEND S.
    ENDIF.
    MOVE 'N' TO FOUND.
    SELECT * FROM D021T
    WHERE PROG EQ T-NAME
    AND DYNR EQ T-NUMBER
    AND LANG EQ SY-LANGU. "logged on language
    IF FOUND = 'N'.
    MOVE '????DTXT' TO S-TXT.
    APPEND S.
    MOVE 'Y' TO FOUND.
    ENDIF.
    MOVE-CORRESPONDING D021T TO DTXT.
    MOVE DTXT TO S-TXT.
    APPEND S.
    ENDSELECT.
    CASE SY-SUBRC.
    WHEN 0.
    WHEN OTHERS. "try original language
    SELECT * FROM D021T
    WHERE PROG EQ T-NAME
    AND DYNR EQ T-NUMBER
    AND LANG EQ R-LANGUAGE.
    IF FOUND = 'N'.
    MOVE '????DTXT' TO S-TXT.
    APPEND S.
    MOVE 'Y' TO FOUND.
    ENDIF.
    MOVE-CORRESPONDING D021T TO DTXT.
    MOVE DTXT TO S-TXT.
    APPEND S.
    ENDSELECT.
    ENDCASE.
    ENDLOOP.
    ENDFORM.
    / Build the original dynpro component tables. */
    / Table H1 contains 1 entry for each dynpro. H1 contains */
    / the header for the dynpro prefixed by the program name */
    / and dynpro number. */
    / By looping round this table we can re-build the F */
    / (Fields) and E (Logic) components. By stripping off the */
    / program name and dynpro number the original tables are */
    / re-created. (Tables F1 and E1 also have a prefix of */
    / Program name and dynpro nr). */
    / After the original set of tables has been re-created we */
    / use R3 - SYSTEM-CALL (rel 2.2) to generate the screen */
    / and then get the next entry in table H1 to build the */
    / next screen. For releases 3.0 and higher use generate */
    / dynpro. */
    FORM RECONSTRUCT_DYNPROS.
    LOOP AT H1.
    CASE MAIN.
    WHEN 'Y'.
    if h1-name ne repid.
    IF H1-NAME NE R1-NAME.
    MOVE H1-NAME TO OLDNAME.
    ENDIF.
    ENDCASE.
    PERFORM RECONSTRUCT_F.
    PERFORM RECONSTRUCT_E.
    MOVE-CORRESPONDING H1 TO H.
    IF MAIN = 'Y'.
    move repid to h-prog.
    MOVE R1-NAME TO H-PROG.
    move repid to dynname.
    MOVE R1-NAME TO DYNNAME.
    ELSE.
    MOVE H1-NAME TO H-PROG.
    MOVE H1-NAME TO DYNNAME.
    ENDIF.
    MOVE H1-NUMBER TO H-DNUM.
    WRITE H1-NUMBER TO DYNNAME+40(4).
    EXPORT DYNPRO H F E M ID DYNNAME.
    SYSTEM-CALL GENERATE-SCREEN DYNNAME. "Up to rel 2.2
    GENERATE DYNPRO H F E M ID DYNNAME "R 3.0, 4.0, 4.5
    MESSAGE DYNPRO_MESSAGE
    LINE DYNPRO_LINE
    WORD DYNPRO_WORD.
    REFRESH: M, F, E.
    CLEAR: M, H, F, E.
    ENDLOOP.
    ENDFORM.
    / Re-build Fields table */
    FORM RECONSTRUCT_F.
    LOOP AT F1 WHERE NAME EQ H1-NAME AND
    NUMBER EQ H1-NUMBER.
    MOVE-CORRESPONDING F1 TO F.
    APPEND F.
    ENDLOOP.
    ENDFORM.
    / Re-build Logic table */
    FORM RECONSTRUCT_E.
    LOOP AT E1 WHERE NAME EQ H1-NAME AND
    NUMBER EQ H1-NUMBER.
    MOVE-CORRESPONDING E1 TO E.
    APPEND E.
    ENDLOOP.
    ENDFORM.
    / scan for included files (Upload) */
    FORM SCAN4-INCLUDES.
    IF FUNC = 'D'. "Downloads - whole table needs to be scanned
    LOOP AT S.
    PERFORM SEARCH-FUNC.
    ENDLOOP.
    ENDIF.
    IF FUNC = 'U'. "On upload scan line by line as we are re-building abap
    PERFORM SEARCH-FUNC.
    ENDIF.
    ENDFORM.
    / scan for text INCLUDE xxxxxxxx */
    / reject INCLUDE STRUCTURE as structure not a valid */
    / program name */
    FORM SEARCH-FUNC.
    CONDENSE S-TXT.
    SEARCH S-TXT FOR '.INCLUDE .'.
    CASE SY-SUBRC.
    WHEN 0.
    IF S-TXT+8(9) EQ 'STRUCTURE'
    OR S-TXT+8(9) EQ 'structure'
    OR S-TXT+8(6) EQ '<ICON>' "rel 3.0c 3.0d
    OR S-TXT+8(6) EQ '<icon>'
    OR S-TXT+8(6) EQ '<type>'
    OR S-TXT+8(6) EQ '<TYPE>'
    OR S-TXT+8(9) EQ '<methods>'
    OR S-TXT+8(9) EQ '<METHODS>'.
    EXIT.
    ENDIF.
    IF SY-FDPOS EQ 0. "INCLUDE must be in pos 1 (by reason of condense)
    PERFORM VALIDATE_INCLUDE.
    ELSE.
    EXIT.
    ENDIF.
    ENDCASE.
    ENDFORM.
    / Validate INCLUDES . */
    FORM VALIDATE_INCLUDE.
    SEARCH S-TXT FOR '...' STARTING AT 9 ENDING AT 39.
    CASE SY-SUBRC.
    WHEN 0.
    WHEN OTHERS.
    SEARCH S-TXT FOR '. .' STARTING AT 9 ENDING AT 38.
    IF SY-SUBRC NE 0.
    EXIT.
    ENDIF.
    ENDCASE.
    IX = SY-FDPOS.
    ASSIGN S-TXT+8(IX) TO <F>.
    Now check for Include Mask for example if include mask was set to
    Z* then only include programs whose first letter starts with a Z.
    1) get length of the INCLUDE program name. Must be less than or
    equal 40.
    2) Compare it with the Include mask.
    3) If Ok add include program name to include table
    clear i_include.
    move <f> to i_include-name.
    CLEAR I_INCL.
    SEARCH IMASK FOR '.*.'.
    IF SY-SUBRC = 0.
    CONDENSE IMASK.
    ENDIF.
    IF ( <F> CP IMASK OR IMASK = ' ' ).
    READ TABLE I_INCL WITH KEY = <F>.
    IF SY-SUBRC NE 0.
    MOVE <F> TO I_INCL-NAME.
    move 1 to i_include-count.
    collect i_include.
    APPEND I_INCL.
    ENDIF.
    ENDIF.
    ENDFORM.
    / Download table S. */
    FORM DOWNLOAD_DATA.
    CLEAR TXLINE.
    WRITE 'Downloading ' TO TXLINE.
    WRITE R1-NAME TO TXLINE+12.
    CALL FUNCTION 'SAPGUI_PROGRESS_INDICATOR'
    EXPORTING
    PERCENTAGE = 0
    TEXT = TXLINE
    EXCEPTIONS
    OTHERS = 1.
    CALL FUNCTION 'WS_DOWNLOAD'
    EXPORTING
    FILENAME = FN3
    FILETYPE = 'ASC'
    TABLES
    DATA_TAB = S.
    ENDFORM.
    / Download Binary files H1 */
    FORM DOWNLOAD_BIN_H1.
    DESCRIBE FIELD H1 LENGTH J.
    DESCRIBE TABLE H1 LINES I.
    NR_OF_BYTES = I * J.
    CALL FUNCTION 'WS_DOWNLOAD'
    EXPORTING
    FILENAME = FN1
    FILETYPE = 'BIN'
    BIN_FILESIZE = NR_OF_BYTES
    IMPORTING
    FILELENGTH = FILESIZE
    TABLES
    DATA_TAB = H1.
    ENDFORM.
    / Download Binary files F1 */
    FORM DOWNLOAD_BIN_F1.
    DESCRIBE FIELD F1 LENGTH J.
    DESCRIBE TABLE F1 LINES I.
    NR_OF_BYTES = I * J.
    CALL FUNCTION 'WS_DOWNLOAD'
    EXPORTING
    FILENAME = FN2
    FILETYPE = 'BIN'
    BIN_FILESIZE = NR_OF_BYTES
    IMPORTING
    FILELENGTH = FILESIZE
    TABLES
    DATA_TAB = F1.
    ENDFORM.
    / Upload data from file .EEE */
    FORM UPLOAD_EEE.
    CLEAR TXLINE.
    WRITE 'Uploading ' TO TXLINE.
    WRITE R1-NAME TO TXLINE+10.
    CALL FUNCTION 'SAPGUI_PROGRESS_INDICATOR'
    EXPORTING
    PERCENTAGE = 0
    TEXT = TXLINE
    EXCEPTIONS
    OTHERS = 1.
    MOVE 'Y' TO FIRST-TIME.
    CALL FUNCTION 'WS_UPLOAD'
    EXPORTING
    FILENAME = FN3
    FILETYPE = 'ASC'
    IMPORTING
    FILELENGTH = NR_OF_BYTES
    TABLES
    DATA_TAB = S1.
    LOOP AT S1.
    IF S1-TXT(4) = '????'.
    MOVE S1-TXT(8) TO NEW-FUNC.
    IF FIRST-TIME = 'Y'.
    MOVE S1-TXT(8) TO OLD-FUNC.
    MOVE 'N' TO FIRST-TIME.
    ELSE.
    PERFORM STORE_COMPONENT.
    MOVE NEW-FUNC TO OLD-FUNC.
    ENDIF.
    ENDIF.
    IF S1-TXT(4) NE '????'.
    PERFORM REBUILD-COMPONENT.
    ENDIF.
    ENDLOOP.
    PERFORM STORE_COMPONENT. "last component still to be processed
    PERFORM REBUILD-CUA. "re-build CUA, statuses, pfk etc
    ENDFORM.
    / Upload Dynpro headers (HHH) and fields (FFF) */
    / titles and dynpro logic is contained in file .EEE */
    / and has already been processed. */
    FORM UPLOAD_HHH.
    CASE REL3.
    WHEN 'X'.
    CALL FUNCTION 'WS_UPLOAD'
    EXPORTING
    FILENAME = FN1
    FILETYPE = 'BIN'
    IMPORTING
    FILELENGTH = NR_OF_BYTES
    TABLES
    DATA_TAB = H2.
    LOOP AT H2.
    MOVE H2-CNAME TO H1-NAME.
    MOVE H2-CNUM TO H1-NUMBER.
    MOVE H2-NNAME TO H1-PROG.
    MOVE H2-NNUM TO H1-DNUM.
    MOVE H2-CTIM TO H1-TGEN.
    WRITE '19' TO H1-DGEN(2).
    WRITE H2-CDAT TO H1-DGEN+2(6).
    WRITE H2-FILL TO H1+88(39).
    APPEND H1.
    ENDLOOP.
    WHEN OTHERS.
    CALL FUNCTION 'WS_UPLOAD'
    EXPORTING
    FILENAME = FN1
    FILETYPE = 'BIN'
    IMPORTING
    FILELENGTH = NR_OF_BYTES
    TABLES
    DATA_TAB = H1.
    ENDCASE.
    LOOP AT H1.
    MOVE H1-NAME TO T-NAME.
    MOVE H1-NUMBER TO T-NUMBER.
    APPEND T.
    ENDLOOP.
    ENDFORM.
    / Upload Binary file F1 - Dynpro fields */
    FORM UPLOAD_FFF.
    CASE REL3.
    WHEN 'X'.
    CALL FUNCTION 'WS_UPLOAD'
    EXPORTING
    FILENAME = FN2
    FILETYPE = 'BIN'
    IMPORTING
    FILELENGTH = NR_OF_BYTES
    TABLES
    DATA_TAB = F2.
    LOOP AT F2.
    OLD_F1 = F2.
    APPEND OLD_F1.
    ENDLOOP.
    LOOP AT OLD_F1.
    MOVE-CORRESPONDING OLD_F1 TO F1.
    APPEND F1.
    ENDLOOP.
    WHEN OTHERS.
    CALL FUNCTION 'WS_UPLOAD'
    EXPORTING
    FILENAME = FN2
    FILETYPE = 'BIN'
    IMPORTING
    FILELENGTH = NR_OF_BYTES
    TABLES
    DATA_TAB = F1.
    ENDCASE.
    ENDFORM.
    / Re-construct data from file .EEE */
    FORM REBUILD-COMPONENT.
    CASE OLD-FUNC.
    WHEN '????LOGC'. "Dynpro LOGIC.
    CASE REL3.
    WHEN 'X'.
    SHIFT S1-TXT+8 RIGHT BY 32 PLACES.
    ENDCASE.
    MOVE S1-TXT TO E1.
    APPEND E1.
    / Load ABAP Source code, CUA, pfkeys etc to int tables */
    WHEN '????SRCE'.
    MOVE S1-TXT TO S-TXT.
    APPEND S.
    CASE INCLUDES. "Included file wanted
    WHEN 'Y'.
    PERFORM SCAN4-INCLUDES.
    ENDCASE.
    if restoring / uploading rel 3.1 or lower different cua tables
    are used. At generate CUA time these will be converted by the
    system to rel 4.0
    WHEN '????STAT'.
    CASE REL3.
    WHEN 'X'.
    MOVE S1-TXT TO OLD_STA.
    APPEND OLD_STA.
    WHEN SPACE.
    MOVE S1-TXT TO STA.
    APPEND STA.
    ENDCASE.
    MOVE 'Y' TO CUA-FLAG.
    WHEN '????FUNC'.
    CASE REL3.
    WHEN 'X'.
    MOVE S1-TXT TO OLD_FUN.
    APPEND OLD_FUN.
    WHEN SPACE.
    MOVE S1-TXT TO FUN.
    APPEND FUN.
    ENDCASE.
    MOVE 'Y' TO CUA-FLAG.
    WHEN '????MEN1'.
    CASE REL3.
    WHEN 'X'.
    MOVE S1-TXT TO OLD_MEN.
    APPEND OLD_MEN.
    WHEN SPACE.
    MOVE S1-TXT TO MEN.
    APPEND

  • How to upload logos in module pool programs?

    hi frnds,
    My requirement is to upload the logo in the module pool screen.Can any one explain in detail? its urgent.

    Hi,
    First you need to upload using OAER or OAOR.
    you need to have containers, and you need to use classes.
    data: DG_DYNDOC_ID TYPE REF TO CL_DD_DOCUMENT.
    using this method you can set background picture.
    CALL METHOD DG_DYNDOC_ID->SET_DOCUMENT_BACKGROUND
    EXPORTING
    PICTURE_ID = DL_BACKGROUND_ID.
    Here is the sample code
    Create a screen
    Place a custom container for the picture on the screen.
    Name the container GO_PICTURE_CONTAINER.
    Type pool for using SAP icons
    TYPE-POOLS: icon.
    Declarations
    DATA:
    go_picture TYPE REF TO cl_gui_picture,
    go_picture_container TYPE REF TO cl_gui_custom_container.
    MODULE status_0100 OUTPUT.
    IF go_picture_container IS INITIAL.
    Create obejcts for picture and container and
    setup picture control
    CREATE OBJECT go_picture_container
    EXPORTING
    container_name = 'PICTURE_CONTAINER'.
    CREATE OBJECT go_picture
    EXPORTING
    parent = go_picture_container.
    Set display mode (Stretching, original size etc.)
    CALL METHOD go_picture->set_display_mode
    EXPORTING
    DISPLAY_MODE = CL_GUI_PICTURE=>display_mode_fit_center
    EXCEPTIONS = 1.
    Load picture from SAP Icons. To oad a picture from an URL use method
    load_picture_from_url
    CALL METHOD go_picture->load_picture_from_sap_icons
    EXPORTING
    icon = icon_delete
    EXCEPTIONS error = 1.
    ENDIF.
    ENDMODULE. [/code]
    check the below link.
    http://www.sapgenie.com/abap/controls/picture.htm
    Award points if helpful.
    Regards,
    Shiva KUmar

  • How can I run a Module pool program in Background

    Hi all,
           I have created report program and called a dialog screen e.g call screen 0100.
    this screen contains only one table control and a tabstrip control which allows user to select diffrent options.there is a push button on the application tool bar named as Background. once u click , the report has to run in background.
    if its a selection screen , i can easily create a variant n can run it in background.but here its a dialog screen, i m unable to create a variant for it. can anybody tell me how can i saves the user input values and run in background ..plz help me ....
    Bishnu Dash

    Hi ..
    Create a Transaction code for this Program.
    Then implement the BDC Code to Process the SCreens with the Required input Values.
    Schedule this BDC Session in Backgound using RSBDCSUB.
    reward if Helpful.

  • How to copy a module pool program

    Hi All,
    How to copy a module pool program from one system (Organization) to other system(organization) i.e. from one company to other company. My requirement is to how to download & upload module pool program.
    Regards,
    Rajesh Vasudeva

    Hi,
    Check the below link
    [How to DOWNLOAD  a whole module pool program????]
    [Download the Module pool program]
    Cheers,
    Surinder

  • How to download  and upload a module pool program ?

    hi i am a sudent.can anyone suggest me how to download and upload a module pool program?
    Moderator message: please search for available information/documentation.
    Edited by: Thomas Zloch on May 29, 2011 12:45 PM

    Hi,
    You cannot just download and upload module pool programs .
    There are 2 different ways.
    1. Copy all the includes and and create the same in the target system. You can download and upload the the Screen.
      But GUI status you have to manually create.
    2. If you have completely saved the module-pool program in one Workbench request(including Z tables u have used) in the original system ,just  release the workbench request and copy the data file and co file and upload to the target system ( use CG3Y & CG3Z).
    If the workbench is a Local Request save it in a Transport of copies and then move.
    Regards
    Aromal R

  • How to Upload a module Pool Program in SAP

    Hello All,
                I have downloaded My Program Using Report REPTRAN. Now i want to know how we can Upload the Module pool program and Reports in SAP .

    Hi Ram,
    Use open source project SAPLINK for downloading objects into files and uploading them into SAP. I think REPTRAN is only to download the source code.
    Regards,
    Shravan

  • How to copy the module pool program ( Screens, codeing ) ?

    Hi guys,
           How can I copy the Module pool program to another program including screen and every thing?
          can anyone help me....

    1. GO TO SE80, and select program from drop down
    2. Enter Source Prog Name and press enter
    3. Below Object name, right click on the program
    4. Select COPY and enter the (New) Target Prog Name
    it ll ask for following check box options
    -Source
    -Text Element
    -Documentation
    -Variant...etc.
    5 Select all and press enter.
    Hope this ll be helpful.
    Thanks & Regards
    Vinsee

  • How can i add total in Module Pool Programming

    Hai abapers,
    My problem is I have 15 fields in a tablecontrol.The 15th field is total field...
    When ever user enter a values in remaing fields,the 15 the field must be updated...
    how can i achieve in module pool programming..................
    i have one more problem.That is when user pressing any key.my content in table control r clearing..i need to restrict clearing values..how can i achieve it ...
    Waiting for y r favourable replies
    Regards
    Maruthi

    maruthi,
    1. when user pressing any key.my content in table control r clearing..i need to
        restrict clearing values..how can i achieve it ...
    Ans. When ever you press button it will go first to PAI event and will go back to
            PBO.So in PBO event you might have wriiten some coding that will get
            process and  updated in Table control.That time your updated data will get
           removed.
             For this take all your function codes of your buttons on screen and write
            condition
              if sy-ucom ne 'ADD'  or
                 sy-ucom ne 'Delete'.
    ********Here you keep your  PBO code
             endif.
    Now it will work fine.
    2.When ever user enter a values in remaing fields,the 15 the field must be updated
    Ans)After you entered the data in 14 fields some event has to get trigger then
           only  you can achieve your goal.
    In PBO write 
             If SY-UCOM is eq 'ADD'.            
                 collect all fields records and add here 
                 move total value to 15th record .
              Endif.
    when you press ADD button  you will achieve .
    Pls. reward if useful

  • Calling a module pool program screen to an executable program

    Hi gurus,
    I have created a executable program to use selection-screen and want to see my output in module pool program where I have designed table control according to my requirement.
    How can I call the module-pool program screen from an executable program?
    Any help?
    Regards
    Mac

    Hi Mac,
    I think you can proceed with a report program alone . There you create a screen with the table control to populate your result.
    In the report program, after getting values for internal table for your display, just call the said screen.
    i.e.
    CALL SCREEN <screen number>.
    Hope this may help you.
    Regards,
    Smart Varghese

  • Simple module pool  programming.

    hi,
    can  anybody tell me how to go about doing module pool programming ....... to start with ....... how to add  2 nos. using screen  with 2 i\o fields for user to input 2 nos. and a output field  for result.........
    can  u tell the coding and the wat plz ..

    Hey deepak i think you are very new to module pool programming but it is very difficutlt to explain step by step process but easyest programming.
    do the following steps
    1. Create a program in SE38 ex: prog name is ztest create the program as executable program
    2.  Write a code in that program like this.
    data: w_no1 type i,
             w_no2 type i.
    3. Just save the program and activate it, and now go back to SE38 tcode.
    4. Now goto SE51 transaction
    5. give ztest in the program name and give screen number as 100 now press create button
    6. give the short test and press the Layout button
    7. In the there are some buttons in the left side in that press the second button Text field and now drag and drop in the flag screen give the name and text for that
    8. and now press the third button from the top and grag and drop it now give the name as W_NO1
    9. do the 7th and third steps for second number but give the name for the second field as w_NO2
    10. save it activate it and press the Flowlogic button
    11. Now uncomment the * MODULE USER_COMMAND_0100* and double click on that in the Main program and write the code in this.
    see the following.
    PROGRAM  ZTEST20.
    data: w_no1 type i,
    w_no2 type i.
    call screen 100.
    *&      Module  USER_COMMAND_0100  INPUT
    *       text
    module USER_COMMAND_0100 input.
    *write the code here
    endmodule.                 " USER_COMMAND_0100  INPUT
    <REMOVED BY MODERATOR>
    Mahi.
    Edited by: Alvaro Tejada Galindo on Feb 22, 2008 6:18 PM

Maybe you are looking for

  • RE: [iPlanet-JATO] Parse error in JSP parser in IAS6

    Hi Todd, removing the defaultValue="" attribute works. I have not got around to testing the SP3. BTW. The reason the default value tag was added was to stop Null pointer exceptions being thrown in the HrefTag.beginDisplay(). buffer.append("?") .appen

  • Error Message when opening Apps in PSE10

    I don't have any issues opening external Apps such as IPhoto, PSE Organizer, ACDSee outside of PSE10.  All of my photo's and elements are stored on these three programs and work fine on their own. However when I open PSE10 and try to open and access

  • Inbound delivery

    Dear experts, Once the ME21K created and Inbound delivery is created with respect to Purchase order. ---Is there any provision that there should not be any changes like increasing the quantity in purchase order once inbound delivery is created. in me

  • Error in mtl_material_transactions  Cost Manager

    Hi, I am using EBS-R12 I want to find per unit costl.But I find in mtl_material_transactions Costed_flag=E and ERROR_EXPLANATION='The transaction date is not within the accounting period specified.' & inventory costing methods is average. I have upda

  • Issues exporting versions from tiff files

    I upgraded to Aperture 3 [3.0.2] running on 10.6. Aperture works fine, except when trying to export a version of a tiff file [these are 8 bit 200mb scans]. Exporting a master from a tiff file works, exporting versions from RAW files work, but Apertur