implemented support for BatchConv SAP interface
This commit is contained in:
@ -20,7 +20,7 @@ DECLARE SUBROUTINE Sleepery
|
||||
DECLARE FUNCTION Get_Property, Get_Status, Popup, Send_Message, Msg, Security_Check, Dialog_Box, RowExists
|
||||
DECLARE FUNCTION Dialog_Box, obj_WO_Log, obj_NCR, Check_Notes, obj_MUWafers, obj_WO_Mat, Signature_Services
|
||||
DECLARE FUNCTION MemberOf, obj_Tables, obj_RDS, Environment_Services, Logging_Services, Material_Services
|
||||
DECLARE FUNCTION Database_Services, RetStack, Datetime
|
||||
DECLARE FUNCTION Database_Services, RetStack, Datetime, Error_Services
|
||||
|
||||
$INSERT POPUP_EQUATES
|
||||
$INSERT LOGICAL
|
||||
@ -72,8 +72,6 @@ EQU COL$USER_ID TO 8
|
||||
EQU COL$TAGS TO 9
|
||||
EQU COL$TOOL_ID TO 10
|
||||
|
||||
EQU MULTILINE_STYLE$ TO 512 ;* MultiLine Select
|
||||
|
||||
LogPath = Environment_Services('GetApplicationRootPath') : '\LogFiles\WO_Mat'
|
||||
LogDate = Oconv(Date(), 'D4/')
|
||||
LogTime = Oconv(Time(), 'MTS')
|
||||
@ -122,8 +120,6 @@ Create:
|
||||
IOOptions<6> = 1 ; // Do not clear on write
|
||||
Set_Property(@WINDOW, "IOOPTIONS", IOOptions)
|
||||
|
||||
* get the current style
|
||||
|
||||
* Provides compatibility with the existing messaging attachment system
|
||||
|
||||
IF Parm1 NE '' THEN
|
||||
@ -244,13 +240,7 @@ Refresh:
|
||||
HotLot = Vals[COL2()+1,@RM]
|
||||
UseMUWafers = Vals[COL2()+1,@RM]
|
||||
|
||||
IF MemberOf(@USER4,'OI_ADMIN') THEN
|
||||
Set_Property(@WINDOW:'.REM_MAKEUP_BUTTON','VISIBLE',1)
|
||||
END
|
||||
|
||||
IF NOT(MakeupBox) AND UseMUWafers THEN
|
||||
Set_Property(@WINDOW:'.ADD_MAKEUP_BUTTON','VISIBLE',1)
|
||||
Set_Property(@WINDOW:'.REM_MAKEUP_BUTTON','VISIBLE',1)
|
||||
Set_Property(@WINDOW:'.MU_BOX_LABEL','VISIBLE',0)
|
||||
END ELSE
|
||||
IF MakeupBox = 1 THEN
|
||||
@ -258,12 +248,6 @@ Refresh:
|
||||
END ELSE
|
||||
Set_Property(@WINDOW:'.MU_BOX_LABEL','VISIBLE',0)
|
||||
END
|
||||
Set_Property(@WINDOW:'.ADD_MAKEUP_BUTTON','VISIBLE',0)
|
||||
Set_Property(@WINDOW:'.REM_MAKEUP_BUTTON','VISIBLE',0)
|
||||
END
|
||||
|
||||
IF MemberOf(@USER4,'OI_ADMIN') THEN
|
||||
Set_Property(@WINDOW:'.REM_MAKEUP_BUTTON','VISIBLE',1)
|
||||
END
|
||||
|
||||
IF HotLot THEN
|
||||
@ -383,12 +367,6 @@ Refresh:
|
||||
NEXT COL
|
||||
NEXT Line
|
||||
|
||||
SAPBatchNo = Xlate('WO_MAT', WOMatKey, WO_MAT_SAP_BATCH_NO$, 'X')
|
||||
SAPTXDtm = XLATE('WO_MAT', WOMatKey, WO_MAT_SAP_TX_DTM$, 'X')
|
||||
IF SAPBatchNo NE '' OR SAPTXDtm NE '' then
|
||||
Set_Property(@Window: '.MAKEUP_CHECKBOX', 'ENABLED', 0)
|
||||
end
|
||||
|
||||
RETURN
|
||||
|
||||
|
||||
@ -639,15 +617,13 @@ RecallMat:
|
||||
END
|
||||
END
|
||||
END
|
||||
NEXT I
|
||||
|
||||
|
||||
NEXT I
|
||||
|
||||
FOR I = 1 TO RecallNCRCnt
|
||||
RecallNCRNo = RecallNCRNos<I>
|
||||
RecallSlot = RecallSlotNos<I>
|
||||
|
||||
SlotCnt = COUNT(SlotInfo<1>, @VM) + (SlotInfo<1> NE '')
|
||||
SlotInfo = '' ; // Initializing variable here to prevent compilation warning. This code looks unfinished...
|
||||
SlotCnt = COUNT(SlotInfo<1>, @VM) + (SlotInfo<1> NE '')
|
||||
FOR N = 1 TO SlotCnt
|
||||
SlotNo = SlotInfo<1,N>
|
||||
PrevWaferID = SlotInfo<2,N>
|
||||
@ -665,7 +641,6 @@ RecallMat:
|
||||
RETURN
|
||||
|
||||
|
||||
|
||||
* * * * * * *
|
||||
NCRKeysDC:
|
||||
* * * * * * *
|
||||
@ -775,162 +750,169 @@ AddMakeup:
|
||||
Parms := 1:@RM ;* ReturnKeys Flag
|
||||
Parms := 1 ;* Use Reactor Run Table Flag
|
||||
|
||||
If 1 then
|
||||
Response = Dialog_Box('NDW_MAKEUP_WAFERS', @Window, WOMatKey)
|
||||
Begin Case
|
||||
Case Response EQ True$
|
||||
// User requested to convert the current cassette into a makeup box.
|
||||
SAPBatchNo = Xlate('WO_MAT', WOMatKey, 'SAP_BATCH_NO', 'X')
|
||||
IF SAPBatchNo then
|
||||
Msg(@Window , 'Lot has an SAP Batch No. and cannot be turned into a MU lot.')
|
||||
Return
|
||||
end
|
||||
AvailMU_WOMatKeys = ''
|
||||
UserResp = Response
|
||||
MakeupBox = ''
|
||||
Case Response EQ ''
|
||||
// User has cancelled this process.
|
||||
Return
|
||||
Case Otherwise$
|
||||
// User has selected a makeup box to use and backfill.
|
||||
AvailMU_WOMatKeys = Response
|
||||
MakeupBox = Response
|
||||
MuWfrsNeeded = SelCnt
|
||||
If AvailMU_WOMatKeys NE '' then
|
||||
// Wafer counter check - Account for the possibility of selecting more than one makeup box.
|
||||
For each MuWoMatKey in AvailMU_WOMatKeys using @FM
|
||||
MuRdsNo = Xlate('WO_MAT', MuWoMatKey, 'RDS_NO', 'X')
|
||||
QtyAdj = MuWfrsNeeded
|
||||
CurrMuWfrCnt = obj_WO_Mat('CurrWaferCnt', MuWoMatKey)
|
||||
If MuWfrsNeeded GT CurrMuWfrCnt then
|
||||
QtyAdj = CurrMuWfrCnt
|
||||
MuWfrsNeeded -= CurrMuWfrCnt
|
||||
end
|
||||
Parms = ''
|
||||
Parms<1> = MuRdsNo ; // Cassette to verify wafer count of.
|
||||
Parms<2> = QtyAdj ; // Wafer count adjustment - Number of makeup wafers being used.
|
||||
Parms<3> = 'MU' ; // Wafer counter tool location
|
||||
Proceed = Dialog_Box('NDW_WAFER_COUNTER', @Window, Parms)
|
||||
If Proceed NE True$ then return
|
||||
Next MuWoMatKey
|
||||
end
|
||||
End Case
|
||||
If Response EQ True$ then
|
||||
// User requested to convert the current cassette into a makeup box.
|
||||
// Verify the quantity before proceeding.
|
||||
RDSNo = Get_Property(@Window:'.RDS_NO', 'TEXT')
|
||||
If RDSNo NE '' then
|
||||
Parms = ''
|
||||
Parms<1> = RDSNo ; // Cassette to verify wafer count of.
|
||||
Parms<2> = 0 ; // Wafer count adjustment - 0 because converting box.
|
||||
Parms<3> = 'MU' ; // Wafer counter tool location
|
||||
Proceed = Dialog_Box('NDW_WAFER_COUNTER', @Window, Parms)
|
||||
If Proceed NE True$ then return
|
||||
end else
|
||||
ErrMsg('Error starting wafer counter check. RDS No is missing.')
|
||||
end
|
||||
end
|
||||
end else
|
||||
AvailMU_WOMatKeys = obj_MUWafers('AvailWafers',WONo:@RM:@RM:1:@RM:1)
|
||||
end
|
||||
|
||||
LOCATE WOMatKey IN AvailMU_WOMatKeys USING @VM SETTING Pos THEN
|
||||
AvailMU_WOMatKeys = DELETE(AvailMU_WOMatKeys,1,Pos,0) ;* Remove current cassette from list
|
||||
END
|
||||
|
||||
IF AvailMU_WOMatKeys = '' THEN
|
||||
|
||||
RDSNo = Get_Property(@Window : '.RDS_NO', 'TEXT') ; // Get the RDS No now before the WRITE in case it is needed to toggle the index.
|
||||
If 0 then
|
||||
UserResp = Msg(@WINDOW,'','MAKEUP_WAFERS') ;* This box is being made into m/u wafers message
|
||||
end
|
||||
|
||||
IF UserResp = CHAR(27) THEN RETURN
|
||||
|
||||
Send_Event(@WINDOW,'WRITE')
|
||||
|
||||
FieldNo = WO_MAT_MAKEUP_BOX$
|
||||
CheckValue = 1
|
||||
|
||||
obj_WO_Mat('ChangeFlag',WOMatKey:@RM:FieldNo:@RM:CheckValue)
|
||||
* WOMatRow = Database_Services('ReadDataRow', 'WO_MAT', WOMatKey)
|
||||
* WOMatRow<12> = '' ; // Clear the RDS No so the index will be forced to recalculate.
|
||||
* WOMatRow<23> = False$ ; // Clear the MakeUp box flag so the index will be forced to recalculate.
|
||||
* Database_Services('WriteDataRow', 'WO_MAT', WOMatKey, WOMatRow, True$, False$, True$)
|
||||
* WOMatRow<12> = RDSNo ; // Restore the RDS No so the index on RDS_FINAL_SIG will be forced to recalculate with the most recent value.
|
||||
* WOMatRow<23> = True$ ; // Restore the MakeUp box flag so the index will be forced to recalculate.
|
||||
* WOMatRec = WOMatRow
|
||||
//GoSub LogRecord
|
||||
//Database_Services('WriteDataRow', 'WO_MAT', WOMatKey, WOMatRow, True$, False$, True$)
|
||||
SlotWaferIDs = Xlate('WO_MAT', WOMatKey, 'SLOT_WAFER_ID', 'X')
|
||||
Convert @VM to '' in SlotWaferIDs
|
||||
|
||||
// Flush/update pending index transactions.
|
||||
Update_Index('WO_MAT', 'MU_PART_NO', False$, True$)
|
||||
Update_Index('WO_MAT', 'CURR_STATUS', False$, True$)
|
||||
|
||||
IF Get_Status(errCode) THEN
|
||||
ErrMsg(errCode)
|
||||
end
|
||||
|
||||
CurrStatus = obj_WO_Mat('CurrStatus',WOMatKey)
|
||||
CurrDTM = OCONV(Date(),'D2/'):' ':OCONV(Time(),'MTS')
|
||||
|
||||
IF CurrStatus = 'RTU' THEN
|
||||
EventParms = ''
|
||||
EventParms<COL$LOG_FILE> = 'WO_MAT'
|
||||
EventParms<COL$LOG_DTM> = CurrDTM
|
||||
EventParms<COL$ACTION> = 'RTU'
|
||||
EventParms<COL$WH_CD> = 'CR'
|
||||
EventParms<COL$LOC_CD> = 'MU'
|
||||
EventParms<COL$WO_NOS> = WONo
|
||||
EventParms<COL$CASS_NOS> = CassNo
|
||||
EventParms<COL$USER_ID> = @USER4
|
||||
EventParms<COL$TAGS> = ''
|
||||
EventParms<COL$TOOL_ID> = ''
|
||||
|
||||
CONVERT @FM TO @RM IN EventParms
|
||||
|
||||
obj_WO_Mat_Log('Create',EventParms) ;* * * * * INV EVENT LOG * * * * *
|
||||
|
||||
IF Get_Status(errCode) THEN
|
||||
CALL ErrMsg(ErrCode)
|
||||
END
|
||||
|
||||
END
|
||||
|
||||
obj_AppWindow('LoadFormKeys',@WINDOW:@RM:WOMatKey)
|
||||
|
||||
END
|
||||
|
||||
TypeOver = ''
|
||||
TypeOver<PDISPLAY$> = AvailMU_WOMatKeys
|
||||
|
||||
If 0 then
|
||||
MakeupBox = Popup(@WINDOW,TypeOver,'WO_MAT_MAKEUP')
|
||||
end
|
||||
|
||||
IF NOT(MemberOf(@USER4,'OI_ADMIN')) THEN
|
||||
IF MakeupBox NE AvailMU_WOMatKeys<1,1> THEN
|
||||
ErrMsg('Only the first available cassette can be used for makeup.')
|
||||
MakeupBox = ''
|
||||
END
|
||||
END
|
||||
IF MakeupBox = '' THEN
|
||||
Post_Event(@Window, 'READ')
|
||||
RETURN
|
||||
end
|
||||
|
||||
Valid = Dialog_Box('NDW_VERIFY_USER', @Window, @User4)
|
||||
|
||||
IF NOT(Valid) THEN RETURN ;* User is not worthy or can't type
|
||||
|
||||
Send_Event(@WINDOW,'WRITE')
|
||||
|
||||
obj_WO_Mat('AddMakeupWafers',WOMatKey:@RM:EmptySlots:@RM:MakeupBox)
|
||||
|
||||
Send_Event(@WINDOW,'READ')
|
||||
|
||||
Response = Dialog_Box('NDW_MAKEUP_WAFERS', @Window, WOMatKey)
|
||||
Begin Case
|
||||
Case Response EQ True$
|
||||
// User requested to convert the current cassette into a makeup box.
|
||||
WOMatRec = Database_Services("ReadDataRow", 'WO_MAT', WOMatKey)
|
||||
If Error_Services('NoError') then
|
||||
SAPBatchNo = WOMatRec<WO_MAT_SAP_BATCH_NO$>
|
||||
SAPTXDtm = WOMatRec<WO_MAT_SAP_TX_DTM$>
|
||||
AwaitingBatchNo = ( (SAPTXDtm NE '') and (SAPBatchNo EQ '') )
|
||||
HasBatchNo = (SAPBatchNo NE '')
|
||||
FullBoxReject = (SAPBatchNo[-1, 1] = 'R')
|
||||
Begin Case
|
||||
Case AwaitingBatchNo
|
||||
InvalidRequest = True$
|
||||
ErrMsg('WARNING: Cassette ineligible to be converted as it is awaiting a batch number from SAP.')
|
||||
Return
|
||||
Case FullBoxReject
|
||||
InvalidRequest = True$
|
||||
ErrMsg('WARNING: Cassette ineligible to be converted as it is a full box reject.')
|
||||
Return
|
||||
Case HasBatchNo
|
||||
// Operation limited to LEAD and SUPERVISOR groups
|
||||
OverrideMsg = "Cassette has a batch number. SUPERVISOR or LEAD must override."
|
||||
Response = Msg(@Window, '', 'OVERRIDE', '', OverrideMsg)
|
||||
|
||||
Begin Case
|
||||
Case Response EQ 1
|
||||
Response = True$ ; // User Clicked Override
|
||||
Case Response EQ 2
|
||||
Response = False$ ; // User Clicked Cancel
|
||||
Case Response EQ char(27)
|
||||
Response = False$ ; // User Pressed Escape Key
|
||||
End Case
|
||||
|
||||
If Response EQ True$ then
|
||||
Response = Dialog_Box('NDW_VERIFY_USER', @WINDOW, @USER4:@FM:'LEAD':@VM:'SUPERVISOR')
|
||||
Authorized = Response<1>
|
||||
end else
|
||||
Authorized = False$
|
||||
end
|
||||
If Not(Authorized) then Return
|
||||
Case Otherwise$
|
||||
Null
|
||||
End Case
|
||||
|
||||
AvailMU_WOMatKeys = ''
|
||||
UserResp = Response
|
||||
MakeupBox = ''
|
||||
|
||||
// User requested to convert the current cassette into a makeup box.
|
||||
// Verify the quantity before proceeding.
|
||||
RDSNo = Get_Property(@Window:'.RDS_NO', 'TEXT')
|
||||
If RDSNo NE '' then
|
||||
Parms = ''
|
||||
Parms<1> = RDSNo ; // Cassette to verify wafer count of.
|
||||
Parms<2> = 0 ; // Wafer count adjustment - 0 because converting box.
|
||||
Parms<3> = 'MU' ; // Wafer counter tool location
|
||||
Proceed = Dialog_Box('NDW_WAFER_COUNTER', @Window, Parms)
|
||||
If Proceed NE True$ then return
|
||||
end else
|
||||
ErrMsg('Error starting wafer counter check. RDS No is missing.')
|
||||
end
|
||||
|
||||
RDSNo = Get_Property(@Window : '.RDS_NO', 'TEXT') ; // Get the RDS No now before the WRITE in case it is needed to toggle the index.
|
||||
|
||||
Send_Event(@WINDOW,'WRITE')
|
||||
|
||||
FieldNo = WO_MAT_MAKEUP_BOX$
|
||||
CheckValue = 1
|
||||
|
||||
obj_WO_Mat('ChangeFlag',WOMatKey:@RM:FieldNo:@RM:CheckValue)
|
||||
|
||||
SlotWaferIDs = Xlate('WO_MAT', WOMatKey, 'SLOT_WAFER_ID', 'X')
|
||||
Convert @VM to '' in SlotWaferIDs
|
||||
|
||||
// Flush/update pending index transactions.
|
||||
Update_Index('WO_MAT', 'MU_PART_NO', False$, True$)
|
||||
Update_Index('WO_MAT', 'CURR_STATUS', False$, True$)
|
||||
|
||||
IF Get_Status(errCode) THEN
|
||||
ErrMsg(errCode)
|
||||
end
|
||||
|
||||
CurrStatus = obj_WO_Mat('CurrStatus',WOMatKey)
|
||||
CurrDTM = OCONV(Date(),'D2/'):' ':OCONV(Time(),'MTS')
|
||||
|
||||
IF CurrStatus = 'RTU' THEN
|
||||
EventParms = ''
|
||||
EventParms<COL$LOG_FILE> = 'WO_MAT'
|
||||
EventParms<COL$LOG_DTM> = CurrDTM
|
||||
EventParms<COL$ACTION> = 'RTU'
|
||||
EventParms<COL$WH_CD> = 'CR'
|
||||
EventParms<COL$LOC_CD> = 'MU'
|
||||
EventParms<COL$WO_NOS> = WONo
|
||||
EventParms<COL$CASS_NOS> = CassNo
|
||||
EventParms<COL$USER_ID> = @USER4
|
||||
EventParms<COL$TAGS> = ''
|
||||
EventParms<COL$TOOL_ID> = ''
|
||||
|
||||
CONVERT @FM TO @RM IN EventParms
|
||||
|
||||
obj_WO_Mat_Log('Create',EventParms) ;* * * * * INV EVENT LOG * * * * *
|
||||
|
||||
IF Get_Status(errCode) THEN
|
||||
CALL ErrMsg(ErrCode)
|
||||
END
|
||||
|
||||
END
|
||||
|
||||
obj_AppWindow('LoadFormKeys',@WINDOW:@RM:WOMatKey)
|
||||
|
||||
Post_Event(@Window, 'READ')
|
||||
RETURN
|
||||
|
||||
end else
|
||||
ErrMsg('WARNING: Error reading WO_MAT record.')
|
||||
Return
|
||||
end
|
||||
|
||||
Case Response EQ ''
|
||||
// User has cancelled this process.
|
||||
Return
|
||||
|
||||
Case Otherwise$
|
||||
// User has selected a makeup box to use and backfill.
|
||||
AvailMU_WOMatKeys = Response
|
||||
MakeupBox = Response
|
||||
MuWfrsNeeded = SelCnt
|
||||
If AvailMU_WOMatKeys NE '' then
|
||||
// Wafer counter check - Account for the possibility of selecting more than one makeup box.
|
||||
For each MuWoMatKey in AvailMU_WOMatKeys using @FM
|
||||
MuRdsNo = Xlate('WO_MAT', MuWoMatKey, 'RDS_NO', 'X')
|
||||
QtyAdj = MuWfrsNeeded
|
||||
CurrMuWfrCnt = obj_WO_Mat('CurrWaferCnt', MuWoMatKey)
|
||||
If MuWfrsNeeded GT CurrMuWfrCnt then
|
||||
QtyAdj = CurrMuWfrCnt
|
||||
MuWfrsNeeded -= CurrMuWfrCnt
|
||||
end
|
||||
Parms = ''
|
||||
Parms<1> = MuRdsNo ; // Cassette to verify wafer count of.
|
||||
Parms<2> = QtyAdj ; // Wafer count adjustment - Number of makeup wafers being used.
|
||||
Parms<3> = 'MU' ; // Wafer counter tool location
|
||||
Proceed = Dialog_Box('NDW_WAFER_COUNTER', @Window, Parms)
|
||||
If Proceed NE True$ then return
|
||||
Next MuWoMatKey
|
||||
end
|
||||
|
||||
IF NOT(MemberOf(@USER4,'OI_ADMIN')) THEN
|
||||
IF MakeupBox NE AvailMU_WOMatKeys<1,1> THEN
|
||||
ErrMsg('Only the first available cassette can be used for makeup.')
|
||||
MakeupBox = ''
|
||||
return
|
||||
END
|
||||
END
|
||||
|
||||
Valid = Dialog_Box('NDW_VERIFY_USER', @Window, @User4)
|
||||
IF NOT(Valid) THEN RETURN ;* User is not worthy or can't type
|
||||
Send_Event(@WINDOW,'WRITE')
|
||||
obj_WO_Mat('AddMakeupWafers',WOMatKey:@RM:EmptySlots:@RM:MakeupBox)
|
||||
Send_Event(@WINDOW,'READ')
|
||||
|
||||
End Case
|
||||
|
||||
end else
|
||||
// Cassette is on hold so makeup wafers cannot be added.
|
||||
ErrorMessage = 'Add makeup wafer(s) denied!. The cassette must be taken off hold before adding makeup wafer(s).'
|
||||
@ -1039,35 +1021,59 @@ MakeUpLot:
|
||||
WOMatKey = WONo:'*':CassNo
|
||||
OnHold = Xlate('WO_MAT', WOMatKey, 'HOLD', 'X')
|
||||
If OnHold NE True$ then
|
||||
IF (MemberOf(@USER4,'MASTER_SCHED')) |
|
||||
OR (MemberOf(@USER4,'SUPERVISOR')) |
|
||||
OR (MemberOf(@USER4,'ENGINEERING')) |
|
||||
OR (MemberOf(@USER4,'LEAD')) |
|
||||
OR (MemberOf(@USER4,'OI_ADMIN')) THEN
|
||||
RDSNo = Get_Property(@Window:'.RDS_NO', 'TEXT')
|
||||
If RDSNo NE '' then
|
||||
Parms = ''
|
||||
Parms<1> = RDSNo ; // Cassette to verify wafer count of.
|
||||
Parms<2> = 0 ; // Wafer count adjustment - 0 because converting box.
|
||||
Parms<3> = 'MU' ; // Wafer counter tool location
|
||||
Proceed = Dialog_Box('NDW_WAFER_COUNTER', @Window, Parms)
|
||||
If Proceed EQ True$ then
|
||||
Set_Property(@WINDOW,'SAVEWARN', False$)
|
||||
Send_Event(@WINDOW,'CLEAR')
|
||||
obj_WO_Mat('ChangeFlag',WOMatKey:@RM:FieldNo:@RM:CheckValue)
|
||||
IF Get_Status(errCode) THEN
|
||||
ErrMsg(errCode)
|
||||
END
|
||||
end else
|
||||
InvalidRequest = True$
|
||||
end
|
||||
end else
|
||||
InvalidRequest = True$
|
||||
ErrMsg('WARNING: Error starting wafer counter check. RDS No is missing.')
|
||||
end
|
||||
IF (MemberOf(@USER4,'MASTER_SCHED')) |
|
||||
OR (MemberOf(@USER4,'SUPERVISOR')) |
|
||||
OR (MemberOf(@USER4,'ENGINEERING')) |
|
||||
OR (MemberOf(@USER4,'LEAD')) |
|
||||
OR (MemberOf(@USER4,'OI_ADMIN')) THEN
|
||||
|
||||
WOMatRec = Database_Services("ReadDataRow", 'WO_MAT', WOMatKey)
|
||||
If Error_Services('NoError') then
|
||||
SAPBatchNo = WOMatRec<WO_MAT_SAP_BATCH_NO$>
|
||||
SAPTXDtm = WOMatRec<WO_MAT_SAP_TX_DTM$>
|
||||
AwaitingBatchNo = ( (SAPTXDtm NE '') and (SAPBatchNo EQ '') )
|
||||
FullBoxReject = (SAPBatchNo[-1, 1] = 'R')
|
||||
Begin Case
|
||||
Case AwaitingBatchNo
|
||||
InvalidRequest = True$
|
||||
ErrMsg('WARNING: Cassette ineligible to be converted as it is awaiting a batch number from SAP.')
|
||||
Case FullBoxReject
|
||||
InvalidRequest = True$
|
||||
ErrMsg('WARNING: Cassette ineligible to be converted as it is a full box reject.')
|
||||
Case Otherwise$
|
||||
Null
|
||||
End Case
|
||||
|
||||
If Not(InvalidRequest) then
|
||||
RDSNo = Get_Property(@Window:'.RDS_NO', 'TEXT')
|
||||
If RDSNo NE '' then
|
||||
Parms = ''
|
||||
Parms<1> = RDSNo ; // Cassette to verify wafer count of.
|
||||
Parms<2> = 0 ; // Wafer count adjustment - 0 because converting box.
|
||||
Parms<3> = 'MU' ; // Wafer counter tool location
|
||||
Proceed = Dialog_Box('NDW_WAFER_COUNTER', @Window, Parms)
|
||||
If Proceed EQ True$ then
|
||||
Set_Property(@WINDOW,'SAVEWARN', False$)
|
||||
Send_Event(@WINDOW,'CLEAR')
|
||||
obj_WO_Mat('ChangeFlag',WOMatKey:@RM:FieldNo:@RM:CheckValue)
|
||||
IF Get_Status(errCode) THEN
|
||||
ErrMsg(errCode)
|
||||
END
|
||||
end else
|
||||
InvalidRequest = True$
|
||||
end
|
||||
end else
|
||||
InvalidRequest = True$
|
||||
ErrMsg('WARNING: Error starting wafer counter check. RDS No is missing.')
|
||||
end
|
||||
end
|
||||
end else
|
||||
InvalidRequest = True$
|
||||
ErrMsg('ERROR: Error reading WO_MAT record.')
|
||||
end
|
||||
END ELSE
|
||||
InvalidRequest = True$
|
||||
ErrMsg('INFO: This function is limited to authorized users only.')
|
||||
ErrMsg('INFO: This function is limited to members of MASTER_SCHED, SUPERVISOR, ENGINEERING, or LEAD security groups.')
|
||||
END
|
||||
end else
|
||||
InvalidRequest = True$
|
||||
@ -1195,6 +1201,3 @@ LogRecord:
|
||||
|
||||
return
|
||||
|
||||
|
||||
|
||||
|
||||
|
Reference in New Issue
Block a user