DBA Data[Home] [Help]

PACKAGE BODY: APPS.JG_GLOBE_FLEX_VAL_SHARED

Source


1 PACKAGE BODY JG_GLOBE_FLEX_VAL_SHARED AS
2 /* $Header: jggdfvsb.pls 120.1 2005/07/01 19:55:20 sachandr ship $ */
3 
4   --
5   -- PUBLIC PROCEDURE
6   --
7   ---------------------------------------------------------------------------
8   --  INSERT_REJECTIONS():
9   --     AP Invoice Gateway Import Process uses this procedure to reject
10   --     invalid data and insert them to AP_INTERFACE_REJECTIONS table.
14   --     AP_INVOICE_LINES_INTERFACE. If the source of PARENT_TABLE is
11   --     The table stores both header and line level invoice information.
12   --     The column PARENT_TABLE indicates the table from which the invoice
13   --     fetched is being rejected - AP_INVOICES_INTERFACE or
15   --     AP_INVOICES_INTERFACE then the column PARENT_ID would have the
16   --     invoice_id else if the source of PARENT_TABLE is
17   --     AP_INVOICE_LINES_INTERFACE, then PARENT_ID would have
18   --     invoice_line_id.
19   ---------------------------------------------------------------------------
20   PROCEDURE Insert_rejections(
21 	p_parent_table			IN	VARCHAR2,
22 	p_parent_id			IN	NUMBER,
23 	p_reject_code			IN	VARCHAR2,
24 	p_last_updated_by		IN	NUMBER,
25 	p_last_update_login		IN	NUMBER,
26 	p_calling_sequence   		IN    	VARCHAR2) IS
27 
28         l_debug_loc                     VARCHAR2(30) := 'Insert_Rejections';
29         l_curr_calling_sequence  	VARCHAR2(2000);
30         l_debug_info                    VARCHAR2(100);
31   BEGIN
32     -------------------------- DEBUG INFORMATION ------------------------------
33     l_curr_calling_sequence := 'jg_globe_flex_val.'||l_debug_loc||'<-'||p_calling_sequence;
34     l_debug_info := 'Insert rejection information to ap_interface_rejections';
35     ---------------------------------------------------------------------------
36     --
37     -- Insert into AP_INTERFACE_REJECTIONS
38     --
39     INSERT INTO ap_interface_rejections(
40     	         parent_table,
41 	         parent_id,
42 	         reject_lookup_code,
43 	         last_updated_by,
44 	         last_update_date,
45 	         last_update_login,
46 	         created_by,
47 	         creation_date)
48          VALUES (p_parent_table,
49 	         p_parent_id,
50 	         p_reject_code,
51 	         p_last_updated_by,
52 	         sysdate,
53 	         p_last_update_login,
54 	         p_last_updated_by,
55 	         sysdate);
56 
57   EXCEPTION
58   WHEN OTHERS then
59     IF (SQLCODE <> -20001) THEN
60       FND_MESSAGE.SET_NAME('SQLAP', 'AP_DEBUG');
61       FND_MESSAGE.SET_TOKEN('ERROR', 'SQLERRM');
62       FND_MESSAGE.SET_TOKEN('CALLING_SEQUENCE', l_curr_calling_sequence);
63       FND_MESSAGE.SET_TOKEN('PARAMETERS',
64                             'Parent Table = '||p_parent_table
65                         ||', Parent Id = '||to_char(p_parent_id)
66                         ||', Reject Code = '||p_reject_code
67                         ||', Last Updated By = '||to_char(p_last_updated_by)
68                         ||', Last Update Date = '||to_char(p_last_update_login));
69       FND_MESSAGE.SET_TOKEN('DEBUG_INFO',l_debug_info);
70     END IF;
71     APP_EXCEPTION.RAISE_EXCEPTION;
72 
73   END Insert_rejections;
74 
75   ---------------------------------------------------------------------------
76   --  UPDATE_RA_CUSTOMERS_INTERFACE():
77   --
78   --   Update Interface_status column  with error or warning code
79   --   in RA_CUSTOMERS_INTERFACE View.
80   ---------------------------------------------------------------------------
81   PROCEDURE update_ra_customers_interface(
82           p_code               IN      VARCHAR2,
83           p_row_id             IN      VARCHAR2,
84           p_current_status     IN      VARCHAR2) IS
85 
86   BEGIN
87     IF p_current_status = 'E' THEN
88       UPDATE ra_customers_interface
89       SET interface_status = interface_status||p_code
90       WHERE ROWID = p_row_id;
91     ELSIF p_current_status = 'W' THEN
92       UPDATE ra_customers_interface
93       SET warning_text = warning_text||p_code
94       WHERE rowid = p_row_id;
95     END IF;
96   EXCEPTION
97   WHEN NO_DATA_FOUND THEN
98     arp_standard.debug('No data found in RA_CUSTOMERS_INTERFACE View');
99   WHEN OTHERS THEN
100     arp_standard.debug('Exception in JG_GLOBE_FLEX_VAL1.UPDATE_RA_CUSTOMERS_INTERFACE()');
101     arp_standard.debug(SQLERRM);
102   END update_ra_customers_interface;
103 
104   ---------------------------------------------------------------------------
105   -- UPDATE_INTERFACE_STATUS():
106   --
107   -- PURPOSE
108   -- Update Interface Status with a Given Message Code.
109   -- Use this procedure for new validation in 11.5.1 or later
110   -- instead of update_ra_customers_interface.
111   --
112   -- PARAMETERS
113   -- ** Valid Parameter Values for p_table_name **
114   -- 1. ra_customers_interface
115   -- 2. ra_customer_profiles_interface
116   -- 3. ra_contact_phones_interface
117   -- 4. ra_customer_banks_interface
118   -- 5. ra_cust_pay_method_interface
119   ---------------------------------------------------------------------------
120   PROCEDURE update_interface_status(
121          p_rowid                       IN VARCHAR2,
122          p_table_name                  IN VARCHAR2,
123          p_code                        IN VARCHAR2,
124          p_current_status              IN VARCHAR2) IS
125 
126     TYPE TableName IS TABLE OF VARCHAR(30) INDEX BY BINARY_INTEGER;
127 
128     l_table_tab       TableName;
129     l_rowid           ROWID            DEFAULT p_rowid;
130     l_table_name      VARCHAR2(30)     DEFAULT p_table_name;
131     l_code            VARCHAR2(200)    DEFAULT p_code;
132     l_current_status  VARCHAR2(1)      DEFAULT p_current_status;
133 
134     l_sql_stmt        VARCHAR2(200);
135     l_sql_stmt_upd    VARCHAR2(200);
136     l_sql_stmt_set    VARCHAR2(200);
137     l_sql_stmt_where  VARCHAR2(200);
138 
139     Invalid_Table     EXCEPTION;
140 
141   BEGIN
142     -- ** Index **
143     -- 1. Validate Table Name
144     -- 2. Build Common Update Statement
145     -- 3. Build Update Statement for Errors
146     -- 4. Build Update Statement for Warnings
147     -- 5. Bulid Final Update Statement
148     -- 6. Execute Update Statement
149     -- 7. Raise Exception When No Row is Updated
150     --
151 
152     --
153     -- Validate Table Name
154     --
155     -- Add "l_table_tab(i) := <Table Name>" for new interface tables.
156     --
157     l_table_tab(1) := 'RA_CUSTOMERS_INTERFACE';
158     l_table_tab(2) := 'RA_CUSTOMER_PROFILES_INTERFACE';
159     l_table_tab(3) := 'RA_CONTACT_PHONES_INTERFACE';
160     l_table_tab(4) := 'RA_CUSTOMER_BANKS_INTERFACE';
161     l_table_tab(5) := 'RA_CUST_PAY_METHOD_INTERFACE';
162 
163     FOR i IN 1..l_table_tab.COUNT LOOP
164       --
165       -- If a table name is valid, exit the loop.
166       --
167       IF l_table_tab(i) = UPPER(l_table_name) THEN
168         EXIT;
169       END IF;
170       --
171       -- If a table name is invalid, raise an exception.
172       --
173       IF i = l_table_tab.COUNT THEN
174         RAISE Invalid_Table;
175       END IF;
176     END LOOP;
177     --
178     -- Update Interface Tables When Current Status is 'E' or 'W'.
179     --
180     IF l_current_status IN ('E','W') THEN
181       --
182       -- Build Common Update Statement
183       --
184       l_sql_stmt_upd   := 'UPDATE ' || l_table_name;
185       l_sql_stmt_where := ' WHERE rowid = :v_rowid';
186 
187       --
188       -- Build Update Statement for Errors
189       --
190       IF l_current_status = 'E' THEN
191         l_sql_stmt_set := ' SET interface_status = interface_status || :v_code';
192 
193       --
194       -- Build Update Statement for Warnings
195       --
196       ELSIF l_current_status = 'W' THEN
197         IF UPPER(l_table_name) = 'RA_CUSTOMERS_INTERFACE' THEN
198           l_sql_stmt_set := ' SET warning_text = warning_text || :v_code';
199         ELSE
200           RAISE Invalid_Table;
201         END IF;
202       END IF;
203 
204       --
205       -- Bulid Final Update Statement
206       --
207       l_sql_stmt := l_sql_stmt_upd || l_sql_stmt_set || l_sql_stmt_where;
208 
209       --
210       -- Execute Update Statement
211       --
212       EXECUTE IMMEDIATE l_sql_stmt USING l_code, l_rowid;
213 
214       --
215       -- Raise Exception When No Row is Updated.
216       --
217       IF SQL%NOTFOUND THEN
218         RAISE NO_DATA_FOUND;
219       END IF;
220     END IF;
221   EXCEPTION
222   WHEN Invalid_Table THEN
223     arp_standard.debug(SQLERRM);
224     arp_standard.debug('Invalid Table Name: ' || l_table_name);
225     RAISE;
226   WHEN OTHERS THEN
227     arp_standard.debug(SQLERRM);
228     arp_standard.debug(l_sql_stmt);
229     RAISE;
230   END;
231 
232   ---------------------------------------------------------------------------
233   --  CHECK_FORMAT():
234   --
235   --   Check format of each descriptive flexfield segment
236   ---------------------------------------------------------------------------
237   FUNCTION check_format(
238                        p_value          IN VARCHAR2,
239                        p_format_type    IN VARCHAR2,
240                        p_maximum_size   IN NUMBER,
241                        p_precision      IN NUMBER,
242                        p_alphanumeric   IN VARCHAR2,
243                        p_uppercase_only IN VARCHAR2,
244                        p_right_justify  IN VARCHAR2,
245                        p_min_value      IN VARCHAR2,
246                        p_max_value      IN VARCHAR2 )
247   RETURN BOOLEAN IS
248 
249     c_num          NUMBER;
250     c_date         DATE;
251 
252   FUNCTION check_maximum_size( v IN VARCHAR2, s in NUMBER )
253   RETURN BOOLEAN IS
254   BEGIN
255     if( lengthb( v ) > s ) then
256       return( FALSE );
257     else
258       return( TRUE );
259     end if;
260   END check_maximum_size;
261 
262   FUNCTION check_maximum_size_just( v IN VARCHAR2, s in NUMBER )
263   RETURN BOOLEAN IS
264   BEGIN
265     if( lengthb( v ) <> s ) and ( v IS NOT NULL) then
266       return( FALSE );
267     else
268       return( TRUE );
269     end if;
270   END check_maximum_size_just;
271 
272   FUNCTION check_date9( v IN VARCHAR2, d OUT NOCOPY DATE )
273   RETURN BOOLEAN IS
274   BEGIN
275     d :=  fnd_date.chardate_to_date( v );
276     return(TRUE);
277   EXCEPTION
278     WHEN OTHERS then
279       d := NULL;
280       return(FALSE);
281   END check_date9;
282 
283   FUNCTION check_date11( v IN VARCHAR2, d OUT NOCOPY DATE )
284   RETURN BOOLEAN IS
285   BEGIN
286     d :=  fnd_date.chardate_to_date( v );
287     return(TRUE);
288   EXCEPTION
289     WHEN OTHERS then
290       d := NULL;
291       return(FALSE);
292   END check_date11;
293 
294   FUNCTION check_number( v IN VARCHAR2, n OUT NOCOPY NUMBER )
295   RETURN BOOLEAN IS
296   BEGIN
297     n := to_number( v );
298     return(TRUE);
299   EXCEPTION
300     WHEN OTHERS then
301       n := NULL;
302       return(FALSE);
303   END check_number;
304 
305   FUNCTION check_uppercase( v IN VARCHAR2 )
306   RETURN BOOLEAN IS
307     dummy VARCHAR2(150);
308   BEGIN
309     dummy := upper( v );
310     if( dummy <> v ) then
311       return( FALSE );
312     else
313       return( TRUE );
314     end if;
315   END check_uppercase;
316 
317   BEGIN
318 
319   if( p_format_type = 'C' )then
320 
321     if ( NOT check_maximum_size( p_value, p_maximum_size ) ) then
322       return( FALSE );
323     end if;
324 
325     if( p_alphanumeric = 'N' ) then
326       if( NOT check_number( p_value, c_num ) ) then
327         return( FALSE );
328       end if;
329     end if;
330 
331     if( p_uppercase_only = 'Y' ) then
332       if( NOT check_uppercase( p_value ) ) then
333         return( FALSE );
334       end if;
335     end if;
336 
337     if( p_right_justify = 'Y' ) then
338       if( NOT check_maximum_size_just( p_value, p_maximum_size ) ) then
339         return( FALSE );
340       end if;
341     end if;
342 
343   elsif( p_format_type = 'D' )then
344 
345     if ( NOT check_maximum_size_just( p_value, p_maximum_size ) ) then
346       return( FALSE );
347     end if;
348 
349     if( NOT check_uppercase( p_value ) ) then
350       return( FALSE );
351     end if;
352 
353     if ( p_maximum_size = 9 ) then
354 
355       if( NOT check_date9( p_value, c_date ) ) then
356         return( FALSE );
357       end if;
358 
359     elsif ( p_maximum_size = 11 ) then
360 
361       if( NOT check_date11( p_value, c_date ) ) then
362         return( FALSE );
363       end if;
364 
365     end if;
366 
367   elsif( p_format_type = 'N' )then
368 
369     if ( NOT check_maximum_size( p_value, p_maximum_size ) ) then
370       return( FALSE );
371     end if;
372 
373     if( NOT check_number( p_value, c_num ) ) then
374       return( FALSE );
375     end if;
376 
377   end if;
378 
379     return( TRUE );
380 
381   END check_format;
382 
383 END jg_globe_flex_val_shared;