COMPILE FUNCTION WO_Mat_Batch(EntID,Event,Parm1,Parm2,Parm3,Parm4,Parm5) /* Commuter module for WO_Mat_Batch window 10/5/2009 - John C. Henry, J.C. Henry & Co., Inc. */ DECLARE SUBROUTINE Set_Property, End_Dialog, Send_Event, Set_Status, Center_Window, Post_Event DECLARE SUBROUTINE ErrMsg, Send_Message, Set_Property, Send_Event, Btree.Extract, obj_AppWindow, DECLARE SUBROUTINE obj_Notes, Security_Err_Msg, End_Window, Forward_Event, Start_Window, Create_Note, Print_SAP_Cass_Ship_Label DECLARE FUNCTION Get_Property, Get_Status, Dialog_Box, Utility, Popup, Collect.Ixvals DECLARE FUNCTION Send_Message, Msg, Security_Check, Select_Into, MemberOf $INSERT MSG_EQUATES $INSERT APPCOLORS $INSERT LSL_USERS_EQU $INSERT SECURITY_RIGHTS_EQU $INSERT WO_LOG_EQUATES $INSERT WO_MAT_EQUATES $INSERT REACT_RUN_EQUATES $INSERT POPUP_EQUATES $INSERT LOGICAL $INSERT RTI_STYLE_EQUATES EQU CRLF$ TO \0D0A\ EQU TAB$ TO \09\ ErrTitle = 'Error in WO_MAT_BATCH' ErrorMsg = '' Result = '' BEGIN CASE CASE EntID = @WINDOW BEGIN CASE CASE Event = 'CLEAR' ; GOSUB Clear CASE Event = 'CREATE' ; GOSUB Create CASE Event = 'CLOSE' ; GOSUB Close CASE Event = 'READ' ; GOSUB Read CASE Event = 'WRITE' ; GOSUB Write CASE Event[1,3] = 'QBF' ; GOSUB Refresh END CASE CASE EntID = @WINDOW:'.USE_ORG_BATCH' AND Event = 'CLICK' ; GOSUB UseOrgBatch CASE EntID = @WINDOW:'.USE_LOT_NO' AND Event = 'CLICK' ; GOSUB UseLotNo CASE EntID = @WINDOW:'.CASS_NO' AND EVENT = 'GOTFOCUS' ; GOSUB LUCassNo CASE EntID = @WINDOW:'.PRINT_LABELS' AND EVENT = 'CLICK' ; GOSUB PrintLabels CASE EntID = @WINDOW:'.LU_RDS_NOS' AND EVENT = 'CLICK' ; GOSUB LURDSNos CASE 1 DEBUG 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) IF MemberOf(@USER4, 'OI_SUPERUSER') THEN Set_Property(@WINDOW:'.SEND_SPC','VISIBLE',1) Set_Property(@WINDOW:'.SPC_DTM','VISIBLE',1) END ELSE Set_Property(@WINDOW:'.SEND_SPC','VISIBLE',0) Set_Property(@WINDOW:'.SPC_DTM','VISIBLE',0) END * Set result table special styles (Dropdowns) GOSUB Refresh RETURN * * * * * * * Clear: * * * * * * * IF Get_Property(@WINDOW,'@READONLY') THEN obj_AppWindow('ReadOnly',@RM:1) ;* Reenables data bound controls Set_Property(@WINDOW,'@READONLY',0) ;* Clear flag on window END * * * * * * * Refresh: * * * * * * * * 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> 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 I NEXT I RETURN * * * * * * * LURDSNos: * * * * * * * RDSNos = Get_Property(@WINDOW:'.XREF_RDS','DEFPROP') RDSCnt = COUNT(RDSNos,@VM) + (RDSNos NE '') WOMatKeys = '' FOR I = 1 TO RDSCnt RDSNo = RDSNos<1,I> IF RDSNo NE '' THEN ReactRunRec = XLATE('REACT_RUN',RDSNo,'','X') WONo = ReactRunRec CassNo = ReactRunRec WOMatKeys<1,-1> = WONo:'*':CassNo END NEXT I IF INDEX(WOMatKeys,@VM,1) THEN Set_Property(@WINDOW,'QBFLIST',WOMatKeys) END ELSE obj_Appwindow('LoadFormKeys',@WINDOW:@RM:WOMatKeys) END Set_Property(@WINDOW:'.XREF_RDS','DEFPROP',STR(@VM,18)) RETURN * * * * * * * UseOrgBatch: * * * * * * * OrgBatch = Get_Property(@WINDOW:'.ORG_SAP_BATCH_NO','DEFPROP') Set_Property(@WINDOW:'.SAP_BATCH_NO','DEFPROP',OrgBatch) RETURN * * * * * * * UseLotNo: * * * * * * * LotNo = Get_Property(@WINDOW:'.LOT_NO','DEFPROP') Set_Property(@WINDOW:'.SAP_BATCH_NO','DEFPROP',LotNo) RETURN * * * * * * * LUCassNo: * * * * * * * WONo = Get_Property(@WINDOW:'.WO_NO','DEFPROP') IF WONo NE '' THEN TypeOver = '' TypeOver = 'WITH WO_NO = ':WONo TypeOver = 2 ;* Cass No(s) PopupLines = POPUP(@WINDOW,TypeOver,'WO_MAT_FIXIT') IF PopupLines = '' THEN RETURN IF INDEX(PopupLines,@FM,1) THEN LineCnt = COUNT(PopupLines,@FM) + (PopupLines NE '') WOMatKeys = '' FOR I = 1 TO LineCnt WOMatKeys<1,-1> = WONo:'*':PopupLines NEXT I Send_Event(@WINDOW,'QBFINIT') Set_Property(@WINDOW,'QBFLIST',WOMatKeys) GOSUB Refresh Send_Event(@WINDOW,'QBFIRST') END ELSE CassNo = PopupLines<1,2> Set_Property(@WINDOW:'.CASS_NO','DEFPROP',CassNo) Send_Event(@WINDOW:'.CASS_NO','LOSTFOCUS') END END RETURN * * * * * * * PrintLabels: * * * * * * * QBFList = Get_Property(@WINDOW,'QBFLIST') IF QBFList = '' THEN WONo = Get_Property(@WINDOW:'.WO_NO','DEFPROP') CassNo = Get_Property(@WINDOW:'.CASS_NO','DEFPROP') WOMatKeys = WONo:'*':CassNo END ELSE WOMatKeys = QBFList END WOMatCnt = COUNT(WOMatKeys,@FM) + (WOMatKeys NE '') PrintLabelWOs = '' PLSteps = '' PLCassNos = '' PLRDSNos = '' FOR I = 1 TO WOMatCnt WOMatKey = WOMatKeys WOSteps = XLATE('WO_LOG',WONo,WO_LOG_WO_STEP_KEY$,'X')[-1,'B':@VM] StepNo = WOSteps[-1,'B*'] CassNo = FIELD(WOMatKey,'*',2) RDSNo = XLATE('WO_MAT',WOMatKey,WO_MAT_RDS_NO$,'X')[-1,'B':@VM] LOCATE WONo IN PrintLabelWOs BY 'AR' USING @FM SETTING Pos THEN LOCATE CassNo IN PLCassNos BY 'AR' USING @VM SETTING CassPos ELSE PLSteps = INSERT(PLSteps,Pos,CassPos,0,StepNo) PLCassNos = INSERT(PLCassNos,Pos,CassPos,0,CassNo) PLRDSNos = INSERT(PLRDSNos,Pos,CassPos,0,RDSNo) END END ELSE PrintLabelWOs = INSERT(PrintLabelWOs,Pos,0,0,WONo) PLSteps = INSERT(PLSteps,Pos,0,0,StepNo) PLCassNos = INSERT(PLCassNos,Pos,0,0,CassNo) PLRDSNos = INSERT(PLRDSNos,Pos,0,0,RDSNo) END 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 RETURN * * * * * * * Read: * * * * * * * GOSUB Refresh RETURN * * * * * * * Write: * * * * * * * ParentWindow = Get_Property(@WINDOW,'PARENT') IF ParentWindow = 'WO_MAT' THEN ParentWindow = Get_Property(@WINDOW,'PARENT') ParentKey = Get_Property(@WINDOW,'@RETURNKEY') obj_AppWindow('LoadFormKeys',ParentWindow:@RM:ParentKey) Post_Event(@WINDOW,'CLOSE') END RETURN * * * * * * * Close: * * * * * * * RETURN