COMPILE FUNCTION Comm_Fiscal_Qtr(Instruction,Parm1,Parm2) /* Commuter module for FISCAL_QTR 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, obj_Tables DECLARE FUNCTION Get_Property, Get_Status, Dialog_Box, Utility, Center_Window, Popup, Collect.Ixvals DECLARE FUNCTION Send_Message, Msg, obj_Tables $INSERT FISCAL_QTR_EQUATES $INSERT APPCOLORS $INSERT POPUP_EQUATES 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 DROPDOWN$ TO 131072 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 = 'Page' ; GOSUB Page CASE Instruction = 'Close' ; GOSUB Close CASE Instruction = 'LUFiscalQtr' ; GOSUB LUFiscalQtr CASE Instruction = 'CopyTargets' ; GOSUB CopyTargets CASE Instruction = 'ThruputReport' ; GOSUB ThruputReport Case Instruction = 'PIDtOptions' ; GOSUB PIDtOptions CASE Instruction = 'PIDtOptionsGaN' ; GOSUB PIDtOptionsGaN CASE 1 ErrorMsg = 'Unknown Instruction ':QUOTE(Instruction):' passed to routine.' ErrMsg(ErrorMsg) END CASE RETURN Result * * * * * * * Create: * * * * * * * obj_Appwindow('Create',@WINDOW) ColStyles = Send_Message( @WINDOW:'.TARGETS', "COLSTYLE", 0, '' ) ColStyles<1> = BitOr( ColStyles<1>, DROPDOWN$ ) ColStyles<2> = BitOr( ColStyles<2>, DROPDOWN$ ) Send_Message( @WINDOW:'.TARGETS', "COLSTYLE", 0, ColStyles ) Groups = XLATE('SYSREPOSPOPUPS','LSL2**THRUPUT_GROUP',8,'X') Cats = XLATE('SYSREPOSPOPUPS','LSL2**THRUPUT_CATS',8,'X') void = Send_Message(@WINDOW:'.TARGETS','COLFORMAT',1,Groups) void = Send_Message(@WINDOW:'.TARGETS','COLFORMAT',2,Cats) GOSUB Refresh RETURN * * * * * * * Clear: * * * * * * * Send_Event(@WINDOW,'PAGE',1) * * * * * * * Refresh: * * * * * * * TargetArray = Get_Property(@WINDOW:'.TARGETS','ARRAY') IF TargetArray<1,1> = '' THEN Set_Property(@WINDOW:'.COPY_TARGETS','ENABLED',1) END ELSE Set_Property(@WINDOW:'.COPY_TARGETS','ENABLED',0) END * 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 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 * * * * * * * Page: * * * * * * * obj_Appwindow('Page') RETURN * * * * * * * Read: * * * * * * * GOSUB Refresh RETURN * * * * * * * Write: * * * * * * * RETURN * * * * * * * Delete: * * * * * * * RETURN * * * * * * * LUFiscalQtr: * * * * * * * Send_Event(@WINDOW,'CLEAR') FQKeys = Popup(@WINDOW,'','FISCAL_QTR') IF Get_Status(errCode) THEN ErrMsg(errCode) IF FQKeys = '' THEN RETURN CONVERT @VM TO @FM IN FQKeys IF INDEX(FQKeys,@FM,1) THEN Send_Event(@WINDOW,'QBFINIT') Set_Property(@WINDOW,'QBFLIST',FQKeys) GOSUB Refresh Send_Event(@WINDOW,'QBFIRST') END ELSE obj_Appwindow('LoadFormKeys',@WINDOW:@RM:FQKeys) END * RETURN * * * * * * * CopyTargets: * * * * * * * Typeover = '' Typeover = 1 KeyToCopy = Popup(@WINDOW,Typeover,'FISCAL_QTR') IF KeyToCopy = '' THEN RETURN SourceRec = XLATE('FISCAL_QTR',KeyToCopy,'','X') IF SourceRec = '' THEN RETURN FiscalYear = Get_Property(@WINDOW:'.FISCAL_YR','DEFPROP') FiscalQty = Get_Property(@WINDOW:'.FISCAL_QTR','DEFPROP') FQKey = FiscalYear:'*':FiscalQty Send_Event(@WINDOW, 'WRITE') OtParms = 'FISCAL_QTR':@RM:FQKey DestRec = obj_Tables('ReadRec',OtParms) DestRec = SourceRec DestRec = SourceRec DestRec = SourceRec DestRec = SourceRec OtParms = FieldStore(OtParms,@RM,4,0,DestRec) ;* Put record in 4th field of OtParms obj_Tables('WriteRec',OtParms) obj_Appwindow('LoadFormKeys',@WINDOW:@RM:FQKey) RETURN * * * * * * * Close: * * * * * * * obj_Appwindow('DetailReturn') RETURN * * * * * * * ThruputReport: * * * * * * * QuarterEndDt = Get_Property(@WINDOW:'.END_DT','TEXT') CALL Report_Thruput(QuarterEndDt) RETURN * * * * * * * PIDtOptions: * * * * * * * StartDt = Get_Property(@WINDOW:'.START_DT','DEFPROP') EndDt = Get_Property(@WINDOW:'.END_DT','DEFPROP') StartDt = ICONV(StartDt,'D') EndDt = ICONV(EndDt,'D') IF StartDt = '' OR EndDt = '' THEN Errmsg('Invalid or Missing Start/End Dates') RETURN END DateCnt = EndDt - StartDt + 1 DisplayVals = '' LineCnt = 1 FOR WDate = StartDt TO EndDt Day = MOD(WDate,7) BEGIN CASE CASE Day = 0 ; Day = 'Sunday' CASE Day = 1 ; Day = 'Monday' CASE Day = 2 ; Day = 'Tuesday' CASE Day = 3 ; Day = 'Wednesday' CASE Day = 4 ; Day = 'Thursday' CASE Day = 5 ; Day = 'Friday' CASE Day = 6 ; Day = 'Saturday' END CASE DisplayVals<1,LineCnt,1> = OCONV(WDate,'D4-') DisplayVals<1,LineCnt,2> = Day LineCnt += 1 NEXT WDate TypeOver = '' TypeOver = DisplayVals IdleDts = Popup(@WINDOW,TypeOver,'PLAN_DOWN_DATES') IF IdleDts NE '' THEN *Set_Property(@WINDOW:'.PLAN_IDLE_DTS','ARRAY',IdleDts) CurrRecord = Get_Property(@WINDOW,'ATRECORD') CurrRecord = ICONV(IdleDts,'D') Set_Property(@WINDOW,'ATRECORD',CurrRecord) END RETURN * * * * * * * * PIDtOptionsGaN: * * * * * * * * StartDt = Get_Property(@WINDOW:'.START_DT','DEFPROP') EndDt = Get_Property(@WINDOW:'.END_DT','DEFPROP') StartDt = ICONV(StartDt,'D') EndDt = ICONV(EndDt,'D') IF StartDt = '' OR EndDt = '' THEN Errmsg('Invalid or Missing Start/End Dates') RETURN END DateCnt = EndDt - StartDt + 1 DisplayVals = '' LineCnt = 1 FOR WDate = StartDt TO EndDt Day = MOD(WDate,7) BEGIN CASE CASE Day = 0 ; Day = 'Sunday' CASE Day = 1 ; Day = 'Monday' CASE Day = 2 ; Day = 'Tuesday' CASE Day = 3 ; Day = 'Wednesday' CASE Day = 4 ; Day = 'Thursday' CASE Day = 5 ; Day = 'Friday' CASE Day = 6 ; Day = 'Saturday' END CASE DisplayVals<1,LineCnt,1> = OCONV(WDate,'D4-') DisplayVals<1,LineCnt,2> = Day LineCnt += 1 NEXT WDate TypeOver = '' TypeOver = DisplayVals IdleDts = Popup(@WINDOW,TypeOver,'PLAN_DOWN_DATES') IF IdleDts NE '' THEN *Set_Property(@WINDOW:'.PLAN_IDLE_DTS','ARRAY',IdleDts) CurrRecord = Get_Property(@WINDOW,'ATRECORD') CurrRecord = ICONV(IdleDts,'D') Set_Property(@WINDOW,'ATRECORD',CurrRecord) END RETURN