DBA Data[Home] [Help]

PACKAGE BODY: APPS.IGS_FI_VAL_FCFL

Source


1 PACKAGE BODY IGS_FI_VAL_FCFL AS
2 /* $Header: IGSFI26B.pls 115.10 2002/11/29 12:49:29 vvutukur ship $ */
3   --who       when        what
4   --vvutukur 29-Nov-2002  Enh#2584986.Modified finp_val_fcfl_cur.
5   --vvutukur 26-Aug-2002  Bug#2531390. Modified function finp_val_fcfl_cur.
6   --vvutukur 23-Jul-2002  Removed function finp_val_fcfl_rank which validates
7   --                      payment_hierarchy_rank column, which is obsoleted.
8   -- Removed reference to IGS_FI_FEE_ENCMB since the table is obselted as part of bug 2126091 - sykrishn -30112001 --
9   -- Validate FCFL can be made ACTIVE.
10   FUNCTION finp_val_fcfl_active(
11   p_fee_liability_status IN VARCHAR2 ,
12   p_fee_cal_type IN VARCHAR2 ,
13   p_fee_ci_sequence_number IN NUMBER ,
14   p_message_name OUT NOCOPY VARCHAR2 )
15   RETURN BOOLEAN AS
16   	gv_other_detail			VARCHAR2(255);
17   BEGIN 	-- finp_val_fcfl_active
18   	-- Validates that IGS_FI_F_CAT_FEE_LBL has a system calendar category of
19   	-- 'FEE' and that the calendar instance is active when setting the
20   	-- IGS_FI_F_CAT_FEE_LBL status to active.
21   DECLARE
22   	cst_active			CONSTANT VARCHAR2(6) := 'ACTIVE';
23   	cst_fee				CONSTANT VARCHAR2(3) := 'FEE';
24   	v_s_cal_cat			IGS_CA_TYPE.s_cal_cat%TYPE;
25   	v_s_cal_status			IGS_CA_STAT.s_cal_status%TYPE;
26   	v_dummy				VARCHAR2(1);
27   	CURSOR c_fss (
28   		cp_fee_liability_status	IGS_FI_F_CAT_FEE_LBL.fee_liability_status%TYPE) IS
29   		SELECT	'x'
30   		FROM	IGS_FI_FEE_STR_STAT		fss
31   		WHERE	fss.fee_structure_status	= cp_fee_liability_status AND
32   			fss.s_fee_structure_status	= cst_active;
33   	CURSOR c_cict (
34   			cp_cal_type 			IGS_CA_INST.cal_type%TYPE,
35   			cp_sequence_number		IGS_CA_INST.sequence_number%TYPE) IS
36   		SELECT	cat.s_cal_cat,
37   			cs.s_cal_status
38   		FROM	IGS_CA_INST			ci,
39   			IGS_CA_STAT			cs,
40   			IGS_CA_TYPE			cat
41   		WHERE	ci.cal_type			= cp_cal_type AND
42   			ci.sequence_number		= cp_sequence_number AND
43   			ci.cal_type			= cat.cal_type AND
44   			ci.cal_status			= cs.cal_status;
45   BEGIN
46   	p_message_name := NULL;
47   	-- Check parameters
48   	IF(p_fee_liability_status IS NULL OR
49   			p_fee_cal_type IS NULL OR
50   			p_fee_ci_sequence_number IS NULL) THEN
51   		RETURN TRUE;
52   	END IF;
53   	-- Check system value of status.
54   	-- If not 'ACTIVE', no further processing is required.
55   	OPEN	c_fss(
56   			p_fee_liability_status);
57   	FETCH	c_fss INTO v_dummy;
58   	IF(c_fss%NOTFOUND) THEN
59   		CLOSE c_fss;
60   		RETURN TRUE;
61   	END IF;
62   	CLOSE c_fss;
63   	-- Check the calendar system category
64   	OPEN	c_cict(
65   			p_fee_cal_type,
66   			p_fee_ci_sequence_number);
67   	FETCH	c_cict INTO 	v_s_cal_cat,
68   				v_s_cal_status;
69   	CLOSE	c_cict;
70   	IF(v_s_cal_cat <> cst_fee) THEN
71   		p_message_name := 'IGS_FI_CAL_MUSTBE_CAT_AS_FEE';
72   		RETURN FALSE;
73   	END IF;
74   	IF(v_s_cal_status <> cst_active) THEN
75   		p_message_name := 'IGS_FI_CALINST_MUSTBE_ACTIVE';
76   		RETURN FALSE;
77   	END IF;
78   	RETURN TRUE;
79   END;
80   END finp_val_fcfl_active;
81   --
82   -- Ensure fields are/are not allowable.
83   FUNCTION finp_val_fcfl_rqrd(
84   p_fee_cal_type IN VARCHAR2 ,
85   p_fee_ci_sequence_number IN NUMBER ,
86   p_fee_type IN VARCHAR2 ,
87   p_chg_method IN VARCHAR2 ,
88   p_rule_sequence IN NUMBER ,
89   p_message_name OUT NOCOPY VARCHAR2 )
90   RETURN BOOLEAN AS
91   	gv_other_detail		VARCHAR2(255);
92   BEGIN
93   DECLARE
94   	v_fee_type	IGS_FI_FEE_TYPE.fee_type%TYPE;
95   	v_s_fee_trigger_cat	IGS_FI_FEE_TYPE.s_fee_trigger_cat%TYPE;
96   	v_s_chg_method_type	IGS_FI_F_TYP_CA_INST.s_chg_method_type%TYPE;
97   	v_rul_sequence_number	IGS_FI_F_TYP_CA_INST.rul_sequence_number%TYPE;
98   	cst_fee_trigger_cat	CONSTANT	VARCHAR2(9):= 'INSTITUTN';
99   	cst_fee_type		CONSTANT	VARCHAR2(4):= 'HECS';
100   	CURSOR c_ft IS
101   		SELECT	ft.s_fee_type,
102   			ft.s_fee_trigger_cat
103   		FROM	IGS_FI_FEE_TYPE	ft
104   		WHERE	ft.fee_type = p_fee_type;
105   	CURSOR c_ftci IS
106   		SELECT 	ftci.s_chg_method_type,
107   			ftci.rul_sequence_number
108   		FROM	IGS_FI_F_TYP_CA_INST	ftci
109   		WHERE	ftci.fee_cal_type = p_fee_cal_type AND
110   			ftci.fee_ci_sequence_number = p_fee_ci_sequence_number AND
111   			ftci.fee_type = p_fee_type;
112   BEGIN
113   	-- Validate if IGS_FI_F_CAT_FEE_LBL.s_chg_method_type and
114   	--IGS_FI_F_CAT_FEE_LBL.rul_sequence_number are required or
115   	--not, depending on related values.
116   	--1.	Check parameters.
117   	IF (p_fee_cal_type IS NULL OR
118   			p_fee_ci_sequence_number IS NULL OR
119   			p_fee_type IS NULL) THEN
120   		p_message_name := NULL;
121   		RETURN TRUE;
122   	END IF;
123   	--2.	If p_chg_method is not null or p_rule_sequence is not
124   	--null then validate the fee_type to see if it is permissable
125   	--for these values to be specified. Not permissable when
126   	--IGS_FI_FEE_TYPE.s_fee_trigger_cat = 'INSTITUTN' or s_fee_type =
127   	--'HECS'.
128   	OPEN c_ft;
129   	FETCH c_ft INTO		v_fee_type,
130   				v_s_fee_trigger_cat;
131   	CLOSE c_ft;
132   	IF v_fee_type = cst_fee_type AND p_chg_method is not null THEN
133   		p_message_name := 'IGS_FI_CHARGE_METHOD_NOT_SPEC';
134   		RETURN FALSE;
135   	END IF;
136   	IF v_fee_type = cst_fee_type AND p_rule_sequence is not null THEN
137   		p_message_name := 'IGS_FI_RULSEQ_HECS';
138   		RETURN FALSE;
139   	END IF;
140   	IF v_s_fee_trigger_cat = cst_fee_trigger_cat AND
141   	   p_chg_method is not null THEN
142   		p_message_name := 'IGS_FI_CHGMTH_INSTITUTN';
143   		RETURN FALSE;
144   	END IF;
145   	IF  v_fee_type = cst_fee_type AND
146   	   p_rule_sequence is not null THEN
147   		p_message_name := 'IGS_FI_RULE_SEQ_NOT_SPECIFIED';
148   		RETURN FALSE;
149   	END IF;
150   	--3.	Validate the IGS_FI_F_TYP_CA_INST record to see if
151   	-- these fields are set.  If not, they must be specified in the
152   	-- IGS_FI_F_CAT_FEE_LBL record.  If they are, they cannot be
153   	-- specified in the IGS_FI_F_CAT_FEE_LBL record.
154   	IF  v_fee_type <> cst_fee_type AND  v_fee_type <> cst_fee_type THEN
155   		OPEN c_ftci;
156   		FETCH c_ftci INTO	v_s_chg_method_type,
157   					v_rul_sequence_number;
158   		CLOSE c_ftci;
159     		IF v_s_chg_method_type IS NOT NULL AND
160     				p_chg_method IS NOT NULL THEN
161     			p_message_name := 'IGS_FI_CHGMTH_FEETYPE_EXISTS';
162     			RETURN FALSE;
163     		END IF;
164     		IF v_rul_sequence_number IS NOT NULL AND
165     				p_rule_sequence IS NOT NULL THEN
166     			p_message_name := 'IGS_FI_RULSEQ_FEETYPE_EXISTS';
167     			RETURN FALSE;
168     		END IF;
169   		IF v_s_chg_method_type IS NULL AND
170   				p_chg_method IS NULL THEN
171   			p_message_name := 'IGS_FI_CHARGE_METHOD_SPECIFY';
172   			RETURN FALSE;
173   		END IF;
174   		IF v_rul_sequence_number IS NULL AND
175   				p_rule_sequence IS NULL THEN
176   			p_message_name := 'IGS_FI_RULE_SEQ_SPECIFY';
177   			RETURN FALSE;
178   		END IF;
179   	END IF;
180   	--4.	Return no error.
181   	p_message_name := NULL;
182   	RETURN TRUE;
183   END;
184   END finp_val_fcfl_rqrd;
185   --
186   -- Ensure status value is allowed.
187   FUNCTION finp_val_fcfl_status(
188   p_fee_cal_type IN VARCHAR2 ,
189   p_fee_ci_sequence_number IN NUMBER ,
190   p_fee_cat IN VARCHAR2 ,
191   p_fee_type IN VARCHAR2 ,
192   p_fee_status IN VARCHAR2 ,
193   p_message_name OUT NOCOPY VARCHAR2 )
194   RETURN BOOLEAN AS
195   	gv_other_detail		VARCHAR2(255);
196   BEGIN
197   DECLARE
198   	v_fss_fee_structure_status	IGS_FI_FEE_STR_STAT.s_fee_structure_status%TYPE;
199   	cst_active_status		CONSTANT	VARCHAR2(6):= 'ACTIVE';
200   	CURSOR c_ftci IS
201   		SELECT	fss.s_fee_structure_status
202   		FROM	IGS_FI_F_TYP_CA_INST	ftci,
203   			IGS_FI_FEE_STR_STAT	fss
204   		WHERE	ftci.fee_cal_type = p_fee_cal_type AND
205   			ftci.fee_ci_sequence_number = p_fee_ci_sequence_number AND
206   			ftci.fee_type = p_fee_type AND
207   			ftci.fee_type_ci_status = fss.fee_structure_status;
208   	CURSOR c_fss IS
209   		SELECT	fss.s_fee_structure_status
210   		FROM	IGS_FI_FEE_STR_STAT	fss
211   		WHERE	fss.fee_structure_status = p_fee_status;
212   	CURSOR c_fcci IS
213   		SELECT	fss.s_fee_structure_status
214   		FROM	IGS_FI_F_CAT_CA_INST	fcci,
215   			IGS_FI_FEE_STR_STAT	fss
216   		WHERE	fcci.fee_cal_type = p_fee_cal_type AND
217   			fcci.fee_ci_sequence_number = p_fee_ci_sequence_number AND
218   			fcci.fee_cat = p_fee_cat AND
219   			fcci.fee_cat_ci_status = fss.fee_structure_status;
220   BEGIN
221   	--Validate IGS_FI_F_CAT_FEE_LBL.fee_liability_status.  Check
222   	-- that parent records have a status of 'ACTIVE' when
223   	-- setting fee_liability_status to 'ACTIVE'.
224   	--1. 	Check Parameters
225   	IF (p_fee_cal_type IS NULL OR
226   			p_fee_ci_sequence_number IS NULL OR
227   			p_fee_cat IS NULL OR
228   			p_fee_type IS NULL OR
229   			p_fee_status IS NULL) THEN
230   		p_message_name := NULL;
231   		RETURN TRUE;
232   	END IF;
233   	--2.	Get the system status of the fee status.  If not 'ACTIVE'
234   	--no further processing is required.
235   	OPEN c_fss;
236   	FETCH c_fss INTO v_fss_fee_structure_status;
237   	CLOSE c_fss;
238   	IF (v_fss_fee_structure_status IS NULL OR
239   			v_fss_fee_structure_status <> cst_active_status) THEN
240   		p_message_name := NULL;
241   		RETURN TRUE;
242   	END IF;
243   	v_fss_fee_structure_status := NULL;
244   	--3.	Validate that corresponding IGS_FI_F_TYP_CA_INST
245   	-- record has status of 'ACTIVE'. (IGS_GE_NOTE: IGS_FI_F_CAT_FEE_LBL
246   	-- records cannot exist without corresponding IGS_FI_F_TYP_CA_INST
247   	-- records.
248   	OPEN c_ftci;
249   	FETCH c_ftci INTO v_fss_fee_structure_status;
250   	CLOSE c_ftci;
251   	IF (v_fss_fee_structure_status IS NULL OR
252   			v_fss_fee_structure_status <> cst_active_status) THEN
253   		p_message_name := 'IGS_FI_STNOT_ACTIVE_CORTYPE';
254   		RETURN FALSE;
255   	END IF;
256   	v_fss_fee_structure_status := NULL;
257   	--4.	Validate that corresdponding fee_cal_cat_instance record
258   	-- has a status of 'ACTIVE'. (IGS_GE_NOTE: IGS_FI_F_CAT_FEE_LBL
259   	-- records cannot exist without corresponding IGS_FI_F_TYP_CA_INST
260   	-- records.
261   	OPEN c_fcci;
262   	FETCH c_fcci INTO v_fss_fee_structure_status;
263   	CLOSE c_fcci;
264   	IF (v_fss_fee_structure_status IS NULL OR
265   			v_fss_fee_structure_status <> cst_active_status) THEN
266   		p_message_name := 'IGS_FI_STNOT_ACTIVE_CORCAT';
267   		RETURN FALSE;
268   	END IF;
269   	--5.	Return no error.
270   	p_message_name := NULL;
271   	RETURN TRUE;
272   END;
273   END finp_val_fcfl_status;
274   --
275   -- Validate insert of FCFL does not clash currency with FTCI definitions
276   FUNCTION finp_val_fcfl_cur(
277   p_fee_cal_type IN IGS_CA_TYPE.cal_type%TYPE ,
278   p_fee_ci_sequence_number IN IGS_CA_INST_ALL.sequence_number%TYPE ,
279   p_fee_type IN IGS_FI_FEE_TYPE_ALL.fee_type%TYPE ,
280   p_fee_cat IN IGS_FI_FEE_CAT_ALL.fee_cat%TYPE ,
281   p_message_name OUT NOCOPY VARCHAR2 )
282   RETURN BOOLEAN AS
283   /*----------------------------------------------------------------------------
284   ||  Created By :
285   ||  Created On :
286   ||  Purpose :
287   ||  Known limitations, enhancements or remarks :
288   ||  Change History :
289   ||  Who             When            What
290   ||  (reverse chronological order - newest change first)
291   ||  vvutukur        29-Nov-2002  Enh#2584986.Removed references to igs_fi_cur as the same has been
292   ||                               obsoleted.Instead defaulted the currency that is set up in System Options Form.
293   ----------------------------------------------------------------------------*/
294   	gv_other_detail		VARCHAR2(255);
295   BEGIN	-- finp_val_fcfl_cur
296   	-- Validate insert of the IGS_FI_F_CAT_FEE_LBL.
297   	-- When the fee category currency does not match the local currency
298   	-- check there are no inherited definitions taken from the
299   	-- fee type calendar instance. All definitions at the FTCI level
300   	-- operate under the local currency
301   DECLARE
302   	v_check			CHAR;
303   	v_fee_cat_currency_cd	igs_fi_control.currency_cd%TYPE;
304         l_v_currency            igs_fi_control.currency_cd%TYPE;
305 
306         CURSOR cur_ctrl IS
307           SELECT currency_cd
308           FROM   igs_fi_control;
309 
310   	CURSOR c_fc	IS
311   		SELECT	currency_cd
312   		FROM	IGS_FI_FEE_CAT
313   		WHERE	fee_cat	= p_fee_cat;
314 
315   	CURSOR c_frtns	IS
316   		SELECT	'x'
317   		FROM	IGS_FI_FEE_RET_SCHD
318   		WHERE	fee_cal_type = p_fee_cal_type AND
319   			fee_ci_sequence_number = p_fee_ci_sequence_number AND
320   			s_relation_type = 'FTCI' AND
321   			fee_type = p_fee_type;
322 
323   -- Removed reference to IGS_FI_FEE_ENCMB(c_fe cursor) since the table is obselted as part of bug 2126091 - sykrishn -30112001 --
324   	CURSOR c_far	IS
325   		SELECT	'x'
326   		FROM	IGS_FI_FEE_AS_RATE
327   		WHERE	fee_type = p_fee_type AND
328   			fee_cal_type = p_fee_cal_type AND
329   			fee_ci_sequence_number = p_fee_ci_sequence_number AND
330   			s_relation_type = 'FTCI' AND
331   			logical_delete_dt IS NULL;
332   BEGIN
333   	p_message_name := NULL;
334   	-- get the fee category currency code
335   	OPEN c_fc;
336   	FETCH c_fc INTO v_fee_cat_currency_cd;
337   	CLOSE	c_fc;
338   	IF (v_fee_cat_currency_cd IS NULL) THEN
339   		-- local currency is the default
340   		RETURN TRUE;
341   	END IF;
342 
343         --Capture the default currency that is set up in System Options Form.
344         OPEN cur_ctrl;
345         FETCH cur_ctrl INTO l_v_currency;
346         IF cur_ctrl%NOTFOUND THEN
347           p_message_name := 'IGS_FI_SYSTEM_OPT_SETUP';
348           CLOSE cur_ctrl;
349           RETURN FALSE;
350         END IF;
351         CLOSE cur_ctrl;
352 
353  	IF (v_fee_cat_currency_cd = l_v_currency) THEN
354   		-- local currency is being used
355   		RETURN TRUE;
356   	END IF;
357   	-- check there are no definitions under the fee category taken from
358   	-- the fee type calendar instance. All definitions at the FTCI level
359   	-- operate under the local currency
360 
361   	-- check if FTCI retention schedules exist for the fee category fee liability
362   	OPEN	c_frtns;
363   	FETCH	c_frtns INTO v_check;
364   	IF (c_frtns%FOUND) THEN
365   		CLOSE c_frtns;
366   		p_message_name := 'IGS_FI_FEETYPE_CLASH_RETNSCH';
367   		RETURN FALSE;
368   	END IF;
369   	CLOSE	c_frtns;
370   	-- check if FTCI fee encumbrances exist for the fee category fee liability
371    -- This check Removed since reference to IGS_FI_FEE_ENCMB is removed since the table is obselted as part of bug 2126091 - sykrishn -30112001 --
372   	-- check if FTCI fee assessment rates exist for the fee category fee liability
373   	OPEN	c_far;
374   	FETCH	c_far INTO v_check;
375   	IF (c_far%FOUND) THEN
376   		CLOSE c_far;
377   		p_message_name := 'IGS_FI_FEETYPE_CLASH_FEEASSES';
378   		RETURN FALSE;
379   	END IF;
380   	CLOSE	c_far;
381   	RETURN TRUE;
382   END;
383   END finp_val_fcfl_cur;
384   --
385   -- Validate the fee structure status closed indicator
386   -- bug 1956374 Duplicate code removal removed finp_val_fss_closed
387   -- Validate the PAYMENT_HIERARCHY_RANK
388   -- As part of bugfix#2425767, removed function finp_val_fcfl_rank, as payment_hierarchy_rank column is
389   -- obsoleted.
390 END IGS_FI_VAL_FCFL;