COMPILE FUNCTION Comm_LSL_Users(EntID,Event,Parm1,Parm2,Parm3,Parm4,Parm5)
/*
	Commuter module for LSL_Users (LSL_USERS table) window
	
	02/29/2012 - John C. Henry, J.C. Henry & Co., Inc.
*/
DECLARE SUBROUTINE Set_Property,  Set_Status, ErrMsg, Set_Property, obj_AppWindow, obj_Sec_Groups
DECLARE SUBROUTINE Btree.Extract, Send_Event, Security_Err_Msg, RList, End_Window, Database_Services
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, Database_Services
$INSERT MSG_EQUATES
$INSERT APPCOLORS
$INSERT	SEC_GROUPS_EQUATES
$INSERT LSL_USERS_EQUATES
$INSERT SECURITY_RIGHTS_EQU
$INSERT POPUP_EQUATES
EQU CRLF$	TO \0D0A\
EQU TARGET_ACTIVELIST$	TO 5
EQU COL$GROUP	TO 1
EQU COL$DESC	TO 2
 
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_USER' AND			Event = 'CLICK'		; GOSUB LUUser
	CASE EntID = @WINDOW:'.ADD_GROUP' AND 		Event = 'CLICK'		; GOSUB AddGroup
	CASE EntID = @WINDOW:'.REMOVE_GROUP' AND 	Event = 'CLICK'		; GOSUB RemoveGroup
	CASE EntID = @WINDOW:'.BTN_WRITE_FIX' AND	Event = 'CLICK'		; GOSUB Write	
	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) AND NOT(Memberof(@User4, 'BUSINESS_ADMINS')) THEN
	ErrMsg('Improper security to enter Security Groups')
	End_Window(@WINDOW)
	RETURN
END
//Populate Classification Combo Box
ClassOptions = Database_Services('ReadDataRow', 'APP_INFO', 'USER_CLASSES')
Set_Property(@Window : '.CMB_USER_CLASS', 'LIST', ClassOptions)
//Populate Shift Combo Box
ShiftOptions = Database_Services('ReadDataRow', 'APP_INFO', 'Shifts')
Set_Property(@Window : '.CMB_USER_SHIFT', 'LIST', ShiftOptions)
GOSUB Refresh
RETURN
* * * * * * *
Read:
* * * * * * *
GOSUB Refresh
RETURN
* * * * * * *
Write:
* * * * * * *
//get values before commit
User 		= Get_Property(@WINDOW:'.USERNAME','DEFPROP')
Active		= Get_Property(@Window : '.ACTIVE', 'CHECK')
GroupArray	= Get_Property(@WINDOW:'.GROUPS','DEFPROP')
CurrGroups	= GroupArray
Send_Event(@WINDOW,'WRITE')
 
//if deactivating user, remove all group and table memberships
if Active EQ '0' then ; //if inactivating user, remove all group membership too
	@Record<3> = '' ;//tables
	@Record<4> = '' ;//rights
	Database_Services('WriteDataRow', 'LSL_USERS', User, @Record)
	obj_Sec_Groups('RemoveUser',User:@RM:CurrGroups)
end
RETURN
* * * * * * *
Clear:
* * * * * * *
GOSUB Refresh
RETURN
* * * * * * *
Delete:
* * * * * * *
ErrMsg('Sec_Groups 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 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
* * * * * * *
AddGroup:
* * * * * * *
User 		= Get_Property(@WINDOW:'.USERNAME','DEFPROP')
GroupArray	= Get_Property(@WINDOW:'.GROUPS','DEFPROP')
CurrGroups = GroupArray
LOOP
UNTIL CurrGroups[-1,1] NE @VM
	CurrGroups[-1,1] = ''
REPEAT
Set_Status(0)
RList('SELECT SEC_GROUPS BY GROUP',TARGET_ACTIVELIST$,'','','')
OpenGroups = ''
Done = 0
LOOP
	READNEXT GroupID ELSE Done = 1
UNTIL Done
	LOCATE GroupID IN CurrGroups USING @VM SETTING Dummy ELSE
		OpenGroups<1,-1> = GroupID
	END
REPEAT
TypeOver = ''
TypeOver = 'K'
TypeOver = OpenGroups
GroupIDs = Popup(@WINDOW,TypeOver,'SEC_GROUPS')
Send_Event(@WINDOW,'WRITE')
IF GroupIDs NE '' Then
	obj_Sec_Groups('AddUser',User:@RM:GroupIDs)
end 
IF Get_Status(errCode) THEN
	ErrMsg(errCode)
END
obj_AppWindow('LoadFormKeys',@WINDOW:@RM:User)
RETURN
* * * * * * *
RemoveGroup:
* * * * * * *
User 		= Get_Property(@WINDOW:'.USERNAME','DEFPROP')
GroupArray	= Get_Property(@WINDOW:'.GROUPS','DEFPROP')
CurrGroups = GroupArray
LOOP
UNTIL CurrGroups[-1,1] NE @VM
	CurrGroups[-1,1] = ''
REPEAT
TypeOver = ''
TypeOver = 'K'
TypeOver = CurrGroups
GroupIDs = Popup(@WINDOW,TypeOver,'SEC_GROUPS')
Send_Event(@WINDOW,'WRITE')
IF GroupIDs NE '' then	
	obj_Sec_Groups('RemoveUser',User:@RM:GroupIDs)
end
IF Get_Status(errCode) THEN
	ErrMsg(errCode)
END
obj_AppWindow('LoadFormKeys',@WINDOW:@RM:User)
RETURN
* * * * * * *
LUUser:
* * * * * * *
Set_Status(0)
RList( 'SELECT LSL_USERS BY LAST_FIRST', TARGET_ACTIVELIST$, '', '', '' )
UserIDs = Popup(@WINDOW,'','SHOW_USERS')
IF UserIDs = '' THEN RETURN
CONVERT @VM TO @FM IN UserIDs
IF INDEX(UserIDs,@FM,1) THEN
	Send_Event(@WINDOW,'QBFINIT')
	Set_Property(@WINDOW,'QBFLIST',UserIDs)
	GOSUB Refresh
	Send_Event(@WINDOW,'QBFIRST')
END ELSE
	obj_Appwindow('LoadFormKeys',@WINDOW:@RM:UserIDs)
END
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