DBA Data[Home] [Help]

PACKAGE BODY: APPS.PO_AUTOSOURCE_SV

Source


1 PACKAGE BODY PO_AUTOSOURCE_SV AS
2 /* $Header: POXSRCDB.pls 120.24.12010000.9 2008/11/01 09:40:36 adevadul ship $*/
3 
4 G_PKG_NAME  CONSTANT VARCHAR2(30) := 'PO_AUTOSOURCE_SV';
5 
6 --<Shared Proc FPJ START>
7 g_log_head  CONSTANT VARCHAR2(50) := 'po.plsql.' || g_pkg_name || '.';
8 
9 g_debug_stmt BOOLEAN := PO_DEBUG.is_debug_stmt_on;
10 
11 g_debug_unexp BOOLEAN := PO_DEBUG.is_debug_unexp_on;
12 --<Shared Proc FPJ END>
13 g_root_invoking_module VARCHAR2(30); --<bug#4936992>
14 -------------------------------------------------------------------------------
15 --Start of Comments
16 --Name: AUTOSOURCE
17 --Pre-reqs:
18 --  None.
19 --Modifies:
20 --  None.
21 --Locks:
22 --  None.
23 --Function:
24 --  This procedure performs automatic document sourcing based on item/item category,
25 --  supplier/supplier site, and profile option settings
26 --Parameters:
27 --IN:
28 --x_mode
29 --  Valid values 'VENDOR','INVENTORY', 'BOTH', 'DOCUMENT'
30 --x_destination_doc_type
31 --  The form from which the call to the API is made. Vaild values are
32 --  'PO', 'REQ', 'STANDARD PO', 'REQ_NONCATALOG' and NULL.
33 --  'REQ_NONCATALOG' is for requisition lines that are non-catalog requests (created
34 --  through iProcurement)  -- <Contract AutoSourcing FPJ >
35 --x_item_id
36 --  item_id to be matched to source document
37 --x_commodity_id
38 --  The same as category_id, used in category-based ASL sourcing
39 --x_dest_organization_id
40 --  Destination organization id
41 --x_dest_subinventory
42 --  Destination subinventory
43 --x_autosource_date
44 --  Date to be used for Sourcing date check
45 --x_item_rev
46 --  Item revision that needs to be compared to.
47 --x_currency_code
48 --  Currency code to be compared to get matching document
49 --IN OUT:
50 --x_vendor_id
51 --  Vendor id to be matched to source document or ASL
52 --x_vendor_site_id
53 --  This parameter is used as IN OUT parameter. For callers who do not want
54 --  to do vendor site sourcing will pass in a value and set vendor_site_sourcing_flag
55 --  = 'N'. When vendor_site_sourcing_flag = 'Y' then this parameter would contain
56 --  the site_id obtained by vendor site sourcing
57 --x_vendor_contact_id
58 --  If there is a unique contact id present then this returns that value
59 --x_source_organization_id,
60 --  Organization that owns the source document
61 --x_source_subinventory
62 --  Subinventory that associated with the source document
63 --x_document_header_id
64 --  The unique identifier of the document returned
65 --x_document_line_id
66 --  The unique identifier of the document line returned
67 --x_document_type_code
68 --  Valid values 'BLANKET', 'QUOTATION' and 'CONTRACT'
69 --x_document_line_num
70 --  The line number of the document returned
71 --x_buyer_id
72 --  The buyer mentioned on the document returned
73 --x_vendor_product_num
74 --  Supplier product_num associated with given Item
75 --x_purchasing_uom
76 --  Purchasing unit of measure
77 --x_asl_id
78 --  Unique identifier of the ASL associated with the source document
79 --Testing:
80 --  None
81 --End of Comments
82 -----------------------------------------------------------------------------*/
83 --<PKGCOMP R12 Start>
84 -- We need the value of the asl_id in the PO_AUTOSOURCE_SV.reqimport_sourcing. We
85 -- have to get it from the PO_AUTOSOURCE_SV.autosource. Added a new parameter
86 -- x_asl_id as IN OUT type so that we can pass this value back to the
87 -- calling procedure.
88 --<PKGCOMP R12 End>
89 PROCEDURE autosource(
90 		x_mode				IN	VARCHAR2,
91 		x_destination_doc_type		IN	VARCHAR2,
92 		x_item_id			IN	NUMBER,
93 		x_commodity_id			IN	NUMBER,
94 		x_dest_organization_id		IN	NUMBER,
95 		x_dest_subinventory		IN	VARCHAR2,
96 		x_autosource_date		IN	DATE,
97 		x_item_rev			IN	VARCHAR2,
98 		x_currency_code			IN	VARCHAR2,
99 		x_vendor_id			IN OUT NOCOPY  NUMBER,
100 		x_vendor_site_id		IN OUT NOCOPY  NUMBER,
101 		x_vendor_contact_id		IN OUT NOCOPY  NUMBER,
102 		x_source_organization_id	IN OUT	NOCOPY NUMBER,
103 		x_source_subinventory		IN OUT	NOCOPY VARCHAR2,
104 		x_document_header_id		IN OUT NOCOPY  NUMBER,
105 		x_document_line_id		IN OUT	NOCOPY NUMBER,
106 		x_document_type_code		IN OUT NOCOPY  VARCHAR2,
107 		x_document_line_num		IN OUT	NOCOPY NUMBER,
108 		x_buyer_id			IN OUT NOCOPY  NUMBER,
109 		x_vendor_product_num		IN OUT NOCOPY  VARCHAR2,
110 		x_purchasing_uom		IN OUT NOCOPY  VARCHAR2,
111 		x_asl_id 		        IN OUT NOCOPY NUMBER --<PKGCOMP R12>
112                 --<R12 STYLES PHASE II START>
113                ,p_purchase_basis   IN VARCHAR2 DEFAULT NULL,
114                 p_line_type_id     IN VARCHAR2 DEFAULT NULL,
115                 p_destination_type IN VARCHAR2 DEFAULT NULL,
116                 p_style_id         IN NUMBER   DEFAULT NULL
117                 --<R12 STYLES PHASE II END>
118 ) IS
119     x_sourcing_rule_id	    NUMBER;
120     -- Bug 2836530 Changed x_error_message from VARCHAR2(240) to %TYPE
121     x_error_message	    FND_NEW_MESSAGES.message_text%TYPE := '';
122     x_organization_id	    NUMBER;
123     x_item_buyer_id         NUMBER;
124     x_ga_flag               VARCHAR2(1) := '';
125     x_owning_org_id         NUMBER;
126     x_fsp_org_id            NUMBER;
127     l_vendor_site_code      PO_VENDOR_SITES_ALL.vendor_site_code%TYPE; --<Shared Proc FPJ>
128     l_return_code           BOOLEAN; --<Bug 3234201 mbhargav>
129     l_buyer_ok              VARCHAR2(1); --<Shared Proc FPJ>
130     l_progress              VARCHAR2(3) := '000'; -- Bug 2836530
131     l_log_head     CONSTANT VARCHAR2(100) := g_log_head||'autosource';
132 BEGIN
133 
134     IF g_debug_stmt THEN
135        PO_DEBUG.debug_begin(l_log_head);
136        PO_DEBUG.debug_var(l_log_head,l_progress,'x_mode', x_mode);
137        PO_DEBUG.debug_var(l_log_head,l_progress,'x_item_id', x_item_id);
138        PO_DEBUG.debug_var(l_log_head,l_progress,'x_commodity_id', x_commodity_id);
139        PO_DEBUG.debug_var(l_log_head,l_progress,'x_dest_organization_id', x_dest_organization_id);
140        PO_DEBUG.debug_var(l_log_head,l_progress,'x_autosource_date', x_autosource_date);
141     END IF;
142 
143     l_progress := '001';
144 
145 /* AGARG Bug# 523766
146    The following code has been duplicated in reqimport_sourcing procedure in order
147    to avoid calling the MRP sourcing routines if the vendor and vendor site is already
148    known. In that case we want to do every thing in this procedure for x_mode of VENDOR
149    other than calling the mrp_sourcing_api_pk.mrp_sourcing.
150    SO if any souring changes are made in this routine they should also be duplicated in
151    reqimport_sourcing procedure.
152    This has been done , since autosource is called from a lot of other places besides
153    Req Import. and the above change is Req Import specific.
154 */
155 
156     IF x_dest_organization_id IS NULL THEN
157 
158         -- Get organization_id from financials_system_parameters.
159         SELECT   inventory_organization_id
160         INTO     x_organization_id
161         FROM     financials_system_parameters;
162 
163     ELSE
164 	    x_organization_id := x_dest_organization_id;
165     END IF;
166 
167     l_progress := '010';
168 
169     -- Get buyer_id from item definition.  If we cannot get buyer_id from
170     -- the item definition then we will try to get it from the source document.
171 
172     /*  Bug - 1135210 - Added the Exception NO_DATA_FOUND, if the sql returns
173     **  no data. This is done to avoid the system from hanging when the item
174     **  that has been entered is not valid in that destination org in the
175     **  Enter Req form.
176     **/
177 
178     IF (x_item_id IS NOT NULL) THEN
179 
180      BEGIN
181        SELECT   msi.buyer_id
182        INTO     x_buyer_id
183        FROM	mtl_system_items msi
184        WHERE    msi.inventory_item_id = x_item_id
185        AND	msi.organization_id = x_organization_id;
186 
187       x_item_buyer_id := x_buyer_id;    -- FPI GA
188 
189       IF g_debug_stmt THEN
190          PO_DEBUG.debug_var(l_log_head,l_progress,'x_item_buyer_id', x_item_buyer_id);
191       END IF;
192 
193      EXCEPTION
194          WHEN NO_DATA_FOUND THEN
195             x_buyer_id := NULL;
196             x_item_buyer_id := NULL;
197      END;
198 --bug#3048965 if the buyer id in mtl_system_items table is null then
199 --we make an attempt to default it from the po_agents table
200 --if there is only one buyer defined for the category associated
201 --with the Purchasing category set of the concerned item.
202      IF(x_buyer_id is null)THEN
203 	begin
204 	        select poa.agent_id into x_buyer_id
205 		from po_agents poa,mtl_item_categories mic
206 		where mic.inventory_item_id=x_item_id
207 		and mic.category_id=poa.category_id
208 		and mic.organization_id=x_organization_id
209 		and mic.category_set_id=(select category_set_id
210 	                        	 from   mtl_default_sets_view
211                         		 where  functional_area_id = 2);
212 		 x_item_buyer_id := x_buyer_id;
213 	exception
214 		when others then
215 --bug#3048965 if more than one record is found or in case of
216 --other error we just make the buyer id null
217 			x_buyer_id:=null;
218 			x_item_buyer_id:=null;
219 	end;
220 --bug#3048965
221 
222      END IF;
223 
224     END IF;
225 
226     l_progress := '020';
227 
228     IF (x_mode IN ('VENDOR', 'INVENTORY', 'BOTH')) THEN
229 
230        l_progress := '030';
231        IF g_debug_stmt THEN
232           PO_DEBUG.debug_stmt(l_log_head,l_progress,'Calling MRP Sourcing API');
233        END IF;
234 
235        --<Shared Proc FPJ START>
236        --<Bug 3234201 mbhargav START>
237        --Call the signature of mrp_sourcing_api which returns
238        --vendor_site_code instead of vendor_site_id. This
239        --vendor_site_code will be used to determine vendor_site_id
240        --in document_sourcing procedure
241        l_return_code := MRP_SOURCING_API_PK.mrp_sourcing(
242                arg_mode		            =>x_mode,
243                arg_item_id	            => x_item_id,
244                arg_commodity_id		    => x_commodity_id,
245                arg_dest_organization_id   =>x_organization_id,
246                arg_dest_subinventory	    =>x_dest_subinventory,
247                arg_autosource_date	    =>trunc(nvl(x_autosource_date, sysdate)),
248                arg_vendor_id		        =>    x_vendor_id,
249                arg_vendor_site_code	    =>l_vendor_site_code,
250                arg_source_organization_id =>x_source_organization_id,
251                arg_source_subinventory 	=>x_source_subinventory,
252                arg_sourcing_rule_id 	    =>x_sourcing_rule_id,
253                arg_error_message 	        =>x_error_message);
254         --<Bug 3234201 mbhargav END>
255 	  if ( not l_return_code and trunc(x_autosource_date) <> trunc(sysdate)) then
256                     l_return_code := MRP_SOURCING_API_PK.mrp_sourcing(
257                    arg_mode                    =>x_mode,
258                    arg_item_id                => x_item_id,
259                    arg_commodity_id            => x_commodity_id,
260                    arg_dest_organization_id   =>x_organization_id,
261                   arg_dest_subinventory        =>x_dest_subinventory,
262                    arg_autosource_date        =>trunc(sysdate),     -- bug6825123
263                    arg_vendor_id                =>    x_vendor_id,
264                    arg_vendor_site_code        =>l_vendor_site_code,
265                    arg_source_organization_id =>x_source_organization_id,
266                    arg_source_subinventory     =>x_source_subinventory,
267                    arg_sourcing_rule_id         =>x_sourcing_rule_id,
268                    arg_error_message             =>x_error_message);
269            end if;
270         --<Shared Proc FPJ END>
271 
272         l_progress := '040';
273          IF g_debug_stmt THEN
274             --PO_DEBUG.debug_var(l_log_head,l_progress,'MRP API return status', l_return_status);
275             PO_DEBUG.debug_var(l_log_head,l_progress,'x_vendor_id', x_vendor_id);
276             PO_DEBUG.debug_var(l_log_head,l_progress,'l_vendor_site_code', l_vendor_site_code);
277             PO_DEBUG.debug_var(l_log_head,l_progress,'x_source_organization_id', x_source_organization_id);
278             PO_DEBUG.debug_var(l_log_head,l_progress,'x_sourcing_rule_id', x_sourcing_rule_id);
279             PO_DEBUG.debug_var(l_log_head,l_progress,'x_error_message', x_error_message);
280         END IF;
281 
282         l_progress := '045';
283         IF NOT l_return_code THEN
284            x_error_message := FND_MESSAGE.get;
285            IF g_debug_stmt THEN
286               PO_DEBUG.debug_var(l_log_head,l_progress,'x_error_message', x_error_message);
287            END IF;
288         END IF;
289 
290             --<Contract AutoSourcing FPJ>: Removed 'x_item_id is not null' condition because
291             --category-based ASL sourcing is enabled
292 	    IF (l_return_code
293             AND x_mode IN ('VENDOR', 'BOTH')) THEN
294 
295                IF g_debug_stmt THEN
296                   PO_DEBUG.debug_stmt(l_log_head,l_progress,'Calling Document Sourcing');
297                END IF;
298 
299                --<Shared Proc FPJ START>
300                --The document sourcing will also do vendor site_id sourcing
301                --We set vendor_site_sourcing_flag to 'Y' and pass vendor_site_code
302 	       --<PKGCOMP R12 Start>
303 	       -- Replaced the hardcoded NULL with x_asl_id as we need to communicate it back
304 	       -- to reqimport_sourcing.
305 	       --<PKGCOMP R12 End>
306                document_sourcing(
307                     x_item_id			=>x_item_id,
308                	    x_vendor_id		        =>x_vendor_id,
309                	    x_destination_doc_type	=>x_destination_doc_type,
310                     x_organization_id 		=>x_organization_id,
311                     x_currency_code 		=>x_currency_code,
312                     x_item_rev			=>x_item_rev,
316                     x_document_type_code 	=>x_document_type_code,
313                     x_autosource_date 		=>x_autosource_date,
314                     x_vendor_site_id 		=>x_vendor_site_id,
315                     x_document_header_id	=>x_document_header_id,
317                     x_document_line_num	        =>x_document_line_num,
318                     x_document_line_id		=>x_document_line_id,
319                     x_vendor_contact_id		=>x_vendor_contact_id,
320                     x_vendor_product_num 	=>x_vendor_product_num,
321                     x_buyer_id 		        =>x_buyer_id,
322                     x_purchasing_uom		=>x_purchasing_uom,
323                     x_asl_id			=>x_asl_id, --<PKGCOMP R12>
324                     x_multi_org		        =>'N',
325                     p_vendor_site_sourcing_flag	=>'Y',
326                     p_vendor_site_code		=>l_vendor_site_code,
327                     p_category_id               =>x_commodity_id --<Contract AutoSourcing FPJ>
328                     --<R12 STYLES PHASE II START>
329                    ,p_purchase_basis   => p_purchase_basis,
330                     p_line_type_id     => p_line_type_id,
331                     p_destination_type => p_destination_type,
332                     p_style_id         => p_style_id
333                     --<R12 STYLES PHASE II END>
334                 );
335                 l_progress := '050';
336                 IF g_debug_stmt THEN
337                    PO_DEBUG.debug_stmt(l_log_head,l_progress,'Document Sourcing Returned');
338                    PO_DEBUG.debug_var(l_log_head,l_progress,'x_vendor_site_id', x_vendor_site_id);
339                    PO_DEBUG.debug_var(l_log_head,l_progress,'x_document_header_id', x_document_header_id);
340                    PO_DEBUG.debug_var(l_log_head,l_progress,'x_document_line_id', x_document_line_id);
341                 END IF;
342 
343 
344                 IF l_vendor_site_code is NOT NULL
345                    AND x_vendor_site_id is NULL THEN
346 
347                    IF g_debug_stmt THEN
348                       PO_DEBUG.debug_stmt(l_log_head,l_progress,
349                            'No Source Doc found, getting site from current OU');
350                    END IF;
351 
352                    BEGIN
353                         SELECT vendor_site_id
354                         INTO x_vendor_site_id
355                         FROM po_vendor_sites_all pvs,
356                              org_organization_definitions oog
357                         WHERE pvs.vendor_site_code = l_vendor_site_code
358                         AND   nvl(pvs.org_id,nvl(oog.operating_unit,-1)) =
359                                                       nvl(oog.operating_unit,-1)
360                         AND  oog.organization_id = x_organization_id
361                         AND  pvs.vendor_id = x_vendor_id;
362                     EXCEPTION
363                         WHEN OTHERS THEN
364                             x_vendor_site_id := NULL;
365                             x_vendor_id := NULL;
366                     END;
367                 END IF; --vendor_site_code check
368                 --<Shared Proc FPJ END>
369 
370 	     END IF;
371          l_progress := '060';
372     ELSIF x_mode = 'DOCUMENT' THEN
373 
374         l_progress := '070';
375         IF g_debug_stmt THEN
376            PO_DEBUG.debug_stmt(l_log_head,l_progress,'Calling Document Sourcing');
377         END IF;
378        --<Shared Proc FPJ START>
379        --In DOCUMENT mode we do not need to vendor site sourcing.
380        --It is assumed that vendor_site_id is valid. The vendor_site_sourcing_flag is set to N
381 
382        --<PKGCOMP R12 Start>
383        -- Replaced the hardcoded NULL with x_asl_id as we need to communicate it back
384        -- to reqimport_sourcing.
385        --<PKGCOMP R12 End>
386 
387        document_sourcing(
388                 	x_item_id		=>x_item_id,
389                	        x_vendor_id		=>x_vendor_id,
390                	        x_destination_doc_type	=>x_destination_doc_type,
391                 	x_organization_id 	=>x_organization_id,
392                 	x_currency_code 	=>x_currency_code,
393                 	x_item_rev		=>x_item_rev,
394                 	x_autosource_date 	=>x_autosource_date,
395                 	x_vendor_site_id 	=>x_vendor_site_id,
396                 	x_document_header_id	=>x_document_header_id,
397                 	x_document_type_code 	=>x_document_type_code,
398                 	x_document_line_num	=>x_document_line_num,
399                 	x_document_line_id	=>x_document_line_id,
400                 	x_vendor_contact_id	=>x_vendor_contact_id,
401                 	x_vendor_product_num 	=>x_vendor_product_num,
402                 	x_buyer_id 		=>x_buyer_id,
403                 	x_purchasing_uom	=>x_purchasing_uom,
404                 	x_asl_id		=>x_asl_id, --<PKGCOMP R12>
405                 	x_multi_org		=>'N',
406                 	p_vendor_site_sourcing_flag	=>'N',
407                 	p_vendor_site_code	=>NULL,
408                         p_category_id           =>x_commodity_id --<Contract AutoSourcing FPJ >
409                         --<R12 STYLES PHASE II START>
410                        ,p_purchase_basis   => p_purchase_basis,
411                         p_line_type_id     => p_line_type_id,
412                         p_destination_type => p_destination_type,
413                         p_style_id         => p_style_id
414                         --<R12 STYLES PHASE II END>
415                   	);
416          IF g_debug_stmt THEN
417             PO_DEBUG.debug_stmt(l_log_head,l_progress,'Document Sourcing Returned');
421         END IF;
418             PO_DEBUG.debug_var(l_log_head,l_progress,'x_vendor_site_id', x_vendor_site_id);
419             PO_DEBUG.debug_var(l_log_head,l_progress,'x_document_header_id', x_document_header_id);
420             PO_DEBUG.debug_var(l_log_head,l_progress,'x_document_line_id', x_document_line_id);
422         --<Shared Proc FPJ END>
423 
424         l_progress := '080';
425 
426     END IF;
427 
428     l_progress := '090';
429 
430  /* FPI GA start */
431  /* For a global agreement from another org do not get the buyer from the document */
432   IF x_document_header_id is not null
433      AND x_buyer_id is NOT NULL --<Shared Proc FPJ>
434   THEN
435 
436      l_progress := '100';
437      --<Shared Proc FPJ START>
438      --The buyer on Source Document should be in the same business group as
439      --the requesting operating unit(current OU) or the profile option HR: Cross
440      --Business Group should be set to 'Y'. These two conditions are checked in
441      --view definition of per_people_f
442      BEGIN
443           SELECT 'Y'
444           INTO l_buyer_ok
445           FROM per_people_f ppf
446           WHERE x_buyer_id = ppf.person_id
447            AND trunc(sysdate) between ppf.effective_start_date
448                                      AND NVL(ppf.effective_end_date, sysdate +1);
449      EXCEPTION WHEN OTHERS THEN
450            x_buyer_id := x_item_buyer_id;
451      END;
452      --<Shared Proc FPJ END>
453   END IF;
454  /* FPI GA end */
455   l_progress := '110';
456   IF g_debug_stmt THEN
457    PO_DEBUG.debug_end(l_log_head);
458   END IF;
459 -- Bug 2836540 START
460 EXCEPTION
461     WHEN OTHERS THEN
462      IF g_debug_unexp THEN
463       PO_DEBUG.debug_exc(l_log_head,l_progress);
464      END IF;
465 	PO_MESSAGE_S.SQL_ERROR('AUTOSOURCE', l_progress, sqlcode);
466 -- Bug 2836540 END
467 END autosource;
468 
469 --<PKGCOMP R12 Start>
470 -------------------------------------------------------------------------------
471 --Start of Comments
472 --Name: AUTOSOURCE
473 --Pre-reqs:
474 --  None.
475 --Modifies:
476 --  None.
477 --Locks:
478 --  None.
479 --Function:
480 -- This is the overloaded procedure that will be called by all the routines,
481 -- which were already calling PO_AUTOSOURCE_SV.autosource without ASL_ID parameter.
482 -- This procedure in turn will call the autosource procedure, which has the
483 -- additional parameter x_asl_id with a NULL value.
484 --End of Comments
485  -------------------------------------------------------------------------------
486   PROCEDURE autosource(x_mode                   IN VARCHAR2,
487                        x_destination_doc_type   IN VARCHAR2,
488                        x_item_id                IN NUMBER,
489                        x_commodity_id           IN NUMBER,
490                        x_dest_organization_id   IN NUMBER,
491                        x_dest_subinventory      IN VARCHAR2,
492                        x_autosource_date        IN DATE,
493                        x_item_rev               IN VARCHAR2,
494                        x_currency_code          IN VARCHAR2,
495                        x_vendor_id              IN OUT NOCOPY NUMBER,
496                        x_vendor_site_id         IN OUT NOCOPY NUMBER,
497                        x_vendor_contact_id      IN OUT NOCOPY NUMBER,
498                        x_source_organization_id IN OUT NOCOPY NUMBER,
499                        x_source_subinventory    IN OUT NOCOPY VARCHAR2,
500                        x_document_header_id     IN OUT NOCOPY NUMBER,
501                        x_document_line_id       IN OUT NOCOPY NUMBER,
502                        x_document_type_code     IN OUT NOCOPY VARCHAR2,
503                        x_document_line_num      IN OUT NOCOPY NUMBER,
504                        x_buyer_id               IN OUT NOCOPY NUMBER,
505                        x_vendor_product_num     IN OUT NOCOPY VARCHAR2,
506                        x_purchasing_uom         IN OUT NOCOPY VARCHAR2
510                        p_destination_type IN VARCHAR2 DEFAULT NULL,
507                        --<R12 STYLES PHASE II START>
508                       ,p_purchase_basis   IN VARCHAR2 DEFAULT NULL,
509                        p_line_type_id     IN VARCHAR2 DEFAULT NULL,
511                        p_style_id         IN NUMBER DEFAULT NULL
512                        --<R12 STYLES PHASE II END>
513 		       ) IS
514 
515     l_asl_id PO_ASL_DOCUMENTS.ASL_ID%type;
516 
517   begin
518     l_asl_id := NULL;
519     autosource(x_mode                   => x_mode,
520                x_destination_doc_type   => x_destination_doc_type,
521                x_item_id                => x_item_id,
522                x_commodity_id           => x_commodity_id,
523                x_dest_organization_id   => x_dest_organization_id,
524                x_dest_subinventory      => x_dest_subinventory,
525                x_autosource_date        => x_autosource_date,
526                x_item_rev               => x_item_rev,
527                x_currency_code          => x_currency_code,
528                x_vendor_id              => x_vendor_id,
529                x_vendor_site_id         => x_vendor_site_id,
530                x_vendor_contact_id      => x_vendor_contact_id,
531                x_source_organization_id => x_source_organization_id,
532                x_source_subinventory    => x_source_subinventory,
533                x_document_header_id     => x_document_header_id,
534                x_document_line_id       => x_document_line_id,
535                x_document_type_code     => x_document_type_code,
536                x_document_line_num      => x_document_line_num,
537                x_buyer_id               => x_buyer_id,
538                x_vendor_product_num     => x_vendor_product_num,
539                x_purchasing_uom         => x_purchasing_uom,
540                x_asl_id                 => l_asl_id
541                --<R12 STYLES PHASE II START>
542               ,p_purchase_basis   => p_purchase_basis,
543                p_line_type_id     => p_line_type_id,
544                p_destination_type => p_destination_type,
545                p_style_id         => p_style_id
546                --<R12 STYLES PHASE II END>
547                );
548 
549   end autosource;
550 --<PKGCOMP R12 End>
551 
552 /* CONSIGNED FPI START */
553 
554 /*===========================================================================
555 
556   PROCEDURE NAME:       get_asl_info
557 
558   REQUIRED INPUTS:
559 
560   OPTIONAL INPUTS:
561 
562   OUTPUTS:
563 
564   ALGORITHM:		Returns the supplier item number and purchasing
565 			UOM from the ASL entry.
566 
567   NOTES    : Asl_id can also obtained from Get_All_Item_Asl procedure.
568 	     This is the same as x_asl_id but returns vendor_id also and
569 	     in an array. When any changes are made to get_asl_info
570      	     need to consider Get_All_Item_Asl procedure also.
571 
572 ===========================================================================*/
573 
574 PROCEDURE get_asl_info(
575 		x_item_id		IN 	NUMBER,
576 		x_vendor_id		IN 	NUMBER,
577 	        x_vendor_site_id	IN	NUMBER,
578 		x_using_organization_id	IN OUT	NOCOPY NUMBER,
579 		x_asl_id		IN OUT	NOCOPY NUMBER,
580 		x_vendor_product_num	IN OUT	NOCOPY VARCHAR2,
581 		x_purchasing_uom	IN OUT  NOCOPY VARCHAR2,
582                 p_category_id           IN      NUMBER --<Contract AutoSourcing FPJ>
583 )
584 IS
585 
586 l_consigned_from_supplier_flag   VARCHAR2(1)  := NULL;
587 l_enable_vmi_flag                VARCHAR2(1)  := NULL;
588 l_last_billing_date              DATE         := NULL;
589 l_consigned_billing_cycle        NUMBER       := NULL;
590 l_vmi_min_qty                    NUMBER       := NULL;
591 l_vmi_max_qty                    NUMBER       := NULL;
592 l_vmi_auto_replenish_flag VARCHAR2(1)  := NULL;
593 l_vmi_replenishment_approval     VARCHAR2(30) := NULL;
594 
595 BEGIN
596   get_asl_info
597     ( x_item_id                       => x_item_id
598     , x_vendor_id                     => x_vendor_id
599     , x_vendor_site_id                => x_vendor_site_id
600     , x_using_organization_id         => x_using_organization_id
601     , x_asl_id                        => x_asl_id
602     , x_vendor_product_num            => x_vendor_product_num
603     , x_purchasing_uom                => x_purchasing_uom
604     , x_consigned_from_supplier_flag  => l_consigned_from_supplier_flag
605     , x_enable_vmi_flag               => l_enable_vmi_flag
606     , x_last_billing_date             => l_last_billing_date
607     , x_consigned_billing_cycle       => l_consigned_billing_cycle
608     , x_vmi_min_qty                   => l_vmi_min_qty
609     , x_vmi_max_qty                   => l_vmi_max_qty
610     , x_vmi_auto_replenish_flag       => l_vmi_auto_replenish_flag
611     , x_vmi_replenishment_approval    => l_vmi_replenishment_approval
612     , p_category_id                   => p_category_id --<Contract AutoSourcing FPJ>
613     );
614 END;
615 
616 
617 /*===========================================================================
618 
619   PROCEDURE NAME:       get_asl_info
620 
621   REQUIRED INPUTS:
622 
623   OPTIONAL INPUTS:
624 
625   OUTPUTS:      x_using_organization_id	        - actual organization of
626                                                   the ASL
627 		x_asl_id		        - ASL identifier
631 i                x_enable_vmi_flag               - vmi enabled flag
628 		x_vendor_product_num	        - supplier item number
629 		x_purchasing_uom	        - Purchasing Unit of Masure
630 		x_consigned_from_supplier_flag  - consigned enabled flag
632 		x_last_billing_date             - Last date when the consigned
633 		                                  consumption concurrent
634 						  program ran
635 		x_consigned_billing_cycle       - The number of days before
636 		                                  summarizing the consigned
637 						  POs received and transfer
638 						  the goods to regular stock
639 		x_vmi_min_qty                   - Min Quantity for VMI
640 		                                  replenishment
641                 x_vmi_max_qty                   - Max Quantity for VMI
642 		                                  replenishment
643 		x_vmi_auto_replenish_flag       - To allow/disallow automatic
644 		                                  replenishment function
645 		x_vmi_replenishment_approval    - ability to release
646                                                   replenishment requests
647                                                   automatically using
648 						  Collaborative Planning.
649 						  Valid values: None, Supplier
650 						  or Buyer, Buyer
651 
652   ALGORITHM:		Returns the supplier item number and purchasing
653 			UOM from the ASL entry, plus the Consigned From
654 			Supplier and VMI settings.
655 
656   NOTES    : Asl_id can also obtained from Get_All_Item_Asl procedure.
657 	     This is the same as x_asl_id but returns vendor_id also and
658 	     in an array. When any changes are made to get_asl_info
659      	     need to consider Get_All_Item_Asl procedure also.
660 
661 ===========================================================================*/
662 
663 PROCEDURE get_asl_info(
664 		x_item_id		        IN      NUMBER,
665 		x_vendor_id		        IN      NUMBER,
666 	        x_vendor_site_id	        IN      NUMBER,
667 		x_using_organization_id	        IN OUT  NOCOPY NUMBER,
668 		x_asl_id		        IN OUT  NOCOPY NUMBER,
669 		x_vendor_product_num	        IN OUT  NOCOPY VARCHAR2,
670 		x_purchasing_uom	        IN OUT  NOCOPY VARCHAR2,
671 		x_consigned_from_supplier_flag  OUT     NOCOPY VARCHAR2,
672                 x_enable_vmi_flag               OUT     NOCOPY VARCHAR2,
673 		x_last_billing_date             OUT     NOCOPY DATE,
674 		x_consigned_billing_cycle       OUT     NOCOPY NUMBER,
675 		x_vmi_min_qty                   OUT     NOCOPY NUMBER,
676                 x_vmi_max_qty                   OUT     NOCOPY NUMBER,
677 		x_vmi_auto_replenish_flag       OUT     NOCOPY VARCHAR2,
678 		x_vmi_replenishment_approval    OUT     NOCOPY VARCHAR2,
679                 p_category_id                   IN      NUMBER --<Contract AutoSourcing FPJ>
680 )
681 
682 IS
683 
684 	l_progress		VARCHAR2(3) := '010';
685 
686         --<Contract AutoSourcing FPJ>
687 	--If 'Y', look for item-based ASL; if 'N', look for category-based ASL
688 	l_item_based_asl        VARCHAR2(1):= 'Y';
689 	l_log_head   CONSTANT VARCHAR2(100):= g_log_head||'get_asl_info';
690 
691     --<Bug 3545698 mbhargav>
692     -- Separated out cursor C into two cursors L_ITEM_CSR and L_CATEGORY_CSR.
693     -- This was required for performance reasons. With this change the Optimizer
694     -- will be able to use combination index on (vendor_id, item_id) or
695     -- (vendor_id, category_id) as appropriate.
696 
697 	-- Cursor l_item_csr finds the asl entries that matches the ITEM, vendor
698 	-- and vendor site.  It gets the local entry before the global.
699 	-- It also fetches the purchasing UOM for this ASL entry.  It
700         -- fetches the UOM from the local attributes record before the
701 	-- the global.
702 
703 /* Bug # 1671405. pchintal
704 Added the table PO_ASL_STATUS_RULES_V and corresponding where condition
705 to the below cursor so that it will not fetch those asl_id's whose
706 status has a control value of PREVENT and rule is SOURCING, so that
707 the ASL with status debarred will not be picked and sourcing will happen
708 properly.
709 */
710 
711         --Note: If you make any change in this cursor then consider whether you
712         --      need to make change to cursor L_CATEGORY_CSR as well
713         CURSOR L_ITEM_CSR is
714     	  SELECT   pasl.asl_id,
715                    paa.using_organization_id,
716 		   pasl.primary_vendor_item,
717 	           paa.purchasing_unit_of_measure,
718 		   paa.consigned_from_supplier_flag,
719 		   paa.enable_vmi_flag,
720 		   paa.last_billing_date,
721 		   paa.consigned_billing_cycle,
722 		   paa.vmi_min_qty,
723                    paa.vmi_max_qty,
724 		   paa.enable_vmi_auto_replenish_flag,
725 		   paa.vmi_replenishment_approval
726     	  FROM     po_approved_supplier_lis_val_v pasl,
727 		   po_asl_attributes paa,
728            po_asl_status_rules_v pasr
729     	  WHERE    pasl.item_id = x_item_id  -- <Contract AutoSourcing FPJ>
730     	  AND	   pasl.vendor_id = x_vendor_id
731     	  AND	   nvl(pasl.vendor_site_id, -1) = nvl(x_vendor_site_id, -1)
732     	  AND	   pasl.using_organization_id IN (-1, x_using_organization_id)
733 	  AND	   pasl.asl_id = paa.asl_id
734           AND      pasr.business_rule like '2_SOURCING'
735           AND      pasr.allow_action_flag like 'Y'
736           AND      pasr.status_id = pasl.asl_status_id
737 	  AND	   paa.using_organization_id =
738 			(SELECT  max(paa2.using_organization_id)
742 	  ORDER BY pasl.using_organization_id DESC;
739 			 FROM	 po_asl_attributes paa2
740 			 WHERE   paa2.asl_id = pasl.asl_id
741                          AND     paa2.using_organization_id IN (-1, x_using_organization_id))
743 
744 	-- Cursor l_category_csr finds the asl entries that matches the CATEGORY, vendor
745 	-- and vendor site.  It gets the local entry before the global.
746 	-- It also fetches the purchasing UOM for this ASL entry.  It
747         -- fetches the UOM from the local attributes record before the
748 	-- the global.
749 
750         --Note: If you make any change in this cursor then consider whether you
751         --      need to make change to cursor L_ITEM_CSR as well
752         CURSOR L_CATEGORY_CSR is
753     	  SELECT   pasl.asl_id,
754                    paa.using_organization_id,
755 		   pasl.primary_vendor_item,
756 	           paa.purchasing_unit_of_measure,
757 		   paa.consigned_from_supplier_flag,
758 		   paa.enable_vmi_flag,
759 		   paa.last_billing_date,
760 		   paa.consigned_billing_cycle,
761 		   paa.vmi_min_qty,
762                    paa.vmi_max_qty,
763 		   paa.enable_vmi_auto_replenish_flag,
764 		   paa.vmi_replenishment_approval
765     	  FROM     po_approved_supplier_lis_val_v pasl,
766 		   po_asl_attributes paa,
767                    po_asl_status_rules_v pasr
768     	  WHERE    pasl.category_id = p_category_id  -- <Contract AutoSourcing FPJ>
769     	  AND	   pasl.vendor_id = x_vendor_id
770     	  AND	   nvl(pasl.vendor_site_id, -1) = nvl(x_vendor_site_id, -1)
771     	  AND	   pasl.using_organization_id IN (-1, x_using_organization_id)
772 	  AND	   pasl.asl_id = paa.asl_id
773           AND      pasr.business_rule like '2_SOURCING'
774           AND      pasr.allow_action_flag like 'Y'
775           AND      pasr.status_id = pasl.asl_status_id
776 	  AND	   paa.using_organization_id =
777 			(SELECT  max(paa2.using_organization_id)
778 			 FROM	 po_asl_attributes paa2
779 			 WHERE   paa2.asl_id = pasl.asl_id
780                          AND     paa2.using_organization_id IN (-1, x_using_organization_id))
781 	  ORDER BY pasl.using_organization_id DESC;
782 
783 BEGIN
784 
785   --<Contract AutoSourcing FPJ Start>
786   -- Get the item-based ASL if item_id exists
787   IF g_debug_stmt THEN
788      PO_DEBUG.debug_stmt(p_log_head => l_log_head,
789                          p_token    => l_progress,
790                          p_message  => 'Look for item-based ASL first...');
791   END IF;
792 
793   IF x_item_id IS NOT NULL THEN
794      OPEN L_ITEM_CSR; --<Bug 3545698>
795      FETCH L_ITEM_CSR into x_asl_id,
796                   x_using_organization_id,
797 		  x_vendor_product_num,
798 		  x_purchasing_uom,
799 		  x_consigned_from_supplier_flag,
800 		  x_enable_vmi_flag,
801 		  x_last_billing_date,
802 		  x_consigned_billing_cycle,
803                   x_vmi_min_qty,
804                   x_vmi_max_qty,
805 	  	  x_vmi_auto_replenish_flag,
806 	 	  x_vmi_replenishment_approval;
807 
808      CLOSE L_ITEM_CSR;
809   END IF;
810 
811   l_progress := '020';
812   IF g_debug_stmt THEN
813      PO_DEBUG.debug_stmt(p_log_head => l_log_head,
814                          p_token    => l_progress,
815                          p_message  => 'Item-based asl id: '||x_asl_id);
816   END IF;
817 
818   IF x_asl_id IS NOT NULL THEN
819      return;
820   ELSIF (x_asl_id IS NULL) OR (x_item_id IS NULL) THEN
821      l_item_based_asl := 'N';
822 
823      l_progress := '025';
824      IF g_debug_stmt THEN
825         PO_DEBUG.debug_stmt(p_log_head => l_log_head,
826                             p_token    => l_progress,
827                             p_message  => 'Look for category-based asl');
828      END IF;
829 
830      OPEN L_CATEGORY_CSR;  --<Bug 3545698>
831      FETCH L_CATEGORY_CSR into x_asl_id,
832                   x_using_organization_id,
833 		  x_vendor_product_num,
834 		  x_purchasing_uom,
835 		  x_consigned_from_supplier_flag,
836 		  x_enable_vmi_flag,
837 		  x_last_billing_date,
838 		  x_consigned_billing_cycle,
839                   x_vmi_min_qty,
840                   x_vmi_max_qty,
841 	  	  x_vmi_auto_replenish_flag,
842 	 	  x_vmi_replenishment_approval;
843 
844      CLOSE L_CATEGORY_CSR;
845   END IF;
846 
847   l_progress := '030';
848   IF g_debug_stmt THEN
849      PO_DEBUG.debug_stmt(p_log_head => l_log_head,
850                          p_token    => l_progress,
851                          p_message  => 'Category-based asl_id: '||x_asl_id);
852   END IF;
853   --<Contract AutoSourcing FPJ End>
854 
855 END;
856 
857 /* CONSIGNED FPI END */
858 
859 /* VMI FPH START */
860 /*===========================================================================
861 
862   PROCEDURE NAME:       vmi_enabled
863 
864   REQUIRED INPUTS:
865                         x_item_id                 valid item_id
866                         x_vendor_id               valid vendor_id
867                         x_vendor_site_id          valid vendor_site_id
868                         x_using_organization_id   valid using_organization_id
869 
870   OPTIONAL INPUTS:
871 
872   OUTPUTS:
873                         'Y' if the ASL entry corresponding to the required input
874                         is VMI enabled.
875 
879   ALGORITHM:
876                         'N' if not VMI enabled, no ASL entry exists, or the
877                         input data is incorrect
878 
880                         calls get_asl_info procedure
881 		        to determine the correct ASL entry. The enable_vmi_flag
882                         then is queried for that ASL entry.
883 
884 ===========================================================================*/
885 
886 FUNCTION  vmi_enabled
887   ( x_item_id                  IN   NUMBER
888   , x_vendor_id                IN   NUMBER
889   , x_vendor_site_id           IN   NUMBER
890   , x_using_organization_id    IN   NUMBER
891   )
892 RETURN VARCHAR2
893 IS
894 
895   l_asl_id                  NUMBER;
896   l_using_organization_id   NUMBER;
897   l_vendor_product_num      VARCHAR2(25);
898   l_purchasing_uom          VARCHAR2(25);
899   l_enable_vmi_flag         VARCHAR2(1);
900 
901 BEGIN
902 
903   l_using_organization_id  := x_using_organization_id;
904 
905 
906   BEGIN
907     get_asl_info
908       ( x_item_id
909       , x_vendor_id
910       , x_vendor_site_id
911       , l_using_organization_id
912       , l_asl_id
913       , l_vendor_product_num
914       , l_purchasing_uom
915       );
916 
917     SELECT
918       enable_vmi_flag
919     INTO
920       l_enable_vmi_flag
921     FROM
922       po_asl_attributes  asl
923     WHERE
924         asl.asl_id                 =  l_asl_id
925     AND asl.using_organization_id  =  l_using_organization_id
926     ;
927 
928   EXCEPTION
929     WHEN NO_DATA_FOUND THEN
930       NULL;
931     WHEN OTHERS THEN
932       NULL;
933   END;
934 
935 
936   IF  l_enable_vmi_flag  =  'Y'  THEN
937     RETURN 'Y';
938   ELSE
939     RETURN 'N';
940   END IF;
941 
942 END vmi_enabled;
943 /* VMI FPH END */
944 
945 
946 
947 
948 /*===========================================================================
949 
950   PROCEDURE NAME:       document_sourcing
951 
952   REQUIRED INPUTS:	item_id
953 			vendor_id
954 			destination_doc_type  ('PO','REQ','STANDARD PO','REQ_NONCATALOG')
955 
956   OPTIONAL INPUTS:	organization_id
957 			currency_code
958 			item_rev
959 			vendor_site_id (if provided then do not do vendor site sourcing)
960 			autosource_date
961             p_cendor_site_sourcing_flag(Should be Y to do vendor site sourcing)
962             p_vendor_site_code (Used in vendor site sourcing)
963                         p_category_id
964 
965   OUTPUTS:  vendor_site_id
966 			document_header_id
967 			document_type_code
968 			document_line_num
969 			document_line_id
970 			vendor_contact_id
971 			vendor_product_num
972 			buyer_id
973 
974   ALGORITHM:		This procedure returns sourcing information from a
975 			source document as follows:
976 
977   			o If destination_document_type is 'PO', source only
978 			  from quotations.  If destination document type is 'REQ',
979 			  source from quotations and blankets.
980 
981 		   	o Get sourcing info from blanket only if document is
982 	  		  approved and not finally closed or canceled
983 
984 			o Get sourcing info from quotations only if
985 			  document does not require approval or has been
986 			  approved.
987 
988         	o If currency_code, item_revision have null values,
989 			  any value would apply.
990 
991 			o Fetch the local asl entries that matches the item, vendor
992 			  and vendor site.  Fetch the highest ranked document in
993 			  in ASL entry that matches the currency code, item
994 			  revision, and the criteria stated above.  If no such
995 			  document exists in the local entry, check the global entry.
996               --<Shared Proc FPJ>
997    			o If vendor site is not specified as an input and vendor_site_sourcing_flag
998               is Y then this procedure will try to determine vendor_site_id using the
999               vendor_site_code provided. This can come back with Blankets (Local
1000               and Global), Quotations within same operating unit. It can also
1001               return Global Agreements from another operating unti.
1002               It uses ASLs and Global Agreement to do vendor site sourcing
1003 
1004             o Depending on the profile option 'PO: Automatic Document Sourcing',
1005               this procedure calls get_document_from_asl OR get_latest_document.
1006 
1007    <PKGCOMP R12 Start>
1008    * Modifying the parameter x_asl_id from IN to IN OUT parameter in order to
1009      communicate the ASL_ID back to PO_AUTOSOURCE_SV.autosourcing or
1010      PO_AUTOSOURCE_SV.reqimport_sourcing.
1011 
1012    * We need not make any changes to the existing code of this procedure,
1013      as we just make calls to Get_document_from_asl or Get_latest_document
1014      procedure depending on the value of 'PO: Automatic Document Sourcing'
1015      profile option.
1016    <PKGCOMP R12 End>
1017 ===========================================================================*/
1018 PROCEDURE document_sourcing(
1019 	x_item_id		IN 	NUMBER,
1020 	x_vendor_id		IN 	NUMBER,
1021 	x_destination_doc_type	IN	VARCHAR2,
1022 	x_organization_id	IN	NUMBER,
1023 	x_currency_code		IN	VARCHAR2,
1024         x_item_rev		IN	VARCHAR2,
1028 	x_document_type_code	IN OUT NOCOPY  VARCHAR2,
1025 	x_autosource_date	IN	DATE,
1026 	x_vendor_site_id	IN OUT NOCOPY  NUMBER,
1027 	x_document_header_id	IN OUT NOCOPY  NUMBER,
1029 	x_document_line_num	IN OUT NOCOPY  NUMBER,
1030 	x_document_line_id	IN OUT	NOCOPY NUMBER,
1031 	x_vendor_contact_id	IN OUT NOCOPY  NUMBER,
1032 	x_vendor_product_num	IN OUT	NOCOPY VARCHAR2,
1033 	x_buyer_id		IN OUT NOCOPY  NUMBER,
1034 	x_purchasing_uom	IN OUT NOCOPY  VARCHAR2,
1035 	x_asl_id                IN OUT NOCOPY NUMBER, --<PKGCOMP R12> --cto FPH
1036         x_multi_org             IN      VARCHAR2 default 'N', --cto FPH
1037         p_vendor_site_sourcing_flag  IN VARCHAR2 default 'N', --<Shared Proc FPJ>
1038  	p_vendor_site_code   	 IN  	VARCHAR2 default NULL, --<Shared Proc FPJ>
1039         p_category_id            IN     NUMBER --<Contract AutoSourcing FPJ>
1040         --<R12 STYLES PHASE II START>
1041        ,p_purchase_basis   IN VARCHAR2 DEFAULT NULL,
1042         p_line_type_id     IN VARCHAR2 DEFAULT NULL,
1043         p_destination_type IN VARCHAR2 DEFAULT NULL,
1044         p_style_id         IN NUMBER   DEFAULT NULL
1045         --<R12 STYLES PHASE II END>
1046 ) IS
1047 	x_local_asl_id		NUMBER; --cto FPH
1048 	x_org_id		NUMBER; --cto FPH
1049 	x_using_organization_id NUMBER;
1050 	l_progress		VARCHAR2(3) := '000';
1051 	x_sourcing_date		DATE := trunc(nvl(x_autosource_date, sysdate));
1052     x_auto_source_doc       VARCHAR2(1);
1053     x_asl_purchasing_uom    VARCHAR2(25);
1054     x_item_rev_control      NUMBER := 1;
1055     x_source_doc_not_found  VARCHAR2(1) := 'N';  -- Bug 2373004
1056     x_ga_flag               VARCHAR2(1) := 'N';    -- FPI GA
1057     x_owning_org_id         NUMBER;                -- FPI GA
1058     x_valid_flag            VARCHAR2(1) := 'N';
1059     --<Shared Proc FPJ START>
1060     x_vendor_contact_name  	PO_VENDOR_CONTACTS.last_name%TYPE;
1061     l_sequence_number  	PO_ASL_DOCUMENTS.sequence_num%TYPE;
1062     l_vendor_site_sourcing_flag VARCHAR2(1) := p_vendor_site_sourcing_flag;
1063     l_log_head     CONSTANT VARCHAR2(100) := g_log_head||'document_sourcing';
1064     --<Shared Proc FPJ END>
1065 
1066     --<Contract AutoSourcing FPJ Start >
1067     -- In general, contracts can be sourced too; if the destination doc is requisition,
1068     -- user-defined settings in document types form determines whether or not to
1069     -- source to contracts
1070     l_return_contract	VARCHAR2(1) := 'Y';
1071     l_return_status	VARCHAR2(1);
1072     --<Contract AutoSourcing FPJ End >
1073 
1074     l_vendor_contact_name varchar2(240); --<Bug 3692519>
1075 
1076 BEGIN
1077     l_progress := '010';
1078 
1079     IF g_debug_stmt THEN
1080        PO_DEBUG.debug_begin(l_log_head);
1081        PO_DEBUG.debug_var(l_log_head,l_progress,'x_item_id', x_item_id);
1082        PO_DEBUG.debug_var(l_log_head,l_progress,'x_vendor_id', x_vendor_id);
1083        PO_DEBUG.debug_var(l_log_head,l_progress,'x_destination_doc_type', x_destination_doc_type);
1084        PO_DEBUG.debug_var(l_log_head,l_progress,'x_organization_id', x_organization_id);
1085        PO_DEBUG.debug_var(l_log_head,l_progress,'x_currency_code', x_currency_code);
1086        PO_DEBUG.debug_var(l_log_head,l_progress,'x_item_rev', x_item_rev);
1087        PO_DEBUG.debug_var(l_log_head,l_progress,'x_autosource_date', x_autosource_date);
1088        PO_DEBUG.debug_var(l_log_head,l_progress,'x_vendor_site_id', x_vendor_site_id);
1089 
1090        PO_DEBUG.debug_var(l_log_head,l_progress,'x_document_header_id', x_document_header_id);
1091        PO_DEBUG.debug_var(l_log_head,l_progress,'x_document_type_code', x_document_type_code);
1092        PO_DEBUG.debug_var(l_log_head,l_progress,'x_document_line_num', x_document_line_num);
1093        PO_DEBUG.debug_var(l_log_head,l_progress,'x_document_line_id', x_document_line_id);
1094        PO_DEBUG.debug_var(l_log_head,l_progress,'x_vendor_contact_id', x_vendor_contact_id);
1095        PO_DEBUG.debug_var(l_log_head,l_progress,'x_vendor_product_num', x_vendor_product_num);
1096        PO_DEBUG.debug_var(l_log_head,l_progress,'x_buyer_id', x_buyer_id);
1097        PO_DEBUG.debug_var(l_log_head,l_progress,'x_purchasing_uom', x_purchasing_uom);
1098 
1099        PO_DEBUG.debug_var(l_log_head,l_progress,'x_asl_id', x_asl_id);
1100        PO_DEBUG.debug_var(l_log_head,l_progress,'x_multi_org', x_multi_org);
1101        PO_DEBUG.debug_var(l_log_head,l_progress,'p_vendor_site_sourcing_flag', p_vendor_site_sourcing_flag);
1102        PO_DEBUG.debug_var(l_log_head,l_progress,'p_vendor_site_sourcing_flag', p_vendor_site_sourcing_flag);
1103        PO_DEBUG.debug_var(l_log_head,l_progress,'p_vendor_site_code', p_vendor_site_code);
1104        PO_DEBUG.debug_var(l_log_head,l_progress,'p_category_id', p_category_id);
1105        PO_DEBUG.debug_var(l_log_head,l_progress,'p_purchase_basis', p_purchase_basis);
1106        PO_DEBUG.debug_var(l_log_head,l_progress,'p_line_type_id', p_line_type_id);
1107        PO_DEBUG.debug_var(l_log_head,l_progress,'p_destination_type', p_destination_type);
1108        PO_DEBUG.debug_var(l_log_head,l_progress,'p_style_id', p_style_id);
1109     END IF;
1110 
1111 
1112 
1113     -- Check that x_item_id and x_vendor_id have values.
1114     --IF (x_item_id IS NULL OR x_vendor_id IS NULL) THEN
1115 
1116     -- <Contract AutoSourcing FPJ >
1117     -- Deleted the x_item_id IS NULL check. Enable sourcing without item_id if category_id exists;
1118     -- Also check if vendor_id has value
1119     IF (x_item_id IS NULL
1120           AND (p_category_id IS NULL OR x_destination_doc_type NOT IN ('REQ',
1121 								    'REQ_NONCATALOG')))
1122        OR (x_vendor_id IS NULL) THEN
1123 	return;
1124 
1125     END IF;
1126 
1127 	/* Cto Changes FPH start */
1128         if (x_multi_org = 'Y') then
1132 		into x_org_id
1129         	x_org_id := null;
1130 	else
1131 		select org_id
1133 		from financials_system_parameters;
1134 	end if;
1135         /* Cto Changes FPH end */
1136 
1137     IF x_organization_id IS NULL THEN
1138 
1139         -- Get organization_id from financials_system_parameters.
1140 
1141         SELECT   inventory_organization_id
1142         INTO     x_using_organization_id
1143         FROM     financials_system_parameters;
1144 
1145     ELSE
1146 	x_using_organization_id := x_organization_id;
1147     END IF;
1148 
1149     l_progress := '020';
1150 
1151    /* bug 2315931 :   we now call autosource even if revision is null. null revision can
1152      be matched to a source document with a revision . For this - get the revision control
1153      code from the item table and pass it to the cursors C1,C_AUTO_SOURCE_DOC_WITH_UOM and
1154      C_AUTO_SOURCE_DOC_NO_UOM. These cursors will now tey to match the item revisions on the
1155      req line and the source document if both have values. If the item revision on the req
1156      line is not null and the item is not revision controlled the we match this line to the
1157      source doc line irrespective of its revision */
1158    begin
1159 
1160      SELECT   msi.revision_qty_control_code
1161      INTO     x_item_rev_control
1162      FROM     mtl_system_items msi
1163      WHERE    msi.inventory_item_id = x_item_id
1164      AND      msi.organization_id = x_using_organization_id;
1165   exception
1166    when no_data_found then
1167      x_item_rev_control := 1;
1168   end;
1169 
1170   l_progress := '030';
1171   IF l_vendor_site_sourcing_flag = 'Y' THEN
1172 	--If requesting OU has encumbrance enabled or destination inv org is OPM enabled
1173 	--then do not cross OU boundaries
1174     IF (PO_CORE_S.is_encumbrance_on
1175                       (p_doc_type => 'ANY',
1176                        p_org_id   => x_org_id))
1177        -- INVCONV START remove the opm restriction
1178        -- OR  PO_GML_DB_COMMON.check_process_org(x_using_organization_id) = 'Y')
1179        -- INVCONV END
1180     THEN
1181         l_progress := '040';
1182 	    l_vendor_site_sourcing_flag := 'N';
1183 	    --Do local document sourcing
1184 	    IF p_vendor_site_code is NOT NULL
1185                AND x_vendor_site_id is NULL THEN
1186 
1187                IF g_debug_stmt THEN
1188                  PO_DEBUG.debug_stmt(l_log_head,l_progress,'Doing Local Doc Sourcing');
1189                END IF;
1190 
1191               BEGIN
1192                SELECT vendor_site_id
1193                INTO x_vendor_site_id
1194                FROM po_vendor_sites_all pvs,
1195                     org_organization_definitions oog
1196                WHERE pvs.vendor_site_code = p_vendor_site_code
1197                AND   pvs.vendor_id = x_vendor_id --<Bug 3634422>
1198                AND   nvl(pvs.org_id,nvl(oog.operating_unit,-1)) =
1199                                                       nvl(oog.operating_unit,-1)
1200                AND  oog.organization_id = x_using_organization_id;
1201               EXCEPTION
1202                WHEN OTHERS THEN
1203                    x_vendor_site_id := NULL;
1204               END;
1205 	        END IF; --site code NULL check
1206     END IF; --encumbrance check
1207   END IF; --source flag check
1208 
1209   --<Contract AutoSourcing FPJ Start>
1210   -- Find out if contract agreements should be sourced to Requisition lines
1211   -- Currently, should_return_contract only supports Purchase Requisitions
1212   l_progress := '045';
1213   IF x_destination_doc_type IN ('REQ','REQ_NONCATALOG') THEN
1214      should_return_contract (
1215           p_destination_doc_type  => x_destination_doc_type,
1216           p_document_type_code	  => 'REQUISITION',
1217           p_document_subtype      => 'PURCHASE',
1218           x_return_contract       => l_return_contract,
1219           x_return_status         => l_return_status
1220      );
1221      IF l_return_status <> FND_API.g_ret_sts_success THEN
1222 	RAISE FND_API.g_exc_unexpected_error;
1223      END IF;
1224   END IF;
1225 
1226   IF g_debug_stmt THEN
1227      PO_DEBUG.debug_stmt(p_log_head => l_log_head,
1228                          p_token    => l_progress,
1229                          p_message  => 'Return Contract? '||l_return_contract);
1230   END IF;
1231   --<Contract AutoSourcing FPJ End>
1232 
1233   l_progress := '050';
1234     --Do the check for the profile option 'PO: Automatic Document Sourcing'.
1235     --If set to 'Y' then get the latest document. If set to 'N' then get it from ASL.
1236     fnd_profile.get('PO_AUTO_SOURCE_DOC', x_auto_source_doc);
1237     IF nvl(x_auto_source_doc, 'N') = 'N' THEN
1238           l_progress := '060';
1239           IF g_debug_stmt THEN
1240             PO_DEBUG.debug_stmt(l_log_head,l_progress,'Looking at ASLs for Sourcing');
1241           END IF;
1242 
1243           Get_document_from_asl(
1244                 x_item_id		            =>x_item_id,
1245                 x_vendor_id		            =>x_vendor_id,
1246                 x_destination_doc_type	    =>x_destination_doc_type,
1247                 x_currency_code 	        =>x_currency_code,
1248                 x_item_rev		            =>x_item_rev,
1249                 x_autosource_date 	        =>x_autosource_date,
1250                 x_vendor_site_id 	        =>x_vendor_site_id,
1254                 x_document_line_id	        =>x_document_line_id,
1251                 x_document_header_id	    =>x_document_header_id,
1252                 x_document_type_code 	    =>x_document_type_code,
1253                 x_document_line_num	        =>x_document_line_num,
1255                 x_vendor_contact_id	        =>x_vendor_contact_id,
1256                 x_vendor_product_num 	    =>x_vendor_product_num,
1257                 x_buyer_id 		            =>x_buyer_id,
1258                 x_purchasing_uom	        =>x_purchasing_uom,
1259                 x_asl_id		            =>x_asl_id,
1260                 x_multi_org		            =>x_multi_org,
1261                 p_vendor_site_sourcing_flag	=>l_vendor_site_sourcing_flag,
1262                 p_vendor_site_code	        =>p_vendor_site_code,
1263                 p_org_id		            =>x_org_id,
1264                 p_item_rev_control	        =>x_item_rev_control,
1265                 p_using_organization_id     =>x_using_organization_id,
1266                 p_category_id	          	=> p_category_id, --<Contract AutoSourcing FPJ>
1267 	        p_return_contract		=> l_return_contract --<Contract AutoSourcing FPJ>
1268                 --<R12 STYLES PHASE II START>
1269                ,p_purchase_basis   => p_purchase_basis,
1270                 p_line_type_id     => p_line_type_id,
1271                 p_destination_type => p_destination_type,
1272                 p_style_id         => p_style_id
1273                 --<R12 STYLES PHASE II END>
1274             );
1275             l_progress := '070';
1276      ELSE
1277            l_progress := '080';
1278            IF g_debug_stmt THEN
1279             PO_DEBUG.debug_stmt(l_log_head,l_progress,'Looking at Latest Documents for Sourcing');
1280            END IF;
1281 
1282            Get_latest_document(
1283                 x_item_id		            =>x_item_id,
1284                 x_vendor_id		            =>x_vendor_id,
1285                 x_destination_doc_type	    =>x_destination_doc_type,
1286                 x_currency_code 	        =>x_currency_code,
1287                 x_item_rev		            =>x_item_rev,
1288                 x_autosource_date 	        =>x_autosource_date,
1289                 x_vendor_site_id 	        =>x_vendor_site_id,
1290                 x_document_header_id	    =>x_document_header_id,
1291                 x_document_type_code 	    =>x_document_type_code,
1292                 x_document_line_num	        =>x_document_line_num,
1293                 x_document_line_id	        =>x_document_line_id,
1294                 x_vendor_contact_id	        =>x_vendor_contact_id,
1295                 x_vendor_product_num 	    =>x_vendor_product_num,
1296                 x_buyer_id 		            =>x_buyer_id,
1297                 x_purchasing_uom	        =>x_purchasing_uom,
1298                 x_asl_id		            =>x_asl_id,
1299                 x_multi_org		            =>x_multi_org,
1300                 p_vendor_site_sourcing_flag	=>l_vendor_site_sourcing_flag,
1301                 p_vendor_site_code	        =>p_vendor_site_code,
1302                 p_org_id		            =>x_org_id,
1303                 p_item_rev_control	        =>x_item_rev_control,
1304                 p_using_organization_id     =>x_using_organization_id,
1305                 p_category_id	                => p_category_id, --<Contract AutoSourcing FPJ>
1306 	        p_return_contract		=> l_return_contract --<Contract AutoSourcing FPJ>
1307                 --<R12 STYLES PHASE II START>
1308                ,p_purchase_basis   => p_purchase_basis,
1309                 p_line_type_id     => p_line_type_id,
1310                 p_destination_type => p_destination_type,
1311                 p_style_id         => p_style_id
1312                 --<R12 STYLES PHASE II END>
1313           );
1314            l_progress := '090';
1315       END IF;
1316 l_progress := '100';
1317 
1318       --<Bug 3564169, 3692519 mbhargav START>
1319       --Retain the vendor contact from Source Doc as long as
1320       --its valid otherwise redefault based on site
1321       IF x_vendor_site_id is NOT NULL THEN
1322            --If there is no vendor contact or contact is not valid
1323            --Then get the contact from site
1324            IF (x_vendor_contact_id is NULL OR
1325                      (NOT PO_VENDOR_CONTACTS_SV.val_vendor_contact(
1326                            p_vendor_contact_id => x_vendor_contact_id,
1327                            p_vendor_site_id => x_vendor_site_id))) THEN
1328 
1329                  PO_VENDOR_CONTACTS_SV.get_vendor_contact(
1330                         x_vendor_site_id => x_vendor_site_id,
1331                         x_vendor_contact_id => x_vendor_contact_id,
1332                         x_vendor_contact_name => l_vendor_contact_name);
1333 
1334            END IF;
1335       END IF;
1336       --<Bug 3564169, 3692519 mbhargav END>
1337 l_progress := '110';
1338 
1339 IF g_debug_stmt THEN
1340        PO_DEBUG.debug_end(l_log_head);
1341 END IF;
1342 
1343 EXCEPTION
1344     WHEN OTHERS THEN
1345          IF g_debug_unexp THEN
1346             PO_DEBUG.debug_exc(l_log_head,l_progress);
1347          END IF;
1348 
1349         PO_MESSAGE_S.SQL_ERROR('Document_sourcing', l_progress, sqlcode);
1350 END document_sourcing;
1351 
1352 --<Shared Proc FPJ START>
1353 -------------------------------------------------------------------------------
1354 --Start of Comments
1355 --Name: GET_DOCUMENT_FROM_ASL
1356 --Pre-reqs:
1357 --  Assumes that ASL will be used for Document Sourcing
1358 --Modifies:
1359 --  None.
1360 --Locks:
1361 --  None.
1365 --Parameters:
1362 --Function:
1363 --  This procedure first identified an ASL to use and then gets the
1364 --  document on ASL_DOCUMENTS which is suitable for use.
1366 --IN:
1367 --x_item_id
1368 --  item_id to be matched for ASL
1369 --x_vendor_id
1370 --  vendor_id to be matched for ASL
1371 --x_destination_doc_type
1372 --  The form from which the call to the API is made. Vaild values are
1373 --  'PO', 'STANDARD PO', 'REQ', 'REQ_NONCATALOG' and NULL --<Contract AutoSourcing FPJ>
1374 --x_curreny_code
1375 --  Currency code to be compared to get matching document
1376 --x_item_rev
1377 --  Item revision that needs to be compared to.
1378 --p_autosourcing_date
1379 --  Date to be used for Sourcing date check
1380 --p_item_rev_control
1381 --  This parameter tells whether item revision control is ON for given p_item_id
1382 --p_vendor_site_sourcing_flag
1383 --  Parameter which tells whether site sourcing is done or not
1384 --p_vendor_site_code
1385 --  If vendor_site_sourcing_flag = 'Y' then this parameter contains the
1386 --  site code for which the API needs to find appropriate site_id
1387 --p_org_id
1388 --  Operating Unit id
1389 --x_multi_org
1390 --  Parameter used by CTO
1391 --IN OUT:
1392 --x_vendor_product_num
1393 --  Supplier product_num associated with given Item as defined on ASL
1394 --x_purchasing_uom
1395 --  Purchasing UOM provided by Supplier on ASL
1396 --x_vendor_site_id
1397 --  This parameter is used as IN OUT parameter. For callers who do not want
1398 --  to do vendor site sourcing will pass in a value and set vendor_site_sourcing_flag
1399 --  = 'N'. When vendor_site_sourcing_flag = 'Y' then this parameter would contain
1400 --  the site_id obtained by vendor site sourcing
1401 --x_document_header_id
1402 --  The unique identifier of the document returned
1403 --x_document_type_code
1404 --  Valid values 'BLANKET'/'QUOTATION'
1405 --x_document_line_num
1406 --  The line number of the document returned
1407 --x_document_line_id
1408 --  The unique identifier of the document line returned
1409 --x_vendor_contact_id
1410 --  If there is a unique contact id present then this returns that value
1411 --x_buyer_id
1412 --  The buyer mentioned on the document returned
1413 --x_asl_id
1414 --  Parameter used by CTO and PKGCOMP R12 to pass asl_id so that no ASL sourcing is done
1415 --Testing:
1416 --  None
1417 --End of Comments
1418 -------------------------------------------------------------------------------
1419 --<PKGCOMP R12 Start>
1420 --* Modifying the parameter x_asl_id from IN to IN OUT parameter in order to
1421 --  communicate the ASL_ID back to PO_AUTOSOURCE_SV.document_sourcing.
1422 
1423 --* In the existing code of the procedure, we make a local copy of x_asl_id
1424 --  (x_local_asl_id) and use it.
1425 
1426 --* In order to minimize the impact of the type change of x_asl_id, we will
1427 --  initialize the x_asl_id to value of x_local_asl_id just before exiting
1428 --  the Get_document_from_asl procedure.
1429 --<PKGCOMP R12 End>
1430 
1431 Procedure get_document_from_asl(
1432                 x_item_id             	  IN    NUMBER,
1433                 x_vendor_id           	  IN	NUMBER,
1434                 x_destination_doc_type 	  IN  	VARCHAR2,
1435                 x_currency_code           IN    VARCHAR2,
1436                 x_item_rev                IN	VARCHAR2,
1437                 x_autosource_date         IN    DATE,
1438                 x_vendor_site_id          IN OUT NOCOPY NUMBER,
1439                 x_document_header_id      IN OUT NOCOPY NUMBER,
1440                 x_document_type_code      IN OUT NOCOPY VARCHAR2,
1441                 x_document_line_num       IN OUT NOCOPY NUMBER,
1442                 x_document_line_id        IN OUT NOCOPY NUMBER,
1443                 x_vendor_contact_id       IN OUT NOCOPY NUMBER,
1444                 x_vendor_product_num      IN OUT NOCOPY VARCHAR2,
1445                 x_buyer_id                IN OUT NOCOPY NUMBER,
1446                 x_purchasing_uom          IN OUT NOCOPY VARCHAR2,
1447                 x_asl_id                  IN OUT NOCOPY NUMBER,--<PKGCOMP R12>
1448                 x_multi_org        	  IN    VARCHAR2,
1449 	        p_vendor_site_sourcing_flag  IN VARCHAR2,
1450  	        p_vendor_site_code   	  IN  	VARCHAR2,
1451                 p_org_id                  IN    NUMBER,
1452                 p_item_rev_control        IN    NUMBER,
1453                 p_using_organization_id   IN    NUMBER,
1454                 p_category_id		  IN    NUMBER,  --<Contract AutoSourcing FPJ>
1455 		p_return_contract	  IN	VARCHAR2 --<Contract AutoSourcing FPJ>
1456                 --<R12 STYLES PHASE II START>
1457                ,p_purchase_basis   IN VARCHAR2 DEFAULT NULL,
1458                 p_line_type_id     IN VARCHAR2 DEFAULT NULL,
1459                 p_destination_type IN VARCHAR2 DEFAULT NULL,
1460                 p_style_id         IN NUMBER DEFAULT NULL
1461                 --<R12 STYLES PHASE II END>
1462 ) IS
1463     x_local_asl_id          	NUMBER; --cto FPH
1464     l_progress              	VARCHAR2(3) := '000';
1465     x_sourcing_date         	DATE := trunc(nvl(x_autosource_date, sysdate));
1466     x_auto_source_doc       	VARCHAR2(1);
1467     x_asl_purchasing_uom    	VARCHAR2(25);
1468     x_source_doc_not_found  	VARCHAR2(1) := 'N';  -- Bug 2373004
1469     l_sequence_number  		PO_ASL_DOCUMENTS.sequence_num%TYPE; --<Shared Proc FPJ>
1470     x_consigned_from_supplier_flag 	VARCHAR2(1);
1471     x_enable_vmi_flag 		    VARCHAR2(1);
1472     x_return_status			    VARCHAR2(1); --<Shared Proc FPJ>
1476     l_log_head     CONSTANT VARCHAR2(100) := g_log_head||'get_document_from_asl';
1473     l_global_agreement_flag     PO_HEADERS_ALL.global_agreement_flag%type;
1474     l_document_org_id           PO_HEADERS_ALL.org_id%TYPE;
1475     l_using_organization_id     NUMBER;
1477 
1478     -- Bug 3361128: this parameter stores the UOM on the source doc
1479     l_source_doc_purchasing_uom PO_LINES_ALL.unit_meas_lookup_code%TYPE;
1480 
1481     l_item_based_asl		VARCHAR2(1):= 'Y'; --<Contract AutoSourcing FPJ>
1482     l_item_id			NUMBER; --<Contract AutoSourcing FPJ>
1483     l_vendor_contact_name      PO_VENDOR_CONTACTS.last_name%TYPE; --Bug 3545698
1484     l_noncat_item BOOLEAN := FALSE; /* Bug#4263138 */
1485 
1486 
1487     --<R12 STYLES PHASE II START>
1488     l_eligible_doc_flag Boolean;
1489     l_return_status     VARCHAR2(1);
1490     l_msg_count         NUMBER;
1491     l_msg_data          VARCHAR2(2000);
1492     --<R12 STYLES PHASE II END>
1493 
1494     -- Cursor L_GET_DOCS_ON_ASL_CSR gets the documents in the asl entry that
1495     -- matches the currency code, item revision.
1496     -- If destination_doc_type = 'PO', it selects only from quotations.
1497     -- If destination_doc_type = 'REQ', it selects from both
1498     -- quotations and blankets.
1499 
1500   --Changed the name of cursor from C1 to L_GET_DOCS_ON_ASL_CSR
1501   --Changed the signature to take p_sequence_number as input parameter.
1502   --This parameter is used for specifying the sequence number of
1503   -- the document to look for on ASL documents
1504    /*Bug6982267    The end date of quotation lines were not considered while sourcing a document for a PO line
1505                    and when the source document was a quotation. Added code to consider the end date of
1506 		   quotation line*/
1507 
1508   CURSOR L_GET_DOCS_ON_ASL_CSR(
1509  		p_sequence_number 	IN 	NUMBER) is
1510      SELECT   pad.document_header_id,
1511                        pad.document_line_id,
1512                        pol.line_num,
1513                        pad.document_type_code,
1514                        NVL (x_vendor_site_id, poh.vendor_site_id),
1515                        NVL (x_vendor_contact_id, poh.vendor_contact_id),
1516                        NVL (x_buyer_id, poh.agent_id),
1517          /* Bug 2348331 fixed. swapped the elements in the below
1518             nvl statement in order that the vendor_product_num at
1519             blanket line level takes precedence to that at ASL level.
1520          */
1521                         NVL (pol.vendor_product_num, x_vendor_product_num),
1522                         poh.global_agreement_flag,
1523                         poh.org_id,
1524                         -- Bug 3361128: also select the UOM on the doc
1525                         pol.unit_meas_lookup_code
1526     FROM po_asl_documents pad,
1527          po_approved_supplier_list pasl,
1528          po_headers_all poh, --CTO changes FPH
1529          po_lines_all pol --CTO changes FPH
1530    WHERE pasl.asl_id = x_local_asl_id
1531      AND pad.asl_id = pasl.asl_id
1532      AND pad.using_organization_id = l_using_organization_id --<Bug 3733077>
1533      AND pad.document_header_id = poh.po_header_id
1534      AND pol.po_line_id (+) = pad.document_line_id	-- <FPJ Advanced Price>
1535      AND (   x_destination_doc_type = 'REQ'
1536           OR x_destination_doc_type = 'REQ_NONCATALOG'  --<Contract AutoSourcing FPJ>
1537           OR x_destination_doc_type IS NULL
1538           --<Bug 2742147 mbhargav START>
1539           OR (x_destination_doc_type = 'STANDARD PO' and
1540                 (poh.type_lookup_code = 'QUOTATION' OR
1541                 (poh.type_lookup_code = 'BLANKET' AND nvl(poh.global_agreement_flag, 'N') = 'Y'))
1542              )
1543           --<Bug 2742147 mbhargav END>
1544           --for x_destination_doc_type = 'PO'
1545           OR poh.type_lookup_code = 'QUOTATION'
1546          )
1547       AND (   (    poh.type_lookup_code = 'QUOTATION'
1548               AND poh.status_lookup_code = 'A'
1549               AND (  NOT EXISTS (
1550                               SELECT 'no shipments exists'
1551                                 FROM po_line_locations_all poll
1552                                WHERE poll.po_line_id = pol.po_line_id
1553 			         ) --Bug7384016 added this condition to include quotations without price breaks
1554 
1555 		    OR ( poh.approval_required_flag = 'N'
1556 	              AND (EXISTS (SELECT  'valid'
1557 		                   FROM po_line_locations_all poll
1558 				   WHERE poll.po_line_id = pol.po_line_id
1559 				   AND TRUNC (NVL (poll.end_date, x_sourcing_date)) >= --Bug6982267
1560                                            trunc(x_sourcing_date)
1561 			           )
1562                            )
1563 		      )
1564 	    --Bug7384016 segregated the coditions for  approval_required_flag = Y/N
1565 	           OR (poh.approval_required_flag = 'Y'
1566                        AND ( EXISTS (
1567                          SELECT 'quote is approved'
1568                            FROM po_quotation_approvals poqa,
1569                                 po_line_locations_all poll --CTO changes FPH
1570                           WHERE poqa.approval_type IS NOT NULL
1571                             AND poqa.line_location_id = poll.line_location_id
1572                             AND poll.po_line_id = pol.po_line_id
1573 			     AND TRUNC (NVL (poll.end_date, x_sourcing_date)) >= --Bug6982267
1574                                            trunc(x_sourcing_date)
1575 			             )
1576 		            )
1577 			)
1578 
1579 
1580                 )
1581             )
1585                                                  ('FINALLY CLOSED', 'CLOSED')
1582           OR (    poh.type_lookup_code = 'BLANKET'
1583               AND poh.approved_flag = 'Y'
1584               AND NVL (poh.closed_code, 'OPEN') NOT IN
1586               AND NVL (poh.cancel_flag, 'N') = 'N'
1587               AND NVL (poh.frozen_flag, 'N') = 'N'
1588               AND TRUNC (NVL (pol.expiration_date, x_sourcing_date)) >=
1589                                            trunc(x_sourcing_date) --Bug 2695699
1590 	      --<BUG 5334351> following condition (1 line) was missed when it was rewritten in FPJ
1591 	      AND NVL (pol.closed_code, 'OPEN') NOT IN ('FINALLY CLOSED', 'CLOSED')
1592               AND NVL (pol.cancel_flag, 'N') = 'N'
1593              )
1594         -- <FPJ Advanced Price START>
1595         OR ( poh.type_lookup_code = 'CONTRACT'
1596         	 AND (( NVL(FND_PROFILE.VALUE('ALLOW_REFERENCING_CPA_UNDER_AMENDMENT'),'N') =  'Y' --<R12 GCPA ER>
1597 			 	and poh.approved_date is not null               --<FPJGCPA>
1598 					)
1599 			 		or nvl(poh.approved_flag,'N') = 'Y'
1600 			 		)
1601             AND NVL(poh.cancel_flag,'N') = 'N'
1602             AND NVL(poh.frozen_flag,'N') = 'N'
1603             AND NVL(poh.closed_code, 'OPEN') = 'OPEN'
1604             AND p_return_contract = 'Y' --<Contract AutoSourcing FPJ>
1605            )
1606         -- <FPJ Advanced Price END>
1607          )
1608      AND (x_currency_code IS NULL OR poh.currency_code = x_currency_code)
1609      AND (p_sequence_number is NULL OR  --<Shared Proc FPJ>
1610                p_sequence_number = pad.sequence_num)
1611      AND x_sourcing_date >= NVL (poh.start_date, x_sourcing_date - 1)
1612      AND x_sourcing_date <= NVL (poh.end_date, x_sourcing_date + 1)
1613      -- <FPJ Advanced Price START>
1614      AND (poh.type_lookup_code = 'CONTRACT' OR
1615           (NVL(pol.item_revision, -1) = NVL(x_item_rev, -1) OR
1616            (NVL (p_item_rev_control, 1) = 1 AND x_item_rev IS NULL)))
1617      -- <FPJ Advanced Price END>
1618      --<Shared Proc FPJ START>
1619      --This clause returns rows if document is GA or
1620      --EITHER vendor_site_sourcing_flag  is N and site_ids match
1621      --OR vendor_site_sourcing_flag is Y and site codes match
1622      AND
1623          (
1624             (NVL (poh.global_agreement_flag, 'N') = 'Y')
1625           OR
1626             (    NVL (poh.global_agreement_flag, 'N') = 'N'
1627               AND (   (    p_vendor_site_sourcing_flag = 'N'
1628                        AND (x_vendor_site_id IS NULL OR
1629                             poh.vendor_site_id = x_vendor_site_id)
1630                       )
1631                    OR
1632                       (    p_vendor_site_sourcing_flag = 'Y'
1633                        AND (p_vendor_site_code IS NULL OR
1634                             poh.vendor_site_id =
1635                             	(select pvs.vendor_site_id
1636                               	 from po_vendor_sites pvs
1637                               	where pvs.vendor_site_code = p_vendor_site_code
1638                               	and   pvs.vendor_id = x_vendor_id))
1639                        )
1640                   )
1641              )
1642          )
1643      --<Shared Proc FPJ END>
1644      --If document is not a GA then the operating units should match
1645      --If document is GA and vendor site sourcing_flag is Y then
1646      --vendor_site_code for current org(as enabled org)  should match
1647      --If the document is GA and vendor site sourcing_flag is N then
1648      --current org should be enabled in GA
1649      --change is requird to do proper vendor sourcing
1650      AND (   (    NVL (poh.global_agreement_flag, 'N') = 'N'
1651               AND (x_multi_org = 'N')
1652               AND NVL (poh.org_id, -1) = NVL (p_org_id, -1)
1653              )
1654              --<Shared Proc FPJ START>
1655           OR ((       NVL (poh.global_agreement_flag, 'N') = 'Y'
1656                  AND (    p_vendor_site_sourcing_flag = 'Y'
1657                       AND (p_vendor_site_code IS NULL OR
1658                           EXISTS (
1659                              SELECT 'vendor site code matches'
1660                                FROM po_ga_org_assignments poga,
1661                                     po_vendor_sites_all pvsa
1662                               WHERE poh.po_header_id = poga.po_header_id
1663                                 AND poga.organization_id = p_org_id
1664                                 AND poga.vendor_site_id = decode( Nvl (poh.Enable_All_Sites,'N'),'N', pvsa.vendor_site_id ,poga.Vendor_Site_Id) -- <R12 GPCA>pvsa.vendor_site_id
1665                                 AND pvsa.vendor_site_code = p_vendor_site_code
1666                                 AND poga.enabled_flag = 'Y'
1667                                 AND pvsa.vendor_id = x_vendor_id))
1668                      )
1669               )OR (    p_vendor_site_sourcing_flag = 'N'
1670                   --<Bug 3356349 mbhargav START>
1671                   AND EXISTS (
1672                              SELECT 'vendor site id matches'
1673                                FROM po_ga_org_assignments poga
1674                               WHERE poh.po_header_id = poga.po_header_id
1675                                 AND poga.vendor_site_id = decode( Nvl (poh.Enable_All_Sites,'N'),'Y',poga.Vendor_Site_Id,x_vendor_site_id) --< R12 GCPA ER>
1676                                 AND poga.enabled_flag = 'Y')
1677                   AND (x_destination_doc_type = 'STANDARD PO'
1678                        OR EXISTS (
1679                          SELECT 'enabled org exists'
1680                            FROM po_ga_org_assignments poga
1681                           WHERE poh.po_header_id = poga.po_header_id
1682                             AND poga.organization_id = p_org_id
1683                             AND poga.enabled_flag = 'Y'))
1684                   --<Bug 3356349 mbhargav END>
1685                  )
1686              )
1687              --<Shared Proc FPJ END>
1688           OR x_multi_org = 'Y'
1689          ) -- FPI GA
1690 ORDER BY sequence_num ASC;
1691 
1692 /* Bug#4263138 */
1693   /*
1694    * Non-Catalog items in this case refers to any item that does not have an
1695    * item_id reference - includes, iP Non-Catalog item, Punchout item, POs without
1696    * item reference. For all these cases, the autosourcing is always done only
1697    * to a Contract agreement. So the join to po_lines_all, check for blankets/quotes
1698    * are not needed in the sql. This makes the sql more optimized for these
1699    * onetime/non-catalog item.(Also  vendor_site_sourcing_flag is 'N')
1700    */
1701   CURSOR L_GET_DOCS_ON_ASL_NONCAT_CSR(
1702  		p_sequence_number 	IN 	NUMBER) is
1703      SELECT   pad.document_header_id,
1704                        pad.document_line_id,
1705                        NULL line_num, -- Only Contracts are returned
1706                        pad.document_type_code,
1707                        NVL (x_vendor_site_id, poh.vendor_site_id),
1708                        NVL (x_vendor_contact_id, poh.vendor_contact_id),
1709                        NVL (x_buyer_id, poh.agent_id),
1710                         x_vendor_product_num,
1711                         poh.global_agreement_flag,
1712                         poh.org_id,
1713                         NULL unit_meas_lookup_code
1714     FROM po_asl_documents pad,
1715          po_approved_supplier_list pasl,
1716          po_headers_all poh --CTO changes FPH
1717    WHERE pasl.asl_id = x_local_asl_id
1718      AND pad.asl_id = pasl.asl_id
1719      AND pad.using_organization_id = l_using_organization_id --<Bug 3733077>
1720      AND pad.document_header_id = poh.po_header_id
1721      AND (   x_destination_doc_type = 'REQ'
1722           OR x_destination_doc_type = 'REQ_NONCATALOG'  --<Contract AutoSourcing FPJ>
1723           OR x_destination_doc_type IS NULL
1724          )
1725      AND (
1726         -- <FPJ Advanced Price START>
1727             poh.type_lookup_code = 'CONTRACT'
1728         	 AND (( NVL(FND_PROFILE.VALUE('ALLOW_REFERENCING_CPA_UNDER_AMENDMENT'),'N') =  'Y' --<R12 GCPA ER>
1729 			 		and poh.approved_date is not null)
1730 			 		OR
1731 			 		nvl(poh.approved_flag,'N') = 'Y'
1732 			 		)
1733             AND NVL(poh.cancel_flag,'N') = 'N'
1734             AND NVL(poh.frozen_flag,'N') = 'N'
1735             AND NVL(poh.closed_code, 'OPEN') = 'OPEN'
1736             AND p_return_contract = 'Y' --<Contract AutoSourcing FPJ>
1737         -- <FPJ Advanced Price END>
1738          )
1739      AND (x_currency_code IS NULL OR poh.currency_code = x_currency_code)
1740      AND (p_sequence_number is NULL OR  --<Shared Proc FPJ>
1741                p_sequence_number = pad.sequence_num)
1742      AND x_sourcing_date >= NVL (poh.start_date, x_sourcing_date - 1)
1743      AND x_sourcing_date <= NVL (poh.end_date, x_sourcing_date + 1)
1744      -- <FPJ Advanced Price START>
1748      --This clause returns rows if document is GA or
1745      AND poh.type_lookup_code = 'CONTRACT'
1746      -- <FPJ Advanced Price END>
1747      --<Shared Proc FPJ START>
1749      --EITHER vendor_site_sourcing_flag  is N and site_ids match
1750      --OR vendor_site_sourcing_flag is Y and site codes match
1751      AND
1752          (
1753             (NVL (poh.global_agreement_flag, 'N') = 'Y')
1754           OR
1755             (    NVL (poh.global_agreement_flag, 'N') = 'N'
1756               AND (    p_vendor_site_sourcing_flag = 'N'
1757                        AND (x_vendor_site_id IS NULL OR
1758                             poh.vendor_site_id = x_vendor_site_id)
1759                    )
1760              )
1761          )
1762      --<Shared Proc FPJ END>
1763      --If document is not a GA then the operating units should match
1764      --If document is GA and vendor site sourcing_flag is Y then
1765      --vendor_site_code for current org(as enabled org)  should match
1766      --If the document is GA and vendor site sourcing_flag is N then
1767      --current org should be enabled in GA
1768      --change is requird to do proper vendor sourcing
1769      AND (   (    NVL (poh.global_agreement_flag, 'N') = 'N'
1770               AND (x_multi_org = 'N')
1771               AND NVL (poh.org_id, -1) = NVL (p_org_id, -1)
1772              )
1773              --<Shared Proc FPJ START>
1774           OR (  NVL (poh.global_agreement_flag, 'N') = 'Y'
1775             OR (    p_vendor_site_sourcing_flag = 'N'
1776                   --<Bug 3356349 mbhargav START>
1777                   AND
1778                   (
1779                     x_vendor_site_id is null
1780                     OR
1781                     EXISTS (
1782                              SELECT 'vendor site id matches'
1783                                FROM po_ga_org_assignments poga
1784                               WHERE poh.po_header_id = poga.po_header_id
1785                                 AND poga.vendor_site_id = x_vendor_site_id
1786                                 AND poga.enabled_flag = 'Y')
1787                   )
1788                   --<Bug 3356349 mbhargav END>
1789                  )
1790              )
1791              --<Shared Proc FPJ END>
1792           OR x_multi_org = 'Y'
1793          ) -- FPI GA
1794 ORDER BY sequence_num ASC;
1795 
1796 BEGIN
1797 
1798     l_progress := '010';
1799     l_using_organization_id  := p_using_organization_id;
1800 
1801       -- Fetch the local ASL entry if one exists; otherwise,
1802       -- fetch the global entry.
1803 
1804     /* CTO changes FPH. If x_asl_id is not null, then we could have obtained
1805      * from Get_All_Item_Asl procedure. This is the same as x_asl_id but returns
1806      * vendor_id also and in an array. When any changes are made to get_asl_info
1807      * need to consider Get_All_Item_Asl procedure also.
1808     */
1809     if (x_asl_id is null) then --cto FPH
1810 	   IF p_vendor_site_sourcing_flag = 'N' THEN
1811             l_progress := '020';
1812 
1813             IF g_debug_stmt THEN
1814                PO_DEBUG.debug_stmt(l_log_head,l_progress,'Calling get_asl_info');
1815             END IF;
1816 	     --This call does not require vendor site sourcing
1817             --so do existing call to get local_asl_id
1818             get_asl_info(x_item_id               => x_item_id,
1819                          x_vendor_id             => x_vendor_id,
1820 	                 x_vendor_site_id        => x_vendor_site_id,
1821                          x_using_organization_id => l_using_organization_id,
1822                          x_asl_id                => x_local_asl_id,
1823                          x_vendor_product_num    => x_vendor_product_num,
1824                          x_purchasing_uom        => x_asl_purchasing_uom,
1825 			 p_category_id           => p_category_id	--<Contract AutoSourcing FPJ>_item_id,
1826                          );
1827 
1828             IF g_debug_stmt THEN
1829                PO_DEBUG.debug_stmt(l_log_head,l_progress,'get_asl_info returned:');
1830                PO_DEBUG.debug_var(l_log_head,l_progress,'asl_id obtained', x_local_asl_id);
1831             END IF;
1832 
1833 	   ELSE
1834             l_progress := '030';
1835 
1836             IF g_debug_stmt THEN
1837                PO_DEBUG.debug_stmt(l_log_head,l_progress,'Calling asl_sourcing');
1838             END IF;
1839             --This procedure does the sourcing of document based on ASL
1840             --This returns asl_id to use. Optionally it returns sequence_number
1841             --of GA to be used if the ASL is from different OU
1842             asl_sourcing(
1843                          p_item_id		=>x_item_id,
1844                          p_vendor_id		=>x_vendor_id,
1845 	                 p_vendor_site_code	=>p_vendor_site_code,
1846                          p_item_rev		=>x_item_rev,
1847                          p_item_rev_control	=>p_item_rev_control,
1848                          p_sourcing_date	=>x_sourcing_date,
1849                          p_currency_code	=>x_currency_code,
1850                          p_org_id		=>p_org_id,
1851                          p_using_organization_id =>l_using_organization_id,
1852                          x_asl_id 		=>x_local_asl_id,
1853                          x_vendor_product_num 	=>x_vendor_product_num,
1854                          x_purchasing_uom 	=>x_asl_purchasing_uom,
1855  	                 x_consigned_from_supplier_flag =>x_consigned_from_supplier_flag,
1856  	                 x_enable_vmi_flag 	=>x_enable_vmi_flag,
1857                          x_sequence_num 	=>l_sequence_number,
1861               IF g_debug_stmt THEN
1858                          p_category_id          => p_category_id --<Contract AutoSourcing FPJ>
1859                          );
1860 
1862                  PO_DEBUG.debug_stmt(l_log_head,l_progress,'asl_sourcing returned:');
1863                  PO_DEBUG.debug_var(l_log_head,l_progress,'asl_id obtained', x_local_asl_id);
1864                  PO_DEBUG.debug_var(l_log_head,l_progress,'using organization is ', l_using_organization_id);
1865                  PO_DEBUG.debug_var(l_log_head,l_progress,'sequence num obtained', l_sequence_number);
1866               END IF;
1867 
1868               IF (x_local_asl_id IS NULL
1869                   AND trunc(x_sourcing_date) <> trunc(sysdate)) THEN
1870 
1871                   l_progress := '040';
1872                   IF g_debug_stmt THEN
1873                      PO_DEBUG.debug_stmt(l_log_head,l_progress,'Calling asl_sourcing with sysdate');
1874                   END IF;
1875                   --Call ASL_SOURCING again this time passing SYSDATE as SOURCING_DATE
1876                   x_sourcing_date := trunc(sysdate);
1877                   asl_sourcing(
1878                          p_item_id		=>x_item_id,
1879                          p_vendor_id		=>x_vendor_id,
1880 	                 p_vendor_site_code	=>p_vendor_site_code,
1881                          p_item_rev		=>x_item_rev,
1882                          p_item_rev_control	=>p_item_rev_control,
1883                          p_sourcing_date	=>x_sourcing_date,
1884                          p_currency_code	=>x_currency_code,
1885                          p_org_id		=>p_org_id,
1886                          p_using_organization_id =>l_using_organization_id,
1887                          x_asl_id 		=>x_local_asl_id,
1888                          x_vendor_product_num 	=>x_vendor_product_num,
1889                          x_purchasing_uom 	=>x_asl_purchasing_uom,
1890  	                 x_consigned_from_supplier_flag =>x_consigned_from_supplier_flag,
1891  	                 x_enable_vmi_flag 	=>x_enable_vmi_flag,
1892                          x_sequence_num 	=>l_sequence_number,
1893                          p_category_id          => p_category_id --<Contract AutoSourcing FPJ>
1894                          );
1895 
1896                     IF g_debug_stmt THEN
1897                        PO_DEBUG.debug_stmt(l_log_head,l_progress,'asl_sourcing returned:');
1898                        PO_DEBUG.debug_var(l_log_head,l_progress,'asl_id obtained', x_local_asl_id);
1899                        PO_DEBUG.debug_var(l_log_head,l_progress,'using organization is ',
1900                                                                            l_using_organization_id);
1901                        PO_DEBUG.debug_var(l_log_head,l_progress,'sequence num obtained', l_sequence_number);
1902                     END IF;
1903                END IF;
1904        END IF;
1905     else
1906         x_local_asl_id := x_asl_id; --cto FPH
1907     end if; --cto FPH
1908 
1909     l_progress := '050';
1910     x_purchasing_uom := nvl(x_asl_purchasing_uom, x_purchasing_uom);
1911 
1912     IF x_local_asl_id IS NOT NULL THEN
1913 
1914        --<Contract AutoSourcing FPJ Start>
1915        BEGIN
1916          SELECT	item_id
1917          INTO	l_item_id
1918          FROM	po_approved_supplier_list
1919          WHERE	asl_id = x_local_asl_id;
1920        EXCEPTION
1921 	 WHEN NO_DATA_FOUND THEN
1922            null;
1923        END;
1924 
1925        IF l_item_id IS NULL THEN
1926  	  l_item_based_asl := 'N';
1927        END IF;
1928        --<Contract AutoSourcing FPJ End>
1929 
1930        /* Bug#4263138 */
1931        if( (x_destination_doc_type = 'REQ' OR x_destination_doc_type = 'REQ_NONCATALOG')
1932              AND  x_item_id is null)
1933        then
1934          l_noncat_item := TRUE;
1935        else
1936          l_noncat_item := FALSE;
1937        end if;
1938 
1939        if (l_noncat_item) then
1940          OPEN L_GET_DOCS_ON_ASL_NONCAT_CSR(l_sequence_number);
1941        else
1942          OPEN L_GET_DOCS_ON_ASL_CSR(l_sequence_number);
1943        end if;
1944 
1945        -- Get the highest ranked document that matches the criteria.
1946        -- If document found, return.
1947 
1948        -- debug
1949        --dbms_output.put_line('destination doc ='|| x_destination_doc_type);
1950        --dbms_output.put_line('agent_id = '|| to_char(x_buyer_id));
1951        --dbms_output.put_line('currency_code = '|| x_currency_code);
1952        --dbms_output.put_line('item_rev = '|| x_item_rev);
1953        --dbms_output.put_line('sourcing_date = '|| to_char(x_sourcing_date));
1954        --dbms_output.put_line('org_id = '|| to_char(p_org_id));
1955        --dbms_output.put_line('item rev control = '|| to_char(p_item_rev_control));
1956 
1957        l_progress := '060';
1958 
1959        LOOP
1960          if (l_noncat_item) then
1961            FETCH L_GET_DOCS_ON_ASL_NONCAT_CSR into x_document_header_id,
1962                      x_document_line_id,
1963                      x_document_line_num,
1964                      x_document_type_code,
1965                      x_vendor_site_id,
1966                      x_vendor_contact_id,
1967                      x_buyer_id,
1968                      x_vendor_product_num,
1969                      l_global_agreement_flag,
1970                      l_document_org_id,
1971                      l_source_doc_purchasing_uom; -- Bug 3361128
1975                      x_document_line_id,
1972             EXIT WHEN L_GET_DOCS_ON_ASL_NONCAT_CSR%NOTFOUND;
1973           else
1974            FETCH L_GET_DOCS_ON_ASL_CSR into x_document_header_id,
1976                      x_document_line_num,
1977                      x_document_type_code,
1978                      x_vendor_site_id,
1979                      x_vendor_contact_id,
1980                      x_buyer_id,
1981                      x_vendor_product_num,
1982                      l_global_agreement_flag,
1983                      l_document_org_id,
1984                      l_source_doc_purchasing_uom; -- Bug 3361128
1985             EXIT WHEN L_GET_DOCS_ON_ASL_CSR%NOTFOUND;
1986           end if;
1987 
1988 
1989           /* FPI GA start */
1990           if x_document_header_id is not null then
1991 
1992           --<R12 STYLES PHASE II START>
1993           -- Validate whether the Sourced Docuemnt is Style Compatible
1994            IF g_debug_stmt THEN
1995               PO_DEBUG.debug_stmt(l_log_head,l_progress,'style validate source doc');
1996               PO_DEBUG.debug_var(l_log_head,l_progress,'x_destination_doc_type', x_destination_doc_type);
1997               PO_DEBUG.debug_var(l_log_head,l_progress,'x_document_type_code', x_document_type_code);
1998            END IF;
1999 
2000           l_eligible_doc_flag := TRUE;
2001 
2002 	  --in case the sourcing is happening without passing any attributes as in pricing only mode
2003 	  --check if all the attributes are NULL
2004 	  --in such a case bypass the style validation checks
2005         if   p_line_type_id IS NULL
2006 	     AND p_purchase_basis IS NULL
2007 	     AND p_destination_type IS NULL
2008 	     AND p_style_id IS NULL  then
2009 
2010               l_eligible_doc_flag := TRUE;
2011               IF g_debug_stmt THEN
2012                  PO_DEBUG.debug_stmt(l_log_head,l_progress,'bypass style validations');
2013               END IF;
2014 
2015        else --if attributes are passed then do style validation checks
2016 
2017                IF g_debug_stmt THEN
2018                  PO_DEBUG.debug_stmt(l_log_head,l_progress,'do style validations');
2019               END IF;
2020 
2021           if x_destination_doc_type IN ('REQ','REQ_NONCATALOG') then
2022             if (x_document_type_code IN ('BLANKET', 'CONTRACT')) then
2023 
2024                 PO_DOC_STYLE_PVT.style_validate_req_attrs(p_api_version      => 1.0,
2025                                                           p_init_msg_list    => FND_API.G_TRUE,
2026                                                           x_return_status    => l_return_status,
2027                                                           x_msg_count        => l_msg_count,
2028                                                           x_msg_data         => l_msg_data,
2029                                                           p_doc_style_id     => null,
2030                                                           p_document_id      => x_document_header_id,
2031                                                           p_line_type_id     => p_line_type_id,
2032                                                           p_purchase_basis   => p_purchase_basis,
2033                                                           p_destination_type => p_destination_type,
2034                                                           p_source           => 'REQUISITION'
2035                                                           );
2036 
2037               if l_return_status <> FND_API.g_ret_sts_success THEN
2038                 l_eligible_doc_flag := FALSE;
2039                  IF g_debug_stmt THEN
2040                     PO_DEBUG.debug_stmt(l_log_head,l_progress,'style validation failed');
2041                  END IF;
2042               end if;
2043             end if;
2044 
2045         else  -- x_destination_doc_type = 'STANDARD PO','PO' OR NULL
2046 
2047             If (p_style_id <>
2048                PO_DOC_STYLE_PVT.get_doc_style_id(x_document_header_id)) THEN
2049               l_eligible_doc_flag := FALSE;
2050             end if;
2051 
2052        end if; --if x_destination_doc_type IN ('REQ','REQ_NONCATALOG') then
2053      end if;  -- if   p_line_type_id IS NULL
2054 
2055        --<R12 STYLES PHASE II END>
2056        if l_eligible_doc_flag then   --<R12 STYLES PHASE II>
2057           IF g_debug_stmt THEN
2058              PO_DEBUG.debug_stmt(l_log_head,l_progress,'style validation passed 1');
2059           END IF;
2060              --<Contract AutoSourcing FPJ Start>
2061 	     --For category-based ASL, the only valid document type is contract
2062 	     IF l_item_based_asl = 'N' THEN
2063                 IF x_document_type_code = 'CONTRACT' THEN
2064                    --<Bug 3545698 mbhargav START>
2065                    IF nvl(l_global_agreement_flag, 'N') = 'Y' THEN
2066                       IF p_vendor_site_sourcing_flag = 'Y' THEN
2067    	                     --Now get the supplier_site_id and vendor_contact_id
2068     	                 x_vendor_site_id :=
2069                                PO_GA_PVT.get_vendor_site_id(x_document_header_id);
2070 
2071    	                     IF x_vendor_contact_id is NULL then
2072     		                PO_VENDOR_CONTACTS_SV.get_vendor_contact(
2073                                           x_vendor_site_id 	=>x_vendor_site_id,
2074                                           x_vendor_contact_id 	=>x_vendor_contact_id,
2075                                           x_vendor_contact_name 	=>l_vendor_contact_name);
2076    	                     END IF;
2080                         PO_DEBUG.debug_stmt(l_log_head,l_progress,'Found a document from ASL:');
2077                       END IF; --vendor_site_sourcing_flag check
2078                    END IF; --global flag check
2079                    IF g_debug_stmt THEN
2081                         PO_DEBUG.debug_var(l_log_head,l_progress,'Total DOcuments looked at', L_GET_DOCS_ON_ASL_CSR%ROWCOUNT);
2082                         PO_DEBUG.debug_var(l_log_head,l_progress,'x_document_header_id', x_document_header_id);
2083                         PO_DEBUG.debug_var(l_log_head,l_progress,'x_document_line_id', x_document_line_id);
2084                         PO_DEBUG.debug_var(l_log_head,l_progress,'l_vendor_site_id', x_vendor_site_id);
2085                    END IF;
2086                    --<Bug 3545698 mbhargav END>
2087                    EXIT;
2088                 END IF;	 --doc type checkc
2089 	     ELSE
2090 
2091                GET_SITE_ID_IF_ITEM_ON_DOC_OK(
2092                    p_document_header_id        => x_document_header_id,
2093                    p_item_id                   => x_item_id,
2094                    p_vendor_site_sourcing_flag => p_vendor_site_sourcing_flag,
2095                    p_global_agreement_flag     => l_global_agreement_flag,
2096                    p_document_org_id           => l_document_org_id,
2097                    x_return_status             => x_return_status,
2098                    x_vendor_site_id            => x_vendor_site_id,
2099                    x_vendor_contact_id         => x_vendor_contact_id,
2100 	           p_destination_doc_type      => x_destination_doc_type, --<Bug 3356349>
2101 		   p_multi_org                 => x_multi_org --<CTO Bug 4222144>
2102 					     );
2103 
2104               IF x_return_status = FND_API.G_RET_STS_SUCCESS then
2105                      l_progress := '070';
2106                      IF g_debug_stmt THEN
2107                         PO_DEBUG.debug_stmt(l_log_head,l_progress,'Found a document from ASL:');
2108                         PO_DEBUG.debug_var(l_log_head,l_progress,'Total DOcuments looked at', L_GET_DOCS_ON_ASL_CSR%ROWCOUNT);
2109                         PO_DEBUG.debug_var(l_log_head,l_progress,'x_document_header_id', x_document_header_id);
2110                         PO_DEBUG.debug_var(l_log_head,l_progress,'x_document_line_id', x_document_line_id);
2111                         PO_DEBUG.debug_var(l_log_head,l_progress,'l_vendor_site_id', x_vendor_site_id);
2112                      END IF;
2113 
2114                      exit;
2115                END IF;
2116              END IF; -- l_item_based_asl check
2117 
2118           end if; -- if l_eligible_doc_flag --<R12 STYLES PHASE II>
2119 
2120              /* Bug 2752091 : If the item is not valid in the current OU
2121                 we null out the doc info that was already fetched so that
2122                 it does not get returned to the form */
2123              x_document_header_id := null;
2124              x_document_line_id   := null;
2125              x_document_line_num  := null;
2126              x_document_type_code :=  null;
2127 	     l_source_doc_purchasing_uom :=  null;   --<R12 STYLES PHASE II>
2128 
2129           else -- x_document_header_id is null
2130             exit;
2131           end if;-- x_document_header_id IS NOT NULL check
2132           --<Contract AutoSourcing FPJ End>
2133 
2134         END LOOP;
2135           /* FPI GA end */
2136 
2137        if (l_noncat_item) then
2138          CLOSE L_GET_DOCS_ON_ASL_NONCAT_CSR;
2139        else
2140          CLOSE L_GET_DOCS_ON_ASL_CSR;
2141        end if;
2142 
2143 
2144    /* bug 935944 : base - 918701 Cursor L_GET_DOCS_ON_ASL_CSR will return either one or no rows.
2145       If no rows were returned and x_sourcing_date is not equal to sysdate,
2146       then we will try again to fetch sourcing document info using sysdate */
2147 
2148         IF (x_document_header_id IS NULL AND trunc(x_sourcing_date) <> trunc(sysdate)) THEN
2149 
2150           x_sourcing_date := trunc(sysdate);
2151           l_progress := '080';
2152 
2153          /* Bug#4263138 */
2154          if (l_noncat_item) then
2155           OPEN L_GET_DOCS_ON_ASL_NONCAT_CSR(l_sequence_number);
2156          else
2157           OPEN L_GET_DOCS_ON_ASL_CSR(l_sequence_number);
2158          end if;
2159 
2160         LOOP
2161          if (l_noncat_item) then
2162           FETCH L_GET_DOCS_ON_ASL_NONCAT_CSR into x_document_header_id,
2163                         x_document_line_id,
2164                         x_document_line_num,
2165                         x_document_type_code,
2166                         x_vendor_site_id,
2167                         x_vendor_contact_id,
2168                         x_buyer_id,
2169                         x_vendor_product_num,
2170                         l_global_agreement_flag,
2171                         l_document_org_id,
2172                         l_source_doc_purchasing_uom; -- Bug 3361128
2173           EXIT WHEN L_GET_DOCS_ON_ASL_NONCAT_CSR%NOTFOUND;
2174          else
2175           FETCH L_GET_DOCS_ON_ASL_CSR into x_document_header_id,
2176                         x_document_line_id,
2177                         x_document_line_num,
2178                         x_document_type_code,
2179                         x_vendor_site_id,
2180                         x_vendor_contact_id,
2181                         x_buyer_id,
2182                         x_vendor_product_num,
2183                         l_global_agreement_flag,
2184                         l_document_org_id,
2188 
2185                         l_source_doc_purchasing_uom; -- Bug 3361128
2186           EXIT WHEN L_GET_DOCS_ON_ASL_CSR%NOTFOUND;
2187          end if;
2189           /* FPI GA start */
2190           if x_document_header_id is not null then
2191 
2192            --<R12 STYLES PHASE II START>
2193             -- Validate whether the Sourced Docuemnt is Style Compatible
2194            IF g_debug_stmt THEN
2195               PO_DEBUG.debug_stmt(l_log_head,l_progress,'style validate source doc');
2196               PO_DEBUG.debug_var(l_log_head,l_progress,'x_destination_doc_type', x_destination_doc_type);
2197               PO_DEBUG.debug_var(l_log_head,l_progress,'x_document_type_code', x_document_type_code);
2198            END IF;
2199             l_eligible_doc_flag := TRUE;
2200 
2201 	  --in case the sourcing is happening without passing any attributes as in pricing only mode
2202 	  --check if all the attributes are NULL
2203 	  --in such a case bypass the style validation checks
2204         if   p_line_type_id IS NULL
2205 	     AND p_purchase_basis IS NULL
2206 	     AND p_destination_type IS NULL
2207 	     AND p_style_id IS NULL  then
2208 
2209               l_eligible_doc_flag := TRUE;
2210               IF g_debug_stmt THEN
2211                  PO_DEBUG.debug_stmt(l_log_head,l_progress,'bypass style validations');
2212               END IF;
2213 
2214        else --if attributes are passed then do style validation checks
2215 
2216                IF g_debug_stmt THEN
2217                  PO_DEBUG.debug_stmt(l_log_head,l_progress,'do style validations');
2218               END IF;
2219          if x_destination_doc_type IN ('REQ','REQ_NONCATALOG') then
2220               if (x_document_type_code IN ('BLANKET', 'CONTRACT')) then
2221                 PO_DOC_STYLE_PVT.style_validate_req_attrs(p_api_version      => 1.0,
2222                                                           p_init_msg_list    => FND_API.G_TRUE,
2223                                                           x_return_status    => l_return_status,
2224                                                           x_msg_count        => l_msg_count,
2225                                                           x_msg_data         => l_msg_data,
2226                                                           p_doc_style_id     => null,
2227                                                           p_document_id      => x_document_header_id,
2228                                                           p_line_type_id     => p_line_type_id,
2229                                                           p_purchase_basis   => p_purchase_basis,
2230                                                           p_destination_type => p_destination_type,
2231                                                           p_source           => 'REQUISITION'
2232                                                           );
2233 
2234                 if l_return_status <> FND_API.g_ret_sts_success THEN
2235                    l_eligible_doc_flag := FALSE;
2236                    IF g_debug_stmt THEN
2237                       PO_DEBUG.debug_stmt(l_log_head,l_progress,'style validation failed');
2238                    END IF;
2239                 end if;
2240               end if;
2241 
2242          else  -- x_destination_doc_type = 'STANDARD PO','PO' OR NULL
2243 
2244               If (p_style_id <>
2245                  PO_DOC_STYLE_PVT.get_doc_style_id(x_document_header_id)) THEN
2246                 l_eligible_doc_flag := FALSE;
2247               end if;
2248 
2249          end if;
2250        end if;  -- if   p_line_type_id IS NULL
2251             --<R12 STYLES PHASE II END>
2252 
2253           if l_eligible_doc_flag then       --<R12 STYLES PHASE II>
2254              IF g_debug_stmt THEN
2255                 PO_DEBUG.debug_stmt(l_log_head,l_progress,'style validation passed 2');
2256              END IF;
2257 	     --<Contract AutoSourcing FPJ Start>
2258 	     --For category-based ASL, the only valid document type is contract
2259 	     IF l_item_based_asl = 'N' THEN
2260                 IF x_document_type_code = 'CONTRACT' THEN
2261                    --<Bug 3545698 mbhargav START>
2262                    IF nvl(l_global_agreement_flag, 'N') = 'Y' THEN
2263                       IF p_vendor_site_sourcing_flag = 'Y' THEN
2264    	                     --Now get the supplier_site_id and vendor_contact_id
2265     	                 x_vendor_site_id :=
2266                                PO_GA_PVT.get_vendor_site_id(x_document_header_id);
2267 
2268    	                     IF x_vendor_contact_id is NULL then
2269     		                PO_VENDOR_CONTACTS_SV.get_vendor_contact(
2270                                           x_vendor_site_id 	=>x_vendor_site_id,
2271                                           x_vendor_contact_id 	=>x_vendor_contact_id,
2272                                           x_vendor_contact_name 	=>l_vendor_contact_name);
2273    	                     END IF;
2274                       END IF; --vendor_site_sourcing_flag check
2275                    END IF; --global flag check
2276                    IF g_debug_stmt THEN
2277                         PO_DEBUG.debug_stmt(l_log_head,l_progress,'Found a document from ASL:');
2278                         PO_DEBUG.debug_var(l_log_head,l_progress,'Total DOcuments looked at', L_GET_DOCS_ON_ASL_CSR%ROWCOUNT);
2279                         PO_DEBUG.debug_var(l_log_head,l_progress,'x_document_header_id', x_document_header_id);
2280                         PO_DEBUG.debug_var(l_log_head,l_progress,'x_document_line_id', x_document_line_id);
2281                         PO_DEBUG.debug_var(l_log_head,l_progress,'l_vendor_site_id', x_vendor_site_id);
2282                    END IF;
2286 	     ELSE
2283                    --<Bug 3545698 mbhargav END>
2284 		           EXIT;
2285                 END IF; --doc_type_code check
2287                GET_SITE_ID_IF_ITEM_ON_DOC_OK(
2288                    p_document_header_id        => x_document_header_id,
2289                    p_item_id                   => x_item_id,
2290                    p_vendor_site_sourcing_flag => p_vendor_site_sourcing_flag,
2291                    p_global_agreement_flag     => l_global_agreement_flag,
2292                    p_document_org_id           => l_document_org_id,
2293                    x_return_status             => x_return_status,
2294                    x_vendor_site_id            => x_vendor_site_id,
2295                    x_vendor_contact_id         => x_vendor_contact_id,
2296 	           p_destination_doc_type      => x_destination_doc_type, --<Bug 3356349>
2297 		   p_multi_org                 => x_multi_org --<CTO Bug 4222144>
2298 		);
2299 
2300                IF x_return_status = FND_API.G_RET_STS_SUCCESS then
2301                   l_progress := '090';
2302                   IF g_debug_stmt THEN
2303                      PO_DEBUG.debug_stmt(l_log_head,l_progress,'Found a document from ASL with sysdate:');
2304                      PO_DEBUG.debug_var(l_log_head,l_progress,'Total DOcuments looked at', L_GET_DOCS_ON_ASL_CSR%ROWCOUNT);
2305                      PO_DEBUG.debug_var(l_log_head,l_progress,'x_document_header_id', x_document_header_id);
2306                      PO_DEBUG.debug_var(l_log_head,l_progress,'x_document_line_id', x_document_line_id);
2307                      PO_DEBUG.debug_var(l_log_head,l_progress,'l_vendor_site_id', x_vendor_site_id);
2308                   END IF;
2309                   exit;
2310                END IF;
2311              END IF; -- l_item_based_asl check
2312             end if; -- if l_eligible_doc_flag --<R12 STYLES PHASE II>
2313 
2314              /* Bug 2752091 : If the item is not valid in the current OU
2315                 we null out the doc info that was already fetched so that
2316                 it does not get returned to the form */
2317              x_document_header_id := null;
2318              x_document_line_id   := null;
2319              x_document_line_num  := null;
2320              x_document_type_code :=  null;
2321 	     l_source_doc_purchasing_uom :=  null;   --<R12 STYLES PHASE II>
2322 
2323           else -- x_document_header_id is null
2324             exit;
2325           end if; -- x_document_header_id IS NOT NULL check
2326           --<Contract AutoSourcing FPJ End>
2327 
2328         END LOOP;
2329         /* Bug#4263138 */
2330         if (l_noncat_item) then
2331           CLOSE L_GET_DOCS_ON_ASL_NONCAT_CSR;
2332         else
2333           CLOSE L_GET_DOCS_ON_ASL_CSR;
2334         end if;
2335         END IF;
2336 
2337       END IF;  --x_local_asl is NULL check
2338 
2339       -- Bug 3361128: pass back the UOM on the source doc (if any)
2340       x_purchasing_uom := nvl(l_source_doc_purchasing_uom, x_purchasing_uom);
2341       --<PKGCOMP R12 Start>
2342       -- Initialize the x_asl_id to value of x_local_asl_id just before exiting the
2343       -- Get_document_from_asl procedure.
2344         x_asl_id := x_local_asl_id;
2345       --<PKGCOMP R12 End>
2346              IF g_debug_stmt THEN
2347                  PO_DEBUG.debug_var(l_log_head,l_progress,'x_purchasing_uom', x_purchasing_uom);
2348              END IF;
2349       l_progress := '100';
2350 EXCEPTION
2351     WHEN OTHERS THEN
2352         IF g_debug_unexp THEN
2353            PO_DEBUG.debug_exc(l_log_head,l_progress);
2354         END IF;
2355 
2356         PO_MESSAGE_S.SQL_ERROR('Get_Document_FROM_ASL', l_progress, sqlcode);
2357 END get_document_from_asl;
2358 
2359 --<Shared Proc FPJ START>
2360 -------------------------------------------------------------------------------
2361 --Start of Comments
2362 --Name: GET_LATEST_DOCUMENT
2363 --Pre-reqs:
2364 --  Assumes that Profile PO: Automatic Document Sourcing profile is ON
2365 --Modifies:
2366 --  None.
2367 --Locks:
2368 --  None.
2369 --Function:
2370 --  This procedure gets the most recent document which can be used as Source
2371 --  document fro given item, item_revision, destination inv org and need_by_date
2372 --Parameters:
2373 --IN:
2374 --x_item_id
2375 --  item_id to be matched for ASL
2376 --x_vendor_id
2377 --  vendor_id to be matched for ASL
2378 --x_destination_doc_type
2379 --  The form from which the call to the API is made. Vaild values are
2380 --  'PO', 'STANDARD PO', 'REQ', 'REQ_NONCATALOG' and NULL --<Contract AutoSourcing FPJ>
2381 --x_curreny_code
2382 --  Currency code to be compared to get matching document
2383 --x_item_rev
2384 --  Item revision that needs to be compared to.
2385 --p_autosourcing_date
2386 --  Date to be used for Sourcing date check
2387 --p_item_rev_control
2388 --  This parameter tells whether item revision control is ON for given p_item_id
2389 --p_vendor_site_sourcing_flag
2390 --  Parameter which tells whether site sourcing is done or not
2391 --p_vendor_site_code
2392 --  If vendor_site_sourcing_flag = 'Y' then this parameter contains the
2393 --  site code for which the API needs to find appropriate site_id
2394 --p_org_id
2395 --  Operating Unit id
2396 --x_multi_org
2397 --  Parameter used by CTO
2398 --IN OUT:
2399 --x_vendor_product_num
2400 --  Supplier product_num associated with given Item as defined on ASL
2401 --x_purchasing_uom
2405 --  to do vendor site sourcing will pass in a value and set vendor_site_sourcing_flag
2402 --  Purchasing UOM provided by Supplier on ASL
2403 --x_vendor_site_id
2404 --  This parameter is used as IN OUT parameter. For callers who do not want
2406 --  = 'N'. When vendor_site_sourcing_flag = 'Y' then this parameter would contain
2407 --  the site_id obtained by vendor site sourcing
2408 --x_document_header_id
2409 --  The unique identifier of the document returned
2410 --x_document_type_code
2411 --  Valid values 'BLANKET'/'QUOTATION'
2412 --x_document_line_num
2413 --  The line number of the document returned
2414 --x_document_line_id
2415 --  The unique identifier of the document line returned
2416 --x_vendor_contact_id
2417 --  If there is a unique contact id present then this returns that value
2418 --x_buyer_id
2419 --  The buyer mentioned on the document returned
2420 --x_asl_id
2421 --  Parameter used by CTO to pass asl_id so that no ASL sourcing is done
2422 --Testing:
2423 --  None
2424 --End of Comments
2425 -------------------------------------------------------------------------------
2426 Procedure get_latest_document(
2427              x_item_id             	      IN    NUMBER,
2428              x_vendor_id           	      IN	NUMBER,
2429              x_destination_doc_type 	  IN  	VARCHAR2,
2430              x_currency_code              IN    VARCHAR2,
2431              x_item_rev                   IN	VARCHAR2,
2432              x_autosource_date            IN    DATE,
2433              x_vendor_site_id             IN OUT NOCOPY  NUMBER,
2434              x_document_header_id         IN OUT NOCOPY  NUMBER,
2435              x_document_type_code         IN OUT NOCOPY  VARCHAR2,
2436              x_document_line_num          IN OUT NOCOPY  NUMBER,
2437              x_document_line_id           IN OUT  NOCOPY NUMBER,
2438              x_vendor_contact_id          IN OUT NOCOPY  NUMBER,
2439              x_vendor_product_num         IN OUT  NOCOPY VARCHAR2,
2440              x_buyer_id                   IN OUT NOCOPY  NUMBER,
2441              x_purchasing_uom             IN OUT NOCOPY  VARCHAR2,
2442              x_asl_id                     IN OUT NOCOPY NUMBER,--<Bug#4936992>
2443              x_multi_org        	  IN    VARCHAR2,
2444              p_vendor_site_sourcing_flag  IN 	VARCHAR2,
2445  	     p_vendor_site_code   	  IN  	VARCHAR2 ,
2446              p_org_id                     IN    NUMBER,
2447              p_item_rev_control           IN    NUMBER,
2448              p_using_organization_id      IN    NUMBER,
2449              p_category_id		  IN    NUMBER,--<Contract AutoSourcing FPJ>
2450 	     p_return_contract		  IN 	VARCHAR2 --<Contract AutoSourcing FPJ>
2451              --<R12 STYLES PHASE II START>
2452             ,p_purchase_basis   IN VARCHAR2 DEFAULT NULL,
2453              p_line_type_id     IN VARCHAR2 DEFAULT NULL,
2454              p_destination_type IN VARCHAR2 DEFAULT NULL,
2455              p_style_id         IN NUMBER DEFAULT NULL
2456              --<R12 STYLES PHASE II END>
2457 ) IS
2458         x_local_asl_id              NUMBER; --cto FPH
2459         l_progress                  VARCHAR2(3) := '000';
2460         x_sourcing_date             DATE := trunc(nvl(x_autosource_date, sysdate));
2461         x_auto_source_doc           VARCHAR2(1);
2462         x_asl_purchasing_uom        VARCHAR2(25);
2463         x_source_doc_not_found      VARCHAR2(1) := 'N';  -- Bug 2373004
2464         x_return_status	            VARCHAR2(1); --<Shared Proc FPJ>
2465         l_global_agreement_flag     PO_HEADERS_ALL.global_agreement_flag%TYPE;
2466         l_document_org_id           PO_HEADERS_ALL.org_id%TYPE;
2467         l_using_organization_id     NUMBER;
2468         l_log_head     CONSTANT VARCHAR2(100) := g_log_head||'get_latest_document';
2469         l_noncat_item BOOLEAN := FALSE; /* Bug#4263138 */
2470 
2471         -- Bug 3361128: this parameter stores the UOM on the source doc
2472         l_source_doc_purchasing_uom PO_LINES_ALL.unit_meas_lookup_code%TYPE;
2473 
2474 
2475     --<R12 STYLES PHASE II START>
2476     l_eligible_doc_flag Boolean;
2477     l_return_status     VARCHAR2(1);
2478     l_msg_count         NUMBER;
2479     l_msg_data          VARCHAR2(2000);
2480     --<R12 STYLES PHASE II END>
2481 
2482        --Bug5081434
2483        l_doc_type_fetch_order   NUMBER;
2484        l_uom_match  	        NUMBER;
2485        l_global_flag 	        VARCHAR2(1);
2486        l_creation_date          DATE;
2487 
2488        --Replaced two cursors AUTO_SOURCE_DOCS_WITH_UOM and
2489        --AUTO_SOURCE_DOCS_WITHOUT_UOM with L_GET_LATEST_DOCS_CSR
2490        --This is accomplished by taking purchasing_uom as input parameter.
2491        -- Bug 5074119
2492        -- Added an extra condition on type_lookup_code to improve the performance
2493      CURSOR L_GET_LATEST_DOCS_CSR(
2494  		       p_purchasing_uom 	IN 	VARCHAR2) is
2495 SELECT   poh.po_header_id,
2496          pol.po_line_id,
2497          pol.line_num,
2498          poh.type_lookup_code,
2499          NVL (x_vendor_site_id, poh.vendor_site_id),
2500          NVL (x_vendor_contact_id, poh.vendor_contact_id),
2501          NVL (x_buyer_id, poh.agent_id),
2502          /* Bug 2348331 fixed. swapped the elements in the below
2503             nvl statement in order that the vendor_product_num at
2504             blanket line level takes precedence to that at ASL level.
2505          */
2506          NVL (pol.vendor_product_num, x_vendor_product_num),
2507          poh.global_agreement_flag,
2508          poh.org_id,
2509          -- Bug 3361128: also select the UOM on the doc
2510          pol.unit_meas_lookup_code,
2514          poh.creation_date creation_date
2511          decode(poh.type_lookup_code, 'BLANKET', 1, 'QUOTATION', 2) DocTypeFetchOrder,
2512          decode(pol.unit_meas_lookup_code, p_purchasing_uom, 1,2) MatchUom,
2513          NVL (poh.global_agreement_flag, 'N') global_flag,
2515     FROM po_headers_all poh, --CTO changes FPH
2516          po_lines_all pol --CTO changes FPH
2517    WHERE pol.po_header_id = poh.po_header_id	-- <FPJ Advanced Price> Bug5081434 No Outer Join
2518      AND (   x_destination_doc_type = 'REQ'
2519           OR x_destination_doc_type = 'REQ_NONCATALOG' --<Contract AutoSourcing FPJ>
2520           OR x_destination_doc_type IS NULL
2521           --<Bug 2742147 mbhargav START>
2522           OR (x_destination_doc_type = 'STANDARD PO' and
2523                 (poh.type_lookup_code = 'QUOTATION' OR
2524                 (poh.type_lookup_code = 'BLANKET' AND nvl(poh.global_agreement_flag, 'N') = 'Y'))
2525              )
2526           --<Bug 2742147 mbhargav END>
2527           --for x_dest_doc_type = 'PO'
2528           OR poh.type_lookup_code = 'QUOTATION'
2529          )
2530      AND (   (    poh.type_lookup_code = 'BLANKET'
2531               AND poh.approved_flag = 'Y'
2532               AND NVL (poh.cancel_flag, 'N') = 'N'
2533               AND NVL (poh.frozen_flag, 'N') = 'N'
2534               AND TRUNC (NVL (pol.expiration_date, x_sourcing_date)) >=
2535                                           trunc(x_sourcing_date) -- Bug 2695699
2536               AND
2537                   NVL (poh.user_hold_flag, 'N') = 'N'
2538               AND NVL (poh.closed_code, 'OPEN') NOT IN
2539                                                  ('FINALLY CLOSED', 'CLOSED')
2540               --Bug5258984 (following condition was missed when they rewrote this code for FPJ)
2541               AND NVL (pol.closed_code, 'OPEN') NOT IN
2542                                                   ('FINALLY CLOSED', 'CLOSED')
2543               AND NVL (pol.cancel_flag, 'N') = 'N'
2544              )
2545            OR (    poh.type_lookup_code = 'QUOTATION'
2546               AND (poh.status_lookup_code = 'A')
2547               AND (  NOT EXISTS (
2548                               SELECT 'no shipments exists'
2549                                 FROM po_line_locations_all poll
2550                                WHERE poll.po_line_id = pol.po_line_id
2551 			         )--Bug7384016 added this condition to include quotations without price breaks
2552 	        OR (
2553 	             (poh.approval_required_flag = 'Y')
2554                       AND (   EXISTS (
2555                            SELECT *
2556                            FROM po_quotation_approvals poqa,
2557                                 po_line_locations_all poll --CTO changes FPH
2558                           WHERE poqa.approval_type IS NOT NULL
2559                             AND poqa.line_location_id = poll.line_location_id
2560                             AND poll.po_line_id = pol.po_line_id
2561 			     AND TRUNC (NVL (poll.end_date, x_sourcing_date)) >=
2562                                           trunc(x_sourcing_date)
2563 				     ) --Bug6982267
2564 		           )
2565                      )
2566           OR     (
2567 	           (poh.approval_required_flag = 'N')
2568 	            AND ( EXISTS (
2569 		            SELECT 'valid'
2570 	                    FROM po_line_locations_all poll
2571 			    WHERE poll.po_line_id = pol.po_line_id
2572 			    AND TRUNC (NVL (poll.end_date, x_sourcing_date)) >=
2573                                           trunc(x_sourcing_date)
2574 			         ) --Bug6982267
2575 		         )
2576 		  )
2577 
2578               )
2579 	     )
2580 	  )
2581      AND poh.vendor_id = x_vendor_id
2582      AND poh.type_lookup_code IN ('BLANKET','QUOTATION')
2583      --<Shared Proc FPJ START>
2584      --This clause returns rows if document is GA or
2585      --EITHER vendor_site_sourcing_flag  is N and site_ids match
2586      --OR vendor_site_sourcing_flag is Y and site codes match
2587      AND
2588          (
2589             (NVL (poh.global_agreement_flag, 'N') = 'Y')
2590           OR
2591             (    NVL (poh.global_agreement_flag, 'N') = 'N'
2592               AND (   (    p_vendor_site_sourcing_flag = 'N'
2593                        AND (x_vendor_site_id IS NULL OR
2594                             poh.vendor_site_id = x_vendor_site_id)
2595                       )
2596                    OR
2597                       (    p_vendor_site_sourcing_flag = 'Y'
2598                        AND (p_vendor_site_code IS NULL OR
2599                             poh.vendor_site_id =
2600                             	(select pvs.vendor_site_id
2601                               	 from po_vendor_sites pvs
2602                               	where pvs.vendor_site_code = p_vendor_site_code
2603                               	and   pvs.vendor_id = x_vendor_id))
2604                        )
2605                   )
2606              )
2607          )
2608      --<Shared Proc FPJ END>
2609      AND (x_currency_code IS NULL OR poh.currency_code = x_currency_code)
2610      AND x_sourcing_date >= NVL (poh.start_date, x_sourcing_date - 1)
2611      AND x_sourcing_date <= NVL (poh.end_date, x_sourcing_date + 1)
2612      -- <FPJ Advanced Price START>
2613      AND pol.item_id = x_item_id AND
2614          (NVL(pol.item_revision, -1) = NVL(x_item_rev, -1) OR
2615          (NVL (p_item_rev_control, 1) = 1 AND x_item_rev IS NULL))
2616     -- <FPJ Advanced Price END>
2617              --If document is not a GA then the operating units should match
2618              --If document is GA and vendor site sourcing_flag is Y then
2622      AND (   (    NVL (poh.global_agreement_flag, 'N') = 'N'
2619              --vendor_site_code for current org(as enabled org)  should match
2620              --If the document is GA and vendor site sourcing_flag is N then
2621               --current org should be enabled in GA
2623               AND (x_multi_org = 'N')
2624               AND poh.org_id = p_org_id
2625              )
2626           --<Shared Proc FPJ START>
2627           OR (    NVL (poh.global_agreement_flag, 'N') = 'Y'
2628               AND (   (    p_vendor_site_sourcing_flag = 'Y'
2629                        AND EXISTS (
2630                               SELECT 'vendor site code matches'
2631                                 FROM po_ga_org_assignments poga,
2632                                      po_vendor_sites_all pvsa
2633                                WHERE poh.po_header_id = poga.po_header_id
2634                                  AND poga.organization_id = p_org_id
2635                                  AND poga.vendor_site_id = pvsa.vendor_site_id
2636                                  AND pvsa.vendor_site_code =
2637                                                             p_vendor_site_code
2638                                  AND poga.enabled_flag = 'Y'
2639                                  AND pvsa.vendor_id = x_vendor_id)
2640                       )
2641                    OR (    p_vendor_site_sourcing_flag = 'N'
2642                            --<Bug 3356349 mbhargav START>
2643                            AND
2644                            (
2645                              x_vendor_site_id is null
2646                              OR
2647                              EXISTS (
2648                                  SELECT 'vendor site id matches'
2649                                  FROM po_ga_org_assignments poga
2650                                  WHERE poh.po_header_id = poga.po_header_id
2651                                  AND poga.vendor_site_id = x_vendor_site_id
2652                                  AND poga.enabled_flag = 'Y')
2653                            )
2654                            AND (x_destination_doc_type = 'STANDARD PO'
2655                                OR EXISTS (
2656                                    SELECT 'enabled org exists'
2657                                    FROM po_ga_org_assignments poga
2658                                    WHERE poh.po_header_id = poga.po_header_id
2659                                    AND poga.organization_id = p_org_id
2660                                    AND poga.enabled_flag = 'Y'))
2661                            --<Bug 3356349 mbhargav END>
2662                       )
2663                   )
2664              )
2665           --<Shared Proc FPJ END>
2666           OR x_multi_org = 'Y'
2667          ) -- FPI GA
2668 UNION ALL
2669 SELECT   poh.po_header_id,
2670          to_number(NULL),
2671          to_number(NULL),
2672          poh.type_lookup_code,
2673          NVL (x_vendor_site_id, poh.vendor_site_id),
2674          NVL (x_vendor_contact_id, poh.vendor_contact_id),
2675          NVL (x_buyer_id, poh.agent_id),
2676          /* Bug 2348331 fixed. swapped the elements in the below
2677             nvl statement in order that the vendor_product_num at
2678             blanket line level takes precedence to that at ASL level.
2679          */
2680          x_vendor_product_num, --Bug5081434
2681          poh.global_agreement_flag,
2682          poh.org_id,
2683          -- Bug 3361128: also select the UOM on the doc
2684          to_char(NULL),  --Bug5081434
2685          3 DocTypeFetchOrder,
2686          2 MatchUom,
2687          NVL (poh.global_agreement_flag, 'N') global_flag,
2688          poh.creation_date creation_date
2689     FROM po_headers_all poh
2690    WHERE (   x_destination_doc_type = 'REQ'
2691           OR x_destination_doc_type = 'REQ_NONCATALOG' --<Contract AutoSourcing FPJ>
2692           OR x_destination_doc_type IS NULL
2693          )
2694     	 AND (( NVL(FND_PROFILE.VALUE('ALLOW_REFERENCING_CPA_UNDER_AMENDMENT'),'N') =  'Y' --<R12 GCPA ER>
2695 		 		and poh.approved_date is not null)
2696 		 		OR
2697 		 		nvl(poh.approved_flag,'N') = 'Y'
2698 		 		)
2699      AND NVL(poh.cancel_flag,'N') = 'N'
2700      AND NVL(poh.frozen_flag,'N') = 'N'
2701      AND NVL(poh.closed_code, 'OPEN') = 'OPEN'
2702      AND p_return_contract = 'Y'
2703      AND poh.vendor_id = x_vendor_id
2704      AND poh.type_lookup_code = 'CONTRACT'
2705      AND
2706          (
2707             (NVL (poh.global_agreement_flag, 'N') = 'Y')
2708           OR
2709             (    NVL (poh.global_agreement_flag, 'N') = 'N'
2710               AND (   (    p_vendor_site_sourcing_flag = 'N'
2711                        AND (x_vendor_site_id IS NULL OR
2712                             poh.vendor_site_id = x_vendor_site_id)
2713                       )
2714                    OR
2715                       (    p_vendor_site_sourcing_flag = 'Y'
2716                        AND (p_vendor_site_code IS NULL OR
2717                             poh.vendor_site_id =
2718                             	(select pvs.vendor_site_id
2719                               	 from po_vendor_sites pvs
2720                               	where pvs.vendor_site_code = p_vendor_site_code
2721                               	and   pvs.vendor_id = x_vendor_id))
2722                        )
2723                   )
2724              )
2725          )
2726      --<Shared Proc FPJ END>
2727      AND (x_currency_code IS NULL OR poh.currency_code = x_currency_code)
2731      AND (   (    NVL (poh.global_agreement_flag, 'N') = 'N'
2728      AND x_sourcing_date >= NVL (poh.start_date, x_sourcing_date - 1)
2729      AND x_sourcing_date <= NVL (poh.end_date, x_sourcing_date + 1)
2730 
2732               AND (x_multi_org = 'N')
2733               AND poh.org_id = p_org_id
2734              )
2735           --<Shared Proc FPJ START>
2736           OR (    NVL (poh.global_agreement_flag, 'N') = 'Y'
2737               AND (   (    p_vendor_site_sourcing_flag = 'Y'
2738                        AND (p_vendor_site_code IS NULL OR
2739                            EXISTS (
2740                               SELECT 'vendor site code matches'
2741                                 FROM po_ga_org_assignments poga,
2742                                      po_vendor_sites_all pvsa
2743                                WHERE poh.po_header_id = poga.po_header_id
2744                                  AND poga.organization_id = p_org_id
2745                                  AND poga.vendor_site_id = Decode( Nvl (poh.Enable_All_Sites,'N'),'N',pvsa.vendor_site_id,poga.Vendor_Site_Id) --<FPJGCPA> pvsa.vendor_site_id
2746                                  AND pvsa.vendor_site_code =
2747                                                             p_vendor_site_code
2748                                  AND poga.enabled_flag = 'Y'
2749                                  AND pvsa.vendor_id = x_vendor_id))
2750                       )
2751                    OR (    p_vendor_site_sourcing_flag = 'N'
2752                            --<Bug 3356349 mbhargav START>
2753                            AND
2754                            (
2755                              x_vendor_site_id is null
2756                              OR
2757                              EXISTS (
2758                                  SELECT 'vendor site id matches'
2759                                  FROM po_ga_org_assignments poga
2760                                  WHERE poh.po_header_id = poga.po_header_id
2761                                  AND poga.vendor_site_id = decode( Nvl (poh.Enable_All_Sites,'N'),'Y',poga.Vendor_Site_Id,x_vendor_site_id) --< R12 GCPA ER>
2762                                  AND poga.enabled_flag = 'Y')
2763                            )
2764                            AND (x_destination_doc_type = 'STANDARD PO'
2765                                OR EXISTS (
2766                                    SELECT 'enabled org exists'
2767                                    FROM po_ga_org_assignments poga
2768                                    WHERE poh.po_header_id = poga.po_header_id
2769                                    AND poga.organization_id = p_org_id
2770                                    AND poga.enabled_flag = 'Y'))
2771                            --<Bug 3356349 mbhargav END>
2772                       )
2773                   )
2774              )
2775           --<Shared Proc FPJ END>
2776           OR x_multi_org = 'Y'
2777          )  -- FPI GA
2778 ORDER BY
2779          DocTypeFetchOrder Asc,
2780          MatchUom Asc,
2781          global_flag Asc,
2782          creation_date DESC;
2783 
2784 /* Bug#4263138 */
2785     /*
2786      * Non-Catalog items in this case refers to any item that does not have an
2787      * item_id reference - includes, iP Non-Catalog item, Punchout item, POs without
2788      * item reference. For all these cases, the autosourcing is always done only
2789      * to a Contract agreement. So the join to po_lines_all, check for blankets/quotes
2790      * are not needed in the sql. This makes the sql more optimized for these
2791      * onetime/non-catalog item.(Also  vendor_site_sourcing_flag is 'N')
2792      */
2793      -- Bug 5074119
2794      -- Added an extra condition on type_lookup_code to improve the performance
2795      CURSOR L_GET_LATEST_DOCS_NONCAT_CSR(
2796  		       p_purchasing_uom 	IN 	VARCHAR2) is
2797      SELECT   poh.po_header_id,
2798          NULL po_line_id,
2799          NULL line_num, -- Only Contracts are returned
2800          poh.type_lookup_code,
2801          NVL (x_vendor_site_id, poh.vendor_site_id),
2802          NVL (x_vendor_contact_id, poh.vendor_contact_id),
2803          NVL (x_buyer_id, poh.agent_id),
2804          /* Bug 2348331 fixed. swapped the elements in the below
2805             nvl statement in order that the vendor_product_num at
2806             blanket line level takes precedence to that at ASL level.
2807          */
2808          x_vendor_product_num,
2809          poh.global_agreement_flag,
2810          poh.org_id,
2811          NULL unit_meas_lookup_code
2812     FROM po_headers_all poh --CTO changes FPH
2813    WHERE
2814      (   x_destination_doc_type = 'REQ'
2815           OR x_destination_doc_type = 'REQ_NONCATALOG' --<Contract AutoSourcing FPJ>
2816           OR x_destination_doc_type IS NULL
2817           --<Bug 2742147 mbhargav START>
2818      )
2819      AND (
2820             (    poh.type_lookup_code = 'CONTRACT'
2821         	 AND (( NVL(FND_PROFILE.VALUE('ALLOW_REFERENCING_CPA_UNDER_AMENDMENT'),'N') =  'Y' --<R12 GCPA ER>
2822 			 		and poh.approved_date is not null)
2823 			 		OR
2824 			 		nvl(poh.approved_flag,'N') = 'Y'
2825 			 		)
2826               AND NVL(poh.cancel_flag,'N') = 'N'
2827               AND NVL(poh.frozen_flag,'N') = 'N'
2828               AND NVL(poh.closed_code, 'OPEN') = 'OPEN'
2829               AND p_return_contract = 'Y'	--<Contract AutoSourcing FPJ>
2830              )
2831          )
2832      AND poh.vendor_id = x_vendor_id
2833      --<Shared Proc FPJ START>
2834      --This clause returns rows if document is GA or
2838          (
2835      --EITHER vendor_site_sourcing_flag  is N and site_ids match
2836      --OR vendor_site_sourcing_flag is Y and site codes match
2837      AND
2839             (NVL (poh.global_agreement_flag, 'N') = 'Y')
2840           OR
2841             (    NVL (poh.global_agreement_flag, 'N') = 'N'
2842               AND (   (    p_vendor_site_sourcing_flag = 'N'
2843                        AND (x_vendor_site_id IS NULL OR
2844                             poh.vendor_site_id = x_vendor_site_id)
2845                       )
2846                   )
2847              )
2848          )
2849      --<Shared Proc FPJ END>
2850      AND (x_currency_code IS NULL OR poh.currency_code = x_currency_code)
2851      AND x_sourcing_date >= NVL (poh.start_date, x_sourcing_date - 1)
2852      AND x_sourcing_date <= NVL (poh.end_date, x_sourcing_date + 1)
2853              --If document is not a GA then the operating units should match
2854              --If document is GA and vendor site sourcing_flag is Y then
2855              --vendor_site_code for current org(as enabled org)  should match
2856              --If the document is GA and vendor site sourcing_flag is N then
2857               --current org should be enabled in GA
2858      AND (   (    NVL (poh.global_agreement_flag, 'N') = 'N'
2859               AND (x_multi_org = 'N')
2860               AND NVL (poh.org_id, -1) = NVL (p_org_id, -1)
2861              )
2862           --<Shared Proc FPJ START>
2863           OR (    NVL (poh.global_agreement_flag, 'N') = 'Y'
2864               AND (
2865                    (    p_vendor_site_sourcing_flag = 'N'
2866                            --<Bug 3356349 mbhargav START>
2867                            AND
2868                            (
2869                              x_vendor_site_id is null
2870                              OR
2871                              EXISTS (
2872                                  SELECT 'vendor site id matches'
2873                                  FROM po_ga_org_assignments poga
2874                                  WHERE poh.po_header_id = poga.po_header_id
2875                                  AND poga.vendor_site_id = decode( Nvl (poh.Enable_All_Sites,'N'),'Y',poga.Vendor_Site_Id,x_vendor_site_id) --< R12 GCPA ER>
2876                                  AND poga.enabled_flag = 'Y')
2877                            )
2878                            --<Bug 3356349 mbhargav END>
2879                       )
2880                   )
2881              )
2882           --<Shared Proc FPJ END>
2883           OR x_multi_org = 'Y'
2884          ) -- FPI GA
2885 ORDER BY
2886          -- <FPJ Advanced Price START>
2887          decode(poh.type_lookup_code, 'BLANKET', 1, 'QUOTATION', 2, 'CONTRACT', 3) ASC,
2888          -- <FPJ Advanced Price END>
2889          NVL (poh.global_agreement_flag, 'N') ASC,
2890          poh.creation_date DESC;           -- Bug# 1560250
2891 
2892   --<Bug#4936992 Start>
2893   --Created dummy variables so that when we call the asl_sourcing procedure, we can ignore the
2894   --values returned by the procedure. We are interested only in asl_id and do not want the
2895   --source document related info.
2896   l_dummy_cons_from_sup_flag    PO_ASL_ATTRIBUTES.consigned_from_supplier_flag%type := NULL;
2897   l_dummy_enable_vmi_flag       PO_ASL_ATTRIBUTES.enable_vmi_flag%type := NULL;
2898   l_dummy_sequence_number       PO_ASL_DOCUMENTS.sequence_num%type := NULL;
2899   l_dummy_vendor_product_num    PO_REQUISITIONS_INTERFACE_ALL.suggested_vendor_item_num%type := x_vendor_product_num;
2900   l_dummy_asl_purchasing_uom    PO_REQUISITIONS_INTERFACE_ALL.unit_of_measure%type := x_purchasing_uom;
2901   l_dummy_category_id           PO_REQUISITIONS_INTERFACE_ALL.category_id%type := p_category_id;
2902   l_dummy_using_organization_id FINANCIALS_SYSTEM_PARAMS_ALL.inventory_organization_id%type := p_using_organization_id;
2903   --<Bug#4936992 End>
2904 BEGIN
2905 
2906     l_progress := '010';
2907     l_using_organization_id  := p_using_organization_id;
2908     IF g_debug_stmt THEN
2909       PO_DEBUG.debug_var(l_log_head,l_progress,'g_root_invoking_module', g_root_invoking_module);
2910     END IF;
2911 
2912     IF p_vendor_site_sourcing_flag = 'N' THEN
2913 
2914             l_progress := '011';
2915             get_asl_info(
2916                          x_item_id 		=>x_item_id,
2917                          x_vendor_id		=>x_vendor_id,
2918 	                  x_vendor_site_id 	=>x_vendor_site_id,
2919                          x_using_organization_id=>l_using_organization_id,
2920                          x_asl_id 		=>x_local_asl_id,
2921                          x_vendor_product_num 	=>x_vendor_product_num,
2922                          x_purchasing_uom   	=>x_asl_purchasing_uom,
2923                          p_category_id          =>p_category_id  --<Contract AutoSourcing FPJ>
2924             );
2925 
2926             l_progress := '012';
2927             IF g_debug_stmt THEN
2928                PO_DEBUG.debug_stmt(l_log_head,l_progress,'get_asl_info returned:');
2929                PO_DEBUG.debug_var(l_log_head,l_progress,'asl_id obtained', x_local_asl_id);
2930             END IF;
2931 
2932            --Changed the order here. Giving preference to UOM passed in
2933            --over the ASL UOM as the profile says not to look at ASLs
2934 
2935            -- Bug 3361128: the above comment is not correct. The ASL UOM
2936            -- (if there's any) has the precedence over the UOM passed in.
2937            -- Did not change the assignment here, because it will be used
2938            -- in the cursor below to order source docs. Assign the UOM
2939            -- value to be passed back later in the procedure
2943      -- We need the asl_id even when the PO: Automatic Document Sourcing is set to Y
2940 	   x_purchasing_uom := nvl(x_purchasing_uom, x_asl_purchasing_uom);
2941 
2942      --<Bug#4936992 Start>
2944      -- only when we are calling the sourcing logic from Req Import. The reasoning
2945      -- behind the above rule is that irrespective of the above mentioned profile
2946      -- option, we want to get the Order Modifiers from the ASL.
2947     ELSIF g_root_invoking_module = 'REQIMPORT' THEN
2948 
2949            l_progress := '013';
2950            --This procedure does the sourcing of document based on ASL
2951            --This returns asl_id to use. But we ignore all the sourcing
2952            --document related info and just consider asl id.
2953            asl_sourcing(
2954                         p_item_id           => x_item_id,
2955                         p_vendor_id         => x_vendor_id,
2956                         p_vendor_site_code  => p_vendor_site_code,
2957                         p_item_rev          => x_item_rev,
2958                         p_item_rev_control  => p_item_rev_control,
2959                         p_sourcing_date     => x_sourcing_date,
2960                         p_currency_code     => x_currency_code,
2961                         p_org_id            => p_org_id,
2962                         p_using_organization_id => l_dummy_using_organization_id,
2963                         x_asl_id             =>  x_local_asl_id,
2964                         x_vendor_product_num => l_dummy_vendor_product_num,
2965                         x_purchasing_uom     => l_dummy_asl_purchasing_uom,
2966                         x_consigned_from_supplier_flag =>l_dummy_cons_from_sup_flag,
2967                         x_enable_vmi_flag      => l_dummy_enable_vmi_flag,
2968                         x_sequence_num         => l_dummy_sequence_number,
2969                         p_category_id          => l_dummy_category_id);
2970 
2971            l_progress := '014';
2972            IF g_debug_stmt THEN
2973               PO_DEBUG.debug_stmt(l_log_head,l_progress,'asl_sourcing returned:');
2974               PO_DEBUG.debug_var(l_log_head,l_progress,'asl_id obtained', x_local_asl_id);
2975            END IF;
2976            IF (x_local_asl_id IS NULL
2977                AND trunc(x_sourcing_date) <> trunc(sysdate)) THEN
2978 
2979                --Call ASL_SOURCING again this time passing SYSDATE as SOURCING_DATE
2980                l_progress := '015';
2981                x_sourcing_date := trunc(sysdate);
2982                asl_sourcing(
2983                             p_item_id           => x_item_id,
2984                             p_vendor_id         => x_vendor_id,
2985                             p_vendor_site_code  => p_vendor_site_code,
2986                             p_item_rev          => x_item_rev,
2987                             p_item_rev_control  => p_item_rev_control,
2988                             p_sourcing_date     => x_sourcing_date,
2989                             p_currency_code     => x_currency_code,
2990                             p_org_id            => p_org_id,
2991                             p_using_organization_id => l_dummy_using_organization_id,
2992                             x_asl_id             =>  x_local_asl_id,
2993                             x_vendor_product_num => l_dummy_vendor_product_num,
2994                             x_purchasing_uom     => l_dummy_asl_purchasing_uom,
2995                             x_consigned_from_supplier_flag =>l_dummy_cons_from_sup_flag,
2996                             x_enable_vmi_flag      => l_dummy_enable_vmi_flag,
2997                             x_sequence_num         => l_dummy_sequence_number,
2998                             p_category_id          => l_dummy_category_id);
2999 
3000                l_progress := '016';
3001                IF g_debug_stmt THEN
3002                  PO_DEBUG.debug_stmt(l_log_head,l_progress,'asl_sourcing with passing SYSDATE as SOURCING_DATE returned:');
3003                  PO_DEBUG.debug_var(l_log_head,l_progress,'asl_id obtained', x_local_asl_id);
3004                END IF;
3005 
3006             END IF;
3007     --<Bug#4936992 End>
3008     END IF;
3009     --<Bug#4936992 Start>
3010     l_progress := '017';
3011     IF g_root_invoking_module = 'REQIMPORT' THEN
3012       x_asl_id := x_local_asl_id;
3013     END IF;
3014     IF g_debug_stmt THEN
3015        PO_DEBUG.debug_var(l_log_head,l_progress,'asl_id being returned', x_asl_id);
3016     END IF;
3017 
3018     --<Bug#4936992 End>
3019 
3020         l_progress := '020';
3021 
3022       /* Bug#4263138 */
3023       if( (x_destination_doc_type = 'REQ' OR x_destination_doc_type = 'REQ_NONCATALOG')
3024             AND  x_item_id is null) then
3025         l_noncat_item := TRUE;
3026       else
3027         l_noncat_item := FALSE;
3028       end if;
3029 
3030       if (l_noncat_item) then
3031         OPEN  L_GET_LATEST_DOCS_NONCAT_CSR(x_purchasing_uom);
3032       else
3033         OPEN  L_GET_LATEST_DOCS_CSR(x_purchasing_uom);
3034       end if;
3035 
3036       LOOP
3037       if (l_noncat_item) then
3038        FETCH L_GET_LATEST_DOCS_NONCAT_CSR into x_document_header_id,
3039                                             x_document_line_id,
3040                                             x_document_line_num,
3041                                             x_document_type_code,
3042                                             x_vendor_site_id,
3043                                             x_vendor_contact_id,
3044                                             x_buyer_id,
3048                                             l_source_doc_purchasing_uom; -- Bug 3361128
3045                                             x_vendor_product_num,
3046                                             l_global_agreement_flag,
3047                                             l_document_org_id,
3049          EXIT WHEN L_GET_LATEST_DOCS_NONCAT_CSR%NOTFOUND;
3050       ELSE
3051        FETCH L_GET_LATEST_DOCS_CSR into x_document_header_id,
3052                                             x_document_line_id,
3053                                             x_document_line_num,
3054                                             x_document_type_code,
3055                                             x_vendor_site_id,
3056                                             x_vendor_contact_id,
3057                                             x_buyer_id,
3058                                             x_vendor_product_num,
3059                                             l_global_agreement_flag,
3060                                             l_document_org_id,
3061                                             l_source_doc_purchasing_uom, -- Bug 3361128
3062                                             l_doc_type_fetch_order, -- Bug 5081434
3063                                             l_uom_match,     -- Bug 5081434
3064                                             l_global_flag,   -- Bug 5081434
3065                                             l_creation_date; -- bug5081434
3066 
3067 
3068          EXIT WHEN L_GET_LATEST_DOCS_CSR%NOTFOUND;
3069         END IF;
3070 
3071          l_progress := '030';
3072 
3073            /* FPI GA start */
3074            if x_document_header_id is not null then
3075 
3076        --<R12 STYLES PHASE II START>
3077         -- Validate whether the Sourced Docuemnt is Style Compatible
3078            IF g_debug_stmt THEN
3079               PO_DEBUG.debug_stmt(l_log_head,l_progress,'style validate source doc');
3080               PO_DEBUG.debug_var(l_log_head,l_progress,'x_destination_doc_type', x_destination_doc_type);
3081               PO_DEBUG.debug_var(l_log_head,l_progress,'x_document_type_code', x_document_type_code);
3082            END IF;
3083         l_eligible_doc_flag := TRUE;
3084 	  --in case the sourcing is happening without passing any attributes as in pricing only mode
3085 	  --check if all the attributes are NULL
3086 	  --in such a case bypass the style validation checks
3087         IF    p_line_type_id IS NULL
3088 	     AND p_purchase_basis IS NULL
3089 	     AND p_destination_type IS NULL
3090 	     AND p_style_id IS NULL  then
3091 
3092               l_eligible_doc_flag := TRUE;
3093               IF g_debug_stmt THEN
3094                  PO_DEBUG.debug_stmt(l_log_head,l_progress,'bypass style validations');
3095               END IF;
3096 
3097        else --if attributes are passed then do style validation checks
3098 
3099                IF g_debug_stmt THEN
3100                  PO_DEBUG.debug_stmt(l_log_head,l_progress,'do style validations');
3101               END IF;
3102 
3103         if x_destination_doc_type IN ('REQ','REQ_NONCATALOG') then
3104           if (x_document_type_code IN ('BLANKET', 'CONTRACT')) then
3105 
3106                 PO_DOC_STYLE_PVT.style_validate_req_attrs(p_api_version      => 1.0,
3107                                                           p_init_msg_list    => FND_API.G_TRUE,
3108                                                           x_return_status    => l_return_status,
3109                                                           x_msg_count        => l_msg_count,
3110                                                           x_msg_data         => l_msg_data,
3111                                                           p_doc_style_id     => null,
3112                                                           p_document_id      => x_document_header_id,
3113                                                           p_line_type_id     => p_line_type_id,
3114                                                           p_purchase_basis   => p_purchase_basis,
3115                                                           p_destination_type => p_destination_type,
3116                                                           p_source           => 'REQUISITION'
3117                                                           );
3118 
3119              if l_return_status <> FND_API.g_ret_sts_success THEN
3120                 l_eligible_doc_flag := FALSE;
3121              end if;
3122           end if;
3123 
3124         else  -- x_destination_doc_type = 'STANDARD PO','PO' OR NULL
3125 
3126           If (p_style_id <>
3127              PO_DOC_STYLE_PVT.get_doc_style_id(x_document_header_id)) THEN
3128              l_eligible_doc_flag := FALSE;
3129           end if;
3130 
3131         end if; -- x_destination_doc_type = 'STANDARD PO','PO' OR NULL
3132       end if;  -- if   p_line_type_id IS NULL
3133 
3134         --<R12 STYLES PHASE II END>
3135 
3136 
3137         if l_eligible_doc_flag then           --<R12 STYLES PHASE II>
3138 
3139               GET_SITE_ID_IF_ITEM_ON_DOC_OK(
3140                   p_document_header_id        => x_document_header_id,
3141                   p_item_id                   => x_item_id,
3142                   p_vendor_site_sourcing_flag => p_vendor_site_sourcing_flag,
3143                   p_global_agreement_flag     => l_global_agreement_flag,
3144                   p_document_org_id           => l_document_org_id,
3145                   x_return_status             => x_return_status,
3146                   x_vendor_site_id            => x_vendor_site_id,
3150 		);
3147                   x_vendor_contact_id         => x_vendor_contact_id,
3148 	          p_destination_doc_type      => x_destination_doc_type, --<Bug 3356349>
3149 		  p_multi_org                 => x_multi_org --<CTO Bug 4222144>
3151 
3152               IF x_return_status = FND_API.G_RET_STS_SUCCESS then
3153                                    l_progress := '040';
3154                  IF g_debug_stmt THEN
3155                     PO_DEBUG.debug_stmt(l_log_head,l_progress,'Found a document:');
3156                     PO_DEBUG.debug_var(l_log_head,l_progress,'Total Documents looked at', L_GET_LATEST_DOCS_CSR%ROWCOUNT);
3157                     PO_DEBUG.debug_var(l_log_head,l_progress,'x_document_header_id', x_document_header_id);
3158                     PO_DEBUG.debug_var(l_log_head,l_progress,'x_document_line_id', x_document_line_id);
3159                     PO_DEBUG.debug_var(l_log_head,l_progress,'l_vendor_site_id', x_vendor_site_id);
3160                  END IF;
3161                                    exit;
3162               END IF;
3163          end if; -- if l_eligible_doc_flag --<R12 STYLES PHASE II>
3164                   l_progress := '050';
3165 
3166                   /* Bug 2752091 : If the item is not valid in the current OU
3167                      we null out the doc info that was already fetched so that
3168                      it does not get returned to the form */
3169                   x_document_header_id := null;
3170                   x_document_line_id   := null;
3171                   x_document_line_num  := null;
3172                   x_document_type_code :=  null;
3173 
3174             else
3175                exit;
3176             end if; --if x_document_header_id is not null then
3177           /* FPI GA end */
3178 
3179       END LOOP;
3180       if (l_noncat_item) then
3181         CLOSE L_GET_LATEST_DOCS_NONCAT_CSR;
3182       else
3183         CLOSE L_GET_LATEST_DOCS_CSR;
3184       end if;
3185 
3186       l_progress := '060';
3187 
3188 /* Bug 2373004 {
3189    If there is no document which is valid on need-by-date then try to locate
3190    a document which is valid at least on current date.  For consistency with
3191    ASL-based sourcing, coding this behaviour in automatic sourcing as well. */
3192 
3193       IF ( x_document_header_id is NULL
3194          AND trunc(x_sourcing_date) <> trunc(sysdate)) THEN
3195 
3196           x_sourcing_date := trunc(sysdate);
3197 
3198           l_progress := '070';
3199 
3200       if (l_noncat_item) then
3201           OPEN  L_GET_LATEST_DOCS_NONCAT_CSR(x_purchasing_uom);
3202       else
3203           OPEN  L_GET_LATEST_DOCS_CSR(x_purchasing_uom);
3204       end if;
3205           LOOP
3206       if (l_noncat_item) then
3207            FETCH L_GET_LATEST_DOCS_NONCAT_CSR into x_document_header_id,
3208                                             x_document_line_id,
3209                                             x_document_line_num,
3210                                             x_document_type_code,
3211                                             x_vendor_site_id,
3212                                             x_vendor_contact_id,
3213                                             x_buyer_id,
3214                                             x_vendor_product_num,
3215                                             l_global_agreement_flag,
3216                                             l_document_org_id,
3217                                             l_source_doc_purchasing_uom; -- Bug 3361128
3218              EXIT WHEN L_GET_LATEST_DOCS_NONCAT_CSR%NOTFOUND;
3219       else
3220            FETCH L_GET_LATEST_DOCS_CSR into x_document_header_id,
3221                                             x_document_line_id,
3222                                             x_document_line_num,
3223                                             x_document_type_code,
3224                                             x_vendor_site_id,
3225                                             x_vendor_contact_id,
3226                                             x_buyer_id,
3227                                             x_vendor_product_num,
3228                                             l_global_agreement_flag,
3229                                             l_document_org_id,
3230                                             l_source_doc_purchasing_uom, -- Bug 3361128
3231                                             l_doc_type_fetch_order, -- Bug 5081434
3232                                             l_uom_match,     -- Bug 5081434
3233                                             l_global_flag,   -- Bug 5081434
3234                                             l_creation_date; -- bug5081434
3235 
3236              EXIT WHEN L_GET_LATEST_DOCS_CSR%NOTFOUND;
3237       end if;
3238 
3239 
3240               /* FPI GA start */
3241               if x_document_header_id is not null then
3242          --<R12 STYLES PHASE II START>
3243           -- Validate whether the Sourced Docuemnt is Style Compatible
3244            IF g_debug_stmt THEN
3245               PO_DEBUG.debug_stmt(l_log_head,l_progress,'style validate source doc');
3246               PO_DEBUG.debug_var(l_log_head,l_progress,'x_destination_doc_type', x_destination_doc_type);
3247               PO_DEBUG.debug_var(l_log_head,l_progress,'x_document_type_code', x_document_type_code);
3248            END IF;
3249           l_eligible_doc_flag := TRUE;
3250 
3251 	  --in case the sourcing is happening without passing any attributes as in pricing only mode
3252 	  --check if all the attributes are NULL
3253 	  --in such a case bypass the style validation checks
3257 	     AND p_style_id IS NULL  then
3254         if   p_line_type_id IS NULL
3255 	     AND p_purchase_basis IS NULL
3256 	     AND p_destination_type IS NULL
3258 
3259               l_eligible_doc_flag := TRUE;
3260               IF g_debug_stmt THEN
3261                  PO_DEBUG.debug_stmt(l_log_head,l_progress,'bypass style validations');
3262               END IF;
3263 
3264        else --if attributes are passed then do style validation checks
3265 
3266                IF g_debug_stmt THEN
3267                  PO_DEBUG.debug_stmt(l_log_head,l_progress,'do style validations');
3268               END IF;
3269 
3270         if x_destination_doc_type IN ('REQ','REQ_NONCATALOG') then
3271             if (x_document_type_code IN ('BLANKET', 'CONTRACT')) then
3272                 PO_DOC_STYLE_PVT.style_validate_req_attrs(p_api_version      => 1.0,
3273                                                           p_init_msg_list    => FND_API.G_TRUE,
3274                                                           x_return_status    => l_return_status,
3275                                                           x_msg_count        => l_msg_count,
3276                                                           x_msg_data         => l_msg_data,
3277                                                           p_doc_style_id     => null,
3278                                                           p_document_id      => x_document_header_id,
3279                                                           p_line_type_id     => p_line_type_id,
3280                                                           p_purchase_basis   => p_purchase_basis,
3281                                                           p_destination_type => p_destination_type,
3282                                                           p_source           => 'REQUISITION'
3283                                                           );
3284 
3285              if l_return_status <> FND_API.g_ret_sts_success THEN
3286                 l_eligible_doc_flag := FALSE;
3287              end if;
3288 
3289             end if;
3290 
3291         else  -- x_destination_doc_type = 'STANDARD PO','PO' OR NULL
3292 
3293             If (p_style_id <>
3294                PO_DOC_STYLE_PVT.get_doc_style_id(x_document_header_id)) THEN
3295               l_eligible_doc_flag := FALSE;
3296             end if;
3297 
3298           end if; -- x_destination_doc_type = 'STANDARD PO','PO' OR NULL
3299         end if;  -- if   p_line_type_id IS NULL
3300           --<R12 STYLES PHASE II END>
3301 
3302           if l_eligible_doc_flag then       --<R12 STYLES PHASE II>
3303 
3304 
3305               GET_SITE_ID_IF_ITEM_ON_DOC_OK(
3306                   p_document_header_id        => x_document_header_id,
3307                   p_item_id                   => x_item_id,
3308                   p_vendor_site_sourcing_flag => p_vendor_site_sourcing_flag,
3309                   p_global_agreement_flag     => l_global_agreement_flag,
3310                   p_document_org_id           => l_document_org_id,
3311                   x_return_status             => x_return_status,
3312                   x_vendor_site_id            => x_vendor_site_id,
3313                   x_vendor_contact_id         => x_vendor_contact_id,
3314 	          p_destination_doc_type      => x_destination_doc_type, --<Bug 3356349>
3315 	          p_multi_org                 => x_multi_org --<CTO Bug 4222144>
3316 		);
3317 
3318               IF x_return_status = FND_API.G_RET_STS_SUCCESS then
3319                              l_progress := '080';
3320                  IF g_debug_stmt THEN
3321                     PO_DEBUG.debug_stmt(l_log_head,l_progress,'Found a document with sysdate:');
3322                     PO_DEBUG.debug_var(l_log_head,l_progress,'Total Documents looked at', L_GET_LATEST_DOCS_CSR%ROWCOUNT);
3323                     PO_DEBUG.debug_var(l_log_head,l_progress,'x_document_header_id', x_document_header_id);
3324                     PO_DEBUG.debug_var(l_log_head,l_progress,'x_document_line_id', x_document_line_id);
3325                     PO_DEBUG.debug_var(l_log_head,l_progress,'l_vendor_site_id', x_vendor_site_id);
3326                  END IF;
3327                              exit;
3328                END IF;
3329           end if; -- if l_eligible_doc_flag --<R12 STYLES PHASE II>
3330                   l_progress := '090';
3331 
3332                   /* Bug 2752091 : If the item is not valid in the current OU
3333                      we null out the doc info that was already fetched so that
3334                      it does not get returned to the form */
3335                   x_document_header_id := null;
3336                   x_document_line_id   := null;
3337                   x_document_line_num  := null;
3338                   x_document_type_code :=  null;
3339                   l_source_doc_purchasing_uom :=  null;   --<R12 STYLES PHASE II>
3340 
3341             else
3342                exit;
3343             end if;
3344               /* FPI GA end */
3345 
3346          END LOOP;
3347       if (l_noncat_item) then
3348          CLOSE L_GET_LATEST_DOCS_NONCAT_CSR;
3349       else
3350          CLOSE L_GET_LATEST_DOCS_CSR;
3351       end if;
3352 
3353       END IF;
3354 
3355       -- Bug 3361128: pass back the UOM on the source doc (if any);
3356       -- also, the ASL UOM takes precedence over the UOM passed in
3357       x_purchasing_uom := nvl(nvl(l_source_doc_purchasing_uom, x_asl_purchasing_uom),
3358                               x_purchasing_uom);
3359 
3360       l_progress := '100';
3361 
3362 EXCEPTION
3363     WHEN OTHERS THEN
3367 
3364          IF g_debug_unexp THEN
3365             PO_DEBUG.debug_exc(l_log_head,l_progress);
3366          END IF;
3368         PO_MESSAGE_S.SQL_ERROR('GET_LATEST_DOCUMENT', l_progress, sqlcode);
3369 END get_latest_document;
3370 
3371 --<Shared Proc FPJ START>
3372 -------------------------------------------------------------------------------
3373 --Start of Comments
3374 --Name: GET_SITE_ID_IF_ITEM_ON_DOC_OK
3375 --Pre-reqs:
3376 --  None
3377 --Modifies:
3378 --  None.
3379 --Locks:
3380 --  None.
3381 --Function:
3382 --  This function does ITEM validation checks on GA OU, ROU and POU.
3383 --  If item is valid and p_vendor_site_sourcing_flag = 'Y' then
3384 --  this procedure returns the vendor_site_id
3385 --Parameters:
3386 --IN:
3387 --p_document-header_id
3388 --  The source doc unique identifier
3389 --p_item_id
3390 --  item_id of item on source doc
3391 --p_vendor_site_sourcing_flag
3392 --  Flag which determines if vendor_site_id needs to be derived
3393 --p_global_agreement_flag
3394 --  flag indicating if the document passed in is GA
3395 --p_document_org_id
3396 --  Operating Unit ID of the source document
3397 --p_multi_org
3398 --  Flag indicating if its CTO call
3399 --IN OUT
3400 --x_vendor_site_id
3401 --  The site id derived from Source DOc
3402 --x_vendor_contact_id
3403 --  contact id is returned if there is unique contact defined
3404 --OUT:
3405 --x_return_status
3406 --  Tells whether item is valid and the outcome of the call
3407 --Testing:
3408 --  None
3409 --End of Comments
3410 -------------------------------------------------------------------------------
3411 procedure GET_SITE_ID_IF_ITEM_ON_DOC_OK(
3412                    p_document_header_id        IN NUMBER,
3413                    p_item_id                   IN NUMBER,
3414                    p_vendor_site_sourcing_flag IN VARCHAR2,
3415                    p_global_agreement_flag     IN VARCHAR2,
3416                    p_document_org_id           IN NUMBER,
3417                    x_return_status             OUT NOCOPY VARCHAR2,
3418                    x_vendor_site_id            IN OUT NOCOPY NUMBER,
3419                    x_vendor_contact_id         IN OUT NOCOPY NUMBER,
3420 		   p_destination_doc_type      IN VARCHAR2, --<Bug 3356349>
3421                    p_multi_org                 IN VARCHAR2 --<CTO Bug 4222144>
3422 					) IS
3423 
3424 l_is_item_valid            BOOLEAN := FALSE;
3425 l_is_org_valid  BOOLEAN := FALSE;
3426 l_item_revision            PO_LINES_ALL.item_revision%TYPE;
3427 x_vendor_contact_name      PO_VENDOR_CONTACTS.last_name%TYPE;
3428 l_current_org_id           PO_HEADERS_ALL.org_id%TYPE;
3429 l_purchasing_org_id        PO_HEADERS_ALL.org_id%TYPE; --<Bug 3356349>
3430 l_progress                 VARCHAR2(3) := '000';
3431 l_log_head     CONSTANT VARCHAR2(100) := g_log_head||'get_site_id_if_item_on_doc_ok';
3432 BEGIN
3433 
3434      l_progress := '010';
3435      --<CTO Bug 4222144 START>
3436      --No need to do item validity checks for CTO call
3437      IF p_multi_org = 'Y' THEN
3438 	x_return_status := FND_API.G_RET_STS_SUCCESS;
3439 	RETURN;
3440      END IF;
3441      --<CTO Bug 4222144 END>
3442 
3443      IF p_global_agreement_flag = 'Y' THEN
3444 
3445         l_progress := '020';
3446 
3447         --<Bug 3356349 mbhargav START>
3448         IF p_destination_doc_type = 'STANDARD PO' AND
3449            p_vendor_site_sourcing_flag = 'N'
3450         THEN
3451            --Get purchasing org from site
3452            l_purchasing_org_id := PO_VENDOR_SITES_SV.get_org_id_from_vendor_site(
3453                       p_vendor_site_id => x_vendor_site_id);
3454 
3455            --Validate that the item is valid in GA org and POU
3456            PO_GA_PVT.validate_in_purchasing_org(
3457                   x_return_status     => x_return_status,
3458                   p_po_header_id      => p_document_header_id,
3459                   p_item_id           => p_item_id,
3460                   p_purchasing_org_id => l_purchasing_org_id,
3461                   --No Need to do Item Revision checks
3462                   --They are done in the cursor already
3463                   p_ga_item_revision  => NULL,
3464                   p_owning_org_id     => p_document_org_id,
3465                   x_is_pou_valid      => l_is_org_valid,
3466                   x_is_item_valid     => l_is_item_valid,
3467                   x_item_revision     => l_item_revision);
3468         ELSE
3469            l_current_org_id := PO_GA_PVT.get_current_org;
3470            --Validate that the item is valid in GA org, ROU and POU
3471            PO_GA_PVT.validate_in_requesting_org(
3472                   x_return_status     => x_return_status,
3473                   p_po_header_id      => p_document_header_id,
3474                   p_item_id           => p_item_id,
3475                   p_requesting_org_id => l_current_org_id,
3476                   --No Need to do Item Revision checks
3477                   --They are done in the cursor already
3478                   p_ga_item_revision  => NULL,
3479                   p_owning_org_id     => p_document_org_id,
3480                   x_is_rou_valid      => l_is_org_valid,
3481                   x_is_item_valid     => l_is_item_valid,
3482                   x_item_revision     => l_item_revision);
3483         END IF;
3484         --<Bug 3356349 mbhargav END>
3485 
3486         IF (x_return_status <> FND_API.g_ret_sts_success) THEN
3487             RETURN;
3488         END IF;
3489 
3493 	              --Now get the supplier_site_id and vendor_contact_id
3490         IF l_is_org_valid and l_is_item_valid then
3491             l_progress := '030';
3492             IF p_vendor_site_sourcing_flag = 'Y' THEN
3494  	              x_vendor_site_id :=
3495                             PO_GA_PVT.get_vendor_site_id(p_document_header_id);
3496 
3497 	              IF x_vendor_contact_id is NULL then
3498  		                PO_VENDOR_CONTACTS_SV.get_vendor_contact(
3499                                        x_vendor_site_id 	=>x_vendor_site_id,
3500                                        x_vendor_contact_id 	=>x_vendor_contact_id,
3501                                        x_vendor_contact_name 	=>x_vendor_contact_name);
3502 	              END IF;
3503             END IF; --vendor_site_sourcing_flag check
3504 
3505              x_return_status := FND_API.G_RET_STS_SUCCESS;
3506 
3507         ELSE
3508 
3509              x_return_status := FND_API.G_RET_STS_ERROR;
3510         END IF; --l_valid_flag check
3511 
3512      ELSE
3513            l_progress := '040';
3514             IF p_vendor_site_sourcing_flag = 'Y' and x_vendor_site_id is NULL THEN
3515 
3516                 x_vendor_site_id := PO_VENDOR_SITES_SV.get_vendor_site_id(
3517                                            p_po_header_id   => p_document_header_id);
3518 
3519  		        PO_VENDOR_CONTACTS_SV.get_vendor_contact(
3520                                        x_vendor_site_id 	=>x_vendor_site_id,
3521                                        x_vendor_contact_id 	=>x_vendor_contact_id,
3522                                        x_vendor_contact_name 	=>x_vendor_contact_name);
3523             END IF;
3524             x_return_status := FND_API.G_RET_STS_SUCCESS;
3525      END IF; --GA Check
3526      l_progress := '050';
3527 
3528 END GET_SITE_ID_IF_ITEM_ON_DOC_OK;
3529 --<Shared Proc FPJ END>
3530 
3531 --<Shared Proc FPJ START>
3532 -------------------------------------------------------------------------------
3533 --Start of Comments
3534 --Name: ASL_SOURCING
3535 --Pre-reqs:
3536 --  Assumes that ASL will be used for Document Sourcing
3537 --Modifies:
3538 --  None.
3539 --Locks:
3540 --  None.
3541 --Function:
3542 --  Looks at ASLs and tries to find a document that
3543 --  can be used as source document. Returns the asl_id of ASL
3544 --  It can additionally return sequence_number of doc on ASL
3545 --Parameters:
3546 --IN:
3547 --p_item_id
3548 --  item_id to be matched for ASL
3549 --p_vendor_id
3550 --  vendor_id to be matched for ASL
3551 --p_vendor_site_code
3552 --  if provided, this parameter is used for finding a matching ASL
3553 --p_item_rev
3554 --  Revision number of Item p_item_id
3555 --p_item_rev_control
3556 --  This parameter tells whether item revision control is ON for given p_item_id
3557 --p_sourcing_date
3558 --  Date to be used for Sourcing date check
3559 --p_currency_code
3560 --  Currency Code to be used in Sourcing
3561 --p_org_id
3562 --  Operating Unit id
3563 --p_using_organization_id
3564 --  LOCAL/GLOBAL
3565 --OUT:
3566 --x_asl_id
3567 --  The unique identifier of Asl returned
3568 --x_vendor_product_num
3569 --  Supplier product_num associated with given Item as defined on ASL
3570 --x_purchasing_uom
3571 --  Purchasing UOM provided by Supplier on ASL
3572 --x_consigned_from_supplier_flag
3573 --  Flag indicating whether this combination is consigned
3574 --x_enable_vmi_flag
3575 --  Flag indicating if the ASL is VMI enabled
3576 --x_sequence_num
3577 --  The document position in ASL Documents window. This will be returned
3578 --   if during ASL determination, we have also determined the exact document to source
3579 --Notes:
3580 --  Logic: This is a 4 way match (item, vendor, vendor site code, destination inv org)
3581 --              The picking order of ASLs is:
3582 --          1. Look for local ASLs in current OU
3583 --          2. Look for Global Agreements in local ASLs in other OUs.
3584 --              Pick the latest created GA to break ties
3585 --           3. Look for Global ASLs in current OU
3586 --           4. Look for Global Agreements in Global ASLs in other OUs.
3587 --              Pick the latest created GA to break ties
3588 --Testing:
3589 --  None
3590 --End of Comments
3591 -------------------------------------------------------------------------------
3592 PROCEDURE asl_sourcing (
3593    p_item_id                      IN        NUMBER,
3594    p_vendor_id                    IN        NUMBER,
3595    p_vendor_site_code             IN        VARCHAR2,
3596    p_item_rev		          IN 	    VARCHAR2,
3597    p_item_rev_control		  IN	    NUMBER,
3598    p_sourcing_date		  IN	    DATE,
3599    p_currency_code	          IN 	    VARCHAR2,
3600    p_org_id			  IN	    NUMBER,
3601    p_using_organization_id        IN OUT NOCOPY NUMBER,
3602    x_asl_id                       OUT NOCOPY NUMBER,
3603    x_vendor_product_num           OUT NOCOPY VARCHAR2,
3604    x_purchasing_uom               OUT NOCOPY VARCHAR2,
3605    x_consigned_from_supplier_flag OUT NOCOPY VARCHAR2,
3606    x_enable_vmi_flag              OUT NOCOPY VARCHAR2,
3607    x_sequence_num                 OUT NOCOPY NUMBER,
3608    p_category_id 		  IN 	    NUMBER --<Contract AutoSourcing FPJ>
3609 )
3610 IS
3611    l_progress     VARCHAR2(3) := '000';
3612    l_log_head     CONSTANT VARCHAR2(100) := g_log_head||'asl_sourcing';
3613    l_using_organization_id   po_asl_documents.using_organization_id%TYPE;
3614 
3615 BEGIN
3616 
3617    l_progress := '010';
3618 
3622    -- This was required for performance reasons. With this change the Optimizer
3619    --<Bug 3545698 mbhargav START>
3620    --Seperated out the asl_sourcing into two procedures item_based_asl_sourcing
3621    --and CATEGORY_BASED_ASL_SOURCING.
3623    -- will be able to use combination index on (vendor_id, item_id) or
3624    -- (vendor_id, category_id) as appropriate.
3625 
3626    IF p_item_id IS NOT NULL THEN
3627      item_based_asl_sourcing(
3628             p_item_id		=>p_item_id,
3629             p_vendor_id		=>p_vendor_id,
3630 	        p_vendor_site_code	=>p_vendor_site_code,
3631             p_item_rev		=>p_item_rev,
3632             p_item_rev_control	=>p_item_rev_control,
3633             p_sourcing_date	=>p_sourcing_date,
3634             p_currency_code	=>p_currency_code,
3635             p_org_id		=>p_org_id,
3636             p_using_organization_id =>p_using_organization_id,
3637             x_asl_id 		=>x_asl_id,
3638             x_vendor_product_num 	=>x_vendor_product_num,
3639             x_purchasing_uom 	=>x_purchasing_uom,
3640  	        x_consigned_from_supplier_flag =>x_consigned_from_supplier_flag,
3641  	        x_enable_vmi_flag 	=>x_enable_vmi_flag,
3642             x_sequence_num 	=>x_sequence_num,
3643             p_category_id          => p_category_id --<Contract AutoSourcing FPJ>
3644             );
3645 
3646      IF x_asl_id IS NOT NULL THEN
3647         IF g_debug_stmt THEN
3648             PO_DEBUG.debug_stmt(l_log_head,l_progress,'item_based_asl_sourcing returned:');
3649             PO_DEBUG.debug_var(l_log_head,l_progress,'asl_id obtained', x_asl_id);
3650             PO_DEBUG.debug_var(l_log_head,l_progress,'sequence num obtained', x_sequence_num);
3651         END IF;
3652         RETURN;
3653      END IF;
3654    END IF;
3655 
3656     l_progress := '020';
3657 
3658    IF p_category_id IS NOT NULL THEN
3659       category_based_asl_sourcing(
3660             p_item_id		=>p_item_id,
3661             p_vendor_id		=>p_vendor_id,
3662 	        p_vendor_site_code	=>p_vendor_site_code,
3663             p_item_rev		=>p_item_rev,
3664             p_item_rev_control	=>p_item_rev_control,
3665             p_sourcing_date	=>p_sourcing_date,
3666             p_currency_code	=>p_currency_code,
3667             p_org_id		=>p_org_id,
3668             p_using_organization_id =>p_using_organization_id,
3669             x_asl_id 		=>x_asl_id,
3670             x_vendor_product_num 	=>x_vendor_product_num,
3671             x_purchasing_uom 	=>x_purchasing_uom,
3672  	        x_consigned_from_supplier_flag =>x_consigned_from_supplier_flag,
3673  	        x_enable_vmi_flag 	=>x_enable_vmi_flag,
3674             x_sequence_num 	=>x_sequence_num,
3675             p_category_id          => p_category_id --<Contract AutoSourcing FPJ>
3676             );
3677 
3678      IF x_asl_id IS NOT NULL THEN
3679         IF g_debug_stmt THEN
3680             PO_DEBUG.debug_stmt(l_log_head,l_progress,'category_based_asl_sourcing returned:');
3681             PO_DEBUG.debug_var(l_log_head,l_progress,'asl_id obtained', x_asl_id);
3682             PO_DEBUG.debug_var(l_log_head,l_progress,'sequence num obtained', x_sequence_num);
3683         END IF;
3684         RETURN;
3685      END IF;
3686    END IF; --category_id is NOT NULL
3687    --<Bug 3545698 mbhargav END>
3688 
3689    l_progress := '030';
3690    IF g_debug_stmt THEN
3691         PO_DEBUG.debug_stmt(l_log_head,l_progress,'No matching ASL not found');
3692    END IF;
3693 
3694 EXCEPTION
3695     WHEN OTHERS THEN
3696          IF g_debug_unexp THEN
3697             PO_DEBUG.debug_exc(l_log_head,l_progress);
3698          END IF;
3699 
3700         PO_MESSAGE_S.SQL_ERROR('ASL_SOURCING', l_progress, sqlcode);
3701 END ASL_SOURCING;
3702 --<Shared Proc FPJ END>
3703 
3704 -------------------------------------------------------------------------------
3705 --Start of Comments
3706 --Name: ITEM_BASED_ASL_SOURCING
3707 --Pre-reqs:
3708 --  Assumes that ASL will be used for Document Sourcing
3709 --Modifies:
3710 --  None.
3711 --Locks:
3712 --  None.
3713 --Function:
3714 --  Looks at ASLs and tries to find a document that
3715 --  can be used as source document for given ITEM_ID. Returns the asl_id of ASL
3716 --  It can additionally return sequence_number of doc on ASL
3717 --Parameters:
3718 --IN:
3719 --p_item_id
3720 --  item_id to be matched for ASL
3721 --p_vendor_id
3722 --  vendor_id to be matched for ASL
3723 --p_vendor_site_code
3724 --  if provided, this parameter is used for finding a matching ASL
3725 --p_item_rev
3726 --  Revision number of Item p_item_id
3727 --p_item_rev_control
3728 --  This parameter tells whether item revision control is ON for given p_item_id
3729 --p_sourcing_date
3730 --  Date to be used for Sourcing date check
3731 --p_currency_code
3732 --  Currency Code to be used in Sourcing
3733 --p_org_id
3734 --  Operating Unit id
3735 --p_using_organization_id
3736 --  LOCAL/GLOBAL
3737 --OUT:
3738 --x_asl_id
3739 --  The unique identifier of Asl returned
3740 --x_vendor_product_num
3741 --  Supplier product_num associated with given Item as defined on ASL
3742 --x_purchasing_uom
3743 --  Purchasing UOM provided by Supplier on ASL
3744 --x_consigned_from_supplier_flag
3745 --  Flag indicating whether this combination is consigned
3746 --x_enable_vmi_flag
3747 --  Flag indicating if the ASL is VMI enabled
3748 --x_sequence_num
3749 --  The document position in ASL Documents window. This will be returned
3753 --              The picking order of ASLs is:
3750 --   if during ASL determination, we have also determined the exact document to source
3751 --Notes:
3752 --  Logic: This is a 4 way match (item, vendor, vendor site code, destination inv org)
3754 --          1. Look for local ASLs in current OU
3755 --          2. Look for Global Agreements in local ASLs in other OUs.
3756 --              Pick the latest created GA to break ties
3757 --           3. Look for Global ASLs in current OU
3758 --           4. Look for Global Agreements in Global ASLs in other OUs.
3759 --              Pick the latest created GA to break ties
3760 --Testing:
3761 --  None
3762 --End of Comments
3763 -------------------------------------------------------------------------------
3764 PROCEDURE ITEM_BASED_ASL_SOURCING (
3765    p_item_id                      IN        NUMBER,
3766    p_vendor_id                    IN        NUMBER,
3767    p_vendor_site_code             IN        VARCHAR2,
3768    p_item_rev		          IN 	    VARCHAR2,
3769    p_item_rev_control		  IN	    NUMBER,
3770    p_sourcing_date		  IN	    DATE,
3771    p_currency_code	          IN 	    VARCHAR2,
3772    p_org_id			  IN	    NUMBER,
3773    p_using_organization_id        IN OUT NOCOPY NUMBER, --<Bug 3733077>
3774    x_asl_id                       OUT NOCOPY NUMBER,
3775    x_vendor_product_num           OUT NOCOPY VARCHAR2,
3776    x_purchasing_uom               OUT NOCOPY VARCHAR2,
3777    x_consigned_from_supplier_flag OUT NOCOPY VARCHAR2,
3778    x_enable_vmi_flag              OUT NOCOPY VARCHAR2,
3779    x_sequence_num                 OUT NOCOPY NUMBER,
3780    p_category_id 		  IN 	    NUMBER --<Contract AutoSourcing FPJ>
3781 )
3782 IS
3783    l_progress     VARCHAR2(3) := '000';
3784    l_log_head     CONSTANT VARCHAR2(100) := g_log_head||'item_based_asl_sourcing';
3785    l_using_organization_id   po_asl_documents.using_organization_id%TYPE;
3786 
3787   --This cursor is used to look for ITEM ASLs in current OU
3788   --Note: If you make any change in this cursor then consider whether you
3789   --      need to make change to cursor L_CATEGORY_ASL_IN_CUR_OU_CSR as well
3790   CURSOR L_ITEM_ASL_IN_CUR_OU_CSR (
3791       p_using_organization_id  IN   NUMBER
3792    )
3793    IS
3794       --SQL WHAT: Get the matching asl_id if one exists in current OU
3795       --SQL WHY: This information will be used to identify the document in ASL.
3796       --SQL JOIN: po_asl_attributes using asl_id, po_asl_status_rules_v using status_id
3797       --                     po_vendor_sites_all using vendor_site_id
3798       SELECT   pasl.asl_id, paa.using_organization_id,
3799                pasl.primary_vendor_item, paa.purchasing_unit_of_measure,
3800                paa.consigned_from_supplier_flag, paa.enable_vmi_flag
3801           FROM po_approved_supplier_lis_val_v pasl,
3802                po_asl_attributes paa,
3803                po_asl_status_rules_v pasr,
3804                po_vendor_sites_all pvs
3805          WHERE pasl.item_id = p_item_id  --<Contract AutoSourcing FPJ>
3806            AND pasl.vendor_id = p_vendor_id
3807            AND pasl.using_organization_id in (-1, p_using_organization_id) --<Bug 3733077>
3808            AND pasl.asl_id = paa.asl_id
3809            AND pasr.business_rule = '2_SOURCING'
3810            AND pasr.allow_action_flag ='Y'
3811            AND pasr.status_id = pasl.asl_status_id
3812            AND paa.using_organization_id = p_using_organization_id
3813            AND (   (pasl.vendor_site_id IS NULL AND p_vendor_site_code IS NULL)
3814                 OR (    pasl.vendor_site_id = pvs.vendor_site_id
3815                     AND pvs.vendor_site_code = p_vendor_site_code
3816                     AND nvl(pvs.org_id,-99) = nvl(p_org_id, -99)
3817                     AND pvs.vendor_id = p_vendor_id
3818                    )
3819                )
3820       ORDER BY pasl.vendor_site_id ASC;
3821 
3822    --Look for ITEM ASLs in other Operating Units. This cursor also returns
3823    --the sequence number of the GA found. If the GA passes the item validity
3824    --check then this document is returned as source document
3825    --Note: If you make any change in this cursor then consider whether you
3826    --      need to make change to cursor L_CATEGORY_ASL_DOCUMENTS_CSR as well
3827    CURSOR L_ITEM_ASL_DOCUMENTS_CSR(
3828       p_using_organization_id   IN   NUMBER
3829    )
3830    IS
3831       --SQL WHAT: Get the matching asl_id, sequence_num of GA if one exists in other OU
3832       --SQL WHY: This information will be used to identify the document in ASL.
3833       --SQL JOIN: po_asl_attributes using asl_id, po_asl_status_rules_v using status_id
3834       --          po_asl_docuyment using asl_id, sequence_num, po_headers_all using
3835       --          po_header_id, po_lines_all using po_line_id
3836       SELECT   pasl.asl_id, paa.using_organization_id,
3837                pasl.primary_vendor_item, paa.purchasing_unit_of_measure,
3838                paa.consigned_from_supplier_flag, paa.enable_vmi_flag,
3839                pad.sequence_num
3840           FROM po_approved_supplier_lis_val_v pasl,
3841                po_asl_attributes paa,
3842                po_asl_status_rules_v pasr,
3843                po_asl_documents pad,
3844                po_headers_all poh,
3845                po_lines_all pol
3846          WHERE pasl.item_id = p_item_id    --<Contract AutoSourcing FPJ>
3847            AND pasl.vendor_id = p_vendor_id
3848            AND pasl.using_organization_id in (-1, p_using_organization_id) --<Bug 3733077>
3849            AND pasl.asl_id = paa.asl_id
3850            AND pasr.business_rule = '2_SOURCING'
3851            AND pasr.allow_action_flag = 'Y'
3852            AND pasr.status_id = pasl.asl_status_id
3856            AND pol.po_line_id (+) = pad.document_line_id	-- <FPJ Advanced Price>
3853            AND paa.using_organization_id = p_using_organization_id
3854            AND pad.asl_id = pasl.asl_id
3855            AND pad.document_header_id = poh.po_header_id
3857            AND ((    poh.type_lookup_code = 'BLANKET'
3858                  AND poh.approved_flag = 'Y'
3859                  AND NVL (poh.closed_code, 'OPEN') NOT IN
3860                                                   ('FINALLY CLOSED', 'CLOSED')
3861                  AND NVL (pol.closed_code, 'OPEN') NOT IN
3862                                                   ('FINALLY CLOSED', 'CLOSED')
3863                  AND NVL (poh.cancel_flag, 'N') = 'N'
3864                  AND NVL (poh.frozen_flag, 'N') = 'N'
3865                  AND TRUNC (NVL (pol.expiration_date, p_sourcing_date)) >=
3866                                                        p_sourcing_date
3867                  AND NVL (pol.cancel_flag, 'N') = 'N'
3868                 )
3869             -- <FPJ Advanced Price START>
3870              OR (    poh.type_lookup_code = 'CONTRACT'
3871         	 	AND (( NVL(FND_PROFILE.VALUE('ALLOW_REFERENCING_CPA_UNDER_AMENDMENT'),'N') =  'Y' --<R12 GCPA ER>
3872 			 			and poh.approved_date is not null)
3873 			 			OR
3874 			 			nvl(poh.approved_flag,'N') = 'Y'
3875 			 			)
3876                  AND NVL(poh.cancel_flag,'N') = 'N'
3877                  AND NVL(poh.frozen_flag,'N') = 'N'
3878                  AND NVL(poh.closed_code, 'OPEN') = 'OPEN'
3879                 )
3880                )
3881             -- <FPJ Advanced Price END>
3882            AND (p_currency_code IS NULL OR poh.currency_code = p_currency_code
3883                )
3884            AND p_sourcing_date >= NVL (poh.start_date, p_sourcing_date - 1)
3885            AND p_sourcing_date <= NVL (poh.end_date, p_sourcing_date + 1)
3886            -- <FPJ Advanced Price START>
3887            AND (poh.type_lookup_code = 'CONTRACT' OR
3888                 (NVL(pol.item_revision, -1) = NVL(p_item_rev, -1) OR
3889 	         (NVL (p_item_rev_control, 1) = 1 AND p_item_rev IS NULL)))
3890            -- <FPJ Advanced Price END>
3891            AND ((pasl.vendor_site_id IS NULL AND p_vendor_site_code IS NULL)
3892                 OR EXISTS (
3893                        SELECT  'vendor site code matches ASL'
3894                        FROM  po_vendor_sites_all pvs
3895                        WHERE pasl.vendor_site_id = decode(nvl(poh.Enable_all_sites,'N'),'N',pvs.vendor_site_id,pasl.vendor_site_id)  --<R12GCPA ER>
3896                        AND pvs.vendor_site_code = p_vendor_site_code
3897                        AND pvs.vendor_id = p_vendor_id)
3898                 )
3899            AND (    NVL (poh.global_agreement_flag, 'N') = 'Y'
3900                 AND EXISTS (
3901                        SELECT 'vendor site code matches GA'
3902                          FROM po_ga_org_assignments poga,
3903                               po_vendor_sites_all pvs
3904                         WHERE poh.po_header_id = poga.po_header_id
3905                           AND poga.organization_id = p_org_id
3906                           AND poga.enabled_flag = 'Y'
3907                           AND pvs.vendor_site_id = decode( Nvl (poh.Enable_All_Sites,'N'),'N',poga.Vendor_Site_Id,pvs.vendor_site_id) --< R12 GCPA ER>
3908                           AND pvs.vendor_site_code = p_vendor_site_code
3909                           AND pvs.vendor_id = p_vendor_id)
3910                )
3911       ORDER BY poh.creation_date DESC;
3912 
3913 BEGIN
3914 
3915    l_progress := '010';
3916 
3917    --<Contract AutoSourcing FPJ>
3918    --Look for item-based ASLs
3919      IF g_debug_stmt THEN
3920         --<Contract AutoSourcing FPJ>
3921        PO_DEBUG.debug_stmt(l_log_head,l_progress,'Look in Local item-based ASLs in current OU');
3922      END IF;
3923 
3924      --First look for local ASLs in current operating unit
3925      --Local ASL: p_using_organization_id = p_using_organization_id
3926      --Current Operating Unit: p_operating_unit =l_operating_unit
3927      --Will return rows if vendor_site is not provided on ASL and in input parameter OR
3928      -- the site on ASL is in current OU and site_code match
3929      OPEN L_ITEM_ASL_IN_CUR_OU_CSR (
3930                      p_using_organization_id =>p_using_organization_id);
3931 
3932      FETCH L_ITEM_ASL_IN_CUR_OU_CSR INTO x_asl_id,
3933       p_using_organization_id,
3934       x_vendor_product_num,
3935       x_purchasing_uom,
3936       x_consigned_from_supplier_flag,
3937       x_enable_vmi_flag;
3938 
3939 
3940      IF L_ITEM_ASL_IN_CUR_OU_CSR%FOUND
3941      THEN
3942         CLOSE L_ITEM_ASL_IN_CUR_OU_CSR;
3943         x_sequence_num := NULL;
3944         l_progress := '020';
3945         IF g_debug_stmt THEN
3946            PO_DEBUG.debug_stmt(l_log_head,l_progress,'Found:');
3947            PO_DEBUG.debug_var(l_log_head,l_progress,'x_asl_id', x_asl_id);
3948         END IF;
3949         RETURN;
3950      END IF;
3951 
3952      CLOSE L_ITEM_ASL_IN_CUR_OU_CSR;
3953 
3954      IF g_debug_stmt THEN
3955         --<Contract AutoSourcing FPJ>
3956         PO_DEBUG.debug_stmt(l_log_head,l_progress,'Look in Local item-based ASLs in other OUs');
3957      END IF;
3958 
3959      --Try to find local ASLs in other operating units
3960      --Local ASL: p_using_organization_id = p_using_organization_id
3961      --Other OUs: p_operating_unit = NULL
3962      --Will return rows if we can find a GA in other OUs which are listed in ASLs
3963      OPEN L_ITEM_ASL_DOCUMENTS_CSR(
3967       x_vendor_product_num,
3964               p_using_organization_id	=> p_using_organization_id);
3965      FETCH L_ITEM_ASL_DOCUMENTS_CSR INTO x_asl_id,
3966       p_using_organization_id,
3968       x_purchasing_uom,
3969       x_consigned_from_supplier_flag,
3970       x_enable_vmi_flag,
3971       x_sequence_num;
3972 
3973      IF L_ITEM_ASL_DOCUMENTS_CSR%FOUND
3974      THEN
3975         CLOSE L_ITEM_ASL_DOCUMENTS_CSR;
3976         l_progress := '030';
3977         IF g_debug_stmt THEN
3978            PO_DEBUG.debug_stmt(l_log_head,l_progress,'Found:');
3979            PO_DEBUG.debug_var(l_log_head,l_progress,'x_asl_id', x_asl_id);
3980            PO_DEBUG.debug_var(l_log_head,l_progress,'x_sequence_num', x_sequence_num);
3981         END IF;
3982         RETURN;
3983      END IF;
3984 
3985      CLOSE L_ITEM_ASL_DOCUMENTS_CSR;
3986 
3987      IF g_debug_stmt THEN
3988         --<Contract AutoSourcing FPJ>
3989         PO_DEBUG.debug_stmt(l_log_head,l_progress,'Look in Global item-based ASLs in current OU');
3990      END IF;
3991 
3992      --Now look for global ASLs in current operating unit
3993      --Global ASL: p_using_organization_id = -1
3994      --Current Operating Unit: p_operating_unit =l_operating_unit
3995      --Will return rows if vendor_site is not provided on ASL and in input parameter OR
3996      -- the site on ASL is in current OU and site_code match
3997      OPEN L_ITEM_ASL_IN_CUR_OU_CSR (
3998                      p_using_organization_id	=>-1);
3999      FETCH L_ITEM_ASL_IN_CUR_OU_CSR INTO x_asl_id,
4000       p_using_organization_id,
4001       x_vendor_product_num,
4002       x_purchasing_uom,
4003       x_consigned_from_supplier_flag,
4004       x_enable_vmi_flag;
4005 
4006      IF L_ITEM_ASL_IN_CUR_OU_CSR%FOUND
4007      THEN
4008         CLOSE L_ITEM_ASL_IN_CUR_OU_CSR;
4009         x_sequence_num := NULL;
4010         l_progress := '040';
4011         IF g_debug_stmt THEN
4012            PO_DEBUG.debug_stmt(l_log_head,l_progress,'Found:');
4013            PO_DEBUG.debug_var(l_log_head,l_progress,'x_asl_id', x_asl_id);
4014         END IF;
4015         RETURN;
4016      END IF;
4017 
4018      CLOSE L_ITEM_ASL_IN_CUR_OU_CSR;
4019 
4020      IF g_debug_stmt THEN
4021         --<Contract AutoSourcing FPJ>
4022         PO_DEBUG.debug_stmt(l_log_head,l_progress,'Look in Global item-based ASLs in other OUs');
4023 
4024      END IF;
4025 
4026      --Try to find Global ASLs in other operating units
4027      --Global ASL: p_using_organization_id = -1
4028      --Other OUs: p_operating_unit = NULL
4029      --Will return rows if we can find a GA in other OUs which are listed in ASLs
4030      OPEN L_ITEM_ASL_DOCUMENTS_CSR(
4031               P_using_organization_id	=> -1);
4032      FETCH L_ITEM_ASL_DOCUMENTS_CSR INTO x_asl_id,
4033       p_using_organization_id,
4034       x_vendor_product_num,
4035       x_purchasing_uom,
4036       x_consigned_from_supplier_flag,
4037       x_enable_vmi_flag,
4038       x_sequence_num;
4039 
4040      IF L_ITEM_ASL_DOCUMENTS_CSR %FOUND
4041      THEN
4042         CLOSE L_ITEM_ASL_DOCUMENTS_CSR;
4043         l_progress := '050';
4044         IF g_debug_stmt THEN
4045            PO_DEBUG.debug_stmt(l_log_head,l_progress,'Found:');
4046            PO_DEBUG.debug_var(l_log_head,l_progress,'x_asl_id', x_asl_id);
4047            PO_DEBUG.debug_var(l_log_head,l_progress,'x_sequence_num', x_sequence_num);
4048         END IF;
4049         RETURN;
4050      END IF;
4051 
4052      CLOSE L_ITEM_ASL_DOCUMENTS_CSR;
4053 
4054      x_vendor_product_num := NULL;
4055      x_purchasing_uom := NULL;
4056      x_consigned_from_supplier_flag := NULL;
4057      x_enable_vmi_flag := NULL;
4058      x_sequence_num := NULL;
4059      l_progress := '060';
4060 
4061      IF g_debug_stmt THEN
4062        --<Contract AutoSourcing FPJ>
4063        PO_DEBUG.debug_stmt(l_log_head,l_progress,'Matching Item-based ASL not found');
4064      END IF;
4065 
4066 EXCEPTION
4067     WHEN OTHERS THEN
4068          IF g_debug_unexp THEN
4069             PO_DEBUG.debug_exc(l_log_head,l_progress);
4070          END IF;
4071 
4072         PO_MESSAGE_S.SQL_ERROR('ITEM_BASED_ASL_SOURCING', l_progress, sqlcode);
4073 END ITEM_BASED_ASL_SOURCING;
4074 
4075 -------------------------------------------------------------------------------
4076 --Start of Comments
4077 --Name: CATEGORY_BASED_ASL_SOURCING
4078 --Pre-reqs:
4079 --  Assumes that ASL will be used for Document Sourcing
4080 --Modifies:
4081 --  None.
4082 --Locks:
4083 --  None.
4084 --Function:
4085 --  Looks at ASLs and tries to find a document that
4086 --  can be used as source document for given CATEGORY_ID. Returns the asl_id of ASL
4087 --  It can additionally return sequence_number of doc on ASL
4088 --Parameters:
4089 --IN:
4090 --p_item_id
4091 --  item_id to be matched for ASL
4092 --p_vendor_id
4093 --  vendor_id to be matched for ASL
4094 --p_vendor_site_code
4095 --  if provided, this parameter is used for finding a matching ASL
4096 --p_item_rev
4097 --  Revision number of Item p_item_id
4098 --p_item_rev_control
4099 --  This parameter tells whether item revision control is ON for given p_item_id
4100 --p_sourcing_date
4101 --  Date to be used for Sourcing date check
4102 --p_currency_code
4103 --  Currency Code to be used in Sourcing
4104 --p_org_id
4105 --  Operating Unit id
4106 --p_using_organization_id
4110 --OUT:
4107 --  LOCAL/GLOBAL
4108 --p_category_id
4109 --  category_id to be matched for ASL
4111 --x_asl_id
4112 --  The unique identifier of Asl returned
4113 --x_vendor_product_num
4114 --  Supplier product_num associated with given Item as defined on ASL
4115 --x_purchasing_uom
4116 --  Purchasing UOM provided by Supplier on ASL
4117 --x_consigned_from_supplier_flag
4118 --  Flag indicating whether this combination is consigned
4119 --x_enable_vmi_flag
4120 --  Flag indicating if the ASL is VMI enabled
4121 --x_sequence_num
4122 --  The document position in ASL Documents window. This will be returned
4123 --   if during ASL determination, we have also determined the exact document to source
4124 --Notes:
4125 --  Logic: This is a 4 way match (item, vendor, vendor site code, destination inv org)
4126 --              The picking order of ASLs is:
4127 --          1. Look for local ASLs in current OU
4128 --          2. Look for Global Agreements in local ASLs in other OUs.
4129 --              Pick the latest created GA to break ties
4130 --           3. Look for Global ASLs in current OU
4131 --           4. Look for Global Agreements in Global ASLs in other OUs.
4132 --              Pick the latest created GA to break ties
4133 --Testing:
4134 --  None
4135 --End of Comments
4136 -------------------------------------------------------------------------------
4137 PROCEDURE CATEGORY_BASED_ASL_SOURCING (
4138    p_item_id                      IN        NUMBER,
4139    p_vendor_id                    IN        NUMBER,
4140    p_vendor_site_code             IN        VARCHAR2,
4141    p_item_rev		          IN 	    VARCHAR2,
4142    p_item_rev_control		  IN	    NUMBER,
4143    p_sourcing_date		  IN	    DATE,
4144    p_currency_code	          IN 	    VARCHAR2,
4145    p_org_id			  IN	    NUMBER,
4146    p_using_organization_id        IN OUT NOCOPY NUMBER, --<Bug 3733077>
4147    x_asl_id                       OUT NOCOPY NUMBER,
4148    x_vendor_product_num           OUT NOCOPY VARCHAR2,
4149    x_purchasing_uom               OUT NOCOPY VARCHAR2,
4150    x_consigned_from_supplier_flag OUT NOCOPY VARCHAR2,
4151    x_enable_vmi_flag              OUT NOCOPY VARCHAR2,
4152    x_sequence_num                 OUT NOCOPY NUMBER,
4153    p_category_id 		  IN 	    NUMBER --<Contract AutoSourcing FPJ>
4154 )
4155 IS
4156    l_progress     VARCHAR2(3) := '000';
4157    l_log_head     CONSTANT VARCHAR2(100) := g_log_head||'category_based_asl_sourcing';
4158    l_using_organization_id   po_asl_documents.using_organization_id%TYPE;
4159 
4160   --This cursor is used to look for CATEGORY based ASLs in current OU
4161   --Note: If you make any change in this cursor then consider whether you
4162   --      need to make change to cursor L_ITEM_ASL_IN_CUR_OU_CSR as well
4163   CURSOR L_CATEGORY_ASL_IN_CUR_OU_CSR (
4164       p_using_organization_id  IN   NUMBER
4165    )
4166    IS
4167       --SQL WHAT: Get the matching asl_id if one exists in current OU
4168       --SQL WHY: This information will be used to identify the document in ASL.
4169       --SQL JOIN: po_asl_attributes using asl_id, po_asl_status_rules_v using status_id
4170       --                     po_vendor_sites_all using vendor_site_id
4171       SELECT   pasl.asl_id, paa.using_organization_id,
4172                pasl.primary_vendor_item, paa.purchasing_unit_of_measure,
4173                paa.consigned_from_supplier_flag, paa.enable_vmi_flag
4174           FROM po_approved_supplier_lis_val_v pasl,
4175                po_asl_attributes paa,
4176                po_asl_status_rules_v pasr,
4177                po_vendor_sites_all pvs
4178          WHERE pasl.category_id = p_category_id  --<Contract AutoSourcing FPJ>
4179            AND pasl.vendor_id = p_vendor_id
4180            AND pasl.using_organization_id in (-1, p_using_organization_id) --<Bug 3733077>
4181            AND pasl.asl_id = paa.asl_id
4182            AND pasr.business_rule = '2_SOURCING'
4183            AND pasr.allow_action_flag ='Y'
4184            AND pasr.status_id = pasl.asl_status_id
4185            AND paa.using_organization_id = p_using_organization_id
4186            AND (   (pasl.vendor_site_id IS NULL AND p_vendor_site_code IS NULL)
4187                 OR (    pasl.vendor_site_id = pvs.vendor_site_id
4188                     AND pvs.vendor_site_code = p_vendor_site_code
4189                     AND nvl(pvs.org_id,-99) = nvl(p_org_id, -99)
4190                     AND pvs.vendor_id = p_vendor_id
4191                    )
4192                )
4193       ORDER BY pasl.vendor_site_id ASC;
4194 
4195    --Look for CATEGORY based ASLs in other Operating Units. This cursor also returns
4196    --the sequence number of the GA found. If the GA passes the item validity
4197    --check then this document is returned as source document
4198    --Note: If you make any change in this cursor then consider whether you
4199    --      need to make change to cursor L_ITEM_ASL_DOCUMENTS_CSR as well
4200    CURSOR L_CATEGORY_ASL_DOCUMENTS_CSR(
4201       p_using_organization_id   IN   NUMBER
4202    )
4203    IS
4204       --SQL WHAT: Get the matching asl_id, sequence_num of GA if one exists in other OU
4205       --SQL WHY: This information will be used to identify the document in ASL.
4206       --SQL JOIN: po_asl_attributes using asl_id, po_asl_status_rules_v using status_id
4207       --                     po_asl_docuyment using asl_id, sequence_num, po_headers_all using
4208       --                     po_header_id, po_lines_all using po_line_id
4209       SELECT   pasl.asl_id, paa.using_organization_id,
4210                pasl.primary_vendor_item, paa.purchasing_unit_of_measure,
4211                paa.consigned_from_supplier_flag, paa.enable_vmi_flag,
4215                po_asl_status_rules_v pasr,
4212                pad.sequence_num
4213           FROM po_approved_supplier_lis_val_v pasl,
4214                po_asl_attributes paa,
4216                po_asl_documents pad,
4217                po_headers_all poh,
4218                po_lines_all pol
4219          WHERE pasl.category_id = p_category_id  --<Contract AutoSourcing FPJ>
4220            AND pasl.vendor_id = p_vendor_id
4221            AND pasl.using_organization_id in (-1, p_using_organization_id) --<Bug 3733077>
4222            AND pasl.asl_id = paa.asl_id
4223            AND pasr.business_rule = '2_SOURCING'
4224            AND pasr.allow_action_flag = 'Y'
4225            AND pasr.status_id = pasl.asl_status_id
4226            AND paa.using_organization_id = p_using_organization_id
4227            AND pad.asl_id = pasl.asl_id
4228            AND pad.document_header_id = poh.po_header_id
4229            AND pol.po_line_id (+) = pad.document_line_id	-- <FPJ Advanced Price>
4230            AND ((    poh.type_lookup_code = 'BLANKET'
4231                  AND poh.approved_flag = 'Y'
4232                  AND NVL (poh.closed_code, 'OPEN') NOT IN
4233                                                   ('FINALLY CLOSED', 'CLOSED')
4234                  AND NVL (pol.closed_code, 'OPEN') NOT IN
4235                                                   ('FINALLY CLOSED', 'CLOSED')
4236                  AND NVL (poh.cancel_flag, 'N') = 'N'
4237                  AND NVL (poh.frozen_flag, 'N') = 'N'
4238                  AND TRUNC (NVL (pol.expiration_date, p_sourcing_date)) >=
4239                                                        p_sourcing_date
4240                  AND NVL (pol.cancel_flag, 'N') = 'N'
4241                 )
4242             -- <FPJ Advanced Price START>
4243              OR (    poh.type_lookup_code = 'CONTRACT'
4244 	        	 AND (( NVL(FND_PROFILE.VALUE('ALLOW_REFERENCING_CPA_UNDER_AMENDMENT'),'N') =  'Y' --<R12 GCPA ER>
4245 				 		and poh.approved_date is not null)
4246 				 		OR
4247 				 		nvl(poh.approved_flag,'N') = 'Y'
4248 				 		)
4249                  AND NVL(poh.cancel_flag,'N') = 'N'
4250                  AND NVL(poh.frozen_flag,'N') = 'N'
4251                  AND NVL(poh.closed_code, 'OPEN') = 'OPEN'
4252                 )
4253                )
4254             -- <FPJ Advanced Price END>
4255            AND (p_currency_code IS NULL OR poh.currency_code = p_currency_code
4256                )
4257            AND p_sourcing_date >= NVL (poh.start_date, p_sourcing_date - 1)
4258            AND p_sourcing_date <= NVL (poh.end_date, p_sourcing_date + 1)
4259            -- <FPJ Advanced Price START>
4260            AND (poh.type_lookup_code = 'CONTRACT' OR
4261                 (NVL(pol.item_revision, -1) = NVL(p_item_rev, -1) OR
4262 	         (NVL (p_item_rev_control, 1) = 1 AND p_item_rev IS NULL)))
4263            -- <FPJ Advanced Price END>
4264            AND ((pasl.vendor_site_id IS NULL AND p_vendor_site_code IS NULL)
4265                 OR EXISTS (
4266                        SELECT  'vendor site code matches ASL'
4267                        FROM  po_vendor_sites_all pvs
4268                        WHERE pasl.vendor_site_id = decode(nvl(poh.Enable_All_Sites,'N'),'N',pvs.vendor_site_id,pasl.vendor_site_id)  --<R12GCPA ER>
4269                        AND pvs.vendor_site_code = p_vendor_site_code
4270                        AND pvs.vendor_id = p_vendor_id)
4271                 )
4272            AND (    NVL (poh.global_agreement_flag, 'N') = 'Y'
4273                 AND EXISTS (
4274                        SELECT 'vendor site code matches GA'
4275                          FROM po_ga_org_assignments poga,
4276                               po_vendor_sites_all pvs
4277                         WHERE poh.po_header_id = poga.po_header_id
4278                           AND poga.organization_id = p_org_id
4279                           AND poga.enabled_flag = 'Y'
4280                           AND pvs.vendor_site_id = decode( Nvl (poh.Enable_All_Sites,'N'),'Y',pvs.vendor_site_id, poga.Vendor_Site_Id) --< R12 GCPA ER>
4281                           AND pvs.vendor_site_code = p_vendor_site_code
4282                           AND pvs.vendor_id = p_vendor_id)
4283                )
4284       ORDER BY poh.creation_date DESC;
4285 
4286 BEGIN
4287 
4288    l_progress := '010';
4289 
4290    --<Contract AutoSourcing FPJ>
4291    --Look for category-based ASLs
4292 
4293      IF g_debug_stmt THEN
4294         --<Contract AutoSourcing FPJ>
4295         PO_DEBUG.debug_stmt(l_log_head,l_progress,'Look in Local category-based ASLs in current OU');
4296      END IF;
4297 
4298      --First look for local ASLs in current operating unit
4299      --Local ASL: p_using_organization_id = p_using_organization_id
4300      --Current Operating Unit: p_operating_unit =l_operating_unit
4301      --Will return rows if vendor_site is not provided on ASL and in input parameter OR
4302      -- the site on ASL is in current OU and site_code match
4303      OPEN L_CATEGORY_ASL_IN_CUR_OU_CSR (
4304                      p_using_organization_id =>p_using_organization_id);
4305 
4306      FETCH L_CATEGORY_ASL_IN_CUR_OU_CSR INTO x_asl_id,
4307       p_using_organization_id,
4308       x_vendor_product_num,
4309       x_purchasing_uom,
4310       x_consigned_from_supplier_flag,
4311       x_enable_vmi_flag;
4312 
4313 
4314      IF L_CATEGORY_ASL_IN_CUR_OU_CSR%FOUND
4315      THEN
4316         CLOSE L_CATEGORY_ASL_IN_CUR_OU_CSR;
4317         x_sequence_num := NULL;
4318         l_progress := '020';
4319         IF g_debug_stmt THEN
4320            PO_DEBUG.debug_stmt(l_log_head,l_progress,'Found:');
4324      END IF;
4321            PO_DEBUG.debug_var(l_log_head,l_progress,'x_asl_id', x_asl_id);
4322         END IF;
4323         RETURN;
4325 
4326      CLOSE L_CATEGORY_ASL_IN_CUR_OU_CSR;
4327 
4328      IF g_debug_stmt THEN
4329         --<Contract AutoSourcing FPJ>
4330         PO_DEBUG.debug_stmt(l_log_head,l_progress,'Look in Local category-based ASLs in other OUs');
4331      END IF;
4332 
4333      --Try to find local ASLs in other operating units
4334      --Local ASL: p_using_organization_id = p_using_organization_id
4335      --Other OUs: p_operating_unit = NULL
4336      --Will return rows if we can find a GA in other OUs which are listed in ASLs
4337      OPEN L_CATEGORY_ASL_DOCUMENTS_CSR(
4338               p_using_organization_id	=> p_using_organization_id);
4339      FETCH L_CATEGORY_ASL_DOCUMENTS_CSR INTO x_asl_id,
4340       p_using_organization_id,
4341       x_vendor_product_num,
4342       x_purchasing_uom,
4343       x_consigned_from_supplier_flag,
4344       x_enable_vmi_flag,
4345       x_sequence_num;
4346 
4347      IF L_CATEGORY_ASL_DOCUMENTS_CSR%FOUND
4348      THEN
4349         CLOSE L_CATEGORY_ASL_DOCUMENTS_CSR;
4350         l_progress := '030';
4351         IF g_debug_stmt THEN
4352            PO_DEBUG.debug_stmt(l_log_head,l_progress,'Found:');
4353            PO_DEBUG.debug_var(l_log_head,l_progress,'x_asl_id', x_asl_id);
4354            PO_DEBUG.debug_var(l_log_head,l_progress,'x_sequence_num', x_sequence_num);
4355         END IF;
4356         RETURN;
4357      END IF;
4358 
4359      CLOSE L_CATEGORY_ASL_DOCUMENTS_CSR;
4360 
4361      IF g_debug_stmt THEN
4362         --<Contract AutoSourcing FPJ>
4363         PO_DEBUG.debug_stmt(l_log_head,l_progress,'Look in Global category-based ASLs in current OU');
4364      END IF;
4365 
4366      --Now look for global ASLs in current operating unit
4367      --Global ASL: p_using_organization_id = -1
4368      --Current Operating Unit: p_operating_unit =l_operating_unit
4369      --Will return rows if vendor_site is not provided on ASL and in input parameter OR
4370      -- the site on ASL is in current OU and site_code match
4371      OPEN L_CATEGORY_ASL_IN_CUR_OU_CSR (
4372                      p_using_organization_id	=>-1);
4373      FETCH L_CATEGORY_ASL_IN_CUR_OU_CSR INTO x_asl_id,
4374       p_using_organization_id,
4375       x_vendor_product_num,
4376       x_purchasing_uom,
4377       x_consigned_from_supplier_flag,
4378       x_enable_vmi_flag;
4379 
4380      IF L_CATEGORY_ASL_IN_CUR_OU_CSR%FOUND
4381      THEN
4382         CLOSE L_CATEGORY_ASL_IN_CUR_OU_CSR;
4383         x_sequence_num := NULL;
4384         l_progress := '040';
4385         IF g_debug_stmt THEN
4386            PO_DEBUG.debug_stmt(l_log_head,l_progress,'Found:');
4387            PO_DEBUG.debug_var(l_log_head,l_progress,'x_asl_id', x_asl_id);
4388         END IF;
4389         RETURN;
4390      END IF;
4391 
4392      CLOSE L_CATEGORY_ASL_IN_CUR_OU_CSR;
4393 
4394      IF g_debug_stmt THEN
4395         --<Contract AutoSourcing FPJ>
4396         PO_DEBUG.debug_stmt(l_log_head,l_progress,'Look in Global category-based ASLs in other OUs');
4397      END IF;
4398 
4399      --Try to find Global ASLs in other operating units
4400      --Global ASL: p_using_organization_id = -1
4401      --Other OUs: p_operating_unit = NULL
4402      --Will return rows if we can find a GA in other OUs which are listed in ASLs
4403      OPEN L_CATEGORY_ASL_DOCUMENTS_CSR(
4404               P_using_organization_id	=> -1);
4405      FETCH L_CATEGORY_ASL_DOCUMENTS_CSR INTO x_asl_id,
4406       p_using_organization_id,
4407       x_vendor_product_num,
4408       x_purchasing_uom,
4409       x_consigned_from_supplier_flag,
4410       x_enable_vmi_flag,
4411       x_sequence_num;
4412 
4413      IF L_CATEGORY_ASL_DOCUMENTS_CSR %FOUND
4414      THEN
4415         CLOSE L_CATEGORY_ASL_DOCUMENTS_CSR;
4416         l_progress := '050';
4417         IF g_debug_stmt THEN
4418            PO_DEBUG.debug_stmt(l_log_head,l_progress,'Found:');
4419            PO_DEBUG.debug_var(l_log_head,l_progress,'x_asl_id', x_asl_id);
4420            PO_DEBUG.debug_var(l_log_head,l_progress,'x_sequence_num', x_sequence_num);
4421         END IF;
4422         RETURN;
4423      END IF;
4424 
4425      CLOSE L_CATEGORY_ASL_DOCUMENTS_CSR;
4426 
4427      x_vendor_product_num := NULL;
4428      x_purchasing_uom := NULL;
4429      x_consigned_from_supplier_flag := NULL;
4430      x_enable_vmi_flag := NULL;
4431      x_sequence_num := NULL;
4432      l_progress := '060';
4433 
4434      IF g_debug_stmt THEN
4435         --<Contract AutoSourcing FPJ>
4436         PO_DEBUG.debug_stmt(l_log_head,l_progress,'Matching Category-based ASL not found');
4437      END IF;
4438 
4439 EXCEPTION
4440     WHEN OTHERS THEN
4441          IF g_debug_unexp THEN
4442             PO_DEBUG.debug_exc(l_log_head,l_progress);
4443          END IF;
4444 
4445         PO_MESSAGE_S.SQL_ERROR('CATEGORY_BASED_ASL_SOURCING', l_progress, sqlcode);
4446 END CATEGORY_BASED_ASL_SOURCING;
4447 
4448 --<PKGCOMP R12 Start>
4449   -------------------------------------------------------------------------------
4450   --Start of Comments
4451   --Name: process_req_qty
4452   --Pre-reqs:
4453   --  None.
4454   --Modifies:
4455   --  PO_REQ_DIST_INTERFACE.
4456   --Locks:
4457   --  None.
4458   --Function:
4462   -- passed as the parameter.
4459   -- This procedure applies the order modifiers on the line level quantity
4460   -- and pro-rates the change in the line level quantity to the distributions.
4461   -- It converts the requisition quantity according the UOM conversion rate
4463   -- It also performs rounding operations on the line level quantity depending
4464   -- on the rounding factor, passed as an argument.
4465   --Parameters:
4466   --IN:
4467   --p_mode
4468   -- Valid values are 'INVENTORY' or 'VENDOR'. It determines the type of Requisition
4469   --  been processed
4470   --p_request_id
4471   -- The request_id to identify all the records to be processed during the
4472   -- concurrent request
4473   --p_multi_dist_flag
4474   -- 'Multiple Distribution' Value provided by the user during the concurrent
4475   -- request submission
4476   --p_req_dist_sequence_id
4477   -- It identifies the distributions for a given requisition
4478   --p_min_order_qty
4479   -- Order Modifier: Minimum Order Quantity
4480   --p_fixed_lot_multiple
4481   -- Order Modifier: Fixed Lot Multiple
4482    --p_uom_conversion_rate
4483   -- Conversion rate used for converting quantity from one uom to another
4484   --p_rounding factor
4485   -- Rounding factor used rounding the Requisition line level quantity
4486   --p_enforce_full_lot_qty
4487   -- PO System parameters: Enforce Full Lot Quantities. Valid values are
4488   -- NONE, ADVISORY and MANDATORY
4489   --IN OUT:
4490   --x_quantity
4491   -- Requisition line level quantity.
4492   --Testing:
4493   -- Refer the Technical Design for 'ReqImport Packaging Requirement Compliance'
4494   --End of Comments
4495 /*-----------------------------------------------------------------------------
4496   ALGORITHM
4497  => If the quantity on the Req line is less than the Minimum Order Quantity then
4498       Change the requisition quantity to Minimum Order Quantity.
4499 
4500  => If the quantity  on the Req line is not an integral multiple of Fixed Lot Multiple
4501       Increase the requisition quantity so that it becomes an integral Multiple.
4502 
4503  => Any change in the quantity due to application of Order Modifiers should
4504     be prorated to the distribution.
4505 
4506  => If p_uom_conversion_rate is not null then
4507       quantity on Req line and its distribution should be converted
4508 
4509  =>If it is a Purchase Requisition and p_rounding_factor is not null
4510         Perform Rounding.
4511    else if it is a Internal Requisition and p_rounding_factor is not null
4512         Check p_enforce_full_lot_qty should not be NONE.
4513         If it is not NONE then
4514               Perform Rounding.
4515 
4516  =>If rounding results in change of quantity then
4517       reflect the quantity change in the distribution with the max distribution_number.
4518  Note: Quantities on the distribution are only modified when all the three condition
4519        are satisfied.
4520 
4521        if the p_multi_dist_flag = 'Y'
4522        if p_req_dist_sequence_id is not null
4523        if distribution quantity is not null
4524  --------------------------------------------------------------------------------*/
4525 PROCEDURE process_req_qty(p_mode                  IN VARCHAR2,
4526                           p_request_id            IN NUMBER,
4527                           p_multi_dist_flag       IN VARCHAR2,
4528                           p_req_dist_sequence_id  IN NUMBER,
4529                           p_min_order_qty         IN NUMBER,
4530                           p_fixed_lot_multiple    IN NUMBER,
4531                           p_uom_conversion_rate   IN NUMBER,
4532                           p_rounding_factor       IN NUMBER,
4533                           p_enforce_full_lot_qty  IN VARCHAR2,
4534                           x_quantity              IN OUT NOCOPY NUMBER)
4535   IS
4536     l_temp_quantity PO_REQUISITIONS_INTERFACE.quantity%type;
4537     l_remainder      NUMBER;
4538     l_adjust         NUMBER;
4539     l_progress       VARCHAR2(3);
4540     l_log_head CONSTANT VARCHAR2(100) := g_log_head || 'PROCESS_REQ_QTY';
4541 
4542   BEGIN
4543     l_progress := '001';
4544 
4545     IF g_debug_stmt THEN
4546       PO_DEBUG.debug_begin(l_log_head);
4547       PO_DEBUG.debug_var(l_log_head,l_progress,'p_request_id',p_request_id);
4548       PO_DEBUG.debug_var(l_log_head,l_progress,'p_multi_dist_flag',p_multi_dist_flag);
4549       PO_DEBUG.debug_var(l_log_head,l_progress,'p_min_order_qty',p_min_order_qty);
4550       PO_DEBUG.debug_var(l_log_head,l_progress,'p_fixed_lot_multiple',p_fixed_lot_multiple);
4551       PO_DEBUG.debug_var(l_log_head,l_progress,'p_req_dist_sequence_id',p_req_dist_sequence_id);
4552       PO_DEBUG.debug_var(l_log_head,l_progress,'p_uom_conversion_rate',p_uom_conversion_rate);
4553       PO_DEBUG.debug_var(l_log_head,l_progress,'p_rounding_factor',p_rounding_factor);
4554       PO_DEBUG.debug_var(l_log_head, l_progress, 'x_quantity', x_quantity);
4555     END IF;
4556 
4557          --* Converting the Line level Quantity according to the change in the UOM
4558     --  using the p_uom_conversion_rate
4559     --we have already called nvl on   p_uom_conversion_rate before calling this function.
4560 
4561 	x_quantity := round((x_quantity * p_uom_conversion_rate), 18);
4562 
4563     	l_progress := '010';
4564 
4565     	IF g_debug_stmt THEN
4566      		 PO_DEBUG.debug_stmt(l_log_head,l_progress,'After UOM Conversion');
4567 		 PO_DEBUG.debug_var(l_log_head, l_progress, 'x_quantity', x_quantity);
4568    	 END IF;
4569 
4570      -- Keeping the requisition quantity in a temporary variable
4571     -- to determine the change in the quantity due to application
4575 
4572     -- of order modifiers.
4573 
4574 	  l_temp_quantity := x_quantity;
4576 	  l_progress := '020';
4577 
4578     	IF g_debug_stmt THEN
4579      		 PO_DEBUG.debug_stmt(l_log_head,l_progress,'After storing the quantity to temporary variable');
4580    	 END IF;
4581 
4582 
4583 	 -- Applying the 'Minimum Order Quantity' order Modifier. If the quantity on the req
4584     -- line is less than the Minimum Order Quantity, change the requisition quantity to
4585     -- Minimum Order Quantity.
4586 
4587     IF (p_min_order_qty is not null and x_quantity < p_min_order_qty) THEN
4588       x_quantity := p_min_order_qty;
4589     END IF;
4590 
4591     l_progress := '030';
4592 
4593     IF g_debug_stmt THEN
4594      		 PO_DEBUG.debug_stmt(l_log_head,l_progress,'After applying the minimum Order quantity');
4595 		  PO_DEBUG.debug_var(l_log_head, l_progress, 'x_quantity', x_quantity);
4596     END IF;
4597 
4598     -- Applying the 'Fixed Lot Multiple' order Modifier. If the quantity  on the req
4599     -- line is not an integral multiple of Fixed Lot Multiple increase the requisition
4600     -- quantity so that it becomes an integral Multiple.
4601 
4602       IF ((nvl(p_fixed_lot_multiple, 0) <> 0) AND (nvl(p_enforce_full_lot_qty,'NONE') <> 'NONE')) THEN
4603       x_quantity := ceil(x_quantity / p_fixed_lot_multiple) *
4604                     p_fixed_lot_multiple;
4605     END IF;
4606 
4607     l_progress := '040';
4608 
4609     IF g_debug_stmt THEN
4610       PO_DEBUG.debug_stmt(l_log_head,l_progress,'After Applying the Fixed Lot Multiple Order Modifiers');
4611       PO_DEBUG.debug_var(l_log_head, l_progress, 'x_quantity', x_quantity);
4612     END IF;
4613 
4614     --* Distribution table is only updated if Multi_dist_flag is 'Y'
4615 
4616     --* Pro-rating the change in the line level quantity to the distribution level quantity
4617     --  only if there is a change in the line level quantity.
4618 
4619     --* If the Purchasing UOM is different then we convert the distribution level quantity
4620     --  using the conversion rate.
4621     IF ((p_multi_dist_flag = 'Y')
4622          AND (p_req_dist_sequence_id IS NOT NULL)
4623          AND ((l_temp_quantity <> x_quantity) OR p_uom_conversion_rate IS NOT NULL)) THEN
4624 
4625       UPDATE PO_REQ_DIST_INTERFACE prdi
4626       SET    prdi.quantity = round((prdi.quantity *p_uom_conversion_rate)*
4627                                    (1 + (x_quantity - l_temp_quantity) / l_temp_quantity)
4628                                    , 18)
4629        WHERE prdi.dist_sequence_id = p_req_dist_sequence_id
4630        AND   prdi.quantity is not null
4631        AND   prdi.request_id = p_request_id;
4632 
4633     END IF;
4634 
4635 
4636     l_progress := '060';
4637 
4638      IF g_debug_stmt THEN
4639       PO_DEBUG.debug_stmt(l_log_head,l_progress,'After making the changed to distributions');
4640     END IF;
4641 
4642     -- Applying the rounding factor to the requisition line level quantity
4643     -- Rounding Factor for Internal Requisition is only applied if
4644     -- Enforce Full Lot Quantities is set to ADVISORY or MANDATORY
4645     IF ( p_rounding_factor IS NOT NULL
4646          AND( (p_mode = 'VENDOR')
4647               OR ( p_mode ='INVENTORY'
4648                    AND (nvl(p_enforce_full_lot_qty,'NONE') <> 'NONE')
4649                  )
4650              )
4651        ) THEN
4652 
4653       l_remainder := x_quantity - floor(x_quantity);
4654 
4655       IF l_remainder >= p_rounding_factor THEN
4656         x_quantity := ceil(x_quantity);
4657         l_adjust   := 1 - l_remainder;
4658       ELSE
4659         x_quantity := floor(x_quantity);
4660         l_adjust   := -l_remainder;
4661       END IF;
4662 
4663       IF g_debug_stmt THEN
4664         PO_DEBUG.debug_stmt(l_log_head,l_progress,'Before applying the change in quantity due to rounding');
4665         PO_DEBUG.debug_var(l_log_head, l_progress, 'l_adjust', l_adjust);
4666       END IF;
4667 
4668       --* If rounding results in change of quantity we reflect the quantity change in the
4669       --  distribution with the max distribution_number.
4670       IF (p_multi_dist_flag = 'Y'
4671 	   AND (p_req_dist_sequence_id IS NOT NULL)
4672            AND (l_adjust is NOT NULL )) THEN
4673 
4674         UPDATE PO_REQ_DIST_INTERFACE prdi
4675         SET    prdi.quantity = round((prdi.quantity + l_adjust), 18)
4676         WHERE  prdi.request_id = p_request_id
4677         AND    prdi.quantity is not null
4678         AND    prdi.dist_sequence_id = p_req_dist_sequence_id
4679         AND    distribution_number =
4680                   (SELECT MAX(distribution_number)
4681                    FROM   PO_REQ_DIST_INTERFACE
4682                    WHERE  prdi.request_id = p_request_id
4683                    AND    prdi.dist_sequence_id = p_req_dist_sequence_id);
4684 
4685       END IF;
4686       l_progress := '070';
4687       IF g_debug_stmt THEN
4688         PO_DEBUG.debug_stmt(l_log_head,l_progress,'After applying the change in quantity due to rounding');
4689       END IF;
4690 
4691     END IF;
4692     l_progress := '080';
4693 
4694     IF g_debug_stmt THEN
4695       PO_DEBUG.debug_stmt(l_log_head,l_progress,'After quantity rounding');
4696       PO_DEBUG.debug_var(l_log_head, l_progress, 'x_quantity', x_quantity);
4697       PO_DEBUG.debug_end(l_log_head);
4698     END IF;
4699 
4700   EXCEPTION
4701     WHEN OTHERS THEN
4705        END IF;
4702        FND_MSG_PUB.add_exc_msg (g_pkg_name,'process_req_qty');
4703        IF g_debug_unexp THEN
4704           PO_DEBUG.debug_exc (l_log_head ,l_progress);
4706        RAISE;
4707   END process_req_qty;
4708 --<PKGCOMP R12 End>
4709 
4710 --<PKGCOMP R12 Start>
4711 -- Added the parameter to get the parameter 'Multiple Distribution' Value provided by
4712 -- the user during the concurrent request submission.
4713 
4714 PROCEDURE reqimport_sourcing(
4715 	x_mode			IN	VARCHAR2,
4716 	x_request_id		IN	NUMBER,
4717         p_multi_dist_flag       IN      VARCHAR2
4718 ) IS
4719 --<PKGCOMP R12 End>
4720 	x_rowid				VARCHAR2(250) := '';
4721 	x_item_id			NUMBER := NULL;
4722 	x_category_id			NUMBER := NULL;
4723 	x_dest_organization_id		NUMBER := NULL;
4724 	x_dest_subinventory		VARCHAR2(10) := '';
4725 	x_need_by_date			DATE := NULL;
4726 	x_item_revision			VARCHAR2(3) := '';
4727 	x_currency_code			VARCHAR2(15) := '';
4728 	x_vendor_id			NUMBER := NULL;
4729 	x_vendor_name			PO_VENDORS.VENDOR_NAME%TYPE := NULL; --Bug# 1813740 / Bug 2823775
4730 	x_vendor_site_id		NUMBER := NULL;
4731 	x_vendor_contact_id		NUMBER := NULL;
4732 	x_source_organization_id	NUMBER := NULL;
4733 	x_source_subinventory		VARCHAR2(10) := '';
4734 	x_document_header_id		NUMBER := NULL;
4735 	x_document_line_id		NUMBER := NULL;
4736 	x_document_type_code		VARCHAR2(25) := '';
4737 	x_document_line_num		NUMBER := NULL;
4738 	x_buyer_id			NUMBER := NULL;
4739 	x_vendor_product_num		VARCHAR2(240) := '';
4740 	x_quantity			NUMBER := NULL;
4741 	x_rate_type			VARCHAR2(30) := '';
4742 	x_base_price			NUMBER := NULL;
4743 	x_currency_price		NUMBER := NULL;
4744 	x_discount			NUMBER := NULL;
4745 	x_rate_date			DATE := NULL;
4746 	x_rate				NUMBER := NULL;
4747 	x_return_code			BOOLEAN := NULL;
4748 	x_commodity_id			NUMBER := NULL;
4749 	x_purchasing_uom		po_asl_attributes.purchasing_unit_of_measure%type;
4750 	x_uom_code			po_requisitions_interface.uom_code%type;
4751 	x_unit_of_measure		po_requisitions_interface.unit_of_measure%type;
4752 	x_autosource_flag		po_requisitions_interface.autosource_flag%type;
4753 	x_organization_id		NUMBER := NULL;
4754 	x_conversion_rate		NUMBER := 1;
4755         x_item_buyer_id                 NUMBER;
4756         x_ga_flag                       VARCHAR2(1) := '';
4757         x_owning_org_id                 NUMBER;
4758         x_fsp_org_id                    NUMBER;
4759     --<Shared Proc FPJ START>
4760     x_suggested_vendor_site_code PO_VENDOR_SITES_ALL.vendor_site_code%TYPE;
4761     l_buyer_ok                   VARCHAR2(1);
4762     --<Shared Proc FPJ END>
4763 
4764     l_negotiated_by_preparer_flag   PO_LINES_ALL.NEGOTIATED_BY_PREPARER_FLAG%TYPE;  -- PO DBI FPJ
4765 
4766     --<PKGCOMP R12 Start>
4767     l_asl_id               PO_ASL_DOCUMENTS.ASL_ID%type;
4768     l_req_dist_sequence_id PO_REQUISITIONS_INTERFACE.req_dist_sequence_id%type;
4769     l_primary_uom          MTL_SYSTEM_ITEMS.primary_unit_of_measure%type;
4770     l_unit_of_issue        MTL_SYSTEM_ITEMS.unit_of_issue%type;
4771     l_rounding_factor      MTL_SYSTEM_ITEMS.rounding_factor%type;
4772     l_min_ord_qty          PO_ASL_ATTRIBUTES.min_order_qty%type;
4773     l_fixed_lot_multiple   PO_ASL_ATTRIBUTES.fixed_lot_multiple%type;
4774     l_uom_conversion_rate  NUMBER;
4775     l_enforce_full_lot_qty PO_SYSTEM_PARAMETERS.enforce_full_lot_quantities%type;
4776     l_interface_source_code  PO_REQUISITIONS_INTERFACE.interface_source_code%type;
4777     l_asl_purchasing_uom   PO_ASL_ATTRIBUTES.purchasing_unit_of_measure%type; --<Bug#5137508>
4778     --<PKGCOMP R12 End>
4779 
4780     --<R12 STYLES PHASE II START>
4781     l_line_type_id     PO_REQUISITION_LINES_ALL.line_type_id%TYPE;
4782     l_destination_type PO_REQUISITION_LINES_ALL.destination_type_code%TYPE;
4783     --<R12 STYLES PHASE II END>
4784 
4785     --<Shared Proc FPJ>
4786     --Changed the name of cursor from C1 to L_GET_REQ_INFO_VENDOR_CSR
4787 
4788     --<PKGCOMP R12 Start>
4789     -- Retrieving the dist_sequence_id for getting the distributions for the requisition
4790 
4791     Cursor L_GET_REQ_INFO_VENDOR_CSR is
4792 	SELECT  rowid,
4793 		item_id,
4794 		category_id,  -- Bug 5524728
4795 		destination_organization_id,
4796 		destination_subinventory,
4797 		nvl(need_by_date, sysdate),
4798 		item_revision,
4799 		currency_code,
4800 		quantity,
4801 		rate_type,
4802                 suggested_vendor_id,
4803                 suggested_vendor_name, --Bug# 1813740
4804                 suggested_vendor_site_id,
4805                 suggested_vendor_site,
4806                 suggested_vendor_item_num,
4807                 autosource_flag,
4808 		uom_code,
4809 		unit_of_measure,
4810                 req_dist_sequence_id,
4811                 interface_source_code
4812                 --<R12 STYLES PHASE II START>
4813                ,line_type_id
4814                ,destination_type_code
4815                 --<R12 STYLES PHASE II END>
4816 		FROM	po_requisitions_interface
4817 	WHERE 	autosource_flag in ('Y', 'P')
4818 	AND	source_type_code = 'VENDOR'
4819 	AND	item_id IS NOT NULL
4820 	AND	request_id = x_request_id;
4821     --<PKGCOMP R12 End>
4822 
4823     --<Shared Proc FPJ>
4824     --Changed the name of cursor from C2 to L_GET_REQ_INFO_INV_CSR
4825 
4826     --<PKGCOMP R12 Start>
4827     -- For Application Of Order Modifiers and UOM Conversion we need to retrieve
4828     -- quantity, unit_of_measure, and also the req_dist_sequence_id for getting the
4832 	SELECT  rowid,
4829     -- distributions for the requisition.
4830 
4831     CURSOR L_GET_REQ_INFO_INV_CSR IS
4833 		decode(item_id, NULL, category_id, NULL),
4834 		item_id,
4835 		destination_subinventory,
4836 		destination_organization_id,
4837                 source_organization_id,
4838                 source_subinventory,
4839 		nvl(need_by_date, sysdate),
4840 		quantity,
4841 		unit_of_measure,
4842 		req_dist_sequence_id,
4843                 interface_source_code
4844                 --<R12 STYLES PHASE II START>
4845                ,line_type_id
4846                ,destination_type_code
4847                 --<R12 STYLES PHASE II END>
4848 	FROM	po_requisitions_interface
4849 	WHERE	autosource_flag in ('Y', 'P')
4850 	AND	source_type_code = 'INVENTORY'
4851 	AND 	destination_organization_id IS NOT NULL
4852 	AND	request_id = x_request_id;
4853     --<PKGCOMP R12 End>
4854 
4855 BEGIN
4856   g_root_invoking_module := 'REQIMPORT'; --<Bug#4936992>
4857   IF (x_mode = 'VENDOR') THEN
4858 
4859     OPEN L_GET_REQ_INFO_VENDOR_CSR;
4860     LOOP
4861 
4862 	FETCH L_GET_REQ_INFO_VENDOR_CSR into
4863 		x_rowid,
4864 		x_item_id,
4865 		x_category_id,
4866 		x_dest_organization_id,
4867 		x_dest_subinventory,
4868 		x_need_by_date,
4869 		x_item_revision,
4870 		x_currency_code,
4871 		x_quantity,
4872 		x_rate_type,
4873                 x_vendor_id,
4874                 x_vendor_name,    --Bug# 1813740
4875                 x_vendor_site_id,
4876                 x_suggested_vendor_site_code, --<Shared Proc FPJ>
4877                 x_vendor_product_num,
4878                 x_autosource_flag,
4879 		x_uom_code,
4880 		x_unit_of_measure,
4881                 --<PKGCOMP R12 Start>
4882                l_req_dist_sequence_id
4883                ,l_interface_source_code
4884                 --<PKGCOMP R12 End>
4885                 --<R12 STYLES PHASE II START>
4886                ,l_line_type_id
4887                ,l_destination_type
4888                 --<R12 STYLES PHASE II END>
4889                 ;
4890 
4891     EXIT WHEN L_GET_REQ_INFO_VENDOR_CSR%NOTFOUND;
4892 
4893 	-- reinitialize values
4894     IF (x_autosource_flag = 'Y' or ( x_autosource_flag = 'P' and x_vendor_id
4895  is null)) THEN
4896                 x_vendor_id := NULL;
4897                 x_vendor_name := NULL;  -- Bug# 1813740
4898                 x_vendor_site_id := NULL;
4899                 x_suggested_vendor_site_code := NULL; --<Shared Proc FPJ>
4900                 x_vendor_product_num := NULL;
4901     END IF;
4902 
4903     -- DBI FPJ ** Begin
4904     IF x_document_type_code = 'BLANKET' THEN
4905 
4906         SELECT NEGOTIATED_BY_PREPARER_FLAG INTO l_negotiated_by_preparer_flag FROM PO_LINES_ALL
4907                 WHERE
4908                 PO_HEADER_ID = x_document_header_id AND LINE_NUM = x_document_line_num;
4909 
4910     ELSIF x_document_type_code = 'QUOTATION' THEN
4911 
4912         l_negotiated_by_preparer_flag := 'Y';
4913 
4914     ELSE
4915 
4916         l_negotiated_by_preparer_flag := 'N';
4917 
4918     END IF;
4919     -- DBI FPJ ** End
4920 
4921         x_document_header_id := NULL;
4922 	x_document_line_id := NULL;
4923 	x_document_type_code := NULL;
4924 	x_document_line_num := NULL;
4925 	x_vendor_contact_id := NULL;
4926 --	x_vendor_product_num := NULL;
4927 	x_purchasing_uom := NULL;
4928 	x_buyer_id := NULL;
4929 
4930         --<PKGCOMP R12 Start>
4931         l_asl_id               := NULL;
4932         l_uom_conversion_rate  := 1;
4933         l_fixed_lot_multiple   := NULL;
4934         l_min_ord_qty          := NULL;
4935         l_primary_uom          := NULL;
4936         l_rounding_factor      := NULL;
4937         l_enforce_full_lot_qty := NULL;
4938         --<PKGCOMP R12 End>
4939 
4940 /*      Bug # 1507557.
4941         The value of x_conversion_rate has to be initialised so that the
4942         conversion value of sourced record will not be carried to the
4943         next record.
4944 */
4945       x_conversion_rate := 1;
4946 
4947       IF x_dest_organization_id IS NULL THEN
4948 
4949        -- Get organization_id from financials_system_parameters.
4950 
4951             SELECT   inventory_organization_id
4952             INTO     x_organization_id
4953             FROM     financials_system_parameters;
4954 
4955       ELSE
4956            x_organization_id := x_dest_organization_id;
4957       END IF;
4958 
4959      IF (x_autosource_flag = 'Y' or ( x_autosource_flag = 'P' and x_vendor_id
4960  is null)) THEN
4961         --<PKGCOMP R12 Start>
4962         --Added the parameter to get the asl_id for the ASL so that we can retrieve
4963 	-- the order modifiers later in the procedure.
4964         --<PKGCOMP R12 End>
4965 
4966 	autosource(
4967 		'VENDOR',
4968 		'REQ',
4969 		x_item_id,
4970 		x_category_id,   -- Bug# 5524728,
4971 		x_dest_organization_id,
4972 		x_dest_subinventory,
4973 		x_need_by_date,
4974 		x_item_revision,
4975 		x_currency_code,
4976 		x_vendor_id,
4977 		x_vendor_site_id,
4978 		x_vendor_contact_id,
4979 		x_source_organization_id,
4980 		x_source_subinventory,
4981 		x_document_header_id,
4982 		x_document_line_id,
4983 		x_document_type_code,
4984 		x_document_line_num,
4988                 l_asl_id  --<PKGCOMP R12>
4985 		x_buyer_id,
4986 		x_vendor_product_num,
4987 		x_purchasing_uom,
4989                 --<R12 STYLES PHASE II START>
4990                ,null,
4991                 l_line_type_id,
4992                 l_destination_type,
4993                 null
4994                 --<R12 STYLES PHASE II END>
4995                 );
4996      ELSE
4997 
4998 
4999             -- Get buyer_id from item definition.  If we cannot get buyer_id from
5000             -- the item definition then we will try to get it from the source document.
5001 
5002             IF (x_item_id IS NOT NULL) THEN
5003 
5004                SELECT   msi.buyer_id
5005                INTO     x_buyer_id
5006                FROM     mtl_system_items msi
5007                WHERE    msi.inventory_item_id = x_item_id
5008                AND      msi.organization_id = x_organization_id;
5009 
5010                x_item_buyer_id := x_buyer_id;
5011 
5012             END IF;
5013 
5014             --<Shared Proc FPJ START>
5015             --To accommodate Planning calls: We do vendor site sourcing when
5016             --vendor site code is provided (vendor site_id is not provided)
5017 
5018             --<PKGCOMP R12 Start>
5019             -- Earlier hardcoded value of NULL was passed for asl_id in document_sourcing.
5020             -- But now we get back the value from document_sourcing procedure in l_asl_id.
5021             --<PKGCOMP R12 End>
5022 
5023 	        IF (x_autosource_flag = 'P' and x_vendor_id is not null
5024                   and x_vendor_site_id is null
5025                   and x_suggested_vendor_site_code is not null) THEN
5026 
5027                   document_sourcing(
5028                 	x_item_id             	 	=> x_item_id,
5029                 	x_vendor_id           		=> x_vendor_id,
5030                 	x_destination_doc_type	    => 'REQ',
5031                 	x_organization_id     		=> x_organization_id,
5032                 	x_currency_code       		=> x_currency_code,
5033                 	x_item_rev              	=> x_item_revision,
5034                 	x_autosource_date     		=> x_need_by_date,
5035                 	x_vendor_site_id     		=> x_vendor_site_id,
5036                 	x_document_header_id	    => x_document_header_id,
5037                 	x_document_type_code	    => x_document_type_code,
5038                 	x_document_line_num 	    => x_document_line_num,
5039                 	x_document_line_id   		=> x_document_line_id,
5040                 	x_vendor_contact_id  		=> x_vendor_contact_id,
5041                 	x_vendor_product_num	    => x_vendor_product_num,
5042                 	x_buyer_id          		=> x_buyer_id,
5043                 	x_purchasing_uom    		=>  x_purchasing_uom,
5044                         x_asl_id                    => l_asl_id, --<PKGCOMP R12>
5045                 	x_multi_org        	    	=> 'N',
5046 	        	p_vendor_site_sourcing_flag =>  'Y',
5047  	        	p_vendor_site_code  		=> x_suggested_vendor_site_code,
5048 			p_category_id                =>x_category_id -- Bug# 5524728
5049                         --<R12 STYLES PHASE II START>
5050                        ,p_line_type_id     => l_line_type_id,
5051                         p_purchase_basis   => NULL,
5052                         p_destination_type => l_destination_type,
5053                         p_style_id         => NULL
5054                         --<R12 STYLES PHASE II END>
5055                         );
5056 	        ELSE
5057                    --Its not required to do vendor site sourcing
5058  	           document_sourcing(
5059                 	x_item_id             	 	=> x_item_id,
5060                 	x_vendor_id           		=> x_vendor_id,
5061                 	x_destination_doc_type	    => 'REQ',
5062                 	x_organization_id     		=> x_organization_id,
5063                 	x_currency_code       		=> x_currency_code,
5064                 	x_item_rev              	=> x_item_revision,
5065                 	x_autosource_date     		=> x_need_by_date,
5066                 	x_vendor_site_id     		=> x_vendor_site_id,
5067                 	x_document_header_id	    => x_document_header_id,
5068                 	x_document_type_code	    => x_document_type_code,
5069                 	x_document_line_num 	    => x_document_line_num,
5070                 	x_document_line_id   		=> x_document_line_id,
5071                 	x_vendor_contact_id  		=> x_vendor_contact_id,
5072                 	x_vendor_product_num	    => x_vendor_product_num,
5073                 	x_buyer_id          		=> x_buyer_id,
5074                 	x_purchasing_uom    		=>  x_purchasing_uom,
5075                         x_asl_id                    => l_asl_id, --<PKGCOMP R12>
5076                 	x_multi_org        	    	=> 'N',
5077 	        	p_vendor_site_sourcing_flag =>  'N',
5078  	        	p_vendor_site_code  		=> NULL,
5079 			p_category_id                =>x_category_id -- Bug# 5524728
5080                         --<R12 STYLES PHASE II START>
5081                        ,p_line_type_id     => l_line_type_id,
5082                         p_purchase_basis   => NULL,
5083                         p_destination_type => l_destination_type,
5084                         p_style_id         => NULL
5085                         --<R12 STYLES PHASE II END>
5086                         );
5087              END IF;
5088              --<Shared Proc FPJ END>
5089 
5090               --<Shared Proc FPJ START>
5091               IF x_document_header_id is not null
5092                  AND x_buyer_id is NOT NULL
5093               THEN
5097                      --view definition of per_people_f
5094                       --The buyer on Source Document should be in the same business group as
5095                      --the requesting operating unit(current OU) or the profile option HR: Cross
5096                      --Business Group should be set to 'Y'. These two conditions are checked in
5098                      BEGIN
5099                              SELECT 'Y'
5100                              INTO l_buyer_ok
5101                              FROM per_people_f ppf
5102                              WHERE x_buyer_id = ppf.person_id
5103                              AND trunc(sysdate) between ppf.effective_start_date
5104                                      AND NVL(ppf.effective_end_date, sysdate +1);
5105                      EXCEPTION WHEN OTHERS THEN
5106                               x_buyer_id := NULL;
5107                      END;
5108 
5109               END IF;
5110               --<Shared Proc FPJ END>
5111         END IF;
5112 
5113         --<PKGCOMP R12 Start>
5114 
5115         --* Removing the code for bug 3810029 fix as we call the
5116         --  pocis_unit_of_measure for UOM defaulting before calling
5117         --  the sourcing procedure in reqimport code.
5118 
5119         -- We modify the quantity on the req line only if it is not null
5120         IF x_quantity IS NOT NULL THEN
5121             --* Retrieving the primary_unit_of_measure and rounding_factor
5122             -- from Item Masters
5123 
5124             BEGIN
5125               SELECT msi.primary_unit_of_measure, msi.rounding_factor
5126               INTO   l_primary_uom, l_rounding_factor
5127               FROM   mtl_system_items msi
5128               WHERE  msi.inventory_item_id = x_item_id
5129               AND    msi.organization_id = x_organization_id;
5130             EXCEPTION
5131               WHEN OTHERS THEN
5132                 l_primary_uom     := NULL;
5133                 l_rounding_factor := NULL;
5134             END;
5135 
5136         --* Retrieving the min_order_qty, fixed_lot_multiple from PO_ASL_ATTRIBUTES table,
5137         --  only if primary_uom of the item is same as the UOM mentioned on the requisition.
5138 
5139         --* This if condition is required as Order Modifiers will only be applied in case
5140         --  the above condition is true.
5141 
5142         --  <Bug#4025605 Start>
5143         --* We apply the order modifiers to requisitions generated from Inventory only
5144         --  (Interface source code = 'INV')
5145 
5146 
5147             IF (l_asl_id IS NOT NULL AND l_interface_source_code = 'INV' ) THEN
5148               BEGIN
5149                 SELECT min_order_qty, fixed_lot_multiple, purchasing_unit_of_measure
5150                 INTO   l_min_ord_qty, l_fixed_lot_multiple, l_asl_purchasing_uom
5151                 FROM   PO_ASL_ATTRIBUTES
5152                 WHERE  ASL_ID = l_asl_id;
5153               EXCEPTION
5154                 WHEN OTHERS THEN
5155                   l_min_ord_qty := NULL;
5156                   l_fixed_lot_multiple := NULL;
5157               END;
5158               IF x_unit_of_measure IS NULL OR (x_unit_of_measure <> l_primary_uom) THEN
5159                   l_min_ord_qty := NULL;
5160                   l_fixed_lot_multiple := NULL;
5161               END IF;
5162               --<Bug#5137508 Start>
5163               --We will be applying the ASL Purchasing UOM if the Sourcing routine
5164               --does not fetch any Blanket Agreement. This is because Contract Agreement
5165               --wont have an UOM and we would pick the UOM from the
5166               IF  x_document_line_id IS NULL THEN
5167                 x_purchasing_uom := l_asl_purchasing_uom;
5168               END IF;
5169               --<Bug#5137508 End>
5170             END IF;
5171         --  <Bug#4025605 End>
5172             --* Get the conversion rate between the Req's UOM and the Sourcing document's UOM
5173             --  if the source document exists else get the conversion rate between Req's UOM and
5174             --  ASL's Purchasing UOM if an ASL exists.
5175 
5176             --* Sourcing Document UOM is given preference over the ASL's Purchasing UOM.
5177 
5178             IF nvl(x_purchasing_uom, x_unit_of_measure) <> x_unit_of_measure THEN
5179               l_uom_conversion_rate := nvl(po_uom_s.po_uom_convert(x_unit_of_measure,
5180                                                                    x_purchasing_uom,
5181                                                                    x_item_id),1);
5182             END IF;
5183 
5184             -- Calling the procedure for applying order modifier, quantity conversion and rounding
5185             PO_AUTOSOURCE_SV.process_req_qty(p_mode                 => x_mode,
5186                                              p_request_id           => x_request_id,
5187                                              p_multi_dist_flag      => p_multi_dist_flag,
5188                                              p_req_dist_sequence_id => l_req_dist_sequence_id,
5189                                              p_min_order_qty        => l_min_ord_qty,
5190                                              p_fixed_lot_multiple   => l_fixed_lot_multiple,
5191                                              p_uom_conversion_rate  => l_uom_conversion_rate,
5192                                              p_rounding_factor      => l_rounding_factor,
5193                                              p_enforce_full_lot_qty => l_enforce_full_lot_qty,
5194                                              x_quantity             => x_quantity);
5195         END IF;
5196         --<PKGCOMP R12 End>
5197 
5198 
5199 
5203    -- we now NULL out the vendor name when autosource flag is 'Y'. The logic in
5200    -- Bug 1813740 - When suggested vendor name was populated in the Interface
5201    -- table and if Sourcing takes place and brings in a new Vendor Id the
5202    -- Vendor Name was not changed to that of the new vendor Id. To avoid this
5204    -- pocis.opc takes care of populating the suggested_vendor_name if it
5205    -- is NULL.
5206    -- Bug 3669203: The vendorname should only be nulled out if autosourcing
5207    -- brought back a new vendor.
5208    -- Bug 3810029 : changed the uom update : see above
5209 
5210    --<PKGCOMP R12 Start>
5211       -- Update the po_requisitions_interface table with the calculated quantity returned
5212       -- by the above procedure instead of computing the new quantity in the update statement.
5213 
5214 	UPDATE  po_requisitions_interface
5215 	SET	suggested_vendor_id = nvl(x_vendor_id,suggested_vendor_id),
5216 		suggested_vendor_name = decode(x_vendor_id, null , suggested_vendor_name, x_vendor_name),
5217 		suggested_vendor_site_id = nvl(x_vendor_site_id,suggested_vendor_site_id),
5218 		suggested_buyer_id = nvl(suggested_buyer_id, x_buyer_id),
5219 		autosource_doc_header_id = x_document_header_id,
5220 		autosource_doc_line_num	= x_document_line_num,
5221 		document_type_code = x_document_type_code,
5222                 -- Bug 4523369 START
5223                 -- If autosourcing did not return a vendor site, keep the
5224                 -- current vendor contact.
5225 		suggested_vendor_contact_id =
5226                   decode(x_vendor_site_id,
5227                          null, suggested_vendor_contact_id,
5228                          x_vendor_contact_id),
5229                 -- Bug 4523369 END
5230 		suggested_vendor_item_num =
5231 			nvl(suggested_vendor_item_num, x_vendor_product_num),
5232 		unit_of_measure = nvl(x_purchasing_uom,nvl(x_unit_of_measure,unit_of_measure)),
5233 		quantity = x_quantity, --<PKGCOMP R12>
5234                 negotiated_by_preparer_flag = l_negotiated_by_preparer_flag   -- DBI FPJ
5235  	WHERE	rowid = x_rowid;
5236 
5237    --<PKGCOMP R12 End>
5238     END LOOP;
5239     CLOSE L_GET_REQ_INFO_VENDOR_CSR;
5240 
5241     /* 7234465 - Imported Requisitions were getting Reserved Even when the Source BPA is Encumbered. */
5242 	/* This sql will set the Prevent Encumbrance Flag to Y, if BPA is Encumbered. */
5243 	UPDATE po_Requisitions_InterFace po_Requisitions_InterFace
5244 	SET    po_Requisitions_InterFace.Prevent_Encumbrance_Flag = 'Y'
5245 	WHERE  po_Requisitions_InterFace.AutoSource_Doc_Header_Id IS NOT NULL
5246 	AND    po_Requisitions_Interface.request_id = x_request_id
5247        AND EXISTS (SELECT 'BPA Encumbered'
5248                    FROM   po_Distributions_All d,
5249                           po_Headers_All h
5250                    WHERE  h.po_Header_Id = po_Requisitions_InterFace.AutoSource_Doc_Header_Id
5251                           AND h.po_Header_Id = d.po_Header_Id
5252                           AND h.Type_LookUp_Code = 'BLANKET'
5253                           AND d.Line_Location_Id IS NULL
5254                           AND d.po_Release_Id IS NULL
5255                           AND Nvl(d.Encumbered_Flag,'N') = 'Y');
5256 	/*7234465 End*/
5257 
5258   ELSIF (x_mode = 'INVENTORY') THEN
5259 
5260     --<PKGCONS Start>
5261     --Fecthing the value of ENFORCE_FULL_LOT_QUANTITY for determining whether
5262     --UOM conversion and rounding operations are to be performed on the
5263     --Requisition.
5264     SELECT enforce_full_lot_quantities
5265     INTO l_enforce_full_lot_qty
5266     FROM po_system_parameters;
5267     --<PKGCONS End>
5268 
5269     OPEN L_GET_REQ_INFO_INV_CSR;
5270     LOOP
5271 
5272 
5273 	x_buyer_id := NULL;
5274 	x_source_organization_id := NULL;
5275 	x_source_subinventory := NULL;
5276 	x_document_header_id := NULL;
5277 	x_document_line_id := NULL;
5278 	x_document_type_code := NULL;
5279 	x_document_line_num := NULL;
5280 	x_vendor_product_num := NULL;
5281 	x_purchasing_uom := NULL;
5282         --<PKGCOMP R12 Start>
5283         x_quantity             := NULL;
5284         x_unit_of_measure      := NULL;
5285         l_uom_conversion_rate  := 1;
5286         l_fixed_lot_multiple   := NULL;
5287         l_min_ord_qty          := NULL;
5288         l_unit_of_issue        := NULL;
5289         l_req_dist_sequence_id := NULL;
5290         l_rounding_factor      := NULL;
5291         l_asl_id               := NULL;
5292         --<PKGCOMP R12 End>
5293 
5294 
5295 	FETCH L_GET_REQ_INFO_INV_CSR into
5296 		x_rowid,
5297 		x_commodity_id,
5298 		x_item_id,
5299 		x_dest_subinventory,
5300 		x_dest_organization_id,
5301 		x_source_organization_id,
5302 		x_source_subinventory,
5303 		x_need_by_date,
5304                 --<PKGCOMP R12 Start>
5305                 x_quantity,
5306                 x_unit_of_measure,
5307                 l_req_dist_sequence_id,
5308                 l_interface_source_code
5309                 --<PKGCOMP R12 End>
5310                 --<R12 STYLES PHASE II START>
5311                ,l_line_type_id
5312                ,l_destination_type
5313                 --<R12 STYLES PHASE II END>
5314                 ;
5315 
5316 
5317 	EXIT WHEN L_GET_REQ_INFO_INV_CSR%NOTFOUND;
5318 
5319         --<PKGCOMP R12 Start>
5320         -- Added the parameter to get the asl_id for the ASL so that we can retrieve the
5321         -- order modifiers later in the procedure.
5322         --<PKGCOMP R12 End>
5323 	autosource(
5324 		'INVENTORY',
5325 		'REQ',
5326 		x_item_id,
5330 		x_need_by_date,
5327 		x_commodity_id,
5328 		x_dest_organization_id,
5329 		x_dest_subinventory,
5331 		x_item_revision,
5332 		x_currency_code,
5333 		x_vendor_id,
5334 		x_vendor_site_id,
5335 		x_vendor_contact_id,
5336 		x_source_organization_id,
5337 		x_source_subinventory,
5338 		x_document_header_id,
5339 		x_document_line_id,
5340 		x_document_type_code,
5341 		x_document_line_num,
5342 		x_buyer_id,
5343 		x_vendor_product_num,
5344 		x_purchasing_uom,
5345 		l_asl_id --<PKGCOMP R12>
5346                 --<R12 STYLES PHASE II START>
5347                ,null,
5348                 l_line_type_id,
5349                 l_destination_type,
5350                 null
5351                 --<R12 STYLES PHASE II END>
5352                 );
5353 
5354 	--<PKGCOMP R12 Start>
5355         --Retrieving the primary_unit_of_measure and rounding_factor
5356         --from Item Masters of source organisation
5357 
5358 	BEGIN
5359           SELECT msi.primary_unit_of_measure, msi.rounding_factor, msi.unit_of_issue
5360           INTO   l_primary_uom, l_rounding_factor, l_unit_of_issue
5361           FROM   mtl_system_items msi
5362           WHERE  msi.inventory_item_id = x_item_id
5363           AND    msi.organization_id = x_source_organization_id;
5364         EXCEPTION
5365           WHEN OTHERS THEN
5366             l_primary_uom     := NULL;
5367             l_rounding_factor := NULL;
5368             l_unit_of_issue   := NULL;
5369         END;
5370 
5371         -- We can apply the order modifiers or do any processing on the req quantity
5372         -- only if it is not null
5373         IF x_quantity IS NOT NULL THEN
5374             --* We retrieve and apply order modifiers <min_order_qty, fixed_lot_multiple >
5375             --  1. if primary_uom of  the item is same as the UOM mentioned on the requisition
5376             --  2. if  requisitions are generated from Inventory(Interface source code = 'INV') <Bug#4025605 Start>
5377 
5378             --* The values from MTL_ITEM_SUB_INVENTORIES take precedence over MTL_SYSTEM_ITEMS.
5379 
5380             IF (l_primary_uom = x_unit_of_measure
5381                  AND l_interface_source_code = 'INV')THEN
5382 
5383                 IF x_source_subinventory IS NOT NULL THEN
5384                     BEGIN
5385                         SELECT mssi.fixed_lot_multiple, mssi.minimum_order_quantity
5386                         INTO   l_fixed_lot_multiple, l_min_ord_qty
5387                         FROM   MTL_ITEM_SUB_INVENTORIES mssi
5388                         WHERE  mssi.secondary_inventory = x_source_subinventory
5389                         AND    mssi.inventory_item_id = x_item_id
5390                         AND    mssi.organization_id = x_source_organization_id;
5391                     EXCEPTION
5392                         WHEN NO_DATA_FOUND THEN
5393                            l_fixed_lot_multiple := null;
5394                            l_min_ord_qty        := null;
5395                     END;
5396                 END IF; --x_source_subinventory IS NOT NULL
5397 
5398                 IF ((l_fixed_lot_multiple is null) OR (l_min_ord_qty is null)) THEN
5399                     -- In the exception we are intentionally doing nothing because
5400                     -- we want to retain the data from the previous query even if this
5401                     -- query raises an exception.
5402                     BEGIN
5403                         SELECT nvl(l_fixed_lot_multiple,msi.fixed_lot_multiplier),
5404                                nvl(l_min_ord_qty, msi.minimum_order_quantity)
5405                         INTO   l_fixed_lot_multiple, l_min_ord_qty
5406                         FROM   MTL_SYSTEM_ITEMS msi
5407                         WHERE  msi.inventory_item_id = x_item_id
5408                         AND    msi.organization_id = x_source_organization_id;
5409                     EXCEPTION
5410                         WHEN NO_DATA_FOUND THEN
5411                              NULL;
5412                     END;
5413                 END IF; --(l_fixed_lot_multiple is null) OR (l_min_ord_qty is null)
5414 
5415             END IF; --_primary_uom = x_unit_of_measure
5416 
5417             --* Get the conversion rate between the Req's UOM and the unit of issue.
5418             --  only if enforce_full_lot_quantities is set to 'ADVISORY' or 'MANDATORY'
5419             IF ( (nvl(l_unit_of_issue, x_unit_of_measure) <> x_unit_of_measure)
5420                  AND (nvl(l_enforce_full_lot_qty,'NONE') <> 'NONE')
5421                ) THEN
5422                  l_uom_conversion_rate := nvl(po_uom_s.po_uom_convert(x_unit_of_measure,
5423                                                                       l_unit_of_issue,
5424                                                                       x_item_id),1);
5425             END IF;
5426 
5427             -- Calling the procedure for applying order modifier, quantity conversion and rounding
5428             PO_AUTOSOURCE_SV.process_req_qty(p_mode                 => x_mode,
5429                                              p_request_id           => x_request_id,
5430                                              p_multi_dist_flag      => p_multi_dist_flag,
5431                                              p_req_dist_sequence_id => l_req_dist_sequence_id,
5432                                              p_min_order_qty        => l_min_ord_qty,
5433                                              p_fixed_lot_multiple   => l_fixed_lot_multiple,
5434                                              p_uom_conversion_rate  => l_uom_conversion_rate,
5435                                              p_rounding_factor      => l_rounding_factor,
5439         END IF;
5436                                              p_enforce_full_lot_qty => l_enforce_full_lot_qty,
5437                                              x_quantity             => x_quantity);
5438 
5440         -- Updating the quantity and the unit_of_measure in the po_requisitions_interface
5441         -- after the quantity conversion.
5442 
5443         -- We need to put the l_enforce_full_lot_qty in the decode as there should be no
5444         -- UOM conversion if enforce_full_lot_quantities is set to 'NONE'
5445         UPDATE po_requisitions_interface
5446         SET source_organization_id = x_source_organization_id,
5447             source_subinventory    = x_source_subinventory,
5448             suggested_buyer_id     = nvl(suggested_buyer_id, x_buyer_id),
5449             quantity               = x_quantity,
5450             unit_of_measure        = decode(nvl(l_enforce_full_lot_qty, 'NONE'),
5451                                                'NONE',x_unit_of_measure,
5452                                                nvl(l_unit_of_issue,x_unit_of_measure))
5453         WHERE rowid = x_rowid;
5454         --<PKGCOMP R12 End>
5455 
5456     END LOOP;
5457     CLOSE L_GET_REQ_INFO_INV_CSR;
5458 
5459   END IF;
5460   g_root_invoking_module := NULL; --<Bug#4936992>
5461 END reqimport_sourcing;
5462 
5463 
5464 /* Cto Changes FPH. For the given item id this procedure gives all the valid vendor ,
5465  * vendor sites and Asl ids from the global Asl.
5466 */
5467 
5468 Procedure Get_All_Item_Asl(
5469                         x_item_id                    IN   Mtl_system_items.inventory_item_id%type,
5470                         x_using_organization_id      IN    Number, --will be -1
5471                         X_vendor_details             IN OUT NOCOPY PO_AUTOSOURCE_SV.vendor_record_details,
5472 			x_return_status              OUT NOCOPY varchar2,
5473 			x_msg_count                  OUT NOCOPY Number,
5474 			x_msg_data                   OUT NOCOPY Varchar2 ) is
5475 
5476 CURSOR C is
5477 SELECT   pasl.vendor_id,
5478          pasl.vendor_site_id,
5479          pasl.asl_id,
5480          pasl.primary_vendor_item,
5481          paa.purchasing_unit_of_measure
5482           FROM     po_approved_supplier_lis_val_v pasl,
5483                    po_asl_attributes paa,
5484            	   po_asl_status_rules_v pasr
5485           WHERE    pasl.item_id = x_item_id
5486           AND     (pasl.using_organization_id IN
5487                                         (-1, x_using_organization_id))
5488           AND      pasl.asl_id = paa.asl_id
5489      	  AND      pasr.business_rule like '2_SOURCING'
5490       	  AND      pasr.allow_action_flag like 'Y'
5491       	  AND      pasr.status_id = pasl.asl_status_id
5492           AND      paa.using_organization_id =
5493                         (SELECT  max(paa2.using_organization_id)
5494 			 FROM    po_asl_attributes paa2
5495                          WHERE   paa2.asl_id = pasl.asl_id
5496                          AND     (pasl.using_organization_id IN
5497                                                 (-1,x_using_organization_id)))
5498           ORDER BY pasl.using_organization_id DESC;
5499 n number :=0;
5500 begin
5501          x_msg_data := 'No error';
5502          x_msg_count := 0;
5503          x_return_status := FND_API.G_RET_STS_SUCCESS;
5504         x_vendor_details.DELETE;
5505         open c;
5506         loop
5507                 n := n+1;
5508                 fetch c into x_vendor_details(n);
5509                 exit when c%notfound;
5510         end loop;
5511   exception
5512 when others then
5513 x_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
5514 FND_MSG_PUB.Count_And_Get
5515   	 (p_count => x_msg_count
5516    	 ,p_data  => x_msg_data
5517     	 );
5518 end;
5519 
5520 /* Cto Changes FPH. This is a wrapper for the procedure document_sourcing to give only
5521  * the Blanket PO information. Returns x_doc_Return as Y if it has any blankets.
5522  * The parameters x_destination_doc_type,x_currency_code,x_autosource_date can be null.
5523  * The parameter x_item_rev must be sent if you want the blanket info which has this
5524  * item revision. x_organization_id should be -1 if you want the global asls only.
5525 */
5526 
5527 Procedure blanket_document_sourcing(
5528 	 	x_item_id               IN      NUMBER,
5529                 x_vendor_id             IN      NUMBER,
5530                 x_destination_doc_type  IN      VARCHAR2,
5531                 x_organization_id       IN      NUMBER,
5532                 x_currency_code         IN      VARCHAR2,
5533                 x_item_rev              IN      VARCHAR2,
5534                 x_autosource_date       IN      DATE,
5535                 x_vendor_site_id        IN OUT NOCOPY  NUMBER,
5536                 x_document_header_id    IN OUT NOCOPY  NUMBER,
5537                 x_document_type_code    IN OUT NOCOPY  VARCHAR2,
5538                 x_document_line_num     IN OUT NOCOPY  NUMBER,
5539 		x_document_line_id      IN OUT NOCOPY  NUMBER,
5540                 x_vendor_contact_id     IN OUT NOCOPY  NUMBER,
5541                 x_vendor_product_num    IN OUT NOCOPY  VARCHAR2,
5542                 x_buyer_id              IN OUT NOCOPY  NUMBER,
5543                 x_purchasing_uom        IN OUT NOCOPY  VARCHAR2, -- should be sent since if the value obtained from get_all_item_asl is null this is used.
5544                 x_return_status 	   OUT NOCOPY varchar2,
5545                  x_msg_count     	   OUT NOCOPY Number,
5546                  x_msg_data      	   OUT NOCOPY Varchar2,
5550 IS
5547 		 x_doc_return		   OUT NOCOPY Varchar2,
5548                 x_asl_id 	       	IN     NUMBER default null,
5549                 x_multi_org        	IN     VARCHAR2 default 'N') --cto sends Y  Cto Changes FPH
5551 x_type_lookup_code varchar2(25);
5552 
5553 --<PKGCOMP R12 Start>
5554 -- Added a variable for making local copy of x_asl_id It is required because now x_asl_id
5555 -- would be a IN OUT parameter in document_sourcing procedure, which  return a value.
5556 -- In order to maintain the existing flow we make a local copy and pass it to the document_sourcing.
5557 
5558 l_local_asl_id PO_ASL_DOCUMENTS.asl_id%type;
5559 --<PKGCOMP R12 End>
5560 begin
5561 	x_msg_data :='No error';
5562         x_msg_count := 0;
5563         x_return_status := FND_API.G_RET_STS_SUCCESS;
5564 	x_doc_return := 'Y';
5565 	--<PKGCOMP R12 Start>
5566 	l_local_asl_id := x_asl_id;
5567 	--<PKGCOMP R12 End>
5568     --<Shared Proc FPJ START>
5569     --We are doing only document sourcing so the p_vendor_site_sourcing_flag
5570     --is 'N'.
5571     document_sourcing(
5572                         x_item_id	           =>x_item_id,
5573                	        x_vendor_id		   =>x_vendor_id,
5574                	        x_destination_doc_type	   =>x_destination_doc_type,
5575                 	x_organization_id 	   =>x_organization_id,
5576                 	x_currency_code 	   =>x_currency_code,
5577                 	x_item_rev	           =>x_item_rev,
5578                 	x_autosource_date 	   =>x_autosource_date,
5579                 	x_vendor_site_id 	   =>x_vendor_site_id,
5580                 	x_document_header_id	   =>x_document_header_id,
5581                 	x_document_type_code 	   =>x_document_type_code,
5582                 	x_document_line_num	   =>x_document_line_num,
5583                 	x_document_line_id	   =>x_document_line_id,
5584                 	x_vendor_contact_id	   =>x_vendor_contact_id,
5585                 	x_vendor_product_num 	   =>x_vendor_product_num,
5586                 	x_buyer_id 		   =>x_buyer_id,
5587                 	x_purchasing_uom	   =>x_purchasing_uom,
5588                 	x_asl_id	           =>l_local_asl_id,--<PKGCOMP R12>
5589                 	x_multi_org		   =>x_multi_org,
5590                 	p_vendor_site_sourcing_flag =>'N',
5591                 	p_vendor_site_code	   =>NULL);
5592 
5593     --<Shared Proc FPJ END>
5594 	IF x_document_header_id is NOT NULL THEN --<Shared Proc FPJ>
5595 	  select poh.type_lookup_code
5596 	  into x_type_lookup_code
5597 	  from po_headers_all poh
5598         where poh.po_header_id = x_document_header_id;
5599 
5600    	 /* If it is not blanket then return null */
5601      if (x_type_lookup_code <>  'BLANKET') THEN
5602 		x_doc_return := 'N';
5603 	 end if;
5604     ELSE
5605         x_doc_return := 'N'; --<Shared Proc FPJ>
5606     END IF;
5607 
5608 exception
5609 when others then
5610 x_doc_return := 'N'; -- no rows were obtained from document_sourcing
5611 x_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
5612 FND_MSG_PUB.Count_And_Get
5613   	 (p_count => x_msg_count
5614    	 ,p_data  => x_msg_data
5615     	 );
5616 end blanket_document_sourcing;
5617 
5618 --------------------------------------------------------------------------------
5619 --Start of Comments
5620 --Name        : is_dup_vendor_record
5621 --Pre-reqs    : None
5622 --Modifies    : None
5623 --Locks       : None
5624 --Function    : To determine if a given (vendor, vendor site) record is prent in
5625 --              a given list of (vendor, vendor site) records.
5626 --Parameter(s):
5627 -- IN         : p_vendor_id - The Vendor id that needs to be checked in the list
5628 --              p_vendor_site_id - The Vendor Site that needs to be checked.
5629 --              p_vendor_id_list - The list of vendors where the check is
5630 --                                 required to be done.
5631 --              p_vendor_site_id_list - The list of vendors sites where the
5632 --                                 check is required to be done.
5633 --
5634 -- IN OUT     : None
5635 --Returns     : BOOLEAN
5636 --                TRUE: If the (vendor, vendor site) record belongs to the given
5637 --                      list of (vendor, vendor site) records.
5638 --                FALSE: Otherwise
5639 --Notes       : None
5640 --Testing     : None
5641 --End of Comments
5642 --------------------------------------------------------------------------------
5643 FUNCTION is_dup_vendor_record(p_vendor_id           IN NUMBER,
5644                               p_vendor_site_id      IN NUMBER,
5645                               p_vendor_id_list      IN po_tbl_number,
5646                               p_vendor_site_id_list IN po_tbl_number)
5647 RETURN BOOLEAN
5648 IS
5649 BEGIN
5650   IF (p_vendor_id_list.FIRST IS NOT NULL) THEN
5651     FOR i IN p_vendor_id_list.FIRST..p_vendor_id_list.LAST LOOP
5652       IF (p_vendor_id_list(i) = p_vendor_id AND
5653           nvl(p_vendor_site_id_list(i), -1) = nvl(p_vendor_site_id, -1)) THEN
5654         RETURN TRUE;
5655       END IF;
5656     END LOOP;
5657   END IF;
5658   RETURN FALSE;
5659 END is_dup_vendor_record;
5660 
5661 --------------------------------------------------------------------------------
5662 --Start of Comments
5663 --Name        : is_vendor_site_outside_OU
5664 --Pre-reqs    : None
5665 --Modifies    : None
5666 --Locks       : None
5667 --Function    : To determine if a vendor site belongs to a given Operating Unit.
5668 --Parameter(s):
5669 -- IN         : p_vendor_site_id - The Vendor Site that needs to be checked.
5673 --Returns     : BOOLEAN
5670 --              p_ou_id - The ID of the Operating Unit where the check is
5671 --                        required.
5672 -- IN OUT     : None
5674 --                TRUE: If the vendor site belongs to the given OU
5675 --                FALSE: Otherwise
5676 --Notes       : None
5677 --Testing     : None
5678 --End of Comments
5679 --------------------------------------------------------------------------------
5680 FUNCTION is_vendor_site_outside_OU(p_vendor_site_id IN NUMBER,
5681                                    p_ou_id          IN NUMBER)
5682 RETURN BOOLEAN
5683 IS
5684   l_vendor_site_status VARCHAR2(20);
5685 BEGIN
5686   SELECT 'Site is within OU'
5687   INTO l_vendor_site_status
5688   FROM po_vendor_sites_all
5689   WHERE vendor_site_id = p_vendor_site_id
5690     AND org_id = p_ou_id;
5691 
5692   RETURN FALSE;
5693 EXCEPTION
5694   WHEN NO_DATA_FOUND THEN
5695     RETURN TRUE;
5696   WHEN OTHERS THEN
5697     RAISE;
5698 END is_vendor_site_outside_OU;
5699 
5700 --------------------------------------------------------------------------------
5701 --Start of Comments
5702 --Name        : validate_vendor_sites
5703 --Pre-reqs    : None
5704 --Modifies    : None
5705 --Locks       : None
5706 --Function    : To validate that the vendor site is active and is a valid
5707 --              purchasing or rfq_only site. If the vendor site is invalid, then
5708 --              it is nulled out. We do not want to skip the whole (supplier,
5709 --              supplier site) record if just the site is invalid.
5710 --Parameter(s):
5711 -- IN         : None
5712 -- IN OUT     : px_vendor_site_id_list - The list of vendor sites found for the
5713 --                                       given commodity. The site is nulled out
5714 --                                       if found invalid.
5715 --Returns     : None
5716 --Notes       : None
5717 --Testing     : None
5718 --End of Comments
5719 --------------------------------------------------------------------------------
5720 PROCEDURE validate_vendor_sites(px_vendor_site_id_list IN OUT NOCOPY po_tbl_number)
5721 IS
5722  l_vendor_site_status VARCHAR2(20);
5723 BEGIN
5724   IF (px_vendor_site_id_list.FIRST IS NULL) THEN
5725     RETURN;
5726   END IF;
5727 
5728   FOR i IN px_vendor_site_id_list.FIRST..px_vendor_site_id_list.LAST LOOP
5729     IF (px_vendor_site_id_list(i) IS NOT NULL) THEN
5730       BEGIN
5731         SELECT 'Valid supplier site'
5732         INTO   l_vendor_site_status
5733         FROM   po_vendor_sites_all
5734         WHERE  vendor_site_id = px_vendor_site_id_list(i)
5735           AND  (purchasing_site_flag = 'Y' OR rfq_only_site_flag = 'Y')
5736           AND  sysdate <= nvl(inactive_date, sysdate);
5737       EXCEPTION
5738         WHEN NO_DATA_FOUND THEN
5739           -- Invalid vendor site, null it out
5740           px_vendor_site_id_list(i) := NULL;
5741         WHEN OTHERS THEN
5742           RAISE;
5743       END;
5744     END IF;
5745   END LOOP;
5746 END validate_vendor_sites;
5747 
5748 ---------------------------------------------------------------------------------------
5749 --Start of Comments
5750 --Name        : get_services_asl_list
5751 --
5752 --Pre-reqs    : None
5753 --
5754 --Modifies    : None
5755 --
5756 --Locks       : None
5757 --
5758 --Function    : This procedure will obtain a list of ASL, their associated purchasing
5759 --              documents and pricing information.
5760 --
5761 --Parameter(s):
5762 --
5763 --IN          : p_job_id              : The job for which we need to retrieve the ASL Documents
5764 --              p_category_id         : The category for which we need to retreive the ASL's
5765 --              p_order_type_lookup_code : The value basis of Line type on the Document Line
5766 --                p_start_date          : Assignment start date to determine pricing
5767 --              p_deliver_to_loc_id   : Deliver to location to determine pricing
5768 --              p_destination_org_id  : Destination organizations to determine pricing
5769 --              p_api_version         : The value is 1.0
5770 --              p_init_msg_list       : Standard API parameter: Initializes FND
5771 --                                      message list if set to FND_API.G_TRUE.
5772 --
5773 --IN OUT:     : None
5774 --
5775 --
5776 --Returns     : Vendor ID
5777 --              Vendor Site ID
5778 --              Vendor Contact ID
5779 --              Document Header ID
5780 --              Document Line ID
5781 --              Document Line Num
5782 --              Price break ID
5783 --              Document Type
5784 --              Base currency Price
5785 --              Foreign currency Price
5786 --              Document UOM
5787 --              Document Currency
5788 --              Price Override flag
5789 --              Flag to indicate if price differentials exist
5790 --
5791 --     x_return_status - (a) FND_API.G_RET_STS_SUCCESS if validation successful
5792 --                       (b) FND_API.G_RET_STS_ERROR if error during validation
5793 --                       (c) FND_API.G_RET_STS_UNEXP_ERROR if unexpected error
5794 --     x_msg_count     - Standard API parameter: The count of number of messages
5795 --                       added to the message list in this call.
5796 --     x_msg_data      - Standard API parameter: Contains error msg in case
5797 --                       x_return_status is returned as FND_API.G_RET_STS_ERROR
5801 --Testing     : None
5798 --                       or FND_API.G_RET_STS_UNEXP_ERROR.
5799 --Notes       : None
5800 --
5802 --
5803 --End of Comments
5804 -----------------------------------------------------------------------------------------
5805 PROCEDURE get_services_asl_list
5806              (p_job_id                     IN         NUMBER,
5807               p_category_id                IN         NUMBER,
5808               p_line_type_id               IN         NUMBER,
5809               p_start_date                 IN         DATE,
5810               p_deliver_to_loc_id          IN         NUMBER,
5811               p_destination_org_id         IN         NUMBER,
5812               p_api_version                IN         NUMBER,
5813               -- Bug# 3404477: Follow the API standards
5814               p_init_msg_list              IN         VARCHAR2,
5815               x_vendor_id                  OUT NOCOPY po_tbl_number,
5816               x_vendor_site_id             OUT NOCOPY po_tbl_number,
5817               x_vendor_contact_id          OUT NOCOPY po_tbl_number,
5818               x_src_doc_header_id          OUT NOCOPY po_tbl_number,
5819               x_src_doc_line_id            OUT NOCOPY po_tbl_number,
5820               x_src_doc_line_num           OUT NOCOPY po_tbl_number,
5821               x_src_doc_type_code          OUT NOCOPY po_tbl_varchar30,
5822               x_base_price                 OUT NOCOPY po_tbl_number,
5823               x_currency_price             OUT NOCOPY po_tbl_number,
5824               x_currency_code              OUT NOCOPY po_tbl_varchar15,
5825               x_unit_of_measure            OUT NOCOPY po_tbl_varchar25,
5826               x_price_override_flag        OUT NOCOPY po_tbl_varchar1,
5827               x_not_to_exceed_price        OUT NOCOPY po_tbl_number,
5828               x_price_break_id             OUT NOCOPY po_tbl_number,
5829               x_price_differential_flag    OUT NOCOPY po_tbl_varchar1,
5830               x_rate_type                  OUT NOCOPY po_tbl_varchar30,
5831               x_rate_date                  OUT NOCOPY po_tbl_date,
5832               x_rate                       OUT NOCOPY po_tbl_number,
5833               x_return_status              OUT NOCOPY VARCHAR2,
5834               -- Bug# 3404477: Return msg count and data
5835               x_msg_count                  OUT NOCOPY NUMBER,
5836               x_msg_data                   OUT NOCOPY VARCHAR2
5837 ) IS
5838 
5839 l_org_id NUMBER;
5840 l_use_contract VARCHAR2(1) := 'N';	--<Contract AutoSourcing FPJ>
5841 
5842 
5843 -- SQL What: Gets the vendor ID and the vendor site ID using category
5844 --           ID and job ID as primary matching criteria.
5845 -- SQL Why : To obtain all ASLs together with vendor information.
5846 CURSOR l_get_asl_vendors_csr (p_dest_organization_id IN number) is
5847     SELECT pasl.vendor_id,
5848            pasl.vendor_site_id,
5849            pasl.asl_id
5850     FROM   po_approved_supplier_list pasl,
5851            po_asl_status_rules pasr,
5852            po_vendors pov
5853     WHERE  pasl.category_id = p_category_id
5854     AND    pasl.item_id IS NULL -- as part of Bug# 3379053: For commodity based ASL's,
5855                                 -- the item MUST be NULL
5856            -- Bug# 3379053: Use destination inv org instead of the default inv org of the ROU.
5857     AND    (pasl.using_organization_id = p_dest_organization_id
5858             OR pasl.using_organization_id = -1)
5859     AND    pasr.status_id = pasl.asl_status_id
5860     AND    pasr.business_rule like '2_SOURCING'
5861     AND    pasr.allow_action_flag like 'Y'
5862     AND    nvl(pasl.disable_flag,'N') = 'N'
5863     -- Supplier validations (Bug# 3361784)
5864     AND    pov.vendor_id = pasl.vendor_id              -- Join
5865     AND    trunc(sysdate) >= trunc(nvl(pov.start_date_active, sysdate))
5866     AND    trunc(sysdate) <  trunc(nvl(pov.end_date_active, sysdate+1)) -- Bug# 3432045: Exclude end_date_active
5867     AND    pov.enabled_flag = 'Y'
5868     AND    nvl(pov.hold_flag, 'N') = 'N'
5869            -- Bug# 3379053: Supplier site validations moved later in the flow
5870  ORDER BY pasl.vendor_id ASC,              -- Bug# 3379053: To filter out duplicates, the supplier
5871           pasl.vendor_site_id ASC,         -- and supplier-sites must be grouped together.
5872           pasl.using_organization_id DESC; -- And Local ASL's must come above Global ASL's.
5873 
5874 -- SQL What: Gets the document header ID, line ID, document type,
5875 --           vendor ID, vendor site ID and vendor contact ID using
5876 --           category ID and job ID as primary matching criteria.
5877 -- SQL Why : To obtain all ASLs and their corresponding documents,
5878 --           together with vendor information.
5879 
5880 -- Bug# 3372867: This cursor is not being used anymore, but is not
5881 -- being removed from the code for possible future references
5882 /*
5883 CURSOR l_get_docs_on_asl_csr (l_org_id         IN number,
5884                               l_vendor_site_id IN number,
5885                               l_asl_id         IN number
5886                               ) is
5887     SELECT poh.vendor_contact_id,
5888            pad.document_header_id,
5889            pad.document_line_id,
5890            pol.line_num,
5891            pad.document_type_code,
5892            nvl(pol.allow_price_override_flag,'N'),
5893            pol.not_to_exceed_price,
5894            pol.unit_meas_lookup_code
5895     FROM   po_asl_documents pad,
5896            po_headers_all poh,
5897            po_lines_all pol
5898     WHERE  pad.asl_id = l_asl_id
5899     AND    pad.document_header_id = poh.po_header_id
5900     -- <FPJ Advanced Price START>
5904              pol.category_id = p_category_id AND
5901     AND    pol.po_line_id (+) = pad.document_line_id
5902     AND    (poh.type_lookup_code = 'CONTRACT' OR
5903             (pol.job_id = p_job_id AND
5905              pol.line_type_id = p_line_type_id))
5906     -- <FPJ Advanced Price END>
5907     AND   ( (poh.type_lookup_code = 'CONTRACT'
5908            AND nvl(poh.global_agreement_flag,'N') = 'N')  -- Bug 3262136
5909            OR exists (select 'site in POU'
5910                        from po_ga_org_assignments poga,
5911                             po_vendor_sites_all povs
5912                        where  poh.po_header_id = poga.po_header_id
5913                        and povs.vendor_site_id = l_vendor_site_id
5914                        and povs.org_id = poga.purchasing_org_id
5915                        and poga.vendor_site_id = l_vendor_site_id
5916                        and poga.organization_id = l_org_id
5917                        and poga.enabled_flag = 'Y')  )
5918     AND    ((poh.type_lookup_code = 'BLANKET'
5919                AND poh.approved_flag    = 'Y'
5920                AND nvl(poh.closed_code, 'OPEN') NOT IN
5921                       ('FINALLY CLOSED','CLOSED')
5922                AND nvl(pol.closed_code, 'OPEN') NOT IN
5923                       ('FINALLY CLOSED','CLOSED')
5924                AND nvl(poh.cancel_flag,'N') = 'N'
5925                AND nvl(poh.frozen_flag,'N') = 'N'
5926                AND trunc(nvl(pol.expiration_date, sysdate))
5927                    >= trunc(sysdate)
5928                AND nvl(pol.cancel_flag,'N') = 'N')
5929            -- <FPJ Advanced Price START>
5930            OR (    poh.type_lookup_code = 'CONTRACT'
5931                AND poh.approved_flag = 'Y'
5932                AND NVL(poh.cancel_flag,'N') = 'N'
5933                AND NVL(poh.frozen_flag,'N') = 'N'
5934                AND NVL(poh.closed_code, 'OPEN') = 'OPEN'
5935               )
5936            )
5937            -- <FPJ Advanced Price END>
5938     AND    sysdate >= nvl(poh.start_date, sysdate)
5939     AND    sysdate <= nvl(poh.end_date, sysdate)
5940     AND    ( (poh.type_lookup_code = 'CONTRACT'
5941               AND nvl(poh.global_agreement_flag,'N') = 'N')  OR   -- Bug 3262136
5942             (nvl(poh.global_agreement_flag,'N') = 'Y'
5943              AND EXISTS (SELECT 'enabled orgs'
5944                    FROM   po_ga_org_assignments poga
5945                    WHERE  poh.po_header_id = poga.po_header_id
5946                    AND    poga.organization_id = l_org_id
5947                    AND    poga.enabled_flag = 'Y'
5948                   ) )
5949            )
5950  ORDER BY pad.sequence_num;
5951 */
5952 
5953 -- SQL What: Gets the document header ID, line ID, document type,
5954 --           vendor ID, vendor site ID and vendor contact ID using
5955 --           category ID and job ID as primary matching criteria.
5956 --           The sql also returns contracts available in the system
5957 -- SQL Why : To obtain all ASLs and their corresponding documents,
5958 --           together with vendor information.
5959 -- Bug 5074119
5960 -- Added an extra condition on type_lookup_code to improve the performance
5961 CURSOR l_get_latest_docs_csr(l_org_id          IN number,
5962                               l_vendor_id      IN number,
5963                               l_vendor_site_id IN number) is
5964     SELECT poh.vendor_contact_id,
5965            poh.po_header_id,
5966            pol.po_line_id,
5967            pol.line_num,
5968            poh.type_lookup_code,
5969            nvl(pol.allow_price_override_flag,'N'),
5970            pol.not_to_exceed_price,
5971            pol.unit_meas_lookup_code
5972     FROM   po_headers_all poh,
5973            po_lines_all pol
5974     WHERE  poh.vendor_id = l_vendor_id
5975        AND poh.type_lookup_code IN ('BLANKET','CONTRACT')
5976     AND    (  ( poh.type_lookup_code = 'CONTRACT'
5977                 AND nvl(poh.global_agreement_flag,'N') = 'N'     -- Bug 3262136
5978                 -- As part of Bug# 3379053: Local Contract must belong to ROU
5979                 AND poh.org_id = l_org_id
5980                 -- As part of Bug# 3379053: Vendor Site on Local Contract must belong to ROU
5981                 AND poh.vendor_site_id = l_vendor_site_id
5982                 AND EXISTS  -- Bug# 3379053
5983                     (SELECT 'Site must be in ROU for local contracts'
5984                      FROM po_vendor_sites_all povs
5985                      WHERE povs.vendor_site_id = l_vendor_site_id
5986                        AND povs.org_id = l_org_id)
5987                )
5988             OR
5989             EXISTS (SELECT 'site in POU'
5990                        FROM po_ga_org_assignments poga,
5991                             po_vendor_sites_all povs
5992                        WHERE  poh.po_header_id = poga.po_header_id
5993                        AND povs.vendor_site_id = l_vendor_site_id
5994                        AND povs.org_id = poga.purchasing_org_id
5995                        AND poga.vendor_site_id = l_vendor_site_id
5996                        AND poga.organization_id = l_org_id
5997                        AND poga.enabled_flag = 'Y')  )
5998     -- <FPJ Advanced Price START>
5999     AND    pol.po_header_id (+) = poh.po_header_id
6000     AND    (poh.type_lookup_code = 'CONTRACT' OR
6001             (pol.job_id = p_job_id AND
6002              pol.category_id = p_category_id AND
6003              pol.line_type_id = p_line_type_id))
6007                AND nvl(poh.closed_code, 'OPEN') NOT IN
6004     -- <FPJ Advanced Price END>
6005     AND    ((poh.type_lookup_code = 'BLANKET'
6006                AND poh.approved_flag    = 'Y'
6008                       ('FINALLY CLOSED','CLOSED')
6009                AND nvl(pol.closed_code, 'OPEN') NOT IN
6010                       ('FINALLY CLOSED','CLOSED')
6011                AND nvl(poh.cancel_flag,'N') = 'N'
6012                AND nvl(poh.frozen_flag,'N') = 'N'
6013                AND trunc(nvl(pol.expiration_date, sysdate))
6014                    >= trunc(sysdate)
6015                AND nvl(pol.cancel_flag,'N') = 'N')
6016            -- <FPJ Advanced Price START>
6017            OR (    poh.type_lookup_code = 'CONTRACT'
6018 	        	 AND (( NVL(FND_PROFILE.VALUE('ALLOW_REFERENCING_CPA_UNDER_AMENDMENT'),'N') =  'Y' --<R12 GCPA ER>
6019 				 		and poh.approved_date is not null)
6020 				 		OR
6021 				 		nvl(poh.approved_flag,'N') = 'Y'
6022 				 		)
6023                AND NVL(poh.cancel_flag,'N') = 'N'
6024                AND NVL(poh.frozen_flag,'N') = 'N'
6025                AND NVL(poh.closed_code, 'OPEN') = 'OPEN'
6026                AND l_use_contract = 'Y'		--<Contract AutoSourcing FPJ>
6027               )
6028            )
6029            -- <FPJ Advanced Price END>
6030     AND    sysdate >= nvl(poh.start_date, sysdate)
6031     AND    sysdate <= nvl(poh.end_date, sysdate)
6032     AND    ( (poh.type_lookup_code = 'CONTRACT'
6033               AND nvl(poh.global_agreement_flag,'N') = 'N')  OR     -- Bug 3262136
6034            (nvl(poh.global_agreement_flag,'N') = 'Y'
6035            AND EXISTS (SELECT 'enabled orgs'
6036                    FROM   po_ga_org_assignments poga
6037                    WHERE  poh.po_header_id = poga.po_header_id
6038                    AND    poga.organization_id = l_org_id
6039                    AND    poga.enabled_flag = 'Y'
6040                   ) )
6041            )
6042   ORDER BY  -- <FPJ Advanced Price START>
6043          decode(poh.type_lookup_code, 'BLANKET', 1, 'QUOTATION', 2, 'CONTRACT', 3) ASC,
6044          NVL (poh.global_agreement_flag, 'N') ASC,
6045          poh.creation_date DESC;
6046          -- <FPJ Advanced Price END>
6047 
6048 l_discount		po_line_locations_all.price_discount%TYPE;
6049 l_rate_type		po_headers_all.rate_type%TYPE;
6050 l_rate_date		po_headers_all.rate_date%TYPE;
6051 l_rate			po_headers_all.rate%TYPE;
6052 l_base_unit_price	po_lines_all.base_unit_price%TYPE;	-- <FPJ Advanced Price>
6053 l_base_price		po_lines_all.unit_price%TYPE;
6054 l_currency_price	po_lines_all.unit_price%TYPE;
6055 l_currency_amount	po_lines_all.unit_price%TYPE;
6056 l_base_amount    	po_lines_all.unit_price%TYPE;
6057 l_currency_code		po_headers_all.currency_code%TYPE;
6058 l_price_break_id	po_line_locations_all.line_location_id%TYPE;
6059 l_price_diff_src_id	po_price_differentials.entity_id%TYPE;
6060 l_using_organization_id	po_approved_supplier_list.using_organization_id%TYPE;
6061 l_entity_type		po_price_differentials.entity_type%TYPE;
6062 l_vendor_contact_id     po_headers_all.vendor_contact_id%TYPE;
6063 l_src_doc_header_id     po_headers_all.po_header_id%TYPE;
6064 l_src_doc_line_id       po_lines_all.po_line_id%TYPE;
6065 l_src_doc_line_num      po_lines_all.line_num%TYPE;
6066 l_src_doc_type_code     po_headers_all.type_lookup_code%TYPE;
6067 l_price_override_flag   po_lines_all.allow_price_override_flag%TYPE;
6068 l_not_to_exceed_price   po_lines_all.not_to_exceed_price%TYPE;
6069 l_unit_of_measure       po_lines_all.unit_meas_lookup_code%TYPE;
6070 l_order_type_lookup_code po_line_types_b.order_type_lookup_code%TYPE;
6071 
6072 l_api_version		NUMBER       := 1.0;
6073 l_api_name		VARCHAR2(60) := 'get_services_asl_list';
6074 l_log_head		CONSTANT varchar2(100) := g_log_head || l_api_name;
6075 l_progress		VARCHAR2(3) := '000';
6076 
6077 x_asl_id                po_tbl_number;
6078 l_sysdate               DATE  := trunc(sysdate); --   Bug 3282423
6079 
6080   -- Bug# 3379053
6081   l_supplier_site_status VARCHAR2(20);
6082   l_vendor_id_list      po_tbl_number := po_tbl_number();
6083   l_vendor_site_id_list po_tbl_number := po_tbl_number();
6084   l_asl_id_list         po_tbl_number := po_tbl_number();
6085   l_count                  NUMBER;
6086   l_prev_vendor_id         NUMBER;
6087   l_prev_vendor_site_id    NUMBER;
6088   l_current_vendor_id      NUMBER;
6089   l_current_vendor_site_id NUMBER;
6090   l_found_dup_null_site    VARCHAR2(1);
6091 BEGIN
6092 
6093   IF g_debug_stmt THEN
6094     PO_DEBUG.debug_begin(l_log_head);
6095     PO_DEBUG.debug_var(l_log_head,l_progress,'p_job_id',p_job_id);
6096     PO_DEBUG.debug_var(l_log_head,l_progress,'p_category_id',p_category_id);
6097     PO_DEBUG.debug_var(l_log_head,l_progress,'p_line_type_id',p_line_type_id);
6098     PO_DEBUG.debug_var(l_log_head,l_progress,'p_start_date',p_start_date);
6099     PO_DEBUG.debug_var(l_log_head,l_progress,'p_deliver_to_loc_id',p_deliver_to_loc_id);
6100     PO_DEBUG.debug_var(l_log_head,l_progress,'p_destination_org_id',p_destination_org_id);
6101     PO_DEBUG.debug_var(l_log_head,l_progress,'p_api_version',p_api_version);
6102   END IF;
6103 
6104     -- Initialize the out parameter tables
6105     x_vendor_id               := po_tbl_number(); -- Bug# 3379053: Initialize x_vendor_id and
6106     x_vendor_site_id          := po_tbl_number(); -- x_vendor_site_id collections
6107     x_base_price              := po_tbl_number();
6108     x_currency_price          := po_tbl_number();
6109     x_currency_code           := po_tbl_varchar15();
6110     x_price_break_id          := po_tbl_number();
6114     x_rate                    := po_tbl_number();
6111     x_price_differential_flag := po_tbl_varchar1();
6112     x_rate_type               := po_tbl_varchar30();
6113     x_rate_date               := po_tbl_date();
6115     x_vendor_contact_id       := po_tbl_number();
6116     x_src_doc_header_id       := po_tbl_number();
6117     x_src_doc_line_id         := po_tbl_number();
6118     x_src_doc_line_num        := po_tbl_number();
6119     x_src_doc_type_code       := po_tbl_varchar30();
6120     x_price_override_flag     := po_tbl_varchar1();
6121     x_not_to_exceed_price     := po_tbl_number();
6122     x_unit_of_measure         := po_tbl_varchar25();
6123 
6124     l_progress := '010';
6125 
6126     -- Initialize the return status
6127     x_return_status := FND_API.G_RET_STS_SUCCESS;
6128     -- Bug# 3404477: Return msg count and data
6129     x_msg_count     := 0;
6130     x_msg_data      := NULL;
6131 
6132     -- Bug# 3404477: Follow the API standards
6133     IF FND_API.to_boolean(p_init_msg_list) THEN
6134       -- initialize message list
6135       FND_MSG_PUB.initialize;
6136     END IF;
6137 
6138     -- Check for the API version
6139     IF ( NOT FND_API.compatible_api_call(l_api_version,p_api_version,l_api_name,G_PKG_NAME) ) THEN
6140         l_progress := '020';
6141         -- As part of bug# 3404477: No need to proceed if the API is not
6142         -- compatible. Hence, raise exception.
6143         --x_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
6144         RAISE FND_API.G_EXC_UNEXPECTED_ERROR;
6145     END IF;
6146 
6147     -- Sql What: Gets the org id and default inv org from FSP
6148     -- Sql Why : To determine the current OU and the default FSP org
6149     BEGIN
6150         l_progress := '030';
6151         SELECT org_id,
6152                inventory_organization_id
6153         INTO   l_org_id,
6154                l_using_organization_id
6155         FROM   financials_system_parameters;
6156     EXCEPTION
6157         WHEN OTHERS THEN
6158             null;
6159     END;
6160 
6161     -- Sql What: get the order type lookup code for the line type id that is passed in
6162     -- Sql why : to distinguish between rate based and fixed price lines
6163     BEGIN
6164         l_progress := '035';
6165         SELECT order_type_lookup_code
6166         INTO   l_order_type_lookup_code
6167         FROM   po_line_types_b
6168         WHERE  line_type_id = p_line_type_id;
6169     EXCEPTION
6170         WHEN OTHERS THEN
6171             null;
6172     END;
6173 
6174     --<Contract AutoSourcing FPJ Start>
6175     -- Find out if contract agreements should be sourced to requisition lines
6176     -- Currently, should_return_contract only supports Purchase Requisitions
6177     l_progress := '040';
6178     should_return_contract(p_destination_doc_type => 'REQ',
6179                            p_document_type_code   => 'REQUISITION',
6180                            p_document_subtype     => 'PURCHASE',
6181                            x_return_contract      => l_use_contract,
6182                            x_return_status        => x_return_status);
6183     IF x_return_status <>  FND_API.g_ret_sts_success  THEN
6184       RAISE FND_API.g_exc_unexpected_error;
6185     END IF;
6186     --<Contract AutoSourcing FPJ End>
6187 
6188     -- Retrive all the ASL's for the category that is passed in
6189     OPEN l_get_asl_vendors_csr (--l_using_organization_id,
6190                                 p_destination_org_id);      -- Bug# 3379053
6191 
6192     -- Retrieve data using the cursor into variables;
6193        FETCH l_get_asl_vendors_csr BULK COLLECT INTO
6194                    --x_vendor_id             ,
6195                    --x_vendor_site_id        ,
6196                    --x_asl_id                ;
6197                    -- Bug# 3379053 : Fetch into local collections so that duplicates can be removed
6198                    l_vendor_id_list        ,
6199                    l_vendor_site_id_list   ,
6200                    l_asl_id_list           ;
6201 
6202     CLOSE l_get_asl_vendors_csr;
6203 
6204     -- Bug# 3379053: If no supplier records found in the ASL, then just return.
6205     IF (l_vendor_id_list.FIRST IS NULL) THEN
6206       RETURN;
6207     END IF;
6208 
6209     -- Bug# 3379053: Validate supplier sites. Null out the site, if it is invalid
6210     validate_vendor_sites(l_vendor_site_id_list);
6211 
6212     -- For each ASL vendor get the source document and pricing information
6213     -- Bug# 3379053 : Loop through local collection to identify duplicate (suppl, suppl-sites)
6214     l_count := 0;
6215     FOR i IN l_vendor_id_list.FIRST..l_vendor_id_list.LAST LOOP
6216 
6217       -- Bug# 3379053: For a supplier/supplier-site combination, remove duplicates.
6218       IF (is_dup_vendor_record(l_vendor_id_list(i),
6219                                l_vendor_site_id_list(i),
6220                                x_vendor_id,
6221                                x_vendor_site_id)) THEN
6222         GOTO end_vendor_loop; -- skip record
6223       END IF;
6224 
6225      -- If vendor site is NULL, then Document SOurcing is not required.
6226      IF l_vendor_site_id_list(i) IS NULL THEN
6227        l_count := l_count + 1;
6228        -- Extend the out parameter table to create a new OUT record
6229        x_vendor_id.extend;
6230        x_vendor_site_id.extend;
6231        x_currency_price.extend;
6232        x_currency_code.extend;
6233        x_price_break_id.extend;
6234        x_price_differential_flag.extend;
6238        x_vendor_contact_id.extend;
6235        x_rate_type.extend;
6236        x_rate_date.extend;
6237        x_rate.extend;
6239        x_src_doc_header_id.extend;
6240        x_src_doc_line_id.extend;
6241        x_src_doc_line_num.extend;
6242        x_src_doc_type_code.extend;
6243        x_price_override_flag.extend;
6244        x_not_to_exceed_price.extend;
6245        x_unit_of_measure.extend;
6246        x_base_price.extend;
6247 
6248        x_vendor_id(l_count) := l_vendor_id_list(i);
6249        x_vendor_site_id(l_count) := NULL;
6250 
6251      ELSE -- IF l_current_vendor_site_id IS NOT NULL THEN
6252 
6253      -- Proceed with the document sourcing flow, only if the ASL has a site
6254      --IF x_vendor_site_id(i) is not null THEN
6255      --IF l_current_vendor_site_id IS NOT NULL THEN -- Bug# 3379053: Moved doc sourcing up
6256 
6257        l_current_vendor_id := l_vendor_id_list(i);
6258        l_current_vendor_site_id := l_vendor_site_id_list(i);
6259 
6260        -- Initialize the local variables
6261        l_vendor_contact_id   := null;
6262        l_src_doc_header_id   := null;
6263        l_src_doc_line_id     := null;
6264        l_src_doc_line_num    := null;
6265        l_src_doc_type_code   := null;
6266        l_price_override_flag := null;
6267        l_not_to_exceed_price := null;
6268        l_unit_of_measure     := null;
6269 
6270     -- Retreive the Automatic document sourcing Profile. Based on the profile we either
6271     -- use the document info from the ASL documents tables or the PO tables directly
6272 
6273       -- Bug# 3372867: Functional design changes to the Services Source API:
6274       -- Services Sourcing API will always source from the latest source doc/line
6275       -- matching the Job/Category.  The Profile Option "PO:Automatic Document
6276       -- Sourcing" will be ignored for temp labor lines and behaves as if it is
6277       -- set to Yes.
6278       -- This code section is not being deleted for possible future references.
6279       /*
6280       IF (nvl(fnd_profile.value('PO_AUTO_SOURCE_DOC'),'N') = 'N') THEN
6281 
6282         l_progress := '040';
6283         IF g_debug_stmt THEN
6284           PO_DEBUG.debug_stmt(l_log_head,l_progress,'Open Cursor l_get_docs_on_asl_csr');
6285         END IF;
6286 
6287         OPEN l_get_docs_on_asl_csr (l_org_id,
6288                                     x_vendor_site_id(i),
6289                                     x_asl_id(i));
6290 
6291         -- Retrieve data using the cursor into variables;
6292 
6293 	    FETCH  l_get_docs_on_asl_csr INTO
6294                    l_vendor_contact_id     ,
6295                    l_src_doc_header_id     ,
6296                    l_src_doc_line_id       ,
6297                    l_src_doc_line_num      ,
6298                    l_src_doc_type_code     ,
6299                    l_price_override_flag   ,
6300                    l_not_to_exceed_price   ,
6301                    l_unit_of_measure       ;
6302         CLOSE l_get_docs_on_asl_csr;
6303     ELSE
6304     */
6305 
6306       l_progress := '050';
6307       IF g_debug_stmt THEN
6308         PO_DEBUG.debug_stmt(l_log_head,l_progress,'Open Cursor l_get_latest_docs_csr');
6309       END IF;
6310 
6311         OPEN l_get_latest_docs_csr (l_org_id,
6312                                     --x_vendor_id(i),
6313                                     --x_vendor_site_id(i)
6314                                     l_vendor_id_list(i),       -- Bug# 3379053: Using local collections
6315                                     l_vendor_site_id_list(i));
6316 
6317         l_progress := '060';
6318         -- Retrieve data using the cursor into variables
6319 
6320            FETCH  l_get_latest_docs_csr INTO
6321                    l_vendor_contact_id     ,
6322                    l_src_doc_header_id     ,
6323                    l_src_doc_line_id       ,
6324                    l_src_doc_line_num      ,
6325                    l_src_doc_type_code     ,
6326                    l_price_override_flag   ,
6327                    l_not_to_exceed_price   ,
6328                    l_unit_of_measure       ;
6329         CLOSE l_get_latest_docs_csr;
6330 
6331         l_progress := '070';
6332 
6333     --END IF;   -- end of profile check -- Bug# 3372867
6334 
6335     -- Bug# 3379053: If no source doc is found, then the Supplier Site MUST belong to ROU
6336     --               If it is outside ROU, then null out the supplier site.
6337     IF l_src_doc_header_id IS NULL THEN
6338       l_progress := '080';
6339       IF (is_vendor_site_outside_OU(l_current_vendor_site_id, l_org_id)) THEN
6340         l_current_vendor_site_id := NULL;
6341 
6342         l_progress := '090';
6343         -- Check for duplicate (Supplier, NULL) records in the filtered list.
6344         IF (is_dup_vendor_record(l_current_vendor_id,
6345                                  NULL, -- vendor_site_id
6346                                  x_vendor_id,
6347                                  x_vendor_site_id)) THEN
6348           GOTO end_vendor_loop; -- skip record
6349         END IF;
6350         l_progress := '110';
6351       END IF; -- IF is_vendor_site_outside_OU
6352     END IF; -- IF l_src_doc_header_id IS NULL THEN
6353     -- Bug# 3379053: End
6354 
6355       l_progress := '120';
6356 
6357       -- Count of the valid records that are filtered from the result rowset of
6358       -- the cursor 'l_get_asl_vendors_csr'
6359       l_count := l_count + 1;
6360 
6361        -- Extend the out parameter table
6362        x_vendor_id.extend;
6363        x_vendor_site_id.extend;
6364 
6365        x_vendor_id(l_count) := l_current_vendor_id;
6366        x_vendor_site_id(l_count) := l_current_vendor_site_id;
6367 
6368        -- Extend the out parameter table
6369        --x_base_price.extend(x_vendor_id.COUNT);
6370        x_base_price.extend; -- Bug# 3379053: Extend by 1 in one loop.
6371                             -- Remove the parameter (x_vendor_id.COUNT) from all collections below
6372 
6373        x_currency_price.extend;
6374        x_currency_code.extend;
6375        x_price_break_id.extend;
6376        x_price_differential_flag.extend;
6377        x_rate_type.extend;
6378        x_rate_date.extend;
6379        x_rate.extend;
6380        x_vendor_contact_id.extend;
6381        x_src_doc_header_id.extend;
6382        x_src_doc_line_id.extend;
6383        x_src_doc_line_num.extend;
6384        x_src_doc_type_code.extend;
6385        x_price_override_flag.extend;
6386        x_not_to_exceed_price.extend;
6387        x_unit_of_measure.extend;
6388 
6389 
6390     l_progress := '130';
6391 
6392     IF g_debug_stmt THEN
6393       PO_DEBUG.debug_var(l_log_head,l_progress,'x_vendor_id',x_vendor_id);
6394       PO_DEBUG.debug_var(l_log_head,l_progress,'x_vendor_site_id',x_vendor_site_id);
6395       PO_DEBUG.debug_var(l_log_head,l_progress,'x_vendor_contact_id',x_vendor_contact_id);
6396       PO_DEBUG.debug_var(l_log_head,l_progress,'x_src_doc_header_id',x_src_doc_header_id);
6397       PO_DEBUG.debug_var(l_log_head,l_progress,'x_src_doc_line_id',x_src_doc_line_id);
6398       PO_DEBUG.debug_var(l_log_head,l_progress,'x_src_doc_line_num',x_src_doc_line_num);
6399       PO_DEBUG.debug_var(l_log_head,l_progress,'x_src_doc_type_code',x_src_doc_type_code);
6400       PO_DEBUG.debug_var(l_log_head,l_progress,'x_price_override_flag',x_price_override_flag);
6401       PO_DEBUG.debug_var(l_log_head,l_progress,'x_not_to_exceed_price',x_not_to_exceed_price);
6402     END IF;
6403 
6404        l_progress := '140';
6405 
6406        -- Call the pricing API only for Blankets and not for contracts
6407        IF l_src_doc_type_code = 'BLANKET' and l_src_doc_header_id is not null THEN
6408 
6409          IF l_order_type_lookup_code = 'RATE' THEN
6410 
6411            l_progress := '150';
6412 
6413            IF g_debug_stmt THEN
6414              PO_DEBUG.debug_stmt(l_log_head,l_progress,'Call PO_PRICE_BREAK_GRP.get_price_break');
6415            END IF;
6416 
6417            -- Bug 3282423 -  Passing sysdate for p_need_by_date instead of start date
6418 
6419            PO_PRICE_BREAK_GRP.get_price_break
6420      	   (  p_source_document_header_id	=> l_src_doc_header_id
6421 	   ,  p_source_document_line_num	=> l_src_doc_line_num
6422 	   ,  p_in_quantity	        	=> null
6423 	   ,  p_unit_of_measure		        => null
6424 	   ,  p_deliver_to_location_id	        => p_deliver_to_loc_id
6425 	   ,  p_required_currency		=> null
6426 	   ,  p_required_rate_type	        => null
6427 	   ,  p_need_by_date		        => l_sysdate
6428 	   ,  p_destination_org_id	        => p_destination_org_id
6429 	   ,  x_base_price		        => l_base_price
6430 	   ,  x_currency_price		        => l_currency_price
6431 	   ,  x_discount			=> l_discount
6432 	   ,  x_currency_code		        => l_currency_code
6433 	   ,  x_rate_type                       => l_rate_type
6434 	   ,  x_rate_date                       => l_rate_date
6435 	   ,  x_rate                            => l_rate
6436 	   ,  x_price_break_id                  => l_price_break_id
6437 	   );
6438 
6439            l_progress := '160';
6440 
6441            IF g_debug_stmt THEN
6442              PO_DEBUG.debug_stmt(l_log_head,l_progress,'After Call PO_PRICE_BREAK_GRP.get_price_break');
6443            END IF;
6444 
6445            -- Set the source of the pricing (line or price break)
6446            l_progress := '170';
6447            IF l_price_break_id is NULL THEN
6448               l_price_diff_src_id := l_src_doc_line_id;
6449               l_entity_type       := 'BLANKET LINE';
6450            ELSE
6451               l_price_diff_src_id := l_price_break_id;
6452               l_entity_type       := 'PRICE BREAK';
6453            END IF;
6454 
6455            -- Find out if the line or price break has any price differentials or not
6456            l_progress := '180';
6457            IF PO_PRICE_DIFFERENTIALS_PVT.has_price_differentials(p_entity_type => l_entity_type,
6461            ELSE
6458                                                                  p_entity_id   => l_price_diff_src_id) THEN
6459                 --x_price_differential_flag(i) := 'Y';
6460                 x_price_differential_flag(l_count) := 'Y'; -- Bug# 3379053
6462                 --x_price_differential_flag(i) := 'N';
6463                 x_price_differential_flag(l_count) := 'N'; -- Bug# 3379053
6464            END IF;
6465 
6466              -- Bug# 3379053: Change i to l_count for all of the following variables
6467              x_base_price(l_count)     := l_base_price;
6468 	   x_currency_price(l_count) := l_currency_price;
6469 	   x_currency_code(l_count)  := l_currency_code;
6470 	   x_rate_type(l_count)      := l_rate_type;
6471 	   x_rate_date(l_count)      := l_rate_date;
6472 	   x_rate(l_count)           := l_rate;
6473 	   x_price_break_id(l_count) := l_price_break_id;
6474 
6475          ELSE
6476 
6477            -- For fixed price lines there is no price and price breaks and hence no pricing
6478            -- call is made. Instead we return the amount in the functional and forein currencies
6479 
6480            l_progress := '190';
6481 
6482            get_line_amount(p_source_document_header_id => l_src_doc_header_id
6483 	           ,  p_source_document_line_id	  => l_src_doc_line_id
6484 	           ,  x_base_amount		  => l_base_amount
6485 	           ,  x_currency_amount	    	  => l_currency_amount
6486                    ,  x_currency_code             => l_currency_code
6487                    ,  x_rate_type                 => l_rate_type
6488                    ,  x_rate_date                 => l_rate_date
6489                    ,  x_rate                      => l_rate            );
6490 
6491            -- For fixed price temp labor lines the amount is returned as the base and currency prices
6492              -- Bug# 3379053: Change i to l_count for all of the following variables
6493              x_base_price(l_count)      := l_base_amount;
6494 	   x_currency_price(l_count)  := l_currency_amount;
6495 	   x_currency_code(l_count)   := l_currency_code;
6496 	   x_rate_type(l_count)       := l_rate_type;
6497 	   x_rate_date(l_count)       := l_rate_date;
6498 	   x_rate(l_count)            := l_rate;
6499 
6500          END IF; -- End of pricing for rate based lines
6501 
6502        END IF;    -- End of Pricing for blanket
6503 
6504           -- Bug# 3379053: Change i to l_count for all of the following variables
6505           x_vendor_contact_id(l_count)   := l_vendor_contact_id;
6506           x_src_doc_header_id(l_count)   := l_src_doc_header_id;
6507           x_src_doc_line_id(l_count)     := l_src_doc_line_id;
6508           x_src_doc_line_num(l_count)    := l_src_doc_line_num;
6509           x_src_doc_type_code(l_count)   := l_src_doc_type_code;
6510           x_price_override_flag(l_count) := l_price_override_flag;
6511           x_not_to_exceed_price(l_count) := l_not_to_exceed_price;
6512           x_unit_of_measure(l_count)     := l_unit_of_measure;
6513 
6514       END IF; -- end of null site check
6515 
6516       -- Bug# 3379053: To skip the loop for duplicate (supplier, suppl-site) combinations
6517       <<end_vendor_loop>>
6518       NULL;
6519 
6520     END LOOP;
6521 
6522   l_progress := '200';
6523 
6524   IF g_debug_stmt THEN
6525     PO_DEBUG.debug_end(l_log_head);
6526     PO_DEBUG.debug_var(l_log_head,l_progress,'x_return_status',x_return_status);
6527     PO_DEBUG.debug_var(l_log_head,l_progress,'x_vendor_id',x_vendor_id);
6528     PO_DEBUG.debug_var(l_log_head,l_progress,'x_vendor_site_id',x_vendor_site_id);
6529     PO_DEBUG.debug_var(l_log_head,l_progress,'x_vendor_contact_id',x_vendor_contact_id);
6530     PO_DEBUG.debug_var(l_log_head,l_progress,'x_src_doc_header_id',x_src_doc_header_id);
6531     PO_DEBUG.debug_var(l_log_head,l_progress,'x_src_doc_line_id',x_src_doc_line_id);
6532     PO_DEBUG.debug_var(l_log_head,l_progress,'x_src_doc_line_num',x_src_doc_line_num);
6533     PO_DEBUG.debug_var(l_log_head,l_progress,'x_src_doc_type_code',x_src_doc_type_code);
6534     PO_DEBUG.debug_var(l_log_head,l_progress,'x_base_price',x_base_price);
6535     PO_DEBUG.debug_var(l_log_head,l_progress,'x_currency_price',x_currency_price);
6536     PO_DEBUG.debug_var(l_log_head,l_progress,'x_price_override_flag',x_price_override_flag);
6537     PO_DEBUG.debug_var(l_log_head,l_progress,'x_not_to_exceed_price',x_not_to_exceed_price);
6538     PO_DEBUG.debug_var(l_log_head,l_progress,'x_price_break_id',x_price_break_id);
6539     PO_DEBUG.debug_var(l_log_head,l_progress,'x_price_differential_flag',x_price_differential_flag);
6540     PO_DEBUG.debug_var(l_log_head,l_progress,'x_rate_type',x_rate_type);
6541     PO_DEBUG.debug_var(l_log_head,l_progress,'x_rate_date',x_rate_date);
6542     PO_DEBUG.debug_var(l_log_head,l_progress,'x_rate',x_rate);
6543   END IF;
6544 EXCEPTION
6545     -- Bug# 3404477: Return msg count and data
6546     WHEN FND_API.G_EXC_ERROR THEN
6547        x_return_status := FND_API.G_RET_STS_ERROR;
6548        FND_MSG_PUB.count_and_get(p_count => x_msg_count
6549                                , p_data  => x_msg_data);
6550     WHEN OTHERS THEN
6551        x_return_status := FND_API.G_RET_STS_UNEXP_ERROR;
6552 
6553        IF FND_MSG_PUB.check_msg_level(FND_MSG_PUB.g_msg_lvl_unexp_error) THEN
6554          FND_MSG_PUB.add_exc_msg(p_pkg_name       => g_pkg_name
6555                                , p_procedure_name => l_api_name
6556                                , p_error_text     => 'Progress: '||l_progress||
6557                                            ' Error: '||SUBSTRB(SQLERRM,1,215));
6558        END IF;
6562        --<Contract AutoSourcing FPJ>
6559        FND_MSG_PUB.count_and_get(p_count => x_msg_count
6560                                , p_data  => x_msg_data);
6561 
6563        IF g_debug_unexp THEN
6564           PO_DEBUG.debug_exc(l_log_head,l_progress);
6565        END IF;
6566 END get_services_asl_list;
6567 
6568 
6569 -----------------------------------------------------------------<SERVICES FPJ>
6570 -------------------------------------------------------------------------------
6571 --Start of Comments
6572 --Name: get_source_info
6573 --Pre-reqs:
6574 --  None.
6575 --Modifies:
6576 --  None.
6577 --Locks:
6578 --  None.
6579 --Function:
6580 --  Retrieves the source document information for a particular Line.
6581 --Parameters:
6582 --IN
6583 --p_po_line_id
6584 --  Unique ID of line on which to check source document reference.
6585 --OUT
6586 --x_from_header_id
6587 --  Source Document Header ID on the line.
6588 --x_from_line_id
6589 --  Source Document Line ID on the line.
6590 --x_from_line_location_id
6591 --  Source Document Price Break ID on the line.
6592 --Testing:
6593 --  None.
6594 --End of Comments
6595 -------------------------------------------------------------------------------
6596 -------------------------------------------------------------------------------
6597 PROCEDURE get_source_info
6598 (
6599     p_po_line_id               IN          NUMBER
6600 ,   x_from_header_id           OUT NOCOPY  NUMBER
6601 ,   x_from_line_id             OUT NOCOPY  NUMBER
6602 ,   x_from_line_location_id    OUT NOCOPY  NUMBER
6603 )
6604 IS
6605 BEGIN
6606 
6607     SELECT from_header_id
6608     ,      from_line_id
6609     ,      from_line_location_id
6610     INTO   x_from_header_id
6611     ,      x_from_line_id
6612     ,      x_from_line_location_id
6613     FROM   po_lines_all
6614     WHERE  po_line_id = p_po_line_id;
6615 
6616 EXCEPTION
6617 
6618     WHEN OTHERS THEN
6619         PO_MESSAGE_S.sql_error('PO_AUTOSOURCE_SV.get_source_info','000',sqlcode);
6620         RAISE;
6621 
6622 END get_source_info;
6623 
6624 
6625 -----------------------------------------------------------------<SERVICES FPJ>
6626 -------------------------------------------------------------------------------
6627 --Start of Comments
6628 --Name: get_source_info
6629 --Pre-reqs:
6630 --  None.
6631 --Modifies:
6632 --  None.
6633 --Locks:
6634 --  None.
6635 --Function:
6636 --  Determines if the source document values passed in are the same as what
6637 --  is in the database.
6638 --Parameters:
6639 --IN
6640 --p_po_line_id
6641 --  Unique ID of line on which to check source document reference.
6642 --p_from_header_id
6643 --  Source Document Header ID to check.
6644 --p_from_line_id
6645 --  Source Document Line ID to check.
6646 --p_from_line_location_id
6647 --  Source Document Price Break ID to check.
6648 --Returns:
6649 --  TRUE if all three parameters match their respective database values.
6650 --  FALSE otherwise.
6651 --Testing:
6652 --  None.
6653 --End of Comments
6654 -------------------------------------------------------------------------------
6655 -------------------------------------------------------------------------------
6656 FUNCTION has_source_changed
6657 (
6658     p_po_line_id               IN          NUMBER
6659 ,   p_from_header_id           IN          NUMBER
6660 ,   p_from_line_id             IN          NUMBER
6661 ,   p_from_line_location_id    IN          NUMBER
6662 )
6663 RETURN BOOLEAN
6664 IS
6665     l_from_header_id_db        PO_LINES_ALL.from_header_id%TYPE;
6666     l_from_line_id_db          PO_LINES_ALL.from_line_id%TYPE;
6667     l_from_line_location_id_db PO_LINES_ALL.from_line_location_id%TYPE;
6668 
6669 BEGIN
6670 
6671     PO_AUTOSOURCE_SV.get_source_info
6672     (   p_po_line_id            => p_po_line_id
6673     ,   x_from_header_id        => l_from_header_id_db
6674     ,   x_from_line_id          => l_from_line_id_db
6675     ,   x_from_line_location_id => l_from_line_location_id_db
6676     );
6677 
6678     IF  (
6679             (   ( l_from_header_id_db = p_from_header_id )
6680             OR  (   ( l_from_header_id_db IS NULL )
6681                 AND ( p_from_header_id IS NULL ) ) )
6682         AND
6683             (   ( l_from_line_id_db = p_from_line_id )
6684             OR  (   ( l_from_line_id_db IS NULL )
6685                 AND ( p_from_line_id IS NULL ) ) )
6686         AND
6687             (   ( l_from_line_location_id_db = p_from_line_location_id )
6688             OR  (   ( l_from_line_location_id_db IS NULL )
6689                 AND ( p_from_line_location_id IS NULL ) ) )
6690         )
6691     THEN
6692         return (FALSE);
6693     ELSE
6694         return (TRUE);
6695     END IF;
6696 
6697 EXCEPTION
6698 
6699     WHEN OTHERS THEN
6700         PO_MESSAGE_S.sql_error('PO_AUTOSOURCE_SV.has_source_changed','000',sqlcode);
6701         RAISE;
6702 
6703 END has_source_changed;
6704 
6705 -----------------------------------------------------------------<SERVICES FPJ>
6706 -------------------------------------------------------------------------------
6707 --Start of Comments
6708 --Name: get_line_amt
6709 --Pre-reqs:
6713 --Locks:
6710 --  None.
6711 --Modifies:
6712 --  None.
6714 --  None.
6715 --Function:
6716 --  Retrieves the line amount and related currency infor for a fixed price
6717 --  temp labor line
6718 --Parameters:
6719 --IN
6720 --p_source_doc_line_id
6721 --  Unique ID of line on which to get the amount
6722 --OUT
6723 --   Base currency Amount
6724 --   Foreign currency Amount
6725 --   Document Currency
6726 --   Currency Rate type
6727 --   Currency Rate date
6728 --   Currency Rate
6729 --Testing:
6730 --  None.
6731 --End of Comments
6732 -------------------------------------------------------------------------------
6733 -------------------------------------------------------------------------------
6734 PROCEDURE get_line_amount(p_source_document_header_id IN NUMBER
6735 	           ,  p_source_document_line_id	             IN NUMBER
6736 	           ,  x_base_amount		             OUT NOCOPY NUMBER
6737 	           ,  x_currency_amount	    	             OUT NOCOPY NUMBER
6738                    ,  x_currency_code                        OUT NOCOPY VARCHAR2
6739                    ,  x_rate_type                            OUT NOCOPY VARCHAR2
6740                    ,  x_rate_date                            OUT NOCOPY DATE
6741                    ,  x_rate                                 OUT NOCOPY NUMBER )
6742 IS
6743 
6744 l_rate_type		  po_headers_all.rate_type%TYPE;
6745 l_rate_date		  po_headers_all.rate_date%TYPE;
6746 l_rate			  po_headers_all.rate%TYPE;
6747 l_base_amount		  po_lines_all.amount%TYPE;
6748 l_currency_amount	  po_lines_all.amount%TYPE;
6749 l_currency_code		  po_headers_all.currency_code%TYPE;
6750 l_base_curr_ext_precision number;
6751 l_sob_id                  number;
6752 
6753 BEGIN
6754      -- SQL What : Gets the currency code and amount from the given source document
6755      -- SQL Why  : To Return the amount and converted base amount to IP
6756 
6757         SELECT poh.currency_code ,
6758                pol.amount
6759         INTO   l_currency_code ,
6760                l_currency_amount
6761         FROM   po_headers_all poh,
6762                po_lines_all pol
6763         WHERE  poh.po_header_id = pol.po_header_id
6764         AND    poh.po_header_id = p_source_document_header_id
6765         AND    pol.po_line_id = p_source_document_line_id;
6766 
6767      -- SQL What: Get the set of books id from system parameters
6768      -- SQL Why : To calculate the currency conversion rate
6769 
6770         SELECT set_of_books_id
6771         INTO   l_sob_id
6772         FROM   financials_system_parameters;
6773 
6774      -- SQL What: Get the default currency exchange rate type from system parameters
6775      -- SQL Why : To calculate the currency conversion rate
6776 
6777         SELECT default_rate_type
6778         INTO   l_rate_type
6779         FROM   po_system_parameters;
6780 
6781      -- SQL What: Get the currency precision from system parameters
6782      -- SQL Why : To round the calculated amount
6783 
6784         SELECT nvl(FND.extended_precision,5)
6785         INTO   l_base_curr_ext_precision
6786         FROM   FND_CURRENCIES FND,
6787                FINANCIALS_SYSTEM_PARAMETERS FSP,
6788                GL_SETS_OF_BOOKS GSB
6789         WHERE  FSP.set_of_books_id = GSB.set_of_books_id AND
6790                FND.currency_code = GSB.currency_code;
6791 
6792         x_rate := PO_CORE_S.get_conversion_rate( l_sob_id        ,
6793                                                  l_currency_code ,
6794                                                  sysdate         ,
6795                                                  l_rate_type     );
6796 
6797         x_rate_date := sysdate;
6798         x_rate_type := l_rate_type;
6799         x_currency_code := l_currency_code;
6800         x_currency_amount := l_currency_amount;
6801         x_base_amount := round(l_currency_amount * nvl(x_rate,1), l_base_curr_ext_precision);
6802 
6803 EXCEPTION
6804 
6805     WHEN OTHERS THEN
6806         PO_MESSAGE_S.sql_error('PO_AUTOSOURCE_SV.get_line_amount','000',sqlcode);
6807         RAISE;
6808 END get_line_amount;
6809 
6810 --<Contract AutoSourcing FPJ Start >
6811 -------------------------------------------------------------------------------
6812 -- Start of Comments
6813 -- Name: SHOULD_RETURN_CONTRACT
6814 -- Pre-reqs:
6815 -- None
6816 -- Modifies:
6817 -- None
6818 -- Locks:
6819 -- None
6820 -- Function:
6821 -- Determines whether or not contract agreements can be sourced to
6822 -- Parameters:
6823 -- IN:
6824 -- p_destination_doc_type:
6825 --   Valid values are 'PO','REQ','STANDARD PO','REQ_NONCATALOG'and NULL
6826 -- p_document_type_code:
6827 --   Valid value is 'REQUISITION'
6828 -- p_document_subtype:
6829 --   Valid value is 'PURCHASE'
6830 -- OUT:
6831 -- x_return_contract:
6832 --   If 'Y', contracts can be returned as source documents; otherwise,
6833 --   do not source to contracts
6834 -- x_return_status:
6835 --   FND_API.g_ret_sts_success: if the procedure completed successfully
6836 --   FND_API.g_ret_sts_unexp_error: if unexpected error occurrred
6837 -- Notes:
6838 -- None
6839 -- Testing:
6840 -- None
6841 -- End of Comments
6842 -------------------------------------------------------------------------------
6843 PROCEDURE should_return_contract (
6844   p_destination_doc_type		IN	VARCHAR2,
6848   x_return_status     		OUT 	NOCOPY 	VARCHAR2)
6845   p_document_type_code	       		IN	VARCHAR2,
6846   p_document_subtype	       		IN	VARCHAR2,
6847   x_return_contract		OUT	NOCOPY	VARCHAR2,
6849 IS
6850   l_use_contract_for_sourcing
6851  	PO_DOCUMENT_TYPES_ALL_B.use_contract_for_sourcing_flag%TYPE;
6852   l_include_noncatalog_flag
6853  	PO_DOCUMENT_TYPES_ALL_B.include_noncatalog_flag%TYPE;
6854   l_progress		VARCHAR2(3) := '000';
6855   l_log_head   CONSTANT VARCHAR2(100) := g_log_head||'should_return_contract';
6856 
6857 BEGIN
6858   l_progress := '010';
6859 
6860   IF (p_document_type_code IS NULL) OR (p_document_subtype IS NULL) THEN
6861      x_return_contract := 'N';
6862      return;
6863   END IF;
6864 
6865   x_return_status := FND_API.g_ret_sts_success;
6866   x_return_contract := 'N';
6867 
6868   IF g_debug_stmt THEN
6869      PO_DEBUG.debug_stmt (p_log_head => l_log_head,
6870                           p_token    => l_progress,
6871                           p_message  => 'Destination Doc Type: '||p_destination_doc_type ||
6872                                         ' Document Type Code: '||p_document_type_code ||
6873                                         ' Document Subtype: '||p_document_subtype
6874                           );
6875   END IF;
6876 
6877   SELECT	nvl (use_contract_for_sourcing_flag, 'N'),
6878  	     	nvl (include_noncatalog_flag, 'N')
6879   INTO	      	l_use_contract_for_sourcing,
6880  		l_include_noncatalog_flag
6881   FROM     	PO_DOCUMENT_TYPES_B
6882   WHERE  	document_type_code = p_document_type_code
6883   AND 	      	document_subtype = p_document_subtype;
6884 
6885   l_progress := '020';
6886   IF g_debug_stmt THEN
6887      PO_DEBUG.debug_stmt (p_log_head => l_log_head,
6891   END IF;
6888                           p_token    => l_progress,
6889                           p_message  => 'Use contract for sourcing? '||l_use_contract_for_sourcing||
6890                                         ' Include noncatalog request? '||l_include_noncatalog_flag);
6892 
6893   IF l_use_contract_for_sourcing = 'Y' AND
6894      (l_include_noncatalog_flag = 'Y' OR
6895      (l_include_noncatalog_flag = 'N' AND p_destination_doc_type <> 'REQ_NONCATALOG'))
6896   THEN
6897      x_return_contract := 'Y';
6898   END IF;
6899 
6900   l_progress := '030';
6901   IF g_debug_stmt THEN
6902      PO_DEBUG.debug_stmt (p_log_head => l_log_head,
6903                           p_token    => l_progress,
6904                           p_message  => 'Should return contract? '||x_return_contract);
6905   END IF;
6906 
6907 EXCEPTION
6908   WHEN OTHERS THEN
6909     x_return_status := FND_API.g_ret_sts_unexp_error;
6910     FND_MSG_PUB.add_exc_msg (p_pkg_name	=> g_pkg_name,
6911   			     p_procedure_name => 'should_return_contract',
6912     			     p_error_text => 'Progress: '||l_progress||' Error: '||SUBSTRB(SQLERRM,1,215));
6913     IF g_debug_unexp THEN
6914        PO_DEBUG.debug_exc (p_log_head => l_log_head ||'should_return_contract',
6915 			   p_progress => l_progress);
6916     END IF;
6917 
6918 END should_return_contract;
6919 --<Contract AutoSourcing FPJ End >
6920 
6921 END PO_AUTOSOURCE_SV;