DBA Data[Home] [Help]

PACKAGE BODY: APPS.PO_AUTOSOURCE_SV

Source


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