open-insight/LSL2/STPROC/COMM_WM_IN.txt
Infineon\Mitchem 507c6bffba Commit to save progress.
Feature complete. Ready for UAT.

Minor changes to ZPL Hold header and darkness.

Implement post UAT changes.

fixed small bug in WMO reprint event logic

formatted code and removed commented out code
2025-03-26 14:49:02 -07:00

880 lines
22 KiB
Plaintext

COMPILE FUNCTION Comm_WM_In(Instruction, Parm1,Parm2)
/*
Commuter module for WM_In (Work Order Material - Inbound) window
05/22/2005 - John C. Henry, J.C. Henry & Co., Inc.
02/27/2025 - DJM - Added prompt to remove hold when creating NCR in 'RejMat'
*/
DECLARE SUBROUTINE Set_Property, Set_Status, ErrMsg, Set_Property, obj_AppWindow, Send_Message, Labeling_Services
DECLARE SUBROUTINE Btree.Extract, Send_Event, Security_Err_Msg, Forward_Event, End_Window, Start_Window, Sleepery
DECLARE SUBROUTINE EditCell, obj_NCR, obj_Notes, obj_WO_Mat, obj_WO_Wfr, WM_IN_Services, Hold_Services, Error_Services
DECLARE FUNCTION Get_Property, Get_Status, Popup, Send_Message, Msg, Security_Check, Dialog_Box, RowExists, Error_Services
DECLARE FUNCTION Dialog_Box, obj_WO_Log, obj_NCR, MemberOf, WM_IN_Services, Hold_Services, Database_Services, Datetime
$INSERT POPUP_EQUATES
$INSERT MSG_EQUATES
$INSERT APPCOLORS
$INSERT WM_IN_EQUATES
$INSERT WO_LOG_EQU
$INSERT WO_STEP_EQU
$INSERT WO_MAT_EQUATES
$INSERT ORDER_EQU
$INSERT RDS_EQU
$INSERT PROD_SPEC_EQU
$INSERT LSL_USERS_EQU
$INSERT SECURITY_RIGHTS_EQU
$INSERT NOTIFICATION_EQU
$INSERT RTI_STYLE_EQUATES
$INSERT LOGICAL
EQU CRLF$ TO \0D0A\
EQU COL$PRE_CODE TO 1
EQU COL$BOAT_ID TO 2
EQU COL$SRD_NO TO 3
EQU COL$PRE_EPI_SIG TO 4
EQU COL$PRE_EPI_NAME TO 5
EQU COL$PRE_EPI_DTM TO 6
EQU COL$SLOT TO 1
EQU COL$RDS TO 2
EQU COL$RDS_STATUS TO 3
EQU COL$POCKET TO 4
EQU COL$ZONE TO 5
EQU COL$CHAR TO 6
EQU COL$SLOT_NCR_NO TO 7
EQU COL$ON_HOLD_DTM TO 1
EQU COL$ON_HOLD_USER TO 2
EQU COL$ON_REASON TO 3
EQU COL$OFF_HOLD_DTM TO 4
EQU COL$OFF_HOLD_USER TO 5
EQU COL$OFF_REASON TO 6
ErrTitle = 'Error in Comm_WM_In'
ErrorMsg = ''
Result = ''
BEGIN CASE
CASE Instruction = 'Create' ; GOSUB Create
CASE Instruction = 'Refresh' ; GOSUB Refresh
CASE Instruction = 'Read' ; GOSUB Read
CASE Instruction = 'Page' ; GOSUB Page
CASE Instruction = 'Write' ; GOSUB Write
CASE Instruction = 'Clear' ; GOSUB Clear
CASE Instruction = 'Delete' ; GOSUB Delete
CASE Instruction = 'Close' ; GOSUB Close
CASE Instruction = 'Surfscan' ; GOSUB Surfscan
CASE Instruction = 'SigBlockDC' ; GOSUB SigBlockDC
CASE Instruction = 'SigBlockPC' ; GOSUB SigBlockPC
CASE Instruction = 'SigBlockDelete' ; GOSUB SigBlockDelete
CASE Instruction = 'SigBlockInsert' ; GOSUB SigBlockInsert
CASE Instruction = 'SigBlockClick' ; GOSUB SigBlockClick
CASE Instruction = 'Sign' ; GOSUB Sign
CASE Instruction = 'RejMat' ; GOSUB RejMat
CASE Instruction = 'NCRKeysDC' ; GOSUB NCRKeysDC
CASE Instruction = 'HoldClick' ; GOSUB HoldClick
CASE Instruction = 'HoldDC' ; GOSUB HoldDC
CASE Instruction = 'AddComment' ; GOSUB AddComment
CASE Instruction = 'ViewComments' ; GOSUB ViewComments
CASE Instruction = 'ReprintHold' ; GOSUB ReprintHold
CASE 1
ErrorMsg = 'Unknown Instruction passed to routine'
END CASE
RETURN Result
* * * * * * *
Create:
* * * * * * *
obj_Appwindow('Create',@WINDOW)
* Provides compatibility with the existing messaging attachment system
IF Parm1 NE '' THEN
PassedKeys = Parm1
obj_Appwindow('ViewRelated',@WINDOW:@RM:PassedKeys)
END
IF MemberOf(@USER4, 'OI_SUPERUSER') THEN
Set_Property(@WINDOW:'.VOID','VISIBLE',1)
END ELSE
Set_Property(@WINDOW:'.VOID','VISIBLE',0)
END
GOSUB Refresh
RETURN
* * * * * * *
Read:
* * * * * * *
GOSUB Refresh
RETURN
* * * * * * *
Write:
* * * * * * *
Result = 1
RETURN
* * * * * * *
Clear:
* * * * * * *
GOTO Refresh
RETURN
* * * * * * *
Delete:
* * * * * * *
ErrMsg('Records may not be modified or deleted.')
Result = 0 ;* No Deletes
RETURN
* * * * * * *
Close:
* * * * * * *
obj_Appwindow('DetailReturn')
RETURN
* * * * * * *
ReprintHold:
* * * * * * *
WONo = Get_Property(@WINDOW:'.WO_NO','DEFPROP')
WOStep = Get_Property(@WINDOW:'.PROC_STEP_NO','DEFPROP')
InCassNo = Get_Property(@WINDOW:'.IN_CASS_NO','DEFPROP')
WMIKey = WONo:'*':WOStep:'*':InCassNo
Labeling_Services('ReprintHoldLabel', 'WM_IN', WMIKey)
RETURN
* * * * * * *
Refresh:
* * * * * * *
IF Get_Property(@WINDOW:'.HOLD_CHECKBOX','CHECK') THEN
Set_Property(@WINDOW:'.HOLD_BUTTON','TEXT','Remove Hold')
Set_Property(@Window:'.MENU.PRINT.REPRINT_HOLD_LABEL', 'ENABLED', True$)
END ELSE
Set_Property(@WINDOW:'.HOLD_BUTTON','TEXT','Place on Hold')
Set_Property(@Window:'.MENU.PRINT.REPRINT_HOLD_LABEL', 'ENABLED', False$)
END
IF Get_Property(@WINDOW:'.SPEC_PRE_SURFSCAN','CHECK') THEN
Set_Property(@WINDOW:'.SURFSCAN_BUTTON','ENABLED',1)
END ELSE
Set_Property(@WINDOW:'.SURFSCAN_BUTTON','ENABLED',0)
END
* 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>
IF ETCtrl NE @WINDOW:'.CASSETTES' THEN
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 Line
END
NEXT I
CtrlName = @WINDOW:'.NCR_KEYS'
NCRList = Get_Property(CtrlName,'LIST')
ColCount = COUNT(NCRList<1>,@VM) + (NCRList<1> NE '')
FOR Line = 1 TO COUNT(NCRList,@FM) + (NCRList NE '')
Status = NCRList<Line,2>
BEGIN CASE
CASE Status = '' ; Color = WHITE$
CASE Status = 'Closed' ; Color = GREEN$
CASE Status = 'Open' ; Color = RED$
CASE Status = 'Verified' ; Color = YELLOW$
CASE 1 ; Color = WHITE$
END CASE
FOR Col = 1 TO ColCount
stat = Send_Message(CtrlName,'COLOR_BY_POS',Col,Line,Color)
NEXT Col
NEXT Line
RETURN
* * * * * * * *
AddComment:
* * * * * * * *
WONo = Get_Property(@WINDOW:'.WO_NO','TEXT')
WONo = WONo : '*' : Get_Property(@WINDOW:'.PROC_STEP_NO','TEXT')
WONo = WONo : '*' : Get_Property(@WINDOW:'.IN_CASS_NO','TEXT')
If WONo NE '' then
Response = Dialog_Box('NDW_ADD_RDS_COMMENT', @Window)
If Response NE '' then WM_IN_Services('AddComment', WONo, Response)
end
return
* * * * * * * *
ViewComments:
* * * * * * * *
WONo = Get_Property(@WINDOW:'.WO_NO','TEXT')
WONo = WONo : '*' : Get_Property(@WINDOW:'.PROC_STEP_NO','TEXT')
WONo = WONo : '*' : Get_Property(@WINDOW:'.IN_CASS_NO','TEXT')
If WONo NE '' then Response = Dialog_Box('NDW_WM_IN_COMMENT_VIEWER', @Window, WONo)
return
* * * * * * *
Surfscan:
* * * * * * *
Ctrls = @WINDOW:'.WO_NO':@RM ; Props = 'DEFPROP':@RM
Ctrls := @WINDOW:'.PROC_STEP_NO':@RM ; Props := 'DEFPROP':@RM
Ctrls := @WINDOW:'.IN_CASS_NO' ; Props := 'DEFPROP'
Vals = Get_Property(Ctrls,Props)
WONo = Vals[1,@RM]
ProcStepNo = Vals[COL2()+1,@RM]
InCassNo = Vals[COL2()+1,@RM]
IF WONo NE '' AND ProcStepNo NE '' AND InCassNo NE '' THEN
Stage = 'PE' ;* PreEpi
SurfScanKey = WONO:'*':ProcStepNo:'*':InCassNo:'*':Stage
obj_AppWindow('ViewRelated','SURFACE_SCAN':@RM:SurfScanKey)
END
RETURN
* * * * * * *
SigBlockDC:
* * * * * * *
CtrlEntID = @WINDOW:'.SIG_BLOCK'
CurrArray = Get_Property(CtrlEntID,'DEFPROP')
CurrPos = Get_Property(CtrlEntID,'SELPOS')
CurrCol = CurrPos<1>
CurrRow = CurrPos<2>
BEGIN CASE
CASE CurrCol = COL$PRE_CODE
ColumnPopup ='PRECLEANCODE'
CASE CurrCol = COL$BOAT_ID
ColumnPopup = 'PRECLEANCASSID'
CASE CurrCol = COL$SRd_NO
ColumnPopup = 'PRECLEANSRD'
CASE CurrCol = COL$PRE_EPI_SIG
TypeOver = ''
TypeOver<PDISPLAY$> = 'WITH ACTIVE BY LAST_FIRST'
TypeOver<PSELECT$> = 1
UserID = Popup(@WINDOW,TypeOver,'SHOW_USERS')
IF UserID = '' THEN RETURN
obj_AppWindow('LUValReturn',UserID:@RM:CtrlEntID:@RM:CurrPos)
RETURN
END CASE
ReturnValue = Popup( @WINDOW, '', ColumnPopup )
IF ReturnValue NE '' THEN
obj_AppWindow('LUValReturn',ReturnValue:@RM:CtrlEntID:@RM:CurrPos)
END
RETURN
* * * * * * *
SigBlockDelete:
* * * * * * *
CtrlEntID = @WINDOW:'.SIG_BLOCK'
RowPos = Parm1
DelRow = Parm2
IF DelRow<1,COL$PRE_EPI_SIG> NE '' THEN
Send_Message( CtrlEntId, 'INSERT', RowPos, DelRow )
SelPos = Get_Property(CtrlEntID,'SELPOS')
SelPos<2> = SelPos<2> - 1
Set_Property(CtrlEntID,'SELPOS',SelPos)
RETURN
END
MsgInfo = ''
MsgInfo<MTEXT$> = 'Do you wish to delete this cleaning entry?'
MsgInfo<MTYPE$> = 'BNY'
Resp = Msg( '', MsgInfo )
IF NOT(Resp) THEN
Send_Message( CtrlEntId, 'INSERT', RowPos, DelRow )
SelPos = Get_Property(CtrlEntID,'SELPOS')
SelPos<2> = SelPos<2> - 1
Set_Property(CtrlEntID,'SELPOS',SelPos)
END
RETURN
* * * * * * *
SigblockInsert:
* * * * * * *
CtrlEntID = @WINDOW:'.SIG_BLOCK'
RowPos = Parm1
MsgInfo = ''
MsgInfo<MTEXT$> = 'Do you wish to insert a cleaning?'
MsgInfo<MTYPE$> = 'BNY'
Resp = Msg( '', MsgInfo )
IF Resp ELSE
Send_Message( CtrlEntId, "DELETE", RowPos )
END
RETURN
* * * * * * *
SigBlockPC:
* * * * * * *
CtrlEntID = @WINDOW:'.SIG_BLOCK'
CurrList = Get_Property(CtrlEntID,'LIST')
CurrPos = Get_Property(CtrlEntID,'SELPOS')
CurrCol = CurrPos<1>
CurrRow = CurrPos<2>
RowData = CurrList<CurrRow>
IF RowData<1,COL$PRE_EPI_SIG> NE '' THEN
Set_Property(CtrlEntId,"SELPOS",1:@FM:CurrRow + 1)
RETURN
END
BEGIN CASE
CASE CurrCol = COL$PRE_EPI_NAME
Set_Property(CtrlEntID,'SELPOS',COL$PRE_EPI_DTM:@FM:CurrRow)
CASE CurrCol = COL$PRE_EPI_DTM
IF CurrList<CurrRow,CurrCol> = '' AND CurrList<CurrRow,COL$PRE_EPI_SIG> NE '' THEN
CurrTime = OCONV(Time(),'MTHS')
CurrDate = OCONV(Date(),'D4/')
Set_Property(CtrlEntID,'CELLPOS',CurrDate:' ':CurrTime,CurrPos)
END
END CASE
RETURN
* * * * * * *
SigBlockClick:
* * * * * * *
CtrlEntID = @WINDOW:'.SIG_BLOCK'
Forward_Event()
Send_Event(@WINDOW,'POSCHANGED')
RETURN
* * * * * * *
Sign:
* * * * * * *
CtrlEntID = @WINDOW:'.SIG_BLOCK'
CurrArray = Get_Property(CtrlEntID,'ARRAY')
CurrPos = Get_Property(CtrlEntID,'SELPOS')
CurrCol = CurrPos<1>
CurrRow = CurrPos<2>
Signatures = CurrArray<COL$PRE_EPI_SIG>
SigCnt = COUNT(Signatures, @VM ) + (Signatures NE '')
LOOP
UNTIL Signatures[-1,1] NE @VM
Signatures[-1,1] = ''
REPEAT
PSNo = Get_Property(@WINDOW:'.PS_NO','DEFPROP')
VerifyInstructions = XLATE('PROD_SPEC',PSNo,PROD_SPEC_PRE_EPI_VER_INST$,'X')
IF VerifyInstructions NE '' THEN
Yes = Dialog_Box( 'RDS_VER', @WINDOW, PSNO:'*':PROD_SPEC_PRE_EPI_VER_INST$ )
IF NOT(Yes) THEN RETURN ;* User bailed
END
Valid = Dialog_Box( 'QUOTE_SIG_PWD_ENTRY', @WINDOW, @USER4:@VM:XLATE( 'LSL_USERS', @USER4, LSL_USERS_PASSWORD$, 'X' ) )
IF Valid THEN
SigCnt = COUNT(Signatures,@VM) + (Signatures NE '')
NextLine = SigCnt + 1
CurrDTM = OCONV(Date(),'D4/'):' ':OCONV(Time(),'MTHS')
UserName = XLATE( 'LSL_USERS', @USER4, 'FIRST_LAST', 'X' )
Set_Property(CtrlEntID,'CELLPOS','',COL$PRE_CODE:@FM:NextLine)
Set_Property(CtrlEntID,'CELLPOS','',COL$BOAT_ID:@FM:NextLine)
Set_Property(CtrlEntID,'CELLPOS','',COL$SRD_NO:@FM:NextLine)
Set_Property(CtrlEntID,'CELLPOS',@USER4,COL$PRE_EPI_SIG:@FM:NextLine)
Set_Property(CtrlEntID,'CELLPOS',UserName,COL$PRE_EPI_NAME:@FM:NextLine)
Set_Property(CtrlEntID,'CELLPOS',CurrDTM,COL$PRE_EPI_DTM:@FM:NextLine)
END
RETURN
* * * * * * *
RdsDC:
* * * * * * *
WOStepKey = Get_Property(@WINDOW,'ID')
IF WOStepKey = '' THEN RETURN
CtrlEntID = @WINDOW:'.CASSETTES'
CurrPos = Get_Property(CtrlEntID,'NOTIFYPOS') ;* Undocumented property that gives cell location when multi select is enabled.
CurrCol = CurrPos<1>
CurrRow = CurrPos<2>
RDSNo = Get_Property(CtrlEntID,'CELLPOS',2:@FM:CurrRow)
IF RDSNo NE '' THEN
Set_Property(@WINDOW,'@RETURN_FROM_RDS',WOStepKey) ;* Bullshit lashup to work with multiple RDS windows
thisFormName = 'RDS'
thisFormWindowUp = Get_Property(thisFormName,'VISIBLE') ;* Returns 0 = hidden, 1 = visible, 2 = minimized, 3 = maximized
IF thisFormWindowUp = '' THEN
If Get_Property('NDW_MAIN', 'VISIBLE') then
AppMain = 'NDW_MAIN'
end else
AppMain = 'LSL_MAIN2'
end
Start_Window(thisFormName,AppMain,RDSNo:'*CENTER', '', '') ;* Put up the card window
RETURN
END
IF thisFormWindowUp = 2 THEN Set_Property(thisFormName,'VISIBLE',9) ;* Restore the window if minimized
IF Get_Property(thisFormName,'SAVEWARN') THEN
Send_Event(thisFormName,'CLEAR') ;* Clear anything existing (prompts for save first)
END
END
RETURN
* * * * * * *
RejMat:
* * * * * * *
WMInList = Get_Property(@WINDOW:'.SLOT_NO','LIST')
SlotSelection = Get_Property(@WINDOW:'.SLOT_NO','SELPOS')
SelectedRows = SlotSelection<2>
CONVERT @VM TO @FM in SelectedRows
SelCnt = COUNT(SelectedRows,@FM) + (SelectedRows NE '')
IF SelCnt = 0 THEN
ErrMsg('You must select at least one row in order to create an NCR.')
RETURN
END
WONo = Get_Property(@WINDOW:'.WO_NO','DEFPROP')
WOStep = Get_Property(@WINDOW:'.PROC_STEP_NO','DEFPROP')
InCassNo = Get_Property(@WINDOW:'.IN_CASS_NO','DEFPROP')
WMIKey = WONo:'*':WOStep:'*':InCassNo
WMIStatus = Xlate('WM_IN', WMIKey, 'CURR_STATUS', 'X')
OnHold = (WMIStatus EQ 'HOLD')
WOMatKey = Xlate('WM_IN', WMIKey, 'WO_MAT_KEY', 'X')
Result = ''
If OnHold EQ True$ then
Result = Dialog_Box('NDW_HOLD_REMOVAL_PROMPT',@WINDOW,'WM_IN':@VM:WMIKey:@VM:WOMatKey)
If Result NE True$ then
Return
end else
Send_Event(@Window, 'READ')
end
end
If (OnHold NE True$) OR (Result = True$) then
SAPBatchNo = Xlate('WO_MAT', WOMatKey, WO_MAT_SAP_BATCH_NO$, 'X')
OffHoldDTMs = Xlate('WO_MAT', WOMatKey, 'HOLD_STOP_DTM', 'X')
If OffHoldDTMs NE '' then
// Ensure at least a minute has elapsed since the cassette was last taken off hold.
LastDTM = OffHoldDTMs[-1, 'B':@VM]
TimeElapsed = Datetime() - LastDTM
// .000694 is the equivalent to 60 seconds in datetime format
If (TimeElapsed LT '.000694') AND (SAPBatchNo NE '') then
Def = ""
Def<MTEXT$> = "Please wait for SAP to process off hold transaction..."
Def<MTYPE$> = "U"
MsgUp = Msg(@window, Def) ;* display the processing message
WaitTime = '.000694' - TimeElapsed
WaitSeconds = WaitTime * 86400 ;* 86400 = 60 seconds * 60 minutes * 24 hours
WaitMilliSec = WaitSeconds * 1000
Sleepery(WaitMilliSec)
Msg(@window, MsgUp) ;* take down the processing message
end
end
InCassNos = ''
InSlotNos = ''
RDSNos = ''
PocketNos = ''
Zones = ''
OutSlotNos = ''
OutCassNos = ''
SlotNCRs = ''
FOR I = 1 TO SelCnt
RDSNo = WMInList<SelectedRows<I>,COL$RDS>
IF RDSNo NE '' THEN
ErrMsg('Slot ':SelectedRows<I>:' has already been loaded into the reactor.')
RETURN
END ELSE
InSlotNos<1,I> = WMInList<SelectedRows<I>,COL$SLOT>
InCassNos<1,I> = InCassNo
SlotNCRs<1,I> = WMInList<SelectedRows<I>,COL$SLOT_NCR_NO>
END
NEXT I
IF InCassNos = '' THEN RETURN
ncrParms = WONo:@RM
ncrParms := WOStep:@RM
ncrParms := InCassNo:@RM ;* WO_MAT_CASS_NO ;* changed from null on WM_IN jch 12/1/11
ncrParms := '':@RM ;* Single RDS field
ncrParms := '':@RM ;* Reactor No
ncrParms := 'PRE':@RM
ncrParms := InCassNos:@RM
ncrParms := InSlotNos:@RM
ncrParms := PocketNos:@RM ;* Pocket Nos
ncrParms := Zones:@RM ;* Zones
ncrParms := OutCassNos:@RM ;* OutCassNos
ncrParms := OutSlotNos:@RM ;* OutSlotNos
ncrParms := RDSNos:@RM ;* RDSNos
ncrParms := '':@RM ;* Placeholder for RejWaferIDs
ncrParms := SlotNCRs
BarcodeVerified = Dialog_Box('NDW_VERIFY_BARCODE', @Window, WMIKey, @User4)
If BarcodeVerified EQ TRUE$ then
Set_Status(0)
NCRNo = obj_NCR('Create',ncrParms) ;* Create new NCR for this wafer/group of wafers
errCode = ''
IF Get_Status(errCode) THEN
ErrMsg(errCode)
END ELSE
RejDTM = OCONV(Date(),'D4/'):' ':OCONV(Time(),'MTS')
RejWfrIDs = ''
NewSlotIDs = ''
CurrSlotIDs = ''
RunLocs = ''
FOR N = 1 TO COUNT(InSlotNos,@VM) + (InSlotNos NE '')
* * * * Added 3/23/2016 JCH - wafer history * * * *
RejWfrID = WONo:'*':InCassNos<1,N>:'*':InSlotNos<1,N>
RejWfrIDs<1,-1> = RejWfrID
CurrSlotIDs<1,-1> = RejWfrID ;*Inbound box WfrID = SlotID
Parms = RejWfrID:@RM ;* WfrID
Parms := RejDTM:@RM ;* EventDtm
Parms := @USER4:@RM ;* EventBy
Parms := 'NCR':@RM ;* Event
Parms := '':@RM ;* NewSlotID
Parms := '':@RM ;* RunLoc
Parms := NCRNo:@RM ;* NCRNo
Parms := '':@RM ;* TWUse
Parms := RejWfrID:@RM ;* CurrSlotID Inbound box WfrID = SlotID
Parms := '':@RM ;* NewToolID
Parms := '':@RM ;* CurrToolID
Parms := '':@RM ;* NewInvLoc
Parms := '':@RM ;* CurrInvLoc
Parms := 'I' ;* WfrSide
obj_WO_Wfr('AddEvent',Parms)
* * * * *
LineNo = InSlotNos<1,N>
Set_Property(@WINDOW:'.SLOT_NO','CELLPOS','',COL$RDS:@FM:LineNo)
Set_Property(@WINDOW:'.SLOT_NO','CELLPOS','',COL$RDS_STATUS:@FM:LineNo)
Set_Property(@WINDOW:'.SLOT_NO','CELLPOS','',COL$POCKET:@FM:LineNo)
Set_Property(@WINDOW:'.SLOT_NO','CELLPOS','',COL$ZONE:@FM:LineNo)
Set_Property(@WINDOW:'.SLOT_NO','CELLPOS','',COL$CHAR:@FM:LineNo)
Set_Property(@WINDOW:'.SLOT_NO','CELLPOS',NCRNo,COL$SLOT_NCR_NO:@FM:LineNo)
NEXT N
END
Set_Property(@WINDOW:'.SLOT','SELPOS',SlotSelection) ;* Toggle WM_IN select off
Send_Event(@WINDOW,'WRITE')
DetWindow = 'NCR'
DetKeys = NCRNo
DefaultRec = ''
RetKey = WMIKey
RetWin = @WINDOW
RetPage = 1
RetCtrl = @WINDOW:'.SLOT'
RetPos = 1:@FM:1
obj_Appwindow('ViewNewDetail',DetWindow:@RM:DetKeys:@RM:DefaultRec:@RM:RetKey:@RM:RetPage:@RM:RetCtrl:@RM:RetPos)
End
end
RETURN
* * * * * * *
NCRKeysDC:
* * * * * * *
WMId = Get_Property(@WINDOW,'ID')
CtrlEntID = @WINDOW:'.NCR_KEYS'
CurrPos = Get_Property(CtrlEntID,'SELPOS')
CurrCol = CurrPos<1>
CurrRow = CurrPos<2>
NCRKey = Get_Property(CtrlEntID,'CELLPOS',1:@FM:CurrRow)
Send_Event(@WINDOW,'WRITE')
DetWindow = 'NCR'
DetKeys = NCRKey
DefaultRec = ''
RetKey = WMId
RetWin = @WINDOW
RetPage = 1
RetCtrl = CtrlEntID
RetPos = CurrPos
obj_Appwindow('ViewNewDetail',DetWindow:@RM:DetKeys:@RM:DefaultRec:@RM:RetKey:@RM:RetPage:@RM:RetCtrl:@RM:RetPos)
RETURN
* * * * * * *
HoldClick:
* * * * * * *
CtrlEntID = @WINDOW
WMInKey = Get_Property(@WINDOW,'ID')
WONo = WMInKey[1,'*']
CassNo = FIELD(WMInKey,'*',3)
WOMatKey = WONo:'*':CassNo
HoldEntity = 'WM_IN'
HoldEntityID = WMInKey
Reactor = 'EPP'
PSN = Get_Property(@Window:'.PS_NO', 'TEXT')
Send_Event(@WINDOW,'WRITE')
Transition = Hold_Services('CheckForHold', WOMatKey, CtrlEnt)
HoldType = 'HOLD'
Stage = Xlate('WO_MAT', WOMatKey, WO_MAT_HOLD_STAGE$, 'X')
Interrupted = Xlate('WO_MAT', WOMatKey, WO_MAT_HOLD_INTERRUPTED$, 'X')
HoldData = ''
HoldData = Dialog_Box('DIALOG_HOLD',@WINDOW,Transition:@FM:@FM:HoldType:@FM:Stage:@FM:Interrupted)
If HoldData NE 'Cancel' then
Hold_Services('ToggleHold', WOMatKey, HoldEntity, HoldEntityID, CtrlEntID, '', HoldData)
IF Error_Services("HasError") THEN
ErrCode = Error_Services("GetMessage")
ErrMsg(errCode)
end else
If Transition EQ False$ then
MsgInfo = ''
MsgInfo<MTYPE$> = 'BNY'
MsgInfo<MTEXT$> = 'Hold Successful. Would you like to print label(s)?'
MsgInfo<MICON$> = '!'
PrintLabel = Msg(@WINDOW,MsgInfo,'')
HoldBy = HoldData<1>
Reason = HoldData<2>
Stage = HoldData<4>
Interrupted = HoldData<5>
DTM = Datetime()
If PrintLabel EQ True$ then
Labeling_Services('PrintHoldLabel', HoldEntity, HoldEntityID, Stage, Reason, HoldBy, DTM, PSN, Reactor, Interrupted)
end
end
end
end
obj_AppWindow('LoadFormKeys',@WINDOW:@RM:WMInKey)
RETURN
* * * * * * *
HoldDC:
* * * * * * *
CtrlEntID = @WINDOW:'.HOLD_HISTORY'
RecordID = Get_Property(@WINDOW,'ID')
WONo = Get_Property(@WINDOW:'.WO_NO','DEFPROP')
CassNo = Get_Property(@WINDOW:'.IN_CASS_NO','DEFPROP')
IF WONo = '' OR CassNo = '' THEN RETURN
WOMatKey = WONo:'*':CassNo
HoldHistory = Get_Property(CtrlEntID,'LIST')
CurrPos = Get_Property(CtrlEntID,'SELPOS')
CurrCol = CurrPos<1>
CurrRow = CurrPos<2>
HistoryCols = Get_Property(CtrlEntID, "COLUMN")
ColName = HistoryCols<1,1,CurrCol>
WOMatRec = Database_Services("ReadDataRow", "WO_MAT", WOMatKey, "", "", FALSE$)
IF INDEX(ColName,'START',1) THEN
HoldStartReason = WOMatRec<WO_MAT_HOLD_START_REASON$,CurrRow>
UpdatedText = Dialog_Box('DIALOG_TEXT',@WINDOW,'Hold Start Reason':@FM:HoldStartReason)
END ELSE
IF INDEX(ColName,'STOP',1) THEN
HoldStopReason = WOMatRec<WO_MAT_HOLD_STOP_REASON$,CurrRow>
UpdatedText = Dialog_Box('DIALOG_TEXT',@WINDOW,'Hold Stop Reason':@FM:HoldStopReason)
END
END
If UpdatedText NE 'Cancel' then
Hold_Services("EditHoldReason",WOMatKey, ColName, CurrRow, UpdatedText)
End
IF Error_Services("NoError") NE TRUE$ THEN
ErrMsg(Error_Services("GetMessage"))
end
Send_Event(CtrlEntID,'CALCULATE',CurrCol)
RETURN
* * * * * * *
Page:
* * * * * * *
Page = Parm1
IF Page = '' THEN
Page = Get_Property(@WINDOW:'.TAB_MAIN','VALUE')
END ELSE
Set_Property(@WINDOW:'.TAB_MAIN','VALUE',Page)
END
Set_Property(@WINDOW,'VPOSITION', Page)
RETURN