COMPILE FUNCTION Comm_Dialog_Order_Find(Method, Parm1) /* Commuter module for Dialog_Order_Find window. 08/16/2004 - John C. Henry, J.C. Henry & Co., Inc. */ DECLARE SUBROUTINE Set_Property, End_Dialog, Send_Event, Set_Status, ErrMsg DECLARE SUBROUTINE obj_Appwindow, Start_Window, Btree.Extract, Msg, Send_Info DECLARE FUNCTION Get_Property, Get_Status, Dialog_Box, Utility, Send_Message, Popup, Collect.IXVals, Msg EQU CRLF$ TO \0D0A\ EQU COL$CUST_NO TO 1 ;* Customer edit table column equates EQU COL$CUST_NAME TO 2 EQU LTGREY$ TO 229 + (229*256) + (229*65536) ;* JCH standard colors for edittable backgrounds EQU GREY$ TO 192 + (192*256) + (192*65536) EQU GREEN$ TO 192 + (220*256) + (192*65536) EQU RED$ TO 255 + (128*256) + (128*65536) EQU BLUE$ TO 128 + (255*256) + (255*65536) EQU WHITE$ TO 255 + (255*256) + (255*65536) EQU YELLOW$ TO 255 + (255*256) + (202*65536) EQU LTBLUE$ TO 128 + (255*256) + (255*65536) EQU PURPLE$ TO 225 + (181*256) + (255*65536) EQU DTS_MULTIROW$ TO 512 EQU DTS_LARGEDATA$ TO 4096 $INSERT ORDER_EQU $INSERT WO_LOG_EQU $INSERT PS_EQUATES $INSERT POPUP_EQUATES $INSERT LOGICAL $INSERT MSG_EQUATES ErrTitle = 'Error in Comm_Dialog_Order_Find' ErrorMsg = '' Result = '' BEGIN CASE CASE Method = 'Create' ; GOSUB Create CASE Method = 'CustChar' ; GOSUB CustChar CASE Method = 'CustPC' ; GOSUB CustPC CASE Method = 'CustDC' ; GOSUB CustDC CASE Method = 'PONoDC' ; GOSUB PONoDC CASE Method = 'AnnContDC' ; GOSUB AnnContDC CASE Method = 'QuoteDC' ; GOSUB QuoteDC CASE Method = 'CustPNDC' ; GOSUB CustPNDC CASE Method = 'LUDate' ; GOSUB LUDate CASE Method = 'Cancel' ; GOSUB Cancel CASE Method = 'Refresh' ; GOSUB Refresh CASE Method = 'PerformQuery' ; GOSUB PerformQuery CASE 1 ErrMsg(ErrTitle:@SVM:'Unknown method ':QUOTE(Method):' passed to routine.') END CASE RETURN Result * * * * * * * Create: * * * * * * * obj_AppWindow('Create') Set_Property(@WINDOW,'STATUSLINE',@WINDOW:'.STATUSLINE_FIX') GOSUB Refresh RETURN * * * * * * * Refresh: * * * * * * * * Turn edit table symbolic column backgrounds to green stat = Send_Message(@WINDOW:'.CUST_INFO','COLOR_BY_POS',COL$CUST_NAME,0,GREEN$) ;* Turn names column all rows green RETURN * * * * * * * CustChar: * * * * * * * CtrlName = @WINDOW:'.CUST_INFO' CustArray = Get_Property(CtrlName,'ARRAY') ;* Customer Information table CurrPos = Get_Property(CtrlName,'SELPOS') CurrRow = CurrPos<2> DataIn = CustArray IF LEN(DataIn) > 2 THEN ReturnToCtrl = CtrlName ReturnToPos = CurrPos IF NOT(NUM(DataIn)) THEN Set_Property(CtrlName,'CELLPOS','',CurrPos) ;* Clear characters input Start_Window('COMP_LOOKUP',@WINDOW,DataIn:@VM:'C':@FM:ReturnToCtrl:@FM:ReturnToPos,'','') END END RETURN * * * * * * * CustPC: * * * * * * * CtrlName = @WINDOW:'.CUST_INFO' CustList = Get_Property(CtrlName,'LIST') ;* Customer Information table CurrPos = Get_Property(CtrlName,'SELPOS') CurrCol = CurrPos<1> CurrRow = CurrPos<2> CustNo = CustList IF CustNo NE '' THEN Set_Property(CtrlName,'CELLPOS',XLATE('COMPANY',CustNo,4,'X'),COL$CUST_NAME:@FM:CurrRow) END RETURN * * * * * * * CustDC: * * * * * * * CtrlName = @WINDOW:'.CUST_INFO' CustList = Get_Property(CtrlName,'LIST') ;* Customer Information table CurrPos = Get_Property(CtrlName,'SELPOS') CurrCol = CurrPos<1> CurrRow = CurrPos<2> CustNo = CustList LineCnt = COUNT(CustList,@FM) + (CustList NE '') IF CustNo = '' THEN CustNos = Popup(@WINDOW,'','CUSTOMER') CustCnt = COUNT(CustNos,@VM) + (CustNos NE '') IF CustCnt > LineCnt THEN FOR I = 1 TO CustCnt stat = Send_Message(CtrlName,'INSERT',-1,@VM:@FM) ; * Add blank lines NEXT I END FOR I = CurrRow TO CurrRow + CustCnt CustNo = CustNos<1,I> CustName = XLATE('COMPANY',CustNo,4,'X') Set_Property(CtrlName,'CELLPOS',CustNo,COL$CUST_NO:@FM:I) Set_Property(CtrlName,'CELLPOS',CustName,COL$CUST_NAME:@FM:I) Set_Property(CtrlName,'SELPOS',COL$CUST_NO:@FM:I+1) NEXT I END ELSE ErrMsg('DoubleClick on the first empty Cust No field to view a popup of all Customers') END RETURN * * * * * * * PONoDC: * * * * * * * CustArray = Get_Property(@WINDOW:'.CUST_INFO','ARRAY') CustNos = CustArray LOOP LastCustNo = CustNos[-1,'B':@VM] UNTIL LastCustNo NE '' OR CustNos = '' CustNos[COL1(),99] = '' ;* Trim trailing blanks REPEAT IF CustNos = '' THEN RETURN * display the processing message and do the processing Def = "" Def = "Selecting PO Numbers..." Def = "U" MsgUp = Msg(@window, Def) OPEN 'DICT.ORDER' TO DictVar THEN SearchString = 'CUST_NO':@VM:CustNos:@VM:@FM SearchString := 'PO_NO':@VM:'#':@FM Btree.Extract(SearchString, 'ORDER', DictVar, OrderKeys, '', Flag) IF Get_Status(errCode) THEN Msg(@WINDOW,MsgUp) ErrMsg(errCode) RETURN END IF OrderKeys NE '' THEN RawPONos = XLATE('ORDER',OrderKeys,ORDER_PO_NO$,'X') IF Get_Status(errCode) THEN DEBUG PONos = '' FOR I = 1 TO COUNT(RawPONos,@VM) + (RawPONos NE '') RawPONo = RawPONos<1,I> LOCATE RawPONo IN PONos BY 'AL' USING @VM SETTING Pos ELSE PONos = INSERT(PONos,1,Pos,0,RawPONo) END NEXT I END ELSE PONos = '' END Msg(@WINDOW,MsgUp) IF PONos = '' THEN ErrMsg('No Purchase Orders on file for specified customer.') RETURN END PONos := @VM CONVERT @VM TO @RM IN PONos CALL V119('S','','D','R',PONos,'') IF Get_Status(errCode) THEN DEBUG CONVERT @RM TO @VM IN PONos PONos[-1,1] = '' ;* Strip trailing delimiter TypeOver = '' TypeOver = PONos PONos = Popup(@WINDow,TypeOver,'CUST_PO') IF Get_Status(errCode) THEN DEBUG IF PONos NE '' THEN PONos := @VM:@VM Set_Property(@WINDOW:'.PO_NO','DEFPROP',PONos) END END ELSE ErrMsg('Unable to open DICT.ORDER in COMM_DIALOG_ORDER_FIND.') END RETURN * * * * * * * AnnContDC: * * * * * * * CustNos = Get_Property(@WINDOW:'.CUST_INFO','ARRAY') LOOP LastCustNo = CustNos[-1,'B':@VM] UNTIL LastCustNo NE '' OR CustNos = '' CustNos[COL1(),99] = '' ;* Trim trailing blanks REPEAT OPEN 'DICT.ANNUAL_CONTRACTS' TO DictVar THEN SearchString = 'CUST_NO':@VM:CustNos:@VM:@FM Btree.Extract(SearchString, 'ANNUAL_CONTRACTS', DictVar, ACNos, '', Flag) IF Get_Status(errCode) THEN ErrMsg(errCode) RETURN END IF ACNos = '' THEN ErrMsg('No Annual Contracts on file for specified customer.') RETURN END ACNos := @VM CONVERT @VM TO @RM IN ACNos CALL V119('S','','D','R',ACNos,'') IF Get_Status(errCode) THEN DEBUG CONVERT @RM TO @VM IN ACNos acNos[-1,1] = '' ;* Strip trailing delimiter TypeOver = '' TypeOver = ACNos ACNos = Popup(@WINDow,TypeOver,'CUST_ANN_CONT') IF ACNos NE '' THEN ACNos := @VM:@VM Set_Property(@WINDOW:'.ANN_CONT','DEFPROP',ACNos) END END ELSE ErrMsg('Unable to open DICT.ANNUAL_CONTRACTS in COMM_DIALOG_ORDER_FIND routine.') END RETURN * * * * * * * QuoteDC: * * * * * * * CustArray = Get_Property(@WINDOW:'.CUST_INFO','ARRAY') CustNos = CustArray LOOP LastCustNo = CustNos[-1,'B':@VM] UNTIL LastCustNo NE '' OR CustNos = '' CustNos[COL1(),99] = '' ;* Trim trailing blanks REPEAT IF CustNos = '' THEN RETURN * display the processing message and do the processing Def = "" Def = "Selecting Quotes..." Def = "U" MsgUp = Msg(@window, Def) OPEN 'DICT.ORDER' TO DictVar THEN SearchString = 'CUST_NO':@VM:CustNos:@VM:@FM SearchString := 'QUOTE_NO':@VM:'#':@FM Btree.Extract(SearchString, 'ORDER', DictVar, OrderKeys, '', Flag) IF Get_Status(errCode) THEN Msg(@WINDOW,MsgUp) ErrMsg(errCode) RETURN END IF OrderKeys NE '' THEN QuoteNos = '' OrderNos = '' FOR N = 1 TO COUNT(OrderKeys,@VM) + (OrderKeys NE '') OrderKey = OrderKeys<1,N> RawQuoteNos = XLATE('ORDER',OrderKey,'QUOTE_NO','X') FOR I = 1 TO COUNT(RawQuoteNos,@VM) + (RawQuoteNos NE '') RawQuoteNo = RawQuoteNos<1,I> LOCATE RawQuoteNo IN QuoteNos BY 'AL' USING @VM SETTING Pos ELSE QuoteNos = INSERT(QuoteNos,1,Pos,0,RawQuoteNo) END NEXT I NEXT N END ELSE QuoteNos = '' END Msg(@WINDOW,MsgUp) IF QuoteNos = '' THEN ErrMsg('No Quotes on file for specified customer.') RETURN END QuoteNos := @VM CONVERT @VM TO @RM IN QuoteNos CALL V119('S','','D','R',QuoteNos,'') IF Get_Status(errCode) THEN DEBUG CONVERT @RM TO @VM IN QuoteNos QuoteNos[-1,1] = '' ;* Strip trailing delimiter TypeOver = '' TypeOver = QuoteNos QuoteNos = Popup(@WINDow,TypeOver,'CUST_PO') IF Get_Status(errCode) THEN DEBUG IF QuoteNos NE '' THEN CONVERT @VM TO @FM IN QuoteNos Set_Property(@WINDOW:'.QUOTE','LIST',QuoteNos) END END ELSE ErrMsg('Unable to open DICT.ORDER in COMM_DIALOG_ORDER_FIND.') END RETURN * * * * * * * CustPNDC: * * * * * * * CustArray = Get_Property(@WINDOW:'.CUST_INFO','ARRAY') CustNos = CustArray LOOP LastCustNo = CustNos[-1,'B':@VM] UNTIL LastCustNo NE '' OR CustNos = '' CustNos[COL1(),99] = '' ;* Trim trailing blanks REPEAT IF CustNos = '' THEN RETURN * display the processing message and do the processing Def = "" Def = "Selecting Part Numbers..." Def = "U" MsgUp = Msg(@window, Def) OPEN 'DICT.WO_LOG' TO DictVar THEN SearchString = 'CUST_NO':@VM:CustNos:@VM:@FM SearchString := 'PART_NO':@VM:'#':@FM Btree.Extract(SearchString, 'WO_LOG', DictVar, WOKeys, '', Flag) IF Get_Status(errCode) THEN Msg(@WINDOW,MsgUp) ErrMsg(errCode) RETURN END IF WOKeys NE '' THEN PartNos = '' OrderNos = '' FOR N = 1 TO COUNT(WOKeys,@VM) + (WOKeys NE '') WOKey = WOKeys<1,N> RawPartNos = XLATE('WO_LOG',WOKey,'PART_NO','X') OrderNo = XLATE('WO_LOG',WOKey,WO_LOG_ORDER_NO$,'X') FOR I = 1 TO COUNT(RawPartNos,@VM) + (RawPartNos NE '') RawPartNo = RawPartNos<1,I> LOCATE RawPartNo IN PartNos BY 'AL' USING @VM SETTING Pos ELSE PartNos = INSERT(PartNos,1,Pos,0,RawPartNo) END LOCATE OrderNo IN OrderNos BY 'DR' USING @VM SETTING OPos ELSE OrderNos = INSERT(OrderNos,Pos,OPos,0,OrderNo) END NEXT I NEXT N END ELSE PartNos = '' END Msg(@WINDOW,MsgUp) IF PartNos = '' THEN ErrMsg('No Purchase Orders on file for specified customer.') RETURN END PartNos := @VM CONVERT @VM TO @RM IN PartNos CALL V119('S','','D','R',PartNos,'') IF Get_Status(errCode) THEN DEBUG CONVERT @RM TO @VM IN PartNos PartNos[-1,1] = '' ;* Strip trailing delimiter TypeOver = '' TypeOver = PartNos PartNos = Popup(@WINDow,TypeOver,'CUST_PO') IF Get_Status(errCode) THEN DEBUG IF PartNos NE '' THEN debug END END ELSE ErrMsg('Unable to open DICT.WO_LOG in COMM_DIALOG_ORDER_FIND.') END RETURN * * * * * * * LUDate: * * * * * * * ReturnCtrl = Parm1[1,@RM] IF ReturnCtrl = '' THEN ReturnCtrl = Get_Property(@WINDOW,'FOCUS') DateSelected = Dialog_Box('POPUP_YEAR',@WINDOW) RetVal = OCONV(DateSelected, 'D4/') IF RetVal NE '' THEN obj_Appwindow('LUValReturn',RetVal:@RM:ReturnCtrl) END RETURN * * * * * * * Cancel: * * * * * * * RETURN * * * * * * * PerformQuery: * * * * * * * * Customer numbers * SearchString = '' CustNos = Get_Property(@WINDOW:'.CUST_INFO','ARRAY') LOOP LastVar = CustNos[-1,'B':@VM] UNTIL LastVar NE '' OR CustNos = '' CustNos[COL1(),99] = '' ;* Trim trailing blanks REPEAT ORdCustNos = '' FOR I = 1 TO COUNT(CustNos,@VM) + (CustNos NE '') ORdCustNos<1,I> = ';':CustNos<1,I> NEXT I IF CustNos NE '' THEN SearchString := 'CUST_NO':@VM:CustNos:@FM:'CUST_BILL_TO':@VM:ORdCustNos:@FM * Annual contracts * ACNos = Get_Property(@WINDOW:'.ANN_CONT','ARRAY')<1> LOOP LastVal = ACNos[-1,'B':@VM] UNTIL LastVal NE '' OR ACNos = '' ACNos[COL1(),99] = '' ;* Trim trailing blanks REPEAT IF ACNos NE '' THEN SearchString := 'AC_ID':@VM:ACNos:@FM * Work Orders * WONos = Get_Property(@WINDOW:'.WO_NO','ARRAY')<1> LOOP LastVal = WONos[-1,'B':@VM] UNTIL LastVal NE '' OR WONos = '' WONos[COL1(),99] = '' ;* Trim trailing blanks REPEAT IF WONos NE '' THEN SearchString := 'WO_KEYS':@VM:WONos:@FM * Quotes * QuoteNos = Get_Property(@WINDOW:'.QUOTE','ARRAY')<1> LOOP LastVal = QuoteNos[-1,'B':@VM] UNTIL LastVal NE '' OR QuoteNos = '' QuoteNos[COL1(),99] = '' ;* Trim trailing blanks REPEAT IF QuoteNos NE '' THEN SearchString := 'QUOTE_NO':@VM:QuoteNos:@FM * PONos * PONos = Get_Property(@WINDOW:'.PO_NO','ARRAY')<1> LOOP LastVal = PONos[-1,'B':@VM] UNTIL LastVal NE '' OR PONos = '' PONos[COL1(),99] = '' ;* Trim trailing blanks REPEAT IF PONos NE '' THEN SearchString := 'PO_NO':@VM:PONos:@FM * Start and End Dates StartDt = ICONV(Get_Property(@WINDOW:'.START_DT','TEXT'),'D') EndDt = ICONV(Get_Property(@WINDOW:'.END_DT','TEXT'),'D') BEGIN CASE CASE StartDt NE '' AND EndDt = '' SearchString := 'ENTRY_DATE':@VM:'>=':OConv(StartDt, 'D4/'):@FM CASE StartDt = '' AND EndDt NE '' SearchString := 'ENTRY_DATE':@VM:'<=':OConv(EndDt, 'D4/'):@FM CASE StartDt NE '' AND EndDt NE '' * Fudge the dates - '~' is not inclusive of the end dates StartDt -= 1 EndDt += 1 SearchString := 'ENTRY_DATE':@VM:OConv(StartDt, 'D4/'):'~':OConv(EndDt, 'D4/'):@FM CASE 1 NULL END CASE OrdStatus = Get_Property(@WINDOW:'.STATUS','VALUE') IF OrdStatus NE 'I' THEN IF OrdStatus = 1 THEN SearchString := 'CLOSE_DATE':@VM:'#':@FM END ELSE SearchString := 'CLOSE_DATE':@VM:'=':@FM END END OPEN 'DICT.ORDER' TO DictVar THEN Def = "" Def = "Selecting Orders..." Def = "U" * display the processing message and do the processing MsgUp = Msg(@window, Def) Btree.Extract(SearchString,'ORDER',DictVar,OrderKeys,'',flag) IF Get_Status(errCode) THEN ErrMsg(errCode) Msg(@window, MsgUp) IF Get_Status(errCode) THEN ErrMsg(errCode) RETURN END End_Dialog(@WINDOW,OrderKeys) END ELSE ErrMsg('Unable to open DICT.ORDER in routine COMM_DIALOG_ORDER_FIND') END RETURN