Bank statement

when i run my program for electronic bank statement i am getting an error when posting. the error requires me to populate the business area field and i have no idea on were i can populate the business area field. please help.
below is the source code of bank statement program
  Report zum Einlesen und Verarbeiten des Elektronischen             *
  Kontoauszugs                                                       *
  Erzeugung von Testdateien mit RFEBKAt0 und RFEBKAt1                *
051198ak reorganized export of print / archive parameters to         *
         insure correct setup for all modes (online/batch/print&exec)*
         changed variable names in EXPORT statement to insure correct*
         functioning of IMPORT statement                             *
mo271101 included changes for Web GUI compatibility (section 508)    *
mo260105 included MT942 handling (setting dunning blocks             *
REPORT RFEBKA00 MESSAGE-ID FB
                LINE-SIZE 132
                NO STANDARD PAGE HEADING.
Include Common Data                                          *
INCLUDE ZFEBKA03.
*INCLUDE RFEBKA03.
INCLUDE ZFEBFR03.
*INCLUDE RFEBFR03.                      " Data France
TABLES: RFSDO,
        SSCRFIELDS.
data: lt_statements type standard table of fieb_kukey,
      l_statement type fieb_kukey.
*Daten fu00FCr die Mahnsperre                                  "mo260105
TYPES: BEGIN OF S_KUKEY_MANSP,
        SIGN(1),
        OPTION(2),
        LOW TYPE KUKEY_EB,
        HIGH TYPE KUKEY_EB,
        MANSP TYPE MANSP,
        ANZTG TYPE ANZTG,
        BUKRS TYPE BUKRS,
      END OF S_KUKEY_MANSP.
DATA: LT_KUKEY TYPE STANDARD TABLE OF S_KUKEY_MANSP,
      L_KUKEY LIKE LINE OF LT_KUKEY,
      L_GJAHR TYPE GJAHR,
      L_MANSP TYPE MANSP,
      L_KUNNR TYPE KUNNR,
      L_LIFNR TYPE LIFNR.
FIELD-SYMBOLS: <MANSP> LIKE LINE OF GT_MANSP.
*Ende der Daten fu00FCr die Mahnsperre                         "mo260105
C5053392 Code Begins
Parameters                                                   *
*------- Dateiangaben -
SELECTION-SCREEN  BEGIN OF BLOCK 1 WITH FRAME TITLE TEXT-165.
PARAMETERS: EINLESEN  LIKE RFPDO1-FEBEINLES,
            FORMAT       LIKE RFPDO1-FEBFORMAT DEFAULT 'M',
            FILE LIKE RFPDO1-FEBAUSZF default
               'c:\TESTEBS2.txt',
            STMTNO(5),
            AUSZFILE     LIKE RFPDO1-FEBAUSZF default
               'c:\bank\auszug.txt',
            UMSFILE      LIKE RFPDO1-FEBUMSF default
               'c:\bank\umsatz.txt',
           UMSFILE      LIKE RFPDO1-FEBUMSF,
            PCUPLOAD     LIKE RFPDO1-FEBPCUPLD DEFAULT 'X'.
data : file1 type string.
*PARAMETERS: INTRADAY     TYPE C DEFAULT SPACE NO-DISPLAY.
*PARAMETERS: INTRADAY     TYPE C AS CHECKBOX DEFAULT SPACE.
SELECTION-SCREEN  END OF BLOCK 1.
*------- Buchungsparameter -
SELECTION-SCREEN  BEGIN OF BLOCK 2 WITH FRAME TITLE TEXT-160.
SELECTION-SCREEN  BEGIN OF LINE.
PARAMETERS: PA_XCALL LIKE FEBPDO-XCALL    RADIOBUTTON GROUP 1.
SELECTION-SCREEN
  COMMENT 03(29) TEXT-161 FOR FIELD PA_XCALL.
PARAMETERS: PA_XBKBU LIKE FEBPDO-XBKBU.
SELECTION-SCREEN
  COMMENT 35(16) TEXT-171 FOR FIELD PA_XBKBU.
PARAMETERS: PA_MODE  LIKE RFPDO-ALLGAZMD NO-DISPLAY.
SELECTION-SCREEN: END OF LINE.
SELECTION-SCREEN  BEGIN OF LINE.
PARAMETERS: PA_XBDC  LIKE FEBPDO-XBINPT   RADIOBUTTON GROUP 1.
SELECTION-SCREEN
  COMMENT 03(29) TEXT-163 FOR FIELD PA_XBDC.
SELECTION-SCREEN
  COMMENT 35(15) TEXT-164 FOR FIELD MREGEL.
PARAMETERS: MREGEL   LIKE RFPDO1-FEBMREGEL DEFAULT '1'.
SELECTION-SCREEN: END OF LINE.
SELECTION-SCREEN: BEGIN OF LINE.
PARAMETERS: PA_TEST LIKE RFPDO1-FEBTESTL RADIOBUTTON GROUP 1.
SELECTION-SCREEN
  COMMENT 03(29) TEXT-168 FOR FIELD PA_TEST.
SELECTION-SCREEN: END OF LINE.
PARAMETERS: VALUT_ON     LIKE RFPDO2-FEBVALUT DEFAULT 'X'.
SELECTION-SCREEN  END OF BLOCK 2.
*------- Finanzdisposition -
SELECTION-SCREEN  BEGIN OF BLOCK 5 WITH FRAME TITLE TEXT-172.
SELECTION-SCREEN: BEGIN OF LINE.
PARAMETERS: PA_XDISP LIKE FEBPDO-XDISP.
SELECTION-SCREEN
  COMMENT 03(29) TEXT-170 FOR FIELD PA_XDISP.
PARAMETERS: PA_VERD  LIKE RFFFPDO1-FFDISXVERD.
SELECTION-SCREEN
  COMMENT 34(15) TEXT-174 FOR FIELD PA_VERD.
SELECTION-SCREEN
  COMMENT 55(15) TEXT-173 FOR FIELD PA_DSART.
PARAMETERS: PA_DSART LIKE FDES-DSART.
SELECTION-SCREEN: END OF LINE.
PARAMETERS: INTRADAY     LIKE RFPDO1_EN-AKINTRADAY AS CHECKBOX.
SELECTION-SCREEN  END OF BLOCK 5.
*------- Interpretationsparameter -
SELECTION-SCREEN  BEGIN OF BLOCK 3 WITH FRAME TITLE TEXT-166.
DATA: NUM10(10) TYPE N.
DATA: CHR16(16) TYPE C.
SELECT-OPTIONS: S_FILTER FOR  FEBPDO-FEBFILTER1.
SELECT-OPTIONS: T_FILTER FOR  FEBPDO-FEBFILTER2.
SELECTION-SCREEN: BEGIN OF LINE.
SELECTION-SCREEN
   COMMENT 01(31) TEXT-176 FOR FIELD PA_BDART.
PARAMETERS: PA_BDART     LIKE FEBPDO-BDART.
SELECTION-SCREEN
   COMMENT 36(21) TEXT-177 FOR FIELD PA_BDANZ.
PARAMETERS: PA_BDANZ     LIKE FEBPDO-BDANZ.
data : bankfile1 type string,
       umsfile1 type string,
       ausfile1 type string.
SELECTION-SCREEN: END OF LINE.
SELECTION-SCREEN  END OF BLOCK 3.
*------- Ausgabeparameter -
SELECTION-SCREEN  BEGIN OF BLOCK 4 WITH FRAME TITLE TEXT-167.
PARAMETERS: BATCH        LIKE RFPDO2-FEBBATCH,
            P_KOAUSZ     LIKE RFPDO1-FEBPAUSZ,   " Kontoauszug drucken
            P_BUPRO      LIKE RFPDO2-FEBBUPRO,
            P_STATIK     LIKE RFPDO2-FEBSTAT,
            PA_LSEPA     LIKE FEBPDO-LSEPA.
SELECTION-SCREEN  END OF BLOCK 4.
*eject
AT SELECTION-SCREEN                                          *
AT SELECTION-SCREEN ON VALUE-REQUEST FOR FILE.
  CALL FUNCTION 'KD_GET_FILENAME_ON_F4'
    EXPORTING
      MASK      = ',Multicash,*.txt'
      STATIC    = 'X'
    CHANGING
      FILE_NAME = FILE.
DATA: L_FILES TYPE FILETABLE,                             "mo271101
       H_FILES TYPE FILE_TABLE,                            "mo271101
       L_RC LIKE SY-SUBRC.                                 "mo271101
CALL METHOD CL_GUI_FRONTEND_SERVICES=>FILE_OPEN_DIALOG    "mo271101
   CHANGING                                                "mo271101
     FILE_TABLE              = L_FILES                     "mo271101
     RC                      = L_RC                        "mo271101
   EXCEPTIONS                                              "mo271101
     FILE_OPEN_DIALOG_FAILED = 1                           "mo271101
     CNTL_ERROR              = 2                           "mo271101
     ERROR_NO_GUI            = 3                           "mo271101
     NOT_SUPPORTED_BY_GUI    = 4                           "mo271101
     OTHERS                  = 5.                          "mo271101
IF SY-SUBRC <> 0 OR L_RC < 0.                             "mo271101
   MESSAGE ID SY-MSGID TYPE SY-MSGTY NUMBER SY-MSGNO       "mo271101
              WITH SY-MSGV1 SY-MSGV2 SY-MSGV3 SY-MSGV4.    "mo271101
ENDIF.                                                    "mo271101
READ TABLE L_FILES INDEX 1 INTO H_FILES.                  "mo271101
UMSFILE = H_FILES-FILENAME.                               "mo271101
AT SELECTION-SCREEN ON VALUE-REQUEST FOR UMSFILE.
  CALL FUNCTION 'KD_GET_FILENAME_ON_F4'
    EXPORTING
      MASK      = ',Multicash,*.txt'
      STATIC    = 'X'
    CHANGING
      FILE_NAME = UMSFILE.
**AT SELECTION-SCREEN ON VALUE-REQUEST FOR AUSZFILE.          "mo271101
DATA: L_FILES TYPE FILETABLE,                             "mo271101
       H_FILES TYPE FILE_TABLE,                            "mo271101
       L_RC LIKE SY-SUBRC.                                 "mo271101
CALL METHOD CL_GUI_FRONTEND_SERVICES=>FILE_OPEN_DIALOG    "mo271101
   CHANGING                                                "mo271101
     FILE_TABLE              = L_FILES                     "mo271101
     RC                      = L_RC                        "mo271101
   EXCEPTIONS                                              "mo271101
     FILE_OPEN_DIALOG_FAILED = 1                           "mo271101
     CNTL_ERROR              = 2                           "mo271101
     ERROR_NO_GUI            = 3                           "mo271101
     NOT_SUPPORTED_BY_GUI    = 4                           "mo271101
     OTHERS                  = 5.                          "mo271101
IF SY-SUBRC <> 0 OR L_RC < 0.                             "mo271101
   MESSAGE ID SY-MSGID TYPE SY-MSGTY NUMBER SY-MSGNO       "mo271101
              WITH SY-MSGV1 SY-MSGV2 SY-MSGV3 SY-MSGV4.    "mo271101
ELSE.                                                     "mo271101
   READ TABLE L_FILES INDEX 1 INTO H_FILES.                "mo271101
   AUSZFILE = H_FILES-FILENAME.                            "mo271101
ENDIF.                                                    "mo271101
AT SELECTION-SCREEN ON VALUE-REQUEST FOR AUSZFILE.
  CALL FUNCTION 'KD_GET_FILENAME_ON_F4'
    EXPORTING
      MASK      = ',Multicash,*.txt'
      STATIC    = 'X'
    CHANGING
      FILE_NAME = AUSZFILE.
*------- Dateiangaben -
AT SELECTION-SCREEN ON BLOCK 1.
  IF SSCRFIELDS-UCOMM = 'ONLI' OR
     SSCRFIELDS-UCOMM = 'PRIN' OR
     SSCRFIELDS-UCOMM = 'SJOB'.
    IF EINLESEN IS INITIAL.
      MESSAGE I660(FV).
      SUBMIT RFEBKA30 VIA SELECTION-SCREEN.
    ENDIF.
    MOVE AUSZFILE TO AUSZUG-FILE.
    MOVE UMSFILE  TO UMSATZ-FILE.
    IF NOT UMSFILE IS INITIAL AND FORMAT NE 'M'.
      SET CURSOR FIELD 'UMSFILE'.
      MESSAGE E621(FV).
    ENDIF.
    IF UMSFILE IS INITIAL AND FORMAT EQ 'M'.
      SET CURSOR FIELD 'UMSFILE'.
      MESSAGE E659(FV).
    ENDIF.
  ENDIF.
*------- Buchungsparameter -
AT SELECTION-SCREEN ON BLOCK 2.
  IF NOT PA_XBDC IS INITIAL.
  Batch Input erzeugen
    IF MREGEL IS INITIAL.
      SET CURSOR FIELD 'MREGEL'.
      MESSAGE E619(FV).
    ENDIF.
    IF NOT PA_XBKBU IS INITIAL.
      SET CURSOR FIELD 'PA_XBKBU'.
      MESSAGE E611(FV).
    ENDIF.
  ENDIF.
*------- Algorithmen  -
AT SELECTION-SCREEN ON BLOCK 3.
  CLEAR T_FILTER.
  LOOP AT T_FILTER.
    SHIFT T_FILTER-LOW  RIGHT DELETING TRAILING ' '.
    SHIFT T_FILTER-HIGH RIGHT DELETING TRAILING ' '.
    MODIFY T_FILTER.
  ENDLOOP.
  CASE PA_BDART.
    WHEN 1.
      IF NOT PA_BDANZ IS INITIAL.
        SET CURSOR FIELD 'PA_BDANZ'.
        MESSAGE E618(FV).
      ENDIF.
    WHEN 2.
      IF PA_BDANZ IS INITIAL.
        SET CURSOR FIELD 'PA_BDANZ'.
        MESSAGE E615(FV).
      ENDIF.
  ENDCASE.
  EXPORT PA_BDART PA_BDANZ TO MEMORY ID 'RFEBKA00_SEL'. "note 410904
*---- Ausgabesteuerung
AT SELECTION-SCREEN ON BLOCK 4.
  IF SY-BATCH = 'X'.
    IF BATCH NE 'X'.
      BATCH = 'X'.
    ENDIF.
  ENDIF.
*---- Program started with EXEC+PRINT online
  IF BATCH NE 'X'.
    IF P_BUPRO = 'X' OR P_STATIK = 'X'.
      IF SSCRFIELDS-UCOMM = 'PRIN'.
        EXECPRI = 'X'.
      ENDIF.
    ENDIF.
  ENDIF.
*------- Finanzdisposition -
AT SELECTION-SCREEN ON BLOCK 5.
  IF NOT PA_XDISP IS INITIAL.
  Call Transaktion
    IF NOT PA_XCALL IS INITIAL.
      SET CURSOR FIELD 'PA_XDISP'.
      MESSAGE E610(FV).
    ENDIF.
    IF PA_DSART IS INITIAL.
      SET CURSOR FIELD 'PA_DSART'.
      MESSAGE E612(FV).
    ENDIF.
  ENDIF.
  IF NOT INTRADAY IS INITIAL.
    IF NOT format CA 'AS'.                                  "mo260105
      SET CURSOR FIELD 'INTRADAY'.
      CLEAR ADVICE_X.
      MESSAGE E003(FTCM).
    ELSE.
      ADVICE_X = '4'.
    ENDIF.
  ENDIF.
*eject
START-OF-SELECTION                                           *
START-OF-SELECTION.
read print parameters (user defaults) for list-output         *
required for list-output to spool (i.e. batch or exec&print)  *
  IF ( BATCH = 'X' ) OR ( EXECPRI = 'X' ).
    PERFORM GET_PRINT_PARAMETERS USING PRI_PARAM ARC_PARAM.
  ENDIF.
  PERFORM INITIALIZATION.
  VGEXT_OK = TRUE.
Einlesen im richtigen Format                                 *
  IF EINLESEN = 'X'.
    CASE FORMAT.
      WHEN 'M'.
      Format: MultiCash (AUSZUG.TXT und UMSAT.TXT)
        perform gmbimport.
        PERFORM MULTICASH(RFEKA200).
      WHEN 'S'.
      Format: SWIFT MT940 (mit Strukturiertem Feld 86)
        PERFORM SWIFT_MT940(RFEKA400).
      WHEN 'I'.
      Format: SWIFT MT940 (unstrukturiertes Feld 86)
        PERFORM SWIFT_MT940(RFEKA400).
      WHEN 'D'.
      Format: DTAUS im Diskettenformat
        PERFORM DTAUS_DISK(RFEKA100).
      WHEN 'E'.
      Format: ETEBAC-Format Frankreich
        PERFORM FORMAT_FRANKREICH(RFEBFR20).
      WHEN 'F'.
      Format: TITO-Format Finnland.
        PERFORM FORMAT_TITO(RFEBFI20).
      WHEN 'C'.
      Format: CSB43-Format Spanien
        PERFORM FORMAT_CSB43(RFEBES20).
      WHEN 'R'.
      Format: CSB43-Format Spanien: Referenzfelder zusammen
        PERFORM FORMAT_CSB43_R(RFEBES20).
      WHEN 'B'.
      Format: Brazil, Banco Itau
        PERFORM FORMAT_ITAU(J_1BBR20).
      WHEN '1'.
      Format: Brazil, Banco Bradesco
        PERFORM FORMAT_BRADESCO(J_1BBR30).
      WHEN 'A'.
      Format: Americas/Austrailia BAI
        PERFORM BAI_STMT_HANDLING(RFEKA700).
      WHEN OTHERS.
    ENDCASE.
begin process returns:
    loop at s_kukey.
      l_statement-kukey = s_kukey-low.
      append l_statement to lt_statements.
    endloop.
    call function 'FIEB_RETURNS'
      TABLES
        t_statements     = lt_statements
        t_return_charges = g_return_charges.
end returns
  ENDIF.
Kontoauszug drucken                                          *
o printout works for statements only that were newly read in *
  IF P_KOAUSZ = 'X' AND EINLESEN = 'X'.
  die zu druckenden Kontoauszuege sind in Range S_KUKEY (Global Data)
    DESCRIBE TABLE S_KUKEY LINES TFILL_S_KUKEY.
    IF TFILL_S_KUKEY > 0 AND VGEXT_OK = TRUE.
      IF BATCH = 'X'.                            " set up print to spool
        NEW-PAGE PRINT ON PARAMETERS PRI_PARAM
                 ARCHIVE PARAMETERS ARC_PARAM  NO DIALOG.
      ENDIF.
      PERFORM DRUCK_KONTOAUSZUG.
      IF BATCH = 'X'.
        NEW-PAGE PRINT OFF.
        MESSAGE S640(FV) WITH SY-SPONO.
      ENDIF.
    ENDIF.
  ENDIF.
Finanzdispo Avise erzeugen                                   *
  IF PA_XDISP = 'X'.
    PERFORM FINANZDISPO_AVISE_ERZEUGEN.
  ENDIF.
Export Print Parameters to Memory                            *
  o at least ONE of the variables EXECPRI / BATCH is ALWAYS   *
    initial here (or both)                                    *
  o import takes place in RFEBBU00 if EXECPRI = 'X'           *
  o import takes place in RFEBBU01 if BATCH (<->JOBNAME) = 'X'*
  o WATCH OUT HERE: variablenames for EXPORT / IMPORT must be *
    identical otherwise IMPORT will not return the        *
    contents of the variables while SY-SUBRC EQ 0 (!!)        *
  IF ( EXECPRI = 'X' ) OR ( BATCH = 'X' ).
    PERFORM EXPORT_PRI_PARAMS.
  ENDIF.
Verbuchung aufrufen                                          *
  IF  PA_XDISP  = 'X'
  AND PA_TEST   = 'X'.
  falls FINANZDISPOAVISE und NICHT BUCHEN Verbuchung nicht aufrufen
  ELSE.
    IF ANWND = '0004'.   "Intraday
create dunning blocks if customized in T028B*************"mo260105
    REFRESH R_KUKEY.
      LOOP AT S_KUKEY.
        READ TABLE GT_MANSP ASSIGNING <MANSP>
          WITH KEY KUKEY = S_KUKEY-LOW.
*gt_mansp is filled by the format specific programs (RFEKA400)
        IF SY-SUBRC = 0.
          IF NOT <MANSP>-MANSP IS INITIAL
            AND NOT <MANSP>-BUKRS IS INITIAL.
            MOVE-CORRESPONDING S_KUKEY TO L_KUKEY.
            MOVE <MANSP>-MANSP TO L_KUKEY-MANSP.
            MOVE <MANSP>-BUKRS TO L_KUKEY-BUKRS.
            MOVE <MANSP>-ANZTG TO L_KUKEY-ANZTG.
            APPEND L_KUKEY TO LT_KUKEY.
          ENDIF.
        ENDIF.
      ENDLOOP.
      IF LINES( LT_KUKEY ) > 0.
        PERFORM SET_GLOBAL_RKUKEY(RFEBBU10) USING LT_KUKEY.
        PERFORM SET_GLOBAL_FILTER(RFEBBU10) USING S_FILTER[] T_FILTER[].
        PERFORM EINZELPOSTEN_AUSWERTEN(RFEBBU10) USING 'X'.
        LOOP AT LT_KUKEY INTO L_KUKEY.
          SELECT * FROM FEBCL
            WHERE KUKEY = L_KUKEY-LOW
              AND ( KOART = 'K' OR KOART = 'D' )
              AND AGKON <> SPACE
              AND SELFD = 'BELNR'
              AND SELVON <> SPACE.
            IF FEBCL-SELVON+10(4) <> SPACE.
              L_GJAHR = FEBCL-SELVON+10(4).
            ELSE.
              L_GJAHR = FEBKO-AZDAT(4).
            ENDIF.
            IF FEBCL-KOART = 'D'.
              L_KUNNR = FEBCL-AGKON.
              L_LIFNR = SPACE.
            ELSE.
              L_KUNNR = SPACE.
              L_LIFNR = FEBCL-AGKON.
            ENDIF.
            CALL FUNCTION 'FIEB_SET_DUNNING_BLOCK'
              EXPORTING
                I_KUKEY          = FEBCL-KUKEY
                I_ESNUM          = FEBCL-ESNUM
                I_BUKRS          = L_KUKEY-BUKRS
                I_BELNR          = FEBCL-SELVON(10)
                I_GJAHR          = L_GJAHR
                I_KUNNR          = L_KUNNR
                I_LIFNR          = L_LIFNR
                I_MANSP          = L_KUKEY-MANSP
                I_ANZTG          = L_KUKEY-ANZTG
              IMPORTING
                E_MANSP          = L_MANSP
              EXCEPTIONS
                ALREADY_EXISTING = 1
                NOT_POSSIBLE     = 2
                OTHERS           = 3.
            IF SY-SUBRC <> 0 OR L_MANSP <> L_KUKEY-MANSP.
*should be entered in the protocol
            ELSE.
*should also be entered in the protocol
            ENDIF.
          ENDSELECT.
          UPDATE FEBEP SET VB1OK = 'X' VB2OK = 'X'
                           BELNR = '' NBBLN = ''
            WHERE KUKEY = L_KUKEY-LOW.
          UPDATE FEBKO SET VB1OK = 'X' VB2OK = 'X'
                           ASTAT = '8'
            WHERE KUKEY = L_KUKEY-LOW.
        ENDLOOP.
      ENDIF.
end of dunning block enhancement*************************"mo260105
      PERFORM CREATE_MEMO_RECORDS.
    ELSE.
  Verbuchung aufrufen, falls externe Vorgu00E4nge in T028G
      IF VGEXT_OK = TRUE.
        PERFORM VERBUCHUNG_AUFRUFEN.
        DESCRIBE TABLE NOTT028G LINES TFILL_S_KUKEY.        "Unallocated
        IF TFILL_S_KUKEY > 0.            "is OK
        perform set_print_parameters using batch pri_param.
        perform write_wrong_t028g.                        "no data yet
        perform druck_kontoauszug.                        "put in nott
        perform close_print_parameters using batch.       "yet
        perform delete_statement.
          PERFORM WRITE_WRONG_T028G.                        "hw397778
        ENDIF.
      ELSE.
        DESCRIBE TABLE S_KUKEY LINES TFILL_S_KUKEY.
        IF TFILL_S_KUKEY > 0.
          IF BATCH = 'X'.                        " set up print to spool
            NEW-PAGE PRINT ON PARAMETERS PRI_PARAM
                     ARCHIVE PARAMETERS ARC_PARAM  NO DIALOG.
          ENDIF.
          PERFORM WRITE_WRONG_T028G.
          PERFORM DRUCK_KONTOAUSZUG.
          IF BATCH = 'X'.
            NEW-PAGE PRINT OFF.
            MESSAGE S640(FV) WITH SY-SPONO.
          ENDIF.
          PERFORM DELETE_STATEMENT.
        ENDIF.
      ENDIF.
    ENDIF.
  ENDIF.
*eject
Seitenanfangsverarbeitung                                   *
TOP-OF-PAGE.
--Batch-Heading-Routine aufrufen--
  PERFORM BATCH-HEADING(RSBTCHH0).
  WRITE: /01 SY-VLINE, 02 SY-ULINE(130), 132 SY-VLINE.
  IF PRINTFLAG = 'A'.
    PERFORM DRUCK_BANKUEBERSCHRIFT.
  ENDIF.
*eject
Form-Routinen                                               *
FORM VERBUCHUNG_AUFRUFEN.                                    *
FORM VERBUCHUNG_AUFRUFEN.
Wenn Range leer und Einlesen angeXt, dann gab es keine zu verbuchenden
Kontoauszu00FCge. Z.B. wenn alle Ktoauszu00FCge schon eingelesen wurden.
  DESCRIBE TABLE S_KUKEY LINES TFILL_S_KUKEY.
  IF TFILL_S_KUKEY = 0 AND EINLESEN = 'X'.
    EXIT.
  ENDIF.
Felder fu00FCr Reportaufruf fu00FCllen.
  IF BATCH = 'X'.
    JOBNAME(8)     = SY-REPID.
    JOBNAME+8(1)   = '-'.
    JOBNAME+9(14)  = TEXT-002.
    EXPORTID(8)    = SY-REPID.
    EXPORTID+8(8)  = SY-DATUM.
    EXPORTID+16(6) = SY-UZEIT.
    LOOP AT S_KUKEY.
      EXPORTID+23(8) = S_KUKEY-LOW.
      EXIT.
    ENDLOOP.
  ENDIF.
IF SPOOL = 'X'.                       " QHA  GB
   CLEAR PRI_PARAM.                   " QHA  GB
   PRI_PARAM = %_PRINT.               " QHA  GB
   EXPORT PRI_PARAM TO MEMORY.        " QHA  GB
   IF SY-SUBRC NE 0.                  " QHA  GB
      SPOOL = ' '.                    " QHA  GB
   ENDIF.                             " QHA  GB
ENDIF.                                " QHA  GB
Verbuchungsreport aufrufen falls Buchungen erzeugt werden sollen.
  IF BUBER NE SPACE.
    SUBMIT RFEBBU01 AND RETURN
                    WITH ANWND    =  ANWND
                    WITH S_KUKEY  IN S_KUKEY
                    WITH JOBNAME  =  JOBNAME
                    WITH EXPORTID =  EXPORTID
                    WITH BUBER    =  BUBER
                  WITH USEREXIT =  USEREXIT                     "30D
                   WITH SELFD    =  SELFD
                   WITH SELFDLEN =  SELFDLEN
                    WITH S_FILTER IN S_FILTER
                    WITH T_FILTER IN T_FILTER
                    WITH PA_BDART =  PA_BDART
                    WITH PA_BDANZ =  PA_BDANZ
                    WITH FUNCTION =  FUNCTION
                    WITH MODE     =  MODE
                    WITH MREGEL   =  MREGEL
                    WITH PA_EFART =  EFART
                    WITH P_BUPRO  =  P_BUPRO
                  WITH SPOOL    =  SPOOL
                    WITH P_STATIK =  P_STATIK
                    WITH VALUT_ON =  VALUT_ON
                    WITH TESTL    =  PA_TEST
                    WITH EXECPRI  = EXECPRI.
  Jobcount importieren
    IMPORT JOBCOUNT FROM MEMORY ID EXPORTID.
  WRITE: / 'Jobcount = ', JOBCOUNT.
  ENDIF.
ENDFORM.                    "VERBUCHUNG_AUFRUFEN
*eject
*&      Form  FINANZDISPO_AVISE_ERZEUGEN
      text                                                           *
FORM FINANZDISPO_AVISE_ERZEUGEN.
  LOOP AT S_KUKEY.
    SELECT * FROM FEBKO WHERE KUKEY = S_KUKEY-LOW.
    ENDSELECT.
    IF SY-SUBRC = 0.
      SUBMIT RFEBFD00 AND RETURN
                      WITH P_BUKRS  =  FEBKO-BUKRS
                      WITH P_HBKID  =  FEBKO-HBKID
                      WITH P_HKTID  =  FEBKO-HKTID
                      WITH P_ANWND  =  FEBKO-ANWND          "40a
                      WITH R_AZNUM  =  FEBKO-AZNUM
                      WITH R_AZDAT  =  FEBKO-AZDAT
                      WITH BI-NAME  =  SY-REPID
                      WITH BI-PROC  =  ADVICE_X             "46b
                      WITH BI-DSART =  PA_DSART
                      WITH P_VERD   =  PA_VERD.
    ENDIF.
  ENDLOOP.
ENDFORM.                               " FINANZDISPO_AVISE_ERZEUGEN
*eject
*&      Form  INITIALIZATION
      Felder initialisieren                                          *
FORM INITIALIZATION.
  DATA: l_job LIKE tbtcjob-jobcount,                        "mo260105
        ls_param LIKE btcselect,                            "mo260105
        lt_joblist TYPE STANDARD TABLE OF tbtcjob.          "mo260105
  UPLOAD    = PCUPLOAD.
  EB_FORMAT = FORMAT.
  IF NOT PA_XCALL IS INITIAL.
    FUNCTION = 'C'.
  ENDIF.
  IF NOT PA_XBDC  IS INITIAL.
    FUNCTION = 'B'.
  ENDIF.
  MODE     = PA_MODE.
  IF  PA_XCALL = 'X'
  AND PA_XBKBU = 'X'.
    BUBER    = '1'.
  ELSE.
    BUBER    = 'A'.
  ENDIF.
  IF INTRADAY = 'X'.
    ANWND    = '0004'.                   "Intraday Stmt
*begin of MT942 intraday enhancement                       "mo260105
    SELECT SINGLE * FROM t028b WHERE mansp <> space.
    IF sy-subrc = 0.
      ls_param-jobname = 'RFEBKA20'.
      ls_param-username = '*'.
      CALL FUNCTION 'BP_JOB_SELECT'
        EXPORTING
          jobselect_dialog  = 'N'
          jobsel_param_in   = ls_param
          enddate           = sy-datum
        TABLES
          jobselect_joblist = lt_joblist
        EXCEPTIONS
          OTHERS            = 6.
      IF sy-subrc <> 0 OR LINES( lt_joblist ) = 0.
        CALL FUNCTION 'JOB_OPEN'
          EXPORTING
            jobname  = 'RFEBKA20'
          IMPORTING
            jobcount = l_job
          EXCEPTIONS
            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.
        SUBMIT rfebka20 VIA JOB 'RFEBKA20' NUMBER l_job AND RETURN.
        IF sy-subrc = 0.
          CALL FUNCTION 'JOB_CLOSE'
            EXPORTING
              jobcount  = l_job
              jobname   = 'RFEBKA20'
              strtimmed = 'X'
            EXCEPTIONS
              OTHERS    = 9.
          IF sy-subrc <> 0.
            MESSAGE ID sy-msgid TYPE sy-msgty NUMBER sy-msgno
              WITH sy-msgv1 sy-msgv2 sy-msgv3 sy-msgv4.
          ENDIF.
        ENDIF.
      ENDIF.
    ENDIF.
*end of MT942 intraday enhancement                         "mo260105
  ELSE.
    ANWND    = '0001'.                   "Anwendung Zwischenspeicher
  ENDIF.
  EFART    = 'E'.                      "Electronischer Kontoauszug
IF SY-PDEST NE SPACE.                             " QHA
   SPOOL  = 'X'.                                  " QHA
ENDIF.                                            " QHA
*-- Avoid initial BUKRS - field: Defaults to page-header for company
*-- 0000. Fill instead with non-existing value - leads to printout of
*-- header-text for client.
  BHDGD-BUKRS = '----'.                                     "ak101199
ENDFORM.                               " INITIALIZATION
*eject
*&      Form  WRITE_WRONG_T028G
      Ausgabe der fehlenden Eintru00E4ge in T028G                        *
FORM WRITE_WRONG_T028G.
  DATA: FIRST(1) TYPE C.                                    "HP
  DATA: x_noposting(1) TYPE c.
  PRINTFLAG = SPACE.
  clear x_noposting.
  LOOP AT NOTT028G WHERE VGDEF = SPACE.
    x_noposting = 'X'.
    exit.
  ENDLOOP.
  NEW-PAGE.
    Druck der ext. Vorgu00E4nge, die nicht in T028G enhalten sind.
  WRITE: /01 SY-VLINE,  TEXT-010,  132 SY-VLINE.
  WRITE: /01 SY-VLINE,  TEXT-011,  132 SY-VLINE.
  WRITE: /01 SY-VLINE,  TEXT-012,  132 SY-VLINE.
  WRITE: /01 SY-VLINE,  TEXT-013,  132 SY-VLINE.
  WRITE: /01 SY-VLINE,  TEXT-014,  132 SY-VLINE.
  WRITE: /01 SY-VLINE,  TEXT-015,  132 SY-VLINE.
  IF X_NOPOSTING EQ 'X'.
    WRITE: /01 sy-vline,  text-017,  132 sy-vline.
  ENDIF.
WRITE: /01 SY-VLINE,  TEXT-018,  132 SY-VLINE.           "MP
WRITE: /01 SY-VLINE,  TEXT-019,  132 SY-VLINE.           "MP
WRITE: /01 SY-VLINE,  TEXT-020,  132 SY-VLINE.           "MP
  FIRST = 'X'.                                              "HP
  LOOP AT NOTT028G WHERE VOZPM = '*'.                       "HP
    IF FIRST = 'X'.                                         "HP
      WRITE: /01 SY-VLINE,  TEXT-010,  132 SY-VLINE.        "HP
      WRITE: /01 SY-VLINE,  TEXT-040,  132 SY-VLINE.        "HP
      WRITE: /01 SY-VLINE,  TEXT-041,  132 SY-VLINE.        "HP
      WRITE: /01 SY-VLINE,  TEXT-042,  132 SY-VLINE.        "HP
      WRITE: /01 SY-VLINE,  TEXT-031,  132 SY-VLINE.        "HP
      "HP
      WRITE: /01 SY-VLINE, 02 SY-ULINE(130), 132 SY-VLINE.  "HP
      CLEAR FIRST.                                          "HP
    ENDIF.                                                  "HP
    WRITE: /01     SY-VLINE,                                "HP
            03(08) NOTT028G-VGTYP,                          "HP
            12(27) NOTT028G-VGEXT,                          "HP
            40(03) '+/-',                                   "HP
            44(20) TEXT-032,                                "HP
            65(15) NOTT028G-BANKL,                          "HP
            81(18) NOTT028G-KTONR,                          "HP
           100(05) NOTT028G-AZNUM,                          "HP
           106(08) NOTT028G-KUKEY,                          "HP
           115(05) NOTT028G-ESNUM,                          "HP
           132     SY-VLINE.                                "HP
    DELETE NOTT028G.                                        "HP
  ENDLOOP.                                                  "HP
  SORT NOTT028G.                                            "HP
  LOOP AT NOTT028G.                                         "HP
    AT FIRST.                                               "HP
      WRITE: /01 SY-VLINE,  TEXT-010,  132 SY-VLINE.
      WRITE: /01 SY-VLINE,  TEXT-030,  132 SY-VLINE.
      WRITE: /01 SY-VLINE,  TEXT-031,  132 SY-VLINE.
      WRITE: /01 SY-VLINE, 02 SY-ULINE(130), 132 SY-VLINE.
    ENDAT.                                                  "HP
LOOP AT nott028g.                                         "HP
    WRITE: /01     SY-VLINE,
            03(08) NOTT028G-VGTYP,
            12(27) NOTT028G-VGEXT,
            40(01) NOTT028G-VOZPM,
            44(20) TEXT-032,
            65(15) NOTT028G-BANKL,
            81(18) NOTT028G-KTONR,
           100(05) NOTT028G-AZNUM,
           106(08) NOTT028G-KUKEY,
           115(05) nott028g-esnum.
    if nott028g-vgdef = 'X'.
      write  121(07) G_VGEXT.
    endif.
    write  132     sy-vline.
  ENDLOOP.
  WRITE: /01 SY-VLINE, 02 SY-ULINE(130), 132 SY-VLINE.
  if x_noposting = 'X'.
    MESSAGE s773.
  endif.
ENDFORM.                               " WRITE_WRONG_T028G
*eject
Include der Form-Routinen  fu00FCr Ausdruck des Kontoauszuges    *
INCLUDE ZFEKAP00.
      Form  DELETE_STATEMENT
FORM DELETE_STATEMENT.
  SELECT * FROM FEBKO  WHERE KUKEY IN S_KUKEY AND ANWND = '0001'.
    DELETE FROM FEBRE WHERE KUKEY = FEBKO-KUKEY.
    DELETE FROM FEBEP WHERE KUKEY = FEBKO-KUKEY.
    MOVE-CORRESPONDING FEBKO TO FEBVW.
    DELETE FEBVW.
    DELETE FEBKO.
  ENDSELECT.
ENDFORM.                               " DELETE_STATEMENT
Form  GET_PRINT_PARAMETERS                                           *
FORM GET_PRINT_PARAMETERS USING P_PRI_PARAM LIKE PRI_PARAMS
                                P_ARC_PARAM LIKE ARC_PARAMS.
  DATA: LIST_NAME LIKE PRI_PARAMS-PLIST.
  LIST_NAME     = SY-REPID.
  CALL FUNCTION 'GET_PRINT_PARAMETERS'
       EXPORTING
            NO_DIALOG              = 'X'
            LIST_NAME              = LIST_NAME
            MODE                   = 'CURRENT'
          LAYOUT                 = 'X_65_132'
       IMPORTING
            OUT_ARCHIVE_PARAMETERS = P_ARC_PARAM
            OUT_PARAMETERS         = P_PRI_PARAM.
P_PRI_PARAM-LINSZ = '132'.  "workaround
ENDFORM.                    "GET_PRINT_PARAMETERS
Form  EXPORT_PRI_PARAMS                                             *
Export print and archive parameters for later import in reports     *
RFEBBU00 or RFEBBU01 (depending on parameters EXECPRI and JOBNAME)*
Variablenames for IMPORT / EXPORT must be the same, so we better    *
don't use local variables here.                                     *
FORM EXPORT_PRI_PARAMS.
  CLEAR PRI_KEY.
  PRI_KEY-REPID = 'RFEBBU00'.
  LOOP AT S_KUKEY.
    PRI_KEY-KUKEY = S_KUKEY-LOW.
    EXIT.
  ENDLOOP.
  EXPORT PRI_PARAM ARC_PARAM TO MEMORY ID PRI_KEY.
ENDFORM.                                            " EXPORT_PRI_PARAMS
----  T H E   E N D -
*&      Form  CREATE_MEMO_RECORDS
      text
-->  p1        text
<--  p2        text
FORM CREATE_MEMO_RECORDS.
  DATA: XFEBKO LIKE FEBKO OCCURS 2 WITH HEADER LINE.
  DATA: XFEBPI LIKE FEBPI OCCURS 2 WITH HEADER LINE.
  DATA: HEADER_LINE(130) TYPE C.
  DATA: POMSG LIKE BALMT.
  DATA: BEGIN OF ITAB_FDES OCCURS 10.
          INCLUDE STRUCTURE FDES.
  DATA: END OF ITAB_FDES.
  PRINTFLAG = SPACE.
  LOOP AT S_KUKEY.
    AT FIRST.
      IF P_BUPRO = 'X'.
        NEW-PAGE.
        WRITE: /01 SY-VLINE,
                   TEXT-170,
               132 SY-VLINE.
        WRITE: /01 SY-VLINE, 02 SY-ULINE(130), 132 SY-VLINE.
        HEADER_LINE = TEXT-031.
        SHIFT HEADER_LINE BY 62 PLACES.
        WRITE: /01 SY-VLINE,
                   HEADER_LINE(35),
               132 SY-VLINE.
        WRITE: /01 SY-VLINE, 02 SY-ULINE(130), 132 SY-VLINE.
      ENDIF.
    ENDAT.
    SELECT * FROM FEBKO WHERE KUKEY = S_KUKEY-LOW.
    ENDSELECT.
    IF SY-SUBRC = 0.
      REFRESH XFEBKO.
      CLEAR   XFEBKO.
      XFEBKO = FEBKO.
      APPEND XFEBKO.
      REFRESH XFEBPI.
      CLEAR   XFEBPI.
      SELECT SINGLE * FROM FEBPI INTO XFEBPI
             WHERE KUKEY = XFEBKO-KUKEY
               AND ESNUM = 0.
      IF SY-SUBRC = 0.
        APPEND XFEBPI.
        CALL FUNCTION 'POST_MEMO_ENTRIES_POLLING_DIR'
          TABLES
            T_FEBKO                 = XFEBKO
          T_FEBEP                 =
            T_FEBPI                 = XFEBPI
          EXCEPTIONS
            STATEMENT_NOT_PROCESSED = 1
            DISTINCT_FDES_NOT_FOUND = 1
            OTHER_CUSTOMIZATION     = 1
            NOTHING_TO_POST         = 2
            OTHERS                  = 1.
        IF SY-SUBRC = 0.
          CLEAR POMSG.
*-- update bdb --
          LOOP AT XFEBKO.
            UPDATE FEBKO
               SET ASTAT = XFEBKO-ASTAT
                   VB1OK = XFEBKO-VB1OK
                   VB2OK = XFEBKO-VB2OK
                   XFDIS = XFEBKO-XFDIS
             WHERE ANWND = XFEBKO-ANWND
               AND ABSND = XFEBKO-ABSND
               AND AZIDT = XFEBKO-AZIDT
               AND EMKEY = XFEBKO-EMKEY.
          ENDLOOP.
          LOOP AT XFEBPI.
            UPDATE FEBPI
               SET IDENR = XFEBPI-IDENR
                   DATM1 = XFEBPI-DATM1
                   TIME1 = XFEBPI-TIME1
             WHERE KUKEY = XFEBPI-KUKEY
           

More than 90% of this time it's due to a misunderstanding (in-apps, subscription renewals, etc.), or accidental due to family members (other accunts)...
At least you can check what's purchased on your own account:
Tunes Store & Mac App Store: Seeing your purchase history and order numbers
          http://support.apple.com/kb/HT2727
If the purchases do not show up there, then it's coming from another iTS account. You may wish to contact iTS...
iTunes Store Support
http://www.apple.com/emea/support/itunes/contact.html
They could disable the other account if it turns out not to be accidental, etc.

Similar Messages

  • Manual Bank Statement

    Hi,
    I have processed the manual bank statement, I could see in the stament overview that Manual posting is done and There are 2 transactions under FB01 with Debiting the amount. But nothing is shown under credit amount. When I check the concerned bank account and customer open and cleared items, no posting is made. What could be the error? Later I have done manual post processing (FEBA), still the same result. What could be the problem?
    Thanks

    Hi,
    1. Check in Bank config.. Create and assign Business Transactions and Define Posting Keys and Posting Rules for Manual Bank Statement.
    2. Check GL accounts are attached to the bank accounts under House bank node.
    3.In FF67 Verify the specifications Memo record entry -- Start variant, customer and vendor match codes and Further processing -- 'Processing Type' -- 2.
    4.Check other account assignment in FF67: Tran type, Value date, Amount, Bank ref.,Cost Center and Profit center..
    4.If the processing type is '2' Run the session by using SM35.
    Regards,
    Padmaja N.
    Edited by: NUKALA PADMAJA on Apr 29, 2008 5:04 AM

  • CE Bank Statement Open Interface

    Hi,
    I have successfully run the Bank Statement Loader for Open Interface.
    Then I run the 2nd step > Bank Statement Import:
    The docs said:
    2. Bank Statement Import
    The required parameters to this job are the following:
    Bank Branch Name - Provide the bank branch name that you setup in the Bank
    Account Setup section.
    GL Date - Although this parameter is not marked as required, the import will
    often fail if you do not provide a value for this parameter.  The date must in
    an open period in both AP and AR.
    Note:  If you have multiple files loaded, but only want to import one of them,
    use the Statement Date or Statement Number range parameters to limit the import
    job.
    If successful, this program moves records from the
    CE_STATEMENT_HEADERS_INTERFACE and CE_STATEMENT_LINES_INTERFACE tables into
    the CE_STATEMENT_HEADERS and CE_STATEMENT_LINES tables.May run request was successful, and I got this logs
    Output log
                                                                   Execution Report                       Report Date   26-MAR-09 20:28
                                                                                                                 Page     1 of      1
    Statement Number        -
    Statement Date          -
    Bank Branch Name       Rufino                                       Bank Name            Asia United Bank
    Bank Account Number     -                                           Bank Account Currency    -
    Bank Account Name       -
                              ******* Program Ran Successfully, No Error Found. ********View Log
    +---------------------------------------------------------------------------+
    Cash Management: Version : 12.0.0
    Copyright (c) 1979, 1999, Oracle Corporation. All rights reserved.
    CEIMPERR module: Bank Statement Import Execution Report
    +---------------------------------------------------------------------------+
    Current system time is 26-MAR-2009 20:28:57
    +---------------------------------------------------------------------------+
    +-----------------------------
    | Starting concurrent program execution...
    +-----------------------------
    Arguments
    P_BANK_BRANCH_ID='3104'
    P_SQL_TRACE='N'
    P_DISPLAY_DEBUG='N'
    Current NLS_LANG and NLS_NUMERIC_CHARACTERS Environment Variables are :
    American_America.US7ASCII
    Enter Password:
    Report Builder: Release 10.1.2.2.0 - Production on Thu Mar 26 20:28:58 2009
    Copyright (c) 1982, 2005, Oracle.  All rights reserved.
    +---------------------------------------------------------------------------+
    Start of log messages from FND_FILE
    +---------------------------------------------------------------------------+
    +---------------------------------------------------------------------------+
    End of log messages from FND_FILE
    +---------------------------------------------------------------------------+
    +---------------------------------------------------------------------------+
    Executing request completion options...
    +------------- 1) PRINT   -------------+
    Printing output file.
                   Request ID : 328310      
             Number of copies : 0      
                      Printer : noprint
    +--------------------------------------+
    Finished executing request completion options.
    +---------------------------------------------------------------------------+
    Concurrent request completed successfully
    Current system time is 26-MAR-2009 20:29:00
    +---------------------------------------------------------------------------+Why is that my
    CE_STATEMENT_HEADERS
    and
    CE_STATEMENT_LINES
    have no rows?
    Thanks a lot

    The error tables has no contents either :(
    The trace files does not help much , I want to know the program part that inserts into the target tables, but its just showing other reports process :((
    trace file
    PARSING IN CURSOR #2 len=11462 dep=0 uid=173 oct=3 lid=173 tim=1209109154828460 hv=1080153458 ad='436471d8'
    SELECT /* Created Miscellaneous Receipt */
            l1.meaning                              error_type,
            'D'                             break_group,
            sh.statement_number                     statement_no,
            sh.doc_sequence_value                                   doc_sequence_value,
            sl.line_number                  line_no,
            sh.statement_date                       statement_date,
            sl.trx_date                             trx_date,
            ba.bank_account_num                     bank_acc,
            ba.bank_account_name            bank_account_name,
            ba.currency_code                        acc_currency,
            NULL                            message_name,
            nvl(sl.amount,0)                        amount,
            acr.currency_code                       C_CURRENCY_CODE,
            l2.meaning                              trx_type,
            acr.receipt_number                      trx_no,
            'CE'                            application_short_name,
            bb.branch_party_id                      bank_branch_id
    FROM        ce_lookups                  l1,
            ce_lookups                      l2,
            ce_bank_accts_gt_v                      ba,
            ce_bank_branches_v                      bb,
                       ce_statement_headers         sh,
                       ce_statement_lines                   sl,
            ar_cash_receipts_all    acr,
                       ce_222_reconciled_v cr
      WHERE l1.lookup_type = 'ABR_REPORT_EXCEPTIONS' AND l1.lookup_code = 'MISC_RECEIPT_CREATED' AND l2.lookup_type = 'BANK_TRX_TYPE' AND l2.lookup_code = sl.trx_type AND bb.branch_party_id = ba.bank_branch_id AND bb.branch_party_id = : P_BANK_BRANCH_ID AND ba.bank_account_id = sh.bank_account_id AND sh.statement_header_id = sl.statement_header_id AND ba.bank_account_id = DECODE ( : P_BANK_ACCOUNT_ID , NULL , ba.bank_account_id , : P_BANK_ACCOUNT_ID ) AND to_char ( sh.statement_date , 'YYYY/MM/DD' ) >= nvl ( to_char ( : P_STAT_DATE_FROM , 'YYYY/MM/DD' ) , to_char ( sh.statement_date , 'YYYY/MM/DD' ) ) AND to_char ( sh.statement_date , 'YYYY/MM/DD' ) <= nvl ( to_char ( : P_STAT_DATE_TO , 'YYYY/MM/DD' ) , to_char ( sh.statement_date , 'YYYY/MM/DD' ) ) AND sh.statement_number >= nvl ( : P_STAT_NUMBER_FROM , sh.statement_number ) AND sh.statement_number <= nvl ( : P_STAT_NUMBER_TO , sh.statement_number ) and acr.cash_receipt_id = cr.cash_receipt_id and cr.statement_line_id = sl.statement_line_id and acr.comments = 'Created by Auto Bank Rec' UNION ALL SELECT    /* Reconciliation errors */
            l1.description                  error_type,
            'C'                             break_group,
            sh.statement_number                     statement_no,
            sh.doc_sequence_value                                   doc_sequence_value,
            sl.line_number                  line_no,
            sh.statement_date                       statement_date,
            sl.trx_date                             trx_date,
            ba.bank_account_num                             ba.bank_account_name            bank_account_name,
            ba.currency_code                        acc_currency,
            e.message_name                          message_name,
            to_number(NULL)                 amount,
            ba.currency_code                        C_CURRENCY_CODE,
            NULL                            trx_type,
            NULL                            trx_no,
            NVL(e.application_short_name,'CE')      application_short_name,
            bb.branch_party_id                      bank_branch_id
    FROM        ce_lookups                          l1,
            ce_bank_accts_gt_v                      ba,
            ce_bank_branches_v                      bb,
                       ce_statement_headers         sh,
            ce_reconciliation_errors                e
      WHERE l1.lookup_type = 'ABR_REPORT_EXCEPTIONS' AND l1.lookup_code = 'RECONCILIATION' AND bb.branch_party_id = ba.bank_branch_id AND bb.branch_party_id = : P_BANK_BRANCH_ID AND ba.bank_account_id = sh.bank_account_id AND ba.account_classification = 'INTERNAL' AND sh.statement_header_id = e.statement_header_id AND e.statement_line_id is null AND ba.bank_account_id = DECODE ( : P_BANK_ACCOUNT_ID , NULL , ba.bank_account_id , : P_BANK_ACCOUNT_ID ) AND to_char ( sh.statement_date , 'YYYY/MM/DD' ) >= nvl ( to_char ( : P_STAT_DATE_FROM , 'YYYY/MM/DD' ) , to_char ( sh.statement_date , 'YYYY/MM/DD' ) ) AND to_char ( sh.statement_date , 'YYYY/MM/DD' ) <= nvl ( to_char ( : P_STAT_DATE_TO , 'YYYY/MM/DD' ) , to_char ( sh.statement_date , 'YYYY/MM/DD' ) ) AND sh.statement_number >= nvl ( : P_STAT_NUMBER_FROM , sh.statement_number ) AND sh.statement_number <= nvl ( : P_STAT_NUMBER_TO , sh.statement_number ) UNION ALL ( SELECT     /* Header interface errors */
            l.description                   error_type,
            'A'                             break_group,
            e.statement_number                      statement_no,
                      to_number(NULL)                       doc_sequence_value,
            1                               line_no,
            sh.statement_date                       statement_date,
            sh.statement_date                       trx_date,
            e.bank_account_num                      bank_acc,
            ba.bank_account_name            bank_account_name,
            ba.currency_code                        acc_currency,
            e.message_name                  message_name,
            0                               amount,
            ' '                             C_CURRENCY_CODE,
            ' '                             trx_type,
            ' '                             trx_no,
            NVL(e.application_short_name,'CE')      application_short_name,
            bb.branch_party_id                      bank_branch_id
    FROM         ce_lookups                 l,
                       ce_statement_headers_int     sh,
                       ce_header_interface_errors   e,
            ce_bank_branches_v              bb,
            ce_bank_accts_gt_v              ba
    bank_acc,   WHERE l.lookup_type = 'ABR_REPORT_EXCEPTIONS' AND l.lookup_code = 'STATEMENT' AND sh.bank_account_num = e.bank_account_num AND sh.statement_number = e.statement_number AND sh.bank_branch_name = bb.bank_branch_name AND e.bank_account_num = NVL ( ba.bank_account_num , e.bank_account_num ) AND ba.bank_branch_id = bb.branch_party_id AND bb.bank_branch_name = DECODE ( : C_BANK_BRANCH_NAME_DSP , : C_ALL_TRANSLATION , bb.bank_branch_name , : C_BANK_BRANCH_NAME_DSP ) AND ba.bank_account_id = NVL ( : P_BANK_ACCOUNT_ID , ba.bank_account_id ) AND ba.account_classification = 'INTERNAL' AND to_char ( sh.statement_date , 'YYYY/MM/DD' ) >= nvl ( to_char ( : P_STAT_DATE_FROM , 'YYYY/MM/DD' ) , to_char ( sh.statement_date , 'YYYY/MM/DD' ) ) AND to_char ( sh.statement_date , 'YYYY/MM/DD' ) <= nvl ( to_char ( : P_STAT_DATE_TO , 'YYYY/MM/DD' ) , to_char ( sh.statement_date , 'YYYY/MM/DD' ) ) AND sh.statement_number >= nvl ( : P_STAT_NUMBER_FROM , sh.statement_number ) AND sh.statement_number <= nvl ( : P_STAT_NUMBER_TO , sh.statement_number )thanks

  • I can no longer read my bank statements. I believe they are using a PDF to display this information.

    I can no longer read my bank statements. I believe they are using a PDF to display this information. If I go to chrome it will open the bank statements but Firefox no longer open these flies. Why??????

    It's very unusual to get no results for PDF in the Application preferences list. It's possible that the file which stores those preferences might have become corrupted. Perhaps it would be best to rename or delete the file and let Firefox re-create it.
    Here's how:
    Open your current Firefox settings (AKA Firefox profile) folder using
    Help > Troubleshooting Information > "Show Folder" button
    Switch back to Firefox and Exit
    Pause while Firefox finishes its cleanup, then rename '''mimeTypes.rdf''' to something like mimeTypes.old
    Restart Firefox. After things setting down, check the Application preferences again to see whether PDF is listed and then set the drop-down on the right side to the desired action.
    orange Firefox button or classic Tools menu > Options > Applications
    Does that work any better?

  • Error in updating OBNK Table ( Bank Statements and Reconciliations,Manual)

    PLease advise ,
    Bank Statements and Reconciliations,Manual Reconciliation
    Client is receiving the following message:
    Error in updating OBNK Table
    Edited by: Philip Eller on May 20, 2008 9:03 AM

    Hi Darpal Thiarha,
    Please kindly refer to note 1132591 and note 1128677 to see if these are relevant to this issue. Upgrading to  2007A PL15 or above may avoid such issues relevant with the error 'Error in updating OBNK Table'.
    Regards,
    Candice Ren
    SAP Business One Forums Team

  • Electronic Bank Statement Determining Incorrect Business Partners

    Have an issue with some electronic bank statements we import into SAP. Several of the line items we get from the bank identify the incorrect business partner when creating the payment advice. We are using intepretation algorirthm 001 to interpret the Note to Payee field in the statment.
    We do have 5 search strings in place which do successfully replace the text in the Note to Payee and replace with the vendor #. These work just fine.
    What is weird to me is that when I repeat the issue in another environment and simulate using FEBSTS, it is finding "document numbers" that are text strings and somehow determining the vendor from that. I cannot figure out what logic it is using to do this and why it thinks that when it sees ABCDEGF in the Note to Payee it should be for vendor 1234555, for example.
    These are files from Citibank and the Note to Payee field is in German if that make any difference. The easy solution is to setup search strings that correspond to the text found in there like we do for the other 5 instances which would solve it but we probably won't catch all instances upfront and this issue will still be present;
    Thanks in advance for any assistance.

    Anyone?

  • Receipt of EBS multiple times in a day (Electronic Bank Statement)

    Hi Gurus,
    We had a requirement for receipt of Bank statement, in a single day we have to receive bank statement twice a day, but in both statements some transactions will be repeated.
    Now my question is once in the morning statement came, then postings will be made in the system based on the transaction information in the bank statement. Then later in the evening for the second bank statement if postings are to be made, then how system will respond to the already posted transactions, as some transactions in the statement will be repeated in the evening statement also.
    Please let me know how system will respond for this type of scenario or will there be not any problem?
    Thanks in advance
    regards
    srikanth.

    solved

  • Unable to clear sub-ledger items on uploading electronic bank statement

    Hi All,
    The client is in Belgium & uses format BE for bank statements. in postprocessing of EBS (FEBA), there are a few items with a posting rule 0002 (for Eg) that need to be posted manually. The posting rule is as below:
    0002   1  40   BE INTERIM                 50  BE BANK      ZR   1
    0002   2         BE OUTGOING BE      50  BE INTERIM   ZV   4
    As you can see the posting type is 1 & 4. The user's contention is that this should knock off items in sub-ledger i.e., vendor & customer open items but the system is posting to the GL accounts that are assigned to the account symbols shown above.
    My question is... Is it possible with such a posting rule to clear items in sub-ledger? If yes, is there any setting that needs to done to ensire that in FEBA, on manually trying to post the system should direct to the screen where you can enter the customer or vendor number & select open item?
    Thanks,
    Lakshmi

    I found the answer in Customizing new G/L. thanks anyway.
    Heiidi

  • Without a receipt, but with a bank statement, will I be able to get a free replacement on my broken iPod headphones, bought only two months ago?

    Hi,
    I bought a new pair of iPod headphones just over two months ago from an HMV store, and in the last few days, one of the headphones has stopped working altogether. Unfortunately, I no longer have the receipt for the headphones, but I do have the information booklet, the one year warranty statement and a bank statement showing the transaction of when I purchased the headphones. Am I still able to get a refund or replacement for my headphones, as the damage was not my fault, just a technical fault?
    Thanking you in advance,
    Natasha

    Am I still able to get a refund or replacement for my headphones, as the damage was not my fault, just a technical fault?
    Yes. Make a trip to your local Apple Store and show them what is going on. Since the headset is still under a year old, they should swap it out for you at no cost. Unless for some reason they deem the issue the result of misuse or abuse, but that doesn't sound like the case here.
    B-rock

  • How can i open a PDF bank statement in numbers so that the rows and columns contain properly aligned data from statement?

    how can i open a PDF bank statement in "numbers" so that the rows and columns contain properly aligned data from statement?

    Numbers can store pdfs pages or clippings but does not directly open pdf files.  To get the bank statement into Numbers as a table I would open the bank statment in Preview (or Skim) or some pdf viewer.
    Then hold the option key while selecting a column of data.
    Then copy
    Then switch to numbers and paste the column into a table
    Then repeat for the other columns in the pdf document
    It would be easier (in my opinion) to download the QFX or CSV version from your bank

  • FEBA :Banking: Red Cross on bank statement upload

    Hello Gurus,
    I am facing a strange behaviour in electronic bank statement uploads.
    The file is uploaded in the system and its shown as Red cross. There are no transactions in the bank statement and the opening and closing balances are same.
    There is no activity in the bank account and still on loading the satement it shows a Red Cross for file loaded on June 20th.
    The file coming on June23rd is loaded successfully and has a green checkbox where again there were no transactions and opening and closing balances are tallied.
    I dont see any value or sign difference. I checked other threads but couldnt get solution and had to open a new discussion
    Any thoughts on how we can change the red cross to Green Tick. SAP instance is on ECC 6.0.
    Any utility to be developed?
    Regards
    Rutvij

    Hello Rutvij,
    FEBAN - give Co.code, house bank, account id, statement date and statement nubmer.
    If it is outgoing payment then go to statement items i con in top side of that screen. Then click post option.
    In the next screen click on payment order because if you want to clear invoices based on payment orders or click either reference or document number in additional selections tab. And then give your co.code and account type. If required, put additional selection like amount, reference, etc in additonal selections tab.
    Press enter and then select open items to be cleared and then save.
    Now SAP will display all open invoices against the customers. Activate the invoices that must be cleared. Simulate document. Now enter the payment amount and press enter.
    Enter once again in the next screen then press save. Now you will get a message saying that document got posted with no.xxxx in co.code
    I hope it will resolve your issue else revert us with your query.
    Thanks & Regards,
    Lakshmi S

  • Reg:Document Type creation in Manual bank Statement.

    HI all,
    What is the document type for Manual bank statement reconsolation.
    I created (BZ )for Manual bank statement reconsolation which fields i have to  select.
    regards
    JK

    Hi,
    Document types are created at client level. to restrict one kind transactions only and to identify the transactions pertaining to what.
    At the time of configuring BRS we have to specify the document type there u can specify what ever you want before it has to create. go to OBA7
    Hope this is clear, if yes assign points
    Regards,
    Sankar

  • Manual bank statement: no batch input was generated

    Hi,
    maybe somebody has a clue with this problem regarding FF67: after the data processing, no batch input is generated in order to post the bank statement.
    Please, I need your help with an OSS note or with a posting solution without batch input ( I tried to process the bank statement with "processing type = 4", but it didn't work).

    Hi Andrea,
    Try to add value in <i>Session name for bank postings</i>
    Do not hesitate to ask for further clarifications. Award points if useful.
    Regards,
    Siva

  • Manual bank statement upload error FB727

    Hi Experts
    When we are uploading the manual bank statements using transaction FF67, we are getting the error message FB727 "There are no transactions that have this amount's plus or minus sign"
    We are using SAP version 4.7, I am not sure how this message is coming and how can we correct this
    I could see there is a OSS note for this but that is not applicable for version 4.7 and above
    Rishi

    Hi Rishi,
    Message - FB727 says There are no transactions that have this amount's plus or minus sign
    While assigning the Business transactions to posting rules you may specified the +/- symbol to Incoming payments. Similarly while entering the amounts use the symbols.
    Eg: If the amount CHQ deposit (Incoming Payment) : +XXXX
          If the amount CHQ Issue (Out Going Payment)  : - XXXX
          If the amount Bank Charge (Expense-Outgoing) : - XXXX
    Amount with Symbol if you enter, Then you will not get this error.

  • Manaul Bank Statement  - ff67

    Dear Experts,
    Please help me,  I did Manual Bank Statement (FF67)  cheque received and issued enteries are posted to main bank a/c but still that line items are still open item status,  i checked in fbl3n  cheque received and cheque issued a/c and main bank a/c.    In statement overview also i observed status it is displaing posted. 
    how to check,  where is the problem in my case
    Regards
    Chandu

    Dear Ravi,
    Thanks for your reply,   please calify me ,  
    onece if we do manual BRS in FF67 after that we need to do manual cleaing in f.13.
    automatically it will not come as a cleared (green clolour) Item ?
    Regards
    Chandu

Maybe you are looking for