COMPILE FUNCTION Comm_Dialog_Mat_Scan(Instruction, Parm1,Parm2) #pragma precomp SRP_PreCompiler /* Commuter module for Dialog_Mat_Scan (Material - Barcode Scan) window 10/24/2004 - John C. Henry, J.C. Henry & Co., Inc. */ DECLARE SUBROUTINE Set_Property, Set_Status, ErrMsg, Set_Property, Dialog_Box, obj_WO_Mat_Log, Logging_Services DECLARE SUBROUTINE Btree.Extract, Send_Event, Security_Err_Msg, obj_Appwindow, End_Dialog, End_Window DECLARE SUBROUTINE Send_Message, Print_Cass_Ship_Label, Print_SAP_Cass_Ship_Label, Post_Event DECLARE FUNCTION Get_Property, Get_Status, Popup, Send_Message, Msg, Security_Check, Dialog_Box, Logging_Services DECLARE FUNCTION obj_Schedule, Dialog_Box, Utility, obj_WO_Mat, Database_Services, Environment_Services, Start_Window, End_Window $INSERT RDS_EQUATES $INSERT REACT_RUN_EQUATES $INSERT WO_LOG_EQUATES $INSERT POPUP_EQUATES $INSERT LOGICAL $INSERT MSG_EQUATES $INSERT APPCOLORS $INSERT LSL_USERS_EQU $INSERT SECURITY_RIGHTS_EQU $INSERT WO_MAT_EQUATES Equ Tab$ to \09\ Equ CRLF$ to \0D0A\ Equ LF$ to \0A\ Equ Comma$ to ',' EQU COL$LABEL_SCAN TO 1 EQU COL$CURR_STATUS TO 2 EQU COL$CURR_LOC TO 3 EQU COL$CR_COMP TO 4 LogPath = Environment_Services('GetApplicationRootPath') : '\LogFiles\WoMatLog' LogDate = Oconv(Date(), 'D4/') LogTime = Oconv(Time(), 'MTS') LogFileName = LogDate[7, 4] : '-' : LogDate[1, 2] : '-' : LogDate[4, 2] : ' Material Log.csv' Headers = 'Logging DTM' : @FM : 'User' : @FM : 'Notes' objLog = Logging_Services('NewLog', LogPath, LogFileName, CRLF$, Comma$, Headers, '', False$, False$) LoggingDTM = LogDate : ' ' : LogTime ; // Logging DTM ErrTitle = 'Error in Comm_Dialog_Mat_Scan' ErrorMsg = '' Result = '' BEGIN CASE CASE Instruction = 'Create' ; GOSUB Create CASE Instruction = 'Refresh' ; GOSUB Refresh CASE Instruction = 'OK' ; GOSUB OK CASE Instruction = 'Cancel' ; GOSUB Cancel CASE Instruction = 'CassIDPC' ; GOSUB CassIDPC CASE Instruction = 'LocLF' ; GOSUB LocLF CASE 1 ErrorMsg = 'Unknown Instruction passed to routine' END CASE IF ErrorMsg NE '' THEN ErrMsg(ErrTitle:@SVM:ErrorMsg) END RETURN Result * * * * * * * Create: * * * * * * * IF @User4 EQ 'DAN_CR' OR @User4 EQ 'DON_T' OR @User4 EQ 'MADELINE_S' OR @User4 EQ 'JUSTIN_H' OR @User4 EQ 'JOSEPH_F' THEN Set_Property(@WINDOW:'.BTN_NEW','VISIBLE',True$) END IF NOT(Security_Check('RDS',READ$)) THEN Security_Err_Msg('RDS',READ$) End_Dialog(@WINDOW,'Cancel') RETURN END obj_Appwindow('Create',@WINDOW) IF Parm1<1,1> = 'Ship' THEN WONo = Parm1<1,2>[-1,'B '] Set_Property(@WINDOW,'@WONO',WONo) Set_Property(@WINDOW,'@SHIPMENT',1) Set_Property(@WINDOW,'TEXT',Parm1<1,2>) Set_Property(@WINDOW:'.WINDOW_LABEL','TEXT','Scan WO ':WONo:' Shipment') END ELSE Set_Property(@WINDOW:'@SHIPMENT','') Set_Property(@WINDOW:'@WONO','') END GOSUB Refresh RETURN * * * * * * * Clear: * * * * * * * Send_Event(@WINDOW,'PAGE',1) GOTO Refresh RETURN * * * * * * * Refresh: * * * * * * * WindowLabel = Get_Property(@WINDOW:'.WINDOW_LABEL','TEXT') IF INDEX(WindowLabel,' IN ',1) THEN BackColor = GREEN$ END ELSE BackColor = YELLOW$ END CtrlName = @WINDOW:'.CASS_IDS' CassArray = Get_Property(CtrlName,'DEFPROP') CassStatuses = CassArray ;* Second Column CurrLocations = CassArray CurrCRCompFlags = ICONV(CassArray,'B') Location = Get_Property(@WINDOW:'.LOCATION_CODE','DEFPROP') SWAP '\J' WITH '*' IN Location Beeped = 0 FOR I = 1 TO COUNT(CassStatuses,@VM) + (CassStatuses NE '') CassStatus = CassStatuses<1,I> CurrLocation = CurrLocations<1,I> CurrCRCompFlag = CurrCRCompFlags<1,I> BEGIN CASE CASE Location[-3,3] = 'PTO' AND CurrLocation NE '' IF CurrCRCompFlag OR CassStatus = 'Verify Qty' THEN stat = Send_Message(CtrlName,'COLOR_BY_POS',0,I,GREEN$) END ELSE stat = Send_Message(CtrlName,'COLOR_BY_POS',0,I,RED$) IF NOT(Beeped) THEN void = Utility('BEEP') Beeped = 1 END END CASE Location[-2,2] = 'SB' AND CurrLocation NE '' IF INDEX(CassStatus,'-',1) THEN CassStatus = FIELD(CassStatus,'-',1) CassStatus = TRIM(CassStatus) END IF CassStatus[-4,4] NE 'Ship' THEN stat = Send_Message(CtrlName,'COLOR_BY_POS',0,I,RED$) IF NOT(Beeped) THEN void = Utility('BEEP') Beeped = 1 END END ELSE stat = Send_Message(CtrlName,'COLOR_BY_POS',0,I,GREEN$) END CASE 1 stat = Send_Message(CtrlName,'COLOR_BY_POS',0,I,GREEN$) END CASE NEXT I IF Beeped = 1 THEN Set_Property(@WINDOW:'.OK_BUTTON','ENABLED',0) END ELSE Set_Property(@WINDOW:'.OK_BUTTON','ENABLED',1) END LastLabel = CassArray[-1,'B':@VM] IF LastLabel NE '' THEN Send_Message(CtrlName, "INSERT", -1,'':@VM :'') ;* Insert blank row at bottom of the list Set_Property(CtrlName,'SELPOS',1:@FM:-1) ;* Move cursor down END RETURN * * * * * * * OK: * * * * * * * LocCd = Get_Property(@WINDOW:'.LOCATION_CODE','DEFPROP') IF LocCd = '' THEN ErrMsg('Missing Location Code') RETURN END SWAP '/J' WITH '*' IN LocCd WhCd = LocCd[1,'*'] LocCd = LocCd[COL2()+1,'*'] CassIDs = Get_Property(@WINDOW:'.CASS_IDS','ARRAY')<1> LOOP UNTIL CassIDs[-1,1] NE @VM OR CassIDs = '' CassIDs[-1,1] = '' REPEAT IF CassIDs<1,1> = '' THEN RETURN TestCassID = CassIDs<1,1> Convert '*' to '.' in TestCassID Action = 'PLACE' ;* Default Action PrintLabelWOs = '' PLSteps = '' PLCassNos = '' PLRDSNos = '' IF INDEX(TestCassID,'.',2) THEN EpiPRO = 1 ELSE EpiPRO = 0 IF INDEX(TestCassID,'.',1) THEN GaN = 1 ELSE GaN = 0 IF LocCd = 'PTO' THEN PrintLabelWOs = Get_Property(@WINDOW,'@WONO') ; FOR I = 1 To COUNT(CassIDs,@VM) + (CassIDs NE '') CassID = CassIDs<1,I> BEGIN CASE CASE EpiPRO EQ True$ IF CassID[1,1] = 'O' THEN CassID[1,1] = '' IF CassID[1,1] = 'I' THEN CassID[1,1] = '' WONo = FIELD(CassID,'.',1) StepNo = FIELD(CassID,'.',2) CassNo = FIELD(CassID,'.',3) RDSNo = '' CASE GaN EQ True$ IF CassID[1,1] = 'O' THEN CassID[1,1] = '' IF CassID[1,1] = 'I' THEN CassID[1,1] = '' Convert '*' to '.' in CassID WONo = FIELD(CassID,'.',1) StepNo = 1 CassNo = FIELD(CassID,'.',2) RDSNo = '' CASE Otherwise$ RDSNo = CassID ReactRunRec = XLATE('REACT_RUN',RDSNo,'','X') WONo = ReactRunRec StepNo = ReactRunRec CassNo = ReactRunRec END CASE PLSteps<1,-1> = StepNo ; PLCassNos<1,-1> = CassNo ; PLRDSNos<1,-1> = RDSNo ; NEXT I WOCnt = COUNT(PrintLabelWOs,@FM) + (PrintLabelWOs NE '') FOR I = 1 TO WOCnt PrintLabelWO = PrintLabelWOs PrintLabelProdOrd = XLATE('WO_LOG',PrintLabelWO,WO_LOG_PROD_ORD_NO$,'X') IF PrintLabelProdOrd NE '' THEN Print_SAP_Cass_Ship_Label(PrintLabelWO,PLSteps,PLCassNos,PLRDSNos) END NEXT I END IF Get_Property(@WINDOW,'@SHIPMENT') THEN IF INDEX(TestCassID,'.',2) THEN EpiPRO = 1 ELSE EpiPRO = 0 Result = '' ;* This gets returned to COMM_SHIPMENT and placed on the shipment record FOR I = 1 To COUNT(CassIDs,@VM) + (CassIDs NE '') CassID = CassIDs<1,I> IF NOT(EpiPRO) THEN RDSNo = CassID ReactRunRec = XLATE('REACT_RUN',RDSNo,'','X') WONo = ReactRunRec StepNo = ReactRunRec CassNo = ReactRunRec Result<-1> = StepNo:@VM:CassNo:@VM:RDSNo END ELSE IF CassID[1,1] = 'O' THEN CassID[1,1] = '' IF CassID[1,1] = 'I' THEN CassID[1,1] = '' Step = FIELD(CassID,'.',2) CassNo = FIELD(CassID,'.',3) Result<-1> = Step:@VM:CassNo END NEXT I Action = 'SHIP' END CurrDTM = OCONV(Date(),'D2/'):' ':OCONV(Time(),'MTS') WONos = '' CassNos = '' CassCnt = COUNT(CassIDs,@VM) + (CassIDs NE '') FOR I = 1 TO CassCnt CassID = CassIDs<1,I> BEGIN CASE CASE ( (EpiPro EQ True$) or (GaN EQ True$) ) IF CassID[1,1] = 'I' OR CassID[1,1] = 'O' THEN CassID[1,1] = '' ;* Skip the first character (I or O) Convert '*' to '.' in CassID WONos<1,I> = CassID[1,'.'] CassNos<1,I> = CassID[-1,'B.'] CASE Otherwise$ * Numeric CassID is an RDS ReactRunRec = XLATE('REACT_RUN',CassID,'','X') WONos<1,I> = ReactRunRec CassNos<1,I> = ReactRunRec END CASE NEXT I UserID = @USER4 LogFile = 'WO_MAT' ;* Changed so all scans are logged in the WO_MAT table 12/3/2006 Set_Status(0) // Log form contents FormContents = Get_Property(@Window:'.CASS_IDS', 'LIST') NumRows = DCount(FormContents, @FM) LogContents = '' For Row = 1 to NumRows Cass = FormContents IF Cass NE '' THEN LogContents<-1> = FormContents END Next Row LogData = '' LogData<1> = '*** Form Contents ***' LogData<2, 1> = LoggingDTM LogData<2, 2> = @User4 LogData<3> = LogContents Logging_Services('AppendLog', objLog, LogData, @FM, @VM) // Log Material Log parameters LogData<1> = ' ' LogData<2> = '*** Material Log Parameters ***' LogData<3> = 'LogFile: ':LogFile LogData<4> = 'CurrDTM: ':CurrDTM LogData<5> = 'Action: ':Action LogData<6> = 'WhCd: ':WhCd LogData<7> = 'LocCd: ':LocCd LogData<8> = 'WONos: ':WONos LogData<9> = 'CassNos: ':CassNos LogData<10> = 'UserID: ':UserID LogData<11> = 'CassIDs: ':CassIDs LogData<12> = ' ' Logging_Services('AppendLog', objLog, LogData, @FM, @VM) obj_WO_Mat_Log('Create',LogFile:@RM:CurrDTM:@RM:Action:@RM:WhCd:@RM:LocCd:@RM:WONos:@RM:CassNos:@RM:UserID:@RM:CassIDs) errCode = '' IF Get_Status(errCode) THEN Errmsg(errCode) END IF Get_Property(@WINDOW,'@SHIPMENT') THEN End_Dialog(@WINDOW,Result) ;* Move this down and replace the CLEAR when called from the Shipment window RETURN END ELSE Send_Event(@WINDOW,'CLEAR') END RETURN * * * * * * * * Cancel: * * * * * * * * End_Dialog(@WINDOW,'Cancel') RETURN * * * * * * * * CassIDPC: * * * * * * * * CtrlEntID = @WINDOW:'.CASS_IDS' Shipment = Get_Property(@WINDOW, '@SHIPMENT') ;* Shipment flag AtWONo = Get_Property(@WINDOW, '@WONO') Location = Get_Property(@WINDOW:'.LOCATION_CODE','DEFPROP')[-1,'B*'] 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') IF ListData = '' THEN ColPointer = CurrCol LinePointer = CurrRow ColCnt = 1 * Find the first non-empty cell LOOP Test = ListData UNTIL Test NE '' OR (LinePointer = 0 AND ColPointer = 1) ColPointer -= 1 IF ColPointer = 0 THEN ColPointer = ColCnt LinePointer -= 1 END REPEAT * Move one past the non empty cell BEGIN CASE CASE LinePointer = 0 * Empty Table LinePointer = 1 CoilPointer = 1 CASE ColPointer = ColCnt LinePointer += 1 ColPointer = 1 CASE 1 ColPointer += 1 END CASE Set_Property(CtrlEntId,"SELPOS",ColPointer:@FM:LinePointer) END IF ListData NE '' AND PrevCol = COL$LABEL_SCAN THEN ScanCassID = TRIM(ListData) IF ScanCassID[1,2] = '1T' THEN Swap '1T' with '' in ScanCassID Set_Property(CtrlEntId,"CELLPOS",ScanCassID,PrevSelPos) END CassID = ScanCassID * Check for data already in the list (repeat scan) TestArray = ArrayData<1> ;* First Column TestArray<1,PrevRow> = '' ;* Remove the label just scanned LOCATE CassID IN TestArray USING @VM SETTING Pos THEN Set_Property(CtrlEntId,"SELPOS",PrevSelPos) Set_Property(CtrlEntID,'INVALUE','',PrevSelPos) ;* Label Data already scanned RETURN END IF INDEX(CassID,'.',2) THEN EpiPRO = 1 GaN = 0 END ELSE IF INDEX(CassID,'.',1) THEN GaN = 1 EpiPRO = 0 END CONVERT '.' TO '*' IN CassID Test = '' CurrStatus = '' BEGIN CASE CASE CassID[1,1] = 'I' * WM_IN table TestKey = CassID[2,99] Test = XLATE('WM_IN',TestKey,'','X') CurrStatus = OCONV(XLATE('WM_IN',TestKey,'CURR_STATUS','X'),'[WM_IN_CURR_STATUS_CONV]') TestWO = FIELD(TestKey,'*',1) IF Location = 'PTO' THEN IF AtWONo = '' THEN Set_Property(@WINDOW,'@WONO',TestWO) Set_Property(@WINDOW:'.WINDOW_LABEL','TEXT','Scanning WO ':TestWO) END END WOMatKey = TestWO:'*':FIELD(TestKey,'*',3) LastPTO = obj_WO_Mat('OutofPTO',WOMatKey) IF LastPTO THEN MsgHead = 'Cassette already scanned through the PTO' MsgText = 'Scanned at ':LastPTO<2>:' by ':LastPTO<1>:CRLF$ MsgText := 'Are you sure you wish to rescan and reprint the shipping label?' OK = Msg(@WINDOW,'','YESNO','',MsgHead:@FM:MsgText) IF NOT(OK) THEN Set_Property(CtrlEntId,"SELPOS",PrevSelPos) Set_Property(CtrlEntID,'INVALUE','',PrevSelPos) ;* User opted out of rescan and print RETURN END END CASE CassID[1,1] = 'O' * GaN or EPP TestKey = CassID[2,99] IF GaN THEN Test = XLATE('WO_MAT',TestKey,'','X') END ELSE Test = XLATE('WM_OUT',TestKey,'','X') END CurrStatus = OCONV(XLATE('WM_OUT',TestKey,'CURR_STATUS','X'),'[WM_OUT_CURR_STATUS_CONV]') TestWO = FIELD(TestKey,'*',1) IF Location = 'PTO' THEN IF AtWONo = '' THEN Set_Property(@WINDOW,'@WONO',TestWO) Set_Property(@WINDOW:'.WINDOW_LABEL','TEXT','Scanning WO ':TestWO) END END IF (FIELD(TestKey,'*',3)) THEN WOMatKey = TestWO:'*':FIELD(TestKey,'*',3) END ELSE WOMatKey = TestWO:'*':FIELD(TestKey,'*',2) END LastPTO = obj_WO_Mat('OutofPTO',WOMatKey) IF LastPTO THEN MsgHead = 'Cassette already scanned through PTO' MsgText = 'Scanned at ':LastPTO<2>:' by ':LastPTO<1>:CRLF$ MsgText := 'Are you sure you wish to rescan and reprint the shipping label?' OK = Msg(@WINDOW,'','YESNO','',MsgHead:@FM:MsgText) IF NOT(OK) THEN Set_Property(CtrlEntId,"SELPOS",PrevSelPos) Set_Property(CtrlEntID,'INVALUE','',PrevSelPos) ;* User opted out of rescan and print RETURN END END CASE ( INDEX(CassID,'*',1) AND NOT(INDEX(CassID,'*',2)) OR INDEX(CassID,'.',1) AND NOT(INDEX(CassID,'.',2)) ) * This is a WO_MAT format label TestKey = CassID Test = XLATE('WO_MAT',TestKey,'','X') CurrStatus = OCONV(XLATE('WO_MAT',TestKey,'CURR_STATUS','X'),'[WO_MAT_CURR_STATUS_CONV]') TestWO = FIELD(TestKey,'*',1) IF Location = 'PTO' THEN IF AtWONo = '' THEN Set_Property(@WINDOW,'@WONO',TestWO) Set_Property(@WINDOW:'.WINDOW_LABEL','TEXT','Scanning WO ':TestWO) END END WOMatKey = TestKey LastPTO = obj_WO_Mat('OutofPTO',WOMatKey) IF LastPTO THEN MsgHead = 'Cassette already scanned through the PTO' MsgText = 'Scanned at ':LastPTO<2>:' by ':LastPTO<1>:CRLF$ MsgText := 'Are you sure you wish to rescan and reprint the shipping label?' OK = Msg(@WINDOW,'','YESNO','',MsgHead:@FM:MsgText) IF NOT(OK) THEN Set_Property(CtrlEntId,"SELPOS",PrevSelPos) Set_Property(CtrlEntID,'INVALUE','',PrevSelPos) ;* User opted out of rescan and print RETURN END END CASE INDEX(CassID,'*',2) * EpiPRO material indeterminate direction TestKey = CassID Test = XLATE('WM_IN',TestKey,'','X') CurrStatus = OCONV(XLATE('WM_IN',TestKey,'CURR_STATUS','X'),'[WM_IN_CURR_STATUS_CONV]') IF Test = '' THEN Test = XLATE('WM_OUT',TestKey,'','X') CurrStatus = OCONV(XLATE('WM_OUT',TestKey,'CURR_STATUS','X'),'[WM_OUT_CURR_STATUS_CONV]') END TestWO = FIELD(TestKey,'*',1) IF Location = 'PTO' THEN IF AtWONo = '' THEN Set_Property(@WINDOW,'@WONO',TestWO) Set_Property(@WINDOW:'.WINDOW_LABEL','TEXT','Scanning WO ':TestWO) END END WOMatKey = FIELD(TestKey,'*',3) LastPTO = obj_WO_Mat('OutofPTO',WOMatKey) IF LastPTO THEN MsgHead = 'Cassette already scanned through the PTO' MsgText = 'Scanned at ':LastPTO<2>:' by ':LastPTO<1>:CRLF$ MsgText := 'Are you sure you wish to rescan and reprint the shipping label?' OK = Msg(@WINDOW,'','YESNO','',MsgHead:@FM:MsgText) IF NOT(OK) THEN Set_Property(CtrlEntId,"SELPOS",PrevSelPos) Set_Property(CtrlEntID,'INVALUE','',PrevSelPos) ;* User opted out of rescan and print RETURN END END CASE 1 ReactRunRec = XLATE('REACT_RUN',CassID,'','X') IF ReactRunRec EQ '' THEN RDSRec = XLATE('RDS',CassID,'','X') TestWO = RDSRec CassNo = RDSRec END ELSE TestWO = ReactRunRec CassNo = ReactRunRec END IF Location = 'PTO' THEN IF AtWONo = '' THEN Set_Property(@WINDOW,'@WONO',TestWO) Set_Property(@WINDOW:'.WINDOW_LABEL','TEXT','Scanning WO ':TestWO) END END WOMatKey = TestWO:'*':CassNo Test = XLATE('WO_MAT',WOMatKey,'','X') CurrStatus = OCONV(XLATE('WO_MAT',WOMatKey,'CURR_STATUS','X'),'[WO_MAT_CURR_STATUS_CONV]') LastPTO = obj_WO_Mat('OutofPTO',WOMatKey) SAPBatchNo = Test IF LastPTO THEN MsgHead = 'Cassette already scanned through the PTO' MsgText = 'Scanned at ':LastPTO<2>:' by ':LastPTO<1>:CRLF$ MsgText := 'Are you sure you wish to rescan and reprint the shipping label?' OK = Msg(@WINDOW,'','YESNO','',MsgHead:@FM:MsgText) IF NOT(OK) THEN Set_Property(CtrlEntId,"SELPOS",PrevSelPos) Set_Property(CtrlEntID,'INVALUE','',PrevSelPos) ;* User opted out of rescan and print RETURN END END END CASE WoMatAction = Database_Services('ReadDataColumn', 'WO_MAT',WoMatKey, 8) SAPBatchNo = Xlate('WO_MAT', WOMatKey, 'SAP_BATCH_NO', 'X') hasPack = Index(WoMatAction, 'PACK', 1) > 0 IF ( (Location EQ 'PTO') AND (hasPack EQ False$) ) THEN MsgHead = 'Cassette is missing Packaging scan' MsgText = 'Unable to print SAP label without packaging scan.':CRLF$ MsgText := 'Please return cassette #':CassID:' to warehouse manager.' OK = Msg(@WINDOW, '', 'OK', '', MsgHead:@FM:MsgText) Set_Property(CtrlEntID, 'SELPOS', PrevSelPos);*remove entry from grid Set_Property(CtrlEntID, 'INVALUE', '', PrevSelPos) LogFile = 'WO_MAT' CurrDTM = OCONV(Date(),'D2/'):' ':OCONV(Time(),'MTS') Action = 'PLACE' WhCd = '1K' LocCd = 'PTI' WONo = Field(WOMatKey, '*', 1) CassNo = Field(WOMatKey, '*', 2) UserID = @User4 Tag = 'Missing Packaging Scan' obj_WO_Mat_Log('Create',LogFile:@RM:CurrDTM:@RM:Action:@RM:WhCd:@RM:LocCd:@RM:WONo:@RM:CassNo:@RM:UserID:@RM:Tag) RETURN END ELSE IF ( (Location EQ 'PTO') AND (SAPBatchNo EQ '') ) THEN MsgHead = 'Cassette does not have SAP Batch ID' MsgText = 'Unable to print SAP label without SAP Batch ID.':CRLF$ MsgText := 'Please return cassette #':CassID:' to warehouse manager.' OK = Msg(@WINDOW, '', 'OK', '', MsgHead:@FM:MsgText) Set_Property(CtrlEntID, 'SELPOS', PrevSelPos);*remove entry from grid Set_Property(CtrlEntID, 'INVALUE', '', PrevSelPos) //write log entry, showing SAP ID missing in tag LogFile = 'WO_MAT' CurrDTM = OCONV(Date(),'D2/'):' ':OCONV(Time(),'MTS') Action = 'PLACE' WhCd = '1K' LocCd = 'PTI' WONo = Field(WOMatKey, '*', 1) CassNo = Field(WOMatKey, '*', 2) UserID = @User4 Tag = 'Missing SAP Batch ID' obj_WO_Mat_Log('Create',LogFile:@RM:CurrDTM:@RM:Action:@RM:WhCd:@RM:LocCd:@RM:WONo:@RM:CassNo:@RM:UserID:@RM:Tag) RETURN END END CRComp = obj_WO_Mat('CRComp',WOMatKey:@RM:@RM) CRComp = OCONV(CRComp,'B') CurrLoc = XLATE('WO_MAT',WOmatKey,'CURR_LOCATION','X') AtWONo = Get_Property(@WINDOW,'@WONO') IF AtWONo NE '' THEN IF TestWO NE AtWONo THEN ErrMsg('':@VM:'Process Error':@SVM:'Label Scanned is NOT part of WO ':AtWoNo) Set_Property(CtrlEntId,"SELPOS",PrevSelPos) Set_Property(CtrlEntID,'INVALUE','',PrevSelPos) ;* Work Order scanned doesn't match 1st WO scanned or passed in from the Shipment RETURN END END IF Test = '' THEN Set_Property(CtrlEntId,"SELPOS",PrevSelPos) Set_Property(CtrlEntID,'INVALUE','',PrevSelPos) ;* No corresponding data record found for label scanned RETURN END Set_Property(CtrlEntID,'CELLPOS',CurrStatus,2:@FM:PrevRow) ;* Load Current Status Set_Property(CtrlEntID,'CELLPOS',CurrLoc,3:@FM:PrevRow) ;* Load Current Location Set_Property(CtrlEntID,'CELLPOS',CRComp,4:@FM:PrevRow) ;* Load Cleanroom Complete flag END GOSUB Refresh RETURN * * * * * * * LocLF: * * * * * * * DataIn = Get_Property(@WINDOW:'.LOCATION_CODE','DEFPROP') IF DataIn = '' THEN RETURN SWAP '/J' WITH '*' IN DataIn IF DataIn = '1K*PTI' THEN ErrMsg('PTI scans may not be done with this form. Use the PTI Material Scan form instead.') Set_Property(@WINDOW:'.LOCATION_CODE','DEFPROP','') Set_Property(@WINDOW:'.LOCATION_CODE','FOCUS',1) END ELSE IF DataIn = '1K*PTO' THEN ErrMsg('PTO scans may not be done with this form. Use the PTO Material Scan form instead.') Set_Property(@WINDOW:'.LOCATION_CODE','DEFPROP','') Set_Property(@WINDOW:'.LOCATION_CODE','FOCUS',1) void = End_Window(@WINDOW) void = Start_Window( 'NDW_PTO_MAT_SCAN', '', '', '', '' ) END ELSE IF RowExists('LOCATION',DataIn) THEN Set_Property(@WINDOW:'.LOCATION_CODE','DEFPROP',DataIn) END ELSE ErrMsg(QUOTE(DataIn):' is not a valid location in the LOCATION table.') Set_Property(@WINDOW:'.LOCATION_CODE','DEFPROP','') Set_Property(@WINDOW:'.LOCATION_CODE','FOCUS',1) END RETURN