Application Development Discussions
Join the discussions or start your own on all things application development, including tools and APIs, programming models, and keeping your skills sharp.
cancel
Showing results for 
Search instead for 
Did you mean: 

select field 'B' based on field 'A'

Former Member
0 Kudos

Hi,

I have a report with selection screen. I want to display the list of possible entries for field 'B' as per the value in field 'A'.

I am doing this on event

<b>"Selection screen on value-request for <B></b>

using functional module

<b>'REUSE_ALV_POPUP_TO_SELECT'</b>

Everything is fine except one problem.

Let's take a example that screen has two fields

A).

<b>parsmeters: p_vbeln like vbap-vbeln.</b>

"Sales order number

B).

<b>parameters: p_posnr like vbap-posnr.</b>

"line item

Based on sales order number i have to show an popup with corresponding line item numbers. and i have coded this under,

<b>Selection screen on value-request for POSNR</b>

<u><b>Scenario 1:</b></u> i enter the sales order number in the field p_vbeln <b>and hit enter</b>

when i do F4 on p_posnr, it displays the popup with corresponding line items.

<b>This works fine</b>

<u><b>Scenario 2:</b></u> i just type in the sales order number and <b>do not hit enter or anything)</b>

Now if i do F4 on p_posnr, it doesn't display the line items, since there is not value populated in p_vbeln as entered it but did not press enter.

I hope i am making sense.

So, my problem is how display possible value for field 'B' if user type in the value in field 'A' but do not hit enter.

Please let me know.

Thanks,

Pal

1 ACCEPTED SOLUTION

Former Member
0 Kudos

Hi ,

You can try using the FM "DYNP_VALUES_READ" to get the value of the other field before you trigger your F4 help on line item fields.

This situation occurs when the selection screen is complex and it happens in many situations. Mostly this situations occurs when you have mulitple radio buttons with multiple box frames defined for the selection screen or if you have defined tabs on selection screen.

SAP has documented that FM nicely with example. You can try that and i am sure it would work for you.

All the best!!

Cheers

VJ

8 REPLIES 8

Former Member
0 Kudos

Hi ,

You can try using the FM "DYNP_VALUES_READ" to get the value of the other field before you trigger your F4 help on line item fields.

This situation occurs when the selection screen is complex and it happens in many situations. Mostly this situations occurs when you have mulitple radio buttons with multiple box frames defined for the selection screen or if you have defined tabs on selection screen.

SAP has documented that FM nicely with example. You can try that and i am sure it would work for you.

All the best!!

Cheers

VJ

0 Kudos

Here is how we usually do it when providing F4 help, you can use this logic for your requirement as well.



report zrich_0002 .

parameters: p_vbeln type vbak-vbeln,
            p_posnr type vbap-posnr.

at selection-screen on value-request for p_posnr.


  data: begin of help_item occurs 0,
          posnr type vbap-posnr,
          matnr type vbap-matnr,
          arktx type vbap-arktx,
        end of help_item.

  data: dynfields type table of dynpread with header line.


  dynfields-fieldname = 'P_VBELN'.
  append dynfields.

  call function 'DYNP_VALUES_READ'
       exporting
            dyname               = sy-cprog
            dynumb               = sy-dynnr
            translate_to_upper   = 'X'
       tables
            dynpfields           = dynfields
       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.


  read table dynfields with key fieldname = 'P_VBELN'.

  p_vbeln = dynfields-fieldvalue.


  call function 'CONVERSION_EXIT_ALPHA_INPUT'
       exporting
            input  = p_vbeln
       importing
            output = p_vbeln.

  select posnr matnr arktx into table help_item
                 from vbap
                      where vbeln = p_vbeln.



  call function 'F4IF_INT_TABLE_VALUE_REQUEST'
       exporting
            retfield    = 'POSNR'
            dynprofield = 'P_POSNR'
            dynpprog    = sy-cprog
            dynpnr      = sy-dynnr
            value_org   = 'S'
       tables
            value_tab   = help_item.

Please be sure to award points for helpful answers and mark your post as solved when solved completely. Thanks.

Regards,

Rich Heilman

Former Member
0 Kudos

DATA: LTAB_FIELDS LIKE DYNPREAD OCCURS 0 WITH HEADER LINE,

LC_PROG LIKE D020S-PROG,

LC_DNUM LIKE D020S-DNUM.

TRANSLATE F_FIELD TO UPPER CASE.

refresh ltab_fields.

LTAB_FIELDS-FIELDNAME = P_POSNR.

append ltab_fields.

LC_PROG = SY-REPID .

LC_DNUM = SY-DYNNR .

CALL FUNCTION 'DYNP_VALUES_READ'

EXPORTING

DYNAME = LC_PROG

DYNUMB = LC_DNUM

TABLES

dynpfields = LTAB_FIELDS

EXCEPTIONS

OTHERS = 01.

read table LTAB_FIELDS index 1.

IF SY-SUBRC EQ 0.

P_POSNR = LTAB_FIELDS-FIELDVALUE.

refresh LTAB_FIELDS.

ENDIF.

Then call F4IF_FIELD_VALUE_REQUEST.

Thanks,

Pramod

Former Member
0 Kudos

Hi,

See this sample code:

DATA: BEGIN OF iitab OCCURS 0.
        INCLUDE STRUCTURE dynpread.
DATA: END OF iitab.

DATA: BEGIN OF rtab OCCURS 0.
        INCLUDE STRUCTURE ddshretval.
DATA: END OF rtab.

DATA: BEGIN OF t_maktx.
        INCLUDE STRUCTURE t001.
DATA: END OF t_maktx.

DATA: t_bukrs LIKE t001-bukrs.

**-------------------------------
PARAMETERS : bukrs LIKE t001-bukrs. "MATCHCODE OBJECT C_T001.
PARAMETERS : butxt LIKE t001-butxt.
**------------------------
AT SELECTION-SCREEN ON VALUE-REQUEST FOR bukrs.
*

  CALL FUNCTION 'F4IF_FIELD_VALUE_REQUEST'
    EXPORTING
      tabname    = 'T001'
      fieldname  = 'BUKRS'
    TABLES
      return_tab = rtab.
  IF sy-subrc <> 0.
* MESSAGE ID SY-MSGID TYPE SY-MSGTY NUMBER SY-MSGNO
* WITH SY-MSGV1 SY-MSGV2 SY-MSGV3 SY-MSGV4.
  ENDIF.


  CLEAR iitab.
  REFRESH iitab.
  iitab-fieldname = 'BUKRS'.
  APPEND iitab.
  iitab-fieldname = 'BUTXT'.
  APPEND iitab.

  READ TABLE rtab. "with key fieldname = 'MATNR'.
  t_bukrs = rtab-fieldval.

  SELECT SINGLE * FROM t001 INTO t_maktx WHERE bukrs = t_bukrs .
  READ TABLE iitab WITH KEY fieldname = 'BUKRS'.
  iitab-fieldvalue = t_bukrs.
  MODIFY iitab TRANSPORTING fieldvalue WHERE fieldname = 'BUKRS'.
  READ TABLE iitab WITH KEY fieldname = 'BUTXT'.
  iitab-fieldvalue = t_maktx-butxt.
  MODIFY iitab TRANSPORTING fieldvalue WHERE fieldname = 'BUTXT'.

  CALL FUNCTION 'DYNP_VALUES_UPDATE'
  EXPORTING
  dyname = sy-cprog
  dynumb = sy-dynnr
  TABLES
  dynpfields = iitab
* EXCEPTIONS
* INVALID_ABAPWORKAREA = 1
* INVALID_DYNPROFIELD = 2
* INVALID_DYNPRONAME = 3
* INVALID_DYNPRONUMMER = 4
* INVALID_REQUEST = 5
* NO_FIELDDESCRIPTION = 6
* UNDEFIND_ERROR = 7
* OTHERS = 8
  .
  IF sy-subrc <> 0.
* MESSAGE ID SY-MSGID TYPE SY-MSGTY NUMBER SY-MSGNO
* WITH SY-MSGV1 SY-MSGV2 SY-MSGV3 SY-MSGV4.
  ENDIF.

start-of-selection.

Regards,

Anjali

vinod_gunaware2
Active Contributor
0 Kudos

*-- F4 help for Payroll Administrator

AT SELECTION SCREEN ON VALUE REQUEST FOR P_SACHA.

PERFORM VALUES_SACHA.

*-- F4 help for Pay Scale Group

AT SELECTION SCREEN ON VALUE REQUEST FOR P_TRFGR.

*-- F4 help for Pay Scale Level

AT SELECTION SCREEN ON VALUE REQUEST FOR P_TRFST.

----


  • FORM VALUES_SACHA

----


  • Provide popup help for the Payroll Admin field

----


FORM VALUES_SACHA.

REFRESH: LTAB_DYNPSELECT,

LTAB_DYNPVALUETAB.

PERFORM READ_VALUE_FROM_SCREEN USING SY-REPID

SY-DYNNR

'PA0001-WERKS'

CHANGING LTAB_DYNPSELECT-FLDNAME

LTAB_DYNPSELECT-FLDINH.

APPEND LTAB_DYNPSELECT.

LTAB_DYNPSELECT-FLDNAME = 'MANDT'.

APPEND LTAB_DYNPSELECT.

LTAB_DYNPSELECT-FLDNAME = 'SACHX'.

APPEND LTAB_DYNPSELECT.

PERFORM SHOW_HELP TABLES LTAB_DYNPSELECT

LTAB_DYNPVALUETAB

USING 'T526'

'SACHX'

CHANGING PA0001-SACHA.

ENDFORM. " VALUES_SACHA

----


  • FORM VALUES_TRFGR

----


  • Provide popup help for Pay Scale Group

----


FORM VALUES_TRFGR.

REFRESH: LTAB_DYNPSELECT,

LTAB_DYNPVALUETAB.

LTAB_DYNPSELECT-FLDNAME = 'MANDT'.

APPEND LTAB_DYNPSELECT.

LTAB_DYNPSELECT-FLDNAME = 'MOLGA'.

SELECT SINGLE MOLGA FROM T001P

INTO LTAB_DYNPSELECT-FLDINH

WHERE WERKS = *PA0001-WERKS

AND BTRTL = *PA0001-BTRTL.

IF SY-SUBRC NE 0.

LTAB_DYNPSELECT-FLDINH = SPACE.

ENDIF.

APPEND LTAB_DYNPSELECT.

LTAB_DYNPSELECT-FLDNAME = 'TRFAR'.

LTAB_DYNPSELECT-FLDINH = *PA0008-TRFAR.

APPEND LTAB_DYNPSELECT.

LTAB_DYNPSELECT-FLDNAME = 'TRFGB'.

LTAB_DYNPSELECT-FLDINH = *PA0008-TRFGB.

APPEND LTAB_DYNPSELECT.

LTAB_DYNPSELECT-FLDNAME = 'TRFKZ'.

SELECT SINGLE TRFKZ FROM T503

INTO LTAB_DYNPSELECT-FLDINH

WHERE PERSG = *PA0001-PERSG

AND PERSK = *PA0001-PERSK.

IF SY-SUBRC NE 0.

LTAB_DYNPSELECT-FLDINH = SPACE.

ENDIF.

APPEND LTAB_DYNPSELECT.

LTAB_DYNPSELECT-FLDNAME = 'TRFGR'.

LTAB_DYNPSELECT-FLDINH = SPACE.

APPEND LTAB_DYNPSELECT.

PERFORM SHOW_HELP TABLES LTAB_DYNPSELECT

LTAB_DYNPVALUETAB

USING 'T510'

'TRFGR'

CHANGING PA0008-TRFGR.

PERFORM UPDATE_VALUE_ON_SCREEN USING SY-REPID

SY-DYNNR

'PA0008-TRFGR'

PA0008-TRFGR.

ENDFORM. " VALUES_TRFGR

----


  • FORM VALUES_TRFST

----


  • Provide popup help for Pay Scale Area

----


FORM VALUES_TRFST.

REFRESH: LTAB_DYNPSELECT,

LTAB_DYNPVALUETAB.

LTAB_DYNPSELECT-FLDNAME = 'MANDT'.

APPEND LTAB_DYNPSELECT.

LTAB_DYNPSELECT-FLDNAME = 'MOLGA'.

SELECT SINGLE MOLGA FROM T001P

INTO LTAB_DYNPSELECT-FLDINH

WHERE WERKS = *PA0001-WERKS

AND BTRTL = *PA0001-BTRTL.

IF SY-SUBRC NE 0.

LTAB_DYNPSELECT-FLDINH = SPACE.

ENDIF.

APPEND LTAB_DYNPSELECT.

LTAB_DYNPSELECT-FLDNAME = 'TRFAR'.

LTAB_DYNPSELECT-FLDINH = *PA0008-TRFAR.

APPEND LTAB_DYNPSELECT.

LTAB_DYNPSELECT-FLDNAME = 'TRFGB'.

LTAB_DYNPSELECT-FLDINH = *PA0008-TRFGB.

APPEND LTAB_DYNPSELECT.

LTAB_DYNPSELECT-FLDNAME = 'TRFKZ'.

SELECT SINGLE TRFKZ FROM T503

INTO LTAB_DYNPSELECT-FLDINH

WHERE PERSG = *PA0001-PERSG

AND PERSK = *PA0001-PERSK.

IF SY-SUBRC NE 0.

LTAB_DYNPSELECT-FLDINH = SPACE.

ENDIF.

APPEND LTAB_DYNPSELECT.

PERFORM READ_VALUE_FROM_SCREEN USING SY-REPID

SY-DYNNR

'PA0008-TRFGR'

CHANGING LTAB_DYNPSELECT-FLDNAME

LTAB_DYNPSELECT-FLDINH.

APPEND LTAB_DYNPSELECT.

LTAB_DYNPSELECT-FLDNAME = 'TRFST'.

LTAB_DYNPSELECT-FLDINH = SPACE.

APPEND LTAB_DYNPSELECT.

PERFORM SHOW_HELP TABLES LTAB_DYNPSELECT

LTAB_DYNPVALUETAB

USING 'T510'

'TRFST'

CHANGING PA0008-TRFST.

PERFORM UPDATE_VALUE_ON_SCREEN USING SY-REPID

SY-DYNNR

'PA0008-TRFST'

PA0008-TRFST.

ENDFORM. " VALUES_TRFST

----


  • FORM SHOW_HELP *

----


  • ........ *

----


  • --> FTAB_DYNPSELECT *

  • --> FTAB_DYNPVALUETAB *

  • --> FSTR_HELP_INFO *

  • --> F_NEWVALUE *

----


FORM SHOW_HELP TABLES FTAB_DYNPSELECT STRUCTURE DSELC

FTAB_DYNPVALUETAB STRUCTURE DVAL

USING F_CHECKTABLE LIKE HELP_INFO-CHECKTABLE

F_CHECKFIELD LIKE HELP_INFO-CHECKFIELD

CHANGING F_NEWVALUE.

DATA: LSTR_HELP_INFO LIKE HELP_INFO.

DATA: LC_SELECTION_VALUE LIKE HELP_INFO-FLDVALUE.

DATA: LC_SELECTION(1) TYPE C.

*-- Fill in fields required for help function call

LSTR_HELP_INFO-CALL = 'T'.

LSTR_HELP_INFO-OBJECT = 'F'.

LSTR_HELP_INFO-SPRAS = SY-LANGU.

LSTR_HELP_INFO-CHECKTABLE = F_CHECKTABLE.

LSTR_HELP_INFO-CHECKFIELD = F_CHECKFIELD.

CALL FUNCTION 'HELP_START'

EXPORTING

HELP_INFOS = LSTR_HELP_INFO

IMPORTING

SELECTION = LC_SELECTION

SELECT_VALUE = LC_SELECTION_VALUE

TABLES

DYNPSELECT = FTAB_DYNPSELECT

DYNPVALUETAB = FTAB_DYNPVALUETAB

EXCEPTIONS

OTHERS = 1.

IF LC_SELECTION NE SPACE AND SY-SUBRC = 0.

F_NEWVALUE = LC_SELECTION_VALUE.

ENDIF.

ENDFORM. " SHOW_HELP

----


  • FORM READ_VALUE_FROM_SCREEN *

----


  • ........ *

----


  • --> F_REPID *

  • --> F_DYNNR *

  • --> VALUE(F_FIELDNAME_IN) *

  • --> F_FIELDNAME_OUT *

  • --> F_FIELDVALUE *

----


FORM READ_VALUE_FROM_SCREEN USING F_REPID

F_DYNNR

VALUE(F_FIELDNAME_IN)

CHANGING F_FIELDNAME_OUT

F_FIELDVALUE.

DATA: LTAB_FIELDS LIKE DYNPREAD OCCURS 0 WITH HEADER LINE.

DATA: LC_DYNAME LIKE SY-REPID.

DATA: LC_DYNUMB LIKE SY-DYNNR.

DATA: LC_DUMMY(1) TYPE C.

*-- Read the screen to see if the user has entered a value for WERKS

LTAB_FIELDS-FIELDNAME = F_FIELDNAME_IN.

append ltab_fields.

LC_DYNAME = F_REPID.

LC_DYNUMB = F_DYNNR.

CALL FUNCTION 'DYNP_VALUES_READ'

EXPORTING

DYNAME = LC_DYNAME

DYNUMB = LC_DYNUMB

TABLES

dynpfields = ltab_fields

EXCEPTIONS

OTHERS = 01.

read table ltab_fields index 1.

*-- Return the value from the screen

IF SY-SUBRC EQ 0.

SPLIT LTAB_FIELDS-FIELDNAME AT '-'

INTO LC_DUMMY

F_FIELDNAME_OUT.

F_FIELDVALUE = LTAB_FIELDS-FIELDVALUE.

ENDIF.

ENDFORM. " READ_VALUE_FROM_SCREEN

----


  • FORM UPDATE_VALUE_ON_SCREEN *

----


  • The PROCESS ON VALUE-REQUEST does not always return blanks. *

  • If a blank value is to be returned, this routine must be *

  • called.

----


  • --> F_REPID *

  • --> F_DYNNR *

  • --> VALUE(F_FIELDNAME) *

  • --> F_FIELDVALUE *

----


FORM UPDATE_VALUE_ON_SCREEN USING F_REPID F_DYNNR VALUE(F_FIELDNAME) F_FIELDVALUE.

DATA: LTAB_FIELDS LIKE DYNPREAD OCCURS 0 WITH HEADER LINE.

DATA: LC_DYNAME LIKE SY-REPID.

DATA: LC_DYNUMB LIKE SY-DYNNR.

LC_DYNAME = SY-REPID.

LC_DYNUMB = SY-DYNNR.

LTAB_FIELDS-FIELDNAME = F_FIELDNAME.

LTAB_FIELDS-FIELDVALUE = F_FIELDVALUE.

APPEND LTAB_FIELDS.

CALL FUNCTION 'DYNP_VALUES_UPDATE'

EXPORTING DYNAME = LC_DYNAME

DYNUMB = LC_DYNUMB

TABLES DYNPFIELDS = LTAB_FIELDS

EXCEPTIONS OTHERS = 8.

ENDFORM. " UPDATE_VALUE_ON_SCREEN

regards

vinod

jayanthi_jayaraman
Active Contributor
0 Kudos

Hi,

Check this sample code and kindly reward points by clicking the star on the left of reply,if it helps.

REPORT  ZGK_TEST
        message-id zsd
        line-count 16(1)
        no standard page heading .
*----------------------------------------------------------------------*
*                        Tables Declaration
*----------------------------------------------------------------------*

tables : vbap.         " Sales Document: Item Data
*----------------------------------------------------------------------*
*                      Constant Declaration                           		 *
*----------------------------------------------------------------------*

CONSTANTS:
  C_X TYPE C VALUE 'X'.     " Translate to Uppercase
*----------------------------------------------------------------------*
*                      Variable Declaration                            		*
*----------------------------------------------------------------------*

* Variable for Table index
  data v_sytabix like sy-tabix.

* Variable for Program name
  data L_NAME LIKE SYST-REPID.
*----------------------------------------------------------------------*
*                         Ranges Declaration                           		*
*----------------------------------------------------------------------*

* Range for getting values form selection screen
 DATA: BEGIN OF range1 OCCURS 0,
         SIGN(1),
         OPTION(2),
         LOW  LIKE vbap-vbeln,
         high like vbap-vbeln,
      END OF range1.
*----------------------------------------------------------------------*
*                         Structure Declaration                        		*
*----------------------------------------------------------------------*

*----------------------------------------------------------------------*
*                    Internal table Declaration                        		*
*----------------------------------------------------------------------*

* Internal table for Report output
  data: begin of i_vbap occurs 0,
          vbeln like vbap-vbeln,            " Sales Document
          posnr like vbap-posnr,            " Sales Document item
        end of i_vbap.

* Internal table for output to the F4 help
  data: begin of I_DISPLAY occurs 0,
          vbeln like vbap-vbeln,            " Sales Document
          posnr like vbap-posnr,            " Sales Document item
        end of I_DISPLAY.

* Internal table for return value form function module
  DATA: BEGIN OF I_RETURNVAL OCCURS 0.
          INCLUDE STRUCTURE DDSHRETVAL.     " Interface Structure Search
  DATA: END OF I_RETURNVAL.

* Internal table for F4 help field heading
  DATA: I_FIELDTAB LIKE DFIES OCCURS 0 WITH HEADER LINE.

* Internal table for getting screen values from selection screen
  data L_SCR_FIELDS LIKE DYNPREAD OCCURS 1 WITH HEADER LINE.
*----------------------------------------------------------------------*
*                      Field-Symbols                                   *
*----------------------------------------------------------------------*

*----------------------------------------------------------------------*
*                      Selection-screen                                *
*----------------------------------------------------------------------*

SELECTION-SCREEN BEGIN OF BLOCK B1 WITH FRAME title text-001.
  select-options:
        S_VBELN for vbap-vbeln no intervals,
        S_POSNR for vbap-posnr no intervals.
SELECTION-SCREEN end OF BLOCK B1.
*----------------------------------------------------------------------*
*                      AT SELECTION-SCREEN ON VALUE-REQUEST            *
*----------------------------------------------------------------------*

at selection-screen on value-request for s_posnr-low.

  clear: L_SCR_FIELDS, I_FIELDTAB, i_display, I_RETURNVAL.
  refresh: L_SCR_FIELDS, I_FIELDTAB, i_display, I_RETURNVAL.

  L_NAME = SYST-REPID.

  MOVE 'S_VBELN-LOW' TO L_SCR_FIELDS-FIELDNAME.
  APPEND L_SCR_FIELDS.

* Call the Function module DYNP_VALUES_READ to get the values form
* selection screen
  CALL FUNCTION 'DYNP_VALUES_READ'
    EXPORTING
      DYNAME                         = L_NAME
      DYNUMB                         = SYST-DYNNR
      TRANSLATE_TO_UPPER             = C_X         " X
    TABLES
      DYNPFIELDS                     = L_SCR_FIELDS
   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 eq 0.
    LOOP AT L_SCR_FIELDS.
      range1-sign = 'I'.
      range1-option = 'EQ'.
      range1-low = L_SCR_FIELDS-FIELDVALUE.
      range1-high = space.
      append range1.
    ENDLOOP.
  ENDIF.


* F4 help Field headings

  I_FIELDTAB-TABNAME = 'I_DISPLAY'.

  I_FIELDTAB-FIELDNAME = 'VBELN'.
  I_FIELDTAB-POSITION = '1'.
  I_FIELDTAB-OUTPUTLEN = '10'.
  I_FIELDTAB-INTTYPE = 'C'.
  I_FIELDTAB-INTLEN = '10'.
  APPEND I_FIELDTAB.

  I_FIELDTAB-FIELDNAME = 'POSNR'.
  I_FIELDTAB-POSITION = '2'.
  I_FIELDTAB-OFFSET = '10'.
  I_FIELDTAB-OUTPUTLEN = '6'.
  I_FIELDTAB-INTTYPE = 'N'.
  I_FIELDTAB-INTLEN = '6'.
  APPEND I_FIELDTAB.

* Retrieve sales document, Sales document item from table Sales
* Document: Item Data(VBAP).
* Primary keys used for selection: VBELN
  select vbeln posnr from vbap
               into table i_display
               where vbeln in range1.

* Call the function module F4IF_INT_TABLE_VALUE_REQUEST for F4 values

  CALL FUNCTION 'F4IF_INT_TABLE_VALUE_REQUEST'
    EXPORTING
      RETFIELD               = 'POSNR'
      WINDOW_TITLE           = 'Line Item'
      VALUE_ORG              = 'S'
      MULTIPLE_CHOICE        = C_X           " (for muliple selection)
    TABLES
      VALUE_TAB              = I_DISPLAY
      FIELD_TAB              = I_FIELDTAB
      RETURN_TAB             = I_RETURNVAL
    EXCEPTIONS
      PARAMETER_ERROR        = 1
      NO_VALUES_FOUND        = 2
      OTHERS                 = 3
          .
  IF SY-SUBRC <> 0.
* MESSAGE ID SY-MSGID TYPE SY-MSGTY NUMBER SY-MSGNO
*         WITH SY-MSGV1 SY-MSGV2 SY-MSGV3 SY-MSGV4.
  ELSE.

* Star for For single values
*   READ TABLE I_RETURNVAL INDEX 1.
*    S_POSNR-LOW = I_RETURNVAL-FIELDVAL.
* End for the single values

* Start For multiple selection
   loop at i_returnval.
     s_posnr-sign = 'I'.
     s_posnr-option = 'EQ'.
     s_posnr-low = I_RETURNVAL-FIELDVAL.
     append s_posnr.
   endloop.
   sort s_posnr.
   read table s_posnr index 1.
* End for multiple selection
  ENDIF.
*----------------------------------------------------------------------*
*                      Start-of-selection                              		*
*----------------------------------------------------------------------*

start-of-selection.
* Retrieve sales document, Sales document item from table Sales
* Document: Item Data(VBAP).
* Primary keys used for selection: VBELN
  select vbeln posnr from vbap
                    into table i_vbap
                    where vbeln in s_vbeln
                      and posnr in s_posnr.
* if the above selection is successful continue the process else exit *
* form the report
  if sy-subrc ne 0.
*    message e002 with 'No data to display'.
  endif.

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

*                        End-of-selection                              		*

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

end-of-selection.
  if not i_vbap[] is initial.
    loop at i_vbap.
      write:/ i_vbap-vbeln, i_vbap-posnr.
    endloop.
  endif.

Former Member
0 Kudos

hi,

U can use at selection screen event and then call FM 'REUSE_ALV_POPUP_TO_SELECT' .

Hope this helps.

regards

pragya

Former Member
0 Kudos

HI,

You can use at selction screen event wherein you can use fm 'REUSE_ALV_POPUP_TO_SELECT'.

hope this helps.

regards

pragya