1 /******************************** -*- C -*- ****************************
2  *
3  *	External definitions for C callin module
4  *
5  *
6  ***********************************************************************/
7 
8 /***********************************************************************
9  *
10  * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2006,2008,2009
11  * Free Software Foundation, Inc.
12  * Written by Steve Byrne.
13  *
14  * This file is part of GNU Smalltalk.
15  *
16  * GNU Smalltalk is free software; you can redistribute it and/or modify it
17  * under the terms of the GNU General Public License as published by the Free
18  * Software Foundation; either version 2, or (at your option) any later
19  * version.
20  *
21  * Linking GNU Smalltalk statically or dynamically with other modules is
22  * making a combined work based on GNU Smalltalk.  Thus, the terms and
23  * conditions of the GNU General Public License cover the whole
24  * combination.
25  *
26  * In addition, as a special exception, the Free Software Foundation
27  * give you permission to combine GNU Smalltalk with free software
28  * programs or libraries that are released under the GNU LGPL and with
29  * independent programs running under the GNU Smalltalk virtual machine.
30  *
31  * You may copy and distribute such a system following the terms of the
32  * GNU GPL for GNU Smalltalk and the licenses of the other code
33  * concerned, provided that you include the source code of that other
34  * code when and as the GNU GPL requires distribution of source code.
35  *
36  * Note that people who make modified versions of GNU Smalltalk are not
37  * obligated to grant this special exception for their modified
38  * versions; it is their choice whether to do so.  The GNU General
39  * Public License gives permission to release a modified version without
40  * this exception; this exception also makes it possible to release a
41  * modified version which carries forward this exception.
42  *
43  * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT
44  * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
45  * FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License for
46  * more details.
47  *
48  * You should have received a copy of the GNU General Public License along with
49  * GNU Smalltalk; see the file COPYING.  If not, write to the Free Software
50  * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA.
51  *
52  ***********************************************************************/
53 
54 
55 
56 #ifndef GST_CALLIN_H
57 #define GST_CALLIN_H
58 
59 
60 /* Sends SELECTOR (which should be a Symbol, otherwise _gst_nil_oop is
61    returned) to RECEIVER.  The message arguments pointed to by AP
62    should also be OOPs (otherwise, an access violation exception is
63    pretty likely) and are passed in a NULL-terminated list after the
64    selector.  The value returned from the method is passed back as an
65    OOP to the C program as the result of the function, or _gst_nil_oop
66    if the number of arguments is wrong.  */
67 extern OOP _gst_va_msg_send (OOP receiver,
68 			     OOP selector,
69 			     va_list ap)
70   ATTRIBUTE_HIDDEN;
71 
72 /* Sends SELECTOR (which should be a Symbol, otherwise _gst_nil_oop is
73    returned) to RECEIVER.  The message arguments should also be OOPs
74    (otherwise, an access violation exception is pretty likely) and are
75    passed in a NULL-terminated list after the selector.  The value
76    returned from the method is passed back as an OOP to the C program
77    as the result of the function, or _gst_nil_oop if the number of
78    arguments is wrong.  */
79 extern OOP _gst_msg_send (OOP receiver,
80 			  OOP selector, ...)
81   ATTRIBUTE_HIDDEN;
82 
83 /* Sends SELECTOR (which should be a Symbol, otherwise _gst_nil_oop is
84    returned) to RECEIVER.  The message arguments should also be OOPs
85    (otherwise, an access violation exception is pretty likely) and are
86    passed in a NULL-terminated list pointed to by ARGS.  The value
87    returned from the method is passed back as an OOP to the C program
88    as the result of the function, or _gst_nil_oop if the number of
89    arguments is wrong.  */
90 extern OOP _gst_vmsg_send (OOP receiver,
91 			   OOP selector,
92 			   OOP * args)
93   ATTRIBUTE_HIDDEN;
94 
95 /* Sends the SEL selector to RECEIVER.  The message arguments should
96    also be OOPs (otherwise, an access violation exception is pretty
97    likely) and are passed in a NULL-terminated list after the
98    selector.  The value returned from the method is passed back as an
99    OOP to the C program as the result of the function, or _gst_nil_oop
100    if the number of arguments is wrong.  */
101 extern OOP _gst_str_msg_send (OOP receiver, const char * sel, ...)
102   ATTRIBUTE_HIDDEN;
103 
104 /* See manual; basically it takes care of the conversion from C to
105    Smalltalk data types.  */
106 extern void _gst_va_msg_sendf (PTR resultPtr, const char * fmt, va_list ap)
107   ATTRIBUTE_HIDDEN;
108 
109 /* See manual; basically it takes care of the conversion from C to
110    Smalltalk data types.  */
111 extern void _gst_msg_sendf (PTR resultPtr, const char * fmt, ...)
112   ATTRIBUTE_HIDDEN;
113 
114 /* Evaluate the Smalltalk code in STR and return the result as an OOP.
115    STR is a Smalltalk method body which can have local variables, but
116    no parameters.  This is much like the immediate expression
117    evaluation that the command interpreter provides.  */
118 extern OOP _gst_eval_expr (const char *str)
119   ATTRIBUTE_HIDDEN;
120 
121 /* Evaluate the Smalltalk code in STR, a Smalltalk method body which
122    can have local variables, but no parameters.  This is much like the
123    immediate expression evaluation that the command interpreter
124    provides.  */
125 extern void _gst_eval_code (const char *str)
126   ATTRIBUTE_HIDDEN;
127 
128 /* Puts the given OOP in the registry.  If you register an object
129    multiple times, you will need to unregister it the same number of
130    times.  You may want to register objects returned by Smalltalk
131    call-ins.  */
132 extern OOP _gst_register_oop (OOP oop)
133   ATTRIBUTE_HIDDEN;
134 
135 /* Removes an occurrence of the given OOP from the registry.  */
136 extern void _gst_unregister_oop (OOP oop)
137   ATTRIBUTE_HIDDEN;
138 
139 /* Remember that an array of OOPs must be made part of the root set.
140    The two parameters, FIRST and LAST, point to two variables
141    containing respectively the base and the top of the array: the
142    double indirection allows one to move the array freely in memory,
143    for example using realloc.  */
144 extern void _gst_register_oop_array (OOP **first, OOP **last)
145   ATTRIBUTE_HIDDEN;
146 
147 /* Unregister the given array of OOPs from the root set.  FIRST points
148    to a variables containing the base of the array: the double
149    indirection allows one to move the array freely in memory, for
150    example using realloc.  */
151 extern void _gst_unregister_oop_array (OOP **first)
152   ATTRIBUTE_HIDDEN;
153 
154 /* Allocates an OOP for a newly created instance of the class whose
155    OOP is passed as the first parameter; if that parameter is not a
156    class the results are undefined (for now, read as ``the program
157    will most likely core dump'', but that could change in a future
158    version).
159 
160    The second parameter is used only if the class is an indexable one,
161    otherwise it is discarded: it contains the number of indexed
162    instance variables in the object that is going to be created.  */
163 extern OOP _gst_object_alloc (OOP class_oop,
164 			      int size)
165   ATTRIBUTE_HIDDEN;
166 
167 /* Returns the number of indexed instance variables in OOP */
168 extern int _gst_basic_size (OOP oop)
169   ATTRIBUTE_HIDDEN;
170 
171 /* Convert C datatypes to Smalltalk types */
172 extern OOP _gst_id_to_oop (long i)
173   ATTRIBUTE_HIDDEN;
174 extern OOP _gst_int_to_oop (long i)
175   ATTRIBUTE_HIDDEN;
176 extern OOP _gst_uint_to_oop (unsigned long i)
177   ATTRIBUTE_HIDDEN;
178 extern OOP _gst_float_to_oop (double f)
179   ATTRIBUTE_HIDDEN;
180 extern OOP _gst_bool_to_oop (int b)
181   ATTRIBUTE_HIDDEN;
182 extern OOP _gst_char_to_oop (char c)
183   ATTRIBUTE_HIDDEN;
184 extern OOP _gst_wchar_to_oop (wchar_t c)
185   ATTRIBUTE_HIDDEN;
186 extern OOP _gst_class_name_to_oop (const char *name)
187   ATTRIBUTE_HIDDEN;
188 extern OOP _gst_string_to_oop (const char *str)
189   ATTRIBUTE_HIDDEN;
190 extern OOP _gst_wstring_to_oop (const wchar_t *str)
191   ATTRIBUTE_HIDDEN;
192 extern OOP _gst_byte_array_to_oop (const char *str,
193 				   int n)
194   ATTRIBUTE_HIDDEN;
195 extern OOP _gst_symbol_to_oop (const char *str)
196   ATTRIBUTE_HIDDEN;
197 extern OOP _gst_c_object_to_oop (PTR co)
198   ATTRIBUTE_HIDDEN;
199 extern OOP _gst_type_name_to_oop (const char *name)
200   ATTRIBUTE_HIDDEN;
201 extern void _gst_set_c_object (OOP oop, PTR co)
202   ATTRIBUTE_HIDDEN;
203 extern OOP _gst_long_double_to_oop (long double f)
204   ATTRIBUTE_HIDDEN;
205 
206 /* Convert Smalltalk datatypes to C data types */
207 extern long _gst_oop_to_c (OOP oop)
208   ATTRIBUTE_HIDDEN;	/* sometimes answers a PTR */
209 extern long _gst_oop_to_id (OOP oop)
210   ATTRIBUTE_HIDDEN;
211 extern long _gst_oop_to_int (OOP oop)
212   ATTRIBUTE_HIDDEN;
213 extern double _gst_oop_to_float (OOP oop)
214   ATTRIBUTE_HIDDEN;
215 extern int _gst_oop_to_bool (OOP oop)
216   ATTRIBUTE_HIDDEN;
217 extern char _gst_oop_to_char (OOP oop)
218   ATTRIBUTE_HIDDEN;
219 extern wchar_t _gst_oop_to_wchar (OOP oop)
220   ATTRIBUTE_HIDDEN;
221 extern char *_gst_oop_to_string (OOP oop)
222   ATTRIBUTE_HIDDEN;
223 extern wchar_t *_gst_oop_to_wstring (OOP oop)
224   ATTRIBUTE_HIDDEN;
225 extern char *_gst_oop_to_byte_array (OOP oop)
226   ATTRIBUTE_HIDDEN;
227 extern PTR _gst_oop_to_c_object (OOP oop)
228   ATTRIBUTE_HIDDEN;
229 extern long double _gst_oop_to_long_double (OOP oop)
230   ATTRIBUTE_HIDDEN;
231 extern OOP _gst_get_object_class (OOP oop)
232   ATTRIBUTE_HIDDEN;
233 extern OOP _gst_get_superclass (OOP oop)
234   ATTRIBUTE_HIDDEN;
235 extern mst_Boolean _gst_class_is_kind_of (OOP candidate, OOP superclass)
236   ATTRIBUTE_HIDDEN;
237 extern mst_Boolean _gst_object_is_kind_of (OOP candidate, OOP superclass)
238   ATTRIBUTE_HIDDEN;
239 extern OOP _gst_perform (OOP receiver, OOP selector)
240   ATTRIBUTE_HIDDEN;
241 extern OOP _gst_perform_with (OOP receiver, OOP selector, OOP arg)
242   ATTRIBUTE_HIDDEN;
243 extern mst_Boolean _gst_class_implements_selector (OOP classOOP, OOP selector)
244   ATTRIBUTE_HIDDEN;
245 extern mst_Boolean _gst_class_can_understand (OOP classOOP, OOP selector)
246   ATTRIBUTE_HIDDEN;
247 extern mst_Boolean _gst_responds_to (OOP oop, OOP selector)
248   ATTRIBUTE_HIDDEN;
249 extern size_t _gst_oop_size (OOP oop)
250   ATTRIBUTE_HIDDEN;
251 extern OOP _gst_oop_at (OOP oop, size_t index)
252   ATTRIBUTE_HIDDEN;
253 extern OOP _gst_oop_at_put (OOP oop, size_t index, OOP new)
254   ATTRIBUTE_HIDDEN;
255 extern void *_gst_oop_indexed_base (OOP oop)
256   ATTRIBUTE_HIDDEN;
257 extern enum gst_indexed_kind _gst_oop_indexed_kind (OOP oop)
258   ATTRIBUTE_HIDDEN;
259 
260 
261 /* Marks/copies the registered OOPs (they are part of the rootset by
262    definition) */
263 extern void _gst_mark_registered_oops (void)
264   ATTRIBUTE_HIDDEN;
265 extern void _gst_copy_registered_oops (void)
266   ATTRIBUTE_HIDDEN;
267 
268 /* Initializes the registry of OOPs which some C code is holding.  */
269 extern void _gst_init_oopregistry (void)
270   ATTRIBUTE_HIDDEN;
271 
272 /* Returns a copy of the VMProxy.  */
273 extern struct VMProxy *_gst_get_vmproxy (void)
274   ATTRIBUTE_HIDDEN;
275 
276 /* Initialize the VMProxy.  */
277 extern void _gst_init_vmproxy (void)
278   ATTRIBUTE_HIDDEN;
279 
280 #endif /* GST_CALLIN_H */
281