Текущее время: Сб, май 10 2025, 10:00

Часовой пояс: UTC + 3 часа


Правила форума


ВНИМАНИЕ! Прежде чем задавать вопрос, ознакомьтесь со ссылками ниже:

Вопросы по отличиям версий SAP, Add-On, EHP - сюда
Вопросы по SAP Front End (SAPlogon, SAPgui, guiXT и т.д.) - сюда
Вопросы по LSMW - сюда
Вопросы по архивации в SAP - сюда
Вопросы по SAP GRC - сюда
Вопросы по SAP Business Workplace (почте SAP) и SAP Office - сюда
Вопросы по miniSAP (SAP mini basis) - сюда
Вопросы по SAP HANA - сюда
Вопросы по лицензированию продуктов SAP - сюда



Начать новую тему Ответить на тему  [ Сообщений: 2 ] 
Автор Сообщение
 Заголовок сообщения: как выгрузить жунал пакетного ввода?
СообщениеДобавлено: Ср, апр 28 2010, 19:05 
Старший специалист
Старший специалист
Аватара пользователя

Зарегистрирован:
Чт, окт 14 2004, 18:02
Сообщения: 415
Откуда: из HR
Пол: Мужской
Коллеги, добрый вечер,

помогите с сабжем пожалуйста. ERP6.0

Дима


Пометить тему как нерешенную
Вернуться к началу
 Профиль  
 
 Заголовок сообщения: Re: как выгрузить жунал пакетного ввода?  Тема решена
СообщениеДобавлено: Ср, апр 28 2010, 21:02 
Старший специалист
Старший специалист
Аватара пользователя

Зарегистрирован:
Чт, окт 14 2004, 18:02
Сообщения: 415
Откуда: из HR
Пол: Мужской
ввиду срочности пришлось сделать из стандартной RSBDC_ANALYSE
код не причесывал, кому нужно - вэлком
на входе указываем ID очереди и первые 10 символов, из лога будут выдраны все вхождения
на выходе файл в C:\SM35_LOG.TXT

Code:
REPORT  ZGET_SM35_LOG.

parameters:
  queue_id like apqi-qid,
  tcod_idx type i no-display,
  dynp_idx type i no-display,
  look_up(10) type C.

include rsbdcil3.   "Read plain log from TemSe
type-pools: icon, sdydo.

tables:
  apqi, apqd, apql, t100, snap, bdc_sessio.

controls:
  tc_tcodes   type tableview using screen 200,
  tc_dynpro   type tableview using screen 300,
  tc_protocol type tableview using screen 400,
  tc_bdcld    type tableview using screen 600,
  tc_q_tcodes type tableview using screen 700,
  tab_dynpro  type tabstrip,
  tab_apqi    type tabstrip.

field-symbols:
  <mtxt>,
  <vtxt>.

* upload struct
DATA: BEGIN OF TMP OCCURS 1000,
        STRING(255),
      END OF TMP.
* upload path
data F_PATH type STRING.
DATA F_LEN TYPE I.

data:
* this table keeps those tcodes actually displayed
  begin of bdc_tcodes occurs 0,
    index type i, tcode like sy-tcode, status(1), s_text(16),
  end of bdc_tcodes,
* this table keeps all tcodes of the session
  begin of all_bdc_tcodes occurs 0,
    index type i, tcode like sy-tcode, status(1), s_text(16),
  end of all_bdc_tcodes.

data:
* this table keeps those dynpros actually displayed
  begin of bdc_dynpro occurs 0,
    program like sy-cprog, dynpro like sy-dynnr,
    fnam like bdcdata-fnam, fval like bdcdata-fval,
    index(5) type c,
  end of bdc_dynpro,
* this table keeps all dynpros of the session
  begin of all_bdc_dynpro occurs 0,
    program like sy-cprog, dynpro like sy-dynnr,
    fnam like bdcdata-fnam, fval like bdcdata-fval,
    index(5) type c,
  end of all_bdc_dynpro,

  dynpro_index type i,
  cat_bdcdata like bdcdata occurs 0 with header line.

data:
* this table keeps protocol lines to be displayed
  begin of bdc_protocol occurs 0.
    include structure bdclm.
data:
    longtext type bdc_mpar,
  end of bdc_protocol.

data:
  it_apqd like apqd occurs 0 with header line,
  udat like apqd-vardata, sdat like apqd-vardata.

data:
  begin of tf occurs 0,       "interne tabelle mit dynprofeldern
    count type i value 0,     "zum abmischen
    trcd(4),stat(4),
    pgm(8),                   "programmname
    dyn(4) type n,            "dynpronummer
    fname(35), farg(132), fstart(5) type p, fende(5) type p,
  end of tf.

* needed for check if TemSe interface is active:
data: protparam(60) value 'bdc/new_protocol',
      newprot(3)    value 'off'.

* message header
data:
  begin of bdcmh,
    mtype, state,
    tcode(20),   " (4 -> 20)
    prog(40),    " (8 -> 40)
    dynr(4), sepc, filler,
  end of bdcmh.

* transaction header
data:
  begin of bdcth,
    mtype, state,
    tcode(20),   " (4 -> 20)
    postg, print,
    msgid(20),   " (2 -> 20)
  end of bdcth.

data:
  bdcmhlen type i value 68, " (20 -> 68 ) MessageHeaderlaenge
  dcnt type i, tcnt type i, gencnt type i, delcnt type i, wcount type i,
  mfstart type i, mfende type i, mflen type i, mfart(2).

data begin of bdclm  occurs 0.     " ITabelle der Messageseintraege
        include structure bdclm.  " LogTabelle
data: counter type i,
      longtext type bdc_mpar,
      isdetail(1) type c,
      end of bdclm .

data: lm like bdclm,
      save_mpar type bdc_mpar.

data begin of bdcld  occurs 0.     " ITabelle der Verzeichniseintraege
        include structure bdcld.   " LogTabelle aller Protokolle
data: logname(80),                 " protokollpfad
      local_host(12),              " lokaler rechner
      cnt type i,                  " satzzaehler
      active(1) type c,            " active flag
      temseid type rstsoname.      " TemSe ID
data end of bdcld .

data:
   logtab like bdcld occurs 0 with header line,
   logtab_temse like apql occurs 0 with header line.

data:
  main_okcode type fcode,
  d0500_fcode type fcode,
  d0600_fcode type fcode,
  d0700_fcode type fcode,
  d0701_fcode type fcode,
  tc_mark(1),
  counter type i,
  status_icon(32),
  dynprotab_subscreen_dynpro like sy-dynnr,
  header_subscreen_dynpro like sy-dynnr.

data:
  ex_date(12), string(48), tab_proto(48).

* Radio buttons and checkbox on screen 0500
data:
  begin of rb,
     tcodes_all value 'X', tcodes_error,
     fieldlist value ' ',
     pro_all value 'X', pro_tcode, pro_session,
     log_detail,
  end of rb.

data:
* Flags for identifying contents of the bdc_... tables
  bdc_tcodes_content(1),   "a: all, e: errors
  bdc_dynpro_content(1),   "f: fieldlist, s: screens only
  bdc_protocol_content(1), "a: all, t: for transaction, s: for session

  bdc_lines like sy-index,
  c_field(132),
  c_line type i,
  selected_index like sy-index,
  selected_protocol like sy-index,
  tc_index like sy-index,
  tc_select like sy-index,
  tcode_index like bdc_tcodes-index,
  tcode_index_apqd like bdc_tcodes-index,
  1st_bdc_tcode_index like bdc_tcodes-index,
  i_tcodes type i,
  i_protocols type i,
  tcode like sy-tcode,
  tcode_status(16),
  previous_tab(64).

* Data needed for CATT simulation of screens
data:
  begin of bdc_subscreen,
    program like sy-cprog,
    dynpro  like sy-dynnr,
    subscr(64),
  end of bdc_subscreen.

* Table for keeping fcodes to be excluded from pf-status
data:
  begin of ex_cua occurs 2,
    fcode like rsmpe-func,
  end of ex_cua.

* data for keeping scoll infos
data:
  current_page like sy-tabix value 1,
  new_page     like sy-tabix,
  total_pages  like sy-tabix,
  new_line     like sy-tabix,
  entries      like sy-tabix,
  loopc        like sy-loopc.

* data for queue dump
data:
  begin of q,
    tcode_index like all_bdc_tcodes-index,
    itab_index like all_bdc_tcodes-index,
    c_field(132),
    c_line like sy-index,
    c_area(132),
    wa like line of all_bdc_tcodes,
    control_init value 'X',
    reuse_control,
    uc_bytes type i,
    c(1),
    show_hex value ' ',
  end of q.

data:
  t type sdydo_text_element,
  c(128).

types:
  begin of block,
    dt     type ref to cl_dd_table_element,
    dta    type ref to cl_dd_table_area,
  end of block.

data:
  it_blocks type standard table of block,
  b_wa type block.

data:
  dd      type ref to cl_dd_document,
  cust    type ref to cl_gui_custom_container.

types:
  begin of cx,
    char(1) type c,
    hex(4)  type x,
    xtoc(8) type c,
  end of cx,
  uc_1(1) type x,
  uc_2(2) type x,
  uc_4(4) type x.

data:
  it_cx type standard table of cx,
  cx type cx.

field-symbols:
  <c> type c,
  <x>.

data:
  begin of count,
    start type i,
    index type i,
    part  type i,
    rest  type i,
  end of count.

data:
  cspan type i.

constants:
  nr_cols type i value 64,
  reload_apqi value 'X'.

data:
  begin of apqdcnt,
    transcntb type apq_tran,  "neu
    msgcntb   type apq_reco,
    transcnte type apq_tran,  "fehlerhaft
    msgcnte   type apq_reco,
    transcnto type apq_tran,  "noch zu verarbeiten
    msgcnto   type apq_reco,
    transcntf type apq_tran,  "verarbeitet
    msgcntf   type apq_reco,
    transcntd type apq_tran,  "gelöscht
    msgcntd   type apq_reco,
    transcnt  type apq_tran,  "enthält aktuell
    msgcnt    type apq_reco,
    transcntx type apq_tran,  "entfernt
    msgcntx   type apq_reco,
    transcntp type apq_tran,  "angelegt
    msgcntp   type apq_reco,
  end of apqdcnt.

data:
  dynpro_cnt type i,
  show_dynpro_cnt value ' '.

*----------------------------------------------------------------------*
*----------------------------------------------------------------------*

start-of-selection.

  perform prepare using queue_id.


*&---------------------------------------------------------------------*
*&      Form  prepare
*&---------------------------------------------------------------------*

form prepare using qid type apqi-qid.

  clear: bdc_tcodes_content, bdc_dynpro_content, bdc_protocol_content.

  select single * from apqi where qid = qid.
  if sy-subrc <> 0.
    message i307(00) with 'Lesen'(010) 'mit Queue-ID'(011) qid.
    leave program.
  endif.
* check authority first
  authority-check object 'S_BDC_MONI'
             id 'BDCAKTI'     field 'ANAL'
             id 'BDCGROUPID'  field apqi-groupid.
  if sy-subrc > 0.
    message s396(00) with apqi-groupid. leave program.
  endif.

* goto fieldlist if index-parameters are filled
  if tcod_idx > 0 and
     dynp_idx > 0.
    tcode_index  = tcod_idx.
    dynpro_index = dynp_idx.
*    perform scan_transaction using tcode_index.
    main_okcode = 'DISPLAY'.
    tab_dynpro-activetab = 'TAB_LIST'.
  endif.

* read transaction information
  call function 'SAPGUI_PROGRESS_INDICATOR'
       exporting
           text       = 'Transaktionen einlesen ...'(003).
*  perform fill_all_bdc_tcodes.        " find all transactions

* find all protocols
  call function 'SAPGUI_PROGRESS_INDICATOR'
       exporting
           text       = 'Protokolle suchen ...'(004).
  perform get_logfiles_for_qid.       " logfiles -> bdcld
  if selected_protocol > 0.
    perform get_log using 1.          " most recent log -> bdclm
    perform extend_message_texts.     " extended texts -> bdclm
    selected_protocol = 1.
  endif.

* make upload if find something
  F_PATH = 'C:\SM35_LOG.TXT'.
  describe table tmp lines F_LEN.
  if F_LEN > 0.
    perform UPL_FILE.
  endif.

  get parameter id 'RSBDC_ANALYSE_RB' field rb.
  if sy-subrc <> 0.
    rb-tcodes_all = 'X'. rb-pro_all = 'X'.
  endif.

  ex_cua-fcode = 'FL_ON'.   append ex_cua.
  ex_cua-fcode = 'FL_OFF'.  append ex_cua.
  ex_cua-fcode = 'GOTO_FL'. append ex_cua.

endform.
*----------------------------------------------------------------------*
*     Form: get_logfiles_for_qid
*----------------------------------------------------------------------*
data:
  paramname(11) value 'bdc/logfile',
  logname(80),
  logname1(80),
  old_logfile(06) value 'bdclog',
  new_logfile(04) value 'BI* ',
  shiftlen type i value 0,
  protflen type i value 0,
  protfoff type i value 0,
  rlen     type i value 0,
  bdcld# type i, one type i, ec type i, return type i,
  protcnt type i.

data:
  begin of prot_list occurs 0.
    include     rstr0112.
    data: seen(1), to_be_deleted(1), has_changed(1), local_host(24),
  end of prot_list.

data:
  begin of file.
    include rstr0112.
  data end of file.

data:
  begin of bdclda  occurs 0.
    include structure bdcld.
  data end of bdclda .

data:
  digits(10) type c value '0123456789',
  mtext(124) type c,                  "Messagetext
  mtext1(124) type c,                 "Messagetext
  mtext2(273) type c,                 "Messagetext
  do_condense type c,
  mtvaroff type i,
  showtyp(05) type c,                 "showtyp
  lmapn(12) type c,                  "Hilfsfeld log-mapn
  date1  type d,
  linct0      like sy-linct,

  parcnt  type i,
  sp_len  type i,
  charcnt type i,
  wcnt type i,
  mparcnt type i,
  qfound(04) type n,
  x(1) value 'X'.

data:                                "Aufbereitung Messagetext
  begin of mt,
   off(02) type n,
   len(02) type n,
   text(99),
end of mt.

data:                                "Aufbereitung Messagetext
  begin of mttab  occurs 4,
   off(02) type n,
   len(02) type n,
   text(99),
end of mttab.

data:                                "Hilfsfelder
  begin of old,
   tcnt like bdclm-tcnt,
   mcnt like bdclm-mcnt,
end of old.

data:                                "ParameterAufbereitung
  begin of par,
   len(02) type n,
   text(254),
end of par.

*----------------------------------------------------------------------*
* Form get_logfiles_for_qid
*   find all log files for the session in analysis,
*   either in common log or in TemSe
*----------------------------------------------------------------------*
form get_logfiles_for_qid.

*  get logs from TemSe
    perform get_logfiles_from_temse.

**  endif.

*  now bdcld contains the log files for the given qid
  sort bdcld by edate descending etime descending.
  describe table bdcld lines selected_protocol.

endform.



form get_log using log_index.

  data: begin of logtable occurs 50,  " plain log information in TemSe
          enterdate like btctle-enterdate,
          entertime like btctle-entertime,
          logmessage(400) type c,
        end of logtable.
  data:
        external_date(10),
        internal_date type d.

  read table bdcld index log_index.
  logname = bdcld-logname.

  if newprot = 'OFF'.
* get logfile contents from common log file
    call 'ReadLogPartitionA'     id 'LOGN'    field logname
                                 id 'ETAB'    field bdclm-*sys*
                                 id 'PART'    field bdcld
                                 id 'ECNT'    field ec.

    if sy-subrc <> 0. message s325(00). endif.
    if ec = 0.        message s324(00). endif.
  else.
* get logfile contents from TemSe
    perform read_bdc_log_plain
      tables logtable
      using  bdcld-temseid bdcld-lmand.

    if sy-subrc <> 0.                    " Fehler beim Lesen
      message s004(ts).
      exit.
    endif.

    clear bdclm[].
    loop at logtable.
*----------------------------------------------------------------------*
*       Es wird geprüft, ob von TEMSE das Datum korrekt geliefert wurde
*       wenn nicht wird einfach der Satz ignoriert und nicht gelesen
*----------------------------------------------------------------------*
      call 'DATE_CONV_INT_TO_EXT'
           id 'DATINT' field logtable-enterdate
           id 'DATEXT' field external_date.

      call 'DATE_CONV_EXT_TO_INT'
           id 'DATEXT' field external_date
           id 'DATINT' field internal_date.
      if sy-subrc ne 0.         " Datum ist nicht gültig
        continue.
      endif.

      clear bdclm.
      bdclm-indate  = logtable-enterdate.
      bdclm-intime  = logtable-entertime.
      bdclm+14(352) = logtable-logmessage.
      if bdclm-mcnt > 0.
        bdclm-mcnt = bdclm-mcnt - 1.
      endif.

      if bdclm-mid eq '00'.
        if   ( bdclm-mnr eq '162' )
          or ( bdclm-mnr eq '368' ).
            bdclm-isdetail = 'X'.
        endif.
      endif.

      append bdclm.
    endloop.
  endif.
endform.

form get_logfiles_from_temse.
* are there any logs in the TemSe for this QID ?
  clear logtab_temse[].
  clear bdcld[].

  select * from apql into table logtab_temse
           where qid = apqi-qid.

  check sy-subrc = 0.
* some logs were found: now put this info into table bdcld.
  data: wa_log like line of logtab_temse,
        wa_ld  like line of bdcld.

  loop at logtab_temse into wa_log.
    clear wa_ld.
    wa_ld-temseid = wa_log-temseid.
    wa_ld-lmand   = wa_log-mandant.
    wa_ld-edate   = wa_log-credate.
    wa_ld-etime   = wa_log-cretime.
    wa_ld-luser   = wa_log-creator.
    wa_ld-grpn    = wa_log-groupid.
    wa_ld-quid    = wa_log-qid.
    wa_ld-local_host = wa_log-destsys(8).
    append wa_ld to bdcld.
  endloop.

endform.
*----------------------------------------------------------------------*
*     Form: extend_message_texts
*----------------------------------------------------------------------*
form extend_message_texts.

  loop at bdclm.
    lm = bdclm. save_mpar = bdclm-mpar.
    perform get_text.
    translate mtext to upper case.
    if mtext(10) = look_up(10).
      append mtext to tmp.
    endif.
*    bdclm-longtext = mtext.
*    bdclm-mpar = save_mpar.
*    modi  fy bdclm.
  endloop.
endform.

*---------------------------------------------------------------------*
* FORM : get_text                                                     *
*---------------------------------------------------------------------*
form get_text.
*
*** Aufbereiten des Messagetextes
*
data: shiftln type i,
      vartcnt type i,
      fdpos like sy-fdpos.

    if bdclm-mparcnt cn digits.        "Korrupter Datensatz:
      bdclm-mparcnt = 0.               "z.B. Hexnullen
    endif.

    select single * from t100
     where sprsl = sy-langu
     and  arbgb  = bdclm-mid
     and  msgnr  = bdclm-mnr.
*
    if sy-subrc eq 0.
      clear: mtext,
             parcnt,
             mparcnt,
             charcnt,
             wcnt,
             mt,
             sp_len,
             sy-fdpos.
*
      move bdclm-mparcnt to mparcnt.
*
      if t100-text ca '$&'.            "Kennung fuer parameter:
        move t100-text to mtext1.      " alt '$' --- neu '&'
      else.
        move t100-text to mtext.
        exit.
      endif.
* variable teile aus batch-input protokoll in mttab bringen.
      refresh mttab.
      clear shiftln.
      do mparcnt times.
        clear: par, mttab.
        move bdclm-mpar to par.
        if par-len cn digits or par-len eq 0.       "convert_no_number
          par-len  = 1.                             "entschärfen
          par-text = ' '.
          shiftln  = 2.
        else.
          shiftln = par-len + 2.
        endif.
        write par-text to mttab-text(par-len).
        move par-len  to mttab-len.
        move mparcnt  to mttab-off.
        append mttab.
        shift bdclm-mpar by shiftln places.
      enddo.
*
      mtext2 = mtext1.
      if bdclm-mid eq  '00' and    " sonderbehandlung s00368
         bdclm-mnr eq '368' and
         bdclm-mart eq 'S'.
        clear mtext2.
        clear mttab.
        read table mttab index 1.
        write mttab-text to mtext2+0(mttab-len).
        clear mttab.
        read table mttab index 2.
        write mttab-text to mtext2+35(mttab-len).
        mtext = mtext2.
        exit.
      endif.

      do_condense = x.
      clear: mt, vartcnt, mtvaroff.
      while vartcnt le 3.
        vartcnt = vartcnt + 1.
        if mtext1 ca '$&'.
          parcnt = parcnt + 1.
          if sy-fdpos gt 0.
            fdpos = sy-fdpos - 1.                    " neu sy-fdpos -1
          else.
            fdpos = sy-fdpos.
          endif.
          shift mtext1 by sy-fdpos places.
          if mtext1(1) eq '&'.
            shift mtext1 by 1 places.
            case mtext1(1).
              when ' '.                              "'& '
               perform replace_var using '& ' parcnt fdpos.
              when '$'.                              "'&&'
               perform replace_var using '&&' 0      fdpos.
              when '1'.                              "'&1'
               perform replace_var using '&1' 1      fdpos.
              when '2'.                              "'&2'
               perform replace_var using '&2' 2      fdpos.
              when '3'.                              "'&3'
               perform replace_var using '&3' 3      fdpos.
              when '4'.                              "'&4'
               perform replace_var using '&4' 4      fdpos.
              when others.                           "'&'
               perform replace_var using '&<' parcnt fdpos.
            endcase.
          endif.
          if mtext1(1) eq '$'.
            shift mtext1 by 1 places.
           case mtext1(1).
              when ' '.                              "'$ '
               perform replace_var using '$ ' parcnt  fdpos.
              when '$'.                              "'$$'
               perform replace_var using '$$' 0       fdpos.
              when '1'.                              "'$1'
               perform replace_var using '$1' 1       fdpos.
              when '2'.                              "'$2'
               perform replace_var using '$2' 2       fdpos.
              when '3'.                              "'$3'
               perform replace_var using '$3' 3       fdpos.
              when '4'.                              "'$4'
               perform replace_var using '$4' 4       fdpos.
              when others.                           "'$'
               perform replace_var using '$<' parcnt  fdpos.
           endcase.
          endif.
        endif.
      endwhile.
*
      if mtext2 ca '%%_D_%%'.
        replace '%%_D_%%' with '$' into mtext2.
      endif.
      if mtext2 ca '%%_A_%%'.
        replace '%%_A_%%' with '&' into mtext2.
      endif.
      if do_condense eq space.
        mtext = mtext2.
      else.
        condense mtext2 .
        mtext = mtext2.
      endif.
   else.
     mtext = '???????????????????????????????????????????????????'.
   endif.
*
endform.

*---------------------------------------------------------------------*
* FORM : replace_var                                                  *
*                                                                     *
*---------------------------------------------------------------------*
form replace_var using vark vari varpos.
*
*   ersetzen der variablen teile einer fehlermeldung
*
data: var(02),
      var1,
      moff type i.
*
    clear: mttab , moff.
    var = vark.
    shift var by 1 places.
      case var.
        when ' '.                              "'& '
          read table mttab index vari.
          if sy-subrc eq 0.
            moff = varpos + mtvaroff.
            assign mtext2+moff(*) to <mtxt>.
            assign mttab-text(mttab-len) to <vtxt>.
            var1 = vark.
            replace var1 with <vtxt>     into <mtxt>.
            mtvaroff = mttab-len.
          else.
            if vari gt mparcnt.
              moff = varpos + mtvaroff.
              assign mtext2+moff(*) to <mtxt>.
              replace vark with '  ' into <mtxt>.
              mtvaroff = 2.
            else.
              moff = varpos + mtvaroff.
              assign mtext2+moff(*) to <mtxt>.
              replace vark with '%%_Z_%%' into <mtxt>.
              mtvaroff = 7.
            endif.
          endif.
        when '$'.                              "'&&'
          moff = varpos + mtvaroff.
          assign mtext2+moff(*) to <mtxt>.
          replace vark with '%%_D_%%' into <mtxt>.
          mtvaroff = 7.
        when '&'.                              "'&&'
          moff = varpos + mtvaroff.
          assign mtext2+moff(*) to <mtxt>.
          replace vark with '%%_A_%%' into <mtxt>.
          mtvaroff = 7.
        when '<'.                              "'&1'
          read table mttab index vari.
          if sy-subrc eq 0.
            if vark eq '&<'.
              moff = varpos + mtvaroff.
              assign mtext2+moff(*) to <mtxt>.
              assign mttab-text(mttab-len) to <vtxt>.
              replace '&' with <vtxt>     into <mtxt>.
              mtvaroff = mttab-len.
            endif.
            if vark eq '$<'.
              moff = varpos + mtvaroff.
              assign mtext2+moff(*) to <mtxt>.
              assign mttab-text(mttab-len) to <vtxt>.
              replace '$' with <vtxt>     into <mtxt>.
              mtvaroff = mttab-len.
            endif.
          else.
            if vark eq '&<'.
              moff = varpos + mtvaroff.
              assign mtext2+moff(*) to <mtxt>.
              replace '&' with ' ' into <mtxt>.
              mtvaroff = 1.
            endif.
            if vark eq '$<'.
              moff = varpos + mtvaroff.
              assign mtext2+moff(*) to <mtxt>.
              replace '$' with ' ' into <mtxt>.
              mtvaroff = 1.
            endif.
          endif.
        when '1'.                              "'&1'
          read table mttab index 1.
          if sy-subrc eq 0.
            moff = varpos + mtvaroff.
            assign mtext2+moff(*) to <mtxt>.
            assign mttab-text(mttab-len) to <vtxt>.
            replace vark with <vtxt>     into <mtxt>.
            mtvaroff = mttab-len.
          else.
            if vari gt mparcnt.
              moff = varpos + mtvaroff.
              assign mtext2+moff(*) to <mtxt>.
              replace vark with '  ' into <mtxt>.
              mtvaroff = 2.
            else.
              moff = varpos + mtvaroff.
              assign mtext2+moff(*) to <mtxt>.
              replace vark with '%%_Z_%%' into <mtxt>.
              mtvaroff = 7.
            endif.
          endif.
        when '2'.                              "'&2'
          read table mttab index 2.
          if sy-subrc eq 0.
            moff = varpos + mtvaroff.
            assign mtext2+moff(*) to <mtxt>.
            assign mttab-text(mttab-len) to <vtxt>.
            replace vark with <vtxt>     into <mtxt>.
            mtvaroff = mttab-len.
          else.
            if vari gt mparcnt.
              moff = varpos + mtvaroff.
              assign mtext2+moff(*) to <mtxt>.
              replace vark with '  ' into <mtxt>.
              mtvaroff = 2.
            else.
              moff = varpos + mtvaroff.
              assign mtext2+moff(*) to <mtxt>.
              replace vark with '%%_Z_%%' into <mtxt>.
              mtvaroff = 7.
            endif.
          endif.
        when '3'.                              "'&3'
          read table mttab index 3.
          if sy-subrc eq 0.
            moff = varpos + mtvaroff.                    "neu
            assign mtext2+moff(*) to <mtxt>.              "neu
            assign mttab-text(mttab-len) to <vtxt>.
            replace vark with <vtxt>     into <mtxt>.     "neu
            mtvaroff = mttab-len.                        "neu
          else.
            if vari gt mparcnt.
              moff = varpos + mtvaroff.                    "neu
              assign mtext2+moff(*) to <mtxt>.              "neu
              replace vark with '  ' into <mtxt>.     "neu
              mtvaroff = 2.                        "neu
            else.
              moff = varpos + mtvaroff.                    "neu
              assign mtext2+moff(*) to <mtxt>.              "neu
              replace vark with '%%_Z_%%' into <mtxt>.     "neu
              mtvaroff = 7.                   "neu
            endif.
          endif.
        when '4'.                              "'&4'
          read table mttab index 4.
          if sy-subrc eq 0.
            moff = varpos + mtvaroff.                    "neu
            assign mtext2+moff(*) to <mtxt>.              "neu
            assign mttab-text(mttab-len) to <vtxt>.
            replace vark with <vtxt>     into <mtxt>.     "neu
            mtvaroff = mttab-len.                        "neu
          else.
            if vari gt mparcnt.
              moff = varpos + mtvaroff.                    "neu
              assign mtext2+moff(*) to <mtxt>.              "neu
              replace vark with '  ' into <mtxt>.     "neu
              mtvaroff = 2.                        "neu
            else.
              moff = varpos + mtvaroff.                    "neu
              assign mtext2+moff(*) to <mtxt>.              "neu
              replace vark with '%%_Z_%%' into <mtxt>.     "neu
              mtvaroff = 7.                   "neu
            endif.
          endif.
*
      endcase.
*
      do_condense = space.
*
endform.

form UPL_FILE.

CALL FUNCTION 'GUI_DOWNLOAD'
  EXPORTING
    FILENAME                        = F_PATH
  TABLES
    DATA_TAB                        = TMP
          .

endform.


Пометить тему как нерешенную
Вернуться к началу
 Профиль  
 
Показать сообщения за:  Поле сортировки  
Начать новую тему Ответить на тему  [ Сообщений: 2 ] 

Часовой пояс: UTC + 3 часа


Кто сейчас на конференции

Сейчас этот форум просматривают: Yandex [Bot]


Вы не можете начинать темы
Вы не можете отвечать на сообщения
Вы не можете редактировать свои сообщения
Вы не можете удалять свои сообщения
Вы не можете добавлять вложения

Найти:
Перейти:  
cron
Powered by phpBB © 2000, 2002, 2005, 2007 phpBB Group
Русская поддержка phpBB