DBA Data[Home] [Help]

PACKAGE BODY: APPS.GMS_LD_PKG

Source


1 PACKAGE BODY GMS_LD_PKG AS
2 -- $Header: gmsenxfb.pls 120.5.12020000.2 2012/07/18 09:30:02 admarath ship $
3 
4    -- Bug :3265300, 3345880
5    -- PSP: encumbrance summarize and transfer gives 'GMS_UNEXPECTED_ERROR'
6    -- Procedure created to log unexpected errors in the log file.
7    -- irrespective of the debug enabled flag.
8    PROCEDURE write_to_log( p_message varchar2 ) IS
9    BEGIN
10        if p_message is NULL then
11           return ;
12        end if ;
13 
14        fnd_file.put(fnd_file.log, substr(p_message,1,255)) ;
15 
16        if substr(p_message,256) is not null then
17           fnd_file.put(fnd_file.log, substr(p_message,256)) ;
18        end if ;
19    END write_to_log ;
20 
21    PROCEDURE PRE_PROCESS (P_TRANSACTION_SOURCE    IN  VARCHAR2,
22                          P_BATCH                 IN  VARCHAR2,
23                          P_XFACE_ID              IN  NUMBER,
24                          P_USER_ID               IN  NUMBER) IS
25 
26     CURSOR TrxBatches IS
27     SELECT
28 	        xc.transaction_source
29     ,       xc.batch_name
30     ,       xc.system_linkage_function
31     --,       xc.batch_name ||xc.system_linkage_function|| to_char(P_xface_id) exp_group_name name  --Bug 3035863 : commented as its not used anywhere
32       FROM
33             pa_transaction_xface_control xc
34      WHERE
35             xc.transaction_source = P_transaction_source
36        AND  xc.batch_name         = nvl(P_batch, xc.batch_name)
37        AND  xc.status             = 'PENDING';
38 
39     -- PA.L Changes
40     CURSOR c_trans_source is
41     SELECT allow_emp_org_override_flag ,
42            purgeable_flag              ,   -- Added following columns for Bug 3035863
43            allow_duplicate_reference_flag,
44 	   gl_accounted_flag ,
45            allow_reversal_flag     ,
46            costed_flag             ,
47            allow_burden_flag
48       from pa_transaction_sources
49      where transaction_source = P_TRANSACTION_SOURCE ;
50     -- PA.L Changes.
51 
52     CURSOR TrxRecs ( X_transaction_source  VARCHAR2
53                    , current_batch         VARCHAR2
54                    , curr_etype_class_code VARCHAR2  ) IS
55     SELECT
56             to_char(trunc(expenditure_ending_date), 'J')||':'||
57             nvl(employee_number, '-DUMMY EMP-')||':'||
58             nvl(organization_name, '-DUMMY ORG-')||':'||
59             nvl(orig_exp_txn_reference1, '-DUMMY EXP_TXN_REF1-') || ':' ||
60             nvl(orig_user_exp_txn_reference, '-DUMMY USER_EXP_TXN_REF-') || ':' ||
61             nvl(vendor_number, '-DUMMY VENDOR_NUMBER-') || ':' ||
62             nvl(orig_exp_txn_reference2, '-DUMMY EXP_TXN_REF2-') || ':' ||
63             nvl(orig_exp_txn_reference3, '-DUMMY EXP_TXN_REF3-') expend
64     ,       decode(system_linkage,'OT','ST',system_linkage) || ':' ||
65             decode(system_linkage,'ER', nvl(denom_currency_code,'-DUMMY CODE-'),
66                                   'VI', nvl(denom_currency_code,'-DUMMY CODE-'),
67                                   '-DUMMY CODE-')||':'||
68             decode(system_linkage,'ER', nvl(to_char(acct_rate_date,'MMDDYYYY'),'-DUMMY DATE-'),
69                                   'VI', nvl(to_char(acct_rate_date,'MMDDYYYY'),'-DUMMY DATE-'),
70                                   '-DUMMY DATE-')||':'||
71             decode(system_linkage,'ER', nvl(acct_rate_type,'-DUMMY TYPE-'),
72                                   'VI', nvl(acct_rate_type,'-DUMMY TYPE-'),
73                                   '-DUMMY TYPE-')||':'||
74             decode(system_linkage,'ER', nvl(to_char(acct_exchange_rate),'-DUMMY RATE-'),
75                                   'VI', nvl(to_char(acct_exchange_rate),'-DUMMY RATE-'),
76                                   '-DUMMY RATE-') expend2
77     ,       system_linkage
78     ,       trunc(expenditure_ending_date) expenditure_ending_date
79     ,       employee_number
80     ,       organization_name
81     ,       trunc(expenditure_item_date) expenditure_item_date
82     ,       project_number
83     ,       task_number
84     ,       expenditure_type
85     ,       non_labor_resource
86     ,       non_labor_resource_org_name
87     ,       quantity
88     ,       raw_cost
89     ,       raw_cost_rate
90     ,       orig_transaction_reference
91     ,       attribute_category
92     ,       attribute1
93     ,       attribute2
94     ,       attribute3
95     ,       attribute4
96     ,       attribute5
97     ,       attribute6
98     ,       attribute7
99     ,       attribute8
100     ,       attribute9
101     ,       attribute10
102     ,       expenditure_comment
103     ,       interface_id
104     ,       expenditure_id
105     ,       nvl(unmatched_negative_txn_flag, 'N') unmatched_negative_txn_flag
106     ,       to_number( NULL )  expenditure_item_id
107     ,       to_number( NULL )  job_id
108     ,       org_id             org_id
109     ,       dr_code_combination_id
110     ,       cr_code_combination_id
111     ,       cdl_system_reference1
112     ,       cdl_system_reference2
113     ,       cdl_system_reference3
114     ,       gl_date
115     ,       burdened_cost
116     ,       burdened_cost_rate
117     ,       receipt_currency_amount
118     ,       receipt_currency_code
119     ,	      receipt_exchange_rate
120     ,       denom_currency_code
121     ,	      denom_raw_cost
122     ,	      denom_burdened_cost
123     ,	      acct_rate_date
124     ,	      acct_rate_type
125     ,       acct_exchange_rate
126     ,       pa_currency.round_currency_amt(acct_raw_cost) acct_raw_cost
127     ,       acct_burdened_cost
128     ,       acct_exchange_rounding_limit
129     ,       project_currency_code
130     ,       project_rate_date
131     ,       project_rate_type
132     ,       project_exchange_rate
133     ,       orig_exp_txn_reference1
134     ,       orig_user_exp_txn_reference
135     ,       vendor_number
136     ,       orig_exp_txn_reference2
137     ,       orig_exp_txn_reference3
138     ,       override_to_organization_name
139     ,       reversed_orig_txn_reference
140     ,       billable_flag
141     ,       txn_interface_id
142     ,       person_business_group_name
143 	-- Bug 2464841 : Added parameters for 11.5 PA-J certification.
144     ,	    projfunc_currency_code
145     ,	    projfunc_cost_rate_type
146     ,	    projfunc_cost_rate_date
147     ,	    projfunc_cost_exchange_rate
148     ,	    project_raw_cost
149     ,	    project_burdened_cost
150     ,	    assignment_name
151     ,	    work_type_name
152     ,	    accrual_flag
153     ,       project_id -- PA.L Changes
154     ,       task_id
155     ,       person_id
156     ,       organization_id
157     ,       non_labor_resource_org_id
158     ,       vendor_id
159     ,       override_to_organization_id
160     ,       assignment_id
161     ,       work_type_id
162     ,       person_business_group_id   -- PA.L Changes end.
163     ,       po_number  /* cwk */
164     ,       po_header_id
165     ,       po_line_num
166     ,       po_line_id
167     ,       person_type
168     ,       po_price_type
169     ,       wip_resource_id
170     ,       inventory_item_id
171     ,       unit_of_measure
172       FROM pa_transaction_interface_all
173      WHERE transaction_source = X_transaction_source
174        AND batch_name = current_batch
175        AND transaction_status_code = 'P'
176        AND decode(system_linkage,'OT','ST',system_linkage) =
177                                                       curr_etype_class_code
178     ORDER BY
179             decode(system_linkage,'OT','ST',system_linkage)
180     ,       expenditure_ending_date DESC
181     ,       employee_number
182     ,       organization_name
183     ,       orig_exp_txn_reference1
184     ,       orig_user_exp_txn_reference
185     ,       vendor_number
186     ,       orig_exp_txn_reference2
187     ,       orig_exp_txn_reference3
188     ,       denom_currency_code
189     ,	      acct_rate_date
190     ,	      acct_rate_type
191     ,	      acct_exchange_rate
192     ,       expenditure_item_date
193     ,       project_number
194     ,       task_number
195     FOR UPDATE OF transaction_status_code;
196 
197     -- Bug 3465939: Defined cursor to fetch the information associated with Liquidated Encumbrance item.
198     -- This cursor returns 'Y' as Net_zero_adjustment_flag if the Encumbrance item being imported is
199     -- a liquidated Encumbrance Item.
200 
201     CURSOR c_get_org_enc_item_id(p_txn_interface_id NUMBER) IS
202     SELECT original_encumbrance_item_id ,
203            DECODE(original_encumbrance_item_id,NULL,NULL,'Y')  net_zero_adjustment_flag
204       FROM gms_transaction_interface_all
205      WHERE txn_interface_id = p_txn_interface_id ;
206 
207     TrxRec		TrxRecs%ROWTYPE;
208     X_status		varchar2(100);
209     X_success       varchar2(1)  ;
210     X_bill_flag		varchar2(100);
211      l_encumbrance_grp          GMS_ENCUMBRANCE_GROUPS_ALL.ENCUMBRANCE_GROUP%TYPE; -- Bug 3035863 : Modified to reflect size change
212      l_org_id                   NUMBER ;
213      l_exp_ending_date          DATE;
214      l_enc_id                   NUMBER ; -- Bug 3220756 : Removed intialization to zero
215      l_system_linkage_fn        VARCHAR2(100);
216      l_task_id                  VARCHAR2(30);
217      l_override_organization_id NUMBER; -- bug# 2111317
218      l_organization_id          NUMBER; -- not initializing this just in case
219      x_dummy		        NUMBER  ;
220      l_gen_seq                  VARCHAR2(1) ;
221      --l_organization_name        VARCHAR2(60);
222       -- The width of the variable is changed for UTF8 changes for HRMS schema. refer bug 2302839.
223      l_organization_name        HR_ALL_ORGANIZATION_UNITS_TL.NAME%TYPE;
224      l_employee_number          VARCHAR2(30);
225      dummy                      NUMBER;
226      FIRST_RECORD       BOOLEAN ;
227      ORG_FIRST          BOOLEAN ;
228      GROUP_FIRST        BOOLEAN ;
229      TASK_FIRST         BOOLEAN ;
230      PROJ_FIRST         BOOLEAN ;
231 
232      -- S.N. Introduced for the bug# 4138033
233      TASK_FAIL          BOOLEAN ;
234      PROJ_FAIL          BOOLEAN ;
235      -- E.N. Introduced for the bug# 4138033
236 
237      l_rowid                    VARCHAR2(40);
238      l_person_id                NUMBER(15);
239      l_task_number              VARCHAR2(40);
240      l_project_id               NUMBER(15);
241      l_award_id                 gms_awards_all.award_id%TYPE; /*Bug# 4138033*/
242      l_enc_item_id              NUMBER(15);
243      l_project_number           VARCHAR2(25);
244      x_calling_module		varchar2(50)  ;
245      x_acct_currency_code	VARCHAR2(15); -- Added for Bug:1331903
246      l_emp_org_oride            varchar2(1) ;
247      l_emporg_id                NUMBER ;
248      l_empJob_id                NUMBER ;
249      -- Bug 3465939 and 3035863 :  Defined following variables
250      l_orig_enc_item_id         NUMBER ;
251      l_net_zero_adj_flag        VARCHAR2(1);
252      l_purgeable_flag           VARCHAR2(1);
253      l_allow_dup_ref_flag       VARCHAR2(1);
254      l_gl_accted_flag	        VARCHAR2(1) ;
255      l_allow_reversal_flag      VARCHAR2(1) ;
256      l_costed_flag              VARCHAR2(1) ;
257      l_allow_burden_flag        VARCHAR2(1) ;
258      x_status_code              VARCHAR2(100) ;
259 
260 
261   RESOURCE_BUSY     EXCEPTION;
262   PRAGMA EXCEPTION_INIT( RESOURCE_BUSY, -0054 );
263 
264   FUNCTION lockCntrlRec     ( trx_source   VARCHAR2
265                           , batch        VARCHAR2
266                           , etypeclasscode VARCHAR2 ) RETURN NUMBER
267     IS
268     -- Bug 3035863 : Moved the select statement to cursor for locking more than one
269     -- record when batch name is NULL
270 
271     CURSOR C_lock_records IS
272        SELECT 1
273         FROM
274               pa_transaction_xface_control
275        WHERE
276               transaction_source = trx_source
277          AND  batch_name = NVL(batch,batch_name) -- Bug 3035863 : Introduced NVL as batch can be NULL
278          AND  system_linkage_function = NVL(etypeclasscode,system_linkage_function) -- Bug 3035863 : Introduced NVL as etypeclasscode can be NULL
279          AND  status = 'PENDING'
280       FOR UPDATE OF status NOWAIT;
281 
282     BEGIN
283 
284       pa_cc_utils.set_curr_function('lockCntrlRec');
285 
286       pa_cc_utils.log_message('Trying to get lock for record in xface ctrl:'||
287                                 ' transaction source ='||trx_source||
288                                 ' batch = '||batch||
289                                 ' sys link = '||etypeclasscode, 1);
290 
291       -- Bug 3035863 : Moved the select logic to cursor for handling locking of multiple rows
292       FOR i in C_lock_records LOOP
293         NULL;
294       END LOOP;
295 
296        pa_cc_utils.log_message('Got lock for record',1);
297 
298        /* Bug 3035863:  Explanation on below code modification
299 
300           Oracle projects Transaction import process picks the PENDING status records
301 	  from control table pa_transaction_xface_control and updates them to 'IN_PROGRESS'
302 	  during processing .At the end of process updates them to 'PROCESSED' if successful
303 	  else in case of failure updates them back to 'PENDING' status.
304 
305           But in Grants the records are marked and left in 'IN_PROGRESS' status. We don't
306 	  mark the records to 'PROCESSED'  as the Projects code deletes 'PROCESSED' records
307 	  when purgeable_flag is set to 'Yes'.And to prevent user from updating/deleting
308 	  the Encumbrance transaction source details through 'Transaction Sources' form
309 	  i.e. PAXTRTXS.fmb  we need record in control table ,hence Grants code leaves records
310 	  in control table with 'IN_PROGRESS' status.
311 
312           Scenario Fixed : When transaction which is rejected is marked for re-processing
313 	  then grants code was failing with unique constraint violation on above control table.
314 
315           Code issue : After processing records are left in 'In_PROGRESS' status and when the
316 	  transaction is marked for re-processing projects code checks for PENDING status
317 	  record in control table and as it fails to find one it creates a new record with
318 	  PENDING status. Grants code tries to mark even this new record to In_PROGRESS and
319 	  fails with UNIQUE constraint violation, as both records are similar.
320 
321           Solution:  Delete the 'IN_PROGRESS' record created during the previous unsuccessful
322 	  run before updating the current run record to same status. */
323 
324       pa_cc_utils.log_message('GMS_LD_PKG.LOCKCNTRLREC : Deleting interface control record in IN_PROGRESS status which is created during last run' ,1);
325 
326       DELETE  pa_transaction_xface_control
327        WHERE  transaction_source = trx_source
328          AND  batch_name = NVL(batch,batch_name) -- Bug 3035863
329          AND  system_linkage_function = NVL(etypeclasscode,system_linkage_function) -- Bug 3035863
330          AND  status = 'IN_PROGRESS' ;
331 
332       pa_cc_utils.log_message('GMS_LD_PKG.LOCKCNTRLREC : Number of records deleted from pa_transaction_xface_control : '||SQl%ROWCOUNT);
333 
334       UPDATE  pa_transaction_xface_control
335          SET
336               interface_id = P_xface_id
337       ,       status = 'IN_PROGRESS'
338        WHERE
339               transaction_source = trx_source
340          AND  batch_name = NVL(batch,batch_name) -- Bug 3035863
341          AND  system_linkage_function = NVL(etypeclasscode,system_linkage_function) -- Bug 3035863
342          AND  status = 'PENDING';
343 
344       pa_cc_utils.log_message('Updated interface id/status on pa_transaction_xface_control',1);
345 
346       pa_cc_utils.reset_curr_function;
347       RETURN 0;
348 
349     EXCEPTION
350       WHEN  RESOURCE_BUSY  THEN
351       pa_cc_utils.log_message('Cannot get lock',1);
352       pa_cc_utils.reset_curr_function;
353       write_to_log('GMS :lockCntrlRec RESOURCE_BUSY exception raised '||SQLCODE) ;
354       write_to_log('GMS :SQLERRM '||SQLERRM) ;
355       write_to_log('GMS :Parameter trx_source :'||trx_source||' system_linkage_function :'||etypeclasscode) ;
356       raise_application_error(SQLCODE,SQLERRM) ;
357       RETURN -1;
358   END lockCntrlRec;
359 
360   FUNCTION GET_award_id return NUMBER is
361 
362     X_award_id  NUMBER ;
363 
364     -- Bug 31221039 : Modified the below cursor to fetch award_id based on award_number/award_id.
365 
366     CURSOR C1 IS
367     SELECT ga.award_id
368       FROM gms_transaction_interface_all gtxn,
369            gms_awards_all ga
370      WHERE ((gtxn.award_number IS NULL AND ga.award_id = NVL(gtxn.award_id,0)  ) OR
371             (ga.award_number = gtxn.award_number) )
372        AND gtxn.txn_interface_id = Trxrec.txn_interface_id ;
373 
374   begin
375     open c1 ;
376     fetch C1 into x_award_id ;
377     IF c1%notfound then
378         x_award_id := 0 ;
379     end if ;
380     close C1 ;
381     return x_award_id ;
382   exception
383     when others then
384         IF c1%isopen then
385             close c1 ;
386         end if ;
387     	pa_cc_utils.log_message('Unexpected error : get_award_id: '||SQLERRM,1);
388         write_to_log('GMS :get_award_id When OTHERS exception raised '||SQLCODE) ;
389         write_to_log('GMS :SQLERRM '||SQLERRM) ;
390         write_to_log('GMS :Parameter txn_interface_id :'||Trxrec.txn_interface_id||' award id :'||NVL(x_award_id,0)) ;
391         return 0 ;
392   end get_award_id ;
393 /* **************************************************************
394 
395   PROCEDURE PROC_FUNDS_CHECK_ENC IS
396 		x_err_buf			varchar2(2000) ;
397 		x_ret_code			varchar2(1) ;
398 		x_encumbrance_grp 	varchar2(15) ;
399 		x_packet_id			NUMBER ;
400 
401 	CURSOR C_enc is
402     select distinct encumbrance_id
403       from gms_encumbrances
404      where encumbrance_group = x_encumbrance_grp ;
405   begin
406   END	 PROC_FUNDS_CHECK_ENC ;
407  **************************************************************/
408 
409   PROCEDURE PROC_CREATE_GROUP (p_batch_name pa_transaction_xface_control.batch_name%TYPE ) is
410   l_req_id   NUMBER;    /*bug 5689213*/
411   BEGIN
412 
413     if (X_status is null) then -- Record is accepted by the ValidateItem Proc.
414         -- --------------------------
415         -- Group Creation
416         -- --------------------------
417 	l_req_id := FND_GLOBAL.CONC_REQUEST_ID ;  /*bug 5689213*/
418         IF (FIRST_RECORD) then
419 
420                 select gms_encumbrance_groups_s.nextval
421                   into l_encumbrance_grp
422                  from dual;
423 
424                 l_org_id := TrxRec.org_id;
425                 l_exp_ending_date := TrxRec.expenditure_ending_date;
426                 l_system_linkage_fn := TrxRec.system_linkage;
427 		--
428 		-- bug : 3265300,3425124
429 		-- encumbrance summarize and transfer process gives 'gms_unexpected_error'
430 		--
431 		l_encumbrance_grp := SUBSTR(p_batch_name||' '||l_encumbrance_grp,1,240) ;
432 
433                 gms_encumbrance_groups_pkg.insert_row (x_rowid	    => l_rowid,
434                        x_encumbrance_group		    => l_encumbrance_grp,
435                        x_last_update_date		    => sysdate,
436                        x_last_updated_by		    => to_number(fnd_profile.value('USER_ID')),
437                        x_creation_date			    => sysdate,
438                        x_created_by			        => to_number(fnd_profile.value('USER_ID')),
439                        x_encumbrance_group_status	=> 'RELEASED',
440                        x_encumbrance_ending_date	=> TrxRec.expenditure_ending_date,
441                        x_system_linkage_function	=> TrxRec.system_linkage,
442                        x_control_count			    =>  NULL,
443                        x_control_total_amount	    =>  NULL,
444                        x_description			    =>  NULL,
445                        x_last_update_login		    =>  to_number(fnd_profile.value('LOGIN_ID')),
446                        x_transaction_source		    =>  P_TRANSACTION_SOURCE ,
447                        x_org_id                             =>  l_org_id,
448 		       x_request_id                         =>  l_req_id  /*bug 5689213*/
449 		                                               ); -- bug : 2376730
450 
451                        FIRST_RECORD := FALSE;
452                        l_gen_seq := 'Y';
453 
454         ELSIF (l_org_id <> TrxRec.org_id OR l_exp_ending_date <> TrxRec.expenditure_ending_date
455                         OR  l_system_linkage_fn <> TrxRec.system_linkage ) then
456 
457 			-- ---------------------------------------------------------------------
458 			-- CALL GMS_funds_check Routine and reject items if FUNDS_CHECK_Failed.
459 			-- ---------------------------------------------------------------------
460 			--PROC_FUNDS_CHECK_ENC ;
461 
462                         select gms_encumbrance_groups_s.nextval
463                           into l_encumbrance_grp
464                           from dual;
465 
466                         l_org_id := TrxRec.org_id;
467                         l_exp_ending_date := TrxRec.expenditure_ending_date;
468                         l_system_linkage_fn := TrxRec.system_linkage;
469 			--
470 			-- bug : 3265300,3425124
471 			-- encumbrance summarize and transfer process gives 'gms_unexpected_error'
472 			--
473 
474 		        l_encumbrance_grp := SUBSTR(p_batch_name||' '||l_encumbrance_grp,1,240) ;
475 
476                         gms_encumbrance_groups_pkg.insert_row (x_rowid	    => l_rowid,
477                             x_encumbrance_group		    => l_encumbrance_grp,
478                             x_last_update_date		    => sysdate,
479                             x_last_updated_by		    => to_number(fnd_profile.value('USER_ID')),
480                             x_creation_date			    => sysdate,
481                             x_created_by			        => to_number(fnd_profile.value('USER_ID')),
482                             x_encumbrance_group_status	=> 'RELEASED',
483                             x_encumbrance_ending_date	=> TrxRec.expenditure_ending_date,
484                             x_system_linkage_function	=> TrxRec.system_linkage,
485                             x_control_count			    =>  NULL,
486                             x_control_total_amount	    =>  NULL,
487                             x_description			    =>  NULL,
488                             x_last_update_login		    =>  to_number(fnd_profile.value('LOGIN_ID')),
489                             x_transaction_source		    =>  P_TRANSACTION_SOURCE ,
490                             x_org_id                             =>  l_org_id,
491 			    x_request_id                         =>  l_req_id  /*bug 5689213*/
492 			                                           ); -- bug : 2376730
493 
494                        l_gen_seq := 'Y';
495 
496         END IF  ;
497     END IF ;
498   EXCEPTION
499     WHEN OTHERS THEN
500         X_SUCCESS := 'F' ;
501     	pa_cc_utils.log_message('Unexpected error : PROC_CREATE_GROUP: '||SQLERRM,1);
502         write_to_log('GMS :proc_create_group When OTHERS exception raised '||SQLCODE) ;
503         write_to_log('GMS :SQLERRM '||SQLERRM) ;
504         write_to_log('GMS :Parameter x_encumbrance_group :'||l_encumbrance_grp) ;
505   END PROC_CREATE_GROUP ;
506 
507 PROCEDURE PROC_VALIDATE_LOCAL (  p_raw_cost    IN NUMBER,    -- Bug 3465936
508                                  p_status_code OUT NOCOPY VARCHAR2) IS
509    l_bg_id       NUMBER ;
510    l_temp_org_id NUMBER ;
511    -- Bug 3465939  : Added following variables
512    l_net_zero_adjustment_flag   VARCHAR2(1) ;
513    l_orig_raw_cost                   NUMBER ;
514 
515    --Bug 3465939 : Cursor to fetch original Labor distribution
516    --              encumbrance Item details.
517 
518    CURSOR  c_original_enc_exists IS
519    SELECT  net_zero_adjustment_flag,amount
520      FROM  gms_encumbrance_items_all gei
521     WHERE  gei.transaction_source =  P_transaction_source
522       AND  gei.encumbrance_item_id = l_orig_enc_item_id ;
523 
524 BEGIN
525 
526    pa_cc_utils.log_message('GMS_LD_PKG.PROC_VALIDATE_LOCAL :  Start');
527 
528     -- Bug 3465936 : Added following code to validate the original_encumbrance_item_id  and
529     -- to check whether liquidation of encumbrance item id is allowed
530 
531     IF l_orig_enc_item_id IS NOT NULL THEN
532 
533        pa_cc_utils.log_message('GMS_LD_PKG.PROC_VALIDATE_LOCAL :  Before vaildating the liquidated Encumbrance');
534 
535        IF l_allow_reversal_flag = 'N'  THEN
536             p_status_code := 'GMS_IMP_ENC_NO_REVERSAL';
537        ELSE
538 
539          OPEN  c_original_enc_exists;
540          FETCH c_original_enc_exists INTO l_net_zero_adjustment_flag,l_orig_raw_cost;
541          IF c_original_enc_exists%NOTFOUND THEN
542             p_status_code := 'GMS_IMP_ORIG_ENC_NOT_EXISTS';
543          ELSIF NVL(l_net_zero_adjustment_flag,'N') = 'Y' THEN
544             p_status_code := 'GMS_IMP_ORIG_ENC_REVERSED';
545          ELSIF (NVL(p_raw_cost,0)+ NVL(l_orig_raw_cost,0)) <> 0 THEN
546             p_status_code := 'GMS_IMP_ORIG_AMT_MISMATCH';
547          END IF;
548          CLOSE c_original_enc_exists ;
549 
550        END IF;
551 
552        pa_cc_utils.log_message('GMS_LD_PKG.PROC_VALIDATE_LOCAL :  After vaildating the liquidated Encumbrance ,p_status_code : '||p_status_code);
553 
554        IF p_status_code IS NOT NULL THEN
555         X_success := 'F' ;
556         RETURN;
557        END IF;
558 
559     END IF;
560 
561     l_bg_id  := PA_TRX_IMPORT.G_Business_Group_Id ;
562 
563     IF ((GROUP_FIRST) OR (l_employee_number <> TrxRec.employee_number)) then
564 
565             -- BUG : 3226607
566 	    -- Bug : 3601539 : Added parameter alias as expenditure_ending_date was getting passed
567 	    --                 for p_person_type parameter.
568             pa_utils2.GetEmpId( P_Business_Group_Id => l_bg_id,
569                                 P_Employee_Number   => TrxRec.employee_number,
570                                 X_Employee_Id       => l_person_id,
571                                 P_EiDate            => TrxRec.expenditure_ending_date );
572             IF ( pa_utils2.G_return_status IS NOT NULL and TrxRec.system_linkage not in ('PJ', 'USG')) THEN --Bug: 4594620
573               X_status := pa_utils2.G_return_status ;
574               pa_cc_utils.log_message('EXECPTION :Person  ' || TrxRec.employee_number, 1);
575               pa_cc_utils.log_message('EXECPTION :Expenditure Item date ' || TrxRec.expenditure_ending_date, 1);
576               pa_cc_utils.log_message('EXECPTION : Person ID validation ' || x_status);
577 
578               X_success := 'F' ;
579               return ;
580             END IF ;
581 
582             l_gen_seq         := 'Y';
583             l_employee_number := TrxRec.employee_number;
584             GROUP_FIRST       := FALSE;
585     end if;
586 
587     if (    (ORG_FIRST) OR
588             (l_organization_name <> nvl(TrxRec.override_to_organization_name, TrxRec.organization_name))) then
589 
590 	    l_override_organization_id := NULL;
591 	    l_organization_id := NULL;
592             l_organization_name := nvl(TrxRec.override_to_organization_name, TrxRec.organization_name);
593 
594             If (l_organization_name is NULL) then /* Bug 4901079 */
595               X_success := 'F';
596               p_status_code := 'PA_EXP_ORG_NOT_SPECIFIED' ;
597               RETURN;
598             End If;
599 
600             pa_utils.GetOrgnId(X_org_name => l_organization_name,
601 			       X_bg_id    => l_bg_id,
602 			       X_Orgn_Id  => l_temp_org_id,
603 			       X_Return_Status => x_status);
604 
605             If x_status is Not Null OR l_temp_org_id is NULL Then
606 	       X_success := 'F';
607                pa_cc_utils.log_message('EXECPTION : organization_name validation ' || x_status);
608 	       RETURN;
609 	    End If;
610 
611 
612             IF (TrxRec.override_to_organization_name is not null) then
613                     l_override_organization_id := l_temp_org_id ;
614             ELSE
615 	 	    l_organization_id          := l_temp_org_id ;
616             END IF ;
617 
618             pa_cc_utils.log_message('Organization  ' || l_organization_id, 1);
619             l_gen_seq := 'Y';
620             ORG_FIRST := FALSE;
621 
622             select organization_id
623               into l_temp_org_id
624               from pa_organizations_expend_v
625                    --hr_all_organization_units
626              WHERE organization_id = l_temp_org_id
627                and active_flag = 'Y'
628                and trunc(TrxRec.expenditure_ending_date) between date_from
629                    and nvl(date_to,trunc(TrxRec.expenditure_ending_date));
630 
631             X_success := 'S' ;
632  end if;
633 
634  pa_cc_utils.log_message('GMS_LD_PKG.PROC_VALIDATE_LOCAL :  End');
635 EXCEPTION
636     WHEN no_data_found THEN
637          pa_cc_utils.log_message('EXECPTION :Person  ' || TrxRec.employee_number, 1);
638          pa_cc_utils.log_message('EXECPTION :Override Organization  ' || TrxRec.override_to_organization_name, 1);
639          pa_cc_utils.log_message('EXECPTION :Expenditure Item date ' || TrxRec.expenditure_ending_date, 1);
640          pa_cc_utils.log_message('EXECPTION :Organization  ' || TrxRec.organization_name, 1);
641 
642         X_success := 'F' ;
643         write_to_log('GMS :proc_validate_local When no_data_found exception raised '||SQLCODE) ;
644         write_to_log('GMS :SQLERRM '||SQLERRM) ;
645         write_to_log('GMS :Parameter person :'||TrxRec.employee_number) ;
646         write_to_log('GMS :Parameter Override Organization :'||TrxRec.override_to_organization_name) ;
647         write_to_log('GMS :Parameter Expenditure Item date :'|| TrxRec.expenditure_ending_date) ;
648         write_to_log('GMS :Organization  ' || TrxRec.organization_name);
649 
650     When others then
651         X_success := 'F' ;
652     	pa_cc_utils.log_message('Unexpected error: PROC_VALIDATE_LOCAL: '||SQLERRM,1);
653         write_to_log('GMS :proc_validate_local When OTHERS exception raised '||SQLCODE) ;
654         write_to_log('GMS :SQLERRM '||SQLERRM) ;
655         write_to_log('GMS :Parameter person :'||TrxRec.employee_number) ;
656         write_to_log('GMS :Parameter Override Organization :'||TrxRec.override_to_organization_name) ;
657         write_to_log('GMS :Parameter Expenditure Item date :'|| TrxRec.expenditure_ending_date) ;
658         write_to_log('GMS :Organization  ' || TrxRec.organization_name);
659 
660 END PROC_VALIDATE_LOCAL ;
661 
662   FUNCTION F_create_adls return boolean is
663     x_adl_rec           gms_award_distributions%ROWTYPE ;
664     x_award_id          NUMBER ;
665     x_award_set_id      NUMBER ;
666     X_request_id        NUMBER ;
667     x_raw_cost          NUMBER;
668     x_ei_id             NUMBER;
669     x_project_id        NUMBER;
670     X_task_id           NUMBER;
671   begin
672         X_raw_cost        :=  TrxRec.raw_cost ;
673         X_ei_id           :=  l_enc_item_id ;
674         X_project_id      :=  l_project_id;
675         X_task_id         :=  l_task_id;
676 		x_award_id        := get_award_id ;
677         X_request_id := FND_GLOBAL.CONC_REQUEST_ID ;
678 
679         IF x_award_id = 0 then
680             return false ;
681         end if ;
682         x_award_set_id                      := GMS_AWARDS_DIST_PKG.get_award_set_id  ;
683         x_adl_rec.award_set_id              := x_award_set_id ;
684         X_adl_rec.adl_line_num              := 1 ;
685 		-- -----------------------------------------------------------
686 		-- BUG: 1363695 - CDL line num is missing into ADLS.
687 		-- -----------------------------------------------------------
688 		X_adl_rec.cdl_line_num				:= 1   ;
689 
690         X_adl_rec.project_id                := X_project_id ;
691 		X_adl_rec.document_type				:= 'ENC' ;
692         X_adl_rec.task_id                   := X_task_id ;
693         X_adl_rec.award_id                  := X_award_id ;
694         x_adl_rec.expenditure_item_id       := x_ei_id ;
695         x_adl_rec.raw_cost                  := X_raw_cost ;
696         x_adl_rec.request_id                := X_request_id ;
697         x_adl_rec.billed_flag               := 'N' ;
698         X_adl_rec.adl_status                := 'A' ;
699 		X_adl_rec.line_type					:= 'R' ;
700 		X_adl_rec.cost_distributed_flag		:= 'N' ;
701         GMS_AWARDS_DIST_PKG.create_adls(x_adl_rec) ;
702 
703         return TRUE ;
704   exception
705     when others then
706     	pa_cc_utils.log_message('Unexpected error: F_create_adls: '||SQLERRM,1);
707         write_to_log('GMS :f_create_adls When OTHERS exception raised '||SQLCODE) ;
708         write_to_log('GMS :SQLERRM '||SQLERRM) ;
709         write_to_log('GMS :Parameter X_ei_id :'|| l_enc_item_id) ;
710         write_to_log('GMS :Parameter project_id, task_id :'||l_project_id||' , '||l_task_id) ;
711         write_to_log('GMS :Parameter award_id :'|| x_award_id) ;
712 
713         return false   ;
714   END F_create_adls ;
715 
716    PROCEDURE PROC_PROJECT_TASK IS
717    BEGIN
718 
719        if ((PROJ_FIRST) OR (l_project_number <> TrxRec.project_number)) then
720                     select project_id
721                     into l_project_id
722                     from pa_projects_all
723                     where segment1 = TrxRec.project_number;
724 
725                     PROJ_FIRST := FALSE;
726       end if;
727       pa_cc_utils.log_message('Task : ' || TrxRec.task_number ||' , project id : ' || l_project_id, 1);
728       PROJ_FAIL := FALSE;
729 
730       ----------------------------------------------------------------------------
731       -- BUG:2389535 - Encumbrances have Identical Task Ids
732       ----------------------------------------------------------------------------
733       if ((TASK_FIRST) OR (l_project_number <> TrxRec.project_number) OR (l_task_number <> TrxRec.task_number)) then
734                 select task_id
735                      into l_task_id
736                     from pa_tasks
737                     where task_number = TrxRec.task_number
738                     and project_id = l_project_id;
739 
740                     TASK_FIRST := FALSE;
741       end if;
742       TASK_FAIL := FALSE;
743 
744       ----------------------------------------------------------------------------
745       -- BUG:2389535 - Encumbrances have Identical Task Ids
746       ----------------------------------------------------------------------------
747       l_project_number := TrxRec.project_number;
748       l_task_number := TrxRec.task_number;
749 
750    EXCEPTION
751         when no_data_found then
752 	     pa_cc_utils.log_message('EXCEPTION:Project  : ' || TrxRec.project_number, 1);
753              pa_cc_utils.log_message('EXCEPTION:Task  : ' || TrxRec.task_number, 1);
754              x_success := 'F' ;
755              write_to_log('GMS :proc_project_task When no_data_found exception raised '||SQLCODE) ;
756              write_to_log('GMS :SQLERRM '||SQLERRM) ;
757              write_to_log('GMS :Parameter project_number, task_number :'|| TrxRec.project_number||','||TrxRec.task_number) ;
758         When others then
759              x_success := 'F' ;
760     	     pa_cc_utils.log_message('Unexpected error: PROC_PROJECT_TASK: '||SQLERRM,1);
761              write_to_log('GMS :proc_project_task when others exception raised '||SQLCODE) ;
762              write_to_log('GMS :SQLERRM '||SQLERRM) ;
763              write_to_log('GMS :Parameter project_number, task_number :'|| TrxRec.project_number||','||TrxRec.task_number) ;
764    END PROC_PROJECT_TASK ;
765 
766    -- Bug 3035863 : Added following procedure to validate the encumbrance transaction source.
767 
768    PROCEDURE VALIDATE_TRANSACTION_SOURCE IS
769    BEGIN
770      	-- Bug 3035863: The following code is added to stop further processing of
771         -- encumbrance if flags not properly set .
772 
773         pa_cc_utils.log_message('GMS_LD_PKG.VALIDATE_TRANSACTION_SOURCE :  Start');
774 	x_status := NULL;
775 
776         pa_cc_utils.log_message('GMS_LD_PKG.VALIDATE_TRANSACTION_SOURCE : Validating transaction source '||p_transaction_source );
777 
778         IF NVL(l_gl_accted_flag ,'N') = 'Y' THEN
779            x_status := 'GMS_IMP_ENC_GLACCT_FLAG';
780         ELSIF NVL(l_costed_flag,'N') = 'N' THEN
781            x_status := 'GMS_IMP_ENC_COSTED_FLAG';
782         ELSIF NVL(l_allow_burden_flag,'N') = 'Y' THEN
783            x_status := 'GMS_IMP_ENC_BURDEN_FLAG';
784         END IF;
785 
786         pa_cc_utils.log_message('GMS_LD_PKG.VALIDATE_TRANSACTION_SOURCE : After validating transaction source ,Value of x_status : '||x_status );
787 
788         pa_cc_utils.log_message('GMS_LD_PKG.VALIDATE_TRANSACTION_SOURCE :  End ');
789 
790    EXCEPTION
791      When others then
792      	 pa_cc_utils.log_message('GMS_LD_PKG.VALIDATE_TRANSACTION_SOURCE : Unexpected error : '||SQLERRM,1);
793          x_status := 'GMS_UNEXPECTED_ERROR';
794    END;
795 
796    BEGIN
797 
798     -- --------------------------------------------
799     -- Pre processing extension is exclusively for
800     -- GOLDE transaction source
801     -- --------------------------------------------
802     -- Bug 3035863 : Included check to allow processing for transaction sources starting with 'GMSE'
803     l_org_id    := 0;
804     l_gen_seq   := 'N' ;
805      FIRST_RECORD       := TRUE;
806      ORG_FIRST          := TRUE;
807      GROUP_FIRST        := TRUE;
808      TASK_FIRST         := TRUE;
809      PROJ_FIRST         := TRUE;
810      x_calling_module	:= 'GMS_LD_PKG.PRE_PROCESS' ;
811 
812     IF (P_TRANSACTION_SOURCE = 'GOLDE' OR (SUBSTR(P_TRANSACTION_SOURCE,1,4) = 'GMSE')) THEN
813         NULL;
814      ELSE
815         return ;
816      END IF ;
817 
818     write_to_log('GMS :begin gms_ld_pkg.pre_process :'||P_TRANSACTION_SOURCE) ;
819     write_to_log('GMS :start time gms_ld_pkg.pre_process :'||to_char(sysdate, 'DD-MON-YYYY HH24:MI:SS')) ;
820 
821     open  c_trans_source ;
822     fetch c_trans_source into l_emp_org_oride,l_purgeable_flag,l_allow_dup_ref_flag ,
823           l_gl_accted_flag,l_allow_reversal_flag,l_costed_flag,l_allow_burden_flag; -- Bug 3035863
824     close c_trans_source ;
825 
826     pa_cc_utils.log_message('GMS_LD_PKG.PRE_PROCESS : Before calling VALIDATE_TRANSACTION_SOURCE ');
827 
828     -- Bug 3035863 : Call to validate encumbrance transaction source.
829 
830     IF SUBSTR(p_transaction_source,1,4) ='GMSE'  THEN
831 
832        VALIDATE_TRANSACTION_SOURCE;
833 
834        IF  X_STATUS IS NOT NULL THEN
835 
836          UPDATE pa_transaction_interface_all
837             SET transaction_rejection_code = X_status,
838                 interface_id = P_xface_id,
839                 transaction_status_code = 'R'
840           WHERE transaction_status_code ='P'
841             AND (transaction_source,batch_name,decode(system_linkage,'OT','ST',system_linkage)) IN
842   	          (SELECT xc.transaction_source,xc.batch_name,xc.system_linkage_function
843 		     FROM pa_transaction_xface_control xc
844                     WHERE xc.transaction_source = P_transaction_source
845                       AND  xc.batch_name         = nvl(P_batch, xc.batch_name)
846                       AND  xc.status             = 'PENDING');
847 
848          pa_cc_utils.log_message('GMS_LD_PKG.PRE_PROCESS : Number of records marked for failure after VALIDATE_TRANSACTION_SOURCE'||SQL%ROWCOUNT);
849 
850          dummy := lockCntrlRec( p_transaction_source,
851                                 p_batch ,
852                                 NULL );
853 
854          IF ( dummy <> 0 ) THEN
855 	   rollback;
856            RETURN;
857          END IF ;
858 
859          COMMIT;
860 	 RETURN;
861        END IF;   --  IF  X_STATUS IS NOT NULL THEN
862      END IF; -- IF SUBSTR(p_transaction_source,1,4) ='GMSE'  THEN
863 
864     /*=============================================================================================================================*/
865     /* The following FND_STATS.GATHER_TABLE_STATS procedure call has been modified by VBANDARU for bug 2465932*/
866     /*=============================================================================================================================*/
867 
868     /*FND_STATS.Gather_Table_Stats(ownname=>'PA',
869                                   tabname =>'PA_TRANSACTION_INTERFACE_ALL',
870                                   percent =>10,
871                                   tmode => 'TEMPORARY');*/
872 
873       --FND_STATS.Gather_Table_Stats(ownname=>'PA',
874        --                           tabname =>'PA_TRANSACTION_INTERFACE_ALL');
875 
876     x_success := 'S' ;
877     FOR  eachGroup  IN  TrxBatches  LOOP
878 
879       pa_debug.G_err_Stage := 'Locking xface ctrl record';
880       pa_cc_utils.log_message(pa_debug.G_err_stage||
881                          'Transaction source = '||eachGroup.transaction_source
882                          ||' batch= '||eachGroup.batch_name||' sys link= '||
883                          eachGroup.system_linkage_function,1);
884 
885 
886       dummy := lockCntrlRec( eachGroup.transaction_source
887                            , eachGroup.batch_name
888                            , eachGroup.system_linkage_function );
889 
890       IF ( dummy <> 0 ) THEN
891           GOTO NEXTREC ;
892       END IF ;
893 
894      pa_debug.G_err_Stage := 'Open cursor trxrecs';
895      pa_cc_utils.log_message( pa_debug.G_err_Stage,1);
896 
897      IF TrxRecs%ISOPEN THEN
898         CLOSE TrxRecs ;
899      END IF ;
900 
901      OPEN TrxRecs( eachGroup.transaction_source
902                , eachGroup.batch_name
903                , eachGroup.system_linkage_function  );
904 
905      FIRST_RECORD := TRUE;
906      GROUP_FIRST  := TRUE;
907      ORG_FIRST    := TRUE;
908      PROJ_FIRST   := TRUE;
909      TASK_FIRST   := TRUE;
910 
911      x_success := 'S' ;
912      l_orig_enc_item_id := NULL;
913      l_net_zero_adj_flag := NULL;
914      l_enc_id := NULL ; -- Bug 3220756 :Intializing the variable to NULL for every new batch processed.
915                         -- As for every new batch processed a new encumbrance Id will be generated.
916 
917      <<expenditures>>
918      LOOP
919         BEGIN
920 
921             PROJ_FAIL := TRUE;
922             TASK_FAIL := TRUE;
923 
924 	    FETCH TrxRecs into TrxRec;
925 
926             SAVEPOINT SAVE_TrxREC ;
927 
928             IF ( TrxRecs%ROWCOUNT = 0 ) THEN
929                 pa_cc_utils.log_message('Zero Records Fetched',1);
930                 EXIT expenditures ;
931 
932             elsif TrxRecs%NOTFOUND then
933                 exit expenditures;
934             end if;
935 
936            -- Bug# 4138033 Moved this code
937 
938            -- Bug 3465939 :Code to fetch liquidated encumbrance item id information
939 	   -- from grants transaction_interface table
940 
941            pa_cc_utils.log_message('GMS_LD_PKG.PRE_PROCESS : Fetching liquidated Encumbrance for txn interface id : '||TrxRec.txn_interface_id);
942 
943            OPEN  c_get_org_enc_item_id(TrxRec.txn_interface_id);
944            FETCH c_get_org_enc_item_id INTO l_orig_enc_item_id,l_net_zero_adj_flag ;
945            CLOSE c_get_org_enc_item_id;
946 
947            pa_cc_utils.log_message('GMS_LD_PKG.PRE_PROCESS : Value of l_orig_enc_item_id'||l_orig_enc_item_id);
948            pa_cc_utils.log_message('GMS_LD_PKG.PRE_PROCESS : Value of l_net_zero_adj_flag'||l_net_zero_adj_flag);
949 
950            -- Bug 3465939 :Shifted the call to PROC_VALIDATE_LOCAL before encumbrance group creation
951 
952 	   PROC_PROJECT_TASK ;
953            IF x_success = 'F' THEN
954                  write_to_log('GMS :PROC_PROJECT_TASK returned x_success False') ;
955                 -- --------------------
956                 -- ERROR
957                 -- --------------------
958 
959 		 ROLLBACK TO SAVE_TrxREC; -- Bug 3035863 : Introduced rollback in case of failure
960 
961                  IF PROJ_FAIL THEN
962 
963 		 UPDATE pa_transaction_interface_all
964                     SET  transaction_rejection_code = 'INVALID_PROJECT'
965                         ,       interface_id = P_xface_id
966                         ,       expenditure_id = l_enc_id
967                         ,       transaction_status_code = 'R'
968                  WHERE current of TrxRecs ;
969 
970 		 ELSIF TASK_FAIL THEN
971 
972 		 UPDATE pa_transaction_interface_all
973                     SET  transaction_rejection_code = 'INVALID_TASK'
974                         ,       interface_id = P_xface_id
975                         ,       expenditure_id = l_enc_id
976                         ,       transaction_status_code = 'R'
977                  WHERE current of TrxRecs ;
978 
979 		 ELSE
980 
981 		 UPDATE pa_transaction_interface_all
982                     SET  transaction_rejection_code = 'GMS_UNEXPECTED_ERROR'
983                         ,       interface_id = P_xface_id
984                         ,       expenditure_id = l_enc_id
985                         ,       transaction_status_code = 'R'
986                  WHERE current of TrxRecs ;
987 
988                  END IF;
989 
990 		-- Bug 3221039 : Commented the following update statement as gms_transaction_
991 		-- interface_all.transaction_status_code column is obsolete
992 
993 		 /*UPDATE gms_transaction_interface_all
994 		    SET transaction_status_code = 'R'
995 		  WHERE orig_transaction_reference = TrxRec.orig_transaction_reference;*/
996 
997                  X_success := 'S' ;
998                  GOTO MOVETONEXT ;
999             END IF ;
1000 
1001            -- Bug# 4138033 End
1002 
1003            l_award_id := get_award_id;
1004 
1005            /* Bug# 4138033 */
1006            Validate_Dates_YN(l_award_id,
1007 	                     l_project_id,
1008 			     l_task_id,
1009 			     l_orig_enc_item_id);
1010 
1011 	    pa_cc_utils.log_message('Trying to call the validate item proc', 1);
1012 	    l_emporg_id := NULL ;
1013 	    l_empjob_id := NULL ;
1014 
1015 	    IF NVL(l_emp_org_oride, 'N') = 'N' AND
1016 	       TrxRec.person_id is NOT NULL    THEN
1017 
1018 	       pa_utils.GetEmpOrgJobID( trxRec.person_id,
1019 	                                trxRec.expenditure_item_date,
1020 					l_emporg_id ,
1021 					l_empJob_id ) ;
1022 	    END IF ;
1023 
1024             PA_TRX_IMPORT.ValidateItem(      p_transaction_source
1025                       ,  TrxRec.employee_number
1026                       ,  TrxRec.organization_name
1027                       ,  TrxRec.expenditure_ending_date
1028                       ,  TrxRec.expenditure_item_date
1029                       ,  TrxRec.expenditure_type
1030                       ,  TrxRec.project_number
1031                       ,  TrxRec.task_number
1032                       ,  TrxRec.non_labor_resource
1033                       ,  TrxRec.non_labor_resource_org_name
1034                       ,  TrxRec.quantity
1035                       ,  TrxRec.denom_raw_cost
1036                       ,  x_calling_module         -- 'GMS_LD_PKG.PRE_PROCESS' calling_module is hardcoded to this.
1037                       ,  TrxRec.orig_transaction_reference
1038                       ,  TrxRec.unmatched_negative_txn_flag
1039                       ,  p_user_id
1040                       ,  TrxRec.attribute_category
1041                       ,  TrxRec.attribute1
1042                       ,  TrxRec.attribute2
1043                       ,  TrxRec.attribute3
1044                       ,  TrxRec.attribute4
1045                       ,  TrxRec.attribute5
1046                       ,  TrxRec.attribute6
1047                       ,  TrxRec.attribute7
1048                       ,  TrxRec.attribute8
1049                       ,  TrxRec.attribute9
1050                       ,  TrxRec.attribute10
1051                       ,  TrxRec.dr_code_combination_id
1052                       ,  TrxRec.cr_code_combination_id
1053                       ,  TrxRec.gl_date
1054                       ,  TrxRec.denom_burdened_cost
1055                       ,  TrxRec.system_linkage
1056                       ,  X_status
1057                       ,  X_bill_flag
1058 	   	      ,  TrxRec.receipt_currency_amount
1059 	   	      ,  TrxRec.receipt_currency_code
1060 	   	      ,  TrxRec.receipt_exchange_rate
1061 	   	      ,  TrxRec.denom_currency_code
1062 	   	      ,  TrxRec.acct_rate_date
1063 	   	      ,  TrxRec.acct_rate_type
1064 	   	      ,  TrxRec.acct_exchange_rate
1065 	   	      ,  TrxRec.acct_raw_cost
1066 	   	      ,  TrxRec.acct_burdened_cost
1067 	   	      ,  TrxRec.acct_exchange_rounding_limit
1068 	   	      ,  TrxRec.project_currency_code
1069 	   	      ,  TrxRec.project_rate_date
1070 	   	      ,  TrxRec.project_rate_type
1071 	   	      ,  TrxRec.project_exchange_rate
1072 		      ,  TrxRec.raw_cost
1073 		      ,  TrxRec.burdened_cost
1074                       ,  TrxRec.override_to_organization_name
1075                       ,  TrxRec.vendor_number
1076 		      -- ---------------------------------------------
1077                       -- Adding 2 new parameters to the ValidateItem
1078                       -- Commented due to PA Patch dependency
1079                       -- Need to uncomment when PA patch released
1080 		      -- BUG:1359088 - PA CBG changes.
1081 		      -- ---------------------------------------------
1082 		      ,  TrxRec.org_id
1083 		      ,  TrxRec.person_business_group_name  -- Removed Null for BUSINESS_GROUP_NAME
1084 			-- Bug 2464841 : Added parameters for 11.5 PA-J certification.
1085  		      ,  TrxRec.projfunc_currency_code
1086 		      ,  TrxRec.projfunc_cost_rate_type
1087 		      ,  TrxRec.projfunc_cost_rate_date
1088 		      ,  TrxRec.projfunc_cost_exchange_rate
1089 		      ,  TrxRec.project_raw_cost
1090 		      ,  TrxRec.project_burdened_cost
1091 		      ,  TrxRec.assignment_name
1092 		      ,  TrxRec.work_type_name
1093 		      ,  TrxRec.accrual_flag
1094 		      ,  TrxRec.project_id
1095 		      ,  TrxRec.Task_id
1096 		      ,  TrxRec.person_id
1097 		      ,  TrxRec.Organization_id
1098 		      ,  TrxRec.non_labor_resource_org_id
1099 		      ,  TrxRec.vendor_id
1100 		      ,  TrxRec.override_to_organization_id
1101 		      ,  TrxRec.person_business_group_id
1102 		      ,  TrxRec.assignment_id
1103 		      ,  TrxRec.work_type_id
1104 		      ,  l_emporg_id
1105 		      ,  l_empjob_id
1106 		      ,  TrxRec.txn_interface_id
1107                       ,  TrxRec.po_number /* CWK */
1108                       ,  TrxRec.po_header_id
1109                       ,  TrxRec.po_line_num
1110                       ,  TrxRec.po_line_id
1111                       ,  TrxRec.person_type
1112                       ,  TrxRec.po_price_type    );
1113                         pa_cc_utils.log_message('Done calling ValidateItem....from pre-process ', 1);
1114 			-- --------------------------------------------------
1115 			-- INFORMATION :
1116 			-- We do this because validate item pkg calls
1117 			-- GetTrxSrcInfo is called for external each time
1118 			-- we want it to be called only the 1st time.
1119 			-- -------------------------------------------------
1120 			x_calling_module := 'PAXTRTRX' ;
1121 
1122 			pa_cc_utils.reset_curr_function ;
1123             -- gms validations for Bug:2431943
1124             gms_pa_api.vert_app_validate(eachGroup.transaction_source,
1125                                          eachGroup.batch_name,
1126                                          TrxRec.txn_interface_id,
1127                                          TrxRec.org_id,
1128                                          x_status);
1129 
1130 		    /* Resetting the value of Global variable after the gms validation */
1131             PA_TRX_IMPORT.Set_GVal_ProjTskEi_Date('Y'); -- bug 7271321
1132 
1133             IF  X_STATUS IS NOT NULL THEN
1134 
1135 	         ROLLBACK TO SAVE_TrxREC; -- Bug 3035863 : Introduced rollback in case of failure
1136 
1137                  UPDATE pa_transaction_interface_all
1138                     SET  transaction_rejection_code = X_status
1139                  ,       interface_id = P_xface_id
1140                  ,       expenditure_id = l_enc_id
1141                  ,       transaction_status_code = 'R'
1142                  WHERE CURRENT OF TrxRecs;
1143 
1144 		-- Bug 3221039 : Commented the following update statement as gms_transaction_
1145 		-- interface_all.transaction_status_code column is obsolete
1146 
1147 		/* UPDATE gms_transaction_interface_all
1148 		    SET transaction_status_code = 'R'
1149 		  WHERE orig_transaction_reference = TrxRec.orig_transaction_reference; */
1150 
1151                 pa_cc_utils.log_message('This  record is rejected Stage: Pre-Process ' || X_status, 1);
1152 
1153                 GOTO MOVETONEXT ;
1154 
1155            end if;  -- For the accepted records
1156 
1157            if x_acct_currency_code is NULL then
1158               pa_multi_currency.init;
1159               x_acct_currency_code := pa_multi_currency.G_accounting_currency_code;
1160            end if;
1161 
1162            pa_cc_utils.log_message('GMS_LD_PKG.PRE_PROCESS : Before calling PROC_VALIDATE_LOCAL');
1163 
1164 	   PROC_VALIDATE_LOCAL(TrxRec.raw_cost,x_status_code) ;
1165 
1166             IF x_success = 'F' THEN
1167                  write_to_log('GMS :PROC_VALIDATE_LOCAL returned x_success False') ;
1168 
1169 	         ROLLBACK TO SAVE_TrxREC; -- Bug 3035863 : Introduced rollback in case of failure
1170 
1171                  UPDATE pa_transaction_interface_all
1172                     SET  transaction_rejection_code = DECODE(x_status_code ,NULL,'GMS_UNEXPECTED_ERROR',x_status_code) -- Bug 3465939
1173                         ,       interface_id = P_xface_id
1174                         ,       expenditure_id = l_enc_id
1175                         ,       transaction_status_code = 'R'
1176                  WHERE current of TrxRecs ;
1177 
1178 		-- Bug 3221039 : Commented the following update statement as gms_transaction_
1179 		-- interface_all.transaction_status_code column is obsolete
1180 
1181 		 /* UPDATE gms_transaction_interface_all
1182 		    SET transaction_status_code = 'R'
1183 		  WHERE orig_transaction_reference = TrxRec.orig_transaction_reference; */
1184 
1185                  X_success := 'S' ;
1186                  GOTO MOVETONEXT ;
1187             END IF ;
1188 
1189            --
1190 	   -- bug : 3265300,3425124
1191 	   -- encumbrance summarize and transfer process gives 'gms_unexpected_error'
1192 	   --
1193            PROC_CREATE_GROUP( eachGroup.batch_name ) ;
1194 
1195            IF x_success = 'F' THEN
1196                  write_to_log('GMS :PROC_CREATE_GROUP returned x_success False') ;
1197 
1198 	         ROLLBACK TO SAVE_TrxREC; -- Bug 3035863 : Introduced rollback in case of failure
1199 
1200                 --*******************************
1201                 --*** ERROR
1202                 --*** DO Something for failure ;
1203                 --*** ****************************
1204                  UPDATE pa_transaction_interface_all
1205                     SET  transaction_rejection_code = 'GMS_UNEXPECTED_ERROR'
1206                         ,       interface_id = P_xface_id
1207                         ,       expenditure_id = l_enc_id
1208                         ,       transaction_status_code = 'R'
1209                  WHERE batch_name = P_batch ;
1210 
1211 		-- Bug 3221039 : Commented the following update statement as gms_transaction_
1212 		-- interface_all.transaction_status_code column is obsolete
1213 
1214 		 /*UPDATE gms_transaction_interface_all
1215 		    SET transaction_status_code = 'R'
1216 		  WHERE batch_name = P_batch ; */
1217 
1218 
1219                  X_success := 'S' ;
1220                  EXIT ;
1221            END IF ;
1222             -- --------------------------
1223             -- Group Creation  END..
1224             -- --------------------------
1225 
1226 	    -- Bug 3465939 :Shifted the call to PROC_VALIDATE_LOCAL before encumbrance group creation
1227 
1228 	    if l_gen_seq = 'Y' then
1229 
1230                 select gms_encumbrances_s.nextval
1231                 into l_enc_id
1232                 from dual;
1233 
1234                 gms_encumbrances_pkg.insert_row (x_rowid	=> l_rowid,
1235                        x_encumbrance_id			     => l_enc_id,
1236                        x_last_update_date		     => sysdate,
1237                        x_last_updated_by		     => to_number(fnd_profile.value('USER_ID')),
1238                        x_creation_date			     => sysdate,
1239                        x_created_by			         => to_number(fnd_profile.value('USER_ID')),
1240                        x_encumbrance_status_code	 => 'APPROVED',
1241                        x_encumbrance_ending_date	 => TrxRec.expenditure_ending_date,
1242                        x_encumbrance_class_code		 => TrxRec.system_linkage, /* changed to TrxRec.system_linkage from 'ST' for bug 5035700 --'ST',*/
1243                        x_incurred_by_person_id		 => l_person_id,
1244                        x_incurred_by_organization_id => l_organization_id,
1245                        x_encumbrance_group		     => l_encumbrance_grp,
1246                        x_control_total_amount		 => NULL,
1247                        x_entered_by_person_id		 => NULL,
1248                        x_description			     => NULL,
1249                        x_initial_submission_date	 => sysdate,
1250                        x_last_update_login		     => to_number(fnd_profile.value('LOGIN_ID')),
1251                        x_attribute_category		     => NULL,
1252                        x_attribute1			         => NULL,
1253                        x_attribute2			         => NULL,
1254                        x_attribute3			         => NULL,
1255                        x_attribute4			         => NULL,
1256                        x_attribute5			         => NULL,
1257                        x_attribute6			         => NULL,
1258                        x_attribute7			         => NULL,
1259                        x_attribute8			         => NULL,
1260                        x_attribute9			         => NULL,
1261                        x_attribute10		         => NULL,
1262 	                   x_denom_currency_code	     => 'USD',  -- Currency code hard coded
1263 -- The following fix is for Bug: 1331903
1264 --		               x_acct_currency_code	         => 'USD',  -- Currency code hard coded
1265 		               x_acct_currency_code	         => x_acct_currency_code,
1266 		               x_acct_rate_type	             => NULL,
1267 		               x_acct_rate_date	             => NULL,
1268 		               x_acct_exchange_rate	         => NULL,
1269                        x_orig_enc_txn_reference1 	 => NULL,
1270                        x_orig_enc_txn_reference2 	 => NULL,
1271                        x_orig_enc_txn_reference3 	 => NULL,
1272                        x_orig_user_enc_txn_reference => NULL,
1273                        x_vendor_id 			         => NULL,
1274                        x_org_id                      => TrxRec.org_id ); -- fix for bug : 2376730
1275 
1276                 l_gen_seq := 'N';
1277 
1278             end if;
1279 
1280             pa_cc_utils.log_message('Project : ' || TrxRec.project_number, 1);
1281 
1282              -- Bug 3035863 : Added below if condition to check for duplicate flags based on
1283 	     -- Allow_duplicate_flag value.
1284 
1285 	     IF NVL(l_allow_dup_ref_flag,'Y') = 'N' THEN
1286 
1287 			--CHECK for duplicates ...
1288 			begin
1289 				x_dummy := 0 ;
1290 				select count(*)
1291 				  into x_dummy
1292 				  from gms_encumbrance_items_all gei
1293 				 where orig_transaction_reference = trxRec.orig_transaction_reference
1294 				   and transaction_source	  = P_TRANSACTION_SOURCE ;
1295 
1296 		if x_dummy > 0 then
1297 
1298 	           ROLLBACK TO SAVE_TrxREC; -- Bug 3035863 : Introduced rollback in case of failure
1299 
1300                    UPDATE pa_transaction_interface_all
1301                       SET  transaction_rejection_code = 'DUPLICATE_ITEM'
1302                            ,       interface_id = P_xface_id
1303                            ,       expenditure_id = l_enc_id
1304                            ,       transaction_status_code = 'R'
1305                    WHERE CURRENT OF TrxRecs;
1306 
1307 		-- Bug 3221039 : Commented the following update statement as gms_transaction_
1308 		-- interface_all.transaction_status_code column is obsolete
1309 
1310 		 /*UPDATE gms_transaction_interface_all
1311 		    SET transaction_status_code = 'R'
1312 		  WHERE orig_transaction_reference = TrxRec.orig_transaction_reference
1313 		    AND transaction_source = P_TRANSACTION_SOURCE;*/
1314 
1315 		end if;
1316 
1317 			exception
1318 				when no_data_found then
1319 					NULL ;
1320 				WHEN others THEN
1321 					RAISE ;
1322 			end ;
1323 
1324 			IF x_dummy > 0 THEN
1325 				goto MOVETONEXT ;
1326 			END IF ;
1327 	    END IF;	-- Bug 3035863
1328 
1329             select gms_encumbrance_items_s.nextval
1330               into l_enc_item_id
1331               from dual;
1332 
1333             savepoint SAVE_ENC_ADL_REC ;
1334 
1335             /* Modified the following insert call by passing attributes instead of NULL for bug 3646187*/
1336             gms_encumbrance_items_pkg.insert_row (x_rowid         => l_rowid,
1337                        x_encumbrance_item_id          => l_enc_item_id,
1338                        x_last_update_date             => sysdate,
1339                        x_last_updated_by              => to_number(fnd_profile.value('USER_ID')),
1340                        x_creation_date                => sysdate,
1341                        x_created_by                   => to_number(fnd_profile.value('USER_ID')),
1342                        x_encumbrance_id               => l_enc_id,
1343                        x_task_id                      => l_task_id,
1344                        x_encumbrance_item_date        => TrxRec.expenditure_item_date,
1345                        x_encumbrance_type             => TrxRec.expenditure_type,
1346                        x_enc_distributed_flag         => 'N', -- default
1347                        x_amount                       => TrxRec.raw_cost,
1348                        x_override_to_organization_id  => l_override_organization_id,
1349                        x_adjusted_encumbrance_item_id => l_orig_enc_item_id, -- Bug 3465939
1350                        x_net_zero_adjustment_flag     => l_net_zero_adj_flag, -- Bug 3465939
1351                        x_transferred_from_enc_item_id => NULL,
1352                        x_last_update_login            => to_number(fnd_profile.value('LOGIN_ID')),
1353                        x_request_id                   => NULL,
1354                        x_attribute_category           => TrxRec.attribute_category,
1355                        x_attribute1                   => TrxRec.attribute1,
1356                        x_attribute2                   => TrxRec.attribute2,
1357                        x_attribute3                   => TrxRec.attribute3,
1358                        x_attribute4                   => TrxRec.attribute4,
1359                        x_attribute5                   => TrxRec.attribute5,
1360                        x_attribute6                   => TrxRec.attribute6,
1361                        x_attribute7                   => TrxRec.attribute7,
1362                        x_attribute8                   => TrxRec.attribute8,
1363                        x_attribute9                   => TrxRec.attribute9,
1364                        x_attribute10                  => TrxRec.attribute10,
1365                        x_orig_transaction_reference   => TrxRec.orig_transaction_reference,
1366                        x_transaction_source           => P_TRANSACTION_SOURCE,
1367                        x_project_id                   => l_project_id,
1368                        x_source_encumbrance_item_id   => NULL,
1369                        x_job_id                       => NULL,
1370                        x_system_linkage_function      => TrxRec.system_linkage,
1371                        x_denom_currency_code          => TrxRec.denom_currency_code,
1372                        x_denom_raw_amount             => TrxRec.acct_raw_cost,
1373                        x_acct_exchange_rounding_limit => TrxRec.acct_exchange_rounding_limit,
1374 -- The following fix is for Bug:1331903
1375 --                       x_acct_currency_code           => NULL,
1376                        x_acct_currency_code           => x_acct_currency_code,
1377                        x_acct_rate_date               => TrxRec.acct_rate_date,
1378                        x_acct_rate_type               => TrxRec.acct_rate_type,
1379                        x_acct_exchange_rate           => TrxRec.acct_exchange_rate,
1380                        x_acct_raw_cost                => TrxRec.acct_raw_cost,
1381                        x_project_currency_code        => TrxRec.project_currency_code,
1382                        x_project_rate_date            => TrxRec.project_rate_date,
1383                        x_project_rate_type            => TrxRec.project_rate_type,
1384                        x_project_exchange_rate        => TrxRec.project_exchange_rate,
1385                        x_denom_tp_currency_code       => NULL,
1386                        x_denom_transfer_price         => NULL,
1387                        x_encumbrance_comment          => TrxRec.expenditure_comment, --Bug#3755610
1388                        x_person_id                    => NULL,
1389                        x_incurred_by_person_id        => l_person_id,
1390                        x_ind_compiled_set_id          =>  NULL,
1391                        x_pa_date                      => NULL,
1392                        x_gl_date                      => NULL ,
1393                        x_line_num                     => 1,
1394                        x_burden_sum_dest_run_id       => NULL,
1395                        x_burden_sum_source_run_id     => NULL,
1396                        x_org_id                       => TrxRec.org_id ); -- fix for bug : 2376730
1397 
1398             pa_cc_utils.log_message('This  record validated ' || X_status, 1);
1399 
1400             IF f_create_adls THEN
1401                           UPDATE pa_transaction_interface_all
1402                             SET transaction_rejection_code = NULL,
1403                                 interface_id = P_xface_id,
1404                                 expenditure_id = l_enc_id,
1405                                 transaction_status_code = 'A',
1406                                 expenditure_item_id = l_enc_item_id
1407                           WHERE CURRENT OF TrxRecs;
1408 
1409 		-- Bug 3221039 : Commented the following update statement as gms_transaction_
1410 		-- interface_all.transaction_status_code column is obsolete
1411 
1412 		 /*UPDATE gms_transaction_interface_all
1413 		    SET transaction_status_code = 'A'
1414 		  WHERE orig_transaction_reference = TrxRec.orig_transaction_reference
1415 		    AND transaction_source = P_TRANSACTION_SOURCE;*/
1416 
1417                   -- Bug  3465939 : Updating the original encumbrance Item to Net zero.
1418 
1419                   UPDATE gms_encumbrance_items_all
1420                      SET net_zero_adjustment_flag = 'Y'
1421                    WHERE encumbrance_item_id = l_orig_enc_item_id;
1422 
1423            ELSE
1424                         rollback to save_enc_adl_rec ;
1425                         UPDATE pa_transaction_interface_all
1426                             SET  transaction_rejection_code = 'GMS_CREATE_ADL_FAILED'
1427                             ,       interface_id = P_xface_id
1428                             ,       expenditure_id = l_enc_id
1429                             ,       transaction_status_code = 'R'
1430                         WHERE CURRENT OF TrxRecs;
1431 
1432      		       -- Bug 3221039 : Commented the following update statement as gms_transaction_
1433        		       -- interface_all.transaction_status_code column is obsolete
1434 
1435 		       /* UPDATE gms_transaction_interface_all
1436 		          SET transaction_status_code = 'R'
1437 		        WHERE orig_transaction_reference = TrxRec.orig_transaction_reference
1438 		    	  AND transaction_source = P_TRANSACTION_SOURCE; */
1439 
1440            END IF ;
1441 
1442         <<MOVETONEXT>>
1443         NULL ;
1444     EXCEPTION
1445         WHEN  RESOURCE_BUSY  THEN
1446           pa_cc_utils.log_message('Cannot get lock',1);
1447           pa_cc_utils.reset_curr_function;
1448           write_to_log('GMS :RESOURCE_BUSY exception stage 20 ') ;
1449           write_to_log('GMS :SQLCODE '||SQLCODE) ;
1450           write_to_log('GMS :SQLERRM '||SQLERRM) ;
1451           raise_application_error(SQLCODE,SQLERRM) ;
1452         WHEN OTHERS THEN
1453             write_to_log('GMS :OTHERS exception stage 20 ') ;
1454             write_to_log('GMS :SQLCODE '||SQLCODE) ;
1455             write_to_log('GMS :SQLERRM '||SQLERRM) ;
1456             --*******************************
1457             --*** ERROR
1458             --***REJECT ITEM and continue.....
1459             --*** ******************************
1460 	    ROLLBACK TO SAVE_TrxREC; -- Bug 3035863 : Introduced rollback in case of failure
1461             UPDATE pa_transaction_interface_all
1462               SET  transaction_rejection_code = 'GMS_UNEXPECTED_ERROR'
1463                    ,       interface_id = P_xface_id
1464                    ,       expenditure_id = l_enc_id
1465                    ,       transaction_status_code = 'R'
1466              WHERE CURRENT OF TrxRecs;
1467 
1468 	    -- Bug 3221039 : Commented the following update statement as gms_transaction_
1469 	    -- interface_all.transaction_status_code column is obsolete
1470 
1471 	    /* UPDATE gms_transaction_interface_all
1472 	       SET transaction_status_code = 'R'
1473 	     WHERE orig_transaction_reference = TrxRec.orig_transaction_reference; */
1474 
1475           	 pa_cc_utils.log_message('Unexpected error :TrxRecs LOOP: '||SQLERRM,1);
1476     END ;
1477     end loop;  -- TrxRecs
1478     --end if;
1479     <<NEXTREC>>
1480     NULL ;
1481 end loop;
1482 
1483 --PROC_FUNDS_CHECK_ENC ;
1484 
1485 -- Bug  3035863 : Deleting the records from Grants Transactions tables
1486 -- based on purgeable flag.
1487 
1488 IF NVL(l_purgeable_flag,'N')  = 'Y' THEN
1489 
1490      DELETE gms_transaction_interface_all
1491       WHERE txn_interface_id IN (SELECT txn_interface_id
1492                                    FROM pa_transaction_interface_all
1493                                   WHERE interface_id = P_XFACE_ID
1494                                     AND transaction_status_code ='A' );
1495      pa_cc_utils.log_message('GMS_LD_PKG.PRE_PROCESS : Number of success records deleted from Grants interface table :'||SQL%ROWCOUNT);
1496 
1497 END IF ;
1498 
1499 write_to_log('GMS :end time gms_ld_pkg.pre_process :'||to_char(sysdate, 'DD-MON-YYYY HH24:MI:SS')) ;
1500 
1501 
1502 commit;
1503 
1504 EXCEPTION
1505  WHEN  RESOURCE_BUSY  THEN
1506        pa_cc_utils.log_message('Cannot get lock',1);
1507        pa_cc_utils.reset_curr_function;
1508        write_to_log('GMS :RESOURCE_BUSY exception stage30 ') ;
1509        write_to_log('GMS :SQLCODE '||SQLCODE) ;
1510        write_to_log('GMS :SQLERRM '||SQLERRM) ;
1511        raise_application_error(SQLCODE,SQLERRM) ;
1512  when no_data_found then
1513       pa_cc_utils.log_message('No data found for some item..', 1);
1514       write_to_log('GMS :NO_DATA_FOUND exception stage30 ') ;
1515       write_to_log('GMS :SQLCODE '||SQLCODE) ;
1516       write_to_log('GMS :SQLERRM '||SQLERRM) ;
1517       raise_application_error(SQLCODE, SQLERRM) ;
1518       rollback ;
1519  when others then
1520       pa_cc_utils.log_message('Unexpected error: '||SQLERRM,1);
1521       write_to_log('GMS :OTHERS exception stage30 ') ;
1522       write_to_log('GMS :SQLCODE '||SQLCODE) ;
1523       write_to_log('GMS :SQLERRM '||SQLERRM) ;
1524       raise_application_error(SQLCODE, SQLERRM) ;
1525       rollback ;
1526 END;
1527 
1528 /* Bug# 4138033 */
1529 PROCEDURE Validate_Dates_YN
1530              ( l_award_id1           IN gms_awards_all.award_id%TYPE,  -- Original Encumbrance Award Id
1531 	       l_project_id1         IN pa_projects_all.project_id%TYPE, -- Original Encumbrance Project Id
1532 	       l_task_id1            IN pa_tasks.task_id%TYPE, -- Original Encumbrance Task Id
1533 	       l_orig_enc_item_id1   IN gms_encumbrance_items_all.encumbrance_item_id%TYPE -- Original Encumbrance Item Id
1534 	       )  IS
1535 
1536    /*  relaxing this check from bug 7271321
1537 
1538        We just need to verify the existance of the encumbrance transaction in the
1539        gms_encumbrance_items and not really that the original encumrbance transaction
1540        should be behind the max start date or beyond min end date fetched in this cursor.
1541 
1542        This means that the liquidation transaction can be for an encumbrance transaction
1543        which may be falling between the dates or not.
1544 
1545     -- The following cursor is to get the maximum start date and minimum completion date
1546     -- out of award, project and task's start and end dates.
1547     CURSOR Cur_MaxMin_StartEnd_Dates IS
1548         SELECT max(start_date), min(completion_date)
1549 	FROM   (   select start_date, completion_date
1550                    from   pa_tasks tsk1
1551                    where  task_id = l_task_id1
1552                    union all
1553                    select start_date, completion_date
1554                    from   pa_projects_all
1555                    where  project_id = l_project_id1
1556                    union all
1557                    select start_date_active start_date, end_date_active completion_date
1558                    from   gms_awards_all
1559                    where  award_id = l_award_id1
1560 	        );
1561 
1562    l_max_start_date DATE;
1563    l_min_end_date   DATE;
1564 
1565    end for the bug 7271321   */
1566 
1567    -- To verify if the original encumbrance item date is behind the max start date
1568    -- or min end date fetched in the above cursor.
1569    -- If this cursor returs a row, it means that the original encumbrance item is falling out of
1570    -- the start and end dates of any of the task/project/award.
1571    -- Now, we can skip the dates validation for the reversal encumbrance item which happens
1572    -- in the procedure PATC.Get_Status, as the original encumbrance itself falls out of the
1573    -- dates there is no need to do the date validation for the reversal encumbrance item.
1574 
1575    CURSOR Cur_Check_EncItemDate IS
1576        SELECT 1
1577        FROM   gms_encumbrance_items_all
1578        WHERE  encumbrance_item_id = l_orig_enc_item_id1;
1579        --AND    (encumbrance_item_date < l_max_start_date OR encumbrance_item_date > l_min_end_date); --  bug 7271321
1580 
1581    l_Check_EncItemDate NUMBER := 0;
1582 
1583 BEGIN
1584 
1585       /* BUG7271321 OPEN Cur_MaxMin_StartEnd_Dates;
1586        FETCH Cur_MaxMin_StartEnd_Dates INTO l_max_start_date, l_min_end_date;
1587        CLOSE Cur_MaxMin_StartEnd_Dates;*/
1588 
1589        OPEN Cur_Check_EncItemDate;
1590        FETCH Cur_Check_EncItemDate INTO l_Check_EncItemDate;
1591        CLOSE Cur_Check_EncItemDate;
1592 
1593        IF l_Check_EncItemDate = 1 THEN
1594          -- set the global variable so as to skip validating the dates in PATC.get_status.
1595           PA_TRX_IMPORT.Set_GVal_ProjTskEi_Date('N');
1596        ELSE
1597           PA_TRX_IMPORT.Set_GVal_ProjTskEi_Date('Y');
1598        END IF;
1599 
1600 END Validate_Dates_YN;
1601 
1602 END GMS_LD_PKG;