DBA Data[Home] [Help]

PACKAGE BODY: APPS.PA_PROJECT_VERIFY_PKG

Source


1 PACKAGE BODY PA_PROJECT_VERIFY_PKG AS
2 /* $Header: PAXPRVRB.pls 120.3 2007/02/06 10:18:36 dthakker ship $ */
3 
4   PROCEDURE customer_exists
5 		 (x_project_id		IN     NUMBER,
6                   x_err_stage           IN OUT NOCOPY VARCHAR2, --File.Sql.39 bug 4440895
7                   x_err_code            IN OUT NOCOPY NUMBER, --File.Sql.39 bug 4440895
8 		  x_err_stack           IN OUT NOCOPY VARCHAR2, --File.Sql.39 bug 4440895
9 		  x_err_msgname		IN OUT NOCOPY VARCHAR2) is --File.Sql.39 bug 4440895
10     CURSOR get_top_task_cust_enbled IS
11     SELECT enable_top_task_customer_flag
12     FROM pa_projects_all
13     WHERE project_id = x_project_id;
14     l_en_top_task_cust_flag VARCHAR2(1);
15 
16     --added the below code for Federal changes by sunkalya
17     --sunkalya:federal Bug#5511353
18     CURSOR get_date_eff_funds_flag
19     IS
20     SELECT nvl(DATE_EFF_FUNDS_CONSUMPTION,'N')
21     FROM
22     pa_projects_all
23     WHERE project_id = x_project_id;
24     l_date_eff_funds_flag VARCHAR2(1);
25 
26     --end of code added for federal changes by sunkalya
27     --sunkalya:federal Bug#5511353
28 
29     x_old_stack varchar2(630);
30     dummy number;
31   begin
32     x_err_code := 0;
33     x_old_stack := x_err_stack;
34     x_err_stack := x_err_stack ||'->PA_PROJECT_VERIFY_PKG.client_exists';
35     x_err_msgname := NULL;
36     x_err_stage := 'Checking client exists...';
37 
38     OPEN get_top_task_cust_enbled;
39     FETCH get_top_task_cust_enbled INTO l_en_top_task_cust_flag;
40     CLOSE get_top_task_cust_enbled;
41 
42     OPEN  get_date_eff_funds_flag;
43     FETCH get_date_eff_funds_flag INTO l_date_eff_funds_flag;
44     CLOSE get_date_eff_funds_flag;
45 
46     --modified the below if for federal changes by sunkalya
47     --sunkalya:federal Bug#5511353
48     IF l_en_top_task_cust_flag <> 'Y' AND l_date_eff_funds_flag <> 'Y' THEN
49         SELECT NULL
50         INTO dummy
51         FROM sys.dual
52         WHERE exists (
53           SELECT NULL
54           FROM    PA_PROJECT_CUSTOMERS
55           WHERE   PROJECT_ID = x_project_id
56           GROUP   BY PROJECT_ID
57           HAVING SUM(CUSTOMER_BILL_SPLIT) = 100);
58     END IF;
59 
60     x_err_stack := x_old_stack;
61   exception
62     when NO_DATA_FOUND then
63       x_err_code := 10;
64       x_err_stage := 'PA_NO_CLIENT_EXISTS';
65       x_err_msgname := 'PA_PR_INSUF_BILL_SPLIT';
66     when others then
67       x_err_code := SQLCODE;
68   end customer_exists;
69 
70   PROCEDURE contact_exists
71 		 (x_project_id		IN     NUMBER,
72                   x_err_stage           IN OUT NOCOPY VARCHAR2, --File.Sql.39 bug 4440895
73                   x_err_code            IN OUT NOCOPY NUMBER, --File.Sql.39 bug 4440895
74 		  x_err_stack           IN OUT NOCOPY VARCHAR2, --File.Sql.39 bug 4440895
75 		  x_err_msgname		IN OUT NOCOPY VARCHAR2) is --File.Sql.39 bug 4440895
76     x_old_stack varchar2(630);
77     dummy number;
78   begin
79     x_err_code := 0;
80     x_old_stack := x_err_stack;
81     x_err_stack := x_err_stack ||'->PA_PROJECT_VERIFY_PKG.contact_exists';
82     x_err_msgname := NULL;
83     x_err_stage := 'Checking contact exists...';
84     SELECT NULL
85     INTO dummy
86     FROM sys.dual
87     WHERE exists (
88       SELECT NULL
89       FROM    PA_PROJECT_CUSTOMERS CUST
90       WHERE   CUST.PROJECT_ID = x_project_id
91       AND     CUST.CUSTOMER_BILL_SPLIT > 0
92       AND     NOT EXISTS (SELECT NULL
93                   FROM    PA_PROJECT_CONTACTS CONT
94                   WHERE   CONT.PROJECT_ID = x_project_id
95                   AND     CONT.CUSTOMER_ID=  CUST.CUSTOMER_ID
96                   AND     CONT.PROJECT_CONTACT_TYPE_CODE = 'BILLING'));
97     x_err_code := 10;
98     x_err_stage := 'PA_NO_CONTACT_EXISTS';
99     x_err_msgname := 'PA_PR_INSUF_BILL_CONTACT';
100   exception
101     when NO_DATA_FOUND then
102       x_err_stack := x_old_stack;
103     when others then
104       x_err_code := SQLCODE;
105   end contact_exists;
106 
107   PROCEDURE category_required
108 		 (x_project_id		IN     NUMBER,
109                   x_err_stage           IN OUT NOCOPY VARCHAR2, --File.Sql.39 bug 4440895
110                   x_err_code            IN OUT NOCOPY NUMBER, --File.Sql.39 bug 4440895
111 		  x_err_stack           IN OUT NOCOPY VARCHAR2, --File.Sql.39 bug 4440895
112 		  x_err_msgname		IN OUT NOCOPY VARCHAR2) is --File.Sql.39 bug 4440895
113     x_old_stack varchar2(630);
114     dummy number;
115 
116     /*
117     The following cursor has been commented for Performance Bug # 3691123
118     The cursor is split into C11 and C12 for performance reasons so that
119     queries can be based on base tables directly.
120 
121     CURSOR C1
122     IS
123     SELECT NULL
124     FROM    PA_VALID_CATEGORIES_V VC,
125             PA_PROJECTS_ALL PPA,
126             PA_PROJECT_TYPES_ALL PPTA
127     WHERE   VC.MANDATORY_FLAG = 'Y'
128     AND     PPA.PROJECT_ID = x_project_id
129     AND     PPA.PROJECT_TYPE = PPTA.PROJECT_TYPE
130     AND     nvl(PPA.ORG_ID, -99) = nvl(PPTA.ORG_ID, -99)
131     AND     VC.OBJECT_TYPE_ID = PPTA.PROJECT_TYPE_ID
132     AND     NOT EXISTS (SELECT NULL
133                         FROM   PA_PROJECT_CLASSES PC
134                        WHERE   PC.PROJECT_ID = x_project_id
135                          AND   PC.CLASS_CATEGORY = VC.CLASS_CATEGORY);
136     */
137 
138     CURSOR C11
139     IS
140     SELECT NULL
141       FROM DUAL
142      WHERE EXISTS
143     (
144     SELECT 1
145     FROM   PA_CLASS_CATEGORIES cc,
146            PA_VALID_CATEGORIES vc,
147            PA_PROJECT_TYPES_ALL PPTA,
148            PA_PROJECTS_ALL PPA
149     WHERE  VC.CLASS_CATEGORY = CC.CLASS_CATEGORY
150     AND    TRUNC(SYSDATE) BETWEEN TRUNC(CC.START_DATE_ACTIVE)
151                               AND TRUNC(NVL(CC.END_DATE_ACTIVE, SYSDATE))
152     AND    VC.OBJECT_TYPE_ID = PPTA.PROJECT_TYPE_ID
153     AND    TRUNC(SYSDATE) BETWEEN TRUNC(PPTA.START_DATE_ACTIVE)
154 			      AND TRUNC(NVL(PPTA.END_DATE_ACTIVE, SYSDATE))
155     AND    VC.MANDATORY_FLAG = 'Y'
156     AND    PPA.PROJECT_ID = x_project_id
157     AND    PPA.PROJECT_TYPE = PPTA.PROJECT_TYPE
158     AND    PPA.ORG_ID = PPTA.ORG_ID --MOAC Changes: Bug 4363092: removed nvl usage with org_id
159     AND    NOT EXISTS (SELECT NULL
160                         FROM   PA_PROJECT_CLASSES PC
161                        WHERE   PC.PROJECT_ID = x_project_id
162                          AND   PC.CLASS_CATEGORY = VC.CLASS_CATEGORY)
163     );
164 
165     CURSOR C12
166     IS
167     SELECT NULL
168       FROM DUAL
169      WHERE EXISTS (SELECT 1
170                      from PA_CLASS_CATEGORIES CC
171                     WHERE CC.MANDATORY_FLAG = 'Y'
172                       AND CC.OBJECT_TYPE = 'PA_PROJECTS'
173                       AND CC.ALL_TYPES_VALID_FLAG = 'Y'
174                       AND TRUNC(SYSDATE) BETWEEN TRUNC(CC.START_DATE_ACTIVE)
175 					     AND TRUNC(NVL(CC.END_DATE_ACTIVE, SYSDATE))
176                       AND NOT EXISTS(SELECT   NULL
177                                        FROM   PA_PROJECT_CLASSES PC
178                                       WHERE   PC.PROJECT_ID = x_project_id
179                                         AND   PC.CLASS_CATEGORY = CC.CLASS_CATEGORY)
180     );
181 
182     /*
183     The following cursor has been commented for Performance Bug # 3691123
184     The cursor looks only for sort_order = 'A'
185     This View PA_PROJECT_CLASS_TOTALS_V has two select statements joined by UNION
186     The 1st select statement is for sort_order A and C / the 2nd select statement for B
187 
188     So,the query can be based directly on the base table as in 1st select statement of the view
189     CURSOR C2
190     IS
191     SELECT NULL
192     FROM   PA_PROJECT_CLASS_TOTALS_V
193     WHERE  project_id = x_project_id
194     AND    sort_order = 'A';
195     */
196 
197     /* Start of new code for Performance Bug # 3691123 */
198     CURSOR C2
199     IS
200     SELECT NULL
201     FROM PA_PROJECT_CLASSES
202     WHERE  project_id = x_project_id
203     AND    OBJECT_TYPE = 'PA_PROJECTS'
204     AND    decode(PA_PROJECTS_MAINT_UTILS.GET_CLASS_EXCEPTIONS(object_id,object_type, class_category, 'N'), NULL, 'C', 'A') = 'A'
205     ;
206 
207     /*End  code for Performance Bug # 3691123 */
208   begin
209     -- This procedure has been modified for Classification enhancements
210     -- It checks whether there are any mandatory categories that have not
211     -- been specified
212     -- It also checks if there are any categories defined for this project
213     -- that have the total 100 percent flag enabled, but whose defined
214     -- defined class codes do not actually total 100
215     x_err_code := 0;
216     x_old_stack := x_err_stack;
217     x_err_stack := x_err_stack ||'->PA_PROJECT_VERIFY_PKG.category_required';
218     x_err_msgname := NULL;
219     x_err_stage := 'Checking required category exists...';
220 
221     OPEN C11;
222     FETCH C11 INTO dummy;
223     if C11%FOUND then
224       CLOSE C11;
225       x_err_code := 10;
226       x_err_stage := 'PA_NO_REQ_CATEGORY_EXISTS';
227       x_err_msgname := 'PA_PR_INSUF_CLASS_CODES';
228       return;
229     else
230         OPEN C12;
231         FETCH C12 INTO dummy;
232         if C12%FOUND then
233             CLOSE C12;
234             x_err_code := 10;
235             x_err_stage := 'PA_NO_REQ_CATEGORY_EXISTS';
236             x_err_msgname := 'PA_PR_INSUF_CLASS_CODES';
237             return;
238         end if;
239         CLOSE C12 ;
240     end if;
241 
242     CLOSE C11 ;
243 
244     x_err_stage := 'Checking total class code percentages...';
245 
246     OPEN C2;
247     FETCH C2 INTO dummy;
248     if C2%FOUND then
249       CLOSE C2;
250       x_err_code := 20;
251       x_err_stage := 'PA_CLASS_TOTALS_INVALID';
252       x_err_msgname := 'PA_PR_CLASS_TOTAL_INVLD';
253       return;
254     end if;
255     CLOSE C2;
256 
257     x_err_stack := x_old_stack;
258   exception
259     when others then
260       x_err_code := SQLCODE;
261   end category_required;
262 
263   PROCEDURE manager_exists
264 		 (x_project_id		IN     NUMBER,
265                   x_err_stage           IN OUT NOCOPY VARCHAR2, --File.Sql.39 bug 4440895
266                   x_err_code            IN OUT NOCOPY NUMBER, --File.Sql.39 bug 4440895
267 		  x_err_stack           IN OUT NOCOPY VARCHAR2, --File.Sql.39 bug 4440895
268 		  x_err_msgname		IN OUT NOCOPY VARCHAR2) is --File.Sql.39 bug 4440895
269     x_old_stack varchar2(630);
270     proj_start_date DATE;
271     km_start_date DATE;
272     km_end_date DATE;
273     l_dummy NUMBER := 0;
274     CURSOR c1 IS
275       SELECT NVL(Start_Date,trunc(Sysdate)) FROM Pa_Projects_all -- Bug#3807805 : Modified Pa_Projects to Pa_Projects_all
276       WHERE   PROJECT_ID = x_project_id;
277 
278      /* Added the following cursor instead of select statement to
279         handle the "too many rows selected" condition.
280         Bug fix for # 824266 */
281 
282     CURSOR c2 IS
283      SELECT START_DATE_ACTIVE,END_DATE_ACTIVE
284      FROM    PA_PROJECT_PLAYERS
285      WHERE   PROJECT_ID = x_project_id
286      AND     PROJECT_ROLE_TYPE = 'PROJECT MANAGER';
287  BEGIN
288    x_err_code := 0;
289    x_old_stack := x_err_stack;
290    x_err_stack := x_err_stack ||'->PA_PROJECT_VERIFY_PKG.manager_exists';
291    x_err_msgname := NULL;
292    x_err_stage := 'Checking manager exists...';
293 
294    OPEN c1 ;
295    FETCH c1 INTO proj_start_date ;
296    IF c1%notfound then
297         SELECT TRUNC(Sysdate) INTO proj_start_date FROM Dual;
298    END IF;
299    CLOSE c1 ;
300 
301    /* Changed the following logic to use cursor and loop */
302    /* For bug # 824266 fix  */
303 
304    OPEN c2;
305    LOOP
306      FETCH c2 INTO km_start_date,km_end_date ;
307      EXIT WHEN c2%NOTFOUND ;
308 
309      IF TRUNC(SYSDATE) BETWEEN
310         km_start_date AND nvl(km_end_date,GREATEST(km_start_date,TRUNC(SYSDATE)))
311       OR
312         proj_start_date BETWEEN
313         km_start_date AND nvl(km_end_date,GREATEST(km_start_date,TRUNC(SYSDATE)))
314       OR
315         (proj_start_date > TRUNC(SYSDATE) AND
316          km_start_date BETWEEN TRUNC(SYSDATE) and proj_start_date
317          AND km_end_date IS NULL )
318      THEN
319         l_dummy := 0;
320         EXIT ;
321      ELSE
322         l_dummy := -1;
323      END IF;
324    END LOOP;
325 
326    IF c2%ROWCOUNT = 0 THEN
327       close c2;
328       raise no_data_found;
329    END IF;
330 
331    CLOSE c2;
332    /* End of changes made for bug # 824266 fix  */
333 
334    IF l_dummy = -1 THEN
335       x_err_code := 10;
336       x_err_stage := 'PA_NO_MANAGER_EXISTS';
337       x_err_msgname := 'PA_PR_INSUF_PROJ_MGR';
338    END IF;
339    x_err_stack := x_old_stack;
340   exception
341     when NO_DATA_FOUND then
342       x_err_code := 10;
343       x_err_stage := 'PA_NO_MANAGER_EXISTS';
344       x_err_msgname := 'PA_PR_INSUF_PROJ_MGR';
345     when others then
346       x_err_code := SQLCODE;
347  END manager_exists;
348 
349   PROCEDURE revenue_budget
350 		 (x_project_id		IN     NUMBER,
351                   x_err_stage           IN OUT NOCOPY VARCHAR2, --File.Sql.39 bug 4440895
352                   x_err_code            IN OUT NOCOPY NUMBER, --File.Sql.39 bug 4440895
353 		  x_err_stack           IN OUT NOCOPY VARCHAR2, --File.Sql.39 bug 4440895
354 		  x_err_msgname		IN OUT NOCOPY VARCHAR2) is --File.Sql.39 bug 4440895
355     x_old_stack varchar2(630);
356     dummy number;
357   begin
358     x_err_code := 0;
359     x_old_stack := x_err_stack;
360     x_err_stack := x_err_stack ||'->PA_PROJECT_VERIFY_PKG.revenue_budget';
361     x_err_msgname := NULL;
362     x_err_stage := 'Checking revenue budget exists...';
363     SELECT 'x'  INTO dummy
364     FROM PA_BUDGET_VERSIONS bv,
365 		    PA_BUDGET_TYPES bt
366     WHERE
367     bv.budget_type_code = bt.budget_type_code
368     AND bt.budget_amount_code = 'R';
369     x_err_stack := x_old_stack;
370   exception
371     when NO_DATA_FOUND then
372       x_err_code := 10;
373       x_err_stage := 'PA_NO_REV_BUDGET_EXISTS';
374       x_err_msgname := 'PA_PR_NO_REV_BUDGET';
375     when others then
376       x_err_code := SQLCODE;
377   end revenue_budget;
378 
379   PROCEDURE cost_budget
380 		 (x_project_id		IN     NUMBER,
381                   x_err_stage           IN OUT NOCOPY VARCHAR2, --File.Sql.39 bug 4440895
382                   x_err_code            IN OUT NOCOPY NUMBER, --File.Sql.39 bug 4440895
383 		  x_err_stack           IN OUT NOCOPY VARCHAR2, --File.Sql.39 bug 4440895
384 		  x_err_msgname		IN OUT NOCOPY VARCHAR2) is --File.Sql.39 bug 4440895
385     x_old_stack varchar2(630);
386     dummy number;
387   begin
388     x_err_code := 0;
389     x_old_stack := x_err_stack;
390     x_err_stack := x_err_stack ||'->PA_PROJECT_VERIFY_PKG.cost_budget';
391     x_err_msgname := NULL;
392     x_err_stage := 'Checking cost budget exists...';
393     SELECT 'x'  INTO dummy
394     FROM PA_BUDGET_VERSIONS bv,
395 		    PA_BUDGET_TYPES bt
396     WHERE
397     bv.budget_type_code = bt.budget_type_code
398     AND bt.budget_amount_code = 'C';
399     x_err_stack := x_old_stack;
400   exception
401     when NO_DATA_FOUND then
402        x_err_code := 10;
403        x_err_stage := 'PA_NO_COST_BUDGET_EXISTS';
404        x_err_msgname := 'PA_PR_NO_COST_BUDGET';
405     when others then
406       x_err_code := SQLCODE;
407   end cost_budget;
408 
409   PROCEDURE billing_event
410 		 (x_project_id		IN     NUMBER,
411                   x_err_stage           IN OUT NOCOPY VARCHAR2, --File.Sql.39 bug 4440895
412                   x_err_code            IN OUT NOCOPY NUMBER, --File.Sql.39 bug 4440895
413 		  x_err_stack           IN OUT NOCOPY VARCHAR2, --File.Sql.39 bug 4440895
414 		  x_err_msgname		IN OUT NOCOPY VARCHAR2, --File.Sql.39 bug 4440895
415 		  x_eamt_token_name	IN OUT NOCOPY VARCHAR2, --File.Sql.39 bug 4440895
416 		  x_eamt_token_value	IN OUT NOCOPY VARCHAR2) is --File.Sql.39 bug 4440895
417     x_old_stack varchar2(630);
418     dummy number;
419   begin
420     x_err_code := 0;
421     x_old_stack := x_err_stack;
422     x_err_stack := x_err_stack ||'->PA_PROJECT_VERIFY_PKG.billing_event';
423     x_err_msgname := NULL;
424     x_eamt_token_name := 'EAMT';
425     x_eamt_token_value := 0;
426 /*  Commented out for now,since the code is incorrectly referencing
427     pa_subbudgets. Need to fix this since pa_subbudgets is obsolete
428     in Rel 11.0 - Ramesh - 01/13/1998
429     x_err_stage := 'Checking billing event exists...';
430     SELECT NULL
431     INTO dummy
432     FROM sys.dual
433     WHERE exists (
434       select  NULL
435       from    pa_events e
436       ,       pa_event_Types et
437       ,       pa_tasks t
438       where   nvl(e.task_id,t.task_id) = t.task_id
439 	and	e.project_id = t.project_id
440       and     e.event_type = et.event_Type
441       and     t.project_id = x_project_id
442       and     e.completion_date is not null
443       having  sum(nvl(decode(et.event_type_classification,
444                       'INVOICE REDUCTION',-e.bill_amount,
445                                            e.bill_amount),0)) =
446               (select sum(nvl(revenue,0))
447               from pa_subbudgets s
448               ,       pa_tasks t
449               where   s.project_id = x_project_id
450               and     s.budget_Type_code= 'DRAFT'
451               and     s.task_id = t.task_id(+)
452               and     t.task_id = t.top_task_id
453               ));
454 */
455     x_err_stack := x_old_stack;
456   exception
457     when NO_DATA_FOUND then
458       NULL;
459      /*  Commented out since the original sql has been commented out
460       begin
461         select to_char(sum(nvl(decode(et.event_type_classification,
462                         'INVOICE REDUCTION', -e.bill_amount,
463                                               e.bill_amount),0)))
464         into x_eamt_token_value
465         from    pa_events e
466         ,       pa_event_Types et
467         ,       pa_tasks t
468         where   nvl(e.task_id, t.task_id) = t.task_id
469         and	e.project_id = t.project_id
470         and     e.event_Type = et.event_Type
471         and     t.project_id = x_project_id
472         and     e.completion_date is not null;
473       exception
474         when others then
475           null;
476       end;
477       x_err_code := 10;
478       x_err_stage := 'PA_NO_BILL_EVENT_EXISTS';
479       x_err_msgname := 'PA_PR_NEED_BILLING_EVENTS';
480    */
481     when others then
482       x_err_code := SQLCODE;
483   end billing_event;
484 
485 end PA_PROJECT_VERIFY_PKG;