added active directory support to security groups
This commit is contained in:
@ -1,235 +0,0 @@
|
||||
COMPILE FUNCTION Comm_Notification(Instruction, Parm1,Parm2)
|
||||
|
||||
/*
|
||||
Commuter module for Notification window
|
||||
|
||||
09/15/2005 - John C. Henry, J.C. Henry & Co., Inc.
|
||||
*/
|
||||
|
||||
DECLARE SUBROUTINE Set_Property, Set_Status, ErrMsg, Set_Property, obj_AppWindow, obj_Notes
|
||||
DECLARE SUBROUTINE Btree.Extract, Send_Event, Security_Err_Msg, Forward_Event, End_Window, Start_Window
|
||||
DECLARE SUBROUTINE Send_Message
|
||||
DECLARE FUNCTION Get_Property, Get_Status, Popup, Send_Message, Msg, Security_Check, Dialog_Box, RowExists
|
||||
DECLARE FUNCTION Dialog_Box, obj_WO_Log, obj_RDS2, Admin_User
|
||||
|
||||
|
||||
$INSERT POPUP_EQUATES
|
||||
$INSERT MSG_EQUATES
|
||||
$INSERT APPCOLORS
|
||||
$INSERT SECURITY_RIGHTS_EQU
|
||||
|
||||
EQU CRLF$ TO \0D0A\
|
||||
|
||||
|
||||
ErrTitle = 'Error in Comm_Notification'
|
||||
ErrorMsg = ''
|
||||
|
||||
Result = ''
|
||||
|
||||
BEGIN CASE
|
||||
CASE Instruction = 'Create' ; GOSUB Create
|
||||
CASE Instruction = 'Refresh' ; GOSUB Refresh
|
||||
CASE Instruction = 'Page' ; GOSUB Page
|
||||
CASE Instruction = 'Read' ; GOSUB Read
|
||||
CASE Instruction = 'Write' ; GOSUB Write
|
||||
CASE Instruction = 'Clear' ; GOSUB Clear
|
||||
CASE Instruction = 'Delete' ; GOSUB Delete
|
||||
CASE Instruction = 'Close' ; GOSUB Close
|
||||
CASE Instruction = 'LUNotifyID' ; GOSUB LUNotifyID
|
||||
CASE Instruction = 'AddUsers' ; GOSUB AddUsers
|
||||
|
||||
CASE 1
|
||||
ErrorMsg = 'Unknown Instruction passed to routine'
|
||||
END CASE
|
||||
|
||||
IF ErrorMsg NE '' THEN
|
||||
ErrMsg(ErrorMsg)
|
||||
END
|
||||
|
||||
|
||||
RETURN Result
|
||||
|
||||
|
||||
* * * * * * *
|
||||
Create:
|
||||
* * * * * * *
|
||||
|
||||
IF NOT(Admin_User( @USER4 )) THEN
|
||||
Message = 'You do not have the proper security to enter Message Notifications...'
|
||||
Message<micon$> = 'H'
|
||||
Msg( '', Message )
|
||||
send_event( @window, 'CLOSE' )
|
||||
END
|
||||
|
||||
|
||||
obj_Appwindow('Create',@WINDOW)
|
||||
|
||||
GOSUB Refresh
|
||||
|
||||
RETURN
|
||||
|
||||
|
||||
* * * * * * *
|
||||
Read:
|
||||
* * * * * * *
|
||||
|
||||
|
||||
GOSUB Refresh
|
||||
|
||||
RETURN
|
||||
|
||||
|
||||
* * * * * * *
|
||||
Write:
|
||||
* * * * * * *
|
||||
|
||||
RETURN
|
||||
|
||||
|
||||
* * * * * * *
|
||||
Clear:
|
||||
* * * * * * *
|
||||
|
||||
GOTO Refresh
|
||||
|
||||
RETURN
|
||||
|
||||
|
||||
* * * * * * *
|
||||
Delete:
|
||||
* * * * * * *
|
||||
|
||||
IF NOT(Security_Check('RDS',DELETE$)) THEN
|
||||
Security_Err_Msg('RDS',DELETE$)
|
||||
RETURN
|
||||
END
|
||||
|
||||
Result = 0 ;* OK to proceed with the delete
|
||||
|
||||
RETURN
|
||||
|
||||
|
||||
|
||||
* * * * * * *
|
||||
Page:
|
||||
* * * * * * *
|
||||
|
||||
obj_Appwindow('Page')
|
||||
|
||||
GOSUB Refresh
|
||||
|
||||
RETURN
|
||||
|
||||
|
||||
|
||||
* * * * * * *
|
||||
Close:
|
||||
* * * * * * *
|
||||
|
||||
|
||||
RETURN
|
||||
|
||||
|
||||
* * * * * * *
|
||||
Refresh:
|
||||
* * * * * * *
|
||||
|
||||
|
||||
* QBF buttons
|
||||
|
||||
Ctrls = @WINDOW:'.QBF_FIRST_FIX':@RM ; Props = 'ENABLED':@RM
|
||||
Ctrls := @WINDOW:'.QBF_PREV_FIX':@RM ; Props := 'ENABLED':@RM
|
||||
Ctrls := @WINDOW:'.QBF_ABS_FIX':@RM ; Props := 'ENABLED':@RM
|
||||
Ctrls := @WINDOW:'.QBF_NEXT_FIX':@RM ; Props := 'ENABLED':@RM
|
||||
Ctrls := @WINDOW:'.QBF_LAST_FIX':@RM ; Props := 'ENABLED':@RM
|
||||
Ctrls := @WINDOW:'.QBF_STOP_FIX' ; Props := 'ENABLED'
|
||||
|
||||
IF Get_Property(@WINDOW,'QBFLIST') = '' THEN
|
||||
Vals = 0:@RM:0:@RM:0:@RM:0:@RM:0:@RM:0
|
||||
END ELSE
|
||||
Vals = 1:@RM:1:@RM:1:@RM:1:@RM:1:@RM:1
|
||||
END
|
||||
|
||||
Set_Property(Ctrls,Props,Vals)
|
||||
|
||||
* Turn edit table symbolic column backgrounds to green
|
||||
|
||||
ETSymbolics = Get_Property(@WINDOW,'@ET_SYMBOLICS') ;* Loaded during 'Create' in obj_Appwindow
|
||||
|
||||
ETCtrls = ETSymbolics<1>
|
||||
ETCols = ETSymbolics<2>
|
||||
|
||||
FOR I = 1 TO COUNT(ETCtrls,@VM) + (ETCtrls NE '')
|
||||
ETCtrl = ETCtrls<1,I>
|
||||
IF ETCtrl NE @WINDOW:'.CASSETTES' THEN
|
||||
ETList = Get_Property(ETCtrl,'LIST')
|
||||
FOR Line = 1 TO COUNT(ETList,@FM) + (ETList NE '')
|
||||
IF ETList<Line,1> NE '' THEN
|
||||
FOR N = 1 TO COUNT(ETCols<1,I>,@SVM) + (ETCols<1,I> NE '')
|
||||
stat = Send_Message(ETCtrl,'COLOR_BY_POS',ETCols<1,I,N>,Line,GREEN$)
|
||||
NEXT N
|
||||
END
|
||||
NEXT Line
|
||||
END
|
||||
NEXT I
|
||||
|
||||
|
||||
RETURN
|
||||
|
||||
|
||||
* * * * * * *
|
||||
LUNotifyID:
|
||||
* * * * * * *
|
||||
|
||||
|
||||
IF NOT(ASSIGNED(Parm1)) THEN FocusControl = '' ELSE FocusControl = Parm1
|
||||
IF NOT(ASSIGNED(Parm2)) THEN FocusPos = '' ELSE FocusPos = Parm2
|
||||
|
||||
TypeOver = ''
|
||||
TypeOver<PSELECT$> = 1
|
||||
|
||||
NotifyID = Popup(@WINDOW,TypeOver,'NOTIFICATION')
|
||||
IF NotifyID NE '' THEN
|
||||
obj_Appwindow('LUValReturn',NotifyID:@RM:FocusControl:@RM:FocusPos)
|
||||
END
|
||||
|
||||
RETURN
|
||||
|
||||
|
||||
|
||||
|
||||
* * * * * * *
|
||||
AddUsers:
|
||||
* * * * * * *
|
||||
|
||||
CtrlEntID = @WINDOW:'.USER_ID'
|
||||
|
||||
CurrUserIDs = Get_Property(CtrlEntID,'ARRAY')<1> ;* Existing MFC codes in edit table
|
||||
CurrUserIDsTrimmed = ''
|
||||
FOR I = 1 TO COUNT(CurrUserIDs,@VM) + (CurrUserIDs NE '')
|
||||
IF CurrUserIDs<1,I> NE '' THEN
|
||||
CurrUserIDsTrimmed<1,I> = CurrUserIDs<1,I>
|
||||
END
|
||||
NEXT I
|
||||
CurrUserIDs = CurrUserIDsTrimmed
|
||||
|
||||
NewUserIDs = Popup(@WINDOW,'','SHOW_USERS')
|
||||
|
||||
IF NewUserIDs = '' OR NewUserIDs = CHAR(27) THEN RETURN
|
||||
|
||||
FOR I = 1 TO COUNT(NewUserIDs,@VM) + (NewUserIDs NE '')
|
||||
NewUserID = NewUserIDs<1,I>
|
||||
LOCATE NewUserID IN CurrUserIDs BY 'AL' USING @VM SETTING POS ELSE
|
||||
CurrUserIDs = INSERT(CurrUserIDs,1,POS,0,NewUserID)
|
||||
END
|
||||
|
||||
NEXT I
|
||||
|
||||
|
||||
Set_Property(CtrlEntID,'DEFPROP',CurrUserIDs)
|
||||
Send_Event(CtrlEntID,'CALCULATE',2)
|
||||
|
||||
GOSUB Refresh
|
||||
|
||||
RETURN
|
||||
|
@ -1,244 +0,0 @@
|
||||
COMPILE FUNCTION Comm_Sec_Groups(EntID,Event,Parm1,Parm2,Parm3,Parm4,Parm5)
|
||||
|
||||
/*
|
||||
Commuter module for Sec_Groups (Epi Sec_Groups) window
|
||||
|
||||
06/26/2006 - John C. Henry, J.C. Henry & Co., Inc.
|
||||
*/
|
||||
|
||||
DECLARE SUBROUTINE Set_Property, Set_Status, ErrMsg, Set_Property, obj_AppWindow
|
||||
DECLARE SUBROUTINE Btree.Extract, Send_Event, Security_Err_Msg, RList
|
||||
DECLARE SUBROUTINE Send_Message, obj_Sec_Groups_Esc, End_Window
|
||||
DECLARE FUNCTION Get_Property, Get_Status, Popup, Send_Message, Msg, Security_Check, Dialog_Box
|
||||
DECLARE FUNCTION Dialog_Box, MemberOf, Send_Message, obj_Popup, obj_Sec_Groups
|
||||
|
||||
|
||||
|
||||
$INSERT MSG_EQUATES
|
||||
$INSERT APPCOLORS
|
||||
$INSERT SEC_GROUPS_EQUATES
|
||||
$INSERT LSL_USERS_EQU
|
||||
$INSERT SECURITY_RIGHTS_EQU
|
||||
$INSERT POPUP_EQUATES
|
||||
|
||||
|
||||
EQU CRLF$ TO \0D0A\
|
||||
|
||||
EQU TARGET_ACTIVELIST$ TO 5
|
||||
|
||||
|
||||
ErrTitle = 'Error in Comm_Sec_Groups'
|
||||
ErrorMsg = ''
|
||||
|
||||
Result = ''
|
||||
|
||||
BEGIN CASE
|
||||
CASE EntID = @WINDOW
|
||||
BEGIN CASE
|
||||
CASE Event = 'CLEAR' ; GOSUB Clear
|
||||
CASE Event = 'CREATE' ; GOSUB Create
|
||||
CASE Event = 'CLOSE' ; GOSUB Close
|
||||
CASE Event = 'READ' ; GOSUB Read
|
||||
CASE Event = 'WRITE' ; GOSUB Write
|
||||
CASE Event[1,3] = 'QBF' ; GOSUB Refresh
|
||||
END CASE
|
||||
|
||||
CASE EntID = @WINDOW:'.LU_GROUP' AND Event = 'CLICK' ; GOSUB LUGroupID
|
||||
|
||||
CASE EntID = @WINDOW:'.LSL_USER'
|
||||
BEGIN CASE
|
||||
CASE Event = 'DBLCLK' ; GOSUB UserDC
|
||||
END CASE
|
||||
|
||||
CASE 1
|
||||
ErrorMsg = 'Unknown Parameters ':EntID:' - ':Event:' passed to commuter'
|
||||
|
||||
END CASE
|
||||
|
||||
IF ErrorMsg NE '' THEN
|
||||
ErrMsg(ErrTitle:@SVM:ErrorMsg)
|
||||
END
|
||||
|
||||
RETURN Result
|
||||
|
||||
|
||||
* * * * * * *
|
||||
Create:
|
||||
* * * * * * *
|
||||
|
||||
obj_Appwindow('Create',@WINDOW)
|
||||
|
||||
AdminUser = XLATE('LSL_USERS',@USER4,LSL_USERS_ADMIN_USER$,'X')
|
||||
|
||||
IF NOT(AdminUser) THEN
|
||||
ErrMsg('Improper security to enter Security Groups')
|
||||
End_Window(@WINDOW)
|
||||
RETURN
|
||||
END
|
||||
|
||||
|
||||
GOSUB Refresh
|
||||
|
||||
RETURN
|
||||
|
||||
|
||||
* * * * * * *
|
||||
Read:
|
||||
* * * * * * *
|
||||
|
||||
|
||||
GOSUB Refresh
|
||||
|
||||
RETURN
|
||||
|
||||
|
||||
* * * * * * *
|
||||
Write:
|
||||
* * * * * * *
|
||||
|
||||
RETURN
|
||||
|
||||
|
||||
* * * * * * *
|
||||
Clear:
|
||||
* * * * * * *
|
||||
|
||||
|
||||
GOSUB Refresh
|
||||
|
||||
RETURN
|
||||
|
||||
|
||||
* * * * * * *
|
||||
Delete:
|
||||
* * * * * * *
|
||||
|
||||
ErrMsg('Sec_Groupss may not be deleted.')
|
||||
|
||||
Result = 0 ;* NOT OK to proceed with the delete
|
||||
|
||||
RETURN
|
||||
|
||||
|
||||
|
||||
* * * * * * *
|
||||
Close:
|
||||
* * * * * * *
|
||||
|
||||
obj_Appwindow('DetailReturn')
|
||||
|
||||
RETURN
|
||||
|
||||
|
||||
* * * * * * *
|
||||
Refresh:
|
||||
* * * * * * *
|
||||
|
||||
|
||||
* QBF buttons
|
||||
|
||||
Ctrls = @WINDOW:'.QBF_FIRST_FIX':@RM ; Props = 'ENABLED':@RM
|
||||
Ctrls := @WINDOW:'.QBF_PREV_FIX':@RM ; Props := 'ENABLED':@RM
|
||||
Ctrls := @WINDOW:'.QBF_ABS_FIX':@RM ; Props := 'ENABLED':@RM
|
||||
Ctrls := @WINDOW:'.QBF_NEXT_FIX':@RM ; Props := 'ENABLED':@RM
|
||||
Ctrls := @WINDOW:'.QBF_LAST_FIX':@RM ; Props := 'ENABLED':@RM
|
||||
Ctrls := @WINDOW:'.QBF_STOP_FIX' ; Props := 'ENABLED'
|
||||
|
||||
IF Get_Property(@WINDOW,'QBFLIST') = '' THEN
|
||||
Vals = 0:@RM:0:@RM:0:@RM:0:@RM:0:@RM:0
|
||||
END ELSE
|
||||
Vals = 1:@RM:1:@RM:1:@RM:1:@RM:1:@RM:1
|
||||
END
|
||||
|
||||
Set_Property(Ctrls,Props,Vals)
|
||||
|
||||
* Turn edit table symbolic column backgrounds to green
|
||||
|
||||
ETSymbolics = Get_Property(@WINDOW,'@ET_SYMBOLICS') ;* Loaded during 'Create' in obj_Appwindow
|
||||
|
||||
ETCtrls = ETSymbolics<1>
|
||||
ETCols = ETSymbolics<2>
|
||||
|
||||
FOR I = 1 TO COUNT(ETCtrls,@VM) + (ETCtrls NE '')
|
||||
ETCtrl = ETCtrls<1,I>
|
||||
ETList = Get_Property(ETCtrl,'LIST')
|
||||
FOR Line = 1 TO COUNT(ETList,@FM) + (ETList NE '')
|
||||
IF ETList<Line,1> NE '' THEN
|
||||
FOR N = 1 TO COUNT(ETCols<1,I>,@SVM) + (ETCols<1,I> NE '')
|
||||
stat = Send_Message(ETCtrl,'COLOR_BY_POS',ETCols<1,I,N>,Line,GREEN$)
|
||||
NEXT N
|
||||
END
|
||||
NEXT Line
|
||||
|
||||
NEXT I
|
||||
|
||||
RETURN
|
||||
|
||||
|
||||
* * * * * * *
|
||||
LUGroupID:
|
||||
* * * * * * *
|
||||
|
||||
IF NOT(ASSIGNED(Parm1)) THEN FocusControl = '' ELSE FocusControl = Parm1
|
||||
IF NOT(ASSIGNED(Parm2)) THEN FocusPos = '' ELSE FocusPos = Parm2
|
||||
|
||||
Set_Status(0)
|
||||
|
||||
RList('SELECT SEC_GROUPS BY GROUP_NAME',TARGET_ACTIVELIST$,'','','')
|
||||
|
||||
GroupIDs = Popup(@WINDOW,'','SEC_GROUPS')
|
||||
|
||||
IF GroupIDs = '' THEN RETURN
|
||||
|
||||
|
||||
CONVERT @VM TO @FM IN GroupIDs
|
||||
|
||||
IF INDEX(GroupIDs,@FM,1) THEN
|
||||
Send_Event(@WINDOW,'QBFINIT')
|
||||
Set_Property(@WINDOW,'QBFLIST',GroupIDs)
|
||||
GOSUB Refresh
|
||||
Send_Event(@WINDOW,'QBFIRST')
|
||||
END ELSE
|
||||
obj_Appwindow('LoadFormKeys',@WINDOW:@RM:GroupIDs)
|
||||
END
|
||||
|
||||
RETURN
|
||||
|
||||
|
||||
* * * * * * *
|
||||
UserDC:
|
||||
* * * * * * *
|
||||
|
||||
ErrMsg('Under Development')
|
||||
|
||||
|
||||
RETURN
|
||||
|
||||
|
||||
|
||||
* * * * * * *
|
||||
LUSec_GroupsType:
|
||||
* * * * * * *
|
||||
|
||||
IF NOT(ASSIGNED(Parm1)) THEN FocusControl = '' ELSE FocusControl = Parm1
|
||||
IF NOT(ASSIGNED(Parm2)) THEN FocusPos = '' ELSE FocusPos = Parm2
|
||||
|
||||
Sec_GroupsType = Popup(@WINDOW,TypeOver,'TOOL_TYPE')
|
||||
|
||||
IF Sec_GroupsType NE '' THEN
|
||||
obj_Appwindow('LUValReturn',Sec_GroupsType:@RM:FocusControl:@RM:FocusPos)
|
||||
END
|
||||
|
||||
RETURN
|
||||
|
||||
|
||||
|
||||
|
||||
|
||||
|
||||
|
||||
|
||||
|
||||
|
||||
|
||||
|
@ -26,6 +26,7 @@ $insert SERVICE_SETUP
|
||||
$Insert LSL_USERS_EQU
|
||||
$Insert RLIST_EQUATES
|
||||
$Insert NOTIFICATION_EQUATES
|
||||
$Insert SEC_GROUPS_EQUATES
|
||||
|
||||
equ crlf$ to \0D0A\
|
||||
equ tab$ to char(09)
|
||||
@ -45,12 +46,17 @@ Declare Function Get.RecCount, SRP_Datetime, Datetime, SRP_MATH, Lsl_Users_Ser
|
||||
Declare Function DCount, Database_Services, Environment_Services, SRP_Array, Logging_Services
|
||||
Declare subroutine Btree.Extract, Logging_Services
|
||||
|
||||
LogPath = Environment_Services('GetApplicationRootPath') : '\LogFiles\LSLUsers'
|
||||
LogDate = Oconv(Date(), 'D4/')
|
||||
LogTime = Oconv(Time(), 'MTS')
|
||||
LogFileName = LogDate[7, 4] : '-' : LogDate[1, 2] : '-' : LogDate[4, 2] : ' Notification Groups Update Log.csv'
|
||||
Headers = 'Logging DTM' : @FM : 'Notification ID' : @FM : 'Notes'
|
||||
objLog = Logging_Services('NewLog', LogPath, LogFileName, CRLF$, Comma$, Headers, '', False$, False$)
|
||||
LogPath = Environment_Services('GetApplicationRootPath') : '\LogFiles\LSLUsers'
|
||||
LogDate = Oconv(Date(), 'D4/')
|
||||
LogTime = Oconv(Time(), 'MTS')
|
||||
LogFileName = LogDate[7, 4] : '-' : LogDate[1, 2] : '-' : LogDate[4, 2] : ' Notification Groups Update Log.csv'
|
||||
Headers = 'Logging DTM' : @FM : 'Notification ID' : @FM : 'Notes'
|
||||
objNotificationLog = Logging_Services('NewLog', LogPath, LogFileName, CRLF$, Comma$, Headers, '', False$, False$)
|
||||
|
||||
LogFileName = LogDate[7, 4] : '-' : LogDate[1, 2] : '-' : LogDate[4, 2] : ' Security Groups Update Log.csv'
|
||||
Headers = 'Logging DTM' : @FM : 'Notification ID' : @FM : 'Notes'
|
||||
objSecGroupsLog = Logging_Services('NewLog', LogPath, LogFileName, CRLF$, Comma$, Headers, '', False$, False$)
|
||||
|
||||
LoggingDTM = LogDate : ' ' : LogTime ; // Logging DTM
|
||||
|
||||
GoToService else
|
||||
@ -414,14 +420,14 @@ Service UpdateNotificationGroups()
|
||||
LogData<1> = LoggingDtm
|
||||
LogData<2> = KeyId
|
||||
LogData<3> = 'No LSL_USERS record found for active directory member "':ADUserName:'".'
|
||||
Logging_Services('AppendLog', objLog, LogData, @RM, @FM)
|
||||
Logging_Services('AppendLog', objNotficationLog, LogData, @RM, @FM)
|
||||
end
|
||||
end else
|
||||
LogData = ''
|
||||
LogData<1> = LoggingDtm
|
||||
LogData<2> = KeyId
|
||||
LogData<3> = 'Btree.Extract call failed for DOMAIN_USERNAME "':ADUserName:'".'
|
||||
Logging_Services('AppendLog', objLog, LogData, @RM, @FM)
|
||||
Logging_Services('AppendLog', objNotficationLog, LogData, @RM, @FM)
|
||||
end
|
||||
Next ADUserName
|
||||
end
|
||||
@ -434,7 +440,7 @@ Service UpdateNotificationGroups()
|
||||
LogData<1> = LoggingDtm
|
||||
LogData<2> = KeyId
|
||||
LogData<3> = 'Failed to write record during update.'
|
||||
Logging_Services('AppendLog', objLog, LogData, @RM, @FM)
|
||||
Logging_Services('AppendLog', objNotficationLog, LogData, @RM, @FM)
|
||||
end
|
||||
end
|
||||
end else
|
||||
@ -442,14 +448,14 @@ Service UpdateNotificationGroups()
|
||||
LogData<1> = LoggingDtm
|
||||
LogData<2> = KeyId
|
||||
LogData<3> = 'Failed to read record during update.'
|
||||
Logging_Services('AppendLog', objLog, LogData, @RM, @FM)
|
||||
Logging_Services('AppendLog', objNotficationLog, LogData, @RM, @FM)
|
||||
end
|
||||
Unlock hTable, KeyId else
|
||||
LogData = ''
|
||||
LogData<1> = LoggingDtm
|
||||
LogData<2> = KeyId
|
||||
LogData<3> = 'Failed to unlock record during update.'
|
||||
Logging_Services('AppendLog', objLog, LogData, @RM, @FM)
|
||||
Logging_Services('AppendLog', objNotficationLog, LogData, @RM, @FM)
|
||||
end
|
||||
end
|
||||
Repeat
|
||||
@ -460,3 +466,85 @@ Service UpdateNotificationGroups()
|
||||
end service
|
||||
|
||||
|
||||
Service UpdateSecurityGroups()
|
||||
|
||||
hSysLists = Database_Services('GetTableHandle', 'SYSLISTS')
|
||||
Lock hSysLists, ServiceKeyID then
|
||||
Open 'SEC_GROUPS' to hTable then
|
||||
EOF = False$
|
||||
Select hTable
|
||||
Loop
|
||||
ReadNext KeyId else EOF = True$
|
||||
Until EOF
|
||||
Lock hTable, KeyId then
|
||||
Read Rec from hTable, KeyId then
|
||||
UseAD = Rec<SEC_GROUPS_USE_ACTIVE_DIRECTORY$>
|
||||
If UseAD then
|
||||
LSLUserList = ''
|
||||
// Update LSL_User list based on current members in Active Directory groups
|
||||
ADGroups = Rec<SEC_GROUPS_ACTIVE_DIRECTORY_GROUPS$>
|
||||
For each GroupName in ADGroups using @VM
|
||||
MemberList = Active_Directory_Services('GetADGroupMembersByGroupName', GroupName, 'INFINEON')
|
||||
MemberList = SRP_Array('Rotate', MemberList, @FM, @VM)
|
||||
ADUserNames = MemberList<1>
|
||||
LSLUserNames = ''
|
||||
LSLNames = ''
|
||||
Open 'DICT.LSL_USERS' to hDict then
|
||||
For each ADUserName in ADUserNames using @VM setting vPos
|
||||
Query = 'DOMAIN_USERNAME':@VM:ADUserName:@FM:'ACTIVE':@VM:True$:@FM
|
||||
Flag = ''
|
||||
LSLUsername = ''
|
||||
Btree.Extract(Query, 'LSL_USERS', hDict, LSLUsername, '', Flag)
|
||||
If Flag EQ 0 then
|
||||
If LSLUsername NE '' then
|
||||
LSLUserList<0, -1> = LSLUsername
|
||||
end else
|
||||
LogData = ''
|
||||
LogData<1> = LoggingDtm
|
||||
LogData<2> = KeyId
|
||||
LogData<3> = 'No LSL_USERS record found for active directory member "':ADUserName:'".'
|
||||
Logging_Services('AppendLog', objSecGroupsLog, LogData, @RM, @FM)
|
||||
end
|
||||
end else
|
||||
LogData = ''
|
||||
LogData<1> = LoggingDtm
|
||||
LogData<2> = KeyId
|
||||
LogData<3> = 'Btree.Extract call failed for DOMAIN_USERNAME "':ADUserName:'".'
|
||||
Logging_Services('AppendLog', objSecGroupsLog, LogData, @RM, @FM)
|
||||
end
|
||||
Next ADUserName
|
||||
end
|
||||
Next GroupName
|
||||
LSLUserList = SRP_Array('Clean', LSLUserList, 'TrimAndMakeUnique', @VM)
|
||||
LSLUserList = SRP_Array('SortSimpleList', LSLUserList, 'AscendingText', @VM)
|
||||
Rec<SEC_GROUPS_USER$> = LSLUserList
|
||||
Write Rec on hTable, KeyId else
|
||||
LogData = ''
|
||||
LogData<1> = LoggingDtm
|
||||
LogData<2> = KeyId
|
||||
LogData<3> = 'Failed to write record during update.'
|
||||
Logging_Services('AppendLog', objSecGroupsLog, LogData, @RM, @FM)
|
||||
end
|
||||
end
|
||||
end else
|
||||
LogData = ''
|
||||
LogData<1> = LoggingDtm
|
||||
LogData<2> = KeyId
|
||||
LogData<3> = 'Failed to read record during update.'
|
||||
Logging_Services('AppendLog', objSecGroupsLog, LogData, @RM, @FM)
|
||||
end
|
||||
Unlock hTable, KeyId else
|
||||
LogData = ''
|
||||
LogData<1> = LoggingDtm
|
||||
LogData<2> = KeyId
|
||||
LogData<3> = 'Failed to unlock record during update.'
|
||||
Logging_Services('AppendLog', objSecGroupsLog, LogData, @RM, @FM)
|
||||
end
|
||||
end
|
||||
Repeat
|
||||
end
|
||||
Unlock hSysLists, ServiceKeyID else Null
|
||||
end
|
||||
|
||||
end service
|
||||
|
||||
|
@ -52,7 +52,8 @@ Return EventFlow or 1
|
||||
|
||||
Event WINDOW.CREATE(CreateParam)
|
||||
|
||||
SelGroups = CreateParam
|
||||
SelGroups = Field(CreateParam, @RM, 1, 1)
|
||||
GroupType = Field(CreateParam, @RM, 2, 1)
|
||||
Def = ""
|
||||
Def<MCOL$> = -2
|
||||
Def<MROW$> = -2
|
||||
@ -60,9 +61,10 @@ Event WINDOW.CREATE(CreateParam)
|
||||
Def<MTYPE$> = "U"
|
||||
MsgUp = Msg(@window, Def) ;* display the processing message
|
||||
|
||||
ADGroupData = Active_Directory_Services('GetADGroupsByString', 'MES-Mesa*', 'INFINEON')
|
||||
ADGroupData<-1> = Active_Directory_Services('GetADGroupsByString', 'IFX-IRF-Mesa*', 'INFINEON')
|
||||
ADGroupData<-1> = Active_Directory_Services('GetADGroupsByString', 'KLU-Mesa*', 'INFINEON')
|
||||
ADGroupData = Active_Directory_Services('GetADGroupsByString', 'MES-Mesa*', 'INFINEON', '', GroupType)
|
||||
ADGroupData<-1> = Active_Directory_Services('GetADGroupsByString', 'IFX-IRF-Mesa*', 'INFINEON', '', GroupType)
|
||||
ADGroupData<-1> = Active_Directory_Services('GetADGroupsByString', 'KLU-Mesa*', 'INFINEON', '', GroupType)
|
||||
ADGroupData<-1> = Active_Directory_Services('GetADGroupsByString', 'MES-APP*', 'INFINEON', '', GroupType)
|
||||
|
||||
ADGroupData = SRP_Array('Clean', ADGroupData, 'TrimAndMakeUnique', @FM)
|
||||
NumRows = DCount(ADGroupData, @FM)
|
||||
@ -149,3 +151,4 @@ Event EDT_AD_GROUPS.ROWSELCHANGED(SelRow, SelState)
|
||||
|
||||
end event
|
||||
|
||||
|
||||
|
@ -37,11 +37,12 @@ $Insert APP_INSERTS
|
||||
$Insert MSG_EQUATES
|
||||
$Insert POPUP_EQUATES
|
||||
$Insert NOTIFICATION_EQUATES
|
||||
$Insert LSL_USERS_EQUATES
|
||||
|
||||
EQU READONLY_GREEN$ TO 192 + (220*256) + (192*65536)
|
||||
|
||||
Declare function Admin_User, Database_Services, Error_Services, Active_Directory_Services, SRP_Array
|
||||
Declare subroutine PlaceDialog, Error_Services, Database_Services, Btree.Extract
|
||||
Declare subroutine PlaceDialog, Error_Services, Database_Services, Btree.Extract, ErrMsg
|
||||
|
||||
GoToEvent Event for CtrlEntId else
|
||||
// Event not implemented
|
||||
@ -54,98 +55,172 @@ Return EventFlow or 1
|
||||
//-----------------------------------------------------------------------------
|
||||
|
||||
Event WINDOW.CREATE(CreateParam)
|
||||
|
||||
PlaceDialog(-2, -2)
|
||||
ColorArray = Send_Message(@Window:'.EDT_LSL_USERS', "COLOR_BY_POS", 2, 0)
|
||||
ColorArray<1> = READONLY_GREEN$
|
||||
Send_Message(@Window:'.EDT_LSL_USERS', "COLOR_BY_POS", 1, 0, ColorArray)
|
||||
Send_Message(@Window:'.EDT_LSL_USERS', "COLOR_BY_POS", 2, 0, ColorArray)
|
||||
Send_Message(@Window:'.EDT_AD_GROUPS', "COLOR_BY_POS", 1, 0, ColorArray)
|
||||
Send_Message(@Window:'.EDT_AD_GROUPS', "COLOR_BY_POS", 2, 0, ColorArray)
|
||||
Send_Message(@Window:'.EDT_AD_GROUPS', "COLOR_BY_POS", 3, 0, ColorArray)
|
||||
|
||||
AdminUser = Xlate('LSL_USERS', @USER4, LSL_USERS_ADMIN_USER$, 'X')
|
||||
|
||||
If AdminUser then
|
||||
ErrMsg('You do not have the proper security to enter Message Notifications...' )
|
||||
Post_Event(@Window, 'CLOSE')
|
||||
end else
|
||||
PlaceDialog(-2, -2)
|
||||
ColorArray = Send_Message(@Window:'.EDT_LSL_USERS', "COLOR_BY_POS", 2, 0)
|
||||
ColorArray<1> = READONLY_GREEN$
|
||||
Send_Message(@Window:'.EDT_LSL_USERS', "COLOR_BY_POS", 1, 0, ColorArray)
|
||||
Send_Message(@Window:'.EDT_LSL_USERS', "COLOR_BY_POS", 2, 0, ColorArray)
|
||||
Send_Message(@Window:'.EDT_AD_GROUPS', "COLOR_BY_POS", 1, 0, ColorArray)
|
||||
Send_Message(@Window:'.EDT_AD_GROUPS', "COLOR_BY_POS", 2, 0, ColorArray)
|
||||
Send_Message(@Window:'.EDT_AD_GROUPS', "COLOR_BY_POS", 3, 0, ColorArray)
|
||||
end
|
||||
|
||||
End Event
|
||||
|
||||
|
||||
Event WINDOW.READ()
|
||||
|
||||
Key = Get_Property(@Window:'.EDL_NOTIFICATION_ID', 'TEXT')
|
||||
Begin Case
|
||||
Case Key EQ ''
|
||||
Set_Property(@Window:'.EDT_LSL_USERS', 'ENABLED', False$)
|
||||
Case RowExists('NOTIFICATION', Key)
|
||||
// Populate form
|
||||
HaveLock = Database_Services('GetKeyIDLock', 'NOTIFICATION', Key, True$)
|
||||
If HaveLock then
|
||||
Set_Property(@Window, '@HAVE_LOCK', HaveLock)
|
||||
Set_Property(@Window, '@LOCK_KEY', Key)
|
||||
|
||||
Set_Property(@Window:'.EDL_DESCRIPTION', 'ENABLED', True$)
|
||||
Set_Property(@Window:'.CHK_USE_AD', 'ENABLED', True$)
|
||||
Set_Property(@Window:'.CHK_LIMIT_TO_ACTIVE_SHIFT', True$)
|
||||
Set_Property(@Window:'.PUB_CLEAR', 'ENABLED', True$)
|
||||
Set_Property(@Window:'.PUB_DELETE', 'ENABLED', True$)
|
||||
Set_Property(@Window:'.PUB_SAVE', 'ENABLED', True$)
|
||||
NotifyRec = Database_Services('ReadDataRow', 'NOTIFICATION', Key)
|
||||
If Error_Services('NoError') then
|
||||
Set_Property(@Window, '@RECORD', NotifyRec)
|
||||
Set_Property(@Window:'.EDL_DESCRIPTION', 'TEXT', NotifyRec<NOTIFICATION_DESC$>)
|
||||
UseAD = NotifyRec<NOTIFICATION_USE_ACTIVE_DIRECTORY$>
|
||||
Set_Property(@Window:'.CHK_USE_AD', 'DEFPROP', UseAD)
|
||||
LimitOnShift = NotifyRec<NOTIFICATION_LIMIT_TO_ACTIVE_SHIFT$>
|
||||
Set_Property(@Window:'.CHK_LIMIT_TO_ACTIVE_SHIFT', 'DEFPROP', LimitOnShift)
|
||||
EventFlow = EVENT_CONTINUE$
|
||||
OrigRec = Get_Property(@Window, '@RECORD')
|
||||
EditRec = Get_Property(@Window, '@EDIT_RECORD')
|
||||
If OrigRec NE EditRec then
|
||||
Response = Msg(@Window, '', 'YES_NO_CANCEL', '', 'OpenInsight':@FM:'Would you like to save changes to the entry?')
|
||||
Begin Case
|
||||
Case Response EQ Yes$
|
||||
// Save changes and read new record
|
||||
NewKey = Get_Property(@Window:'.EDL_NOTIFICATION_ID', 'TEXT')
|
||||
Set_Property(@Window, '@NEW_KEY', NewKey)
|
||||
Send_Event(@Window, 'WRITE')
|
||||
Case Response EQ No$
|
||||
// Abandon changes and read new form
|
||||
Null
|
||||
Case Otherwise$
|
||||
// Cancel - Stop Read Event
|
||||
EventFlow = EVENT_STOP$
|
||||
End Case
|
||||
end
|
||||
|
||||
If EventFlow EQ EVENT_CONTINUE$ then
|
||||
|
||||
GoSub UnlockRec
|
||||
|
||||
Key = Get_Property(@Window:'.EDL_NOTIFICATION_ID', 'TEXT')
|
||||
NewRec = Get_Property(@Window, '@NEW_REC')
|
||||
If Key EQ '' then
|
||||
Key = Get_Property(@Window, '@NEW_KEY')
|
||||
Set_Property(@Window:'.EDL_NOTIFICATION_ID', 'TEXT', NewKey)
|
||||
Set_Property(@Window, '@NEW_KEY', '')
|
||||
end
|
||||
Begin Case
|
||||
Case Key EQ ''
|
||||
Set_Property(@Window:'.EDT_LSL_USERS', 'ENABLED', False$)
|
||||
Case RowExists('NOTIFICATION', Key)
|
||||
// Populate form
|
||||
HaveLock = Database_Services('GetKeyIDLock', 'NOTIFICATION', Key, True$)
|
||||
If HaveLock then
|
||||
Set_Property(@Window, '@HAVE_LOCK', HaveLock)
|
||||
Set_Property(@Window, '@LOCK_KEY', Key)
|
||||
|
||||
LSLUsers = NotifyRec<NOTIFICATION_USER_ID$>
|
||||
LSLUsernames = Xlate('LSL_USERS', LSLUsers, 'FIRST_LAST', 'X')
|
||||
LSLUsersArray = LSLUsers : @FM : LSLUsernames
|
||||
Set_Property(@Window:'.EDT_LSL_USERS', 'ARRAY', LSLUsersArray)
|
||||
ADGroups = NotifyRec<NOTIFICATION_ACTIVE_DIRECTORY_GROUPS$>
|
||||
GroupList = ''
|
||||
If ADGroups NE '' then
|
||||
For each ADGroup in ADGroups using @VM setting vPos
|
||||
GroupList<-1> = Active_Directory_Services('GetADGroupsByString', ADGroup, 'INFINEON')
|
||||
Next ADGroup
|
||||
Set_Property(@Window:'.EDL_DESCRIPTION', 'ENABLED', True$)
|
||||
Set_Property(@Window:'.CHK_USE_AD', 'ENABLED', True$)
|
||||
Set_Property(@Window:'.CHK_LIMIT_TO_ACTIVE_SHIFT', True$)
|
||||
Set_Property(@Window:'.PUB_CLEAR', 'ENABLED', True$)
|
||||
Set_Property(@Window:'.PUB_DELETE', 'ENABLED', True$)
|
||||
Set_Property(@Window:'.PUB_SAVE', 'ENABLED', True$)
|
||||
NotifyRec = Database_Services('ReadDataRow', 'NOTIFICATION', Key)
|
||||
If Error_Services('NoError') then
|
||||
Set_Property(@Window, '@RECORD', NotifyRec)
|
||||
Set_Property(@Window, '@EDIT_RECORD', NotifyRec)
|
||||
Set_Property(@Window:'.EDL_DESCRIPTION', 'TEXT', NotifyRec<NOTIFICATION_DESC$>)
|
||||
UseAD = NotifyRec<NOTIFICATION_USE_ACTIVE_DIRECTORY$>
|
||||
Set_Property(@Window:'.CHK_USE_AD', 'DEFPROP', UseAD)
|
||||
LimitOnShift = NotifyRec<NOTIFICATION_LIMIT_TO_ACTIVE_SHIFT$>
|
||||
Set_Property(@Window:'.CHK_LIMIT_TO_ACTIVE_SHIFT', 'DEFPROP', LimitOnShift)
|
||||
|
||||
LSLUsers = NotifyRec<NOTIFICATION_USER_ID$>
|
||||
LSLUsernames = Xlate('LSL_USERS', LSLUsers, 'FIRST_LAST', 'X')
|
||||
LSLUsersArray = LSLUsers : @FM : LSLUsernames
|
||||
Set_Property(@Window:'.EDT_LSL_USERS', 'ARRAY', LSLUsersArray)
|
||||
ADGroups = NotifyRec<NOTIFICATION_ACTIVE_DIRECTORY_GROUPS$>
|
||||
GroupList = ''
|
||||
If ADGroups NE '' then
|
||||
For each ADGroup in ADGroups using @VM setting vPos
|
||||
GroupList<-1> = Active_Directory_Services('GetADGroupsByString', ADGroup, 'INFINEON')
|
||||
Next ADGroup
|
||||
end
|
||||
Set_Property(@Window:'.EDT_AD_GROUPS', 'LIST', GroupList)
|
||||
GoSub EnableControls
|
||||
end else
|
||||
Msg(@Window, '', 'OK', '', 'Error':@FM:'Error locking NOTIFICATION record "':Key:'" for update!')
|
||||
end
|
||||
Set_Property(@Window:'.EDT_AD_GROUPS', 'LIST', GroupList)
|
||||
GoSub EnableControls
|
||||
end else
|
||||
Msg(@Window, '', 'OK', '', 'Error':@FM:'Error locking NOTIFICATION record "':Key:'" for update!')
|
||||
Msg(@Window, '', 'OK', '', 'Error':@FM:'Error reading NOTIFICATION record "':Key:'"!')
|
||||
end
|
||||
end else
|
||||
Msg(@Window, '', 'OK', '', 'Error':@FM:'Error reading NOTIFICATION record "':Key:'"!')
|
||||
end
|
||||
Case Otherwise$
|
||||
// User is creating a new record
|
||||
Set_Property(@Window:'.PUB_ADD_USERS', 'ENABLED', True$)
|
||||
GoSub EnableControls
|
||||
End Case
|
||||
Case NewRec
|
||||
Null
|
||||
Case Otherwise$
|
||||
// User is creating a new record
|
||||
Set_Property(@Window, 'REDRAW', False$)
|
||||
Send_Event(@Window, 'CLEAR')
|
||||
Set_Property(@Window:'.EDL_NOTIFICATION_ID', 'TEXT', Key)
|
||||
Set_Property(@Window, '@LOCK_KEY', Key)
|
||||
Set_Property(@Window, '@NEW_REC', True$)
|
||||
GoSub EnableControls
|
||||
Set_Property(@Window:'.PUB_LU_ID', 'FOCUS', True$)
|
||||
Set_Property(@Window, 'REDRAW', True$)
|
||||
End Case
|
||||
end
|
||||
|
||||
end event
|
||||
|
||||
|
||||
Event WINDOW.CLEAR(bSaveKey, bSuppressWarning, bMaintainFocus)
|
||||
|
||||
GoSub EnableControls
|
||||
Set_Property(@Window:'.PUB_DELETE', 'ENABLED', False$)
|
||||
Set_Property(@Window:'.PUB_CLEAR', 'ENABLED', True$)
|
||||
Set_Property(@Window:'.EDL_DESCRIPTION', 'ENABLED', False$)
|
||||
Set_Property(@Window:'.CHK_USE_AD', 'ENABLED', False$)
|
||||
Set_Property(@Window:'.CHK_LIMIT_TO_ACTIVE_SHIFT', 'ENABLED', False$)
|
||||
EventFlow = EVENT_CONTINUE$
|
||||
OrigRec = Get_Property(@Window, '@RECORD')
|
||||
EditRec = Get_Property(@Window, '@EDIT_RECORD')
|
||||
|
||||
Set_Property(@Window:'.PUB_ADD_USERS', 'ENABLED', False$)
|
||||
Set_Property(@Window:'.REM_ADD_USERS', 'ENABLED', False$)
|
||||
If OrigRec NE EditRec then
|
||||
Response = Msg(@Window, '', 'YES_NO_CANCEL', '', 'OpenInsight':@FM:'Would you like to save changes to the entry?')
|
||||
Begin Case
|
||||
Case Response EQ 1
|
||||
// Yes - Save changed and close form
|
||||
Send_Event(@Window, 'WRITE')
|
||||
Case Response EQ 0
|
||||
// No - Abandon changes and clear form
|
||||
Null
|
||||
Case Otherwise$
|
||||
// Cancel - Stop Clear Event
|
||||
EventFlow = EVENT_STOP$
|
||||
End Case
|
||||
end
|
||||
|
||||
Set_Property(@Window:'.GRB_AD_GROUPS', 'ENABLED', False$)
|
||||
Set_Property(@Window:'.EDT_AD_GROUPS', 'ENABLED', False$)
|
||||
Set_Property(@Window:'.PUB_ADD_GROUPS', 'ENABLED', False$)
|
||||
Set_Property(@Window:'.REM_ADD_GROUPS', 'ENABLED', False$)
|
||||
If EventFlow EQ EVENT_CONTINUE$ then
|
||||
|
||||
Set_Property(@Window, '@NEW_REC', False$)
|
||||
GoSub UnlockRec
|
||||
Forward_Event()
|
||||
Set_Property(@Window, '@RECORD', '')
|
||||
Set_Property(@Window, '@EDIT_RECORD', '')
|
||||
|
||||
GoSub EnableControls
|
||||
Set_Property(@Window:'.PUB_DELETE' , 'ENABLED', False$)
|
||||
Set_Property(@Window:'.PUB_CLEAR' , 'ENABLED', True$)
|
||||
Set_Property(@Window:'.EDL_DESCRIPTION' , 'ENABLED', False$)
|
||||
Set_Property(@Window:'.CHK_USE_AD' , 'ENABLED', False$)
|
||||
Set_Property(@Window:'.CHK_LIMIT_TO_ACTIVE_SHIFT', 'ENABLED', False$)
|
||||
Set_Property(@Window:'.PUB_ADD_USERS' , 'ENABLED', False$)
|
||||
Set_Property(@Window:'.REM_ADD_USERS' , 'ENABLED', False$)
|
||||
Set_Property(@Window:'.GRB_AD_GROUPS' , 'ENABLED', False$)
|
||||
Set_Property(@Window:'.EDT_AD_GROUPS' , 'ENABLED', False$)
|
||||
Set_Property(@Window:'.PUB_ADD_GROUPS' , 'ENABLED', False$)
|
||||
Set_Property(@Window:'.REM_ADD_GROUPS' , 'ENABLED', False$)
|
||||
|
||||
end
|
||||
|
||||
end event
|
||||
|
||||
|
||||
Event WINDOW.WRITE()
|
||||
|
||||
Key = Get_Property(@Window:'.EDL_NOTIFICATION_ID', 'TEXT')
|
||||
Key = Get_Property(@Window, '@LOCK_KEY')
|
||||
NotifyRec = Get_Property(@Window, '@RECORD')
|
||||
NotifyRec<NOTIFICATION_DESC$> = Get_Property(@Window:'.EDL_DESCRIPTION', 'TEXT')
|
||||
UserArray = Get_Property(@Window:'.EDT_LSL_USERS', 'ARRAY')
|
||||
@ -159,7 +234,9 @@ Event WINDOW.WRITE()
|
||||
Database_Services('WriteDataRow', 'NOTIFICATION', Key, NotifyRec, True$, False$, True$)
|
||||
If Error_Services('NoError') then
|
||||
GoSub UnlockRec
|
||||
Post_Event(@Window, 'CLEAR')
|
||||
Set_Property(@Window, '@RECORD', GroupRec)
|
||||
Set_Property(@Window, '@EDIT_RECORD', GroupRec)
|
||||
Send_Event(@Window, 'CLEAR')
|
||||
end else
|
||||
Msg(@Window, '', 'OK', '', 'Error':@FM:Error_Services('GetMessage'))
|
||||
end
|
||||
@ -169,7 +246,25 @@ end event
|
||||
|
||||
Event WINDOW.CLOSE(CancelFlag, CloseFlags)
|
||||
|
||||
GoSub UnlockRec
|
||||
EventFlow = EVENT_CONTINUE$
|
||||
OrigRec = Get_Property(@Window, '@RECORD')
|
||||
EditRec = Get_Property(@Window, '@EDIT_RECORD')
|
||||
If OrigRec NE EditRec then
|
||||
Response = Msg(@Window, '', 'YES_NO_CANCEL', '', 'OpenInsight':@FM:'Would you like to save changes to the entry?')
|
||||
Begin Case
|
||||
Case Response EQ 1
|
||||
// Yes - Save changed and close form
|
||||
Send_Event(@Window, 'WRITE')
|
||||
Case Response EQ 0
|
||||
// No - Abandon changes and close form
|
||||
Null
|
||||
Case Otherwise$
|
||||
// Cancel - Stop Close Event
|
||||
EventFlow = EVENT_STOP$
|
||||
End Case
|
||||
end
|
||||
|
||||
If EventFlow EQ EVENT_CONTINUE$ then GoSub UnlockRec
|
||||
|
||||
end event
|
||||
|
||||
@ -191,11 +286,73 @@ end event
|
||||
|
||||
Event PUB_LU_ID.CLICK()
|
||||
|
||||
TypeOver = ''
|
||||
TypeOver<PSELECT$> = 1
|
||||
NotifyID = Popup(@WINDOW,TypeOver,'NOTIFICATION')
|
||||
IF NotifyID NE '' THEN
|
||||
Set_Property(@Window:'.EDL_NOTIFICATION_ID', 'TEXT', NotifyID)
|
||||
EventFlow = EVENT_CONTINUE$
|
||||
OrigRec = Get_Property(@Window, '@RECORD')
|
||||
EditRec = Get_Property(@Window, '@EDIT_RECORD')
|
||||
If OrigRec NE EditRec then
|
||||
Response = Msg(@Window, '', 'YES_NO_CANCEL', '', 'OpenInsight':@FM:'Would you like to save changes to the entry?')
|
||||
Begin Case
|
||||
Case Response EQ Yes$
|
||||
// Save changes and read new record
|
||||
Send_Event(@Window, 'WRITE')
|
||||
Case Response EQ No$
|
||||
// Abandon changes and read new form
|
||||
Null
|
||||
Case Otherwise$
|
||||
// Cancel - Stop Read Event
|
||||
EventFlow = EVENT_STOP$
|
||||
End Case
|
||||
end
|
||||
|
||||
If EventFlow EQ EVENT_CONTINUE$ then
|
||||
|
||||
TypeOver = ''
|
||||
TypeOver<PSELECT$> = 1
|
||||
NotifyID = Popup(@WINDOW,TypeOver,'NOTIFICATION')
|
||||
If NotifyID NE '' then
|
||||
Set_Property(@Window, '@RECORD', '')
|
||||
Set_Property(@Window, '@EDIT_RECORD', '')
|
||||
Set_Property(@Window:'.EDL_NOTIFICATION_ID', 'TEXT', NotifyID)
|
||||
Post_Event(@Window, 'READ')
|
||||
end
|
||||
|
||||
end
|
||||
|
||||
end event
|
||||
|
||||
|
||||
Event EDL_NOTIFICATION_ID.OPTIONS()
|
||||
|
||||
EventFlow = EVENT_CONTINUE$
|
||||
OrigRec = Get_Property(@Window, '@RECORD')
|
||||
EditRec = Get_Property(@Window, '@EDIT_RECORD')
|
||||
If OrigRec NE EditRec then
|
||||
Response = Msg(@Window, '', 'YES_NO_CANCEL', '', 'OpenInsight':@FM:'Would you like to save changes to the entry?')
|
||||
Begin Case
|
||||
Case Response EQ Yes$
|
||||
// Save changes and read new record
|
||||
Send_Event(@Window, 'WRITE')
|
||||
Case Response EQ No$
|
||||
// Abandon changes and read new form
|
||||
Null
|
||||
Case Otherwise$
|
||||
// Cancel - Stop Read Event
|
||||
EventFlow = EVENT_STOP$
|
||||
End Case
|
||||
end
|
||||
|
||||
If EventFlow EQ EVENT_CONTINUE$ then
|
||||
|
||||
TypeOver = ''
|
||||
TypeOver<PSELECT$> = 1
|
||||
NotifyID = Popup(@WINDOW,TypeOver,'NOTIFICATION')
|
||||
IF NotifyID NE '' THEN
|
||||
Set_Property(@Window, '@RECORD', '')
|
||||
Set_Property(@Window, '@EDIT_RECORD', '')
|
||||
Set_Property(CtrlEntId, 'TEXT', NotifyID)
|
||||
Post_Event(@Window, 'READ')
|
||||
end
|
||||
|
||||
end
|
||||
|
||||
end event
|
||||
@ -215,16 +372,6 @@ Event EDT_AD_GROUPS.ROWSELCHANGED(SelRow, SelState)
|
||||
end event
|
||||
|
||||
|
||||
Event EDL_NOTIFICATION_ID.CHANGED(NewData)
|
||||
|
||||
If NewData NE '' then
|
||||
GoSub UnlockRec
|
||||
Post_Event(@Window, 'READ')
|
||||
end
|
||||
|
||||
end event
|
||||
|
||||
|
||||
Event EDL_NOTIFICATION_ID.LOSTFOCUS(Flag, FocusID)
|
||||
|
||||
If Flag EQ 1 then
|
||||
@ -248,19 +395,20 @@ Event PUB_ADD_USERS.CLICK()
|
||||
|
||||
NewUserIDs = Popup(@WINDOW,'','SHOW_USERS')
|
||||
|
||||
IF NewUserIDs = '' OR NewUserIDs = CHAR(27) THEN RETURN
|
||||
If ( (NewUserIDs NE '') and (NewUserIDs NE CHAR(27)) ) then
|
||||
|
||||
FOR I = 1 TO COUNT(NewUserIDs,@VM) + (NewUserIDs NE '')
|
||||
NewUserID = NewUserIDs<1,I>
|
||||
LOCATE NewUserID IN CurrUserIDs BY 'AL' USING @VM SETTING POS ELSE
|
||||
CurrUserIDs = INSERT(CurrUserIDs,1,POS,0,NewUserID)
|
||||
END
|
||||
For I = 1 TO COUNT(NewUserIDs,@VM) + (NewUserIDs NE '')
|
||||
NewUserID = NewUserIDs<1,I>
|
||||
Locate NewUserID in CurrUserIDs by 'AL' using @VM setting POS else
|
||||
CurrUserIDs = INSERT(CurrUserIDs,1,POS,0,NewUserID)
|
||||
end
|
||||
Next I
|
||||
|
||||
NEXT I
|
||||
|
||||
LSLNames = Xlate('LSL_USERS', CurrUserIDs, 'FIRST_LAST', 'X')
|
||||
NewArray = CurrUserIDs : @FM : LSLNames
|
||||
Set_Property(@Window:'.EDT_LSL_USERS', 'ARRAY', NewArray)
|
||||
LSLNames = Xlate('LSL_USERS', CurrUserIDs, 'FIRST_LAST', 'X')
|
||||
NewArray = CurrUserIDs : @FM : LSLNames
|
||||
Set_Property(@Window:'.EDT_LSL_USERS', 'ARRAY', NewArray)
|
||||
Post_Event(@Window:'.EDT_LSL_USERS', 'CHANGED')
|
||||
end
|
||||
|
||||
end event
|
||||
|
||||
@ -278,6 +426,7 @@ Event PUB_REM_USERS.CLICK()
|
||||
Next Row
|
||||
Set_Property(@Window:'.EDT_LSL_USERS', 'LIST', NewList)
|
||||
GoSub EnableControls
|
||||
Post_Event(@Window:'.EDT_LSL_USERS', 'CHANGED')
|
||||
end
|
||||
|
||||
end event
|
||||
@ -287,7 +436,7 @@ Event PUB_ADD_GROUPS.CLICK()
|
||||
|
||||
GroupArray = Get_Property(@Window:'.EDT_AD_GROUPS', 'ARRAY')
|
||||
GroupIds = GroupArray<1>
|
||||
SelGroups = Dialog_Box('NDW_ACTIVE_DIRECTORY_GROUPS', @Window, GroupIds)
|
||||
SelGroups = Dialog_Box('NDW_ACTIVE_DIRECTORY_GROUPS', @Window, GroupIds:@RM:'DL')
|
||||
If SelGroups NE '' then
|
||||
Set_Property(@Window:'.EDT_AD_GROUPS', 'LIST', SelGroups)
|
||||
|
||||
@ -320,13 +469,16 @@ Event PUB_ADD_GROUPS.CLICK()
|
||||
end
|
||||
Next GroupId
|
||||
If LSLUsernames NE '' then
|
||||
LSLNames = Xlate('LSL_USERS', LSLUserNames, 'FIRST_LAST', 'X')
|
||||
LSLUsernames = SRP_Array('Clean', LSLUsernames, 'TrimAndMakeUnique', @VM)
|
||||
LSLUsernames = SRP_Array('SortSimpleList', LSLUsernames, 'AscendingText', @VM)
|
||||
LSLNames = Xlate('LSL_USERS', LSLUsernames, 'FIRST_LAST', 'X')
|
||||
end
|
||||
end
|
||||
Array = LSLUsernames : @FM : LSLNames
|
||||
Set_Property(@Window:'.EDT_LSL_USERS', 'ARRAY', Array)
|
||||
|
||||
Msg(@window, MsgUp) ;* take down the processing message
|
||||
Post_Event(@Window:'.EDT_AD_GROUPS', 'CHANGED')
|
||||
end
|
||||
|
||||
end event
|
||||
@ -345,6 +497,7 @@ Event PUB_REM_GROUPS.CLICK()
|
||||
Next Row
|
||||
Set_Property(@Window:'.EDT_AD_GROUPS', 'LIST', NewList)
|
||||
GoSub EnableControls
|
||||
Post_Event(@Window:'.EDT_AD_GROUPS', 'CHANGED')
|
||||
end
|
||||
|
||||
end event
|
||||
@ -352,25 +505,76 @@ end event
|
||||
|
||||
Event CHK_USE_AD.CLICK()
|
||||
|
||||
EditRecord = Get_Property(@Window, '@EDIT_RECORD')
|
||||
UseAD = Get_Property(CtrlEntId, 'CHECK')
|
||||
EditRecord<NOTIFICATION_USE_ACTIVE_DIRECTORY$> = UseAD
|
||||
Set_Property(@Window, '@EDIT_RECORD', EditRecord)
|
||||
GoSub EnableControls
|
||||
|
||||
end event
|
||||
|
||||
|
||||
Event CHK_LIMIT_TO_ACTIVE_SHIFT.CLICK()
|
||||
|
||||
EditRecord = Get_Property(@Window, '@EDIT_RECORD')
|
||||
UseAD = Get_Property(CtrlEntId, 'CHECK')
|
||||
EditRecord<NOTIFICATION_LIMIT_TO_ACTIVE_SHIFT$> = UseAD
|
||||
Set_Property(@Window, '@EDIT_RECORD', EditRecord)
|
||||
|
||||
end event
|
||||
|
||||
|
||||
Event EDT_AD_GROUPS.CHANGED(NewData)
|
||||
|
||||
EditRecord = Get_Property(@Window, '@EDIT_RECORD')
|
||||
ADGroupsArray = Get_Property(CtrlEntId, 'ARRAY')
|
||||
GroupNames = ADGroupsArray<1>
|
||||
EditRecord<NOTIFICATION_ACTIVE_DIRECTORY_GROUPS$> = GroupNames
|
||||
Set_Property(@Window, '@EDIT_RECORD', EditRecord)
|
||||
|
||||
end event
|
||||
|
||||
|
||||
Event EDT_LSL_USERS.CHANGED(NewData)
|
||||
|
||||
EditRecord = Get_Property(@Window, '@EDIT_RECORD')
|
||||
LSLUsersArray = Get_Property(CtrlEntId, 'ARRAY')
|
||||
LSLUsernames = LSLUsersArray<1>
|
||||
EditRecord<NOTIFICATION_USER_ID$> = LSLUsernames
|
||||
Set_Property(@Window, '@EDIT_RECORD', EditRecord)
|
||||
|
||||
end event
|
||||
|
||||
|
||||
Event EDL_DESCRIPTION.CHANGED(NewData)
|
||||
|
||||
EditRecord = Get_Property(@Window, '@EDIT_RECORD')
|
||||
EditRecord<NOTIFICATION_DESC$> = NewData
|
||||
Set_Property(@Window, '@EDIT_RECORD', EditRecord)
|
||||
|
||||
end event
|
||||
|
||||
|
||||
//-----------------------------------------------------------------------------
|
||||
// Internal GoSubs
|
||||
//-----------------------------------------------------------------------------
|
||||
|
||||
|
||||
EnableControls:
|
||||
|
||||
NotifyID = Get_Property(@Window:'.EDL_NOTIFICATION_ID', 'TEXT')
|
||||
UseAD = Get_Property(@Window:'.CHK_USE_AD', 'DEFPROP')
|
||||
Enabled = (NotifyID NE '')
|
||||
|
||||
Set_Property(@Window:'.PUB_CLEAR', 'ENABLED', (NotifyID NE ''))
|
||||
Set_Property(@Window:'.EDL_DESCRIPTION', 'ENABLED', (NotifyID NE ''))
|
||||
Set_Property(@Window:'.CHK_USE_AD', 'ENABLED', (NotifyID NE ''))
|
||||
Set_Property(@Window:'.PUB_CLEAR' , 'ENABLED', Enabled)
|
||||
Set_Property(@Window:'.EDL_DESCRIPTION', 'ENABLED', Enabled)
|
||||
Set_Property(@Window:'.CHK_USE_AD' , 'ENABLED', Enabled)
|
||||
|
||||
If UseAD NE True$ then Set_Property(@Window:'.CHK_LIMIT_TO_ACTIVE_SHIFT', 'DEFPROP', False$)
|
||||
Set_Property(@Window:'.CHK_LIMIT_TO_ACTIVE_SHIFT', 'ENABLED', UseAD)
|
||||
|
||||
Set_Property(@Window:'.PUB_ADD_USERS', 'ENABLED', (UseAD NE True$))
|
||||
Set_Property(@Window:'.EDT_LSL_USERS', 'ENABLED', (NotifyID NE ''))
|
||||
Set_Property(@Window:'.EDT_LSL_USERS', 'ENABLED', Enabled)
|
||||
|
||||
If NotifyID NE '' then
|
||||
Backcolor = WHITE$
|
||||
@ -378,13 +582,12 @@ EnableControls:
|
||||
Backcolor = GREY$
|
||||
end
|
||||
|
||||
Set_Property(@Window:'.EDT_LSL_USERS', 'BACKCOLOR', Backcolor)
|
||||
|
||||
Set_Property(@Window:'.GRB_AD_GROUPS', 'ENABLED', (UseAD EQ True$))
|
||||
Set_Property(@Window:'.EDT_LSL_USERS' , 'BACKCOLOR', Backcolor)
|
||||
Set_Property(@Window:'.GRB_AD_GROUPS' , 'ENABLED', (UseAD EQ True$))
|
||||
Set_Property(@Window:'.PUB_ADD_GROUPS', 'ENABLED', (UseAD EQ True$))
|
||||
Set_Property(@Window:'.EDT_AD_GROUPS', 'ENABLED', (UseAD EQ True$))
|
||||
Set_Property(@Window:'.EDT_AD_GROUPS' , 'ENABLED', (UseAD EQ True$))
|
||||
|
||||
If ( (NotifyID NE '') and (UseAD EQ True$) ) then
|
||||
If ( Enabled and (UseAD EQ True$) ) then
|
||||
Backcolor = WHITE$
|
||||
end else
|
||||
Backcolor = GREY$
|
||||
@ -438,4 +641,3 @@ UnlockRec:
|
||||
|
||||
return
|
||||
|
||||
|
||||
|
728
LSL2/STPROC/NDW_SEC_GROUPS_EVENTS.txt
Normal file
728
LSL2/STPROC/NDW_SEC_GROUPS_EVENTS.txt
Normal file
@ -0,0 +1,728 @@
|
||||
Compile function NDW_SEC_GROUPS_EVENTS(CtrlEntId, Event, @PARAMS)
|
||||
/***********************************************************************************************************************
|
||||
|
||||
This program is proprietary and is not to be used by or disclosed to others, nor is it to be copied without written
|
||||
permission from Infineon.
|
||||
|
||||
Name : NDW_Sec_Groups_Events
|
||||
|
||||
Description : This function acts as a commuter module for all events related to this window.
|
||||
|
||||
Notes : Commuter Modules are automatically called from the Promoted_Events function which is called by the
|
||||
application-specific promoted event handler. This makes it possible to add QuickEvents that need to
|
||||
execute Basic+ logic without having use the Form Designer to make the association, although this is
|
||||
limited to the events which are currently promoted.
|
||||
|
||||
If the form needs to call the commuter module directly then the QuickEvent parameters should be
|
||||
formatted like this:
|
||||
|
||||
'@SELF','@EVENT',['@PARAM1','@PARAMx']
|
||||
|
||||
Parameters :
|
||||
CtrlEntId [in] -- The fully qualified name of the control calling the promoted event
|
||||
Event [in] -- The event being executed. See the Notes section regarding "PRE" events
|
||||
Param1-15 [in] -- Additional event parameter holders
|
||||
EventFlow [out] -- Set to 1 or 0 so the calling event knows whether or not to chain forward. See comments in
|
||||
EVENT_SETUP insert
|
||||
|
||||
History : (Date, Initials, Notes)
|
||||
11/01/24 djs Created initial commuter module.
|
||||
|
||||
***********************************************************************************************************************/
|
||||
#pragma precomp SRP_PreCompiler
|
||||
#window NDW_SEC_GROUPS
|
||||
|
||||
$Insert EVENT_SETUP
|
||||
$Insert APP_INSERTS
|
||||
$Insert MSG_EQUATES
|
||||
$Insert POPUP_EQUATES
|
||||
$Insert SEC_GROUPS_EQUATES
|
||||
$Insert LSL_USERS_EQUATES
|
||||
|
||||
EQU READONLY_GREEN$ TO 192 + (220*256) + (192*65536)
|
||||
|
||||
Declare function Admin_User, Database_Services, Error_Services, Active_Directory_Services, SRP_Array
|
||||
Declare subroutine PlaceDialog, Error_Services, Database_Services, Btree.Extract, ErrMsg
|
||||
|
||||
GoToEvent Event for CtrlEntId else
|
||||
// Event not implemented
|
||||
end
|
||||
|
||||
Return EventFlow or 1
|
||||
|
||||
//-----------------------------------------------------------------------------
|
||||
// EVENT HANDLERS
|
||||
//-----------------------------------------------------------------------------
|
||||
|
||||
Event WINDOW.CREATE(CreateParam)
|
||||
|
||||
AdminUser = Xlate('LSL_USERS', @USER4, LSL_USERS_ADMIN_USER$, 'X')
|
||||
|
||||
If Not(AdminUser) then
|
||||
ErrMsg('Improper security to enter Security Groups')
|
||||
Post_Event(@Window, 'CLOSE')
|
||||
end else
|
||||
PlaceDialog(-2, -2)
|
||||
ColorArray = Send_Message(@Window:'.EDT_LSL_USERS', "COLOR_BY_POS", 2, 0)
|
||||
ColorArray<1> = READONLY_GREEN$
|
||||
Send_Message(@Window:'.EDT_LSL_USERS', "COLOR_BY_POS", 1, 0, ColorArray)
|
||||
Send_Message(@Window:'.EDT_LSL_USERS', "COLOR_BY_POS", 2, 0, ColorArray)
|
||||
Send_Message(@Window:'.EDT_AD_GROUPS', "COLOR_BY_POS", 1, 0, ColorArray)
|
||||
Send_Message(@Window:'.EDT_AD_GROUPS', "COLOR_BY_POS", 2, 0, ColorArray)
|
||||
Send_Message(@Window:'.EDT_AD_GROUPS', "COLOR_BY_POS", 3, 0, ColorArray)
|
||||
end
|
||||
|
||||
End Event
|
||||
|
||||
|
||||
Event WINDOW.READ()
|
||||
|
||||
EventFlow = EVENT_CONTINUE$
|
||||
OrigRec = Get_Property(@Window, '@RECORD')
|
||||
EditRec = Get_Property(@Window, '@EDIT_RECORD')
|
||||
|
||||
If OrigRec NE EditRec then
|
||||
Response = Msg(@Window, '', 'YES_NO_CANCEL', '', 'OpenInsight':@FM:'Would you like to save changes to the entry?')
|
||||
Begin Case
|
||||
Case Response EQ Yes$
|
||||
// Save changes and read new record
|
||||
Send_Event(@Window, 'WRITE')
|
||||
Case Response EQ No$
|
||||
// Abandon changes and read new form
|
||||
Null
|
||||
Case Otherwise$
|
||||
// Cancel - Stop Read Event
|
||||
EventFlow = EVENT_STOP$
|
||||
End Case
|
||||
end
|
||||
|
||||
If EventFlow EQ EVENT_CONTINUE$ then
|
||||
|
||||
GoSub UnlockRec
|
||||
|
||||
Key = Get_Property(@Window:'.EDL_GROUP_ID', 'TEXT')
|
||||
NewRec = Get_Property(@Window, '@NEW_REC')
|
||||
If Key EQ '' then
|
||||
Key = Get_Property(@Window, '@NEW_KEY')
|
||||
Set_Property(@Window:'.EDL_GROUP_ID', 'TEXT', NewKey)
|
||||
Set_Property(@Window, '@NEW_KEY', '')
|
||||
end
|
||||
Begin Case
|
||||
Case Key EQ ''
|
||||
Set_Property(@Window:'.EDT_LSL_USERS', 'ENABLED', False$)
|
||||
Case RowExists('SEC_GROUPS', Key)
|
||||
// Populate form
|
||||
HaveLock = Database_Services('GetKeyIDLock', 'SEC_GROUPS', Key, True$)
|
||||
If HaveLock then
|
||||
Set_Property(@Window, '@HAVE_LOCK', HaveLock)
|
||||
Set_Property(@Window, '@LOCK_KEY', Key)
|
||||
|
||||
Set_Property(@Window:'.EDL_GROUP_NAME', 'ENABLED', True$)
|
||||
Set_Property(@Window:'.CHK_USE_AD', 'ENABLED', True$)
|
||||
Set_Property(@Window:'.CHK_LIMIT_TO_ACTIVE_SHIFT', True$)
|
||||
Set_Property(@Window:'.PUB_CLEAR', 'ENABLED', True$)
|
||||
Set_Property(@Window:'.PUB_DELETE', 'ENABLED', True$)
|
||||
Set_Property(@Window:'.PUB_SAVE', 'ENABLED', True$)
|
||||
GroupRec = Database_Services('ReadDataRow', 'SEC_GROUPS', Key)
|
||||
If Error_Services('NoError') then
|
||||
Set_Property(@Window, '@RECORD', GroupRec)
|
||||
Set_Property(@Window, '@EDIT_RECORD', GroupRec)
|
||||
Set_Property(@Window:'.EDL_GROUP_NAME', 'TEXT', GroupRec<SEC_GROUPS_GROUP_NAME$>)
|
||||
UseAD = GroupRec<SEC_GROUPS_USE_ACTIVE_DIRECTORY$>
|
||||
Set_Property(@Window:'.CHK_USE_AD', 'DEFPROP', UseAD)
|
||||
|
||||
// Populate Table Rights
|
||||
Tables = GroupRec<SEC_GROUPS_TABLES$>
|
||||
Rights = GroupRec<SEC_GROUPS_RIGHTS$>
|
||||
TableRightsArray = Tables : @FM : Rights
|
||||
Set_Property(@Window:'.EDT_TABLE_RIGHTS', 'ARRAY', TableRightsArray)
|
||||
|
||||
LSLUsers = GroupRec<SEC_GROUPS_USER$>
|
||||
LSLUsernames = Xlate('LSL_USERS', LSLUsers, 'FIRST_LAST', 'X')
|
||||
LSLUsersArray = LSLUsers : @FM : LSLUsernames
|
||||
Set_Property(@Window:'.EDT_LSL_USERS', 'ARRAY', LSLUsersArray)
|
||||
ADGroups = GroupRec<SEC_GROUPS_ACTIVE_DIRECTORY_GROUPS$>
|
||||
GroupList = ''
|
||||
If ADGroups NE '' then
|
||||
For each ADGroup in ADGroups using @VM setting vPos
|
||||
GroupList<-1> = Active_Directory_Services('GetADGroupsByString', ADGroup, 'INFINEON')
|
||||
Next ADGroup
|
||||
end
|
||||
Set_Property(@Window:'.EDT_AD_GROUPS', 'LIST', GroupList)
|
||||
GoSub EnableControls
|
||||
end else
|
||||
Msg(@Window, '', 'OK', '', 'Error':@FM:'Error locking SEC_GROUPS record "':Key:'" for update!')
|
||||
end
|
||||
end else
|
||||
Msg(@Window, '', 'OK', '', 'Error':@FM:'Error reading SEC_GROUPS record "':Key:'"!')
|
||||
end
|
||||
Case NewRec
|
||||
Null
|
||||
Case Otherwise$
|
||||
// User is creating a new record
|
||||
Set_Property(@Window, 'REDRAW', False$)
|
||||
Send_Event(@Window, 'CLEAR')
|
||||
Set_Property(@Window:'.EDL_GROUP_ID', 'TEXT', Key)
|
||||
Set_Property(@Window, '@LOCK_KEY', Key)
|
||||
Set_Property(@Window, '@NEW_REC', True$)
|
||||
GoSub EnableControls
|
||||
Set_Property(@Window:'.PUB_LU_GROUP', 'FOCUS', True$)
|
||||
Set_Property(@Window, 'REDRAW', True$)
|
||||
End Case
|
||||
end
|
||||
|
||||
end event
|
||||
|
||||
|
||||
Event WINDOW.CLEAR(bSaveKey, bSuppressWarning, bMaintainFocus)
|
||||
|
||||
EventFlow = EVENT_CONTINUE$
|
||||
OrigRec = Get_Property(@Window, '@RECORD')
|
||||
EditRec = Get_Property(@Window, '@EDIT_RECORD')
|
||||
|
||||
If OrigRec NE EditRec then
|
||||
Response = Msg(@Window, '', 'YES_NO_CANCEL', '', 'OpenInsight':@FM:'Would you like to save changes to the entry?')
|
||||
Begin Case
|
||||
Case Response EQ 1
|
||||
// Yes - Save changed and close form
|
||||
Send_Event(@Window, 'WRITE')
|
||||
Case Response EQ 0
|
||||
// No - Abandon changes and clear form
|
||||
Null
|
||||
Case Otherwise$
|
||||
// Cancel - Stop Clear Event
|
||||
EventFlow = EVENT_STOP$
|
||||
End Case
|
||||
end
|
||||
|
||||
If EventFlow EQ EVENT_CONTINUE$ then
|
||||
|
||||
GoSub UnlockRec
|
||||
Forward_Event()
|
||||
Set_Property(@Window, '@RECORD', '')
|
||||
Set_Property(@Window, '@EDIT_RECORD', '')
|
||||
|
||||
GoSub EnableControls
|
||||
Set_Property(@Window:'.PUB_DELETE' , 'ENABLED', False$)
|
||||
Set_Property(@Window:'.PUB_CLEAR' , 'ENABLED', True$)
|
||||
Set_Property(@Window:'.EDL_GROUP_NAME', 'ENABLED', False$)
|
||||
Set_Property(@Window:'.CHK_USE_AD' , 'ENABLED', False$)
|
||||
Set_Property(@Window:'.PUB_ADD_USERS' , 'ENABLED', False$)
|
||||
Set_Property(@Window:'.REM_ADD_USERS' , 'ENABLED', False$)
|
||||
Set_Property(@Window:'.GRB_AD_GROUPS' , 'ENABLED', False$)
|
||||
Set_Property(@Window:'.EDT_AD_GROUPS' , 'ENABLED', False$)
|
||||
Set_Property(@Window:'.PUB_ADD_GROUPS', 'ENABLED', False$)
|
||||
Set_Property(@Window:'.REM_ADD_GROUPS', 'ENABLED', False$)
|
||||
|
||||
end
|
||||
|
||||
end event
|
||||
|
||||
|
||||
Event WINDOW.WRITE()
|
||||
|
||||
Key = Get_Property(@Window, '@LOCK_KEY')
|
||||
GroupRec = Get_Property(@Window, '@RECORD')
|
||||
GroupRec<SEC_GROUPS_GROUP_NAME$> = Get_Property(@Window:'.EDL_GROUP_NAME', 'TEXT')
|
||||
TableRightsArray = Get_Property(@Window:'.EDT_TABLE_RIGHTS', 'ARRAY')
|
||||
Tables = TableRightsArray<1>
|
||||
Rights = TableRightsArray<2>
|
||||
GroupRec<SEC_GROUPS_TABLES$> = Tables
|
||||
GroupRec<SEC_GROUPS_RIGHTS$> = Rights
|
||||
UserArray = Get_Property(@Window:'.EDT_LSL_USERS', 'ARRAY')
|
||||
UserIds = UserArray<1>
|
||||
GroupRec<SEC_GROUPS_USER$> = UserIds
|
||||
GroupArray = Get_Property(@Window:'.EDT_AD_GROUPS', 'ARRAY')
|
||||
GroupIds = GroupArray<1>
|
||||
GroupRec<SEC_GROUPS_ACTIVE_DIRECTORY_GROUPS$> = GroupIds
|
||||
GroupRec<SEC_GROUPS_USE_ACTIVE_DIRECTORY$> = Get_Property(@Window:'.CHK_USE_AD', 'DEFPROP')
|
||||
Database_Services('WriteDataRow', 'SEC_GROUPS', Key, GroupRec, True$, False$, True$)
|
||||
If Error_Services('NoError') then
|
||||
GoSub UnlockRec
|
||||
Set_Property(@Window, '@RECORD', GroupRec)
|
||||
Set_Property(@Window, '@EDIT_RECORD', GroupRec)
|
||||
Send_Event(@Window, 'CLEAR')
|
||||
end else
|
||||
Msg(@Window, '', 'OK', '', 'Error':@FM:Error_Services('GetMessage'))
|
||||
end
|
||||
|
||||
end event
|
||||
|
||||
|
||||
Event WINDOW.CLOSE(CancelFlag, CloseFlags)
|
||||
|
||||
EventFlow = EVENT_CONTINUE$
|
||||
OrigRec = Get_Property(@Window, '@RECORD')
|
||||
EditRec = Get_Property(@Window, '@EDIT_RECORD')
|
||||
If OrigRec NE EditRec then
|
||||
Response = Msg(@Window, '', 'YES_NO_CANCEL', '', 'OpenInsight':@FM:'Would you like to save changes to the entry?')
|
||||
Begin Case
|
||||
Case Response EQ 1
|
||||
// Yes - Save changed and close form
|
||||
Send_Event(@Window, 'WRITE')
|
||||
Case Response EQ 0
|
||||
// No - Abandon changes and close form
|
||||
Null
|
||||
Case Otherwise$
|
||||
// Cancel - Stop Close Event
|
||||
EventFlow = EVENT_STOP$
|
||||
End Case
|
||||
end
|
||||
|
||||
If EventFlow EQ EVENT_CONTINUE$ then GoSub UnlockRec
|
||||
|
||||
end event
|
||||
|
||||
|
||||
Event PUB_LU_GROUP.CLICK()
|
||||
|
||||
EventFlow = EVENT_CONTINUE$
|
||||
OrigRec = Get_Property(@Window, '@RECORD')
|
||||
EditRec = Get_Property(@Window, '@EDIT_RECORD')
|
||||
If OrigRec NE EditRec then
|
||||
Response = Msg(@Window, '', 'YES_NO_CANCEL', '', 'OpenInsight':@FM:'Would you like to save changes to the entry?')
|
||||
Begin Case
|
||||
Case Response EQ Yes$
|
||||
// Save changes and read new record
|
||||
Send_Event(@Window, 'WRITE')
|
||||
Case Response EQ No$
|
||||
// Abandon changes and read new form
|
||||
Null
|
||||
Case Otherwise$
|
||||
// Cancel - Stop Read Event
|
||||
EventFlow = EVENT_STOP$
|
||||
End Case
|
||||
end
|
||||
|
||||
If EventFlow EQ EVENT_CONTINUE$ then
|
||||
|
||||
TypeOver = ''
|
||||
TypeOver<PSELECT$> = 1 ; // Only allow one group to be selected
|
||||
GroupID = Popup(@WINDOW, TypeOver, 'SEC_GROUPS')
|
||||
IF GroupID NE '' then
|
||||
Set_Property(@Window, '@RECORD', '')
|
||||
Set_Property(@Window, '@EDIT_RECORD', '')
|
||||
Set_Property(@Window:'.EDL_GROUP_ID', 'TEXT', GroupID)
|
||||
Post_Event(@Window, 'READ')
|
||||
end
|
||||
|
||||
end
|
||||
|
||||
end event
|
||||
|
||||
|
||||
Event PUB_SAVE.CLICK()
|
||||
|
||||
Post_Event(@Window, 'WRITE')
|
||||
|
||||
end event
|
||||
|
||||
|
||||
Event PUB_CLEAR.CLICK()
|
||||
|
||||
GoSub UnlockRec
|
||||
Post_Event(@Window, 'CLEAR')
|
||||
|
||||
end event
|
||||
|
||||
|
||||
Event EDT_TABLE_RIGHTS.OPTIONS()
|
||||
|
||||
SelPos = Get_Property(CtrlEntId, 'SELPOS')
|
||||
Begin Case
|
||||
Case Selpos<1> EQ 1
|
||||
CurrRow = Get_Property(CtrlEntId, 'ROWDATA')
|
||||
RetVal = Popup(@Window, '', 'TABLENAMES')
|
||||
If RetVal then
|
||||
Convert @VM to '' in RetVal
|
||||
CurrRow<1> = RetVal
|
||||
Set_Property(CtrlEntId, 'ROWDATA', CurrRow)
|
||||
Post_Event(CtrlEntID, 'CHANGED')
|
||||
end
|
||||
Case Selpos<1> EQ 2
|
||||
CurrRow = Get_Property(CtrlEntId, 'ROWDATA')
|
||||
RetVal = Popup(@Window, '', 'SECURITY_RIGHTS')
|
||||
If RetVal then
|
||||
Convert @VM to '' in RetVal
|
||||
RetVal = OConv(RetVal, '[RIGHTS_CONV]')
|
||||
CurrRow<2> = RetVal
|
||||
Set_Property(CtrlEntId, 'ROWDATA', CurrRow)
|
||||
Post_Event(CtrlEntID, 'CHANGED')
|
||||
end
|
||||
End Case
|
||||
|
||||
end event
|
||||
|
||||
|
||||
Event EDT_LSL_USERS.ROWSELCHANGED(SelRow, SelState)
|
||||
|
||||
GoSub EnableControls
|
||||
|
||||
end event
|
||||
|
||||
|
||||
Event EDT_AD_GROUPS.ROWSELCHANGED(SelRow, SelState)
|
||||
|
||||
GoSub EnableControls
|
||||
|
||||
end event
|
||||
|
||||
|
||||
Event EDL_GROUP_ID.LOSTFOCUS(Flag, FocusID)
|
||||
|
||||
If Flag EQ 1 then
|
||||
GoSub UnlockRec
|
||||
Post_Event(@Window, 'READ')
|
||||
end
|
||||
|
||||
end event
|
||||
|
||||
|
||||
Event EDL_GROUP_ID.OPTIONS()
|
||||
|
||||
EventFlow = EVENT_CONTINUE$
|
||||
OrigRec = Get_Property(@Window, '@RECORD')
|
||||
EditRec = Get_Property(@Window, '@EDIT_RECORD')
|
||||
If OrigRec NE EditRec then
|
||||
Response = Msg(@Window, '', 'YES_NO_CANCEL', '', 'OpenInsight':@FM:'Would you like to save changes to the entry?')
|
||||
Begin Case
|
||||
Case Response EQ Yes$
|
||||
// Save changes and read new record
|
||||
Send_Event(@Window, 'WRITE')
|
||||
Case Response EQ No$
|
||||
// Abandon changes and read new form
|
||||
Null
|
||||
Case Otherwise$
|
||||
// Cancel - Stop Read Event
|
||||
EventFlow = EVENT_STOP$
|
||||
End Case
|
||||
end
|
||||
|
||||
If EventFlow EQ EVENT_CONTINUE$ then
|
||||
|
||||
TypeOver = ''
|
||||
TypeOver<PSELECT$> = 1 ; // Only allow one group to be selected
|
||||
GroupID = Popup(@WINDOW, TypeOver, 'SEC_GROUPS')
|
||||
IF GroupID NE '' then
|
||||
Set_Property(@Window, '@RECORD', '')
|
||||
Set_Property(@Window, '@EDIT_RECORD', '')
|
||||
Set_Property(@Window:'.EDL_GROUP_ID', 'TEXT', GroupID)
|
||||
Post_Event(@Window, 'READ')
|
||||
end
|
||||
end
|
||||
|
||||
end event
|
||||
|
||||
|
||||
Event PUB_ADD_USERS.CLICK()
|
||||
|
||||
CurrUserIDs = Get_Property(@Window:'.EDT_LSL_USERS','ARRAY')<1>
|
||||
CurrUserIDsTrimmed = ''
|
||||
For I = 1 to COUNT(CurrUserIDs,@VM) + (CurrUserIDs NE '')
|
||||
If CurrUserIDs<1,I> NE '' then
|
||||
CurrUserIDsTrimmed<1,I> = CurrUserIDs<1,I>
|
||||
end
|
||||
Next I
|
||||
CurrUserIDs = CurrUserIDsTrimmed
|
||||
|
||||
NewUserIDs = Popup(@WINDOW,'','SHOW_USERS')
|
||||
|
||||
If ( (NewUserIDs NE '') and (NewUserIDs NE CHAR(27)) ) then
|
||||
|
||||
For I = 1 TO COUNT(NewUserIDs,@VM) + (NewUserIDs NE '')
|
||||
NewUserID = NewUserIDs<1,I>
|
||||
Locate NewUserID in CurrUserIDs by 'AL' using @VM setting POS else
|
||||
CurrUserIDs = INSERT(CurrUserIDs,1,POS,0,NewUserID)
|
||||
end
|
||||
Next I
|
||||
|
||||
LSLNames = Xlate('LSL_USERS', CurrUserIDs, 'FIRST_LAST', 'X')
|
||||
NewArray = CurrUserIDs : @FM : LSLNames
|
||||
Set_Property(@Window:'.EDT_LSL_USERS', 'ARRAY', NewArray)
|
||||
Post_Event(@Window:'.EDT_LSL_USERS', 'CHANGED')
|
||||
end
|
||||
|
||||
end event
|
||||
|
||||
|
||||
Event PUB_REM_USERS.CLICK()
|
||||
|
||||
SelRows = Get_Property(@Window:'.EDT_LSL_USERS', 'SELPOS')
|
||||
SelRows = SelRows<2>
|
||||
SelData = ''
|
||||
NewList = ''
|
||||
If SelRows NE '' then
|
||||
DataList = Get_Property(@Window:'.EDT_LSL_USERS', 'LIST')
|
||||
For each Row in DataList using @FM setting RowIndex
|
||||
If Not(InList(SelRows, RowIndex, @VM)) then NewList<-1> = Row
|
||||
Next Row
|
||||
Set_Property(@Window:'.EDT_LSL_USERS', 'LIST', NewList)
|
||||
GoSub EnableControls
|
||||
Post_Event(@Window:'.EDT_LSL_USERS', 'CHANGED')
|
||||
end
|
||||
|
||||
end event
|
||||
|
||||
|
||||
Event PUB_ADD_GROUPS.CLICK()
|
||||
|
||||
GroupArray = Get_Property(@Window:'.EDT_AD_GROUPS', 'ARRAY')
|
||||
GroupIds = GroupArray<1>
|
||||
SelGroups = Dialog_Box('NDW_ACTIVE_DIRECTORY_GROUPS', @Window, GroupIds:@RM:'SECURITY')
|
||||
If SelGroups NE '' then
|
||||
Set_Property(@Window:'.EDT_AD_GROUPS', 'LIST', SelGroups)
|
||||
|
||||
Def = ""
|
||||
Def<MCOL$> = -2
|
||||
Def<MROW$> = -2
|
||||
Def<MTEXT$> = "Updating LSL user list..."
|
||||
Def<MTYPE$> = "U"
|
||||
MsgUp = Msg(@window, Def) ;* display the processing message
|
||||
|
||||
GroupArray = Get_Property(@Window:'.EDT_AD_GROUPS', 'ARRAY')
|
||||
GroupIds = GroupArray<1>
|
||||
|
||||
LSLUserNames = ''
|
||||
LSLNames = ''
|
||||
If GroupIds NE '' then
|
||||
For each GroupId in GroupIds using @VM
|
||||
MemberList = Active_Directory_Services('GetADGroupMembersByGroupName', GroupId, 'INFINEON')
|
||||
MemberList = SRP_Array('Rotate', MemberList, @FM, @VM)
|
||||
ADUserNames = MemberList<1>
|
||||
|
||||
Open 'DICT.LSL_USERS' to hDict then
|
||||
For each ADUserName in ADUserNames using @VM setting vPos
|
||||
Query = 'DOMAIN_USERNAME':@VM:ADUserName:@FM
|
||||
Flag = ''
|
||||
LSLUsername = ''
|
||||
Btree.Extract(Query, 'LSL_USERS', hDict, LSLUsername, '', Flag)
|
||||
If LSLUsername NE '' then LSLUsernames<0, -1> = LSLUsername<0, 1>
|
||||
Next ADUserName
|
||||
end
|
||||
Next GroupId
|
||||
If LSLUsernames NE '' then
|
||||
LSLUsernames = SRP_Array('Clean', LSLUsernames, 'TrimAndMakeUnique', @VM)
|
||||
LSLUsernames = SRP_Array('SortSimpleList', LSLUsernames, 'AscendingText', @VM)
|
||||
LSLNames = Xlate('LSL_USERS', LSLUsernames, 'FIRST_LAST', 'X')
|
||||
end
|
||||
end
|
||||
Array = LSLUsernames : @FM : LSLNames
|
||||
Set_Property(@Window:'.EDT_LSL_USERS', 'ARRAY', Array)
|
||||
|
||||
Msg(@window, MsgUp) ;* take down the processing message
|
||||
Post_Event(@Window:'.EDT_AD_GROUPS', 'CHANGED')
|
||||
end
|
||||
|
||||
end event
|
||||
|
||||
|
||||
Event EDL_GROUP_NAME.CHANGED(NewData)
|
||||
|
||||
EditRecord = Get_Property(@Window, '@EDIT_RECORD')
|
||||
EditRecord<SEC_GROUPS_GROUP_NAME$> = NewData
|
||||
Set_Property(@Window, '@EDIT_RECORD', EditRecord)
|
||||
|
||||
end event
|
||||
|
||||
|
||||
Event EDT_AD_GROUPS.CHANGED(NewData)
|
||||
|
||||
EditRecord = Get_Property(@Window, '@EDIT_RECORD')
|
||||
ADGroupsArray = Get_Property(CtrlEntId, 'ARRAY')
|
||||
GroupNames = ADGroupsArray<1>
|
||||
EditRecord<SEC_GROUPS_ACTIVE_DIRECTORY_GROUPS$> = GroupNames
|
||||
Set_Property(@Window, '@EDIT_RECORD', EditRecord)
|
||||
|
||||
end event
|
||||
|
||||
|
||||
Event EDT_TABLE_RIGHTS.CHANGED(NewData)
|
||||
|
||||
EditRecord = Get_Property(@Window, '@EDIT_RECORD')
|
||||
TableRightsArray = Get_Property(CtrlEntId, 'ARRAY')
|
||||
TableNames = TableRightsArray<1>
|
||||
TableRights = TableRightsArray<2>
|
||||
EditRecord<SEC_GROUPS_TABLES$> = TableNames
|
||||
EditRecord<SEC_GROUPS_RIGHTS$> = TableRights
|
||||
Set_Property(@Window, '@EDIT_RECORD', EditRecord)
|
||||
|
||||
end event
|
||||
|
||||
|
||||
Event EDT_LSL_USERS.CHANGED(NewData)
|
||||
|
||||
EditRecord = Get_Property(@Window, '@EDIT_RECORD')
|
||||
LSLUsersArray = Get_Property(CtrlEntId, 'ARRAY')
|
||||
LSLUsernames = LSLUsersArray<1>
|
||||
EditRecord<SEC_GROUPS_USER$> = LSLUsernames
|
||||
Set_Property(@Window, '@EDIT_RECORD', EditRecord)
|
||||
|
||||
end event
|
||||
|
||||
|
||||
Event PUB_REM_GROUPS.CLICK()
|
||||
|
||||
SelRows = Get_Property(@Window:'.EDT_AD_GROUPS', 'SELPOS')
|
||||
SelRows = SelRows<2>
|
||||
SelData = ''
|
||||
NewList = ''
|
||||
If SelRows NE '' then
|
||||
DataList = Get_Property(@Window:'.EDT_AD_GROUPS', 'LIST')
|
||||
For each Row in DataList using @FM setting RowIndex
|
||||
If Not(InList(SelRows, RowIndex, @VM)) then NewList<-1> = Row
|
||||
Next Row
|
||||
Set_Property(@Window:'.EDT_AD_GROUPS', 'LIST', NewList)
|
||||
GoSub EnableControls
|
||||
Post_Event(@Window:'.EDT_AD_GROUPS', 'CHANGED')
|
||||
end
|
||||
|
||||
end event
|
||||
|
||||
|
||||
Event PUB_ADD_TABLE.CLICK()
|
||||
|
||||
SelTables = Popup(@Window, '', 'TABLENAMES')
|
||||
If SelTables NE '' then
|
||||
TableRightsList = Get_Property(@Window:'.EDT_TABLE_RIGHTS', 'LIST')
|
||||
TableRightsList<-1> = SelTables
|
||||
TableRightsList = SRP_Array('Clean', TableRightsList, 'TrimAndMakeUnique', @FM)
|
||||
TableRightsList = SRP_Array('SortRows', TableRightsList, 'AL1', 'LIST')
|
||||
Set_Property(@Window:'.EDT_TABLE_RIGHTS', 'LIST', TableRightsList)
|
||||
Post_Event(@Window:'.EDT_TABLE_RIGHTS', 'CHANGED')
|
||||
end
|
||||
|
||||
end event
|
||||
|
||||
|
||||
Event PUB_EDIT_RIGHTS.CLICK()
|
||||
|
||||
CurrRow = Get_Property(@Window:'.EDT_TABLE_RIGHTS', 'ROWDATA')
|
||||
RetVal = Popup(@Window, '', 'SECURITY_RIGHTS')
|
||||
If RetVal then
|
||||
Convert @VM to '' in RetVal
|
||||
RetVal = OConv(RetVal, '[RIGHTS_CONV]')
|
||||
CurrRow<2> = RetVal
|
||||
Set_Property(@Window:'.EDT_TABLE_RIGHTS', 'ROWDATA', CurrRow)
|
||||
Post_Event(@Window:'.EDT_TABLE_RIGHTS', 'CHANGED')
|
||||
end
|
||||
|
||||
end event
|
||||
|
||||
|
||||
Event PUB_REMOVE_TABLE.CLICK()
|
||||
|
||||
SelRows = Get_Property(@Window:'.EDT_TABLE_RIGHTS', 'SELPOS')
|
||||
SelRows = SelRows<2>
|
||||
SelData = ''
|
||||
NewList = ''
|
||||
If SelRows NE '' then
|
||||
DataList = Get_Property(@Window:'.EDT_TABLE_RIGHTS', 'LIST')
|
||||
For each Row in DataList using @FM setting RowIndex
|
||||
If Not(InList(SelRows, RowIndex, @VM)) then NewList<-1> = Row
|
||||
Next Row
|
||||
Set_Property(@Window:'.EDT_TABLE_RIGHTS', 'LIST', NewList)
|
||||
GoSub EnableControls
|
||||
Post_Event(@Window:'.EDT_TABLE_RIGHTS', 'CHANGED')
|
||||
end
|
||||
|
||||
end event
|
||||
|
||||
|
||||
Event CHK_USE_AD.CLICK()
|
||||
|
||||
EditRecord = Get_Property(@Window, '@EDIT_RECORD')
|
||||
UseAD = Get_Property(CtrlEntId, 'CHECK')
|
||||
EditRecord<SEC_GROUPS_USE_ACTIVE_DIRECTORY$> = UseAD
|
||||
Set_Property(@Window, '@EDIT_RECORD', EditRecord)
|
||||
GoSub EnableControls
|
||||
|
||||
end event
|
||||
|
||||
|
||||
//-----------------------------------------------------------------------------
|
||||
// Internal GoSubs
|
||||
//-----------------------------------------------------------------------------
|
||||
|
||||
|
||||
EnableControls:
|
||||
|
||||
GroupID = Get_Property(@Window:'.EDL_GROUP_ID', 'TEXT')
|
||||
UseAD = Get_Property(@Window:'.CHK_USE_AD', 'DEFPROP')
|
||||
Enabled = (GroupID NE '')
|
||||
|
||||
Set_Property(@Window:'.PUB_CLEAR' , 'ENABLED', Enabled)
|
||||
Set_Property(@Window:'.EDL_GROUP_NAME' , 'ENABLED', Enabled)
|
||||
Set_Property(@Window:'.CHK_USE_AD' , 'ENABLED', Enabled)
|
||||
Set_Property(@Window:'.EDT_TABLE_RIGHTS', 'ENABLED', Enabled)
|
||||
Set_Property(@Window:'.PUB_REMOVE_TABLE', 'ENABLED', Enabled)
|
||||
Set_Property(@Window:'.PUB_ADD_TABLE' , 'ENABLED', Enabled)
|
||||
Set_Property(@Window:'.PUB_EDIT_RIGHTS' , 'ENABLED', Enabled)
|
||||
Set_Property(@Window:'.PUB_ADD_USERS' , 'ENABLED', (UseAD NE True$))
|
||||
Set_Property(@Window:'.EDT_LSL_USERS' , 'ENABLED', Enabled)
|
||||
|
||||
If GroupID NE '' then
|
||||
Backcolor = WHITE$
|
||||
end else
|
||||
Backcolor = GREY$
|
||||
end
|
||||
|
||||
Set_Property(@Window:'.EDT_TABLE_RIGHTS', 'BACKCOLOR', Backcolor)
|
||||
Set_Property(@Window:'.EDT_LSL_USERS' , 'BACKCOLOR', Backcolor)
|
||||
Set_Property(@Window:'.GRB_AD_GROUPS' , 'ENABLED', (UseAD EQ True$))
|
||||
Set_Property(@Window:'.PUB_ADD_GROUPS' , 'ENABLED', (UseAD EQ True$))
|
||||
Set_Property(@Window:'.EDT_AD_GROUPS' , 'ENABLED', (UseAD EQ True$))
|
||||
|
||||
If ( Enabled and (UseAD EQ True$) ) then
|
||||
Backcolor = WHITE$
|
||||
end else
|
||||
Backcolor = GREY$
|
||||
end
|
||||
Set_Property(@Window:'.EDT_AD_GROUPS', 'BACKCOLOR', Backcolor)
|
||||
|
||||
DelBtnEnabled = False$
|
||||
SelRows = Get_Property(@Window:'.EDT_LSL_USERS', 'SELPOS')
|
||||
SelRows = SelRows<2>
|
||||
SelData = ''
|
||||
If SelRows NE '' then
|
||||
Data = Get_Property(@Window:'.EDT_LSL_USERS', 'LIST')
|
||||
Convert @VM to '' in Data
|
||||
For each Row in SelRows using @VM
|
||||
If Data<Row> NE '' then
|
||||
SelData<-1> = Data<Row>
|
||||
end
|
||||
Next Row
|
||||
If (SelData NE '') and (UseAD NE True$) then DelBtnEnabled = True$
|
||||
end
|
||||
Set_Property(@Window:'.PUB_REM_USERS', 'ENABLED', DelBtnEnabled)
|
||||
|
||||
DelBtnEnabled = False$
|
||||
SelRows = Get_Property(@Window:'.EDT_AD_GROUPS', 'SELPOS')
|
||||
SelRows = SelRows<2>
|
||||
SelData = ''
|
||||
If SelRows NE '' then
|
||||
Data = Get_Property(@Window:'.EDT_AD_GROUPS', 'LIST')
|
||||
Convert @VM to '' in Data
|
||||
For each Row in SelRows using @VM
|
||||
If Data<Row> NE '' then
|
||||
SelData<-1> = Data<Row>
|
||||
end
|
||||
Next Row
|
||||
If (SelData NE '') and (UseAD EQ True$) then DelBtnEnabled = True$
|
||||
end
|
||||
Set_Property(@Window:'.PUB_REM_GROUPS', 'ENABLED', DelBtnEnabled)
|
||||
|
||||
return
|
||||
|
||||
|
||||
UnlockRec:
|
||||
|
||||
Key = Get_Property(@Window, '@LOCK_KEY')
|
||||
If Key NE '' then
|
||||
HaveLock = Get_Property(@Window, '@HAVE_LOCK')
|
||||
If HaveLock then
|
||||
Database_Services('ReleaseKeyIDLock', 'SEC_GROUPS', Key)
|
||||
end
|
||||
end
|
||||
|
||||
return
|
||||
|
@ -56,6 +56,7 @@ $Insert LSL_USERS_EQUATES
|
||||
$Insert EMAIL_BOX_EQUATES
|
||||
$Insert NOTES_QUEUE_EQUATES
|
||||
$Insert NOTIFICATION_EQUATES
|
||||
$Insert SEC_GROUPS_EQUATES
|
||||
|
||||
Declare function Database_Services, obj_Notes_Sent, Get_Status, Error_Services, Obj_Tables, Datetime, SRP_Datetime
|
||||
Declare function SRP_Array, Environment_Services, Logging_Services, RTI_CreateGuid, LSL_Users_Services
|
||||
@ -375,7 +376,11 @@ Service SendNotes()
|
||||
end
|
||||
end
|
||||
If RowExists('SEC_GROUPS', GroupID) then
|
||||
! Todo: Add SEC_GROUPS support
|
||||
GroupRec = Database_Services('ReadDataRow', 'SEC_GROUPS', GroupID)
|
||||
If Error_Services('NoError') then
|
||||
GroupUsers = GroupRec<SEC_GROUPS_USER$>
|
||||
SecGroupRecipients = GroupUsers
|
||||
end
|
||||
end
|
||||
GroupRecipients = SRP_Array('Join', NotifyGroupRecipients, GroupRecipients, 'OR', @VM)
|
||||
GroupRecipients = SRP_Array('Join', SecGroupRecipients, GroupRecipients, 'OR', @VM)
|
||||
|
Reference in New Issue
Block a user