How to debug a program when it is SUBMITed from another program

Hi All,
Now one more query.  While SUBMITing a Z program1 from Z program2, I want to debug the Z program1.  Even when I keep a break point in Z program1, it is not triggering there.  Any help would be appreciated.
Regards,
Balaji

Hi all,
Please find the full code.  I want to debug the sub routine PERFORM send_mail.
1.  The main program.
REPORT  Z_ITSLIP_MAIL                           .
TABLES : pa0000, pa0001.                         .
SELECT-OPTIONS : pernr FOR pa0000-pernr NO INTERVALS.
DATA : count LIKE tbtcjob-jobcount.
DATA : released LIKE btch0000-char1.
DATA:
        l_valid,
        ls_params LIKE pri_params,
        l_jobcount LIKE tbtcjob-jobcount.
PARAMETERS: p_job TYPE tbtcjob-jobname NO-DISPLAY.
PARAMETERS: p_prog(30) TYPE c NO-DISPLAY..
PARAMETERS: p_sdat LIKE sy-datum DEFAULT sy-datum .
PARAMETERS: p_stim TYPE sy-uzeit DEFAULT sy-uzeit .
PARAMETERS : payroll LIKE qppnp-xabkr OBLIGATORY.
*PARAMETERS : period LIKE qppnp-pabrp OBLIGATORY.
*PARAMETERS : year LIKE qppnp-pabrj OBLIGATORY.
select-options : Period for sy-datum.
DATA : BEGIN OF it_p0001 OCCURS 0,
       pernr LIKE pa0001-pernr,
       END OF it_p0001.
p_sdat = p_sdat + 1.
*Get Print Parameters
CALL FUNCTION 'GET_PRINT_PARAMETERS'
  EXPORTING
    no_dialog      = 'X'
  IMPORTING
    valid          = l_valid
    out_parameters = ls_params.
IF pernr[] IS INITIAL.
  SELECT pernr
   INTO TABLE it_p0001
   FROM pa0001.
  SORT it_p0001 BY pernr.
  DELETE ADJACENT DUPLICATES FROM it_p0001.
  LOOP AT it_p0001.
    MOVE it_p0001-pernr TO pernr-low.
    APPEND pernr.
    CLEAR pernr.
  ENDLOOP.
ENDIF.
LOOP AT pernr.
  CLEAR p_job.
  p_stim = p_stim + 120.
  CONCATENATE'ITSlip' pernr-low p_job sy-datum INTO p_job SEPARATED BY
space.
  CALL FUNCTION 'JOB_OPEN'
    EXPORTING
      jobname  = p_job
    IMPORTING
      jobcount = l_jobcount.
  SUBMIT ZPR022_INNCOMETAX_REPORT_copy
    WITH PNPTIMR6 = 'X'
    WITH PNPBEGDA = period-low
    WITH PNPENDDA = period-high
    WITH PNPPERNR-LOW = PERNR-LOW
    WITH PNPABKRS-LOW = 'IN'
       VIA JOB     p_job
        NUMBER  l_jobcount
       TO SAP-SPOOL WITHOUT SPOOL DYNPRO
           SPOOL PARAMETERS ls_params
           WITH immediately = space
              AND RETURN.
  CALL FUNCTION 'JOB_CLOSE'
    EXPORTING
      jobcount  = l_jobcount
      jobname   = p_job
      strtimmed = 'X'
     PRDMINS = 2.
      sdlstrtdt = p_sdat
      sdlstrttm = p_stim.
ENDLOOP.
2.  The called program.
REPORT  zpr022_inncometax_report_copy NO STANDARD PAGE HEADING LINE-SIZE
89.
TABLES : pernr, t512e, t512t,pa0105.
      Infotypes
INFOTYPES : 0000, 0001, 0008, 0580.
      Types                    Begin with TY_
DATA : BEGIN OF wa_lgart,
       lgart TYPE t512e-lgart,
       windo TYPE t512e-windo,
       slart TYPE t512e-slart,
       lgtxt TYPE t512t-lgtxt,
       kztxt TYPE t512t-kztxt,
       END OF wa_lgart.
DATA : BEGIN OF wa_income,
       particular(24) TYPE c,
       lgart    TYPE lgart,
       cumm(13) TYPE p DECIMALS 2,
       proj(13) TYPE p DECIMALS 2,
       exem(13) TYPE p DECIMALS 2,
       annu(13) TYPE p DECIMALS 2,
       END OF wa_income.
DATA : BEGIN OF wa_income1,
       particular(24) TYPE c,
       lgart    TYPE lgart,
       cumm(13) TYPE c,
       proj(13) TYPE c,
       exem(13) TYPE c,
       annu(13) TYPE c,
       END OF wa_income1.
DATA : BEGIN OF wa_invest,
       particular(40) TYPE c,
       betrg(13) TYPE p DECIMALS 2,
       END OF wa_invest.
DATA : BEGIN OF wa_invest1,
       particular(40) TYPE c,
       betrg(13) TYPE c,
       END OF wa_invest1.
DATA : BEGIN OF wa_deduct,
       particular(40) TYPE c,
       sbs TYPE pin_sbsec,
       betrg(13) TYPE p DECIMALS 2,
       END OF wa_deduct.
DATA : BEGIN OF wa_deduct1,
       particular(40) TYPE c,
       sbs TYPE c,
       betrg(13) TYPE c,
       END OF wa_deduct1.
DATA: BEGIN OF cocd OCCURS 10.
        INCLUDE STRUCTURE pincc.
DATA: END OF cocd.
DATA: BEGIN OF f16 OCCURS 10.
        INCLUDE STRUCTURE pin16.
DATA: END OF f16.
      Constants                Begin with C_
      Data                     Begin with W_
DATA : w_clstrid TYPE t500l-relid,         "Cluster ID
       w_molga   TYPE t500p-molga,         "Country Code
       w_period(6) TYPE c,
       w_var(2) TYPE n,
       w_pr_from1 TYPE t569v-pabrj,        "year
       w_pr_to1 TYPE t569v-pabrp,          "period
       w_fpper-low1 TYPE pc261-fpper,
       w_year(4) TYPE n,
       w_ltaexe(13) TYPE p DECIMALS 2,
       w_cumm(13) TYPE p DECIMALS 2,
       w_lgtxt(20) TYPE c,
       w_lgart     TYPE lgart,
       w_amount(13) TYPE p DECIMALS 2,
       w_wage(4)   TYPE c,
       w_flag(1) TYPE c,
       w_total(13) TYPE p DECIMALS 2,
       w_start TYPE sy-datum,
       w_end   TYPE sy-datum,
       w_date  TYPE sy-datum,
       w_index(2) TYPE n VALUE 00,
       w_investnm(40),
       w_investnm1(40),
       w_ded0585(13) TYPE p DECIMALS 2,
       w_itext TYPE t7ini3-itext,
       w_dtext TYPE t7ini8-sbdds,
       w_inprvemp(13) TYPE p DECIMALS 2,
       w_nettaxin(13) TYPE p DECIMALS 2,
       w_ptaxprvemp(13) TYPE p DECIMALS 2,
       w_ptaxcremp(13) TYPE p DECIMALS 2,
       w_othtaxin(13) TYPE p DECIMALS 2,
       w_gssin(13) TYPE p DECIMALS 2,
       w_dedtot(13) TYPE p DECIMALS 2,
       w_invtot(13) TYPE p DECIMALS 2,
       w_inchrtax(13) TYPE p DECIMALS 2,
       w_nettaxpay(13) TYPE p DECIMALS 2,
       w_surchr(13) TYPE p DECIMALS 2,
       w_cess(13) TYPE p DECIMALS 2,
       w_totintax(13) TYPE p DECIMALS 2,
       w_tdsothin(13) TYPE p DECIMALS 2,
       w_cessrec(13) TYPE p DECIMALS 2,
       w_prvemp(13) TYPE p DECIMALS 2,
       w_tottaxpay(13) TYPE p DECIMALS 2,
       w_var1(13) TYPE p DECIMALS 2,
       w_var2(13) TYPE p DECIMALS 2,
       w_balit(13) TYPE p DECIMALS 2,
       w_avgmon(13) TYPE p DECIMALS 2,
       w_remmon(2) TYPE n,
       w_profund(13) TYPE p DECIMALS 2,
       w_pf(13) TYPE p DECIMALS 2,
       w_dept(25) TYPE c,
       w_desig(25) TYPE c,
       w_join TYPE sy-datum,
       w_annperk(13) TYPE p DECIMALS 2,
       w_percent TYPE pin_txexm,
       w_limit TYPE pin_sdvlt,
       w_st0008  TYPE sy-datum,
       w_en0008  TYPE sy-datum.
DATA: w_cmonth(2) TYPE n,
      w_cyear(4)  TYPE n,
      w_cdate LIKE sy-datum,
      w_ldate LIKE sy-datum.
      Internal tables          Begin with IT_
DATA : it_0001 TYPE STANDARD TABLE OF pa0001,
       it_data TYPE STANDARD TABLE OF pa0001,
       it_0000 TYPE STANDARD TABLE OF pa0000,
       it_lgart LIKE STANDARD TABLE OF wa_lgart,
       it_pc261 TYPE STANDARD TABLE OF pc261,
       it_payrt_result TYPE payin_result,
       it_income LIKE STANDARD TABLE OF wa_income,
       it_income1 LIKE STANDARD TABLE OF wa_income1,
       it_wage   LIKE it_income,
       it_invest LIKE STANDARD TABLE OF wa_invest,
       it_invest1 LIKE STANDARD TABLE OF wa_invest1,
       it_deduct LIKE STANDARD TABLE OF wa_deduct,
       it_deduct1 LIKE STANDARD TABLE OF wa_deduct1,
       it_0586 TYPE STANDARD TABLE OF pa0586,
       it_0580 TYPE STANDARD TABLE OF pa0580,
       it_0584 TYPE STANDARD TABLE OF pa0584,
       it_0585 TYPE STANDARD TABLE OF pa0585,
       it_t7ini3 TYPE STANDARD TABLE OF t7ini3,
       it_info TYPE STANDARD TABLE OF zpt011_fep_pay,
       it_0008 TYPE STANDARD TABLE OF pa0008,
       it_rt TYPE STANDARD TABLE OF pbwla WITH HEADER LINE.
DATA    : p_email1 LIKE somlreci1-receiver,
                                 DEFAULT '[email protected]'
           p_sender LIKE somlreci1-receiver.
                                     DEFAULT '[email protected]',
*DATA DECLARATION
DATA: gd_recsize TYPE i.
data: date like sy-datum.
Spool IDs
TYPES: BEGIN OF t_tbtcp.
        INCLUDE STRUCTURE tbtcp.
TYPES: END OF t_tbtcp.
DATA: it_tbtcp TYPE STANDARD TABLE OF t_tbtcp INITIAL SIZE 0,
      wa_tbtcp TYPE t_tbtcp.
Job Runtime Parameters
DATA: gd_eventid LIKE tbtcm-eventid,
      gd_eventparm LIKE tbtcm-eventparm,
      gd_external_program_active LIKE tbtcm-xpgactive,
      gd_jobcount LIKE tbtcm-jobcount,
      gd_jobname LIKE tbtcm-jobname,
      gd_stepcount LIKE tbtcm-stepcount,
      gd_error    TYPE sy-subrc,
      gd_reciever TYPE sy-subrc.
DATA:  w_recsize TYPE i.
DATA: gd_subject   LIKE sodocchgi1-obj_descr,
      it_mess_bod LIKE solisti1 OCCURS 0 WITH HEADER LINE,
      it_mess_att LIKE solisti1 OCCURS 0 WITH HEADER LINE,
      gd_sender_type     LIKE soextreci1-adr_typ,
      gd_attachment_desc TYPE so_obj_nam,
      gd_attachment_name TYPE so_obj_des.
Spool to PDF conversions
DATA: gd_spool_nr LIKE tsp01-rqident,
      gd_destination LIKE rlgrap-filename,
      gd_bytecount LIKE tst01-dsize,
      gd_buffer TYPE string.
Binary store for PDF
DATA: BEGIN OF it_pdf_output OCCURS 0.
        INCLUDE STRUCTURE tline.
DATA: END OF it_pdf_output.
CONSTANTS: c_dev LIKE  sy-sysid VALUE 'DEV',
           c_no(1)     TYPE c   VALUE ' ',
           c_device(4) TYPE c   VALUE 'LOCL'.
      Work Area                Begin with WA_
DATA : wa_0001 LIKE LINE OF it_0001,
       wa_data LIKE LINE OF it_data,
       wa_0000 LIKE LINE OF it_0000,
       wa_pc261 LIKE LINE OF it_pc261,
       wa_payrt_result TYPE LINE OF hrpay99_rt,
       wa_paycrt_result TYPE LINE OF hrpay99_crt,
       wa_0586 LIKE LINE OF it_0586,
       wa_0580 LIKE LINE OF it_0580,
       wa_0584 LIKE LINE OF it_0584,
       wa_0585 LIKE LINE OF it_0585,
       wa_t7ini3 LIKE LINE OF it_t7ini3,
       wa_in LIKE LINE OF it_income,
       wa_info LIKE LINE OF it_info,
       wa_0008 LIKE LINE OF it_0008,
       wa_wage LIKE wa_income,
       wa_rt TYPE pbwla.
      Field Symbols            Begin with FS_
FIELD-SYMBOLS: <itc> TYPE ANY,
               <ain> TYPE ANY,
               <amt> TYPE ANY,
               <sbdnn> TYPE ANY,
               <tot> TYPE ANY.
      Select Options          Begin with SO_
*SELECT-OPTIONS :
      Parameters              Begin with PR_
*PARAMETERS     :
      Initialisation
INITIALIZATION.
date = sy-datum.
      Selection-Screen
      S T A R T   O F   S E L E C T I O N
START-OF-SELECTION.
GET pernr.
  SELECT * FROM pa0001 INTO CORRESPONDING FIELDS OF TABLE it_0001
                WHERE pernr IN pnppernr
                AND   abkrs IN pnpabkrs
                AND   bukrs IN pnpbukrs.
  DELETE ADJACENT DUPLICATES FROM it_0001 COMPARING pernr.
  SELECT * FROM pa0000 INTO CORRESPONDING FIELDS OF TABLE it_0000
                WHERE pernr IN pnppernr.
  SELECT   t512e~lgart
           t512e~slart
           t512t~lgtxt
           t512t~kztxt
           INTO CORRESPONDING FIELDS OF TABLE it_lgart
           FROM t512e INNER JOIN t512t ON
                                 t512elgart = t512tlgart AND
                                 t512emolga = t512tmolga
           WHERE t512e~forml = 'ZPY2' AND
                 t512t~sprsl = sy-langu AND
                 t512e~molga = '40' AND
                 t512e~windo EQ 'W1' .
  LOOP AT it_lgart INTO wa_lgart WHERE lgart+0(1) EQ '/'.
    DELETE it_lgart.
  ENDLOOP.
  SORT it_lgart BY lgart.
**---Here we are getting the start and the End of the financial year...
  CLEAR : w_date, w_start, w_end, w_year.
  w_date = sy-datum.
**---Here we get the start date of the year.....
  IF w_date+4(2) BETWEEN '01' AND '04'.
    w_year = w_date+0(4).
    w_year = w_year - 1.
    CONCATENATE w_year '04' '01' INTO w_start.
  ELSE.
    CONCATENATE w_date+0(4) '04' '01' INTO w_start.
  ENDIF.
**---Here we get the end date of the year......
  CLEAR : w_year.
  IF w_date+4(2) BETWEEN '01' AND '04'.
    CONCATENATE w_date+0(4) '03' '31' INTO w_end.
  ELSE.
    w_year = w_date+0(4).
    w_year = w_year + 1.
    CONCATENATE w_year '03' '31' INTO w_end.
  ENDIF.
  CLEAR : w_year.
      E N D       O F   S E L E C T I O N
END-OF-SELECTION.
**---perform for getting the Income tax Calculation part....
  PERFORM f000_get_income.
  PERFORM send_mail.
      User Command Processing
*AT USER-COMMAND.
      Top Of Page
TOP-OF-PAGE.
  WRITE : / 'Mindtree Consulting Pvt Ltd',
          / 'No.42, 27th Cross',
          / '2nd Stage, Banashankari',
          / 'Bangalore - 560070'.
*&      Form  f000_get_income
      text
     -->P_IT_0001  text
     -->P_IT_LGART  text
FORM f000_get_income.
  LOOP AT it_0001 INTO wa_0001.
    CLEAR : wa_invest, wa_deduct, wa_income.
    REFRESH : it_invest, it_deduct, it_income.
    CONCATENATE pnppabrj pnppabrp INTO w_period.
**---Here we are getting the Earnings in India from RT Table...
**---Getting the relid for each employee....
    CALL FUNCTION 'PYXX_GET_RELID_FROM_PERNR'
      EXPORTING
        employee                    = wa_0001-pernr
      IMPORTING
        relid                       = w_clstrid
        molga                       = w_molga
      EXCEPTIONS
        error_reading_infotype_0001 = 1
        error_reading_molga         = 2
        error_reading_relid         = 3
        OTHERS                      = 4.
    IF sy-subrc <> 0.
     MESSAGE ID sy-msgid TYPE sy-msgty NUMBER sy-msgno
     WITH sy-msgv1 sy-msgv2 sy-msgv3 sy-msgv4.
    ENDIF.
**---Reading the rgdir of cluster 'CU' for each of the employees...
    CALL FUNCTION 'CU_READ_RGDIR'
      EXPORTING
        persnr          = wa_0001-pernr
      TABLES
        in_rgdir        = it_pc261
      EXCEPTIONS
        no_record_found = 1
        OTHERS          = 2.
    IF sy-subrc <> 0.
     MESSAGE ID sy-msgid TYPE sy-msgty NUMBER sy-msgno
     WITH sy-msgv1 sy-msgv2 sy-msgv3 sy-msgv4.
    ENDIF.
    CLEAR : w_lgtxt, w_cumm, w_ltaexe, w_flag.
    LOOP AT it_pc261 INTO wa_pc261 WHERE fpper = w_period
                                   AND   srtza  = 'A'.
**---Importing the Payroll cluster results for each employee from RT....
      CALL FUNCTION 'PYXX_READ_PAYROLL_RESULT'
        EXPORTING
          clusterid                    = w_clstrid
          employeenumber               = wa_0001-pernr
          sequencenumber               = wa_pc261-seqnr
        CHANGING
          payroll_result               = it_payrt_result
        EXCEPTIONS
          illegal_isocode_or_clusterid = 1
          error_generating_import      = 2
          import_mismatch_error        = 3
          subpool_dir_full             = 4
          no_read_authority            = 5
          no_record_found              = 6
          versions_do_not_match        = 7
          error_reading_archive        = 8
          error_reading_relid          = 9
          OTHERS                       = 10.
      IF sy-subrc <> 0.
       MESSAGE ID sy-msgid TYPE sy-msgty NUMBER sy-msgno
       WITH sy-msgv1 sy-msgv2 sy-msgv3 sy-msgv4.
      ENDIF.
**---Processing....
      LOOP AT it_lgart INTO wa_lgart.
        CLEAR : wa_income.
        IF wa_lgart-lgart NE '5004' AND
           wa_lgart-lgart NE '5007' AND
           wa_lgart-lgart NE '5008' AND
           wa_lgart-lgart NE '5011' AND
           wa_lgart-lgart NE '5012' AND
           wa_lgart-lgart NE '5014' AND
           wa_lgart-lgart NE '5017' AND
           wa_lgart-lgart NE '5018' AND
           wa_lgart-lgart NE '5027' AND
           wa_lgart-lgart NE '5029' AND
           wa_lgart-lgart NE '5031' AND
           wa_lgart-lgart NE '5039' AND
           wa_lgart-lgart NE '5060' AND
           wa_lgart-lgart NE '7004' AND
           wa_lgart-lgart NE '7007' AND
           wa_lgart-lgart NE '7008' AND
           wa_lgart-lgart NE '7011' AND
           wa_lgart-lgart NE '7012' AND
           wa_lgart-lgart NE '7014' AND
           wa_lgart-lgart NE '7017' AND
           wa_lgart-lgart NE '7018' AND
           wa_lgart-lgart NE '7027' AND
           wa_lgart-lgart NE '7029' AND
           wa_lgart-lgart NE '7031' AND
           wa_lgart-lgart NE '7039' AND
           wa_lgart-lgart NE '7060'.
          LOOP AT it_payrt_result-inter-crt INTO wa_paycrt_result
                  WHERE cumty = 'Y' AND lgart EQ wa_lgart-lgart.
            IF wa_lgart-lgart+0(1) = '7'.
              LOOP AT it_payrt_result-inter-crt INTO wa_paycrt_result
                       WHERE cumty = 'M' AND lgart EQ wa_lgart-lgart.
                READ TABLE it_payrt_result-inter-rt INTO
                           wa_payrt_result WITH
                           KEY lgart = wa_lgart-lgart.
                IF sy-subrc = 0.
                  wa_income-particular = wa_lgart-lgtxt.
                  wa_income-lgart      = wa_paycrt_result-lgart.
                  wa_income-cumm       = wa_paycrt_result-betrg.
                ENDIF.
              ENDLOOP.
            ELSE.
              wa_income-particular = wa_lgart-lgtxt.
              wa_income-lgart      = wa_paycrt_result-lgart.
              wa_income-cumm       = wa_paycrt_result-betrg.
            ENDIF.
          ENDLOOP.
          REFRESH : it_0008.
          CLEAR : wa_0008.
          PERFORM f010_get_date USING pnppabrp pnppabrj.
          CALL FUNCTION 'SG_PS_GET_LAST_DAY_OF_MONTH'
            EXPORTING
              day_in            = w_cdate
            IMPORTING
              last_day_of_month = w_ldate
            EXCEPTIONS
              day_in_not_valid  = 1
              OTHERS            = 2.
          SELECT * FROM pa0008 INTO CORRESPONDING FIELDS OF TABLE
                   it_0008 WHERE pernr = wa_0001-pernr
                           AND   begda <= w_cdate
                           AND   endda >= w_ldate.
          IF it_0008 IS INITIAL.
            SELECT * FROM pa0008 INTO CORRESPONDING FIELDS OF TABLE
                     it_0008 WHERE pernr = wa_0001-pernr
                             AND   begda BETWEEN w_cdate AND w_ldate.
            IF it_0008 IS INITIAL.
              SELECT * FROM pa0008 INTO CORRESPONDING FIELDS OF TABLE
                    it_0008 WHERE pernr = wa_0001-pernr
                            AND   begda = w_cdate.
            ENDIF.
          ENDIF.
          CLEAR : w_st0008, w_en0008.
          LOOP AT it_0008 INTO wa_0008.
            w_st0008 = wa_0008-begda.
            w_en0008 = wa_0008-endda.
            EXIT.
          ENDLOOP.
          CLEAR : wa_rt.
          REFRESH : it_rt.
          CALL FUNCTION 'RP_FILL_WAGE_TYPE_TABLE'
            EXPORTING
              begda                        = w_st0008
              endda                        = w_en0008
              infty                        = '0008'
              pernr                        = wa_0001-pernr
            TABLES
              ppbwla                       = it_rt
            EXCEPTIONS
              error_at_indirect_evaluation = 1
              OTHERS                       = 2.
          LOOP AT it_rt INTO wa_rt.
            CLEAR : w_var.
            IF wa_rt-lgart         = '5000' AND         "Basic
               wa_lgart-lgart        = '5000'.
              w_var = 12 - pnppabrp.
              wa_income-proj = wa_rt-betrg * w_var.
              wa_income-lgart = wa_rt-lgart.
**---Here we are checking for the arrers of Basic to deduct from the
*cummulation amount...
              READ TABLE it_payrt_result-inter-rt INTO wa_payrt_result
                         WITH KEY lgart = '7000'.
              IF sy-subrc = 0.
                wa_income-cumm = wa_income-cumm - wa_payrt_result-betrg.
              ENDIF.
            ENDIF.
            IF wa_rt-lgart         = '5001' AND         "HRA
               wa_lgart-lgart        = '5001'.
              w_var = 12 - pnppabrp.
              wa_income-proj = wa_rt-betrg * w_var.
              wa_income-lgart = wa_rt-lgart.
**---Here we are checking for the arrers of HRA to deduct from the
*cummulation amount...
              READ TABLE it_payrt_result-inter-rt INTO wa_payrt_result
                         WITH KEY lgart = '7001'.
              IF sy-subrc = 0.
                wa_income-cumm = wa_income-cumm - wa_payrt_result-betrg.
              ENDIF.
            ENDIF.
            IF wa_rt-lgart         = '5003' AND         "Conveyance
               wa_lgart-lgart        = '5003'.
              w_var = 12 - pnppabrp.
              wa_income-proj = wa_rt-betrg * w_var.
              wa_income-lgart = wa_rt-lgart.
**---Here we are checking for the arrers of Conveyance to deduct from
*the cummulation amount...
              READ TABLE it_payrt_result-inter-rt INTO wa_payrt_result
                         WITH KEY lgart = '7003'.
              IF sy-subrc = 0.
                wa_income-cumm = wa_income-cumm - wa_payrt_result-betrg.
              ENDIF.
            ENDIF.
            IF wa_rt-lgart         = '5005' AND         "Special Pay
               wa_lgart-lgart        = '5005'.
              w_var = 12 - pnppabrp.
              wa_income-proj = wa_rt-betrg * w_var.
              wa_income-lgart = wa_rt-lgart.
**---Here we are checking for the arrers of Special pay to deduct from
*the cummulation amount...
              READ TABLE it_payrt_result-inter-rt INTO wa_payrt_result
                         WITH KEY lgart = '7005'.
              IF sy-subrc = 0.
                wa_income-cumm = wa_income-cumm - wa_payrt_result-betrg.
              ENDIF.
            ENDIF.
            IF wa_rt-lgart         = '5002' AND         "CLA
               wa_lgart-lgart        = '5002'.
              w_var = 12 - pnppabrp.
              wa_income-proj = wa_rt-betrg * w_var.
              wa_income-lgart = wa_rt-lgart.
**---Here we are checking for the arrers of CLA to deduct from the
*cummulation amount...
              READ TABLE it_payrt_result-inter-rt INTO wa_payrt_result
                         WITH KEY lgart = '7002'.
              IF sy-subrc = 0.
                wa_income-cumm = wa_income-cumm - wa_payrt_result-betrg.
              ENDIF.
            ENDIF.
          ENDLOOP.
         LOOP AT it_payrt_result-inter-rt INTO wa_payrt_result
                 WHERE lgart = wa_lgart-lgart.
           CLEAR : w_var.
           IF wa_payrt_result-lgart = '5000' AND         "Basic
              wa_lgart-lgart        = '5000'.
             w_var = 12 - pnppabrp.
             wa_income-proj = wa_payrt_result-betrg * w_var.
             wa_income-lgart = wa_payrt_result-lgart.
           ENDIF.
***---Here we are checking for the arrers of Basic to deduct from the
*cummulation amount...
             READ TABLE it_payrt_result-inter-rt INTO wa_payrt_result
                        WITH KEY lgart = '7000'.
             IF sy-subrc = 0.
*wa_income-cumm = wa_income-cumm - wa_payrt_result-betrg.
             ENDIF.
           IF wa_payrt_result-lgart = '5001' AND         "HRA
              wa_lgart-lgart        = '5001'.
             w_var = 12 - pnppabrp.
             wa_income-proj = wa_payrt_result-betrg * w_var.
             wa_income-lgart = wa_payrt_result-lgart.
           ENDIF.
***---Here we are checking for the arrers of HRA to deduct from the
*cummulation amount...
             READ TABLE it_payrt_result-inter-rt INTO wa_payrt_result
                        WITH KEY lgart = '7001'.
             IF sy-subrc = 0.
*wa_income-cumm = wa_income-cumm - wa_payrt_result-betrg.
             ENDIF.
           IF wa_payrt_result-lgart = '5003' AND         "Conveyance
              wa_lgart-lgart        = '5003'.
             w_var = 12 - pnppabrp.
             wa_income-proj = wa_payrt_result-betrg * w_var.
             wa_income-lgart = wa_payrt_result-lgart.
           ENDIF.
***---Here we are checking for the arrers of Conveyance to deduct from
*the cummulation amount...
             READ TABLE it_payrt_result-inter-rt INTO wa_payrt_result
                        WITH KEY lgart = '7003'.
             IF sy-subrc = 0.
*wa_income-cumm = wa_income-cumm - wa_payrt_result-betrg.
             ENDIF.
           IF wa_payrt_result-lgart = '5005' AND         "Special Pay
              wa_lgart-lgart        = '5005'.
             w_var = 12 - pnppabrp.
             wa_income-proj = wa_payrt_result-betrg * w_var.
             wa_income-lgart = wa_payrt_result-lgart.
           ENDIF.
***---Here we are checking for the arrers of Special pay to deduct from
*the cummulation amount...
             READ TABLE it_payrt_result-inter-rt INTO wa_payrt_result
                        WITH KEY lgart = '7005'.
             IF sy-subrc = 0.
*wa_income-cumm = wa_income-cumm - wa_payrt_result-betrg.
             ENDIF.
           IF wa_payrt_result-lgart = '5002' AND         "CLA
              wa_lgart-lgart        = '5002'.
             w_var = 12 - pnppabrp.
             wa_income-proj = wa_payrt_result-betrg * w_var.
             wa_income-lgart = wa_payrt_result-lgart.
           ENDIF.
***---Here we are checking for the arrers of CLA to deduct from the
*cummulation amount...
             READ TABLE it_payrt_result-inter-rt INTO wa_payrt_result
                        WITH KEY lgart = '7002'.
             IF sy-subrc = 0.
*wa_income-cumm = wa_income-cumm - wa_payrt_result-betrg.
             ENDIF.
         ENDLOOP.
          IF wa_lgart-lgart = '5065'.
            READ TABLE it_payrt_result-inter-rt INTO wa_payrt_result
                       WITH KEY lgart = '5065'.
            IF sy-subrc = 0.
              wa_income-particular = wa_lgart-lgtxt.
              wa_income-lgart      = wa_lgart-lgart.
              wa_income-cumm       = wa_payrt_result-betrg.
              wa_income-proj       = 0.
            ENDIF.
          ENDIF.
          CLEAR : wa_payrt_result.
          IF wa_lgart-lgart = '5001'.
            "HRA Exemptions
            READ TABLE it_payrt_result-inter-rt INTO wa_payrt_result
                       WITH KEY lgart = '/4E4'.
            IF sy-subrc = 0.
              wa_income-exem = wa_payrt_result-betrg.
             wa_income-lgart = wa_payrt_result-lgart.
            ENDIF.
          ENDIF.
          CLEAR : wa_payrt_result.
          IF wa_lgart-lgart = '5003'.
            "Conveyance Exemptions
            READ TABLE it_payrt_result-inter-rt INTO wa_payrt_result
                       WITH KEY lgart = '/4E3'.
            IF sy-subrc = 0.
              wa_income-exem = wa_payrt_result-betrg.
             wa_income-lgart = wa_payrt_result-lgart.
            ENDIF.
          ENDIF.
          CLEAR : wa_payrt_result.
          IF wa_lgart-lgart = '5025'.
            "Leave Encashment
            READ TABLE it_payrt_result-inter-rt INTO wa_payrt_result
                       WITH KEY lgart = '/4E7'.
            IF sy-subrc = 0.
              wa_income-particular = wa_lgart-lgtxt.
             wa_income-lgart      = wa_payrt_result-lgart.
              wa_income-cumm       = wa_payrt_result-betrg.
              wa_income-exem       = wa_payrt_result-betrg.
            ENDIF.
          ENDIF.
**---Here we are calculating the annual field of the IT it_income....
          wa_income-annu = ( wa_income-cumm + wa_income-proj ) -
          wa_income-exem.
          IF wa_income IS NOT INITIAL.
            APPEND wa_income TO it_income.
          ENDIF.
        ENDIF.
      ENDLOOP.
    ENDLOOP.
    READ TABLE  it_payrt_result-inter-rt INTO wa_payrt_result
                WITH KEY lgart = '5038'.
    IF sy-subrc EQ 0.
      READ TABLE it_lgart INTO wa_lgart WITH KEY lgart = '5038'.
      wa_wage-annu       = wa_payrt_result-betrg.
      wa_wage-particular = wa_lgart-lgtxt.
      wa_wage-lgart      = w_lgart.
      wa_wage-cumm       = wa_payrt_result-betrg.
      APPEND wa_wage TO it_wage.
    ENDIF.
**---Here we are looping the RGDIR internal table for the LTA Amount in
*Offcycle....
    LOOP AT it_pc261 INTO wa_pc261 WHERE fpper = '000000'
                                   AND   srtza = 'A'.
      IF w_flag IS INITIAL.
        IF wa_pc261-fpbeg+4(2) = '01' OR
           wa_pc261-fpbeg+4(2) = '02' OR
           wa_pc261-fpbeg+4(2) = '03'.
          w_year = wa_pc261-fpbeg+0(4) - 1.
          w_pr_from1 = w_year.
        ELSE.
          w_pr_from1 = wa_pc261-fpbeg+0(4).
        ENDIF.
        IF wa_pc261-fpbeg+4(2) EQ '01'.
          w_pr_to1 = '10'.
        ELSEIF wa_pc261-fpbeg+4(2) EQ '02'.
          w_pr_to1 = '11'.
        ELSEIF wa_pc261-fpbeg+4(2) EQ '03'.
          w_pr_to1 = '12'.
        ELSEIF wa_pc261-fpbeg+4(2) EQ '04'.
          w_pr_to1 = '01'.
        ELSEIF wa_pc261-fpbeg+4(2) EQ '05'.
          w_pr_to1 = '02'.
        ELSEIF wa_pc261-fpbeg+4(2) EQ '06'.
          w_pr_to1 = '03'.
        ELSEIF wa_pc261-fpbeg+4(2) EQ '07'.
          w_pr_to1 = '04'.
        ELSEIF wa_pc261-fpbeg+4(2) EQ '08'.
          w_pr_to1 = '05'.
        ELSEIF wa_pc261-fpbeg+4(2) EQ '09'.
          w_pr_to1 = '06'.
        ELSEIF wa_pc261-fpbeg+4(2) EQ '10'.
          w_pr_to1 = '07'.
        ELSEIF wa_pc261-fpbeg+4(2) EQ '11'.
          w_pr_to1 = '08'.
        ELSEIF wa_pc261-fpbeg+4(2) EQ '12'.
          w_pr_to1 = '09'.
        ENDIF.
        CONCATENATE w_pr_from1 w_pr_to1 INTO w_fpper-low1.
        IF w_period = w_fpper-low1.
          w_flag = 'X'.
          CLEAR : wa_payrt_result.
**---Importing the Payroll cluster results for each employee from RT....
          CALL FUNCTION 'PYXX_READ_PAYROLL_RESULT'
            EXPORTING
              clusterid                    = w_clstrid
              employeenumber               = wa_0001-pernr
              sequencenumber               = wa_pc261-seqnr
            CHANGING
              payroll_result               = it_payrt_result
            EXCEPTIONS
              illegal_isocode_or_clusterid = 1
              error_generating_import      = 2
              import_mismatch_error        = 3
              subpool_dir_full             = 4
              no_read_authority            = 5
              no_record_found              = 6
              versions_do_not_match        = 7
              error_reading_archive        = 8
              error_reading_relid          = 9
              OTHERS                       = 10.
          IF sy-subrc <> 0.
       MESSAGE ID sy-msgid TYPE sy-msgty NUMBER sy-msgno
       WITH sy-msgv1 sy-msgv2 sy-msgv3 sy-msgv4.
          ENDIF.
          LOOP AT it_lgart INTO wa_lgart WHERE lgart = '5039'.
            "LTA
            LOOP AT it_payrt_result-inter-crt INTO wa_paycrt_result
                    WHERE lgart = '5039' AND cumty = 'C'.
              w_lgtxt = wa_lgart-lgtxt.
              w_lgart = wa_paycrt_result-betrg.
              w_cumm  = wa_paycrt_result-betrg.
            ENDLOOP.
          ENDLOOP.
        ENDIF.
      ENDIF.
    ENDLOOP.
**---Here we are looping through the RT table to get the LTA Exemptions
*Amount....
    LOOP AT it_payrt_result-inter-rt INTO wa_payrt_result
            WHERE lgart = '/4E5'.                    "LTA Exemptions
      w_ltaexe = wa_payrt_result-betrg.
      wa_income-particular = w_lgtxt.
      wa_income-lgart      = w_lgart.
      wa_income-cumm       = w_cumm.
      wa_income-exem       = w_ltaexe.
    ENDLOOP.
**---Here we are deducting the arrears amount from the original wagetype
*of the
**---arrear and then calculating the total of the annual column....
   CLEAR : wa_income.
   LOOP AT it_income INTO wa_income.
     CLEAR : w_wage.
     IF wa_income-lgart+0(1) = '5'.
       CONCATENATE '7' wa_income-lgart+1(3) INTO w_wage.
       READ TABLE it_income INTO wa_in WITH KEY lgart = w_wage.
       IF sy-subrc = 0.
         CLEAR : w_amount.
         w_amount = wa_in-annu.
         wa_income-annu = wa_income-annu - w_amount.
         MODIFY it_income FROM wa_income TRANSPORTING annu.
       ENDIF.
     ENDIF.
   ENDLOOP.
    APPEND LINES OF it_wage TO it_income.
**---perform to get the data of the Investments of the employee...
    PERFORM f00_investmants USING wa_0001.
    LOOP AT it_income INTO wa_income.
      READ TABLE it_0000 INTO wa_0000 WITH KEY pernr = wa_0001-pernr
                                               massn = 'GO'.
      IF sy-subrc EQ 0 AND wa_0000-begda0(6) = w_cdate0(6).
        CLEAR wa_income-proj.
        wa_income-annu = wa_income-cumm - wa_income-exem.
        MODIFY it_income FROM wa_income.
      ENDIF.
    ENDLOOP.
    LOOP AT it_income INTO wa_income.
      READ TABLE it_0000 INTO wa_0000 WITH KEY pernr = wa_0001-pernr
                                               massn = 'FF'.
      IF sy-subrc EQ 0 AND wa_0000-begda0(6) = w_cdate0(6).
        CLEAR wa_income-proj.
        wa_income-annu = wa_income-cumm - wa_income-exem.
        MODIFY it_income FROM wa_income.
      ENDIF.
    ENDLOOP.
**---Perform to reach to the Income chargable to Tax of the Employee....
    PERFORM f001_chargeable_income USING wa_0001.
**---perform to display the data in IT form.....
    PERFORM f00_output_data TABLES it_income it_deduct it_invest
                            USING  wa_0001.
  ENDLOOP.
ENDFORM.                    " f000_get_income
*&      Form  f00_output_data
      text
     -->P_IT_INCOME  text
     -->P_WA_0001  text
FORM f00_output_data  TABLES   p_it_income STRUCTURE wa_income
                               p_it_deduct STRUCTURE wa_deduct
                               p_it_invest STRUCTURE wa_invest
                      USING    p_wa_0001 TYPE pa0001.
  CLEAR : w_dept, w_desig, w_join.
  rp-provide-from-last p0001 space '18000101' '99991231'.
  rp-provide-from-frst p0000 space '18000101' '99991231'.
  w_join = p0000-begda.
  SELECT SINGLE plstx FROM t528t INTO w_desig
                  WHERE sprsl = 'E'
                  AND   plans = p0001-plans.
  SELECT SINGLE orgtx FROM t527x INTO w_dept
                WHERE sprsl = 'E'
                AND   orgeh = p0001-orgeh.
  WRITE : /.
  WRITE : / 'EMPLOYEE NUMBER :',
          p_wa_0001-pernr.
  WRITE AT 35 'EMPLOYEE NAME :'.
  WRITE : p_wa_0001-ename.
  WRITE : / 'DEPARTMENT      :',
          w_dept.
  WRITE AT 35 'DESIGNATION   :'.
  WRITE : w_desig.
  WRITE : / 'DATE OF JOINING :',
          w_join.
**---Here we are starting the output of the IT Report....
  WRITE : /.
  ULINE.
  WRITE AT 28 'INCOME TAX CALCULATION'.
  ULINE.
  WRITE : /.
  WRITE : / 'Particulars'.
  WRITE AT 26 'Cummulative Total'.
  WRITE AT 45 'Add:Projected'.
  WRITE AT 61 'Less:Exempted'.
  WRITE AT 77 'Annual. Rs.'.
  WRITE : /.
  LOOP AT p_it_income INTO wa_income.
    CLEAR : wa_income1.
    WRITE wa_income-particular TO wa_income1-particular.
    WRITE wa_income-lgart RIGHT-JUSTIFIED TO wa_income1-lgart.
    WRITE wa_income-cumm RIGHT-JUSTIFIED TO wa_income1-cumm.
    WRITE wa_income-proj RIGHT-JUSTIFIED TO wa_income1-proj.
    WRITE wa_income-exem RIGHT-JUSTIFIED TO wa_income1-exem.
    WRITE wa_income-annu RIGHT-JUSTIFIED TO wa_income1-annu.
    APPEND wa_income1 TO it_income1.
  ENDLOOP.
  LOOP AT it_income1 INTO wa_income1.
    WRITE : / wa_income1-particular LEFT-JUSTIFIED UNDER 'Particulars',
            wa_income1-cumm       UNDER 'Cummulative Total',
            wa_income1-proj       UNDER 'Add:Projected',
            wa_income1-exem       UNDER 'Less:Exempted',
            wa_income1-annu       UNDER 'Annual. Rs.'.
     w_total = w_total + wa_income-annu.
 

Similar Messages

  • Error when calling  a form from another program

    Hi all,
    I'm using the following code in EXIT_SAPLV50Q_001:
    PERFORM STATIC_CREDIT_CHECK(SAPLVKMP)  
    USING '' LIKP-KKBER LIKP-KNKLI '' 'X'
    CHANGING RC_CHECK_A RC_CHECK_F RC_WARNING RC_ERROR RC_STATUS_SET CMPSA
    I'm getting the following error:
    GETWA_NOT_ASSIGNED - Field symbol has not yet been assigned in line LOCAL: XVBKD-PRSDT which is in FORM MESSAGE_EXCEEDED_VALUE.
    I have assigned a value for field XVBKD-PRSDT so it won't be initial, but this was not helpful.
    Any ideas would be appreciated.
    Hagit

    Hi guest,
    the data definition is:
    DATA: XVBKD LIKE VBKDVB OCCURS 0 WITH HEADER LINE.
    the assignment:
    XVBKD-PRSDT = likp-erdat.
    Thanks,
    Hagit

  • How to create a variant to a report from another program at run time

    Hi experts,
                   when i am using FM  :  /OSP/REPORT_CREATE_VARIANT to create a report variant from a program then i am getting  an error 'For object /OSP/ERPNR , number range interval 01 does not exist ', how should i avoid it or can any one help me out to create a report variant from another program at run time with the results of the program.so that i can execute the report from here with this variant

    If i understand you,
    - You can use a FM like [RS_CREATE_VARIANT|https://www.sdn.sap.com/irj/sdn/advancedsearch?cat=sdn_all&query=rs_create_variant+&adv=false&sortby=cm_rnd_rankvalue] to create a variant and then use it in the [SUBMIT|http://help.sap.com/erp2005_ehp_03/helpdata/EN/fa/096d67543b11d1898e0000e8322d00/frameset.htm] statement USING SELECTION-SET.
    - But you may also use SUBMIT with WITH parameters which doesnt require variant creation and with much less programming efforts.
    - You can mix the two solutions also.
    So what is you actual requirement, also look at some documentation like [ Scheduling a Job: Full-Control Method|http://help.sap.com/erp2005_ehp_03/helpdata/EN/fa/096ce5543b11d1898e0000e8322d00/frameset.htm]
    Regards

  • How to call an alv report from another program and return back

         Hello ,
    I am calling one abap program (Prgm B) from another program (Prgrm A).
    Here, Prgm B is an ALV report. I have fetch some data from Prgem B that gets stored in an internal table.
    Now, I am using below code in Prgrm A,
      SUBMIT Prgrm B VIA SELECTION-SCREEN
                          WITH SELECTION-TABLE rspar
                          EXPORTING LIST TO MEMORY
                          AND RETURN.
    When Prgrm A executed, it lead me to selection screen of Prgrm B and when I click F8, it shows me the report output, In short, it doesnt return back to Prgrm A. It ends up showing me the alv report if Prgrm B even afetr using RETURN statement.
    I want to get back to Prgrm A by fetching some data from Prgrm B.
    Please let me know, if i am missing something.
    Regards,
    Seema

    Hi Seema,
    Refer below code.
    DATA: v_matnr LIKE mara-matnr.
    DATA: t_listobject TYPE abaplist OCCURS 0 WITH HEADER LINE.
    DATA: t_mara TYPE mara OCCURS 0 WITH HEADER LINE.
    DATA: BEGIN OF t_ascilist OCCURS 0,
             line(200).
    DATA: END OF t_ascilist.
    data var(3) type c.
    SELECT-OPTIONS: s_matnr FOR v_matnr.
    var = '  3'.
    START-OF-SELECTION.
       SUBMIT ztestaks1 WITH s_matnr IN s_matnr EXPORTING LIST TO MEMORY
       AND RETURN.
       CALL FUNCTION 'LIST_FROM_MEMORY'
            TABLES
                 listobject = t_listobject
            EXCEPTIONS
                 not_found  = 1
                 OTHERS     = 2.
       IF sy-subrc <> 0.
         MESSAGE ID sy-msgid TYPE sy-msgty NUMBER sy-msgno
                 WITH sy-msgv1 sy-msgv2 sy-msgv3 sy-msgv4.
       ELSE.
         CALL FUNCTION 'LIST_TO_ASCI'
    *     EXPORTING
    *       LIST_INDEX               = -1
    *       WITH_LINE_BREAK          = ' '
           TABLES
             listasci                 = t_ascilist
             listobject               = t_listobject
           EXCEPTIONS
             empty_list               = 1
             list_index_invalid       = 2
             OTHERS                   = 3.
         IF sy-subrc <> 0.
           MESSAGE ID sy-msgid TYPE sy-msgty NUMBER sy-msgno
                   WITH sy-msgv1 sy-msgv2 sy-msgv3 sy-msgv4.
         ELSE.
           WRITE:/ 'Below are the lines from the submitted program.'.
           LOOP AT t_ascilist.
             WRITE:/ t_ascilist-line.
           ENDLOOP.
           SKIP 2.
         ENDIF.
       ENDIF.
       IMPORT t_mara FROM MEMORY ID 'T_MARA'.
       WRITE:/
    'Here is the output from the table exported from the submitted program.'
       LOOP AT t_mara.
         WRITE:/ t_mara-matnr.
       ENDLOOP.
    Submitted program
    REPORT  ZTESTAKS1.
    DATA: v_matnr LIKE mara-matnr,
           v_maktx LIKE makt-maktx.
    DATA: t_mara TYPE mara OCCURS 0 WITH HEADER LINE.
    DATA: BEGIN OF t_makt OCCURS 0,
             matnr LIKE makt-matnr.
    DATA: END OF t_makt.
    SELECT-OPTIONS: s_matnr FOR v_matnr,
                     s_maktx FOR v_maktx.
    START-OF-SELECTION.
       SELECT matnr INTO TABLE t_makt
                    FROM makt
                   WHERE matnr IN s_matnr
                     AND maktx IN s_maktx.
    if not t_makt[] is initial.
       SELECT * FROM mara
                INTO TABLE t_mara FOR ALL ENTRIES IN t_makt
               WHERE matnr = t_makt-matnr.
    endif.
       EXPORT t_mara TO MEMORY ID 'T_MARA'.
       WRITE:/ 'This list is from the submitted program'.
       SKIP 1.
       LOOP AT t_mara.
         WRITE:/ t_mara-mtart.
       ENDLOOP.
    Hopes this helps you.
    Thanks,
    Ashok.

  • How to create a file under web application root from java program

    how to create a file under web application root from java program like an action class?

    like an action class?Huh? What exactly is your requirement?
    Creating a file is usually done with java.io API. Read the java.io tutorials how to play with files.

  • Why does Firefox give this message when I do not have another program running "Firefox is already running, but is not responding. To open a new window, you must first close the existing Firefox process, or restart your system."

    Question
    why does Firefox give this message when I do not have another program running or another window open - "Firefox is already running, but is not responding. To open a new window, you must first close the existing Firefox process, or restart your system." edit

    See also "Hang at exit":
    *http://kb.mozillazine.org/Firefox_hangs
    *https://support.mozilla.com/kb/Firefox+hangs

  • How to import photos from another program on computer eg. Adobe Photoshop

    Can photos be imported to IPhotos from another program on the same computer eg. Adobe Photoshop?

    Photos aren't "in" Photoshop. They're in the Finder and has just been set to use Photoshop to open them.
    You can import files into iPhoto by
    The File -> Add to Libary command
    Drag and Drop to either the iPhoto window or the iPhoto icon.

  • CALL TRANSACTION 'ME33K  from another program

    Hi,
    I ma trying to CALL TRANSACTION 'ME33K  from another program, but it is not working.  The transactions is opening, but it is not opening with the contract number (ls_ekpo-ebeln) i am passing.
    ls_ekpo-ebeln does have a valued when CALL TRANSACTION 'ME33K  is called.
    In debug, I noticed the "value" is blank when step into CALL TRANSACTION 'ME33K .
       WHEN 'EBELN'.  "Contract
          l_field = 'EVRTN'.
         IF ls_ekpo-ebeln <> ''.
            GET PARAMETER ID 'VRT' FIELD l_field.  "EVRTN.
           SET PARAMETER ID 'VRT' FIELD ls_ekpo-ebeln.
           CALL TRANSACTION 'ME33K AND SKIP FIRST SCREEN.
            SET PARAMETER ID 'VRT' FIELD ls_ekpo-ebeln.
          ENDIF.
    Any help or suggestions would be great.
    Thanks,
    Naing

    Dear Naing,
    I execute the same code
    IF ls_ekpo IS INITIAL.
    GET PARAMETER ID 'VRT' FIELD LS_EKPO.
    SET PARAMETER ID 'VRT' FIELD ls_ekpo.
    CALL TRANSACTION 'ME33K' AND SKIP FIRST SCREEN.
    SET PARAMETER ID 'VRT' FIELD ls_ekpo.
    ENDIF.
    And it is working.
    Try to do de simple sintax.
    A program with one pararmeter to introduce the contract number.
    The set parameter for this parameter and the call transaction.
    I´m waiting your comments.
    Regards.
    Antonio.

  • Checking whether field-symbol from another program is assigned?

    Hi all
    I'm attempting to access a FS from another program.
    As the FS can be assigned, or unassigned within that program, how do I checked for that in my calling program?
    e.g. calling program;
    FIELD-SYMBOLS: <fs> TYPE STANDARD TABLE.
    DATA: lv_var(40) type c.
    lv_var = '(ZTGT_PROG)<read_fs>'.
    ASSIGN (lv_var) TO <fs>.   " statement might dump...

    Hi
    Go through this doc and use accordingly
    Field Symbols
    Field symbols are placeholders or symbolic names for other fields. They do not physically reserve space for a field, but point to its contents. A field symbol cam point to any data object. The data object to which a field symbol points is assigned to it after it has been declared in the program.
    Whenever you address a field symbol in a program, you are addressing the field that is assigned to the field symbol. After successful assignment, there is no difference in ABAP whether you reference the field symbol or the field itself. You must assign a field to each field symbol before you can address the latter in programs.
    Field symbols are similar to dereferenced pointers in C (that is, pointers to which the content operator * is applied). However, the only real equivalent of pointers in ABAP, that is, variables that contain a memory address (reference) and that can be used without the contents operator, are reference variables in ABAP Objects.
    All operations programmed with field symbols are applied to the field assigned to it. For example, a MOVE statement between two field symbols moves the contents of the field assigned to the first field symbol to the field assigned to the second field symbol. The field symbols themselves point to the same fields after the MOVE statement as they did before.
    You can create field symbols either without or with type specifications. If you do not specify a type, the field symbol inherits all of the technical attributes of the field assigned to it. If you do specify a type, the system checks the compatibility of the field symbol and the field you are assigning to it during the ASSIGN statement.
    Field symbols provide greater flexibility when you address data objects:
    If you want to process sections of fields, you can specify the offset and length of the field dynamically.
    You can assign one field symbol to another, which allows you to address parts of fields.
    Assignments to field symbols may extend beyond field boundaries. This allows you to address regular sequences of fields in memory efficiently.
    You can also force a field symbol to take different technical attributes from those of the field assigned to it.
    The flexibility of field symbols provides elegant solutions to certain problems. On the other hand, it does mean that errors can easily occur. Since fields are not assigned to field symbols until runtime, the effectiveness of syntax and security checks is very limited for operations involving field symbols. This can lead to runtime errors or incorrect data assignments.
    While runtime errors indicate an obvious problem, incorrect data assignments are dangerous because they can be very difficult to detect. For this reason, you should only use field symbols if you cannot achieve the same result using other ABAP statements.
    For example, you may want to process part of a string where the offset and length depend on the contents of the field. You could use field symbols in this case. However, since the MOVE statement also supports variable offset and length specifications, you should use it instead. The MOVE statement (with your own auxiliary variables if required) is much safer than using field symbols, since it cannot address memory beyond the boundary of a field. However, field symbols may improve performance in some cases.
    check the below links u will get the answers for your questions
    http://help.sap.com/saphelp_nw04/helpdata/en/fc/eb3860358411d1829f0000e829fbfe/content.htm
    http://www.sts.tu-harburg.de/teaching/sap_r3/ABAP4/field_sy.htm
    http://searchsap.techtarget.com/tip/1,289483,sid21_gci920484,00.html
    Syntax Diagram
    FIELD-SYMBOLS
    Basic form
    FIELD-SYMBOLS <fs>.
    Extras:
    1. ... TYPE type
    2. ... TYPE REF TO cif
    3. ... TYPE REF TO DATA
    4. ... TYPE LINE OF type
    5. ... LIKE s
    6. ... LIKE LINE OF s
    7. ... TYPE tabkind
    8. ... STRUCTURE s DEFAULT wa
    The syntax check performed in an ABAP Objects context is stricter than in other ABAP areas. See Cannot Use Untyped Field Symbols ad Cannot Use Field Symbols as Components of Classes.
    Effect
    This statement declares a symbolic field called <fs>. At runtime, you can assign a concrete field to the field symbol using ASSIGN. All operations performed with the field symbol then directly affect the field assigned to it.
    You can only use one of the additions.
    Example
    Output aircraft type from the table SFLIGHT using a field symbol:
    FIELD-SYMBOLS <PT> TYPE ANY.
    DATA SFLIGHT_WA TYPE SFLIGHT.
    ASSIGN SFLIGHT_WA-PLANETYPE TO <PT>.
    WRITE <PT>.
    Addition 1
    ... TYPE type
    Addition 2
    ... TYPE REF TO cif
    Addition 3
    ... TYPE REF TO DATA
    Addition 4
    ... TYPE LINE OF type
    Addition 5
    ... LIKE s
    Addition 6
    ... LIKE LINE OF s
    Addition 7
    ... TYPE tabkind
    Effect
    You can define the type of the field symbol using additions 2 to 7 (just as you can for FORM parameters (compare Defining the Type of Subroutine Parameters). When you use the ASSIGN statement, the system carries out the same type checks as for USING parameters of FORMs.
    This addition is not allowed in an ABAP Objects context. See Cannot Use Obsolete Casting for FIELD SYMBOLS.
    In some cases, the syntax rules that apply to Unicode programs are different than those for non-Unicode programs. See Defining Types Using STRUCTURE.
    Effect
    Assigns any (internal) field string or structure to the field symbol from the ABAP Dictionary (s). All fields of the structure can be addressed by name: <fs>-fieldname. The structured field symbol points initially to the work area wa specified after DEFAULT.
    The work area wa must be at least as long as the structure s. If s contains fields of the type I or F, wa should have the structure s or at least begin in that way, since otherwise alignment problems may occur.
    Example
    Address components of the flight bookings table SBOOK using a field symbol:
    DATA SBOOK_WA LIKE SBOOK.
    FIELD-SYMBOLS <SB> STRUCTURE SBOOK
    DEFAULT SBOOK_WA.
    WRITE: <SB>-BOOKID, <SB>-FLDATE.
    Related
    ASSIGN, DATA
    Additional help
    Declaring Field Symbols
    Reward points if useful
    Regards
    Anji

  • Recieve data from another program

    hi, i'm trying to recieve some kind of data from another program i know where is the output of the program the problem is that i don't know how to get these datas. for example my program is writing the output in a temporary file but i'd like to recieve these datas without a temp file. the question is: Is possible to make a class that be listening to the meddle and when any program send any data to its it recieves??? if yes how can i do it?
    i'm working with girds and is easy to descover where my output will arrive the only problem is how to recieve.
    Thanks

    Or a pipe. In unix you can create a named pipe with mkfifo, which can hadilly do this kind of transfer.

  • Set the parameter in the selection screen of a program from another program

    Hi ALL,
    I need to call the program RHALESMD from another program and the program RHALESMD takes from date as one of the input parameter.how do i set the from date from the calling program and call RHALESMD
    Thanks
    Bala Duvvuri

    i got the answer
    Program accessed
    REPORT report1.
    DATA text TYPE c LENGTH 10.
    SELECTION-SCREEN BEGIN OF SCREEN 1100.
      SELECT-OPTIONS: selcrit1 FOR text,
                      selcrit2 FOR text.
    SELECTION-SCREEN END OF SCREEN 1100.
    Calling program
    REPORT report2.
    DATA: text       TYPE c LENGTH 10,
          rspar_tab  TYPE TABLE OF rsparams,
          rspar_line LIKE LINE OF rspar_tab,
          range_tab  LIKE RANGE OF text,
          range_line LIKE LINE OF range_tab.
    rspar_line-selname = 'SELCRIT1'.
    rspar_line-kind    = 'S'.
    rspar_line-sign    = 'I'.
    rspar_line-option  = 'EQ'.
    rspar_line-low     = 'ABAP'.
    APPEND rspar_line TO rspar_tab.
    range_line-sign   = 'E'.
    range_line-option = 'EQ'.
    range_line-low    = 'H'.
    APPEND range_line TO range_tab.
    range_line-sign   = 'E'.
    range_line-option = 'EQ'.
    range_line-low    = 'K'.
    APPEND range_line TO range_tab.
    SUBMIT report1 USING SELECTION-SCREEN '1100'
                   WITH SELECTION-TABLE rspar_tab
                   WITH selcrit2 BETWEEN 'H' AND 'K'
                   WITH selcrit2 IN range_tab
                   AND RETURN.
    Thanks
    Bala Duvvuri

  • How do I pass parameter to different portlet regions from another page?

    How do I pass parameter to different portlet regions from
    another page?
    I have a page that with two regions. Each region has a report
    that uses the same information to generate its report.
    Individually running the reports, I can use p_arg_names and
    p_arg_values to get what I want. However, when I run the page
    that has both portlets, my .show is gone and I cannot get it to
    use the p_arg_names, etc. Do you have any idea how to overcome
    this? Thanks for any help.

    How do I pass parameter to different portlet regions from
    another page?
    I have a page that with two regions. Each region has a report
    that uses the same information to generate its report.
    Individually running the reports, I can use p_arg_names and
    p_arg_values to get what I want. However, when I run the page
    that has both portlets, my .show is gone and I cannot get it to
    use the p_arg_names, etc. Do you have any idea how to overcome
    this? Thanks for any help.

  • CallerPrincipal when calling one sessionbean from another

    Hi all,
    I have a little problem when calling one sessionbean from another sessionbean. The problem is, that in the method, which is called, is used SessionContext's getCallerPrincipal().getName(). This works great from client, but from other sessionbeans getCallerPrincipal() retuns an "ANONYMOUS" principal. How can I set the correct principal (the principal from the first sessionbean)?
    Thank you
    My env: Glassfish 2.1.1, Netbeans 6.8, Eclipselink 2.0.0, Java 1.6.0.18
    My code:
    @Stateless
    public class ABean implements ASessionRemote{
    @Resource
    SessionContext ctx;
    @Override
    public void aMethod(){
    String name = ctx.getCallerPrincipal().getName(); // the name is ANONYMOUS, when the call is done from other sessionbean
    @Stateless
    public class BBean implements BSessionRemote{
    @Resource
    SessionContext ctx;
    @EJB
    private ASessionRemote aSessionBean;
    @Override
    public void bMethod(){
    aSessionBean.aMethod();
    }

    "This works great from client"
    What do you mean by this, i.e what sort of client are you using (stand alone app, servlet) ?
    what shows up if you printout the caller principal in the calling bean ?
    are the two ejbs in the same ear ?
    what security meta-information are you using in ejb-jar.xml and sun-ejb-jar.xml, if any ?

  • We have a 5s active on our account.  After turning on a previously active 4s (it had the same number)  The 5s can no longer place call and when you call it from another phone the 4s rings, but will not pick up.  Texting over the cell networks works fine.

    We have a 5s active on our account.  After turning on a previously active 4s (it had the same number)  The 5s can no longer place call and when you call it from another phone the 4s rings, but will not pick up.  Texting over the cell networks works fine.  Any suggestions??

    hens0861,
    Hmm, let's ensure this is working as it should be! So what phone should be active on your account? Did you switch the devices online or how to did you activate the 5s? Please share details.
    KarenC_VZW
    Follow us on Twitter @VZWSupport

  • How do i log on to my itunes account from another computer

    how do i log on to my itunes account from another computer

    Press sign in, login.
    Go to Store -> authorize this computer. Do what you have to do.
    And do not forget when you leave to deauthorize that comp and log out.

Maybe you are looking for

  • Background jobs

    Hi,         We can schedule the programs or transactions in background through SM36 and we can see the status through SM37.Then what is the use of FM's JOb_open,Job_submit and Job_close.When we will use these FM's. Can anybody tell me the difference

  • How do I allow other users limited access to iPhoto?

    I am seeking to create other user accounts for my Mac that will allow my wife and my 8 year old to view photos in iPhoto but will not allow them to screw it up (i.e., will not allow them to edit or delete any photos, etc.).  Is there a way that I can

  • How do I mark podcasts as unplayed in iTunes 11.0.1?

    You can mark unplayed as played but not Played as Unplayed? I've controlled clicked on played podcasts and there is no option to mark as unplayed. thx, Drake

  • Problem, Garageband won't save as, or create new documents.

    It says "Document 'asdfas.band' could not be saved as 'sdfsdf.band'" or, when trying to make a new song "My song.band could not be opened because there is no such file." HELP PLEASE.

  • OS X.7.5 with iTunes 11.1.3.(8) won't recognize devices

    An iPod touch (with version 4.1) and an iPad II no longer recognized since updating to iTunes 11.1.3. All devices chage up when plugged in. Have tried restarting the iPod. Also, in iTunes the iTunes Store link that normally resides near the right-han