445 lines
		
	
	
		
			16 KiB
		
	
	
	
		
			Plaintext
		
	
	
	
	
	
			
		
		
	
	
			445 lines
		
	
	
		
			16 KiB
		
	
	
	
		
			Plaintext
		
	
	
	
	
	
| COMPILE FUNCTION Quote_Sigs(EntID,Event,Parm1,Parm2,Parm3,Parm4,Parm5)
 | |
| 
 | |
| /*
 | |
| 	Commuter module for Quote_Sigs (Work Process Access Control) window
 | |
| 	
 | |
| 	01/7/2010 - John C. Henry, J.C. Henry & Co., Inc.
 | |
| */
 | |
| 
 | |
| DECLARE SUBROUTINE Set_Property, End_Dialog, Send_Event, Set_Status, obj_Tables,ErrMsg
 | |
| DECLARE SUBROUTINE ErrMsg, Send_Message, Set_Property, Send_Event, Btree.Extract, obj_AppWindow, Send_Dyn
 | |
| DECLARE SUBROUTINE obj_Notes, Security_Err_Msg, End_Window, Forward_Event, Start_Window, Create_Note
 | |
| 
 | |
| DECLARE FUNCTION Get_Property, Get_Status, Dialog_Box, Utility, Popup, Collect.Ixvals
 | |
| DECLARE FUNCTION Send_Message, Msg, Security_Check, Admin_User, obj_Tables
 | |
| 
 | |
| 
 | |
| 
 | |
| $INSERT MSG_EQUATES
 | |
| $INSERT APPCOLORS
 | |
| $INSERT LSL_USERS_EQU
 | |
| $INSERT SECURITY_RIGHTS_EQU
 | |
| $INSERT QUOTE_SIGS_EQU
 | |
| $INSERT POPUP_EQUATES
 | |
| 
 | |
| EQU CRLF$	TO \0D0A\
 | |
| EQU TAB$	TO \09\
 | |
| 
 | |
| 
 | |
| ErrTitle = 'Error in Quote_Sigs'
 | |
| ErrorMsg = ''
 | |
| 
 | |
| Result = ''
 | |
| 
 | |
| 
 | |
| BEGIN CASE
 | |
|     CASE EntID = @WINDOW
 | |
|         BEGIN CASE
 | |
|             CASE Event = 'CLEAR'			; GOSUB Clear
 | |
|             CASE Event = 'CREATE' 			; GOSUB Create
 | |
|             CASE Event = 'CLOSE'			; GOSUB Close
 | |
|                 
 | |
|         END CASE
 | |
|         
 | |
|     CASE EntID = @WINDOW:'.CANCEL' AND Event = 'CLICK'			; GOSUB Cancel
 | |
|     CASE EntID = @WINDOW:'.SAVE' AND Event = 'CLICK'			; GOSUB Save
 | |
|         
 | |
|     CASE EntID = @WINDOW:'.NUM_SIGS'		AND Event = 'OPTIONS'	; GOSUB UserNameOption
 | |
|     CASE EntID = @WINDOW:'.SIGNERS'			AND Event = 'OPTIONS'	; GOSUB UserNameOption
 | |
|     CASE EntID = @WINDOW:'.WO_SIG_PROF'		AND Event = 'OPTIONS'	; GOSUB UserNameOption
 | |
|     CASE EntID = @WINDOW:'.VIP_MFG'			AND Event = 'OPTIONS'	; GOSUB UserNameOption
 | |
|     CASE EntID = @WINDOW:'.VIP_MFG_PWD' 	AND Event = 'OPTIONS'	; GOSUB UserNameOption
 | |
|     CASE EntID = @WINDOW:'.ENG_MGR'			AND Event = 'OPTIONS'	; GOSUB UserNameOption
 | |
|     CASE EntID = @WINDOW:'.FACIL_MGR'		AND Event = 'OPTIONS'	; GOSUB UserNameOption
 | |
|     CASE EntID = @WINDOW:'.MAINT_MGR'		AND Event = 'OPTIONS'	; GOSUB UserNameOption
 | |
|     CASE EntID = @WINDOW:'.MKT_MGR'			AND Event = 'OPTIONS'	; GOSUB UserNameOption
 | |
|     CASE EntID = @WINDOW:'.MKT_MGR_PWD'		AND Event = 'OPTIONS'	; GOSUB UserNameOption
 | |
|     CASE EntID = @WINDOW:'.MTLS_MGR'		AND Event = 'OPTIONS'	; GOSUB UserNameOption
 | |
|     CASE EntID = @WINDOW:'.PROD_CTRL_MGR'	AND Event = 'OPTIONS'	; GOSUB UserNameOption
 | |
|     CASE EntID = @WINDOW:'.PROD_MGR'		AND Event = 'OPTIONS'	; GOSUB UserNameOption
 | |
|     CASE EntID = @WINDOW:'.QUALITY_MGR'		AND Event = 'OPTIONS'	; GOSUB UserNameOption
 | |
|     CASE EntID = @WINDOW:'.SHIP_MGR'		AND Event = 'OPTIONS'	; GOSUB UserNameOption
 | |
|     CASE EntID = @WINDOW:'.MET_MGR'			AND Event = 'OPTIONS'	; GOSUB UserNameOption
 | |
|     CASE EntID = @WINDOW:'.SHIFT1_SUP'		AND Event = 'OPTIONS'	; GOSUB UserNameOption
 | |
|     CASE EntID = @WINDOW:'.SHIFT1_QTL'		AND Event = 'OPTIONS'	; GOSUB UserNameOption
 | |
|     CASE EntID = @WINDOW:'.SHIFT2_SUP'		AND Event = 'OPTIONS'	; GOSUB UserNameOption
 | |
|     CASE EntID = @WINDOW:'.SHIFT2_QTL'		AND Event = 'OPTIONS'	; GOSUB UserNameOption
 | |
|     CASE EntID = @WINDOW:'.SHIFT3_SUP'		AND Event = 'OPTIONS'	; GOSUB UserNameOption
 | |
|     CASE EntID = @WINDOW:'.SHIFT3_QTL'		AND Event = 'OPTIONS'	; GOSUB UserNameOption
 | |
|     CASE EntID = @WINDOW:'.SHIFT4_SUP'		AND Event = 'OPTIONS'	; GOSUB UserNameOption
 | |
|     CASE EntID = @WINDOW:'.SHIFT4_QTL'		AND Event = 'OPTIONS'	; GOSUB UserNameOption
 | |
|     CASE EntID = @WINDOW:'.EPIPRO_LEAD'		AND Event = 'OPTIONS'	; GOSUB UserNameOption
 | |
|     CASE EntID = @WINDOW:'.REENG_SPEC'		AND Event = 'OPTIONS'	; GOSUB UserNameOption
 | |
|     CASE EntID = @WINDOW:'.TRAIN_SPEC'		AND Event = 'OPTIONS'	; GOSUB UserNameOption
 | |
|     CASE EntID = @WINDOW:'.MAIN_FAX_USER'	AND Event = 'OPTIONS'	; GOSUB UserNameOption
 | |
|     CASE EntID = @WINDOW:'.PREQUAL_SIGS'	AND Event = 'OPTIONS'	; GOSUB UserNameOption
 | |
|     CASE EntID = @WINDOW:'.QUAL_SIGS'		AND Event = 'OPTIONS'	; GOSUB UserNameOption
 | |
|     CASE EntID = @WINDOW:'.PREPROD_SIGS'	AND Event = 'OPTIONS'	; GOSUB UserNameOption
 | |
|     CASE EntID = @WINDOW:'.PROD_SIGS'		AND Event = 'OPTIONS'	; GOSUB UserNameOption
 | |
|     CASE EntID = @WINDOW:'.RCV_MGR'	    	AND Event = 'OPTIONS'	; GOSUB UserNameOption
 | |
|         
 | |
| 
 | |
|     CASE 1
 | |
|         ErrorMsg = 'Unknown Parameters ':EntID:' - ':Event:' passed to commuter'
 | |
|         ErrMsg(ErrorMsg)
 | |
|         RETURN
 | |
|         
 | |
| END CASE
 | |
| 
 | |
| IF ErrorMsg NE '' THEN
 | |
|     ErrMsg(ErrTitle:@SVM:ErrorMsg)
 | |
| END
 | |
| 
 | |
| RETURN Result
 | |
| 
 | |
| 
 | |
| 
 | |
| * * * * * * *
 | |
| UserNameOption:
 | |
| * * * * * * *
 | |
|     
 | |
|     
 | |
|     EditTables  = Utility('OBJECTLIST', @WINDOW, 'EDITTABLE')
 | |
|     EditLines = Utility('OBJECTLIST',@WINDOW,'EDITFIELD')
 | |
|     
 | |
|     LOCATE EntID IN EditLines USING @FM SETTING Pos THEN
 | |
|         
 | |
|         TypeOver = ''
 | |
|         TypeOver<PSELECT$> = 1	;* Single Select
 | |
|         
 | |
|         Result = Popup(@WINDOW,TypeOver,'SHOW_USERS')
 | |
|         
 | |
|         
 | |
|         IF Result NE '' THEN
 | |
|             Set_Property(EntID,'DEFPROP',Result)
 | |
|             RETURN
 | |
|         END
 | |
|     END
 | |
|     
 | |
|     LOCATE EntID IN EditTables USING @FM SETTING Dummy THEN
 | |
|         
 | |
|         TypeOver = ''
 | |
|         TypeOver<PSELECT$> = 2	;* Multiple Select
 | |
|         
 | |
|         Result = Popup(@WINDOW,TypeOver,'SHOW_USERS')
 | |
|         
 | |
|         CurrList = Get_Property(EntID,'LIST')
 | |
|         
 | |
|         IF INDEX(CurrList<1>,@VM,1) THEN
 | |
|             NullLine = @VM
 | |
|         END ELSE
 | |
|             NullLine = ''
 | |
|         END	
 | |
|         
 | |
|         LOOP
 | |
|             LastLine = CurrList[-1,'B':@FM]
 | |
|         UNTIL LastLine NE NullLine
 | |
|             CurrList[COL1(),99] = ''
 | |
|         REPEAT
 | |
|         
 | |
|         
 | |
|         RCnt = COUNT(Result,@VM) + (Result NE '')
 | |
|         
 | |
|         FOR I = 1 TO RCnt
 | |
|             IF INDEX(CurrList<1>,@VM,1) THEN
 | |
|                 CurrList<-1> = Result<1,I>:@VM
 | |
|             END ELSE
 | |
|                 CurrList<-1> = Result<1,I>
 | |
|             END
 | |
|         NEXT I
 | |
|         
 | |
|         Set_Property(EntID,'LIST',CurrList)
 | |
|         
 | |
|     END
 | |
|     
 | |
|     
 | |
|     
 | |
|     
 | |
| RETURN
 | |
| 
 | |
| 
 | |
| 
 | |
| * * * * * * *
 | |
| Create:
 | |
| * * * * * * *
 | |
|     
 | |
|     obj_Appwindow('Create',@WINDOW)
 | |
|     
 | |
|     
 | |
|     IF Admin_User( @USER4 ) THEN
 | |
|         
 | |
|         OPEN 'CONFIG' TO ConfigTable ELSE
 | |
|             ErrMsg('Unable to open CONFIG table' )
 | |
|             End_Dialog(@WINDOW, '' )
 | |
|             RETURN
 | |
|         END
 | |
|         
 | |
|         LOCK ConfigTable, 'QUOTE_SIGS' ELSE
 | |
|             ErrMsg('QUOTE_SIGS is in use somewhere else...' )
 | |
|             End_Dialog( @WINDOW, '' )
 | |
|             RETURN
 | |
|         END
 | |
|         
 | |
|         READ QuoteSigInfo FROM ConfigTable,'QUOTE_SIGS' ELSE
 | |
|             ErrMsg('Unable to READ QuoteSigInfo FROM "CONFIG", "QUOTE_SIGS" record' )
 | |
|             End_Dialog( @WINDOW, '' )
 | |
|             RETURN
 | |
|         END
 | |
|         
 | |
|         IF QuoteSigInfo NE '' THEN
 | |
|             
 | |
|             NumQuoteSigs		= QuoteSigInfo<NumQuoteSigs$>
 | |
|             
 | |
|             QuoteSigners		= QuoteSigInfo<QuoteSigners$>
 | |
|             QuotePassWords		= QuoteSigInfo<QSPasswords$>
 | |
|             
 | |
|             RefreshWOMatSigProf	= QuoteSigInfo<RefreshWOMatSigProf$>
 | |
|             
 | |
|             VPMfg				= QuoteSigInfo<VipMfg$>
 | |
|             VPMfgPwd			= QuoteSigInfo<VipMfgPwd$>
 | |
|             EngMgr				= QuoteSigInfo<EngMgr$>
 | |
|             FacMgr				= QuoteSigInfo<FacilMgr$>
 | |
|             MaintMgr			= QuoteSigInfo<MaintMgr$>
 | |
|             MarketingMgr		= QuoteSigInfo<MktMgr$>
 | |
|             MarketingMgrPwd		= QuoteSigInfo<MktMgrPwd$>
 | |
|             MaterialsMgr		= QuoteSigInfo<MtlsMgr$>
 | |
|             ProdCtrlMgr			= QuoteSigInfo<ProdCtrlMgr$>
 | |
|             ProdMgr				= QuoteSigInfo<ProdMgr$>
 | |
|             QualityMgr			= QuoteSigInfo<QualityMgr$>
 | |
|             QualityMgr2			= QuoteSigInfo<QualityMgr2$>
 | |
|             ShippingMgr			= QuoteSigInfo<ShipMgr$>
 | |
|             MetMgr				= QuoteSigInfo<MetMgr$>
 | |
|             
 | |
|             Shift1Sup			= QuoteSigInfo<Shift1Sup$>
 | |
|             Shift1Lead			= QuoteSigInfo<Shift1Lead$>
 | |
|             Shift2Sup			= QuoteSigInfo<Shift2Sup$>
 | |
|             Shift2Lead			= QuoteSigInfo<Shift2Lead$>
 | |
|             Shift3Sup			= QuoteSigInfo<Shift3Sup$>
 | |
|             Shift3Lead			= QuoteSigInfo<Shift3Lead$>
 | |
|             Shift4Sup			= QuoteSigInfo<Shift4Sup$>
 | |
|             Shift4Lead			= QuoteSigInfo<Shift4Lead$>
 | |
|             
 | |
|             EpiPROLead			= QuoteSigInfo<EpiPROLead$>
 | |
|             ReEngSpec			= QuoteSigInfo<ReEngSpec$>
 | |
|             TrainingSpec		= QuoteSigInfo<TrainSpec$>
 | |
|             
 | |
|             QuoteFaxUser		= QuoteSigInfo<QuoteFaxUser$>
 | |
|             
 | |
|             PSNPreQualSigs		= QuoteSigInfo<PSNPreQualSigs$>
 | |
|             PSNQualSigs			= QuoteSigInfo<PSNQualSigs$>
 | |
|             PSNPreProdSigs		= QuoteSigInfo<PSNPreProdSigs$>
 | |
|             PSNProdSigs			= QuoteSigInfo<PSNProdSigs$>
 | |
|             
 | |
|             RcvMgr              = QuoteSigInfo<RcvMgr$>
 | |
|             
 | |
|             Set_Property(@WINDOW:'.NUM_SIGS','TEXT',NumQuoteSigs)
 | |
|             Set_Property(@WINDOW:'.SIGNERS','ARRAY',QuoteSigners:@FM:QuotePassWords)
 | |
|             Set_Property(@WINDOW:'.WO_SIG_PROF','ARRAY',RefreshWOMatSigProf)
 | |
|             Set_Property(@WINDOW:'.VIP_MFG','TEXT',VPMfg)
 | |
|             Set_Property(@WINDOW:'.VIP_MFG_PWD','TEXT',VPMfgPwd)
 | |
|             
 | |
|             Set_Property(@WINDOW:'.ENG_MGR','TEXT',EngMgr)
 | |
|             Set_Property(@WINDOW:'.FACIL_MGR','TEXT',FacMgr)
 | |
|             Set_Property(@WINDOW:'.MAINT_MGR','TEXT',MaintMgr)
 | |
|             Set_Property(@WINDOW:'.MKT_MGR','TEXT',MarketingMgr)
 | |
|             Set_Property(@WINDOW:'.MKT_MGR_PWD','TEXT',MarketingMgrPwd)
 | |
|             Set_Property(@WINDOW:'.MTLS_MGR','TEXT',MaterialsMgr)
 | |
|             Set_Property(@WINDOW:'.PROD_CTRL_MGR','TEXT',ProdCtrlMgr)
 | |
|             Set_Property(@WINDOW:'.PROD_MGR','TEXT',ProdMgr)
 | |
|             Set_Property(@WINDOW:'.QUALITY_MGR','TEXT',QualityMgr)
 | |
|             Set_Property(@WINDOW:'.QUALITY_MGR2','TEXT',QualityMgr2)
 | |
|             Set_Property(@WINDOW:'.SHIP_MGR','TEXT',ShippingMgr)
 | |
|             Set_Property(@WINDOW:'.MET_MGR','TEXT',MetMgr)
 | |
|             Set_Property(@WINDOW:'.SHIFT1_SUP','TEXT',Shift1Sup)
 | |
|             Set_Property(@WINDOW:'.SHIFT1_QTL','TEXT',Shift1Lead)
 | |
|             Set_Property(@WINDOW:'.SHIFT2_SUP','TEXT',Shift2Sup)
 | |
|             Set_Property(@WINDOW:'.SHIFT2_QTL','TEXT',Shift2Lead)
 | |
|             Set_Property(@WINDOW:'.SHIFT3_SUP','TEXT',Shift3Sup)
 | |
|             Set_Property(@WINDOW:'.SHIFT3_QTL','TEXT',Shift3Lead)
 | |
|             Set_Property(@WINDOW:'.SHIFT4_SUP','TEXT',Shift4Sup)
 | |
|             Set_Property(@WINDOW:'.SHIFT4_QTL','TEXT',Shift4Lead)
 | |
|             
 | |
|             Set_Property(@WINDOW:'.EPIPRO_LEAD','TEXT',EpiPROLead)
 | |
|             Set_Property(@WINDOW:'.REENG_SPEC','TEXT',ReEngSpec)
 | |
|             Set_Property(@WINDOW:'.TRAIN_SPEC','TEXT',TrainingSpec)
 | |
|             Set_Property(@WINDOW:'.MAIN_FAX_USER','TEXT',QuoteFaxUser)
 | |
|             
 | |
|             Set_Property(@WINDOW:'.RCV_MGR','TEXT',RcvMgr)
 | |
|             
 | |
| 
 | |
|             
 | |
|             Set_Property(@WINDOW:'.PREQUAL_SIGS','ARRAY',PSNPreQualSigs)
 | |
|             Set_Property(@WINDOW:'.QUAL_SIGS','ARRAY',PSNQualSigs)
 | |
|             Set_Property(@WINDOW:'.PREPROD_SIGS','ARRAY',PSNPreProdSigs)
 | |
|             Set_Property(@WINDOW:'.PROD_SIGS','ARRAY',PSNProdSigs)  
 | |
|             
 | |
|         END	;* End of check for null data
 | |
|     END ELSE
 | |
|         Message = 'You do not have the proper security to enter Authorized quote signatures...' 
 | |
|         Message<micon$> = 'H'
 | |
|         MSG( '', Message )
 | |
|         Send_Event( @WINDOW, 'CLOSE' )
 | |
|     END
 | |
|     
 | |
|     
 | |
| 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
 | |
|     
 | |
|     
 | |
|     
 | |
|     
 | |
|     
 | |
|     * * * * * * *
 | |
| Save:
 | |
| * * * * * * *
 | |
|     
 | |
|     
 | |
|     OPEN 'CONFIG' TO ConfigTable ELSE
 | |
|         ErrMsg('Unable to open CONFIG table' )
 | |
|         End_Dialog(@WINDOW, '' )
 | |
|         RETURN
 | |
|     END
 | |
|     
 | |
|     
 | |
|     
 | |
|     NumQuoteSigs	= Get_Property(@WINDOW:'.NUM_SIGS','TEXT')
 | |
|     
 | |
|     SignerArray		= Get_Property(@WINDOW:'.SIGNERS','ARRAY')
 | |
|     QuoteSigners	= SignerArray<1>
 | |
|     QuotePassWords	= SignerArray<2>
 | |
|     
 | |
|     
 | |
|     RefreshWOMatSigProf	= Get_Property(@WINDOW:'.WO_SIG_PROF','ARRAY')
 | |
|     
 | |
|     VPMfg			= Get_Property(@WINDOW:'.VIP_MFG','TEXT')
 | |
|     VPMfgPwd		= Get_Property(@WINDOW:'.VIP_MFG_PWD','TEXT')
 | |
|     
 | |
|     EngMgr			= Get_Property(@WINDOW:'.ENG_MGR','TEXT')
 | |
|     FacMgr			= Get_Property(@WINDOW:'.FACIL_MGR','TEXT')
 | |
|     MaintMgr		= Get_Property(@WINDOW:'.MAINT_MGR','TEXT')
 | |
|     MarketingMgr	= Get_Property(@WINDOW:'.MKT_MGR','TEXT')
 | |
|     MarketingMgrPwd	= Get_Property(@WINDOW:'.MKT_MGR_PWD','TEXT')
 | |
|     MaterialsMgr	= Get_Property(@WINDOW:'.MTLS_MGR','TEXT')
 | |
|     ProdCtrlMgr		= Get_Property(@WINDOW:'.PROD_CTRL_MGR','TEXT')
 | |
|     ProdMgr			= Get_Property(@WINDOW:'.PROD_MGR','TEXT')
 | |
|     QualityMgr		= Get_Property(@WINDOW:'.QUALITY_MGR','TEXT')
 | |
|     QualityMgr2		= Get_Property(@WINDOW:'.QUALITY_MGR2','TEXT')
 | |
|     ShippingMgr		= Get_Property(@WINDOW:'.SHIP_MGR','TEXT')
 | |
|     MetMgr			= Get_Property(@WINDOW:'.MET_MGR','TEXT')
 | |
|     Shift1Sup		= Get_Property(@WINDOW:'.SHIFT1_SUP','TEXT')
 | |
|     Shift1Lead		= Get_Property(@WINDOW:'.SHIFT1_QTL','TEXT')
 | |
|     Shift2Sup		= Get_Property(@WINDOW:'.SHIFT2_SUP','TEXT')
 | |
|     Shift2Lead		= Get_Property(@WINDOW:'.SHIFT2_QTL','TEXT')
 | |
|     Shift3Sup		= Get_Property(@WINDOW:'.SHIFT3_SUP','TEXT')
 | |
|     Shift3Lead		= Get_Property(@WINDOW:'.SHIFT3_QTL','TEXT')
 | |
|     Shift4Sup		= Get_Property(@WINDOW:'.SHIFT4_SUP','TEXT')
 | |
|     Shift4Lead		= Get_Property(@WINDOW:'.SHIFT4_QTL','TEXT')
 | |
|     
 | |
|     EpiPROLead		= Get_Property(@WINDOW:'.EPIPRO_LEAD','TEXT')
 | |
|     ReEngSpec		= Get_Property(@WINDOW:'.REENG_SPEC','TEXT')
 | |
|     TrainingSpec	= Get_Property(@WINDOW:'.TRAIN_SPEC','TEXT')
 | |
|     QuoteFaxUser	= Get_Property(@WINDOW:'.MAIN_FAX_USER','TEXT')
 | |
|     RcvMgr      	= Get_Property(@WINDOW:'.RCV_MGR','TEXT')
 | |
| 
 | |
|     
 | |
|     PSNPreQualSigs	= Get_Property(@WINDOW:'.PREQUAL_SIGS','ARRAY')
 | |
|     PSNQualSigs		= Get_Property(@WINDOW:'.QUAL_SIGS','ARRAY')
 | |
|     PSNPreProdSigs	= Get_Property(@WINDOW:'.PREPROD_SIGS','ARRAY')
 | |
|     PSNProdSigs		= Get_Property(@WINDOW:'.PROD_SIGS','ARRAY')  
 | |
|     
 | |
|     
 | |
|     QuoteSigInfo = ''
 | |
|     
 | |
|     QuoteSigInfo<NumQuoteSigs$>			= NumQuoteSigs
 | |
|     
 | |
|     QuoteSigInfo<QuoteSigners$>			= QuoteSigners
 | |
|     QuoteSigInfo<QSPasswords$>			= QuotePassWords
 | |
|     
 | |
|     QuoteSigInfo<RefreshWOMatSigProf$>	= RefreshWOMatSigProf
 | |
|     
 | |
|     QuoteSigInfo<VipMfg$>				= VPMfg
 | |
|     QuoteSigInfo<VipMfgPwd$>			= VPMfgPwd
 | |
|     QuoteSigInfo<EngMgr$>				= EngMgr
 | |
|     QuoteSigInfo<FacilMgr$>				= FacMgr
 | |
|     QuoteSigInfo<MaintMgr$>				= MaintMgr
 | |
|     QuoteSigInfo<MktMgr$>				= MarketingMgr
 | |
|     QuoteSigInfo<MktMgrPwd$>			= MarketingMgrPwd
 | |
|     QuoteSigInfo<MtlsMgr$>				= MaterialsMgr
 | |
|     QuoteSigInfo<ProdCtrlMgr$>			= ProdCtrlMgr
 | |
|     QuoteSigInfo<ProdMgr$>				= ProdMgr
 | |
|     QuoteSigInfo<QualityMgr$>			= QualityMgr
 | |
|     QuoteSigInfo<QualityMgr2$>			= QualityMgr2
 | |
|     QuoteSigInfo<ShipMgr$>				= ShippingMgr
 | |
|     QuoteSigInfo<MetMgr$>				= MetMgr
 | |
|     
 | |
|     QuoteSigInfo<Shift1Sup$>			= Shift1Sup
 | |
|     QuoteSigInfo<Shift1Lead$>			= Shift1Lead
 | |
|     QuoteSigInfo<Shift2Sup$>			= Shift2Sup
 | |
|     QuoteSigInfo<Shift2Lead$>			= Shift2Lead
 | |
|     QuoteSigInfo<Shift3Sup$>			= Shift3Sup
 | |
|     QuoteSigInfo<Shift3Lead$>			= Shift3Lead
 | |
|     QuoteSigInfo<Shift4Sup$>			= Shift4Sup
 | |
|     QuoteSigInfo<Shift4Lead$>			= Shift4Lead
 | |
|     
 | |
|     QuoteSigInfo<EpiPROLead$>			= EpiPROLead
 | |
|     QuoteSigInfo<ReEngSpec$>			= ReEngSpec
 | |
|     QuoteSigInfo<TrainSpec$>			= TrainingSpec
 | |
|     
 | |
|     QuoteSigInfo<QuoteFaxUser$>			= QuoteFaxUser
 | |
|     QuoteSigInfo<RcvMgr$>			    = RcvMgr
 | |
|     
 | |
|     QuoteSigInfo<PSNPreQualSigs$>		= PSNPreQualSigs
 | |
|     QuoteSigInfo<PSNQualSigs$>			= PSNQualSigs	
 | |
|     QuoteSigInfo<PSNPreProdSigs$>		= PSNPreProdSigs
 | |
|     QuoteSigInfo<PSNProdSigs$>			= PSNProdSigs
 | |
|     
 | |
|     
 | |
|     WRITE QuoteSigInfo ON ConfigTable, 'QUOTE_SIGS' ELSE
 | |
|         ErrMsg('Unable to write QUOTE_SIGS in CONFIG table' )
 | |
|         End_Dialog(@WINDOW, '' )
 | |
|         RETURN
 | |
|     END
 | |
|     
 | |
|     UNLOCK ConfigTable,'QUOTE_SIGS' ELSE
 | |
|         ErrMsg( 'Unable to unlock QUOTE_SIGS in CONFIG table' )
 | |
|     END
 | |
|     
 | |
|     End_Dialog(@WINDOW, '' )
 | |
|     
 | |
| RETURN
 | |
| 
 | |
| 
 | |
| * * * * * *
 | |
| Close:
 | |
| * * * * * * 
 | |
|     
 | |
|     
 | |
|     
 | |
|     * * * * * * *
 | |
| Cancel:
 | |
| * * * * * * *
 | |
|     
 | |
|     OPEN 'CONFIG' TO ConfigTable ELSE
 | |
|         ErrMsg('Unable to open CONFIG table' )
 | |
|         End_Dialog(@WINDOW, '' )
 | |
|         RETURN
 | |
|     END
 | |
|     
 | |
|     UNLOCK ConfigTable, 'QUOTE_SIGS' ELSE NULL
 | |
|     
 | |
|     End_Dialog(@WINDOW, '' )
 | |
|     
 | |
| RETURN
 | |
| 
 | |
| 
 |