COMPILE FUNCTION Comm_Fiscal_Yr(Instruction,Parm1,Parm2) /* Commuter module for FISCAL_YR window 12/01/2006 - 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, obj_AppWindow DECLARE SUBROUTINE Security_Err_Msg, End_Window, Start_Window DECLARE FUNCTION Get_Property, Get_Status, Dialog_Box, Utility, Center_Window, Popup, Collect.Ixvals DECLARE FUNCTION Send_Message, Msg $INSERT APPCOLORS EQU CRLF$ TO \0D0A\ EQU COL$COLUMN_1 TO 1 ;* Equates for edit table. EQU COL$COLUMN_2 TO 2 EQU COL$COLUMN_3 TO 3 EQU COL$QTR_NO TO 1 EQU COL$QTR_START_DT TO 2 EQU COL$QTR_END_DT TO 3 EQU COL$QTR_KEY TO 4 EQU COL$WK_NO TO 1 EQU COL$WK_START_DT TO 2 EQU COL$WK_END_DT TO 3 EQU COL$WK_MONTH_NO TO 4 EQU COL$WK_QTR_NO TO 5 ErrTitle = 'Error in Comm_Fiscal_Qtr' ErrorMsg = '' Result = '' BEGIN CASE CASE Instruction = 'Create' ; GOSUB Create CASE Instruction = 'Refresh' ; GOSUB Refresh CASE Instruction = 'Read' ; GOSUB Read CASE Instruction = 'Write' ; GOSUB Write CASE Instruction = 'Clear' ; GOSUB Clear CASE Instruction = 'Delete' ; GOSUB Delete CASE Instruction = 'Close' ; GOSUB Close CASE Instruction = 'LUFiscalYr' ; GOSUB LUFiscalYr CASE Instruction = 'NewQtr' ; GOSUB NewQtr CASE Instruction = 'QtrDC' ; GOSUB QtrDC CASE Instruction = 'WeekStartPC' ; GOSUB Refresh CASE 1 ErrorMsg = 'Unknown Instruction ':QUOTE(Instruction):' passed to routine.' ErrMsg(ErrorMsg) END CASE RETURN Result * * * * * * * Create: * * * * * * * obj_Appwindow('Create',@WINDOW) GOSUB Refresh RETURN * * * * * * * Clear: * * * * * * * Send_Event(@WINDOW,'PAGE',1) * * * * * * * Refresh: * * * * * * * * 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(@WINDOW,'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> ETList = Get_Property(ETCtrl,'LIST') FOR Line = 1 TO COUNT(ETList,@FM) + (ETList NE '') IF ETList NE '' THEN IF ETCtrl = @WINDOW:'.WEEK_START_DT' THEN BEGIN CASE CASE ETList NE '' ; LineColor = INP_BLUE$ CASE ETList NE '' ; LineColor = PRE_BLUE$ CASE 1 ; LineColor = RCV_BLUE$ END CASE stat = Send_Message(ETCtrl,'COLOR_BY_POS',0,Line,LineColor) END ELSE 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 END NEXT I NEXT I RETURN * * * * * * * Page: * * * * * * * obj_Appwindow('Page') RETURN * * * * * * * Read: * * * * * * * GOSUB Refresh RETURN * * * * * * * Write: * * * * * * * Result = 1 RETURN * * * * * * * Delete: * * * * * * * /* IF Security_Check('Order',Delete$) THEN Result = 1 ;* Proceed with delete END ELSE Security_Err_Msg('Order',Delete$) Result = 0 ;* Stop event chain END */ RETURN * * * * * * * LUFiscalYr: * * * * * * * IF NOT(ASSIGNED(Parm1)) THEN FocusControl = '' ELSE FocusControl = Parm1 IF NOT(ASSIGNED(Parm2)) THEN FocusPos = '' ELSE FocusPos = Parm2 Set_Status(0) FiscalYear = Popup(@WINDOW,'','FISCAL_YR')<1,1> ;* Popup returns complete row IF FiscalYear = '' THEN Return obj_Appwindow('LoadFormKeys',@WINDOW:@RM:FiscalYear) RETURN * * * * * * * Close: * * * * * * * /* obj_Notes('Inbox',@USER4) ;* Checks for any new messages obj_Appwindow('CardReturn',@WINDOW) */ RETURN * * * * * * * NewQtr: * * * * * * * CtrlEntID = @WINDOW:'.FISCAL_QTY' FiscalYr = Get_Property(@WINDOW:'.FISCAL_YR','DEFPROP') IF FiscalYr = '' THEN RETURN FiscalQtrNos = Get_Property(CtrlEntID,'ARRAY')<1> ;* Just need the first column LastQtrNo = 0 QtrCnt = COUNT(FiscalQtrNos,@VM) + (FiscalQtrNos NE '') FOR I = 1 TO QtrCnt QtrNo = FiscalQtrNos<1,I> IF QtrNo = '' THEN QtrNo = 0 IF QtrNo > LastQtrNo THEN LastQtrNo = QtrNo NEXT I IF LastQtrNo >= 3 THEN RETURN Send_Event(@WINDOW,'WRITE') FiscalQtrKey = FiscalYr:'*':LastQtrNo + 1 DetWindow = 'FISCAL_QTR' DetKeys = FiscalQtrKey DefaultRec = '' RetKey = FiscalYr RetWin = @WINDOW RetPage = 1 RetCtrl = CtrlEntID RetPos = 1:@FM:LastQtrNo + 1 obj_Appwindow('ViewNewDetail',DetWindow:@RM:DetKeys:@RM:DefaultRec:@RM:RetKey:@RM:RetPage:@RM:RetCtrl:@RM:RetPos) RETURN * * * * * * * ItemPC: * * * * * * * RETURN * * * * * * * QtrDC: * * * * * * * FiscalYr = Get_Property(@WINDOW,'ID') CtrlEntID = @WINDOW:'.FISCAL_QTR' CurrPos = Get_Property(CtrlEntID,'SELPOS') CurrCol = CurrPos<1> CurrRow = CurrPos<2> IF CurrCol = COL$WK_NO OR CurrCol = COL$QTR_START_DT OR CurrCol = COL$QTR_END_DT THEN QtrKey = Get_Property(CtrlEntID,'CELLPOS',COL$QTR_KEY:@FM:CurrRow) IF QtrKey NE '' THEN IF Get_Property(@WINDOW,'QBFLIST') = '' THEN Send_Event(@WINDOW,'WRITE') END DetWindow = 'FISCAL_QTR' DetKeys = QtrKey DefaultRec = '' RetKey = FiscalYr RetPage = 1 RetCtrl = CtrlEntID RetPos = CurrPos oAParms = DetWindow:@RM:DetKeys:@RM:DefaultRec:@RM:RetKey:@RM:RetPage:@RM:RetCtrl:@RM:RetPos obj_AppWindow('ViewNewDetail',oAParms) IF Get_Status(errCode) THEN ErrMsg(errCode) END END END RETURN