COMPILE FUNCTION WO_MAT_IN(EntID,Event,Parm1,Parm2,Parm3,Parm4,Parm5) /* Commuter module for WO_MAT_IN (EpiPRO Inbound material) window 08/12/2010 - John C. Henry, J.C. Henry & Co., Inc. */ DECLARE SUBROUTINE Set_Property, End_Dialog, Set_Status, Center_Window DECLARE SUBROUTINE ErrMsg, Send_Message, Set_Property, obj_AppWindow DECLARE SUBROUTINE Security_Err_Msg, Send_Event DECLARE FUNCTION Get_Property, Get_Status, Dialog_Box, Utility, Popup, Collect.Ixvals DECLARE FUNCTION Send_Message, Msg, Security_Check, obj_React_Run_CI, NextKey, MemberOf $INSERT MSG_EQUATES $INSERT APPCOLORS $INSERT LSL_USERS_EQU $INSERT SECURITY_RIGHTS_EQU $INSERT POPUP_EQUATES $INSERT LOGICAL EQU CRLF$ TO \0D0A\ EQU TAB$ TO \09\ EQU COL$SLOT TO 1 EQU COL$WAFER_ID TO 2 EQU COL$RUN_ID TO 3 EQU COL$SLOT_NCR TO 4 EQU COL$MET_NO$ TO 5 EQU COL$MOVED_TO_SLOT TO 6 EQU COL$REPLACED_BY TO 7 EQU COL$NCR_NO TO 1 EQU COL$NCR_STATUS TO 2 EQU COL$NCR_REJ_QTY TO 3 EQU COL$NCR_RESP TO 4 EQU COL$NCR_STAGE TO 5 EQU COL$NCR_LOSS_DESC TO 6 EQU COL$NCR_LOSS_COMM TO 7 EQU COL$NCR_FIN_SIG TO 8 EQU COL$NCR_FIN_SIG_DTM TO 9 ErrTitle = 'Error in WO_Mat_In routine' ErrorMsg = '' Result = '' BEGIN CASE CASE EntID = @WINDOW BEGIN CASE CASE Event = 'CLEAR' ; GOSUB Clear CASE Event = 'CREATE' ; GOSUB Create CASE Event = 'READ' ; GOSUB Read CASE Event[1,3] = 'QBF' ; GOSUB Refresh END CASE 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','WO_MAT_IN') * get the current style EQU MULTILINE_STYLE$ TO 512 ;* MultiLine Select Style = Get_Property(@WINDOW:'.SLOT_NO', 'STYLE') IF Style [1,2] _EQC "0x" THEN CONVERT @LOWER.CASE TO @UPPER.CASE IN STYLE Style = ICONV(Style [3,99], "MX") END Style = BitOr(Style, MULTILINE_STYLE$) Set_Property('WO_MAT_IN.SLOT_NO', "STYLE", Style) * Provides compatibility with the existing messaging attachment system IF Parm1 NE '' THEN PassedKeys = FIELD(Parm1,'*',1) obj_Appwindow('ViewRelated','WO_MAT_IN':@RM:PassedKeys) END GOSUB Refresh RETURN * * * * * * * Read: * * * * * * * WONo = Get_Property(@WINDOW:'.WO_NO','DEFPROP') CassNo = Get_Property(@WINDOW:'.CASS_NO','DEFPROP') DEBUG IF RowExists('WO_MAT',WONo:'*':CassNo) THEN IF NOT(Security_Check('RDS',READ$)) THEN Send_Event(@WINDOW,'CLEAR') Security_Err_Msg('Work Order Mat',READ$) RETURN END IF NOT(Security_Check('RDS',EDIT$)) THEN obj_Appwindow('ReadOnly',@WINDOW) ;*Set to Read Only END END ELSE ErrMsg('Work Order Mat entries are only created by the program.') Send_Event(@WINDOW,'CLEAR') RETURN END GOSUB Refresh RETURN * * * * * * * Write: * * * * * * * RETURN * * * * * * * Clear: * * * * * * * GOTO Refresh RETURN * * * * * * * Delete: * * * * * * * ErrMsg('Records may not be modified or deleted.') Result = 0 ;* No Deletes RETURN * * * * * * * Close: * * * * * * * obj_Appwindow('DetailReturn') RETURN * * * * * * * Refresh: * * * * * * * Ctrls = @WINDOW:'.HOLD':@RM:@WINDOW:'.HOTLOT' Props = 'CHECK':@RM:'CHECK' Vals = Get_Property(Ctrls,Props) Hold = Vals[1,@RM] HotLot = Vals[COL2()+1,@RM] IF HotLot THEN Set_Property(@WINDOW:'.HOT_LOT_LABEL','VISIBLE',1) END ELSE Set_Property(@WINDOW:'.HOT_LOT_LABEL','VISIBLE',0) END CtrlEntID = @WINDOW:'.SLOT_NO' SlotList = Get_Property(CtrlEntID,'LIST') SlotListCnt = COUNT(SlotList,@FM) + (SlotList NE '') FOR Line = 1 TO SlotListCnt BEGIN CASE CASE SlotList = '' ; LineColor = GREY$ CASE SlotList NE '' AND SlotList NE '' ; LineColor = GREEN$ CASE SlotList NE '' AND SlotList = '' ; LineColor = WHITE$ CASE 1 ; LineColor = WHITE$ END CASE FOR Col = 1 TO 7 stat = Send_Message(CtrlEntID,'COLOR_BY_POS',Col,Line,LineColor) NEXT COL NEXT Line * 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('WO_MAT_WFR','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:'.SLOT_NO' THEN ETList = Get_Property(ETCtrl,'LIST') FOR Line = 1 TO COUNT(ETList,@FM) + (ETList NE '') IF ETList 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 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