COMPILE FUNCTION Dialog_QA_Label_Check(EntID,Event,Parm1,Parm2,Parm3,Parm4,Parm5) #pragma precomp SRP_PreCompiler /* Commuter module for Dialog_QA_LabelCehck (QA Label CHeck - Barcode Scan) window 2/22/2016 John C. Henry, J.C. Henry & Co., Inc. */ DECLARE SUBROUTINE Set_Property, Set_Status, ErrMsg, Set_Property, Dialog_Box, obj_WO_Mat_Log DECLARE SUBROUTINE Btree.Extract, Send_Event, Security_Err_Msg, obj_Appwindow, End_Dialog, Post_Event DECLARE SUBROUTINE Send_Message, Print_Cass_Ship_Label, Print_SAP_Cass_Ship_Label, obj_Notes DECLARE FUNCTION Get_Property, Get_Status, Popup, Send_Message, Msg, Security_Check, Dialog_Box DECLARE FUNCTION Dialog_Box, Utility, obj_WO_Mat, Signature_Services $INSERT MSG_EQUATES $INSERT APPCOLORS $INSERT LSL_USERS_EQU $INSERT SECURITY_RIGHTS_EQU $Insert REACT_RUN_EQUATES $Insert WM_IN_EQUATES $Insert WM_OUT_EQUATES $Insert WO_MAT_EQUATES $Insert WO_LOG_EQUATES $Insert RDS_EQUATES $Insert NOTIFICATION_EQUATES $Insert LOGICAL EQU CRLF$ TO \0D0A\ EQU COL$TOP_LABEL TO 1 EQU COL$BOTTOM_LABEL TO 2 EQU COL$LOT_NO TO 3 EQU COL$IFX_LABEL TO 4 EQU COL$RESULT TO 5 EQU COL$WOLOGKEY TO 6 ErrTitle = 'Error in Dialog_QALabel_Check' ErrorMsg = '' Result = '' BEGIN CASE CASE EntID = @WINDOW BEGIN CASE CASE Event = 'CREATE' ; GOSUB Create CASE Event = 'CLOSE' ; GOSUB Done END CASE CASE EntID = @WINDOW:'.DONE_BUTTON' AND Event = 'CLICK' ; GOSUB Done CASE EntID = @WINDOW:'.CASS_IDS' AND Event = 'POSCHANGED' ; GOSUB CassIdPC 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: * * * * * * * obj_Appwindow('Create',@WINDOW) GOSUB Refresh RETURN * * * * * * * Refresh: * * * * * * * WindowLabel = Get_Property(@WINDOW:'.WINDOW_LABEL','TEXT') RETURN * * * * * * * * Done: * * * * * * * * End_Dialog(@WINDOW,'') RETURN ********* CassIdPC: ********* //IF @UserName = 'FRANCOIS_R' OR @UserName = 'DAN_CR' THEN debug CtrlEntID = @WINDOW:'.CASS_IDS' PrevSelPos = Get_Property(CtrlEntId,"PREVSELPOS") PrevCol = PrevSelPos<1> PrevRow = PrevSelPos<2> CurrPos = Get_Property(CtrlEntId,"SELPOS") CurrCol = CurrPos<1> CurrRow = CurrPos<2> ListData = Get_Property(CtrlEntId,'LIST') ArrayData = Get_Property(CtrlEntId,'ARRAY') MismatchDetected = False$ /* No mismatch */ CellValue = TRIM(Send_Message(CtrlEntID, "TEXT_BY_POS", CurrCol, CurrRow)) IF (CellValue = '') THEN ColPointer = CurrCol LinePointer = CurrRow ColCnt = 5 /* Find the first non-empty cell */ LOOP Test = TRIM(Send_Message(CtrlEntID, "TEXT_BY_POS", ColPointer, LinePointer)) UNTIL Test NE '' OR (LinePointer = 0 AND ColPointer = 1) ColPointer = ColPointer - 1 IF ColPointer = 0 THEN ColPointer = ColCnt LinePointer = LinePointer - 1 END REPEAT /* Move to the next empty cell */ BEGIN CASE CASE LinePointer = 0 * Empty Table LinePointer = 1 ColPointer = 1 CASE ColPointer = ColCnt LinePointer = LinePointer + 1 ColPointer = 1 CASE 1 ColPointer = ColPointer + 1 END CASE Set_Property("SYSTEM", "BLOCK_EVENTS", True$) Set_Property(CtrlEntId, "SELPOS", ColPointer:@FM:LinePointer) Set_Property("SYSTEM", "BLOCK_EVENTS", False$) END ***************************** * Post Prompt for Top Label * ***************************** TopLabel = TRIM(Send_Message(CtrlEntID, "TEXT_BY_POS", COL$TOP_LABEL, PrevRow)) IF TopLabel[1,2] = '1T' THEN TopLabel = TopLabel[3,99] Set_Property(CtrlEntId,"CELLPOS",TopLabel,PrevSelPos) END IF ((TopLabel NE '') AND (PrevCol = COL$TOP_LABEL)) THEN Set_Property(@WINDOW,'@EPIPRO_FLAG',0) BEGIN CASE CASE TopLabel[1,1] = 'I' * WM_IN table TopLabel = TopLabel[2,99] WOMatKey = FIELD(TopLabel,'.',1):'*':FIELD(TopLabel,'.',3) Set_Property(CtrlEntID, "CELLPOS", TopLabel, PrevSelPos) Set_Property(@WINDOW,'@EPIPRO_FLAG',1) CASE TopLabel[1,1] = 'O' * EpiPro Silicon or GaN TopLabel = TopLabel[2,99] WONo = TopLabel[1, 'F.'] CassNo = TopLabel[-1, 'B.'] WOMatKey = WONo:'*':CassNo Set_Property(CtrlEntID, "CELLPOS", TopLabel, PrevSelPos) If (Count(TopLabel, '.') EQ 2) then // EpiPro Set_Property(@WINDOW,'@EPIPRO_FLAG',1) end else // GaN Set_Property(@WINDOW,'@GAN_FLAG',1) end CASE INDEX(TopLabel,'.',1) AND NOT(INDEX(TopLabel,'.',2)) * This is a WO_MAT format label WOMatKey = TopLabel Convert '.' To '*' In WOMatKey CASE INDEX(TopLabel,'.',2) * EpiPRO material indeterminate direction WOMatKey = FIELD(TopLabel,'.',1):'*':Field(TopLabel,'.',3) Set_Property(@WINDOW,'@EPIPRO_FLAG',1) CASE 1 ReactRunRec = XLATE('REACT_RUN', TopLabel, '', 'X') IF ReactRunRec = '' THEN RDSRec = XLATE('RDS',TopLabel,'','X') TestWO = RDSRec CassNo = RDSRec END ELSE TestWO = ReactRunRec CassNo = ReactRunRec End WOMatKey = TestWO:'*':CassNo END CASE WOMatRec = XLATE('WO_MAT', WOMatKey, '', 'X') IF (WOMatRec = '') THEN Set_Property(CtrlEntID, "CELLPOS", '', PrevSelPos) ;* No corresponding data record found for label scanned bad read or wrong thing scanned Set_Property("SYSTEM", "BLOCK_EVENTS", True$) Set_Property(CtrlEntID, "SELPOS", PrevSelPos) Set_Property("SYSTEM", "BLOCK_EVENTS", False$) RETURN END ELSE Set_Property(CtrlEntID, "CELLPOS", FIELD(WOMatKey,'*',1), COL$WOLOGKEY:@FM:PrevRow) * * Check for FQA signature completed * * FQASigned = '' WorkOrdNo = Field(WOMatKey, '*', 1) ReactorType = XLATE('WO_LOG', WorkOrdNo, 'REACT_TYPE', 'X') QAStage = '' Begin Case Case ReactorType EQ 'EPP' QAStage = 'MO_QA' Case ReactorType EQ 'GAN' QAStage = 'G_FQA' Case Otherwise$ QAStage = 'QA' End Case FQASigned = Signature_Services('CheckSignature', WOMatKey, QAStage) IF NOT(FQASigned) THEN Msg(@WINDOW, '', 'UNSIGNED_CASSETTE') Set_Property(CtrlEntID, "CELLPOS", '', PrevSelPos) ;* No corresponding data record found for label scanned bad read or wrong thing scanned Set_Property("SYSTEM", "BLOCK_EVENTS", True$) Set_Property(CtrlEntID, "SELPOS", PrevSelPos) Set_Property("SYSTEM", "BLOCK_EVENTS", False$) RETURN END Set_Property(@WINDOW,'@WO_MAT_KEY',WOMatKey) Set_Property(@WINDOW,'@WO_MAT_LOT',WOMatRec) END END ******************************** * Post Prompt for Bottom Label * ******************************** TopLabel = TRIM(Send_Message(CtrlEntID, "TEXT_BY_POS", COL$TOP_LABEL, PrevRow)) BottomLabel = TRIM(Send_Message(CtrlEntID, "TEXT_BY_POS", COL$BOTTOM_LABEL, PrevRow)) IF BottomLabel[1,2] = '1T' THEN BottomLabel = BottomLabel[3,99] Set_Property(CtrlEntId,"CELLPOS",BottomLabel,PrevSelPos) END IF ((BottomLabel NE '') AND (PrevCol = COL$BOTTOM_LABEL)) Then BEGIN CASE CASE BottomLabel[1,1] = 'I' * WM_IN table BottomLabel = BottomLabel[2,99] Set_Property(CtrlEntID, "CELLPOS", BottomLabel, PrevSelPos) CASE BottomLabel[1,1] = 'O' * WM_OUT table BottomLabel = BottomLabel[2,99] Set_Property(CtrlEntID, "CELLPOS", BottomLabel, PrevSelPos) CASE INDEX(BottomLabel,'.',1) AND NOT(INDEX(BottomLabel,'.',2)) * This is a WO_MAT format label NULL CASE INDEX(BottomLabel,'.',2) * EpiPRO material indeterminate direction NULL CASE 1 NULL END CASE ************************************ * Validate the Top & Bottom Labels * ************************************ IF (TopLabel NE BottomLabel) THEN MismatchDetected = True$ /* Mismatch Detected */ void = Utility('BEEP') Set_Property(CtrlEntID, "CELLPOS", 'Mismatch', COL$RESULT:@FM:PrevRow) /* Load Current Location */ stat = Send_Message(CtrlEntID, 'COLOR_BY_POS', 0, PrevRow, RED$) Set_Property("SYSTEM", "BLOCK_EVENTS", True$) Set_Property(CtrlEntID, "SELPOS", COL$TOP_LABEL:@FM:PrevRow+1) /* Move to the next line ready to scan */ Set_Property("SYSTEM", "BLOCK_EVENTS", False$) InsertedPosition = Send_Message(CtrlEntID, "INSERT", -1, '') TypeOver = '' TypeOver = 'FQA Label Mismatch' TypeOver = CRLF$:'Label ID Mismatch!':CRLF$ OK = Msg(@WINDOW,TypeOver,'LABEL_MISMATCH') * Inform Quality Insurance that a mismatch has occurred * Recipients = '' OtherRecipients = XLATE('NOTIFICATION','LABEL_CHECK_FQA',NOTIFICATION_USER_ID$,'X') ;* Added 10/03/2005 JCH - J.C. Henry & Co., Inc Changed from LABEL_MISMATCH by dkk 11/6/15 FOR N = 1 TO COUNT(OtherRecipients,@VM) + (OtherRecipients NE '') OtherRecip = OtherRecipients<1,N> LOCATE OtherRecip IN Recipients USING @VM SETTING Pos ELSE Recipients = INSERT(Recipients,1,Pos,0,OtherRecip) END NEXT N SentFrom = @USER4 Subject = 'Final QA Label Check Mismatch' Message = 'Cassette Top ID ':QUOTE(TopLabel):' has mismatched Bottom ID ':QUOTE(BottomLabel)'.' AttachWindow = '' AttachKey = '' SendToGroup = '' Parms = Recipients:@RM:SentFrom:@RM:Subject:@RM:Message:@RM:AttachWindow:@RM:AttachKey:@RM:SendToGroup obj_Notes('Create',Parms) IF Num(TopLabel) THEN RDSNo = TopLabel ReactRunRec = XLATE('REACT_RUN', RDSNo, '', 'X') WONo = ReactRunRec StepNo = ReactRunRec CassNo = ReactRunRec END ELSE IF TopLabel[1,1] = 'O' THEN TopLabel[1,1] = '' IF TopLabel[1,1] = 'I' THEN TopLabel[1,1] = '' WONo = FIELD(TopLabel,'.',1) StepNo = FIELD(TopLabel,'.',2) CassNo = FIELD(TopLabel,'.',3) RDSNo = '' END * Setup parameters to WO_Mat_Log method * CurrDTM = OCONV(Date(),'D2/'):' ':OCONV(Time(),'MTS') UserID = @USER4 IF UserID = '' THEN UserID = @USERNAME LogFile = 'WO_MAT' ;* Changed so all scans are logged in the WO_MAT table 12/3/2006 Action = 'LBLCHK' ;* Final label check for same top and bottom and correct Lot Number on WO_MAT record WHCd = 'CR' ;* Clean room @ final QA LocCd = 'QA' ;* MisMatch - keep the cassette location at Final QA Set_Status(0) obj_WO_Mat_Log('Create',LogFile:@RM:CurrDTM:@RM:Action:@RM:WhCd:@RM:LocCd:@RM:WONo:@RM:CassNo:@RM:UserID:@RM:'Mismatch') IF Get_Status(errCode) THEN Errmsg(errCode) END END /* End of check for top & bottom labels check */ END /* End of check for bottom label available */ ********************** * Process Lot Number * ********************** IF (MismatchDetected = False$) THEN LotNumber = TRIM(Send_Message(CtrlEntID, "TEXT_BY_POS", COL$LOT_NO, PrevRow)) IF ((TopLabel NE '') AND (BottomLabel NE '') AND (LotNumber = '')) THEN EpiProFlag = Get_Property(@WINDOW, '@EPIPRO_FLAG') GaNFlag = Get_Property(@WINDOW, '@GAN_FLAG') Begin Case Case EpiProFlag EQ True$ LotNumber = 'EpiPRO' Set_Property(CtrlEntID, "CELLPOS", LotNumber, COL$LOT_NO:@FM:PrevRow) Case GaNFlag EQ True$ LotNumber = 'GaN' Set_Property(CtrlEntID, "CELLPOS", LotNumber, COL$LOT_NO:@FM:PrevRow) End Case END IF ((LotNumber NE '') AND (PrevCol = COL$LOT_NO)) THEN *************************** * Validate the Lot Number * *************************** IF (LotNumber NE 'EpiPRO' and LotNumber NE 'GaN') THEN IF ((LotNumber[1,2] = '1T') OR (LotNumber[1,2] = '2T')) THEN /* Trim off field identifiers (1T) or (2T) if present - changed by dkk 12/13/16 */ LotNumber[1,2] = '' Set_Property(CtrlEntID, "CELLPOS", LotNumber, COL$LOT_NO:@FM:PrevRow) END WOMatKey = Get_Property(@WINDOW,'@WO_MAT_KEY') WONo = WOMatKey[1,'*'] CassNo = WOMatKey[COL2()+1,'*'] WOMatLot = Get_Property(@WINDOW,'@WO_MAT_LOT') * * * Check for Wales added suffix "-BB" on implant wafers coming back * * * IF (WOMatLot[-3,1] = '-') AND (WOMatLot[-2,1] = WOMatLot[-1,1]) And WOMatLot[-2,2] Matches "2A" THEN IF LotNumber = WOMatLot[1,Len(WOMatLot) - 3] THEN LotNumber := WOMatLot[-3,3] END END ;* End of check for "-AA" type lot suffix added by Wales IF (LotNumber NE WOMatLot) THEN MismatchDetected = True$ /* Mismatch Detected */ void = Utility('BEEP') Set_Property(CtrlEntID, "CELLPOS", 'Mismatch',COL$RESULT:@FM:PrevRow) /* Load Current Location */ stat = Send_Message(CtrlEntID, 'COLOR_BY_POS', 0, PrevRow,RED$) Set_Property("SYSTEM", "BLOCK_EVENTS", True$) Set_Property(CtrlEntID, "SELPOS", COL$TOP_LABEL:@FM:PrevRow+1) /* Move to the next line ready to scan */ Set_Property("SYSTEM", "BLOCK_EVENTS", False$) InsertedPosition = Send_Message(CtrlEntID, "INSERT", -1, '') TypeOver = '' TypeOver = 'FQA Label Mismatch' TypeOver = CRLF$:'Lot No. Mismatch!':CRLF$ OK = Msg(@WINDOW,TypeOver,'LABEL_MISMATCH') /* Inform Quality Insurance that a mismatch has occurred */ Recipients = '' OtherRecipients = XLATE('NOTIFICATION','LABEL_CHECK_FQA',NOTIFICATION_USER_ID$,'X') ;* Added 10/03/2005 JCH - J.C. Henry & Co., Inc Changed from LABEL_MISMATCH by dkk 11/6/15 FOR N = 1 TO COUNT(OtherRecipients,@VM) + (OtherRecipients NE '') OtherRecip = OtherRecipients<1,N> LOCATE OtherRecip IN Recipients USING @VM SETTING Pos ELSE Recipients = INSERT(Recipients,1,Pos,0,OtherRecip) END NEXT N SentFrom = @USER4 Subject = 'Final QA Label Check Mismatch' Message = 'Cassette ':QUOTE(TopLabel):' has incorrect Lot No ':QUOTE(LotNumber)'.' AttachWindow = '' AttachKey = '' SendToGroup = '' Parms = Recipients:@RM:SentFrom:@RM:Subject:@RM:Message:@RM:AttachWindow:@RM:AttachKey:@RM:SendToGroup obj_Notes('Create',Parms) CurrDTM = OCONV(Date(),'D2/'):' ':OCONV(Time(),'MTS') UserID = @USER4 IF UserID = '' THEN UserID = @USERNAME LogFile = 'WO_MAT' ;* Changed so all scans are logged in the WO_MAT table 12/3/2006 Action = 'LBLCHK' ;* Final label check for same top and bottom and correct Lot Number on WO_MAT record WHCd = 'CR' ;* Clean room @ final QA LocCd = 'QA' ;* MisMatch - keep the cassette location at Final QA Set_Status(0) obj_WO_Mat_Log('Create',LogFile:@RM:CurrDTM:@RM:Action:@RM:WhCd:@RM:LocCd:@RM:WONo:@RM:CassNo:@RM:UserID:@RM:'Mismatch') IF Get_Status(errCode) THEN Errmsg(errCode) END END ELSE NULL END /* End of check for LotNumber and WOMatLot matching */ END ELSE NULL END /* End of check for EpiPro lot */ END /* End of check for lot number validation */ END ********************* * Process IFX Label * ********************* * IF (MismatchDetected = False$) THEN * * IFXValid = 0 * * /* Read scanned information from edit table */ * TopLabel = TRIM(Send_Message(CtrlEntID, "TEXT_BY_POS", COL$TOP_LABEL, PrevRow)) * BottomLabel = TRIM(Send_Message(CtrlEntID, "TEXT_BY_POS", COL$BOTTOM_LABEL, PrevRow)) * LotNumber = TRIM(Send_Message(CtrlEntID, "TEXT_BY_POS", COL$LOT_NO, PrevRow)) * WOLogKey = TRIM(Send_Message(CtrlEntID, "TEXT_BY_POS", COL$WOLOGKEY, PrevRow)) * * IF ((TopLabel NE '') AND (BottomLabel NE '') AND (LotNumber NE '') AND (WOLogKey NE '')) THEN * * /* Get the Customer Information */ * WOLogRec = XLATE('WO_LOG', WOLogKey, '', 'X') * IF (WOLogRec NE '') THEN * CustomerNo = WOLogRec * END ELSE * CustomerNo = '' * END * GaNFlag = Get_Property(@Window, '@GAN_FLAG') * IF (CustomerNo = '7112') | * OR (CustomerNo = '7113') | * OR (CustomerNo = '7114') | * OR (CustomerNo = '7115') | * OR (CustomerNo = '7116') | * OR (CustomerNo = '7118') | * OR (CustomerNo = '7121') | * OR (CustomerNo = '7123') | * AND (GaNFlag NE True$) THEN * * IFXLabel = TRIM(Send_Message(CtrlEntID, "TEXT_BY_POS", COL$IFX_LABEL, PrevRow)) * * IF ((IFXLabel NE '') AND (PrevCol = COL$IFX_LABEL)) THEN * * IF ((IFXLabel[1,2] = '1T') OR (IFXLabel[1,2] = '2T')) THEN * /* Trim off field identifiers (1T) or (2T) if present - changed by dkk 12/13/16 */ * IFXLabel[1,2] = '' * Set_Property(CtrlEntID, "CELLPOS", IFXLabel, COL$IFX_LABEL:@FM:PrevRow) * END * * ********************** * * Validate IFX Label * * ********************** * * IF (IFXLabel NE TopLabel) THEN * * MismatchDetected = True$ /* Mismatch Detected */ * * void = Utility('BEEP') * Set_Property(CtrlEntID, "CELLPOS", 'Mismatch', COL$RESULT:@FM:PrevRow) /* Load Current Location */ * stat = Send_Message(CtrlEntID, 'COLOR_BY_POS', 0, PrevRow, RED$) * Set_Property("SYSTEM", "BLOCK_EVENTS", True$) * Set_Property(CtrlEntID, "SELPOS", COL$TOP_LABEL:@FM:PrevRow+1) /* Move to the next line ready to scan */ * Set_Property("SYSTEM", "BLOCK_EVENTS", False$) * InsertedPosition = Send_Message(CtrlEntID, "INSERT", -1, '') * * TypeOver = '' * TypeOver = 'FQA Label Mismatch' * TypeOver = CRLF$:'IFX Label Mismatch!':CRLF$ * * OK = Msg(@WINDOW,TypeOver,'LABEL_MISMATCH') * * * Inform Quality Insurance that a mismatch has occurred * * * Recipients = '' * OtherRecipients = XLATE('NOTIFICATION','LABEL_CHECK_FQA',NOTIFICATION_USER_ID$,'X') ;* Added 10/03/2005 JCH - J.C. Henry & Co., Inc Changed from LABEL_MISMATCH by dkk 11/6/15 * * FOR N = 1 TO COUNT(OtherRecipients,@VM) + (OtherRecipients NE '') * OtherRecip = OtherRecipients<1,N> * LOCATE OtherRecip IN Recipients USING @VM SETTING Pos ELSE * Recipients = INSERT(Recipients,1,Pos,0,OtherRecip) * END * NEXT N * * SentFrom = @USER4 * Subject = 'Final QA Label Check Mismatch' * Message = 'Cassette IFX Label ':QUOTE(IFXLabel):' has mismatched Top Label ':QUOTE(TopLabel)'.' * AttachWindow = '' * AttachKey = '' * SendToGroup = '' * * Parms = Recipients:@RM:SentFrom:@RM:Subject:@RM:Message:@RM:AttachWindow:@RM:AttachKey:@RM:SendToGroup * obj_Notes('Create',Parms) * * IF Num(TopLabel) THEN * RDSNo = TopLabel * ReactRunRec = XLATE('REACT_RUN', RDSNo, '', 'X') * * WONo = ReactRunRec * StepNo = ReactRunRec * CassNo = ReactRunRec * * END ELSE * IF TopLabel[1,1] = 'O' THEN TopLabel[1,1] = '' * IF TopLabel[1,1] = 'I' THEN TopLabel[1,1] = '' * * WONo = FIELD(TopLabel,'.',1) * StepNo = FIELD(TopLabel,'.',2) * CassNo = FIELD(TopLabel,'.',3) * RDSNo = '' * END * * * Setup parameters to WO_Mat_Log method * * CurrDTM = OCONV(Date(),'D2/'):' ':OCONV(Time(),'MTS') * UserID = @USER4 * IF UserID = '' THEN UserID = @USERNAME * * LogFile = 'WO_MAT' ;* Changed so all scans are logged in the WO_MAT table 12/3/2006 * Action = 'LBLCHK' ;* Final label check for same top and bottom and correct Lot Number on WO_MAT record * WHCd = 'CR' ;* Clean room @ final QA * LocCd = 'QA' ;* MisMatch - keep the cassette location at Final QA * * Set_Status(0) * obj_WO_Mat_Log('Create',LogFile:@RM:CurrDTM:@RM:Action:@RM:WhCd:@RM:LocCd:@RM:WONo:@RM:CassNo:@RM:UserID:@RM:'Mismatch') * * IF Get_Status(errCode) THEN * Errmsg(errCode) * END * * END ELSE * /* IFX Lavel = Top Label */ * IFXValid = 1 * * END /* End of check for IFX label check */ * * END ELSE * NULL /* No IFX Label scanned yet */ * END * * END ELSE * Set_Property(CtrlEntID, "CELLPOS", 'N/A', COL$IFX_LABEL:@FM:PrevRow) * IFXValid = 1 * END * END * END ******************************** * Validate Scanned Information * ******************************** IF (MismatchDetected = False$) THEN /* Read scanned information from edit table */ TopLabel = TRIM(Send_Message(CtrlEntID, "TEXT_BY_POS", COL$TOP_LABEL, PrevRow)) BottomLabel = TRIM(Send_Message(CtrlEntID, "TEXT_BY_POS", COL$BOTTOM_LABEL, PrevRow)) LotNumber = TRIM(Send_Message(CtrlEntID, "TEXT_BY_POS", COL$LOT_NO, PrevRow)) //IFXLabel = TRIM(Send_Message(CtrlEntID, "TEXT_BY_POS", COL$IFX_LABEL, PrevRow)) IF ((TopLabel NE '') AND (BottomLabel NE '') AND (LotNumber NE '')) THEN ;//AND (IFXValid = 1) AND (IFXLabel NE '')) THEN ******************************** * FQA Labels Validation = GOOD * ******************************** Set_Property(CtrlEntID, "CELLPOS", 'OK', COL$RESULT:@FM:PrevRow) stat = Send_Message(CtrlEntID, "COLOR_BY_POS", 0, PrevRow,GREEN$) Set_Property("SYSTEM", "BLOCK_EVENTS", True$) Set_Property(CtrlEntID, "SELPOS", COL$TOP_LABEL:@FM:PrevRow+1) /* Move to the next line ready to scan */ Set_Property("SYSTEM", "BLOCK_EVENTS", False$) InsertedPosition = Send_Message(CtrlEntID, "INSERT", -1, '') * Add transaction to Posting system to time-stamp WO_MAT record ! 10/28/2019 - DJS & Dan Crisp ! This transaction is moving to Packaging_Services and is triggered by ! the NDW_PACKAGING form upon a successful scan sequence. IF Num(TopLabel) THEN RDSNo = TopLabel ReactRunRec = XLATE('REACT_RUN',RDSNo,'','X') WONo = ReactRunRec StepNo = ReactRunRec CassNo = ReactRunRec END ELSE IF TopLabel[1,1] = 'O' THEN TopLabel[1,1] = '' IF TopLabel[1,1] = 'I' THEN TopLabel[1,1] = '' EpiProFlag = Get_Property(@Window, '@EPIPRO_FLAG') GaNFlag = Get_Property(@Window, '@GAN_FLAG') Begin Case Case EpiProFlag EQ True$ WONo = FIELD(TopLabel,'.',1) StepNo = FIELD(TopLabel,'.',2) CassNo = FIELD(TopLabel,'.',3) RDSNo = '' Case GaNFlag EQ True$ WONo = Field(TopLabel, '*', 1) CassNo = Field(TopLabel, '*', 2) StepNo = 1 RDSNo = '' End Case END CurrDTM = OCONV(Date(),'D2/'):' ':OCONV(Time(),'MTS') UserID = @USER4 IF UserID = '' THEN UserID = @USERNAME LogFile = 'WO_MAT' ;* Changed so all scans are logged in the WO_MAT table 12/3/2006 Action = 'LBLCHK' ;* Final label check for same top and bottom and correct Lot Number on WO_MAT record WHCd = 'CR' ;* Clean room @ final QA LocCd = 'PKO' ;* QA wants this to "place" the cassette into the outbound passthrough Set_Status(0) obj_WO_Mat_Log('Create',LogFile:@RM:CurrDTM:@RM:Action:@RM:WhCd:@RM:LocCd:@RM:WONo:@RM:CassNo:@RM:UserID:@RM:'Match') IF Get_Status(errCode) THEN Errmsg(errCode) END END /* End of check for all information available to be checked*/ END GOSUB Refresh RETURN