1------------------------------------------------------------------------------
2--                                                                          --
3--                          APQ DATABASE BINDINGS                           --
4--                                                                          --
5--                                  A P Q                                   --
6--                                                                          --
7--                                 S p e c                                  --
8--                                                                          --
9--         Copyright (C) 2002-2007, Warren W. Gay VE3WWG                    --
10--         Copyright (C) 2007-2011, KOW Framework Project                   --
11--                                                                          --
12--                                                                          --
13-- APQ is free software;  you can  redistribute it  and/or modify it under  --
14-- terms of the  GNU General Public License as published  by the Free Soft- --
15-- ware  Foundation;  either version 2,  or (at your option) any later ver- --
16-- sion.  APQ is distributed in the hope that it will be useful, but WITH-  --
17-- OUT ANY WARRANTY;  without even the  implied warranty of MERCHANTABILITY --
18-- or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License --
19-- for  more details.  You should have  received  a copy of the GNU General --
20-- Public License  distributed with APQ;  see file COPYING.  If not, write  --
21-- to  the Free Software Foundation,  59 Temple Place - Suite 330,  Boston, --
22-- MA 02111-1307, USA.                                                      --
23--                                                                          --
24-- As a special exception,  if other files  instantiate  generics from this --
25-- unit, or you link  this unit with other files  to produce an executable, --
26-- this  unit  does not  by itself cause  the resulting  executable  to  be --
27-- covered  by the  GNU  General  Public  License.  This exception does not --
28-- however invalidate  any other reasons why  the executable file  might be --
29-- covered by the  GNU Public License.                                      --
30--                                                                          --
31------------------------------------------------------------------------------
32
33
34
35-------------------------------------------------------------------------------
36-- This is the base package for APQ.                                         --
37-- That's  everything  that  should  be  used when developping in a database --
38-- vendor  independent  manner.                                              --
39-- It doesn't mean that by only using those methods your code will run at any--
40-- backend.  This  only  assures  that your code will be able to be linked   --
41-- against  other  drivers,  even  in  runtime  (using  plugins).            --
42-------------------------------------------------------------------------------
43
44
45
46-- TODO: move all the database dependent code to the database driver!
47-- TIP for Time and Date values:
48-- 	make the Value() return String abstract in such way that, when it's
49-- 	a date value, it should be automatically translated to a standard way
50--
51-- 	This way should be the ISO way so it's a lot easier to develop.
52--
53-- 	An equivalent technique should be applied whenever needed.
54-- Other approach might be implemeting Value() for each primitive APQ supports.
55-- Then the generic methods would use those primitives whever needed.
56-- These generic methods would have to be changed in order to receive Class wide objetcs.
57
58
59
60with Ada.Calendar;
61with Ada.Calendar.Time_Zones;
62with Ada.Exceptions;	use Ada.Exceptions;
63with Ada.Text_IO;
64with Ada.Finalization;
65with Ada.Unchecked_Deallocation;
66with Ada.Streams;
67with Ada.Characters.Latin_1;
68with Ada.Strings.Bounded;
69with Ada.Strings.Unbounded;	use Ada.Strings.Unbounded;
70with Interfaces.C.Strings;
71with Interfaces.C_Streams;
72with System;
73
74package APQ is
75
76
77	----------------
78	-- EXCEPTIONS --
79	----------------
80
81	SQL_Error :          exception;     -- SQL Error Occurred
82	Use_Error :          exception;     -- USE Database error occurred
83	Not_Connected :      exception;     -- Connect failed, or no connection
84	Already_Connected :  exception;     -- A connection has already been established
85	No_Result :          exception;     -- No result available
86	No_Column :          exception;     -- Column does not exist (at index)
87	No_Tuple :           exception;     -- No such tuple
88	Null_Value :         exception;     -- Attempt to access a null value
89	Invalid_Format :     exception;     -- Invalid format or bad data
90	Small_Buffer :       exception;     -- Truncation into a small buffer
91	Blob_Error :         exception;     -- Operation on blob failed
92	Abort_State :        exception;     -- A ROLLBACK operation is required
93	Tracing_State :      exception;     -- Already tracing to a file
94	Failed :             exception;     -- General operation failed
95	Not_Supported :      exception;     -- Feature or attribute is not supported
96
97
98
99	type APQ_Error is (
100		APQ01,
101		APQ02,
102		APQ03,
103		APQ04,
104		APQ05,
105		APQ06,
106		APQ07,
107		APQ08,
108		APQ09,
109		APQ10,
110		APQ11,
111		APQ12,
112		APQ13,
113		APQ14,
114		APQ15,
115		APQ16,
116		APQ17,
117		APQ18,
118		APQ19,
119		APQ20,
120		APQ24,
121		APQ25,
122		APQ26,
123		APQ27,
124		APQ28);
125	-- It's a type used to raise exceptions with messages
126	-- Each APQ_Error is linked to an error message that can be retrieved from the
127	-- constant array APQ_Error_Descriptions.
128
129
130	subtype APQ_Error_Description is Unbounded_String;
131	-- represents a description message for an APQ error.
132	-- This message should follow the pattern:
133	-- "some text %0% %1% some other text %2% ...."
134	-- Where %i% will be substituted by the 1th element of an pattern array
135	-- See To_UString_Array() and Raise_APQ_Exception.
136
137	type APQ_Error_Description_Array is Array(APQ_Error range <>) of APQ_Error_Description;
138	-- it's used to map the error codes to messages
139
140	APQ_Error_Descriptions: constant APQ_Error_Description_Array :=
141		(
142			APQ01 => To_Unbounded_String("Unable to return UNIX socket port as Integer"),
143			APQ02 => To_Unbounded_String("Unable to return TCP/IP port # as string"),
144			APQ03 => To_Unbounded_String("String '%0%' is not a YYYY-MM-DD format date"),
145			APQ04 => To_Unbounded_String("'%0%' is invalid APQ date format"),
146			APQ05 => To_Unbounded_String("String '%0%' is an invalid time format"),
147			APQ06 => To_Unbounded_String("String '%0%' is an invalid time format"),
148			APQ07 => To_Unbounded_String("String '%0%' does not a boolean represent"),
149			APQ08 => To_Unbounded_String("Converting Row_ID_Type value for column #%0%"),
150			APQ09 => To_Unbounded_String("Buffer is too small to receive column #%0%"),
151			APQ10 => To_Unbounded_String("Bad value for boolean in column #%0%"),
152			APQ11 => To_Unbounded_String("Bad integer value for column #%0%"),
153			APQ12 => To_Unbounded_String("Bad modular value for column #%0%"),
154			APQ13 => To_Unbounded_String("Bad float value for column #%0%"),
155			APQ14 => To_Unbounded_String("Bad fixed value for column #%0%"),
156			APQ15 => To_Unbounded_String(""), -- empty error slot
157			APQ16 => To_Unbounded_String("Bad decimal value for column #%0%"),
158			APQ17 => To_Unbounded_String("Bad date value for column #%0%"),
159			APQ18 => To_Unbounded_String("Bad date value (%0%) for column #%1%"),
160			APQ19 => To_Unbounded_String("Bad time value (%0%) for column #%1%"),
161			APQ20 => To_Unbounded_String("Bad timestamp format (%0%) for column #%1%"),
162			APQ24 => To_Unbounded_String("Receiving string too small for column #%0%"),
163			APQ25 => To_Unbounded_String("Receiving string too small for column #%0%"),
164			APQ26 => To_Unbounded_String("Receiving bounded string too small for column #%0%"),
165			APQ27 => To_Unbounded_String("Receiving bitstring too small for column #%0%"),
166			APQ28 => To_Unbounded_String("Cursors are not supported for this database product in the client library")
167		);
168
169
170	type Pattern_Array is Array(Natural range<>) of Unbounded_String;
171
172	function To_Pattern_Array(Zero: in String) return Pattern_Array;
173	-- return a Pattern array that maps from 0 to Zero.
174
175	function To_Pattern_Array(Zero, One: in String) return Pattern_Array;
176	-- same as the previous, but including both zero and one.
177	function To_Pattern_Array(Zero, One, Two: in String) return Pattern_Array;
178	-- same as the previous, but including both zero, one and two.
179
180	procedure Raise_APQ_Error_Exception( E: in Exception_Id;
181		Code: in APQ_Error; Where: in String; Zero: in String := "" );
182	-- Raise the Exception E with a comprehensive error message
183	procedure Raise_APQ_Error_Exception( E: in Exception_Id;
184		Code: in APQ_Error; Where: in String; Zero, One: in String );
185	-- Raise the Exception E with a comprehensive error message
186	procedure Raise_APQ_Error_Exception( E: in Exception_Id;
187		Code: in APQ_Error; Where: in String; Zero, One, Two: in String );
188	-- Raise the Exception E with a comprehensive error message
189	procedure Raise_APQ_Error_Exception( E: in Exception_Id;
190		Code: in APQ_Error; Where: in String; Patterns: in Pattern_Array );
191	-- Raise the Exception E with a comprehensive error message
192
193
194
195	--------------------
196	-- SQL DATA MODEL --
197	--------------------
198
199	-- scalar types
200	type APQ_Smallint is range -32768..32767;
201	type APQ_Integer is range -2 ** 31 .. 2 ** 31 - 1;
202	type APQ_Bigint is range -2 ** 63 .. 2 ** 63 - 1;
203	type APQ_Real is digits 6;
204	type APQ_Double is digits 15;
205	type APQ_Serial is range 1..2147483647;
206	type APQ_Bigserial is range 1..9223372036854775807;
207
208
209	-- time types
210	subtype APQ_Date is Ada.Calendar.Time;          -- Date (time ignored)
211	subtype APQ_Time is Ada.Calendar.Day_Duration;  -- Time only (date ignored)
212	type APQ_Timestamp is new Ada.Calendar.Time;    -- Date and time, stored in UTC
213
214
215	type Hour_Number is range 0..23;
216	type Minute_Number is range 0..59;
217	type Second_Number is range 0..59;
218
219
220	-- other types..
221	subtype APQ_Boolean is Boolean;                 -- Boolean type
222	type APQ_Bitstring is array(Positive range <>) of APQ_Boolean;
223	pragma pack(APQ_Bitstring);
224
225
226	--------------
227	-- SQL MISC --
228	--------------
229
230	type SQL_Case_Type is ( Upper_Case, Lower_Case, Preserve_Case );
231
232	Line_Feed : constant String(1..1) := Ada.Characters.Latin_1.LF & "";
233	-- it's a String for a simple reason:
234	-- 	it's appended by several functions to the end of a query.
235	-- 	an this suffix can be changed by another (bigger) string.
236	-- 	this makes things a lot easier
237
238	type SQL_Code_Type is range -2 ** 31 .. 2 ** 31 - 1;
239
240
241	-------------------------------------
242	-- SQL Fetch, Indexing and Tracing --
243	-------------------------------------
244
245
246	-- INDEX:
247	type Row_ID_Type is mod 2 ** 64;
248	-- Identifies a specific row
249	type Tuple_Index_Type is mod 2 ** 64;
250	-- Related concept to Row_ID_Type
251	First_Tuple_Index : constant Tuple_Index_Type := 1;
252
253	subtype Tuple_Count_Type is Tuple_Index_Type;
254
255	type Column_Index_Type is new Positive;
256
257	-- FETCH:
258
259	type Fetch_Mode_Type is (
260		Sequential_Fetch,		-- All databases : sequential fetch mode
261		Random_Fetch,			-- PostgreSQL, MySQL, not Sybase
262		Cursor_For_Update,		-- Sybase
263		Cursor_For_Read_Only		-- Sybase
264		);
265
266	type Trace_Mode_Type is (
267		Trace_None,			-- No tracing
268		Trace_DB,			-- Enable database library tracing
269		Trace_APQ,			-- APQ Trace
270		Trace_Full			-- Full trace information (Trace_DB and Trace_APQ)
271		);
272
273
274
275	 type Database_Type is (
276		 Engine_PostgreSQL,		-- PostgreSQL database engine is being used
277		 Engine_MySQL,			-- MySQL database engine is being used
278		 Engine_Sybase,			-- Sybase ASE 12.5x +
279		 Engine_CT_Lib,			-- The native, low-level programming interface for
280		 				-- the Sybase SQL Server database
281		 Engine_ODBC,                   -- ODBC engine (not ready)
282		 Engine_Other			-- Other engine, not supported by the APQ team
283		 );
284
285
286	----------------------------------------------------------------------------------
287	--				THE MAIN TYPEs					--
288	----------------------------------------------------------------------------------
289	-- Those types should be extended and have their abstract methods implemented	--
290	-- by the new type.                                                           	--
291	--										--
292	-- Those are the types responsible for interfacing with the database's native	--
293	-- connector.									--
294	----------------------------------------------------------------------------------
295
296	type Root_Connection_Type is abstract new Ada.Finalization.Limited_Controlled with private;
297	type Connection_Ptr is access all Root_Connection_Type'Class;
298
299	type Root_Query_Type is abstract new Ada.Finalization.Controlled with private;
300	type Query_Ptr is access all Root_Query_Type'Class;
301
302
303
304	----------------------------------------------------------------------------------
305	--				ABSTRACT METHOS FOR BOTH			--
306	-- 	. Root_Connection_Type and						--
307	-- 	. Root_Query_Type							--
308	----------------------------------------------------------------------------------
309	-- Those are the basic methos do be implemented by the driver implementor.	--
310	-- Other methods shall be implemented as well, but these represent the basic set--
311	-- of funcionalities required by APQ.						--
312	----------------------------------------------------------------------------------
313
314
315	--------------------------
316	-- ROOT_CONNECTION_TYPE --
317	--------------------------
318	function Engine_Of(C : Root_Connection_Type) return Database_Type is abstract;
319	-- Return a identifier for the connection used.
320
321
322	procedure Connect(C : in out Root_Connection_Type; Check_Connection : Boolean := True) is abstract;
323	-- Connect to the Database C.
324	-- if Check_Connection = False, then assume it's not connected.
325	-- Usefull when Is_Connected has been called before.
326
327	procedure Connect(C : in out Root_Connection_Type; Same_As : Root_Connection_Type'Class) is abstract;
328	-- Clone the connection Same_As to C
329
330	procedure Disconnect(C : in out Root_Connection_Type) is abstract;
331	-- Close the database connection
332
333	function Is_Connected(C : Root_Connection_Type) return Boolean is abstract;
334	-- Checks if the connection is active
335
336	procedure Reset(C : in out Root_Connection_Type) is abstract;
337	-- Reset the Connection object, not the connection itself.
338	-- It makes possible the reuse of the Root_Connection_Type object in another
339	-- connection.
340	-- It does not disconnect and then reconnect!
341
342
343	function Error_Message(C : Root_Connection_Type) return String is abstract;
344	-- Return an error message describing why the connection might have failed.
345	-- To be used when the No_Connection exception is raised by the Connect predicate
346
347
348	procedure Open_DB_Trace(C : in out Root_Connection_Type;
349		Filename : String; Mode : Trace_Mode_Type := Trace_APQ) is abstract;
350	-- Initialize the tracing
351
352	---------------------
353	-- ROOT_QUERY_TYPE --
354	---------------------
355	function Engine_Of(Q : Root_Query_Type) return Database_Type is abstract;
356	-- Return an identifier for the database type used.
357
358	procedure Execute(Query : in out Root_Query_Type;
359		Connection : in out Root_Connection_Type'Class) is abstract;
360	-- Execute the query using the specified connection
361
362	procedure Execute_Checked(Query : in out Root_Query_Type;
363		Connection : in out Root_Connection_Type'Class; Msg : String := "") is abstract;
364	-- Execute the query using the specified connection, reporting
365	-- any error that might occur to the Standard_Error output.
366	--
367	-- The exception is then re-raised to leave control in the caller's hands.
368	--
369	-- If the Msg string is specified, a line is printed before
370	-- the error message following the pattern:
371	-- **** SQL ERROR: [Msg]
372
373
374	-- Transation Operations --
375	--
376	--  Use these procedures in favour of using the custom SQL syntax for better portability:
377	procedure Begin_Work(Query : in out Root_Query_Type;
378		Connection : in out Root_Connection_Type'Class) is abstract;
379	procedure Commit_Work(Query : in out Root_Query_Type;
380		Connection : in out Root_Connection_Type'Class) is abstract;
381	procedure Rollback_Work(Query : in out Root_Query_Type;
382		Connection : in out Root_Connection_Type'Class) is abstract;
383
384
385	procedure Rewind(Q : in out Root_Query_Type) is abstract;
386	-- Rewind to the first result when Random_Fetch mode is used.
387	-- Raises SQL_Error when not in the right mode.
388
389
390	procedure Fetch(Q : in out Root_Query_Type) is abstract;
391	-- Fetch the next result of the query when in Random_Fetch or Sequential_Fetch mode
392
393	procedure Fetch(Q : in out Root_Query_Type; TX : Tuple_Index_Type) is abstract;
394	-- Fetch the TXth result when in the Random_Fetch mode.
395
396	function End_of_Query(Q : Root_Query_Type) return Boolean is abstract;
397	-- !!!!DEPRECATED!!!!
398	-- Catch the No_Tuple exception instead!
399	-- This won't work as expected with MySQL due to a bug in the client library used
400	--
401	-- Checks if there are more results to be fetched.
402
403	function Tuple(Q : Root_Query_Type) return Tuple_Index_Type is abstract;
404	-- return the last tuple fetched
405
406	function Tuples(Q : Root_Query_Type) return Tuple_Count_Type is abstract;
407	-- count the tuples returned by the query
408
409	function Columns(Q : Root_Query_Type) return Natural is abstract;
410	-- count the columns returned by the query
411
412	function Value(Query : Root_Query_Type; CX : Column_Index_Type) return String is abstract;
413	-- get a value as an String.
414
415	function Column_Name(Query : Root_Query_Type; Index : Column_Index_Type) return String is abstract;
416	-- get the Index'th column name.
417
418	function Column_Index(Query : Root_Query_Type; Name : String) return Column_Index_Type is abstract;
419	-- get the index for the column "Name"
420
421	function Result(Query : Root_Query_Type) return Natural is abstract;
422	-- get the result code for the query
423	-- the meaning of the returned code varies from database product to another.
424
425	function Is_Null(Q : Root_Query_Type; CX : Column_Index_Type) return Boolean is abstract;
426	-- checks if the result in the CXth column is null.
427
428	function Command_Oid(Query : Root_Query_Type) return Row_ID_Type is abstract;
429	-- After running an INSERT statement, return the Row_ID for the inserted column.
430	-- Can raise:
431	-- 	No_Result	=> there is no result status (no execution)
432	-- 	SQL_Error	=> An SQL error occurred obtaining the OID
433	--
434	-- Each database product has it's own requirements for this function to work.
435	-- For more information reffer to the driver's documentation.
436
437	function Null_Oid(Query : Root_Query_Type) return Row_ID_Type is abstract;
438	-- Used to avoid hardcoded numbers.
439	-- Return the ID that represents a NULL OID.
440
441	function Error_Message(Query : Root_Query_Type) return String is abstract;
442	-- Return an error message when the query has failed.
443
444	function Is_Duplicate_Key(Query : Root_Query_Type) return Boolean is abstract;
445	-- When an INSERT statement runs it might have a duplicated key.
446	-- When it does, SQL_Error is raised and then the developer might use
447	-- Is_Duplicate_Key to check if the error was due the row being duplicated.
448
449	function SQL_Code(Query : Root_Query_Type) return SQL_Code_Type is abstract;
450	-- Return a Code, that varies from database product to another, representing
451	-- the result status.
452	-- Currently, this feature is only avaliable to the Sybase binding.
453
454
455	function Query_Factory( C: in Root_Connection_Type ) return Root_Query_Type'Class is abstract;
456	-- create a query object for the selected connection type.
457	-- this is used internally by the New_Query function.
458	-- NOTE: DO NOT USE THIS FUNCTION AS IT'S MEANT TO BE USED INTERNALLY ONLY!
459	-- NOTE: USE New_Query INSTEAD
460
461
462	procedure Finalize(Q : in out Root_Query_Type) is abstract;
463	-- finalization routines should be extended by database vendo support implementor
464
465	----------------------------------------------------------------------------------
466	--			 IMPLEMENTED METHODS FOR BOTH				--
467	-- 	. Root_Connection_Type and						--
468	-- 	. Root_Query_Type							--
469	----------------------------------------------------------------------------------
470	-- These methods are provided by the APQ base package but the driver implementor--
471	-- might provide their own implementations.					--
472	-- Those methods, in their original implementation, make use of the abstract	--
473	-- methods defined in the previous code session.				--
474	----------------------------------------------------------------------------------
475
476
477	function New_Query(C : Root_Connection_Type'Class) return Root_Query_Type'Class;
478	-- Use this function to create a new query object for your connection.
479
480
481	--------------------------
482	-- ROOT_CONNECTION_TYPE --
483	--------------------------
484
485	function Get_Case(C : Root_Connection_Type) return SQL_Case_Type;
486	-- Get the SQL case used by default in this connection.
487	-- All new queries will use this casing by default.
488	procedure Set_Case(C : in out Root_Connection_Type; SQL_Case : SQL_Case_Type);
489	-- Set the SQL case used by default in this connection.
490	-- All new queries will use this casing by default.
491	pragma Inline(Get_Case,Set_Case);
492
493
494	function Get_Instance(C: Root_Connection_Type) return String;
495	-- Get the instance Name for the Database.
496	function Instance(C : Root_Connection_type) return String renames Get_Instance;
497	-- Get the instance Name for the Database. It's an alias for Get_Instance
498	procedure Set_Instance(C : in out Root_Connection_Type; Instance : String);
499	-- Set the instance Name for the Database.
500
501	function Get_Host_Name(C: Root_Connection_Type) return String;
502	-- Get the host name for the Database server.
503	function Host_Name(C : Root_Connection_Type) return String renames Get_Host_Name;
504	-- Get the host name for the Database server. It's an alias for Get_Host_Name
505	procedure Set_Host_Name(C : in out Root_Connection_Type; Host_Name : String);
506	-- Set the host name for the Database server.
507
508	function Get_Host_Address(C: in Root_Connection_Type) return String;
509	-- Set the host address for the database server.
510	function Host_Address(C: in Root_Connection_Type) return String renames Get_Host_Address;
511	-- Set the host address for the database server. It's an alias for Get_Host_Address
512	procedure Set_Host_Address(C : in out Root_Connection_Type; Host_Address : String);
513	-- Set the host address for the database server.
514
515	function Get_Port( C: in Root_Connection_Type ) return Integer;
516	-- Get the TCP port number.
517	function Port(C : Root_Connection_Type) return Integer renames Get_Port;
518	-- Get the TCP port number. It's an alias for Get_Port.
519	procedure Set_Port(C : in out Root_Connection_Type; Port_Number : Integer);
520	-- Set the TCP port number.
521
522	function Get_Port( C: in Root_Connection_Type) return String;
523	-- Get the Unix Port.
524	function Port(C : Root_Connection_Type) return String renames Get_Port;
525	-- Get the Unix Port. It's an alias for Get_Port.
526	procedure Set_Port(C : in out Root_Connection_Type; Port_Name : String);
527	-- Set the Unix Port
528
529	function Get_DB_Name(C : Root_Connection_Type) return String;
530	-- Get the Database name used in this connection.
531	function DB_Name(C : Root_Connection_Type) return String renames Get_DB_Name;
532	-- Get the Database name used in this connection. It's an alias for Get_DB_Name.
533	procedure Set_DB_Name(C : in out Root_Connection_Type; DB_Name : String);
534	-- Set the Database name used in this connection.
535
536
537	function Get_User( C: in Root_Connection_Type ) return String;
538	-- Get the Username for this connection.
539	function User( C: in Root_Connection_Type ) return String renames Get_User;
540	-- Get the Username for this connection. It's ana alias for Get_User
541	procedure Set_User( C: in out Root_Connection_Type; User: in String );
542	-- Set the Username for this connection.
543
544	function Get_Password( C: Root_Connection_Type ) return String;
545	-- Get the Password for this connection.
546	function Password(C : Root_Connection_Type) return String renames Get_Password;
547	-- Get the Password for this connection. It's an alias for Get_Password
548	procedure Set_Password( C: in out Root_Connection_Type; Password: in String );
549	-- Get the Password for this connection.
550
551	procedure Set_User_Password(C : in out Root_Connection_Type;
552		User_Name, User_Password : String);
553	-- Set both the username and the password for this connection.
554
555
556	function In_Abort_State(C : Root_Connection_Type) return Boolean;
557	-- Some database products (eg, PostgreSQL) can enter in a status where
558	-- every operation is ignored.
559	-- There is the Abort_State Exception for this, but there is also
560	-- this function that checks if the connection is in this state.
561
562
563	function Get_Rollback_On_Finalize( C: in Root_Connection_Type ) return Boolean;
564	-- Get if the work will be rollbacked when finalizing.
565	function Will_Rollback_On_Finalize(C : Root_Connection_Type)
566		return Boolean renames Get_Rollback_On_Finalize;
567	-- Get if the work will be rollbacked when finalizing.
568	-- It's an alias for Get_Rollback_on_Finalize.
569	procedure Set_Rollback_On_Finalize(C : in out Root_Connection_Type;
570		Rollback : Boolean);
571	-- Set if the work will be rollbacked when finalizing
572
573
574
575	procedure Set_Auto_Reconnect( C : in out Root_Connection_Type; Auto_Reconnect : in Boolean := True );
576	-- set if it should reconnect automatically when the connection is droped.
577
578	function Get_Auto_Reconnect( C : in Root_Connection_Type ) return Boolean;
579	-- return true if the connection should be automatically restablished when droped
580
581
582	---------------------
583	-- ROOT_QUERY_TYPE --
584	---------------------
585
586	-- Query setup ...
587
588	function Get_Case(Q : Root_Query_Type) return SQL_Case_Type;
589	-- Get the case used by this query
590	-- This case might be different from the one used by default
591	procedure Set_Case(Q : in out Root_Query_Type; SQL_Case : SQL_Case_Type);
592	-- Set the case used by this query.
593
594	function Get_Fetch_Mode( Q: in Root_Query_Type ) return Fetch_Mode_Type;
595	-- Get the fetch mode used by this query.
596	function Fetch_Mode(Q : Root_Query_Type) return Fetch_Mode_Type renames Get_Fetch_Mode;
597	-- Get the fetch mode used by this query. It's an alias for Get_Fetch_Mode
598	procedure Set_Fetch_Mode(Q : in out Root_Query_Type; Mode : Fetch_Mode_Type);
599	-- Set the fetch mode used by this query.
600
601	procedure Raise_Exceptions(Query : in out Root_Query_Type; Raise_On : Boolean := True);
602	-- when Execute_Checked is called, should raise the exception back to the caller?
603	pragma No_Return (Raise_APQ_Error_Exception);
604
605	procedure Report_Errors(Query : in out Root_Query_Type; Report_On : Boolean := True);
606	-- report sql erros when Execute_Checked is called?
607
608
609	-- Query information ...
610
611	function To_String(Query : Root_Query_Type) return String;
612	-- get the query text
613
614	function Is_Select(Q : Root_Query_Type) return Boolean;
615	-- is this query a select statement?
616
617	function Cursor_Name(Query : Root_Query_Type) return String;
618	-- get the cursor name for the current result
619	-- this function is meant to be overwriten by the driver if it supports cursor
620
621
622	-- SQL creation ...
623
624	procedure Clear(Q : in out Root_Query_Type);
625	-- Clear the query so one can start a new SQL expression.
626
627	procedure Grow(Q : in out Root_Query_Type);
628	-- used internally to grow the query lines size so one can Append to it.
629
630	procedure Prepare(Q : in out Root_Query_Type; SQL : String; After : String := Line_Feed);
631	-- Clear the query, starting a new one.
632
633
634	procedure Append(Q : in out Root_Query_Type; SQL : String; After : String := "");
635	-- Append a string to the query
636	procedure Append(Q : in out Root_Query_Type;
637		SQL : Ada.Strings.Unbounded.Unbounded_String; After : String := "");
638	-- Append an Unbounded_String to the query
639	procedure Append_Line(Q : in out Root_Query_Type; SQL : String := "");
640	-- Append a String followed by a new line.
641	-- If the parameter SQL is omited, there is inserted only a line break
642
643	procedure Append(Q : in out Root_Query_Type; V : APQ_Boolean; After : String := "");
644	-- Append a boolean to the query
645
646	procedure Append(Q : in out Root_Query_Type; V : APQ_Date; After : String := "");
647	-- Append a date to the query
648
649	procedure Append(Q : in out Root_Query_Type; V : APQ_Time; After : String := "");
650	-- Append a time...
651
652	procedure Append(Q : in out Root_Query_Type; V : APQ_Timestamp; After : String := "");
653	-- Append a timestamp...
654
655	procedure Append(Q : in out Root_Query_Type; V : APQ_Bitstring; After : String := "");
656	-- Append a bitstring...
657
658	procedure Append(Q : in out Root_Query_Type; V : Row_ID_Type; After : String := "");
659	-- Append a row_id_type...
660
661	procedure Append_Quoted(Q : in out Root_Query_Type;
662		Connection : Root_Connection_Type'Class; SQL : String; After : String := "");
663	-- Append a quoted String.
664	-- The case of this String isn't changed.
665	-- This primitive should normally be overriden for a specific database.
666	-- PostgreSQL and MySQL will potentially have different quoting requirements.
667
668	procedure Append_Quoted(Q : in out Root_Query_Type;
669		Connection : Root_Connection_Type'Class;
670		SQL : Ada.Strings.Unbounded.Unbounded_String; After : String := "");
671	-- Append a quoted Unbouned_String.
672	-- The case of this String isn't changed.
673	-- This primitive should normally be overriden for a specific database.
674	-- PostgreSQL and MySQL will potentially have different quoting requirements.
675
676
677
678	-- Data retrieval:
679
680
681	--Note: there is an abstract function value() which returns string;
682	-- This function is used in all these following methods:
683
684	procedure Value(Query: Root_Query_Type; CX : Column_Index_Type; V : out String);
685	-- Get the value of the CXth column as String.
686	-- Fixed length String Fetch
687	function Value(Query : Root_Query_Type; CX : Column_Index_Type)
688		return Ada.Strings.Unbounded.Unbounded_String;
689	-- Get the value of the CXth column as Unbounded_String.
690	function Value(Query : Root_Query_Type; CX : Column_Index_Type) return Row_ID_Type;
691	-- Get the value of the CXth column as Row_Id_Type.
692	function Value(Query : Root_Query_Type; CX : Column_Index_Type) return APQ_Bitstring;
693	-- Get the value of the CXth column as Bitstring.
694
695
696	--           METHODS THAT SHOULD BE OVERRIDDEN BY THE DATABASE DRIVER           --
697
698	--TODO: change the types to APQ_Something.
699	function Value(Query : Root_Query_Type; CX : Column_Index_Type) return Boolean;
700
701	function Value(Query : Root_Query_Type; CX : Column_Index_Type) return Integer;
702
703	function Value(Query : Root_Query_Type; CX : Column_Index_Type) return Float;
704
705	function Value(Query : Root_Query_Type; CX : Column_Index_Type) return APQ_Date;
706
707	function Value(Query : Root_Query_Type; CX : Column_Index_Type) return APQ_Time;
708
709	function Value(Query : Root_Query_Type; CX : Column_Index_Type) return APQ_Timestamp;
710
711
712
713
714
715	----------------------------------------------------------------------------------
716	--				GENERIC METHODS FOR				--
717	-- 	. Root_Query_Type							--
718	----------------------------------------------------------------------------------
719	-- These  methods  are  implemented  using the abstract and implemented methods	--
720	-- that are listed before this block.						--
721	--										--
722	-- They  are  meant  to  enforce  strong  typing  with  Database  programming.	--
723	----------------------------------------------------------------------------------
724
725
726	-- SQL creation :: append ...
727
728	generic
729	type Val_Type is new Boolean;
730	procedure Append_Boolean(Q : in out Root_Query_Type'Class;
731		V : Val_Type; After : String := "");
732
733	generic
734	type Val_Type is range <>;
735	procedure Append_Integer(Q : in out Root_Query_Type'Class;
736		V : Val_Type; After : String := "");
737
738	generic
739	type Val_Type is mod <>;
740	procedure Append_Modular(Q : in out Root_Query_Type'Class;
741		V : Val_Type; After : String := "");
742
743	generic
744	type Val_Type is digits <>;
745	procedure Append_Float(Q : in out Root_Query_Type'Class;
746		V : Val_Type; After : String := "");
747
748	generic
749	type Val_Type is delta <>;
750	procedure Append_Fixed(Q : in out Root_Query_Type'Class;
751		V : Val_Type; After : String := "");
752
753	generic
754	type Val_Type is delta <> digits <>;
755	procedure Append_Decimal(Q : in out Root_Query_Type'Class;
756		V : Val_Type; After : String := "");
757
758	generic
759	type Val_Type is new Ada.Calendar.Time;
760	procedure Append_Date(Q : in out Root_Query_Type'Class;
761		V : Val_Type; After : String := "");
762
763	generic
764	type Val_Type is new Ada.Calendar.Day_Duration;
765	procedure Append_Time(Q : in out Root_Query_Type'Class;
766		V : Val_Type; After : String := "");
767
768	generic
769	type Val_Type is new Ada.Calendar.Time;
770	procedure Append_Timestamp(Q : in out Root_Query_Type'Class;
771		V : Val_Type; After : String := "");
772
773	generic
774	type Val_Type is new APQ_Bitstring;
775	procedure Append_Bitstring(Q : in out Root_Query_Type'Class;
776		V : Val_Type; After : String := "");
777
778	generic
779	with package P is new Ada.Strings.Bounded.Generic_Bounded_Length(<>);
780	procedure Append_Bounded(Q : in out Root_Query_Type'Class;
781		SQL : P.Bounded_String; After : String := "");
782
783	generic
784	with package P is new Ada.Strings.Bounded.Generic_Bounded_Length(<>);
785	procedure Append_Bounded_Quoted(Q : in out Root_Query_Type'Class;
786		Connection : Root_Connection_Type'Class;
787		SQL : P.Bounded_String; After : String := "");
788
789
790	-- SQL creation :: encode...
791	-- encode is the same as append, but supporting null values.
792
793
794	generic
795	type Val_Type is new Boolean;
796	type Ind_Type is new Boolean;
797	procedure Encode_Boolean(Q : in out Root_Query_Type'Class;
798		V : Val_Type; Indicator : Ind_Type; After : String := "");
799
800	generic
801	type Val_Type is range <>;
802	type Ind_Type is new Boolean;
803	procedure Encode_Integer(Q : in out Root_Query_Type'Class;
804		V : Val_Type; Indicator : Ind_Type; After : String := "");
805
806	generic
807	type Val_Type is mod <>;
808	type Ind_Type is new Boolean;
809	procedure Encode_Modular(Q : in out Root_Query_Type'Class;
810		V : Val_Type; Indicator : Ind_Type; After : String := "");
811
812	generic
813	type Val_Type is digits <>;
814	type Ind_Type is new Boolean;
815	procedure Encode_Float(Q : in out Root_Query_Type'Class;
816		V : Val_Type; Indicator : Ind_Type; After : String := "");
817
818	generic
819	type Val_Type is delta <>;
820	type Ind_Type is new Boolean;
821	procedure Encode_Fixed(Q : in out Root_Query_Type'Class;
822		V : Val_Type; Indicator : Ind_Type; After : String := "");
823
824	generic
825	type Val_Type is delta <> digits <>;
826	type Ind_Type is new Boolean;
827	procedure Encode_Decimal(Q : in out Root_Query_Type'Class;
828		V : Val_Type; Indicator : Ind_Type; After : String := "");
829
830	generic
831	type Val_Type is new APQ_Date;
832	type Ind_Type is new Boolean;
833	procedure Encode_Date(Q : in out Root_Query_Type'Class;
834		V : Val_Type; Indicator : Ind_Type; After : String := "");
835
836	generic
837	type Val_Type is new APQ_Time;
838	type Ind_Type is new Boolean;
839	procedure Encode_Time(Q : in out Root_Query_Type'Class;
840		V : Val_Type; Indicator : Ind_Type; After : String := "");
841
842	generic
843	type Val_Type is new APQ_Timestamp;
844	type Ind_Type is new Boolean;
845	procedure Encode_Timestamp(Q : in out Root_Query_Type'Class;
846		V : Val_Type; Indicator : Ind_Type; After : String := "");
847
848
849	generic
850	type Val_Type is new APQ_Bitstring;
851	type Ind_Type is new Boolean;
852	procedure Encode_Bitstring(Q : in out Root_Query_Type'Class;
853		V: Val_Type; Indicator : Ind_Type; After : String := "");
854
855	generic
856	type Ind_Type is new Boolean;
857	procedure Encode_String_Quoted(Q : in out Root_Query_Type'Class;
858		Connection : Root_Connection_Type'Class;
859		SQL : String; Indicator : Ind_Type; After : String := "");
860
861	generic
862	type Ind_Type is new Boolean;
863	with package P is new Ada.Strings.Bounded.Generic_Bounded_Length(<>);
864	procedure Encode_Bounded_Quoted(Q : in out Root_Query_Type'Class;
865		Connection : Root_Connection_Type'Class;
866		SQL : P.Bounded_String; Indicator : Ind_Type; After : String := "");
867
868	generic
869	type Ind_Type is new Boolean;
870	procedure Encode_Unbounded(Q : in out Root_Query_Type'Class;
871		Connection : Root_Connection_Type'Class;
872		SQL : Ada.Strings.Unbounded.Unbounded_String;
873		Indicator : Ind_Type; After : String := "");
874
875	generic
876	type Ind_Type is new Boolean;
877	procedure Encode_Unbounded_Quoted(Q : in out Root_Query_Type'Class;
878		Connection : Root_Connection_Type'Class;
879		SQL : Ada.Strings.Unbounded.Unbounded_String;
880		Indicator : Ind_Type; After : String := "");
881
882
883
884
885	-- Data retrieval :: misc ...
886
887
888
889	generic
890	type Ind_Type is new Boolean;
891	function Column_Is_Null(Q : Root_Query_Type'Class; CX : Column_Index_Type) return Ind_Type;
892	-- checks if the result in the CXth column is null.
893
894
895
896	-- Data retrieval :: value operations ...
897	-- TODO: Remove all these operations and implement value operations instead returning the correct type.
898
899
900	generic
901	type Val_Type is new Boolean;
902	function Boolean_Value(Query : Root_Query_Type'Class;
903		CX : Column_Index_Type) return Val_Type;
904
905	generic
906	type Val_Type is range <>;
907	function Integer_Value(Query : Root_Query_Type'Class;
908		CX : Column_Index_Type) return Val_Type;
909
910	generic
911	type Val_Type is mod <>;
912	function Modular_Value(Query : Root_Query_Type'Class;
913		CX : Column_Index_Type) return Val_Type;
914
915	generic
916	type Val_Type is digits <>;
917	function Float_Value(Query : Root_Query_Type'Class;
918		CX : Column_Index_Type) return Val_Type;
919
920	generic
921	type Val_Type is delta <>;
922	function Fixed_Value(Query : Root_Query_Type'Class;
923		CX : Column_Index_Type) return Val_Type;
924
925	generic
926	type Val_Type is delta <> digits <>;
927	function Decimal_Value(Query : Root_Query_Type'Class;
928		CX : Column_Index_Type) return Val_Type;
929
930	generic
931	type Val_Type is new APQ_Date;
932	function Date_Value(Query : Root_Query_Type'Class;
933		CX : Column_Index_Type) return Val_Type;
934
935	generic
936	type Val_Type is new APQ_Time;
937	function Time_Value(Query : Root_Query_Type'Class;
938		CX : Column_Index_Type) return Val_Type;
939
940	generic
941	type Val_Type is new Ada.Calendar.Time;
942	function Timestamp_Value(Query : Root_Query_Type'Class;
943		CX : Column_Index_Type) return Val_Type;
944
945	generic
946	with package P is new Ada.Strings.Bounded.Generic_Bounded_Length(<>);
947	function Bounded_Value(Query : Root_Query_Type'Class;
948		CX : Column_Index_Type) return P.Bounded_String;
949
950
951
952	-- Data retrieval :: fetch operations ...
953	-- They are the same as the value operations, but with null support
954
955
956	generic
957	type Val_Type is new Boolean;
958	type Ind_Type is new Boolean;
959	procedure Boolean_Fetch(Query : Root_Query_Type'Class;
960		CX : Column_Index_Type; V : out Val_Type; Indicator : out Ind_Type);
961
962	generic
963	type Val_Type is range <>;
964	type Ind_Type is new Boolean;
965	procedure Integer_Fetch(Query : Root_Query_Type'Class;
966		CX : Column_Index_Type; V : out Val_Type; Indicator : out Ind_Type);
967
968	generic
969	type Val_Type is mod <>;
970	type Ind_Type is new Boolean;
971	procedure Modular_Fetch(Query : Root_Query_Type'Class;
972		CX : Column_Index_Type; V : out Val_Type; Indicator : out Ind_Type);
973
974	generic
975	type Val_Type is digits <>;
976	type Ind_Type is new Boolean;
977	procedure Float_Fetch(Query : Root_Query_Type'Class;
978		CX : Column_Index_Type; V : out Val_Type; Indicator : out Ind_Type);
979
980	generic
981	type Val_Type is delta <>;
982	type Ind_Type is new Boolean;
983	procedure Fixed_Fetch(Query : Root_Query_Type'Class;
984		CX : Column_Index_Type; V : out Val_Type; Indicator : out Ind_Type);
985
986	generic
987	type Val_Type is delta <> digits <>;
988	type Ind_Type is new Boolean;
989	procedure Decimal_Fetch(Query : Root_Query_Type'Class;
990		CX : Column_Index_Type; V : out Val_Type; Indicator : out Ind_Type);
991
992	generic
993	type Val_Type is new Ada.Calendar.Time;
994	type Ind_Type is new Boolean;
995	procedure Date_Fetch(Query : Root_Query_Type'Class;
996		CX : Column_Index_Type; V : out Val_Type; Indicator : out Ind_Type);
997
998	generic
999	type Val_Type is new Ada.Calendar.Day_Duration;
1000	type Ind_Type is new Boolean;
1001	procedure Time_Fetch(Query : Root_Query_Type'Class;
1002		CX : Column_Index_Type; V : out Val_Type; Indicator : out Ind_Type);
1003
1004	generic
1005	type Val_Type is new Ada.Calendar.Time;
1006	type Ind_Type is new Boolean;
1007	procedure Timestamp_Fetch(Query : Root_Query_Type'Class;
1008		CX : Column_Index_Type; V : out Val_Type; Indicator : out Ind_Type);
1009
1010
1011	generic
1012	type Ind_Type is new Boolean;
1013	procedure Bitstring_Fetch(Query : Root_Query_Type'Class;
1014		CX : Column_Index_Type; V : out APQ_Bitstring; Last : out Natural;
1015		Indicator : out Ind_Type);
1016
1017	generic
1018	type Ind is new Boolean;
1019	with package P is new Ada.Strings.Bounded.Generic_Bounded_Length(<>);
1020	procedure Bounded_Fetch(Query : Root_Query_Type'Class;
1021		CX : Column_Index_Type; V : out P.Bounded_String; Indicator : out Ind);
1022
1023	generic
1024	type Ind_Type is new Boolean;
1025	procedure Unbounded_Fetch(Query : Root_Query_Type'Class;
1026		CX : Column_Index_Type; V : out Ada.Strings.Unbounded.Unbounded_String;
1027		Indicator : out Ind_Type);
1028
1029	generic
1030	type Ind_Type is new Boolean;
1031	procedure Char_Fetch(Query : Root_Query_Type'Class;
1032		CX : Column_Index_Type; V : out String; Indicator : out Ind_Type);
1033
1034	generic
1035	type Ind_Type is new Boolean;
1036	procedure Varchar_Fetch(Query : Root_Query_Type'Class;
1037		CX : Column_Index_Type; V : out String; Last : out Natural;
1038		Indicator : out Ind_Type);
1039
1040
1041	-- Conversion :: anything to string (APQ primitives) ...
1042
1043	function To_String(V : APQ_Boolean) return String;
1044
1045	function To_String(V : APQ_Date) return String;
1046
1047	function To_String(V : APQ_Time) return String;
1048
1049	function To_String(V : APQ_Timestamp) return String;
1050
1051	function To_String(V : APQ_Bitstring) return String;
1052
1053
1054	-- Conversion :: anything to string (generic for derived types) ...
1055
1056	generic
1057		type Val_Type is range <>;
1058	function Integer_String(V : Val_Type) return String;
1059
1060	generic
1061		type Val_Type is mod <>;
1062	function Modular_String(V : Val_Type) return String;
1063
1064	generic
1065		type Val_Type is digits <>;
1066	function Float_String(V : Val_Type) return String;
1067
1068	generic
1069		type Val_Type is delta <>;
1070	function Fixed_String(V : Val_Type) return String;
1071
1072	generic
1073		type Val_Type is delta <> digits <>;
1074	function Decimal_String(V : Val_Type) return String;
1075
1076	generic
1077		type Val_Type is new Ada.Calendar.Time;
1078	function Date_String(V : Val_Type) return String;
1079
1080	generic
1081		type Val_Type is new Ada.Calendar.Day_Duration;
1082	function Time_String(V : Val_Type) return String;
1083
1084	generic
1085		type Val_Type is new Ada.Calendar.Time;
1086	function Timestamp_String(V : Val_Type) return String;
1087
1088
1089	-- Conversion :: anything from string ...
1090 	--TODO: These functions may not need to be generic anymore. If so, make
1091 	--them return the APQ_types.
1092
1093	generic
1094		type Val_Type is new Boolean;
1095	function Convert_To_Boolean(S : String) return Val_Type;
1096
1097
1098	generic
1099		type Val_Type is new Duration;
1100	function Convert_To_Time(S : String) return Val_Type;
1101
1102
1103	generic
1104		type Val_Type is new Ada.Calendar.Time;
1105	function Convert_to_Timestamp(
1106				S	: in String;
1107				TZ	: in Ada.Calendar.Time_Zones.Time_Offset
1108			) return Val_Type;
1109
1110	function To_Date(
1111				S	: in String
1112			) return APQ_Date;
1113	-- convert the string to apq_date using the UTC timezone
1114
1115	function To_Time(
1116				S	: in String
1117			) return APQ_Time;
1118	-- convert the string to apq_time
1119
1120	function To_Timestamp(
1121				S	: in String
1122			) return APQ_Timestamp;
1123	-- convert the string to apq_timestamp using the UTC timezone
1124
1125
1126
1127	generic
1128		type Date_Type is new Ada.Calendar.Time;
1129		type Time_Type is new Ada.Calendar.Day_Duration;
1130		type Result_Type is new Ada.Calendar.Time;
1131	function Convert_Date_and_Time(
1132					DT	: in Date_Type;
1133					TM	: in Time_Type
1134				) return Result_Type;
1135	-- return a new timestamp in DT's timezone at TM duration
1136
1137
1138	-- Misc ...
1139
1140
1141	generic
1142	type Oid_Type is new Row_ID_Type;
1143	function Generic_Command_Oid(Query : Root_Query_Type'Class) return Oid_Type;
1144	-- The Generic_Command_Oid causes GNAT 3.14p to fall over and die.
1145	--
1146	-- It isn't really required, since Command_Oid(Query) can be used instead,
1147	-- and the return value converted to whatever Oid_Type is.
1148
1149	---------------------------------
1150	-- EXTENDED CALENDAR FUNCTIONS --
1151	---------------------------------
1152
1153	generic
1154	type Date_Type is new Ada.Calendar.Time;
1155	type Time_Type is new Ada.Calendar.Day_Duration;
1156	function Generic_Time_of_Day(V : Date_Type) return Time_Type;
1157
1158	generic
1159	type Time_Type is new Ada.Calendar.Day_Duration;
1160	function Generic_Hour(TM : Time_Type) return Hour_Number;
1161
1162	generic
1163	type Time_Type is new Ada.Calendar.Day_Duration;
1164	function Generic_Minute(TM : Time_Type) return Minute_Number;
1165
1166	generic
1167	type Time_Type is new Ada.Calendar.Day_Duration;
1168	function Generic_Second(TM : Time_Type) return Second_Number;
1169
1170
1171   -------------------
1172   --- misc types ----
1173   -------------------
1174   type Unsigned_Integer is new interfaces.c.unsigned;
1175   type Unsigned_Integer_Ptr is access all unsigned_integer;
1176
1177private
1178
1179   package CStr renames Interfaces.C_Streams;
1180
1181	type String_Ptr is access all String;
1182	type String_Ptr_Array is array(Natural range <>) of String_Ptr;
1183	type String_Ptr_Array_Access is access all String_Ptr_Array;
1184	type Stream_Element_Array_Ptr is access all Ada.Streams.Stream_Element_Array;
1185
1186	type Boolean_Array is array(Natural range <>) of Boolean;
1187	type Boolean_Array_Access is access all Boolean_Array;
1188
1189	subtype Port_Integer is Integer range 0..32768;
1190	type Port_Format_Type is ( IP_Port, UNIX_Port );
1191
1192
1193	type Root_Connection_Type is abstract new Ada.Finalization.Limited_Controlled with record
1194		Instance		: String_Ptr;                      -- Engine instance name
1195		Host_Name		: String_Ptr;                      -- Host name string or..
1196		Host_Address		: String_Ptr;                      -- Host IP address
1197		Port_Format		: Port_Format_Type := UNIX_Port;   -- I/O type
1198		Port_Number		: Port_Integer := 0;               -- Port number of the database server
1199		Port_Name		: String_Ptr;                      -- UNIX pathname for UNIX socket
1200		DB_Name			: String_Ptr;                      -- Database name
1201		User_Name		: String_Ptr;                      -- The user name
1202		User_Password		: String_Ptr;                      -- User password (if required)
1203		Abort_State		: Boolean := False;                -- Transaction abort state
1204		Rollback_Finalize	: Boolean := True;                 -- Rollback transaction on Finalization
1205		Trace_Filename		: String_Ptr;                      -- Filename for tracing
1206		Trace_On		: Boolean := False;                -- True if tracing is enabled
1207		Trace_Mode		: Trace_Mode_Type := Trace_None;   -- Current Trace mode
1208		Trace_File		: CStr.FILEs := CStr.Null_Stream;  -- C Stream (FILE *)
1209		Trace_Ada		: Ada.Text_IO.File_Type;           -- Ada version of Trace_File
1210		SQL_Case		: SQL_Case_Type := Upper_Case;     -- How to map SQL "case"
1211		Auto_Reconnect		: Boolean := False;                -- TODO: reconnect when the connection drops
1212	end record;
1213
1214
1215	type Root_Query_Type is abstract new Ada.Finalization.Controlled with record
1216		Count		: Natural := 0;					-- # of elements in the Collection
1217		Alloc		: Natural := 0;					-- # of allocated elements in the Collection
1218		Collection	: String_Ptr_Array_Access;			-- Array of strings
1219		Caseless	: Boolean_Array_Access;				-- True where case is to be preserved
1220		Raise_Exceptions: Boolean := True;				-- Raise exception in Execute_Checked()
1221		Report_Errors	: Boolean := True;				-- Report SQL error in Execute_Checked()
1222		Mode		: Fetch_Mode_Type := Random_Fetch;		-- Random Fetches
1223		Rewound		: Boolean := True;				-- At first tuple
1224		Tuple_Index	: Tuple_Index_Type := Tuple_Index_Type'First;	-- Current tuple index
1225		SQL_Case	: SQL_Case_Type := Upper_Case;			-- How to map SQL "case"
1226	end record;
1227
1228
1229	function To_Case(S : String; C : SQL_Case_Type) return String;
1230	-- convert the string to the selected case
1231
1232
1233	procedure Clear_Abort_State(C : in out Root_Connection_Type);
1234
1235	procedure Adjust(Q : in out Root_Query_Type);
1236	function Is_Insert(Q : Root_Query_Type) return Boolean;
1237	-- True if query is an INSERT statement
1238	function Is_Update(Q : Root_Query_Type) return Boolean;
1239	-- True if query is an UPDATE statement
1240
1241	procedure Free is new Ada.Unchecked_Deallocation(String,String_Ptr);
1242	procedure Free is new Ada.Unchecked_Deallocation(
1243		Interfaces.C.char_array,Interfaces.C.Strings.char_array_access);
1244	procedure Free is new Ada.Unchecked_Deallocation(String_Ptr_Array,String_Ptr_Array_Access);
1245	procedure Free is new Ada.Unchecked_Deallocation(Boolean_Array,Boolean_Array_Access);
1246	procedure Free is new Ada.Unchecked_Deallocation(
1247		Ada.Streams.Stream_Element_Array,Stream_Element_Array_Ptr);
1248
1249	procedure Free_Ptr(SP : in out String_Ptr);
1250
1251	function To_String(S : String_Ptr) return String;
1252	function To_Ada_String(P : Interfaces.C.Strings.chars_ptr) return String;
1253	function Blanks_To_Zero(S : String) return String;
1254
1255	procedure C_String(S : String_Ptr;
1256		CP : out Interfaces.C.Strings.char_array_access;
1257		Addr : out System.Address);
1258
1259	procedure C_String(S : String;
1260		CP : out Interfaces.C.Strings.char_array_access;
1261		Addr : out System.Address);
1262
1263	function Strip_NL(S : String) return String;
1264
1265	procedure Replace_String(SP : in out String_Ptr; S : String);
1266
1267	function Value_Of(C_String : Interfaces.C.Strings.chars_ptr) return String;
1268   function Is_Null(C_String : Interfaces.C.Strings.chars_ptr) return Boolean;
1269
1270
1271
1272   function to_string( val : Unsigned_Integer ) return string;
1273   function to_string( val : Unsigned_Integer ) return string_ptr;
1274   function to_string( val : Unsigned_Integer_ptr ) return string;
1275   function to_string( val : Unsigned_Integer_ptr ) return string_ptr;
1276
1277   function to_unsigned_integer( val : string ) return Unsigned_Integer;
1278   function to_unsigned_integer( val : string ) return Unsigned_Integer_Ptr;
1279   function to_unsigned_integer( val : string_ptr ) return Unsigned_Integer;
1280   function to_unsigned_integer( val : String_Ptr ) return Unsigned_Integer_Ptr;
1281
1282   function is_valid_unsigned( val : string ) return boolean;
1283   function is_valid_unsigned( val : String_Ptr ) return boolean;
1284
1285   procedure free is new Ada.Unchecked_Deallocation( Unsigned_Integer , Unsigned_Integer_Ptr );
1286
1287   pragma Inline( to_string , to_unsigned_integer );
1288
1289
1290end APQ;
1291