COMPILE FUNCTION Prod_Ver(EntID,Event,Parm1,Parm2,Parm3,Parm4,Parm5)
/*
	Commuter module for PROD_VER TABLE
	
	03/15/2011 - John C. Henry, J.C. Henry & Co., Inc.
*/
DECLARE SUBROUTINE Set_Property, End_Dialog, Send_Event, Set_Status, Center_Window, Post_Event, obj_Tables
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
DECLARE SUBROUTINE obj_Cust_Epi_Part, obj_EPI_Part
DECLARE FUNCTION Get_Property, Get_Status, Dialog_Box, Utility, Popup, Collect.Ixvals, obj_Tables
DECLARE FUNCTION Send_Message, Msg, Security_Check, obj_React_Run_CI, Select_Into, NextKey, MemberOf
$INSERT MSG_EQUATES
$INSERT APPCOLORS
$INSERT LSL_USERS_EQU
$INSERT SECURITY_RIGHTS_EQU
$INSERT EPI_PART_EQUATES
$INSERT CUST_EPI_PART_EQUATES
$INSERT PROD_VER_EQUATES
$INSERT PROD_SPEC_EQUATES
$INSERT POPUP_EQUATES
$INSERT LOGICAL
$INSERT RTI_STYLE_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 CRLF$	TO \0D0A\
EQU TAB$	TO \09\
EQU COL$STEP		TO 1
EQU COL$STEP_PSN	TO 2
EQU COL$STEP_DESC	TO 3
EQU COL$PSN_STATUS	TO 4
EQU COL$REACT_TYPE	TO 5
EQU COL$TARG_THICK	TO 6
EQU COL$PRE_CLEAN	TO 7
EQU COL$POST_CLEAN	TO 8
EQU COL$TYPE		TO 9
EQU COL$MAKEUPS		TO 10
EQU COL$SUB_PART_NO			TO 1
EQU COL$SUB_SUPP_CD			TO 2
EQU COL$SUB_SUPPLIER		TO 3
EQU COL$SUB_PART_REV		TO 4
EQU COL$SUB_PURCH_SPEC		TO 5
EQU COL$SUB_PURCH_SPEC_REV	TO 6
ErrTitle = 'Error in PROD_VER Commuter PROD_VER'
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:'.NEW_PROD_VER_NO' AND			Event = 'CLICK'	; GOSUB NewProdVer
	CASE EntID = @WINDOW:'.LU_PROD_VER' AND				Event = 'CLICK'	; GOSUB LUProdVer
	CASE EntID = @WINDOW:'.LU_REACT_TYPE' AND			Event = 'CLICK'	; GOSUB LUReactType
	CASE EntID = @WINDOW:'.LU_EPI_PART_NO' AND			Event = 'CLICK'	; GOSUB LUEpiPartNo
	CASE EntID = @WINDOW:'.LU_COMP_NO' And 				Event = 'CLICK'	; GOSUB LUComp_No
	CASE EntID = @WINDOW:'.COPY_LAST' AND				Event = 'CLICK'	; GOSUB CopyLast
	CASE EntID = @WINDOW:'.VIEW_EPI_PART' AND			Event = 'CLICK'	; GOSUB ViewEpiPart
	CASE EntID = @WINDOW:'.VIEW_CUST_EPI_PART' AND		Event = 'CLICK'	; GOSUB ViewCustEpiPart
	CASE EntID = @WINDOW:'.LOAD_FROM_PROD_SPEC' AND		Event = 'CLICK'	; GOSUB LoadFromProdSpec
	
	CASE EntID = @WINDOW:'.PROC_STEP_NO'
		BEGIN CASE
			CASE Event = 'DBLCLK'			; GOSUB StepDC
		END CASE
	
	
	
	*CASE EntID = @WINDOW:'.CLEAN_RESULTS'
	*	BEGIN CASE 
	*		CASE Event = 'POSCHANGED'		; GOSUB CleanPC
	*		CASE Event = 'DBLCLK'			; GOSUB CleanDC
	*	END CASE
		
	
	*CASE EntID = @WINDOW:'.SEND_SPC' AND Event = 'CLICK' 	; GOSUB SendSPC
	
	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)
* Set result table special styles (Dropdowns)
if (MemberOf(@USER4,'EXPORT_CONTROL_ADMINS')) then
    Set_Property(@WINDOW:'.EXPORT_CONTROL','VISIBLE',1)
end else
    Set_Property(@WINDOW:'.EXPORT_CONTROL','VISIBLE',0)
end
SubPNStyles = Send_Message(@WINDOW:'.SUB_PART_NO','COLSTYLE',0,'')	
SubPNStyles
= BitOr(SubPNStyles,DROPDOWN_STYLE$)
Send_Message(@WINDOW:'.SUB_PART_NO','COLSTYLE',0,SubPNStyles)
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
* * * * * * *
Read:
* * * * * * *
GOSUB Refresh
RETURN
* * * * * * *
Write:
* * * * * * *
* Pre Event Handler
EntryID		= Get_Property(@WINDOW:'.CREATE_BY','TEXT')
CustNo		= Get_Property(@WINDOW:'.CUST_NO','DEFPROP')
PSNos		= Get_Property(@WINDOW:'.PROC_STEP_NO','ARRAY')
LOOP
	TestChar = PSNos[-1,1]
UNTIL TestChar NE @VM OR PSNos = ''
	PSNos[-1,1] = ''
REPEAT
CONVERT @VM TO @FM IN PSNos											;* PSNo's used on this PROD_VER record
PSCnt 		= COUNT(PSNos,@FM) + (PSNos NE '')
PSCustNos	= ''
FOR I = 1 TO PSCnt
	PSNo = PSNos
	PSCustNos = XLATE('PROD_SPEC',PSNo,'PROD_VER_CUST_NO','X')
NEXT I
IF EntryID = '' THEN
	CurrDate = OCONV(Date(),'D4/')
	CurrTime = OCONV(Time(),'MTH')
	CurrDTM = CurrDate:' ':CurrTime
	
	Ctrls  = @WINDOW:'.CREATE_BY':@RM		; Props  = 'TEXT':@RM	; Vals	= @USER4:@RM
	Ctrls := @WINDOW:'.CREATE_DTM'			; Props := 'DEFPROP'	; Vals := CurrDTM
	
	Set_Property(Ctrls,Props,Vals)
END
Record = Get_Property(@WINDOW,'RECORD')
Set_Property(@WINDOW,'@PREVREC',Record)
Forward_Event()
* Post Event Handler
* * * * * *  Added 1/16/2015 JCH & DKK   * * * * * * *
* *   Adds Index Transaction record to !PROD_SPEC*PROD_VER_CUST_NO to update PROD_SPEC index from Changes in PROD_VER record   * * 
IndexTransactionRows = ''		;* Index Transaction Rows to add
	
FOR I = 1 TO PSCnt
	PSNo 		= PSNos
	PSCustNo 	= PSCustNos
	NewPSCustNo = XLATE('PROD_SPEC',PSNo,'PROD_VER_CUST_NO','X')
	
	IF PSCustNo NE NewPSCustNo  THEN
		IndexTransactionRows := 'PROD_VER_CUST_NO':@FM:PSNo:@FM:PSCustNo:@FM:NewPSCustNo:@FM 
	END 
NEXT I
IF IndexTransactionRows NE '' THEN	
	
	OPEN "!PROD_SPEC" TO BangTable THEN
		LOCK BangTable, 0 THEN
			READ PendingTrans FROM BangTable, 0 ELSE PendingTrans = '0':@FM
			
			PendingTrans := IndexTransactionRows
			
			WRITE PendingTrans ON BangTable, 0 ELSE
				ErrMsg('Unable to write index transaction to !PROD_SPEC. ')
			END
			UNLOCK BangTable, 0 ELSE ErrMsg('Unable to Open !PROD_SPEC to add index transaction. ')
		END ELSE
			ErrMsg('Unable to Lock !PROD_SPEC to add index transaction. ')
		END
	END ELSE
		ErrMsg('Unable to Open !PROD_SPEC to add index transaction. ')
	END
	
END	;* End of check for changed index value
* *    End of Index transaction code.
IF Get_Property(@WINDOW,'PARENT') = 'PROD_SPEC' THEN
	Post_Event(@WINDOW,'CLOSE')
END ELSE
	GOSUB Refresh
END
Result = 0
RETURN
* * * * * * *
Refresh:
* * * * * * *
IF Get_Property(@WINDOW,'@PREVREC') NE '' AND Get_Property(@WINDOW:'.PROD_VER','DEFPROP') = '' THEN
	Set_Property(@WINDOW:'.COPY_LAST','VISIBLE',1)
END ELSE
	Set_Property(@WINDOW:'.COPY_LAST','VISIBLE',0)
END ;* End of check for @PREVREC loaded
EpiPN = Get_Property(@WINDOW:'.EPI_PART_NO','DEFPROP')
IF EpiPN NE '' THEN
	SubPartNos = XLATE('EPI_PART',EpiPN,EPI_PART_SUB_PART_NO$,'X')
	Send_Message(@WINDOW:'.SUB_PART_NO','COLFORMAT',COL$SUB_PART_NO,SubPartNos)
END ELSE
	Send_Message(@WINDOW:'.SUB_PART_NO','COLFORMAT',COL$SUB_PART_NO,'')
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 Line
NEXT I
StatusArray = Get_Property(@WINDOW:'.PROC_STEP_NO','ARRAY')
LOOP
	StatusVal = StatusArray[-1,1]
UNTIL StatusVal NE @VM OR StatusArray = ''
	StatusArray[-1,1] = ''
REPEAT
StatCnt = COUNT(StatusArray,@VM) + (StatusArray NE '')
FOR I = 1 TO StatCnt
	StatusVal = StatusArray<1,I>
	
	IF StatusVal[1,1] = 'I' THEN
		stat = Send_Message(@WINDOW:'.PROC_STEP_NO','COLOR_BY_POS',COL$PSN_STATUS,I,RED$)
	END
	IF StatusVal[1,1] = 'H' THEN
		stat = Send_Message(@WINDOW:'.PROC_STEP_NO','COLOR_BY_POS',COL$PSN_STATUS,I,ORANGE$)
	END
	
NEXT I
RETURN
* * * * * * *
NewProdVer:
* * * * * * *
ProdVerNo = Get_Property(@WINDOW:'.PROD_VER_NO','DEFPROP')
IF NOT(Security_Check('Prod Ver',WRITE$)) THEN
	Security_Err_Msg('Prod Ver',WRITE$)
	RETURN
END
IF ProdVerNo = '' THEN
	NextProdVerNo = NextKey('PROD_VER')
	obj_Appwindow('LoadFormKeys',@WINDOW:@RM:NextProdVerNo)
END
RETURN
* * * * * * *
LUProdVer:
* * * * * * *
EpiPartNo = Get_Property(@WINDOW:'.EPI_PART_NO','DEFPROP')
TypeOver = ''
IF EpiPartNo NE '' THEN
	ProdVerNos = XLATE('EPI_PART',EpiPartNo,EPI_PART_PROD_VER_NO$,'X')
	
	TypeOver	= 'K'
	TypeOver	= ProdVerNos
END
Set_Status(0)
ProdVerNos = Popup(@WINDOW,TypeOver,'PROD_VER')
errCode    = ''
IF Get_Status(errCode) THEN
	ErrMsg(errCode)
	RETURN
END
IF ProdVerNos NE '' THEN
	IF INDEX(ProdVerNos,@VM,1) THEN
		Send_Event(@WINDOW,'QBFINIT')
		Set_Property(@WINDOW,'QBFLIST',ProdVerNos)
		Send_Event(@WINDOW,'QBFFIRST')
	END ELSE
		obj_AppWindow('LoadFormKeys',@WINDOW:@RM:ProdVerNos)
	END
END
RETURN
* * * * * * *
LUReactType:
* * * * * * *
ReactType = Popup(@WINDOW,TypeOver,'REACTOR_TYPE')
IF ReactType NE '' THEN
	Set_Property(@WINDOW:'.REACT_TYPE','DEFPROP',ReactType)
END
RETURN
* * * * * * *
LUEpiPartNo:
* * * * * * *
TypeOver = ''
TypeOver = 1	;* Single selection
EpiPartNo = Popup(@WINDOW,TypeOver,'EPI_PART_NOS')
IF EpiPartNo NE '' THEN
	obj_Appwindow('LUValReturn',EpiPartNo:@RM:@WINDOW:'.EPI_PART_NO':@RM:'')
END
RETURN
* * * * * * *
LUComp_No:
* * * * * * *
CompKeys = Collect.IXVals('COA', 'COMP_NO')
CONVERT @FM TO @VM IN CompKeys
PopOver = ''
PopOver = CompKeys
CompanyKey = Popup(@WINDOW,PopOver,'COMPANY_COA')
obj_AppWindow('LUValReturn',@WINDOW:'.CUST_NO':@RM:CompanyKey)
RETURN
* * * * * * *
Close:
* * * * * * *
obj_Appwindow('DetailReturn')
RETURN
* * * * * * *
StepDC:
* * * * * * *
CtrlEntID = @WINDOW:'.PROC_STEP_NO'
CurrPos = Get_Property(CtrlEntID,'SELPOS')
CurrCol = CurrPos<1>
CurrRow = CurrPos<2>
RowData = Get_Property(CtrlEntId,'ROWDATA')
Step 	= RowData
PSNo	= RowData
IF PSNo = '' THEN
	RETURN
	/*
	SearchString = 'CUST_ID':@VM:CompNo:@FM
	Option = ''
	Flag = ''
	OPEN 'DICT.PROD_SPEC' TO DictVar ELSE RETURN
	Btree.Extract(SearchString, 'PROD_SPEC', DictVar, PSNos, Option, Flag)
	IF Get_Status(errCode) THEN ErrMsg(errCode)
	IF PSNos = '' THEN
		ErrMsg('No PSNs on file for company ':QUOTE(CompNo))
		RETURN
	END
	PSNo = ''
	IF INDEX(PSNos,@VM,1) THEN
		TypeOver = ''
		TypeOver = PSNos
		PSNo = Popup(@WINDOW,TypeOver,'PROD_SPEC')
		IF Get_Status(errCode) THEN ErrMsg(errCode)
	END ELSE
		PSNo = PSNos
	END
	IF PSNo NE '' THEN
		obj_AppWindow('LUValReturn',PSNo:@RM:CtrlEntID:@RM:CurrPos)
	END
	*/
END ELSE
	* Display the Prod Spec Window
	obj_AppWindow('ViewRelated','PROD_SPEC':@RM:PSNo)
	IF Get_Status(errCode) THEN
		ErrMsg(errCode)
	END
END
RETURN
* * * * * * *
CopyLast:
* * * * * * *
PrevRec = Get_Property(@WINDOW,'@PREVREC')
PartNo = NextKey('PART')			;* Sequential part number assigned
PartRec = PrevRec
*PartRec 	= ''
*PartRec	= ''
*PartRec	= ''
otParms = 'PART':@RM:PartNo:@RM:@RM:PartRec
obj_Tables('WriteRec',otParms)
obj_Appwindow('LoadFormKeys',@WINDOW:@RM:PartNo)
RETURN
* * * * * * * 
ViewEpiPart:
* * * * * * *
EpiPN = Get_Property(@WINDOW:'.EPI_PART_NO','DEFPROP')
ProdVerNo = Get_Property(@WINDOW:'.PROD_VER_NO','DEFPROP')
IF EpiPN = '' THEN RETURN
IF ProdVerNo = '' THEN RETURN
Send_Event(@WINDOW,'WRITE')
DetWindow	= 'EPI_PART'
DetKeys		= EpiPN
DefaultRec	= ''
RetKey		= ProdVerNo
RetWin		= @WINDOW
RetPage		= 1
RetCtrl		= ''
RetPos		= ''
obj_Appwindow('ViewNewDetail',DetWindow:@RM:DetKeys:@RM:DefaultRec:@RM:RetKey:@RM:RetPage:@RM:RetCtrl:@RM:RetPos)
RETURN
* * * * * * *
ViewCustEpiPart:
* * * * * * *
EpiPN = Get_Property(@WINDOW:'.EPI_PART_NO','DEFPROP')
ProdVerNo = Get_Property(@WINDOW:'.PROD_VER_NO','DEFPROP')
CustNo = Get_Property(@WINDOW:'.CUST_NO','DEFPROP')
IF EpiPN = '' THEN RETURN
IF ProdVerNo = '' THEN RETURN
IF CustNo = '' THEN RETURN
Send_Event(@WINDOW,'WRITE')
DetWindow	= 'CUST_EPI_PART'
DetKeys		= CustNo:'*':EpiPN
DefaultRec	= ''
RetKey		= ProdVerNo
RetWin		= @WINDOW
RetPage		= 1
RetCtrl		= ''
RetPos		= ''
obj_Appwindow('ViewNewDetail',DetWindow:@RM:DetKeys:@RM:DefaultRec:@RM:RetKey:@RM:RetPage:@RM:RetCtrl:@RM:RetPos)
RETURN
* * * * * * *
LoadFromProdSpec:
* * * * * * *
RETURN