Programm "ZSAPLINK"

Aus SAP-Wiki
Zur Navigation springenZur Suche springen
*/---------------------------------------------------------------------\
*|   This file is part of SAPlink.                                     |
*|                                                                     |
*|   SAPlink is free software; you can redistribute it and/or modify   |
*|   it under the terms of the GNU General Public License as published |
*|   by the Free Software Foundation; either version 2 of the License, |
*|   or (at your option) any later version.                            |
*|                                                                     |
*|   SAPlink is distributed in the hope that it will be useful,        |
*|   but WITHOUT ANY WARRANTY; without even the implied warranty of    |
*|   MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the     |
*|   GNU General Public License for more details.                      |
*|                                                                     |
*|   You should have received a copy of the GNU General Public License |
*|   along with SAPlink; if not, write to the                          |
*|   Free Software Foundation, Inc.,                                   |
*|   51 Franklin St, Fifth Floor, Boston, MA  02110-1301  USA          |
*\---------------------------------------------------------------------/
*/---------------------------------------------------------------------\
*| /  __ \           | |      (_) |         | |                        |
*| | /  \/ ___  _ __ | |_ _ __ _| |__  _   _| |_ ___  _ __ ___         |
*| | |    / _ \| '_ \| __| '__| | '_ \| | | | __/ _ \| '__/ __|        |
*| | \__/\ (_) | | | | |_| |  | | |_) | |_| | || (_) | |  \__ \        |
*|  \____/\___/|_| |_|\__|_|  |_|_.__/ \__,_|\__\___/|_|  |___/        |
*|---------------------------------------------------------------------|
*| Lead Developers : ed herrmann                                       |
*|                        ewherrmann+saplinkcred@gmail.com             |
*|                   dan mcweeney                                      |
*|                        daniel.mcweeney+saplinkcred@gmail.com        |
*|---------------------------------------------------------------------|
*| For a full list of contributors visit:                              |
*|                                                                     |
*| project homepage: <a href="http://saplink.org">http://saplink.org</a>                                |
*| discussion group: <a href="http://groups.google.com/group/saplink">http://groups.google.com/group/saplink</a>            |
*| project wiki:     <a href="https://wiki.sdn.sap.com/wiki/display/HOME/SAPlink%7C">https://wiki.sdn.sap.com/wiki/display/HOME/SAPlink%7C</a>
*\---------------------------------------------------------------------/
REPORT  ZSAPLINK.

*/------------------------DATA----------------------------\
TABLES: SSCRFIELDS, E071, E07T.

TYPE-POOLS: icon, slis, sabc, stms, trwbo.

types: begin of t_plugin,
         object type KO100-object,
         text type KO100-text,
       end of t_plugin.

types: begin of t_objectTable,
         classname type string,
         object type ko100-object,
         text type ko100-text,
       end of t_objectTable.

types: begin of t_nuggetObject,
          objType type string,
          objName type string,
          exists type flag,
       end of t_nuggetObject.
*addition of package data
****   Read all objects of the package
types: begin of t_objects_package,
          select     type char1,
          object     type tadir-object,
          object_txt type string,
          obj_name   type tadir-obj_name,
          srcsystem  type tadir-srcsystem,
          down_flag  type char1,
          status     type char1,
          msg        type string,
       end of t_objects_package.

data objects_package type table of t_objects_package.
data packageLine type t_objects_package.
field-symbols: <obj> like line of objects_package.
data tabletypeline type ko105.
data tabletypesin type table of ko105.
data tabletypesout type tr_object_texts.
data tabletypeoutline type ko100.
data lt_fieldcat  type          slis_t_fieldcat_alv.
data ls_fieldcat  like line of  lt_fieldcat.
data ls_layout    type          slis_layout_alv.
data lv_count type i.
data lv_pers  type i.

*end of data addition for packages
*addition of Transport data
types: begin of t_requestObject,
          object   type e071-object,
          OBJ_NAME type e071-obj_name,
       end of t_requestObject.

types: tt_requestObject TYPE TABLE OF t_requestObject.

data it_requestObject type table of t_requestObject.
data wa_requestObject type t_requestObject.

*end of data addition for transport

data pluginLine type t_plugin.
data pluginList type table of t_plugin.
data hidid(3) type c.
data currentTab type string.
data isSlinkee(1) type c value ' '.
data objectTable type table of t_objectTable.
data objectLine type t_objectTable.
data _objName type string.
data _objType type string.
data nuggetName type string.
data targetObject type ref to zsaplink.
data xml type string.
data excClass type ref to ZCX_SAPLINK.
data errorMsg type string.
data statusMsg type string.
data _pluginExists type flag.
data _objectExists type flag.
data _flag type flag.

data errorFlag type flag.
data it_nuggetObject type table of t_nuggetObject.
data wa_nuggetObject type t_nuggetObject.

data defFilename type string.
data retFileName type string.
data retPath type string.
data retFullpath type string.
data retUserAct type i.
data retFileTable type FILETABLE.
data retRc type sysubrc.
data retUserAction type i.

data nugg type ref to zsaplink_nugget.
data sTemp type string.
data anXMLDoc type ref to if_ixml_document.
data ixmlDocument type ref to if_ixml_document.

data foo type ref to data.
data len type i.

data: l_marker type i,
      l_offset type i,
      l_total_offset type i.

DATA:
  es_selected_request TYPE trwbo_request_header,
  es_selected_task TYPE trwbo_request_header,
  iv_organizer_type TYPE trwbo_calling_organizer,
  is_selection TYPE trwbo_selection.

*\--------------------------------------------------------------------/


*/------------------------SELECTION SCREEN----------------------------\

SELECTION-SCREEN BEGIN OF TABBED BLOCK tabb FOR 20 LINES.
SELECTION-SCREEN TAB (17) text-tb2 USER-COMMAND nugg
                     DEFAULT SCREEN 120.
SELECTION-SCREEN TAB (17) text-tb1 USER-COMMAND obj
                     DEFAULT SCREEN 110.
SELECTION-SCREEN END OF BLOCK tabb.

*Slinkee tab
SELECTION-SCREEN BEGIN OF SCREEN 110 AS SUBSCREEN.
  selection-screen begin of block main with frame.
    selection-screen begin of block splk with frame title text-slk.
      parameters Import type c RADIOBUTTON GROUP 2 default 'X'
        user-command updown.
      parameters Export type c RADIOBUTTON GROUP 2.
    selection-screen end of block splk.

    selection-screen begin of block opt with frame title text-opt.
      parameters filename(300) lower case type c modif id did.
      parameters OverWr type c as checkbox modif id did.
      parameters plugin type KO100-object modif id uid.
      parameters objName(40) type c modif id uid.
    selection-screen end of block opt.
  selection-screen end of block main.
SELECTION-SCREEN END OF SCREEN 110.

*Nugget tab
SELECTION-SCREEN BEGIN OF SCREEN 120 AS SUBSCREEN.
  selection-screen begin of block main2 with frame.
    selection-screen begin of block splk2 with frame title text-slk.
        parameters NugI type c RADIOBUTTON GROUP 3 default 'X'
          user-command updown.
        parameters nugD type c radiobutton group 3.
        selection-screen uline.
        parameters nugC type c radiobutton group 3.
        parameters NugA type c RADIOBUTTON GROUP 3.
        parameters nugP type c radiobutton group 3.
        parameters nugR type c radiobutton group 3.
    selection-screen end of block splk2.

    selection-screen begin of block opt2 with frame title text-opt.
      parameters NuggNam(300) type c modif id nnm.
      parameters nPlugIn type  KO100-object modif id npg.
      parameters NObjNam(40) type c modif id npg.
*      parameters nPlugIn type  KO100-object modif id npg.
      parameter package      type tadir-devclass modif id npc.
      select-options  ReqNugg for E071-TRKORR NO INTERVALS
        NO-EXTENSION modif id rnm.
      parameter NugFile(300) lower case type c modif id nfl.
      parameters nOvrWr type c as checkbox modif id now.
    selection-screen end of block opt2.
  selection-screen end of block main2.
SELECTION-SCREEN END OF SCREEN 120.
*\--------------------------------------------------------------------/


*/----------------------selection screen events-----------------------\
initialization.
  call method zsaplink=>getplugins(
    changing objectTable = objectTable ).

  IMPORT isSlinkee FROM MEMORY ID 'ISSLNK'.

  if isSlinkee = 'X'.
    tabb-dynnr = 110.
    tabb-activetab = 'OBJ'.
  else.
    tabb-dynnr   = 120.
    tabb-activetab = 'NUGG'.
  endif.

at selection-screen.
  case SSCRFIELDS-UCOMM.
    when 'OBJ'.
      isSlinkee = 'X'.
    when 'NUGG'.
      isSlinkee = ' '.
  endcase.
  EXPORT isSlinkee TO MEMORY ID 'ISSLNK'.

AT SELECTION-SCREEN OUTPUT.
*** hide/show fields according to current selection
  if Import = 'X'.
    hidID = 'UID'.
  elseif Export = 'X'.
    hidID = 'DID'.
  endif.

  LOOP AT SCREEN.
    if SCREEN-GROUP1 = hidID.
      SCREEN-ACTIVE = '0'.
      SCREEN-INVISIBLE = '1'.
      MODIFY SCREEN.
    endif.
  ENDLOOP.

  loop at screen.
    if NugC = 'X'.
      if screen-group1 = 'NNM'.
        SCREEN-ACTIVE = '1'.
        SCREEN-INVISIBLE = '0'.
        MODIFY SCREEN.
       elseif screen-group1 = 'NPG' or screen-group1 = 'NFL'
         or screen-group1 = 'NOW' or screen-group1 = 'NPC'
         or screen-group1 = 'RNM'.
        SCREEN-ACTIVE = '0'.
        SCREEN-INVISIBLE = '1'.
        MODIFY SCREEN.
       endif.
    elseif NugI = 'X'.
      if screen-group1 = 'NFL' or screen-group1 = 'NOW'.
        SCREEN-ACTIVE = '1'.
        SCREEN-INVISIBLE = '0'.
        MODIFY SCREEN.
       elseif screen-group1 = 'NNM' or screen-group1 ='NPG'
          or screen-group1 = 'NPC' or screen-group1 = 'RNM'.
        SCREEN-ACTIVE = '0'.
        SCREEN-INVISIBLE = '1'.
        MODIFY SCREEN.
       endif.
    elseif NugA = 'X'.
      if screen-group1 = 'NFL' or screen-group1 = 'NPG'.
        SCREEN-ACTIVE = '1'.
        SCREEN-INVISIBLE = '0'.
        MODIFY SCREEN.
      elseif screen-group1 = 'NNM' or screen-group1 = 'NOW'
         or screen-group1 = 'NPC' or screen-group1 = 'RNM'.
        SCREEN-ACTIVE = '0'.
        SCREEN-INVISIBLE = '1'.
        MODIFY SCREEN.
      endif.
    elseif NugP = 'X'.
      if screen-group1 = 'NFL' or screen-group1 = 'NPC'.
        SCREEN-ACTIVE = '1'.
        SCREEN-INVISIBLE = '0'.
        MODIFY SCREEN.
      elseif screen-group1 = 'NNM' or screen-group1 = 'NOW'
        or screen-group1 = 'NPG' or screen-group1 = 'RNM'.
        SCREEN-ACTIVE = '0'.
        SCREEN-INVISIBLE = '1'.
        MODIFY SCREEN.
      endif.
    elseif NugD = 'X'.
      if screen-group1 = 'NFL'.
        SCREEN-ACTIVE = '1'.
        SCREEN-INVISIBLE = '0'.
        MODIFY SCREEN.
       elseif screen-group1 = 'NNM' or screen-group1 ='NPG'
        or screen-group1 = 'NOW' or screen-group1 = 'NPC'
        or screen-group1 = 'RNM'.
        SCREEN-ACTIVE = '0'.
        SCREEN-INVISIBLE = '1'.
        MODIFY SCREEN.
       endif.
    elseIf NugR = 'X'.
      if screen-group1 = 'NFL' or screen-group1 = 'RNM'.
        SCREEN-ACTIVE = '1'.
        SCREEN-INVISIBLE = '0'.
        MODIFY SCREEN.
      elseif screen-group1 = 'NNM' or screen-group1 = 'NOW'
        or screen-group1 = 'NPG' or screen-group1 = 'NPC'.
        SCREEN-ACTIVE = '0'.
        SCREEN-INVISIBLE = '1'.
        MODIFY SCREEN.
      endif.
    endif.
  endloop.

*** value request for input fields
at selection-screen on value-request for plugin.
  refresh pluginList.
  loop at objectTable into objectLine.
    move-corresponding objectLine to pluginLine.
    append pluginLine to pluginList.
  endloop.

  CALL FUNCTION 'F4IF_INT_TABLE_VALUE_REQUEST'
   EXPORTING
     retfield               = 'OBJECT'
     window_title           = 'Installed Plugins'
     dynpprog    = sy-repid
     dynpnr      = '1000'
     dynprofield = 'PLUGIN'
     value_org   = 'S'
   TABLES
     value_tab              =  pluginList
   EXCEPTIONS
     PARAMETER_ERROR        = 1
     NO_VALUES_FOUND        = 2
     OTHERS                 = 3.

at selection-screen on value-request for Nplugin.
  refresh pluginList.
  loop at objectTable into objectLine.
    move-corresponding objectLine to pluginLine.
    append pluginLine to pluginList.
  endloop.

  CALL FUNCTION 'F4IF_INT_TABLE_VALUE_REQUEST'
   EXPORTING
     retfield               = 'OBJECT'
     window_title           = 'Installed Plugins'
     dynpprog    = sy-repid
     dynpnr      = '1000'
     dynprofield = 'NPLUGIN'
     value_org   = 'S'
   TABLES
     value_tab              =  pluginList
   EXCEPTIONS
     PARAMETER_ERROR        = 1
     NO_VALUES_FOUND        = 2
     OTHERS                 = 3.

at selection-screen on value-request for filename.
  call method CL_GUI_FRONTEND_SERVICES=>FILE_OPEN_DIALOG
      exporting
        MULTISELECTION = abap_false
        FILE_FILTER = '*.slnk'
        DEFAULT_EXTENSION = 'slnk'
      changing
        FILE_TABLE = retFileTable
        rc = retRc
        user_Action = retUserAction.
  read table retFileTable into fileName index 1.

at selection-screen on value-request for NugFile.
  call method CL_GUI_FRONTEND_SERVICES=>FILE_OPEN_DIALOG
      exporting
        MULTISELECTION = abap_false
        FILE_FILTER = '*.nugg'
        DEFAULT_EXTENSION = 'nugg'
      changing
        FILE_TABLE = retFileTable
        rc = retRc
        user_Action = retUserAction.
  read table retFileTable into NugFile index 1.

* begin-->search help on objname according to selected plugin
* provided by Michael Diehl
AT SELECTION-SCREEN ON VALUE-REQUEST FOR objname.
 DATA l_object_type LIKE  euobj-id.
* l_object_type = plugin.  "commented ewH

*ewH-->get most current value of plugin param
 perform get_current_screen_value using 'PLUGIN' '0110'
                               changing l_object_type.

 IF  l_object_type IS NOT INITIAL.
*  rrq --> START of implementation for object specific value help

   data: temp_object type ko100-object.
*   move the object type to a field like the ObjectTable expects
   temp_object = l_object_type.
   read table objectTable into objectLine with key object = temp_object.
    IF sy-subrc = 0.
*    if it is found...intanciate it so you can call the right value help
     create object targetObject type (objectLine-classname)
        exporting name = _objName.
      _objType = l_object_type.
      CALL METHOD TARGETOBJECT->VALUEHELP
        EXPORTING
          I_OBJTYPE = _objType
        RECEIVING
          E_OBJNAME = _objName.
        objName = _objName.
     ENDIF.

*commented out...moved logic to instance method of ZSAPLINK.  to be overwritten by
*objects that don't use the repository Info_system f4 Function
*   CALL FUNCTION 'REPOSITORY_INFO_SYSTEM_F4'
*     EXPORTING
*       object_type           = l_object_type
*       object_name           = objname
*       suppress_selection    = 'X'
*       use_alv_grid          = 
*       without_personal_list = 
*     IMPORTING
*       object_name_selected  = objname
*     EXCEPTIONS
*       cancel                = 1.
*<-- rrq end of implentation for object specific value help
 ENDIF.


AT SELECTION-SCREEN ON VALUE-REQUEST FOR nobjnam.
 DATA l_object_type LIKE  euobj-id.
* l_object_type = nplugin. "commented ewH

*ewH-->get most current value of plugin param
 perform get_current_screen_value using 'NPLUGIN' '0120'
                               changing l_object_type.

 IF  l_object_type IS NOT INITIAL.
*  rrq --> START of implementation for object specific value help

   data: temp_object type ko100-object.
*   move the object type to a field like the ObjectTable expects
   temp_object = l_object_type.
   read table objectTable into objectLine with key object = temp_object.
    IF sy-subrc = 0.
*    if it is found...intanciate it so you can call the right value help
     create object targetObject type (objectLine-classname)
        exporting name = _objName.
      _objType = l_object_type.
      CALL METHOD TARGETOBJECT->VALUEHELP
        EXPORTING
          I_OBJTYPE = _objType
        RECEIVING
          E_OBJNAME = _objName.
        nobjnam = _objName.


     ENDIF.
*commented out...moved logic to instance method of ZSAPLINK.  to be overwritten by
*objects that don't use the repository Info_system f4 Function
*   CALL FUNCTION 'REPOSITORY_INFO_SYSTEM_F4'
*     EXPORTING
*       object_type           = l_object_type
*       object_name           = objname
*       suppress_selection    = 'X'
*       use_alv_grid          = 
*       without_personal_list = 
*     IMPORTING
*       object_name_selected  = objname
*     EXCEPTIONS
*       cancel                = 1.
*<-- rrq end of implentation for object specific value help
 ENDIF.
* <--end of search help on objname according to selected plugin
* provided by Michael Diehl

at selection-screen on value-request for ReqNugg-low.
  iv_organizer_type = 'W'.
*  is_selection-reqstatus = 'R'.
  CALL FUNCTION 'TR_PRESENT_REQUESTS_SEL_POPUP'
    EXPORTING
      iv_organizer_type   = iv_organizer_type
      is_selection        = is_selection
    IMPORTING
      es_selected_request = es_selected_request
      es_selected_task    = es_selected_task.

  ReqNugg-low = es_selected_request-trkorr.

*\--------------------------------------------------------------------/

*/----------------------main------------------------------------------\
start-of-selection.
  clear: errorMsg, statusMsg.
************* S L I N K E E *************
  if isSlinkee is not initial.
    _objName = objName.
*   Export slinkee
    if Export = 'X'.
      if plugin is initial.
        message s208(00) with 'object type required'.
        exit.
      elseif _objName is initial.
        message s208(00) with 'object name required'.
        exit.
      endif.
      read table objectTable into objectLine with key object = plugin.
      if sy-subrc <> 0.
        concatenate 'Plugin for object type' plugin
          'is not installed on this system' into errorMsg
          separated by space.
          perform writeMessage using 'E' errorMsg.
        exit.
      endif.
      create object targetObject type (objectLine-classname)
        exporting name = _objName.
      try.
        ixmlDocument = targetObject->CREATEIXMLDOCFROMOBJECT( ).
        catch ZCX_SAPLINK into excClass.
          errorMsg = excClass->get_text( ).
          perform writeMessage using 'E' errorMsg.
      endtry.
      if errorMsg is not initial.
        exit.
      endif.
      xml = zsapLink=>convertIxmlDoctoString( ixmlDocument ).

      concatenate plugin '_' _objName '.slnk' into defFilename.
      clear errorFlag.
      perform downloadXMLtoLM using defFilename xml
                              changing errorFlag.
      if errorFlag is not initial.
        message s208(00) with 'Action cancelled'.
        exit.
      endif.
      perform displayXMLOnScreen using xml.
*   Import slinkee
    elseif Import = 'X'.
      if filename is initial.
        message s208(00) with 'slinkee filename required'.
        exit.
      endif.
      perform uploadXMLFromLM using filename xml.
      if sy-subrc <> 0.
        exit.
      endif.
      ixmlDocument = zsapLink=>convertStringToIxmlDoc( xml ).
*     run some checks before install
      perform checkObject using ixmlDocument
                          changing _objType
                                   _objName
                                   _pluginExists
                                   _objectExists.
      move _objType to plugin.
      read table objectTable into objectLine with key object = plugin.

      if _objtype = 'NUGG'.
        message s208(00) with 'use nugget tab for nugget import'.
        exit.
      elseif _pluginExists is initial.
        concatenate
          'There is no installed SAPlink plugin for object type'
          _objType into errorMsg separated by space.
          perform writeMessage using 'E' errorMsg.
        exit.
      elseif _objectExists = 'X' and overWr is initial.
        concatenate _objType objectline-text _objName
          'already exists. Use overwrite orginals option to replace'
          into errorMsg separated by space.
        perform writeMessage using 'E' errorMsg.
        exit.
      elseif _objectExists = 'X' and overWr = 'X'.
        concatenate _objType _objName into sTemp separated by space.
        perform confirmOverwrite using sTemp
                              changing _flag.
        if _flag = 'A'. "cancel
          perform writeMessage using 'W' 'Import cancelled by user'.
          exit.
        endif.
      endif.

*     install object
      perform installObject using ixmlDocument overWr
                         changing errorFlag
                                  statusMsg.
      if errorFlag = 'X'.
        perform writeMessage using 'E' statusmsg.
        exit.
      else.
        perform writeMessage using 'S' statusmsg.
      endif.
      message s208(00) with 'Import successful'.
    endif.
  else.
************* N U G G E T *************
*   create empty nugget
    if nugC = 'X'.
      if nuggNam is initial.
        message s208(00) with 'enter name of new nugget to be created'.
        exit.
      endif.
      stemp = nuggNam.
      perform CreateEmptyNugget using stemp.
*   add object to nugget
    elseif NugA = 'X'.
      if nplugin is initial.
        message s208(00) with 'object type required'.
        exit.
      elseif nobjNam is initial.
        message s208(00) with 'object name required'.
        exit.
      elseif nugfile is initial.
        message s208(00) with 'nugget filename required'.
        exit.
      endif.
      read table objectTable into objectLine with key object = nplugin.
      if sy-subrc <> 0.
        concatenate 'Plugin for object type' nplugin
          'is not installed on this system' into errormsg
            separated by space.
          perform writeMessage using 'E' errormsg.
        exit.
      endif.
      sTemp = nuggNam.
      perform uploadXMLFromLM using nugfile xml.
      if sy-subrc <> 0.
        exit.
      endif.
      ixmlDocument = zsapLink=>convertStringToIxmlDoc( xml ).
      create object nugg exporting ixmlDocument = ixmlDocument.

      _objName = nobjNam.
      sTemp = nplugin.

      try.
        nugg->ADDOBJECTTONUGGET( objName = _objName objType = sTemp ).
        catch ZCX_SAPLINK into excClass.
          errorMsg = excClass->get_text( ).
          perform writeMessage using 'E' errorMsg.
          exit.
      endtry.
      ixmlDocument = nugg->CREATEIXMLDOCFROMNUGGET( ).
      xml = zsapLink=>convertIxmlDoctoString( ixmlDocument ).
*      concatenate  nuggNam '.nugg' into sTemp.
      sTemp = nugFile.
      perform putOnMachine using sTemp xml.
*   import nugget
    elseif NugI = 'X'.
      if nugfile is initial.
        message s208(00) with 'nugget filename required'.
        exit.
      endif.
      perform uploadXMLFromLM using nugfile xml.
      if sy-subrc <> 0.
        exit.
      endif.
      ixmlDocument = zsapLink=>convertStringToIxmlDoc( xml ).
      nuggetName = zsaplink_nugget=>getnuggetinfo( ixmlDocument ).
      concatenate 'Start import of nugget' nuggetName into statusmsg
        separated by space.

      perform writeMessage using 'S' statusmsg.
      skip.

      create object nugg exporting ixmlDocument = ixmlDocument.

*     check for installed plugins
      clear errorFlag.
      refresh it_nuggetObject.
      anXMLDoc = nugg->getNextObject( ).
      while anXMLDoc is not Initial.
        clear: _objType, _objName, _pluginExists, _objectExists,
               wa_nuggetObject.
        perform checkObject using anXMLDoc
                            changing _objType
                                     _objName
                                     _pluginExists
                                     _objectExists.
        if _pluginExists is initial.
          concatenate
            'There is no installed SAPlink plugin for object type'
            _objType into errorMsg separated by space.
          perform writeMessage using 'E' errormsg.
          errorFlag = 'X'.
        elseif _objectExists = 'X' and nOvrWr is initial.
          concatenate _objType _objName 'already exists. Use overwrite'
            'orginals option to replace'
              into errorMsg separated by space.
          perform writeMessage using 'W' errormsg.
          errorFlag = 'X'.
        endif.
        wa_nuggetObject-objType = _objType.
        wa_nuggetObject-objName = _objName.
        wa_nuggetObject-exists = _objectExists.
        append wa_nuggetObject to it_nuggetObject.

        anXMLDoc = nugg->getNextObject( ).
      endwhile.

      if errorFlag = 'X'.
        exit.
      endif.

*     confirm overwrite
      loop at it_nuggetObject into wa_nuggetObject where exists = 'X'.
        clear _flag.
        concatenate wa_nuggetObject-objType wa_nuggetObject-objName
          into sTemp separated by space.
        perform confirmOverwrite using sTemp
                              changing _flag.
        if _flag = '1'. "yes
          continue.
        elseif _flag = '2'. "yes to all
          clear errorFlag.
          exit.
        elseif _flag = 'A'. "cancel
          perform writeMessage using 'W' 'Import cancelled by user'.
          errorFlag = 'X'.
          exit.
        endif.
      endloop.

      if errorFlag = 'X'.
        exit.
      endif.

*     install
      nugg->reset( ). "reset nugget iterator
      anXMLDoc = nugg->getNextObject( ).
      while anXMLDoc is not Initial.
        clear statusMsg.
        perform installObject using anXMLDoc nOvrWr
                           changing errorFlag
                                    statusMsg.
        if errorFlag = 'X'.
          perform writeMessage using 'E' statusmsg.
          exit.
        else.
          perform writeMessage using 'S' statusmsg.
          anXMLDoc = nugg->getNextObject( ).
        endif.
      endwhile.

      if errorFlag = 'X'.
        exit.
      endif.
*   display objects in a nugget
    elseif NugD = 'X'.
      if nugfile is initial.
        message s208(00) with 'nugget filename required'.
        exit.
      endif.
      perform uploadXMLFromLM using nugfile xml.
      if sy-subrc <> 0.
        exit.
      endif.
      ixmlDocument = zsapLink=>convertStringToIxmlDoc( xml ).
      nuggetName = zsaplink_nugget=>getnuggetinfo( ixmlDocument ).
      write: / 'Object list for nugget ', nuggetName. skip.

      create object nugg exporting ixmlDocument = ixmlDocument.
      anXMLDoc = nugg->getNextObject( ).

      if anXMLDoc is initial.
        errorMsg = 'You have an empty Nugget'.
        perform writeMessage using 'W' errormsg.
        exit.
      endif.

      while anXMLDoc is not initial.
        call method zsapLink=>GETOBJECTInfoFROMIXMLDOC
              exporting
                ixmlDocument = anXMLDoc
              importing
                objtypename = _objType
                objname     = _objName.

        concatenate _objType _objName into statusMsg separated by space.
        perform writeMessage using 'S' statusMsg.
        anXMLDoc = nugg->getNextObject( ).
      endwhile.

*   rrq: enhancement 3-->
*   add package to nugget
    elseif NugP = 'X'.
      if package  is initial.
        message s208(00) with 'package required'.
        exit.
      endif.
      if nugfile is initial.
        message s208(00) with 'nugget filename required'.
        exit.
      endif.
      select object obj_name srcsystem
          from tadir
          into corresponding fields of table objects_package
          where devclass  eq package
          and  pgmid      eq 'R3TR'
          "//-> Mar: Added logic discard deleted objects from Package - 08/20/2008
          and  delflag    ne 'X'.
          "//<- Mar: Added logic discard deleted objects from Package - 08/20/2008
      if sy-subrc <> 0.
        message s208(00) with 'Package does not exist or empty'.
        return.
      endif.

      perform addObjectstoNugget.
*   <-- rrq: enhancement 3

*   rrq: enhancement 42-->
*   add objects from a transport to a nugget
    elseif nugr = 'X'.
      DATA: ReqName TYPE string.

      Data: L_TRKORR type e07t-trkorr,
            l_as4text type e07t-as4text.

      if nugfile is initial.
        message s208(00) with 'nugget filename required'.
        exit.
      endif.

      if ReqNugg[] is initial.
        message s208(00) with 'Request number required'.
        exit.
      endif.

      select single trkorr from e070 into l_trkorr
        where trkorr in reqNugg.

      if sy-subrc <> 0.
        message s208(00) with 'Transport not found'.
        exit.
      endif.

      SELECT Single TRKORR AS4TEXT
      FROM  E07T
      INTO (l_TRKORR, L_as4text)
      WHERE  TRKORR   IN ReqNugg
        AND  LANGU    EQ sy-langu.

*     ewH-->retrieve tasks as well as transports
      ranges: ra_reqNugg for e070-trkorr.
      data: wa_trkorr type e070-trkorr,
            it_trkorr type table of e070-trkorr,
            wa_reqNugg like line of ra_reqNugg.

      select trkorr from e070 into table it_trkorr
        where strkorr in reqNugg.

      ra_reqNugg[] = reqNugg[].

      loop at it_trkorr into wa_trkorr.
        wa_reqNugg-sign = 'I'.
        wa_reqNugg-option = 'EQ'.
        wa_reqNugg-low = wa_trkorr.
        append wa_reqNugg to ra_reqNugg.
      endloop.
*     <--ewH

      SELECT object OBJ_NAME
      FROM  E071
      INTO TABLE it_requestobject
*      WHERE  TRKORR in ReqNugg.
      WHERE  TRKORR in ra_ReqNugg "ewH
      and PGMID = 'R3TR'. "ewH: don't need subobjects

      if sy-subrc = 0.
        ReqName = l_TRKORR.
      else.
        message s208(00) with 'No R3TR objects in request'.
        exit.
      ENDIF.

      loop at it_requestObject into wa_requestObject.
        move-corresponding wa_requestObject to packageLine.
        append packageLine to objects_package.
      endloop.

      perform addObjectstoNugget.
    endif.
  endif.

*\--------------------------------------------------------------------/

*/----------------------displayXMLOnScreen----------------------------\
form displayXMLOnScreen using xmlString type string.
data printXMLDoc type ref to cl_xml_document.
data rc type sysubrc.

  create object printXMLDoc.
  rc = printXMLDoc->parse_string( xmlString ).
  call method printXMLDoc->display( ).

endform.
*\--------------------------------------------------------------------/

*/----------------------downloadXMLToLM-------------------------------\
form downloadXMLToLM using   defFilename type string
                             xmlString type string
                    changing _errorFlag type flag.

data retFileName type string.
data retPath type string.
data retFullpath type string.
data retUserAct type i.

  clear _errorFlag.

  call method CL_GUI_FRONTEND_SERVICES=>FILE_SAVE_DIALOG
        exporting
          DEFAULT_FILE_NAME = defFilename
        changing
          FILENAME = retFileName
          PATH = retPath
          FULLPATH = retFullPath
          USER_ACTION = retUserAct.

  if retUserAct <> 0.
    _errorFlag = 'X'.
  else.
    perform putOnMachine using retFullPath xmlString.
  endif.


endform.
*\--------------------------------------------------------------------/


*/------------------------putOnMachine--------------------------------\
form putOnMachine using fullpath type string xmlString type string.

*rrq: issue 43--> replace binary with char table
*old code removed, use subversion for recovery
*types: begin of t_char,
*        maxChar(65535) type C,
*       end of t_char.

*data: tempTable_char type table of t_char,
data: tempTable_char type table_of_strings,
      tempString type string.

  if retUserAct = 0.

    split xmlString at CL_ABAP_CHAR_UTILITIES=>NEWLINE
    into table tempTable_char.

    call method CL_GUI_FRONTEND_SERVICES=>GUI_DOWNLOAD
          exporting
            FILENAME = fullpath
            FILETYPE = 'DAT'
          changing
            DATA_TAB = tempTable_char.
  endif.
*<--rrq: issue 43
endform.
*\--------------------------------------------------------------------/


*/----------------------uploadXMLFromLM-------------------------------\
form uploadXMLFromLM using p_filename xmlString type string .
data retFileTable type FILETABLE.
data retRc type sysubrc.
data retUserAction type i.
data tempTable type table_of_strings.
data tempTable_bin type table  of xstring.
data l_fileName type string.

  l_fileName = p_filename.
  call method CL_GUI_FRONTEND_SERVICES=>GUI_UPLOAD
        exporting
          FILENAME = l_fileName
        changing
          data_tab = tempTable
        EXCEPTIONS
          FILE_OPEN_ERROR         = 1
          FILE_READ_ERROR         = 2
          NO_BATCH                = 3
          GUI_REFUSE_FILETRANSFER = 4
          INVALID_TYPE            = 5
          NO_AUTHORITY            = 6
          UNKNOWN_ERROR           = 7
          BAD_DATA_FORMAT         = 8
          HEADER_NOT_ALLOWED      = 9
          SEPARATOR_NOT_ALLOWED   = 10
          HEADER_TOO_LONG         = 11
          UNKNOWN_DP_ERROR        = 12
          ACCESS_DENIED           = 13
          DP_OUT_OF_MEMORY        = 14
          DISK_FULL               = 15
          DP_TIMEOUT              = 16
          NOT_SUPPORTED_BY_GUI    = 17
          ERROR_NO_GUI            = 18
          others                  = 19.
  IF SY-SUBRC <> 0.
    case sy-subrc.
      when '1'.
        perform writeMessage using 'E' 'File Open Error'.
      when others.
        perform writeMessage using 'E' 'Unknown Error occured'.
    endcase.
  ENDIF.

*  call method CL_GUI_FRONTEND_SERVICES=>GUI_UPLOAD
*        exporting
*          FILENAME = l_fileName
*        changing
*          data_tab = tempTable.
  perform createString using tempTable changing xmlString.

endform.
*\--------------------------------------------------------------------/

*/----------------------createString----------------------------------\
form createString
      using
        tempTable type table_of_strings
      changing
        bigString type string.
data sTemp type string.
  loop at tempTable into sTemp.
    concatenate bigString sTemp CL_ABAP_CHAR_UTILITIES=>NEWLINE
      into bigString.
  endloop.

endform.
*\--------------------------------------------------------------------/

*/----------------------installObject---------------------------------\
form installObject using l_ixmlDocument type ref to if_ixml_document
                         l_overwriteFlag type flag
                changing l_errorFlag type flag
                         l_message type string.

data l_objName type string.
data l_objType type string.
data l_objTable type table of t_objectTable.
data l_objLine type t_objectTable.
data l_targetObject type ref to zsaplink.
data l_installObject type string.
data l_excClass type ref to ZCX_SAPLINK.

  clear l_errorFlag.
  call method zsapLink=>GETOBJECTInfoFROMIXMLDOC
        exporting
          ixmlDocument = l_ixmlDocument
        importing
          objtypename = l_objType
          objname     = l_objName.

  call method zsaplink=>getplugins( changing objectTable = l_objTable ).

  read table l_objTable into l_objLine with key object = l_objType.

  if sy-subrc <> 0.
    concatenate 'There is no installed SAPlink plugin for object type'
      l_objType l_objLine-text into l_message separated by space.
    l_errorFlag = 'X'.
  else.
    create object l_targetObject type (l_objLine-classname)
      exporting name = l_objName.

    try.
      l_installObject = l_targetObject->createObjectfromiXMLDoc(
                                      ixmlDocument = l_ixmlDocument
                                      overwrite = l_overwriteFlag ).
*    bad times
      catch ZCX_SAPLINK into l_excClass.
        l_message = l_excClass->get_text( ).
        l_errorFlag = 'X'.
    endtry.
*   good times
    if l_installObject is not initial.
      concatenate 'Installed: ' l_objType '-' l_installObject
       into l_message separated by space.
    endif.
  endif.

endform.
*\--------------------------------------------------------------------/

*/----------------------confirmOverwrite------------------------------\
form confirmOverwrite using l_objInfo type string
                   changing l_answer type flag.

data l_message type string.
data l_title type string.

  clear l_answer.
  l_title = 'Overwrite confirm. Proceed with CAUTION!'.

  concatenate 'You have selected to overwrite originals.'
    l_objinfo 'will be overwritten. Are you sure?'
    into l_message separated by space.

  CALL FUNCTION 'POPUP_TO_CONFIRM'
    EXPORTING
      TITLEBAR                    = l_title
      text_question               = l_message
      TEXT_BUTTON_1               = 'Yes'
      TEXT_BUTTON_2               = 'Yes to all'
      DEFAULT_BUTTON              = '1'
      DISPLAY_CANCEL_BUTTON       = 'X'
    IMPORTING
      ANSWER                      = l_answer
            .
endform.
*\--------------------------------------------------------------------/

*/----------------------checkObject-----------------------------------\
form checkObject using l_ixmlDocument type ref to if_ixml_document
              changing l_objType type string
                       l_objName type string
                       l_pluginExists type flag
                       l_objectExists type flag.

data l_objTable type table of t_objectTable.
data l_objLine type t_objectTable.
data l_targetObject type ref to zsaplink.

  clear: l_objType, l_objName, l_pluginExists, l_objectExists.
  call method zsapLink=>GETOBJECTInfoFROMIXMLDOC
        exporting
          ixmlDocument = l_ixmlDocument
        importing
          objtypename = l_objType
          objname     = l_objName.

  call method zsaplink=>getplugins( changing objectTable = l_objTable ).

  read table l_objTable into l_objLine with key object = l_objType.

  if sy-subrc = 0.
    l_pluginExists = 'X'.
    create object l_targetObject type (l_objLine-classname)
      exporting name = l_objName.

    l_objectExists = l_targetObject->checkexists( ).
  endif.

endform.
*\--------------------------------------------------------------------/

*/---------------------get_current_screen_value-----------------------\
form get_current_screen_value  using    l_screen_field
                                        l_screen_number
                               changing l_screen_value.

  DATA it_dynpfields TYPE STANDARD TABLE OF dynpread.
  DATA wa_dynpfields TYPE dynpread.


  wa_dynpfields-fieldname = l_screen_field.
  APPEND wa_dynpfields TO it_dynpfields.


  CALL FUNCTION 'DYNP_VALUES_READ'
    EXPORTING
      dyname                         = sy-cprog
      dynumb                         = l_screen_number
      translate_to_upper             = 'X'
*     REQUEST                        = ' '
*     PERFORM_CONVERSION_EXITS       = ' '
*     PERFORM_INPUT_CONVERSION       = ' '
*     DETERMINE_LOOP_INDEX           = ' '
    TABLES
      dynpfields                     = it_dynpfields
    EXCEPTIONS
      invalid_abapworkarea           = 1
      invalid_dynprofield            = 2
      invalid_dynproname             = 3
      invalid_dynpronummer           = 4
      invalid_request                = 5
      no_fielddescription            = 6
      invalid_parameter              = 7
      undefind_error                 = 8
      double_conversion              = 9
      stepl_not_found                = 10
      OTHERS                         = 11
            .
  IF sy-subrc <> 0.
*  MESSAGE ID SY-MSGID TYPE SY-MSGTY NUMBER SY-MSGNO
*  WITH SY-MSGV1 SY-MSGV2 SY-MSGV3 SY-MSGV4.
  ELSE.
    READ TABLE it_dynpfields into wa_dynpfields
      WITH KEY fieldname = l_screen_field.
    if sy-subrc = 0.
      l_screen_value = wa_dynpfields-fieldvalue.
    endif.
  ENDIF.


endform.                    " get_current_screen_value
*/---------------------writeMessage-----------------------\
form WriteMessage USING VALUE(p_type) type sy-msgty
                        VALUE(p_msg).
  CASE p_type.
    WHEN 'E' OR 'A' OR 'X'.
      WRITE / icon_led_red AS ICON.
    WHEN 'W'.
      WRITE / icon_led_yellow AS ICON.
    WHEN OTHERS.
      WRITE / icon_led_green AS ICON.
  ENDCASE.

  WRITE p_msg.
endform.                    "WriteMessage

*/-------------------------pf_status_set-------------------\
form pf_status_set using rt_extab type slis_t_extab.

  set pf-status 'SELOBJ' excluding rt_extab.

endform.                    "pf_status_set
*/-------------------------user_command_user-------------------\
form user_command_user using r_ucomm like sy-ucomm
                  rs_selfield type slis_selfield.
  case r_ucomm.
    when 'TAKE'.
      rs_selfield-exit = 'X'.
  endcase.
endform.                    "user_command_user

*---------------build_fieldCatalog---------------------------------*
FORM build_fieldCatalog .
*** Display list to select the objects for downloading
    ls_fieldcat-fieldname = 'OBJECT'.
    ls_fieldcat-seltext_l = 'Object/Plugin'.
    append ls_fieldcat to lt_fieldcat.

    ls_fieldcat-fieldname = 'OBJECT_TXT'.
    ls_fieldcat-seltext_l = 'Object/Plugin'.
    append ls_fieldcat to lt_fieldcat.

    ls_fieldcat-fieldname = 'OBJ_NAME'.
    ls_fieldcat-seltext_l = 'Object name'.
    append ls_fieldcat to lt_fieldcat.

    ls_fieldcat-fieldname = 'DOWN_FLAG'.
    ls_fieldcat-seltext_s = 'Plugin'.
    ls_fieldcat-seltext_l =
    'Plugin available'.
    append ls_fieldcat to lt_fieldcat.

    ls_fieldcat-fieldname = 'MSG'.
    ls_fieldcat-seltext_s = 'Message'.
    ls_fieldcat-seltext_l =
    'Status Message'.
    append ls_fieldcat to lt_fieldcat.

    ls_layout-box_fieldname     = 'SELECT'.
    ls_layout-f2code            = 'MYPICK' .
    ls_layout-colwidth_optimize = 'X'.
    ls_layout-lights_fieldname  = 'STATUS'.
ENDFORM.                    " build_fieldCatalog
*&--------------------------------------------------------------------*
*&      Form  ShowInitialGrid
FORM ShowInitialGrid  TABLES   P_OBJECTS.

      call function 'REUSE_ALV_GRID_DISPLAY'
        exporting
          i_callback_program       = 'ZSAPLINK'
          i_callback_pf_status_set = 'PF_STATUS_SET'
          i_callback_user_command  = 'USER_COMMAND_USER'
          i_grid_title             = 'Select objects'
          it_fieldcat              = lt_fieldcat
          is_layout                = ls_layout
        tables
          t_outtab                 = P_OBJECTS
        exceptions
          others                   = 0.

ENDFORM.                    " ShowInitialGrid
*&---------------------------------------------------------------------*
*&      Form  showResultsGrid
FORM showResultsGrid  TABLES   P_OBJECTS.
*    ** Display results
      call function 'REUSE_ALV_GRID_DISPLAY'
        exporting
          i_callback_program      = 'ZSAPLINK'
          i_callback_user_command = 'USER_COMMAND_USER'
          it_fieldcat             = lt_fieldcat
          i_grid_title            = 'Download results'
          is_layout               = ls_layout
        tables
          t_outtab                = p_objects
        exceptions
          others                  = 0.

ENDFORM.                    " showResultsGrid
*&---------------------------------------------------------------------*
*&      Form  check_objects
*&---------------------------------------------------------------------*
*       text
*----------------------------------------------------------------------*
*  -->  p1        text
*  <--  p2        text
*----------------------------------------------------------------------*
FORM check_objects .
      loop at objects_package assigning <obj>.
*     Check what can be downloaded and what can not.
        read table objecttable into objectline
            with key object = <obj>-object.
        if sy-subrc = 0.
*        Plug-in exists... set flag and make selected by default
          <obj>-down_flag = 'X'.
          <obj>-select = 'X'.
        else.
          <obj>-msg = 'No Plugin Available'.
          <obj>-down_flag = ' '.
        endif.
*     get texts
        refresh tabletypesin.
        tabletypeline-object = <obj>-object.
        append tabletypeline to tabletypesin.

        call function 'TRINT_OBJECT_TABLE'
          tables
            tt_types_in  = tabletypesin
            tt_types_out = tabletypesout.

        loop at tabletypesout into tabletypeoutline.
          <obj>-object      = tabletypeoutline-object.
          <obj>-object_txt = tabletypeoutline-text.
        endloop.

      endloop.
      sort objects_package by down_flag descending object ascending.

ENDFORM.                    " check_objects
*&---------------------------------------------------------------------*
*&      Form  CreateEmptyNugget
*&---------------------------------------------------------------------*
*       text
*----------------------------------------------------------------------*
*  -->  p1        text
*  <--  p2        text
*----------------------------------------------------------------------*
FORM CreateEmptyNugget using p_NuggName.

    ixmlDocument = zsaplink_nugget=>createemptyXML(
      nuggetName = p_NuggName ).
    xml = zsapLink=>convertIxmlDoctoString( ixmlDocument ).
    concatenate 'NUGG_' p_nuggName '.nugg' into sTemp.
    clear errorFlag.
    perform downloadXMLtoLM using sTemp xml
                            changing errorFlag.
    if errorFlag is not initial.
      exit.
    endif.

ENDFORM.                    " CreateEmptyNugget

*rrq: enhancement 3 & 42-->
*&---------------------------------------------------------------------*
*&      Form  addObjectstoNugget
*&---------------------------------------------------------------------*
form addObjectstoNugget .

  perform check_objects.
  perform build_fieldCatalog.

  perform ShowInitialGrid tables objects_package.

  if sy-ucomm <> 'TAKE'.
    return.
  endif .

*  Downloading
  call function 'SAPGUI_PROGRESS_INDICATOR'
    exporting
      percentage = 1
      text       = 'Upload file'.

  perform uploadxmlfromlm using nugfile xml.

  ixmldocument = zsaplink=>convertstringtoixmldoc( xml ).

  create object nugg
    exporting
      ixmldocument = ixmldocument.

  describe table objects_package lines lv_count.
  loop at objects_package assigning <obj>
  where down_flag = 'X' and select = 'X'.
    lv_pers = sy-tabix * 100 / lv_count .
    call function 'SAPGUI_PROGRESS_INDICATOR'
      exporting
        percentage = lv_pers
        text       = <obj>-obj_name.

    _objname = <obj>-obj_name. "nobjNam.
    stemp = <obj>-object.      "nplugin.
    try.
        nugg->addobjecttonugget(
        objname = _objname objtype = stemp ).
      catch zcx_saplink into excclass.
        errormsg = excclass->get_text( ).
*        perform writeMessage using 'E' errorMsg.
        <obj>-msg = errorMsg.
        <obj>-status = 1.
        continue.
    endtry.
    <obj>-msg = 'Added to nugget'.
    <obj>-status = 3.
  endloop.

  read table objects_package into packageLine
    with key status = 3. "ewH:do not download if none added

  if sy-subrc = 0.
    ixmldocument = nugg->createixmldocfromnugget( ).
    xml = zsaplink=>convertixmldoctostring( ixmldocument ).
    stemp = nugfile.
    perform putonmachine using stemp xml.
  endif.

  perform showResultsGrid tables objects_package.

endform.                    " addObjectstoNugget
*  <--rrq: enhancement 3 & 42