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

357 lines
8.3 KiB
Plaintext

COMPILE ROUTINE LOAD_REACT_EVENT(Dummy)
ROWDEF (CHARSTR)
DECLARE SUBROUTINE SEND_INFO, SEND_DYN, Utility, msg, obj_React_Event, RList
$INSERT RLIST_EQUATES
$INSERT REACT_UTIL_EQU
$INSERT REACT_EVENT_EQUATES
$INSERT REACTOR_LOG_EQUATES
$INSERT REACT_ESC_EQUATES
EQU CRLF$ TO \0D0A\
EQU TAB$ TO \09\
OPEN 'REACT_EVENT' TO REventTable ELSE
DEBUG
GOTO Bail
END
OPEN 'REACTOR_LOG' TO RLogTable ELSE
DEBUG
GOTO BAil
END
* REACTOR_LOG table postings
SelectSent = 'SELECT REACTOR_LOG WITH END_DATE >= "1/1/2011"'
RList(SelectSent,TARGET_ACTIVELIST$,'','','')
DEBUG
Done = 0
LOOP
READNEXT RLogKey ELSE Done = 1
UNTIL Done
READ RLogRec FROM RLogTable,RLogKey THEN
IF RLogRec<REACTOR_LOG_CATEGORY$> = 'M' THEN
DEBUG
ReactNo = RLogRec<REACTOR_LOG_REACTOR$>
EndDt = RLogRec<REACTOR_LOG_END_DATE$>
EndTm = RLogRec<REACTOR_LOG_END_TIME$>
exEndDTM = OCONV(EndDt,'D4/'):' ':OCONV(EndTm,'MTS')
EndDTM = ICONV(exEndDTM,'DT')
READ REventRec FROM REventTAble,ReactNo:'*'EndDTM THEN
debug
END
LogUser = RLRec<REACTOR_LOG_ENTRY_ID$>
LogUser = OCONV(LogUser,'[XLATE_CONV,LSL_USERS*FIRST_LAST]')
Note = XLATE('REACTOR_LOG',LogKey,REACTOR_LOG_NOTES$,'X')
* Data coming in with CRLF$ delimiters, T# formatting doesn't deal well with this.
* Divide into Items and text format them individually and reassemble it
SWAP CRLF$ WITH @VM IN Note
FormattedNote = ''
ItemCnt = COUNT(Note,@VM) + (Note NE '')
FOR N = 1 TO ItemCnt
Item = Note<1,N>
FormattedNote<1,N> = OCONV(Item,'T#100')
NEXT N
CONVERT @VM TO @TM IN FormattedNote
Note = FormattedNote
IF Types = '' THEN
Types = 'MTC'
TypeUsers = LogUser
TypeNotes = Note
END ELSE
Types = 'COMB'
TypeUsers = LogUser
TypeNotes := @TM:STR('- ',20):@TM:Note
END
END ;* End of check for Maintenance record
END ;* End of REACTOR_LOG record read
REPEAT
* * * * * * * * *
FixCnt = 0
Done = 0
LOOP
READNEXT ReactEventKey ELSE Done = 1
UNTIL Done
READ ReactEventRec FROM ReactEventTable,ReactEventKey THEN
FixCnt += 1
/*
ReactNo = ReactEventKey[1,'*']
StartDTM = ReactEventKey[COL2()+1,'*']
ReactModeKey = ReactEventRec<REACT_EVENT_REACT_MODE_KEY$>
MaintKey = ReactEventRec<REACT_EVENT_REACT_LOG_KEY$>
PDKey = ReactEventRec<REACT_EVENT_REACT_LOG_PD_KEY$>
EscStartKey = ReactEventRec<REACT_EVENT_REACT_ESC_START_KEY$>
EscStopKey = ReactEventRec<REACT_EVENT_REACT_ESC_STOP_KEY$>
RelatedKeyList = ''
KeyNameList = ''
IF ReactModeKey NE '' THEN
RelatedKeyList<1,-1> = ReactModeKey
KeyNameList<1,-1> = 'ReactMode'
END
IF MaintKey NE '' THEN
RelatedKeyList<1,-1> = MaintKey
KeyNameList<1,-1> = 'RLMaintKey'
END
IF PDKey NE '' THEN
RelatedKeyList<1,-1> = PDKey
KeyNameList<1,-1> = 'Passdown'
END
IF EscStartKey NE '' THEN
RelatedKeyList<1,-1> = EscStartKey
KeyNameList<1,-1> = 'Esc Start'
END
IF EscStopKey NE '' THEN
RelatedKeyList<1,-1> = EscStopKey
KeyNameList<1,-1> = 'Esc Stop'
END
RLCnt = COUNT(RelatedKeyList,@VM) + (RelatedKeyList NE '')
IF RLCnt > 1 THEN
DEBUG
Send_Dyn(ReactNo:' ':OCONV(StartDTM,'DT4/^HS'):' ':KeyNameList:' ':RelatedKeyList)
END
Send_Info(FixCnt)
GOTO SkipIt
/*
Types = ''
TypeUsers = ''
TypeNotes = ''
IF ReactEventRec<REACT_EVENT_REACT_MODE_KEY$> NE '' THEN
ModeKey = ReactEventRec<REACT_EVENT_REACT_MODE_KEY$>
ModeRec = XLATE('REACT_MODE',ModeKey,'','X')
Mode = OCONV(ModeRec<REACT_MODE_MODE$ >,'[REACT_MODE_CONV]')
StartNote = ModeRec<REACT_MODE_START_NOTE$>
StartUser = ModeRec<REACT_MODE_START_USER$>
StartUser = OCONV(StartUser,'[XLATE_CONV,LSL_USERS*FIRST_LAST]')
Note = 'Mode: ':Mode:@TM:OCONV(ModeRec<REACT_MODE_START_NOTE$>,'T#100')
IF Types = '' THEN
Types = 'MODE'
TypeUsers = StartUser
TypeNotes = Note
END ELSE
Types = 'COMB'
TypeUsers = StartUser
TypeNotes := @TM:STR('- ',20):@TM:Note
END
END
IF ReactEventRec<REACT_EVENT_REACT_LOG_KEY$> NE '' THEN
LogKey = ReactEventRec<REACT_EVENT_REACT_LOG_KEY$>
LogUser = XLATE('REACTOR_LOG',LogKey,REACTOR_LOG_ENTRY_ID$,'X')
LogUser = OCONV(LogUser,'[XLATE_CONV,LSL_USERS*FIRST_LAST]')
Note = XLATE('REACTOR_LOG',LogKey,REACTOR_LOG_NOTES$,'X')
* Data coming in with CRLF$ delimiters, T# formatting doesn't deal well with this.
* Divide into Items and text format them individually and reassemble it
SWAP CRLF$ WITH @VM IN Note
FormattedNote = ''
ItemCnt = COUNT(Note,@VM) + (Note NE '')
FOR N = 1 TO ItemCnt
Item = Note<1,N>
FormattedNote<1,N> = OCONV(Item,'T#100')
NEXT N
CONVERT @VM TO @TM IN FormattedNote
Note = FormattedNote
IF Types = '' THEN
Types = 'MTC'
TypeUsers = LogUser
TypeNotes = Note
END ELSE
Types = 'COMB'
TypeUsers = LogUser
TypeNotes := @TM:STR('- ',20):@TM:Note
END
END
IF ReactEventRec<REACT_EVENT_REACT_LOG_PD_KEY$> NE '' THEN
LogKey = ReactEventRec<REACT_EVENT_REACT_LOG_PD_KEY$>
LogUser = XLATE('REACTOR_LOG',LogKey,REACTOR_LOG_ENTRY_ID$,'X')
LogUser = OCONV(LogUser,'[XLATE_CONV,LSL_USERS*FIRST_LAST]')
Note = XLATE('REACTOR_LOG',LogKey,REACTOR_LOG_NOTES$,'X')
* Data coming in with CRLF$ delimiters, T# formatting doesn't deal well with this.
* Divide into Items and text format them individually and reassemble it
SWAP CRLF$ WITH @VM IN Note
FormattedNote = ''
ItemCnt = COUNT(Note,@VM) + (Note NE '')
FOR N = 1 TO ItemCnt
Item = Note<1,N>
FormattedNote<1,N> = OCONV(Item,'T#100')
NEXT N
CONVERT @VM TO @TM IN FormattedNote
Note = FormattedNote
IF Types = '' THEN
Types = 'PD'
TypeUsers = LogUser
TypeNotes = Note
END ELSE
Types = 'COMB'
TypeUsers = LogUser
TypeNotes := @TM:STR('- ',20):@TM:Note
END
END
IF ReactEventRec<REACT_EVENT_REACT_ESC_START_KEY$> NE '' THEN
EscKey = ReactEventRec<REACT_EVENT_REACT_ESC_START_KEY$>
EscUser = XLATE('REACT_ESC',EscKey,REACT_ESC_START_USER$,'X')
EscUser = OCONV(EscUser,'[XLATE_CONV,LSL_USERS*FIRST_LAST]')
Note = XLATE('REACT_ESC',EscKey,REACT_ESC_START_REASON$,'X')
SWAP CRLF$ WITH @VM IN Note
FormattedNote = ''
ItemCnt = COUNT(Note,@VM) + (Note NE '')
FOR N = 1 TO ItemCnt
Item = Note<1,N>
FormattedNote<1,N> = OCONV(Item,'T#100')
NEXT N
CONVERT @VM TO @TM IN FormattedNote
Note = FormattedNote
IF Types = '' THEN
Types = 'ESTR'
TypeUsers = EscUser
TypeNotes = Note
END ELSE
Types = 'COMB'
TypeUsers = EscUser
TypeNotes := @TM:STR('- ',20):@TM:Note
END
END
IF ReactEventRec<REACT_EVENT_REACT_ESC_STOP_KEY$> NE '' THEN
EscKey = ReactEventRec<REACT_EVENT_REACT_ESC_STOP_KEY$>
EscUser = XLATE('REACT_ESC',EscKey,REACT_ESC_STOP_USER$,'X')
EscUser = OCONV(EscUser,'[XLATE_CONV,LSL_USERS*FIRST_LAST]')
Note = XLATE('REACT_ESC',EscKey,REACT_ESC_STOP_REASON$,'X')
SWAP CRLF$ WITH @VM IN Note
FormattedNote = ''
ItemCnt = COUNT(Note,@VM) + (Note NE '')
FOR N = 1 TO ItemCnt
Item = Note<1,N>
FormattedNote<1,N> = OCONV(Item,'T#100')
NEXT N
CONVERT @VM TO @TM IN FormattedNote
Note = FormattedNote
IF Types = '' THEN
Types = 'ESTP'
TypeUsers = EscUser
TypeNotes = Note
END ELSE
Types = 'COMB'
TypeUsers = EscUser
TypeNotes := @TM:STR('- ',20):@TM:Note
END
END
**********************************************
WRITE ReactEventRec ON ReactEventTable,ReactEventKey THEN
FixCnt += 1
Send_Info(FixCnt:' ':ReactEventKey:' ':OCONV(EventDTM,'DT4/^HS'):' Updated from REACT_UTIL')
END
END
*/
END
SkipIt:
REPEAT
*UNLOCK All
* * * * * * *
Bail:
* * * * * * *
END