Merged PR 11767: NCR hold removal prompt
This commit is contained in:
parent
87d79edef8
commit
779ed0ba29
2
.gitignore
vendored
2
.gitignore
vendored
@ -1,4 +1,2 @@
|
||||
LSL2/STPROC/TEST_DANIEL3.txt
|
||||
LSL2/STPROC/TEST_DAKOTA.txt
|
||||
LSL2/STPROC/TEST_DAKOTA.txt
|
||||
LSL2/STPROC/TEST_DAKOTA.txt
|
||||
|
3262
LSL2/OIWIN/NDW_HOLD_REMOVAL_PROMPT.json
Normal file
3262
LSL2/OIWIN/NDW_HOLD_REMOVAL_PROMPT.json
Normal file
File diff suppressed because it is too large
Load Diff
@ -4,13 +4,14 @@ 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
|
||||
DECLARE SUBROUTINE Btree.Extract, Send_Event, Security_Err_Msg, Forward_Event, End_Window, Start_Window
|
||||
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
|
||||
DECLARE FUNCTION Dialog_Box, obj_WO_Log, obj_NCR, MemberOf, WM_IN_Services, Hold_Services, Database_Services, Datetime
|
||||
|
||||
|
||||
$INSERT POPUP_EQUATES
|
||||
@ -558,127 +559,162 @@ RejMat:
|
||||
SelectedRows = SlotSelection<2>
|
||||
|
||||
CONVERT @VM TO @FM in SelectedRows
|
||||
|
||||
SelCnt = COUNT(SelectedRows,@FM) + (SelectedRows NE '')
|
||||
IF SelCnt = 0 THEN RETURN
|
||||
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 = ''
|
||||
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
|
||||
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
|
||||
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
|
||||
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)
|
||||
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 * * * *
|
||||
END ELSE
|
||||
RejDTM = OCONV(Date(),'D4/'):' ':OCONV(Time(),'MTS')
|
||||
|
||||
RejWfrID = WONo:'*':InCassNos<1,N>:'*':InSlotNos<1,N>
|
||||
RejWfrIDs = ''
|
||||
NewSlotIDs = ''
|
||||
CurrSlotIDs = ''
|
||||
RunLocs = ''
|
||||
|
||||
RejWfrIDs<1,-1> = RejWfrID
|
||||
CurrSlotIDs<1,-1> = RejWfrID ;*Inbound box WfrID = SlotID
|
||||
FOR N = 1 TO COUNT(InSlotNos,@VM) + (InSlotNos NE '')
|
||||
|
||||
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
|
||||
* * * * 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)
|
||||
|
||||
* * * * *
|
||||
obj_WO_Wfr('AddEvent',Parms)
|
||||
|
||||
LineNo = InSlotNos<1,N>
|
||||
* * * * *
|
||||
|
||||
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
|
||||
|
||||
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
|
||||
END
|
||||
|
||||
Set_Property(@WINDOW:'.SLOT','SELPOS',SlotSelection) ;* Toggle WM_IN select off
|
||||
|
||||
Send_Event(@WINDOW,'WRITE')
|
||||
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
|
||||
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
|
||||
|
||||
|
||||
@ -813,3 +849,4 @@ RETURN
|
||||
|
||||
|
||||
|
||||
|
||||
|
@ -11,12 +11,13 @@ COMPILE FUNCTION Comm_WM_Out(Instruction, Parm1,Parm2)
|
||||
with the current WM_OUT record have metrology run data.
|
||||
08/26/2019 - DJS - Updated the RDS Metrology verification section to use RDS_Services('VerifyEPPMetrology'), which
|
||||
contains code adapted from the RDS_POST_EPI FQA sign button event.
|
||||
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, Set_List_Box_Data, obj_Post_Log
|
||||
DECLARE SUBROUTINE Btree.Extract, Send_Event, Security_Err_Msg, Forward_Event, End_Window, Start_Window, obj_WO_Mat_Log
|
||||
DECLARE SUBROUTINE Send_Message, Print_Cass_Out, obj_WM_Out, obj_Notes, obj_WO_Mat, obj_Tables, Set_Property, obj_WO_Wfr
|
||||
DECLARE SUBROUTINE Start_Window, Obj_RDS, Database_Services, Rds_Services, Signature_Services, Wm_Out_Services
|
||||
DECLARE SUBROUTINE Start_Window, Obj_RDS, Database_Services, Rds_Services, Signature_Services, Wm_Out_Services, Sleepery
|
||||
DECLARE SUBROUTINE Logging_Services, Wo_Mat_Qa_Services, Error_Services, Post_Event, Wafer_Counter_Services, Hold_Services
|
||||
|
||||
DECLARE FUNCTION Get_Property, Get_Status, Popup, Send_Message, Msg, Security_Check, Dialog_Box, RowExists, obj_Tables
|
||||
@ -1278,20 +1279,53 @@ RejMat:
|
||||
WMOKey = WONo:'*':WOStep:'*':OutCassNo
|
||||
WMOStatus = Xlate('WM_OUT', WMOKey, 'CURR_STATUS', 'X')
|
||||
OnHold = (WMOStatus EQ 'HOLD')
|
||||
If Onhold NE True$ then
|
||||
GoSub FQAVerify
|
||||
If Not(Authorized) then Return 0
|
||||
Result = ''
|
||||
|
||||
SlotSelection = Get_Property(@WINDOW:'.SLOT','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
|
||||
|
||||
GoSub FQAVerify
|
||||
If Not(Authorized) then Return 0
|
||||
|
||||
If OnHold EQ True$ then
|
||||
Result = Dialog_Box('NDW_HOLD_REMOVAL_PROMPT',@WINDOW,'WM_OUT':@VM:WMOKey:@VM:WOMatKey)
|
||||
If Result NE True$ then
|
||||
Return
|
||||
end else
|
||||
Send_Event(@Window, 'READ')
|
||||
end
|
||||
end
|
||||
If (OnHold NE True$) OR (Result = True$) then
|
||||
OffHoldDTMs = Xlate('WO_MAT', WOMatKey, 'HOLD_STOP_DTM', 'X')
|
||||
SAPBatchNo = Xlate('WO_MAT', WOMatKey, WO_MAT_SAP_BATCH_NO$, '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
|
||||
|
||||
|
||||
WMOutList = Get_Property(@WINDOW:'.SLOT','LIST')
|
||||
|
||||
SlotSelection = Get_Property(@WINDOW:'.SLOT','SELPOS')
|
||||
SelectedRows = SlotSelection<2>
|
||||
|
||||
CONVERT @VM TO @FM in SelectedRows
|
||||
|
||||
SelCnt = COUNT(SelectedRows,@FM) + (SelectedRows NE '')
|
||||
IF SelCnt = 0 THEN RETURN
|
||||
|
||||
InCassNos = ''
|
||||
InSlotNos = ''
|
||||
RDSNos = ''
|
||||
@ -1448,10 +1482,6 @@ RejMat:
|
||||
|
||||
obj_Appwindow('ViewNewDetail',DetWindow:@RM:DetKeys:@RM:DefaultRec:@RM:RetKey:@RM:RetPage:@RM:RetCtrl:@RM:RetPos)
|
||||
End
|
||||
end else
|
||||
// Cassette is on hold so material cannot be rejected.
|
||||
ErrorMessage = 'Create NCR denied!. The cassette must be taken off hold before rejecting material.'
|
||||
Msg(@Window, '', 'OK', '', 'Error':@FM:ErrorMessage)
|
||||
end
|
||||
|
||||
RETURN
|
||||
@ -2268,3 +2298,4 @@ RefreshWaferCounterData:
|
||||
return
|
||||
|
||||
|
||||
|
||||
|
@ -10,6 +10,7 @@ COMPILE FUNCTION Comm_WO_Mat_Wfr(Instruction, Parm1,Parm2)
|
||||
01/04/2019 - djs - Fixed an issue within the "Refresh" subroutine, which was preventing the "SLOT_NO" edit table
|
||||
from being colored correctly. The coloring code was moved to be executed after the section of
|
||||
code responsible for coloring edit tables with symbolic fields.
|
||||
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, Logging_Services
|
||||
@ -379,15 +380,39 @@ RejMat:
|
||||
CassNo = Get_Property(@Window:'.CASS_NO', 'TEXT')
|
||||
WOMatKey = WONo:'*':CassNo
|
||||
OnHold = Xlate('WO_MAT', WOMatKey, 'HOLD', 'X')
|
||||
If OnHold NE True$ then
|
||||
|
||||
Result = ''
|
||||
|
||||
SlotList = Get_Property('WO_MAT_WFR.SLOT_NO','LIST')
|
||||
SlotSelection = Get_Property('WO_MAT_WFR.SLOT_NO','SELPOS')
|
||||
SelectedRows = SlotSelection<2>
|
||||
CONVERT @VM TO @FM in SelectedRows
|
||||
|
||||
SelCnt = DCount(SelectedRows, @FM)
|
||||
IF SelCnt = 0 THEN
|
||||
ErrMsg('You must select at least one row in order to create an NCR.')
|
||||
RETURN
|
||||
END
|
||||
|
||||
GoSub FQAVerify
|
||||
If Not(Authorized) then Return 0
|
||||
|
||||
If OnHold EQ True$ then
|
||||
Result = Dialog_Box('NDW_HOLD_REMOVAL_PROMPT',@WINDOW,'WO_MAT':@VM:WOMatKey:@VM:WOMatKey)
|
||||
If Result NE True$ then
|
||||
Return 0
|
||||
end else
|
||||
Send_Event(@Window, 'READ')
|
||||
end
|
||||
end
|
||||
If (OnHold NE True$) OR (Result = True$) then
|
||||
OffHoldDTMs = Xlate('WO_MAT', WOMatKey, 'HOLD_STOP_DTM', 'X')
|
||||
SAPBatchNo = Xlate('WO_MAT', WOMatKey, WO_MAT_SAP_BATCH_NO$, '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' then
|
||||
If (TimeElapsed LT '.000694') AND (SAPBatchNo NE '') then
|
||||
Def = ""
|
||||
Def<MTEXT$> = "Please wait for SAP to process off hold transaction..."
|
||||
Def<MTYPE$> = "U"
|
||||
@ -400,19 +425,9 @@ RejMat:
|
||||
end
|
||||
end
|
||||
|
||||
GoSub FQAVerify
|
||||
If Not(Authorized) then Return 0
|
||||
|
||||
SlotList = Get_Property('WO_MAT_WFR.SLOT_NO','LIST')
|
||||
SlotSelection = Get_Property('WO_MAT_WFR.SLOT_NO','SELPOS')
|
||||
SelectedRows = SlotSelection<2>
|
||||
CONVERT @VM TO @FM in SelectedRows
|
||||
|
||||
SelCnt = DCount(SelectedRows, @FM)
|
||||
IF SelCnt = 0 THEN
|
||||
ErrMsg('You must select at least one row in order to create an NCR.')
|
||||
RETURN
|
||||
END
|
||||
|
||||
|
||||
IneligibleSlots = ''
|
||||
AllSlotsPermitted = True$ ; // Assume that all slots are permitted to be NCR'd for now.
|
||||
@ -555,11 +570,7 @@ RejMat:
|
||||
rv = Dialog_Box('NCR', @WINDOW, NCRNo)
|
||||
Send_Event(@WINDOW, 'READ')
|
||||
end
|
||||
end else
|
||||
// Cassette is on hold so material cannot be rejected.
|
||||
ErrorMessage = 'Create NCR denied!. The cassette must be taken off hold before rejecting material.'
|
||||
Msg(@Window, '', 'OK', '', 'Error':@FM:ErrorMessage)
|
||||
end
|
||||
end
|
||||
|
||||
RETURN
|
||||
|
||||
@ -1204,3 +1215,4 @@ LogRecord:
|
||||
|
||||
return
|
||||
|
||||
|
||||
|
@ -1,7 +1,7 @@
|
||||
Compile function Hold_Services(@Service, @Params)
|
||||
/***********************************************************************************************************************
|
||||
|
||||
Name : Hols_Services
|
||||
Name : Hold_Services
|
||||
|
||||
Description : Handler program for all Hold services.
|
||||
|
||||
|
136
LSL2/STPROC/NDW_HOLD_REMOVAL_PROMPT_EVENTS.txt
Normal file
136
LSL2/STPROC/NDW_HOLD_REMOVAL_PROMPT_EVENTS.txt
Normal file
@ -0,0 +1,136 @@
|
||||
Compile function NDW_HOLD_REMOVAL_PROMPT_EVENTS(CtrlEntId, Event, @PARAMS)
|
||||
/***********************************************************************************************************************
|
||||
|
||||
This program is proprietary and is not to be used by or disclosed to others, nor is it to be copied without written
|
||||
permission from Infineon.
|
||||
|
||||
Name : NDW_HOLD_REMOVAL_PROMPT_EVENTS
|
||||
Description : This function acts as a commuter module for all events related to this window.
|
||||
|
||||
Notes : Commuter Modules are automatically called from the Promoted_Events function which is called by the
|
||||
application-specific promoted event handler. This makes it possible to add QuickEvents that need to
|
||||
execute Basic+ logic without having use the Form Designer to make the association, although this is
|
||||
limited to the events which are currently promoted.
|
||||
|
||||
If the form needs to call the commuter module directly then the QuickEvent parameters should be
|
||||
formatted like this:
|
||||
|
||||
'@SELF','@EVENT',['@PARAM1','@PARAMx']
|
||||
|
||||
Parameters :
|
||||
CtrlEntId [in] -- The fully qualified name of the control calling the promoted event
|
||||
Event [in] -- The event being executed. See the Notes section regarding "PRE" events
|
||||
Param1-15 [in] -- Additional event parameter holders
|
||||
EventFlow [out] -- Set to 1 or 0 so the calling event knows whether or not to chain forward. See comments in
|
||||
EVENT_SETUP insert
|
||||
|
||||
History : (Date, Initials, Notes)
|
||||
2/17/25 djm Initial programmer
|
||||
|
||||
***********************************************************************************************************************/
|
||||
#pragma precomp SRP_PreCompiler
|
||||
#window NDW_HOLD_REMOVAL_PROMPT
|
||||
|
||||
$Insert WO_MAT_EQUATES
|
||||
$Insert LOGICAL
|
||||
|
||||
Declare Subroutine Set_Property, Form_Services, Hold_Services, Error_Services, End_Dialog
|
||||
Declare function Get_Property, Hold_Services, Error_Services, End_Dialog
|
||||
|
||||
GoToEvent Event for CtrlEntId else
|
||||
// Event not implemented
|
||||
end
|
||||
|
||||
Return EventFlow or 1
|
||||
|
||||
//-----------------------------------------------------------------------------
|
||||
// EVENT HANDLERS
|
||||
//-----------------------------------------------------------------------------
|
||||
|
||||
Event WINDOW.CREATE(CreateParam)
|
||||
|
||||
EventFlow = 1
|
||||
EntityType = Field(Param1, @VM, 1)
|
||||
EntityID = Field(Param1, @VM, 2)
|
||||
WOMatKey = Field(Param1, @VM, 3)
|
||||
Gosub PopulateHold
|
||||
|
||||
End Event
|
||||
|
||||
Event EDB_REMOVAL_REASON.CHAR(VirtCode, ScanCode, CtrlKey, ShiftKey, AltKey)
|
||||
|
||||
Reason = Get_Property(CtrlEntId, 'TEXT')
|
||||
|
||||
If ( (Reason NE '') AND (Len(Reason) LE 255) ) or ( (Reason NE '') ) then
|
||||
Set_Property(@Window : '.PUB_OK', 'ENABLED', True$)
|
||||
end else
|
||||
Set_Property(@Window : '.PUB_OK', 'ENABLED', False$)
|
||||
end
|
||||
|
||||
End Event
|
||||
|
||||
|
||||
Event PUB_OK.CLICK()
|
||||
|
||||
Result = ''
|
||||
HoldType = ''
|
||||
EntityType = Get_Property(@Window: '.EDL_ENTITY_TYPE', 'TEXT')
|
||||
EntityID = Get_Property(@Window: '.EDL_ENTITY_ID', 'TEXT')
|
||||
WOMatKey = Get_Property(@Window: '.EDL_WO_MAT', 'TEXT')
|
||||
Reason = Get_Property(@Window: '.EDB_REMOVAL_REASON', 'TEXT')
|
||||
WOMatRec = Xlate('WO_MAT', WOMatKey, '', 'X')
|
||||
If WOMatRec NE '' then
|
||||
If WOMatRec<WO_MAT_SHIP_HOLD$,1> EQ True$ then
|
||||
HoldType = 'SHOLD'
|
||||
end else
|
||||
HoldType = 'HOLD'
|
||||
end
|
||||
If Reason NE '' then
|
||||
If EntityType NE '' AND EntityType NE '' AND WOMatKey NE '' then
|
||||
HoldData = @User4:@FM:Reason:@FM:''
|
||||
Hold_Services('OffHold', WOMatKey, EntityType, EntityID, HoldType, HoldData, @User4, '')
|
||||
If Error_Services('NoError') then
|
||||
Result = True$
|
||||
End_Dialog(@Window, Result)
|
||||
end else
|
||||
Errors = Error_Services('GetMessages')
|
||||
Result = Errors
|
||||
End_Dialog(@Window, Result)
|
||||
end
|
||||
end
|
||||
end
|
||||
end
|
||||
|
||||
end event
|
||||
|
||||
|
||||
|
||||
////////////////////////////////////////////////////////////////////////////////////////////////////////////////////////
|
||||
// Internal GoSubs
|
||||
////////////////////////////////////////////////////////////////////////////////////////////////////////////////////////
|
||||
|
||||
PopulateHold:
|
||||
|
||||
Set_Property(@Window: '.EDL_ENTITY_TYPE', 'TEXT', EntityType)
|
||||
Set_Property(@Window: '.EDL_ENTITY_ID', 'TEXT', EntityID)
|
||||
Set_Property(@Window: '.EDL_WO_MAT', 'TEXT', WOMatKey)
|
||||
WOMatRec = Xlate('WO_MAT', WOMatKey, '', 'X')
|
||||
|
||||
If WOMatRec<WO_MAT_SHIP_HOLD$> NE True$ then
|
||||
Set_Property(@Window: '.EDL_DATETIME', 'TEXT', Oconv(WOMatRec<WO_MAT_HOLD_START_DTM$,1>, 'D4-'))
|
||||
Set_Property(@Window: '.EDL_USER_ID', 'TEXT', WOMatRec<WO_MAT_HOLD_START_USER$,1>)
|
||||
UserName = OCONV(WOMatRec<WO_MAT_HOLD_START_USER$,1>,'[XLATE_CONV,LSL_USERS*FIRST_LAST]')
|
||||
Set_Property(@Window: '.EDL_USER_NAME', 'TEXT', UserName)
|
||||
Set_Property(@Window: '.EDB_HOLD_REASON', 'TEXT', WOMatRec<WO_MAT_HOLD_START_REASON$,1>)
|
||||
Set_Property(@Window: '.CHK_EXTENDED', 'CHECK', WOMatRec<WO_MAT_HOLD_EXTENDED$,1>)
|
||||
end else
|
||||
Set_Property(@Window: '.EDL_DATETIME', 'TEXT', Oconv(WOMatRec<WO_MAT_SHIP_HOLD_START_DTM$,1>, 'D4-'))
|
||||
Set_Property(@Window: '.EDL_USER_ID', 'TEXT', WOMatRec<WO_MAT_SHIP_HOLD_START_USER$,1>)
|
||||
UserName = OCONV(WOMatRec<WO_MAT_SHIP_HOLD_START_USER$,1>,'[XLATE_CONV,LSL_USERS*FIRST_LAST]')
|
||||
Set_Property(@Window: '.EDL_USER_NAME', 'TEXT', UserName)
|
||||
Set_Property(@Window: '.EDB_HOLD_REASON', 'TEXT', WOMatRec<WO_MAT_SHIP_HOLD_START_REASON$,1>)
|
||||
Set_Property(@Window: '.CHK_EXTENDED', 'CHECK', WOMatRec<WO_MAT_SHIP_HOLD_EXTENDED$,1>)
|
||||
end
|
||||
|
||||
return
|
||||
|
Loading…
x
Reference in New Issue
Block a user