COMPILE FUNCTION Comm_Tool_Class(EntID,Event,Parm1,Parm2,Parm3,Parm4,Parm5)
/*
Commuter module for TOOL_CLASS (Tool Class) window
10/12/2012 - John C. Henry, J.C. Henry & Co., Inc.
*/
DECLARE SUBROUTINE Set_Property, Set_Status, ErrMsg, Set_Property, obj_AppWindow, Send_Event, Send_Message
DECLARE FUNCTION Get_Property, Get_Status, Popup, Send_Message, Msg, Start_Window
$INSERT POPUP_EQUATES
$INSERT MSG_EQUATES
$INSERT APPCOLORS
$INSERT TOOL_CLASS_EQUATES
$INSERT TOOL_PROP_EQUATES
$INSERT TOOL_EQUATES
EQU EDITABLE$ TO 4
EQU PROTECTED$ TO 8 ;* Protected - Edittable COLSTYLE constants
EQU MULTILINE_STYLE$ TO 512 ;* MultiLine Select
EQU LOCKED$ TO 8192
EQU DROPDOWN_STYLE$ TO 131072
EQU HIDDEN$ TO 32
EQU SKIPPED$ TO 4100
EQU CRLF$ TO \0D0A\
EQU COL$STAGE TO 1
EQU COL$PROP_CODE TO 1
EQU COL$PROP_DESC TO 2
ErrTitle = 'Error in Comm_Tool_Class'
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:'.LU_TOOL_CLASS' AND Event = 'CLICK' ; GOSUB LUToolClass
CASE EntID = @WINDOW:'.LU_TOOL_TYPE' AND Event = 'CLICK' ; GOSUB LUToolType
CASE EntID = @WINDOW:'.LU_QIN_LOC' AND Event = 'CLICK' ; GOSUB LUQueLoc
CASE EntID = @WINDOW:'.LU_QOUT_LOC' AND Event = 'CLICK' ; GOSUB LUQueLoc
CASE EntID = @WINDOW:'.STAGE' AND Event = 'DBLCLK' ; GOSUB StageDC
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',@WINDOW)
PropStyles = Send_Message(@WINDOW:'.PROP_CD','COLSTYLE',0,'')
PropStyles
= BitOr(PropStyles,DROPDOWN_STYLE$)
Send_Message(@WINDOW:'.PROP_CD','COLSTYLE',0,PropStyles)
* Met Property dropdown Contents *
PopContents = XLATE('SYSREPOSPOPUPS','LSL2**MET_PROPERTY',8,'X')
ItemCnt = COUNT(PopContents<1>,@VM) + (PopContents<1> NE '')
PropCodes = ''
FOR I = 1 TO ItemCnt
PropCodes<1,I> = PopContents<1,I,1>
NEXT I
Send_Message(@WINDOW:'.PROP_CD','COLFORMAT',COL$PROP_CODE,PropCodes)
GOSUB Refresh
RETURN
* * * * * * *
Read:
* * * * * * *
GOSUB Refresh
RETURN
* * * * * * *
Write:
* * * * * * *
GOTO Close
RETURN
* * * * * * *
Clear:
* * * * * * *
GOTO Refresh
RETURN
* * * * * * *
Close:
* * * * * * *
obj_Appwindow('DetailReturn')
RETURN
* * * * * * *
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
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
NEXT I
RETURN
* * * * * * *
StageDC:
* * * * * * *
ClassCd = Get_Property(@WINDOW:'.CLASS_CD','DEFPROP')
CtrlEntID = @WINDOW:'.STAGE'
CurrPos = Get_Property(CtrlEntID,'SELPOS')
CurrCol = CurrPos<1>
CurrRow = CurrPos<2>
IF CurrCol = COL$STAGE THEN
Stage = Get_Property(CtrlEntID,'CELLPOS',COL$STAGE:@FM:CurrRow)
IF Stage NE '' THEN
Send_Event(@WINDOW,'WRITE')
DetWindow = 'TOOL_STAGE'
DetKeys = ClassCd:'*':Stage
DefaultRec = ''
RetKey = ClassCd
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 ;* End of Stage column
RETURN
* * * * * * *
LUToolClass:
* * * * * * *
ClassCd = Popup(@WINDOW,'','TOOL_CLASS')
IF ClassCD NE '' THEN
oaParms = @WINDOW:@RM:ClassCd
obj_Appwindow('ViewRelated',oaParms)
END
RETURN
* * * * * * *
LUToolType:
* * * * * * *
ToolType = Popup(@WINDOW,'','TOOL_TYPE')
IF ToolType NE '' THEN
oaParms = ToolType:@RM:@WINDOW:'.TOOL_TYPE'
obj_Appwindow('LUValReturn',oaParms)
END
RETURN
* * * * * * *
LUQueLoc:
* * * * * * *
BEGIN CASE
CASE EntID = @WINDOW:'.LU_QIN_LOC'
WHCtrl = @WINDOW:'.QIN_WH'
LocCtrl = @WINDOW:'.QIN_LOC'
CASE EntID = @WINDOW:'.LU_QOUT_LOC'
WHCtrl = @WINDOW:'.QOUT_WH'
LocCtrl = @WINDOW:'.QOUT_LOC'
CASE 1
RETURN
END CASE
QueID = Popup(@WINDOW,'','GAN_LOCATIONS')
IF QueID = '' OR QueID = CHAR(27) THEN RETURN
IF QueID NE '' THEN
WHCd = QueID[1,'*']
LocCd = QueID[COL2()+1,'*']
obj_Appwindow('LUValReturn',WHCd:@RM:WHCtrl)
obj_Appwindow('LUValReturn',LocCd:@RM:LocCtrl)
END
RETURN