SAP R/3 форум ABAP консультантов
Russian ABAP Developer's Club

Home - FAQ - Search - Memberlist - Usergroups - Profile - Log in to check your private messages - Register - Log in - English
Blogs - Weblogs News

List of Users According to Logon Date and Password Change



 
Post new topic   Reply to topic    Russian ABAP Developer's Club Forum Index -> Security and Monitoring
View previous topic :: View next topic  
Author Message
admin
Администратор
Администратор



Joined: 01 Sep 2007
Posts: 1639

PostPosted: Sat Jan 26, 2008 4:43 pm    Post subject: List of Users According to Logon Date and Password Change Reply with quote

Code:
REPORT z_alv_rsusr200.
*---------------------------------------------------------------------*
* List of Users According to Logon Date and Password Change           *
* Copy of standard program RSUSR200                                   *
*---------------------------------------------------------------------*
* Author : Michel PIOUD                                               *
* Email : [email protected]  HomePage : http://www.geocities.com/mpioud *
*---------------------------------------------------------------------*
CONSTANTS :
  c_typdia          VALUE 'A', " Dialog users
  c_typbatch        VALUE 'B', " Batch users
  c_typcpic         VALUE 'C', " System users
  c_typsim          VALUE 'S', " Service users
  c_yulock   TYPE x VALUE '80'," Incorrect logons.
  c_yusloc   TYPE x VALUE '40'," Administrator lock
  c_yugloc   TYPE x VALUE '20'," Global lock
  c_x VALUE 'X',
  c_refresh TYPE syucomm VALUE '&REFRESH'.
*---------------------------------------------------------------------*
TYPE-POOLS :
  icon,                                " Icons
  slis.                                " ALV Global types
*---------------------------------------------------------------------*
TYPES :
  BEGIN OF ty_s_usr02.
INCLUDE TYPE usr02.       " Logon data
TYPES :
   name_text TYPE ad_namtext,
   icon_pwd(30),
   icon_lock(30),
   text_lock(40),
   icon_con(40),
   checkbox(1),
  END OF  ty_s_usr02.
*---------------------------------------------------------------------*
DATA:
  gs_usr02 TYPE usr02,
  gt_data  TYPE TABLE OF ty_s_usr02.
*---------------------------------------------------------------------*
FIELD-SYMBOLS :
  <data> TYPE ty_s_usr02.
*---------------------------------------------------------------------*
SELECTION-SCREEN BEGIN OF BLOCK main WITH FRAME TITLE text_021.
SELECTION-SCREEN BEGIN OF LINE.
SELECTION-SCREEN COMMENT 1(31) text_100 FOR FIELD s_mandt.
SELECT-OPTIONS s_mandt FOR gs_usr02-mandt DEFAULT sy-mandt
                 MATCHCODE OBJECT ddsef4clnt.
SELECTION-SCREEN END OF LINE.
SELECTION-SCREEN BEGIN OF LINE.
SELECTION-SCREEN COMMENT 1(31) text_101 FOR FIELD s_bname.
SELECT-OPTIONS s_bname FOR gs_usr02-bname MATCHCODE OBJECT user_comp.
SELECTION-SCREEN END OF LINE.
SELECTION-SCREEN BEGIN OF LINE.
SELECTION-SCREEN COMMENT 1(31) text_102 FOR FIELD s_class.
SELECT-OPTIONS s_class FOR gs_usr02-class.
SELECTION-SCREEN END OF LINE.
SELECTION-SCREEN BEGIN OF LINE.
SELECTION-SCREEN COMMENT 1(34) text_103 FOR FIELD p_dtrdat.
PARAMETER p_dtrdat TYPE i.
SELECTION-SCREEN END OF LINE.
SELECTION-SCREEN BEGIN OF LINE.
SELECTION-SCREEN COMMENT 1(34) text_104 FOR FIELD p_dbcda1.
PARAMETER p_dbcda1 TYPE i.
SELECTION-SCREEN END OF LINE.
SELECTION-SCREEN END OF BLOCK main.

SELECTION-SCREEN BEGIN OF BLOCK validity WITH FRAME TITLE text_036.
SELECTION-SCREEN BEGIN OF LINE.
PARAMETER p_valid AS CHECKBOX DEFAULT c_x.
SELECTION-SCREEN COMMENT 2(40) text_034 FOR FIELD p_valid.
SELECTION-SCREEN END OF LINE.
SELECTION-SCREEN BEGIN OF LINE.
PARAMETER notvalid AS CHECKBOX DEFAULT c_x.
SELECTION-SCREEN COMMENT 2(40) text_035 FOR FIELD notvalid.
SELECTION-SCREEN END OF LINE.
SELECTION-SCREEN END OF BLOCK validity.

SELECTION-SCREEN BEGIN OF BLOCK activity WITH FRAME TITLE text_022.
SELECTION-SCREEN BEGIN OF LINE.
PARAMETER unlocked AS CHECKBOX DEFAULT c_x.
SELECTION-SCREEN COMMENT 2(40) text_009 FOR FIELD unlocked.
SELECTION-SCREEN END OF LINE.
SELECTION-SCREEN BEGIN OF LINE.
PARAMETER locked   AS CHECKBOX DEFAULT c_x.
SELECTION-SCREEN COMMENT 2(40) text_020 FOR FIELD locked.
SELECTION-SCREEN END OF LINE.
SELECTION-SCREEN BEGIN OF LINE.
PARAMETER faillog  AS CHECKBOX DEFAULT c_x.
SELECTION-SCREEN COMMENT 2(40) text_019 FOR FIELD faillog.
SELECTION-SCREEN END OF LINE.
SELECTION-SCREEN END OF BLOCK activity.

SELECTION-SCREEN BEGIN OF BLOCK type WITH FRAME TITLE text_023.
SELECTION-SCREEN BEGIN OF LINE.
PARAMETER diaguser AS CHECKBOX DEFAULT c_x.
SELECTION-SCREEN COMMENT 2(40) text_015 FOR FIELD diaguser.
SELECTION-SCREEN END OF LINE.
SELECTION-SCREEN BEGIN OF LINE.
PARAMETER commuser AS CHECKBOX DEFAULT c_x.
SELECTION-SCREEN COMMENT 2(40) text_030 FOR FIELD commuser.
SELECTION-SCREEN END OF LINE.
SELECTION-SCREEN BEGIN OF LINE.
PARAMETER sysuser AS CHECKBOX DEFAULT c_x.
SELECTION-SCREEN COMMENT 2(40) text_029 FOR FIELD sysuser.
SELECTION-SCREEN END OF LINE.
SELECTION-SCREEN BEGIN OF LINE.
PARAMETER servuser AS CHECKBOX DEFAULT c_x.
SELECTION-SCREEN COMMENT 2(40) text_032 FOR FIELD servuser.
SELECTION-SCREEN END OF LINE.
SELECTION-SCREEN END OF BLOCK type.

SELECTION-SCREEN BEGIN OF BLOCK pass WITH FRAME TITLE text_024.
SELECTION-SCREEN BEGIN OF LINE.
PARAMETER defpass AS CHECKBOX DEFAULT c_x.
SELECTION-SCREEN COMMENT 2(40) text_033 FOR FIELD defpass.
SELECTION-SCREEN END OF LINE.
SELECTION-SCREEN BEGIN OF LINE.
PARAMETER initpass AS CHECKBOX DEFAULT c_x.
SELECTION-SCREEN COMMENT 2(40) text_008 FOR FIELD initpass.
SELECTION-SCREEN END OF LINE.
SELECTION-SCREEN END OF BLOCK pass.
*---------------------------------------------------------------------*
AT SELECTION-SCREEN.

  IF  (    unlocked  IS INITIAL
       AND locked    IS INITIAL
       AND faillog   IS INITIAL )
    OR
      (    p_valid   IS INITIAL
       AND notvalid  IS INITIAL )
    OR
      (    diaguser  IS INITIAL
       AND commuser  IS INITIAL
       AND sysuser   IS INITIAL
       AND servuser  IS INITIAL )
    OR
      (    initpass  IS INITIAL
       AND defpass   IS INITIAL ).
*   Please make a selection
    MESSAGE e609(00).
  ENDIF.

*---------------------------------------------------------------------*
INITIALIZATION.

  text_008 = 'Users with initial password         '(008).
  text_009 = 'Not locked users                    '(009).
  text_015 = 'Dialog users                        '(015).
  text_019 = 'Users with failed logon             '(019).
  text_020 = 'Locked users                        '(020).
  text_021 = 'Standard selection                  '(021).
  text_022 = 'Selection by users status           '(022).
  text_023 = 'Selection by user type              '(023).
  text_024 = 'Selection by password status        '(024).
  text_029 = 'System users                        '(029).
  text_030 = 'Communication users                 '(030).
  text_032 = 'Service users                       '(032).
  text_033 = 'Users with defined password         '(033).
  text_034 = 'Users valid today                   '(034).
  text_035 = 'Users not valid today               '(035).
  text_036 = 'Users Validity                      '(036).
  text_100 = 'Client                              '(100).
  text_101 = 'User                                '(101).
  text_102 = 'Users group                         '(102).
  text_103 = 'No. days since last logon           '(103).
  text_104 = 'No. days since password change      '(104).

*---------------------------------------------------------------------*
START-OF-SELECTION.

* Check authorization
  AUTHORITY-CHECK OBJECT 'S_USER_GRP'
                  ID 'CLASS' DUMMY
                  ID 'ACTVT' FIELD '03'.    " Display
  IF sy-subrc NE 0.
*   You are not authorized to use function &
    MESSAGE e150(00) WITH 'Display user'(014).
  ENDIF.

  PERFORM f_read_data.

*---------------------------------------------------------------------*
END-OF-SELECTION.

  PERFORM f_display_data.

*---------------------------------------------------------------------*
*      Form  f_read_data
*---------------------------------------------------------------------*
FORM f_read_data.

  DATA :
    l_usr02flag TYPE x,
    lt_uinfo    TYPE TABLE OF uinfo.

  gs_usr02-trdat = sy-datum - p_dtrdat.
  gs_usr02-bcda1 = sy-datum - p_dbcda1.

* Read data
  SELECT u~mandt u~bname gltgb gltgv class trdat bcda1 ltime locnt
           uflag ustyp aname erdat name_text
           INTO CORRESPONDING FIELDS OF TABLE gt_data
           FROM usr02 AS u
           JOIN usr21 AS s
             ON u~mandt = s~mandt
            AND u~bname = s~bname
           JOIN adrp AS a
             ON a~client = s~mandt
            AND a~persnumber = s~persnumber
         CLIENT SPECIFIED
          WHERE u~mandt IN s_mandt
            AND u~bname IN s_bname
            AND class IN s_class
            AND trdat LE gs_usr02-trdat
            AND bcda1 LE gs_usr02-bcda1.

* Get connected users
  PERFORM get_users CHANGING lt_uinfo.

  LOOP AT gt_data ASSIGNING <data>.

    l_usr02flag = <data>-uflag.
*   Valid users
    IF   (    NOT p_valid    IS INITIAL
              AND (  (   <data>-gltgb GE sy-datum
                     AND <data>-gltgv LE sy-datum )
                  OR (   <data>-gltgv IS INITIAL
                     AND <data>-gltgb IS INITIAL  )
                  OR (   <data>-gltgv LE sy-datum
                     AND <data>-gltgb IS INITIAL  ) ) )
*   Not valid users
        OR
             (    NOT notvalid IS INITIAL
              AND (  <data>-gltgv GT sy-datum
                     OR
                     (        <data>-gltgb LT sy-datum
                      AND NOT <data>-gltgb IS INITIAL ) ) ).
    ELSE.
      DELETE gt_data.
      CONTINUE.
    ENDIF.

*   Active users
    IF   (    NOT unlocked IS INITIAL
              AND NOT (   l_usr02flag O c_yulock
                       OR l_usr02flag O c_yusloc
                       OR l_usr02flag O c_yugloc ) )
        OR
*   Locked users
             (    NOT locked   IS INITIAL
              AND (   l_usr02flag O c_yulock
                   OR l_usr02flag O c_yusloc
                   OR l_usr02flag O c_yugloc ) )
*   Users with failed logon
        OR
             (    NOT faillog  IS INITIAL
              AND <data>-locnt GT 0 ).
    ELSE.
      DELETE gt_data.
      CONTINUE.
    ENDIF.

*   Dialog users
    IF    (    NOT diaguser IS INITIAL
              AND <data>-ustyp EQ c_typdia )
        OR
*   System users
             (    NOT sysuser  IS INITIAL
              AND <data>-ustyp EQ c_typbatch )
        OR
*   Communication users
             (    NOT commuser IS INITIAL
              AND <data>-ustyp EQ c_typcpic )
        OR
*   Service users
             (    NOT servuser IS INITIAL
              AND <data>-ustyp EQ c_typsim ).
    ELSE.
      DELETE gt_data.
      CONTINUE.
    ENDIF.

*   Users with initial password
    IF     (    NOT initpass IS INITIAL
              AND <data>-ltime IS INITIAL )
*   Users with defined password
        OR
             (    NOT defpass  IS INITIAL
              AND <data>-codvn NE c_x
              AND NOT <data>-ltime IS INITIAL ).
    ELSE.
      DELETE gt_data.
      CONTINUE.
    ENDIF.

    IF <data>-codvn = c_x.
      <data>-icon_pwd = icon_deactivate.
    ELSE.
      IF <data>-ltime IS INITIAL.
        <data>-icon_pwd = icon_cancel.
      ELSE.
        <data>-icon_pwd = icon_checked.
      ENDIF.
    ENDIF.

*   Type of lock
    IF l_usr02flag O c_yulock OR l_usr02flag O c_yusloc OR
       l_usr02flag O c_yugloc.
      <data>-icon_lock = icon_locked.
    ENDIF.

*   Message lock
    IF l_usr02flag O c_yulock.
      <data>-text_lock = 'Incorrect logons'(011).
    ELSEIF l_usr02flag O c_yusloc.
      <data>-text_lock = 'Administrator'(012).
    ELSEIF l_usr02flag O c_yugloc.
      <data>-text_lock = 'Global lock'(017).
    ELSEIF <data>-locnt GT 0.
      WRITE: <data>-locnt NO-SIGN LEFT-JUSTIFIED TO <data>-text_lock.
      CONCATENATE 'No. of Incorrect Logons:'(018)
                  <data>-text_lock INTO <data>-text_lock.
    ENDIF.

    READ TABLE lt_uinfo WITH KEY mandt = <data>-mandt
                                 bname = <data>-bname
                 TRANSPORTING NO FIELDS.
    IF sy-subrc EQ 0.
      <data>-icon_con = icon_dimension.
    ENDIF.

  ENDLOOP.

ENDFORM.                    " F_READ_DATA
*---------------------------------------------------------------------*
*     Form  f_display_data
*---------------------------------------------------------------------*
FORM f_display_data.

* Macro definition
  DEFINE m_sort.
    add 1 to ls_sort-spos.
    ls_sort-fieldname = &1.
    ls_sort-up = &2.
    ls_sort-down = &3.
    ls_sort-group = &4.
    append ls_sort to lt_sort.
  END-OF-DEFINITION.

* Macro definition
  DEFINE m_fieldcat.
    clear ls_fieldcat.
    add 1 to l_pos.
    ls_fieldcat-col_pos = l_pos.
    ls_fieldcat-fieldname   = &1.
    ls_fieldcat-ref_tabname = &2.
    append ls_fieldcat to lt_fieldcat.
  END-OF-DEFINITION.

  DATA:
    l_pos TYPE i,
    ls_print      TYPE slis_print_alv,
    ls_layout     TYPE slis_layout_alv,
    ls_filter     TYPE slis_filter_alv,
    lt_filter     TYPE slis_t_filter_alv,
    ls_sort       TYPE slis_sortinfo_alv,
    lt_sort       TYPE slis_t_sortinfo_alv,
    ls_fieldcat   TYPE slis_fieldcat_alv,
    lt_fieldcat   TYPE slis_t_fieldcat_alv,
    ls_event_exit TYPE slis_event_exit,
    lt_event_exit TYPE slis_t_event_exit.

* Layout
  ls_layout-zebra             = c_x.
  ls_layout-cell_merge        = c_x.
  ls_layout-colwidth_optimize = c_x.
  ls_layout-group_change_edit = c_x.
  ls_layout-box_fieldname = 'CHECKBOX'.

* Build sort table
  m_sort 'TRDAT' ''  c_x 'UL'.
  m_sort 'LTIME' ''  c_x ''.

* Build field catalog table
  CLEAR ls_fieldcat.
  ADD 1 TO l_pos.
  ls_fieldcat-col_pos = l_pos.
  ls_fieldcat-fieldname = 'ICON_CON'.
  ls_fieldcat-icon      = c_x.
  ls_fieldcat-seltext_s = 'C'.
  ls_fieldcat-seltext_l = 'Connected'.
  APPEND ls_fieldcat TO lt_fieldcat.

  m_fieldcat 'MANDT'      'USR02'.
  m_fieldcat 'BNAME'      'USR02'.
  m_fieldcat 'NAME_TEXT'  'ADDR3_DATA'.
  m_fieldcat 'CLASS'      'USR02'.
  m_fieldcat 'USTYP'      'USR02'.
  m_fieldcat 'ANAME'      'USR02'.
  m_fieldcat 'ERDAT'      'USR02'.
  m_fieldcat 'TRDAT'      'USR02'.
  m_fieldcat 'LTIME'      'USR02'.
  m_fieldcat 'GLTGB'      'USR02'.

  CLEAR ls_fieldcat.
  ADD 1 TO l_pos.
  ls_fieldcat-col_pos = l_pos.
  ls_fieldcat-fieldname = 'ICON_PWD'.
  ls_fieldcat-icon      = c_x.
  ls_fieldcat-seltext_s = 'P.'.
  ls_fieldcat-seltext_l = 'icon password'.
  APPEND ls_fieldcat TO lt_fieldcat.

  m_fieldcat 'BCDA1'      'USR02'.

  CLEAR ls_fieldcat.
  ADD 1 TO l_pos.
  ls_fieldcat-col_pos = l_pos.
  ls_fieldcat-fieldname = 'ICON_LOCK'.
  ls_fieldcat-icon      = c_x.
  ls_fieldcat-seltext_s = 'L.'.
  ls_fieldcat-seltext_l = 'icon lock'.
  APPEND ls_fieldcat TO lt_fieldcat.

  m_fieldcat 'TEXT_LOCK' ''.

  ls_fieldcat-seltext_s = 'Creat.date'.                     "#EC NOTEXT
  MODIFY lt_fieldcat FROM ls_fieldcat
  TRANSPORTING seltext_s WHERE fieldname EQ 'ERDAT'.

  ls_fieldcat-seltext_s = 'Logon date'.                     "#EC NOTEXT
  MODIFY lt_fieldcat FROM ls_fieldcat
  TRANSPORTING seltext_s WHERE fieldname EQ 'TRDAT'.

  ls_fieldcat-seltext_s = 'Log.time'.                       "#EC NOTEXT
  MODIFY lt_fieldcat FROM ls_fieldcat
  TRANSPORTING seltext_s WHERE fieldname EQ 'LTIME'.

  ls_fieldcat-seltext_m = 'Message lock'.                   "#EC NOTEXT
  MODIFY lt_fieldcat FROM ls_fieldcat
  TRANSPORTING seltext_m WHERE fieldname EQ 'TEXT_LOCK'.

* Activate refresh button
  CLEAR ls_event_exit.
  ls_event_exit-ucomm = c_refresh.     " Refresh
  ls_event_exit-after = c_x.
  APPEND ls_event_exit TO lt_event_exit.

* Print options
  ls_print-no_print_selinfos  = c_x.   " Display no selection infos
  ls_print-no_print_listinfos = c_x.   " Display no listinfos

* Filter
  CLEAR ls_filter.
  ls_filter-fieldname = 'TRDAT'.
  ls_filter-valuf_int = sy-datum.
  ls_filter-sign0 = 'I'.
  ls_filter-optio = 'EQ'.
  APPEND ls_filter TO lt_filter.

* Display data
  CALL FUNCTION 'REUSE_ALV_GRID_DISPLAY'
    EXPORTING
      i_callback_program       = sy-cprog
      i_callback_user_command  = 'USER_COMMAND'
      i_callback_pf_status_set = 'PF_STATUS_SET'
      is_layout                = ls_layout
      is_print                 = ls_print
      it_fieldcat              = lt_fieldcat
      it_sort                  = lt_sort
      it_filter                = lt_filter
      it_event_exit            = lt_event_exit
      i_save                   = 'A'
    TABLES
      t_outtab                 = gt_data.

ENDFORM.                    " F_DISPLAY_DATA
*---------------------------------------------------------------------*
*       FORM USER_COMMAND                                             *
*---------------------------------------------------------------------*
FORM user_command USING u_ucomm     TYPE syucomm
                        us_selfield TYPE slis_selfield.     "#EC CALLED

  CASE u_ucomm.
    WHEN '&IC1'.                       " Pick
      READ TABLE gt_data INDEX us_selfield-tabindex ASSIGNING <data>.
      CHECK sy-subrc EQ 0.
      IF NOT <data>-bname IS INITIAL AND <data>-mandt = sy-mandt.
        CALL FUNCTION 'AUTHORITY_CHECK_TCODE'
          EXPORTING
            tcode  = 'SU01D'
          EXCEPTIONS
            ok     = 1
            not_ok = 2
            OTHERS = 3.
        IF sy-subrc NE 1.
*         You are not authorized to use Transaction &
          MESSAGE e172(00) WITH 'SU01D'.
        ENDIF.
*       User name
        SET PARAMETER ID 'XUS' FIELD <data>-bname.
        CALL TRANSACTION 'SU01D'.
      ENDIF.
    WHEN c_refresh.
      PERFORM f_read_data.
      us_selfield-refresh = c_x.
  ENDCASE.

ENDFORM.                               " USER_COMMAND
*---------------------------------------------------------------------*
*       FORM PF_STATUS_SET                                            *
*---------------------------------------------------------------------*
FORM pf_status_set USING ut_extab TYPE slis_t_extab.        "#EC CALLED

* Display refresh button
  DELETE ut_extab WHERE fcode = c_refresh.

  SET PF-STATUS 'STANDARD_FULLSCREEN' OF PROGRAM 'SAPLKKBL'
      EXCLUDING ut_extab.

ENDFORM.                               " PF_STATUS_SET
*---------------------------------------------------------------------*
*       FORM get_users                                                *
*---------------------------------------------------------------------*
FORM get_users CHANGING ut_uinfo TYPE table.

  DATA :
    l_msg(80) TYPE c,                                       "#EC NEEDED
    ls_desti  TYPE rfchosts,
    lt_uinfo  TYPE TABLE OF uinfo,
    lt_desti  TYPE TABLE OF rfchosts.

  CALL FUNCTION 'RFC_GET_LOCAL_DESTINATIONS'
    TABLES
      localdest = lt_desti.

  LOOP AT lt_desti INTO ls_desti.
    REFRESH lt_uinfo.
    CALL FUNCTION 'THUSRINFO' DESTINATION ls_desti
      TABLES
        usr_tabl              = lt_uinfo
      EXCEPTIONS
        communication_failure = 17  MESSAGE l_msg
        system_failure        = 17  MESSAGE l_msg.
    IF sy-subrc = 0.
      APPEND LINES OF lt_uinfo TO ut_uinfo.
    ENDIF.
  ENDLOOP.

ENDFORM.                    "get_users
******************** END OF PROGRAM Z_ALV_RSUSR200 ********************
 
Back to top
View user's profile Send private message
Display posts from previous:   
Post new topic   Reply to topic    Russian ABAP Developer's Club Forum Index -> Security and Monitoring All times are GMT + 4 Hours
Page 1 of 1

 
Jump to:  
You cannot post new topics in this forum
You cannot reply to topics in this forum
You cannot edit your posts in this forum
You cannot delete your posts in this forum
You cannot vote in polls in this forum
You cannot attach files in this forum
You can download files in this forum


All product names are trademarks of their respective companies. SAPNET.RU websites are in no way affiliated with SAP AG.
SAP, SAP R/3, R/3 software, mySAP, ABAP, BAPI, xApps, SAP NetWeaver and any other are registered trademarks of SAP AG.
Every effort is made to ensure content integrity. Use information on this site at your own risk.