1 /******************************** -*- C -*- ****************************
2  *
3  *	Symbol Table declarations
4  *
5  *
6  ***********************************************************************/
7 
8 /***********************************************************************
9  *
10  * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2003,2005,2006,2008
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 #ifndef GST_SYM_H
56 #define GST_SYM_H
57 
58 #define SYMBOL_TABLE_SIZE	512
59 
60 typedef enum
61 {
62   SCOPE_TEMPORARY,
63   SCOPE_RECEIVER,
64   SCOPE_GLOBAL,
65   SCOPE_SPECIAL
66 }
67 scope_type;
68 
69 typedef struct gst_symbol
70 {
71   OBJ_HEADER;			/* I love inheritance */
72   char symString[1];
73 }
74  *gst_symbol;
75 
76 typedef struct symbol_entry
77 {
78   scope_type scope;
79   OOP symbol;
80   mst_Boolean readOnly;
81   int varIndex;			/* index of receiver or temporary */
82   unsigned int scopeDistance;	/* how many frames up the stack is this
83 				   variable from where we are? */
84 }
85 symbol_entry;
86 
87 enum undeclared_strategy {
88   UNDECLARED_NONE,
89   UNDECLARED_GLOBALS,
90   UNDECLARED_TEMPORARIES,
91   UNDECLARED_CURRENT
92 };
93 
94 /* Set whether undeclared globals can be considered forward references,
95    or whether they should be considered like temporary variables.  */
96 extern int _gst_set_undeclared (enum undeclared_strategy value)
97   ATTRIBUTE_HIDDEN;
98 
99 /* Establish a new dictionary that will host local variables of the
100    evaluations; return the old one.  */
101 extern OOP _gst_push_temporaries_dictionary (void)
102   ATTRIBUTE_HIDDEN;
103 
104 /* Switch back to a previously used dictionary to host local variables of the
105    evaluations.  */
106 extern void _gst_pop_temporaries_dictionary (OOP dictionaryOOP)
107   ATTRIBUTE_HIDDEN;
108 
109 extern OOP _gst_and_symbol ATTRIBUTE_HIDDEN;
110 extern OOP _gst_as_scaled_decimal_radix_scale_symbol ATTRIBUTE_HIDDEN;
111 extern OOP _gst_bad_return_error_symbol ATTRIBUTE_HIDDEN;
112 extern OOP _gst_boolean_symbol ATTRIBUTE_HIDDEN;
113 extern OOP _gst_byte_array_out_symbol ATTRIBUTE_HIDDEN;
114 extern OOP _gst_byte_array_symbol ATTRIBUTE_HIDDEN;
115 extern OOP _gst_c_object_ptr_symbol ATTRIBUTE_HIDDEN;
116 extern OOP _gst_c_object_symbol ATTRIBUTE_HIDDEN;
117 extern OOP _gst_category_symbol ATTRIBUTE_HIDDEN;
118 extern OOP _gst_char_symbol ATTRIBUTE_HIDDEN;
119 extern OOP _gst_does_not_understand_symbol ATTRIBUTE_HIDDEN;
120 extern OOP _gst_double_symbol ATTRIBUTE_HIDDEN;
121 extern OOP _gst_false_symbol ATTRIBUTE_HIDDEN;
122 extern OOP _gst_float_symbol ATTRIBUTE_HIDDEN;
123 extern OOP _gst_if_false_if_true_symbol ATTRIBUTE_HIDDEN;
124 extern OOP _gst_if_false_symbol ATTRIBUTE_HIDDEN;
125 extern OOP _gst_if_true_if_false_symbol ATTRIBUTE_HIDDEN;
126 extern OOP _gst_if_true_symbol ATTRIBUTE_HIDDEN;
127 extern OOP _gst_int_symbol ATTRIBUTE_HIDDEN;
128 extern OOP _gst_long_double_symbol ATTRIBUTE_HIDDEN;
129 extern OOP _gst_long_symbol ATTRIBUTE_HIDDEN;
130 extern OOP _gst_must_be_boolean_symbol ATTRIBUTE_HIDDEN;
131 extern OOP _gst_nil_symbol ATTRIBUTE_HIDDEN;
132 extern OOP _gst_or_symbol ATTRIBUTE_HIDDEN;
133 extern OOP _gst_permission_symbol ATTRIBUTE_HIDDEN;
134 extern OOP _gst_primitive_symbol ATTRIBUTE_HIDDEN;
135 extern OOP _gst_repeat_symbol ATTRIBUTE_HIDDEN;
136 extern OOP _gst_self_smalltalk_symbol ATTRIBUTE_HIDDEN;
137 extern OOP _gst_self_symbol ATTRIBUTE_HIDDEN;
138 extern OOP _gst_short_symbol ATTRIBUTE_HIDDEN;
139 extern OOP _gst_ushort_symbol ATTRIBUTE_HIDDEN;
140 extern OOP _gst_smalltalk_symbol ATTRIBUTE_HIDDEN;
141 extern OOP _gst_smalltalk_namespace_symbol ATTRIBUTE_HIDDEN;
142 extern OOP _gst_start_execution_symbol ATTRIBUTE_HIDDEN;
143 extern OOP _gst_string_out_symbol ATTRIBUTE_HIDDEN;
144 extern OOP _gst_string_symbol ATTRIBUTE_HIDDEN;
145 extern OOP _gst_super_symbol ATTRIBUTE_HIDDEN;
146 extern OOP _gst_symbol_symbol ATTRIBUTE_HIDDEN;
147 extern OOP _gst_symbol_out_symbol ATTRIBUTE_HIDDEN;
148 extern OOP _gst_terminate_symbol ATTRIBUTE_HIDDEN;
149 extern OOP _gst_this_context_symbol ATTRIBUTE_HIDDEN;
150 extern OOP _gst_times_repeat_symbol ATTRIBUTE_HIDDEN;
151 extern OOP _gst_to_by_do_symbol ATTRIBUTE_HIDDEN;
152 extern OOP _gst_to_do_symbol ATTRIBUTE_HIDDEN;
153 extern OOP _gst_true_symbol ATTRIBUTE_HIDDEN;
154 extern OOP _gst_uchar_symbol ATTRIBUTE_HIDDEN;
155 extern OOP _gst_uint_symbol ATTRIBUTE_HIDDEN;
156 extern OOP _gst_ulong_symbol ATTRIBUTE_HIDDEN;
157 extern OOP _gst_undeclared_symbol ATTRIBUTE_HIDDEN;
158 extern OOP _gst_unknown_symbol ATTRIBUTE_HIDDEN;
159 extern OOP _gst_value_with_rec_with_args_symbol ATTRIBUTE_HIDDEN;
160 extern OOP _gst_variadic_smalltalk_symbol ATTRIBUTE_HIDDEN;
161 extern OOP _gst_variadic_symbol ATTRIBUTE_HIDDEN;
162 extern OOP _gst_vm_primitives_symbol ATTRIBUTE_HIDDEN;
163 extern OOP _gst_void_symbol ATTRIBUTE_HIDDEN;
164 extern OOP _gst_wchar_symbol ATTRIBUTE_HIDDEN;
165 extern OOP _gst_wstring_symbol ATTRIBUTE_HIDDEN;
166 extern OOP _gst_wstring_out_symbol ATTRIBUTE_HIDDEN;
167 extern OOP _gst_while_false_colon_symbol ATTRIBUTE_HIDDEN;
168 extern OOP _gst_while_false_symbol ATTRIBUTE_HIDDEN;
169 extern OOP _gst_while_true_colon_symbol ATTRIBUTE_HIDDEN;
170 extern OOP _gst_while_true_symbol ATTRIBUTE_HIDDEN;
171 extern OOP _gst_symbol_table ATTRIBUTE_HIDDEN;
172 extern OOP _gst_current_namespace ATTRIBUTE_HIDDEN;
173 
174 /* This returns the name of the given scope (instance variable, temporary, ...). */
175 extern const char *_gst_get_scope_kind (scope_type scope)
176   ATTRIBUTE_CONST
177   ATTRIBUTE_HIDDEN;
178 
179 /* This walks the list of scopes and of symbols defined for each scope,
180    looking for a variable represented by the tree LIST.  Then it looks in
181    the instance variables, then in the class variables, and then in the
182    pool dictionaries (starting from those declared in the class and going
183    up in the hierarchy).
184 
185    If the variable is not found anywhere but starts with an uppercase letter,
186    it is declared in the Undeclared dictionary and the methods will be fixed
187    automatically as soon as it is defined (if it is).
188 
189    True is returned, and SE is filled with the information about the
190    variable if it is found or it is deemed part of Undeclared.  Else,
191    SE is untouched and FALSE is returned.  */
192 extern mst_Boolean _gst_find_variable (symbol_entry * se,
193 				       tree_node list)
194   ATTRIBUTE_HIDDEN;
195 
196 /* This converts a C string to a symbol and stores it in the symbol
197    table.  */
198 extern OOP _gst_intern_string (const char *str)
199   ATTRIBUTE_HIDDEN;
200 
201 /* This makes an Array with an element for each instance variable
202    declared in VARIABLESTRING, plus those inherited from
203    SUPERCLASSOOP.  */
204 extern OOP _gst_make_instance_variable_array (OOP superclassOOP,
205 					      const char * variableString)
206   ATTRIBUTE_HIDDEN;
207 
208 /* This makes a BindingDictionary whose keys are the class variables
209    declared in VARIABLENAMES.  The environment of the dictionary is
210    classOOP.  */
211 extern OOP _gst_make_class_variable_dictionary (const char * variableNames,
212 						OOP classOOP)
213   ATTRIBUTE_HIDDEN;
214 
215 /* This makes an Array whose elements are the pool dictionaries
216    declared in POOLNAMES.  */
217 extern OOP _gst_make_pool_array (const char * poolNames)
218   ATTRIBUTE_HIDDEN;
219 
220 /* This resolves the variable binding constant expressed by the LIST parse
221    tree node.  Unless DECLARE_TEMPORARY is false, temporary variables
222    may be automatically declared.  */
223 extern tree_node _gst_find_variable_binding (tree_node list)
224   ATTRIBUTE_HIDDEN;
225 
226 /* This returns the dictionary in which to define an undeclared variable
227    binding.  */
228 extern OOP _gst_get_undeclared_dictionary ()
229   ATTRIBUTE_PURE
230   ATTRIBUTE_HIDDEN;
231 
232 /* This converts the Smalltalk String STRINGOOP into a Symbol and
233    return the converted Symbol.  */
234 extern OOP _gst_intern_string_oop (OOP stringOOP)
235   ATTRIBUTE_HIDDEN;
236 
237 /* This computes an hash of LEN bytes, starting at STR.  */
238 extern uintptr_t _gst_hash_string (const char *str,
239 				   int len)
240   ATTRIBUTE_PURE
241   ATTRIBUTE_HIDDEN;
242 
243 /* This computes the length of a String object OOP.  */
244 extern int _gst_string_oop_len (OOP oop)
245   ATTRIBUTE_PURE
246   ATTRIBUTE_HIDDEN;
247 
248 /* This returns the number of arguments declared in the current
249    scope.  */
250 extern int _gst_get_arg_count (void)
251   ATTRIBUTE_PURE
252   ATTRIBUTE_HIDDEN;
253 
254 /* This returns the number of temporaries declared in the current
255    scope.  */
256 extern int _gst_get_temp_count (void)
257   ATTRIBUTE_PURE
258   ATTRIBUTE_HIDDEN;
259 
260 /* This adds the arguments corresponding to the message declaration in
261    ARGS to the list of arguments in the current scope.  Note that this
262    handles unary, binary and keyword expressions.  Arguments must be
263    declared before temporaries, so this resets the number of
264    temporaries in the current scope to 0 and absorbs any temporaries
265    into the arguments.  The number of arguments is returned.  */
266 extern int _gst_declare_arguments (tree_node args)
267   ATTRIBUTE_HIDDEN;
268 
269 /* This adds the declarations in TEMPS to the list of arguments
270    in the current scope.  */
271 extern int _gst_declare_temporaries (tree_node temps)
272   ATTRIBUTE_HIDDEN;
273 
274 /* This adds the arguments corresponding to the message declaration in
275    ARGS to the list of arguments in the current scope.  Note that this
276    does not handle unary, binary and keyword expressions, but only
277    blocks.  Arguments must be declared before temporaries, so this
278    resets the number of temporaries in the current scope to 0 and
279    absorbs any temporaries into the arguments.  The number of
280    arguments is returned.  */
281 extern int _gst_declare_block_arguments (tree_node args)
282   ATTRIBUTE_HIDDEN;
283 
284 /* Declare the argument or temporary variable whose name is pointed to
285    by NAME as either WRITEABLE or not.  A Symbol corresponding to NAME
286    is created and links a new entry inside the symbol list for the
287    currently active scope.  Unless ALLOWDUP is true, search for a
288    variable with the same name in the currently active scope and return
289    -1 if one is found; otherwise, return the index of the variable into
290    the activation record.  */
291 extern int _gst_declare_name (const char *name,
292 			      mst_Boolean writeable,
293 			      mst_Boolean allowDup)
294   ATTRIBUTE_HIDDEN;
295 
296 /* Computes the number of arguments that a message named SYMBOLOOP
297    expects.  */
298 extern int _gst_selector_num_args (OOP symbolOOP)
299   ATTRIBUTE_PURE
300   ATTRIBUTE_HIDDEN;
301 
302 /* This removes from the current scope the knowledge of the last
303    declared temporary variable.  */
304 extern void _gst_undeclare_name (void)
305   ATTRIBUTE_HIDDEN;
306 
307 /* This adds a new scope (corresponding to a level of block nesting)
308    to the linked list of scopes.  */
309 extern void _gst_push_new_scope (void)
310   ATTRIBUTE_HIDDEN;
311 
312 /* Convert a lightweight class (instance of Behavior) or a Metaclass
313    into the corresponding Class object.  */
314 extern OOP _gst_get_class_object (OOP classOOP)
315   ATTRIBUTE_HIDDEN;
316 
317 /* Find a pragma handler for the given selector into the class and its
318    superclasses.  */
319 extern OOP _gst_find_pragma_handler (OOP classOOP, OOP symbolOOP)
320   ATTRIBUTE_HIDDEN;
321 
322 /* This removes the outermost scope (corresponding to a level of block
323    nesting) to the linked list of scopes.  */
324 extern void _gst_pop_old_scope (void)
325   ATTRIBUTE_HIDDEN;
326 
327 /* This frees the whole linked list of scopes.  */
328 extern void _gst_pop_all_scopes (void)
329   ATTRIBUTE_HIDDEN;
330 
331 /* For debugging purposes, this prints the declaration of ENT.  */
332 extern void _gst_print_symbol_entry (symbol_entry * ent)
333   ATTRIBUTE_HIDDEN;
334 
335 /* This routine is used for symbol table debugging only.  */
336 extern void _gst_print_symbols (void)
337   ATTRIBUTE_HIDDEN;
338 
339 /* This routine initializes the variables containing the Symbols
340    known to the VM.  This one creates the symbol OOPs, which have to
341    be consecutive in order to speed up the load.  */
342 extern void _gst_init_symbols_pass1 (void)
343   ATTRIBUTE_HIDDEN;
344 
345 /* This one creates the SymLink OOPs for the Symbols previously
346    created.  */
347 extern void _gst_init_symbols_pass2 (void)
348   ATTRIBUTE_HIDDEN;
349 
350 /* This routine reloads the variables containing the Symbols
351    known to the VM.  It is invocated upon image load.  */
352 extern void _gst_restore_symbols (void)
353   ATTRIBUTE_HIDDEN;
354 
355 
356 extern void _gst_check_symbol_chain (void)
357   ATTRIBUTE_HIDDEN;
358 
359 #ifdef HAVE_READLINE
360 extern void _gst_add_all_symbol_completions (void)
361   ATTRIBUTE_HIDDEN;
362 #endif
363 
364 struct builtin_selector {
365   int offset;
366   OOP symbol;
367   int numArgs;
368   int bytecode;
369 };
370 
371 extern struct builtin_selector _gst_builtin_selectors[256]
372   ATTRIBUTE_HIDDEN;
373 
374 extern struct builtin_selector *_gst_lookup_builtin_selector (const char *str,
375 							      unsigned int len)
376   ATTRIBUTE_HIDDEN;
377 
378 #endif /* GST_SYM_H */
379