open-insight/LSL2/STPROC/OBJ_REACT_MODE.txt
Infineon\StieberD 7762b129af pre cutover push
2024-09-04 20:33:41 -07:00

308 lines
8.7 KiB
Plaintext

COMPILE FUNCTION obj_React_Mode(Method,Parms)
/*
Methods for the Reactor Mode (REACT_MODE) table
10/02/2006 JCH - Initial Coding
Properties:
Methods:
Create() ;* Create new React Mode record
Close() ;* Close existing React Mode record
*/
DECLARE FUNCTION Get_Status, Msg, Utility, obj_Tables, Dialog_Box,NextKey, Popup, Get_Property
DECLARE SUBROUTINE Set_Status, Msg, obj_Tables, Send_Dyn, Btree.Extract, ErrMsg, obj_React_Event
$INSERT MSG_EQUATES
$INSERT REACT_MODE_EQUATES
$INSERT REACT_MODE_NG_EQUATES
$INSERT LOGICAL
DevSwitch = XLATE('SYSLISTS', 'DEV_SWITCH', 1, 'X')
ErrTitle = 'Error in Stored Procedure "obj_React_Mode"'
ErrorMsg = ''
IF NOT(ASSIGNED(Method)) THEN ErrorMsg = 'Unassigned parameter "Method" passed to subroutine'
IF NOT(ASSIGNED(Parms)) THEN Parms = ''
IF ErrorMsg NE '' THEN
Set_Status(-1,ErrTitle:@SVM:ErrorMsg)
RETURN ''
END
Result = ''
BEGIN CASE
CASE Method = 'Create' ; GOSUB Create
CASE Method = 'Close' ; GOSUB Close
CASE Method = 'NonProdDates' ; GOSUB NonProdDates
CASE Method = 'DateNonProdHrs' ; GOSUB DateNonProdHrs
CASE 1
ErrorMsg = 'Unknown Method ':QUOTE(Method):' passed to routine.'
END CASE
IF ErrorMsg NE '' THEN
Set_Status(-1,ErrTitle:@SVM:ErrorMsg)
RETURN ''
END
RETURN Result
* * * * * * *
Create:
* * * * * * *
ReactNo = Parms[1,@RM]
StartDTM = Parms[COL2()+1,@RM]
UserID = Parms[COL2()+1,@RM]
Mode = Parms[COL2()+1,@RM]
Note = Parms[COL2()+1,@RM]
ReactUtilID = Parms[COL2()+1,@RM]
ReactLogID = Parms[COL2()+1,@RM]
ServiceDesc = Parms[COL2()+1,@RM]
IF ReactNo = '' THEN ErrorMsg = 'Null parameter ReactNo passed to routine (':Method:').'
IF StartDTM = '' THEN ErrorMsg = 'Null parameter StartDTM passed to routine (':Method:').'
IF UserID = '' THEN ErrorMsg = 'Null parameter UserID passed to routine (':Method:').'
IF Mode = '' THEN ErrorMsg = 'Null parameter Mode passed to routine (':Method:').'
IF ErrorMsg NE '' THEN RETURN
thisStartDTM = ICONV(StartDTM,'DT')
IF thisStartDTM = '' THEN
ErrorMsg = 'Invalid value ':QUOTE(StartDTM):' passed for parameter StartDTM (':Method:').'
RETURN
END
ReactModeKey = ReactNo:'*':thisStartDTM
ReactModeRec = ''
ReactModeRec<REACT_MODE_START_USER$> = UserID
ReactModeRec<REACT_MODE_START_NOTE$> = Note
ReactModeRec<REACT_MODE_START_RU_ID$> = ReactUtilID
ReactModeRec<REACT_MODE_START_RL_ID$> = ReactLogID
IF DevSwitch then
ReactModeRec<REACT_MODE_NG_SERVICE_DESC$> = ServiceDesc; //New home for the PROB_CAT_DESC
end
IF DevSwitch then
ReactModeRec<REACT_MODE_MODE$> = Mode
end else
IF LEN(Mode) > 2 THEN
ModeData = XLATE('SYSREPOSPOPUPS','LSL2**REACTOR_MODE',8,'X')
Pointer = 1
LOOP
ModeCode = ModeData<1,Pointer,1>
UNTIL ModeData<1,Pointer,2> = Mode OR Pointer = 50
Pointer += 1
REPEAT
ReactModeRec<REACT_MODE_MODE$> = ModeCode
END ELSE
ReactModeRec<REACT_MODE_MODE$> = Mode
END
end
CurrReactMode = XLATE('REACTOR',ReactNo,'CURR_MODE','X') ;* Mode prior to change
TableVar = ''
IF DevSwitch then
OtParms = 'REACT_MODE_NG':@RM:ReactModeKey:@RM:TableVar:@RM:ReactModeRec
end else
OtParms = 'REACT_MODE':@RM:ReactModeKey:@RM:TableVar:@RM:ReactModeRec
end
obj_Tables('WriteOnlyRec',OtParms) ;* Writes and unlocks the record
***** Added 10/2/1013 JCH - Log Mode change in the REACT_EVENT table.
oREParms = ReactNo:@RM
oREParms := StartDTM:@RM
oREParms := 'MODE':@RM
oREParms := UserID:@RM
oREParms := Note:@RM
oREParms := ReactModeRec<REACT_MODE_MODE$>:@RM
oREParms := CurrReactMode ;* Added 12/5/2013 JCH
obj_React_Event('Create',oREParms)
RETURN
* * * * * * *
Close:
* * * * * * *
ReactNo = Parms[1,@RM]
StartDTM = Parms[COL2()+1,@RM]
StopDTM = Parms[COL2()+1,@RM]
UserID = Parms[COL2()+1,@RM]
Note = Parms[COL2()+1,@RM]
ReactUtilID = Parms[COL2()+1,@RM]
ReactLogID = Parms[COL2()+1,@RM]
IF ReactNo = '' THEN ErrorMsg = 'Null parameter ReactNo passed to routine (':Method:').'
IF StartDTM = '' THEN ErrorMsg = 'Null parameter StartDTM passed to routine (':Method:').'
IF StopDTM = '' THEN ErrorMsg = 'Null parameter StopDTM passed to routine (':Method:').'
IF UserID = '' THEN ErrorMsg = 'Null parameter UserID passed to routine (':Method:').'
IF ErrorMsg NE '' THEN RETURN
thisStartDTM = ICONV(StartDTM,'DT')
IF thisStartDTM = '' THEN
ErrorMsg = 'Invalid value ':QUOTE(StartDTM):' passed for parameter StartDTM (':Method:').'
RETURN
END
thisStopDTM = ICONV(StopDTM,'DT')
IF thisStopDTM = '' THEN
ErrorMsg = 'Invalid value ':QUOTE(StopDTM):' passed for parameter StopDTM (':Method:').'
RETURN
END
ReactModeKey = ReactNo:'*':thisStartDTM
ReactModeOld = XLATE('REACT_MODE', ReactModeKey, '','X')
//Determine if REACT_MODE is in Old Table or Next Gen. Table
IF ReactModeOld NE '' then
OtParms = 'REACT_MODE':@RM:ReactModeKey
end else
OtParms = 'REACT_MODE_NG':@RM:ReactModeKey
end
ReactModeRec = obj_Tables('ReadOnlyRec',OtParms)
ReactModeRec<REACT_MODE_STOP_DTM$> = thisStopDTM
ReactModeRec<REACT_MODE_STOP_USER$> = UserID
ReactModeRec<REACT_MODE_STOP_NOTE$> = Note
ReactModeRec<REACT_MODE_STOP_RU_ID$> = ReactUtilID
ReactModeRec<REACT_MODE_STOP_RL_ID$> = ReactLogID
OtParms = FieldStore(OtParms,@RM,4,1,ReactModeRec)
obj_Tables('WriteOnlyRec',OtParms) ;* Writes and unlocks the record
RETURN
* * * * * * *
NonProdDates:
* * * * * * *
RecKey = Parms[1,@RM]
Record = Parms[COL2()+1,@RM]
IF RecKey = '' THEN RETURN
IF Record = '' THEN Record = XLATE('REACT_ESC',RecKey,'','X')
StartDtm = FIELD(RecKey,'*',2)
StartDt = StartDtm[1,'.']
Mode = Record<REACT_MODE_MODE$>
IF Mode = 'P' OR Mode = 'U' OR Mode = 'S' THEN RETURN ;* Production modes plus Shutdown are excluded
StopDt = Record<REACT_MODE_STOP_DTM$>[1,'.']
IF StopDt = '' THEN
StopDt = Date()
END
Ans = ''
FOR NonProdDt = StartDt TO StopDt
LOCATE NonProdDt IN Ans USING @VM SETTING Pos ELSE
Ans = INSERT(Ans,1,Pos,0,NonProdDt)
END
NEXT StopDt
Result = Ans
RETURN
* * * * * * *
DateNonProdHrs:
* * * * * * *
ReactNo = Parms[1,@RM]
NonProdDt = Parms[COL2()+1,@RM]
IF ReactNo = '' THEN ErrorMsg = 'Null parameter ReactNo passed to routine (':Method:').'
IF NonProdDt = '' THEN ErrorMsg = 'Null parameter NonProdDt passed to routine (':Method:').'
IF ErrorMsg NE '' THEN RETURN
thisNonProdDt = ICONV(NonProdDt,'D')
IF thisNonProdDt = '' THEN
ErrorMsg = 'Invalid value ':QUOTE(NonProdDt):' passed for parameter NonProdDt (':Method:').'
RETURN
END
OPEN 'DICT.REACT_MODE' TO DictVar ELSE
CALL FsMsg()
RETURN
END
SearchString = 'REACT_NO':@VM:ReactNo:@FM
SearchString := 'NON_PROD_DT':@VM:OConv(thisNonProdDt, 'D4/'):@FM
Option = ''
Flag = ''
Btree.Extract(SearchString, 'REACT_MODE', DictVar, ReactModeKeys, Option, Flag)
Ans = ''
FOR I = 1 TO COUNT(ReactModeKeys,@VM) + (ReactModeKeys NE '')
ReactModeKey = ReactModeKeys<1,I>
ReactModeRec = XLATE('REACT_MODE',ReactModeKey,'','X')
DateStartDTM = thisNonProdDt:'.0000115741'
DateStopDTM = thisNonProdDt:'.999988459'
StartDTM = FIELD(ReactModeKey,'*',2)
StopDTM = ReactModeRec<REACT_MODE_STOP_DTM$>
IF StartDTM _LTX DateStartDTM THEN StartDTM = DateStartDTM
IF StopDTM = '' THEN
IF thisNonProdDt = Date() THEN
StopDTM = ICONV(OCONV(thisNonProdDt,'D4/'):' ':OCONV(Time(),'MTS'),'DT')
END ELSE
StopDTM = DateStopDTM
END
END ELSE
IF StopDTM _GTX DateStopDTM THEN StopDTM = DateStopDTM
END
Ans += (StopDTM - StartDTM)*24
NEXT I
IF Ans NE '' THEN
Result = ICONV(Ans,'MD2')
END
RETURN