ready for UAT
final commit added PSN to reactor maintenance report query dialog
This commit is contained in:
committed by
Stieber Daniel (CSC FI SPS MESLEO)
parent
8b0eb3e468
commit
333cf0b8e2
@ -767,8 +767,8 @@ ReactNo = Get_Property(@WINDOW:'.REACT_NO','DEFPROP')
|
||||
|
||||
IF ReactNo NE '' THEN
|
||||
|
||||
TypeOver = ''
|
||||
TypeOver<PDISPLAY$> = 'WITH INJ_SET_REACT_NO = ':ReactNo:' BY-DSND INJ_SET_DTM'
|
||||
TypeOver = ''
|
||||
TypeOver<PDISPLAY$> = 'WITH REACTOR_NO = ':ReactNo:' BY-DSND INJ_SET_DTM'
|
||||
|
||||
void = Popup(@WINDOW,TypeOver,'REACT_INJ_SETTINGS')
|
||||
|
||||
@ -1107,3 +1107,4 @@ return
|
||||
|
||||
|
||||
|
||||
|
||||
|
File diff suppressed because it is too large
Load Diff
@ -6,17 +6,19 @@ COMPILE SUBROUTINE Print_Reactor_Maint1(Dummy)
|
||||
*/
|
||||
|
||||
|
||||
DECLARE SUBROUTINE Utility, ErrMsg, Set_Status, Set_Printer, RList
|
||||
DECLARE FUNCTION Set_Printer, Get_Printer, Msg, Get_Status, Printer_Select, obj_Install, Dialog_Box
|
||||
DECLARE SUBROUTINE Utility, ErrMsg, Set_Status, Set_Printer, RList, Push.Select, Pop.Select, Run_Report
|
||||
DECLARE FUNCTION Set_Printer, Get_Printer, Msg, Get_Status, Printer_Select, obj_Install, Dialog_Box
|
||||
DECLARE FUNCTION Reactor_Services
|
||||
|
||||
$INSERT OIPRINT_EQUATES
|
||||
$INSERT INVOICE_EQU
|
||||
$INSERT APPCOLORS
|
||||
$INSERT MSG_EQUATES
|
||||
|
||||
|
||||
EQU TAB$ TO \09\
|
||||
EQU TARGET_ACTIVELIST$ TO 5
|
||||
Equ BASE_NUM_COLS$ to 9
|
||||
Equ REPORT_WIDTH$ to 14670
|
||||
EQU TAB$ TO \09\
|
||||
EQU TARGET_ACTIVELIST$ TO 5
|
||||
|
||||
ErrorTitle = 'Error in stored procedure Print_Reactor_Maint'
|
||||
|
||||
@ -32,23 +34,24 @@ OPEN 'DICT.REACTOR_LOG' TO @DICT ELSE
|
||||
RETURN
|
||||
END
|
||||
|
||||
|
||||
Params = Dialog_Box( 'REACTOR_LOG_SRPT1', @WINDOW, '*CENTER' )
|
||||
|
||||
IF Params = 'CANCEL' OR Params = '' THEN
|
||||
RETURN
|
||||
END
|
||||
|
||||
|
||||
CONVERT '*' TO @FM IN Params
|
||||
|
||||
StartDateFrom = Params<1>
|
||||
StartDateThru = Params<2>
|
||||
Reactors = Params<3>
|
||||
ProblemCats = Params<4>
|
||||
ServiceIDs = Params<5>
|
||||
|
||||
WithStmt = ''
|
||||
StartDateFrom = Params<1>
|
||||
StartDateThru = Params<2>
|
||||
Reactors = Params<3>
|
||||
ProblemCats = Params<4>
|
||||
ServiceIDs = Params<5>
|
||||
PSNs = Params<6>
|
||||
IncludeReactItemIds = Params<7>
|
||||
IncludeInjSettings = Params<8>
|
||||
IncludeReactRatios = Params<9>
|
||||
WithStmt = ''
|
||||
|
||||
IF StartDateFrom AND StartDateThru THEN
|
||||
WithStmt:= 'WITH START_DATE FROM "':StartDateFrom:'" TO "':StartDateThru:'"'
|
||||
@ -79,6 +82,12 @@ IF ServiceIDs <> '' THEN
|
||||
WithStmt :=' AND WITH REACT_SERV_ID = ':ServiceIDs
|
||||
END
|
||||
|
||||
IF PSNs <> '' THEN
|
||||
SWAP @VM WITH "' '" IN PSNs
|
||||
PSNs = "'":PSNs:"'"
|
||||
WithStmt :=' AND WITH PROD_SPEC_NO = ':PSNs
|
||||
END
|
||||
|
||||
IF Reactors <> '' THEN
|
||||
SWAP "'" WITH '' IN Reactors
|
||||
SWAP " " WITH ", " IN Reactors
|
||||
@ -120,9 +129,9 @@ PageInfo<7> = LETTER ;* Pagesize
|
||||
|
||||
PageSetup = '1' ;* Landscape = 1
|
||||
PrintSetup = '2' ;* Preview Normal
|
||||
PrintPath = Printer_Select()
|
||||
PrintSetup<1, 2> = 0
|
||||
|
||||
If PrintPath EQ '' then return
|
||||
PrintPath = ''
|
||||
|
||||
stat = Set_Printer('INIT',FileName,Title,PageInfo,PageSetup,PrintSetup,PrintPath)
|
||||
IF stat < 0 THEN GOTO OIPrintErr
|
||||
@ -151,18 +160,41 @@ FirstPass = 1
|
||||
LastRecord = 0
|
||||
FirstLine = 1
|
||||
|
||||
* Make Column Heading
|
||||
NumCols = BASE_NUM_COLS$
|
||||
// 14670 width to work with
|
||||
|
||||
colHead = '' ; colFmt = ''
|
||||
colHead<1,1> = 'R' ; colFmt<1,1> = '^360'
|
||||
colHead<1,2> = 'Problem Cat Desc' ; colFmt<1,2> = '<1800'
|
||||
colHead<1,3> = 'Serv':CRLF$:'ID' ; colFmt<1,3> = '^540'
|
||||
colHead<1,4> = 'Reactor Svc Desc' ; colFmt<1,4> = '<3600'
|
||||
colHead<1,5> = 'Tech' ; colFmt<1,5> = '^1080'
|
||||
colHead<1,6> = 'Reactor Item ID' ; colFmt<1,6> = '<2160'
|
||||
colHead<1,7> = 'Notes' ; colFmt<1,7> = '<3600'
|
||||
colHead<1,8> = 'Start' ; colFmt<1,8> = '^810'
|
||||
colHead<1,9> = 'Hrs' ; colFmt<1,9> = '>720'
|
||||
* Make Column Heading
|
||||
If IncludeReactItemIds then
|
||||
NumCols += 1
|
||||
end
|
||||
|
||||
If IncludeInjSettings then
|
||||
NumCols += 1
|
||||
end
|
||||
|
||||
If IncludeReactRatios then
|
||||
NumCols += 1
|
||||
end
|
||||
|
||||
colHead = '' ; colFmt = ''
|
||||
colHead<1,-1> = 'R' ; colFmt<1,-1> = '^':(REPORT_WIDTH$ * (.050 * (BASE_NUM_COLS$ / NumCols) ) )
|
||||
colHead<1,-1> = 'PSN' ; colFmt<1,-1> = '^':(REPORT_WIDTH$ * (.049 * (BASE_NUM_COLS$ / NumCols) ) )
|
||||
colHead<1,-1> = 'Problem Cat Desc' ; colFmt<1,-1> = '<':(REPORT_WIDTH$ * (.117 * (BASE_NUM_COLS$ / NumCols) ) )
|
||||
colHead<1,-1> = 'Serv':CRLF$:'ID' ; colFmt<1,-1> = '^':(REPORT_WIDTH$ * (.073 * (BASE_NUM_COLS$ / NumCols) ) )
|
||||
colHead<1,-1> = 'Reactor Svc Desc' ; colFmt<1,-1> = '<':(REPORT_WIDTH$ * (.258 * (BASE_NUM_COLS$ / NumCols) ) )
|
||||
colHead<1,-1> = 'Tech' ; colFmt<1,-1> = '^':(REPORT_WIDTH$ * (.068 * (BASE_NUM_COLS$ / NumCols) ) )
|
||||
If IncludeReactItemIds then
|
||||
colHead<1,-1> = 'Reactor Item ID' ; colFmt<1,-1> = '<':(REPORT_WIDTH$ * ( 1 / NumCols) )
|
||||
end
|
||||
If IncludeInjSettings then
|
||||
colHead<1,-1> = 'Inj Settings' ; colFmt<1,-1> = '<':(REPORT_WIDTH$ * ( 1 / NumCols) - 50 )
|
||||
end
|
||||
If IncludeReactRatios then
|
||||
colHead<1,-1> = 'Ratios' ; colFmt<1,-1> = '<':(REPORT_WIDTH$ * ( 1 / NumCols) + 150 )
|
||||
end
|
||||
colHead<1,-1> = 'Notes' ; colFmt<1,-1> = '<':(REPORT_WIDTH$ * (.248 * (BASE_NUM_COLS$ / NumCols) ) )
|
||||
colHead<1,-1> = 'Start' ; colFmt<1,-1> = '^':(REPORT_WIDTH$ * (.079 * (BASE_NUM_COLS$ / NumCols) ) )
|
||||
colHead<1,-1> = 'Hrs' ; colFmt<1,-1> = '>':(REPORT_WIDTH$ * (.043 * (BASE_NUM_COLS$ / NumCols) ) )
|
||||
|
||||
* Zero Accumulators For Each Break
|
||||
|
||||
@ -207,26 +239,45 @@ END
|
||||
@RECCOUNT += 1
|
||||
|
||||
* CALCULATE VALUE(S) FOR COLUMN(S)
|
||||
|
||||
S.ATID = {@ID}
|
||||
|
||||
S.Reactor={REACTOR}
|
||||
|
||||
S.React_Prob_Cat_Desc = {REACT_PROB_CAT_DESC}
|
||||
S.React_Serv_ID = {REACT_SERV_ID}
|
||||
S.React_Serv_Desc = {REACT_SERV_DESC}
|
||||
S.Tech = {TECH_SIG}
|
||||
S.Notes = {NOTES}
|
||||
S.StartDTM = OCONV({START_DATE},'D2/'):' ':OCONV({START_TIME},'MTS')
|
||||
S.Elapsed_Hours = {ELAPSED_HOURS}
|
||||
S.React_Item_IDS = {REACT_ITEM_IDS}
|
||||
|
||||
S.Reactor = {REACTOR}
|
||||
S.PSN = {PROD_SPEC_NO}
|
||||
S.React_Prob_Cat_Desc = {REACT_PROB_CAT_DESC}
|
||||
S.React_Serv_ID = {REACT_SERV_ID}
|
||||
S.React_Serv_Desc = {REACT_SERV_DESC}
|
||||
S.Tech = {TECH_SIG}
|
||||
S.Notes = {NOTES}
|
||||
S.StartDTM = OCONV({START_DATE},'D2/'):' ':OCONV({START_TIME},'MTS')
|
||||
S.Elapsed_Hours = {ELAPSED_HOURS}
|
||||
S.React_Item_IDS = {REACT_ITEM_IDS}
|
||||
Push.Select(f1, f2, f3, f4)
|
||||
S.InjSettings = ''
|
||||
InjSettings = OConv(Reactor_Services('GetInjectorSettingsByReactorLog', @ID), 'MD3,')
|
||||
NumSettings = DCount(InjSettings, @VM)
|
||||
If NumSettings GT 0 then
|
||||
For SettingIndex = 1 to NumSettings
|
||||
S.InjSettings<0, SettingIndex> = 'Inj ':SettingIndex:': ':InjSettings<0, SettingIndex>
|
||||
Next SettingIndex
|
||||
end
|
||||
Pop.Select(f1, f2, f3, f4)
|
||||
Push.Select(f1, f2, f3, f4)
|
||||
S.ReactorRatios = ''
|
||||
ReactorRatios = OConv(Reactor_Services('GetRatiosByReactorLog', @ID), 'MD3,')
|
||||
NumRatios = DCount(ReactorRatios, @VM)
|
||||
If NumRatios GT 0 then
|
||||
For RatioIndex = 1 to NumRatios
|
||||
S.ReactorRatios<0, RatioIndex> = 'Ratio ':RatioIndex:': ':ReactorRatios<0, RatioIndex>
|
||||
Next RatioIndex
|
||||
end
|
||||
Pop.Select(f1, f2, f3, f4)
|
||||
SWAP @VM WITH CRLF$ IN S.React_Prob_Cat_Desc
|
||||
SWAP @VM WITH CRLF$ IN S.React_Serv_ID
|
||||
SWAP @VM WITH CRLF$ IN S.React_Serv_Desc
|
||||
SWAP @VM WITH CRLF$ IN S.Notes
|
||||
SWAP @VM WITH CRLF$ IN S.React_Item_IDS
|
||||
|
||||
SWAP @VM WITH CRLF$ IN S.InjSettings
|
||||
SWAP @VM WITH CRLF$ IN S.ReactorRatios
|
||||
|
||||
* TEST FOR CONTROL BREAK(S)
|
||||
|
||||
@ -277,10 +328,6 @@ IF LastRecord THEN
|
||||
|
||||
GOSUB PrintTable
|
||||
|
||||
*status = Set_Printer('TEXT','')
|
||||
*status = Set_Printer('TEXT',@RECCOUNT:' Records Processed')
|
||||
|
||||
|
||||
GOTO Bail
|
||||
|
||||
END
|
||||
@ -301,16 +348,25 @@ END
|
||||
|
||||
* Print Detail Line
|
||||
|
||||
colData = ""
|
||||
colData<1,1> = S.Reactor
|
||||
colData<1,2> = S.React_Prob_Cat_Desc
|
||||
colData<1,3> = S.React_Serv_ID
|
||||
colData<1,4> = S.React_Serv_Desc
|
||||
colData<1,5> = S.Tech
|
||||
colData<1,6> = S.React_Item_IDS
|
||||
colData<1,7> = S.Notes
|
||||
colData<1,8> = S.StartDTM
|
||||
colData<1,9> = OCONV(S.Elapsed_Hours,'MD2')
|
||||
colData = ""
|
||||
colData<1,-1> = S.Reactor
|
||||
colData<1,-1> = S.PSN
|
||||
colData<1,-1> = S.React_Prob_Cat_Desc
|
||||
colData<1,-1> = S.React_Serv_ID
|
||||
colData<1,-1> = S.React_Serv_Desc
|
||||
colData<1,-1> = S.Tech
|
||||
If IncludeReactItemIds then
|
||||
colData<1,-1> = S.React_Item_IDS
|
||||
end
|
||||
If IncludeInjSettings then
|
||||
colData<1,-1> = S.InjSettings
|
||||
end
|
||||
If IncludeReactRatios then
|
||||
colData<1,-1> = S.ReactorRatios
|
||||
end
|
||||
colData<1,-1> = S.Notes
|
||||
colData<1,-1> = S.StartDTM
|
||||
colData<1,-1> = OCONV(S.Elapsed_Hours,'MD2')
|
||||
|
||||
GOSUB PrintTable
|
||||
|
||||
@ -342,7 +398,6 @@ RETURN
|
||||
PrintTable:
|
||||
* * * * * *
|
||||
|
||||
|
||||
stat = Set_Printer('CALCTABLE',colFmt:@FM:colData)
|
||||
TableSize = Get_Printer('CALCTABLE')
|
||||
TableHeight = TableSize<2>
|
||||
@ -375,278 +430,3 @@ END
|
||||
|
||||
RETURN
|
||||
|
||||
|
||||
/*
|
||||
|
||||
* ZERO ACCUMULATORS FOR EACH BREAK
|
||||
|
||||
Elapsed_Hours.Reactor.Total=0
|
||||
Elapsed_Hours.Reactor.Count=0
|
||||
Elapsed_Hours.Grand.Total=0
|
||||
Elapsed_Hours.Grand.Count=0
|
||||
|
||||
* NULL PREVIOUS BREAK BUCKETS
|
||||
|
||||
Prev.Reactor=''
|
||||
Last.Reactor.Break = 1
|
||||
|
||||
* * * * * * *
|
||||
READRECORD:
|
||||
* * * * * * *
|
||||
|
||||
IF @RECCOUNT GE 10 THEN
|
||||
Last.Record=1
|
||||
Reactor.Break=1
|
||||
REACTOR=Prev.Reactor
|
||||
REACTOR=Prev.Reactor
|
||||
GOTO BREAKS
|
||||
END
|
||||
*
|
||||
*
|
||||
* ZERO BREAK FLAGS TO FALSE
|
||||
*
|
||||
Reactor.Break=0
|
||||
*
|
||||
*
|
||||
READNEXT @ID, WHICH.VALUE ELSE
|
||||
IF STATUS() GT 0 THEN
|
||||
STATX = SET_FSERROR()
|
||||
RETURN
|
||||
END
|
||||
IF @FILE.ERROR<1> EQ 421 THEN
|
||||
STATX = SET_FSERROR()
|
||||
GOTO READRECORD
|
||||
END
|
||||
IF @FILE.ERROR<1> NE 111 THEN
|
||||
@ANS = @FILE.ERROR<1>
|
||||
STATX = SEND_DYN( {RLIST_TEXT_4} )
|
||||
READERR += 1
|
||||
GOTO READRECORD
|
||||
END
|
||||
Last.Record=1
|
||||
Reactor.Break=1
|
||||
REACTOR=Prev.Reactor
|
||||
END
|
||||
@FILE.ERROR.MODE=0
|
||||
|
||||
S.ATID = @ID
|
||||
|
||||
IF FirstPass AND Last.Record THEN
|
||||
STATX = SEND_DYN( {RLIST_TEXT_2} )
|
||||
RETURN
|
||||
END
|
||||
|
||||
IF Last.Record THEN GOTO BREAKS
|
||||
|
||||
IF @REDUCTION.DONE THEN
|
||||
READO @RECORD FROM FILE.IN, @ID ELSE
|
||||
@FILE.ERROR.MODE = 0
|
||||
IF STATUS() GT 0 THEN
|
||||
STATX = SET_FSERROR()
|
||||
RETURN
|
||||
END
|
||||
IF @FILE.ERROR<1> NE 100 THEN
|
||||
READERR += 1
|
||||
END
|
||||
GOTO READRECORD
|
||||
END
|
||||
END
|
||||
|
||||
@RECCOUNT += 1
|
||||
|
||||
|
||||
* CALCULATE VALUE(S) FOR COLUMN(S)
|
||||
|
||||
S.ATID={@ID}
|
||||
I.ATID=S.ATID
|
||||
S.Reactor={REACTOR}
|
||||
I.Reactor=S.Reactor
|
||||
S.Reactor1={REACTOR}
|
||||
I.Reactor1=S.Reactor1
|
||||
M.REACT_PROB_CAT_DESC={REACT_PROB_CAT_DESC}<1,WHICH.VALUE> ; P.REACT_PROB_CAT_DESC=1 ; C.REACT_PROB_CAT_DESC=7
|
||||
|
||||
* INITIALIZE MULTIVALUE BREAK CHECK VARIABLE
|
||||
|
||||
S.REACT_PROB_CAT_DESC = M.REACT_PROB_CAT_DESC
|
||||
M.REACT_SERV_ID={REACT_SERV_ID}<1,WHICH.VALUE> ; P.REACT_SERV_ID=1 ; C.REACT_SERV_ID=7
|
||||
|
||||
* INITIALIZE MULTIVALUE BREAK CHECK VARIABLE
|
||||
|
||||
S.REACT_SERV_ID = M.REACT_SERV_ID
|
||||
M.REACT_SERV_DESC={REACT_SERV_DESC}<1,WHICH.VALUE> ; P.REACT_SERV_DESC=1 ; C.REACT_SERV_DESC=7
|
||||
|
||||
* INITIALIZE MULTIVALUE BREAK CHECK VARIABLE
|
||||
|
||||
S.REACT_SERV_DESC = M.REACT_SERV_DESC
|
||||
S.TECH_SIG={TECH_SIG}
|
||||
I.TECH_SIG=S.TECH_SIG
|
||||
M.NOTES=FMT({NOTES},"T#20") ; P.NOTES=1 ; C.NOTES=7
|
||||
|
||||
* INITIALIZE TEXT BREAK CHECK VARIABLE(S)
|
||||
|
||||
S.NOTES = M.NOTES
|
||||
S.START_DATE={START_DATE}
|
||||
I.START_DATE=S.START_DATE
|
||||
S.Elapsed_Hours={Elapsed_Hours}
|
||||
I.Elapsed_Hours=S.Elapsed_Hours
|
||||
|
||||
PREVIOUS.MARK.LEVEL=0
|
||||
|
||||
* TEST FOR CONTROL BREAK(S)
|
||||
|
||||
IF (S.Reactor NE Prev.Reactor) OR Reactor.Break THEN
|
||||
REACTOR=Prev.Reactor
|
||||
Prev.Reactor=S.Reactor
|
||||
Reactor.Break+=1
|
||||
END
|
||||
|
||||
|
||||
IF FirstPass THEN
|
||||
FirstPass=0
|
||||
GOTO DETAIL
|
||||
END
|
||||
|
||||
* * * * * *
|
||||
BREAKS:
|
||||
* * * * * *
|
||||
|
||||
* PRINT BREAK TOTAL(S) AND ACCUMULATE TOTAL(S)
|
||||
|
||||
IF Reactor.Break THEN
|
||||
STATX = SEND_DYN("")
|
||||
PRINTLINE = ""
|
||||
PRINTLINE := FMT("***" : "", "R#14") : TAB$
|
||||
|
||||
PRINTLINE := SPACE(14) : TAB$
|
||||
|
||||
PRINTLINE := SPACE(24) : TAB$
|
||||
|
||||
PRINTLINE := SPACE(14) : TAB$
|
||||
|
||||
PRINTLINE := SPACE(20) : TAB$
|
||||
|
||||
PRINTLINE := SPACE(20) : TAB$
|
||||
|
||||
PRINTLINE := SPACE(20) : TAB$
|
||||
|
||||
PRINTLINE := SPACE(11) : TAB$
|
||||
|
||||
PRINTLINE := FMT(OCONV(Elapsed_Hours.Reactor.Total ,"MD2") , "R#16")
|
||||
STATX = SEND_DYN( PRINTLINE )
|
||||
STATX = SEND_DYN("")
|
||||
|
||||
Elapsed_Hours.Grand.Total+=Elapsed_Hours.Reactor.Total
|
||||
Elapsed_Hours.Reactor.Total=0
|
||||
Elapsed_Hours.Grand.Count+=Elapsed_Hours.Reactor.Count
|
||||
Elapsed_Hours.Reactor.Count=0
|
||||
END
|
||||
|
||||
* PERFORM LAST RECORD OUTPUT IF DONE
|
||||
|
||||
IF Last.Record THEN
|
||||
STATX = SEND_DYN("")
|
||||
PRINTLINE = ""
|
||||
PRINTLINE := FMT("***" : "", "R#14") : TAB$
|
||||
PRINTLINE := SPACE(14) : TAB$
|
||||
PRINTLINE := SPACE(24) : TAB$
|
||||
PRINTLINE := SPACE(14) : TAB$
|
||||
PRINTLINE := SPACE(20) : TAB$
|
||||
PRINTLINE := SPACE(20) : TAB$
|
||||
PRINTLINE := SPACE(20) : TAB$
|
||||
PRINTLINE := SPACE(11) : TAB$
|
||||
PRINTLINE := FMT(OCONV(Elapsed_Hours.Grand.Total ,"MD2") , "R#16")
|
||||
STATX = SEND_DYN( PRINTLINE )
|
||||
STATX = SEND_DYN("")
|
||||
@ANS=@RECCOUNT
|
||||
STATX = SEND_DYN( {RLIST_TEXT_1} )
|
||||
IF READERR THEN
|
||||
@ANS=READERR
|
||||
STATX = SEND_DYN( {RLIST_TEXT_3} )
|
||||
END
|
||||
RETURN
|
||||
END
|
||||
|
||||
* * * * * * *
|
||||
DETAIL:
|
||||
* * * * * * *
|
||||
|
||||
* REMOVE APPROPRIATE VALUE FROM MULTI-VALUED COLUMN(S)
|
||||
|
||||
NEW.MARK.LEVEL=0
|
||||
|
||||
IF C.REACT_PROB_CAT_DESC GE PREVIOUS.MARK.LEVEL THEN
|
||||
REMOVE I.REACT_PROB_CAT_DESC FROM M.REACT_PROB_CAT_DESC AT P.REACT_PROB_CAT_DESC SETTING C.REACT_PROB_CAT_DESC
|
||||
S.REACT_PROB_CAT_DESC=I.REACT_PROB_CAT_DESC
|
||||
END
|
||||
IF C.REACT_PROB_CAT_DESC GT NEW.MARK.LEVEL THEN NEW.MARK.LEVEL=C.REACT_PROB_CAT_DESC
|
||||
|
||||
IF C.REACT_SERV_ID GE PREVIOUS.MARK.LEVEL THEN
|
||||
REMOVE I.REACT_SERV_ID FROM M.REACT_SERV_ID AT P.REACT_SERV_ID SETTING C.REACT_SERV_ID
|
||||
S.REACT_SERV_ID=I.REACT_SERV_ID
|
||||
END
|
||||
IF C.REACT_SERV_ID GT NEW.MARK.LEVEL THEN NEW.MARK.LEVEL=C.REACT_SERV_ID
|
||||
|
||||
IF C.REACT_SERV_DESC GE PREVIOUS.MARK.LEVEL THEN
|
||||
REMOVE I.REACT_SERV_DESC FROM M.REACT_SERV_DESC AT P.REACT_SERV_DESC SETTING C.REACT_SERV_DESC
|
||||
S.REACT_SERV_DESC=I.REACT_SERV_DESC
|
||||
END
|
||||
IF C.REACT_SERV_DESC GT NEW.MARK.LEVEL THEN NEW.MARK.LEVEL=C.REACT_SERV_DESC
|
||||
|
||||
IF C.NOTES GE PREVIOUS.MARK.LEVEL THEN
|
||||
REMOVE I.NOTES FROM M.NOTES AT P.NOTES SETTING C.NOTES
|
||||
S.NOTES=I.NOTES
|
||||
END
|
||||
IF C.NOTES GT NEW.MARK.LEVEL THEN NEW.MARK.LEVEL=C.NOTES
|
||||
|
||||
|
||||
* DO CONVERSIONS IF ANY
|
||||
|
||||
IF S.Reactor NE "" THEN S.Reactor=OCONV(S.Reactor,"MD0")
|
||||
IF S.Reactor1 NE "" THEN S.Reactor1=OCONV(S.Reactor1,"MD0")
|
||||
IF S.REACT_SERV_ID NE "" THEN S.REACT_SERV_ID=OCONV(S.REACT_SERV_ID,"MD0")
|
||||
IF S.START_DATE NE "" THEN S.START_DATE=OCONV(S.START_DATE,"D2/")
|
||||
IF S.Elapsed_Hours NE "" THEN S.Elapsed_Hours=OCONV(S.Elapsed_Hours,"MD2")
|
||||
|
||||
* ACCUMULATE TOTAL(S)
|
||||
|
||||
IF NUM(I.Elapsed_Hours) AND I.Elapsed_Hours NE "" THEN
|
||||
Elapsed_Hours.Reactor.Total+=I.Elapsed_Hours
|
||||
Elapsed_Hours.Reactor.Count+=1
|
||||
I.Elapsed_Hours=''
|
||||
END
|
||||
|
||||
* PRINT DETAIL LINE
|
||||
|
||||
PRINTLINE = ""
|
||||
PRINTLINE := FMT( S.Reactor, "R#14") : TAB$
|
||||
PRINTLINE := FMT( S.Reactor1, "R#14") : TAB$
|
||||
PRINTLINE := FMT( S.REACT_PROB_CAT_DESC, "L#24") : TAB$
|
||||
PRINTLINE := FMT( S.REACT_SERV_ID, "R#14") : TAB$
|
||||
PRINTLINE := FMT( S.REACT_SERV_DESC, "L#20") : TAB$
|
||||
PRINTLINE := FMT( S.TECH_SIG, "L#20") : TAB$
|
||||
PRINTLINE := FMT( S.NOTES, "L#20") : TAB$
|
||||
PRINTLINE := FMT( S.START_DATE, "R#11") : TAB$
|
||||
PRINTLINE := FMT( S.Elapsed_Hours, "R#16")
|
||||
STATX = SEND_DYN( PRINTLINE )
|
||||
|
||||
IF NEW.MARK.LEVEL THEN
|
||||
S.Reactor=''
|
||||
S.Reactor1=''
|
||||
S.REACT_PROB_CAT_DESC=''
|
||||
S.REACT_SERV_ID=''
|
||||
S.REACT_SERV_DESC=''
|
||||
S.TECH_SIG=''
|
||||
S.NOTES=''
|
||||
S.START_DATE=''
|
||||
S.Elapsed_Hours=''
|
||||
PREVIOUS.MARK.LEVEL=NEW.MARK.LEVEL
|
||||
GOTO DETAIL
|
||||
END
|
||||
|
||||
GOTO READRECORD
|
||||
|
||||
END
|
||||
|
||||
*/
|
||||
|
||||
|
||||
|
@ -165,7 +165,7 @@ Event WINDOW.OMNIEVENT(Message, Param1, Param2, Param3, Param4)
|
||||
CtrlMap = Get_Property(@Window, 'CTRLMAP')
|
||||
For each Ctrl in CtrlMap using @FM setting fPos
|
||||
CtrlType = Get_Property(Ctrl, 'TYPE')
|
||||
If Not( (Ctrl EQ @Window:'.OLE_EDT_NOTES') or (Ctrl EQ @Window:'.PUB_ADD_COMMENT') or (Ctrl EQ @Window:'.NEW_BUTTON') or (Ctrl EQ @Window:'.PRINT_ROOT_CAUSE') or (Ctrl EQ @Window:'.BUTTON_18') or (Ctrl EQ @Window:'.LU_RL_NO') or (CtrlType EQ 'STATIC') or (Ctrl EQ @Window:'.TECH_SIGN') or (CtrlType EQ 'WINDOW') or (Ctrl EQ @Window:'.PHX_BTN_CLEAR') or (Ctrl EQ @Window:'.TAB') or (IndexC(Ctrl, 'QBF', 1) GT 0) or (Ctrl EQ @Window:'.REACTOR_LOG_NO') or (CtrlType EQ 'GROUPBOX') ) then
|
||||
If Not( (Ctrl EQ @Window:'.OLE_EDT_NOTES') or (Ctrl EQ @Window:'.PUB_ADD_COMMENT') or (Ctrl EQ @Window:'.NEW_BUTTON') or (Ctrl EQ @Window:'.PRINT_ROOT_CAUSE') or (Ctrl EQ @Window:'.BUTTON_18') or (Ctrl EQ @Window:'.LU_RL_NO') or (CtrlType EQ 'STATIC') or (Ctrl EQ @Window:'.TECH_SIGN') or (CtrlType EQ 'WINDOW') or (Ctrl EQ @Window:'.PHX_BTN_CLEAR') or (Ctrl EQ @Window:'.TAB') or (IndexC(Ctrl, 'QBF', 1) GT 0) or (Ctrl EQ @Window:'.REACTOR_LOG_NO') or (CtrlType EQ 'GROUPBOX') or (Ctrl EQ @Window:'.INJ_SETTING_HIST') or (Ctrl EQ @Window:'.PUB_RATIO_HISTORY') ) then
|
||||
Set_Property(Ctrl, 'ENABLED', (Signature EQ ''))
|
||||
end
|
||||
Next Ctrl
|
||||
@ -281,3 +281,4 @@ UpdateNotes:
|
||||
|
||||
return
|
||||
|
||||
|
||||
|
@ -184,17 +184,17 @@ Service SignReactorLog(ReactorLogID, UserID)
|
||||
end
|
||||
If ErrorMsg EQ '' then
|
||||
// Check if injector settings have been entered
|
||||
ReactInjSetting = ReactorLogRec<REACTOR_LOG_INJ_SETTING$>
|
||||
If ReactInjSetting NE '' then
|
||||
plParms = 'REACT_STATE':@RM
|
||||
plParms := ReactorNo:@RM
|
||||
plParms := REACT_STATE_CURR_INJ_RL_ID$:@RM
|
||||
plParms := ReactorLogID:@RM
|
||||
obj_Post_Log('Create',plParms)
|
||||
If Get_Status(ErrCode) then
|
||||
ErrorMsg = 'Error in ':Service:' service. Error calling obj_Post_Log("Create"). Error code: ':ErrCode:'.'
|
||||
end
|
||||
end
|
||||
* ReactInjSetting = ReactorLogRec<REACTOR_LOG_INJ_SETTING$>
|
||||
* If ReactInjSetting NE '' then
|
||||
* plParms = 'REACT_STATE':@RM
|
||||
* plParms := ReactorNo:@RM
|
||||
* plParms := REACT_STATE_CURR_INJ_RL_ID$:@RM
|
||||
* plParms := ReactorLogID:@RM
|
||||
* obj_Post_Log('Create',plParms)
|
||||
* If Get_Status(ErrCode) then
|
||||
* ErrorMsg = 'Error in ':Service:' service. Error calling obj_Post_Log("Create"). Error code: ':ErrCode:'.'
|
||||
* end
|
||||
* end
|
||||
If ErrorMsg EQ '' then
|
||||
// Check reactor prevent maintenance records
|
||||
CurServices = ReactorLogRec<REACTOR_LOG_REACT_SERV_ID$>
|
||||
@ -974,3 +974,4 @@ ClearCursors:
|
||||
|
||||
return
|
||||
|
||||
|
||||
|
@ -167,3 +167,4 @@ write '' on SysListsTable, ListsId else
|
||||
end
|
||||
return 0
|
||||
|
||||
|
||||
|
@ -55,8 +55,12 @@ $Insert IQS_VIOL_DATA_EQUATES
|
||||
$Insert FEATURE_FLAGS_EQUATES
|
||||
$Insert REACT_PROB_CAT_EQUATES
|
||||
$Insert NICA_ORDERS_EQUATES
|
||||
$Insert REACTOR_INJECTOR_SETTINGS_EQUATES
|
||||
$Insert REACTOR_RATIOS_EQUATES
|
||||
$Insert REACT_STATE_EQUATES
|
||||
|
||||
Equ WOCust$ to 2
|
||||
Equ WOCust$ to 2
|
||||
Equ SECONDS_IN_DAY$ to 86400
|
||||
|
||||
// Uptime Percentage Equates
|
||||
Equ PRODUCTIVE$ to 1
|
||||
@ -68,13 +72,13 @@ Equ ENG$ to 5
|
||||
Declare subroutine Error_Services, Reactor_Services, Memory_Services, RList, Database_Services, SRP_JSON
|
||||
Declare subroutine Excel_Services, Schedule_Services, Logging_Services, Set_Status, obj_React_Status, Errmsg
|
||||
Declare subroutine Obj_Notes, Btree.Extract, SRP_Fastarray, Delay, Mona_Services, SRP_List, Msg, Rds_Services
|
||||
Declare subroutine React_Assign_Conv, Nica_Orders_Services, obj_React_Mode, Reactor_Log_Services
|
||||
Declare subroutine React_Assign_Conv, Nica_Orders_Services, obj_React_Mode, Reactor_Log_Services, obj_Post_Log
|
||||
Declare function SRP_Array, Reactor_Services, Memory_Services, Database_Services, SRP_Sort_Array, Excel_Services
|
||||
Declare function SRP_Math, SRP_Hash, SRP_JSON, Epi_Part_Services, Schedule_Services, Date_Services, Environment_Services
|
||||
Declare function Logging_Services, GetCommandLine, NextKey, Reactor_Log_Services, SRP_DateTime, ole_getwebpage
|
||||
Declare function Datetime, Reactor_Modes_Services, Work_Order_Services, React_Mode_NG_Services, Lsl_Users_Services
|
||||
Declare function SRP_Time, Rds_Services, SRP_Fastarray, Httpclient_Services, SRP_List, Utility, Memberof, Error_Services
|
||||
Declare function Nica_Orders_Services, Max
|
||||
Declare function Nica_Orders_Services, Max, RTI_CreateGUID
|
||||
|
||||
// Report paths for various performance report services.
|
||||
TemplatesFolder = Environment_Services('GetApplicationRootPath') : '\Reports\Scheduler\Templates\'
|
||||
@ -2116,6 +2120,15 @@ Service CreateReactModeChange(UserID, ReactNo, Mode, ModeSubCat, ModeText, Force
|
||||
RLRec<reactor_log_react_util_id$> = NewRUKey
|
||||
RLRec<reactor_log_react_prob_cat_id$> = ModeSubCatID
|
||||
|
||||
CurrWoNo = Xlate('CONFIG', 'WO_DAILY_SCHED':ReactNo, 'F2', 'X')
|
||||
CurrWoNo = CurrWoNo[1, 'F ']
|
||||
If CurrWoNo NE '' then
|
||||
CurrPSNo = Xlate('WO_LOG', CurrWoNo, 'PS_NO', 'X')
|
||||
end else
|
||||
CurrPSNo = ''
|
||||
end
|
||||
RLRec<REACTOR_LOG_PROD_SPEC_NO$> = CurrPSNo
|
||||
|
||||
Database_Services('WriteDataRow', 'REACTOR_LOG', NewRLKey, RLRec)
|
||||
If Error_Services('NoError') then
|
||||
Database_Services('WriteDataRow', 'REACT_UTIL', NewRUKey, RUtilRec)
|
||||
@ -3738,6 +3751,7 @@ Service GetActiveProveInProgresses(ReactNo)
|
||||
|
||||
end service
|
||||
|
||||
|
||||
Service GetActiveProveInOrderIds(ReactNo)
|
||||
|
||||
If ReactNo NE '' then
|
||||
@ -3760,6 +3774,495 @@ Service GetIdleStartupRequired(ReactNo)
|
||||
|
||||
end service
|
||||
|
||||
|
||||
Service GetCurrentInjectorSettings(ReactorNo)
|
||||
|
||||
ErrorMsg = ''
|
||||
CurrInjSettings = ''
|
||||
If ReactorNo NE '' then
|
||||
If RowExists('REACTOR', ReactorNo) then
|
||||
Open 'DICT.REACTOR_INJECTOR_SETTINGS' to hDict then
|
||||
Query = 'REACTOR_NO':@VM:ReactorNo:@FM
|
||||
Query := 'ACTIVE':@VM:True$:@FM
|
||||
KeyList = ''
|
||||
Option = 'E'
|
||||
Flag = ''
|
||||
Btree.Extract(Query, 'REACTOR_INJECTOR_SETTINGS', hDict, KeyList, Option, Flag)
|
||||
If Flag EQ 0 then
|
||||
Begin Case
|
||||
Case DCount(KeyList, @VM) EQ 0
|
||||
CurrInjSettings<0, 1> = ''
|
||||
CurrInjSettings<0, 2> = ''
|
||||
CurrInjSettings<0, 3> = ''
|
||||
CurrInjSettings<0, 4> = ''
|
||||
CurrInjSettings<0, 5> = ''
|
||||
Case DCount(KeyList, @VM) EQ 1
|
||||
SettingsRec = Database_Services('ReadDataRow', 'REACTOR_INJECTOR_SETTINGS', KeyList)
|
||||
If Error_Services('NoError') then
|
||||
CurrInjSettings<0, 1> = SettingsRec<REACTOR_INJECTOR_SETTINGS.INJECTOR_1$>
|
||||
CurrInjSettings<0, 2> = SettingsRec<REACTOR_INJECTOR_SETTINGS.INJECTOR_2$>
|
||||
CurrInjSettings<0, 3> = SettingsRec<REACTOR_INJECTOR_SETTINGS.INJECTOR_3$>
|
||||
CurrInjSettings<0, 4> = SettingsRec<REACTOR_INJECTOR_SETTINGS.INJECTOR_4$>
|
||||
CurrInjSettings<0, 5> = SettingsRec<REACTOR_INJECTOR_SETTINGS.INJECTOR_5$>
|
||||
end
|
||||
Case DCount(KeyList, @VM) GT 1
|
||||
ErrorMsg = 'Error in ':Service:' service. Multiple active REACTOR_INJECTOR_SETTINGS records returned.'
|
||||
End Case
|
||||
end else
|
||||
ErrorMsg = 'Error in ':Service:' service. Error calling Btree.Extract.'
|
||||
end
|
||||
end else
|
||||
ErrorMsg = 'Error in ':Service:' service. Error opening DICT.REACTOR_INJECTOR_SETTINGS.'
|
||||
end
|
||||
end else
|
||||
ErrorMsg = 'Error in ':Service:' service. REACTOR, ':ReactorNo:', does not exist.'
|
||||
end
|
||||
end else
|
||||
ErrorMsg = 'Error in ':Service:' service. Null ReactorNo passed into service.'
|
||||
end
|
||||
|
||||
If ErrorMsg EQ '' then
|
||||
Response = CurrInjSettings
|
||||
end else
|
||||
Error_Services('Add', ErrorMsg)
|
||||
end
|
||||
|
||||
end service
|
||||
|
||||
|
||||
Service GetCurrentRatios(ReactorNo)
|
||||
|
||||
ErrorMsg = ''
|
||||
CurrRatios = ''
|
||||
If ReactorNo NE '' then
|
||||
If RowExists('REACTOR', ReactorNo) then
|
||||
Open 'DICT.REACTOR_RATIOS' to hDict then
|
||||
Query = 'REACTOR_NO':@VM:ReactorNo:@FM
|
||||
Query := 'ACTIVE':@VM:True$:@FM
|
||||
KeyList = ''
|
||||
Option = 'E'
|
||||
Flag = ''
|
||||
Btree.Extract(Query, 'REACTOR_RATIOS', hDict, KeyList, Option, Flag)
|
||||
If Flag EQ 0 then
|
||||
NumRatios = ''
|
||||
ReactorType = Xlate('REACTOR', ReactorNo, REACTOR_REACT_TYPE$, 'X')
|
||||
Begin Case
|
||||
Case ReactorNo EQ 73
|
||||
// OpenInsight needs to be updated to support reactor type HTR+, which requires 16 ratios.
|
||||
NumRatios = 16
|
||||
Case ReactorType EQ 'ASM' or ReactorType EQ 'ASM+'
|
||||
NumRatios = 10
|
||||
Case ReactorType EQ 'HTR'
|
||||
NumRatios = 12
|
||||
Case Otherwise$
|
||||
ErrorMsg = 'Error in ':Service:' service. Error determining number '
|
||||
ErrorMsg := 'of Ratios required for reactor ':ReactorNo:'.'
|
||||
End Case
|
||||
If ErrorMsg EQ '' then
|
||||
Begin Case
|
||||
Case DCount(KeyList, @VM) EQ 0
|
||||
For RatioIndex = 1 to NumRatios
|
||||
CurrRatios<0, RatioIndex> = ''
|
||||
Next RatioIndex
|
||||
Case DCount(KeyList, @VM) EQ 1
|
||||
SettingsRec = Database_Services('ReadDataRow', 'REACTOR_RATIOS', KeyList)
|
||||
If Error_Services('NoError') then
|
||||
For RatioIndex = 0 to (NumRatios - 1)
|
||||
CurrRatios<0, RatioIndex + 1> = SettingsRec<REACTOR_RATIOS.RATIO_1$ + RatioIndex>
|
||||
Next RatioIndex
|
||||
end
|
||||
Case DCount(KeyList, @VM) GT 1
|
||||
ErrorMsg = 'Error in ':Service:' service. Multiple active REACTOR_RATIOS records returned.'
|
||||
End Case
|
||||
end
|
||||
end else
|
||||
ErrorMsg = 'Error in ':Service:' service. Error calling Btree.Extract.'
|
||||
end
|
||||
end else
|
||||
ErrorMsg = 'Error in ':Service:' service. Error opening DICT.REACTOR_RATIOS.'
|
||||
end
|
||||
end else
|
||||
ErrorMsg = 'Error in ':Service:' service. REACTOR, ':ReactorNo:', does not exist.'
|
||||
end
|
||||
end else
|
||||
ErrorMsg = 'Error in ':Service:' service. Null ReactorNo passed into service.'
|
||||
end
|
||||
|
||||
If ErrorMsg EQ '' then
|
||||
Response = CurrRatios
|
||||
end else
|
||||
Error_Services('Add', ErrorMsg)
|
||||
end
|
||||
|
||||
end service
|
||||
|
||||
|
||||
Service GetRatiosByReactorLog(ReactorLogId)
|
||||
|
||||
RatiosKey = ''
|
||||
Ratios = ''
|
||||
ErrorMsg = ''
|
||||
ReactorNo = ''
|
||||
If ReactorLogId NE '' then
|
||||
If RowExists('REACTOR_LOG', ReactorLogId) then
|
||||
Query = 'SELECT REACTOR_RATIOS WITH REACTOR_LOG_ID EQ ':Quote(ReactorLogId)
|
||||
Query := ' BY-DSND RATIO_SET_DTM'
|
||||
RList(Query, TARGET_ACTIVELIST$)
|
||||
ErrCode = ''
|
||||
If Not(Get_Status(ErrCode)) then
|
||||
If @RecCount GT 0 then
|
||||
ReadNext RatiosKey else
|
||||
ErrorMsg = 'Error in ':Service:' service. Error looking up reactor '
|
||||
ErrorMsg := 'ratios associated with REACTOR_LOG ':ReactorLogId:'.'
|
||||
end
|
||||
ClearSelect TARGET_ACTIVELIST$
|
||||
end
|
||||
end else
|
||||
ErrorMsg = 'Error in ':Service:' service. Error looking up reactor '
|
||||
ErrorMsg := 'ratios associated with REACTOR_LOG ':ReactorLogId:'.'
|
||||
end
|
||||
end else
|
||||
ErrorMsg = 'Error in ':Service:' service. REACTOR_LOG ':ReactorLogId:' does not exist.'
|
||||
end
|
||||
end else
|
||||
ErrorMsg = 'Error in ':Service:' service. Null ReactorLogId passed into service.'
|
||||
end
|
||||
|
||||
If ErrorMsg EQ '' then
|
||||
If RatiosKey NE '' then
|
||||
RatiosRec = Database_Services('ReadDataRow', 'REACTOR_RATIOS', RatiosKey)
|
||||
If Error_Services('NoError') then
|
||||
If ReactorNo EQ '' then ReactorNo = Xlate('REACTOR_LOG', ReactorLogId, 'REACTOR', 'X')
|
||||
If ReactorNo NE '' then
|
||||
NumRatios = Reactor_Services('GetNumRatios', ReactorNo)
|
||||
For RatioIndex = 0 to (NumRatios - 1)
|
||||
Ratios<0, RatioIndex + 1> = RatiosRec<REACTOR_RATIOS.RATIO_1$ + RatioIndex>
|
||||
Next RatioIndex
|
||||
end else
|
||||
ErrorMsg = 'Error in ':Service:' service. Null Reactor in REACTOR_LOG ':ReactorLogId:'.'
|
||||
end
|
||||
end else
|
||||
ErrorMsg = 'Error in ':Service:' service. Error reading REACTOR_RATIOS record ':RatiosKey:'.'
|
||||
end
|
||||
end
|
||||
end
|
||||
|
||||
If ErrorMsg EQ '' then
|
||||
Response = Ratios
|
||||
end else
|
||||
Error_Services('Add', ErrorMsg)
|
||||
end
|
||||
|
||||
end service
|
||||
|
||||
|
||||
Service GetInjectorSettingsByReactorLog(ReactorLogId)
|
||||
|
||||
ReactInjSetKey = ''
|
||||
InjSettings = ''
|
||||
ErrorMsg = ''
|
||||
If ReactorLogId NE '' then
|
||||
If RowExists('REACTOR_LOG', ReactorLogId) then
|
||||
Query = 'SELECT REACTOR_INJECTOR_SETTINGS WITH REACTOR_LOG_ID EQ ':Quote(ReactorLogId)
|
||||
Query := ' BY-DSND INJ_SET_DTM'
|
||||
RList(Query, TARGET_ACTIVELIST$)
|
||||
ErrCode = ''
|
||||
If Not(Get_Status(ErrCode)) then
|
||||
If @RecCount GT 0 then
|
||||
ReadNext ReactInjSetKey else
|
||||
ErrorMsg = 'Error in ':Service:' service. Error looking up reactor injector '
|
||||
ErrorMsg := 'settings associated with REACTOR_LOG ':ReactorLogId:'.'
|
||||
end
|
||||
ClearSelect TARGET_ACTIVELIST$
|
||||
end
|
||||
end else
|
||||
ErrorMsg = 'Error in ':Service:' service. Error looking up reactor injector '
|
||||
ErrorMsg := 'settings associated with REACTOR_LOG ':ReactorLogId:'.'
|
||||
end
|
||||
end else
|
||||
ErrorMsg = 'Error in ':Service:' service. REACTOR_LOG ':ReactorLogId:' does not exist.'
|
||||
end
|
||||
end else
|
||||
ErrorMsg = 'Error in ':Service:' service. Null ReactorLogId passed into service.'
|
||||
end
|
||||
|
||||
If ErrorMsg EQ '' then
|
||||
If ReactInjSetKey NE '' then
|
||||
ReactInjSetRec = Database_Services('ReadDataRow', 'REACTOR_INJECTOR_SETTINGS', ReactInjSetKey)
|
||||
If Error_Services('NoError') then
|
||||
For InjIndex = 0 to 4
|
||||
InjSettings<0, InjIndex + 1> = ReactInjSetRec<REACTOR_INJECTOR_SETTINGS.INJECTOR_1$ + InjIndex>
|
||||
Next InjIndex
|
||||
end else
|
||||
ErrorMsg = 'Error in ':Service:' service. Error reading REACTOR_INJECTOR_SETTINGS record ':ReactInjSetKey:'.'
|
||||
end
|
||||
end
|
||||
end
|
||||
|
||||
If ErrorMsg EQ '' then
|
||||
Response = InjSettings
|
||||
end else
|
||||
Error_Services('Add', ErrorMsg)
|
||||
end
|
||||
|
||||
end service
|
||||
|
||||
|
||||
Service SetNewInjectorSettings(ReactorNo, InjSettings)
|
||||
|
||||
// Injector settings should be passed in internal format (MD3)
|
||||
ErrorMsg = ''
|
||||
If ReactorNo NE '' then
|
||||
If RowExists('REACTOR', ReactorNo) then
|
||||
If InjSettings NE '' then
|
||||
If DCount(InjSettings, @VM) EQ 5 then
|
||||
For each InjSetting in InjSettings using @VM setting vPos
|
||||
If InjSettings EQ '' then ErrorMsg = 'Error in ':Service:' service. Injector setting ':vPos:' is missing.'
|
||||
Until ErrorMsg NE ''
|
||||
Next InjSetting
|
||||
If ErrorMsg EQ '' then
|
||||
CurrInjSettings = Reactor_Services('GetCurrentInjectorSettings', ReactorNo)
|
||||
If (CurrInjSettings NE InjSettings) then
|
||||
CurrRlId = Xlate('CONFIG', 'REACT_MODE':ReactorNo, 8, 'X')
|
||||
If CurrRlId NE '' then
|
||||
Query = 'REACTOR_NO':@VM:ReactorNo:@FM:'ACTIVE':@VM:True$:@FM
|
||||
Open 'DICT.REACTOR_INJECTOR_SETTINGS' to hDict then
|
||||
Option = 'E'
|
||||
ActiveInjSettingsKeys = ''
|
||||
Flag = ''
|
||||
Btree.Extract(Query, 'REACTOR_INJECTOR_SETTINGS', hDict, ActiveInjSettingsKeys, Option, Flag)
|
||||
If Flag EQ 0 then
|
||||
If ActiveInjSettingsKeys NE '' then
|
||||
Open 'REACTOR_INJECTOR_SETTINGS' to hTable then
|
||||
For each ActiveInjSettingsKey in ActiveInjSettingsKeys using @VM
|
||||
WriteV False$ on hTable, ActiveInjSettingsKey, REACTOR_INJECTOR_SETTINGS.ACTIVE$ else
|
||||
ErrorMsg = 'Error in ':Service:' service. Error setting previous injector '
|
||||
ErrorMsg := 'settings to inactive. File error: ':@File_Error
|
||||
end
|
||||
Until ErrorMsg NE ''
|
||||
Next ActiveInjSettingsKey
|
||||
end else
|
||||
ErrorMsg = 'Error in ':Service:' service. Error opening REACTOR_INJECTOR_SETTINGS to '
|
||||
ErrorMsg := 'invalidate previous settings.'
|
||||
end
|
||||
end
|
||||
If ErrorMsg EQ '' then
|
||||
NewInjSettingsKey = RTI_CreateGUID()
|
||||
If NewInjSettingsKey NE '' then
|
||||
NewInjSettingsRec = ''
|
||||
NewInjSettingsRec<REACTOR_INJECTOR_SETTINGS.REACTOR_LOG_ID$> = CurrRlId
|
||||
NewInjSettingsRec<REACTOR_INJECTOR_SETTINGS.REACTOR_NO$> = ReactorNo
|
||||
NewInjSettingsRec<REACTOR_INJECTOR_SETTINGS.INJ_SET_DTM$> = Datetime()
|
||||
NewInjSettingsRec<REACTOR_INJECTOR_SETTINGS.ACTIVE$> = True$
|
||||
For InjIndex = 0 to 4
|
||||
NewInjSettingsRec<REACTOR_INJECTOR_SETTINGS.INJECTOR_1$ + InjIndex> = InjSettings<0, InjIndex + 1>
|
||||
Next InjIndex
|
||||
Database_Services('WriteDataRow', 'REACTOR_INJECTOR_SETTINGS', NewInjSettingsKey, NewInjSettingsRec)
|
||||
If Error_Services('NoError') then
|
||||
plParms = 'REACT_STATE':@RM
|
||||
plParms := ReactorNo:@RM
|
||||
plParms := REACT_STATE_CURR_INJ_RL_ID$:@RM
|
||||
plParms := CurrRlId:@RM
|
||||
obj_Post_Log('Create',plParms)
|
||||
If Get_Status(ErrCode) then
|
||||
ErrorMsg = 'Error in ':Service:' service. Error calling obj_Post_Log("Create"). '
|
||||
ErrorMsg := 'Error code: ':ErrCode:'.'
|
||||
end
|
||||
end else
|
||||
ErrorMsg = Error_Services('GetMessage')
|
||||
end
|
||||
end else
|
||||
ErrorMsg = 'Error in ':Service:' service. Error creating new REACTOR_INJECTOR_SETTINGS record.'
|
||||
end
|
||||
end
|
||||
end else
|
||||
ErrorMsg = 'Error in ':Service:' service. Error calling Btree.Extract.'
|
||||
end
|
||||
end else
|
||||
ErrorMsg = 'Error in ':Service:' service. Error opening DICT.REACTOR_INJECTOR_SETTINGS'
|
||||
end
|
||||
end else
|
||||
ErrorMsg = 'Error in ':Service:' service. Error reading current REACTOR_LOG Id.'
|
||||
end
|
||||
end else
|
||||
ErrorMsg = 'Error in ':Service:' service. Input InjSettings are the same as the current InjSettings.'
|
||||
end
|
||||
end
|
||||
end else
|
||||
ErrorMsg = 'Error in ':Service:' service. All five injector settings are required.'
|
||||
end
|
||||
end else
|
||||
ErrorMsg = 'Error in ':Service:' service. Null InjSettings passed into service.'
|
||||
end
|
||||
end else
|
||||
ErrorMsg = 'Error in ':Service:' service. REACTOR, ':ReactorNo:', does not exist.'
|
||||
end
|
||||
end else
|
||||
ErrorMsg = 'Error in ':Service:' service. Null ReactorNo passed into service.'
|
||||
end
|
||||
|
||||
If ErrorMsg EQ '' then
|
||||
Response = True$
|
||||
end else
|
||||
Error_Services('Add', ErrorMsg)
|
||||
Response = False$
|
||||
end
|
||||
|
||||
end service
|
||||
|
||||
|
||||
Service SetNewRatios(ReactorNo, Ratios)
|
||||
|
||||
// Ratios should be passed in internal format (MD3)
|
||||
ErrorMsg = ''
|
||||
If ReactorNo NE '' then
|
||||
If RowExists('REACTOR', ReactorNo) then
|
||||
If Ratios NE '' then
|
||||
Ratios = SRP_Array('Clean', Ratios, 'Trim', @VM)
|
||||
NumRatios = Reactor_Services('GetNumRatios', ReactorNo)
|
||||
If Error_Services('NoError') then
|
||||
If DCount(Ratios, @VM) EQ NumRatios then
|
||||
For each Ratio in Ratios using @VM setting vPos
|
||||
Begin Case
|
||||
Case Ratio EQ ''
|
||||
ErrorMsg = 'Error in ':Service:' service. Ratio ':vPos:' is missing.'
|
||||
Case OConv(Ratio, 'MD3') LT 30
|
||||
ErrorMsg = 'Error in ':Service:' service. Invalid Ratio value. Ratio ':vPos:' is less than 30.'
|
||||
Case OConv(Ratio, 'MD3') GT 100
|
||||
ErrorMsg = 'Error in ':Service:' service. Invalid Ratio value. Ratio ':vPos:' is greater than 100.'
|
||||
End Case
|
||||
Until ErrorMsg NE ''
|
||||
Next Ratio
|
||||
If ErrorMsg EQ '' then
|
||||
CurrRatios = Reactor_Services('GetCurrentRatios', ReactorNo)
|
||||
If (CurrRatios NE Ratios) then
|
||||
CurrRlId = Xlate('CONFIG', 'REACT_MODE':ReactorNo, 8, 'X')
|
||||
If CurrRlId NE '' then
|
||||
Query = 'REACTOR_NO':@VM:ReactorNo:@FM:'ACTIVE':@VM:True$:@FM
|
||||
Open 'DICT.REACTOR_RATIOS' to hDict then
|
||||
Option = 'E'
|
||||
ActiveRatiosKeys = ''
|
||||
Flag = ''
|
||||
Btree.Extract(Query, 'REACTOR_RATIOS', hDict, ActiveRatiosKeys, Option, Flag)
|
||||
If Flag EQ 0 then
|
||||
If ActiveRatiosKeys NE '' then
|
||||
Open 'REACTOR_RATIOS' to hTable then
|
||||
For each ActiveRatiosKey in ActiveRatiosKeys using @VM
|
||||
WriteV False$ on hTable, ActiveRatiosKey, REACTOR_RATIOS.ACTIVE$ else
|
||||
ErrorMsg = 'Error in ':Service:' service. Error setting previous ratios '
|
||||
ErrorMsg := 'record to inactive. File error: ':@File_Error
|
||||
end
|
||||
Until ErrorMsg NE ''
|
||||
Next ActiveRatiosKey
|
||||
end else
|
||||
ErrorMsg = 'Error in ':Service:' service. Error opening REACTOR_RATIOS table to '
|
||||
ErrorMsg := 'invalidate previous ratios.'
|
||||
end
|
||||
end
|
||||
If ErrorMsg EQ '' then
|
||||
NewRatiosKey = RTI_CreateGUID()
|
||||
If NewRatiosKey NE '' then
|
||||
NewRatiosRec = ''
|
||||
NewRatiosRec<REACTOR_RATIOS.REACTOR_LOG_ID$> = CurrRlId
|
||||
NewRatiosRec<REACTOR_RATIOS.REACTOR_NO$> = ReactorNo
|
||||
NewRatiosRec<REACTOR_RATIOS.RATIO_SET_DTM$> = Datetime()
|
||||
NewRatiosRec<REACTOR_RATIOS.ACTIVE$> = True$
|
||||
For RatioIndex = 0 to (NumRatios - 1)
|
||||
NewRatiosRec<REACTOR_RATIOS.RATIO_1$ + RatioIndex> = Ratios<0, RatioIndex + 1>
|
||||
Next RatioIndex
|
||||
Database_Services('WriteDataRow', 'REACTOR_RATIOS', NewRatiosKey, NewRatiosRec)
|
||||
If Error_Services('NoError') then
|
||||
plParms = 'REACT_STATE':@RM
|
||||
plParms := ReactorNo:@RM
|
||||
plParms := REACT_STATE_CURR_RATIO_RL_ID$:@RM
|
||||
plParms := CurrRlId:@RM
|
||||
obj_Post_Log('Create',plParms)
|
||||
If Get_Status(ErrCode) then
|
||||
ErrorMsg = 'Error in ':Service:' service. Error calling obj_Post_Log("Create"). '
|
||||
ErrorMsg = 'Error code: ':ErrCode:'.'
|
||||
end
|
||||
end else
|
||||
ErrorMsg = Error_Services('GetMessage')
|
||||
end
|
||||
end else
|
||||
ErrorMsg = 'Error in ':Service:' service. Error creating new REACTOR_RATIOS record.'
|
||||
end
|
||||
end
|
||||
end else
|
||||
ErrorMsg = 'Error in ':Service:' service. Error calling Btree.Extract.'
|
||||
end
|
||||
end else
|
||||
ErrorMsg = 'Error in ':Service:' service. Error opening DICT.REACTOR_RATIOS'
|
||||
end
|
||||
end else
|
||||
ErrorMsg = 'Error in ':Service:' service. Error reading current REACTOR_LOG Id.'
|
||||
end
|
||||
end else
|
||||
ErrorMsg = 'Error in ':Service:' service. Input Ratios are the same as the current Ratios.'
|
||||
end
|
||||
end
|
||||
end else
|
||||
ErrorMsg = 'Error in ':Service:' service. Reactor ':ReactorNo:' requires ':NumRatios:' values '
|
||||
ErrorMsg := 'for ratios. Only ':DCount(Ratios, @VM):' were supplied.'
|
||||
end
|
||||
end else
|
||||
ErrorMsg = 'Error in ':Service:' service. Error determining number of required ratios '
|
||||
ErrorMsg := 'for reactor ':ReactorNo:'. Error message: ':Error_Services("GetMessage")
|
||||
end
|
||||
end else
|
||||
ErrorMsg = 'Error in ':Service:' service. Null Ratios passed into service.'
|
||||
end
|
||||
end else
|
||||
ErrorMsg = 'Error in ':Service:' service. REACTOR, ':ReactorNo:', does not exist.'
|
||||
end
|
||||
end else
|
||||
ErrorMsg = 'Error in ':Service:' service. Null ReactorNo passed into service.'
|
||||
end
|
||||
|
||||
If ErrorMsg EQ '' then
|
||||
Response = True$
|
||||
end else
|
||||
Error_Services('Add', ErrorMsg)
|
||||
Response = False$
|
||||
end
|
||||
|
||||
end service
|
||||
|
||||
|
||||
Service GetNumRatios(ReactorNo)
|
||||
|
||||
ErrorMsg = ''
|
||||
NumRatios = ''
|
||||
If (ReactorNo NE '') then
|
||||
If RowExists('REACTOR', ReactorNo) then
|
||||
ReactorType = Xlate('REACTOR', ReactorNo, REACTOR_REACT_TYPE$, 'X')
|
||||
Begin Case
|
||||
Case ReactorNo EQ 73
|
||||
// OpenInsight needs to be updated to support reactor type HTR+, which requires 16 ratios.
|
||||
NumRatios = 16
|
||||
Case ReactorType EQ 'ASM' or ReactorType EQ 'ASM+'
|
||||
NumRatios = 10
|
||||
Case ReactorType EQ 'HTR'
|
||||
NumRatios = 12
|
||||
Case Otherwise$
|
||||
ErrorMsg = 'Error in ':Service:' service. Error determining number '
|
||||
ErrorMsg := 'of Ratios required for reactor ':ReactorNo:'.'
|
||||
End Case
|
||||
end else
|
||||
ErrorMsg = 'Error in ':Service:' service. REACTOR, ':ReactorNo:', does not exist.'
|
||||
end
|
||||
end else
|
||||
ErrorMsg = 'Error in ':Service:' service. Null ReactorNo passed into service.'
|
||||
end
|
||||
|
||||
If ErrorMsg EQ '' then
|
||||
Response = NumRatios
|
||||
end else
|
||||
Error_Services('Add', ErrorMsg)
|
||||
end
|
||||
|
||||
end service
|
||||
|
||||
////////////////////////////////////////////////////////////////////////////////////////////////////////////////////////
|
||||
// Internal GoSubs
|
||||
////////////////////////////////////////////////////////////////////////////////////////////////////////////////////////
|
||||
|
@ -6,13 +6,13 @@ COMPILE FUNCTION REACT_STATE(EntID,Event,Parm1,Parm2,Parm3,Parm4,Parm5)
|
||||
10/8/2009 - John C. Henry, J.C. Henry & Co., Inc.
|
||||
*/
|
||||
|
||||
DECLARE SUBROUTINE Set_Property, ErrMsg, obj_AppWindow
|
||||
|
||||
DECLARE FUNCTION Get_Property, Send_Message, Start_Window
|
||||
DECLARE SUBROUTINE Set_Property, ErrMsg, obj_AppWindow, Error_Services
|
||||
DECLARE FUNCTION Get_Property, Send_Message, Start_Window, Reactor_Services, Error_Services
|
||||
|
||||
$INSERT APPCOLORS
|
||||
$INSERT LOGICAL
|
||||
$INSERT REACT_STATE_EQUATES
|
||||
|
||||
$INSERT POPUP_EQUATES
|
||||
|
||||
EQU CRLF$ TO \0D0A\
|
||||
EQU TAB$ TO \09\
|
||||
@ -24,6 +24,8 @@ EQU COL$RI_SERIAL_NO TO 4
|
||||
EQU COL$RI_INST_DTM TO 5
|
||||
EQU COL$RI_RL_NO TO 6
|
||||
|
||||
Equ POPUP_WHITE$ to 15400411
|
||||
Equ POPUP_GREEN$ to 16777215
|
||||
|
||||
ErrTitle = 'Error in REACT_STATE commuter module'
|
||||
ErrorMsg = ''
|
||||
@ -31,27 +33,29 @@ 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 = 'WRITE' ; GOSUB Write
|
||||
CASE Event = 'READ' ; GOSUB Read
|
||||
CASE Event[1,3] = 'QBF' ; GOSUB Refresh
|
||||
END CASE
|
||||
|
||||
CASE EntID = @WINDOW:'.CURR_RI_TYPE' AND Event = 'DBLCLK' ; GOSUB ReactItemDC
|
||||
|
||||
CASE 1
|
||||
|
||||
ErrorMsg = 'Unknown Parameters ':EntID:' - ':Event:' passed to commuter'
|
||||
ErrMsg('Application Message':@SVM:ErrorMsg)
|
||||
|
||||
CASE EntID = @WINDOW
|
||||
BEGIN CASE
|
||||
CASE Event = 'CLEAR' ; GoSub Clear
|
||||
CASE Event = 'CREATE' ; GoSub Create
|
||||
CASE Event = 'CLOSE' ; GoSub Close
|
||||
CASE Event = 'WRITE' ; GoSub Write
|
||||
CASE Event = 'READ' ; GoSub Read
|
||||
CASE Event[1,3] = 'QBF' ; GoSub Refresh
|
||||
END CASE
|
||||
|
||||
CASE EntID = @WINDOW:'.CURR_RI_TYPE' AND Event = 'DBLCLK' ; GoSub ReactItemDC
|
||||
CASE EntId = @Window:'.PUB_INJECTOR_SETTING_HISTORY' and Event = 'CLICK' ; GoSub DisplayInjectorHistory
|
||||
Case EntId = @Window:'.PUB_RATIO_HISTORY' and Event = 'CLICK' ; GoSub DisplayRatioHistory
|
||||
|
||||
CASE Otherwise$
|
||||
|
||||
ErrorMsg = 'Unknown Parameters ':EntID:' - ':Event:' passed to commuter'
|
||||
ErrMsg('Application Message':@SVM:ErrorMsg)
|
||||
|
||||
END CASE
|
||||
|
||||
IF ErrorMsg NE '' THEN
|
||||
ErrMsg(ErrTitle:@SVM:ErrorMsg)
|
||||
ErrMsg(ErrTitle:@SVM:ErrorMsg)
|
||||
END
|
||||
|
||||
RETURN Result
|
||||
@ -61,17 +65,17 @@ RETURN Result
|
||||
* * * * * * *
|
||||
Create:
|
||||
* * * * * * *
|
||||
|
||||
obj_Appwindow('Create',@WINDOW)
|
||||
|
||||
|
||||
obj_Appwindow('Create',@WINDOW)
|
||||
|
||||
RETURN
|
||||
|
||||
|
||||
* * * * * * *
|
||||
Write:
|
||||
* * * * * * *
|
||||
|
||||
|
||||
|
||||
|
||||
RETURN
|
||||
|
||||
|
||||
@ -79,101 +83,173 @@ RETURN
|
||||
* * * * * * *
|
||||
Clear:
|
||||
* * * * * * *
|
||||
|
||||
*Send_Event(@WINDOW,'PAGE',1)
|
||||
|
||||
GOTO Refresh
|
||||
|
||||
|
||||
GOTO Refresh
|
||||
|
||||
RETURN
|
||||
|
||||
* * * * * * *
|
||||
Read:
|
||||
* * * * * * *
|
||||
|
||||
|
||||
|
||||
|
||||
|
||||
|
||||
|
||||
|
||||
* * * * * * *
|
||||
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,LS2_GREEN$)
|
||||
NEXT N
|
||||
END
|
||||
NEXT I
|
||||
NEXT I
|
||||
|
||||
|
||||
* 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 I
|
||||
NEXT I
|
||||
|
||||
ReactNo = Get_Property(@Window:'.REACT_NO', 'TEXT')
|
||||
If ReactNo NE '' then
|
||||
// Populate Current Injector Settings and Current Reactor Ratios
|
||||
InjSettings = OConv(Reactor_Services('GetCurrentInjectorSettings', ReactNo), 'MD3,')
|
||||
Set_Property(@Window:'.EDT_CURR_INJ_SETTINGS', 'ARRAY', InjSettings)
|
||||
Ratios = OConv(Reactor_Services('GetCurrentRatios', ReactNo), 'MD3,')
|
||||
Set_Property(@Window:'.EDT_CURR_RATIOS', 'ARRAY', Ratios)
|
||||
NumRatios = Reactor_Services('GetNumRatios', ReactNo)
|
||||
If Error_Services('NoError') then
|
||||
Set_Property(@Window:'.EDT_CURR_RATIOS', 'MINROWLIMIT', NumRatios)
|
||||
Set_Property(@Window:'.EDT_CURR_RATIOS', 'MAXROWLIMIT', NumRatios)
|
||||
end
|
||||
end
|
||||
|
||||
RETURN
|
||||
|
||||
|
||||
* * * * * * *
|
||||
ReactItemDC:
|
||||
* * * * * * *
|
||||
|
||||
CurrPos = Get_Property(EntID,'SELPOS')
|
||||
CurrCol = CurrPos<1>
|
||||
CurrRow = CurrPos<2>
|
||||
|
||||
CurrList = Get_Property(EntID,'LIST')
|
||||
|
||||
BEGIN CASE
|
||||
CASE CurrCol = COL$RI_NO
|
||||
RINo = CurrList<CurrRow,COL$RI_NO>
|
||||
IF RINo NE '' THEN
|
||||
obj_AppWindow('ViewRelated','REACT_ITEM':@RM:RINo)
|
||||
END
|
||||
|
||||
CASE CurrCol = COL$RI_RL_NO
|
||||
RLNo = CurrList<CurrRow,COL$RI_RL_NO>
|
||||
IF RLNo NE '' THEN
|
||||
Dummy = Start_Window( 'REACTOR_LOG', @WINDOW, RLNo:'*CENTER', '', '' )
|
||||
END
|
||||
|
||||
END CASE
|
||||
|
||||
|
||||
CurrPos = Get_Property(EntID,'SELPOS')
|
||||
CurrCol = CurrPos<1>
|
||||
CurrRow = CurrPos<2>
|
||||
|
||||
CurrList = Get_Property(EntID,'LIST')
|
||||
|
||||
BEGIN CASE
|
||||
CASE CurrCol = COL$RI_NO
|
||||
RINo = CurrList<CurrRow,COL$RI_NO>
|
||||
IF RINo NE '' THEN
|
||||
obj_AppWindow('ViewRelated','REACT_ITEM':@RM:RINo)
|
||||
END
|
||||
|
||||
CASE CurrCol = COL$RI_RL_NO
|
||||
RLNo = CurrList<CurrRow,COL$RI_RL_NO>
|
||||
IF RLNo NE '' THEN
|
||||
Dummy = Start_Window( 'REACTOR_LOG', @WINDOW, RLNo:'*CENTER', '', '' )
|
||||
END
|
||||
|
||||
END CASE
|
||||
|
||||
RETURN
|
||||
|
||||
|
||||
* * * * * * *
|
||||
Close:
|
||||
* * * * * * *
|
||||
|
||||
|
||||
|
||||
|
||||
|
||||
|
||||
RETURN
|
||||
|
||||
|
||||
* * * * * * * * * * * *
|
||||
DisplayInjectorHistory:
|
||||
* * * * * * * * * * * *
|
||||
|
||||
ReactNo = Get_Property(@Window:'.REACT_NO','DEFPROP')
|
||||
If ReactNo NE '' then
|
||||
TypeOver = ''
|
||||
TypeOver<PDISPLAY$> = 'WITH REACTOR_NO = ':ReactNo:' BY-DSND INJ_SET_DTM'
|
||||
void = Popup(@Window,TypeOver,'REACT_INJ_SETTINGS')
|
||||
end
|
||||
|
||||
return
|
||||
|
||||
|
||||
* * * * * * * * * * * *
|
||||
DisplayRatioHistory:
|
||||
* * * * * * * * * * * *
|
||||
|
||||
ReactNo = Get_Property(@Window:'.REACT_NO','DEFPROP')
|
||||
If ReactNo NE '' then
|
||||
NumRatios = Reactor_Services('GetNumRatios', ReactNo)
|
||||
If Error_Services('NoError') then
|
||||
DisplayText = 'WITH REACTOR_NO EQ ':ReactNo:' BY-DSND RATIO_SET_DTM':@vm:''
|
||||
PopupRec = ""
|
||||
PopupRec<PFILE$> = "REACTOR_RATIOS"
|
||||
PopupRec<PDISPLAY$> = DisplayText
|
||||
PopupRec<PFORMAT$> = 'REACTOR_NO':@svm:'6':@svm:'C':@svm:'C':@svm:'MD0':@svm:'Reactor No'
|
||||
PopupRec<PFORMAT$, -1> = 'RATIO_SET_DTM':@svm:'16':@svm:'C':@svm:'C':@svm:'DT/^S':@svm:'Ratio Set Dtm'
|
||||
For RatioIndex = 1 to NumRatios
|
||||
PopupRec<PFORMAT$, -1> = 'RATIO_':RatioIndex:@svm:'7':@svm:'C':@svm:'C':@svm:'MD3,':@svm:'Ratio ':RatioIndex
|
||||
Next RatioIndex
|
||||
PopupRec<PMODE$> = 'T'
|
||||
PopupRec<PSELECT$> = True$
|
||||
PopupRec<PTITLE$> = 'Reactor Ratios'
|
||||
PopupRec<PFIELD$> = True$
|
||||
PopupRec<PTYPE$> = "F"
|
||||
PopupRec<PCOLHDR$> = True$
|
||||
PopupRec<PROWNUM$> = True$
|
||||
PopupRec<PROWBTN$> = True$
|
||||
PopupRec<PHGRID$> = True$
|
||||
PopupRec<PVGRID$> = True$
|
||||
PopupRec<PRESIZE$> = True$
|
||||
PopupRec<PBORDER$> = True$
|
||||
PopupRec<PBTNSBELOW$> = False$
|
||||
PopupRec<PSEARCH$> = False$
|
||||
PopupRec<PSORT$> = False$
|
||||
PopupRec<PLOCK$> = False$
|
||||
PopupRec<PSHOWMISSING$> = False$
|
||||
PopupRec<PPRINTABLE$> = True$
|
||||
PopupRec<PSHOWGAUGE$> = False$
|
||||
PopupRec<PCAPTUREESC$> = False$
|
||||
PopupRec<PGREENBAR$> = True$
|
||||
PopupRec<PODDROWCOLOR$> = POPUP_WHITE$
|
||||
PopupRec<PEVENROWCOLOR$> = POPUP_GREEN$
|
||||
Response = Popup(@Window, PopupRec, '')
|
||||
end else
|
||||
Error_Services('DisplayError')
|
||||
end
|
||||
end else
|
||||
Error_Services('Add', "Reactor number is missing")
|
||||
Error_Services('DisplayError')
|
||||
end
|
||||
|
||||
return
|
||||
|
||||
|
||||
|
Reference in New Issue
Block a user