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

443 lines
16 KiB
Plaintext

COMPILE FUNCTION LSL_MAIN2(EntID,Event,Parm1,Parm2,Parm3,Parm4,Parm5)
#pragma precomp SRP_PreCompiler
/*
Commuter module for System Menu (LSL_MAIN2) dialog window
10/16/2009 - John C. Henry, J.C. Henry & Co., Inc.
*/
DECLARE SUBROUTINE Set_Property, End_Dialog, Send_Event, Set_Status, Get_BMP_Info, obj_Notes_Sent, obj_Tool_Log, RList
DECLARE SUBROUTINE ErrMsg, Send_Message, Set_Property, Send_Event, obj_AppWindow, Database_Services, obj_React_Status
DECLARE SUBROUTINE obj_Notes, Security_Err_Msg, End_Window, obj_Tables, Start_Window, SRP_JSON, Next_Key, obj_React_Mode
Declare subroutine RTP27
DECLARE FUNCTION Get_Property, Get_Status, Dialog_Box, obj_Tables, obj_Install, Reactor_Services, Database_Services
DECLARE FUNCTION Send_Message, Msg, Security_Check, obj_Notes_Sent, FindWindow, ShowWindow, MemberOf, SRP_JSON, Next_Key
Declare function Error_Services, obj_Tool, Messaging_Services
$INSERT LSL_COMMON
$INSERT LSL_USERS_EQU
$INSERT QUOTE_SIGS_EQU
$INSERT MSG_EQUATES
$INSERT APPCOLORS
$insert LOGICAL
$insert REACT_MODE_EQU
$insert REACT_UTIL_EQU
$insert WO_LOG_EQUATES
$insert REACTOR_CHILD_KEY_IDS_EQUATES
$INSERT TOOL_EQUATES
$insert RLIST_EQUATES
EQU X_OFF$ TO 1
EQU Y_OFF$ TO 2
EQU WIDTH$ TO 3
EQU HEIGHT$ TO 4
EQU CRLF$ TO \0D0A\
EQU TAB$ TO \09\
ErrTitle = 'Error in LSL_MAIN2 commuter module.'
ErrorMsg = ''
Result = ''
BEGIN CASE
CASE EntID = @WINDOW
BEGIN CASE
CASE Event = 'CREATE' ; GOSUB Create
CASE Event = 'CLOSE' ; GOSUB Close
CASE Event = 'TIMER' ; GOSUB Timer
CASE 1
ErrorMsg = 'Unknown Parameters ':EntID:' - ':Event:' passed to commuter'
ErrMsg(ErrorMsg)
END CASE
Case EntID _EQC @Window : '.OLE_DIRECT_CONNECT'
Begin Case
Case Parm1 _EQC 'OnMessage'
GoSub OLE_DIRECT_CONNECTION.OnMessage
End Case
CASE Event = 'MENU'
BEGIN CASE
CASE EntID = 'LSL_MAIN2.MENU.PROD.REACT_STAT' ; GOSUB MenuReactStatus
CASE EntID = 'LSL_MAIN2.MENU.MAINT.REACT_STAT' ; GOSUB MenuMaintReactStatus
CASE EntID = 'LSL_MAIN2.MENU.WIN.PROD.RMC' ; GOSUB MenuProdRMC
CASE EntID = 'LSL_MAIN2.MENU.ADMIN.TOOLS_EVAC' ; GOSUB LSL_MAIN2.MENU.ADMIN.TOOLS_EVAC
END CASE
CASE 1
ErrorMsg = 'Unknown Parameters ':EntID:' - ':Event:' passed to commuter'
ErrMsg(ErrorMsg)
END CASE
IF ErrorMsg NE '' THEN
ErrMsg(ErrTitle:@SVM:ErrorMsg)
END
RETURN Result
* * * * * * *
Create:
* * * * * * *
IF @USERNAME = 'INDEXER' THEN
Start_Window( 'IDXSVR', @window, '', '', '' )
Result = 0
RETURN
END
IF @USERNAME = 'VISION' THEN
Start_Window( 'VISION_COMM', @WINDOW, '', '', '' )
Result = 0
RETURN
END
IF @USERNAME = 'ADCSVR' THEN
Start_Window( 'ADCSVR', @WINDOW, '', '', '' )
Result = 0
RETURN
END
Set_Property(@WINDOW,'TIMER',1000:@FM:1)
Set_Property(@WINDOW,'STATUSLINE',@WINDOW:'.STATUS_LINE') ;* Setup status line
IF @USER4 = '' THEN @USER4 = @USERNAME
obj_Appwindow('Create')
* Added by JCH on 7/18/2004
GraphicPath = obj_Install('Get_Prop','ColorBMP')
IF GraphicPath NE '' THEN
Set_Property(@WINDOW:'.BITMAP_2','BITMAP',GraphicPath)
Get_BMP_Info(GraphicPath,BmSize,BmWidth,BmHeight)
MainSize = Get_Property(@WINDOW, 'SIZE')
WinWidth = MainSize<WIDTH$>
WinHeight = MainSize<HEIGHT$>
IF BmHeight > INT(WinHeight * .666) THEN
Set_Property(@WINDOW:'.BITMAP_2','IMAGECLIP',0) ;* Allow Resize of bitmap
BmDispHeight = INT(WinHeight * .666)
BmDispWidth = INT(BmDispHeight*(BmWidth/BmHeight))
END ELSE
BmDispHeight = WinHeight
BmDispWidth = WinWidth
END
Xorg = INT((WinWidth - BmDispWidth) / 2 )
Yorg = INT((WinHeight - BmDispHeight) / 3)
Set_Property(@WINDOW:'.BITMAP_2','SIZE',Xorg:@FM:Yorg:@FM:BmDispWidth:@FM:BmDispHeight)
Set_Property(@WINDOW:'.BITMAP_2','VISIBLE',1)
END
Company = obj_Install('Get_Prop','CompTitle')
WinTitle = Get_Property(@WINDOW,'TEXT')
Set_Property(@WINDOW,'TEXT',Company:' ':WinTitle)
Set_Property(@WINDOW:'.CURRENT_USER','TEXT','User: ':OCONV( @USER4, '[XLATE_CONV,LSL_USERS*FIRST_LAST]' ))
Set_Property(@WINDOW:'.OLE_PIC_CURRENT_USER','OLE.Caption','User: ':OCONV( @USER4, '[XLATE_CONV,LSL_USERS*FIRST_LAST]' ))
Set_Property(@WINDOW:'.CURRENT_DATE','TEXT','Date: ':OCONV( DATE(), 'D2/' ))
Set_Property(@WINDOW:'.GROUP_1','VISIBLE',1)
NotesSent = obj_Notes_Sent('GetUserKeys',@USER4)
NewMessages = XLATE('NOTE_PTRS',@USER4,'NEW_MESSAGES','X')
ShowPTO = XLATE('APP_INFO', 'MATERIAL_SCAN_FORM_SHOW', 1, 'X')
IF NotesSent NE '' OR NewMessages > 0 THEN
Start_Window( 'NOTE_PTRS', @WINDOW, '*CENTER', '', '' )
END
If ShowPTO NE '1' then
Set_Property(@WINDOW:'.MENU.MATERIAL.MATERIAL_SCAN','VISIBLE',0)
end
IF MemberOf(@USER4, 'OI_ADMIN') THEN
Set_Property(@WINDOW:'.MENU.ADMIN.MGMT','ENABLED',1)
END ELSE
Set_Property(@WINDOW:'.MENU.ADMIN.MGMT','ENABLED',0)
END
IF MemberOf(@USER4, 'OI_ADMIN') OR MemberOf(@USER4, 'OI_SUPERUSER') THEN
Set_Property(@WINDOW:'.MENU.PROD.REACTOR_RUN','ENABLED',1)
END ELSE
Set_Property(@WINDOW:'.MENU.PROD.REACTOR_RUN','ENABLED',0)
END
CalEngSigners = xlate( 'CONFIG', 'QUOTE_SIGS', F4PPOutSpecNotif$, 'X' )
LOCATE @USER4 IN CalEngSigners USING @VM SETTING POS THEN
Start_Window('SET_REMIND_CALIB',@WINDOW,'AUTO*CENTER')
END
IF @ADMIN < 2 THEN
hWnd1% = FindWindow("RTI_OINSIGHT":\00\, "")
hWnd2% = FindWindow("AREV":\00\, "")
hWnd3% = FindWindow("PROGMAN":\00\, "")
rv = ShowWindow(hWnd1%, 0)
rv = ShowWindow(hWnd2%, 0)
rv = ShowWindow(hWnd3%, 2)
END
RETURN
* * * * * * *
Close:
* * * * * * *
Set_Property(@WINDOW,'TIMER','')
UNLOCK All
Result = 1
RETURN
* * * * * * *
Timer:
* * * * * * *
Set_Property(@WINDOW:'.CURRENT_TIME','TEXT','Current Time: ':OCONV( TIME(), 'MTHS' ))
Set_Property(@WINDOW:'.CURRENT_DATE','TEXT','Date: ':OCONV( DATE(), 'D2/' ))
If Get_Property(@Window, '@CLOSE') then
Send_Event(@Window, 'CLOSE')
end
RETURN
* * * * * * *
Size:
* * * * * * *
RETURN
* * * * * * *
MenuReactStatus:
* * * * * * *
Start_Window('WO_DAILY_SCHED_ALL2',@WINDOW,'')
Start_Window('WO_DAILY_SCHED_ALL',@WINDOW,'')
Start_Window('TOOL_STATUS',@WINDOW,'')
RETURN
* * * * * * *
MenuMaintReactStatus:
* * * * * * *
Start_Window('WO_DAILY_SCHED_ALL2',@WINDOW,'')
Start_Window('WO_DAILY_SCHED_ALL',@WINDOW,'')
RETURN
* * * * * * *
MenuProdRMC:
* * * * * * *
DECLARE FUNCTION MemberOf, msg, Start_Window
IF MemberOf(@USER4, 'DATA_ENTRY') OR MemberOf(@USER4, 'SUPERVISOR') THEN
void = Start_Window('REACT_MODE_CHG', @WINDOW, '*CENTER','','')
END ELSE
MsgInfo = ''
MsgInfo<MCOL$> = -2
MsgInfo<MROW$> = -2
MsgInfo<MTEXT$> = 'You must be a Supervisor or Technician in order to change reactor modes...'
MsgInfo<MICON$> = 'H'
void = Msg('',MsgInfo)
END
RETURN 0
LSL_MAIN2.MENU.ADMIN.TOOLS_EVAC:
// Require the user to acknowledge using their application password.
* Valid = Dialog_Box('QUOTE_SIG_PWD_ENTRY', @WINDOW, @USER4 : @VM : XLATE('LSL_USERS', @USER4, LSL_USERS_PASSWORD$, 'X'))
MsgOverride = ''
MsgOverride<MDEFBTN$> = 2 ; // Default to Cancel button.
Valid = Msg(@Window, MsgOverride, 'OK_CANCEL', '', 'Evac Procedures' : @FM : 'Please confirm that you wish to put all tools into Evac mode.')
If Valid EQ '' then
UserName = Oconv(@USER4, '[XLATE_CONV,LSL_USERS*FIRST_LAST]')
CurrDate = Date()
CurrTime = Time()
EvacMode = 'Facilities (UnSched)'
EvacNotes = 'Fab Evac'
NumberTools = 0
// Step 1 - Update the Reactor Tools. This logic is based on the script event handler in the REACT_MODE_CHG.APPLY
// pushbutton control.
ReactorNos = Reactor_Services('GetReactorNumbers')
For Each ReactorNo in ReactorNos using @FM
ReactModeRow = Database_Services('ReadDataRow', 'CONFIG', 'REACT_MODE' : ReactorNo)
ReactModeDesc = ReactModeRow<Mode$>
If ReactModeDesc _NEC 'Shutdown' then
ReactUtilID = ReactModeRow<ReactUtilID$>
ReactLogID = ReactModeRow<ReactorLogID$>
If ReactUtilID NE '' then
ReactUtilRow = Database_Services('ReadDataRow', 'REACT_UTIL', ReactUtilID)
ReactUtilRow<REACT_UTIL_END_DATE$> = CurrDate
ReactUtilRow<REACT_UTIL_END_TIME$> = CurrTime
ReactUtilRow<REACT_UTIL_MODE_FINISH_USER$> = @USER4
Database_Services('WriteDataRow', 'REACT_UTIL', ReactUtilID, ReactUtilRow, True$, '', True$)
end else
ReactUtilRow = ''
end
hReactUtil = Database_Services('GetTableHandle', 'REACT_UTIL')
KeyToUse = Next_Key('REACT_UTIL', hReactUtil, 'NEXT', '')
NewReactUtilRow = ''
NewReactUtilRow<REACT_UTIL_REACTOR$> = ReactorNo
NewReactUtilRow<REACT_UTIL_NOTES$> = EvacNotes
NewReactUtilRow<REACT_UTIL_MODE$> = 'S'
NewReactUtilRow<REACT_UTIL_START_DATE$> = CurrDate
NewReactUtilRow<REACT_UTIL_START_TIME$> = CurrTime
NewReactUtilRow<REACT_UTIL_MODE_START_USER$> = @USER4
WorkOrderNo = ReactUtilRow<REACT_UTIL_WO$>
NewReactUtilRow<REACT_UTIL_WO$> = WorkOrderNo
NewReactUtilRow<REACT_UTIL_CUST_NO$> = Xlate('WO_LOG', WorkOrderNo, WO_LOG_CUST_NO$, 'X')
NewReactUtilRow<REACT_UTIL_REACTOR_LOG_ID$> = ''
Database_Services('WriteDataRow', 'REACT_UTIL', KeyToUse, NewReactUtilRow, True$, '', True$)
Database_Services('ReleaseKeyIDLock', 'REACT_UTIL', KeyToUse)
Next_Key('REACT_UTIL', HReactUtil, 'UPDATE', KeyToUse)
NewReactModeRow = ''
NewReactModeRow<Mode$> = EvacMode
NewReactModeRow<Username$> = UserName
NewReactModeRow<Date$> = Oconv(CurrDate, 'D4/')
NewReactModeRow<Time$> = Oconv(CurrTime, 'MTH')
NewReactModeRow<ReactUtilID$> = KeyToUse
NewReactModeRow<ReactorLogID$> = ''
NewReactModeRow<Note$> = EvacNotes
CurrDTM = NewReactModeRow<Date$> : ' ' : NewReactModeRow<Time$>
PrevModeKey = Xlate('REACTOR_CHILD_KEY_IDS', ReactorNo, REACTOR_CHILD_KEY_IDS_REACT_MODE_KEY_IDS$, 'X')<1, 1>
OpenDTM = Field(PrevModeKey, '*', 2)
OpenDTM = Oconv(OpenDTM, 'DT4/^S')
CurrMode = Oconv(Xlate('REACTOR', ReactorNo, 'CURR_MODE', 'X'), '[REACT_MODE_CONV]')
ProdModes = 'Production':@VM
ProdModes := 'Production (incr sampling)'
Locate CurrMode in ProdModes Using @VM Setting vPos then
Locate EvacMode in ProdModes Using @VM Setting vPos else
OutOfProdDTM = NewReactModeRow<Date$> : ' ' : NewReactModeRow<Time$>
obj_React_Status('SetOutOfProdDTM', ReactorNo : @RM : OutOfProdDTM)
end ; // End of check on New Mode
end ; // End of check on Current Mode
Database_Services('WriteDataRow', 'CONFIG', 'REACT_MODE' : ReactorNo, NewReactModeRow, True$, '', True$)
If Error_Services('NoError') then
NumberTools += 1
If CurrMode NE '' then
// Close the currently active mode
crParms = ReactorNo
crParms := @RM : OpenDTM
crParms := @RM : CurrDTM
crParms := @RM : @USER4
crParms := @RM : NewReactModeRow<Note$>
crParms := @RM : NewReactModeRow<ReactUtilID$>
crParms := @RM : NewReactModeRow<ReactorLogID$>
obj_React_Mode('Close', crParms)
end
// Create new active mode record
crParms = ReactorNo
crParms := @RM : CurrDTM
crParms := @RM : @USER4
crParms := @RM : NewReactModeRow<Mode$>
crParms := @RM : NewReactModeRow<Note$>
crParms := @RM : NewReactModeRow<ReactUtilID$>
crParms := @RM : NewReactModeRow<ReactorLogID$>
obj_React_Mode('Create', crParms)
end
end
Next ReactorNo
// Step 2 - Update the Silicon Tools. This logic is based on the TBClick gosub in the Comm_Dialog_Tool_Status
// commuter module. This commuter module supports the TOOL_STATUS form.
ToolIDs = obj_Tool('KeysByType') ; // All tool IDs sorted by TOOL_TYPE
For Each ToolID in ToolIDs using @VM
ToolRow = Database_Services('ReadDataRow', 'TOOL', ToolID)
CurrModeKey = ToolRow<TOOL_CURR_MODE_KEY$>
CurrMode = Xlate('TOOL', ToolID, 'CURR_MODE', 'X')<1, 1>
If CurrMode NE 'OUT' AND CurrMode NE 'FACILITIES (UnSched)' then
If CurrMode EQ '' then
obj_Tool_Log('InitialLog', ToolID)
CurrMode = 'OUT'
end
NumberTools += 1
CurrModeDTM = Field(CurrModeKey, '*', 2)
CurrModeDTM = Oconv(CurrModeDTM, 'DT4/^S')
Parms = ToolID : @RM
Parms := CurrModeDTM : @RM
Parms := 'FACILITIES (UnSched)' : @RM
Parms := EvacNotes
obj_Tool_Log('SetMode', Parms)
end
Next ToolID
// Step 3 - Update the GaN Tools. This logic is based on the ToolOptions gosub in the GaN_Tool_Status commuter
// module. This commuter module supports the GAN_TOOL_STATUS form.
SelectSent = 'SELECT TOOL WITH TOOL_PROC "G" AND WITH CLASS NE "G_REACT" BY TOOL_WH BY TOOL_TYPE'
RList(SelectSent, TARGET_ACTIVELIST$, '', '', '')
EOF = False$
Loop
Readnext ToolID else EOF = True$
Until EOF
ToolRow = Database_Services('ReadDataRow', 'TOOL', ToolID)
CurrModeKey = ToolRow<TOOL_CURR_MODE_KEY$>
CurrMode = Xlate('TOOL', ToolID, 'CURR_MODE', 'X')<1, 1>
If CurrMode NE 'OUT' AND CurrMode NE 'FACILITIES (UnSched)' then
If CurrMode EQ '' then
obj_Tool_Log('InitialLog', ToolID)
CurrMode = 'OUT'
end
NumberTools += 1
CurrModeDTM = Field(CurrModeKey, '*', 2)
CurrModeDTM = Oconv(CurrModeDTM, 'DT4/^S')
Parms = ToolID : @RM
Parms := CurrModeDTM : @RM
Parms := 'FACILITIES (UnSched)' : @RM
Parms := EvacNotes
obj_Tool_Log('SetMode', Parms)
end
Repeat
Msg(@Window, '', 'OK', '', 'Evac Procedures' : @FM : NumberTools : ' tools have been placed into Evac mode.')
end
return
OLE_DIRECT_CONNECTION.OnMessage:
RTP27('MESSAGING_SERVICES')
Response = Messaging_Services('ProcessMessage', Parm2)
return