Creating MIME for XML

I am reading XML tags from the Spool and converting that into a XML file and displaying in the screen.  But it is not displaying
I am using the following code for that.,
    p_regex = '.[^.]+$'.
    condense p_regex.
    create object regex
      exporting
        pattern     = p_regex
        ignore_case = ''.
* For REGEX match
    matcher = cl_abap_matcher=>create(
                   pattern     = p_regex
                   ignore_case = ' '
                   table       = i_files ).
    lt_result = matcher->find_all( ).
    find first occurrence of regex '.[^.]+$' in lt_result match offset v_offset.
    add 1 to v_offset.
    v_extension = v_filename+v_offset.
    call function 'SDOK_MIMETYPE_GET'
      exporting
        extension = v_extension
      importing
        mimetype  = v_mimetype.
    v_mime_string = v_mimetype.
    call method cl_wd_runtime_services=>attach_file_to_response
      exporting
        i_filename      = v_filename
        i_content       = v_xstring
        i_mime_type     = v_mime_string
        i_in_new_window = abap_true
        i_inplace       = abap_true.

hi check this example .......
Moises Moreno
PROGRAMA    : ZHR02597 Batch Input Datos Reloj Checador              *
                       leyendo un archivo XML                        *
AUTOR       : Moises Moreno De Leon (GALVAK)                         *
FECHA       : Junio 23, 2004                                         *
REPORT ZHR02597 MESSAGE-ID ZG LINE-SIZE  80 LINE-COUNT 65
                                               NO STANDARD PAGE HEADING.
Tablas                                                               *
TABLES:
       PA0000,         "HR Master Record: Infotype 0000 (Events)
       PA0001,         "HR Master Record: Infotype 0001 (Org. Assignment
       PA0007,         "HR Master Record: Infotype 0007 (Work Schedule)
       PA0008,         "HR Master Record: Infotype 0008 (Basic Pay)
       PA2003,         "HR Time Record: Infotype 2003 (Substitutions)
       T508A,          "Work Schedule Rules
       T552A,          "Monthly Work Schedules
       T550A,          "Daily Work Schedules
       ZCATEGORIA.     "Pay Scale Groups - Categorias
Fin de Tablas                                                        *
Estructura                                                           *
DATA: BEGIN OF BDC_TABLE OCCURS 100.   "Tabla para BIS
        INCLUDE STRUCTURE BDCDATA.
DATA: END OF BDC_TABLE.
DATA BEGIN OF TH_MESSTAB OCCURS 10.
        INCLUDE STRUCTURE BDCMSGCOLL.
DATA END OF TH_MESSTAB.
DATA: BEGIN OF TH_ARCHIVO OCCURS 100,
          NUMERO(8),                   "P2011-PERNR  Numero del empleado
          FECHA LIKE SY-DATUM,         "P2011-LDATE  Logical date
          AUSENTISMO(4),               "
          HORA(4),                     "P2011-LTIME  Logical time
          TERMINAL(3),                 "P2011-TERID  Terminal ID
          RAZON(4),                    "P2011-ABWGR  Att/absence reason
          TURNO(2),                    "PA2003-TPROG Daily work schedule
          DEPARTAMENTO(4),             "KOSTL        Cost center
          EMPLEADO2(8),                "PA2003-VPERN Personnel no.to be
          COORDINADOR_AUTORIZA(8),
          IN_OUT(2) TYPE N,
       END OF TH_ARCHIVO.
DATA: BEGIN OF TH_ERROR OCCURS 100,
          NUMERO(5),                   "P2011-PERNR  Numero del empleado
          FECHA LIKE SY-DATUM,         "P2011-LDATE  Logical date
          AUSENTISMO(4),
          HORA(4),                     "P2011-LTIME  Logical time
          TERMINAL(3),                 "P2011-TERID  Terminal ID
          RAZON(4),                    "P2011-ABWGR  Att/absence reason
          TURNO(2),                    "PA2003-TPROG Daily work schedule
          DEPARTAMENTO(4),             "KOSTL        Cost center
          EMPLEADO2(5),                "PA2003-VPERN Personnel no.to be
       END OF TH_ERROR.
TYPES: BEGIN OF REG,
          CAMBIO_TURNO,
          DIA(10),
          AUSENTISMO(4),
          TURNO(2),
          HORA(5),
          TIPO,
          INCIDENCIA(3),
          CCOSTOS(4),
          SOCIO_REEMPLAZA(8),
       END   OF REG.
DATA: REGISTRO TYPE REG OCCURS 0 WITH HEADER LINE.
TYPES: BEGIN OF EMPLEADO,
          NUMERO(8),
          REGISTRO LIKE REGISTRO OCCURS 0,
       END   OF EMPLEADO.
DATA: BEGIN OF CIERRE OCCURS 0,
         EMPLEADO TYPE EMPLEADO,
      END   OF CIERRE.
DATA: CHECADAS TYPE REG OCCURS 0 WITH HEADER LINE.
Fin de estrucutras                                                   *
Variables                                                            *
DATA: SW_ERROR,                          "Swich existencia de empleado
      SW_I2002(1) TYPE C VALUE 'F',
      WC_FECHA(10),                      "Fecha con formato dd.mm.aaaa
      WC_DIA(2),                         "Filtra el día de la fecha
      WC_MES(2),                         "Filtra el mes de la fecha
      WC_YEAR(4),                        "Filtra el año de la fecha
      WC_TIPO(2),                        "Tipo de Substitución
      WC_TPR00(4),                       "Turno del empleado
      WC_TURNO(4),                       "Turno del empleado GK(Turno)
      WC_TURNO_SUST(4),                  "Turno Sustitucion
      WC_TURNO_R(4),                     "Turno del RELOJ GK(Turno)
      WC_TURNO_S(4),                     "Turno del SAP   GK(Turno)
      WC_CATEGORIA(8),                   "Categoria del empleado
      WN_IN_OUT(2)  TYPE N,              "Tipo de evento IN/OUT
      WN_PERNR LIKE PA2003-PERNR,
      WI_BETRG1 LIKE ZCATEGORIA-BETRG,   "Cantidad por turno Emple. 1
      WI_BETRG2 LIKE ZCATEGORIA-BETRG,   "Cantidad por turno Emple. 2
      WT_TIEMPO LIKE P2011-LTIME,        "Hora de chacada
      WT_INICIO(4)   TYPE N,             "Hora de chacada I2002
      WT_FINAL(4)    TYPE N,             "Hora de chacada I2002
      WT_HORA   LIKE P2011-LTIME VALUE '120000',  "Sumar Doce horas
      ARCH1(40) TYPE C VALUE '/users/interf/datos/hr/errores.txt',
      WC_ARCHIVO(40) TYPE C,             "Nombre del archivo
      WI_LC     TYPE I VALUE 0,          "Contador lineas
      WD_FECHA_DESC    LIKE SY-DATUM,    "Fecha de Descanso
      WD_FECHA  LIKE SY-DATUM,
      WI_INDICE LIKE SY-TABIX,           "Indice de la tabla interna
      SW_DELETE(1) TYPE C VALUE 'F',
      WC_REGISTRO1(35) TYPE C,           "Registro de la tabla interna
      WC_REGISTRO2(35) TYPE C.           "Registro de la tabla interna
DATA: QID LIKE APQI-QID,
      B-NAME LIKE RFPDO-ALLGBINA,
      EXCEPT TYPE I.
DATA: ME TYPE REF TO CL_XML_DOCUMENT.
DATA: SUBRC LIKE SY-SUBRC.
DATA: GVK_MODE.
Fin de variables                                                     *
Parámetros de Selección                                              *
SELECTION-SCREEN BEGIN OF BLOCK BL_01 WITH FRAME TITLE TEXT-001.
   PARAMETERS: ARCHIVO TYPE RLGRAP-FILENAME.
SELECTION-SCREEN END OF BLOCK BL_01.
Fin de parametros de sleccion                                        *
AT SELECTION SCREEN                                                  *
AT SELECTION-SCREEN ON VALUE-REQUEST FOR ARCHIVO.
   PERFORM ESPECIFICA_RUTA USING '0'.
AT SELECTION SCREEN                                                  *
Start of selection                                                   *
START-OF-SELECTION.
   CLEAR GVK_MODE.
   GVK_MODE = 'N'.
   IF SY-UNAME0(6) NE 'GKRHUM' AND SY-UNAME0(6) NE 'GK_961' AND
      SY-UNAME+0(6) NE 'GKSIST' AND SY-UNAME      NE 'EXUANL_MML'.
      WRITE:/ 'Usuario no pertenece a GALVAK, S.A. de C.V.'.
      LEAVE PROGRAM.
   ENDIF.
   PERFORM LEE_ARCHIVO_XML.
   PERFORM LLENA_TH_ARCHIVO.
   SORT TH_ARCHIVO BY NUMERO FECHA HORA.
   PERFORM ELIMINA_DUPLICADOS.
   LOOP AT TH_ARCHIVO.
      PERFORM VALIDA_INFO.
      MOVE ' ' TO : WC_DIA,    WC_MES,   WC_YEAR,   WC_FECHA,
                    WC_TIPO,   WC_TPR00, WC_TURNO,  WC_CATEGORIA,
                    WT_TIEMPO, WN_PERNR, WN_IN_OUT, WT_INICIO,
                    WT_FINAL.
      MOVE 0 TO: WI_LC.
      IF SW_ERROR EQ '0'.
         SELECT *
           FROM PA0001
          WHERE PERNR = TH_ARCHIVO-NUMERO.
         ENDSELECT.
         IF SY-SUBRC EQ 0.
            IF TH_ARCHIVO-DEPARTAMENTO = PA0001-KOSTL+6(4).
               TH_ARCHIVO-DEPARTAMENTO = ' '.
            ENDIF.
         ENDIF.
         PERFORM FORMATO_FECHA.
         MOVE TH_ARCHIVO-HORA TO WT_TIEMPO.
         IF TH_ARCHIVO-EMPLEADO2 NE ' '.
            WN_PERNR = TH_ARCHIVO-EMPLEADO2.
         ELSE.
            WN_PERNR = TH_ARCHIVO-NUMERO.
         ENDIF.
         IF TH_ARCHIVO-AUSENTISMO = 'DESC'.
            CONCATENATE WD_FECHA6(2) '.' WD_FECHA4(2) '.' WD_FECHA(4)
                   INTO WC_FECHA.
            PERFORM DATOS_DESC.           "Actualiza 2003
         ELSE.
            PERFORM EVENTO_IN_OUT.
            CONCATENATE WD_FECHA6(2) '.' WD_FECHA4(2) '.' WD_FECHA(4)
                   INTO WC_FECHA.
            PERFORM TRANS_PA61.
            CALL TRANSACTION 'PA61' USING BDC_TABLE MODE GVK_MODE
                 UPDATE 'S' MESSAGES INTO TH_MESSTAB.
            IF SY-SUBRC EQ 0.
               IF WC_TURNO <> WC_TPR00      OR
                  WC_TURNO <> WC_TURNO_SUST OR
                  WC_TURNO = 'DESC'         OR
                  WC_TURNO = 'FREE'.
                  IF TH_ARCHIVO-IN_OUT = '01'.
                     PERFORM OTROS_DATOS.           "Actualiza 2003
                  ENDIF.
               ELSE.
               ENDIF.
            ELSE.
               MOVE-CORRESPONDING TH_ARCHIVO TO TH_ERROR.
               APPEND TH_ERROR.
            ENDIF.
         ENDIF.
      ENDIF.
   ENDLOOP.
   DESCRIBE TABLE TH_ERROR LINES WI_LC.
Fin de start of selection                                            *
End of selection                                                     *
END-OF-SELECTION.
   IF WI_LC NE 0.
      PERFORM ARCHIVO_ERROR.
   ENDIF.
   PERFORM BDC_CLOSE USING EXCEPT.
   MESSAGE I100.
  DELETE DATASET ARCHIVO.  "moises 02.06.1999
Fin de end of slection                                               *
Funcion  valida_info                                                 *
FORM VALIDA_INFO.
   MOVE '0' TO SW_ERROR.
   SELECT DISTINCT *
     FROM PA0000
    WHERE PERNR EQ TH_ARCHIVO-NUMERO.
      EXIT.
   ENDSELECT.
   IF SY-SUBRC NE 0.
      FORMAT INTENSIFIED OFF.
      WRITE:/ 'El empleado  ', TH_ARCHIVO-NUMERO,
              '  no esta dado de alta'.
      FORMAT INTENSIFIED ON.
      MOVE '1' TO SW_ERROR.
   ENDIF.
ENDFORM.
Fin de funcion valida_info                                           *
Funcion formato_fecha                                                *
FORM FORMATO_FECHA.
   WC_DIA  = TH_ARCHIVO-FECHA(2).
   WC_MES  = TH_ARCHIVO-FECHA+2(2).
   WC_YEAR = TH_ARCHIVO-FECHA+4(4).
   CONCATENATE WC_YEAR WC_MES WC_DIA INTO WD_FECHA.
ENDFORM.
Fin de funicon formato_fecha                                         *
Funcion evento_in_out                                                *
FORM EVENTO_IN_OUT.
   SELECT *
     FROM PA0007
    WHERE PERNR EQ WN_PERNR
      AND BEGDA <= WD_FECHA
      AND ENDDA >= WD_FECHA.
   ENDSELECT.
   IF SY-SUBRC EQ 0 AND PA0007-SCHKZ NE ' '.
      SELECT *
        FROM T508A
       WHERE MOFID EQ 'GK'
         AND SCHKZ = PA0007-SCHKZ.
      ENDSELECT.
      SELECT *
        FROM T552A
       WHERE SCHKZ EQ PA0007-SCHKZ
         AND   KJAHR EQ WC_YEAR
         AND   MONAT EQ WC_MES.
      ENDSELECT.
      IF SY-SUBRC EQ 0.
         PERFORM BUSCA_DIA.
         WC_TURNO = WC_TPR00.
         PERFORM VERIFICA_P2003.
         IF WC_TURNO_SUST IS INITIAL.
            WC_TURNO_SUST = WC_TURNO.
         ENDIF.
         IF WC_TURNO EQ 'FREE' OR WC_TURNO EQ 'DESC'.
            WC_TIPO = '02'.
            IF TH_ARCHIVO-RAZON NE 'ETI ' AND
               TH_ARCHIVO-RAZON NE 'EPM ' AND
               TH_ARCHIVO-RAZON NE 'ERP ' AND
               TH_ARCHIVO-RAZON NE 'STI ' AND
               TH_ARCHIVO-RAZON NE 'SPM ' AND
               TH_ARCHIVO-RAZON NE 'SRP '.
               PERFORM VALIDA_SIGUIENTE_DIA.
               IF WC_TPR00 = 'GM11' OR WC_TPR00 = 'GK01'.
                  WC_TURNO = WC_TPR00.
               ENDIF.
            ENDIF.
         ELSEIF WC_TPR00 = 'DESC' OR WC_TPR00 = 'FREE'.
            WC_TIPO = '02'.
         ELSE.
            WC_TIPO = '01'.
         ENDIF.
      ENDIF.
      PERFORM TIEMPOS_EXTRA.
      WC_TURNO_S = WC_TURNO.
      IF TH_ARCHIVO-TURNO NE ' '.
       IF TH_ARCHIVO-TURNO = 'S1' OR TH_ARCHIVO-TURNO = 'S2' OR
          TH_ARCHIVO-TURNO = 'S3'.
          CONCATENATE 'DE' TH_ARCHIVO-TURNO INTO WC_TURNO_R.
          WC_TURNO = WC_TURNO_R.
       ELSEIF TH_ARCHIVO-TURNO = 'T1' OR TH_ARCHIVO-TURNO = 'T2'.
          CONCATENATE 'GK' TH_ARCHIVO-TURNO INTO WC_TURNO_R.
          WC_TURNO = WC_TURNO_R.
       ELSE.
         IF TH_ARCHIVO-TURNO < 10.
            CONCATENATE 'GK' TH_ARCHIVO-TURNO INTO WC_TURNO_R.
         ELSEIF TH_ARCHIVO-TURNO > 10.
            CONCATENATE 'GM' TH_ARCHIVO-TURNO INTO WC_TURNO_R.
         ENDIF.
         IF WC_TURNO NE WC_TURNO_R. " and th_archivo-razon = ' '. moises
            WC_TURNO = WC_TURNO_R.
         ENDIF.
       ENDIF.
      ENDIF.
     IF WC_TURNO EQ 'GM11' OR WC_TURNO = 'GK01'.
        WT_TIEMPO = WT_TIEMPO + WT_HORA.
     ENDIF.
      SELECT *
        FROM T550A
       WHERE MOTPR EQ T508A-MOTPR
         AND TPROG EQ WC_TURNO.
         IF ( T550A-BTBEG <= WT_TIEMPO AND T550A-BTEND >= WT_TIEMPO ) OR
            ( TH_ARCHIVO-RAZON = 'IJ  ' OR TH_ARCHIVO-RAZON = 'II  '  OR
              TH_ARCHIVO-RAZON = 'ESU ' OR TH_ARCHIVO-RAZON = 'EPM '  OR
              TH_ARCHIVO-RAZON = 'ERP ' OR TH_ARCHIVO-RAZON = 'ETI ' ).
            WN_IN_OUT = '01'.
            IF WC_TURNO EQ 'GM11' OR WC_TURNO = 'GK01'.
              WD_FECHA = WD_FECHA + 1.
            ENDIF.
         ELSEIF ( T550A-ETBEG <= WT_TIEMPO AND
                  T550A-ETEND >= WT_TIEMPO ) OR
                ( TH_ARCHIVO-RAZON = 'FJ  '  OR
                  TH_ARCHIVO-RAZON = 'FI  '  OR
                  TH_ARCHIVO-RAZON = 'SSU '  OR
                  TH_ARCHIVO-RAZON = 'SPM '  OR
                  TH_ARCHIVO-RAZON = 'SRP '  OR
                  TH_ARCHIVO-RAZON = 'STI ' ).
            WN_IN_OUT = '02'.
         ELSE.
            WN_IN_OUT = '02'.
         ENDIF.
         IF TH_ARCHIVO-RAZON = 'ETI ' AND
          ( T550A-BTBEG <= WT_TIEMPO AND T550A-BTEND >= WT_TIEMPO ).
            WT_INICIO = WT_TIEMPO(4).
            WT_FINAL  = T550A-SOBEG(4).
            SW_I2002 = 'T'.
         ELSEIF TH_ARCHIVO-RAZON = 'STI ' AND
              ( T550A-ETBEG <= WT_TIEMPO AND T550A-ETEND >= WT_TIEMPO ).
            WT_INICIO = T550A-SOEND(4).
            WT_FINAL  = WT_TIEMPO(4).
            SW_I2002 = 'T'.
         ENDIF.
      ENDSELECT.
      IF SW_I2002 = 'T'.
         SW_I2002 = 'F'.
         CONCATENATE WD_FECHA6(2) '.' WD_FECHA4(2) '.' WD_FECHA(4)
                INTO WC_FECHA.
         PERFORM ALTA_I2002.
      ENDIF.
   ENDIF.
ENDFORM.
Fin de funcion evento_in_out                                         *
Funcion busca_dia                                                    *
FORM BUSCA_DIA.
   CASE WC_DIA.
      WHEN 01.
         MOVE T552A-TPR01 TO WC_TPR00.
      WHEN 02.
         MOVE T552A-TPR02 TO WC_TPR00.
      WHEN 03.
         MOVE T552A-TPR03 TO WC_TPR00.
      WHEN 04.
         MOVE T552A-TPR04 TO WC_TPR00.
      WHEN 05.
         MOVE T552A-TPR05 TO WC_TPR00.
      WHEN 06.
         MOVE T552A-TPR06 TO WC_TPR00.
      WHEN 07.
         MOVE T552A-TPR07 TO WC_TPR00.
      WHEN 08.
         MOVE T552A-TPR08 TO WC_TPR00.
      WHEN 09.
         MOVE T552A-TPR09 TO WC_TPR00.
      WHEN 10.
         MOVE T552A-TPR10 TO WC_TPR00.
      WHEN 11.
         MOVE T552A-TPR11 TO WC_TPR00.
      WHEN 12.
         MOVE T552A-TPR12 TO WC_TPR00.
      WHEN 13.
         MOVE T552A-TPR13 TO WC_TPR00.
      WHEN 14.
         MOVE T552A-TPR14 TO WC_TPR00.
      WHEN 15.
         MOVE T552A-TPR15 TO WC_TPR00.
      WHEN 16.
         MOVE T552A-TPR16 TO WC_TPR00.
      WHEN 17.
         MOVE T552A-TPR17 TO WC_TPR00.
      WHEN 18.
         MOVE T552A-TPR18 TO WC_TPR00.
      WHEN 19.
         MOVE T552A-TPR19 TO WC_TPR00.
      WHEN 20.
         MOVE T552A-TPR20 TO WC_TPR00.
      WHEN 21.
         MOVE T552A-TPR21 TO WC_TPR00.
      WHEN 22.
         MOVE T552A-TPR22 TO WC_TPR00.
      WHEN 23.
         MOVE T552A-TPR23 TO WC_TPR00.
      WHEN 24.
         MOVE T552A-TPR24 TO WC_TPR00.
      WHEN 25.
         MOVE T552A-TPR25 TO WC_TPR00.
      WHEN 26.
         MOVE T552A-TPR26 TO WC_TPR00.
      WHEN 27.
         MOVE T552A-TPR27 TO WC_TPR00.
      WHEN 28.
         MOVE T552A-TPR28 TO WC_TPR00.
      WHEN 29.
         MOVE T552A-TPR29 TO WC_TPR00.
      WHEN 30.
         MOVE T552A-TPR30 TO WC_TPR00.
      WHEN 31.
         MOVE T552A-TPR31 TO WC_TPR00.
   ENDCASE.
ENDFORM.
Fin de funcion busca_dia                                             *
Funcion verifica_p2003                                               *
FORM VERIFICA_P2003.
   DATA: WFECHA LIKE SY-DATUM.
   CONCATENATE TH_ARCHIVO-FECHA4(4) TH_ARCHIVO-FECHA2(2)
               TH_ARCHIVO-FECHA(2) INTO WFECHA.
   CLEAR WC_TURNO_SUST.
   SELECT SINGLE *
     FROM PA2003
    WHERE PERNR = WN_PERNR
      AND BEGDA <= WFECHA
      AND ENDDA >= WFECHA.
   CHECK  SY-SUBRC EQ 0.
   IF PA2003-TPROG NE ' ' AND PA2003-TPROG NE WC_TURNO.
      MOVE PA2003-TPROG TO: WC_TURNO, WC_TURNO_SUST.
   ELSEIF PA2003-SCHKZ NE ' '.
      SELECT *
        FROM T552A
       WHERE SCHKZ EQ PA2003-SCHKZ
         AND KJAHR EQ WC_YEAR
         AND MONAT EQ WC_MES.
      ENDSELECT.
      IF SY-SUBRC EQ 0.
         PERFORM BUSCA_DIA.
         IF WC_TPR00 NE WC_TURNO.
            WC_TURNO = WC_TPR00.
         ENDIF.
      ENDIF.
   ENDIF.
ENDFORM.                    " VERIFICA_P2003
Fin de funcion verifica_p2003                                        *
Funion valida_siguiente_dia                                          *
FORM VALIDA_SIGUIENTE_DIA.
   WD_FECHA_DESC = WD_FECHA + 1.
   WC_DIA = WD_FECHA_DESC+6(2).
   SELECT *
     FROM T552A
    WHERE SCHKZ EQ PA0007-SCHKZ
      AND KJAHR EQ WC_YEAR
      AND MONAT EQ WC_MES.
   ENDSELECT.
   IF SY-SUBRC EQ 0.
      PERFORM BUSCA_DIA.
   ENDIF.
ENDFORM.                    " VALIDA_SIGUIENTE_DIA
Fin de funcion valida_siguiente_dia                                  *
Funcion alta_i2002                                                   *
FORM ALTA_I2002.
   IF TH_ARCHIVO-TURNO = 'S1' OR TH_ARCHIVO-TURNO = 'S2' OR
      TH_ARCHIVO-TURNO = 'S3'.
   ELSE.
      REFRESH BDC_TABLE.
      PERFORM DYNPRO_START USING 'SAPMP50A' '1000'.
      PERFORM DYNPRO_FIELD USING 'RP50G-PERNR' TH_ARCHIVO-NUMERO.
      PERFORM DYNPRO_FIELD USING 'RP50G-CHOIC' '2002'.
      PERFORM DYNPRO_FIELD USING 'RP50G-SUBTY' '0020'.
      PERFORM DYNPRO_FIELD USING 'BDC_OKCODE' '=INS'. "MML QA&C 08.02.00
      PERFORM DYNPRO_START USING 'MP200000' '2050'.
      PERFORM DYNPRO_FIELD USING 'P2002-BEGDA' WC_FECHA.
      PERFORM DYNPRO_FIELD USING 'P2002-ENDDA' WC_FECHA.
      PERFORM DYNPRO_FIELD USING 'P2002-BEGUZ' WT_INICIO.
      PERFORM DYNPRO_FIELD USING 'P2002-ENDUZ' WT_FINAL.
      PERFORM DYNPRO_FIELD USING 'BDC_OKCODE' '=UPD'. "MML QA&C 08.02.00
      CALL TRANSACTION 'PA61' USING BDC_TABLE MODE GVK_MODE UPDATE 'S'
                                           MESSAGES INTO TH_MESSTAB.
      IF SY-SUBRC NE 0.
         MOVE-CORRESPONDING TH_ARCHIVO TO TH_ERROR.
         APPEND TH_ERROR.
      ENDIF.
   ENDIF.
ENDFORM.                    " ALTA_I2002
Fin de funcion alta_i2002                                            *
Funcion trnas_pa61                                                   *
FORM TRANS_PA61.
   REFRESH BDC_TABLE.
   IF TH_ARCHIVO-AUSENTISMO IS INITIAL.
      PERFORM DYNPRO_START USING 'SAPMP50A' '1000'.
      PERFORM DYNPRO_FIELD USING 'RP50G-PERNR' TH_ARCHIVO-NUMERO.
      PERFORM DYNPRO_FIELD USING 'RP50G-CHOIC' '2011'.
      PERFORM DYNPRO_FIELD USING 'BDC_OKCODE' '=INS'. "MML QA&C 20.08.00
      PERFORM DYNPRO_START USING 'MP200000' '2500'.
      PERFORM DYNPRO_FIELD USING 'P2011-LDATE' WC_FECHA.
      PERFORM DYNPRO_FIELD USING 'P2011-LTIME' WT_TIEMPO.
     PERFORM DYNPRO_FIELD USING 'P2011-SATZA' WN_IN_OUT.
      PERFORM DYNPRO_FIELD USING 'P2011-SATZA' TH_ARCHIVO-IN_OUT.
      IF TH_ARCHIVO-RAZON <> 'ARR'.
         PERFORM DYNPRO_FIELD USING 'P2011-ABWGR' TH_ARCHIVO-RAZON.
      ENDIF.
      PERFORM DYNPRO_FIELD USING 'P2011-TERID' TH_ARCHIVO-TERMINAL.
      PERFORM DYNPRO_FIELD USING 'BDC_OKCODE' '=UPD'. "MML QA&C 08.02.00
   ELSE.
      PERFORM DYNPRO_START USING 'SAPMP50A' '1000'.
      PERFORM DYNPRO_FIELD USING 'RP50G-PERNR' TH_ARCHIVO-NUMERO.
      PERFORM DYNPRO_FIELD USING 'RP50G-ENDDA' WC_FECHA.
      PERFORM DYNPRO_FIELD USING 'RP50G-CHOIC' '2001'.
      PERFORM DYNPRO_FIELD USING 'RP50G-SUBTY' TH_ARCHIVO-AUSENTISMO..
      PERFORM DYNPRO_FIELD USING 'BDC_OKCODE' '=INS'. "MML QA&C 20.08.00
      PERFORM DYNPRO_START USING 'MP200000' '2001'.
      PERFORM DYNPRO_FIELD USING 'P2001-BEGDA' WC_FECHA.
      PERFORM DYNPRO_FIELD USING 'P2001-ENDDA' WC_FECHA.
      PERFORM DYNPRO_FIELD USING 'BDC_OKCODE' '=UPD'. "MML QA&C 08.02.00
   ENDIF.
ENDFORM.                    " TRANS_PA61
Fin de funcion trans_pa61                                            *
Funcion otros_datos                                                  *
FORM OTROS_DATOS.
   IF WC_TURNO_SUST = 'DESC' OR WC_TURNO_SUST = 'FREE'.
      PERFORM ELIMINA_SUSTITUCION.
   ENDIF.
   IF TH_ARCHIVO-TURNO = 'S1' OR TH_ARCHIVO-TURNO = 'S2' OR
      TH_ARCHIVO-TURNO = 'S3'.
      PERFORM GENERA_SUSTITUCION_S.
      CALL TRANSACTION 'PA61' USING BDC_TABLE MODE GVK_MODE
           UPDATE 'S' MESSAGES INTO TH_MESSTAB.
      IF SY-SUBRC NE 0.
         MOVE-CORRESPONDING TH_ARCHIVO TO TH_ERROR.
         APPEND TH_ERROR.
      ENDIF.
   ELSE.
      IF WN_IN_OUT = '01'. "or wn_in_out = '02'.
         PERFORM GENERATE_BDC_DATA_1.                 "Actualiza 2003
         CALL TRANSACTION 'PA61' USING BDC_TABLE MODE GVK_MODE
              UPDATE 'S' MESSAGES INTO TH_MESSTAB.
         IF SY-SUBRC NE 0.
            MOVE-CORRESPONDING TH_ARCHIVO TO TH_ERROR.
            APPEND TH_ERROR.
         ENDIF.
      ENDIF.
      IF WN_IN_OUT = '02'.
        IF TH_ARCHIVO-RAZON = 'SSU'.
            PERFORM GENERATE_BDC_DATA_1.
            CALL TRANSACTION 'PA61' USING BDC_TABLE MODE GVK_MODE
                 UPDATE 'S' MESSAGES INTO TH_MESSTAB.
            IF SY-SUBRC NE 0.
               MOVE-CORRESPONDING TH_ARCHIVO TO TH_ERROR.
               APPEND TH_ERROR.
            ENDIF.
        ELSE.
            PERFORM GENERATE_BDC_DATA_1.
            CALL TRANSACTION 'PA61' USING BDC_TABLE MODE GVK_MODE
                 UPDATE 'S' MESSAGES INTO TH_MESSTAB.
            IF SY-SUBRC NE 0.
               MOVE-CORRESPONDING TH_ARCHIVO TO TH_ERROR.
               APPEND TH_ERROR.
            ENDIF.
        ENDIF.
      ENDIF.
   ENDIF.
ENDFORM.                    " OTROS_DATOS
Fin de funicion ortors_datos                                         *
Funcion generate_bdc_data_1                                          *
FORM GENERATE_BDC_DATA_1.
   REFRESH BDC_TABLE.
   PERFORM DYNPRO_START USING 'SAPMP50A' '1000'.
   PERFORM DYNPRO_FIELD USING 'RP50G-PERNR' TH_ARCHIVO-NUMERO.
   PERFORM DYNPRO_FIELD USING 'RP50G-CHOIC' '2003'.
   PERFORM DYNPRO_FIELD USING 'BDC_OKCODE' '=INS'. "MML QA&C 08.02.00
   PERFORM DYNPRO_START USING 'MP200000' '2100'.
   PERFORM DYNPRO_FIELD USING 'P2003-BEGDA' WC_FECHA.
   PERFORM DYNPRO_FIELD USING 'P2003-ENDDA' WC_FECHA.
   PERFORM DYNPRO_FIELD USING 'P2003-VTART' WC_TIPO.
   IF TH_ARCHIVO-EMPLEADO2 NE ' '  AND
      TH_ARCHIVO-EMPLEADO2 NE TH_ARCHIVO-NUMERO.
      PERFORM BUSCA_CATEGORIA.
   ENDIF.
   IF WC_TURNO <> WC_TURNO_SUST.
      PERFORM DYNPRO_FIELD USING 'P2003-TPROG' WC_TURNO.
   ELSE.
      IF TH_ARCHIVO-TURNO NE ' ' AND TH_ARCHIVO-TURNO NE WC_TURNO_S.
         PERFORM DYNPRO_FIELD USING 'P2003-TPROG' WC_TURNO.
      ENDIF.
      IF WC_TURNO <> WC_TPR00.
         PERFORM DYNPRO_FIELD USING 'P2003-TPROG' WC_TURNO.
      ENDIF.
   ENDIF.
   IF WI_BETRG1 < WI_BETRG2.           "Cambia categoria del Empleado 1
      PERFORM BUSCA_CATEGORIA.
      PERFORM DYNPRO_FIELD USING 'BDC_OKCODE' 'DIFP'.
      PERFORM DYNPRO_START USING 'MP200000' '2221'.
      PERFORM DYNPRO_FIELD USING 'P2APL-TRFGR' WC_CATEGORIA.
      PERFORM DYNPRO_FIELD USING 'BDC_OKCODE' '/8'.
      PERFORM DYNPRO_START USING 'MP200000' '2100'.
   ENDIF.
   IF TH_ARCHIVO-DEPARTAMENTO NE ' '.
      PERFORM DYNPRO_FIELD USING 'BDC_OKCODE' 'PRIM'.
      PERFORM DYNPRO_START USING 'SAPLHRTV' '0300'.
      PERFORM DYNPRO_FIELD USING 'COBL-KOSTL' TH_ARCHIVO-DEPARTAMENTO.
      PERFORM DYNPRO_FIELD USING 'BDC_OKCODE' '/8'.
      PERFORM DYNPRO_START USING 'MP200000' '2100'.
   ENDIF.
   PERFORM DYNPRO_FIELD USING 'BDC_OKCODE' '=UPD'. "MML QA&C 08.02.00
ENDFORM.                    " GENERATE_BDC_DATA_1
Fin de funcion generate_bdc_data_1                                   *
Funcion busca_categoria                                              *
FORM BUSCA_CATEGORIA.
   SELECT *
     FROM PA0008
    WHERE PERNR EQ TH_ARCHIVO-NUMERO.    "Empleado 1
      IF SY-SUBRC EQ 0.
         SELECT *
           FROM ZCATEGORIA
          WHERE TRFGR EQ PA0008-TRFGR.
            WI_BETRG1    = ZCATEGORIA-BETRG.
         ENDSELECT.
      ENDIF.
   ENDSELECT.
   SELECT *
     FROM PA0008
    WHERE PERNR EQ TH_ARCHIVO-EMPLEADO2. "Empleado 2
      IF SY-SUBRC EQ 0.
         SELECT *
           FROM ZCATEGORIA
          WHERE TRFGR EQ PA0008-TRFGR.
            WI_BETRG2 = ZCATEGORIA-BETRG.
            WC_CATEGORIA = ZCATEGORIA-TRFGR.
         ENDSELECT.
      ENDIF.
   ENDSELECT.
ENDFORM.
Fin de funcin busca_categoria                                        *
Fucion archivo_error                                                 *
FORM ARCHIVO_ERROR.
   OPEN DATASET ARCH1 FOR OUTPUT IN TEXT MODE.
   IF SY-SUBRC NE 0.
      STOP. EXIT.
   ENDIF.
   LOOP AT TH_ERROR.
      TRANSFER TH_ERROR TO ARCH1.
   ENDLOOP.
   CLOSE DATASET ARCH1.
ENDFORM.
Fin de archivo_error                                                 *
Funcion bdc_close                                                    *
FORM BDC_CLOSE USING EXCEPT.
   CALL FUNCTION 'BDC_CLOSE_GROUP'
      EXCEPTIONS
         NOT_OPEN    = 1
         QUEUE_ERROR = 2
         OTHERS      = 3.
         EXCEPT = SY-SUBRC.
ENDFORM.
Fin de funicon bdc_close                                             *
Funcion dynpro_start                                                 *
FORM DYNPRO_START USING PROGRAM DYNPRO.
   CLEAR BDC_TABLE.
   BDC_TABLE-PROGRAM = PROGRAM.
   BDC_TABLE-DYNPRO = DYNPRO.
   BDC_TABLE-DYNBEGIN = 'X'.
   APPEND BDC_TABLE.
ENDFORM.                    " DYNPRO_START
Fin de funcion dynpro_start                                          *
Funion dynpro_field                                                  *
FORM DYNPRO_FIELD USING FIELD VALUE.
   CLEAR BDC_TABLE.
   BDC_TABLE-FNAM = FIELD.
   BDC_TABLE-FVAL = VALUE.
   APPEND BDC_TABLE.
ENDFORM.                    " DYNPRO_FIELD
Fin de funcion dypro_field                                           *
Fucnion tiempos_extra                                                *
FORM TIEMPOS_EXTRA.
   IF TH_ARCHIVO-TURNO = 'S1' OR TH_ARCHIVO-TURNO = 'S2' OR
      TH_ARCHIVO-TURNO = 'S3'.
      CONCATENATE 'DE' TH_ARCHIVO-TURNO INTO WC_TURNO_R.
      WC_TURNO = WC_TURNO_R.
   ELSEIF TH_ARCHIVO-TURNO = 'T1' OR TH_ARCHIVO-TURNO = 'T2'.
     CONCATENATE 'GK' TH_ARCHIVO-TURNO INTO WC_TURNO_R.
     WC_TURNO = WC_TURNO_R.
   ELSE.
      IF ( TH_ARCHIVO-RAZON = 'ETI ' OR TH_ARCHIVO-RAZON = 'EPM ' OR
           TH_ARCHIVO-RAZON = 'ERP ' ) AND TH_ARCHIVO-TURNO NE ' '.
         IF TH_ARCHIVO-TURNO < 10.
            CONCATENATE 'GK' TH_ARCHIVO-TURNO INTO WC_TURNO_R.
         ELSEIF TH_ARCHIVO-TURNO > 10.
            CONCATENATE 'GM' TH_ARCHIVO-TURNO INTO WC_TURNO_R.
         ENDIF.
         IF ( WC_TURNO = 'FREE' OR WC_TURNO = 'DESC' ).
            IF WC_TURNO_R = 'GM13' OR WC_TURNO_R = 'GK03'.
               PERFORM VALIDA_SIGUIENTE_DIA.
               IF WC_TPR00 = 'GM11' OR WC_TPR00 = 'GK01'.
                  IF WC_TPR00 = 'GK01'.
                     WC_TURNO = 'GK01'.
                  ELSEIF WC_TPR00 = 'GM11'.
                     WC_TURNO = 'GM11'.
                  ENDIF.
               ELSE.
                  WC_TURNO = WC_TURNO_R.
               ENDIF.
            ELSE.
               WC_TURNO = WC_TURNO_R.
            ENDIF.
         ENDIF.
         IF ( WC_TURNO NE 'FREE' OR WC_TURNO NE 'DESC' ).
            IF WC_TURNO_R = 'GK02' AND WC_TURNO = 'GK03'.
               WC_TURNO = 'GK03'.
            ENDIF.
            IF WC_TURNO_R = 'GK03' AND WC_TURNO = 'GK01'.
               WC_TURNO = 'GK01'.
            ENDIF.
            IF WC_TURNO_R = 'GK01' AND WC_TURNO = 'GK02'.
               WC_TURNO = 'GK02'.
            ENDIF.
         ENDIF.
      ENDIF.
      IF ( TH_ARCHIVO-RAZON = 'STI ' OR TH_ARCHIVO-RAZON = 'SPM ' OR
           TH_ARCHIVO-RAZON = 'SRP ' ) AND TH_ARCHIVO-TURNO NE ' '.
         IF TH_ARCHIVO-TURNO < 10.
            CONCATENATE 'GK' TH_ARCHIVO-TURNO INTO WC_TURNO_R.
         ELSEIF TH_ARCHIVO-TURNO > 10.
            CONCATENATE 'GM' TH_ARCHIVO-TURNO INTO WC_TURNO_R.
         ENDIF.
         IF ( WC_TURNO = 'FREE' OR WC_TURNO = 'DESC' ).
            IF WC_TURNO_R = 'GM11' OR WC_TURNO_R = 'GK01'.
               WD_FECHA_DESC = WD_FECHA - 2.
               PERFORM VALIDA_SIGUIENTE_DIA. "En realidad DIA ANTERIOR
               IF WC_TPR00 = 'GM13' OR WC_TPR00 = 'GK03'.
                  IF WC_TPR00 = 'GK03'.
                     WC_TURNO = 'GK03'.
                  ELSEIF WC_TPR00 = 'GM13'.
                     WC_TURNO = 'GM13'.
                  ENDIF.
               ELSE.
                  WC_TURNO = WC_TURNO_R.
               ENDIF.
            ELSE.
               WC_TURNO = WC_TURNO_R.
            ENDIF.
         ENDIF.
         IF ( WC_TURNO NE 'FREE' OR WC_TURNO NE 'DESC' ).
            IF WC_TURNO_R = 'GK03' AND WC_TURNO = 'GK02'.
               WC_TURNO = 'GK02'.
            ENDIF.
            IF WC_TURNO_R = 'GK01' AND WC_TURNO = 'GK03'.
               WC_TURNO = 'GK03'.
           ENDIF.
            IF WC_TURNO_R = 'GK02' AND WC_TURNO = 'GK01'.
               WC_TURNO = 'GK01'.
            ENDIF.
         ENDIF.
      ENDIF.
   ENDIF.
ENDFORM.
Fin de funicon tiempos_extra                                         *
Funcion elimina_duplicados                                           *
FORM ELIMINA_DUPLICADOS.
   DELETE ADJACENT DUPLICATES FROM TH_ARCHIVO.
ENDFORM.
Fin de funcion elimina_duplicados                                    *
Form  LEE_ARCHIVO_XML                                                *
FORM LEE_ARCHIVO_XML.
   CREATE OBJECT ME.
   REFRESH CIERRE.
   CALL METHOD ME->CREATE_WITH_FILE
      EXPORTING
         FILENAME = ARCHIVO
      RECEIVING
         RETCODE  = SUBRC.
   CALL METHOD ME->GET_DATA
      IMPORTING
         RETCODE    = SUBRC
      CHANGING
         DATAOBJECT = CIERRE[].
ENDFORM.
Form  LEE_ARCHIVO_XML                                                *
FORM ESPECIFICA_RUTA                                                 *
FORM ESPECIFICA_RUTA USING PAR_VALOR.
   CASE PAR_VALOR.
      WHEN '0'.
         CALL FUNCTION 'KD_GET_FILENAME_ON_F4'
            EXPORTING
            MASK       = 'C:*.xml'
            STATIC     = 'X'
         CHANGING
            FILE_NAME  = ARCHIVO.
      WHEN '1'.
        CALL FUNCTION 'KD_GET_FILENAME_ON_F4'
           EXPORTING
           MASK       = 'C:*.txt'
           STATIC     = 'x'
        CHANGING
           FILE_NAME  = DESCARGA.
   ENDCASE.
ENDFORM.
FORM ESPECIFICA_RUTA                                                 *
Form  LLENA_TH_ARCHIVO                                               *
FORM LLENA_TH_ARCHIVO.
   CONSTANTS GVK_12HRS LIKE P2011-LTIME VALUE '120000'.
   CONSTANTS GVK_1159  LIKE P2011-LTIME VALUE '115900'.
   CONSTANTS GVK_0630  LIKE P2011-LTIME VALUE '063000'.
   CONSTANTS GVK_0715  LIKE P2011-LTIME VALUE '071500'.
   CONSTANTS GVK_1830  LIKE P2011-LTIME VALUE '183000'.
   CONSTANTS GVK_1915  LIKE P2011-LTIME VALUE '191500'.
   DATA:     GVK_HORA  LIKE P2011-LTIME.
   DATA:     GVK_FECHA LIKE SY-DATUM.
   CLEAR CIERRE.
   REFRESH TH_ARCHIVO.
   LOOP AT CIERRE.
      CLEAR TH_ARCHIVO.
      CHECADAS[] = CIERRE-EMPLEADO-REGISTRO[].
      LOOP AT CHECADAS.
         CLEAR TH_ARCHIVO.
         MOVE: CIERRE-EMPLEADO-NUMERO   TO TH_ARCHIVO-NUMERO,
               CHECADAS-INCIDENCIA      TO TH_ARCHIVO-RAZON,
               CHECADAS-CCOSTOS         TO TH_ARCHIVO-DEPARTAMENTO,
               CHECADAS-SOCIO_REEMPLAZA TO TH_ARCHIVO-EMPLEADO2.
         CONCATENATE CHECADAS-DIA(2)   CHECADAS-DIA+3(2)
                     CHECADAS-DIA+6(4) INTO TH_ARCHIVO-FECHA.
         CONCATENATE CHECADAS-HORA(2) CHECADAS-HORA+3(2)
                INTO TH_ARCHIVO-HORA.
         IF CHECADAS-TURNO = 'S1' OR CHECADAS-TURNO = 'S2' OR
            CHECADAS-TURNO = 'S3'.
            MOVE CHECADAS-TURNO TO TH_ARCHIVO-TURNO.
            IF CHECADAS-TIPO = 'E'.
               MOVE 'ETI' TO TH_ARCHIVO-RAZON.
            ELSEIF CHECADAS-TIPO = 'S'.
               MOVE 'STI' TO TH_ARCHIVO-RAZON.
            ENDIF.
         ELSE.
            MOVE CHECADAS-TURNO TO TH_ARCHIVO-TURNO.
         ENDIF.
         IF CHECADAS-CAMBIO_TURNO = 1.
            MOVE CHECADAS-TURNO TO TH_ARCHIVO-TURNO.
         ENDIF.
         MOVE CHECADAS-AUSENTISMO TO TH_ARCHIVO-AUSENTISMO.
         CASE CHECADAS-TURNO.
            WHEN '01' OR 'S1'.
               IF CHECADAS-TIPO = 'E'.
                  CLEAR GVK_FECHA.
                  CONCATENATE CHECADAS-DIA6(4) CHECADAS-DIA3(2)
                              CHECADAS-DIA(2)
                         INTO GVK_FECHA.
                  GVK_FECHA = GVK_FECHA + 1.
                  CONCATENATE GVK_FECHA6(2) GVK_FECHA4(2) GVK_FECHA(4)
                         INTO TH_ARCHIVO-FECHA.
               ELSEIF CHECADAS-TIPO = 'S'.
                  GVK_HORA = TH_ARCHIVO-HORA.
                  IF GVK_HORA > GVK_1159.
                    CLEAR GVK_FECHA.
                    CONCATENATE CHECADAS-DIA6(4) CHECADAS-DIA3(2)
                                CHECADAS-DIA(2)
                           INTO GVK_FECHA.
                    GVK_FECHA = GVK_FECHA + 1.
                    CONCATENATE GVK_FECHA6(2) GVK_FECHA4(2)
                                GVK_FECHA(4)
                           INTO TH_ARCHIVO-FECHA.
                  ENDIF.
               ENDIF.
               CLEAR GVK_HORA.
               GVK_HORA = TH_ARCHIVO-HORA.
               GVK_HORA = GVK_HORA + GVK_12HRS.
               CLEAR TH_ARCHIVO-HORA.
               CONCATENATE GVK_HORA(2) GVK_HORA+2(2)
                      INTO TH_ARCHIVO-HORA.
            WHEN 'T1'.
               IF CHECADAS-TIPO = 'E'.
                  CLEAR GVK_FECHA.
                  CLEAR GVK_HORA.
                  CONCATENATE CHECADAS-DIA6(4) CHECADAS-DIA3(2)
                              CHECADAS-DIA(2)
                         INTO GVK_FECHA.
                  GVK_FECHA = GVK_FECHA + 1.
                  CONCATENATE GVK_FECHA6(2) GVK_FECHA4(2) GVK_FECHA(4)
                         INTO TH_ARCHIVO-FECHA.
                  GVK_HORA = TH_ARCHIVO-HORA.
                  GVK_HORA = GVK_HORA + GVK_12HRS.
                  CLEAR TH_ARCHIVO-HORA.
                  CONCATENATE GVK_HORA(2) GVK_HORA+2(2)
                         INTO TH_ARCHIVO-HORA.
               ELSEIF CHECADAS-TIPO = 'S'.
                  MOVE 'STI' TO TH_ARCHIVO-RAZON.
                  GVK_HORA = TH_ARCHIVO-HORA.
                  IF GVK_HORA > GVK_1159.
                    CLEAR GVK_FECHA.
                    CONCATENATE CHECADAS-DIA6(4) CHECADAS-DIA3(2)
                                CHECADAS-DIA(2)
                           INTO GVK_FECHA.
                    GVK_FECHA = GVK_FECHA + 1.
                    CONCATENATE GVK_FECHA6(2) GVK_FECHA4(2)
                                GVK_FECHA(4)
                           INTO TH_ARCHIVO-FECHA.
                  ENDIF.
                  GVK_HORA = TH_ARCHIVO-HORA.
                  IF GVK_HORA BETWEEN GVK_0630 AND GVK_0715.
                     GVK_HORA = GVK_0630.
                  ENDIF.
                  GVK_HORA = GVK_HORA + GVK_12HRS.
                  CLEAR TH_ARCHIVO-HORA.
                  CONCATENATE GVK_HORA(2) GVK_HORA+2(2)
                         INTO TH_ARCHIVO-HORA.
               ENDIF.
            WHEN 'T2'.
               IF CHECADAS-TIPO = 'S'.
                  MOVE 'STI' TO TH_ARCHIVO-RAZON.
                  CLEAR GVK_HORA.
                  GVK_HORA = TH_ARCHIVO-HORA.
                  IF GVK_HORA BETWEEN GVK_1830 AND GVK_1915.
                     GVK_HORA = GVK_1830.
                     CONCATENATE GVK_HORA(2) GVK_HORA+2(2)
                            INTO TH_ARCHIVO-HORA.
                  ENDIF.
               ENDIF.
         ENDCASE.
         IF CHECADAS-TIPO = 'E'.
            TH_ARCHIVO-IN_OUT = '01'.
         ELSEIF CHECADAS-TIPO = 'S'.
            TH_ARCHIVO-IN_OUT = '02'.
         ENDIF.
         APPEND TH_ARCHIVO.
      ENDLOOP.
   ENDLOOP.
ENDFORM.
Form  LLENA_TH_ARCHIVO                                               *
*&      Form  DATOS_DESC
      text
-->  p1        text
<--  p2        text
FORM DATOS_DESC.
   REFRESH BDC_TABLE.
   PERFORM DYNPRO_START USING 'SAPMP50A' '1000'.
   PERFORM DYNPRO_FIELD USING 'RP50G-PERNR' TH_ARCHIVO-NUMERO.
   PERFORM DYNPRO_FIELD USING 'RP50G-CHOIC' '2003'.
   PERFORM DYNPRO_FIELD USING 'BDC_OKCODE' '=INS'. "MML QA&C 08.02.00
   PERFORM DYNPRO_START USING 'MP200000' '2100'.
   PERFORM DYNPRO_FIELD USING 'P2003-BEGDA' WC_FECHA.
   PERFORM DYNPRO_FIELD USING 'P2003-ENDDA' WC_FECHA.
   PERFORM DYNPRO_FIELD USING 'P2003-VTART' '01'.
   PERFORM DYNPRO_FIELD USING 'P2003-TPROG' 'DESC'.
   PERFORM DYNPRO_FIELD USING 'BDC_OKCODE' '=UPD'. "MML QA&C 08.02.00
   CALL TRANSACTION 'PA61' USING BDC_TABLE MODE GVK_MODE UPDATE 'S'
                                        MESSAGES INTO TH_MESSTAB.
   IF SY-SUBRC NE 0.
      MOVE-CORRESPONDING TH_ARCHIVO TO TH_ERROR.
      APPEND TH_ERROR.

Similar Messages

  • How to create table for XML schema-based Interface form

    Hi All,
    With tcode SFP to crate  a XML schema-based Interface form, how to create a defined table can be listed in "Data View"?
    Just like APAP Dictonary- Based Interface form, that we can drag  a defined table from data view to the panel.

    Hi,
    Just follow these steps:
    1. Create interactive form UI element in your view.
    2. Now provide Datasource and PDFSOURCE to it in form properties.
    3. Now give a template name prefix with 'Z' or 'Y'.
    4. Double click on it. It will prompt for interface name.
    5. Provide interface name prefixed with 'Z' or 'Y'.
    6. Click on Context button in the Pop up window and provide the node you have selected as DATASOURCE.
    7. Click ok and it will open the form designer.
    8. In this way you can create a XML Schema based Form.
    9. Activate the interface and design the form providing layout type and other details.
    Hope it will help.
    Regards,
    Vaibhav

  • Metadata for XML

    Hi,
    I need little help, where do I create metadata for XML forms? Can I access them from form builder (EP7)?
    Thanks a lot,
    Jai
    Message was edited by: Jai Paul

    Hi,
       You should read about:
    Advanced concepts in Metadata properties in km.pdf you can find in:
    https://www.sdn.sap.com/irj/servlet/prt/portal/prtroot/docs/library/uuid/de31ec90-0201-0010-be95-f501d25027a8
    How to create xml form.
    https://www.sdn.sap.com/irj/servlet/prt/portal/prtroot/docs/library/uuid/ee639033-0801-0010-0883-b2c76b18583a
    Properties of XML Documents
    http://help.sap.com/saphelp_nw2004s/helpdata/en/f4/9d1f39a27d0e4f8a69c891dc4a4a05/frameset.htm
    Predefined Properties
    http://help.sap.com/saphelp_nw2004s/helpdata/en/1a/9a4a3b80f2ec40aa7456bc87a94259/frameset.htm
    Repository Services
    http://help.sap.com/saphelp_nw2004s/helpdata/en/69/d96b86a84611d5993600508b6b8b11/frameset.htm
    Patricio.

  • Problem in creating a build.xml for weblogic portal application

    Team ,
    I am facing problem in creating the build.xml using weblogic.BuildXMLGEN tool .
    a) Below is the structure of my portal application
    SrcCode
    --- .metadata (eclipse plugins folder)
    --- B2BApp ( Ear Content)
    --- b2bPortal ( portal related file(controllers,jsp)
    --- b2bsrc     (java src)
    b) Now I executed below utility to generate the build.xml "
    java weblogic.BuildXMLGen -projectName B2BApp -username weblogic -file build.xml -password welcome1 F:\srcCode"
    c) Based on the above step , build.xml got generated .
    d) when I execute "ant compile" target from the command prompt , I see the below exception
    ant compile
    Buildfile: build.xml
    compile:
    +[wlcompile] [JAM] Warning: failed to resolve class AbstractJspBacking+
    +[wlcompile] [JAM] Error: unexpected exception thrown:+
    +[wlcompile] com.bea.util.jam.internal.javadoc.JavadocParsingException: Parsing failure in F:\b2bNew\b2bPortal\src\portlets\b2b\dmr\Picker\PickerController.java at line 58.+
    e) I suspect , the problem is bcoz of classpath issues , as I generated build.xml donot have the references to dependent lib's.As build.xml looks like below :
    +<target name="compile" description="Only compiles B2BApp application, no appc">+
    +<wlcompile srcdir="${src.dir}" destdir="${dest.dir}">+
    +<!-- These referenced libraries were not found -->+
    +<!-- <library file="p13n-core-web-lib" /> -->+
    +<!-- <library file="jersey-web-lib" /> -->+
    +.....+
    +....+
    Please help me to reslove these issues .
    PS: I able to deploy the application using 10.3.2 weblogic workshop ( i.e inbuilt eclipse )

    i JaySen ,
    thanks for your response. As mentioned we added all the necessary library within the -librarydir but still we see the same error :
    +[JAM] Error: unexpected exception thrown:+
    com.bea.util.jam.internal.javadoc.JavadocParsingException: Parsing failure in F:\b2bNew\b2bPortal\src\portlets\typeAhead\TypeAheadController.java at line 70.  Most likely, an annotation is declared whose type has not been imported.
    at com.bea.util.jam.internal.javadoc.JavadocTigerDelegateImpl_150.getAnnotationTypeFor(JavadocTigerDelegateImpl_150.java:410)
    at com.bea.util.jam.internal.javadoc.JavadocTigerDelegateImpl_150.extractAnnotations(JavadocTigerDelegateImpl_150.java:176)
    at com.bea.util.jam.internal.javadoc.JavadocTigerDelegateImpl_150.extractAnnotations(JavadocTigerDelegateImpl_150.java:152)
    at com.bea.util.jam.internal.javadoc.JavadocClassBuilder.addAnnotations(JavadocClassBuilder.java:404)
    at com.bea.util.jam.internal.javadoc.JavadocClassBuilder.populate(JavadocClassBuilder.java:359)
    ===================
    a) this is a upgrade project [ upgrading from wlp 8.1.4 to 10.3.2 ]
    i.e we are using weblogic portal 10.3.2 version.
    b) Searched some sites/forums regarding the above error, and it says something related to "jwsc" ant task [ i.e while compiling a webservice(JWS) ], but we see this error while compiling a normal controller(jpf) class :(
    c) we are using "ant compile" target which internally calls wlcompile task , while executing wlcompile this error is thrown .
    Help Appreciated
    Thx,
    Sarat

  • What should i put in Schme while creating Data server for XML

    I am new to XML and ODI also.
    I was trying to create a data server for XML technology.
    I don't know what should i specify as a schmea in JDBC URL.
    e.g. jdbc:snps:xml?f=../demo/xml/1/file.xml&ro=false&ldoc=true&case_sens=true&s=LEO_FIZ&dod=true
    here schema is LEO_FIZ, so my doubts is LEO_FIZ is a database schema or what ??
    Please help me out.

    The schema referred to here is going to be used by the XML driver for the instantiation of the temporary schema used for the xml data. It can be any name, I recommend you keep it short, as if you use an external database for the XML data instantiation it is used as a part of the "table" names.

  • Error of Creating Data Server for XML

    Hi all,
    When I want to create a new data server for XML in ODI, the error occur.
    error information:
    connection failed
    java.sql.SQLException: Unexpected token: EMP_TABLE in statement [create EMP_TABLE]
    My JDBC url is: jdbc:snps:xml?f=../demo/xml/MOP/MOPEMP.xml&rt=Export&ro=false&case_sens=true&s=EMP
    It seems that the error is caused by the schema "EMP". But when I changed the name of schema, the error still occur...
    Could you give me some advices about this?
    Thanks&Regards
    Yan

    Hi,
    Thans for your reply.
    This is the DTD for my xmldoc.
    <!ELEMENT Data (Department+)>
    <!ELEMENT EmployeeID (#PCDATA)>
    <!ATTLIST EmployeeID col (EMPID) #IMPLIED>
    <!ELEMENT Education (EmployeeID, Sequence, Dgree)>
    <!ATTLIST Education table NMTOKEN #IMPLIED>
    <!ELEMENT Employee (EmployeeName, EmployeeID, DepartmentID, Education*)>
    <!ATTLIST Employee table NMTOKEN #IMPLIED>
    <!ELEMENT EmployeeName (#PCDATA)>
    <!ATTLIST EmployeeName col NMTOKEN #IMPLIED>
    <!ELEMENT DepartName (#PCDATA)>
    <!ATTLIST DepartName col NMTOKEN #IMPLIED>
    <!ELEMENT Table (Column+)>
    <!ATTLIST Table importType NMTOKEN #IMPLIED>
    <!ATTLIST Table parentTable NMTOKEN #IMPLIED>
    <!ATTLIST Table tag NMTOKEN #IMPLIED>
    <!ATTLIST Table columns NMTOKEN #IMPLIED>
    <!ATTLIST Table name NMTOKEN #IMPLIED>
    <!ELEMENT DepartID (#PCDATA)>
    <!ATTLIST DepartID col NMTOKEN #IMPLIED>
    <!ELEMENT MetaData (Table+)>
    <!ELEMENT Sequence (#PCDATA)>
    <!ATTLIST Sequence col NMTOKEN #IMPLIED>
    <!ELEMENT Dgree (#PCDATA)>
    <!ATTLIST Dgree col NMTOKEN #IMPLIED>
    <!ELEMENT Export (MetaData, Data)>
    <!ELEMENT DepartmentID (#PCDATA)>
    <!ATTLIST DepartmentID col NMTOKEN #IMPLIED>
    <!ELEMENT Column (#PCDATA)>
    <!ATTLIST Column deleteKey NMTOKEN #IMPLIED>
    <!ATTLIST Column isKey NMTOKEN #IMPLIED>
    <!ELEMENT Department (DepartName, DepartID, Employee+)>
    <!ATTLIST Department table NMTOKEN #IMPLIED>
    Thanks again!
    Yan

  • Issue in creating data server for xml in ODI

    Hi,
    I have a XMl which has a size around 95 MB. When i tried to create data server in ODI for this xml file.
    I encounter below error,
    "oracle.odi.jdbc.datasource.ConnectionTimeoutException: A login timeout occured while connecting to the database
    at oracle.odi.jdbc.datasource.LoginTimeoutDatasourceAdapter.doGetConnection(LoginTimeoutDatasourceAdapter.java:117)
    at oracle.odi.jdbc.datasource.LoginTimeoutDatasourceAdapter.getConnection(LoginTimeoutDatasourceAdapter.java:62)
    at com.sunopsis.sql.SnpsConnection.testConnection(SnpsConnection.java:1125)
    at com.sunopsis.graphical.dialog.SnpsDialogTestConnet.getLocalConnect(SnpsDialogTestConnet.java:163)
    at com.sunopsis.graphical.dialog.SnpsDialogTestConnet.access$4(SnpsDialogTestConnet.java:159)
    at com.sunopsis.graphical.dialog.SnpsDialogTestConnet$4.doInBackground(SnpsDialogTestConnet.java:520)
    at com.sunopsis.graphical.dialog.SnpsDialogTestConnet$4.doInBackground(SnpsDialogTestConnet.java:1)
    at oracle.odi.ui.framework.AbsUIRunnableTask.run(AbsUIRunnableTask.java:258)
    at oracle.ide.dialogs.ProgressBar.run(ProgressBar.java:656)
    at java.lang.Thread.run(Thread.java:662)"
    Kindly let me know what should i do for resolving the error.
    Thanks and Regards,
    Ida Jebakirubai S.

    Yes Phil i am able to create a data server for xml files which are of smaller in size(in KB). And i can use the files in the interface as well.
    When i using this large file only i am getting this error.
    Please suggest.
    Thanks and Regards,
    Ida.

  • How to create a Plan.xml file for modification

    Hi,
    I am trying to create a plan.xml file. Is there any way, I can generate a plan.xml file.
    I see a tab in Admin Console in deployments and plan. but there is nothing there. what it has to do with plan.
    Thanks
    regards
    Amir riaz

    You can find the steps here.
    http://weblogic-wonders.com/weblogic/2009/11/29/plan-xml-usage-for-message-driven-bean/
    http://weblogic-wonders.com/weblogic/2009/12/16/invalidation-interval-secs/

  • For xml explicit creating wrong hierarchy

    hi we run 2012 std.  My query that is generally of the form u see in block 1,  which without xml phrase creates flat results u see in block 2 is putting all address info under last contact incorrectly.   Does anybody see what i'm doing
    wrong?
    SELECT 1 AS Tag
    ,null AS Parent
    ,NULL AS 'Request!1!'
    ,NULL AS 'Contacts!2!'
    ,NULL AS 'Contact!3!'
    ,NULL AS 'Contact!3!ContactID!Element'
    ,NULL AS 'ContactAddresses!4!'
    ,NULL AS 'ContactAddress!5!'
    ,NULL AS 'ContactAddress!5!Address1!Element'
    ,NULL AS 'ContactAddress!5!eMail!Element'
    UNION ALL
    SELECT 2 AS Tag
    ,1 AS Parent
    ,NULL AS 'Request!1!'
    ,NULL AS 'Contacts!2!'
    ,NULL AS 'Contact!3!'
    ,NULL AS 'Contact!3!ContactID!Element'
    ,NULL AS 'ContactAddresses!4!'
    ,NULL AS 'ContactAddress!5!'
    ,NULL AS 'ContactAddress!5!Address1!Element'
    ,NULL AS 'ContactAddress!5!eMail!Element'
    UNION ALL
    SELECT 3 AS Tag
    ,2 AS Parent
    ,NULL AS 'Request!1!'
    ,NULL AS 'Contacts!2!'
    ,NULL AS 'Contact!3!'
    ,LTRIM(RTRIM(x)) AS 'Contact!3!ContactID!Element'
    ,NULL AS 'ContactAddresses!4!'
    ,NULL AS 'ContactAddress!5!'
    ,NULL AS 'ContactAddress!5!Address1!Element'
    ,NULL AS 'ContactAddress!5!eMail!Element'
    FROM ...
    UNION ALL
    SELECT 4 AS Tag
    ,3 AS Parent
    ,NULL AS 'Request!1!'
    ,NULL AS 'Contacts!2!'
    ,NULL AS 'Contact!3!'
    ,ltrim(rtrim(x)) AS 'Contact!3!ContactID!Element'
    ,NULL AS 'ContactAddresses!4!'
    ,NULL AS 'ContactAddress!5!'
    ,NULL AS 'ContactAddress!5!Address1!Element'
    ,NULL AS 'ContactAddress!5!eMail!Element'
    FROM ...
    UNION ALL
    SELECT 5 AS Tag
    ,4 AS Parent
    ,NULL AS 'Request!1!'
    ,NULL AS 'Contacts!2!'
    ,NULL AS 'Contact!3!'
    ,ltrim(rtrim(x)) AS 'Contact!3!ContactID!Element'
    ,NULL AS 'ContactAddresses!4!'
    ,NULL AS 'ContactAddress!5!'
    ,case when y ='' then null else LTRIM(RTRIM(y)) end AS 'ContactAddress!5!Address1!Element'
    ,LTRIM(RTRIM(z)) AS 'ContactAddress!5!eMail!Element'
    FROM ...
    FOR XML EXPLICIT
    Tag Parent Request!1! Contacts!2! Contact!3! Contact!3!ContactID!Element ContactAddresses!4! ContactAddress!5! ContactAddress!5!Address1!Element ContactAddress!5!eMail!Element
    1 NULL NULL NULL NULL NULL NULL NULL NULL NULL
    2 1 NULL NULL NULL NULL NULL NULL NULL NULL
    3 2 NULL NULL NULL 10 NULL NULL NULL NULL
    3 2 NULL NULL NULL 11 NULL NULL NULL NULL
    4 3 NULL NULL NULL 10 NULL NULL NULL NULL
    4 3 NULL NULL NULL 11 NULL NULL NULL NULL
    5 4 NULL NULL NULL 10 NULL NULL Address-1-1 NULL
    5 4 NULL NULL NULL 10 NULL NULL Address-1-2 NULL
    5 4 NULL NULL NULL 10 NULL NULL NULL [email protected]
    5 4 NULL NULL NULL 11 NULL NULL NULL [email protected]
    5 4 NULL NULL NULL 11 NULL NULL NULL NULL
    <Request>
    <Contacts>
    <Contact>
    <ContactID>10</ContactID>
    </Contact>
    <Contact>
    <ContactID>11</ContactID>
    <ContactAddresses />
    <ContactAddresses>
    <ContactAddress>
    <Address1>Address1-1</Address1>
    </ContactAddress>
    <ContactAddress>
    <Address1>Address1-2</Address1>
    </ContactAddress>
    <ContactAddress>
    <eMail>[email protected]</eMail>
    </ContactAddress>
    <ContactAddress>
    <eMail>[email protected]</eMail>
    </ContactAddress>
    <ContactAddress />
    </ContactAddresses>
    </Contact>
    </Contacts>
    </Request>

    Hi db042190,
    You have to add one more sort column for each statement in the union. The correlation you try to reflect by the column [Contact!3!ContactID!Element] does not effect. The order in the dataset to for xml explict does make sense to shape the xml. Please see below.
    CREATE TABLE [dbo].[debugXML](
    [ID] [tinyint] IDENTITY(1,1) NOT NULL,
    tag int,
    parent int,
    [sort] int,
    [Request!1!] varchar(50),
    [Contacts!2!] varchar(50),
    [Contact!3!] varchar(50),
    [Contact!3!ContactID!Element] int,
    [ContactAddresses!4!] varchar(50),
    [ContactAddress!5!] varchar(50),
    [ContactAddress!5!Address1!Element] varchar(50),
    [ContactAddress!5!eMail!Element] varchar(50),
    CONSTRAINT [PK_debugXML] PRIMARY KEY CLUSTERED
    [ID] ASC
    )WITH (PAD_INDEX = OFF, STATISTICS_NORECOMPUTE = OFF, IGNORE_DUP_KEY = OFF, ALLOW_ROW_LOCKS = ON, ALLOW_PAGE_LOCKS = ON) ON [PRIMARY]
    ) ON [PRIMARY]
    GO
    insert dbo.debugXML
    select 1 , NULL, 1,NULL , NULL , NULL , NULL , NULL , NULL , NULL , NULL
    union all select 2 , 1 , 2,NULL , NULL , NULL , NULL , NULL , NULL , NULL , NULL
    union all select 3 , 2 , 3,NULL , NULL , NULL , 10 , NULL , NULL , NULL , NULL
    union all select 3 , 2 , 8,NULL , NULL , NULL , 11 , NULL , NULL , NULL , NULL
    union all select 4 , 3 , 4,NULL , NULL , NULL , 10 , NULL , NULL , NULL , NULL
    union all select 4 , 3 , 9,NULL , NULL , NULL , 11 , NULL , NULL , NULL , NULL
    union all select 5 , 4 , 5,NULL , NULL , NULL , 10 , NULL , NULL , 'Address-1-1' , NULL
    union all select 5 , 4 , 6,NULL , NULL , NULL , 10 , NULL , NULL , 'Address-1-2' , NULL
    union all select 5 , 4 , 7,NULL , NULL , NULL , 10 , NULL , NULL , NULL , '[email protected]'
    union all select 5 , 4 , 10,NULL , NULL , NULL , 11 , NULL , NULL , NULL , '[email protected]'
    union all select 5 , 4 , 11,NULL , NULL , NULL , 11 , NULL , NULL , NULL , NULL
    SELECT [tag]
    ,[parent]
    ,[Request!1!]
    ,[Contacts!2!]
    ,[Contact!3!]
    ,[Contact!3!ContactID!Element]
    ,[ContactAddresses!4!]
    ,[ContactAddress!5!]
    ,[ContactAddress!5!Address1!Element]
    ,[ContactAddress!5!eMail!Element]
    FROM [dbo].[debugXML]
    order by sort
    for xml explicit
    <Request>
    <Contacts>
    <Contact>
    <ContactID>10</ContactID>
    <ContactAddresses>
    <ContactAddress>
    <Address1>Address-1-1</Address1>
    </ContactAddress>
    <ContactAddress>
    <Address1>Address-1-2</Address1>
    </ContactAddress>
    <ContactAddress>
    <eMail>[email protected]</eMail>
    </ContactAddress>
    </ContactAddresses>
    </Contact>
    <Contact>
    <ContactID>11</ContactID>
    <ContactAddresses>
    <ContactAddress>
    <eMail>[email protected]</eMail>
    </ContactAddress>
    <ContactAddress />
    </ContactAddresses>
    </Contact>
    </Contacts>
    </Request>
    A good reading for "FOR XML EXPLICT"
    for-xml-explicit-tutorial
    If you have any question, feel free to let me know.
    Eric Zhang
    TechNet Community Support

  • Creating data server for xml

    Hi,
    I am trying to create a dataserver for xml using following info:
    jdbc driver: com.sunopsis.jdbc.driver.xml.SnpsXmlDriver
    jdbc url: jdbc:snps:xml?f=C:/Day_Dim.xml&re=Year&ro=false&case_sens=true
    But I am getting following error: "Connection Closed"
    Please help.
    Thanks,
    Monika

    Hi,
    Thans for your reply.
    This is the DTD for my xmldoc.
    <!ELEMENT Data (Department+)>
    <!ELEMENT EmployeeID (#PCDATA)>
    <!ATTLIST EmployeeID col (EMPID) #IMPLIED>
    <!ELEMENT Education (EmployeeID, Sequence, Dgree)>
    <!ATTLIST Education table NMTOKEN #IMPLIED>
    <!ELEMENT Employee (EmployeeName, EmployeeID, DepartmentID, Education*)>
    <!ATTLIST Employee table NMTOKEN #IMPLIED>
    <!ELEMENT EmployeeName (#PCDATA)>
    <!ATTLIST EmployeeName col NMTOKEN #IMPLIED>
    <!ELEMENT DepartName (#PCDATA)>
    <!ATTLIST DepartName col NMTOKEN #IMPLIED>
    <!ELEMENT Table (Column+)>
    <!ATTLIST Table importType NMTOKEN #IMPLIED>
    <!ATTLIST Table parentTable NMTOKEN #IMPLIED>
    <!ATTLIST Table tag NMTOKEN #IMPLIED>
    <!ATTLIST Table columns NMTOKEN #IMPLIED>
    <!ATTLIST Table name NMTOKEN #IMPLIED>
    <!ELEMENT DepartID (#PCDATA)>
    <!ATTLIST DepartID col NMTOKEN #IMPLIED>
    <!ELEMENT MetaData (Table+)>
    <!ELEMENT Sequence (#PCDATA)>
    <!ATTLIST Sequence col NMTOKEN #IMPLIED>
    <!ELEMENT Dgree (#PCDATA)>
    <!ATTLIST Dgree col NMTOKEN #IMPLIED>
    <!ELEMENT Export (MetaData, Data)>
    <!ELEMENT DepartmentID (#PCDATA)>
    <!ATTLIST DepartmentID col NMTOKEN #IMPLIED>
    <!ELEMENT Column (#PCDATA)>
    <!ATTLIST Column deleteKey NMTOKEN #IMPLIED>
    <!ATTLIST Column isKey NMTOKEN #IMPLIED>
    <!ELEMENT Department (DepartName, DepartID, Employee+)>
    <!ATTLIST Department table NMTOKEN #IMPLIED>
    Thanks again!
    Yan

  • How to create new Custom XML Report without using Form Builder

    Hi,
    What are the steps to create new Custom XML Report without using Report Builder ?
    Thanks and Regards,
    Abhi

    Hi,
    Steps we now follow
    1)Create Data Model in Reports Builder
    2)Create xml
    3)Insert xml in Publisher to build Fomat
    4)FTp rdf
    5)Create Data Definition and Template
    6)Create executable and Concurrent Program
    Is there any way we can build reports without use of Report Builder ? By writing PL SQL Package for Before Report and After Report etc ...
    Thanks and Regards,
    Abhijit Rode

  • Unable to locate Spring NamespaceHandler for XML schema namespace

    I am not sure if this is the best practice approach but this is the problem I am ruining into. Below, I explain what I am doing:
    1) What I am doing:
    =============
    Based on the oracle incubator example (http://coherence.oracle.com/display/INCUBATOR/Processing+Pattern+Examples); I am running a server and submitting tasks through a proxy application that submits them to ProcessingPatternConfigurator; let's call my task processReport.
    a) my processReport is using spring and ibatis together, I created a utility static class to obtain a spring context and retrieves beans using the following lines ( see exhibit "A1 and A2" below).
    b) when my task calls the context and that spring loads, it is failing with the error show in exhibit "B".
    I suspect I am missing a lib? I googled the error and searched you site but could find a meaningful discussion on it. I guess my question is if this is not the best approach, how do I integrated with spring initializing beans and setting up ibatis framwork, providing beans and database access through Ibatis for each task ruining on the grid (processReport).
    thanks
    A1) processReport (submitted in the grid) uses this line
    AbstractXmlApplicationContext ctx = (AbstractXmlApplicationContext) AmrContextUtil.getInstance();
              System.out.println("Classpath loaded. Executing Report...");
              ReportProcessor repProcessor = (ReportProcessor) ctx.getBean("reportProcessor");
    A2) Here is the AmrContextUtil:
    import org.springframework.context.support.AbstractApplicationContext;
    import org.springframework.context.support.ClassPathXmlApplicationContext;
    public final class AmrContextUtil {
         private static AbstractApplicationContext ctx = null;
         public AmrContextUtil() {
              super();
         public final static synchronized AbstractApplicationContext getInstance(){
              if (ctx == null){
                   ctx = new ClassPathXmlApplicationContext("classpath:config/applicationContext.xml");
                   setCtx(ctx);
              return ctx;
         public final static synchronized AbstractApplicationContext getCtx() {
              return ctx;
         public final static synchronized void setCtx(AbstractApplicationContext ctx) {
              AmrContextUtil.ctx = ctx;
    B) Here is the error reported by the server:
    2010-02-10 15:42:28.312/57.986 Oracle Coherence GE 3.5.2/463 <Warning> (thread=GridExecutor:Thread-2
    , member=1): TaskRunner - Failed to process 0x00000126B99E5524AC1F007AAB1587BBCFEC5E6637E1DED6CCB984
    03D6AADF4D due to:org.springframework.beans.factory.parsing.BeanDefinitionParsingException: Configuration problem: Failed to import bean definitions from URL location [classpath:config/reports-application.xml] Offending resource: class path resource [config/applicationContext.xml]; nested exception is org.springframework.beans.factory.parsing.BeanDefinitionParsingException: Configuration problem: Unexpected failure during bean definition parsing
    Offending resource: class path resource [config/reports-application.xml] Bean 'reportSqlMapConfig'; nested exception is org.springframework.beans.factory.parsing.BeanDefinitionParsingException: *Configuration problem: Unable to locate Spring NamespaceHandler for XML schema namespace [http://www.springframework.org/schema/util]*
    *Offending resource: class path resource [config/reports-application.xml] Bean 'reportSqlMapConfig'*
    -> Property 'resourceMap'
    c)Here is my application-context.xml offending line:
    <bean id="reportSqlMapConfig"
    class="com.xx.report.generator.ReportSqlMapConfig">
    <property name="resourceMap">
    <map>
    <entry>
    <key>
    <util:constant static-field="com.xx.report.domain.ReportType.FPA"/>
    </key>
    <value>classpath:config/diehardReportSqlMapConfig.xml</value>
    </entry>
    <entry>
    <key>
    <util:constant static-field="com.xx.report.domain.ReportType.FCN"/>
    </key>
    <value>classpath:config/falconReportSqlMapConfig.xml</value>
    </entry>
    <entry>
    <key>
    <util:constant static-field="com.xx.report.domain.ReportType.ODS"/>
    </key>
    <value>classpath:config/odsReportSqlMapConfig.xml</value>
    </entry>
    </map>
    </property>
    </bean>

    My guess is that something is broken in the configuration of the cacheServer and its not finding
    all of the dependencies that your process pattern application needs. Probably the best way
    to debug this stuff is to define a static main in your runnable task which will make the call
    to the run() method and invoke it as the main class using the identical settings (classpath,
    run directory) that you are using to launch the Coherence cache server.
    Regards,
    Bob

  • File is corrupted error while creating excel using xml

      Hi have created one excel file using XML code and sent it to mail as attachement. But when i open it, it displays error  message - file is corrupted and cannot be opened.
    below is my code - please review and tell what is wrong in it ASAP :
    * Creating a ixml Factory
       l_ixml = cl_ixml=>create( ).
    * Creating the DOM Object Model
       l_document = l_ixml->create_document( ).
    * Create Root Node 'Workbook'
       l_element_root  = l_document->create_simple_element( name = 'Workbook'  parent = l_document ).
       l_element_root->set_attribute( name = 'xmlns'  value = 'urn:schemas-microsoft-com:office:spreadsheet' ).
       ns_attribute = l_document->create_namespace_decl( name = 'ss'  prefix = 'xmlns'  uri = 'urn:schemas-microsoft-com:office:spreadsheet' ).
       l_element_root->set_attribute_node( ns_attribute ).
       ns_attribute = l_document->create_namespace_decl( name = 'x'  prefix = 'xmlns'  uri = 'urn:schemas-microsoft-com:office:excel' ).
       l_element_root->set_attribute_node( ns_attribute ).
    * Create node for document properties.
       r_element_properties = l_document->create_simple_element( name = 'TEST_REPORT'  parent = l_element_root ).
       l_value = sy-uname.
       l_document->create_simple_element( name = 'Author'  value = l_value  parent = r_element_properties  ).
    * Styles
       r_styles = l_document->create_simple_element( name = 'Styles'  parent = l_element_root  ).
    * Style for Header
       r_style  = l_document->create_simple_element( name = 'Style'   parent = r_styles  ).
       r_style->set_attribute_ns( name = 'ID'  prefix = 'ss'  value = 'Header' ).
       r_format  = l_document->create_simple_element( name = 'Font'  parent = r_style  ).
       r_format->set_attribute_ns( name = 'Bold'  prefix = 'ss'  value = '1' ).
       r_format  = l_document->create_simple_element( name = 'Interior' parent = r_style  ).
       r_format->set_attribute_ns( name = 'Color'   prefix = 'ss'  value = '#92D050' ).
       r_format->set_attribute_ns( name = 'Pattern' prefix = 'ss'  value = 'Solid' ).
       r_format  = l_document->create_simple_element( name = 'Alignment'  parent = r_style  ).
       r_format->set_attribute_ns( name = 'Vertical'  prefix = 'ss'  value = 'Center' ).
       r_format->set_attribute_ns( name = 'WrapText'  prefix = 'ss'  value = '1' ).
       r_border  = l_document->create_simple_element( name = 'Borders'  parent = r_style ).
       r_format  = l_document->create_simple_element( name = 'Border'   parent = r_border  ).
       r_format->set_attribute_ns( name = 'Position'  prefix = 'ss'  value = 'Bottom' ).
       r_format->set_attribute_ns( name = 'LineStyle'  prefix = 'ss'  value = 'Continuous' ).
       r_format->set_attribute_ns( name = 'Weight'  prefix = 'ss'  value = '1' ).
       r_format  = l_document->create_simple_element( name = 'Border'   parent = r_border  ).
       r_format->set_attribute_ns( name = 'Position'  prefix = 'ss'  value = 'Left' ).
       r_format->set_attribute_ns( name = 'LineStyle'  prefix = 'ss'  value = 'Continuous' ).
       r_format->set_attribute_ns( name = 'Weight'  prefix = 'ss'  value = '1' ).
       r_format  = l_document->create_simple_element( name = 'Border'   parent = r_border  ).
       r_format->set_attribute_ns( name = 'Position'  prefix = 'ss'  value = 'Top' ).
       r_format->set_attribute_ns( name = 'LineStyle'  prefix = 'ss'  value = 'Continuous' ).
       r_format->set_attribute_ns( name = 'Weight'  prefix = 'ss'  value = '1' ).
       r_format  = l_document->create_simple_element( name = 'Border'   parent = r_border  ).
       r_format->set_attribute_ns( name = 'Position'  prefix = 'ss'  value = 'Right' ).
       r_format->set_attribute_ns( name = 'LineStyle'  prefix = 'ss'  value = 'Continuous' ).
       r_format->set_attribute_ns( name = 'Weight'  prefix = 'ss'  value = '1' ).
    * Style for Data
       r_style1  = l_document->create_simple_element( name = 'Style'   parent = r_styles  ).
       r_style1->set_attribute_ns( name = 'ID'  prefix = 'ss'  value = 'Data' ).
       r_border  = l_document->create_simple_element( name = 'Borders'  parent = r_style1 ).
       r_format  = l_document->create_simple_element( name = 'Border'   parent = r_border  ).
       r_format->set_attribute_ns( name = 'Position'  prefix = 'ss'  value = 'Bottom' ).
       r_format->set_attribute_ns( name = 'LineStyle'  prefix = 'ss'  value = 'Continuous' ).
       r_format->set_attribute_ns( name = 'Weight'  prefix = 'ss'  value = '1' ).
       r_format  = l_document->create_simple_element( name = 'Border'   parent = r_border  ).
       r_format->set_attribute_ns( name = 'Position'  prefix = 'ss'  value = 'Left' ).
       r_format->set_attribute_ns( name = 'LineStyle'  prefix = 'ss'  value = 'Continuous' ).
       r_format->set_attribute_ns( name = 'Weight'  prefix = 'ss'  value = '1' ).
       r_format  = l_document->create_simple_element( name = 'Border'   parent = r_border  ).
       r_format->set_attribute_ns( name = 'Position'  prefix = 'ss'  value = 'Top' ).
       r_format->set_attribute_ns( name = 'LineStyle'  prefix = 'ss'  value = 'Continuous' ).
       r_format->set_attribute_ns( name = 'Weight'  prefix = 'ss'  value = '1' ).
       r_format  = l_document->create_simple_element( name = 'Border'   parent = r_border  ).
       r_format->set_attribute_ns( name = 'Position'  prefix = 'ss'  value = 'Right' ).
       r_format->set_attribute_ns( name = 'LineStyle'  prefix = 'ss'  value = 'Continuous' ).
       r_format->set_attribute_ns( name = 'Weight'  prefix = 'ss'  value = '1' ).
    * Worksheet
       r_worksheet = l_document->create_simple_element( name = 'Worksheet'  parent = l_element_root ).
       r_worksheet->set_attribute_ns( name = 'Name'  prefix = 'ss'  value = 'Sheet1' ).
    *  r_worksheet->set_attribute_ns( name = 'Protected'  prefix = 'ss'  value = '1' ).    " WORKING
    * Table
       r_table = l_document->create_simple_element( name = 'Table'  parent = r_worksheet ).
       r_table->set_attribute_ns( name = 'FullColumns'  prefix = 'x'  value = '1' ).
       r_table->set_attribute_ns( name = 'FullRows'     prefix = 'x'  value = '1' ).
    * Column Formatting
       r_column = l_document->create_simple_element( name = 'Column'  parent = r_table ).
       r_column->set_attribute_ns( name = 'Width'  prefix = 'ss'  value = '40' ).
       r_column = l_document->create_simple_element( name = 'Column'  parent = r_table ).
       r_column->set_attribute_ns( name = 'Width'  prefix = 'ss'  value = '90' ).
       r_column = l_document->create_simple_element( name = 'Column'  parent = r_table ).
       r_column->set_attribute_ns( name = 'Width'  prefix = 'ss'  value = '140' ).
       r_column = l_document->create_simple_element( name = 'Column'  parent = r_table ).
       r_column->set_attribute_ns( name = 'Width'  prefix = 'ss'  value = '150' ).
       r_column = l_document->create_simple_element( name = 'Column'  parent = r_table ).
       r_column->set_attribute_ns( name = 'Width'  prefix = 'ss'  value = '90' ).
       r_column = l_document->create_simple_element( name = 'Column'  parent = r_table ).
       r_column->set_attribute_ns( name = 'Width'  prefix = 'ss'  value = '90' ).
       r_column = l_document->create_simple_element( name = 'Column'  parent = r_table ).
       r_column->set_attribute_ns( name = 'Width'  prefix = 'ss'  value = '90' ).
       r_column = l_document->create_simple_element( name = 'Column'  parent = r_table ).
       r_column->set_attribute_ns( name = 'Width'  prefix = 'ss'  value = '90' ).
       r_column = l_document->create_simple_element( name = 'Column'  parent = r_table ).
       r_column->set_attribute_ns( name = 'Width'  prefix = 'ss'  value = '90' ).
    * Blank Row
       r_row = l_document->create_simple_element( name = 'Row'  parent = r_table ).
    * Column Headers Row
       r_row = l_document->create_simple_element( name = 'Row'  parent = r_table ).
       r_row->set_attribute_ns( name = 'AutoFitHeight'  prefix = 'ss'  value = '1' ).
    * RFQ No.
       r_cell = l_document->create_simple_element( name = 'Cell'  parent = r_row ).
       r_cell->set_attribute_ns( name = 'StyleID'  prefix = 'ss'  value = 'Header' ).
       r_data = l_document->create_simple_element( name = 'Data'  value = 'RFQ No.'  parent = r_cell ).
       r_data->set_attribute_ns( name = 'Type'  prefix = 'ss' value = 'String' ).
    * RFQ Line Item No
       r_cell = l_document->create_simple_element( name = 'Cell'  parent = r_row ).
       r_cell->set_attribute_ns( name = 'StyleID'  prefix = 'ss'  value = 'Header' ).
       r_data = l_document->create_simple_element( name = 'Data'  value = 'RFQ Line Item No.'  parent = r_cell ).
       r_data->set_attribute_ns( name = 'Type'  prefix = 'ss' value = 'String' ).
    * Material
       r_cell = l_document->create_simple_element( name = 'Cell'  parent = r_row ).
       r_cell->set_attribute_ns( name = 'StyleID'  prefix = 'ss'  value = 'Header' ).
       r_data = l_document->create_simple_element( name = 'Data'  value = 'Material'  parent = r_cell ).
       r_data->set_attribute_ns( name = 'Type'  prefix = 'ss' value = 'String' ).
    * Quantity
       r_cell = l_document->create_simple_element( name = 'Cell'  parent = r_row ).
       r_cell->set_attribute_ns( name = 'StyleID'  prefix = 'ss'  value = 'Header' ).
       r_data = l_document->create_simple_element( name = 'Data'  value = 'Quantity'  parent = r_cell ).
       r_data->set_attribute_ns( name = 'Type'  prefix = 'ss' value = 'String' ).
    *  Order UNIT
       r_cell = l_document->create_simple_element( name = 'Cell'  parent = r_row ).
       r_cell->set_attribute_ns( name = 'StyleID'  prefix = 'ss'  value = 'Header' ).
       r_data = l_document->create_simple_element( name = 'Data'  value = 'Order Unit'  parent = r_cell ).
       r_data->set_attribute_ns( name = 'Type'  prefix = 'ss' value = 'String' ).
    *  Delivery Date
       r_cell = l_document->create_simple_element( name = 'Cell'  parent = r_row ).
       r_cell->set_attribute_ns( name = 'StyleID'  prefix = 'ss'  value = 'Header' ).
       r_data = l_document->create_simple_element( name = 'Data'  value = 'Delivery Date'  parent = r_cell ).
       r_data->set_attribute_ns( name = 'Type'  prefix = 'ss' value = 'String' ).
    *  RFQ Creation Date
       r_cell = l_document->create_simple_element( name = 'Cell'  parent = r_row ).
       r_cell->set_attribute_ns( name = 'StyleID'  prefix = 'ss'  value = 'Header' ).
       r_data = l_document->create_simple_element( name = 'Data'  value = 'RFQ Creation Date'  parent = r_cell ).
       r_data->set_attribute_ns( name = 'Type'  prefix = 'ss' value = 'String' ).
    *  RFQ Deadline Date
       r_cell = l_document->create_simple_element( name = 'Cell'  parent = r_row ).
       r_cell->set_attribute_ns( name = 'StyleID'  prefix = 'ss'  value = 'Header' ).
       r_data = l_document->create_simple_element( name = 'Data'  value = 'RFQ Deadline Date'  parent = r_cell ).
       r_data->set_attribute_ns( name = 'Type'  prefix = 'ss' value = 'String' ).
    * Price
       r_cell = l_document->create_simple_element( name = 'Cell'  parent = r_row ).
       r_cell->set_attribute_ns( name = 'StyleID'  prefix = 'ss'  value = 'Header' ).
       r_data = l_document->create_simple_element( name = 'Data'  value = 'Net Price'  parent = r_cell ).
       r_data->set_attribute_ns( name = 'Type'  prefix = 'ss' value = 'String' ).
    ** Login
    *  r_cell = l_document->create_simple_element( name = 'Cell'  parent = r_row ).
    *  r_cell->set_attribute_ns( name = 'StyleID'  prefix = 'ss'  value = 'Header' ).
    *  CONCATENATE 'Login - ' lv_date+6(2) '/' lv_date+4(2) '/' lv_date+0(4) INTO l_value.
    *  r_data = l_document->create_simple_element( name = 'Data'  value = l_value  parent = r_cell ).
    *  r_data->set_attribute_ns( name = 'Type'  prefix = 'ss' value = 'String' ).
    * Blank Row after Column Headers
       r_row = l_document->create_simple_element( name = 'Row'  parent = r_table ).
       r_cell = l_document->create_simple_element( name = 'Cell'  parent = r_row ).
       r_cell->set_attribute_ns( name = 'StyleID'  prefix = 'ss'  value = 'Data' ).
       r_cell = l_document->create_simple_element( name = 'Cell'  parent = r_row ).
       r_cell->set_attribute_ns( name = 'StyleID'  prefix = 'ss'  value = 'Data' ).
       r_cell = l_document->create_simple_element( name = 'Cell'  parent = r_row ).
       r_cell->set_attribute_ns( name = 'StyleID'  prefix = 'ss'  value = 'Data' ).
       r_cell = l_document->create_simple_element( name = 'Cell'  parent = r_row ).
       r_cell->set_attribute_ns( name = 'StyleID'  prefix = 'ss'  value = 'Data' ).
       r_cell = l_document->create_simple_element( name = 'Cell'  parent = r_row ).
       r_cell->set_attribute_ns( name = 'StyleID'  prefix = 'ss'  value = 'Data' ).
       r_cell = l_document->create_simple_element( name = 'Cell'  parent = r_row ).
       r_cell->set_attribute_ns( name = 'StyleID'  prefix = 'ss'  value = 'Data' ).
       r_cell = l_document->create_simple_element( name = 'Cell'  parent = r_row ).
       r_cell->set_attribute_ns( name = 'StyleID'  prefix = 'ss'  value = 'Data' ).
       r_cell = l_document->create_simple_element( name = 'Cell'  parent = r_row ).
       r_cell->set_attribute_ns( name = 'StyleID'  prefix = 'ss'  value = 'Data' ).
       r_cell = l_document->create_simple_element( name = 'Cell'  parent = r_row ).
       r_cell->set_attribute_ns( name = 'StyleID'  prefix = 'ss'  value = 'Data' ).
    * Data Table
       LOOP AT it_final1 INTO wa_final1.
         CLEAR l_value.
         r_row = l_document->create_simple_element( name = 'Row'  parent = r_table ).
    * RFQ No.
         r_cell = l_document->create_simple_element( name = 'Cell'  parent = r_row ).
         r_cell->set_attribute_ns( name = 'StyleID'  prefix = 'ss'  value = 'Data' ).
         CLEAR l_value.
         l_value = wa_final1-ebeln .
    *    CONDENSE l_value NO-GAPS.
         r_data = l_document->create_simple_element( name = 'Data'  value = l_value  parent = r_cell ).           " Data
         r_data->set_attribute_ns( name = 'Type'  prefix = 'ss'  value = 'String' ).                               " Cell format
    * Line Item No
         CLEAR l_value.
         r_cell = l_document->create_simple_element( name = 'Cell'  parent = r_row ).
         r_cell->set_attribute_ns( name = 'StyleID'  prefix = 'ss'  value = 'Data' ).
         l_value = wa_final1-ebelp.
         r_data = l_document->create_simple_element( name = 'Data'  value = l_value   parent = r_cell ).           " Data
         r_data->set_attribute_ns( name = 'Type'  prefix = 'ss'  value = 'Number' ).                               " Cell format
    * Material
         CLEAR l_value.
         r_cell = l_document->create_simple_element( name = 'Cell'  parent = r_row ).
         r_cell->set_attribute_ns( name = 'StyleID'  prefix = 'ss'  value = 'Data' ).
         l_value = wa_final1-txz01.
         r_data = l_document->create_simple_element( name = 'Data'  value = l_value   parent = r_cell ).           " Data
         r_data->set_attribute_ns( name = 'Type'  prefix = 'ss'  value = 'String' ).                               " Cell format
    * RFQ QTY
         CLEAR l_value.
         r_cell = l_document->create_simple_element( name = 'Cell'  parent = r_row ).
         r_cell->set_attribute_ns( name = 'StyleID'  prefix = 'ss'  value = 'Data' ).
         l_value = wa_final1-ktmng.
         r_data = l_document->create_simple_element( name = 'Data'  value = l_value   parent = r_cell ).           " Data
         r_data->set_attribute_ns( name = 'Type'  prefix = 'ss'  value = 'Number' ).                               " Cell format
    * UNIT
         CLEAR l_value.
         r_cell = l_document->create_simple_element( name = 'Cell'  parent = r_row ).
         r_cell->set_attribute_ns( name = 'StyleID'  prefix = 'ss'  value = 'Data' ).
         l_value = wa_final1-meins.
         r_data = l_document->create_simple_element( name = 'Data'  value = l_value   parent = r_cell

    How to make a particular column non editable?
    Make your style protected and pass that style name to your required column while passing data.
    for example:
    Find below the code for protection of a style.
    Last two lines are very important.
    * Style for Headert
       r_style  = l_document->create_simple_element( name = 'Style'   parent = r_styles  ).
       r_style->set_attribute_ns( name = 'ID'  prefix = 'ss'  value = 'Headert' ).
       r_format  = l_document->create_simple_element( name = 'Font'  parent = r_style  ).
       r_format->set_attribute_ns( name = 'Bold'  prefix = 'ss'  value = '1' ).
       r_format  = l_document->create_simple_element( name = 'Interior' parent = r_style  ).
       r_format->set_attribute_ns( name = 'Color'   prefix = 'ss'  value = '#B2FF64' ).      
       r_format->set_attribute_ns( name = 'Pattern' prefix = 'ss'  value = 'Solid' ).
       r_format  = l_document->create_simple_element( name = 'Alignment'  parent = r_style  ).
       r_format->set_attribute_ns( name = 'Vertical'  prefix = 'ss'  value = 'Bottom' ).
       r_format->set_attribute_ns( name = 'WrapText'  prefix = 'ss'  value = '1' ).
       r_border  = l_document->create_simple_element( name = 'Borders'  parent = r_style ).
       r_format  = l_document->create_simple_element( name = 'Border'   parent = r_border  ).
       r_format->set_attribute_ns( name = 'Position'  prefix = 'ss'  value = 'Bottom' ).
       r_format->set_attribute_ns( name = 'LineStyle'  prefix = 'ss'  value = 'Continuous' ).
       r_format->set_attribute_ns( name = 'Weight'  prefix = 'ss'  value = '1' ).
       r_format  = l_document->create_simple_element( name = 'Border'   parent = r_border  ).
       r_format->set_attribute_ns( name = 'Position'  prefix = 'ss'  value = 'Left' ).
       r_format->set_attribute_ns( name = 'LineStyle'  prefix = 'ss'  value = 'Continuous' ).
       r_format->set_attribute_ns( name = 'Weight'  prefix = 'ss'  value = '1' ).
       r_format  = l_document->create_simple_element( name = 'Border'   parent = r_border  ).
       r_format->set_attribute_ns( name = 'Position'  prefix = 'ss'  value = 'Top' ).
       r_format->set_attribute_ns( name = 'LineStyle'  prefix = 'ss'  value = 'Continuous' ).
       r_format->set_attribute_ns( name = 'Weight'  prefix = 'ss'  value = '1' ).
       r_format  = l_document->create_simple_element( name = 'Border'   parent = r_border  ).
       r_format->set_attribute_ns( name = 'Position'  prefix = 'ss'  value = 'Right' ).
       r_format->set_attribute_ns( name = 'LineStyle'  prefix = 'ss'  value = 'Continuous' ).
       r_format->set_attribute_ns( name = 'Weight'  prefix = 'ss'  value = '1' ).
       r_format  = l_document->create_simple_element( name = 'Protection'  parent = r_style  ).
       r_format->set_attribute_ns( name = 'Protected'  prefix = 'ss'  value = '1' ).

  • Namespace Error, while creating proxy for a WSRP producer(Created on Exo)

    Hi ,
    I have implemented and deployed WSRP producer on Exo portal container. When I was trying to create proxy for the same in weblogic portal 10.2 its giving me the following error. Upon submiting the WSDL URL
    !ENTRY com.bea.wlp.eclipse.common 4 4 2008-12-08 13:46:27.540
    !MESSAGE NAMESPACE_ERR
    !STACK 0
    org.w3c.dom.DOMException: NAMESPACE_ERR
         at weblogic.xml.domimpl.ElementNSImpl.<init>(ElementNSImpl.java:74)
         at weblogic.xml.saaj.SOAPElementImpl.<init>(SOAPElementImpl.java:40)
         at weblogic.xml.saaj.SaajDocument.createElementNS(SaajDocument.java:63)
         at com.bea.wsrp.util.DomUtils.createChildElement(DomUtils.java:386)
         at com.bea.wsrp.util.DomUtils.addChildElement(DomUtils.java:406)
         at com.bea.wsrp.util.DomUtils.addChildElement(DomUtils.java:371)
         at com.bea.wsrp.bind.serviceDescription.GetServiceDescriptionRequest.writeTo(GetServiceDescriptionRequest.java:40)
         at com.bea.wsrp.client.ProducerAgentImpl.getServiceDescription(ProducerAgentImpl.java:129)
         at com.bea.wsrp.client.ProducerAgentImpl.getServiceDescription(ProducerAgentImpl.java:80)
         at com.bea.wsrp.client.ProducerAgentImpl.getServiceDescription(ProducerAgentImpl.java:68)
         at com.bea.wsrp.client.ProducerAgentImpl.getServiceDescription(ProducerAgentImpl.java:57)
         at com.bea.wlp.eclipse.wsrp.portletbuilder.wsrp.ProducerAgent.getServiceDescription(ProducerAgent.java:99)
         at com.bea.wlp.eclipse.wsrp.portletbuilder.wsrp.ProducerAgent.<init>(ProducerAgent.java:57)
         at com.bea.wlp.eclipse.wsrp.portletbuilder.wsrp.ProducerAgent.<init>(ProducerAgent.java:45)
         at com.bea.wlp.eclipse.wsrp.portletbuilder.wizard.wsrp.SelectProducerPanel$ProducerInfoRunner.run(SelectProducerPanel.java:690)
    Could any one help me to solve this problem.
    Thanks & Regards,
    Naresh

    Hi Nate,
    Please find the following wsdl.
    <?xml version="1.0" encoding="UTF-8" ?>
    <wsdl:definitions targetNamespace="http://localhost:8080/wsrp/services/Version" xmlns:apachesoap="http://xml.apache.org/xml-soap" xmlns:impl="http://localhost:8080/wsrp/services/Version" xmlns:intf="http://localhost:8080/wsrp/services/Version" xmlns:soapenc="http://schemas.xmlsoap.org/soap/encoding/" xmlns:wsdl="http://schemas.xmlsoap.org/wsdl/" xmlns:wsdlsoap="http://schemas.xmlsoap.org/wsdl/soap/" xmlns:xsd="http://www.w3.org/2001/XMLSchema">
    <!--
    WSDL created by Apache Axis version: 1.4
    Built on Nov 19, 2006 (02:31:34 GMT+00:00)
    -->
    <wsdl:message name="getVersionRequest" />
    <wsdl:message name="getVersionResponse">
    <wsdl:part name="getVersionReturn" type="soapenc:string" />
    </wsdl:message>
    <wsdl:portType name="Version">
    <wsdl:operation name="getVersion">
    <wsdl:input message="impl:getVersionRequest" name="getVersionRequest" />
    <wsdl:output message="impl:getVersionResponse" name="getVersionResponse" />
    </wsdl:operation>
    </wsdl:portType>
    <wsdl:binding name="VersionSoapBinding" type="impl:Version">
    <wsdlsoap:binding style="rpc" transport="http://schemas.xmlsoap.org/soap/http" />
    <wsdl:operation name="getVersion">
    <wsdlsoap:operation soapAction="" />
    <wsdl:input name="getVersionRequest">
    <wsdlsoap:body encodingStyle="http://schemas.xmlsoap.org/soap/encoding/" namespace="http://axis.apache.org" use="encoded" />
    </wsdl:input>
    <wsdl:output name="getVersionResponse">
    <wsdlsoap:body encodingStyle="http://schemas.xmlsoap.org/soap/encoding/" namespace="http://localhost:8080/wsrp/services/Version" use="encoded" />
    </wsdl:output>
    </wsdl:operation>
    </wsdl:binding>
    <wsdl:service name="VersionService">
    <wsdl:port binding="impl:VersionSoapBinding" name="Version">
    <wsdlsoap:address location="http://localhost:8080/wsrp/services/Version" />
    </wsdl:port>
    </wsdl:service>
    </wsdl:definitions>
    Thanks & Regards,
    Naresh

  • Need help in creating prompt for Month To Date Report.

    <span class="postbody"><font size="2">Hi All <br />I need to create a Month To Date Report using month(Start date & End date) as prompts, By default it has to run on the previous month data or if user selects his own range of dates then it has to bring the data for that range of dates ,one more thing is i am not showing the month and date columns on the report.Can any one help me how to create prompt for this in DeskI XIR2</font></span>

    Could you clarify some things? You are saying you are trying to transform the xml output of a webservice with an xsd, but an xsd is a schema that describes the allowed format of a xml file. If you want to transform xml from one format to an other (from one xsd to an other) you have to use a xsl file. You can make and test this with JDeveloper. Are you calling the webservice from esb or bpel?
    Kind Regards,
    Andre

Maybe you are looking for

  • Can I use a green screen in Premiere Elements 13?

    I am trying to decide between Premiere Pro and Elements 13 and would like to save some money while still being able to have those capabilities to key. Thank You! -Jesse

  • HT203254 Macbook pro 8600 fails to start

    I have a macbook pro with the 8600m gt graphics chip.  I has recently failed and now will not start, no chime just disk spinning and steady white glow from the sleep indicator. Is this product still covered under the extended waranty programme?  If i

  • BPM with split synchronous calls and merge

    I need to create a BPM that will take a synchronous request message. The synchronous request message contains a customer ID based on two synchronous web services are called on 2 different systems. The results of these need to be merged and sent back

  • MSS-mySAP ERP 2004-PCR- Processing exception during a "Render" operation

    HI, When i navigate to the Personnel Change request,select an employee and select the scenario,say promotion,i get the error: com.sap.tc.webdynpro.services.exceptions.WDRuntimeException: Error during call to AdobeDocumentServer: Processing exception

  • New Emails flagged but not showing up?

    Hi all, I'm using Mac mail in Leopard. I've got some problems with Mail, but the main thing I'm wondering now is whether Mac support ongoing development of Mail for G5? Probably not hey? Mail has the little red flag (or circle) telling me there 1 new