You are on page 1of 14

3/15/2021 Excel VBA connect SAPRFC

Excel Macro Tutorial SUBSCRIBE

Easy way to learn excel macros and follow step by step instruction.

Excel VBA connect SAPRFC


May 12, 2020

This is simple and you don't have to install those development tools to
run the code. Is just required Microsoft excel you can connect into your
SAP R/3. No other tools required, no need the extra software installed
and mainly is using Excel VBA run the code and you able to
retrieve/import data on your SAP R/3 data.

Required item:

This is the items required to start your tutorial:

1. Microsoft excel.
2. SAP Login id and password.
3. SAP program with remote function call. I will show your my
customized RFC coding in my SAP ABAP. The RFC program name
is "ZMM_PRPORS"
4. SAP Gui installed

One more setting you have to do before start the coding. You have to
add SAP reference below:

1. Go to Developer tab -> Click the Visual Basic:

Este sitio utiliza cookies de Google para prestar sus servicios y para
analizar su tráfico. Tu dirección IP y user-agent se comparten con
Google, junto con las métricas de rendimiento y de seguridad, para
garantizar la calidad del servicio, generar estadísticas de uso y
detectar y solucionar abusos. 2. Go to Tools ->
References
MÁS INFORMACIÓN ACEPTAR

https://macrostutorials.blogspot.com/2017/08/excel-vba-connect-saprfc.html 1/14
3/15/2021 Excel VBA connect SAPRFC

3. Click those SAP references show as below and click OK.

Excel VBA Coding

Double click on the sheet1 and pasted code below.

Please ll in your SAP ip address, client, system id, system number, SAP
user id and password. Make sure you have the correct info in SAP
Esteconnection.
sitio utiliza cookies de Google para prestar sus servicios y para
analizar su tráfico. Tu dirección IP y user-agent se comparten con
Google, junto con las métricas de rendimiento y de seguridad, para
___________________________________________________
garantizar la calidad del servicio, generar estadísticas de uso y
detectar y solucionar abusos.
Option Explicit
MÁS INFORMACIÓN ACEPTAR
Di bjBAPIC t l bjG td t A Obj t
https://macrostutorials.blogspot.com/2017/08/excel-vba-connect-saprfc.html 2/14
3/15/2021 Excel VBA connect SAPRFC
Dim objBAPIControl, objGetdata As Object

Dim vLastRow, vCols, DPT, PLT, PGR, ACA, ITC As Integer

Dim vcount_add, index_add As Integer

Dim PREV_OBJ As String

Public objinput, objausp, objt16fs As SAPTableFactoryCtrl.Table

Private Sub GetData_Click()

 'Local variables

  Dim LogonControl As SAPLogonCtrl.SAPLogonControl

  Dim R3Connection As SAPLogonCtrl.Connection

  Dim retcd        As Boolean

  Dim SilentLogon  As Boolean

  Dim R            As Integer


  
  Dim num          As Integer
  

 'Set Connection

  Set LogonControl = CreateObject("SAP.LogonControl.1")

  Set objBAPIControl = CreateObject("SAP.Functions")

  Set R3Connection = LogonControl.NewConnection


Este sitio utiliza cookies de Google para prestar sus servicios y para
analizar
   su tráfico. Tu dirección IP y user-agent se comparten con
Google, junto con las métricas de rendimiento y de seguridad, para
garantizar la calidad del servicio, generar estadísticas de uso y
 'SAP connection
detectar y solucionar abusos.

  R3Connection.Client = "100" MÁS INFORMACIÓN ACEPTAR

https://macrostutorials.blogspot.com/2017/08/excel-vba-connect-saprfc.html 3/14
3/15/2021 Excel VBA connect SAPRFC

  R3Connection.ApplicationServer = "xxxxxx"

  R3Connection.Language = "EN"

  R3Connection.User = "<userid>"

  R3Connection.Password = "<password>"

  R3Connection.System = "DEV"

  R3Connection.SystemNumber = "00"

  R3Connection.UseSAPLogonIni = False

  SilentLogon = False
  

  retcd = R3Connection.Logon(0, SilentLogon)

  If retcd <> True Then MsgBox "Logon failed": Exit Sub

  objBAPIControl.Connection = R3Connection

  

 'Assign the Parameters

  Set objGetdata = objBAPIControl.Add("ZMM_PRPORS")

  Set objt16fs = objGetdata.Tables("ET_T16FS")

  Set objausp = objGetdata.Tables("ET_AUSP_LIST")

  Set objinput = objGetdata.Tables("ET_OBJEK")


Este sitio utiliza cookies de Google para prestar sus servicios y para
analizar su tráfico. Tu dirección IP y user-agent se comparten con
 'Assign customer
Google, junto con las métricas de rendimiento y de seguridad, para
  Sheets("Release Strategy").Select
garantizar la calidad del servicio, generar estadísticas de uso y
  
detectar y solucionar abusos.
  For R = 164 To 400
MÁS INFORMACIÓN ACEPTAR
  num = num + 1
https://macrostutorials.blogspot.com/2017/08/excel-vba-connect-saprfc.html 4/14
3/15/2021 Excel VBA connect SAPRFC

  If ThisWorkbook.ActiveSheet.Cells(R, 2).Value <> "" Then

    objinput.Rows.Add

    objinput.Value(num, "SIGN") = ThisWorkbook.ActiveSheet.Cells(R,


2).Value

    objinput.Value(num, "OPTION") = ThisWorkbook.ActiveSheet.Cells(R,


3).Value

    objinput.Value(num, "LOW") = ThisWorkbook.ActiveSheet.Cells(R,


4).Value

    objinput.Value(num, "HIGH") = ThisWorkbook.ActiveSheet.Cells(R,


5).Value
  
  Else
    Exit For
  End If
  Next
  vCols = 1
  PREV_OBJ = ""
  objGetdata.Call

  vcount_add = objausp.Rows.Count

    For index_add = 1 To vcount_add


      If objausp.Value(index_add, "OBJEK") <> PREV_OBJ Then
          PGR = 97
          PLT = 10
          DPT = 127
          ACA = 121
          ITC = 155
          PREV_OBJ = objausp.Value(index_add, "OBJEK")
          vCols = vCols + 1
Este sitio utiliza cookies de Google para prestar sus servicios y para
      End If
analizar su tráfico. Tu dirección IP y user-agent se comparten con
Google, junto con las métricas de rendimiento y de seguridad, para
      ActiveSheet.Cells(1,
garantizar la calidadvCols)
del= servicio,
objausp.Value(index_add, "OBJEK")
generar estadísticas de uso y
 'Object y solucionar abusos.
detectar
        
MÁS INFORMACIÓN ACEPTAR
      Select Case objausp.Value(index_add, "ATINN")
https://macrostutorials.blogspot.com/2017/08/excel-vba-connect-saprfc.html 5/14
3/15/2021 Excel VBA connect SAPRFC
j p ( )
      Case "0000000835"     'Purchasing Grp
        PGR = PGR + 1
        If PGR < 120 Then
            ActiveSheet.Cells(PGR, vCols) = objausp.Value(index_add,
"ATWRT")  'Value
        End If
      Case "0000000836"     'PR/PO Doc Type
        ActiveSheet.Cells(10, vCols) = objausp.Value(index_add, "ATWRT")
 'Value
      Case "0000000841"     'Plant Level
        PLT = PLT + 1
        If PLT < 98 Then
            ActiveSheet.Cells(PLT, vCols) = objausp.Value(index_add,
"ATWRT")  'Value
        End If
      Case "0000000855"     'Account assignment
        ACA = ACA + 1
        If ACA < 128 Then
            ActiveSheet.Cells(ACA, vCols) = objausp.Value(index_add,
"ATWRT")  'Value
        End If
      Case "0000000856"     'Department
        DPT = DPT + 1
        If DPT < 156 Then
            ActiveSheet.Cells(DPT, vCols) = objausp.Value(index_add,
"ATWRT")  'Value
        End If
      Case "0000000838"     'USD Value
          Select Case objausp.Value(index_add, "ATCOD")  'Code
                Case 3 'GE value from LE Value TO
                ActiveSheet.Cells(120, vCols) = objausp.Value(index_add,
"ATFLV") & " - " & objausp.Value(index_add, "ATFLB") 'Value from
                Case 6 'Less Than
                ActiveSheet.Cells(120, vCols) = " < " & objausp.Value(index_add,
"ATFLB") 'Value TO
Este sitio utiliza cookies de Google para prestar sus servicios y para
              su
analizar   Case 7 ' Less than
tráfico. Tuordirección
equals IP y user-agent se comparten con
           junto
Google,     ActiveSheet.Cells(120,
con las métricas vCols) =de
" <=rendimiento
"& y de seguridad, para
objausp.Value(index_add,
garantizar la calidad "ATFLB") 'Value TO generar estadísticas de uso y
del servicio,
detectar
             y solucionar
  Case abusos.
8 'Greater Than
                ActiveSheet.Cells(120, vCols) = " > " & objausp.Value(index_add,
MÁS INFORMACIÓN ACEPTAR
"ATFLV") 'Value from
https://macrostutorials.blogspot.com/2017/08/excel-vba-connect-saprfc.html 6/14
3/15/2021 Excel VBA connect SAPRFC
ATFLV ) Value from
                Case 9 'Greater Than
                ActiveSheet.Cells(120, vCols) = " >= " &
objausp.Value(index_add, "ATFLB") 'Value TO
          End Select
      Case "0000000840"     'MYR Value
          Select Case objausp.Value(index_add, "ATCOD")  'Code
                Case 3 'GE value from LE Value TO
                ActiveSheet.Cells(121, vCols) = objausp.Value(index_add,
"ATFLV") & " - " & objausp.Value(index_add, "ATFLB") 'Value from
                Case 6 'Less Than
                ActiveSheet.Cells(121, vCols) = " < " & objausp.Value(index_add,
"ATFLB") 'Value TO
                Case 8 'Greater Than
                ActiveSheet.Cells(121, vCols) = " > " & objausp.Value(index_add,
"ATFLV") 'Value from
                Case 9 'Greater Than
                ActiveSheet.Cells(121, vCols) = " >= " &
objausp.Value(index_add, "ATFLB") 'Value TO
          End Select
      Case "0000000871"     'Item Cat
        ITC = ITC + 1
        If ITC < 160 Then
            ActiveSheet.Cells(ITC, vCols) = objausp.Value(index_add,
"ATWRT")  'Value
        End If
      End Select
    

    Next index_add
  
  vcount_add = objt16fs.Rows.Count

    For index_add = 1 To vcount_add


    vCols = 1

Este sitio utiliza cookies de Google para prestar sus servicios y para
        Do su
analizar While Right(ActiveSheet.Cells(1,
tráfico. Tu dirección vCols),
IP 2)y <>
user-agent se comparten con
objt16fs.Value(index_add,
Google, "FRGSX")
junto con las métricas de rendimiento y de seguridad, para
garantizar la= vCols
            vCols calidad
+ 1 del servicio, generar estadísticas de uso y
detectar
        Loop y solucionar abusos.
        If Right(ActiveSheet.Cells(1, vCols), 2) = objt16fs.Value(index_add,
MÁS INFORMACIÓN ACEPTAR
"FRGSX") Then
https://macrostutorials.blogspot.com/2017/08/excel-vba-connect-saprfc.html 7/14
3/15/2021 Excel VBA connect SAPRFC
FRGSX ) Then
            ActiveSheet.Cells(2, vCols) = objt16fs.Value(index_add, "FRGXT")
 'Value
            ActiveSheet.Cells(3, vCols) = objt16fs.Value(index_add, "FRGSX")
 'Value
            ActiveSheet.Cells(5, vCols) = objt16fs.Value(index_add, "FRGC1")
 'Value
            ActiveSheet.Cells(6, vCols) = objt16fs.Value(index_add, "FRGC2")
 'Value
            ActiveSheet.Cells(7, vCols) = objt16fs.Value(index_add, "FRGC3")
 'Value
            ActiveSheet.Cells(8, vCols) = objt16fs.Value(index_add, "FRGC4")
 'Value
            ActiveSheet.Cells(9, vCols) = objt16fs.Value(index_add, "FRGC5")
 'Value
        End If
    Next index_add

  'If address not exist then show error

  If vcount_add = "" Then

    ActiveSheet.Cells(162, 12) = "Invalid Input"

  Else

    ActiveSheet.Cells(163, 12) = "BAPI Call is successfull"

    ActiveSheet.Cells(164, 12) = vcount_add & " rows are returned"

  End If

  

  R3Connection.Logoff
Este sitio utiliza cookies de Google para prestar sus servicios y para
analizar
End Subsu tráfico. Tu dirección IP y user-agent se comparten con
Google, junto con las métricas de rendimiento y de seguridad, para
garantizar la calidad del servicio, generar estadísticas de uso y
detectar y solucionar abusos.
Private Sub ResetOutput_Click()
MÁS INFORMACIÓN ACEPTAR
R ("B1 XFD159") S l t
https://macrostutorials.blogspot.com/2017/08/excel-vba-connect-saprfc.html 8/14
3/15/2021 Excel VBA connect SAPRFC
Range("B1:XFD159").Select
Selection.ClearContents

Range("L162:L164").Select
Selection.ClearContents

End Sub

'(Note: Button properties need to be set)


___________________________________________________

SAP ABAP Coding

Enter t-code SE37 and create function name "ZMM_PRPORS" then


change processing type to Remote-Enabled module.

Here the the import/export table. 

EsteET_AUSP_LIST - This is
sitio utiliza SAP AUSPde
cookies table. Use t-code
Google paraSE11 to create sus servicios y para
prestar
analizar su tráfico. Tu dirección IP y user-agent se comparten con
structure.
Google, junto con las métricas de rendimiento y de seguridad, para
garantizar la calidad del servicio, generar estadísticas de uso y
detectar y solucionar abusos.
MÁS INFORMACIÓN ACEPTAR

https://macrostutorials.blogspot.com/2017/08/excel-vba-connect-saprfc.html 9/14
3/15/2021 Excel VBA connect SAPRFC

ET_T16FS_LIST - This is SAP T16FS table. Use t-code SE11 to create


structure.

ET_T16FS_LIST - This is SAP T16FS table. Use t-code SE11 to create


structure.

EsteRFC Coding:
sitio utiliza cookies de Google para prestar sus servicios y para
analizar su tráfico. Tu dirección IP y user-agent se comparten con
_______________________________________________________________________
Google, junto
_______ con las métricas de rendimiento y de seguridad, para
garantizar la calidad del servicio, generar estadísticas de uso y
detectar y solucionar abusos.
FUNCTION ZMM_PRPORS.
MÁS INFORMACIÓN ACEPTAR
*"----------------------------------------------------------

https://macrostutorials.blogspot.com/2017/08/excel-vba-connect-saprfc.html 10/14
3/15/2021 Excel VBA connect SAPRFC

------------
*"*"Local Interface:
*" TABLES
*" ET_AUSP_LIST STRUCTURE ZMM_AUSP_LIST
*" ET_T16FS STRUCTURE ZMM_T16FS_LIST
*" ET_OBJEK STRUCTURE ZAUS_OBJNUM
*"----------------------------------------------------------
------------
DATA: DESC LIKE T16FT-FRGXT.
IF NOT ET_OBJEK[] IS INITIAL.

  SELECT OBJEK
          ATINN
          ATZHL
          MAFID
          KLART
          ADZHL
          ATWRT
          ATFLV
          ATAWE
          ATFLB
          ATAW1
          ATCOD
    INTO TABLE ET_AUSP_LIST
    FROM AUSP
    WHERE OBJEK IN ET_OBJEK.

    IF sy-subrc <> 0.
        Clear: et_AUSP_list.
    ELSE.
      Sort et_ausp_list by OBJEK ATINN ATWRT.
    ENDIF.

Este        
sitioSELECT * INTO CORRESPONDING 
utiliza FIELDS OF
cookies de Google TABLE
para ET_T16FS
prestar sus servicios y para
analizar su tráfico.
             FROM T16FS Tu dirección IP y user-agent se comparten con
Google,
             junto con las métricas de rendimiento y de seguridad, para
FOR ALL ENTRIES IN et_AUSP_List
garantizar la calidad del servicio, generar estadísticas de uso y
             WHERE FRGGR EQ et_AUSP_List-objek(2)
detectar y solucionar abusos.
               AND FRGSX EQ et_AUSP_List-objek+2(2).
MÁS INFORMACIÓN ACEPTAR

https://macrostutorials.blogspot.com/2017/08/excel-vba-connect-saprfc.html 11/14
3/15/2021 Excel VBA connect SAPRFC

        IF SY-SUBRC EQ 0.

          Sort et_t16fs by FRGSX.

          LOOP AT ET_T16FS.
              SELECT SINGLE FRGXT INTO DESC
                FROM T16FT
               WHERE FRGGR EQ ET_T16FS-FRGGR
                 AND FRGSX EQ ET_T16FS-FRGSX.

                MOVE DESC TO ET_T16FS-FRGXT.


                MODIFY ET_T16FS.
          ENDLOOP.

        ENDIF.
ENDIF.

ENDFUNCTION.

Download excel le here.

Mr Clever 20 December 2019 at 19:18

Thanks for the post!

One question, How do you pass credentials in a Single


Sign On (SSO) environment. From my windows desktop
I'm automatically logged in, and can't see any attributes
from the SAP Launchpad, is there a way to derive this
information or is the process altogether different ?
Thanks in cookies
Este sitio utiliza advance! de Google para prestar sus servicios y para
analizar su tráfico.
REPLY Tu dirección IP y user-agent se comparten con
Google, junto con las métricas de rendimiento y de seguridad, para
garantizar la calidad
Brian Chan 11del
May servicio, generar estadísticas de uso y
2020 at 19:54
detectar y solucionar abusos.
Hi, I’ve try on the SSO environment and it most more a
easy after you have setup every just click on
MÁS INFORMACIÓN the button
ACEPTAR
and execute with to worry to type the user name and
https://macrostutorials.blogspot.com/2017/08/excel-vba-connect-saprfc.html 12/14
3/15/2021 Excel VBA connect SAPRFC
y yp
password.

REPLY

anjali 26 October 2020 at 03:13

How to check , whether the same SAP user is already


logged in SAP applicaiton. This is to avoid multiuser login
.

REPLY

Brian Chan 3 December 2020 at 18:51

You have to check in sapgui using transaction code SM04


to view it.

REPLY

Enter your comment...

Popular posts from this blog

How to Create Sap Gui Scripting


December 16, 2014

SAP GUI Scripting syntax similar like VBScript and you


can used setup your testing data or data migration
from legacy system to SAP. Is easy and less time to …

READ MORE

Excel Macros for Live Stock List


Este sitio utiliza cookies de Google para prestar sus servicios y para
August su
analizar 17,tráfico.
2016 Tu dirección IP y user-agent se comparten con
Google, junto con las métricas de rendimiento y de seguridad, para
garantizar la calidad
Here mydel servicio,
new post on how togenerar estadísticas
use excel macros to get de uso y
detectar y solucionar abusos.
stocks price. You can refer screen shot below, there's
table on the stock
MÁSname, pricing, volume
INFORMACIÓN and etc. I'll …
ACEPTAR

https://macrostutorials.blogspot.com/2017/08/excel-vba-connect-saprfc.html 13/14
3/15/2021 Excel VBA connect SAPRFC

READ MORE

Powered by Blogger

Theme images by Radius Images

Cookie Consent

Macros Tutorial
How to protect Macros code
Video Tutorial
Other Macros Tutorial
1. Variable
2. Other Variable Types
3. Condition
4. Looping Statement
5. Procedure

Report abuse

Followers
Seguidores (0)

Seguir

Este sitio utiliza cookies de Google para prestar sus servicios y para
analizar su tráfico. Tu dirección IP y user-agent se comparten con
Google, junto con las métricas de rendimiento y de seguridad, para
garantizar la calidad del servicio, generar estadísticas de uso y
detectar y solucionar abusos.
MÁS INFORMACIÓN ACEPTAR

https://macrostutorials.blogspot.com/2017/08/excel-vba-connect-saprfc.html 14/14

You might also like