1\section{Conversion of Principal Data Types}	\label{sec:data}
2
3The host language and PCE have incompatible data representation.  We
4assume the host language to be able to represent data types for
5integers (C: int), floating point numbers (C: float) and character
6arrays (C: char~*).  Integers and floating point numbers are
7available in many host languages, character arrays are represented as
8atoms in Prolog and keywords or strings in Lisp.
9
10
11\subsection{Textual constants: interface symbol table}	\label{sec:itftable}
12
13Most symbolic languages have unique representation for textual
14constants (atoms in Prolog; symbols and keywords in Lisp).  PCE
15defines {\em names} for this purpose.  One way to convert
16host-language textual constants into PCE names is to convert the
17host-language constant into a C char~* and then the C char~* into
18a PCE name.  Older version of the PCE external interface enforced
19this mechanism.  Performance analysis has indicated that direct
20mapping improves the performance of message-passing from the
21host-language to PCE by a factor of 3.  For this reason PCE offers the
22possibility to exploit direct mapping of host-language textual
23constants into PCE names.
24
25For each name that 1) has been made visible to the host-language or
262) is the name of a named PCE object (i.e.\ @pce) PCE defines an
27{\em interface symbol}.  The definition of an \idx{pceITFSymbol}
28is given below:
29
30\begin{code}
31typedef struct pceITFSymbol
32{ PceObject	object;			/* global object associated */
33  PceName	name;			/* Pce name associated */
34  hostHandle	handle[0];		/* Alien handles to operate on */
35} *PceITFSymbol;
36\end{code}
37
38The \arg{object} field is the global object associated with
39\arg{name}.  If no object is associated to this name it is the
40constant \const {PCE_FAIL}.  The \arg{handle} array is an array of
41anonymous (void~*) 32 bit fields that may be used by the host-language
42interface to store the corresponding atom/keyword/... and/or
43object-reference.  The allocated size of this array is determined by
44the first argument of \cfunc{pceInitialise()}
45(page~\pageref{func:pceInitialise}).
46
47Implementations of host-languages that do not support a symbol-table
48for textual constants cannot use these handles and should pass 0
49to \cfunc{pceInitialise()}.  The generic Prolog interface in
50\file{xpce/prolog/c/interface.c} uses one handle to save a reference
51to the corresponding Prolog atom.  The generic Lisp interface uses
52two handles.  One to store a Lisp keyword that corresponds to the
53PCE name and one to store a Lisp structure that represents the
54\arg{object} of the interface symbol.
55
56The following functions may be used to access this table:
57
58\begin{description}
59    \cfunction{PceITFSymbol}{pceLookupHandle}{int which, hostHandle handle}
60Return a pointer to the interface symbol for which symbol->handle[which]
61equals \arg{handle}.  Return NULL if no such symbol exists.
62    \cfunction{void}{pceRegisterName}{int which, hostHandle handle,
63				      PceName name}
64Create an interface symbol for \arg{name} if this does not exist and
65assign \\ symbol->handle[\arg{which}] = \arg{handle};
66    \cfunction{void}{pceRegisterAssoc}{int which, hostHandle handle,
67				       PceObject obj}
68Assign symbol->handle[\arg{which}] = \arg{handle} in the interface
69symbol representing \arg{obj}.
70    \cfunction{PceITFSymbol}{getITFSymbolName}{PceName name}
71Return interface symbol for the given PCE \arg{name}.  If \arg{name} does
72not yet have an interface symbol \cfunc{getITFSymbolName()} creates one.
73\end{description}
74
75Section~\ref{sec:examples} illustrates how the interface table may be
76used.
77
78
79\subsection{Converting C Data types to PCE Objects}
80
81Data types and ``proper objects'' are exchanged and converted to their
82appropriate representation by using the conversion functions
83described.  below. The type `PceObject' is defined in the header file
84\file{xpce/src/itf-interface.h} and refers to an anonymous PCE datum.
85
86\begin{description}
87    \cfunction{PceObject}{cToPceName}{char * text}
88Return a PCE name-object for the given \arg{text}.  A PCE name-object
89is a unique representation of its associated text.  If the same name
90is needed several times in the interface the return-value of this
91function may be saved in a global variable for later usage.  \cfunc
92{cToPceName()} always succeeds.  If the name was not previously
93known to PCE this function may call \cfunc{malloc()} to allocate
94memory for the new name-object.  The contents of \arg{text} is
95copied to PCE's data area.
96
97Note that \cfunc{pceRegisterName()}/\cfunc{pceLookupHandle()} provide
98an alternative to map host-language textual constants on PCE names.
99See section~\ref{sec:examples}.
100
101    \cfunction{PceObject}{cToPceInteger}{long value}
102Convert a C-integer into a PCE integer.  PCE integers are signed
10331 bit values.  \arg{cToPceInteger()} always succeeds and never
104calls \cfunc{malloc()}.
105
106    \cfunction{PceObject}{cToPceReal}{double value}
107Convert a C-integer into a PCE real-object.  Real object are
108garbage-collected.  Calling this function twice with the same value
109will yield different instances of class real.  The function
110\cfunc{cToPceReal()} always succeed and might call \cfunc{malloc()}.
111
112    \cfunction{PceObject}{cToPceString}{char *assoc, char *text}
113Convert the C char~* \arg{text} into a PCE string object.
114When not NULL, \arg{assoc} will be the named reference given to the
115object.  See also \cfunc{cToPceAssoc()}, \cfunc{pceNew()}.
116The function \cfunc{cToPceString()} always succeed and might call
117\cfunc{malloc()}.  The example below creates a string with
118<-text ``Hello World!'' and reference @s:
119\begin{code}
120cToPceString("s", "Hello World!");
121\end{code}
122\end{description}
123
124The Lisp interface defines a PCE class \class{lisp_string} for
125representing Lisp strings in PCE.  The PCE interface defines the
126following functions to initialise such user-defined representation
127of a string.
128
129\begin{description}
130    \cfunction{PceObject}{cToPceTmpCharArray}{char *text}
131Return a reference to a temporary instance of class \class{char_array}.
132The `char_array <-text' field is filled with \arg{text}.  Unlike the
133\cfunc{cToPceName()} and \cfunc{cToPceString()} however, the contents
134of \arg{text} is {\em not} copied.  The returned object should therefore
135{\em not} be modified in PCE.
136
137The PCE interface defines a pool of 10 char_array objects used for
138this purpose.  After finishing with the temporary object it should
139be freed using \cfunc{donePceTmpCharArray()}.
140    \cfunction{void}{donePceTmpCharArray}{PceObject}
141Prepare the argument \class{char_array} object for reuse.  The argument
142{\em must} be created using \cfunc{cToPceTmpCharArray()}.
143\end{description}
144
145
146The host language needs to define how a reference to a PCE object is
147represented.  For Prolog as the host language it is usual to represent
148object references as @Atom or @Integer.  See also \cite{PCE:Prolog}
149and \cite{PCE:Lisp}.  The following calls may be used to convert a
150reference in the host-language representation into a PCE object.
151
152\begin{description}
153    \cfunction{PceObject}{cToPceAssoc}{char * assoc}
154Return the PCE object with the given name association.  If no such
155object is available it returns NULL.  This call might perform
156\cfunc{malloc()} and might call-back the host-language from the
157PCE exception mechanism for undefined assocs.  See `@pce
158<-exception_handlers'.
159    \cfunction{PceObject}{cToPceReference}{unsigned long reference}
160Return PCE object from an integer reference.  Returns NULL if the
161given reference is not defined.  This function {\em never} performs
162\cfunc{malloc()}.  Note that the detection of invalid integer
163references is heuristic: PCE might return an invalid object
164from an invalid integer reference.
165\end{description}
166
167Section~\ref{sec:examples} contains typical calling sequences and
168examples of how to use the cToPce... functions.
169
170\subsection{Converting PCE Objects to C Data types}
171
172Conversions from PCE data types to C data-types are performed by
173\cfunc{pceToC()}. The declaration is:
174
175\begin{code}
176int
177pceToC(obj, value)
178    PceObject obj;
179    PceCValue *value;
180\end{code}
181
182where \arg{PceCValue} is a union of the possible C-return-values:
183
184\begin{code}
185typedef union
186{ char		character;
187  long		integer;
188  float 	real;
189  char *	string;
190  PceITFSymbol	itf_symbol;
191} PceCValue;
192\end{code}
193
194The first argument of \cfunc{pceToC()} is an object obtained from one
195of the principal interface functions.  \cfunc{pceToC()} stores the C
196representation in the second argument.  The return value indicates
197the actual type of the \arg{CValue} as shown in table~\ref{tab:pceToC}.
198
199
200\begin{table}
201\begin{center}
202\begin{tabular}{|l|l|}
203\hline
204{\sl type}		& {\sl PceCValue union field}	\\
205\hline
206{\tt PCE_INTEGER}       & {\tt integer}			\\
207{\tt PCE_REAL}          & {\tt real}			\\
208{\tt PCE_NAME}          & {\tt itf_symbol}		\\
209{\tt PCE_ASSOC}         & {\tt itf_symbol}		\\
210{\tt PCE_REFERENCE}     & {\tt integer}			\\
211\hline
212\end{tabular}
213\end{center}
214	\caption{pceToC() return values and corresponding type}
215	\label{tab:pceToC}
216\end{table}
217
218
219
220The PCE interface defines two additional C-functions to convert
221text from PCE to C:
222
223\begin{description}
224    \cfunction{char *}{pceStringToC}{PceObject datum}
225If the argument is an instance of the PCE class \class{string}, return
226a char * representing the value of the string.  Otherwise return
227\const{NULL}.
228    \cfunction{char *}{pceCharArrayToC}{PceObject datum}
229If the argument is an instance of the PCE class \class{char_array}, return
230a char * representing the value of the string.  Otherwise return
231\const{NULL}.
232\end{description}
233
234For both functions, the returned char~* is a pointer into PCE's data-area.
235The contents of the character array may not be changed and the data should
236be copied if it needs to be retained.
237
238
239\subsection{Testing existence of objects}
240
241Whether or not an object exists may be tested using the functions
242defined below.  These calls are used by the Prolog predicate object/1
243and the Lisp function \lfunc{pce-object-p}
244
245\begin{description}
246    \cfunction{int}{pceExistsAssoc}{char *assoc}
247Returns non-zero iff \arg{assoc} is the name of an existing object.  This
248test is different from
249\begin{code}
250if ( cToPceAssoc(assoc) ) ...
251\end{code}
252as \cfunc{cToPceAssoc()} will raise an exception if the object does not
253exists, while this \cfunc{pceExistsAssoc()} simply fails in this case.
254See also `@pce <-exception_handlers'.
255    \cfunction{int}{pceExistsReference}{unsigned long reference}
256Returns non-zero iff \arg{reference} is a valid integer reference.  This
257call is equivalent to testing \cfunc{cToPceReference()} and only exists
258for symetry with \cfunc{pceExistsAssoc()}.
259\end{description}
260
261
262\subsection{Type testing}
263
264\begin{description}
265    \cfunction{int}{pceInstanceOf}{PceObject obj, PceObject class}
266Test if \arg{obj} is an instance of class \arg{class} or a subclass
267thereof.  Returns \const{PCE_SUCCEED} or \const{PCE_FAIL}.
268\end{description}
269