12013-01-17  Gwenael Casaccio  <gwenael.casaccio@gmail.com>
2
3	* libgst/sysdep/win32/timer.c: Correct the function signature.
4
52012-12-29  Paolo Bonzini  <bonzini@gnu.org>
6
7	* libgst/oop.h: MAX_OOP_TABLE_SIZE is expressed in OOPs, not bytes.
8	Reported by Holger Freyther.
9
102012-12-29  Holger Hans Peter Freyther  <holger@freyther.de>
11
12	* libgst/alloc.c: _gst_heap_sbrk returns NULL and not MMAP_FAILED
13	on allocation failure.
14	* libgst/heap.c: Return NULL on allocation failure.
15
162012-09-09  Paolo Bonzini  <bonzini@gnu.org>
17
18	* libgst/sysdep/posix/events.c: Register the fd with gst
19	before polling.
20
212012-07-15  Paolo Bonzini  <bonzini@gnu.org>
22
23	* libgst/opt.c: Fix error in compute_jump_length that could lead
24	to verification errors after optimization.
25
262012-06-15  Thomas Girard  <thomas.g.girard@free.fr>
27
28	* libgst/dict.inl: Add IS_C_LONGLONG and IS_C_ULONGLONG macros.
29	* libgst/cint.c: Add missing long long and unsigned long long types
30	to _gst_c_type_size.  Use new macros.
31	* libgst/prims.def: Use IS_C_ULONG in VMpr_CObject_atPut.
32	Use new macros.
33
342012-06-04  Thomas Girard  <thomas.g.girard@free.fr>
35
36	* libgst/dict.inl: Add FROM_C_LONGLONG and FROM_C_ULONGLONG macros.
37	* libgst/cint.c: Add missing mappings from (unsigned) long long.
38
392012-05-19  Paolo Bonzini  <bonzini@gnu.org>
40
41	* libgst/prims.def: Another fix for the new primitive.
42
432012-05-19  Paolo Bonzini  <bonzini@gnu.org>
44
45	* libgst/prims.def: Fix class test for new primitive.
46
472012-05-19  Paolo Bonzini  <bonzini@gnu.org>
48
49	* libgst/events.h: Adjust prototype for _gst_async_timed_wait.
50	* libgst/prims.def: Switch VMpr_Processor_signalAtMillisecondClockValue
51	to nanosecond precision, adjust call to _gst_async_timed_wait.
52	* libgst/sysdep.h: Adjust prototype for _gst_sigalrm_at.
53	* libgst/sysdep/cygwin/timer.c: Switch _gst_sigalrm_at to nanosecond
54	precision.
55	* libgst/sysdep/posix/timer.c: Switch _gst_sigalrm_at to nanosecond
56	precision.
57	* libgst/sysdep/win32/events.c: Switch _gst_async_timed_wait to nanosecond
58	precision.
59
602012-05-19  Paolo Bonzini  <bonzini@gnu.org>
61
62	* libgst/events.h: Adjust prototype for _gst_async_timed_wait.
63	* libgst/interp.c: Use _gst_sigvtalrm_every.
64	* libgst/prims.def: Pass absolute time to _gst_async_timed_wait.
65	* libgst/sysdep.h: Remove _gst_signal_after, add _gst_sigvtalrm_every
66	and _gst_sigalrm_at.
67	* libgst/sysdep/cygwin/timer.c: Remove _gst_signal_after, add
68	_gst_sigvtalrm_every and _gst_sigalrm_at.
69	* libgst/sysdep/posix/events.c: Use _gst_sigalrm_at.
70	* libgst/sysdep/posix/timer.c: Remove _gst_signal_after, add
71	_gst_sigvtalrm_every and _gst_sigalrm_at.
72	* libgst/sysdep/win32/events.c: Get absolute time in
73	_gst_async_timed_wait.
74	* libgst/sysdep/win32/timer.c: Do not abort on _gst_sigvtalrm_every,
75	just do nothing.
76
772012-05-19  Paolo Bonzini  <bonzini@gnu.org>
78
79	* libgst/prims.def: Support the new primitive
80	VMpr_Processor_signalAtMillisecondClockValue.
81
822012-05-19  Paolo Bonzini  <bonzini@gnu.org>
83
84	* libgst/prims.def: Add VMpr_Time_nanosecondClock.
85	* libgst/sysdep.h: Add _gst_get_ns_time.
86	* libgst/sysdep/common/time.c: Add _gst_get_milli_time.
87	* libgst/sysdep/posix/time.c: Change _gst_get_milli_time to
88	_gst_get_ns_time.
89	* libgst/sysdep/win32/time.c: Likewise.
90
912012-03-30  Paolo Bonzini  <bonzini@gnu.org>
92
93	* libgst/oop.h: Remove _gst_compact and _gst_alloc_old_obj.
94	* libgst/oop.c: Make them static.
95
962012-03-30  Gwenael Casaccio  <mrgwen@gmail.com>
97
98	* libgst/alloc.c: Allocate heaps with xcalloc.
99	* libgst/oop.c: Let oldspace_before_freeing remove grey pages
100	when compacting.
101
1022012-03-29  Paolo Bonzini  <bonzini@gnu.org>
103
104	* libgst/gst-parse.c: Do not call _gst_free_tree in the presence
105	of lookahead, or add assertions that we can do so.  Reported by
106	Gwenael Casaccio.
107
1082012-03-29  Paolo Bonzini  <bonzini@gnu.org>
109
110	* libgst/lex.c: Report location of EOF token.
111
1122012-03-23  Paolo Bonzini  <bonzini@gnu.org>
113
114	* libgst/oop.c: Fix weak objects thinko in Gwen's patch.
115
1162012-03-14  Paolo Bonzini  <bonzini@gnu.org>
117
118	* libgst/oop.c: Return fixedspace from oldspace_nomemory when
119	appropriate.
120
1212012-02-22  Gwenael Casaccio  <mrgwen@gmail.com>
122
123	* libgst/oop.c: Fix weak objects with pointer and byte parts.
124
1252012-03-01  Paolo Bonzini  <bonzini@gnu.org>
126
127	* libgst/oop.c: Remove premature optimization.
128
1292012-02-22  Paolo Bonzini  <bonzini@gnu.org>
130
131	* libgst/gstpriv.h: Include crt_externs.h if present.
132
1332012-02-22  Gwenael Casaccio  <mrgwen@gmail.com>
134
135	* libgst/opt.c: Account for two line number bytecodes.
136
1372011-02-02  Paolo Bonzini  <bonzini@gnu.org>
138
139	* libgst/sysdep/posix/events.c: Fix signal handling race.
140	Reported by Derek Zhou.
141
1422012-02-02  Gwenael Casaccio  <mrgwen@gmail.com>
143            Paolo Bonzini  <pbonzini@redhat.com>
144
145	* libgst/interp.c: Use remove_process_from_list consistently.
146
1472011-12-14  Paolo Bonzini  <pbonzini@redhat.com>
148
149	* libgst/gst-parse.c: Only increase lookahead by one token at
150	a time, so that we do not lookahead past EOF.
151
1522011-11-14  Mehul Sanghvi  <mehul.sanghvi@gmail.com>
153
154	* libgst/cint.c: Add get_environ and pass it to Smalltalk.
155
1562011-09-26  Tony Garnock-Jones  <tonygarnockjones@gmail.com>
157
158	* libgst/cint.c: Try .dylib as a last resort on Mac OS X.
159
1602011-09-22  Paolo Bonzini  <bonzini@gnu.org>
161
162	* libgst/save.c: Close file descriptors upon image save.
163
1642011-09-22  Paolo Bonzini  <bonzini@gnu.org>
165
166	* libgst/dict.c: Add the ClockOnImageSave class variable to time.
167
1682011-08-13  Paolo Bonzini  <bonzini@gnu.org>
169
170	* libgst/prims.def: Atomically nil the file descriptor field
171	when closing a FileDescriptor or socket.
172
1732011-08-13  Paolo Bonzini  <bonzini@gnu.org>
174
175	* libgst/prims.def: Wrap #snapshot in push_jmp_buf/pop_jmp_buf,
176	since it will do call-ins via _gst_invoke_hook.  Suggested by
177	Gwenael Casaccio.
178
1792011-08-05  Holger Freyther  <holger@freyther.de>
180
181	* libgst/byte.h: Make smatch happy and add
182	parameters to the function.
183
1842011-08-01  Mathieu Suen  <mathieusuen@yahoo.fr>
185
186	* libgst/cint.c: Add long long support for calls.
187	* libgst/cint.h: Add CDATA_LONGLONG and CDATA_ULONGLONG.
188	* libgst/dict.c: Pass CLongLongAlignment to Smalltalk.
189	* libgst/prims.def: Add long long support for memory access.
190
1912011-07-27  Gwenael Casaccio  <mrgwen@gmail.com>
192            Paolo Bonzini  <bonzini@gnu.org>
193
194	* libgst/oop.c: Use mark stack.
195	* libgst/oop.h: Define mark stack data structures.
196
1972011-07-27  Paolo Bonzini  <bonzini@gnu.org>
198
199	* libgst/oop.c: Clean up reset_incremental_gc.
200	* libgst/oop.h: Remove first_allocated_oop.
201
2022011-07-27  Paolo Bonzini  <bonzini@gnu.org>
203
204	* libgst/oop.c: Do not sweep below _gst_mem.last_swept_oop
205	when initializing the incremental GC.
206
2072011-07-23  Paolo Bonzini  <bonzini@gnu.org>
208
209	* libgst/sym.c: Remove _gst_symbol_as_string.  Suggested by
210	Gwenael Casaccio.
211	* libgst/sym.h: Likewise.
212
2132011-07-04  Paolo Bonzini  <bonzini@gnu.org>
214            Gwenael Casaccio  <mrgwen@gmail.com>
215
216	* libgst/prims.def: Handle fixed instance variables in
217	VMpr_ArrayedCollection_replaceFromToWithStartingAt, keeping
218	existing failure conditions when the receiver has no fixed
219	instance variables.
220
2212011-07-04  Paolo Bonzini  <bonzini@gnu.org>
222
223	* libgst/events.c: Change _gst_sem_int_vec to async_queue_entry.
224	Adjust uses.  Enqueue it with _gst_async_call_internal.
225	* libgst/events.h: Change declaration.
226	* libgst/gstpriv.h: Remove dummy __sync_synchronize.  Add __sync_swap
227	and barrier().  Include events.h later.
228	* libgst/interp-bc.inl: Use empty_async_queue.
229	* libgst/interp-jit.inl: Likewise.
230	* libgst/interp.c: Remove async_queue_entry.  Change async signal
231	vectors to lists.  Export do_async_signal and add the new function
232	_gst_do_async_signal_and_unregister.  Add gst_async_call_internal.
233	Remove async-signal safe stuff from _gst_async_call, and always
234	allocate an async_queue_entry; use a lockless stack (which is
235	also async-signal-safe, so the same algorithms can be used in both
236	cases).  Rewrite _gst_have_pending_async_calls and add
237	empty_async_queue.  Adjust copying and marking of the lists.
238	* libgst/interp.h: Put async_queue_entry here, adding a next pointer.
239	Add declarations for the new functions.
240	* libgst/oop.c: Use _gst_async_call_internal.
241	* libgst/prims.def: Set exception flag when reenabling interrupts.
242	* libgst/sysdep.c: Include pthread header.
243	* libgst/cygwin/timer.c: Add void argument list.
244	* libgst/posix/events.c: Add no_opt to fix removed volatile qualifier.
245	Adjust access to _gst_sem_int_vec.  Enqueue the file polling call with
246	_gst_async_call_internal.
247
2482011-06-07  Paolo Bonzini  <bonzini@gnu.org>
249
250	* libgst/callin.c: Fix type of _gst_uint_to_oop argument.
251	* libgst/callin.h: Fix type of _gst_uint_to_oop argument.
252	* libgst/gstpub.c: Fix type of gst_uint_to_oop argument.
253	* libgst/gstpub.h: Fix type of gst_uint_to_oop argument.
254
2552011-05-26  Gwenael Casaccio  <mrgwen@gmail.com>
256
257	* libgst/dict.c: Fix superclass of MethodDictionary.
258
2592011-05-19  Paolo Bonzini  <bonzini@gnu.org>
260
261	* libgst/dict.inl: Fix conversion to/from 64-bit values on 32-bit
262	platforms.  Reported by Holger Hans Peter Freyther.
263	* libgst/prims.def: Ensure conversion between epochs is done with
264	64-bit math.
265
2662011-05-19  Paolo Bonzini  <bonzini@gnu.org>
267
268	* libgst/prims.def: Fix conversion between Smalltalk and Unix epoch.
269
2702011-05-19  Paolo Bonzini  <bonzini@gnu.org>
271
272	* libgst/prims.def: Implement one-argument VMpr_Time_timezoneBias.
273
2742011-05-18  Mathieu Suen  <mathieusuen@yahoo.fr>
275
276	* libgst/gst-parse.c: Allow creating unary pragmas.
277
2782011-05-18  Paolo Bonzini  <bonzini@gnu.org>
279
280	* libgst/gst-parse.c: Move creation of ATTRIBUTE_LIST contents here...
281	* libgst/tree.c: ... from here.
282	* libgst/tree.h: Adjust documentation.
283
2842011-04-29  Paolo Bonzini  <bonzini@gnu.org>
285
286	* libgst/callin.c: Use FROM_C_INT and FROM_C_LONG properly.
287	Add _gst_uint_to_oop.
288	* libgst/callin.h: Declare _gst_uint_to_oop.
289	* libgst/gstpub.c: Add _gst_uint_to_oop to proxy, add gst_uint_to_oop.
290	* libgst/gstpub.h: Add matching declarations.
291
2922011-04-29  Paolo Bonzini  <bonzini@gnu.org>
293
294	* libgst/sym.c: Fix argument count of selectors starting with _.
295	Reported by Mathieu Suen.
296
2972011-04-10  Holger Hans Peter Freyther  <holger@freyther.de>
298
299	* libgst/cint.c: Free #string, #byteArray, #symbol, #wstring
300	converted arguments.
301
3022011-03-28  Holger Hans Peter Freyther  <holger@freyther.de>
303
304	* libgst/prims.def: Set errno for VMpr_FileDescriptor_socketOp.
305
3062011-03-25  Paolo Bonzini  <bonzini@gnu.org>
307
308	* libgst/prims.def: Fix crashes with unexpected integer arguments.
309
3102011-03-24  Paolo Bonzini  <bonzini@gnu.org>
311
312	* libgst/interp.inl: Fix brokenness on non-x86 platforms.
313
3142011-03-12  Paolo Bonzini  <bonzini@gnu.org>
315
316	* libgst/callin.c: Remove dead code signaled by clang analyzer.
317	* libgst/cint.c: Likewise.
318	* libgst/comp.c: Likewise, and add missing INC_RESTORE_POINTER.
319	* libgst/dict.c: Likewise.
320	* libgst/interp.c: Likewise.
321	* libgst/mpz.c: Likewise.
322	* libgst/oop.c: Likewise.
323	* libgst/opt.c: Likewise.
324	* libgst/re.c: Likewise.
325
3262011-03-08  Paolo Bonzini  <bonzini@gnu.org>
327
328	* libgst/opt.c: Add missing verification rule.
329
3302011-02-28  Paolo Bonzini  <bonzini@gnu.org>
331
332	* libgst/dict.inl: Fix creation of FloatQ's on non-x86 platforms.
333
3342011-02-24  Paolo Bonzini  <bonzini@gnu.org>
335
336	* libgst/interp.c: Fix GC bug reported by Gwenael Casaccio.
337
3382011-02-14  Holger Hans Peter Freyther  <holger@freyther.de>
339
340	* libgst/interp.c: Always inline unwind_context.
341
3422011-02-11  Paolo Bonzini <bonzini@gnu.org>
343
344	* libgst/cint.c: Fix previous patch.  Add printf for coverage
345	of variadic functions.
346
3472011-02-04  Holger Hans Peter Freyther  <holger@freyther.de>
348
349	* libgst/cint.c: Propagate type conversion failures.
350
3512011-02-04  Holger Hans Peter Freyther  <holger@freyther.de>
352
353	* libgst/sockets.c: Add size check for the socket addr.
354
3552011-01-27  Paolo Bonzini <bonzini@gnu.org>
356
357	* libgst/gstpriv.h: Return boolean values from IS_OOP_*.
358	* libgst/oop.inl: Likewise.
359
3602011-01-14  Paolo Bonzini <bonzini@gnu.org>
361
362	* libgst/cint.c: Accept UndefinedObject for #cObjectPtr.
363
3642011-01-10  Paolo Bonzini <bonzini@gnu.org>
365
366	* libgst/files.c: Load Autoload.st last.
367
3682011-01-10  Paolo Bonzini  <bonzini@gnu.org>
369	    Mathiue Suen  <mathieusuen@yahoo.fr>
370
371	* libgst/dict.inl: Fix 32-bit #int and 64-bit #uint limits.
372
3732010-12-05  Paolo Bonzini  <bonzini@gnu.org>
374
375	* lib-src/sockets.c: Use O_NONBLOCK from socketx.h.
376
3772010-12-04  Paolo Bonzini <bonzini@gnu.org>
378
379	* libgst/dict.inl: Avoid crash on #changeClassTo: and UnicodeString.
380
3812010-11-10  Paolo Bonzini <bonzini@gnu.org>
382
383	* libgst/heap.c: Detect out-of-memory.
384
3852010-11-10  Paolo Bonzini <bonzini@gnu.org>
386
387	* libgst/interp.c: Change the stack top to nil in _gst_sync_wait
388	and put the semaphore back in _gst_sync_signal.  This allows
389	Smalltalk code to distinguish interruptions from successful waits.
390
3912010-11-08  Paolo Bonzini <bonzini@gnu.org>
392
393	* libgst/memzero.h: Remove.
394	* libgst/dict.c: Replace memzero with memset.
395	* libgst/dict.inl: Replace memzero with memset.
396	* libgst/gstpriv.h: Replace memzero with memset.
397	* libgst/heap.c: Replace memzero with memset.
398	* libgst/lex.c: Replace memzero with memset.
399	* libgst/mpz.c: Replace memzero with memset.
400	* libgst/opt.c: Replace memzero with memset.
401	* libgst/prims.def: Replace memzero with memset.
402	* libgst/save.c: Replace memzero with memset.
403	* libgst/xlat.c: Replace memzero with memset.
404
4052010-11-08  Paolo Bonzini <bonzini@gnu.org>
406
407	* libgst/interp.c: Streamline unwind_context even more.  The compiler
408	can do enough optimization that we can use the free_lifo_context
409	global directly.  Also, _gst_nil_oop is kept in a register so
410	icache-wise it pays to always do the store into parentContext.
411
4122010-11-08  Paolo Bonzini <bonzini@gnu.org>
413
414	* libgst/dict.inl: Add instantiate_numbytes, use it for instantiate
415	and non-pointer instantiate_with; do not unroll nil initialization
416	since N is usually small here.  Rewrite nil_fill.
417	* libgst/interp.c: Unroll the first few itertaions of prepare_context.
418	Do not use nil_fill.
419	* libgst/md-config.h: Remove loop unrolling macros.
420
4212010-11-02  Paolo Bonzini <bonzini@gnu.org>
422
423	* libgst/md-config.h: Tune for x86-64.
424
4252010-11-02  Paolo Bonzini <bonzini@gnu.org>
426
427	* libgst/interp.inl: Add optimized x86 versions of tagged arithmetic
428	operations.
429
4302010-11-02  Paolo Bonzini <bonzini@gnu.org>
431
432	* libgst/interp.inl: Add here functions for SmallInteger OOP arithmetic.
433	* libgst/prims.def: Use the new functions.
434	* libgst/vm.def: Use the new functions.
435
4362010-11-02  Paolo Bonzini <bonzini@gnu.org>
437
438	* libgst/comp.c: Reorder printing of statistics so that the results
439	are not influenced by printing the result and by the #afterEval
440	hooks.
441
4422010-10-31 Paolo Bonzini <bonzini@gnu.org>
443
444	* libgst/sysdep/posix/events.c: Remove pthread_in_use.
445
4462010-10-30 Paolo Bonzini <bonzini@gnu.org>
447
448	* libgst/sysdep/posix/events.c: Include pthread.h if using pthreads.
449
4502010-10-17 Paolo Bonzini <bonzini@gnu.org>
451
452	* libgst/prims.def: NULL-terminate the output of VMpr_String_asCData.
453	Suggested by Holger Hans Peter Freyther.
454
4552010-10-08 Paolo Bonzini <bonzini@gnu.org>
456
457	* libgst/cint.c: Retrieve CCallbackDescriptor on image load.
458
4592010-09-27  Holger Hans Peter Freyther  <zecke@selfish.org>
460
461	* libgst/oop.c: Fix a typo.
462
4632010-09-27  Paolo Bonzini <bonzini@gnu.org>
464
465	* libgst/gst-parse.c: Correctly handle scoped methods within
466	a class block.
467
4682010-09-27  Paolo Bonzini <bonzini@gnu.org>
469
470	* libgst/gst-parse.c: Fix NULL pointer dereference.
471
4722010-09-25  Gwenael Casaccio  <mrgwen@gmail.com>
473
474	* libgst/gst-parse.c: Support multi-keyword class attributes.
475
4762010-07-27  Paolo Bonzini <bonzini@gnu.org>
477
478	* libgst/sysdep.h: Correctly use size_t/ssize_t.
479	* libgst/sysdep/common/files.c: Likewise.
480	* libgst/prims.def: Likewise.  Remove duplicate checks.
481
4822010-07-27  Paolo Bonzini <bonzini@gnu.org>
483
484	* libgst/sysdep.h: Remove _gst_full_write.
485	* libgst/sysdep/common/files.c: Move _gst_full_write...
486	* libgst/save.c: ... here.  longjmp out to _gst_save_to_file when
487	it fails.
488
4892010-07-27  Paolo Bonzini <bonzini@gnu.org>
490
491	* libgst/cint.c: Fix warnings.
492	* libgst/real.c: Fix out-of-bounds array access (which is actually
493	unreachable, but GCC still warns).
494	* libgst/prims.def: Fix two warnings.
495	* libgst/sysdep/win32/signals.c: Fix warning.
496
4972010-07-04  Paolo Bonzini <bonzini@gnu.org>
498
499	* libgst/oop.c: Fix GC_DEBUGGING compilation.  Fix GC bug in
500	"ObjectMemory current".
501
5022010-06-13  Paolo Bonzini <bonzini@gnu.org>
503
504	* libgst/callin.c: Use _gst_copy_oop_range and _gst_mark_oop_range.
505	* libgst/oop.c: Rewrite tail recursion in _gst_mark_an_oop_internal.
506	Add _gst_mark_oop_range.
507	* libgst/oop.h: Add _gst_mark_oop_range, change prototype of
508	_gst_mark_an_oop_internal.
509	* libgst/oop.inl: Remove COPY_OOP_RANGE and MARK_OOP_RANGE, adjust
510	MAYBE_MARK_OOP.
511
5122010-06-13  Paolo Bonzini <bonzini@gnu.org>
513
514	* libgst/sockets.c: "Touch" all pointer arguments to socket
515	system calls to avoid EFAULT.
516
5172010-06-06  Paolo Bonzini <bonzini@gnu.org>
518
519	* libgst/sysdep/posix/time.c: Fix previous change for millisecond
520	vs. microsecond confusion.
521
5222010-05-28  Paolo Bonzini <bonzini@gnu.org>
523
524	* libgst/sysdep/posix/time.c: Prefer using nanosleep to usleep.
525	usleep is totally broken under Solaris 8 and 9. Reported by Rick
526	Flower.
527
5282010-05-21  Paolo Bonzini <bonzini@gnu.org>
529
530	* libgst/files.c: Load DynVariable.st.
531
5322010-05-18  Paolo Bonzini  <bonzini@gnu.org>
533
534	* libgst/comp.c: Flush aggressively around _gst_execute_statements.
535	* libgst/gst-parse.c: Likewise.
536
5372010-04-21  Paolo Bonzini  <bonzini@gnu.org>
538
539	* libgst/sockets.c: Fix previous commit.
540
5412010-04-19  Paolo Bonzini  <bonzini@gnu.org>
542
543	* libgst/sockets.c: Make connect return int.
544
5452010-04-17  Paolo Bonzini  <bonzini@gnu.org>
546
547	* libgst/input.c: Remove dead code.
548
5492010-04-11  Paolo Bonzini  <bonzini@gnu.org>
550
551	* libgst/sysdep/win32/events.c: Ahem, this really could not work.
552
5532010-04-11  Paolo Bonzini  <bonzini@gnu.org>
554
555	* libgst/cint.c: Fix warnings on platforms with no lstat.
556
5572010-03-25  Paolo Bonzini  <bonzini@gnu.org>
558
559	* libgst/sockets.c: Fix logic for no SOCK_CLOEXEC or no accept4.
560
5612010-02-20  Paolo Bonzini  <bonzini@gnu.org>
562
563	* libgst/files.c: Adjust for AnsiExcept.st rename.
564
5652010-02-18  Paolo Bonzini  <bonzini@gnu.org>
566
567	* libgst/vm.def: Make EXIT_INTERPRETER safer since we now can fork
568	CallinProcesses to Processes.
569
5702010-02-18  Paolo Bonzini  <bonzini@gnu.org>
571
572	* libgst/comp.c: Compile the termination method with an infinite
573	loop to avoid falling off the last context.
574
5752010-02-05  Gwenael Casaccio  <mrgwen@gmail.com>
576
577	* libgst/sysdep/posix/events.c: Fix initialization of waiting_thread.
578
5792010-01-11  Paolo Bonzini  <bonzini@gnu.org>
580
581	* libgst/genbc-decl.y: Embarrassing typo.
582
5832010-01-08  Paolo Bonzini  <bonzini@gnu.org>
584
585	* libgst/mpz.c: Hack to build with GMP 5.
586
5872010-01-01  Paolo Bonzini  <bonzini@gnu.org>
588
589	* Update copyright years.
590
5912009-12-11  Gwenael Casaccio  <mrgwen@gmail.com>
592
593	* libgst/prims.def: Fix bug in similarityTo:.
594
5952009-12-09  Alexey Zakhlestin  <indeyets@gmail.com>
596
597	* libgst/gstpriv.h: Include sockets.h.
598	* libgst/print.c: Fix printf.
599	* libgst/socklen.c: Use socklen_t where appropriate.
600	* libgst/sym.c: Remove useless cast.
601	* libgst/sysdep/common/files.c: Fix 64-bit cleanliness problems.
602	* libgst/sysdep/posix/findexec.c: Likewise.
603
6042009-12-05  Paolo Bonzini  <bonzini@gnu.org>
605
606	* libgst/byte.c: Add LN_ABSOLUTE, emit relative line number bytecodes
607	together with _following_ bytecode.
608	* libgst/byte.h: Add LN_ABSOLUTE.
609	* libgst/comp.c: Emit absolute line number for the line with the
610	selector.
611	* libgst/opt.c: Remove now useless two-line-numbers optimization.
612
6132009-11-26  Lee Duhem  <lee.duhem@gmail.com>
614
615	* libgst/comp.c: Make formatted source of Behavior>>methodsFor: look
616	better.
617
6182009-11-12  Paolo Bonzini  <bonzini@gnu.org>
619
620	* libgst/dict.c: Pass PREFIX and EXEC_PREFIX.
621
6222009-11-02  Paolo Bonzini  <bonzini@gnu.org>
623
624	* libgst/prims.def: Do not fail on pow(0.0, 0.0).
625
6262009-11-01  Paolo Bonzini  <bonzini@gnu.org>
627
628	* libgst/comp.c: Fix computation of jump lengths.
629
6302009-10-28  Paolo Bonzini  <bonzini@gnu.org>
631
632	* libgst/gstpub.c: Move init_vmproxy and _gst_get_vmproxy...
633	* libgst/callin.c: ... here.  Make_gst_init_vmproxy public, do
634	not call it from _gst_get_vmproxy.
635	* libgst/callin.h: Declare them here...
636	* libgst/files.h: ... not here.
637	* libgst/files.c: Call _gst_init_vmproxy.
638
6392009-10-17  Paolo Bonzini  <bonzini@gnu.org>
640
641	* libgst/sysdep/win32/events.c: Implement pause/wakeup.
642
6432009-10-21  Paolo Bonzini  <bonzini@gnu.org>
644
645	* libgst/sockets.c: Fix !HAVE_IPV6 compilation, and other Cygwin
646	problems.
647
6482009-10-13  Nigel Williams  <nigelw@elder-gods.net>
649
650	* libgst/cint.c: Always open with lt_dlopen first, then try
651	lt_dlopenext.
652
6532009-10-13  Eli Green  <detgk@me.com>
654
655	* libgst/events.h: Fix multiply defined symbols on Mac OS X.
656
6572009-10-06  Paolo Bonzini  <bonzini@gnu.org>
658
659	* libgst/prims.def: Fix #becomeForward: to look at LIFO contexts.
660
6612009-10-04  Paolo Bonzini  <bonzini@gnu.org>
662
663	* libgst/prims.def: Allow reusing #at: primitive for #at:ifAbsent:.
664
6652009-10-04  Paolo Bonzini  <bonzini@gnu.org>
666
667	* libgst/prims.def: Implement memchr primitive.
668
6692009-09-07  Paolo Bonzini  <bonzini@gnu.org>
670
671	* libgst/sysdep/win32/signals.c: Simplify given known set of valid
672	signals.
673
6742009-09-07  Paolo Bonzini  <bonzini@gnu.org>
675
676	* libgst/events.h: Add _gst_get_fd_error.
677	* libgst/sysdep/win32/events.c: Implement it.
678	* libgst/sysdep/posix/events.c: Implement it as a stub.
679	* libgst/sockets.c: Use it in getSoError.
680
6812009-09-07  Paolo Bonzini  <bonzini@gnu.org>
682
683	* libgst/sysdep/win32/events.c: Extract select-based polling from
684	poll_thread, use it in _gst_sync_file_polling and
685	_gst_async_file_polling, save error conditions returned
686	by WSAEnumNetworkEvents.
687
6882009-09-03  Paolo Bonzini  <bonzini@gnu.org>
689
690	* libgst/gst-parse.c: Fix crash on invalid class variable definitions.
691
6922009-08-26  Paolo Bonzini  <bonzini@gnu.org>
693
694	Complete transition from events.c to sysdep/*/events.c, moving
695	the common parts back outside sysdep/ and adding a stab at the
696	Win32 version.  This lets us throw Makefile/lib-src hacks away.
697
698	* libgst/gstpriv.h: Include signal.h, do not include poll.h.
699	* libgst/events.h: Add _gst_register_socket.
700	* libgst/sysdep.h: Add _gst_wait_for_input.  Remove TIMER_REAL,
701	TIMER_PROCESS.
702	* libgst/input.c: Use _gst_wait_for_input and _gst_sync_file_polling.
703	* libgst/sockets.c: Use gstpriv.h.  Do _gst_register_socket.  Do
704	not warn under mingw.
705	* libgst/interp.c: Cope with nonexistent SIGUSR1.  Avoid useless
706	abstraction in _gst_signal_after.
707	* libgst/sysdep/common/files.c: Cope with nonexistent SIGPIPE.
708	* libgst/sysdep/cygwin/timer.c: Adjust for changes in sysdep.h.
709	* libgst/sysdep/posix/timer.c: Adjust for changes in sysdep.h.
710	* libgst/sysdep/win32/timer.c: Adjust for changes in sysdep.h.
711	* libgst/sysdep/win32/events.c: Rewrite.
712	* libgst/sysdep/win32/signals.c: Remove signals not found under mingw.
713	* libgst/sysdep/posix/events.c: Add _gst_register_socket and
714	_gst_wait_for_input.  Adjust to move OS-independent parts...
715	* libgst/events.c: ... here.
716
7172009-08-25  Paolo Bonzini  <bonzini@gnu.org>
718
719	* libgst/dict.c: Just skip primitives that are unknown to the image.
720
7212009-08-25  Paolo Bonzini  <bonzini@gnu.org>
722
723	* libgst/sockets.c: Move from packages/sockets/.
724	* libgst/sockets.h: New.
725	* libgst/files.c: Initialize sockets.
726
7272009-08-24  Paolo Bonzini  <bonzini@gnu.org>
728	    Nicolas Petton  <petton.nicolas@gmail.com>
729
730	* libgst/dict.inl: Add num_valid_oops.
731	* libgst/prims.def: Add becomeForward primitive.
732
7332009-08-23  Paolo Bonzini  <bonzini@gnu.org>
734
735	* libgst/oop.inl: Fix ??? comment.
736
7372009-08-23  Paolo Bonzini  <bonzini@gnu.org>
738
739	* libgst/oop.c: Export finished_incremental_gc.
740	* libgst/oop.h: Declare _gst_finished_incremental_gc.  Use
741	maybe_release_xlat.
742	* libgst/oop.inl: Fix bottom-to-top incremental collector.
743
7442009-08-23  Paolo Bonzini  <bonzini@gnu.org>
745
746	* libgst/oop.c: Rename highest_swept_oop to next_oop_to_sweep,
747	shift it down by one.
748
7492009-08-23  Paolo Bonzini  <bonzini@gnu.org>
750
751	* libgst/oop.c: Always do _gst_finish_incremental_gc so that
752	finished_incremental_gc is called.
753
7542009-08-21  Paolo Bonzini  <bonzini@gnu.org>
755
756	* libgst/events.h: Declare it.
757	* libgst/sysdep/posix/events.c: Add _gst_wakeup.
758	* libgst/sysdep/win32/events.c: Ditto.
759	* libgst/gstpub.c: Add it to VMproxy and add gst_wakeup.
760	* libgst/gstpub.h: Add wakeUp to VMproxy, add gst_wakeup.
761	* libgst/interp.c: Call _gst_wakeup from _gst_async_call.
762
7632009-08-22  Paolo Bonzini  <bonzini@gnu.org>
764
765	* libgst/sysdep.h: Tweak.
766	* libgst/sysdep.c: Split into...
767	* libgst/sysdep/common/files.c, libgst/sysdep/common/time.c,
768	libgst/sysdep/cygwin/files.c, libgst/sysdep/cygwin/findexec.c,
769	libgst/sysdep/cygwin/mem.c, libgst/sysdep/cygwin/signals.c,
770	libgst/sysdep/cygwin/time.c, libgst/sysdep/cygwin/timer.c,
771	libgst/sysdep/posix/files.c, libgst/sysdep/posix/findexec.c,
772	libgst/sysdep/posix/mem.c, libgst/sysdep/posix/signals.c,
773	libgst/sysdep/posix/time.c, libgst/sysdep/posix/timer.c,
774	libgst/sysdep/win32/files.c, libgst/sysdep/win32/findexec.c,
775	libgst/sysdep/win32/mem.c, libgst/sysdep/win32/signals.c,
776	libgst/sysdep/win32/time.c, libgst/sysdep/win32/timer.c: ... all
777	these.
778
779	* libgst/events.c: Copy to...
780	* libgst/sysdep/posix/events.c: ... this...
781	* libgst/sysdep/win32/events.c: ... and this.
782	* libgst/sysdep/cygwin/events.c: New.
783
7842009-08-21  Paolo Bonzini  <bonzini@gnu.org>
785
786	* libgst/events.c: Add _gst_pause.
787	* libgst/events.h: Declare it.
788	* libgst/interp.c: Add active_process_yield.
789	* libgst/prims.def: Use it.  Remove sleeping from VMpr_Processor_yield.
790	Add VMpr_Processor_pause.  Return whether incremental GC has finished
791	in the VMpr_ObjectMemory_incrementalGCStep primitive.
792	* libgst/sysdep.c: Add _gst_usleep.
793	* libgst/sysdep.h: Declare it.
794
7952009-08-21  Paolo Bonzini  <bonzini@gnu.org>
796
797	* libgst/oop.c: Track correctly the bottom-to-top sweeping of OOPs.
798	Return from _gst_incremental_gc_step whether incr. GC has finished.
799	* libgst/oop.h: Adjust prototype.
800	* libgst/oop.inl: Track here the bottom-to-top sweeping of OOPs.
801
8022009-08-18  Paolo Bonzini  <bonzini@gnu.org>
803
804	* libgst/cint.c: Add dlopen functions for modules.
805	* libgst/cint.h: Declare them.
806	* libgst/gstpub.c: Implement public variants and add to VMProxy.
807	* libgst/gstpub.h: Declare public variants.
808
8092009-08-01  Paolo Bonzini  <bonzini@gnu.org>
810
811	* libgst/interp.c: Do not create gcSemaphore.
812	* libgst/oop.c: Abort upon absence of gcSemaphore.
813
8142009-08-01  Paolo Bonzini  <bonzini@gnu.org>
815
816	* libgst/dict.c: Remove Delay, SharedQueue, MappedCollection, Bag.
817	* libgst/dict.h: Likewise.
818	* libgst/files.c: Move them after initialization.
819
8202009-07-28  Paolo Bonzini  <bonzini@gnu.org>
821
822	* libgst/dict.c: Add git revision number to Version contents.
823
8242009-07-26  Paolo Bonzini  <bonzini@gnu.org>
825
826	* libgst/genbc-parse.y: Fix uninitialized memory use that
827	"interestingly" triggered only under Wine.
828
8292009-07-25  Paolo Bonzini  <bonzini@gnu.org>
830
831	* libgst/sysdep.h: Return 64-bit millisecond clock.
832	* libgst/sysdep.c: Return 64-bit millisecond clock, use monotonic
833	clock_gettime if available.
834	* libgst/prims.def: Return 64-bit millisecond clock.
835
8362009-07-23  Paolo Bonzini  <bonzini@gnu.org>
837
838	* libgst/gstpriv.h: Add optimization barrier.
839	* libgst/vm.def: Use it.
840
841	* libgst/prims.def: Eliminate uninitialized variable.
842
8432009-07-22  Paolo Bonzini  <bonzini@gnu.org>
844
845	* libgst/sysdep.c: Small cleanup.
846
8472009-07-20  Paolo Bonzini  <bonzini@gnu.org>
848
849	* libgst/genpr-parse.y: Fix for newer bison.
850
8512009-07-11  Paolo Bonzini  <bonzini@gnu.org>
852
853	* libgst/lex.c: Use new real.c interface.
854	* libgst/real.c: New.
855	* libgst/real.h: New.
856
8572009-07-02  Paolo Bonzini  <bonzini@gnu.org>
858
859	* libgst/input.c: Include all symbols after popular demand for
860	completion.
861
8622009-06-19  Paolo Bonzini  <bonzini@gnu.org>
863
864	* libgst/lex.c: Fix my own snafu.
865
8662009-06-18  Paolo Bonzini  <bonzini@gnu.org>
867
868	* libgst/comp.c: Check for infinite recursion of #doesNotUnderstand:
869	before printing the result of an evaluation.
870
8712009-06-15  Paolo Bonzini  <bonzini@gnu.org>
872
873	* libgst/dict.inl: Pad long doubles to 16 bytes.
874
8752009-06-15  Paolo Bonzini  <bonzini@gnu.org>
876
877	* libgst/lex.c: Fix parsing of 16r2.ABCDEFd.
878
8792009-06-15  Paolo Bonzini  <bonzini@gnu.org>
880
881	* libgst/prims.def: Fix typo.
882
8832009-06-08  Paolo Bonzini  <bonzini@gnu.org>
884
885	* libgst/mpz.c: Return whether large integer->float conversion was
886	exact.
887	* libgst/mpz.h: Adjust prototypes.
888	* libgst/prims.def: Fail on inexact conversions.
889
8902009-03-30  Derek Zhou  <agonyzhou@comcast.net>
891	    Paolo Bonzini  <bonzini@gnu.org>
892
893	* libgst/comp.c: Do not reset counters if profiling is on.
894
895	* libgst/interp-bc.inl: Make state consistent when
896	profiling callbacks might be called.
897	* libgst/interp.c: Likewise.
898
899	* libgst/dict.c: Add profiling callback.
900	* libgst/dict.h: Add profiling callback.
901	* libgst/interp-bc.inl: Call it.
902	* libgst/interp.c: Declare variables.
903	* libgst/interp.h: Declare variables.
904	* libgst/prims.def: Add profiling primitive.
905
9062009-03-05  Paolo Bonzini  <bonzini@gnu.org>
907
908	* libgst/files.c: Load RecursionLock.st before Transcript.st.
909
9102009-02-19  Paolo Bonzini  <bonzini@gnu.org>
911
912	* libgst/dict.c: Fix off-by-one in _gst_identity_dictionary_at_put.
913
9142009-01-23  Derek Zhou  <agonyzhou@comcast.net>
915
916    	* libgst/oop.c: Allow shrinking the heap down to the eden's size.
917
9182009-01-21  Derek Zhou  <agonyzhou@comcast.net>
919
920	* libgst/oop.c: Only compact if there were lots of garbage,
921	shrinking the heap limit at the same time.
922
9232009-01-19  Paolo Bonzini  <bonzini@gnu.org>
924	    Derek Zhou  <agonyzhou@comcast.net>
925
926	* libgst/oop.c: Always call _gst_finish_incremental_gc before
927	a non-growing compaction of the heap.
928
9292009-01-07  Paolo Bonzini  <bonzini@gnu.org>
930
931	* libgst/cint.c: Add chown.
932
9332008-12-30  Paolo Bonzini  <bonzini@gnu.org>
934
935	* libgst/cint.c: Discard EPIPE too, it is caught by POLLHUP.
936
9372008-12-07  Paolo Bonzini  <bonzini@gnu.org>
938
939	* libgst/oop.c: Resize the oldspace if tenuring needs more space than
940	we would have liked to have, but then do a GC if this happens.
941
9422008-11-18  Paolo Bonzini  <bonzini@gnu.org>
943
944	* libgst/alloc.c: Use fixed values for MMAP_AREA_SIZE and
945	MMAP_THRESHOLD.
946
9472008-10-23  Paolo Bonzini  <bonzini@gnu.org>
948
949	* libgst/comp.c: Do not modify already-complete blocks.
950	* libgst/interp-bc.inl: Sync _gst_send_method and _gst_send_message_internal.
951
9522008-10-21  Paolo Bonzini  <bonzini@gnu.org>
953
954	* libgst/xlat.c: Fix ISO C99-ism.
955
9562008-10-20  Paolo Bonzini  <bonzini@gnu.org>
957
958	* libgst/interp-jit.inl: Fix compilation error.
959
9602008-10-18  Paolo Bonzini  <bonzini@gnu.org>
961
962	* libgst/dict.h: Remove ATTRIBUTE_PURE from functions that are CSEable,
963	but write to memory (typically by memoizing values or allocating OOPs).
964	* libgst/input.h: Likewise.
965	* libgst/interp.c: Likewise.
966	* libgst/opt.h: Likewise.
967	* libgst/sym.h: Likewise.
968
969	* libgst/opt.c: Change compute_jump_length to be const.
970
9712008-09-22  Paolo Bonzini  <bonzini@gnu.org>
972
973	* cint.c: Fix ia64 cobjects.st failure by always using a ffi_arg-sized
974	field.
975
9762008-09-22  Paolo Bonzini  <bonzini@gnu.org>
977
978	* genpr-parse.c: Rename strupr.
979	* genpr-parse.h: Rename strupr.
980	* genpr-parse.y: Rename strupr.
981
9822008-09-22  Paolo Bonzini  <bonzini@gnu.org>
983
984	* input.c: Revert 2008-09-18 change.  Check whether get_cur_file()
985	returns nil instead.
986
9872008-09-21  Paolo Bonzini  <bonzini@gnu.org>
988
989	* alloc.h: Change nomemory hook prototype.
990	* alloc.c: Use return value of nomemory hook.
991	* oop.c: Pass new oldspace heap back from nomemory hook.
992
9932008-09-20  Paolo Bonzini  <bonzini@gnu.org>
994
995	* cint.c: Adjust calls to _gst_show_backtrace.
996	* gstpub.c: Add gst_show_backtrace and declare it in VMProxy.
997	* gstpub.h: Likewise.
998	* interp.c: Adjust calls to _gst_show_backtrace, add FILE *
999	argument there.
1000	* interp.h: Adjust prototype of _gst_show_backtrace.
1001	* prims.def: Adjust calls to _gst_show_backtrace.
1002
10032008-09-18  Paolo Bonzini  <bonzini@gnu.org>
1004
1005	* input.c: Do not create FileSegments for non-FileStream streams.
1006
10072008-09-14  Paolo Bonzini  <bonzini@gnu.org>
1008
1009	* cint.c: Fix possible GC bugs.
1010
10112008-09-02  Paolo Bonzini  <bonzini@gnu.org>
1012
1013	* prims.def: Do not use closesocket, close is now emulated
1014	on Windows.
1015
10162008-08-18  Paolo Bonzini  <bonzini@gnu.org>
1017
1018	* libgst/comp.c: Mark the termination method as annotated.
1019
10202008-08-17  Paolo Bonzini  <bonzini@gnu.org>
1021
1022	* libgst/prims.def: Add socket<->fd conversions.
1023	* libgst/sysdep.c: Likewise.
1024
10252008-08-17  Paolo Bonzini  <bonzini@gnu.org>
1026
1027	* libgst/sysdep.c: Emulate FD_CLOEXEC on MinGW.
1028
10292008-08-11  Paolo Bonzini  <bonzini@gnu.org>
1030
1031	* libgst/cint.c: Do not pass POLLHUP errors to Smalltalk.
1032
10332008-08-08  Samuel Tardieu  <sam@rfc1149.net>
1034
1035	* libgst/sysdep.c (do_interrupts): Remove unused prototype.
1036	(DISABLED_MASK): Add SIGQUIT.
1037
10382008-08-08  Samuel Tardieu  <sam@rfc1149.net>
1039
1040	* libgst/sysdep.c (_gst_open_pipe): Remove unused variable.
1041
10422008-08-08  Samuel Tardieu  <sam@rfc1149.net>
1043
1044	* libgst/sysdep.c (find_executable): Correctly zero-terminate
1045	"location" before returning it.
1046
10472008-08-07  Paolo Bonzini  <bonzini@gnu.org>
1048
1049	* gstpriv.h: Define __sync_synchronize.
1050	* interp.h: Do not export _gst_except_flag if not JIT.
1051	* interp.c: Use a separate queue for async calls scheduled
1052	from a signal handler.  Protect other async call queue accesses
1053	with a lock.  Add memory barriers.
1054	* interp-bc.inl: Protect async call queue accesses with a lock.
1055	Add memory barriers.
1056	* interp-jit.inl: Protect async call queue accesses with a lock.
1057	Add memory barriers.  Reset _gst_except_flag earlier.
1058	Use the return value of _gst_run_native_code to check if the
1059	termination method was invoked.
1060	* sysdep.h: Define _gst_signal_count.
1061	* sysdep.c: Use it instead of a static variable.
1062
10632008-08-06  Paolo Bonzini  <bonzini@gnu.org>
1064
1065	* events.c: Reset errno if _gst_sync_file_polling finds
1066	POLLHUP, POLLERR or POLLNVAL.
1067	* events.h: Document this.
1068
10692008-08-06  Paolo Bonzini  <bonzini@gnu.org>
1070
1071	* events.c: Use _gst_{dis,en}able_interrupts (true);
1072	make a worker function for _gst_remove_fd_polling_handlers and
1073	file_polling_handler.  Call it asynchronously from
1074	file_polling_handler.  Do not disable interrupts from
1075	_gst_async_file_polling.
1076	* gstpub.c: Export _gst_async_call and _gst_sync_signal.
1077	* gstpub.h: Likewise.
1078	* interp-bc.inl: Perform asynchronous calls.
1079	* interp-jit.inl: Perform asynchronous calls.
1080	* interp.c: Adjust async_queue_entry for asynchronous calls.
1081	Export sync_signal.  Adjust calls to _gst_{dis,en}able_interrupts.
1082	* interp.h: Declare _gst_async_call and _gst_sync_signal.
1083	* sysdep.c: Rewrite _gst_{dis,en}able_interrupts to rely on
1084	sigaction setting the mask on POSIX systems.  Set up the
1085	mask in _gst_set_signal_handler.
1086	* sysdep.h: Adjust prototypes, adjust documentation of
1087	_gst_set_signal_handler.
1088
10892008-08-06  Paolo Bonzini  <bonzini@gnu.org>
1090
1091	* interp-bc.inl: Change disable_preemption to async_queue_enabled.
1092	* interp-jit.inl: Likewise.
1093	* interp.c: Make queued_async_signals a dynamic array.	Make
1094	sync_signal able to behave like Semaphore>>#notify.  Do not
1095	disable/enable interrupts on behalf of the Smalltalk program;
1096	async_queue_enabled already fakes that.  Do not disable/enable
1097	interrupts in the synchronized wait/signal functions.
1098	* prims.def: Do not disable/enable interrupts around the
1099	synchronized wait/signal functions.
1100
11012008-08-06  Paolo Bonzini  <bonzini@gnu.org>
1102
1103	* input.c: Do not use #nextHunk.
1104
11052008-08-05  Paolo Bonzini  <bonzini@gnu.org>
1106
1107	* dict.c: Adjust layout of FileDescriptor and FileStream.  Do not
1108	fill in FileStream variables in FileDescriptors.
1109	* dict.h: Likewise.
1110	* prims.def: Adjust uses of gst_file_stream.
1111
11122008-08-05  Paolo Bonzini  <bonzini@gnu.org>
1113
1114	* dict.c: Remove _gst_byte_stream_class.  Change superclass of
1115	FileDescriptor.
1116	* dict.h: Likewise.
1117	* files.c: Do not load ByteStream.st.
1118
11192008-08-05  Paolo Bonzini  <bonzini@gnu.org>
1120
1121	* dict.c: Add _gst_iterable_class.  Change superclass of
1122	Collection and Stream.
1123	* dict.h: Likewise.
1124	* files.c: Load Iterable.st.
1125
11262008-08-04  Paolo Bonzini  <bonzini@gnu.org>
1127
1128	* interp.c: Move ignored signals...
1129	* sysdep.c: ... here.  Reset them for exec-ed executables.
1130
11312008-08-01  Paolo Bonzini  <bonzini@gnu.org>
1132
1133	* sysdep.c: Use O_CLOEXEC if available instead of FD_CLOEXEC.
1134
11352008-08-01  Paolo Bonzini  <bonzini@gnu.org>
1136
1137	* sysdep.c: Always set SIGCHLD handler, and invoke the file
1138	interrupt handler from it.  This makes sure that all children
1139	are reaped.
1140
11412008-08-01  Paolo Bonzini  <bonzini@gnu.org>
1142
1143	* sysdep.c: Fix off-by-one errors involving readlink(2).
1144
11452008-07-28  Paolo Bonzini  <bonzini@gnu.org>
1146
1147	* gst-parse.c: Parse negative numbers as unary minus + number.
1148	* lex.c: Add _gst_negate_yylval and simplify _gst_scan_number.
1149	* lex.h: Declare _gst_negate_yylval.
1150
11512008-07-24  Paolo Bonzini  <bonzini@gnu.org>
1152
1153	* libgst/byte.c: Modify _gst_line_number to store the line offset
1154	and emit the first line number as absolute.
1155	* libgst/byte.h: Add LN_RESET and LN_FORCE.
1156	* libgst/comp.c: Use new _gst_line_number functionality instead
1157	of line_offset.
1158	* libgst/opt.c: Rewrite is_simple_return to account for line numbers
1159	that are >= 256.
1160
11612008-07-18  Paolo Bonzini  <bonzini@gnu.org>
1162
1163	* libgst/gstpriv.h: Change HAVE_INET_SOCKETS to HAVE_SOCKETS.
1164	* libgst/prims.def: Change HAVE_INET_SOCKETS to HAVE_SOCKETS.
1165	* libgst/sysdep.c: Change HAVE_INET_SOCKETS to HAVE_SOCKETS.
1166
11672008-07-14  Paolo Bonzini  <bonzini@gnu.org>
1168
1169	* libgst/opt.c: Enable jump superoperators.
1170
11712008-07-14  Paolo Bonzini  <bonzini@gnu.org>
1172
1173	* libgst/interp-bc.inl: Replace FETCH with FETCH_VEC.
1174	* libgst/vm.def: Use ADVANCE instead of PREFETCH also for jump
1175	superoperators.  Move "ip += 2" to ADVANCE.  Remove argument
1176	to FETCH (it was always dispatch_vec), add PREPARE_STACK to
1177	jump bytecodes.
1178
11792008-07-14  Paolo Bonzini  <bonzini@gnu.org>
1180
1181	* libgst/opt.c: Rewrite _gst_optimize_bytecodes to build a CFG
1182	and reassemble the method at the end of the optimization.
1183
11842008-07-10  Paolo Bonzini  <bonzini@gnu.org>
1185
1186	* libgst/dict.c: Fix order of instance variables for metaclass.
1187
11882008-06-04  Paolo Bonzini  <bonzini@gnu.org>
1189
1190	* libgst/interp-bc.inl: Create a jmp_buf for _gst_interpret.
1191	* libgst/interp-jit.inl: Likewise.
1192	* libgst/interp.c: Rewrite handling of interp_jmp_buf and signals.  Use
1193	the jmp_buf from _gst_interpret when SIGINT is sent but the current
1194	process is terminated.
1195	* libgst/prims.def: Use push_jmp_buf and pop_jmp_buf.  Propagate
1196	interruptions until the interpreter is reached.
1197
11982008-06-02  Paolo Bonzini  <bonzini@gnu.org>
1199
1200	* libgst/cint.c: Return the receiver, not nil, if the returned type
1201	is #void.
1202
12032008-05-30  Paolo Bonzini  <bonzini@gnu.org>
1204
1205	* libgst/callin.c: Fix %w in _gst_msg_sendf.
1206
12072008-05-27  Paolo Bonzini  <bonzini@gnu.org>
1208
1209	* libgst/prims.def: Add VMpr_ArrayedCollection_equal.
1210
12112008-05-22  Paolo Bonzini  <bonzini@gnu.org>
1212
1213	* libgst/oop.c: Don't pin weak objects to a fixed location.
1214	* libgst/oop.h: Remove now unused fields.
1215
12162008-05-22  Paolo Bonzini  <bonzini@gnu.org>
1217
1218	* libgst/cint.h: Declare _gst_invalidate_croutine_cache.
1219	* libgst/cint.c: Define it.  Replace cache validity boolean with
1220	a cache generation number.
1221	* libgst/oop.c: Call it after GC.
1222
12232008-05-22  Paolo Bonzini  <bonzini@gnu.org>
1224
1225	* libgst/prims.def: Make VMpr_ByteArray_replaceFromToWithStartingAt
1226	more generic.
1227
12282008-05-21  Paolo Bonzini  <bonzini@gnu.org>
1229
1230	* libgst/cint.c: Extract part of push_smalltalk_obj into c_to_smalltalk.
1231	Add closure support.
1232	* libgst/cint.h: Declare functions for closures.
1233	* libgst/dict.c: Add CCallbackDescriptor.
1234	* libgst/dict.h: Add CCallbackDescriptor.
1235	* libgst/files.c: Load CCallback.st.
1236	* libgst/prims.def: Declare closure primitives.
1237
12382008-05-21  Paolo Bonzini  <bonzini@gnu.org>
1239
1240	* libgst/callin.c: Support '%B' for the receiver in msgSendf.
1241	* libgst/interp.c: Callins evaluate blocks if the selector is NULL.
1242
12432008-05-21  Paolo Bonzini  <bonzini@gnu.org>
1244
1245	* libgst/cint.c: Replace CFunctionDescriptor references with CCallable.
1246	Allow OOPs in the argument vector and parse them as #cObject.
1247	* libgst/cint.h: Likewise.
1248	* libgst/dict.c: Add _gst_c_callable_class and definition of CCallable.
1249	* libgst/dict.h: Add _gst_c_callable_class.
1250	* libgst/files.c: Load CCallable.st.
1251	* libgst/save.c: Replace CFunctionDescriptor references with CCallable.
1252
12532008-05-20  Paolo Bonzini  <bonzini@gnu.org>
1254
1255	* libgst/cint.c: Remove symbol_type_map, type_map, classify_type_symbol,
1256	_gst_make_descriptor.  Make lookup_function global.
1257	* libgst/cint.h: Declare _gst_lookup_function instead of
1258	_gst_make_descriptor.
1259	* libgst/prims.def: Replace VMpr_CFuncDescriptor_create with
1260	VMpr_CFuncDescriptor_addressOf.
1261
12622008-05-20  Paolo Bonzini  <bonzini@gnu.org>
1263
1264	* libgst/cint.c: Make CFunctionDescriptor a subclass of CObject,
1265	moving in turn the indexed instance variables into an array.
1266	* libgst/dict.c: Adjust definition.  Change uninitialized creation
1267	in _gst_cobject_new_base to initialized.
1268	* libgst/save.c: Adjust saving.
1269
12702008-05-20  Paolo Bonzini  <bonzini@gnu.org>
1271
1272	* libgst/cint.c: Complete 2008-04-01 change by splitting part of
1273	c_func_info in a cache accessed with a pointer_map.  This way, the
1274	CFunctionDescriptor can store the function pointer instead of the
1275	pointer to the c_func_info.
1276
12772008-05-18  Paolo Bonzini  <bonzini@gnu.org>
1278
1279	* libgst/sym.c: Improve comment on TwistedPools wrt namespace
1280	imports.
1281
12822008-05-18  Stephen Compall  <scompall@nocandysw.com>
1283
1284	* libgst/gst-parse.c: Refactor pragma evaluation into new
1285	function, and use it to support namespace pragmas.
1286
12872008-05-17  Stephen Compall  <scompall@nocandysw.com>
1288
1289	* libgst/dict.h: Add `sharedPools' instvar to gst_namespace.
1290	* libgst/dict.c: Likewise.
1291	* libgst/sym.c: Import shared pools from namespaces as they are
1292	visited, and expand the comment on TwistedPools to document this.
1293
12942008-05-17  Paolo Bonzini  <bonzini@gnu.org>
1295
1296	* libgst/callin.c: Fix _gst_oop_indexed_base.
1297
12982008-05-16  Paolo Bonzini  <bonzini@gnu.org>
1299
1300	* libgst/callin.c: Allow ints in OOP->float conversions.
1301
13022008-05-15  Paolo Bonzini  <bonzini@gnu.org>
1303
1304	* libgst/cint.c: Allow passing any object with non-pointer indexed
1305	instance variables as a #cObject.
1306
13072008-05-14  Paolo Bonzini  <bonzini@gnu.org>
1308
1309	* libgst/oop.c: Add ephemerons to buffer before marking their class
1310	(else, if the class actually has to be marked, we won't add them to the
1311	buffer at all).
1312
13132008-05-13  Paolo Bonzini  <bonzini@gnu.org>
1314
1315	* libgst/callin.h: Add _gst_oop_indexed_base and _gst_oop_indexed_kind.
1316	* libgst/callin.c: Implement them.
1317	* libgst/gstpub.h: Add them to the VMProxy and to the public API.
1318	* libgst/gstpub.c: Implement the public API wrappers.
1319
13202008-05-13  Paolo Bonzini  <bonzini@gnu.org>
1321
1322	* libgst/gstpriv.h: Move ISP_* constants...
1323	* libgst/dict.h: ... here...
1324	* libgst/gst.h: ... and here.  Prefix these with GST_.
1325	* libgst/dict.c: Adjust uses.
1326	* libgst/dict.inl: Adjust uses.
1327	* libgst/prims.def: Adjust uses.
1328	* libgst/xlat.c: Adjust uses.
1329
13302008-05-12  Paolo Bonzini  <bonzini@gnu.org>
1331
1332	* libgst/interp.c: Adjust send_block_value prototype.
1333	* libgst/interp-bc.inl: Support block argument culling.
1334	* libgst/interp-jit.inl: Support block argument culling.
1335	* libgst/prims.def: Add primitives for block argument culling.
1336	* libgst/vm.def: Adjust calls to send_block_value.
1337
13382008-05-06  Paolo Bonzini  <bonzini@gnu.org>
1339
1340	* libgst/callin.c: Adjust calls to COBJECT_NEW, COBJECT_VALUE,
1341	SET_COBJECT_VALUE.
1342	* libgst/cint.c: Likewise.  Add _gst_c_type_size.
1343	* libgst/cint.h: Declare _gst_c_type_size.
1344	* libgst/dict.c: Likewise.  Rename _gst_c_object_new to
1345	_gst_c_object_new_base, add new instance variable to CObject.
1346	Make CObject absolute in _gst_free_cobject.
1347	* libgst/dict.h: Adjust struct gst_cobject and rename
1348	prototype of _gst_c_object_new to _gst_c_object_new_base.
1349	* libgst/dict.inl: Add cobject_value, set_cobject_value,
1350	cobject_index_check.  Adjust COBJECT_NEW.  Rename COBJECT_VALUE_OBJ
1351	and SET_COBJECT_VALUE_OBJ to COBJECT_OFFSET_OBJ and
1352	SET_COBJECT_OFFSET_OBJ, respectively.
1353	* libgst/prims.def: Adjust calls to COBJECT_NEW, COBJECT_VALUE,
1354	SET_COBJECT_VALUE.  Add calls to cobject_index_check.  Handle
1355	derefAt:type: from a garbage-collected CObject specially, and
1356	otherwise preserve the base when casting a CObject.
1357
13582008-05-06  Paolo Bonzini  <bonzini@gnu.org>
1359
1360	* libgst/prims.def: Eliminate VMpr_CObject_derefAtPut,
1361	restrict VMpr_CObject_derefAt to CObject types.
1362
13632008-04-25  Paolo Bonzini  <bonzini@gnu.org>
1364            Stephen Compall  <scompall@nocandysw.com>
1365
1366	* libgst/sym.c: Document (prose by Stephen Compall) and
1367	implement TwistedPools, using a linearized list of pool dictionaries
1368	for the lookup.
1369
13702008-04-10  Paolo Bonzini  <bonzini@gnu.org>
1371
1372	* libgst/dict.c: Put fundamental instance variables of Behavior
1373	at the beginning.
1374	* libgst/dict.h: Likewise.
1375
13762008-04-07  Paolo Bonzini  <bonzini@gnu.org>
1377
1378	* libgst/dict.c: Rename name variable of FileDescriptor to file.
1379	Support non-existent relocated paths by setting the variable to nil.
1380	* libgst/files.c: Load FilePath.st.
1381	* libgst/input.c: Support separate filename (for printing errors) and
1382	File object (for FileSegments).
1383	* libgst/input.h: Adjust prototypes.
1384	* libgst/prims.def: Add fourth optional argument to filein primitive.
1385
13862008-04-07  Paolo Bonzini  <bonzini@gnu.org>
1387
1388	* libgst/dict.c: Likewise.
1389
13902008-04-01  Paolo Bonzini  <bonzini@gnu.org>
1391
1392	* libgst/cint.c: Don't use numFixedArgs instance variable of
1393	a CFunctionDescriptor.  Add classOOP parameters to _gst_make_descriptor.
1394	Return NULL if there is a problem instead of printing an error.
1395	* libgst/cint.h: Rename numFixedArgs field of gst_cfunc_descriptor
1396	to tagOOP.  Adjust prototype of _gst_make_descriptor.
1397	* libgst/dict.c Rename numFixedArgs variable to tag here too.
1398	* libgst/prims.def: Create subclasses of CFunctionDescriptor
1399	if VMpr_CFuncDescriptor_create is sent to a subclass.  Fail
1400	if _gst_make_descriptor returns NULL.
1401
14022008-04-01  Paolo Bonzini  <bonzini@gnu.org>
1403
1404	* libgst/dict.c: Rename unwindPoints variable of Process to environment.
1405	* libgst/files.c: Load ProcEnv.st.
1406
14072008-04-01  Paolo Bonzini  <bonzini@gnu.org>
1408
1409	* libgst/interp.c: Correct output for execution environment contexts
1410	that have a parent.
1411
14122008-03-26  Paolo Bonzini  <bonzini@gnu.org>
1413
1414	* libgst/cint.c: Add stat/lstat versions that return an object.
1415	* libgst/dict.inl: Move from/to off_t conversion here...
1416	* libgst/prims.def: ... from here.
1417
14182008-03-25  Paolo Bonzini  <bonzini@gnu.org>
1419
1420	* libgst/prims.def: Make #fileIn primitive fail if the filename is bad.
1421
14222008-03-25  Paolo Bonzini  <bonzini@gnu.org>
1423
1424	* libgst/callin.c: Never register the "nil" object, it is useless.
1425
14262008-03-19  Paolo Bonzini  <bonzini@gnu.org>
1427
1428	* libgst/prims.def: Mark VMpr_Process_suspend as a possible
1429	source of interrupts.
1430
14312008-03-19  Paolo Bonzini  <bonzini@gnu.org>
1432
1433	* libgst/files.c: Load BlockClosure before the first closures
1434	are executed (by the JIT).
1435
14362008-03-15  Paolo Bonzini  <bonzini@gnu.org>
1437
1438	* libgst/dict.c: Add SystemKernelPath.
1439	* libgst/files.c: Call `FileSegment relocate' before loading
1440	pre-image files.
1441
14422008-03-15  Paolo Bonzini  <bonzini@gnu.org>
1443
1444	* libgst/cint.c: Relocate MODULE_PATH.
1445	* libgst/dict.c: Relocate paths placed in the Smalltalk dictionary.
1446	* libgst/files.c: Relocate image and kernel paths.  Apply default
1447	executable path.
1448	* libgst/files.h: Remove _gst_executable_path.
1449	* libgst/gstpub.c: Add gst_relocate_path, gst_set_executable_path.
1450	* libgst/gstpub.h: Add gst_relocate_path, gst_set_executable_path.
1451	* libgst/sysdep.c: Add _gst_relocate_path, _gst_set_executable_path.
1452	* libgst/sysdep.h: Add _gst_relocate_path, _gst_set_executable_path.
1453
14542008-03-04  Paolo Bonzini  <bonzini@gnu.org>
1455
1456	* libgst/prims.def: Avoid mixed declarations and code.
1457
14582008-02-26  Paolo Bonzini  <bonzini@gnu.org>
1459
1460	* libgst/events.c: Add _gst_remove_fd_polling_handlers.
1461	* libgst/events.h: Declare it.
1462	* libgst/prims.def: Use it.
1463
14642008-02-19  Paolo Bonzini  <bonzini@gnu.org>
1465
1466	* libgst/cint.c: Don't specify the path to ffi.h.
1467
14682008-02-13  Paolo Bonzini  <bonzini@gnu.org>
1469
1470	* libgst/re.c: Don't convert read-only strings to Regexes,
1471	convert mutable strings instead.
1472
14732008-02-12  Paolo Bonzini  <bonzini@gnu.org>
1474
1475	* libgst/lex.c: Improve the precision of reading 0.1.
1476
14772008-02-11  Paolo Bonzini  <bonzini@gnu.org>
1478
1479	* libgst/oop.c: Move inclusion of sigsegv.h...
1480	* libgst/gstpriv.h: ... here.
1481
14822008-02-11  Paolo Bonzini  <bonzini@gnu.org>
1483
1484	* libgst/vm.def: Microoptimization of + and - (avoid shifts).
1485	* libgst/gstpriv.h: Microoptimization of integer overflow detection.
1486
14872008-01-25  Paolo Bonzini  <bonzini@gnu.org>
1488
1489	* libgst/mpz.c: Fix #divExact: for huge numerator and small
1490	denominator.
1491
14922008-01-17  Tony Garnock-Jones  <tonygarnockjones@gmail.com>
1493
1494	* libgst/prims.def: Differentiate the return value for the
1495	two processes.
1496
14972008-01-15  Paolo Bonzini  <bonzini@gnu.org>
1498
1499	* libgst/prims.def: Do not pop arguments that end up in an
1500	object that the primitive creates.
1501
15022008-01-14  Paolo Bonzini  <bonzini@gnu.org>
1503
1504	* libgst/prims.def: Fix #signal:atMilliseconds: for negative
1505	argument.
1506
15072008-01-07  Paolo Bonzini  <bonzini@gnu.org>
1508
1509	* libgst/save.c: Disable copy-on-write if libsigsegv is not
1510	available.
1511
15122008-01-07  Paolo Bonzini  <bonzini@gnu.org>
1513
1514	* libgst/oop.c: Move definition of NO_SIGSEGV_HANDLING...
1515	* libgst/oop.h: ... here.
1516
15172008-01-07  Paolo Bonzini  <bonzini@gnu.org>
1518
1519	* libgst/mpz.c: Don't fail for 0 divExact: x.
1520
15212008-01-06  Paolo Bonzini  <bonzini@gnu.org>
1522
1523	* libgst/prims.def: Use gst_invoke_hook.
1524
15252008-01-05  Paolo Bonzini  <bonzini@gnu.org>
1526
1527	* libgst/comp.c: Remove _gst_had_error.
1528	* libgst/comp.h: Remove _gst_had_error.
1529	* libgst/lex.c: Add _gst_had_error and _gst_error_recovery, use the
1530	latter in scan_newline.
1531	* libgst/lex.h: Add _gst_had_error and _gst_error_recovery.
1532	* libgst/gst-parse.c: Nest error recovery jmp_bufs when
1533	_gst_push_temporaries_dictionary is used.  Don't call _gst_free_tree
1534	when an error is recovered.  Set _gst_error_recovery in recover_error
1535	and look for ERROR_RECOVERY tokens too.  Don't define TOKEN_SEP.
1536	* libgst/gst-parse.h: Remove need for TOKEN_SEP definition.  Add
1537	ERROR_RECOVERY token.
1538
15392008-01-03  Paolo Bonzini  <bonzini@gnu.org>
1540
1541	* libgst/lex.c: Do not imply '.' after assignment operator.
1542
15432007-12-18  Paolo Bonzini  <bonzini@gnu.org>
1544
1545	* libgst/prims.def: Fix right #bitShift: with high RHS and LHS<0.
1546	* libgst/vm.def: Fix right #bitShift: with high RHS and LHS<0.
1547
15482007-12-17  Paolo Bonzini  <bonzini@gnu.org>
1549
1550	* libgst/oop.c (check_weak_refs): Undo part, only fix the thinko.
1551	(sweep_oop): Undo previous change.
1552
15532007-12-17  Paolo Bonzini  <bonzini@gnu.org>
1554
1555	* libgst/oop.c (check_weak_refs): Make dead weak objects non-weak,
1556	fix thinko.
1557	(sweep_oop): Don't make dead weak objects non-weak.
1558
15592007-12-17  Paolo Bonzini  <bonzini@gnu.org>
1560
1561	* libgst/genpr-parse.y: Declare _gst_primitives_md5 as unsigned char.
1562	* libgst/interp.h: Ditto.
1563
15642007-12-10  Paolo Bonzini  <bonzini@gnu.org>
1565
1566	* libgst/gstpub.h: Declare functions only accessible via the VMProxy.
1567	* libgst/gstpub.c: Define them.
1568
15692007-12-10  Paolo Bonzini  <bonzini@gnu.org>
1570
1571	* libgst/alloc.c: Never override malloc.
1572	* libgst/heap.c: Never defer to sbrk.
1573
15742007-12-10  Paolo Bonzini  <bonzini@gnu.org>
1575
1576	* libgst/interp.c: Don't yield in resume_process.
1577
15782007-12-10  Paolo Bonzini  <bonzini@gnu.org>
1579
1580	* libgst/md-config.h: Disable third register variable for i386.
1581
15822007-12-09  Paolo Bonzini  <bonzini@gnu.org>
1583
1584	* libgst/xlat.c: Fix code generation for DeferredVariableBinding store.
1585
15862007-12-09  Paolo Bonzini  <bonzini@gnu.org>
1587
1588	* libgst/xlat.c: Fix IR generation for DeferredVariableBinding store.
1589
15902007-12-06  Paolo Bonzini  <bonzini@gnu.org>
1591
1592        * libgst/interp.c: Extract part of suspend_process into
1593        remove_process_from_list.  Use it in resume_process if the process
1594        is active.  Yield the active process.
1595        * libgst/prims.def: Add VMpr_Process_suspend.
1596
15972007-11-29  Paolo Bonzini  <bonzini@gnu.org>
1598
1599	* libgst/dict.inl: Loosen tests of usage of instantiate and
1600	instantiate_with.
1601
16022007-11-22  Paolo Bonzini  <bonzini@gnu.org>
1603
1604	* gst-tool.c: Test both EXEEXT and ARGV_EXEEXT.
1605	* libgst/cint.c: Fix my_mkdir for Cygwin.
1606	Reported by Freddie Akeroyd.
1607
16082007-11-19  Paolo Bonzini  <bonzini@gnu.org>
1609
1610	* libgst/sysdep.c: Provide a default MAXSYMLINKS, for Cygwin.
1611	Reported by Freddie Akeroyd.
1612
16132007-11-18  Paolo Bonzini  <bonzini@gnu.org>
1614            Freddie Akeroyd  <F.A.Akeroyd@rl.ac.uk>
1615
1616	* gst-tool.c: Use EXEEXT.  Look for backslashes as directory
1617	separators.
1618	* libgst/cint.c: Add my_mkdir and my_mkdtemp.
1619	* libgst/sysdep.c: Fix syntax error under Win32.
1620
16212007-11-18  Paolo Bonzini  <bonzini@gnu.org>
1622
1623	* main.c: Don't use asprintf.
1624
16252007-11-13  Paolo Bonzini  <bonzini@gnu.org>
1626
1627	* libgst/prims.def: Use pow/powl.
1628
16292007-11-11  Paolo Bonzini  <bonzini@gnu.org>
1630
1631	* libgst/files.c: Use _gst_file_is_newer.
1632	* libgst/sysdep.c: Remove _gst__gst_get_file_modify_time, add
1633	_gst_file_is_newer.
1634	* libgst/sysdep.h: Likewise.
1635
16362007-11-09  Paolo Bonzini  <bonzini@gnu.org>
1637
1638	* libgst/input.c: Return false if file cannot be opened by
1639	gst_process_file, and set errno appropriately.
1640	* libgst/files.c: Use errno on return from gst_process_file.
1641	* main.c: Use errno on return from gst_process_file.
1642	* gst-tool.c: Use errno on return from gst_process_file.
1643
16442007-10-25  Paolo Bonzini  <bonzini@gnu.org>
1645
1646	* libgst/re.c: Call init_re from exported functions.
1647
16482007-10-21  Paolo Bonzini  <bonzini@gnu.org>
1649
1650	* libgst/comp.c: Add brackets to source code of #methodsFor:.
1651	Set isOldSyntax bit of the CompiledMethod header.
1652	* libgst/comp.h: Add isOldSyntax bit.
1653	* libgst/gst-parse.c: Parse isolated methods with new syntax.
1654	* libgst/tree.c: Add isOldSyntax argument to _gst_make_method.
1655	* libgst/tree.h: Likewise, and add it to AST.
1656
16572007-10-12  Paolo Bonzini  <bonzini@gnu.org>
1658
1659	* libgst/gst-parse.c: Don't replace instance variables except
1660	in the first declaration inside a subclass declaration.
1661
16622007-10-12  Paolo Bonzini  <bonzini@gnu.org>
1663
1664	* libgst/dict.inl: Use another scramble function suggested by
1665	Andres Valloud.
1666
16672007-10-09  Paolo Bonzini  <bonzini@gnu.org>
1668
1669	* libgst/save.c: Break hard links when saving.
1670
16712007-10-09  Paolo Bonzini  <bonzini@gnu.org>
1672
1673	* libgst/dict.inl: Do rotations correctly in scramble.
1674
16752007-10-08  Paolo Bonzini  <bonzini@gnu.org>
1676
1677	* libgst/dict.c: Add necessary class variables for rewrite.
1678
16792007-10-01  Stephen Compall  <scompall@nocandysw.com>
1680
1681	* libgst/re.c: Add init_re, registering ASCII case table.
1682
16832007-09-27  Freddie Akeroyd  <F.A.Akeroyd@rl.ac.uk>
1684	    Paolo Bonzini  <bonzini@gnu.org>
1685
1686	* libgst/cint.c: Wrap symlink to avoid errors in case the prototype
1687	is absent.
1688	* libgst/prims.def: Disable ENOTSOCK checking if constant not defined.
1689
16902007-09-27  Paolo Bonzini  <bonzini@gnu.org>
1691
1692	* libgst/gst-parse.c: Strengthen error checking for wrong
1693	"Class >> method [ ... ]" stanzas.
1694
16952007-09-25  Paolo Bonzini  <bonzini@gnu.org>
1696
1697	* libgst/re.c: Cache any read-only string literal.
1698
16992007-09-24  Paolo Bonzini  <bonzini@gnu.org>
1700
1701	* libgst/gst-parse.c: Fix NULL dereference on Smalltalk subclass:
1702	Foo [ ].
1703
17042007-09-24  Paolo Bonzini  <bonzini@gnu.org>
1705
1706	* libgst/md-config.h: Disable register allocation tricks if not
1707	optimizing, as well as third register on Apple compilers.
1708
17092007-09-19  Paolo Bonzini  <bonzini@gnu.org>
1710
1711	* libgst/re.c: Yet another GC problem.
1712
17132007-09-17  Paolo Bonzini  <bonzini@gnu.org>
1714
1715	* libgst/comp.c: Fix GC problem with attributes.
1716
17172007-09-15  Paolo Bonzini  <bonzini@gnu.org>
1718
1719	* libgst/oop.h: Move NO_SIGSEGV_HANDLING...
1720	* libgst/oop.c: ... here.
1721	* libgst/save.c: Make writable mmap if defined.
1722
17232007-09-13  Paolo Bonzini  <bonzini@gnu.org>
1724
1725	* libgst/interp.inl: Fix 64-bit cleanliness error.
1726
17272007-09-12  Paolo Bonzini  <bonzini@gnu.org>
1728
1729	* libgst/save.c: Open image file with r+ and truncate it afterwards.
1730	* libgst/sysdep.c: Use O_CREAT for r+.
1731
17322007-09-03  Paolo Bonzini  <bonzini@gnu.org>
1733
1734	* libgst/input.c: Adjust by fileOffset when generating source string
1735	with _gst_counted_string_new.
1736
17372007-08-24  Paolo Bonzini  <bonzini@gnu.org>
1738
1739	* libgst/comp.c: Create deferred variable bindings with a path.
1740	Adjust calls to _gst_find_variable_binding.
1741	* libgst/dict.c: Add path variable to DeferredVariableBinding.
1742	* libgst/dict.h: Add path variable to struct
1743	gst_deferred_variable_binding.
1744	* libgst/sym.h: Remove last parameter from
1745	_gst_find_variable_binding.
1746	* libgst/sym.c: Assume last parameter of _gst_find_variable_binding
1747	to be true.  Adjust call to _gst_make_deferred_binding_constant.
1748	* libgst/tree.h: Adjust last parameter of
1749	_gst_make_deferred_binding_constant.
1750	* libgst/tree.c: Turn last parameter of _gst_find_variable_binding
1751	into a tree.  Support new constant types in _gst_print_tree.
1752
17532007-08-20  Paolo Bonzini  <bonzini@gnu.org>
1754
1755        * libgst/superop1.inl: Regenerate.
1756        * libgst/superop2.inl: Regenerate.
1757        * libgst/byte.def: Regenerate.
1758	* libgst/vm.def: Reenable superoperators.
1759	* libgst/opt.c: Reenable superoperators.
1760
17612007-08-20  Paolo Bonzini  <bonzini@gnu.org>
1762
1763	* libgst/comp.c: Make make_constant_oop global, adjust for new
1764	return value of _gst_find_variable_binding, create
1765	DeferredVariableBinding objects.  Compile store-into-
1766	variable to store+pop+push.  Adjust equal_constant to
1767	support CONST_DEFERRED_BINDING and adjusting for the new return value
1768	of _gst_find_variable_binding.
1769	* libgst/comp.h: Declare _gst_find_variable_binding.
1770	* libgst/dict.c: Add DeferredVariableBinding.
1771	* libgst/dict.h: Add DeferredVariableBinding and
1772	struct gst_deferred_variable_binding.
1773	* libgst/files.c: Add DeferBinding.st, load LookupKey hierarchy early.
1774	* libgst/opt.c: Temporarily disable superoperators.  Pass LookupKeys
1775	in the verifier.
1776	* libgst/sym.c: Return a tree_node from _gst_find_variable_binding,
1777	adjust _gst_find_variable, add _gst_get_undeclared_dictionary.
1778	* libgst/sym.h: Adjust declarations.
1779	* libgst/tree.c: Add _gst_make_deferred_binding_constant.
1780	* libgst/tree.h: Add _gst_make_deferred_binding_constant.
1781
17822007-08-19  Paolo Bonzini  <bonzini@gnu.org>
1783
1784	* libgst/vm.def: Support non-Associations storing global variables.
1785	* libgst/xlat.c: Support non-Associations storing global variables.
1786	* libgst/print.c: Support LookupKeys storing global variables.
1787	* libgst/dict.c: Reload _gst_lookup_key_class on startup.
1788
17892007-08-13  Paolo Bonzini  <bonzini@gnu.org>
1790
1791	* libgst/dict.c: Dereference the VariableBinding stored in a CType.
1792
17932007-08-13  Paolo Bonzini  <bonzinI@gnu.org>
1794
1795	* libgst/cint.c: Remove enum cdata_type, moved to cint.h.  Reorder
1796	c_type_name and type_map accordingly.  Add CDATA_UCHAR, CDATA_SHORT,
1797	and CDATA_USHORT.  Convert from/to them appropriately in
1798	push_smalltalk_obj, get_ffi_type.
1799	* libgst/cint.h: Add enum cdata_type.
1800	* libgst/prims.def: Use enum cdata_type values.
1801	* libgst/sym.c: Add symbols for #short, #uShort, #uChar.
1802	* libgst/sym.h: Add symbols for #short, #uShort, #uChar.
1803
18042007-08-13  Paolo Bonzini  <bonzinI@gnu.org>
1805
1806	* libgst/interp.c: Fix GC bug in _gst_prepare_execution_environment.
1807
18082007-08-13  Paolo Bonzini  <bonzinI@gnu.org>
1809
1810	* libgst/callin.c: Use _gst_c_object_new instead of
1811	_gst_c_object_new_typed.
1812	* libgst/cint.c: Likewise.
1813	* libgst/dict.inl: Likewise.
1814	* libgst/dict.c: Remove _gst_c_object_type_ctype and _gst_c_type_new.
1815	Add a new parameter to _gst_c_object_new_typed and call it
1816	_gst_c_object_new; dereference the binding of the TYPEOOP.
1817	Remove _gst_alloc_cobject.
1818	* libgst/prims.def: Remove VMpr_CObject_alloc.  Check receiver
1819	type for VMpr_CObject_allocType.  Use _gst_c_object_new instead of
1820	_gst_c_object_new_typed.
1821
18222007-08-12  Paolo Bonzini  <bonzinI@gnu.org>
1823
1824        * libgst/comp.c: Make literals read-only in make_oop_constant.
1825        * libgst/dict.inl: Make Float* and Character literals read-only.
1826
18272007-07-20  Paolo Bonzini  <bonzini@gnu.org>
1828
1829	* libgst/files.c: Load VFSZip.st.
1830
18312007-07-20  Paolo Bonzini  <bonzini@gnu.org>
1832
1833	* libgst/input.h: Fix prototype declaration when readline is not
1834	available.
1835
18362007-07-19  Paolo Bonzini  <bonzini@gnu.org>
1837
1838	* libgst/input.h: Turn second parameter of _gst_set_stream_info to OOP.
1839	* libgst/input.c: Likewise.
1840	* libgst/prims.def: Remove fileIn primitive.  Remove check on
1841	file validity from fileInLine primitive.  Adjust call to
1842	_gst_set_stream_info.
1843
18442007-07-17  Stephen Compall  <scompall@nocandysw.com>
1845
1846	* libgst/prims.def: Rename compileString primitives to
1847	primCompile.
1848	* libgst/xlat.c: Mention #primCompile:.
1849
18502007-07-12  Paolo Bonzini  <bonzini@gnu.org>
1851
1852	* libgst/oop.c: When compacting, do not discard grey pages from
1853	the loaded space.  Add _gst_print_grey_list.
1854	* libgst/oop.h: Add fields to delimit loaded space to
1855	struct memory_space.
1856	* libgst/save.c: Fill them in.
1857
18582007-07-12  Paolo Bonzini  <bonzini@gnu.org>
1859
1860	* libgst/dict.c: Fix pasto in _gst_grow_dictionary.
1861
18622007-07-11  Paolo Bonzini  <bonzini@gnu.org>
1863
1864	* libgst/interp-bc.inl: Reset _gst_except_flag to false at beginning
1865	of monitor_byte_codes.
1866
18672007-07-10  Paolo Bonzini  <bonzini@gnu.org>
1868
1869	* libgst/interp.c: Add break.
1870
18712007-07-10  Paolo Bonzini  <bonzini@gnu.org>
1872
1873	* libgst/lib.c: Rename...
1874	* libgst/files.c: ... to this.
1875
1876	* libgst/files.c: Change "gst_" functions to "_gst_".
1877	* libgst/callin.c: Move gst_interpreter_proxy and _gst_init_vmproxy...
1878	* libgst/gstpub.c: ... here (new file).  Add "gst_*" functions.
1879	* libgst/callin.h: Rename *cobject functions to *c_object.
1880
1881	* libgst/interp.c: Change bool_addr_index to _gst_{get,set}_var.
1882	* libgst/prims.def: Switch to new interface.
1883
1884	* libgst/files.c: Rename find_kernel_file to _gst_find_file, drop
1885	second parameter.
1886	* libgst/input.c: Add _gst_process_stdin, _gst_process_file.
1887	* libgst/gstpub.c: Add public and VMProxy counterparts.
1888
1889	* libgst/comp.c: Turn _gst_invoke_hook parameter into an enum.
1890	* libgst/files.c: Turn _gst_invoke_hook parameter into an enum.
1891	* libgst/save.c: Turn _gst_invoke_hook parameter into an enum.
1892	* libgst/gstpub.c: Add public and VMProxy counterparts.
1893
1894	* libgst/input.c: Add _gst_no_tty and turn "prompt" field into char *.
1895	* libgst/files.c: Remove --emacs-process and -S handling.
1896
1897	* libgst/files.c: Create _gst_initialize out of init_paths and
1898	_gst_init_smalltalk, remove SMALLTALK_KERNEL and SMALLTALK_IMAGE
1899	handling out of init_paths, remove option handling, always derive
1900	image path from image file.
1901	* libgst/callin.c: Change _gst_init_smalltalk calls to _gst_initialize.
1902
1903	* libgst/gst.h: Add enums for above changes.
1904
19052007-07-05  Paolo Bonzini  <bonzini@gnu.org>
1906
1907	* libgst/prims.def: Fix "==" vs. "=" typo.
1908	* libgst/sysdep.c: Fix previous change for Linux.
1909
19102007-07-05  Paolo Bonzini  <bonzini@gnu.org>
1911
1912	* libgst/lib.c: Add _gst_executable_path.
1913	* libgst/lib.h: Set it in gst_smalltalk_args.
1914	* libgst/dict.c: Set CSymbols.ExecutableFileName.
1915	* libgst/sysdep.c: Add _gst_find_executable.
1916	* libgst/sysdep.h: Declare _gst_find_executable.
1917
19182007-07-04  Paolo Bonzini  <bonzini@gnu.org>
1919
1920        * libgst/cint.c: Add binding for mkdtemp and chmod.
1921
19222007-07-03  Freddie Akeroyd  <F.A.Akeroyd@rl.ac.uk>
1923	    Paolo Bonzini  <bonzini@gnu.org>
1924
1925	* libgst/alloc.c: Remove #undef small.
1926	* libgst/alloc.h: Move it here.
1927	* libgst/prims.def: Flush stdio files before quitting.
1928	* libgst/sysdep.c: Implement _gst_recv with recvfrom.
1929
19302007-07-03  Paolo Bonzini  <bonzini@gnu.org>
1931
1932	* libgst/dict.c: Export LibexecPath.
1933
19342007-07-01  Paolo Bonzini  <bonzini@gnu.org>
1935
1936	* libgst/prims.def: Remove bogus check on file in of FileDescriptor
1937	objects.
1938
19392007-06-28  Paolo Bonzini  <bonzini@gnu.org>
1940
1941	* libgst/lib.c: Ensure null termination of _gst_image_file_path.
1942
19432007-06-25  Paolo Bonzini  <bonzini@gnu.org>
1944
1945	* libgst/lex.c: Don't lose on integer literals followed by identifiers.
1946
19472007-06-24  Paolo Bonzini  <bonzini@gnu.org>
1948
1949	* libgst/lib.c: Put full path names into kernel/image paths and into
1950	the image file name.
1951	* libgst/lib.h: Adjust constness.
1952
19532007-06-19  Paolo Bonzini  <bonzini@gnu.org>
1954
1955	* libgst/sysdep.c: Use GetFullPathName under Windows.
1956
19572007-06-18  Paolo Bonzini  <bonzini@gnu.org>
1958
1959	* libgst/sysdep.c: Use utime if utimes missing.
1960	* tests/fileext.st: Run tests using Unix file separator.
1961
19622007-06-15  Freddie Akeroyd  <F.A.Akeroyd@rl.ac.uk>
1963	    Paolo Bonzini  <bonzini@gnu.org>
1964
1965	* libgst/cint.c: Remove my_utime.
1966	* libgst/sysdep.c: Move it here as _gst_set_file_access_times.
1967	* libgst/sysdep.h: Declare it.
1968	* libgst/dict.c: Add CSymbols.PathSeparator.
1969
19702007-06-14  Paolo Bonzini  <bonzini@gnu.org>
1971
1972	* libgst/sysdep.c: Try VirtualAlloc with NULL address if a fixed
1973	address fails.
1974
19752007-06-11  Paolo Bonzini  <bonzini@gnu.org>
1976
1977        * libgst/cint.c: Add symlink function.
1978
19792007-06-07  Paolo Bonzini  <bonzini@gnu.org>
1980
1981	* libgst/comp.c: Initialize an attribute's arguments array before
1982	filling it, a GC may trigger while it is being created.
1983
19842007-06-06  Paolo Bonzini  <bonzini@gnu.org>
1985
1986	* libgst/dict.c: Add Continuation class.
1987	* libgst/dict.h: Add Continuation class.
1988	* libgst/interp.c: Add resume_suspended_context, extracted from
1989	change_process_context.
1990	* libgst/interp.h: Add Continuation class definition.
1991	* libgst/prims.def: Add a primitive for continuations.
1992	* libgst/lib.c: Add Continuation.st and Generator.st.
1993
19942007-06-06  Paolo Bonzini  <bonzini@gnu.org>
1995
1996	* libgst/input.c: Be quiet, but still automatically add periods, when
1997	in Emacs mode.
1998	* libgst/comp.c: Likewise.
1999
20002007-06-05  Paolo Bonzini  <bonzini@gnu.org>
2001
2002	* libgst/interp.h: Add PRIM_SHUTDOWN_WRITE.
2003	* libgst/interp.c: Implement it.  Fix bug in PRIM_MK_TEMP.
2004	* libgst/sysdep.c: Use pipes/sockets instead of pty's.
2005
20062007-06-01  Paolo Bonzini  <bonzini@gnu.org>
2007
2008	* libgst/lib.c: Load StreamOps.st.
2009
20102007-05-31  Paolo Bonzini  <bonzini@gnu.org>
2011
2012	* libgst/gst-parse.c: Support [:arg1 :arg2] syntax for blocks.
2013
20142007-05-29  Paolo Bonzini  <bonzini@gnu.org>
2015
2016	* libgst/gst-parse.c: Revert meaning of the last parameter
2017	to parse_doit.	Skip over the final '!' in parse_chunks,
2018	don't do so in parse_doit and parse_method_list.  Exit
2019	parse_namespace_definition upon finding a '!'.
2020
20212007-05-26  Paolo Bonzini  <bonzini@gnu.org>
2022
2023	* libgst/lex.c: Pass radix when converting ScaledDecimals like 2r1.1s.
2024	* libgst/sym.c: Change #asScaledDecimal:scale: to
2025	#asScaledDecimal:radix:scale:.
2026	* libgst/sym.h: Likewise.
2027
20282007-05-25  Daniele Sciascia  <daniele.sciascia@lu.unisi.ch>
2029
2030	* libgst/dict.c: Turn _gst_find_shared_pool_variable into
2031	_gst_namespace_association_at, add _gst_namespace_at.
2032	* libgst/dict.h: Declare it.
2033	* libgst/gst-parse.c: Support attributes both before and after
2034	temporaries.  Improve error recovery.  Set the correct namespace
2035	when extending a class.  Fix error locations.  Support class
2036	definition in a namespace definition.  Replace "Class protocol" with
2037	"Foo class".  Support subclassing nil.  Lookup classes in the
2038	superspaces too.
2039	* libgst/sym.c: Use _gst_namespace_association_at.
2040
20412007-05-24  Paolo Bonzini  <bonzini@gnu.org>
2042
2043	* libgst/dict.c: Don't trust {FLT,DBL,LDBL}_DIG.
2044
20452007-05-23  Paolo Bonzini  <bonzini@gnu.org>
2046
2047	* libgst/lib.c: Remove TokenStream.st.  Fix pasto.
2048	* libgst/dict.c: Remove TokenStream and _gst_token_stream_class.
2049	* libgst/dict.h: Remove _gst_token_stream_class.
2050
20512007-05-07  Stephen Compall  <s11@member.fsf.org>
2052
2053	* libgst/sysdep.c: Fix return value of anon_mmap_commit.
2054
20552007-04-18  Paolo Bonzini  <bonzini@gnu.org>
2056
2057	* libgst/md-config.h: Fix spelling of __PIC__.
2058
20592007-04-17  Paolo Bonzini  <bonzini@gnu.org>
2060
2061	* libgst/comp.c: Move all FileSegment stuff to input.c
2062	* libgst/input.c: Rename _gst_get_cur_string to _gst_get_source_string
2063	and return FileSegments or substrings here.  Concatenate pieces of
2064	readline input like in a STREAM_OOP.
2065	* libgst/input.h: Adjust _gst_get_cur_string prototype.
2066
20672007-04-17  Paolo Bonzini  <bonzini@gnu.org>
2068
2069	* libgst/input.c: More Smalltalk Stream fixes.
2070
20712007-04-17  Paolo Bonzini  <bonzini@gnu.org>
2072
2073	* libgst/lex.c: Load SysDict.st early in the bootstrap process.
2074	* libgst/prims.def: Remove VMpr_Dictionary_atPut.
2075
20762007-04-17  Paolo Bonzini  <bonzini@gnu.org>
2077
2078	* libgst/input.c: Fix latent bug with Smalltalk Stream parsing.
2079
20802007-04-17  Paolo Bonzini  <bonzini@gnu.org>
2081
2082	* libgst/lex.c: Fix bug if first line entered at REPL is empty.
2083
20842007-04-16  Paolo Bonzini  <bonzini@gnu.org>
2085
2086	* libgst/interp-bc.inl: Fix building on s390.
2087
20882007-04-11  Daniele Sciascia  <daniele.sciascia@lu.unisi.ch>
2089
2090	* libgst/gst-parse.c: Fix locations in error messages.
2091	* libgst/lex.c: Reset parentheses only when showing prompts.
2092
20932007-04-11  Daniele Sciascia  <daniele.sciascia@lu.unisi.ch>
2094
2095	* libgst/gst-parse.c: Fix parsing of "Eval [ foo := ]".
2096
20972007-04-11  Paolo Bonzini  <bonzini@gnu.org>
2098            Daniele Sciascia  <daniele.sciascia@lu.unisi.ch>
2099
2100	* libgst/gst-parse.c: Improved error recovery.
2101
21022007-04-11  Paolo Bonzini  <bonzini@gnu.org>
2103            Daniele Sciascia  <daniele.sciascia@lu.unisi.ch>
2104
2105	* libgst/gst-parse.c: Fix parsing when expressions were required
2106	but not found.
2107
21082007-04-11  Paolo Bonzini  <bonzini@gnu.org>
2109            Daniele Sciascia  <daniele.sciascia@lu.unisi.ch>
2110
2111	* libgst/dict.c: Load _gst_binding_dictionary_class on runtime.
2112	* libgst/gst-parse.c: Fix setting up class variables.
2113
21142007-04-11  Daniele Sciascia  <daniele.sciascia@lu.unisi.ch>
2115
2116	* libgst/comp.c: Make compute_keyword_selector public.
2117	* libgst/comp.h: Likewise.
2118	* libgst/gst-parse.c: Lots of cool new stuff.
2119	* libgst/gst-parse.h: Provide prototype for _gst_print_tokens.
2120
21212007-04-11  Paolo Bonzini  <bonzini@gnu.org>
2122
2123	* libgst/comp.c: Add undeclared parameter to
2124	_gst_exeecute_statements.  Make a statement list if necessary.
2125	Adjust callers.  Add CONST_BINDING case to equal_constant and
2126	make_constant_oop.
2127	* libgst/comp.h: Adjust prototypes.
2128	* libgst/gst-parse.c: Rewrite parse_doit.  Set undeclared parsing
2129	around method compilation.  Don't check errors from
2130	_gst_make_binding_constant
2131	* libgst/gstpriv.h: Load sym.h early.
2132	* libgst/input.c: Don't return true in _gst_get_cur_stream_prompt
2133	for emacs mode.
2134	* libgst/interp.c: Remove bogus comment.
2135	* libgst/interp.h: Reword bogus comment.
2136	* libgst/lex.c: Guess if a period should be added at end of line.
2137	* libgst/lib.c: Set undeclared parsing around file loading.
2138	* libgst/prims.def: Fix warning.  Set undeclared parsing around filein.
2139	* libgst/sym.c: Add possibility to store undeclared variablers into
2140	a custom dictionary.
2141	* libgst/sym.h: Add related definitions.
2142	* libgst/tree.c: Create a CONST_BINDING in _gst_make_binding_constant.
2143	* libgst/tree.h: Add CONST_BINDING to const_type enum.
2144
21452007-03-30  Paolo Bonzini  <bonzini@gnu.org>
2146
2147	* libgst/comp.c: Change _gst_declare_tracing to int, use value of 2
2148	for tracing variables intead _gst_trace_kernel_*.
2149	* libgst/comp.h: Likewise.
2150	* libgst/interp.c: Likewise.  Adapt bool_addr_index to return int *.
2151	* libgst/interp.h: Likewise.
2152	* libgst/prims.def: Support passing/returning an int in trace flag
2153	get/set primitives.
2154	* libgst/lib.c: Remove -d, -e options, and map old -[de] to new
2155	-[DE], allowing the user to specify them multiple times.  Keep only
2156	long version of -p, make option -Q synonym of -q (it was in the
2157	documentation).  Kill _gst_trace_kernel_*.  Only valid verbosity
2158	values are now 1/2/3.
2159	* libgst/oop.h: Change _gst_gc_message to int.
2160	* libgst/oop.c: Likewise, adapting to changes to the verbosity values.
2161
21622007-03-28  Paolo Bonzini  <bonzini@gnu.org>
2163
2164	* libgst/gstpriv.h: Support MacOS X/PPC macros to use lwbrx.
2165	* libgst/save.c: Fix primitive table checksum for 64-biy systems.
2166
21672007-03-28  Paolo Bonzini  <bonzini@gnu.org>
2168
2169	* libgst/lex.c: Fix parsing of #-123.
2170
21712007-03-20  Paolo Bonzini  <bonzini@gnu.org>
2172
2173	* libgst/comp.c: Look for <category: ...> attribute, write result
2174	in this_method_category, pick it in _gst_make_new_method.  Add a
2175	default category argument to _gst_make_new_method.  Always create
2176	a MethodInfo object in _gst_make_new_method.
2177	* libgst/comp.h: Adjust _gst_make_new_method prototype.
2178	* libgst/prims.def: Adjust _gst_make_new_method prototype.
2179	* libgst/sym.c: Add _gst_category_symbol.
2180	* libgst/sym.h: Add _gst_category_symbol.
2181
21822007-03-19  Paolo Bonzini  <bonzini@gnu.org>
2183
2184	* libgst/lib.c: Load Random.st after system is initialized.
2185	* libgst/dict.c: Remove Random class and _gst_random_class.
2186	* libgst/dict.h: Remove _gst_random_class.
2187
21882007-03-12  Paolo Bonzini  <bonzini@gnu.org>
2189
2190	* libgst/comp.c: Fix off-by-one error.
2191	* libgst/input.c: Fix line/column assignment.  Don't provide
2192	method source for readline stream.
2193
21942007-03-08  Paolo Bonzini  <bonzini@gnu.org>
2195
2196	* libgst/comp.c: Create FileSegment and MethodInfo object in
2197	_gst_make_new_method, pass the MethodInfo down to method_new.
2198
21992007-02-22  Paolo Bonzini  <bonzini@gnu.org>
2200
2201	* libgst/oop.c: Remove two unused variables.
2202
2203	* libgst/comp.c: Add start/end position parameters to method_new,
2204	method_info_new, file_segment_new, _gst_make_new_method.  Adjust
2205	callers.  Get ending location of the method in _gst_execute_statements.
2206	* libgst/comp.h: Adjust prototype of _gst_make_new_method.
2207	* libgst/gst-parse.c: Don't call _gst_clear_method_start_pos.
2208	Get ending location of the method in parse_method.
2209	* libgst/gst-parse.h: Add file_offset field to YYLTYPE.
2210	* libgst/input.c: Initialize fileOffset to -1 for a new stream,
2211	and with lseek for a new file stream.  Update it when reading
2212	from a file into the buffer.  Use it to avoid lseeking during the
2213	parsing, so that _gst_get_location can quickly compute the file offset
2214	and store it into the YYLTYPE.  Make _gst_get_location return the
2215        YYLTYPE.  Remove _gst_get_cur_file_pos, _gst_get_method_start_pos and
2216        _gst_clear_method_start_pos, and the field they used in struct stream.
2217        * libgst/input.h: Remove _gst_get_cur_file_pos,
2218	_gst_get_method_start_pos and _gst_clear_method_start_pos, update the
2219	prototype of _gst_get_location and make it pure.
2220	* libgst/lex.c: Adjust calls to _gst_get_location.
2221	* libgst/prims.def: Adjust call to _gst_make_new_method.
2222	* libgst/tree.c: Accept ending location in _gst_make_method.
2223	* libgst/tree.h: Add new field to struct method_node and prototype of
2224	_gst_make_method.
2225
22262007-02-10  Paolo Bonzini  <bonzini@gnu.org>
2227
2228	* libgst/dict.c: Remove KernelFileLocalPath.  Don't touch
2229	KernelFilePath on reload.  Export KernelFileUserPath.
2230	* libgst/lib.c: Add --image-directory and --kernel-directory.
2231	Add a struct loaded_file used to store files given on
2232	the command line.  Find path of user init/user pre/site
2233	pre files in init_paths, delete load_user_init_file and
2234	load_user_pre_image_file.  Call init_paths after parse_args.
2235	Rewrite find_kernel_file, place kernel override files
2236	in ~/.st too (if one needs per-image overrides they can
2237	use --kernel-directory).  Remove some variables that are
2238	now unused.  Simplify ok_to_load_binary as the new semantics
2239	remove the need for some checks.  Export the path to ~/.st in
2240	_gst_user_file_base_path.
2241	* libgst/lib.h: Export _gst_user_file_base_path.
2242	* libgst/sysdep.c: Canonicalize path in _gst_get_full_file_name.
2243
22442007-02-05  Paolo Bonzini  <bonzini@gnu.org>
2245
2246	* libgst/dict.c: Add variables and declarations for weak objects.
2247	* libgst/dict.h: Add variables for weak objects.
2248	* libgst/lib.c: Load WeakObjects.st as part of the kernel classes.
2249
22502007-01-29  Paolo Bonzini  <bonzini@gnu.org>
2251
2252	* libgst/lex.c: Rename ipowl to mul_powl, support gradual underflow.
2253
22542007-01-28  Paolo Bonzini  <bonzini@gnu.org>
2255
2256	* libgst/prims.def: Use truncl and lrint to implement
2257	conversion from float to integer.
2258
22592007-01-28  Paolo Bonzini  <bonzini@gnu.org>
2260
2261	* libgst/mpz.c: Fix right shift bug.
2262
22632007-01-27  Paolo Bonzini  <bonzini@gnu.org>
2264
2265	* libgst/lex.c: Clear obstack after parsing radix.
2266
22672007-01-15  Paolo Bonzini  <bonzini@gnu.org>
2268
2269	* libgst/prims.def: Fix error checking in previous check in.
2270
22712007-01-11  Paolo Bonzini  <bonzini@gnu.org>
2272
2273	* libgst/prims.def: When changing an object's class, allow the
2274	new class to not be a kind of Behavior, as long as the superclass
2275	flagged in it is.
2276
22772007-01-03  Paolo Bonzini  <bonzini@gnu.org>
2278
2279        * libgst/events.c: Avoid infinite loop.
2280
22812006-12-28  Paolo Bonzini  <bonzini@gnu.org>
2282
2283	* libgst/dict.c: Change _gst_init_dictionary_on_image_load to be
2284	whether the primitive table's checksum is ok.  If it is, just copy
2285	the default primitive table just like in _gst_init_dictionary.
2286	* libgst/dict.h: Adjust for above change.
2287	* libgst/genpr-parse.y: Compute MD5 of DEF_FIL as checksum and
2288	print it.
2289	* libgst/interp.h: Declare _gst_primitives_md5.
2290	* libgst/save.c: Save its contents, and compare it to pass the new flag
2291	to _gst_init_dictionary_on_image_load.  Move checks from load_snapshot
2292	to load_file_version.
2293
22942006-12-28  Paolo Bonzini  <bonzini@gnu.org>
2295
2296	* libgst/gstpriv.h: Remove F_FREE.
2297	* libgst/oop.c: Remove loops setting flags to F_FREE.  Set flags to 0
2298	instead of F_FREE elsewhere.
2299	* libgst/oop.h: Fix wrong comment.
2300	* libgst/oop.inl: Adjust IS_OOP_FREE.
2301	* libgst/print.c: Use IS_OOP_FREE.
2302	* libgst/save.c: Set flags to 0 instead of F_FREE.  Use IS_OOP_FREE.
2303	Remove wrong comment.
2304
23052006-12-28  Paolo Bonzini  <bonzini@gnu.org>
2306
2307	* libgst/builtins.gperf: Remove _COLON from the enum for special
2308	bytecodes.
2309	* libgst/byte.def: Likewise.
2310	* libgst/vm.def: Likewise.
2311	* libgst/xlat.c: Likewise.
2312
2313	* libgst/comp.c: Remove the possibility to inline #perform:.
2314
2315	* libgst/byte.c: Turn _gst_builtin_selectors into an array of
2316	structs (instead of pointers).
2317	* libgst/opt.c: Likewise.
2318	* libgst/sym.c: Likewise.
2319	* libgst/vm.def: Use _gst_builtin_selectors instead of symbols
2320	defined in sym.c (not slower with the change above).
2321	* libgst/xlat.c: Only store the opcode in special_send_bytecodes and
2322	use _gst_builtin_selectors for the other pieces of information.
2323
2324	* libgst/dict.c: Don't reload the _gst_*_class variables unless
2325	necessary.  Pass the class to identity_dictionary_new and adjust the
2326	sole caller, _gst_valid_class_method_dictionary.  Split the
2327	creation of symbols in two parts (creating symbols, and populating
2328	the symbol table with SymLink objects); call _gst_restore_symbols
2329	when loading the image.  Remove _gst_directed_message_new_args.
2330	* libgst/interp.c: Remove commented out code to start call-ins through
2331	Process>>#startExecution:.
2332	* libgst/sym.c: Remove symbols for the special selectors.  New
2333	functions alloc_symbol_oop and alloc_symlink to support two-phase
2334	creation of symbols in the image.  Add _gst_smalltalk_namespace_symbol.
2335	New functions intern_string_fast and _gst_restore_symbols to support
2336	fast reloading of symbols when loading the image.
2337	* libgst/sym.h: Adjust for changes to sym.c.
2338
2339	* libgst/genvm-parse.y: Add const qualifier to yyprint.
2340
23412006-12-28  Paolo Bonzini  <bonzini@gnu.org>
2342
2343	* libgst/mpz.c: Fix warnings in _gst_mpz_divexact.
2344
23452006-12-28  Paolo Bonzini  <bonzini@gnu.org>
2346
2347	* libgst/gstpriv.h: Reserve three less bits to runtime flags, add
2348	F_LOADED.
2349	* libgst/oop.c: The address of loaded objects never changes, and
2350	they're always old.  Never compact loaded objects.  Never free them too.
2351	* libgst/print.c: Print loaded OOPs correctly.
2352	* libgst/save.c: Define and use buffer_advance.  Try reusing the
2353	mmap-ed area in load_normal_oops; free buffer in load_normal_oops
2354	only if copy-on-write is not used.  Mmap all the file in a
2355	single step, and using MAP_PRIVATE, and only do the "read" method
2356	in buffer_fill.  Rename use_mmap to buf_used_mmap.  Save objects with
2357	the old bit set and without the F_RUNTIME flags.
2358
23592006-12-22  Paolo Bonzini  <bonzini@gnu.org>
2360
2361	* libgst/mpz.c: Fix a bug in _gst_mpz_divexact, causing memory
2362	corruption sometimes.
2363
23642006-12-22  Paolo Bonzini  <bonzini@gnu.org>
2365
2366	* libgst/lex.c: Previous change not 64-bit clean,
2367	obstack_chunk_size returns unsigned rather than int or size_t.
2368
23692006-12-21  Paolo Bonzini  <bonzini@gnu.org>
2370
2371	* libgst/lex.c: Build strings on obstack instead of the
2372	str.c buffer.  Otherwise the buffer could be cleared out
2373	by oop.c when it uses it to store the live ephemeron OOPs.
2374	* libgst/str.c: Remove dead functions.
2375	* libgst/str.h: Likewise.
2376
23772006-12-19  Paolo Bonzini  <bonzini@gnu.org>
2378
2379	* libgst/heap.c: Remove arithmetic on void *.
2380
2381	* libgst/sym.c: Remove unused symbols.
2382	* libgst/sym.h: Remove unused symbols.
2383	* libgst/vm.def: Use _gst_must_be_boolean_symbol.
2384	* libgst/vm.inl: Regenerate.
2385
23862006-12-18  Paolo Bonzini  <bonzini@gnu.org>
2387
2388	* libgst/save.c: Don't uselessly mark unused OOPs as free.
2389
23902006-12-18  Paolo Bonzini  <bonzini@gnu.org>
2391
2392	* libgst/save.c: Miscellaneous speed-ups, including caching the
2393	number of free OOPs in the saved file.
2394
23952006-12-18  Paolo Bonzini  <bonzini@gnu.org>
2396
2397	* libgst/alloc.c: Adjust calls to _gst_heap_create.
2398	* libgst/lib.c: Likewise.
2399	* libgst/oop.c: Likewise.
2400	* libgst/save.c: Likewise.
2401
2402	* libgst/heap.c: Add address parameter to _gst_heap_create.
2403	* libgst/heap.h: Likewise for declaration.
2404	* libgst/oop.h: Likewise for _gst_init_oop_table declaration.
2405	* libgst/sysdep.c: Add address parameter to _gst_osmem_reserve and
2406	to the implementations of the function.  Support MAP_AUTORESRV
2407	as a synonym of MAP_NORESERVE.
2408	* libgst/sysdep.h: Likewise for declaration.
2409
24102006-12-15  Paolo Bonzini  <bonzini@gnu.org>
2411
2412	* libgst/alloc.c: Remove assertions if !OPTIMIZE.  Increase default
2413	allocation granularity.
2414
24152006-12-15  Paolo Bonzini  <bonzini@gnu.org>
2416
2417	* libgst/save.c: Store object table base in the image, adjust based
2418	on the delta upon loading.  Inline functions that are not used
2419	anymore upon saving due to the previous change.  Reset nativeIP
2420	upon saving rather than upon loading.
2421
24222006-12-14  Paolo Bonzini  <bonzini@gnu.org>
2423
2424	* libgst/cint.c: Move gst_cfunc_descriptor to cint.h.  Accept a nil
2425	cFunction inside a descriptor (now happens upon image load),
2426	remove _gst_restore_cfunc_descriptor.
2427	* libgst/cint.h: Adjust for cint.c changes.
2428	* libgst/comp.c: Remove _gst_restore_primitive_number.
2429	* libgst/comp.h: Remove _gst_restore_primitive_number.
2430	* libgst/dict.c: Initialize primitive table from default in
2431	_gst_init_dictionary, and from the image in prepare_primitives_table
2432	(which replaces prepare_primitive_numbers_map).  Don't reset
2433	the VMPrimitives dictionary upon image load, and don't walk the
2434	OOP table.
2435	* libgst/genpr-parse.y: Initialize _gst_default_primitive_table
2436	instead of _gst_primitive_table.
2437	* libgst/interp.c: Use _gst_default_primitive_table in
2438	_gst_get_primitive_attributes, add _gst_set_primitive_attributes.
2439	Make the primitive tables public.
2440	* libgst/interp.h: Adjust for the above.
2441	* libgst/save.c: Allocate temporary storage for the object that
2442	are about to be saved.  Massage the CallinProcess, Process,
2443	Semaphore and CFunctionDescriptor instances in that temporary
2444	storage rather than at load time.
2445
24462006-12-14  Paolo Bonzini  <bonzini@gnu.org>
2447
2448	* libgst/input.c: Initialize completions only when a readline stream
2449	is pushed.
2450
24512006-12-12  Paolo Bonzini  <bonzini@gnu.org>
2452
2453	* libgst/oop.c: Proceed recursively if marking the ephemerons'
2454	slots finds more ephemerons.  Add more debugging functions.
2455	Rename GC_DEBUGGING and MMAN_DEBUGGING to GC_DEBUG_OUTPUT and
2456	MMAN_DEBUG_OUTPUT.  Preprocessor symbol GC_DEBUGGING now enables
2457	sanity checks.
2458
24592006-12-07  Paolo Bonzini  <bonzini@gnu.org>
2460
2461	* libgst/mpz.c: Use mpn_cmp, mpn_scan1, mpn_bdivmod.
2462	* libgst/mpz.h: Export _gst_mpz_divexact.
2463	* libgst/prims.def: Add primitive for _gst_mpz_divexact.
2464
24652006-12-07  Paolo Bonzini  <bonzini@gnu.org>
2466
2467	* libgst/cint.c: Don't push self for anything but CDATA_SELF and
2468	CDATA_SELF_OOP.
2469
24702006-12-05  Paolo Bonzini  <bonzini@gnu.org>
2471
2472	*** Version 2.3 released.
2473
24742006-12-05  Paolo Bonzini  <bonzini@gnu.org>
2475
2476	* libgst/lex.c: Reject character literals above 128.
2477
24782006-12-02  Paolo Bonzini  <bonzini@gnu.org>
2479
2480	* libgst/mpz.c: Make 64-bit clean.
2481
24822006-12-01  Paolo Bonzini  <bonzini@gnu.org>
2483
2484	* libgst/re.c: Remove ISO C99-ism.
2485
24862006-11-30  Paolo Bonzini  <bonzini@gnu.org>
2487
2488	* libgst/interp.c: Remove misleading comment.
2489	* libgst/xlat.c: Export SP in gen_dirty_block around the function call,
2490	as it may cause a GC.
2491
24922006-11-27  Paolo Bonzini  <bonzini@gnu.org>
2493
2494	* libgst/xlat.c: Use _p variants appropriately.
2495
24962006-11-21  Paolo Bonzini  <bonzini@gnu.org>
2497
2498	* libgst/re.c: Add make_re_results.  Remove _gst_re_free_registers.
2499	* libgst/re.h: Remove _gst_re_free_registers.
2500	* libgst/cint.c: Remove _gst_re_free_registers.
2501	* libgst/callin.c (_gst_class_name_to_oop): Support namespaces.
2502	(_gst_oop_at_put): Fix off-by-one bug.
2503
25042006-11-21  Paolo Bonzini  <bonzini@gnu.org>
2505
2506        * libgst/alloc.c: Add GPL exception.
2507        * libgst/alloc.h: Add GPL exception.
2508        * libgst/byte.c: Add GPL exception.
2509        * libgst/byte.def: Add GPL exception.
2510        * libgst/byte.h: Add GPL exception.
2511        * libgst/callin.c: Add GPL exception.
2512        * libgst/callin.h: Add GPL exception.
2513        * libgst/cint.c: Add GPL exception.
2514        * libgst/cint.h: Add GPL exception.
2515        * libgst/comp.c: Add GPL exception.
2516        * libgst/comp.h: Add GPL exception.
2517        * libgst/comp.inl: Add GPL exception.
2518        * libgst/dict.c: Add GPL exception.
2519        * libgst/dict.h: Add GPL exception.
2520        * libgst/dict.inl: Add GPL exception.
2521        * libgst/events.c: Add GPL exception.
2522        * libgst/events.h: Add GPL exception.
2523        * libgst/genbc-decl.y: Add GPL exception.
2524        * libgst/genbc-impl.y: Add GPL exception.
2525        * libgst/genbc-scan.c: Add GPL exception.
2526        * libgst/genbc-scan.l: Add GPL exception.
2527        * libgst/genbc.c: Add GPL exception.
2528        * libgst/genbc.h: Add GPL exception.
2529        * libgst/genpr-parse.y: Add GPL exception.
2530        * libgst/genpr-scan.c: Add GPL exception.
2531        * libgst/genpr-scan.l: Add GPL exception.
2532        * libgst/genprims.h: Add GPL exception.
2533        * libgst/genvm-parse.y: Add GPL exception.
2534        * libgst/genvm-scan.c: Add GPL exception.
2535        * libgst/genvm-scan.l: Add GPL exception.
2536        * libgst/genvm.h: Add GPL exception.
2537        * libgst/gst-parse.c: Add GPL exception.
2538        * libgst/gst-parse.h: Add GPL exception.
2539        * libgst/gst.h: Add GPL exception.
2540        * libgst/gstpriv.h: Add GPL exception.
2541        * libgst/gstpub.h: Add GPL exception.
2542        * libgst/heap.c: Add GPL exception.
2543        * libgst/heap.h: Add GPL exception.
2544        * libgst/input.c: Add GPL exception.
2545        * libgst/input.h: Add GPL exception.
2546        * libgst/interp-bc.inl: Add GPL exception.
2547        * libgst/interp-jit.inl: Add GPL exception.
2548        * libgst/interp.c: Add GPL exception.
2549        * libgst/interp.h: Add GPL exception.
2550        * libgst/interp.inl: Add GPL exception.
2551        * libgst/jitpriv.h: Add GPL exception.
2552        * libgst/lex.c: Add GPL exception.
2553        * libgst/lex.h: Add GPL exception.
2554        * libgst/lib.c: Add GPL exception.
2555        * libgst/lib.h: Add GPL exception.
2556        * libgst/md-config.h: Add GPL exception.
2557        * libgst/memzero.h: Add GPL exception.
2558        * libgst/oop.c: Add GPL exception.
2559        * libgst/oop.h: Add GPL exception.
2560        * libgst/oop.inl: Add GPL exception.
2561        * libgst/opt.c: Add GPL exception.
2562        * libgst/opt.h: Add GPL exception.
2563        * libgst/prims.def: Add GPL exception.
2564        * libgst/print.c: Add GPL exception.
2565        * libgst/print.h: Add GPL exception.
2566        * libgst/re.c: Add GPL exception.
2567        * libgst/re.h: Add GPL exception.
2568        * libgst/save.c: Add GPL exception.
2569        * libgst/save.h: Add GPL exception.
2570        * libgst/security.c: Add GPL exception.
2571        * libgst/security.h: Add GPL exception.
2572        * libgst/str.c: Add GPL exception.
2573        * libgst/str.h: Add GPL exception.
2574        * libgst/sym.c: Add GPL exception.
2575        * libgst/sym.h: Add GPL exception.
2576        * libgst/sysdep.c: Add GPL exception.
2577        * libgst/sysdep.h: Add GPL exception.
2578        * libgst/tree.c: Add GPL exception.
2579        * libgst/tree.h: Add GPL exception.
2580        * libgst/vm.def: Add GPL exception.
2581        * libgst/xlat.c: Add GPL exception.
2582        * libgst/xlat.h: Add GPL exception.
2583        * main.c: Add GPL exception.
2584
25852006-11-19  Paolo Bonzini  <bonzini@gnu.org>
2586
2587	* libgst/prims.def: Fetch receiver from _gst_self when passing
2588	_gst_this_context_oop to the C call-out primitives.  Suspend current
2589	process before quitting.
2590
25912006-11-15  Paolo Bonzini  <bonzini@gnu.org>
2592
2593	* libgst/builtins.gperf: Rename #callFrom:into: into #callInto:.
2594	* libgst/builtins.inl: Regenerate.
2595	* libgst/prims.def: Support not passing the context to C call-out
2596	primitives, and a "nil" paramter to #callInto:.
2597
25982006-11-03  Paolo Bonzini  <bonzini@gnu.org>
2599
2600	* libgst/gst.h: Compile on C++.  Rename mst_Object to gst_object.
2601	* libgst/gstpub.h: Likewise.
2602
2603	* libgst/comp.c: Rename mst_Object to gst_object.
2604	* libgst/interp.c: Likewise.
2605	* libgst/lex.c: Likewise.
2606	* libgst/oop.c: Likewise.
2607	* libgst/oop.h: Likewise.
2608	* libgst/print.c: Likewise.
2609	* libgst/print.h: Likewise.
2610	* libgst/dict.c: Likewise.
2611	* libgst/save.c: Likewise.
2612	* libgst/security.c: Likewise.
2613	* libgst/sym.c: Likewise.
2614	* libgst/dict.h: Likewise.
2615	* libgst/tree.c: Likewise.
2616	* libgst/xlat.c: Likewise.
2617	* libgst/comp.inl: Likewise.
2618	* libgst/dict.inl: Likewise.
2619	* libgst/oop.inl: Likewise.
2620	* libgst/prims.def: Likewise.
2621
26222006-11-03  Paolo Bonzini  <bonzini@gnu.org>
2623
2624	* libgst/interp.c: Check if we hit the bottom of the stack in
2625	disable_non_unwind_contexts, and percolate a return value of true
2626	through unwind_to up to unwind_method.  Otherwise return false from
2627	both disable_non_unwind_contexts and unwind_to.
2628
26292006-11-02  Paolo Bonzini  <bonzini@gnu.org>
2630
2631	* libgst/opt.c: Fix verification of {{}}.
2632
26332006-10-31  Paolo Bonzini  <bonzini@gnu.org>
2634
2635	* libgst/events.c: Look for events (especially POLLHUP) even
2636	if poll returns 0.
2637
26382006-10-31  Paolo Bonzini  <bonzini@gnu.org>
2639
2640	* libgst/prims.def: Make CObject primitives more resilient to
2641	bad contents of the CType.
2642
26432006-10-25  Paolo Bonzini  <bonzini@gnu.org>
2644
2645	* libgst/gst-parse.c: Extract parse_variable_primary_1
2646	out of parse_variable_primary.
2647
26482006-10-16  Paolo Bonzini  <bonzini@gnu.org>
2649
2650	* libgst/xlat.c: Update gen_send for new super-send implementation.
2651	Disallow deferred super sends.  Fix bug in String>>#at: inlining
2652	and in compiling a gen_push_self+gen_alt_self sequence.  Remove
2653	C99-ism in emit_method_prolog.
2654	* libgst/xlat.h: Fix IS_VALID_IP for methodStart == 0.
2655
26562006-10-16  Roman Zippel  <zippel@linux-m68k.org>
2657
2658	* libgst/alloc.h: Add padding to the bitfields.
2659
26602006-10-11  Paolo Bonzini  <bonzini@gnu.org>
2661
2662	* libgst/cint.c: Avoid buffer overflow on empty variadic argument.
2663
26642006-10-05  Paolo Bonzini  <bonzini@gnu.org>
2665
2666	* libgst/lib.c: Improve help message to document -f.
2667
26682006-10-05  Paolo Bonzini  <bonzini@gnu.org>
2669
2670	* libgst/interp.c: Make less verbose on backtraces.
2671	* libgst/oop.c: Make less verbose on scavenging.
2672
26732006-09-29  Paolo Bonzini  <bonzini@gnu.org>
2674
2675	* libgst/comp.c: Use _gst_get_method_start_pos to find if we can
2676	use _gst_get_cur_file_pos.
2677	* libgst/input.c: Track file offset of FileStream objects.  Extend
2678	buffers when a new hunk is needed, shrink it on _gst_get_cur_string.
2679	Use buffer and file offset tracking it to support _gst_get_cur_file_pos
2680	and _gst_get_cur_string for STREAM_OOP streams.  Delete
2681	_gst_get_cur_readline as it is the same as _gst_get_cur_string
2682	* libgst/input.h: Delete _gst_get_cur_readline.
2683
26842006-09-24  Paolo Bonzini  <bonzini@gnu.org>
2685
2686	* libgst/dict.inl: Fix checking builds.
2687
26882006-09-22  Paolo Bonzini  <bonzini@gnu.org>
2689
2690	* libgst/interp-bc.inl: Shut up compiler warnings.
2691
2692	* libgst/cint.c: Declare regex functions.
2693	* libgst/re.c, libgst/re.h: Move from examples.  Adapt since it
2694`	is not anymore a module.
2695	* libgst/lib.c: Add Regex.st.
2696
26972006-09-15  Paolo Bonzini  <bonzini@gnu.org>
2698
2699	* libgst/byte.c: Include match.h.
2700	* libgst/opt.c: Include match.h.
2701	* libgst/xlat.c: Include match.h.
2702	* libgst/gstpriv.h: Don't.
2703
2704	* libgst/cint.c: Avoid stupid warning.
2705
2706	* libgst/dict.inl: Make IS_A_CLASS/IS_A_METACLASS more robust.
2707	* libgst/opt.c: Detect invalid sends to super.
2708
2709	* libgst/comp.c: Push class, not superclass for send to super.
2710	* libgst/vm.def: Adapt.
2711
27122006-09-13  Paolo Bonzini  <bonzini@gnu.org>
2713
2714	* libgst/comp.c (compile_send): Compile receiver superclass for
2715	sends to super.
2716	* libgst/opt.c: Add receiver class to balance for send to super.
2717	Replace "+= -x" with "-= x" throughout.
2718	* libgst/tree.h: Adjust _gst_make_oop_constant comment.
2719	* libgst/vm.def (SEND_SUPER, SEND_SUPER_IMMEDIATE): Pop class OOP.
2720	(SEND_TO_SUPER): Get methodClass argument.
2721
27222006-09-08  Paolo Bonzini  <bonzini@gnu.org>
2723
2724	* libgst/cint.c: Wrap utime.
2725
27262006-09-05  Paolo Bonzini  <bonzini@gnu.org>
2727
2728	* libgst/dict.c, libgst/dict.inl, libgst/gstpriv.h,
2729	libgst/gst-parse.c: Adjust macro names for upgrade to Autoconf 2.60.
2730
27312006-07-20  Paolo Bonzini  <bonzini@gnu.org>
2732
2733	* libgst/lib.c: Load Getopt.st.
2734
27352006-07-20  Paolo Bonzini  <bonzini@gnu.org>
2736
2737	* libgst/input.c: Merge my_close into _gst_pop_stream.  Always
2738	free memory.  Initialize fileNameOOP for FileDescriptors in
2739	_gst_push_stream_oop.  Clear the fileName field in push_new_stream.
2740	Fix STREAM_OOP case in my_getc.  Use fileNameOOP to print error
2741	messages.
2742	* libgst/prims.def: New primitives VMpr_Stream_fileIn and
2743	VMpr_Stream_fileInLine, extracted from the fileOp primitive.
2744
27452006-07-20  Paolo Bonzini  <bonzini@gnu.org>
2746
2747	* libgst/dict.c: Add 'peek' variable to FileDescriptor.
2748	* libgst/dict.h: Add 'peek' variable to struct gst_file_stream.
2749	* libgst/input.c: Leave poll_and_read upon POLLHUP.
2750	* libgst/interp.h: Add PRIM_GET_CHARS_AT and PRIM_PUT_CHARS_AT.
2751	* libgst/prims.def: Remove useless fstat call, accept any byte
2752	or character class in read/write primitives, implement pread
2753	and pwrite primitives.
2754
27552006-07-18  Paolo Bonzini  <bonzini@gnu.org>
2756
2757	* libgst/callin.c: Support wchars and wstrings.
2758	* libgst/callin.h: Likewise.
2759	* libgst/cint.c: Likewise.
2760	* libgst/gstpub.h: Likewise.
2761	* libgst/sym.c: Add new symbols.
2762	* libgst/sym.h: Likewise.
2763
2764	* libgst/comp.c: Support CONST_CHAR in equal_constant and
2765	make_constant_oop.
2766	* libgst/dict.c: Add UnicodeCharacter and UnicodeString.  Change
2767	instance and class variable names for Character.  Add #utf32 shape
2768	element size in _gst_log2_sizes.  Add helper functions for callin.c
2769	and cint.c changes above.
2770	* libgst/dict.h: Add gst_char and gst_unicode_string, and declare
2771	the helper functions.
2772	* libgst/dict.inl: Move here CHAR_OOP_AT from oop.inl; provide
2773	CHAR_OOP_VALUE here with a new definition.  Add char_new.  Support
2774	#utf32 shape.
2775	* libgst/gst-parse.c: Drop BYTE_LITERAL tokens.  Check range of
2776	integers instead.  Support $< INTEGER_LITERAL > tokens.
2777	* libgst/gst-parse.h: Remove cval from YYSTYPE.
2778	* libgst/gstpriv.h: Add ISP_UTF32; include wchar.h.
2779	* libgst/lex.c: Match the gst-parse.c changes.  Use ival instead of
2780	cval.  Support printing non-ASCII CHAR_LITERALs with their code points.
2781	* libgst/lib.c: Load UniChar.st and UniString.st.
2782	* libgst/oop.c: Fix a comment's spacing.
2783	* libgst/oop.inl: Remove CHAR_OOP_AT and CHAR_OOP_VALUE.
2784	* libgst/prims.def: Define VMpr_CharacterArray_valueAt,
2785	VMpr_CharacterArray_valueAtPut, VMpr_UnicodeCharacter_create,
2786	VMpr_Character_equal.  Accept some UnicodeCharacters in
2787	VMpr_Memory_atPut and VMpr_CObject_atPut.
2788	* libgst/print.c: Print non-ASCII Characters and UnicodeCharacters
2789	with their code points.
2790	* libgst/tree.c: Make a CONST_CHAR in _gst_make_char_constant, not
2791	a CONST_OOP (partly undoing 2000-09-09 change), and accept an int.
2792	* libgst/tree.h: Add back CONST_CHAR.
2793
27942006-07-13  Paolo Bonzini  <bonzini@gnu.org>
2795
2796	* libgst/events.c (_gst_sync_file_polling): Prepare pfd.revents by
2797	zeroing it.
2798
27992006-04-26  Paolo Bonzini  <bonzini@gnu.org>
2800
2801	* libgst/gst-parse.c (parse_doit): Do not read other tokens
2802	after an EOF.
2803
28042006-04-18  Paolo Bonzini  <bonzini@gnu.org>
2805
2806	* libgst/gst-parse.c (parse_array_constructor): Do not crash on {}
2807	or on an invalid attribute like in 'a <3 4>'.
2808
28092006-02-12  Paolo Bonzini  <bonzini@gnu.org>
2810
2811	* libgst/comp.c (equal_constant): Compare floating point constants
2812	with memcmp.
2813
28142005-11-30  Paolo Bonzini  <bonzini@gnu.org>
2815
2816	* libgst/vm.def: Refine previous change using OOP_CLASS instead of
2817	IS_CLASS.
2818
28192005-11-30  Paolo Bonzini  <bonzini@gnu.org>
2820
2821	* libgst/vm.def: Shortcut FloatD/Integer mixed math, and
2822	FloatD division.
2823
28242005-11-30  Paolo Bonzini  <bonzini@gnu.org>
2825
2826	* libgst/xlat.c: Fix ISP_CHARACTER typo.
2827
28282005-11-29  Paolo Bonzini  <bonzini@gnu.org>
2829
2830	* libgst/vm.def: Make the #at: and #at:put: cache store the spec,
2831	and only work on primitives 60/61.
2832	* libgst/interp.c: Adjust.  New functions cached_index_oop_primitive
2833	and cached_index_oop_put_primitive.
2834
28352005-11-29  Paolo Bonzini  <bonzini@gnu.org>
2836
2837	* libgst/dict.c (class_info): Use ISP_CHARACTER shape for
2838	String and Symbol.
2839	(_gst_log2_sizes): Adjust for ISP_CHARACTER.
2840	* libgst/dict.inl (index_oop_put_spec, index_oop_spec): New,
2841	from index_oop_put and index_oop.  Fix typos in handling of
2842	ISP_FLOAT and ISP_DOUBLE.  Handle ISP_CHARACTER.
2843	(index_oop_put, index_oop): Use them.
2844	(index_string_oop_put, index_string_oop): Delete.
2845	* libgst/gstpriv.h: Define ISP_CHARACTER.
2846	* libgst/prims.def (VMpr_String_basicAt,
2847	VMpr_String_basicAtPut): Delete.
2848	(VMpr_String_similarityTo): Accept ISP_CHARACTER shaped classes.
2849	(VMpr_ByteArray_replaceFromToWithStartingAt): Accept ISP_SCHAR and
2850	ISP_CHARACTER shaped classes as well.
2851	* libgst/xlat.c (emit_basic_size_in_r0): Accept ISP_SCHAR and
2852	ISP_CHARACTER shaped classes as well.
2853	(emit_inlined_primitive): Accept ISP_SCHAR and ISP_CHARACTER
2854	shaped classes as well.
2855
28562005-11-29  Paolo Bonzini  <bonzini@gnu.org>
2857
2858	* libgst/interp.h (execute_primitive_operation): Do not declare.
2859	* libgst/interp.c (execute_primitive_operation): New name
2860	of _gst_execute_primitive_operation.  Make static and inline.
2861	* libgst/interp-bc.inl: Adjust.
2862	* libgst/interp-jit.inl: Adjust.
2863	* libgst/vm.def: Adjust.
2864
28652005-11-21  Paolo Bonzini  <bonzini@gnu.org>
2866
2867	* libgst/dict.c (_gst_string_new, _gst_counted_string_new): Handle
2868	zero-length strings.
2869	* libgst/interp.c (_gst_init_signals): Handle SIGTERM.
2870	(interrupt_handler): Exit on SIGINT or SIGTERM.
2871
28722005-09-18  Paolo Bonzini  <bonzini@gnu.org>
2873
2874	* libgst/callin.h: New methods for the interpreter proxy.
2875	* libgst/callin.c: New methods for the interpreter proxy.
2876	* libgst/gstpub.h: New methods for the interpreter proxy.
2877	* libgst/interp.h: New function _gst_find_method, moved from
2878	interp.c.  Declare method_cache_entry.
2879	* libgst/interp.c: Rename find_method to _gst_find_method,
2880	remove declarations of find_method and method_cache_entry.
2881
28822005-09-12  Mike Anderson  <msasjf@yahoo.co.uk>
2883
2884	* libgst/events.c: Fix bug with pollfds being lost if a previous
2885	one has an error.
2886
28872005-09-05  Paolo Bonzini  <bonzini@gnu.org>
2888
2889	* libgst/gst-parse.c: Do not crash on #[].
2890
28912005-09-02  Paolo Bonzini  <bonzini@gnu.org>
2892
2893	* libgst/save.c: Use a better #! sequence.
2894
28952005-08-30  Paolo Bonzini  <bonzini@gnu.org>
2896
2897	* libgst/oop.c: Fix pasto (SIZEOF_LONG instead of SIZEOF_OOP).
2898	* libgst/comp.c: Do not emit PUSH_INTEGER for integers equal or
2899	bigger than 2^31.
2900	* libgst/byte.h: Change final argument of compile_byte to int.
2901	* libgst/byte.c: Likewise.
2902
29032005-08-30  Paolo Bonzini  <bonzini@gnu.org>
2904
2905	* libgst/mpz.c: Fix 64-bit cleanliness problem.
2906
29072005-08-28  Paolo Bonzini  <bonzini@gnu.org>
2908
2909	* libgst/gst-parse.c: Remove last parameter to parse_cascaded_messages.
2910
29112005-08-28  Paolo Bonzini  <bonzini@gnu.org>
2912
2913	* libgst/gstpriv.h: Define ENABLE_SECURITY.
2914	* libgst/gst-parse.c: Fix warnings.
2915	* libgst/opt.c: Reenable verifier.
2916
29172005-08-28  Paolo Bonzini  <bonzini@gnu.org>
2918
2919	* libgst/input.c: Add to input_stream a method_start_pos
2920	member.  Clear it in push_new_stream and _gst_set_stream_info.
2921	Set it in _gst_get_location.  Move _gst_get_method_start_pos
2922	and _gst_clear_method_start_pos here from lex.c.
2923	* libgst/lex.c: Remove the aforementioned two functions and
2924	the code mentioning the local variable method_start_pos.
2925	* libgst/lex.h: Move the functions from here...
2926	* libgst/input.h: ... to here and make _gst_get_method_start_pos
2927	and _gst_get_cur_file_pos return off_t.
2928	* libgst/comp.c: Make usage of these two functions 64-bit safe.
2929
29302005-08-14  Paolo Bonzini  <bonzini@gnu.org>
2931
2932	* libgst/cint.c: Add lstat.
2933
29342005-08-07  Paolo Bonzini  <bonzini@gnu.org>
2935
2936	* libgst/cint.c: Do my math correctly.
2937
29382005-06-17  Paolo Bonzini  <bonzini@gnu.org>
2939
2940	* libgst/cint.c: Do not use ffi_type_slong, it is a 64-bit type!
2941	* libgst/gst-parse.c: Fix more bugs in creation of FileSegments.
2942
29432005-06-16  Paolo Bonzini  <bonzini@gnu.org>
2944
2945	* libgst/lex.c: Fix bugs in creation of FileSegments.
2946	* libgst/gst-parse.c: Fix bugs in creation of FileSegments.
2947	* libgst/gstpriv.h: Fixes for GCC 4.0.0.
2948
29492005-04-09  Paolo Bonzini  <bonzini@gnu.org>
2950
2951	* libgst/gst-parse.c (expected): Fix spacing.
2952	(parse_block): Fix "expected" error message.
2953	(parse_block_variables): Remove useless check for EOF.
2954
29552005-04-04  Paolo Bonzini  <bonzini@gnu.org>
2956
2957	* libgst/callin.c (_gst_eval_code, _gst_eval_expr): Do not use
2958	_gst_compile_code for communication to _gst_parse_stream, use a
2959	parameter to it instead.
2960	* libgst/comp.c (_gst_set_compilation_class): Extract out of
2961	_gst_set_compilation_category.
2962	(_gst_install_initial_methods, _gst_execute_statements): Adjust.
2963	(_gst_make_attribute): Execute statements for the arguments here.
2964	* comp.h (_gst_set_compilation_class): New prototype.
2965	(_gst_set_compilation_category): Adjust prototype.
2966	* libgst/gst-parse.c: Rewritten.
2967	* libgst/gst-parse.h: Rewritten based on Bison output.
2968	* libgst/gstpriv.h: Include gst-parse.h.
2969	* libgst/interp.c (parse_stream_with_protection): Add new parameter
2970	of _gst_parse_stream and forward it.
2971	* libgst/lex.c (parse_*): Rename to scan_*.
2972	(_gst_compile_code): Remove.
2973	(_gst_parse_stream): Add parameter to pick top production.
2974	(_gst_yylex): Remove INTERNAL_TOKEN hacks.  Do not compute last_line
2975	and last_column.
2976	(print_token): Remove INTERNAL_TOKEN.
2977	* libgst/lex.h (_gst_compile_code, _gst_yydebug): Remove.
2978	(_gst_parse_stream): Adjust prototype.
2979	* libgst/lib.c (help_text, parse_args, long_options): Remove -y.
2980	(process_stdin, process_file): Adjust call to _gst_parse_stream.
2981	* libgst/prims.def: Adjust for changes to _gst_set_compilation_category
2982	and parse_stream_with_protection.  Do not use _gst_compile_code,
2983	refer to _gst_current_parser->state instead and fail if methodsFor
2984	is used while not parsing.
2985	* libgst/tree.c (_gst_add_node): Support case where N1 is NULL.
2986	* libgst/tree.h (_gst_add_node): Return a tree_node.
2987
2988	* libgst/gst-parse.y: Remove.
2989	* libgst/Makefile.am: Replace it with gst-parse.c.
2990
29912005-03-25  Paolo Bonzini  <bonzini@gnu.org>
2992
2993	* libgst/comp.c (_gst_make_attribute): Use make_constant_oop.
2994	* libgst/gst-parse.y (attribute_body): Do not include keyword.
2995	(attribute_argument): Add it here.  Do not go through
2996	_gst_execute_statements for TREE_CONST_EXPRs (greatly speeds up
2997	C call-outs).
2998
29992005-03-25  Paolo Bonzini  <bonzini@gnu.org>
3000
3001	* libgst/comp.c (install_method): Evaluate pragma handlers.
3002	Make CompiledMethod read-only.
3003	(method_new): Do not make CompiledMethod read-only here.
3004	* libgst/dict.c (class_info): Include pragmaHandlers instance
3005	variable for Class.
3006	(init_class): Initialize it here.
3007	* libgst/dict.h (gst_class): Include pragmaHandlers instance variable.
3008	* libgst/sym.c (_gst_find_pragma_handler): New.
3009	* libgst/sym.h (_gst_find_pragma_handler): Declare it.
3010
30112005-03-24  Paolo Bonzini  <bonzini@gnu.org>
3012
3013	Fix bug when an ephemeron was tenured directly from eden to
3014	oldspace.
3015
3016	* libgst/oop.c (add_to_grey_list): Remove last parameter.
3017	(add_grey_object): New function, for when the OOP parameter
3018	of add_to_grey_list was non-nil.  Call scanned_fields_in from
3019	here.
3020	(_gst_copy_an_oop, tenure_one_object): Use add_grey_object.
3021
30222005-03-24  Paolo Bonzini  <bonzini@gnu.org>
3023
3024	* libgst/callin.c: Remove out-of-date comment.
3025
30262005-03-24  Paolo Bonzini  <bonzini@gnu.org>
3027
3028	* libgst/lib.c: Load Transcript.st earlier.
3029
30302005-02-02  Paolo Bonzini  <bonzini@gnu.org>
3031
3032	* libgst/alloc.c (NO_MALLOC_OVERRIDE): New define.
3033	(malloc, realloc, free, calloc): Define only if NO_MALLOC_OVERRIDE
3034	is not defined.
3035	(morecore): Do not use the system heap (sbrk) if NO_MALLOC_OVERRIDE
3036	is defined.
3037
30382004-12-20  Paolo Bonzini  <bonzini@gnu.org>
3039
3040	* libgst/sysdep.h (O_NONBLOCK): Unused, remove.
3041
30422004-11-25  Paolo Bonzini  <bonzini@gnu.org>
3043
3044	* libgst/xlat.c (gen_dirty_block): Return value is not in JIT_R0
3045	except on x86.
3046
30472004-11-25  Paolo Bonzini  <bonzini@gnu.org>
3048
3049	* libgst/oop.c: Catch more errors out of mprotect.
3050
30512004-11-25  Paolo Bonzini  <bonzini@gnu.org>
3052
3053	* libgst/alloc.h: Use char for the type of large.data
3054	in struct heap_block.
3055
30562004-11-13  Paolo Bonzini  <bonzini@gnu.org>
3057
3058	* libgst/lib.c: Always print "file not found" error.
3059	* libgst/gstpriv.h: Use autoconf test to look for
3060	availability of __attribute__ ((visibility ("hidden"))).
3061
30622004-09-24  Paolo Bonzini  <bonzini@gnu.org>
3063
3064	* libgst/save.c: Remove code left by mistake.
3065
30662004-09-07  Paolo Bonzini  <bonzini@gnu.org>
3067
3068	* libgst/lex.c: Scan initial shebang as comment.
3069	* libgst/gst-parse.y: Parse initial shebang as comment.
3070	* libgst/lib.c: Add -f option.
3071
30722004-08-29  Paolo Bonzini  <bonzini@gnu.org>
3073
3074	* libgst/comp.h: SIZEOF_INTPTR_T => SIZEOF_OOP.
3075	* libgst/dict.inl: SIZEOF_INTPTR_T => SIZEOF_OOP.
3076	* libgst/gstpriv.h: SIZEOF_INTPTR_T => SIZEOF_OOP.
3077	* libgst/save.c: SIZEOF_INTPTR_T => SIZEOF_OOP.
3078	* libgst/xlat.c: SIZEOF_INTPTR_T => SIZEOF_OOP.
3079
30802004-08-21  Paolo Bonzini  <bonzini@gnu.org>
3081
3082        * libgst/gstpriv.h: Enforce long double alignment for obstacks.
3083        * libgst/alloc.c: Support 16k pages and long double alignment of
3084        malloc-ed blocks.
3085        * libgst/alloc.h: Likewise.
3086
30872004-03-25  Paolo Bonzini  <bonzini@gnu.org>
3088
3089	* libgst/prims.def: Fix C99-ism.
3090	* libgst/lib.c: Simplify handling of -a.
3091
30922004-01-19  Paolo Bonzini  <bonzini@gnu.org>
3093
3094	* libgst/xlat.c: Do not compile body of method if
3095	primitive cannot fail.  Reserve space for emitting
3096	#valueWithReceiver:withArguments:.
3097
30982004-01-18  Paolo Bonzini  <bonzini@gnu.org>
3099
3100	* libgst/oop.c: Discard the translations of objects that
3101	#become: swaps.
3102	* libgst/opt.c: Rewritten compute_stack_positions, factor
3103	code that is common with the verifier.
3104	* libgst/xlat.c: Reset sp before translating user-defined
3105	method callers (subclasses of CompiledMethod with flags=6).
3106	Emit extras in emit_code_tree, not in gen_nothing.  Add
3107	objectReg parameter to emit_basic_size_in_r0, use it to
3108	speed up #javaAsInt and #javaAsLong.
3109
31102004-01-15  Paolo Bonzini  <bonzini@gnu.org>
3111
3112	* libgst/prims.def: Set class of created CompiledMethod
3113	and CompiledBlock objects.
3114	* libgst/comp.c: Incubate attributes properly.
3115	* libgst/dict.c: Return nil if searching a pool variable
3116	in a non-Dictionary class.
3117	* libgst/xlat.c: Translate #javaAsInt and #javaAsLong.
3118
31192004-01-08  Paolo Bonzini  <bonzini@gnu.org>
3120
3121	* libgst/dict.c: Do not scavenge before the interpreter
3122	is activated.
3123	* libgst/interp.c: Check for IS_NIL (_gst_this_context_oop),
3124	not for ip != NULL, to see if a process is active.
3125	* libgst/interp-jit.inl: Refresh native IP of processes if the
3126	method they are executing is not translated anymore.
3127	* libgst/xlat.c: Fix bit-rot.  Basically removed all places in
3128	which the code generators were decoding the bytecodes, and
3129	fixed some places that did not account for superoperators.
3130
31312003-12-11  Paolo Bonzini  <bonzini@gnu.org>
3132
3133	* libgst/comp.c: Add experimental code to inline #perform:
3134	and friends.
3135
3136	* libgst/genbc-decl.y: Initialize all generated variables.
3137	* libgst/genbc-scan.l: Update for flex 2.5.31.
3138	* libgst/genpr-scan.l: Update for flex 2.5.31.
3139	* libgst/genvm-scan.l: Update for flex 2.5.31.
3140
3141	* libgst/comp.c: Remove _colon_ from variable names where
3142	not ambiguous.
3143	* libgst/interp.c: Likewise.
3144	* libgst/lex.c: Likewise.
3145	* libgst/security.c: Likewise.
3146	* libgst/sym.c: Likewise.
3147	* libgst/sym.h: Likewise.
3148	* libgst/vm.def: Likewise.
3149	* libgst/xlat.c: Likewise.
3150
31512003-12-10  Paolo Bonzini  <bonzini@gnu.org>
3152
3153	* libgst/comp.c: Check _gst_verbosity
3154	* libgst/dict.c: Publish _gst_verbosity as OutputVerbosity
3155	* libgst/lib.c: Replace no_errors with _gst_verbosity == 0,
3156	_gst_quiet_execution with _gst_verbosity == 1, _gst_verbose
3157	with _gst_verbosity == 3, don't set _gst_gc_message on -Q.
3158	* libgst/oop.c: Don't print gc messages if _gst_quiet_execution == 0.
3159
31602003-11-27  Paolo Bonzini  <bonzini@gnu.org>
3161
3162	* libgst/byte.def: New bytecodes 25 and 26
3163	(#javaAsInt, #javaAsLong).
3164	* libgst/byte.h: New bytecodes 25 and 26
3165	* libgst/vm.def: Likewise
3166	* libgst/builtins.gperf: Likewise
3167	* libgst/sym.c: Declare _gst_java_as_int_symbol
3168	and _gst_java_as_long_symbol.
3169	* libgst/sym.h: Declare _gst_java_as_int_symbol
3170	and _gst_java_as_long_symbol.
3171
31722003-11-25  Paolo Bonzini  <bonzini@gnu.org>
3173
3174	* libgst/input.c: New function poll_and_read.
3175
31762003-11-21  Paolo Bonzini  <bonzini@gnu.org>
3177
3178	* libgst/byte.def: Suppress uninitialized variable
3179	warning on arg_lsb.
3180
3181	* libgst/dict.c: Support multiple class shapes
3182	* libgst/dict.inl: Likewise
3183	* libgst/gstpriv.h: Likewise
3184	* libgst/prims.def: Likewise
3185	* libgst/xlat.c: Put an abort on blatantly broken code.
3186
31872003-11-20  Paolo Bonzini  <bonzini@gnu.org>
3188
3189	* libgst/opt.c: Be more precise in detecting jumps over
3190	a push that land on a pop.
3191
31922003-11-18  Paolo Bonzini  <bonzini@gnu.org>
3193
3194	* libgst/dict.c: Add break statements to
3195	_gst_set_file_stream_file (ouch!).
3196	* libgst/prims.def: Allow ByteArrays in get/put primitives,
3197	and integers as opening modes.
3198
31992003-11-13  Paolo Bonzini  <bonzini@gnu.org>
3200
3201	* libgst/comp.c: Raise errors on duplicate arguments or temporaries.
3202	* libgst/sym.c: Add third parameter to _gst_declare_name,
3203	use it in _gst_declare_arguments or _gst_declare_temporaries
3204	* libgst/sym.h: Adjust declaration of _gst_declare_name.
3205
32062003-11-12  Paolo Bonzini  <bonzini@gnu.org>
3207
3208	* libgst/alloc.h: Hide all internal symbols.
3209	* libgst/byte.h: Hide all internal symbols.
3210	* libgst/callin.h: Hide all internal symbols.
3211	* libgst/cint.h: Hide all internal symbols.
3212	* libgst/comp.h: Hide all internal symbols.
3213	* libgst/dict.h: Hide all internal symbols.
3214	* libgst/events.h: Hide all internal symbols.
3215	* libgst/gstpriv.h: Hide all internal symbols.
3216	* libgst/heap.h: Hide all internal symbols.
3217	* libgst/input.h: Hide all internal symbols.
3218	* libgst/interp.h: Hide all internal symbols.
3219	* libgst/jitpriv.h: Hide all internal symbols.
3220	* libgst/lex.h: Hide all internal symbols.
3221	* libgst/lib.h: Hide all internal symbols.
3222	* libgst/match.h: Hide all internal symbols.
3223	* libgst/md-config.h: Hide all internal symbols.
3224	* libgst/memzero.h: Hide all internal symbols.
3225	* libgst/mpz.h: Hide all internal symbols.
3226	* libgst/oop.h: Hide all internal symbols.
3227	* libgst/opt.h: Hide all internal symbols.
3228	* libgst/print.h: Hide all internal symbols.
3229	* libgst/save.h: Hide all internal symbols.
3230	* libgst/security.h: Hide all internal symbols.
3231	* libgst/str.h: Hide all internal symbols.
3232	* libgst/sym.h: Hide all internal symbols.
3233	* libgst/sysdep.h: Hide all internal symbols.
3234	* libgst/tree.h: Hide all internal symbols.
3235	* libgst/xlat.h: Hide all internal symbols.
3236
3237	* libgst/interp.h: Declare _gst_abort_execution here.
3238	* libgst/xlat.c: Don't declare it as extern here.
3239	* libgst/oop.c: Make grow_memory_no_capact and oop_heap static.
3240	* libgst/sym.c: Make check_symbol_chain static.
3241
3242	* libgst/sym.c: Initialize global variables so as to make them uncommon.
3243	* libgst/comp.c: Likewise.
3244	* libgst/lib.c: Likewise.
3245	* libgst/save.c: Likewise.
3246	* libgst/oop.c: Likewise.
3247	* libgst/dict.c: Likewise.
3248	* libgst/interp.c: Likewise.
3249	* libgst/cint.c: Likewise.
3250	* libgst/lex.c: Likewise.
3251
32522003-11-11  Paolo Bonzini  <bonzini@gnu.org>
3253
3254	* libgst/input.c: Avoid SIGSEGV if character in range
3255	128..255 is pushed back by the lexer.
3256	* libgst/lex.c: Tweak output of invalid characters.
3257
3258	* libgst/alloc.c: Tweak pool sizes to obtain cacheline alignment.
3259	* libgst/lib.c: Tweak for more shared library friendliness.
3260	* libgst/tree.c: Tweak for more shared library friendliness.
3261	* libgst/builtins.inl: Rebuild for shared library friendliness.
3262	* libgst/sym.c: Adapt.
3263
32642003-11-07  Paolo Bonzini  <bonzini@gnu.org>
3265
3266	* libgst/lex.c: Allow dollars (!) in the middle of
3267	identifiers.
3268	* libgst/dict.inl: Require that the second argument
3269	of is_a_kind_of is not nil, avoid a test if we
3270	are testing for the exact class.
3271	* libgst/prims.def: Allow #perform: of a subclass
3272	of CompiledMethod.
3273
32742003-11-04  Paolo Bonzini  <bonzini@gnu.org>
3275
3276	* libgst/gstpriv.h: Define prefetching macros.
3277	* libgst/oop.c: Use prefetches.
3278	* libgst/oop.inl: Use prefetches.
3279	* libgst/prims.def: Use nanosleep instead of usleep.
3280	Use prefetches.
3281	* libgst/save.c: Use prefetches.
3282
32832003-11-03  Paolo Bonzini  <bonzini@gnu.org>
3284
3285	* libgst/lex.c: Handle 1+-2 as "1 + -2"
3286	rather than as "1 +- 2".
3287
32882003-10-24  Paolo Bonzini  <bonzini@gnu.org>
3289
3290	* libgst/dict.c: Publish HOST_SYSTEM into
3291	CSymbols.hostSystem.
3292
32932003-10-17  Paolo Bonzini  <bonzini@gnu.org>
3294
3295	* libgst/lex.c: New function parse_sharp; extract
3296	SYMBOL_KEYWORDs (now called SYMBOL_LITERAL) into
3297	it instead of lexing them in parse_ident.  Simplify
3298	parse_ident.
3299	* libgst/gst-parse.y: Use new lexer symbol SYMBOL_LITERAL
3300	which sums up every symbol constant.
3301
33022003-10-07  Paolo Bonzini  <bonzini@gnu.org>
3303
3304	* libgst/comp.c: Rename untrusted_methods to
3305	_gst_untrusted_methods, don't declare it here...
3306	* libgst/comp.h: ...and do it here instead
3307	* libgst/sym.c: Use it.
3308
3309	* libgst/dict.c: Define _gst_identity_dictionary_at
3310	* libgst/dict.h: Declare it
3311	* libgst/comp.c: Don't accept to override an
3312	trusted method with an untrusted one.
3313
33142003-09-29  Paolo Bonzini  <bonzini@gnu.org>
3315
3316	* libgst/interp.c: New function find_method.  Use it
3317	within check_send_correctness.  When #perform: is used
3318	with an absent method, send #doesNotUnderstand: even
3319	if the number of arguments is wrong -- this is needed
3320	so that non-standard selector names can be used.
3321
33222003-09-24  Paolo Bonzini  <bonzini@gnu.org>
3323
3324	* libgst/comp.c: Define _gst_process_attributes_array,
3325	split process_attribute out of process_attributes,
3326	rename this one to process_attributes_tree.
3327	* libgst/comp.h: Declare process_attributes
3328	* libgst/prims.def: Use _gst_process_attributes_array,
3329	accepting an array of Messages instead of a primitive
3330	number in VMpr_CompiledMethod_create.
3331
33322003-09-20  Paolo Bonzini  <bonzini@gnu.org>
3333
3334	* libgst/lib.c: Exit with status 1 if a wrong option is
3335	specified.
3336
33372003-09-18  Paolo Bonzini  <bonzini@gnu.org>
3338
3339	* libgst/interp-bc.inl: Only set last_primitive for succeeded
3340	primitives.
3341
33422003-09-15  Paolo Bonzini  <bonzini@gnu.org>
3343
3344	* libgst/interp-bc.inl: Search #doesNotUnderstand: in
3345	superclass if searching for a message fails during a send
3346	to super.
3347	* libgst/comp.c: Sending to super from a root class is
3348	now an error.
3349
3350	* libgst/byte.h: Retouch the encoding of PUSH_SPECIAL in order
3351	to simplify the implementation
3352	* libgst/vm.def: Fix it
3353	* libgst/byte.c: Fix the MATCH_BYTECODES occurrences
3354	* libgst/opt.c: Fix the MATCH_BYTECODES occurrences
3355	* libgst/xlat.c: Fix the MATCH_BYTECODES occurrences
3356
3357	* libgst/interp-bc.inl: Simplify most of the macro cruft.
3358	* libgst/vm.def: Move the rest here.
3359
33602003-09-14  Paolo Bonzini  <bonzini@gnu.org>
3361
3362	* libgst/vm.def: Reimplement jump lookahead
3363	* libgst/interp-bc.inl: With some code here too.
3364
33652003-09-12  Paolo Bonzini  <bonzini@gnu.org>
3366
3367	* libgst/byte.def: Add superoperators
3368	* libgst/vm.def: Add superoperators
3369	* libgst/opt.c: Fix latent bugs exposed by superoperators
3370
3371	* libgst/interp.c: Get rid of the useless third
3372	parameter to SEND_MESSAGE
3373	* libgst/interp-bc.inl: Likewise
3374	* libgst/interp-jit.inl: Likewise
3375	* libgst/prims.def: Likewise
3376	* libgst/vm.def: Likewise
3377
33782003-09-11  Paolo Bonzini  <bonzini@gnu.org>
3379
3380	* libgst/comp.c: Compile #and:/#or: to a shorter
3381	sequence
3382
3383	* libgst/genvm-parse.y: One more little language, ...
3384	* libgst/genvm-scan.l: ... with its scanner, ...
3385	* libgst/genvm.h: ... its header file, ...
3386	* libgst/vm.def: ... its source code, ...
3387	* libgst/vm.inl: ... and its output, ...
3388	* libgst/interp-bc.inl: ... which is included here.
3389
33902003-09-09  Paolo Bonzini  <bonzini@gnu.org>
3391
3392	* libgst/opt.c: Support superoperator synthesis.
3393	* libgst/superop1.inl: New automatically generated file.
3394	* libgst/superop2.inl: New automatically generated file.
3395
33962003-09-08  Paolo Bonzini  <bonzini@gnu.org>
3397
3398	* libgst/genbc-decl.y: Support multiple dispatch statements.
3399
34002003-09-07  Paolo Bonzini  <bonzini@gnu.org>
3401
3402	* libgst/dict.c: Create CSymbols as an instance of Namespace.
3403
34042003-09-05  Paolo Bonzini  <bonzini@gnu.org>
3405
3406	* libgst/opt.c: Fix peephole optimizer's jump fixup
3407	pass for new bytecode set.  Verify jumping in range
3408	and jumping past an extension bytecode.
3409
34102003-09-04  Paolo Bonzini  <bonzini@gnu.org>
3411
3412	* libgst/byte.def: Modify for new syntax and bytecode set
3413	* libgst/genbc-scan.l: Modify for new syntax
3414	* libgst/genbc-decl.y: Modify for new syntax
3415	* libgst/byte.c: Accept two parameters in _gst_compile_byte
3416	* libgst/byte.h: Modify for new bytecode set
3417	* libgst/comp.c: Modify for new bytecode set, death to many
3418	functions
3419	* libgst/interp-bc.inl: Modify for new bytecode set
3420	* libgst/opt.c: Modify for new bytecode set, momentary death
3421	to peephole optimizer (will come back new and improved...)
3422
3423	* libgst/builtins.gperf: New file.
3424	* libgst/builtins.inl: New automatically generated file.
3425	* libgst/sym.c: Include builtins.gperf's hash function
3426	* libgst/sym.h: Declare it
3427
34282003-09-02  Paolo Bonzini  <bonzini@gnu.org>
3429
3430	* libgst/comp.c: Don't rely on _gst_is_kernel_file
3431	* libgst/input.c: Death to _gst_store_no_source and _gst_is_kernel_file
3432	* libgst/input.h: Death to _gst_store_no_source and _gst_is_kernel_file
3433	* libgst/lib.c: Death to _gst_store_no_source and -s.
3434
3435	* libgst/interp.c: Don't let the current process die on image
3436	reload.
3437
34382003-08-25  Paolo Bonzini  <bonzini@gnu.org>
3439
3440	* libgst/cint.c: Fix variadic functions.
3441	* libgst/opt.c: Fix verification of nested array constructors.
3442
34432003-08-09  Paolo Bonzini  <bonzini@gnu.org>
3444
3445	* libgst/security.c: New file
3446	* libgst/security.h: New file
3447	* libgst/lib.c: Load Security.st
3448	* libgst/dict.inl: Provide OrderedCollection accessors
3449
34502003-07-21  Paolo Bonzini  <bonzini@gnu.org>
3451
3452	* libgst/cint.c: Allow to pass integers as float or doubles
3453	(but not vice versa).
3454
34552003-07-13  Paolo Bonzini  <bonzini@gnu.org>
3456
3457	* libgst/dict.c: Make Character not indexed.
3458	* libgst/oop.c: Make Character's asciiValue an OOP.
3459	* libgst/oop.h: Make Character's asciiValue an OOP.
3460	* libgst/prims.def: Remove Character>>#asciiValue primitive.
3461
34622003-07-10  Paolo Bonzini  <bonzini@gnu.org>
3463
3464	* libgst/comp.c: Recalculate number of temporaries used
3465	by a block after it is compiled.
3466
34672003-07-09  Paolo Bonzini  <bonzini@gnu.org>
3468
3469	* libgst/oop.c: Don't scavenge before allocating big
3470	objects.
3471	* libgst/prims.def: Use _gst_init_mem to set GC
3472	parameters.
3473
34742003-07-08  Paolo Bonzini  <bonzini@gnu.org>
3475
3476	* libgst/interp.c: Initialize Processor's gcSemaphore
3477	* libgst/interp.h: Define gcSemaphore and gcArray
3478	* libgst/dict.c: Likewise
3479	* libgst/oop.c: Use it to mourn objects
3480	* libgst/sym.h: No mourn symbol anymore
3481	* libgst/sym.c: No mourn symbol anymore
3482
3483	* libgst/dict.c: Use IS_OOP_VALID_GC during image load
3484	* libgst/oop.c: Use IS_OOP_VALID_GC during the GC
3485	* libgst/oop.inl: Complicate validity test to take
3486	into account incremental GC-ing of old objects.
3487	* libgst/save.c: Use IS_OOP_VALID_GC since we finish
3488	the incremental GC before saving.
3489
34902003-07-07  Paolo Bonzini  <bonzini@gnu.org>
3491
3492	* libgst/mpz.c: *_si routines accept a signed integer,
3493	not an unsigned.
3494	* libgst/xlat.c: Inline the class primitive, don't inline
3495	#class
3496	* libgst/interp-bc.inl: Don't inline #class but cache it.
3497	* libgst/interp.c: Cache primitives for #class.
3498
34992003-07-04  Paolo Bonzini  <bonzini@gnu.org>
3500
3501	* libgst/genbc-impl.y: Output a small comment with the
3502	file and line where each MATCH_BYTECODES block was defined.
3503	* libgst/xlat.c: Use genbc here too... -500 lines, gotta
3504	like this :-)
3505
35062003-07-03  Paolo Bonzini  <bonzini@gnu.org>
3507
3508	* libgst/comp.h: Define MTH_USER_DEFINED
3509	* libgst/comp.inl: Define GET_METHOD_NUM_ARGS
3510	* libgst/interp-bc.inl: Support user-defined methods
3511	* libgst/opt.c: Fix fall-out in the JIT from the
3512	introduction of genbc, support subclasses of CompiledMethod
3513	* libgst/str.c: Fix fall-out from the size_t-ification
3514	of max_buf_len
3515	* libgst/sym.c: Define a new symbol for
3516	#valueWithReceiver:withArguments:
3517	* libgst/sym.h: Likewise
3518	* libgst/xlat.c: Fix fall-out in the JIT from the new
3519	meaning of bytecode 200, and support user-defined methods
3520
35212003-06-27  Paolo Bonzini  <bonzini@gnu.org>
3522
3523	* libgst/opt.c: Verify sends to super
3524
35252003-06-25  Paolo Bonzini  <bonzini@gnu.org>
3526
3527	* libgst/dict.c: Remove values instance variable,
3528	store key/value pairs in adjacent slots.
3529	* libgst/dict.h: Ditto
3530	* libgst/dict.inl: Ditto
3531
3532	* libgst/opt.c: Check for Array bounds in verifier
3533	* libgst/lib.c: Initialize compiler after interpreter
3534
3535	* libgst/comp.c: Store attributes in MethodInfo objects
3536	* libgst/comp.h: Add attributes field to gst_method_info
3537	* libgst/dict.c: Make MethodInfo indexable
3538
35392003-06-23  Paolo Bonzini  <bonzini@gnu.org>
3540
3541	* libgst/comp.c: Death to _gst_get_method_descriptor and
3542	_gst_set_method_descriptor.
3543
3544	* libgst/alloc.h: Remove last occurrences of the register keyword
3545	* libgst/byte.h: Remove last occurrences of the register keyword
3546	* libgst/oop.h: Remove last occurrences of the register keyword
3547
3548	* libgst/comp.c: Apply untrusted attribute to CompiledMethods
3549	and CompiledBlocks as well.
3550	* libgst/opt.c: Check untrusted attribute for CompiledMethods.
3551	* libgst/prims.def: New primitive VMpr_CompiledCode_verificationResult
3552
35532003-06-22  Paolo Bonzini  <bonzini@gnu.org>
3554
3555	* libgst/comp.c: Constify _gst_display_compilation_trace and
3556	_gst_invoke_hook
3557	* libgst/comp.h: Constify _gst_display_compilation_trace and
3558	_gst_invoke_hook
3559	* libgst/dict.c: Constify class_definition and several functions
3560	* libgst/interp.h: Constify prim_table_entry
3561	* libgst/interp.c: Constify stop_executing
3562	* libgst/lib.c: Constify several variables
3563	* libgst/lib.h: Constify several variables
3564	* libgst/gst-parse.y: Constify several variables
3565	* libgst/sym.c: Constify several variables and functions
3566	* libgst/sym.h: Constify several variables and functions
3567	* libgst/tree.c: Constify several variables and functions
3568	* libgst/tree.h: Constify several variables and functions
3569
3570	* libgst/sysdep.c: Use #elif
3571
3572	* libgst/sym.c: Trusted instance variables of an untrusted
3573	class are read-only.  Same goes for class variables.  The
3574	instance variables array is scanned backwards (faster and
3575	more correct).
3576
35772003-06-20  Paolo Bonzini  <bonzini@gnu.org>
3578
3579	* libgst/opt.c: Death to stack_balance_table and
3580	jump_offsets
3581
35822003-06-19  Paolo Bonzini  <bonzini@gnu.org>
3583
3584	* libgst/genbc-decl.y, libgst/genbc-impl.y, libgst/genbc-scan.l
3585	libgst/genbc.c, libgst/genbc.h, libgst/byte.def: new files
3586	* libgst/byte.c: Use genbc's facilities
3587	* libgst/opt.c: Use genbc's facilities
3588	* libgst/gstpriv.h: Include match.h
3589
35902003-06-17  Paolo Bonzini  <bonzini@gnu.org>
3591
3592	* libgst/comp.inl: Define NUM_METHOD_LITERALS
3593	* libgst/gstpriv.h: Define F_VERIFIED and IS_OOP_VERIFIED
3594	* libgst/interp-bc.inl: Invoke bytecode verifier
3595	* libgst/xlat.c: Ditto
3596	* libgst/opt.c: Include bytecode verifier.  Set stack
3597	balance for return opcodes to -1.  Be less forgiving in
3598	_gst_compute_stack_position (abort instead of giving errors)
3599	since the bytecode verifier should have tested the assertions.
3600
36012003-06-15  Paolo Bonzini  <bonzini@gnu.org>
3602
3603	* libgst/xlat.c: New function _gst_reset_inline_caches;
3604	prefix _gst_ to global functions
3605	* libgst/xlat.h: Ditto
3606	* libgst/interp.c: Invoke _gst_reset_inline_caches
3607	* libgst/comp.c: Callers adjusted.
3608	* libgst/oop.c: Callers adjusted.
3609	* libgst/oop.inl: Callers adjusted.
3610	* libgst/prims.def: Callers adjusted.
3611
36122003-06-11  Paolo Bonzini  <bonzini@gnu.org>
3613
3614	* libgst/gstpriv.h: Check for SmallIntegers in
3615	read-only accessors.
3616	* libgst/prims.def: Use the above to simplify
3617	some checks.
3618
3619	* libgst/interp.c: Implement trustedness of contexts.
3620	* libgst/prims.def: Implement trustedness primitives.
3621	* libgst/gstpriv.h: Implement trustedness accessors.
3622	* libgst/comp.c: Don't allow primitives in untrusted
3623	classes.
3624
36252003-06-10  Paolo Bonzini  <bonzini@gnu.org>
3626
3627	* libgst/dict.c: Allow creating multiple subclasses of nil
3628	at bootstrap.  Store bits of the instance specification
3629	directly in the class_definition structures.
3630	* libgst/oop.c: Death to _gst_fixup_metaclass_objects.
3631	* libgst/oop.h: Ditto.
3632
36332003-06-09  Paolo Bonzini  <bonzini@gnu.org>
3634
3635	* libgst/interp-bc.inl: REGISTER with structs is not good.
3636	* libgst/interp-jit.inl: REGISTER with structs is not good.
3637	* libgst/xlat.c: Now that thisContext is no more, represent
3638	storing into thisContext as TREE_STORE | TREE_POP_INTO_ARRAY,
3639	not TREE_SEND | TREE_POP_INTO_ARRAY.
3640
36412003-06-08  Paolo Bonzini  <bonzini@gnu.org>
3642
3643	* libgst/comp.c: Push thisContext as "ContextPart thisContext"
3644	* libgst/byte.h: Death to the push thisContext bytecode
3645	* libgst/interp-bc.inl: Ditto
3646	* libgst/opt.c: Ditto
3647	* libgst/xlat.c: Ditto
3648
3649	* libgst/byte.h: BLOCK_COPY_SPECIAL --> MAKE_DIRTY_BLOCK
3650	* libgst/comp.c: Adjust.  Don't push nil or thisContext
3651	before making a dirty block.  Don't treat #blockCopy:
3652	as a special selector.
3653	* libgst/opt.c: Blocks accessing thisContext are
3654	dirty
3655	* libgst/interp.c: New function _gst_make_dirty_block.
3656	* libgst/interp.h: Declare it
3657	* libgst/interp-bc.inl: Call it from bytecode 200
3658	* libgst/xlat.c: Don't treat bytecode 200 as a special
3659	send, but as an all-of-its-own operation, call this
3660	function from the code generated in gen_dirty_block.
3661	* libgst/prims.def: Remove VMpr_CompiledBlock_blockCopy
3662	* libgst/jitpriv.h: Remove it from the internal functions
3663	* libgst/interp-jit.inl: Ditto
3664	* libgst/sym.c: Remove _gst_block_copy_symbol
3665	* libgst/sym.h: Ditto
3666
36672003-06-05  Paolo Bonzini  <bonzini@gnu.org>
3668
3669	* libgst/comp.c: For non-clean blocks, store CompiledBlocks
3670	directly in the method.
3671	* libgst/prims.def: Implement #blockCopy: for CompiledBlocks.
3672	* libgst/interp-bc.inl: Open code #blockCopy: for CompiledBlocks.
3673	* libgst/xlat.c: Inline #blockCopy: for CompiledBlocks.
3674
3675	* libgst/oop.c: Check for out of range _gst_mem.scan.queue_at
3676	while scanning, not in QUEUE_NEXT.
3677
3678	* libgst/comp.h: Define constants for the possible value of
3679	CompiledMethod flags.
3680	* libgst/comp.c: Use them
3681	* libgst/opt.c: Use them
3682	* libgst/interp-bc.inl: Ditto
3683	* libgst/xlat.c: Ditto; rewrite the handling of shortcut
3684	CompiledMethods to use a switch statement.
3685
36862003-06-04  Paolo Bonzini  <bonzini@gnu.org>
3687
3688	* libgst/comp.c: Flag duplicate primitives or bad primitive
3689	numbers as errors.
3690	* libgst/genpr-parse.y: Start primitive numbers
3691	from 1.
3692
36932003-05-30  Paolo Bonzini  <bonzini@gnu.org>
3694
3695	* libgst/lib.c: Remove logging mechanism
3696	* libgst/input.c: Ditto
3697	* libgst/input.h: Ditto
3698
36992003-05-30  Paolo Bonzini  <bonzini@gnu.org>
3700
3701	Replace primitives with generic attributes.
3702
3703	* libgst/comp.c: Walk through the attribute list in compile_method.
3704	Added _gst_make_attribute.  Return NULL from _gst_execute_statements
3705	if there was a compilation error.  Define the termination method
3706	before #methodsFor:.
3707	* libgst/comp.h: Declare this function
3708	* libgst/tree.c: Added _gst_make_attribute_list, and pretty printing
3709	of attributes
3710	* libgst/tree.h: Declare this function
3711	* libgst/dict.c: Moved _gst_resolve_primitive_name to inside
3712	prepare_primitive_numbers_map.  Added VMPrimitives as a
3713	pool dictionary of Object, so make it a Dictionary and initialize
3714	it in init_smalltalk_dictionary.
3715	* libgst/dict.h: Removed _gst_resolve_primitive_name
3716	* libgst/gst-parse.y: Modified the grammar.  Adjust for the change
3717	to _gst_execute_statements, above.
3718	* libgst/lex.c: Removed PRIMITIVE_START, added '<' and '>' as
3719	separate tokens.
3720	* libgst/sym.c: Added _gst_primitive_symbol and its initializer
3721	* libgst/sym.h: Added _gst_primitive_symbol
3722
37232003-05-27  Paolo Bonzini  <bonzini@gnu.org>
3724
3725	* libgst/prims.def: Add VMpr_Object_allOwners
3726	* libgst/dict.inl: Implement is_owner
3727	* libgst/dict.c: Terminate CallinProcesses when resuming
3728	from a snapshot.
3729	* libgst/interp.c: Made terminate_process extern, renamed
3730	to _gst_terminate_process.
3731
37322003-05-16  Paolo Bonzini  <bonzini@gnu.org>
3733
3734	* libgst/prims.def: Add more C->String primitives
3735
3736	* libgst/cint.c: Support long doubles and #cObjectPtr.
3737	* libgst/sym.h: Add _gst_long_double_symbol
3738	* libgst/sym.c: Add _gst_long_double_symbol
3739	* libgst/prims.def: Add long double access
3740	* libgst/callin.c: Add long double accessors
3741	* libgst/callin.h: Add long double accessors
3742	* libgst/gstpriv.h: Add long double accessors
3743
37442003-05-14  Paolo Bonzini  <bonzini@gnu.org>
3745
3746	* libgst/cint.c: Switch to libffi.  General reorganization.
3747	* libgst/cint.h: Remove _gst_lookup_function.
3748	* libgst/interp.c: Fix some printf formats
3749	* libgst/print.c: Fix some printf formats
3750
37512003-05-12  Paolo Bonzini  <bonzini@gnu.org>
3752
3753	* libgst/comp.c: Remove _gst_compiled_method_at
3754	and _gst_compiled_method_at_put (unused).
3755	* libgst/comp.h: Ditto.
3756	* libgst/dict.inl: Merge find_key and
3757	dictionary_association_at.
3758
37592003-05-10  Paolo Bonzini  <bonzini@gnu.org>
3760
3761	* libgst all files: Use intptr_t, size_t, ptrdiff_t,
3762	time_t, int32_t, uint32_t more widely
3763	* libgst/gstpriv.h: Include stdintx.h
3764
37652003-05-09  Paolo Bonzini  <bonzini@gnu.org>
3766
3767	*** Version 2.1.2 released.
3768
3769	* libgst/alloc.c: Rationalize inclusions
3770	* libgst/byte.c: Rationalize inclusions
3771	* libgst/callin.c: Rationalize inclusions
3772	* libgst/cint.c: Rationalize inclusions
3773	* libgst/comp.c: Rationalize inclusions
3774	* libgst/dict.c: Rationalize inclusions
3775	* libgst/dict.inl: Rationalize inclusions
3776	* libgst/events.c: Rationalize inclusions
3777	* libgst/gstpriv.h: Add more inclusions
3778	* libgst/heap.c: Rationalize inclusions
3779	* libgst/input.c: Rationalize inclusions
3780	* libgst/interp-bc.inl: Rationalize inclusions
3781	* libgst/interp.c: Rationalize inclusions
3782	* libgst/interp.inl: Rationalize inclusions
3783	* libgst/lex.c: Rationalize inclusions
3784	* libgst/lib.c: Rationalize inclusions
3785	* libgst/mpz.c: Rationalize inclusions
3786	* libgst/oop.c: Rationalize inclusions
3787	* libgst/opt.c: Rationalize inclusions
3788	* libgst/print.c: Rationalize inclusions
3789	* libgst/save.c: Rationalize inclusions
3790	* libgst/str.c: Rationalize inclusions
3791	* libgst/sym.c: Rationalize inclusions
3792	* libgst/sysdep.c: Rationalize inclusions
3793	* libgst/tree.c: Rationalize inclusions
3794	* libgst/xlat.c: Rationalize inclusions
3795	* libgst/comp.h: Rationalize inclusions
3796	* libgst/opt.h: Rationalize inclusions
3797	* libgst/interp.h: Rationalize inclusions
3798
37992003-05-06  Paolo Bonzini  <bonzini@gnu.org>
3800
3801	* libgst/interp.c: Define PROTECT_CURRENT_PROCESS_WITH
3802	and PROTECT_FROM_INTERRUPT_WITH.  Use them in
3803	parse_stream_with_protection
3804	* libgst/prims.def: Use them.
3805
3806	* libgst/cint.h: Declare _gst_errno and _gst_set_errno
3807	* libgst/cint.c: Saved_errno -> _gst_errno, implement
3808	_gst_set_errno
3809	* libgst/prims.def: The VMpr_ObjectMemory_snapshot
3810	primitive can fail; use _gst_set_errno
3811
3812	* libgst/save.c: Invoke hook after opening the file.
3813
38142003-04-28  Paolo Bonzini  <bonzini@gnu.org>
3815
3816	* libgst/input.c: Don't advance the pointer in a
3817	STREAM_STRING after EOF; don't unread an EOF as
3818	_gst_next_char will return an EOF again.
3819	* libgst/lex.c: Change the lexing functions to
3820	accept an int so that EOF and 255 are not confused.
3821
38222003-04-27  Paolo Bonzini  <bonzini@gnu.org>
3823
3824	* libgst/sysdep.c: Return ENOMEM properly under Win32.
3825	Separate detection of availability of a particular technique
3826	and reservation of memory.  find_heap_base renamed to
3827	anon_mmap_check.
3828
38292003-04-17  Paolo Bonzini  <bonzini@gnu.org>
3830
3831	*** Version 2.1.1 (stable) released.
3832
3833	* libgst/sysdep.c: Allow MAP_NORESERVE even if MAP_ANON
3834	is not available.  Encapsulate opening /dev/zero into
3835	a macro which is used the same way when MAP_ANON is used
3836	and when it is not.
3837
38382003-04-16  Paolo Bonzini  <bonzini@gnu.org>
3839
3840	* libgst/genpr-parse.y: Add ATTRIBUTE_UNUSED attributes to
3841	the primitives' arguments.
3842	* libgst/input.c: Use newer function rl_completion_matches
3843	instead of completion_matches.
3844	* libgst/alloc.c: Fix for Cygwin, always #undef small
3845	* libgst/sysdep.c: Fix for Cygwin, include process.h
3846	and don't do setsid if HAVE_SPAWNL
3847	* libgst/lib.c: Don't load .stinit in regression
3848	testing mode, disable regression testing mode when
3849	loading .stpre.
3850
38512003-04-12  Paolo Bonzini  <bonzini@gnu.org>
3852
3853	*** Version 2.1 (stable) released.
3854
38552003-04-09  Paolo Bonzini  <bonzini@gnu.org>
3856
3857	* libgst/interp-bc.inl: EndExecution must FLUSH,
3858	not END (this broke the IA64).
3859
38602003-04-08  Paolo Bonzini  <bonzini@gnu.org>
3861
3862	* libgst/interp.inl: Add definitions to support
3863	broken inttypes.h like FreeBSD's.
3864	* libgst/sysdep.c: Move the declaration of the FD
3865	static variable before _gst_osmem_alloc.
3866
38672003-04-07  Paolo Bonzini  <bonzini@gnu.org>
3868
3869	* libgst/dict.c: Fix mismatch between sizeof argument
3870	and actual type.
3871
38722003-03-30  Paolo Bonzini  <bonzini@gnu.org>
3873
3874	* libgst/lex.c: Strdup -> xstrdup
3875	* libgst/alloc.c: Define xstrdup
3876	* libgst/alloc.h: Define xstrdup
3877	* libgst/input.c: Strdup -> xstrdup
3878	* libgst/lex.c: Strdup -> xstrdup
3879	* libgst/lib.c: Strdup -> xstrdup
3880	* libgst/sysdep.c: Strdup -> xstrdup
3881
38822003-03-26  Paolo Bonzini  <bonzini@gnu.org>
3883
3884	* libgst/byte.c: Remove checks on availability of bytecode array.
3885	Make explicit calls to allocate bytecode array.
3886	* libgst/comp.c: Make explicit calls to allocate bytecode array.
3887	* libgst/opt.c: Likewise.
3888
3889	* libgst/comp.c: Associate stack depth to each bytecode array.
3890	Fix bugs along the way.
3891	* libgst/byte.c: Add support for saving and restoring stack
3892	depth.
3893	* libgst/byte.h: Fix declarations.  Move stack depth modification
3894	macros here from comp.c.
3895
3896	* libgst/comp.c: Count depth from 0, not from argCount+tempCount,
3897	and sum the number of arguments only at the end (because
3898	the tempCount might change if there are #to:do: loops!)
3899	* libgst/save.c: Check for file version <= VERSION_REQUIRED,
3900	not ==.
3901
39022003-03-23  Paolo Bonzini  <bonzini@gnu.org>
3903
3904	* libgst/prims.def: Extract a loop invariant from
3905	VMpr_Behavior_someInstance
3906
39072003-03-21  Paolo Bonzini  <bonzini@gnu.org>
3908
3909	* libgst/sysdep.c: Added _gst_full_write
3910	* libgst/input.c: Use it instead of _gst_write
3911	* libgst/save.c: Use it instead of _gst_write
3912
39132003-03-19  Paolo Bonzini  <bonzini@gnu.org>
3914
3915	* libgst/sysdep.c: Always provide _gst_recv & _gst_send
3916	* libgst/sysdep.h: Always declare them
3917	* libgst/save.c: Include socketx.h
3918
39192003-03-15  Paolo Bonzini  <bonzini@gnu.org>
3920
3921	* libgst/dict.inl: Fix initialization of word
3922	subclasses.
3923
39242003-03-14  Paolo Bonzini  <bonzini@gnu.org>
3925
3926	* libgst/sysdep.c: Make _gst_read and _gst_write
3927	abort on EFAULT
3928	* libgst/prims.def: Use them
3929	* libgst/input.c: Use them
3930
39312003-03-04  Paolo Bonzini  <bonzini@gnu.org>
3932
3933	* libgst/lib.c: Load exception handling before VFS.
3934	* libgst/sysdep.c: Redisorganize _gst_open_pipe into
3935	separate functions.  Use spawnl and Win32 pipes if
3936	available.
3937
39382003-03-02  Paolo Bonzini  <bonzini@gnu.org>
3939
3940	* libgst/oop.c: Don't reset the heap_limit if the
3941	heap was grown.
3942
39432003-03-01  Paolo Bonzini  <bonzini@gnu.org>
3944
3945	* libgst/heap.c: Move system dependent stuff...
3946	* libgst/sysdep.c: ...here
3947	* libgst/sysdep.h: Make it public.
3948
3949	* libgst/prims.def: Move enum with file operations...
3950	* libgst/interp.h: ...here.
3951
3952	* libgst/prims.def: Define primitive for sockets.
3953	* libgst/sysdep.c: Define _gst_full_send.
3954	* libgst/sysdep.h: Declare _gst_full_send.
3955
3956	* libgst/heap.c: Define routines for mmap/munmap.
3957	* libgst/heap.h: Declare them.
3958	* libgst/alloc.c: Use them.
3959
39602003-02-28  Paolo Bonzini  <bonzini@gnu.org>
3961
3962	* libgst/events.c: Include signalx.h.
3963	* libgst/heap.c: Include signalx.h.
3964	* libgst/interp.c: Include signalx.h.
3965	* libgst/sysdep.c: Include signalx.h.
3966
39672003-02-28  Paolo Bonzini  <bonzini@gnu.org>
3968
3969	* libgst/sysdep.c: Cook up a simple mechanism to disable
3970	and enable signals where the OS does not provide that (again,
3971	MinGW32).  Fix semicolons in DISABLE and ENABLE.  Don't block
3972	fatal errors.
3973
39742003-02-27  Paolo Bonzini  <bonzini@gnu.org>
3975
3976	* libgst/cint.c: Turn malloc to xmalloc
3977	* libgst/save.c: Turn malloc to xmalloc
3978	* libgst/sym.c: Turn free to xfree
3979
3980	* libgst/alloc.c: Disable usage as system malloc under MinGW32.
3981	* libgst/sysdep.c: Include process.h if we have it (MinGW32)
3982	* libgst/events.c: Likewise
3983	* libgst/sysdep.c: Implement _gst_mem_protect
3984	* libgst/sysdep.h: Declare it and PROT_*
3985	* libgst/oop.c: Use it
3986
39872003-02-25  Paolo Bonzini  <bonzini@gnu.org>
3988
3989	* libgst/oop.c: Avoid out-of-memory while compacting
3990	* libgst/print.c: Tweak the precision for FloatE's,
3991	FloatD's and FloatQ's depending on float.h, except
3992	in regression testing mode.
3993
39942003-02-15  Paolo Bonzini  <bonzini@gnu.org>
3995
3996	* libgst/heap.c: Support !HAVE_SBRK
3997	* libgst/prims.def: Support !HAVE_USLEEP
3998	* libgst/sysdep.c: Use _beginthread under MinGW32 instead of
3999	CreateThread
4000	* libgst/interp.c: Use raise instead of kill
4001	* libgst/sysdep.c: Ditto
4002	* libgst/events.c: Ditto
4003
40042003-02-13  Paolo Bonzini  <bonzini@gnu.org>
4005
4006	* libgst/gst.h: Tweak a little the definition of alloca
4007	* libgst/heap.c: Fix typos, add WIN32_LEAN_AND_MEAN
4008	* libgst/oop.c: Add cast to fix gcc 2.95 warning
4009	* libgst/prims.def: Use POP_N_OOPS to fix gcc 2.95 warning
4010	* libgst/save.c: Disable mmap-ing under WIN32
4011	* libgst/sysdep.c: Add WIN32_LEAN_AND_MEAN
4012
40132003-03-09  Paolo Bonzini  <bonzini@gnu.org>
4014
4015	* libgst/interp.c: Don't print C backtrace during
4016	compilation if SIGINT is received.
4017
40182003-02-07  Paolo Bonzini  <bonzini@gnu.org>
4019
4020	* libgst/heap.c: Fix brokenness of Win32 implementation.
4021	* libgst/alloc.c: Add a very basic logging mechanism.
4022	* libgst/interp.c: Add a very basic backtracing mechanism
4023	to the signal handlers.  Trap SIGILL when JIT-compiling.
4024	Fix mismatch between process operation of JIT compiler
4025	and bytecode interpreter.
4026	* libgst/print.c: Print FloatD and FloatQ objects with
4027	the correct letter for the exponent
4028
40292003-02-06  Paolo Bonzini  <bonzini@gnu.org>
4030
4031	* libgst/alloc.c: Abort on an evident double free (two
4032	frees of the same object without any free on the same
4033	page in the middle).
4034	* libgst/oop.c: Add notice about bad interaction between
4035	SIGSEGV trapping and valgrind.
4036	* libgst/events.c: Use pointer to tail's next pointer
4037	instead of pointer to tail.  Suggested by Carlos Moran.
4038
40392003-02-03  Paolo Bonzini  <bonzini@gnu.org>
4040
4041	* libgst/alloc.c: Allow one to free the NULL pointer
4042	liberally.
4043	* libgst/opt.c: Drop broken code.
4044	* libgst/opt.h: Adjust prototypes
4045	* libgst/xlat.c: Adjust users
4046
40472003-01-20  Paolo Bonzini  <bonzini@gnu.org>
4048
4049	* libgst/comp.c: Keep the returned value of a doit in
4050	the incubator until after the #afterEvaluation hook is
4051	completed.
4052
40532003-01-17  Paolo Bonzini  <bonzini@gnu.org>
4054
4055	* libgst/interp-jit.inl: Check for code not having been
4056	compiled yet moved before check for native_ip == 0
4057
40582003-01-16  Paolo Bonzini  <bonzini@gnu.org>
4059
4060	* libgst/lib.c: While loading standard files disable
4061	_gst_regression_testing.
4062
4063	* libgst/input.c: Define _gst_warningf and _gst_warningf_at
4064	* libgst/input.h: Declare them
4065	* libgst/gst-parse.y: Use them; don't trigger a warning
4066	when *defining* a method named #true, #false and the like
4067
4068	* libgst/save.c: Never read past the end of the file
4069
40702003-01-12  Paolo Bonzini  <bonzini@gnu.org>
4071
4072	* libgst/sysdep.c: Make child process a session group
4073	leader
4074
40752003-01-09  Paolo Bonzini  <bonzini@gnu.org>
4076
4077	* libgst/comp.c: Fix bug in _gst_execute_statements
4078
4079	* libgst/sym.c: Define _gst_pop_all_scopes
4080	* libgst/sym.h: Declare it
4081	* libgst/comp.c: Use it
4082
40832003-01-02  Paolo Bonzini  <bonzini@gnu.org>
4084
4085	* libgst/gst-parse.y: Get rid of right recursion and
4086	shift/reduce conflicts.
4087	* libgst/tree.c: TREE_STATEMENT_LIST now a list node
4088	* libgst/tree.h: Adjust documentation
4089	* libgst/comp.c: Adjust functions that compile
4090	statement lists.
4091
4092	* libgst/lib.c: Bump copyright year
4093	* libgst/interp-jit.inl: Cleanup #if 0 sections
4094	* libgst/prims.def: ValueAndResumeOnUnwind loses the
4095	cache_new_ip attribute.
4096
40972002-12-31  Paolo Bonzini  <bonzini@gnu.org>
4098
4099	* libgst/prims.def: Always use PUSH_OOP to push the
4100	result in VMpr_CObject_at.  Thanks to David Forster.
4101
41022002-12-29  Paolo Bonzini  <bonzini@gnu.org>
4103
4104	* libgst/cint.c: Strdup the name of the function in
4105	_gst_define_cunc (it is freed when the call happens
4106	from Smalltalk).  Thanks to David Forster.
4107
41082002-12-27  Paolo Bonzini  <bonzini@gnu.org>
4109
4110	*** Version 2.0g released
4111
4112	* libgst/prims.def: Fix ISO C99-ism
4113	* libgst/input.c: Fix compilation error when readline
4114	is not there
4115
41162002-12-19  Paolo Bonzini  <bonzini@gnu.org>
4117
4118	* libgst/oop.c: Don't print negative percentages
4119	* libgst/prims.def: Add ObjectMemory>>#abort primitive
4120	* libgst/interp-bc.inl: Fix single step mode
4121	* libgst/interp-jit.inl: Fix single step mode
4122
41232002-12-15  Paolo Bonzini  <bonzini@gnu.org>
4124
4125	* libgst/callin.c: Incubate everything sent through
4126	_gst_msg_sendf.
4127
41282002-12-12  Paolo Bonzini  <bonzini@gnu.org>
4129
4130	*** Version 2.0.10 released
4131
4132	* libgst/input.c: Register the file name object in
4133	_gst_get_cur_file_name, unregister it in my_close
4134	* libgst/oop.c: Add more assertions
4135	* libgst/save.c: Add more assertions
4136
41372002-12-11  Paolo Bonzini  <bonzini@gnu.org>
4138
4139	* libgst/gst-parse.y: New name of gst.y
4140	* libgst/tree.h: Adjust
4141
4142	* libgst/genpr-scan.l: New file
4143	* libgst/genpr-parse.y: New file
4144	* libgst/genprims.h: New file
4145	* libgst/prims.def: Merge with prims.inl again, but with
4146	genprims' syntax
4147	* libgst/interp.c: Remove cruft for multiple inclusions
4148	of prims.def, we only include the generated prims.inl
4149
41502002-12-05  Paolo Bonzini  <bonzini@gnu.org>
4151
4152	*** Version 2.0.9 (stable) and 2.0f (development) released
4153
4154	* libgst/interp.c: Add _gst_check_process_state
4155	* libgst/interp.h: Add _gst_check_process_state
4156
4157	* libgst/interp.c: Do suspend_process correctly when
4158	the process is in the middle of the process list.
4159
41602002-12-04  Paolo Bonzini  <bonzini@gnu.org>
4161
4162	* libgst/alloc.c: Abort instead of asserting
4163	* libgst/save.c: Likewise
4164
4165	* libgst/dict.c: Abort instead of calling _gst_debug
4166	* libgst/dict.inl: Likewise
4167	* libgst/gstpriv.h: Likewise
4168	* libgst/oop.c: Likewise
4169	* libgst/sym.c: Likewise
4170	* libgst/interp.c: Likewise
4171	* libgst/xlat.c: Likewise
4172
4173	* libgst/prims.inl: Abort on a bootstrapping error
4174	* libgst/interp.c: Catch SIGABRT instead of SIGSEGV
4175
41762002-12-01  Paolo Bonzini  <bonzini@gnu.org>
4177
4178	* libgst/heap.c: Provide a fallback whenever
4179	MAP_NORESERVE is used.
4180
41812002-11-29  Paolo Bonzini  <bonzini@gnu.org>
4182
4183	* libgst/gst.y: Fix a couple of shift/reduce conflicts
4184
4185	* libgst/gstpriv.h: Min->MIN, max->MAX, abs->ABS
4186	* libgst/mpz.c: Adjusted
4187	* libgst/opt.c: Adjusted
4188	* libgst/oop.c: Adjusted
4189	* libgst/save.c: Adjusted
4190
4191	* libgst/oop.c: Remove warning
4192	* libgst/prims.inl: Implement asynchronous call-out.
4193	* libgst/prims.def: Implement asynchronous call-out.
4194
41952002-11-19  Paolo Bonzini  <bonzini@gnu.org>
4196
4197	*** Version 2.0e released
4198
4199	* libgst/oop.c: Add _gst_grey_oop_range
4200	* libgst/oop.h: Declare it
4201	* libgst/prims.inl: Check for EFAULT and abort if so.
4202
42032002-11-16  Paolo Bonzini  <bonzini@gnu.org>
4204
4205	* libgst/sysdep.c: Always do the F_SETOWN fcntl after F_SETFL
4206	for the benefit of FreeBSD (thanks to Danilo Fiorenzano).
4207	And always do the F_SETFL fcntl before FIOASYNC for the
4208	benefit of Cygwin.
4209
42102002-11-15  Paolo Bonzini  <bonzini@gnu.org>
4211
4212	*** Version 2.0.8 (stable) released
4213
4214	* libgst/comp.c: Optionally make the method return the last value
4215	in _gst_compile_method, use that in _gst_execute_statements,
4216	don't free the trees in _gst_compile_method
4217	* libgst/gst.y: Adjust callers of _gst_compile_method and
4218	_gst_execute_statements, support ##(...) for compile-time-constants,
4219	free the trees here
4220	* libgst/tree.c: Remove parameter from _gst_free_tree
4221	* libgst/tree.h: Adjust _gst_free_tree
4222
4223	* libgst/dict.c: Get rid of CFunctionDescs
4224
42252002-11-14  Paolo Bonzini  <bonzini@gnu.org>
4226
4227	* libgst/prims.inl: New C callout primitive, removed
4228	methodOOP parameter from primitives
4229	* libgst/interp.c: Adjusted
4230	* libgst/interp.h: Adjusted
4231	* libgst/interp-bc.inl: Adjusted
4232	* libgst/interp-jit.inl: Adjusted
4233	* libgst/cint.c: Adjusted
4234	* libgst/cint.h: Adjusted
4235
4236	* libgst/lib.c: Load additional core classes *before* the C interface
4237	since it now uses ValueHolder.
4238
42392002-11-13  Paolo Bonzini  <bonzini@gnu.org>
4240
4241	* libgst/dict.inl: Define identity_dictionary_find_key
4242	* libgst/dict.c: Use it
4243
4244	* libgst/prims.inl: Moved parts to interp.c and prims.def
4245	* libgst/prims.def: Created from prims.inl
4246	* libgst/interp.c: Added parts of prims.inl
4247
42482002-11-12  Paolo Bonzini  <bonzini@gnu.org>
4249
4250	* libgst/prims.inl: Add VMpr_Semaphore_lock
4251
42522002-11-09  Paolo Bonzini  <bonzini@gnu.org>
4253
4254	* libgst/interp.c: Start a new process in
4255	_gst_prepare_execution_environment,
4256	implement _gst_nvmsg_send here, added suspend_process
4257	and terminate_process, refine detection of "No runnable
4258	process" condition
4259	* libgst/prims.inl: Handle the call-in chain
4260	* libgst/interp-bc.inl: New argument and return value for _gst_interpret
4261	* libgst/interp-jit.inl: New argument and return value for _gst_interpret
4262	* libgst/interp.h: Added _gst_nvmsg_send
4263	* libgst/comp.c: Use _gst_nvmsg_send to call #executeStatements
4264	* libgst/callin.c: Base everything on _gst_nvmsg_send
4265	* libgst/dict.c: Add DirectedMessage-related stuff and
4266	_gst_callin_process_class
4267	* libgst/dict.h: Likewise
4268	* libgst/lib.c: Load DirMessage.st early, and CallinProcess.st
4269
4270	* libgst/alloc.c: Don't move reallocated objects that
4271	get smaller (code produced by the JIT is not position
4272	independent!)
4273	* libgst/xlat.c: Fix some bit-rot
4274	* libgst/opt.c: Fix off-by-one error in _gst_compute_stack_positions
4275
42762002-11-08  Paolo Bonzini  <bonzini@gnu.org>
4277
4278	* libgst/heap.c: Use MAP_NORESERVE if available.
4279	* libgst/alloc.c: Resort to mmap-ed areas once we cannot
4280	use sbrk anymore.
4281
42822002-11-06  Paolo Bonzini  <bonzini@gnu.org>
4283
4284	* libgst/oop.c: Unprotect freed pages, fix bug in removing
4285	pages from remembered table upon freeing.  Blox up and running
4286	with generational and incremental GC.
4287	* libgst/save.c: Use buffered I/O.
4288
42892002-11-05  Paolo Bonzini  <bonzini@gnu.org>
4290
4291	* libgst/input.c: Strdup in _gst_push_string_stream
4292	* libgst/callin.c: So we have to close the streams
4293	* libgst/comp.c: Here as well
4294
4295	* libgst/alloc.c: Ensure a block has already been touched
4296	(written to) before doing free-list operations.  Otherwise,
4297	the SIGSEGV handler might allocate memory while the free-lists
4298	are not consistent.
4299	* libgst/oop.c: For #become:, ensure the two swapped objects are
4300	in the same generation.  Otherwise, references to the new-space
4301	object that used to point to the old-space object are not recorded
4302	in the remembered set.
4303
43042002-11-04  Paolo Bonzini  <bonzini@gnu.org>
4305
4306	*** Version 2.0e (development) released
4307
43082002-10-26  Paolo Bonzini  <bonzini@gnu.org>
4309
4310	* libgst/alloc.c: More hooks
4311	* libgst/oop.c: Use them
4312
43132002-10-25  Paolo Bonzini  <bonzini@gnu.org>
4314
4315	* libgst/interp-bc.inl: Fix an obscure re-entrancy bug
4316	in _gst_send_message_internal, which was commonly
4317	triggered by the new garbage collector in the ANSI test
4318	suite.
4319
43202002-10-23  Paolo Bonzini  <bonzini@gnu.org>
4321
4322	* libgst/oop.c: Put back support for growing the OOP table.
4323
43242002-10-22  Paolo Bonzini  <bonzini@gnu.org>
4325
4326	* libgst/sym.c: Add more consts
4327	* libgst/sym.h: Likewise
4328	* libgst/cint.c: Likewise
4329	* libgst/cint.h: Likewise
4330	* libgst/callin.c: Likewise
4331	* libgst/callin.h: Likewise
4332	* libgst/gstpub.h: Likewise
4333
43342002-10-22  Mike Castle  <dalgoda@ix.netcom.com>
4335
4336	* libgst/callin.c: Fixes for Tcl 8.4.0 (add some consts)
4337	* libgst/callin.h: Fixes for Tcl 8.4.0 (add some consts)
4338	* libgst/dict.c: Fixes for Tcl 8.4.0 (add some consts)
4339	* libgst/dict.h: Fixes for Tcl 8.4.0 (add some consts)
4340	* libgst/gstpub.h: Fixes for Tcl 8.4.0 (add some consts)
4341
43422002-10-21  Paolo Bonzini  <bonzini@gnu.org>
4343
4344	* libgst/alloc.c: Collect statistics
4345	* libgst/dict.c: Add instance variables to ObjectMemory
4346	* libgst/oop.c: Collect statistics
4347	* libgst/oop.h: Declare functions to export statistics
4348	* libgst/prims.inl: Adjust for statistic collection
4349
43502002-10-17  Paolo Bonzini  <bonzini@gnu.org>
4351
4352	*** Version 2.0.7 (stable) released
4353
4354	* libgst/alloc.c: Add some hooking abilities
4355
4356	* libgst/oop.c: Big rewrite for switch to generational GC
4357	* libgst/oop.h: Likewise
4358	* libgst/oop.inl: Likewise
4359	* libgst/save.c: Likewise
4360	* libgst/print.c: Likewise (debugging functions)
4361
4362	* libgst/gstpriv.h: Moved parts to oop.inl or oop.h, changed
4363	many flags for the new generational collector.
4364
4365	* libgst/dict.c: Adjust for changes in variable names
4366	* libgst/prims.inl: Adjust for changes in variable names
4367
4368       * libgst/gstpriv.h: define checks for !OPTIMIZE.
4369       * libgst/input.c: define readline_getc only if readline
4370       is used.
4371       * libgst/interp-bc.inl: fix syntax error for !OPTIMIZE.
4372       * libgst/lib.c: load FileDescr.st before ObjectMemory.
4373
43742002-10-15  Paolo Bonzini  <bonzini@gnu.org>
4375
4376       * libgst/lib.c: Print "GNU Smalltalk ready" only before
4377       reading from stdin.  `verbose' --> _gst_verbose.
4378       * libgst/lib.h: Declare _gst_verbose.
4379       * libgst/comp.c: Conditionalize printing of stats and
4380       explanations on _gst_verbose and _gst_regression_testing.
4381       * libgst/comp.h: Remove `quiet' parameter to
4382       _gst_execute_statements.
4383       * libgst/gst.y: Caller adjusted.
4384
43852002-10-13  Paolo Bonzini  <bonzini@gnu.org>
4386
4387       * libgst/interp.c: Include strspell.h.
4388       * libgst/prims.inl: Define VMpr_String_similarityTo.
4389
43902002-10-08  Paolo Bonzini  <bonzini@gnu.org>
4391
4392	* libgst/print.c: Don't segfault when printing a Metaclass
4393	that has no class yet.
4394
43952002-10-06  Paolo Bonzini  <bonzini@gnu.org>
4396
4397	* libgst/input.c: Add the period to the word-termination
4398	characters.
4399
4400	* libgst/dict.c: Declare AbstractNamespace and
4401	BindingDictionary; support arbitrary number of instance
4402	variables in dictionaries
4403	* libgst/dict.h: Likewise
4404	* libgst/dict.inl: Likewise
4405	* libgst/lib.c: Load AbstNamespace.st and BindingDict.st
4406
4407	* libgst/byte.h: Add LINE_NUMBER_BYTECODE; declared
4408	_gst_line_number
4409	* libgst/byte.c: Print it; added _gst_line_number
4410	* libgst/comp.c: Use _gst_line_number
4411	* libgst/gst.y: Track locations
4412	* libgst/lex.c: Track locations
4413	* libgst/input.h: Added _gst_get_location
4414	* libgst/input.c: Implemented it
4415	* libgst/tree.h: Added location field to trees
4416	* libgst/tree.c: Store locations in trees
4417	* libgst/interp-bc.c: Treat LINE_NUMBER_BYTECODE as nop
4418	* libgst/xlat.c: Treat LINE_NUMBER_BYTECODE as nop
4419
44202002-10-05  Paolo Bonzini  <bonzini@gnu.org>
4421
4422	* libgst/xlat.c: Set F_XLAT_REACHABLE in the method
4423	and block prolog.
4424	* libgst/oop.c: GC unused JITted code.
4425
44262002-10-02  Paolo Bonzini  <bonzini@gnu.org>
4427
4428	* libgst/heap.c: Use EFAULT as an addition to SIGSEGV instead
4429	of an alternative method to detect unmapped memory areas.
4430	* libgst/interp-bc.inl: Don't use [ a ... b ] initializers
4431	because Apple's gcc is actually an Objective C compiler.
4432
44332002-09-29  Paolo Bonzini  <bonzini@gnu.org>
4434
4435	* libgst/alloc.c: New file, from lib-src.
4436	* libgst/alloc.h: New file, from lib-src.
4437
44382002-09-28  Paolo Bonzini  <bonzini@gnu.org>
4439
4440	* libgst/dict.c: Added HomedAssociation and associated
4441	declarations
4442	* libgst/dict.h: Added _gst_homed_association_class
4443	* libgst/lib.c: Load it
4444
4445	* libgst/gstpriv.h: Remove finalization and add ephemerons
4446	* libgst/oop.c: Likewise
4447	* libgst/prims.inl: Likewise
4448	* libgst/sym.c: Remove #finalize symbol and add #mourn
4449	* libgst/sym.h: Likewise
4450
4451	* libgst/lib.c: Set line-based buffering for stdout in
4452	regression testing mode.
4453
44542002-09-26  Paolo Bonzini  <bonzini@gnu.org>
4455
4456	* libgst/dict.inl: Simplify inst_var_at and inst_var_at_put
4457	* libgst/prims.inl: Inst_var_at_put now void, adjust caller.
4458
44592002-09-25  Paolo Bonzini  <bonzini@gnu.org>
4460
4461	* libgst/gst.y: Better error recovery
4462
44632002-09-23  Paolo Bonzini  <bonzini@gnu.org>
4464
4465	* libgst/dict.inl: Do memcpy to char * instead of to
4466	double * (because that does not solve double unalignment
4467	problems).
4468	* libgst/input.c: My_getc reads unsigned chars.
4469
44702002-09-19  Paolo Bonzini  <bonzini@gnu.org>
4471
4472	* libgst/dict.c: Added interruptLock variable to Process
4473	* libgst/interp.h: Added interruptLock field to gst_process
4474	* libgst/interp.c: Semaphore_new() accepts a parameter
4475	for the initial number of signals.  Create the interruptLock
4476	when a new Process is created.
4477
44782002-09-18  Paolo Bonzini  <bonzini@gnu.org>
4479
4480	* libgst/interp.c: The highest priority process was being
4481	put in the process list for priority 4 even if it did
4482	not belong there.
4483
44842002-09-13  Paolo Bonzini  <bonzini@gnu.org>
4485
4486	*** Versions 2.0c (development) and 2.0.6 (stable) released
4487
4488	* libgst/prims.inl: Allow specifying a class as the
4489	current namespace
4490
44912002-09-11  Paolo Bonzini  <bonzini@gnu.org>
4492
4493	* libgst/lex.c: support :: As well as . to separate
4494	namespaces
4495	* libgst/gst.y: Do corresponding changes in the grammar
4496	as well as changes to support compile-time namespace
4497	resolution
4498	* libgst/dict.c: Allow specifying a class as a pool
4499	dictionary and create namespaces at bootstrap
4500	* libgst/sym.c: Extend VARIABLE_NODE treatment in
4501	_gst_find_variable to support compile-time namespace
4502	resolution
4503	* libgst/sym.h: _gst_find_variable accepts a tree_node
4504	* libgst/comp.c: Callers adjusted
4505	* libgst/tree.h: Split tree node type TREE_VARIABLE_LIST
4506	into TREE_VAR_DECL_LIST and TREE_VAR_ASSIGN_LIST
4507	* libgst/tree.c: Likewise
4508
4509	* libgst/dict.c: Give interrupt state to Processes
4510	* libgst/interp.h: Likewise
4511	* libgst/interp.c: Use it
4512	* libgst/prims.inl: Implement interrupt-handling
4513	primitives
4514
4515	* libgst/lib.c: Load RecursionLock.st, drop short names
4516	* libgst/dict.c: Give a name to Semaphores
4517	* libgst/interp.h: Likewise
4518
4519	* libgst/sysdep.h: _gst_disable_interrupts and
4520	_gst_enable_interrupts hold their state internally
4521	* libgst/sysdep.c: Implement this
4522	* libgst/events.c: Callers adjusted
4523	* libgst/interp-bc.inl: Callers adjusted
4524	* libgst/interp-jit.inl: Callers adjusted
4525	* libgst/prims.inl: Callers adjusted
4526	* libgst/interp.c: Callers adjusted
4527
45282002-09-10  Paolo Bonzini  <bonzini@gnu.org>
4529
4530	* libgst/comp.c: Compute stack depth correctly in the
4531	presence of cascades.
4532	* libgst/oop.c: Add valgrind hooks after OOPs are swept,
4533	fix _gst_alloc_words (was not always converting size
4534	from words to bytes)
4535
45362002-09-09  Paolo Bonzini  <bonzini@gnu.org>
4537
4538	* libgst/dict.c: Pass flags to alloc_oop
4539	* libgst/interp.c: Pass flags to alloc_oop
4540	* libgst/oop.c: Pass flags to alloc_oop, check
4541	for opportunities to grow the OOP table in sweep_oop
4542	* libgst/oop.inl: Receive flags in alloc_oop, force a
4543	GC as soon as possible (instead of triggering it)
4544	in low-water conditions
4545
4546	* libgst/print.c: Print subclasses of Association as
4547	Associations.
4548	* libgst/dict.h: Declared _gst_variable_binding_class
4549	* libgst/dict.c: Declared _gst_variable_binding_class,
4550	use NAMESPACE_AT_PUT
4551	* libgst/dict.inl: New function variable_binding_new
4552	and macro NAMESPACE_AT_PUT
4553	* libgst/sym.c: Use NAMESPACE_AT_PUT
4554	* libgst/lib.c: Load VarBinding.st
4555
45562002-09-05  Paolo Bonzini  <bonzini@gnu.org>
4557
4558	* libgst/xlat.c: Support push 8-bit value bytecodes
4559	* libgst/opt.c: Support push 8-bit value bytecodes
4560	* libgst/interp-bc.inl: Support push 8-bit value bytecodes
4561	* libgst/byte.c: Support push 8-bit value bytecodes
4562	* libgst/byte.h: Support push 8-bit value bytecodes
4563	* libgst/comp.c: Support push 8-bit value bytecodes
4564
4565	* libgst/interp.c: Add the alwaysPreempt parameter
4566	to resume_process.  Callers and documentation adjusted.
4567	* libgst/interp-bc.inl: Support single step mode.
4568	* libgst/interp-jit.inl: Support single step mode.
4569	* libgst/prims.inl: Add single stepping primitive.
4570
45712002-08-21  Paolo Bonzini  <bonzini@gnu.org>
4572
4573	* libgst/oop.c: Walk the OOP table forwards in
4574	sweep_pooled_contexts.  Correct off-by-one error
4575	in _gst_oop_index_valid.
4576	* libgst/prims.inl: Added branch hits.  Fix bug
4577	where a too short replacement collection caused
4578	the String>>#replaceFrom:to:with:startingAt: primitive
4579	to succeed without making changes to the receiver.
4580
45812002-08-20  Paolo Bonzini  <bonzini@gnu.org>
4582
4583	* libgst/sysdep.c: Pass SIGCHLD to the signal handler
4584	for asynchronous file polling, as it might reveal a
4585	POLLHUP event.
4586
45872002-08-19  Paolo Bonzini  <bonzini@gnu.org>
4588
4589	* libgst/dict.c: Accept -1 for isPipe in
4590	_gst_set_file_stream_file
4591	* libgst/prims.inl: Try to lseek to the end of the
4592	file descriptor to check if it behaves like a pipe,
4593	and consider EINVAL the same as ESPIPE.  This hack
4594	makes FileDescriptor and FileStream consider /proc
4595	entries as pipes.
4596
45972002-08-18  Paolo Bonzini  <bonzini@gnu.org>
4598
4599	* libgst/gst.y: Give an error message if a binding
4600	to an undeclared class is used.
4601
46022002-08-14  Paolo Bonzini  <bonzini@gnu.org>
4603
4604	*** Version 2.0.5 (stable) released
4605
4606	* libgst/lib.c: Return `int' from _gst_init_smalltalk
4607	instead of exiting; give an error message if a
4608	non-existent file is given for -I.
4609	* libgst/gstpub.h: Adjust documentation and prototype
4610	* main.c: Adjust caller
4611
46122002-08-12  Paolo Bonzini  <bonzini@gnu.org>
4613
4614	*** Version 2.0b (development) released
4615
46162002-08-07  Paolo Bonzini  <bonzini@gnu.org>
4617
4618	*** Versions 2.0a (development) and 2.0.4 (stable) released
4619
46202002-07-24  Paolo Bonzini  <bonzini@gnu.org>
4621
4622	* libgst/prims.inl: Added missing `break' statement
4623
46242002-07-22  Paolo Bonzini  <bonzini@gnu.org>
4625
4626	* libgst/lib.c: Don't load Browser.st
4627
46282002-07-17  Paolo Bonzini  <bonzini@gnu.org>
4629
4630  	*** Version 2.0.3 released
4631
46322002-07-15  Paolo Bonzini  <bonzini@gnu.org>
4633
4634	* libgst/xlat.c: Don't do class checks on global variables
4635	(they refer to the associations!)
4636
46372002-07-11  Paolo Bonzini  <bonzini@gnu.org>
4638
4639	*** Version 2.0.2 released
4640
46412002-07-05  Paolo Bonzini  <bonzini@gnu.org>
4642
4643	* libgst/dict.c: Define _gst_object_copy instead of
4644	_gst_dictionary_copy
4645	* libgst/prims.inl: Define a fast VMpr_Object_shallowCopy
4646
46472002-07-04  Paolo Bonzini  <bonzini@gnu.org>
4648
4649	* libgst/interp.h: Define MCF_ flags
4650	* libgst/prims.inl: Define VMpr_BlockClosure_valueAndResumeOnUnwind
4651	and VMpr_ContextPart_continue
4652	* libgst/interp.c: Complicate unwind_context, unwind_method,
4653	and define unwind_to to implement #ensure: correctly in the
4654	presence of non-local returns.
4655	* libgst/interp-bc.inl: Use MCF_ flags
4656	* libgst/xlat.c: Use MCF_ flags
4657
46582002-07-02  Paolo Bonzini  <bonzini@gnu.org>
4659
4660	* libgst/lex.c: Parse negative scaled decimal constants
4661	as negative; in general, parse them exactly without
4662	floating point errors.
4663	* libgst/prims.inl: Large-integer primitives pass when
4664	they receive LargeIntegerZero
4665	* libgst/mpz.c: Ensure the most significant limb of the
4666	gst_mpz objects is not zero
4667	* libgst/dict.c: Fix GC bug in _gst_grow_identity_dictionary
4668
46692002-06-25  Paolo Bonzini  <bonzini@gnu.org>
4670
4671	* libgst/lib.c: Load FloatD.st/FloatE.st/FloatQ.st
4672
4673	* libgst/lex.c: Parse floats as long doubles, distinguish
4674	FloatD/FloatE/FloatQ literals.
4675	* libgst/comp.c: Distinguish FloatD/FloatE/FloatQ trees
4676	* libgst/tree.c: Add TYPE parameter to _gst_make_float_constant
4677	* libgst/tree.h: Adjust prototype, define CONST_FLOATD/CONST_FLOATE
4678	CONST_FLOATQ
4679	* libgst/gst.y: Pass TYPE parameter to _gst_make_float_constant
4680
4681	* libgst/cint.c: Use FloatD/FloatE/FloatQ
4682	* libgst/callin.c: Use FloatD/FloatE/FloatQ
4683	* libgst/dict.c: Declared FloatD/FloatE/FloatQ
4684	* libgst/dict.h: Declared FloatD/FloatE/FloatQ
4685	* libgst/dict.inl: Declared functions to box and unbox FloatE's
4686	and FloatQ's
4687
4688	* libgst/mpz.c: Defined _gst_mpz_get_ld
4689	* libgst/mpz.h: Declared _gst_mpz_get_ld
4690	* libgst/prims.inl: Define primitives on FloatE/FloatQ
4691	* libgst/interp-bc.inl: Change open-coded math operations to use
4692	FloatD
4693
46942002-06-28  Paolo Bonzini  <bonzini@gnu.org>
4695
4696	*** Version 2.0.1 released
4697
46982002-06-27  Paolo Bonzini  <bonzini@gnu.org>
4699
4700	* libgst/lib.c: Don't require the image directory to be world-writable.
4701	* libgst/xlat.c: Fixed embarrassing syntax error.
4702
4703	* libgst/tree.c: Use %O.
4704	* libgst/sym.c: Likewise.
4705	* libgst/prims.inl: Likewise.
4706	* libgst/byte.c: Likewise.
4707	* libgst/comp.c: Likewise.
4708	* libgst/dict.c: Likewise.
4709	* libgst/dict.h: Likewise.
4710	* libgst/interp-bc.inl: Likewise.
4711	* libgst/interp.c: Likewise.
4712	* libgst/xlat.c: Likewise.
4713
47142002-06-26  Paolo Bonzini  <bonzini@gnu.org>
4715
4716	* libgst/oop.c: Remove printing functions.
4717	* libgst/oop.h: Likewise.
4718	* libgst/dict.c: Likewise.
4719	* libgst/dict.h: Likewise.
4720	* libgst/sym.c: Likewise.
4721	* libgst/sym.h: Likewise.
4722	* libgst/print.c: Move them here...
4723	* libgst/print.h: ... and here.
4724	* libgst/lib.c: Call _gst_init_snprintfv.
4725
47262002-06-25  Paolo Bonzini  <bonzini@gnu.org>
4727
4728	*** Version 2.0 released
4729
47302002-06-19  Paolo Bonzini  <bonzini@gnu.org>
4731
4732	* libgst/dict.c: Removed exceptionHandlers variable from
4733	the Process class.
4734	* libgst/lib.c: Search in the class namespace before
4735	looking in the class pools
4736
47372002-06-13  Paolo Bonzini  <bonzini@gnu.org>
4738
4739  	* libgst/lib.c: reformat help message
4740
47412002-06-06  Paolo Bonzini  <bonzini@gnu.org>
4742
4743	* libgst/dict.inl: Always define 32-bit and 64-bit
4744	int<->OOP conversion functions
4745	* libgst/cint.c: Caller fixed
4746	* libgst/prims.inl: Support 64-bit file offsets
4747
4748	* libgst/interp-bc.inl: Added more branch prediction hints
4749
47502002-06-02  Paolo Bonzini  <bonzini@gnu.org>
4751
4752	* libgst/callin.c: Define _gst_set_c_object
4753	* libgst/callin.h: Declare _gst_set_c_object
4754	* libgst/gstpub.h: Define setCObject in the VMProxy struct
4755
47562002-05-30  Paolo Bonzini  <bonzini@gnu.org>
4757
4758	* libgst/save.c: Made some functions inline; remove amount
4759	of checks on wrong_endianness; store number of pointer
4760	instance variables in advance in the OOP if < 127.  A small
4761	improvement in image loading time, and an example of using
4762	F_COUNT (which will be used by GC in 2.1 to drop the
4763	recursive calls in the mark phase).
4764
47652002-05-30  Paolo Bonzini  <bonzini@gnu.org>
4766
4767	* libgst/save.c: Loop in the used part of the OOP table only
4768	(+15% average speedup on image loading time).
4769	* libgst/dict.c: Likewise
4770	* libgst/dict.h: Adapted prototype of
4771	_gst_init_dictionary_on_image_load
4772
4773	* libgst/lex.c: Use character literals for 1-char tokens
4774	* libgst/gst.y: Likewise
4775
4776	* libgst/jitpriv.h: New name of internal.h
4777	* libgst/xlat.c: Include jitpriv.h
4778	* libgst/interp-jit.inl: Include jitpriv.h instead of internal.h
4779	* libgst/gstpriv.h: Don't include internal.h
4780
47812002-05-28  Paolo Bonzini  <bonzini@gnu.org>
4782
4783	* libgst/dict.c: Don't cache the VMPrimitives dictionary, it
4784	causes bugs.
4785
47862002-05-23  Paolo Bonzini  <bonzini@gnu.org>
4787
4788	* libgst/comp.h: Changed _gst_invoke_init_block to
4789	_gst_invoke_hook.
4790	* libgst/comp.c: Trace exection of the hooks only if -E is
4791	specified; changed _gst_invoke_init_block to _gst_invoke_hook.
4792	* libgst/lib.c: Use _gst_invoke_hook
4793	* libgst/oop.c: Ditto
4794	* libgst/prims.inl: Ditto
4795	* libgst/save.c: Ditto
4796
4797	* libgst/dict.c: Keep dictionary sizes a power of two
4798	and scramble the bits
4799	* libgst/dict.inl: Keep dictionary sizes a power of two
4800	and scramble the bits
4801	* libgst/prims.inl: Declare a primitive to scramble the bits
4802	of a SmallInteger
4803	* libgst/sym.h: Keep symbol table size a power of two
4804	* libgst/sym.c: Use a simpler hash and scramble its bits
4805
48062002-05-14  Paolo Bonzini  <bonzini@gnu.org>
4807
4808	* libgst/mpz.c: Fix multiple evaluation of arguments
4809	of BYTE_INVERT; work around misinterpretation of
4810	mpn_?shift documentation
4811	* libgst/oop.c: Hardcode printing of infinite and nan
4812	values in _gst_print_object, to avoid false regressions
4813	due to libc differences
4814
48152002-05-12  Paolo Bonzini  <bonzini@gnu.org>
4816
4817	* libgst/comp.c: Fire ObjectMemory events before
4818	and after evaluation in _gst_execute_statements
4819	* libgst/lib.h: Declared _gst_kernel_initialized
4820	* libgst/lib.c: Set _gst_kernel_initialized before
4821	invoking the #returnFromSnapshot event.
4822
48232002-05-11  Paolo Bonzini  <bonzini@gnu.org>
4824
4825	*** Version 1.96.6 released
4826
48272002-05-10  Paolo Bonzini  <bonzini@gnu.org>
4828
4829	* libgst/input.c: Fix spurious error from my_close
4830	when stdin is passed on the command line (via -)
4831
48322002-05-08  Paolo Bonzini  <bonzini@gnu.org>
4833
4834	* libgst/internal.h: _gst_internal_funcs now const
4835	* libgst/interp.c: Always mark thisContext (at worst,
4836	it is nil)
4837	* libgst/xlat.c: Include lightning.h, removed by
4838	mistake when switching to gstpriv.h; add const in
4839	dcd_send_special
4840
48412002-05-05  Paolo Bonzini  <bonzini@gnu.org>
4842
4843	* libgst/gst.h: ObjSize now an OOP
4844	* libgst/dict.inl: Likewise
4845	* libgst/xlat.c: Likewise
4846	* libgst/save.c: Likewise
4847	* libgst/oop.c: Likewise
4848	* libgst/mpz.c: Likewise
4849	* libgst/interp.c: Likewise
4850	* libgst/dict.c: Likewise
4851	* libgst/comp.c: Likewise
4852
48532002-05-02  Paolo Bonzini  <bonzini@gnu.org>
4854
4855	* libgst/gstpriv.h: Declare macros for branch prediction hints
4856	* libgst/interp-bc.inl: Use them
4857	* libgst/interp-jit.inl: Use them
4858	* libgst/interp.c: Use them
4859	* libgst/interp.inl: Use them
4860	* libgst/md-config.h: Use them
4861	* libgst/oop.c: Use them
4862	* libgst/oop.inl: Use them
4863
4864	* libgst/oop.c: Allocate objects outside the main heap
4865	in _gst_alloc_obj
4866	* libgst/oop.h: Declare _gst_big_objects_threshold
4867	* libgst/prims.inl: Added primitives to tune threshold
4868	for in-heap allocation
4869
4870	* libgst/oop.c: Modify calling convention for _gst_alloc_obj,
4871	in preparation for allocating outside the main heap
4872	* libgst/oop.h: Declaration adjusted.
4873	* libgst/dict.c: Callers adjusted.
4874	* libgst/oop.c: Callers adjusted.
4875
4876	* libgst/dict.inl: Modify calling convention for
4877	instantiation functions, to account for the change to
4878	_gst_alloc_obj and in preparation for allocating outside
4879	the main heap.
4880	* libgst/interp.c: Callers adjusted.
4881	* libgst/comp.c: Callers adjusted.
4882	* libgst/callin.c: Callers adjusted.
4883	* libgst/sym.c: Callers adjusted.
4884	* libgst/dict.c: Callers adjusted.
4885	* libgst/prims.inl: Callers adjusted.
4886
48872002-05-01  Paolo Bonzini  <bonzini@gnu.org>
4888
4889	* libgst/dict.c: Move C...Size et al. into CSymbols,
4890	refer to CSymbols as to a pool dictionary of ByteArray,
4891	CObject, Float, Integer.  Drop class comments, they are
4892	not needed here.  Create a RegressionTesting global
4893	variable that suppresses more sources of variance.
4894
48952002-04-18  Paolo Bonzini  <bonzini@gnu.org>
4896
4897	* libgst/dict.c: Don't set writePtr and writeEnd
4898	for FileDescriptors in _gst_set_stream_file
4899
49002002-04-16  Paolo Bonzini  <bonzini@gnu.org>
4901
4902	* libgst/prims.inl: Return NaN when transcendental
4903	functions fail.  Removed VMpr_LargeInteger_divide.
4904
49052002-04-14  Paolo Bonzini  <bonzini@gnu.org>
4906
4907	*** Version 1.96.5 released
4908
49092002-04-13  Paolo Bonzini  <bonzini@gnu.org>
4910
4911	* libgst/interp.c: Print a backtrace on SIGUSR1
4912	* libgst/oop.c: Gc_running -> _gst_gc_running
4913	* libgst/oop.h: Declare _gst_gc_running
4914
49152002-04-06  Paolo Bonzini  <bonzini@gnu.org>
4916
4917	* libgst/interp-bc.inl: Properly check for overflows on
4918	bitshifts (used to return 0 instead of 16r-80000000)
4919	* libgst/prims.inl: Likewise
4920
49212002-03-27  Paolo Bonzini  <bonzini@gnu.org>
4922
4923	* libgst/mpz.c: New file
4924	* libgst/mpz.h: New file
4925	* libgst/prims.inl: Implemented primitives for large integers
4926
49272002-03-25  Paolo Bonzini  <bonzini@gnu.org>
4928
4929	* libgst/md-config.h: Added cacheline definitions
4930	* libgst/interp.c: Added cacheline definitions
4931	* libgst/oop.c: Added cacheline definitions
4932	* libgst/xlat.c: Added cacheline definitions
4933
4934	* libgst/interp.inl: Use inttypes.h rather than stdint.h
4935
49362002-03-21  Paolo Bonzini  <bonzini@gnu.org>
4937
4938	* libgst/events.c: Don't include sys/select.h, we don't need it
4939	* libgst/gstpub.h: Don't include sys/select.h, we don't need it
4940	* libgst/sysdep.c: Support HP/UX's FIOSSAIOSTAT and
4941	FIOSSAIOOWN ioctls to setup asynchronous I/O
4942	* libgst/input.c: Check for EINTR when reading from a file
4943	* libgst/prims.inl: Check for EINTR when reading from a file
4944
4945	* libgst/lex.c: Skip _ inside numeric literals
4946
49472002-03-17  Paolo Bonzini  <bonzini@gnu.org>
4948
4949	* libgst/lib.c: Updated list of files for virtual filesystem layer
4950	* libgst/prims.inl: Implement the PRIM_MK_TEMP file operation.
4951
49522002-03-16  Paolo Bonzini  <bonzini@gnu.org>
4953
4954	* libgst/input.h: Added _gst_push_stream_oop
4955	* libgst/input.c: Implement stream operations for
4956	arbitrary OOP's.
4957	* libgst/prims.inl: Remove checks for String-ness
4958	in compilation primitives.
4959
49602002-03-12  Paolo Bonzini  <bonzini@gnu.org>
4961
4962	*** Version 1.96.4 released
4963
49642002-03-10  Paolo Bonzini  <bonzini@gnu.org>
4965
4966	* libgst/oop.h: _gst_gc_flip -> _gst_scavenge,
4967	_gst_minor_gcflip -> _gst_minor_scavenge
4968	* libgst/oop.c: Likewise
4969	* libgst/oop.inl: Likewise
4970	* libgst/save.c: Likewise
4971	* libgst/prims.inl: Likewise
4972	* libgst/interp.c: Likewise
4973
4974	* libgst/oop.c: GC flip -> scavenging
4975
49762002-02-28  Paolo Bonzini  <bonzini@gnu.org>
4977
4978	* libgst/gst.h: Removed private stuff
4979	* libgst/gstpriv.h: Private stuff from gst.h + inclusion
4980	of all the other headers
4981	* byte.c: Include gstpriv.h
4982	* callin.c: Include gstpriv.h
4983	* cint.c: Include gstpriv.h
4984	* comp.c: Include gstpriv.h
4985	* dict.c: Include gstpriv.h
4986	* events.c: Include gstpriv.h
4987	* gst.tab.c: Include gstpriv.h
4988	* heap.c: Include gstpriv.h
4989	* input.c: Include gstpriv.h
4990	* interp.c: Include gstpriv.h
4991	* lex.c: Include gstpriv.h
4992	* lib.c: Include gstpriv.h
4993	* oop.c: Include gstpriv.h
4994	* opt.c: Include gstpriv.h
4995	* save.c: Include gstpriv.h
4996	* str.c: Include gstpriv.h
4997	* sym.c: Include gstpriv.h
4998	* sysdep.c: Include gstpriv.h
4999	* tree.c: Include gstpriv.h
5000	* xlat.c: Include gstpriv.h
5001
50022002-02-26  Paolo Bonzini  <bonzini@gnu.org>
5003
5004	* libgst/xlat.c: Fixed a code generation bug for {} array
5005	constructors (two consecutive updates of the stack pointer).
5006
50072002-02-26  Paolo Bonzini  <bonzini@gnu.org>
5008
5009	Named primitives: interpreter changes
5010	-------------------------------------
5011	* libgst/prims.inl: Implement named primitives (vs. numbered)
5012	* libgst/interp.h: Reflect changes in the interface for named
5013	primitives
5014	* libgst/interp-bc.inl: Call the appropriate named primitive
5015	in MAYBE_PRIMITIVE
5016	* libgst/interp.c: Include prims.inl before interp-bc.inl or
5017	interp-jit.inl
5018	* libgst/internal.h: Include VMpr_BlockClosure_blockCopy
5019	in the internal functions
5020	* libgst/interp-jit.inl: Include VMpr_BlockClosure_blockCopy
5021	in the internal functions
5022	* libgst/xlat.c: Adapt to changes in the interface for named
5023	primitives
5024
5025	Named primitives: compiler changes
5026	----------------------------------
5027	* libgst/gst.y: Declare primitive as type <sval>
5028	* libgst/tree.h: PrimitiveIndex -> primitiveName
5029	* libgst/tree.c: Likewise
5030	* libgst/dict.h: Declared _gst_resolve_primitive_name
5031	* libgst/dict.c: Added _gst_resolve_primitive_name and
5032	init_primitives_dictionary
5033	* libgst/comp.c: Use _gst_resolve_primitive_name
5034
5035	Named primitives: image loading
5036	-------------------------------
5037	* libgst/dict.c: Added prepare_primitive_number_map, removed
5038	bit of init_runtime_objects to initialize the symbols and
5039	calling _gst_init_symbols instead.
5040	* libgst/sym.c: Added _gst_init_symbols, symbol_list not
5041	extern anymore
5042	* libgst/sym.h: Added _gst_init_symbols, symbol_list not
5043	extern anymore
5044	* libgst/comp.c: Added _gst_restore_primitive_number
5045	* libgst/comp.h: Declared _gst_restore_primitive_number
5046
50472002-02-26  Paolo Bonzini  <bonzini@gnu.org>
5048
5049	* libgst/callin.c: Implemented _gst_register_oop_array & co
5050	* libgst/callin.h: Declared _gst_register_oop_array & co
5051	* libgst/gstpub.h: Added registerOOPArray to the VMProxy
5052	* libgst/comp.c: Use pointers rather than indices to implement
5053	the literal vector, to be compatible with _gst_register_oop_array's
5054	conventions.  Use _gst_register_oop_array to register the
5055	literal vector, in init_compiler.
5056	* libgst/oop.c: Replaced mark_incubator_oops with a call to
5057	_gst_register_oop_array.
5058
5059	* libgst/dict.c: Removed CFunctionDescs from the list of pool
5060	dictionaries for Object.
5061
5062	* libgst/interp-bc.inl: Fixed a rare bug by invalidating
5063	last_primitive before exiting the interpreter.
5064
50652002-02-25  Paolo Bonzini  <bonzini@gnu.org>
5066
5067	* libgst/cint.c: Use AVL trees for the C function registry;
5068	get rid of _gst_init_cfunc_vec.
5069	* libgst/callin.c: Use red-black trees for the OOP registry;
5070	get rid of _gst_init_oopregistry.
5071	* libgst/lib.c: Get rid of _gst_init_oopregistry
5072	* libgst/callin.h: Get rid of _gst_init_oopregistry
5073
5074	* libgst/dict.c: Register the Smalltalk dictionary in
5075	init_runtime_objects
5076	* libgst/comp.c: Keep _gst_this_class & co. into the registry.
5077	Got rid of _gst_mark_compile_context.
5078	* libgst/comp.h: Removed _gst_mark_compile_context.
5079	* libgst/events.c: Removed _gst_mark_events_semaphores, use
5080	the registry instead.
5081	* libgst/events.h: Removed _gst_mark_events_semaphores
5082	* libgst/interp.c: Don't call _gst_mark_events_semaphores
5083	* libgst/oop.c: Remove the hooks in mark_oops that have been
5084	replaced by the registry (now that it is a tree it is also
5085	faster)
5086
5087	* libgst/interp.h: Declared _gst_async_signal_and_unregister
5088	* libgst/gstpub.h: Declared asyncSignalAndUnregister in
5089	the VMProxy
5090	* libgst/interp.c: Implemented _gst_async_signal_and_unregister
5091	* libgst/interp-bc.inl: Added glue for _gst_async_signal_and_unregister
5092	* libgst/interp-jit.inl: Added glue for _gst_async_signal_and_unregister
5093
50942002-02-23  Paolo Bonzini  <bonzini@gnu.org>
5095
5096	* libgst/lex.c: Document the functions and variables
5097	* libgst/lex.h: Likewise
5098	* libgst/input.c: Likewise
5099	* libgst/input.h: Likewise
5100	* libgst/sym.c: Likewise
5101	* libgst/sym.h: Likewise
5102	* libgst/sysdep.c: Likewise
5103	* libgst/sysdep.h: Likewise
5104
5105	* libgst/sym.c: Allow _ for variable names in the bootstrapping
5106	declarations.
5107
51082002-02-22  Paolo Bonzini  <bonzini@gnu.org>
5109
5110	* libgst/oop.c: Remove the routines to disable the GC
5111	* libgst/oop.h: Remove the routines to disable the GC
5112	* libgst/save.c: Remove the calls to disable the GC since
5113	the variable was never checked
5114
5115	* libgst/oop.c: Document the functions and variables
5116	* libgst/oop.h: Likewise
5117	* libgst/oop.inl: Likewise
5118
51192002-02-21  Paolo Bonzini  <bonzini@gnu.org>
5120
5121	* libgst/comp.c: Document the functions and variables
5122	* libgst/comp.inl: Likewise
5123	* libgst/byte.c: Likewise
5124	* libgst/byte.h: Likewise
5125	* libgst/dict.inl: Likewise
5126	* libgst/dict.c: Likewise
5127	* libgst/dict.h: Likewise
5128
51292002-02-20  Paolo Bonzini  <bonzini@gnu.org>
5130
5131	* libgst/comp.c: Document the functions and variables
5132	* libgst/comp.h: Likewise
5133	* libgst/input.c: Flush stdout after printing the prompt,
5134	if readline is not used.
5135
51362002-02-19  Paolo Bonzini  <bonzini@gnu.org>
5137
5138	* libgst/callin.c: Remove conditional on PICKY_VA_ARG,
5139	ANSI says it should really be picky (i.e. not accept
5140	a char type)
5141
5142	* libgst/interp.inl: Try to use long long or intmax_t
5143	to check overflow on multiplication
5144
5145	* libgst/interp-jit.inl: When refreshing the native IPs,
5146	special case the termination method so that its native
5147	instruction pointer is the special code to yield control
5148	back to _gst_interpret.
5149
5150	* libgst/interp.h: Document the functions and variables
5151	* libgst/interp-bc.inl: Likewise
5152	* libgst/interp-jit.inl: Likewise
5153	* libgst/prims.inl: Likewise
5154	* libgst/opt.c: Likewise
5155	* libgst/opt.h: Likewise
5156	* libgst/callin.c: Likewise
5157	* libgst/callin.h: Likewise
5158	* libgst/cint.c: Likewise
5159	* libgst/cint.h: Likewise
5160
51612002-02-16  Paolo Bonzini  <bonzini@gnu.org>
5162
5163	* libgst/interp.c: Document the functions and variables
5164
51652002-02-15  Paolo Bonzini  <bonzini@gnu.org>
5166
5167	* libgst/save.c: Document the functions and variables
5168	* libgst/save.h: Likewise
5169	* libgst/str.c: Likewise
5170	* libgst/str.h: Likewise
5171	* libgst/events.c: Likewise
5172	* libgst/events.h: Likewise
5173	* libgst/tree.c: Likewise
5174	* libgst/tree.h: Likewise
5175	* libgst/heap.c: Likewise
5176	* libgst/heap.h: Likewise
5177	* libgst/lib.c: Likewise
5178	* libgst/lib.h: Likewise
5179	* libgst/gst.h: Likewise
5180	* libgst/gstpub.h: Likewise
5181
5182	* libgst/byte.h: Remove leading double underscores from the guard
5183	* libgst/callin.h: Likewise
5184	* libgst/cint.h: Likewise
5185	* libgst/comp.h: Likewise
5186	* libgst/dict.h: Likewise
5187	* libgst/events.h: Likewise
5188	* libgst/gst.h: Likewise
5189	* libgst/gst.tab.h: Likewise
5190	* libgst/gstpub.h: Likewise
5191	* libgst/heap.h: Likewise
5192	* libgst/input.h: Likewise
5193	* libgst/internal.h: Likewise
5194	* libgst/interp.h: Likewise
5195	* libgst/lex.h: Likewise
5196	* libgst/lib.h: Likewise
5197	* libgst/md-config.h: Likewise
5198	* libgst/memzero.h: Likewise
5199	* libgst/oop.h: Likewise
5200	* libgst/opt.h: Likewise
5201	* libgst/save.h: Likewise
5202	* libgst/str.h: Likewise
5203	* libgst/sym.h: Likewise
5204	* libgst/sysdep.h: Likewise
5205	* libgst/tree.h: Likewise
5206	* libgst/xlat.h: Likewise
5207
5208	* libgst/comp.inl: Remove the useless guard
5209	* libgst/dict.inl: Likewise
5210	* libgst/interp.inl: Likewise
5211	* libgst/oop.inl: Likewise
5212
52132002-02-07  Paolo Bonzini  <bonzini@gnu.org>
5214
5215	* libgst/lib.c: Show only the last copyright year.
5216
5217	* libgst/events.c: Major reengineering to avoid race
5218	conditions and dangling pointers... gee, how bad the
5219	code was before this! :-(
5220	* libgst/sysdep.c: To avoid cluttering the straces,
5221	don't set the same signal handlers as the last time
5222	in _gst_set_file_interrupt
5223	* libgst/interp-bc.inl: Protect interrupts while
5224	accessing async_queue_index (even though it is volatile)
5225	* libgst/interp-jit.inl: Likewise
5226
52272002-01-29  Paolo Bonzini  <bonzini@gnu.org>
5228
5229	*** Version 1.96.3 released.
5230
5231	* libgst/opt.c: Convert arguments to qsort and bsearch
5232	to accept two void *'s.
5233	* libgst/input.c: Likewise
5234
52352002-01-23  Paolo Bonzini  <bonzini@gnu.org>
5236
5237	* main.c: Converted to ANSI C and to the GNU
5238	coding standards
5239	* libgst/byte.c: Likewise
5240	* libgst/callin.c: Likewise
5241	* libgst/cint.c: Likewise
5242	* libgst/comp.c: Likewise
5243	* libgst/dict.c: Likewise
5244	* libgst/events.c: Likewise
5245	* libgst/gst.tab.c: Likewise
5246	* libgst/heap.c: Likewise
5247	* libgst/input.c: Likewise
5248	* libgst/interp.c: Likewise
5249	* libgst/lex.c: Likewise
5250	* libgst/lib.c: Likewise
5251	* libgst/oop.c: Likewise
5252	* libgst/opt.c: Likewise
5253	* libgst/save.c: Likewise
5254	* libgst/str.c: Likewise
5255	* libgst/sym.c: Likewise
5256	* libgst/sysdep.c: Likewise
5257	* libgst/tree.c: Likewise
5258	* libgst/xlat.c: Likewise
5259	* libgst/byte.h: Likewise
5260	* libgst/callin.h: Likewise
5261	* libgst/cint.h: Likewise
5262	* libgst/comp.h: Likewise
5263	* libgst/dict.h: Likewise
5264	* libgst/events.h: Likewise
5265	* libgst/gst.h: Likewise
5266	* libgst/gst.tab.h: Likewise
5267	* libgst/gstpub.h: Likewise
5268	* libgst/heap.h: Likewise
5269	* libgst/input.h: Likewise
5270	* libgst/internal.h: Likewise
5271	* libgst/interp.h: Likewise
5272	* libgst/lex.h: Likewise
5273	* libgst/lib.h: Likewise
5274	* libgst/md-config.h: Likewise
5275	* libgst/memzero.h: Likewise
5276	* libgst/oop.h: Likewise
5277	* libgst/opt.h: Likewise
5278	* libgst/save.h: Likewise
5279	* libgst/str.h: Likewise
5280	* libgst/sym.h: Likewise
5281	* libgst/sysdep.h: Likewise
5282	* libgst/tree.h: Likewise
5283	* libgst/xlat.h: Likewise
5284	* libgst/comp.inl: Likewise
5285	* libgst/dict.inl: Likewise
5286	* libgst/interp-bc.inl: Likewise
5287	* libgst/interp-jit.inl: Likewise
5288	* libgst/interp.inl: Likewise
5289	* libgst/oop.inl: Likewise
5290	* libgst/prims.inl: Likewise
5291
52922002-01-22  Paolo Bonzini  <bonzini@gnu.org>
5293
5294	* libgst/gst.y: Signal a warning if self, super, true, false,
5295	nil, or thisContext are sent.  General reformatting of the
5296	source code.
5297
52982002-01-18  Paolo Bonzini  <bonzini@gnu.org>
5299
5300	* libgst/dict.c: Removed initialization blocks
5301
53022002-01-17  Nigel Williams  <nigelw@wizardis.com.au>
5303
5304	* libgst/dict.c: Added atEnd variable to FileDescriptor
5305	* libgst/prims.inl: Provide a primitive to check if a
5306	descriptor is a pipe or a file.
5307
5308	* libgst/dict.c: Added timeSlice variable to ProcessorScheduler
5309	* libgst/events.c: Pass a third parameter to signalAfter
5310	* libgst/interp-bc.inl: Call setPreemptionTimer once the timer
5311	has been fired and acknowledged
5312	* libgst/interp-jit.inl: Call setPreemptionTimer once the timer
5313	has been fired and acknowledged
5314	* libgst/interp.c: New functions related to preemptive
5315	multitasking
5316	* libgst/interp.h: Added timeSlice variable to ProcessorScheduler
5317	* libgst/sysdep.h: Added support for process-time timers (like
5318	ITIMER_VIRTUAL)
5319	* libgst/sysdep.c: Added support for process-time timers (like
5320	ITIMER_VIRTUAL)
5321
53222002-01-15  Paolo Bonzini  <bonzini@gnu.org>
5323
5324	* libgst/lib.c: Ensure that the image path is the directory
5325	from which we loaded the image, rather than the default image
5326	path.
5327
53282002-01-04  Paolo Bonzini  <bonzini@gnu.org>
5329
5330	*** Version 1.96.2 released
5331
53322002-01-02  Paolo Bonzini  <bonzini@gnu.org>
5333
5334	* libgst/dict.c: Add the Source class variable to the Random
5335	class.
5336	* libgst/input.c: Don't use readline unless stdin is a TTY.
5337	* libgst/lib.c: Changed banner to "GNU Smalltalk ready"
5338	(lowercase r)
5339
53402001-12-12  Paolo Bonzini  <bonzini@gnu.org>
5341
5342	* libgst/events.c: Poll until there are no pending events
5343
53442001-11-20  Paolo Bonzini  <bonzini@gnu.org>
5345
5346	*** Version 1.96.1 released
5347
53482001-11-13  Paolo Bonzini  <bonzini@gnu.org>
5349
5350	* libgst/gst.y: Implement #(true false nil) as per the ANSI
5351	standard.
5352
53532001-10-24  Paolo Bonzini  <bonzini@gnu.org>
5354
5355	* libgst/sysdep.c: Define O_ASYNC as FASYNC if not found.
5356
53572001-10-17  David Forster  <dforste@qwest.net>
5358
5359	* libgst/cint.c: Add uInt and uLong support for C interface.
5360	Change longType return to use fromCLong.
5361	* libgst/sym.c: Add uIntSymbol and uLongSymbol.
5362
53632001-10-16  Paolo Bonzini  <bonzini@gnu.org>
5364
5365	*** Version 1.95.5 released.
5366
5367	* libgst/lib.c: Observe quietExecution when loading
5368	.stinit and .stpre.
5369
53702001-10-06  Paolo Bonzini  <bonzini@gnu.org>
5371
5372	* libgst/lib.c: Fixed bugs after applying the two
5373	patches below.
5374
53752001-10-06  Nigel Williams  <nigelw@elder-gods.net>
5376
5377	* libgst/lib.c: Show error message if file not found
5378
53792001-08-28  Carlo Dapor  <catull_us@yahoo.com>
5380
5381	* libgst/lex.c: Reset floating point exception mask under FreeBSD.
5382	* libgst/lib.c: Switch to getopt_long for parsing long command line
5383	options.
5384
53852001-07-14  Paolo Bonzini  <bonzini@gnu.org>
5386
5387	* libgst/gst.h: Gee, what a hiatus!  Fixed for C++.
5388	* libgst/gstpub.h: Likewise
5389
53902001-06-16  Paolo Bonzini  <bonzini@gnu.org>
5391
5392	* libgst/interp.h: Defined PRIM_CHECK_INTERRUPT
5393	* libgst/prims.inl: Added PRIM_CHECK_INTERRUPT
5394	where required
5395	* libgst/xlat.c: EmitInterruptCheck called from
5396	emitPrimitive only if PRIM_CHECK_INTERRUPT
5397
53982001-06-13  Paolo Bonzini  <bonzini@gnu.org>
5399
5400	* libgst/xlat.c: Create the IPMap when translating.
5401	Defined mapVirtualIP.  Store the IP at every possible
5402	synchronization point (emitInterruptCheck).
5403	* libgst/xlat.h: Declared mapVirtualIP.
5404
5405	* libgst/str.c: Declared addBufData
5406	* libgst/str.h: Defined addBufData
5407
5408	* libgst/xlat.c: Generate an interrupt check as part of
5409	the prolog rather than of the return bytecodes.
5410
54112001-06-12  Paolo Bonzini  <bonzini@gnu.org>
5412
5413	* libgst/interp-jit.inl: Defined refreshNativeIPs.
5414	* libgst/interp.c: ReturnIP --> nativeIP
5415	* libgst/interp.h: ReturnIP --> nativeIP
5416	* libgst/dict.c: ReturnIP --> nativeIP
5417	* libgst/save.c: Reset a context's nativeIP upon image load.
5418
54192001-06-08  Paolo Bonzini  <bonzini@gnu.org>
5420
5421	* libgst/sysdep.c: Open the slave pty before forking
5422
54232001-06-06  Paolo Bonzini  <bonzini@gnu.org>
5424
5425	* libgst/md-config.h: Define BRANCH_REGISTER for every
5426	architecture
5427	* libgst/interp-bc.inl: Put the prefetched address into
5428	a branch register.
5429
5430	* libgst/dict.c: Include sysdep.h
5431	* libgst/input.c: Removed unused variable in pushUNIXFile
5432	* libgst/prims.inl: Removed unused variable in primitive 254
5433	* libgst/sysdep.h: Declared fullWrite
5434
54352001-06-05  Paolo Bonzini  <bonzini@gnu.org>
5436
5437	* libgst/xlat.c: GetMethodBase became initTranslator
5438	* libgst/xlat.h: Likewise
5439	* libgst/interp.c: Got rid of the nativeBase
5440	* libgst/interp-jit.inl: Got rid of the nativeBase
5441
5442	* libgst/sysdep.c: Set the CLOEXEC flag in openFile
5443
54442001-06-01  Paolo Bonzini  <bonzini@gnu.org>
5445
5446	* libgst/events.c: Use poll(2) instead of select(2),
5447	I am told it is more scalable.
5448	* libgst/input.c: Likewise, for coherency.
5449
54502001-05-26  Paolo Bonzini  <bonzini@gnu.org>
5451
5452	* libgst/sysdep.c: Use ptys to create a pipe; when
5453	setting file interrupt with SIOCSGRP and FIOASYNC,
5454	check that both ioctls succeed.
5455
54562001-05-24  Paolo Bonzini  <bonzini@gnu.org>
5457
5458	* libgst/interp.c: Make unwindMethod return whether
5459	the return was successful
5460	* libgst/interp-bc.inl: Send #badReturnError if
5461	return from method was unsuccessful
5462	* libgst/xlat.c: Likewise
5463
5464	* libgst/interp-jit.inl: Added a comment re. the only
5465	serious bug remaining.
5466
54672001-05-23  Paolo Bonzini  <bonzini@gnu.org>
5468
5469	* libgst/heap.c: _WIN32 --> WIN32
5470	* libgst/gst.h: Define WIN32 if __CYGWIN__ or __CYGWIN32__
5471	* libgst/sysdep.c: _WIN32 --> WIN32
5472
54732001-05-22  Paolo Bonzini  <bonzini@gnu.org>
5474
5475	* libgst/xlat.c: Added support for inlined primitives
5476	* libgst/prims.inl: Marked a few primitives as inlined
5477	* libgst/dict.inl: Added accessors for the ISP_ISWORDS
5478	bit.
5479
54802001-05-20  Paolo Bonzini  <bonzini@gnu.org>
5481
5482	* libgst/lib.c: Remove calls to moncontrol; will be
5483	replaced by new profiling stuff.
5484	* libgst/prims.inl: Temporarily embed the moncontrol
5485	primitive into #if 0.
5486
54872001-05-17  Paolo Bonzini  <bonzini@gnu.org>
5488
5489	* libgst/dict.c: Recycle existing std{in,out,err}.
5490	* libgst/input.c: Wait for a character to be available
5491	before returning to Readline.
5492	* libgst/prims.inl: Reset errno to 0 after calling
5493	lseek.
5494
54952001-05-15  Paolo Bonzini  <bonzini@gnu.org>
5496
5497	* libgst/interp-jit.inl: In sendMessageInternal force
5498	a call to getNativeCode upon a cache miss
5499
55002001-05-11  Paolo Bonzini  <bonzini@gnu.org>
5501
5502	* libgst/xlat.c: Fixes for PowerPC (sizeof(jit_insn) > 1)
5503
55042001-05-04  Paolo Bonzini  <bonzini@gnu.org>
5505
5506	* libgst/cint.c: Support selfSmalltalk and variadicSmalltalk
5507	as additional parameter types
5508	* libgst/sym.c: Defined selfSmalltalkSymbol and
5509	variadicSmalltalkSymbol
5510	* libgst/sym.h: Declared selfSmalltalkSymbol and
5511	variadicSmalltalkSymbol
5512
55132001-04-30  Paolo Bonzini  <bonzini@gnu.org>
5514
5515	* libgst/prims.inl: Fixed buffer overflows involving
5516	oopVec.
5517
55182001-04-28  Paolo Bonzini  <bonzini@gnu.org>
5519
5520	* libgst/sysdep.h: Fixed isFinite, it reported -2.0 as
5521	infinite!
5522
5523	* libgst/callin.h: Declared basicSize
5524	* libgst/callin.c: Defined basicSize
5525	* libgst/gstpub.h: Added basicSize to the InterpreterProxy
5526
55272001-04-23  Paolo Bonzini  <bonzini@gnu.org>
5528
5529	* libgst/interp.c: Extrapolated a part of it into events.c,
5530	include events.h
5531	* libgst/prims.inl: Turn some primitives into calls to
5532	functions in events.c
5533	* libgst/events.c: New file
5534	* libgst/events.h: New file
5535
5536	* libgst/interp.h: Declared syncWait
5537	* libgst/interp.c: Defined syncWait from primitive 86's code
5538	* libgst/prims.inl: Primitive 86 now calls syncWait
5539	* libgst/gstpub.h: Declared syncWait in the interpreterProxy
5540	* libgst/callin.c: Likewise
5541
5542	* libgst/sysdep.c: Use socketpair to create a pipe
5543
55442001-04-16  Paolo Bonzini  <bonzini@gnu.org>
5545
5546	* libgst/dict.h: Declared fileDescriptorClass
5547	* libgst/dict.c: Declared fileDescriptorClass
5548	* libgst/lib.c: Load FileDescr.st
5549
5550	* libgst/opt.c: fix incorrect peephole optimization: Of
5551	two equal `pop/store into instance variable of new stack top'
5552	bytecodes, the second became a `duplicate stack top' bytecode
5553
55542001-04-15  Paolo Bonzini  <bonzini@gnu.org>
5555
5556	* libgst/callin.c: Use incAddOOP everywhere instead of
5557	registerOOP.  Added objectAlloc to the interpreterProxy
5558	* libgst/callin.h: Declared objectAlloc in the interpreterProxy
5559	* libgst/cint.c: InvokeCFunction now includes an incSavePointer
5560	and incRestorePointer pair.
5561	* libgst/gst.h: Make incAddOOP a single statement instead
5562	of a C block.
5563
5564	* libgst/cint.c: In pushSmalltalkObj, use the incubator rather
5565	than the registry.
5566	* libgst/cint.h: Removed declaration of enableGC, since the above
5567	change left it unused.
5568	* libgst/prims.inl: Removed primitive 264 (#enableGC:)
5569
55702001-04-02  Paolo Bonzini  <bonzini@gnu.org>
5571
5572	* libgst/dict.c: Declared objectMemoryClass
5573	* libgst/dict.h: Declared objectMemoryClass
5574	* libgst/lib.c: Load ObjMemory.st, not initialize.st
5575	* libgst/save.c: Raise ObjectMemory events
5576	* libgst/comp.c: Raise ObjectMemory events
5577	* libgst/oop.c: Raise ObjectMemory events
5578	* libgst/prims.inl: Raise ObjectMemory events
5579
55802001-03-31  Paolo Bonzini  <bonzini@gnu.org>
5581
5582	* libgst/callin.c: Implemented byteArrayToOOP and OOPToByteArray
5583	* libgst/gstpub.h: Declared byteArrayToOOP and OOPToByteArray in
5584	the VMProxy.
5585	* libgst/sysdep.c: Removed code to set the LANG environment
5586	variable on Win32 systems.
5587
55882001-03-28  Paolo Bonzini  <bonzini@gnu.org>
5589
5590	* libgst/dict.c: Added an `access' parameter to setFileStreamFile
5591	* libgst/prims.inl: Pass the `access' parameter to setFileStreamFile
5592	from primitive 254
5593
55942001-03-20  Paolo Bonzini  <bonzini@gnu.org>
5595
5596	* libgst/dict.c: Set up FileStream for new buffering scheme,
5597	and updated setFileStreamFile.
5598	* libgst/prims.inl: Implemented primitive 254 for new buffering
5599	scheme.  Incorporated primitives 247/248 (file-in) into 254.
5600
56012001-03-17  Paolo Bonzini  <bonzini@gnu.org>
5602
5603	* libgst/input.c: Implemented pushUNIXFile & co. in terms
5604	of file descriptors.
5605	* libgst/prims.inl: Implement FileStream in terms of file
5606	descriptors.
5607	* libgst/save.c: Use file descriptors.
5608	* libgst/sysdep.c: Modified openFile/openPipe to use
5609	file descriptors.
5610
56112001-03-05  Paolo Bonzini  <bonzini@gnu.org>
5612
5613	* libgst/comp.c: Bindings are simple oopConsts now.
5614	* libgst/tree.c: Resolve bindings as oopConsts.
5615	* libgst/tree.h: Removed bindingConst.
5616	* libgst/gst.y: Raise an error on an invalid binding.
5617
5618	* libgst/comp.c: initCompiler is now public.
5619	* libgst/comp.h: initCompiler is now public.
5620	* libgst/lib.c: Call initCompiler.
5621
56222001-03-01  Paolo Bonzini  <bonzini@gnu.org>
5623
5624	* libgst/md-config.h: Fixed typo in register allocation
5625	for the SPARC.
5626
56272001-03-01  Dirk Sondermann <d.sondermann@freenet.de>
5628
5629	* libgst/md-config.h: Disable register allocation on the
5630	SPARC (possibly temporary change).
5631
56322001-02-23  Paolo Bonzini  <bonzini@gnu.org>
5633
5634	*** Released version 1.95.3
5635
56362001-02-19  Paolo Bonzini  <bonzini@gnu.org>
5637
5638	* libgst/interp.h: Declare sendMethod.
5639	* libgst/interp.c: Added sendMethod to list of routines
5640	implemented by plug-ins.
5641	* libgst/interp-bc.inl: Added sendMethod.
5642	* libgst/interp-jit.inl: Added sendMethod.
5643	* libgst/prims.inl: Support sending methods in the
5644	#perform: and #perform:withArguments: primitive.
5645
5646	* libgst/comp.c: Add `install' parameter to compileMethod;
5647	set latestCompiledMethod in compileMethod; use sendMethod
5648	in executeStatements.
5649	* libgst/gst.y: Pass `install' parameter to compileMethod
5650
56512001-02-17  Paolo Bonzini  <bonzini@gnu.org>
5652
5653	* libgst/input.c: Made from complete.c and part of lex.c
5654	* libgst/input.h: Made from complete.h and part of lex.h
5655	* libgst/gst.y: Include input.h
5656	* libgst/byte.c: Include input.h instead of lex.h
5657	* libgst/cint.c: Ditto
5658	* libgst/comp.c: Ditto
5659	* libgst/dict.c: Ditto
5660	* libgst/heap.c: Ditto
5661	* libgst/input.c: Ditto
5662	* libgst/interp.c: Ditto
5663	* libgst/lex.c: Ditto
5664	* libgst/lib.c: Ditto
5665	* libgst/oop.c: Ditto
5666	* libgst/opt.c: Ditto
5667	* libgst/sym.c: Ditto
5668	* libgst/tree.c: Ditto
5669
5670	* libgst/comp.c: Removed emacsProcess from here
5671	* libgst/tree.c: Removed hadError from here
5672	* libgst/input.c: Moved emacsProcess and hadError here
5673
5674	* libgst/comp.h: Removed emacsProcess from here
5675	* libgst/tree.h: Removed hadError from here
5676	* libgst/input.h: Moved emacsProcess and hadError here
5677
56782001-02-17  Dirk Sondermann <d.sondermann@freenet.de>
5679
5680	* libgst/heap.c: Fixed for Solaris
5681
56822001-02-16  Paolo Bonzini  <bonzini@gnu.org>
5683
5684	* libgst/complete.c: New file
5685	* libgst/complete.h: New file
5686	* libgst/lex.c: Moved initializeReadline to readline.c
5687	* libgst/lib.c: Call initializeReadline after we loaded the
5688	image, because addAllSymbolCompletions needs the full symbol table.
5689	* libgst/sym.c: Call addSymbolCompletion in internCountedString,
5690	added addAllSymbolCompletions.
5691	* libgst/sym.h: Declared addAllSymbolCompletions
5692
56932001-02-15  Paolo Bonzini  <bonzini@gnu.org>
5694
5695	* libgst/cint.c: Made invokeCRoutine return whether the
5696	call-out was successful.
5697	* libgst/cint.h: Made invokeCRoutine return a boolean.
5698	* libgst/prims.inl: On invalid C call-outs, primitive 255 fails.
5699
57002001-02-14  Paolo Bonzini  <bonzini@gnu.org>
5701
5702	* libgst/prims.inl: In primitive 255 (C call-out) check
5703	that we were not called from the at-cache.
5704
57052001-02-13  Paolo Bonzini  <bonzini@gnu.org>
5706
5707	* libgst/dict.c: Keep dictionaries no more than 75% full,
5708	* libgst/dict.h: Ditto
5709
5710	* libgst/dict.c: Keep dictionary sizes prime (new function
5711	newNumFields).
5712
57132001-02-12  Paolo Bonzini  <bonzini@gnu.org>
5714
5715	* libgst/gst.h: Moved F_FINALIZE into the runtime flags
5716	(not preserved between the time an image is saved and
5717	the time it is loaded)
5718
57192001-02-06  Paolo Bonzini  <bonzini@gnu.org>
5720
5721	* libgst/lex.c: PushReadlineString became pushStdinString,
5722	and calls pushUNIXFile if emacsProcess is true or readline
5723	is not available
5724	* libgst/lex.h: Declare pushStdinString
5725	* libgst/lib.c: Instead of using #ifdef to decide between
5726	pushReadlineString or pushUNIXFile, use pushStdinString.
5727
57282001-02-02  Paolo Bonzini  <bonzini@gnu.org>
5729
5730	* libgst/callin.c: Added idToOOP/OOPToId, declaration of
5731	interpreterProxy
5732	* libgst/gstpub.h: Declared idToOOP/OOPToId, VMProxyStruct
5733	* libgst/callin.h: Moved old contents of gstpub.h here
5734
5735	* libgst/lib.c: Don't call gst_dld_init
5736	* libgst/cint.c: Don't call initUserCFuncs; merged with
5737	dld_gst.c.  In gst_dld_open automatically call gst_initModule
5738	for the shared library; and always use libltdl.
5739	* libgst/cfuncs.c: Removed.
5740	* libgst/dld*: Removed.
5741	* libgst/cint.c: Search the cFuncInfo array backwards,
5742	so that new definitions override the old ones.
5743
57442001-01-31  Paolo Bonzini  <bonzini@gnu.org>
5745
5746	* libgst/cint.c: Declared a wrapper around opendir, which
5747	returns ENOSYS under Linux!  Also declared isExecutable
5748	* libgst/lib.c: Load OtherArrays.st
5749	* libgst/sysdep.h: Declared fileIsExecutable
5750	* libgst/sysdep.c: Defined fileIsExecutable
5751
57522001-01-31  Paolo Bonzini  <bonzini@gnu.org>
5753
5754	* libgst/comp.c: Compile bindingConsts.
5755	* libgst/gst.y: Added #{...} literals
5756	* libgst/sym.c: Defined findVariableBinding
5757	* libgst/sym.h: Declared findVariableBinding
5758	* libgst/tree.c: Defined makeBindingConstant
5759	* libgst/tree.h: Declared makeBindingConstant and bindingConst
5760
57612001-01-30  Paolo Bonzini  <bonzini@gnu.org>
5762
5763	* libgst/dict.c: Define KernelFileSystemPath in
5764	initDictionaryOnImageLoad, and KernelFilePath in
5765	initDictionary
5766
57672001-01-30  Paolo Bonzini  <bonzini@gnu.org>
5768
5769	*** Released version 1.95.1
5770
57712001-01-16  Paolo Bonzini  <bonzini@gnu.org>
5772
5773	* libgst/interp-bc.inl: Define different optimization levels
5774	depending on REG_AVAILABILITY.
5775	* libgst/dict.inl: Include md-config.h instead of register.h
5776	* libgst/interp.c: Include md-config.h instead of register.h
5777	* libgst/md-config.h: New name of register.h
5778
57792001-01-14  Paolo Bonzini  <bonzini@gnu.org>
5780
5781	* libgst/comp.c: Use incubator in makeBlockClosure.
5782	* libgst/oop.inl: IsObjAddr returns false if the address lies beyond
5783	the allocPtr (used to be beyond the maxPtr)
5784
57852001-01-12  Paolo Bonzini  <bonzini@gnu.org>
5786
5787	* libgst/interp-bc.inl: Fixed pipelining bugs; added more caching
5788	opportunities
5789
57902001-01-09  Paolo Bonzini  <bonzini@gnu.org>
5791
5792	* libgst/interp-bc.inl: Implementation of pipelining
5793	* libgst/interp.c: Defined and explained PIPELINING
5794
57952001-01-08  Paolo Bonzini  <bonzini@gnu.org>
5796
5797	* libgst/dict.inl: Added cast to arrayNew to work on 64-bit machines.
5798	* libgst/gst.h: Removed warning for 64-bit machines.
5799	* libgst/interp.c: Fixed prepareContext to work on 64-bit machines
5800	(num is now a long).
5801	* libgst/oop.c: Make data spaces twice as big on 64-bit machines.
5802	* libgst/oop.h: Make data spaces twice as big on 64-bit machines.
5803	* libgst/register.h: Removed warning for unsupported architectures,
5804	was much more a burden than I had expected.
5805
58062000-12-16  Paolo Bonzini  <bonzini@gnu.org>
5807
5808	* libgst/opt.c: Finished first draft of type inferencing.
5809	* libgst/xlat.c: Adapted to use opt.c; nothing was broken for
5810	disabled type inferencing.
5811
58122000-12-05  Paolo Bonzini  <bonzini@gnu.org>
5813
5814	* libgst/heap.c: Moved the process of guessing the heap base from
5815	configure.in to here.
5816	* libgst/sysdep.h: Declared SigHandler
5817	* libgst/sysdep.c: Made setSignalHandler return the previous signal
5818	handler.
5819
58202000-11-01  Paolo Bonzini  <bonzini@gnu.org>
5821
5822	* libgst/lib.c: Changed bug reporting address
5823
58242000-10-14  GertJan Kersten (GertJan.Kersten@bolesian.nl)
5825
5826	* libgst/cint.c: Fix brokenness in Cygwin's stat and chdir
5827	(which set errno even if the function succeeds).
5828
58292000-09-12  Paolo Bonzini  <bonzini@gnu.org>
5830
5831	* libgst/opt.c: Started implementation of type inferencing
5832	(have basic block detection now).  Finally succeded in
5833	passing Physics yesterday.
5834
58352000-09-10  Paolo Bonzini  <bonzini@gnu.org>
5836
5837	* libgst/interp.h: Added declarations for primitive attributes.
5838	* libgst/prims.inl: Added primitive attributes.
5839	* libgst/xlat.c: Use primitive attributes in emitPrimitive.
5840
58412000-09-09  Paolo Bonzini  <bonzini@gnu.org>
5842
5843	* libgst/xlat.c: Added discardNativeCode and modified other
5844	function to use the `discarded' list.
5845	* libgst/xlat.h: Added declaration for discardNativeCode.
5846	* libgst/dict.c: In identityDictionaryAtPut, return the
5847	old value associated to the key.
5848	* libgst/comp.c: Include xlat.h; call discardNativeCode on
5849	the old method if a method is replacing another.
5850	* libgst/prims.inl: Primitive 90, instead of returning the
5851	native code for a method, discards the method (completely
5852	different semantics -- but the old one had no use since
5853	the Smalltalk program had no interesting use of the result).
5854
58552000-09-09  Paolo Bonzini  <bonzini@gnu.org>
5856
5857	* libgst/byte.c: Modified bytecode 134 for pop-into-array
5858	* libgst/byte.h: Modified bytecode 134 for pop-into-array
5859	* libgst/interp-bc.inl: Modified bytecode 134 for pop-into-array
5860	* libgst/opt.c: Modified computeStackPositions for pop-into-array
5861	* libgst/xlat.c: Modified bytecode 134 for pop-into-array,
5862	added gen_popIntoArray
5863
5864	* libgst/comp.c: Added compileArrayConstructor and modified
5865	according to the changes to tree.c below
5866	* libgst/lex.c: Recognize { and }
5867	* libgst/gst.y: Recognize { ... } syntax
5868	* libgst/tree.c: Removed charConst, symbolConst -> oopConst,
5869	implemented makeArrayConstructor
5870	* libgst/tree.h: Declared makeArrayConstructor, added
5871	arrayConstructorType, removed charConst, symbolConst -> oopConst
5872
58732000-09-08  Paolo Bonzini  <bonzini@gnu.org>
5874
5875	* libgst/interp.c: Method cache is no longer static; moved
5876	MethodCacheEntry declaration to interp.h.  Also found bug
5877	in lookupMethod which prevented the method cache from being
5878	fully exploited (startingClassOOP was set to the methodClass).
5879	* libgst/interp.h: Declared MethodCacheEntry
5880	* libgst/interp.inl: Defined checkSendCorrectness
5881	* libgst/prims.inl: Used checkSendCorrectness
5882
5883	* libgst/xlat.c: Included compilation of == into gen_intComparison
5884	(now called gen_binaryBool); renamed gen_intOperation to
5885	gen_binaryInt and TREE_ARIT_* to TREE_BINARY_*
5886
58872000-09-07  Paolo Bonzini  <bonzini@gnu.org>
5888
5889	*** Version 1.8.3 released
5890
5891	* libgst/dict.c: Removed ByteMemory and WordMemory declarations.
5892	* libgst/dict.h: Removed ByteMemory and WordMemory declarations.
5893	* libgst/lib.c: Don't load ByteMemory and WordMemory definitions.
5894	* libgst/prims.inl: Removed ByteMemory primitives.
5895
58962000-09-07  Nigel Williams  <nigelw@wizardis.com.au>
5897
5898	* libgst/cint.c: Allow to pass nil for stringOut, byteArray and
5899	byteArrayOut too.
5900
59012000-09-01  Nigel Williams  <nigelw@wizardis.com.au>
5902
5903	* libgst/prims.inl: Corrected class check for primitive 203/204.
5904
59052000-08-15  Paolo Bonzini  <bonzini@gnu.org>
5906
5907	* libgst/opt.c: Added stub implementation of inferSmallIntegerOps.
5908	* libgst/opt.h: Declare inferSmallIntegerOps and the constants it uses.
5909	* libgst/xlat.c: Added support for inferSmallIntegerOps and ability
5910	to omit overflow checks if the result of an inlined operation is
5911	known to be a SmallInteger.
5912
59132000-08-08  Paolo Bonzini  <bonzini@gnu.org>
5914
5915	* libgst/comp.c: Renamed compileSubexpressionWithGoto to
5916	compileSubexpressionAndJump
5917	* libgst/dict.inl: Only have 8 case's (instead of 9) in nilFill
5918	* libgst/interp.c: Only have 8 case's (instead of 9) in prepareContext
5919	* libgst/save.c: Moved most of loadFromFile to loadSnapshot; removed
5920	goto statements (my life is passing through a phase of structured
5921	programming mania).
5922
59232000-08-06  Paolo Bonzini  <bonzini@gnu.org>
5924
5925	* libgst/byte.c: Moved part to opt.c
5926	* libgst/byte.h: Moved part to opt.h
5927	* libgst/opt.c: Created from byte.c.  As the JIT compiler will
5928	get more sophisticated this part is going to get bigger.
5929	* libgst/opt.h: Created from byte.h
5930
5931	* libgst/comp.c: Include opt.h.  Also, don't generate unreachable
5932	jumps in `... ifTrue: [ ^true ]' (or an analogous pattern with
5933	#ifTrue:ifFalse:).  This pleases computeStackPositions enough
5934	to run the Prolog and Lisp interpreters.
5935	* libgst/xlat.c: Include opt.h
5936
5937	* libgst/gst.h: Added F_FIXED.
5938	* libgst/oop.h: Declared makeFixedOOP.
5939	* libgst/oop.c: Added makeFixedOOP, deal with fixed objects
5940	in prepareForSweep.
5941	* libgst/prims.inl: Added primitive 170-172 to deal with fixed
5942	objects.
5943	* libgst/save.c: Always clear F_RUNTIME flags, not only when
5944	the endianness is wrong!!! This caused the GC to try to release
5945	the native code version of methods that had indeed been compiled
5946	when the image was saved, but were not compiled when GC was
5947	invoked.  Also implemented saving F_FIXED objects.
5948
59492000-07-10  Paolo Bonzini  <bonzini@gnu.org>
5950
5951	* libgst/lib.c: Allow usage of Undeclared in the kernel's source
5952
59532000-07-04  Paolo Bonzini  <bonzini@gnu.org>
5954
5955	* libgst/heap.c: Support MAP_ANON and MAP_ANONYMOUS (thanks to
5956	John David Anglin)
5957	* libgst/oop.c: In gcFlip, modify numFreeOOPs so that allocOOPs
5958	allocates its OOPs merrily, even if we're below the low-water
5959	threshold.
5960	* libgst/oop.h: Defined LOW_WATER_OOP_THRESHOLD
5961	* libgst/oop.inl: In allocOOP, check low-water condition by
5962	looking at numFreeOOPs, not firstFreeOOP.
5963
59642000-07-02  Paolo Bonzini  <bonzini@gnu.org>
5965
5966	* libgst/gst.y: Add `oval' to the union, and define (and parse)
5967	SCALED_DECIMAL_LITERAL
5968	* libgst/lex.c: Parse ScaledDecimal literals
5969	* libgst/sym.c: Declared asScaledDecimalSymbol
5970	* libgst/sym.h: Defined asScaledDecimalSymbol
5971	* libgst/tree.c: Defined makeOOPConstant
5972	* libgst/tree.h: Declared makeOOPConstant
5973
59742000-07-01  Paolo Bonzini  <bonzini@gnu.org>
5975
5976	* libgst/interp.c: Don't overwrite the method cache until we
5977	are sure that the receiver understands the message (lookupMethod)
5978	* libgst/lib.c: Load AnsiDates.st and ScaledDec.st too
5979	* libgst/prims.inl: Handle case where the receiver is a `Float'
5980	but the argument is a `SmallInteger' directly in the 41-to-50
5981	primitives.
5982	* libgst/xlat.c: Another fix to the strength-reduced division
5983	algorithm.  If adjust is true, fixing the dividend if the signs
5984	mismatch produces an incorrect result.
5985
59862000-06-26  Paolo Bonzini  <bonzini@gnu.org>
5987
5988	* libgst/prims.inl: Restored divide-by-zero check in //, \\ and
5989	/ (removed by mistake June 21st)
5990
5991	* libgst/xlat.c: Removed interrupt check from the method prolog,
5992	moved it to the `return' bytecodes and to after a primitive;
5993	this fixed processes.
5994	Also INLINED_CONDITIONAL now adjusts the stack top in V2 and then
5995	resets spDelta instead of simply decrementing spDelta: this
5996	caused incorrect compilation of #ifTrue:ifFalse: if the receiver
5997	was inlined and the returned value was used as a parameter to a
5998	message.  There are no regressions with respect to the bytecode
5999	interpreter now.
6000
60012000-06-21  Paolo Bonzini  <bonzini@gnu.org>
6002
6003	* libgst/comp.c: When compiling a #repeat loop, add a dummy
6004	`push nil' bytecode at the end to please the JIT compiler
6005	(which said its stack had underflowed -- it was right, but it
6006	was compiling unreachable code...).
6007	* libgst/interp.h: Made the primitiveTable `const'
6008	* libgst/interp-bc.inl: Use primitives for //, \\ and / if both
6009	arguments are integers
6010	* libgst/interp-jit.inl: First fixes to add processes to the JIT
6011	compiler
6012	* libgst/prims.inl: Fixed meaning of // and \\ for negative divisors;
6013	in primitive 90, use getReturnIP (defined in interp-jit.inl).
6014	* libgst/xlat.c: Fixed meaning of // and \\ for negative divisors;
6015	fixed overflow detection in multiplication; align interrupt checks
6016	to 4 bytes.
6017
60182000-06-18  Paolo Bonzini  <bonzini@gnu.org>
6019
6020	* libgst/dict.c: Added to SortedCollection two instance variables
6021	needed to be able to amortize sorting cost (through heaps & merging).
6022
60232000-06-17  Paolo Bonzini  <bonzini@gnu.org>
6024
6025	* libgst/xlat.c: Fixed doesNotUnderstand
6026
60272000-06-17  Paolo Bonzini  <bonzini@gnu.org>
6028
6029	*** Released versions 1.95 (development) and 1.7.5 (stable)
6030
60312000-06-10  Paolo Bonzini  <bonzini@gnu.org>
6032
6033	* libgst/byte.c: Fixed bug in optimizeByteCodes (|| was there
6034	instead of &&) which upset the JIT compiler
6035	* libgst/comp.c: If a method is a primitive return of a
6036	BlockClosure, initialize the BlockClosure in methodNew.
6037
6038	* libgst/oop.c: Call releaseNativeCode instead of
6039	freeNativeCode in prepareForSweep, at the end call
6040	freeNativeCode
6041	* libgst/xlat.c: Removed definition of MethodEntry, renamed
6042	freeNativeCode to releaseNativeCode, added freeNativeCode
6043	* libgst/xlat.h: Added definition of MethodEntry, declared
6044	releaseNativeCode
6045	* libgst/interp.h: Declare validateMethodCacheEntries
6046	* libgst/interp-bc.inl: Added validateMethodCacheEntries (no-op)
6047	* libgst/interp-jit.inl: Added validateMethodCacheEntries
6048
60492000-06-07  Paolo Bonzini  <bonzini@gnu.org>
6050
6051	* libgst/interp.c: Fixed behavior of emptyContextStack with
6052	regard to the returnIP field.
6053	* libgst/interp-jit.inl: Don't look at the header flag in
6054	sendMessageInternal.
6055	* libgst/xlat.c: Added inlining of arithmetic operations.
6056	declared TREE_ALT_PUSH and implemented the gen_alt* functions.
6057	Still missing: processes, doesNotUnderstand:
6058
60592000-06-06  Paolo Bonzini  <bonzini@gnu.org>
6060
6061	* libgst/prims.inl: Use a huge table of functions instead of
6062	a huge switch statement
6063	* libgst/interp.h: Declare table of functions for
6064	the primitives
6065	* libgst/internal.h: Removed PTR_EXEC_PRIM_OP
6066	* libgst/interp-jit.inl: Same as above.
6067	* libgst/interp-bc.inl: Use primitiveTable instead of
6068	executePrimitiveOperation
6069	* libgst/xlat.c: Same as above.
6070
60712000-06-04  Paolo Bonzini  <bonzini@gnu.org>
6072
6073	* libgst/byte.c: New function computeStackPositions.
6074	* libgst/byte.h: Declared computeStackPositions.
6075	* libgst/xlat.c: Don't call prepareContext in the prologs
6076	if the method has no arguments and no temporaries.  Plus,
6077	use computeStackPositions.
6078
60792000-06-03  Paolo Bonzini  <bonzini@gnu.org>
6080
6081	* libgst/xlat.c: Support #valueWithArguments: and other
6082	primitives (other than 81) which use sendBlockValue.  Wrote
6083	the code for compiling deferred sends.  Working inlined
6084	comparisons.
6085
6086	* libgst/prims.inl: Added primitive 90 to retrieve the
6087	native code for a method.
6088
60892000-06-02  Paolo Bonzini  <bonzini@gnu.org>
6090
6091	* libgst/comp.c: If USE_JIT_TRANSLATION is defined,
6092	executeStatements skips some values which aren't mantained in
6093	that case.
6094
6095	* libgst/xlat.c: Fixed error in pushing thisContext (wrong
6096	register used, R1 instead of V1).  Fixed problems when the
6097	stack was empty in setTopNodeExtra.  The method hash table
6098	was broken -- did not initialize current->receiverClass.
6099	Also check in the block's prolog, if code for the right
6100	CompiledBlock is being executed.
6101
6102	* libgst/interp-jit.inl: Reset the exceptFlag after execution
6103	of JIT-compiled native code is interrupted.  The interpreter
6104	is now able to create an image and then restore it.
6105
61062000-06-01  Paolo Bonzini  <bonzini@gnu.org>
6107
6108	* libgst/callin.c: Support losing systems which don't allow
6109	va_arg(..., char)
6110	* libgst/dld_beos.c: New file.
6111
61122000-05-29  Paolo Bonzini  <bonzini@gnu.org>
6113
6114	* libgst/xlat.c: Added some inlining (==, isNil, notNil,
6115	blockCopy:); modified suboperation codes so that `2' is reserved
6116	to literals (which aids a lot when inlining).  Blocks done, they
6117	were easy.
6118
61192000-05-28  Paolo Bonzini  <bonzini@gnu.org>
6120
6121	* libgst/comp.c: Moved here a ChangeLog comment that actually
6122	described the code; gave a category to Behavior>>#methodsFor:
6123
6124	* libgst/xlat.c: Usual tons of fixes.  Crashes at initialize.st.
6125	Among others:
6126	- save the returnIP in the parent context, not in the newly created
6127	  context (that is before activateNewContext rather than afterwards).
6128	- fixed the method prolog to update the `self' variable, which I had
6129	  forgotten
6130	- labels did not work (had missed a *)
6131	- do EXPORT_SP_CODE in crucial points, including basic block boundaries
6132
6133	* libgst/interp.c: New procedure showStackContents
6134	* libgst/interp.h: Declared showStackContents
6135	* libgst/prims.inl: Use showStackContents in the temporary definition
6136	of #error: and #doesNotUnderstand: (useful for debugging)
6137
61382000-05-24  Paolo Bonzini  <bonzini@gnu.org>
6139
6140	* lib/xlat.c: More tons of fixes.  Crashes at Character.st
6141	* lib/xlat.h: Export returnFromNativeCode
6142	* lib/heap.c: Switched to Doug Lea's malloc (only an hour's effort!)
6143	* lib/interp.c: Fixed behavior of `execution environment' contexts
6144	with the JIT compiler.
6145
61462000-05-24  Paolo Bonzini  <bonzini@gnu.org>
6147
6148	* lib/xlat.c: Tons of fixes; renamed from lib/dynamic.c
6149
61502000-05-17  Paolo Bonzini  <bonzini@gnu.org>
6151
6152	* lib/gst.h: Added a couple of flags (F_XLAT_2NDCHANCE and
6153	F_XLAT_REACHABLE) for dealing with the changes to lib/oop.c.
6154	* lib/interp-jit.inl: Removed unwindContext and changeProcessContext,
6155	added getContextIP & setThisMethod
6156	* lib/interp-bc.inl: Moved unwindContext and changeProcessContext
6157	back to interp.c, added getContextIP
6158	* lib/interp.c: Restored unwindContext and changeProcessContext from
6159	interp-bc.inl, used getContextIP instead of toInt(...->ipOffset)
6160	* lib/oop.c: Implemented a `second chance' algorithm for disposing
6161	of methods whose native code translations are not referenced by any
6162	context.
6163
61642000-05-13  Paolo Bonzini  <bonzini@gnu.org>
6165
6166	* lib/alloc.c: Moved to lib-src
6167	* lib/alloc.h: Moved to lib-src
6168	* lib/alloca.c: Moved to lib-src
6169	* lib/getdtablesize.c: Moved to lib-src
6170	* lib/getpagesize.c: Moved to lib-src
6171	* lib/memmove.c: Moved to lib-src
6172	* lib/obstack.c: Moved to lib-src
6173	* lib/obstack.h: Moved to lib-src
6174	* lib/putenv.c: Moved to lib-src
6175	* lib/qsort.c: Moved to lib-src
6176	* lib/strdup.c: Moved to lib-src
6177	* lib/strerror.c: Moved to lib-src
6178	* lib/strtoul: Moved to lib-src
6179	* lib/usleep.c: Moved to lib-src
6180	* lib/waitpid.c: Moved to lib-src
6181
61822000-05-12  Paolo Bonzini  <bonzini@gnu.org>
6183
6184	* lib/heap.c: Derive baseaddr by trying to mmap a page, rather than
6185	blindly getting sbrk(0)
6186
61872000-05-09  Paolo Bonzini  <bonzini@gnu.org>
6188
6189	* lib/comp.c: Abort compilation if a method turns out to be too
6190	complex for the bytecode set (i.e. if it jumps too far).
6191	* lib/putenv.c: Strdup the added string
6192
61932000-05-04  *X*X* (aldomel@ix.netcom.com)
6194
6195	* lib/sym.h: Added #include gst.h
6196	* lib/lib.c: Better error message when the Kernel files can't be
6197	found (image bootstrap failed).
6198
61992000-05-04  Paolo Bonzini  <bonzini@gnu.org>
6200
6201	*** Version 1.94.90 released
6202
62032000-05-02  Paolo Bonzini  <bonzini@gnu.org>
6204
6205	* lib/gst.y: Fixed errors in parsing #( () ) and #[]; the
6206	former was parsed to (Array with: nil), the last crashed (!)
6207	* lib/getpagesize.c: Created from part of sysdep.c
6208	* lib/getdtablesize.c: Created from part of sysdep.c
6209	* lib/usleep.c: Created from part of sysdep.c
6210	* lib/sysdep.c: Added code to set the `LANG' environment
6211	variable under Win32.
6212
62132000-04-27  Paolo Bonzini  <bonzini@gnu.org>
6214
6215	* lib/register.h: Issue the #warning only if using GCC
6216
6217Wed Apr 26 14:42.52 2000  Paolo Bonzini  <bonzini@gnu.org>
6218
6219	* lib/sysdep.h: Relinquish -> usleep, added getpagesize
6220	* lib/sysdep.c: Same as above
6221	* lib/prims.inl: Relinquish -> usleep
6222
62232000-04-23  Paolo Bonzini  <bonzini@gnu.org>
6224
6225	* lib/dict.c: Changed `length' variable to `size' in FileSegment
6226
62272000-04-12  Paolo Bonzini  <bonzini@gnu.org>
6228
6229	*** Version 1.7.4 released
6230
62312000-04-01  Paolo Bonzini  <bonzini@gnu.org>
6232
6233	* lib/oop.c: Completed switch to heaps, using heap_sbrk instead of
6234	heap_malloc and	heap_realloc.  Removed maxSpaceSize variable.
6235	* lib/save.c: Use memSpace.totalSize instead of maxSpaceSize.
6236
62372000-03-31  Hideoki Saito (saito@densan.co.jp)
6238
6239	* lib/comp.h: Fixed bogus error on big-endian machines
6240
62412000-03-25  Paolo Bonzini  <bonzini@gnu.org>
6242
6243	* lib/byte.c: Added bytecode 134 (for lots of instance variables).
6244	* lib/byte.h: Added bytecode 134.
6245	* lib/comp.c: Added bytecode 134.
6246	* lib/dynamic.c: Added bytecode 134.
6247	* lib/interp-bc.inl: Added bytecode 134.
6248
62492000-03-24  Paolo Bonzini  <bonzini@gnu.org>
6250
6251	* lib/alloc.c: Removed code for the BSD memory allocator.
6252	* lib/heap.c: Added.
6253	* lib/heap.h: Added.
6254	* lib/oop.c: Use heaps to allow the OOP table to grow.
6255
62562000-03-23  Paolo Bonzini  <bonzini@gnu.org>
6257
6258	*** Version 1.7.3 released
6259
62602000-03-22  Paolo Bonzini  <bonzini@gnu.org>
6261
6262	* lib/gst.h: Added F_XLAT and F_RUNTIME
6263	* lib/save.c: Remove F_RUNTIME flags upon image load
6264
62652000-03-21  Paolo Bonzini  <bonzini@gnu.org>
6266
6267	* lib/comp.h: Include comp.inl
6268	* lib/comp.inl: Created
6269	* lib/dict.c: Added returnIP to ContextParts
6270	* lib/dynamic.c: All but blocks is in place...
6271	* lib/interp.c: Moved a few functions to interp-bc.inl
6272	* lib/interp.h: Added returnIP to ContextPart structs
6273	* lib/interp-bc.inl: (new name of bytecode.inl) moved here a few
6274	functions that are different for the bytecode and JIT interpreter
6275	(sendMessageInternal, unwindContext, changeProcessContext, ...)
6276	* lib/interp-jit.inl: Created
6277	* lib/sym.c: Added mustBeBooleanSymbol and badReturnErrorSymbol
6278	* lib/sym.h: Added mustBeBooleanSymbol and badReturnErrorSymbol
6279
62802000-03-16  Paolo Bonzini  <bonzini@gnu.org>
6281
6282	* lib/byte.h: Since I added atSignSymbol, I put atSignSpecial here.
6283	* lib/bytecode.inl: Since I added atSignSymbol, I use it instead of
6284	internString("@").
6285	* lib/comp.c: Since I added atSignSymbol, I generate bytecode 187
6286	even if it has little use...
6287	* lib/dynamic.c: Shape is getting clearer and clearer...
6288	* lib/sym.c: Added atSignSymbol (for JIT).
6289	* lib/sym.h: Added atSignSymbol (for JIT).
6290
62912000-03-11  Paolo Bonzini  <bonzini@gnu.org>
6292
6293	*** Version 1.7.2 released
6294
6295	* lib/byte.c: IsPush -> isPushTable; added isSendTable
6296	* lib/byte.h: Added isPushByteCode & isSendByteCode
6297	* lib/dynamic.c: Began implementing new version
6298	* lib/dynamic.h: New version
6299
63002000-02-25  Paolo Bonzini  <bonzini@gnu.org>
6301
6302	* lib/lib.c: Use the Undeclared dictionary for files loaded
6303	from the command line too.
6304
63052000-02-24  Paolo Bonzini  <bonzini@gnu.org>
6306
6307	* lib/cint.c: Better output from badType.  Plus, ByteArrays
6308	passed as Strings are considered null-terminated, and Strings
6309	passed as ByteArrays are not.
6310	* lib/interp.c: ShowBacktrace not static anymore.  Fixed crash
6311	on sends to super from a block.
6312	* lib/interp.h: Declare showBacktrace.
6313
63142000-02-22  Paolo Bonzini  <bonzini@gnu.org>
6315
6316	*** Version 1.7.1 released
6317
63182000-02-22  Paolo Bonzini  <bonzini@gnu.org>
6319
6320	* lib/cint.c: Added defineCFuncs to test file accessing modes.
6321
63222000-02-21  Paolo Bonzini  <bonzini@gnu.org>
6323
6324	* lib/prims.inl: Added time-zone primitives for Time
6325	* lib/sysdep.c: Added currentTimeZoneName
6326	* lib/sysdep.h: Added currentTimeZoneName
6327
63282000-02-17  Paolo Bonzini  <bonzini@gnu.org>
6329
6330	* lib/bytecode.inl: Fixed crash on blocks returning from non-existent
6331	method contexts; fixed bug in detecting overflows on bit shifts.
6332	* lib/prims.inl: Fixed bug in detecting overflows on bit shifts.
6333
63342000-02-15  Paolo Bonzini  <bonzini@gnu.org>
6335
6336	*** Version 1.7 released
6337
63382000-02-06  Thorsten Klein  <TK@Thorsten-Klein.de>
6339
6340	* lib/dld_gst.c: Missing asterisk in `i' for loop (second
6341	expression was `i', now is `*i').  Caused SIGSEGV when a missing
6342	library name was passed.
6343
63442000-02-01  Paolo Bonzini  <bonzini@gnu.org>
6345
6346	* lib/byte.h: Subsumed bytecodes 132 and 134 (a whole byte for
6347	the argument count is way too much, and it does not matter if
6348	it's a bit slower because these bytecodes are rare indeed).
6349	* lib/byte.c: Print bytecode 132 according to the new coding
6350	* lib/bytecode.inl: Interpret new coding for bytecode 132
6351	* lib/comp.c: Emit new coding for bytecode 132
6352
63532000-01-31  Paolo Bonzini  <bonzini@gnu.org>
6354
6355	*** Sixth beta of 1.7 (labeled 1.6.85) released
6356
63572000-01-31  Paolo Bonzini  <bonzini@gnu.org>
6358
6359	* lib/interp.c: Worked out bugs in call-ins that were added
6360	after the introduction of the `terminate interpreter' bytecode
6361	(Jan 8th) and which prevented Blox from working.
6362	prepareExecutionEnvironment was stacking a context with an OOP
6363	from the main OOP table over some lifoContexts.
6364	* lib/oop.c: Moved debug() to sysdep.c
6365	* lib/oop.h: Moved debug() to sysdep.h
6366	* lib/sysdep.c: Moved debug() here from oop.c
6367	* lib/sysdep.h: Moved debug() here from oop.h
6368
63692000-01-28  Paolo Bonzini  <bonzini@gnu.org>
6370
6371	* lib/comp.c: Fixed bug with double-freeing of block bytecodes
6372	(this is also due to a very permissive allocator)
6373	* lib/lex.c: Fixed bug in parsePrimitive (xfree without matching
6374	xmalloc) -- strangely enough, it didn't show up on all systems!
6375	* lib/prims.inl: Fixed Memory primitives to return and accept
6376	LargeIntegers for addresses when needed.
6377
63782000-01-24  Paolo Bonzini  <bonzini@gnu.org>
6379
6380	* lib/byte.c: Changed the clean block detection machinery to work
6381	with CompiledBlocks.  Previously, we emitted a fixed sequence of
6382	bytecodes for blocks, then we made a pass on the bytecodes before
6383	optimization patching already generated code in case we found the
6384	block to be clean.  Now, instead, we compute information on the
6385	block's cleanness before we create the CompiledBlock object, we
6386	embed the information in the CompiledBlock's header, and then use
6387	that information to directly emit optimized bytecodes in case the
6388	block is clean (instead of applying patches later).
6389	* lib/comp.c: Moved `class' and `selector' fields to MethodInfo.
6390	Blocks are compiled to CompiledBlocks.
6391	* lib/comp.h: Removed `class' and `selector' fields from [Compiled]Method
6392	* lib/dict.c: New definitions of MethodInfo, CompiledCode, CompiledMethod,
6393	CompiledBlock; declaration of compiledCodeClass and compiledBlockClass.
6394	* lib/dict.h: Declaration of compiledCodeClass and compiledBlockClass
6395	* lib/interp.c: Execute blocks from CompiledBlocks.
6396	* lib/lib.c: Load CompildCode.st and CompiledBlk.st
6397	* lib/prims.inl: Added primitive 68 to create CompiledBlocks.
6398
63992000-01-20  Paolo Bonzini  <bonzini@gnu.org>
6400
6401	* lib/byte.c: Fixed crash on methods whose last act was
6402	returning a clean block.  It turned out that evaluating those
6403	blocks was GST's last act, either...
6404	* lib/cint.c: Enable passing 32-bit LargeIntegers in C call-
6405	outs.  Looks like I had forgotten about it on Sep 10 1999.
6406	Also, introduced a `pVoidFunc' typedef to avoid Lisp-like
6407	abundance of parentheses when passing C function addresses.
6408
64092000-01-20  Paolo Bonzini  <bonzini@gnu.org>
6410
6411	* lib/bytecode.inl: IntegerClass -> smallIntegerClass
6412	* lib/dict.c: IntegerClass -> smallIntegerClass, plus
6413	added definition of SmallInteger
6414	* lib/dict.h: Added declaration of SmallInteger
6415	* lib/gst.h: IntegerClass -> smallIntegerClass
6416	* lib/interp.c: IntegerClass -> smallIntegerClass
6417	* lib/interp.inl: IntegerClass -> smallIntegerClass
6418	* lib/lib.c: Load SmallInt.st too.
6419	* lib/prims.inl: IntegerClass -> smallIntegerClass
6420
64212000-01-15  Paolo Bonzini  <bonzini@gnu.org>
6422
6423	* lib/comp.c: Adapted large integer compilation stuff in
6424	makeConstantOOP to compile ByteArrays too.
6425	* lib/gst.y: Added rules for ByteArray literals and arrays
6426	like #(1 2 3 #(4 5 6)) -- i.e. with the sharp inside the
6427	parentheses
6428	* lib/lex.c: Make parseNumber return BYTE_LITERAL for
6429	integers between 0 and 255
6430	* lib/tree.c: Added makeByteArrayConstant
6431
64322000-01-09  Paolo Bonzini  <bonzini@gnu.org>
6433
6434	* lib/lex.c: CurStrBuf -> obstack_curStrBuf; plus, added
6435	the compilationObstack variable which is initialized in
6436	parseStream.
6437	* lib/lex.h: Added declaration of compilationObstack
6438	* lib/str.c: Added obstack_curStrBuf
6439	* lib/str.h: Declared obstack_curStrBuf
6440	* lib/tree.c: Heavily simplified destruction code by using
6441	obstacks
6442
6443	* lib/lib.c: Solved SIGSEGV when gst.im was not in the
6444	current directory and SMALLTALK_IMAGE was not set.
6445
64462000-01-09  Paolo Bonzini  <bonzini@gnu.org>
6447
6448	* lib/comp.c: Added code to create Smalltalk LargeInteger
6449	objects from large integer ConstNodes in makeConstantOOP.
6450	* lib/gst.y: Handle large integer literals in the grammar
6451	* lib/lex.c: Added code to parse large integer literals
6452	* lib/tree.c: Added code to create large integer ConstNodes
6453	* lib/tree.h: Added declaration of the LargeInteger struct
6454	and of large integer ConstNodes
6455
64562000-01-08  Paolo Bonzini  <bonzini@gnu.org>
6457
6458	* lib/byte.h: Added `exitInterpreter' bytecode.
6459	* lib/comp.h: Declared `getTerminationMethod'.
6460	* lib/comp.c: Implemented `getTerminationMethod', and added code
6461	to installInitialMethods which installs a termination method
6462	which executes the new bytecode above.
6463	* lib/bytecode.inl: Implemented `exitInterpreter' bytecode.
6464	* lib/interp.c: Contexts created by prepareExecutionEnvironment
6465	no longer have to be special cased in unwindLastContext.
6466	* lib/sym.c: Added terminateSymbol.
6467	* lib/sym.h: Added terminateSymbol.
6468
64692000-01-02  Paolo Bonzini  <bonzini@gnu.org>
6470
6471	* lib/interp.c: Gst enters the new millennium!!! (yeah, I know it
6472	actually starts in 2001 but I don't want to wait another year... ;-)
6473	and it does by getting rid of the free lists for contexts -- it is
6474	faster to use the memory chunks like a stack.
6475	Also, I replaced tests for `isNil(thisContextOOP)' with tests for
6476	`!ip'.
6477
6478	* lib/strerror.c: Added.
6479	* lib/sysdep.c: Win32 implementation of getMilliTime now more precise
6480	* lib/sysdep.h: Added macros for frexp and ldexp where they aren't
6481	available
6482
64831999-12-28  Paolo Bonzini  <bonzini@gnu.org>
6484
6485	*** Fifth beta of 1.7 (labeled 1.6.84) released
6486
6487	* lib/byte.c: New functions checkKindOfBlock and patchCleanBlocks.
6488	* lib/byte.h: Declaration of patchCleanBlocks.
6489
64901999-12-27  Paolo Bonzini  <bonzini@gnu.org>
6491
6492	* lib/byte.c: New function fixupBlockClosures.
6493	* lib/comp.c: New way of compiling blocks.
6494	* lib/bytecode.inl: Bytecode 200 is now #blockCopy: (same as the Blue
6495	Book, but the primitive is implemented differently of course).
6496	* lib/prims.inl: New implementation of primitive 80 (blockCopy)
6497	* lib/sym.c: Removed #blockCopy:temporaries: (replaced with #blockCopy:),
6498	added machinery to reveal `clean' blocks
6499	* lib/sym.h: Removed #blockCopy:temporaries: (replaced with #blockCopy:)
6500
65011999-12-27  Paolo Bonzini  <bonzini@gnu.org>
6502
6503	* lib/dict.c: Added method to BlockClosure, changed to new
6504	context structure (methodClass/selector retrieved from the
6505	compiledMethod, method only there for MethodContexts)
6506	* lib/interp.c: Changed to new context and BlockClosure structure
6507	* lib/prims.inl: Changed to new BlockClosure structure
6508
65091999-12-26  Paolo Bonzini  <bonzini@gnu.org>
6510
6511	* lib/comp.c: Store the class and selector in the created
6512	CompiledMethods.  A first step towards leaner context objects
6513	(i.e. more speed when sending messages!) and more powerful
6514	constructs such as `clean' block closures (which do not need
6515	to be created at run-time because are isolated from the outer
6516	contexts).
6517	* lib/comp.h: Added `class' and `selector' to struct Method.
6518	* lib/dict.c: Added `class' and `selector' to CompiledMethod.
6519	* lib/prims.inl: Pass class and selector to makeNewMethod.
6520
65211999-12-19  Paolo Bonzini  <bonzini@gnu.org>
6522
6523	* lib/bytecode.inl: Removed hasBlock (can be replaced with a
6524	test on whether the context lies in the main OOP table); this
6525	simplified both sends and returns.  I also made the structure
6526	of method and block context objects more similar, resulting
6527	in simpler and faster code (except for block returns), and
6528	opening doors to optimizations such as delayed filling of the
6529	`method' and `receiver' slots of context objects.  The overall
6530	improvement obtained since the Dec 17 change amounts to 9-10%.
6531	* lib/dict.c: Same as above
6532	* lib/interp.c: Same as above
6533	* lib/interp.h: Same as above
6534	* lib/prims.inl: Same as above
6535
65361999-12-17  Paolo Bonzini  <bonzini@gnu.org>
6537
6538	* lib/interp.c: Various changes, notably to getMethodContext and
6539	its users, to avoid using oopToObj more than once on the same
6540	object.
6541
65421999-12-17  Paolo Bonzini  <bonzini@gnu.org>
6543
6544	* lib/gst.h: Nil is now 0L (used to be 0), which is better when
6545	used as a pointer.
6546	* lib/interp.c: As long as we're sure that the execution order is
6547	LIFO (i.e. as long as no blocks are involved), allocate OOPs for
6548	the contexts outside of the main OOP table; this is because
6549	allocOOP is slower than picking a pre-built OOP out of a stack.
6550	This partly resembles the design of 1.1.5 (introduced Jan 1, 1991
6551	and modified Oct 18, 1998), but has the advantage that when a
6552	BlockClosure is created we only have to allocate the OOPs that we
6553	tried to avoid -- 1.1.5 copied the whole objects to the main heap,
6554	causing way too many GCs.
6555
65561999-12-16  Paolo Bonzini  <bonzini@gnu.org>
6557
6558	* lib/gst.h: F_FAKE --> F_POOLED, isFake --> isPooled
6559	* lib/interp.h: ResetFakeContexts --> emptyContextsPool
6560	* lib/interp.c: (de)allocFakeContext --> (de)allocPoolContext,
6561	fakeList --> contextPool, plus changes above
6562	* lib/oop.c: RealizeOOPs --> sweepPooledObjects, plus changes above
6563
65641999-12-15  Paolo Bonzini  <bonzini@gnu.org>
6565
6566	* lib/sym.c: Modified hashString to reduce likeliness that
6567	hash be zero.
6568
65691999-12-14  Paolo Bonzini  <bonzini@gnu.org>
6570
6571	* lib/bytecode.inl: Use the new procedures below
6572	* lib/comp.c: Allocated one more bit for the method flags.  If
6573	there is a primitive index, the flags are now 4 (used to be 0).
6574	* lib/interp.c: The old `returnWithValue' procedure was split in
6575	two, unwindToContext and unwindLastContext -- one is used upon an
6576	explicit `return from method', the other does less job and returns
6577	to the parent context upon a `return from context'
6578
65791999-12-11  Paolo Bonzini  <bonzini@gnu.org>
6580
6581	* lib/dict.c: Moved findClassMethod here from lib/dict.inl
6582	* lib/dict.h: Restored declaration of findClassMethod
6583	* lib/dict.inl: Moved findClassMethod here to lib/dict.c -- it is
6584	used rarely (only for method cache misses) and was bloating
6585	sendMessageInternal's code.
6586
6587	* lib/bytecode.inl: Simple one-byte bytecodes prefetch the next
6588	address to jump to (hoping to save address generation interlocks)
6589	* lib/interp.c: Support for prefetching
6590
65911999-12-06  Paolo Bonzini  <bonzini@gnu.org>
6592
6593	* lib/bytecode.inl: Hard-code register allocation of ivar2
6594	and tempOOP only where they are actually used
6595	* lib/dict.inl: Hard-coded register allocation in nilFill
6596	* lib/interp.c: Hard-coded register allocation now relies on
6597	register.h and is used in sendMessageInternal/sendBlockValue.
6598	* lib/register.h: Created
6599
66001999-12-05  Paolo Bonzini  <bonzini@gnu.org>
6601
6602	* lib/byte.c: ReturnMethodStackTop became returnContextStackTop
6603	in isSimpleReturn.
6604	* lib/cint.c: Declare the strerror C function.
6605	* lib/gst.h: ANSI asks for 65535 instance variables, so I shifted
6606	the instance specification's `number of instance vars' field
6607	right by three bits (now 262143 variables are possible).
6608	* lib/lex.c: Parse stuff like 1.0d53 and 1.0q212 correctly even
6609	though FloatD/FloatE/FloatQ is not supported yet.
6610
6611	* lib/memzero.h: Removed a conditional by using LONG_SHIFT in the
6612	generic version of memzero.
6613
66141999-12-05  Paolo Bonzini  <bonzini@gnu.org>
6615
6616	* lib/bytecode.inl: The `hasBlock' instance variable in a context
6617	is now an integer (0 or 1).  This eliminated several lookups for
6618	the `trueOOP' and `falseOOP' globals.
6619	* lib/interp.c: Same as above
6620	* lib/prims.inl: Same as above
6621
66221999-11-26  Paolo Bonzini  <bonzini@gnu.org>
6623
6624	*** Fourth beta of 1.7 (labeled 1.6.83) released
6625
6626	* lib/bytecode.inl: Added caching of primitive numbers for sends of
6627	#at:, #at:put: and #size
6628	* lib/interp.c: Same as above
6629	* lib/prims.inl: Same as above
6630
66311999-11-22  Paolo Bonzini  <bonzini@gnu.org>
6632
6633	* lib/interp.c: Fixed floating-point exception on operations
6634	with infinity and NaN, under FreeBSD.
6635
66361999-11-21  Paolo Bonzini  <bonzini@gnu.org>
6637
6638	* lib/alloc.c: Use memzero instead of memset; also, xmalloc
6639	doesn't zero memory
6640	* lib/byte.c: Use memzero instead of memset
6641	* lib/dict.inl: Use memzero instead of memset
6642	* lib/dynamic.c: Use memzero instead of memset
6643	* lib/gst.h: Include memzero.h
6644	* lib/memzero.h: Added
6645
6646	* lib/oop.c: Don't update numFreeOOPs on allocate/free oop.
6647	It is only used after a GC (to check whether the OOP table
6648	must be resized), so it is sufficient that it be correct
6649	after a GC.
6650
66511999-11-20  Paolo Bonzini  <bonzini@gnu.org>
6652
6653	* lib/dict.c: RestoreCFuncDescriptor was called at the wrong
6654	time in save.c -- before the xxxClass variables were loaded
6655	(Oct 20 change).  So now it is called here.
6656	* lib/save.c: See above for lib/dict.c
6657
66581999-11-20  P. Lecoanet
6659
6660	* lib/bytecode.inl: Special case #blockCopy:temporaries: for
6661	context objects and #value/#value: for BlockClosure objects.
6662	Also, no need to push and pop the object for the `return
6663	self/true/false/nil' bytecodes -- a simple assignment will do.
6664
66651999-11-19  Paolo Bonzini  <bonzini@gnu.org>
6666
6667	* lib/dict.c: Removed initNilVec and nilVec
6668	* lib/dict.inl: Implemented nilFill as an unrolled loop (memcpy
6669	is sloooow)
6670	* lib/interp.c: Arguments are moved between contexts with an
6671	unrolled loop (memcpy is sloooow); pushNNils now sets up the
6672	whole context stack (arguments+temporaries) and is called
6673	prepareContext.  Another +10% for this on send-heavy benchmark!!!
6674
66751999-11-18  Paolo Bonzini  <bonzini@gnu.org>
6676
6677	* lib/byte.h: ReturnBlockStackTop became returnContextStackTop
6678	* lib/comp.c: Compile returns from methods as returnContextStackTop
6679	(should be a bit faster)
6680	* lib/bytecode.inl: `return self' and other similar bytecodes
6681	fall into returnContextStackTop, not returnMethodStackTop.
6682
66831999-11-18  Paolo Bonzini  <bonzini@gnu.org>
6684
6685	* lib/comp.c: Changed to account for removal of cacheHits and
6686	messagesSent.
6687	* lib/comp.h: Removed messagesSent.
6688	* lib/interp.c: Removed cacheHits and messagesSent, which
6689	can be deducted from other statistics.
6690	* lib/interp.h: Removed cacheHits.
6691	* lib/prims.inl: New implementation of mutation does not need
6692	primitive 263 (#specialBasicAt:).
6693
66941999-11-17  Paolo Bonzini  <bonzini@gnu.org>
6695
6696	* lib/dict.inl: Access functions test subscript bounds -- this
6697	eliminates an instanceSpec lookup.
6698	* lib/prims.inl: No need to call checkIndexableBoundsOf on
6699	access primitives (#at:*, #basicAt:*)
6700	* lib/gst.y: Support for the #(1 2 3 #a #b #'cdef' 45) syntax
6701					     ^^ ^^ ^^^^^^^
6702
67031999-11-14  Paolo Bonzini  <bonzini@gnu.org>
6704
6705	* lib/comp.c: `return instance variable' stores index in the
6706	`primitive' field of the method header (allows more optimizations
6707	and better register allocation in sendMessageInternal)
6708	* lib/comp.h: Move flag bits to high end of the methodHeader, so
6709	that there is place for two additional bits if needed
6710	* lib/dict.c: BlockContexts now hold the receiver and the
6711	BlockClosure instead of the number of arguments and temporaries.
6712	* lib/interp.c: Same as comp.c and dict.c above; plus, removed
6713	code for ACCESSOR_DEBUGGING.
6714	* lib/interp.h: Same as dict.c above
6715
67161999-11-13  Paolo Bonzini  <bonzini@gnu.org>
6717
6718	* lib/dict.c: NilVec contains now 128 OOPs
6719	* lib/dict.inl: NilVec contains now 128 OOPs
6720	* lib/interp.c: Doc fixes; cleaned up unused variables in the code
6721	handling fake contexts; finally, the method cache now includes
6722	the method header (+5/10% performance).
6723
67241999-11-11  Paolo Bonzini  <bonzini@gnu.org>
6725
6726	* lib/dynamic.c: Move method whose threaded code representation
6727	is requested to the head of the methodsTable.
6728	* lib/lex.c: USE_MONCONTROL only affects the interpreter, not the
6729	lexer.
6730	* lib/lib.c: Disable execution tracing options when the dynamic
6731	translator is being used.
6732	* lib/oop.c: Removed code for ACCESSOR_DEBUGGING, which I found
6733	more bug-prone than useful in more than a year; added lines
6734	explaining GC_TORTURE.
6735	* lib/oop.inl: Removed the few lines that implemented the
6736	ACCESSOR_DEBUGGING preprocessor symbol and explained what it was
6737	for.
6738
67391999-11-10  Paolo Bonzini  <bonzini@gnu.org>
6740
6741	* lib/bytecode.inl: In most bytecodes that are implemented with a
6742	switch statement, the switch statement is resolved at translation
6743	time.  Also, added `default' clauses to such switch statements so
6744	that the compiler can produce better code.
6745	* lib/dynamic.c: Same as above
6746	* lib/dynamic.h: Same as above
6747	* lib/interp.c: Same as above
6748
6749	* lib/gst.h: Removed declarations of TreeNode, thisClass and
6750	regressionTesting, which are already declared elsewhere
6751	(respectively in tree.h, comp.h and lib.h).  Also removed
6752	declaration of Stream which is needed only in lex.c and is
6753	therefore moved there.
6754	* lib/lex.c: Moved declaration of Stream from gst.h
6755
67561999-11-09  Paolo Bonzini  <bonzini@gnu.org>
6757
6758	* lib/dynamic.c: Invalidating the macro opcode cache is now
6759	separated from invalidating the threaded code cache. Also,
6760	convert from threaded code ip to bytecode ip before
6761	invalidating the threaded code cache; reload the methodBase
6762	and the threaded ip after having invalidated it (in
6763	invalidateMethodCache). Everything works if no optimization
6764	options are set when compiling.
6765
67661999-11-09  Paolo Bonzini  <bonzini@gnu.org>
6767
6768	* lib/callin.c: SelectorNumArgs used; in addition, the result
6769	is checked to be the `nil' object in msgSendf is checked and,
6770	if so, 0 (or some variation of it, like 0.0 and NULL) is
6771	returned.
6772	* lib/interp.c: Added DEBUG_CODE_FLOW preprocessor symbol that
6773	prints every message that is sent in the same form used by
6774	backtraces (e.g. `Integer(Object)>>#retry:coercing:').
6775	* lib/prims.inl: SelectorNumArgs used in implementation
6776	of #perform:...
6777	* lib/sym.c: Added selectorNumArgs
6778	* lib/sym.h: Added selectorNumArgs
6779
67801999-11-08  Paolo Bonzini  <bonzini@gnu.org>
6781
6782	* lib/byte.c: Fixed bug in makeDestinationTable that caused
6783	macro-opcode inlining to lose as soon as a jump was found.
6784	* lib/dynamic.c: Had mistyped an = for an == grrr... 2 days to
6785	find it! Now runs up to WeakObjects.st both with and without
6786	macro-opcode inlining, so macro opcodes should be reasonably
6787	bug-free (except for problems arising from inlining code
6788	optimized by GCC, which I have not tackled yet).
6789
67901999-11-06  Paolo Bonzini  <bonzini@gnu.org>
6791
6792	* lib/bytecode.inl: Jump bytecodes must be `PROTECT' bytecodes,
6793	isNil and notNil sends need not.  Found two unused variables.
6794	* lib/cint.c: Moved `extern' declaration of enableGC into cint.h,
6795	the actual declaration of the variable came here from interp.c
6796	* lib/cint.h: Moved `extern' declaration of enableGC from cint.c
6797	* lib/interp.c: Moved getMethodLiterals to interp.inl and
6798	enableGC to cint.c
6799	* lib/interp.inl: Moved getMethodLiterals from interp.c
6800
68011999-11-05  Paolo Bonzini  <bonzini@gnu.org>
6802
6803	* lib/byte.c: Can print bytecodes without a vector of literals
6804	* lib/dynamic.c: Added debugging support; offsetToFill was not reset
6805	when a non-inlinable opcode was found (fixed by setting it in
6806	newOpcodeEntry) -- now runs up to the first jump bytecode
6807	(#initialize in Character.st), or up to MethodDict.st
6808	with macro-opcode inlining disabled.
6809
68101999-11-02  Paolo Bonzini  <bonzini@gnu.org>
6811
6812	* lib/dynamic.c: Work on the dynamic translator restarted. The first
6813	correct dynamically code was generated today: a small step for
6814	humanity, a big step for me (hmmm... maybe it was the other way
6815	round...) -- runs up to the first `inlined opcode-non inlined opcode-
6816	inlined opcode' pattern (line 1358 of Builtins.st)
6817	* lib/interp.c: Work on the dynamic translator restarted
6818
68191999-10-31  Paolo Bonzini  <bonzini@gnu.org>
6820
6821	* lib/comp.c: Fixed bug when compiling an integer constant
6822	that did not fit in the first 31 literals (`push instance
6823	variable[x]' was emitted instead of `push literal[x]')
6824
68251999-10-31  Paolo Bonzini  <bonzini@gnu.org>
6826
6827	*** Third beta of 1.7 (labeled 1.6.82) released
6828
68291999-10-30  Paolo Bonzini  <bonzini@gnu.org>
6830
6831	* lib/interp.c: A few bytecodes were still sending #booleanRequired
6832	instead of #mustBeBoolean (see May 3rd change).
6833
68341999-10-22  Paolo Bonzini  <bonzini@gnu.org>
6835
6836	* lib/save.c: Ensure that upon load the heap is at least 50% free.
6837
68381999-10-21  Paolo Bonzini  <bonzini@gnu.org>
6839
6840	* lib/dict.c: Added characterArrayClass
6841	* lib/dict.h: Added characterArrayClass
6842	* lib/lib.c: Added CharArray.st
6843
68441999-10-20  Paolo Bonzini  <bonzini@gnu.org>
6845
6846	* lib/dict.c: The new startup sequence (Oct 9) allowed to
6847	make the dictInit function (now called initNilVec) static.
6848	So that has been done since dictInit was just a hack:
6849	it initialized variables in dict.c like initDictionary,
6850	but while the latter is called from lib.c, dictInit had to
6851	be called from initOOPTable and loadFromFile).
6852	* lib/dict.h: Removed declaration of dictInit.
6853	* lib/oop.c: Removed call to dictInit.
6854
68551999-10-12  Paolo Bonzini  <bonzini@gnu.org>
6856
6857	* lib/dld_hpux.c: `return 0' was missing in gst_dld_init
6858	* lib/lib.c: Put the image in the local directory if the
6859	image directory is missing or not writeable.
6860	* lib/sysdep.c: Added fileIsWriteable, plus usage of time_t;
6861	strdup was erroneously declared in getFullFileName.
6862
68631999-10-11  Paolo Bonzini  <bonzini@gnu.org>
6864
6865	* lib/comp.c: Removed addForcedSelector (a copy of addForcedObject).
6866	Open coding of #whileTrue, #whileFalse, #repeat; removed open
6867	coding of #yourself.
6868	* lib/dict.c: Restored lookupKeyClass and its definition as I
6869	finally understood what it was meant to do; modified Association's
6870	definition (doesn't include key instance variable anymore).
6871	* lib/dict.h: Same as above
6872
68731999-10-10  Paolo Bonzini  <bonzini@gnu.org>
6874
6875	* lib/oop.c: Added reallocOOPTable.
6876	* lib/oop.inl: Call reallocOOPTable instead of exiting when
6877	ran out of OOP table slots.
6878	* lib/save.c: FixupObject, restoreObject, restoreInstanceVars accept
6879	an gst_object instead of an OOP; more coherent with their names and
6880	a bit more efficient too.  Also moved updating of CFunctionDescriptors
6881	from restoreInstanceVars to fixupOOPInstanceVars (it is not needed
6882	when saving, only when loading, and was the only part of the code
6883	that required the parameters to be OOPs).
6884	* lib/save.h: FixupObject and restoreObject are now public.
6885
68861999-10-10  Paolo Bonzini  <bonzini@gnu.org>
6887
6888	* lib/gst.h: Define the `min' and `max' macros.
6889	* lib/lib.c: Used oopTableSize instead of OOP_TABLE_SIZE;
6890	use additional parameter to initOOPTable.
6891	* lib/oop.c: Added to initOOPTable a parameter to specify the
6892	table size; defined oopTableSize and used instead of
6893	OOP_TABLE_SIZE.
6894	* lib/oop.h: OOP_TABLE_SIZE became INITIAL_OOP_TABLE_SIZE;
6895	declared oopTableSize.
6896	* lib/oop.inl: Used oopTableSize instead of OOP_TABLE_SIZE
6897	* lib/prims.inl: Used oopTableSize instead of OOP_TABLE_SIZE
6898	* lib/save.c: Used oopTableSize instead of OOP_TABLE_SIZE;
6899	use additional parameter to initOOPTable.
6900
69011999-10-10  Paolo Bonzini  <bonzini@gnu.org>
6902
6903	* lib/oop.c: Moved builtin objects at the front of the oop table;
6904	this is a first step towards a variable-sized oop table
6905	(believe it or not, I did it in less than half an hour!!).
6906	* lib/oop.h: Same as above.
6907	* lib/oop.inl: Same as above.
6908	* lib/prims.inl: Same as above.
6909	* lib/save.c: Same as above.
6910	* lib/sym.c: Same as above.
6911
69121999-10-09  Paolo Bonzini  <bonzini@gnu.org>
6913
6914	*** Second beta of 1.7 (labeled 1.6.81) released
6915
6916	* lib/bytecode.inl: Added a few experimental branch labels
6917	for the dynamic translator.
6918	* lib/prims.inl: Added primitive 90 to flush the dynamic
6919	translator's code cache.
6920
6921	* lib/dict.c: Added code to reinitialize the global OOPs (which
6922	are not saved anymore so that the image is more compatible). Also,
6923	the OOP indices associated to Smalltalk, Processor and the
6924	SymbolTable are fixed so that we know them without storing them
6925	in the image file. Finally, declare the `Undeclared' dictionary in
6926	initSmalltalkDictionary().
6927	* lib/oop.c: Removed markGlobalOOPs (instead, just mark the
6928	`Smalltalk' dictionary).
6929	* lib/save.c: Removed the global OOPs; they are reinitialized
6930	every time in dict.c.
6931	* lib/save.h: Removed the global OOPs
6932	* lib/sym.c: Added undeclaredSymbol, and used in findClassVariable.
6933	* lib/sym.h: Added undeclaredSymbol.
6934
69351999-10-07  Paolo Bonzini  <bonzini@gnu.org>
6936
6937	* lib/dict.c: Restored old MethodDictionary class (see
6938	March 29th, 1989 entry!) It was needed after all.
6939	* lib/dict.h: Same as above
6940	* lib/lib.c: Same as above
6941	* lib/save.c: Same as above
6942	* lib/sysdep.c: Fixed faked closePipe to return status of child
6943	process.
6944
69451999-10-02  Paolo Bonzini  <bonzini@gnu.org>
6946
6947	* lib/comp.c: Was trimming the last character of the method's
6948	source code in FileSegments.
6949	* lib/lex.c: Was trimming the last character of the method's
6950	source code when creating Strings from source code read from
6951	a file.
6952	* lib/lib.c: Added -K option, don't crash on -I/-L/-K without
6953	mandatory argument.
6954
69551999-09-26  Paolo Bonzini  <bonzini@gnu.org>
6956
6957	* lib/interp.c: InitProcessSystem removed the initial process from
6958	its own process list -- result: as soon as `Processor yield' was
6959	called, highestPriorityProcess did not know that the active process
6960	was active!
6961	* lib/prims.inl: Relinquish control to other processes on #yield.
6962	* lib/lib.c: `gst -a' caused a segmentation violation
6963	* lib/sysdep.h: Declaration of `relinquish'.
6964	* lib/sysdep.c: Implemented `relinquish'.
6965
69661999-09-25  Paolo Bonzini  <bonzini@gnu.org>
6967
6968	*** First beta of 1.7 (labeled 1.6.80) released
6969
6970	* lib/bytecode.inl: Use areInts in open-coded operators.
6971	* lib/gst.h: Added areInts, removed F_FINALIZING.
6972	* lib/oop.c: Store objects to be finalized in a buffer, to avoid
6973	an OOP table scan.
6974	* lib/str.h: Added declaration of generic buffer functions
6975	* lib/str.c: Added generic buffer functions (not limited to chars)
6976	* lib/dld_aix.c: Added
6977	* lib/waitpid.c: Added
6978	* lib/strtoul.c: Added
6979
69801999-09-23  Paolo Bonzini  <bonzini@gnu.org>
6981
6982	* lib/dynamic.c: Created.
6983	* lib/dynamic.h: Created.
6984	* lib/obstack.c: Added, fixed to use _obstack_memcpy.
6985	* lib/obstack.h: Added.
6986	* lib/sysdep.h: Added flushCode.
6987	* lib/sysdep.c: Added flushCode & signalAfter implementation using
6988	fork()+getMilliTime().
6989
69901999-09-19  Paolo Bonzini  <bonzini@gnu.org>
6991
6992	* lib/dict.c: Declare lookupTableClass
6993	* lib/dict.h: Declare lookupTableClass
6994	* lib/lib.c: Load LookupTbl.st and WeakObjects.st
6995
69961999-09-18  Paolo Bonzini  <bonzini@gnu.org>
6997
6998	* lib/gst.y: Include "lib.h", define YYPRINT
6999	* lib/lex.c: Define yyprint
7000	* lib/lex.h: Declare yyprint
7001	* lib/lib.h: Added declaration of "quietExecution", previously only
7002	in lib.c
7003
70041999-09-15  Paolo Bonzini  <bonzini@gnu.org>
7005
7006	* lib/cint.c: Added mkdir declaration.
7007
70081999-09-14  Paolo Bonzini  <bonzini@gnu.org>
7009
7010	* lib/dict.c: Added DefaultSortBlock to SortedCollection.
7011	* lib/lex.c: Fixed bug; 8-bit characters *outside* string literals
7012	crashed the lexer.
7013	* lib/sysdep.c: Use getcwd if HAVE_GETCWD (new symbol) is set and
7014	getwd otherwise.  Old behavior was to use getcwd if HAVE_UNISTD_H
7015	was set and getwd if HAVE_GETWD was set
7016
70171999-09-13  Paolo Bonzini  <bonzini@gnu.org>
7018
7019	* lib/comp.c: Compile doits in UndefinedObject.
7020
70211999-09-12  Paolo Bonzini  <bonzini@gnu.org>
7022
7023	* lib/dict.c: Moved variables from ClassDescription; instanceVariables to
7024	Behavior; name/comment/category/environment to Class (they make no sense
7025	in Metaclass!).
7026	* lib/dict.h: Same as above.
7027
70281999-09-11  Paolo Bonzini  <bonzini@gnu.org>
7029
7030	* lib/comp.c: Changes for namespaces (execute doits in the current namespace).
7031	* lib/dict.c: Same as above (shared pool variable search algorithm,
7032	new `environment' variable, declaration of currentNamespace).
7033	* lib/dict.h: Same as above (added `environment' variable to ClassDescription,
7034	declaration of currentNamespace).
7035	* lib/dict.inl: Same as above (setClassEnvironment).
7036	* lib/prims.c: Same as above (primitive 250 to tell the compiler about the
7037	current namespace).
7038	* lib/save.c: Same as above (added uppercaseSuperSymbol, currentNamespace).
7039	* lib/sym.c: Same as above (shared pool variable search algorithm).
7040	* lib/sym.h: Same as above (added uppercaseSuperSymbol).
7041
70421999-09-10  Paolo Bonzini  <bonzini@gnu.org>
7043
7044	* lib/dict.c: VariableWordSubclasses use accessors for 32-bit integers.
7045	BlockClosures are now variableWordSubclasses since the previous encoding
7046	was incompatible with the code to switch the endianness in a saved image.
7047	* lib/dict.inl: Added accessors for 32-bit integers (64-bit on Alphas).
7048	* lib/gst.h: Added warning that says Alphas are not ok yet.
7049	* lib/gst.y: Shell was unusable after a parse error -- solved.
7050	* lib/interp.h: New encoding of BlockClosures (see above).
7051	* lib/prims.inl: C object and memory address primitives use the above
7052	accessors.
7053
70541999-09-08  Paolo Bonzini  <bonzini@gnu.org>
7055
7056	* lib/prims.inl: Flush the FileStream before reading its size.
7057
70581999-09-06  Paolo Bonzini  <bonzini@gnu.org>
7059
7060	* lib/dict.c: Added idleTasks variable to ProcessorScheduler.
7061	* lib/interp.h: Added idleTasks variable to ProcessorScheduler.
7062	* lib/lib.c: Allowed -- to stop option parsing, to comply with getopt.
7063	* lib/sysdep.c: Added POSIX interrupt handling (sigprocmask); Win32
7064	code for alarms now uses kill(2) instead of manually calling the
7065	handler.
7066
70671999-09-02  Paolo Bonzini  <bonzini@gnu.org>
7068
7069	* lib/gst.y: Added support for [ :a :b || temp1 temp2 | ].
7070	* lib/lex.c: UnreadChar not static anymore.  Also removed scanStringoid
7071	and moved its code to stringLiteral.  Parsing a comment does not
7072	actually require to store the whole comment in memory, so it is a
7073	conceptually different operation.  Fixed for the change to str.c below.
7074	Removed memory leak in printToken (not so important since it's just
7075	debugging code, but it's a bug).
7076	* lib/lex.h: UnreadChar is now extern.
7077	* lib/lib.c: Removed references to resizeString.
7078	* lib/str.c: Removed resizeString, curStrBuf now returns a copy of the
7079	string (previously it was a chore left to its caller through strdup).
7080
70811999-08-31  Paolo Bonzini  <bonzini@gnu.org>
7082
7083	* lib/interp.c: Registers where the interpreter's ip and sp stay are
7084	hard-coded for most architectures.  Added definitions for the high
7085	speed interpreter with dynamic translation.
7086	* lib/interp.inl: Moved internal accessors to interp.c; moved object
7087	equality and hashing functions to dict.inl (the only places where they
7088	were actually used).
7089
70901999-08-30  Paolo Bonzini  <bonzini@gnu.org>
7091
7092	* lib/bytecode.inl: Created from part of interp.c
7093	* lib/gst.h: Removed `extern' definition of the instruction pointer.
7094	* lib/interp.c: Made the instruction pointer static; prepared for the
7095	new bytecode.inl file; relativeByteIndex is replaced by
7096	currentBytecodeIndex; added definitions of the latter macro.
7097	* lib/interp.inl: Removed relativeByteIndex.
7098	* lib/prims.inl: RelativeByteIndex is replaced by currentBytecodeIndex.
7099
71001999-08-29  Paolo Bonzini  <bonzini@gnu.org>
7101
7102	*** Version 1.6.2 released.
7103
71041999-08-27  Paolo Bonzini  <bonzini@gnu.org>
7105
7106	* lib/cint.c: Always define DLD functions (at worst they're stubs)
7107	* lib/dld_none.c: Created.
7108	* lib/lib.c: Always load DLD.st (at worst it refers to C stubs)
7109
71101999-08-26  Paolo Bonzini  <bonzini@gnu.org>
7111
7112	* lib/dict.c: Put CDoubleMin and CDoubleMax in the Smalltalk dictionary.
7113	* lib/interp.c: NEXT_BYTECODE was not defined for old (switch statement)
7114	dispatching.
7115
71161999-08-08  Paolo Bonzini  <bonzini@gnu.org>
7117
7118	* lib/dict.c: In initRuntimeObjects, define the ImageFileName global
7119	as equal to binaryImageName.
7120	* lib/lib.c: Load .stpre only when creating local image files.  Removed
7121	findImageFile.  Option -v shows the hard-coded kernel and image paths.
7122	binaryImageName is not static anymore, defaultImageName is.
7123	* lib/lib.h: Removed findImageFile.  binaryImageName is now declared
7124	here as an extern symbol, and defaultImageName is not.
7125	* lib/prims.inl: `Smalltalk snapshot' primitive (250) removed -- the
7126	new ImageFileName global makes it redundant.
7127	* lib/save.c: LoadFromFile now expects a full path to the image just like
7128	saveToFile, does not call findImageFile.
7129
71301999-08-07  Paolo Bonzini  <bonzini@gnu.org>
7131
7132	* lib/cint.c: Declare `unlink' (valid only for files) instead of `remove'
7133	(which nukes whole directories too) to be used to implement
7134	File class>>#primRemove:
7135	* lib/sysdep.c: Added simulation of popen and pclose in openPipe
7136	and closePipe.
7137
71381999-08-07  Paolo Bonzini  <bonzini@gnu.org>
7139
7140	* lib/dict.h: InitSTDIOObjects became initRuntimeObjects
7141	* lib/dict.c: InitSTDIOObjects became initRuntimeObjects, and various
7142	initializations (Features, KernelPath, ImagePath) were moved here from
7143	initSmalltalkDictionary.  This completes the change made on July 14th.
7144	* lib/lib.c: InitSTDIOObjects became initRuntimeObjects
7145
71461999-08-06  Paolo Bonzini  <bonzini@gnu.org>
7147
7148	* lib/interp.inl: RelativeByteIndex now explicitly casts to int for
7149	Alpha compatibility.
7150	* lib/sym.c: Switched from int to long when dealing with differences
7151	between addresses, for Alpha compatibility.
7152	* lib/dict.c: Switched from int to long when dealing with differences
7153	between addresses, for Alpha compatibility.
7154
71551999-07-15  Paolo Bonzini  <bonzini@gnu.org>
7156
7157	* lib/dld_gnu.c: Added gst_dld_exts (.o, .a)
7158	* lib/dld_gst.h: Added gst_dld_exts
7159	* lib/dld_gst.c: Added gst_dld_openext
7160	* lib/dld_hpux.c: Added gst_dld_exts (.sl)
7161	* lib/dld_ltdl.c: Added gst_dld_exts (dummy)
7162	* lib/dld_libdl.c: Added gst_dld_exts (.so, .a)
7163	* lib/dld_win32.c: Added gst_dld_exts (.dll, .exe)
7164
71651999-07-14  Paolo Bonzini  <bonzini@gnu.org>
7166
7167	* lib/gst.h: Added F_BYTE, used while saving to ease reloading
7168	if the endianness changes.
7169	* lib/save.c: Added ability to load images from machines with
7170	different endianness and to recognize (and reject) images from
7171	machines with different sizeof(long).  This change unveiled a bug
7172	in GNU C 2.7.2!!!
7173	* lib/dld_ltdl.c: Created (thanks to Alexander Shinn for pointing
7174	me to libtool!)
7175
71761999-07-10  Paolo Bonzini  <bonzini@gnu.org>
7177
7178	* lib/interp.c: InterruptHandler should set again the handler
7179	for SIGINT
7180	* lib/sysdep.c: Fixed syntax error. Also, sigaction should use
7181	SA_RESETHAND if available because signal is supposed to work
7182	that way.
7183	* lib/sysdep.c: #define SIGALRM if not provided by C headers.
7184
71851999-07-05  Paolo Bonzini  <bonzini@gnu.org>
7186
7187	* gstconf.h.in: Changed USE_READLINE to HAVE_READLINE (more coherent)
7188	* gstconf.h: Same as above
7189	* lib/comp.c: Same as above
7190	* lib/lex.c: Same as above
7191	* lib/lex.h: Same as above
7192	* lib/lib.c: Same as above
7193
71941999-07-04  Paolo Bonzini  <bonzini@gnu.org>
7195
7196	* lib/sysdep.c: Renamed dprintf to debugf. glibc 2.0 defines
7197	a different prototype for a function with the same name (glibc 2.1
7198	only defines it if __USE_GNU is defined and does not break gst).
7199
72001999-06-28  Paolo Bonzini  <bonzini@gnu.org>
7201
7202	* lib/qsort.c: Added standard stuff to make alloca work.
7203	* lib/gstpub.h: Moved inclusion of gst.h *inside* `extern "C"'
7204
72051999-06-25  Paolo Bonzini  <bonzini@gnu.org>
7206
7207	*** Bug-fixing version 1.6.1 released.
7208
72091999-06-21  Paolo Bonzini  <bonzini@gnu.org>
7210
7211	* lib/alloc.c: In xrealloc, we must call malloc explicitly when
7212	the first argument is 0, since some reallocs don't do this.
7213	* lib/cint.c: Fix for Solaris' brokenness (in their stat.h, they use
7214	`#define st_atime st_atim.tv_sec')
7215	* lib/qsort.c: Added (from GCC).
7216
72171999-06-17  Mark Elbrecht  <snowball@bigfoot.com>
7218
7219	*** Version 1.6 released.
7220	* lib/lex.c: Fix crash when using drive letters in isKernelFile.
7221	* lib/lib.c: For DOS, use '_stinit' and '_stpre' as init files since
7222	DOS doesn't allow a period to start a filename.
7223
72241999-06-09  Pahi Andras  <pahi@mozart.eet.bme.hu>
7225
7226	* lib/cint.c: DefineCFunc makes a private copy with strdup of the
7227	C function's name. The problem is likely to root to the pre-DLD days
7228	(1989-1990) when only string constants were passed to defineCFunc, so
7229	strdup was unnecessary.
7230
72311999-06-03  Paolo Bonzini  <bonzini@gnu.org>
7232
7233	* lib/comp.c: Added displayCompilationTrace
7234	* lib/comp.h: Added declaration of displayCompilationTrace
7235	* lib/prims.inl: If declaration tracing is on, shows new
7236	categories as encountered.
7237
72381999-05-30  Paolo Bonzini  <bonzini@gnu.org>
7239
7240	* lib/gst.h: Added default values for the definitions that used to
7241	be in gstpaths.h
7242	* lib/gstpaths.h: Removed since configure did not create it properly
7243	after the installer was fixed
7244	* lib/Makefile.in: Added definitions to be used in place of gstpaths.h
7245	* lib/lib.c: If the the paths cannot be located, try using the local
7246	directory
7247	* lib/lib.h: DefaultImageName is now a variable
7248	* lib/str.c: Added resizeString
7249
72501999-05-28  Paolo Bonzini  <bonzini@gnu.org>
7251
7252	* lib/cint.c: Object passed as `unknown' or `self', whose class is not
7253	recognized, are now passed as an OOP (they used to be skipped).
7254	* lib/interp.c: the open-coded // was rounding like quo: Does.
7255	* lib/prims.inl: The base date for secondClock was 2 Jan 2000 instead
7256	of 1 Jan 2000.  This was apparent after the fix above.
7257
72581999-05-20  Paolo Bonzini  <bonzini@gnu.org>
7259
7260	* lib/alloc.c: Moved platform-dependent definitions here.  Modified
7261	so that, if we replace libc's allocator, we define calloc too (see
7262	glibc's manual).  Also modified so that xmalloc exits if it fails.
7263	* lib/alloc.h: Removed platform-dependent definitions.  Now this
7264	file only contains extern declarations (correctly).
7265
72661999-05-15  Paolo Bonzini  <bonzini@gnu.org>
7267
7268	* lib/gst.h: Added code to #define `volatile' to nothing if it is
7269	not supported.
7270	* lib/interp.c: Modified to pass through -Wall when optimization
7271	is on.  This highlighted a possible (although never observed) bug in
7272	sendMessageInternal: the setjmp/longjmps in executePrimitiveOperation
7273	could have clobbered methodOOP, which is now declared volatile.
7274
72751999-05-14  Paolo Bonzini  <bonzini@gnu.org>
7276
7277	* lib/byte.c: Modified to (almost) pass through -Wall.
7278	* lib/cint.c: Modified to pass through -Wall.
7279	* lib/comp.c: Modified to pass through -Wall.
7280	* lib/dict.c: Modified to pass through -Wall.
7281	* lib/dict.inl: Modified to pass through -Wall.
7282	* lib/gstpub.h: Added C++ `extern "C"' guard.
7283	* lib/interp.c: Modified to pass through -Wall.
7284	* lib/interp.inl: Modified to pass through -Wall.
7285	* lib/lex.c: Modified to pass through -Wall.
7286	* lib/oop.c: Modified to pass through -Wall.
7287	* lib/save.c: Modified to pass through -Wall.
7288	* lib/sym.c: Modified to pass through -Wall.
7289
72901999-05-13  Paolo Bonzini  <bonzini@gnu.org>
7291
7292	* lib/callin.c: Added objectAlloc.
7293	* lib/gst.h: Added guards to avoid including heavily implementation
7294	dependent stuff when gst.h is included by gstpub.h
7295	* lib/gstpub.h: Changed to use those guards.
7296	* lib/dld_hpux.c: Created.
7297	* lib/dld_libdl.c: New name of dld_sun.c
7298	* lib/lex.c: Stream description for readline streams is not
7299	`a Readline string' anymore, but `stdin' (since that's where we
7300	actually get the string).  Also, when readline is used I also
7301	include <readline/history.h> now; and I disable readline's auto-
7302	completion feature, not supported by gst (initializeReadline).
7303
7304
73051999-05-11  Paolo Bonzini  <bonzini@gnu.org>
7306
7307	* lib/comp.c: Various performance counters are now unsigned longs.
7308	* lib/comp.h: Various performance counters are now unsigned longs.
7309	* lib/interp.c: #mustBeBoolean is now sent to the object that should
7310	have been a Boolean, as the Blue Book says.  Plus, same as above.
7311	* lib/interp.h: Various performance counters are now unsigned longs.
7312
73131999-05-09  Paolo Bonzini  <bonzini@gnu.org>
7314
7315	* lib/id.c: Removed -- I'm very sorry to do it, since it was created
7316	10 1/2 years ago, but it was a copy of str.c
7317	* lib/id.h: Removed -- I'm very sorry to do it, since it was created
7318	10 1/2 years ago, but it was a copy of str.h
7319	* lib/lex.c: Removed references to function that used to be in poor id.c;
7320	changed references to copyStr to use strdup.
7321	* lib/prims.inl: Added code to test for infinity, NaNs and other failures
7322	in mathematical functions (exp/ln/sqrt/trigonometry).
7323	* lib/str.c: Removed copyStr.
7324	* lib/sysdep.h: Added portable macros to test for nan and infinity.
7325	Not all libc's have isnan, isinfinity and the like.
7326
73271999-05-08  Paolo Bonzini  <bonzini@gnu.org>
7328
7329	* lib/comp.c: fixed bug when compiling to:do:/to:by:do: And the loop
7330	index temporary was in position 15 (a 2-byte push was erroneously
7331	compiled, since a 1-byte push can be used).
7332	* lib/interp.c: Did not trap divides by zero on open-coded // messages.
7333	* lib/lib.c: Added Transcript.st to the list of kernel files.
7334	* lib/oop.c: Character objects' objSize field was uninitialized. Fixed.
7335	* lib/prims.inl: fixed SIGSEGV on (IndexableClass new: ANegativeNumber).
7336
73371999-05-06  Paolo Bonzini  <bonzini@gnu.org>
7338
7339	* lib/dict.c: Added exceptionHandlers variable to Process.
7340	* lib/gst.y: Fixed bug with conditional compilation -- conditional
7341	exclusion was not disabled by the double bang sequence.
7342	* lib/interp.h: Added exceptionHandlers variable to Process.
7343
73441999-05-03  Paolo Bonzini  <bonzini@gnu.org>
7345
7346	* lib/interp.c: Changed the system message #booleanRequired to
7347	#mustBeBoolean for coherence with the Blue Book (I had not noted
7348	that passage).  Fixed async signals (actually, I just removed
7349	the error messages -- they seem to work as they are and their
7350	implementation is exactly the same as in the book...) and
7351	changed the signal handling routines to use them instead of
7352	separate variables.  Added asyncSignal().
7353	* lib/interp.h: Added declarations for asyncSignal().
7354	* lib/interp.inl: Fixed unparenthesized arguments in the `equal' macro.
7355	* lib/gstpub.h: Added declarations for asyncSignal().
7356	* lib/lib.c: Search for a local copy of the kernel files in the
7357	`kernel' subdirectory of the local directory; always save the
7358	kernel sources as FileSegments.  This way, GNU Smalltalk works
7359	both if a) it is installed and the kernel lies in /usr/local/share
7360	b) it is not installed and everything is done inside the
7361	user's home directory c) it is not installed, we are under Windows
7362	and everything is done inside the current directory (maybe I'll
7363	switch to the executable directory in the future...)
7364
73651999-04-29  Paolo Bonzini  <bonzini@gnu.org>
7366
7367	* lib/comp.c: Now does compile correctly optimized selectors whose
7368	block arguments have arguments or temporaries.  In fact I simply
7369	don't optimize them -- but maybe I will sooner or later.  Also,
7370	#timesRepeat:, #to:do: and #to:by:do: are now open-coded.
7371	Finally, I fixed the fact that the bytecodes for an erroneous method
7372	were put at the beginning of the next syntactically valid method.
7373	* lib/lib.c: The `Smalltalk Ready' banner is now `GNU Smalltalk Ready'.
7374	* lib/save.c: Added timesRepeatColonSymbol, toColonDoColonSymbol and
7375	toColonByColonDoColonSymbol.
7376	* lib/sym.c: Same as above.
7377	* lib/sym.h: Same as above.
7378
73791999-04-27  Paolo Bonzini  <bonzini@gnu.org>
7380
7381	*** Version 1.5.beta3 released.
7382	* lib/alloc.c: Added inclusion of stdlib.h (or malloc.h for old C's)
7383	when the custom allocator is not used.
7384	* lib/byte.c: Fixed optimization of pushIndexed.
7385	* lib/dld_sun.c: Added missing semicolon.
7386	* lib/interp.c: Finished new GCC implementation at last -- now we
7387	only have to do a single goto for EVERY bytecode.  Maybe something
7388	better could be done by caching dispatchVec in a register...  Auto-
7389	matic #undef-ining of USE_OLD_DISPATCH is now based on the new
7390	gstconf.h definition HAVE_GOTO_VOID_P (used to simply check __GNUC__).
7391
73921999-04-25  Paolo Bonzini  <bonzini@gnu.org>
7393
7394	* lib/byte.c: Added optimization of nopBytecode.  Added `replace
7395	stack top' bytecodes 140-142 in optimizeBasicBlock.
7396	* lib/byte.h: Added `replace stack top' bytecodes.
7397	* lib/comp.c: Added yourselfSymbol in whichBuiltinSelector (yourself
7398	is now open-coded).
7399	* lib/interp.c: Added `replace stack top' bytecodes.
7400	* lib/prims.inl: Changed GC-tuning primitives (spaceGrowRate
7401	and growThreshold) to accept integers too.
7402	* lib/sym.h: Added yourselfSymbol.
7403	* lib/sym.c: Added yourselfSymbol.
7404	* lib/save.c: Added yourselfSymbol.
7405
74061999-04-23  Paolo Bonzini  <bonzini@gnu.org>
7407
7408	* lib/gst.h: Cleaned up some definitions for ANSI features which
7409	can be checked by autoconf -- the old #ifdef method only makes things
7410	cumbersome.  Also renamed config.h to gstconf.h, so that it can be
7411	installed without filename clashes.
7412	* lib/interp.c: Changed verbose execution tracing to print the stack
7413	top *BEFORE* the bytecode -- the output is easier to follow.  Added
7414	jump lookahead (see definition of JUMP_LOOKAHEAD).
7415	* lib/oop.c: Began switching to something resembling a generational
7416	collector.  Changed GC-tuning variables (spaceGrowRate/growThreshold)
7417	to be integers -- because they are now checked in allocObj and doubles
7418	are more expensive in busy code, I think.
7419
74201999-04-22  Paolo Bonzini  <bonzini@gnu.org>
7421
7422	* lib/byte.h: Merged bytecodes 138-139 (push/store outer temp) into a
7423	single bytecode 138, which can also do a `pop and store outer temp'.
7424	* lib/byte.c: Same as above. The new bytecode behaves much like bytecode
7425	126, so the code for that bytecode in the optimizer can be used by the
7426	new bytecode too.  Added more cases in the peephole optimizer.
7427	* lib/comp.c: Same as above.
7428	* lib/interp.c: Same as above. Moved various optimization #define's at
7429	the top of the file.
7430
74311999-04-20  Paolo Bonzini  <bonzini@gnu.org>
7432
7433	* lib/byte.c: Optimizer in and working.  Fixed challenging cases in
7434	the flow analyzer which were apparent now because the peephole
7435	optimizer does some `interesting' changes to the bytecode -- previously
7436	the changes were not `interesting' enough for these bugs to show up.
7437	Performance +5-10%, but some interesting optimizations are not there
7438	yet (e.g. pop-store/push --> store, and push/push --> dup).
7439
74401999-04-19  Paolo Bonzini  <bonzini@gnu.org>
7441
7442	* lib/byte.c: Added to the flow analysis some support for optimizing
7443	#ifTrue: and #ifFalse: in the common case where their result is
7444	discarded.  Added a first peephole optimizer in optimizeBasicBlock.
7445	* lib/byte.h: Added nop bytecode 139
7446	* lib/comp.c: Changed the compilatation of #ifTrue:/#ifFalse: to one
7447	which is more optimizable if the result is discarded.  #and:/#or: are
7448	left as they were because their result is usually kept.  Also ALWAYS
7449	put a pop bytecode at the end of a statement -- it makes flow analysis
7450	simpler and is removed by the peephole optimizer if unnecessary.
7451	* lib/interp.c: Added nop bytecode 139
7452
74531999-04-18  Paolo Bonzini  <bonzini@gnu.org>
7454
7455	* lib/byte.c: The new optimization scheme proved to be easily
7456	extendable (which is what I wanted). I added jump optimization
7457	(10 lines of code) and unreachable code elimination (5 lines) -- no
7458	big speed improvements, but now I have moer experience with
7459	optimization and will approach peepholing.
7460	* lib/byte.c: Modified various internal functions to avoid continuous
7461	reallocation of bytecodes.  For instance, reallocByteCodes uses
7462	xrealloc() -- it was always malloc-ing everything from scratch --
7463	and allocByteCodes and reallocByteCodes have a parameter with the
7464	amount of memory to be allocated.
7465	* lib/cint.c: Call initDldLib if HAVE_DLD is defined.
7466
74671999-04-16  Paolo Bonzini  <bonzini@gnu.org>
7468
7469	* lib/dld_gst.c: Created from old cxtnsn/dld.c
7470	* lib/dld_gst.h: Created
7471	* lib/dld_gnu.c: Created
7472	* lib/dld_sun.c: Created
7473	* lib/dld_win32.c: Created
7474	* lib/byte.c: Changed the algorithm for optimizeByteCodes.  Instead of
7475	doing a single scan on the bytecodes and fixing up jumps the hard way,
7476	I'm now dividing the bytecodes into basic blocks, optimizing each of
7477	them one at a time in optimizeBasicBlock.
7478	* lib/dict.c: Moved hasBlock to ContextPart, yanked it out from
7479	BlockContext and MethodContext.
7480	* lib/interp.c: Moved hasBlock to the fourth position (inside
7481	MethodContexts and BlockContexts) so that we can put it in ContextPart.
7482	* lib/lib.c: Load DLD.st from kernel if HAVE_DLD is defined.
7483
74841999-04-12  Paolo Bonzini  <bonzini@gnu.org>
7485
7486	* lib/sysdep.c: Functions handling time_t's now use signed longs.
7487	* lib/sysdep.c: Stole more portable implementations of adjustTimeZone
7488	and currentTimeZoneBias from GNU Emacs.  Added support for broken
7489	versions of localTime(3) that cache the time zone.
7490	* lib/sysdep.h: Functions handling time_t's now use signed longs.
7491
74921999-04-10  Paolo Bonzini  <bonzini@gnu.org>
7493
7494	*** Version 1.5.beta2 released.
7495	* lib/cint.c: My_stat now adjusts file times to local times.
7496	* lib/sysdep.c: Added adjustTimeZone and currentTimeZoneBias.
7497	* lib/sysdep.h: Added adjustTimeZone and currentTimeZoneBias.
7498
74991999-04-09  Paolo Bonzini  <bonzini@gnu.org>
7500
7501	* lib/cint.c: Fixed my_stat to return times relative to 1/1/2000
7502	to avoid possible overflows (which would have happened around 2004
7503	on 32-bit machine, and around 8.000.000.000 AD on 64-bit ones...).
7504
75051999-04-08  Paolo Bonzini  <bonzini@gnu.org>
7506
7507	* lib/interp.c: Fixed bug in sendMessageInternal and sendBlockValue.
7508	Basically, we now make sure that sp and thisContext->spOffset are
7509	consistent whenever a GC could happen; otherwise, fixupObjectPointers
7510	recomputes thisContext->spOffset from sp, storing an erroneous value
7511	into the former.
7512
75131999-03-29  Paolo Bonzini  <bonzini@gnu.org>
7514
7515	* lib/gst.h: Added definition of WIN32 because Cygwin only defines
7516	_WIN32, but many programs rely on WIN32 instead.
7517
75181999-03-22  Paolo Bonzini  <bonzini@gnu.org>
7519
7520	* lib/sysdep.c: Fixed Win32 version of Delays, which was buggy if a
7521	delay had to cancel the previous one.  The new version is also much
7522	more precise.
7523
75241999-03-21  Paolo Bonzini  <bonzini@gnu.org>
7525
7526	* lib/interp.c: Changed Integer relational operators to not do a
7527	toInt() (instead we use a simple typecast).
7528
75291999-03-15  Paolo Bonzini  <bonzini@gnu.org>
7530
7531	*** Version 1.5.beta1 released.
7532	* lib/dict.c: Changed to use setCObjectValueObj and cObjectValueObj.
7533	* lib/dict.h: Doc fixes for CObject.
7534	* lib/dict.inl: Added setCObjectValueObj and cObjectValueObj.  Now, the
7535	address pointed by the CObject is the LAST instance variable (including
7536	indexed ones), not always the SECOND (which could still be a fixed
7537	one).  For currently defined CObject subclasses this was not a problem,
7538	but it could have been a serious one if a CObject subclass declared
7539	additional instance variables.
7540	* lib/prims.inl: Changed to use setCObjectValueObj and cObjectValueObj.
7541
75421999-03-13  Paolo Bonzini  <bonzini@gnu.org>
7543
7544	* lib/cint.c: Was crashing if a call-out to a non-existent function
7545	was attempted.
7546	* lib/comp.c: Fixed a strange bug I'm not sure I understood well. It
7547	seems that, if an error occurred in a method with literals, and if an
7548	immediately following method had literals, the literal array
7549	contained bogus data and GST would lose.  I don't think it was there
7550	before my March 3rd change...
7551
75521999-03-11  Paolo Bonzini  <bonzini@gnu.org>
7553
7554	* lib/lib.c: Added --silent as a synonim of --quiet and -q.
7555
75561999-03-03  Paolo Bonzini  <bonzini@gnu.org>
7557
7558	* lib/comp.c: Added stack depth tracing (variables and macros
7559	containing stackDepth).  Made makeNewMethod public, to avoid lots of
7560	duplicate code for the C and Smalltalk compiler.
7561	* lib/prims.inl: Added primitive 79, which maps to makeNewMethod.
7562	* lib/interp.c: Added support for mixed size contexts. Added
7563	resetFakeContexts.
7564	* lib/interp.c: The change above unveiled lots of bugs - especially
7565	uninitialized pointers here and there. In particular: a) GST would
7566	core dump when you did a send to super from a class without a
7567	superclass; b) prepareExecutionEnvironment set the stack pointer of
7568	the context to 0 instead of -1 so markAnOOPInternal would try to
7569	mark an additional stack slot.
7570	* lib/oop.c: In minorGCFlip, call resetFakeContexts at the end instead
7571	of using deallocFakeContext for every context.
7572
75731999-02-28  Paolo Bonzini  <bonzini@gnu.org>
7574
7575	* lib/comp.c: Modified compileAssignments to use preferrably the
7576	`storeIndexed' bytecode. This is faster and also makes the task
7577	of an eventual bytecode optimizer a bit simpler.
7578	* lib/byte.c: Added truncateByteCodes.  Moved optimizeByteCodes
7579	here and made it extern (it was a static in lib/comp.c), and added
7580	it some (working but currently not used) code.
7581	* lib/byte.h: Added optimizeByteCodes and truncateByteCodes
7582
75831999-02-27  Paolo Bonzini  <bonzini@gnu.org>
7584
7585	* lib/prims.inl: Added primitive 101 (ProcessorScheduler>>
7586	isTimeoutProgrammed).
7587	* lib/dict.c: Added DelayProcess and IdleProcess as
7588	Delay's class variables
7589	* lib/interp.c: In initProcessSystem, leave the processes the way
7590	they were unless we get here after a deadlock.
7591
75921999-02-26  Paolo Bonzini  <bonzini@gnu.org>
7593
7594	* lib/interp.c: Changes to have an error-free compile with
7595	-pedantic.  Also fixed highestPriorityProcess to return the
7596	active process if it is not waiting on a semaphore (because
7597	`Processor yield' must not stop execution if the only
7598	runnable process is the active one).
7599	* lib/lex.c: Added support for -s command line option in
7600	isKernelFile.
7601	* lib/lib.c: Added -s command line option.
7602	* lib/oop.c: Removed arithmetics on void * in realizeOOPs.
7603
76041999-02-23  Paolo Bonzini  <bonzini@gnu.org>
7605
7606	* lib/gst.y: Added #'abcd' symbols (not in Smalltalk-80,
7607	but ANSI and common in many commercial Smalltalk
7608	implementations).
7609
76101999-02-22  Paolo Bonzini  <bonzini@gnu.org>
7611
7612	* lib/lib.c: Moved some initializations *after* parsing the
7613	command line (obviously *before* loading user files),
7614	so that parameters on the cmdline can influence the
7615	initialization process.
7616
76171999-02-21  Paolo Bonzini  <bonzini@gnu.org>
7618
7619	* lib/interp.c: Added printing of what is the erroneous method in
7620	sendMessageInternal.  Also renamed global SP/IP to outerSP and
7621	outerIP (which are then #defined to ip and sp in gst.h), so that
7622	there is no name collision between the local IP/SP and the global
7623	ones; and eliminating ipAddr/spAddr we get some more speed. But
7624	remember this when using GDB!!
7625
76261999-02-18  Paolo Bonzini  <bonzini@gnu.org>
7627
7628	* lib/interp.c: Struggled to make the process system work as
7629	intended; it still has a few bugs but it mostly works (for
7630	example, philosophers now work).
7631
76321999-02-16  Paolo Bonzini  <bonzini@gnu.org>
7633
7634	* lib/oop.c: Started switching to generational GC!! In short,
7635	minor GCs only take care of fake contexts and are faster
7636	because no sweeping happens; major GCs don't bother of
7637	fake contexts (they assume there are none) and deal with
7638	removing real unused objects.
7639
76401999-02-15  Paolo Bonzini  <bonzini@gnu.org>
7641
7642	* lib/byte.h: Added bigLiteral bytecode.
7643	* lib/comp.c: Changed so that methods are normal objects - no
7644	more variable classes and variable byte classes at
7645	the same time. Now, the header does not include the
7646	number of literals, so I also added code to use the
7647	new 126 bytecode.
7648	* lib/interp.c: Changed so that methods are normal objects - no more
7649	variable classes and variable byte classes at the
7650	same time.
7651	* lib/interp.inl: Changed so that methods are normal objects - no more
7652	variable classes and variable byte classes at the
7653	same time.
7654	* lib/prims.inl: Now methods are normal objects - no more variable
7655	classes and variable byte classes at the same time.
7656	So I removed primitives 68/69/79.
7657	* lib/save.c: Changed so that methods are normal objects - no more
7658	variable classes and variable byte classes at the
7659	same time.
7660
76611999-02-14  Paolo Bonzini  <bonzini@gnu.org>
7662
7663	* lib/oop.c: Experimentally moved markGlobalOOPs at the START
7664	of the marking phase, so that by the time the other
7665	objects in the root set are dealt with, many objects
7666	will have been marked. This might improve a bit GC
7667	locality of reference.
7668	* lib/save.c: Experimentally reorganized the global OOPs.
7669	smalltalkDictionary and the symbols at the END of
7670	the global OOP table, so that by the time they are
7671	marked other objects will have been dealt with and
7672	recursion will be more shallow; this might improve
7673	a bit GC locality of reference.
7674
76751999-02-13  Paolo Bonzini  <bonzini@gnu.org>
7676
7677	* lib/sysdep.c: Using setSignalHandler() inside signalAfter().
7678
76791999-02-12  Paolo Bonzini  <bonzini@gnu.org>
7680
7681	* lib/sysdep.c: GetCurDirName, now performs special error handling
7682	when getcwd is used (code stolen from the gettext
7683	library's source code, by David MacKenzie).
7684
76851999-02-09  Paolo Bonzini  <bonzini@gnu.org>
7686
7687	* lib/gst.h: Moved incubator here from oop.h so that it is public
7688	* lib/oop.h: Moved incubator to gst.h so that it is public (see
7689	comment in GST 1.1.5 - "it is likely that this
7690	interface will be moved..."
7691
76921999-02-08  Paolo Bonzini  <bonzini@gnu.org>
7693
7694	* lib/byte.c: Print new bytecode 126 for many literals, > 64.
7695	* lib/cint.c: Removed code to print "function not registered"
7696	message - Smalltalk code handles that now.
7697	* lib/lib.c: CFuncs.st is now loaded *after* CObject and CType -
7698	a logical choice since C function declarations could
7699	use CTypes.  Added PkgLoader.
7700
77011999-02-06  Paolo Bonzini  <bonzini@gnu.org>
7702
7703	* lib/prims.inl: Sped up nextInstance by avoiding to search in the
7704	unused OOPs.
7705
77061999-02-05  Paolo Bonzini  <bonzini@gnu.org>
7707
7708	* lib/interp.c: Added callbacks #booleanRequired and #interrupt.
7709	Implemented bytecode 126 for many literals, > 64.
7710	* lib/prims.inl: Primitive 255 now does not blindly set inCCode to
7711	false if a C callout made a callin which in turn made
7712	a callout.
7713
77141999-02-04  Paolo Bonzini  <bonzini@gnu.org>
7715
7716	* lib/lex.c: Modified so that a bang is not part of a binary op.
7717	It's just a one-char token like [ and #.  Needs
7718	fixing, though.
7719
77201999-02-03  Paolo Bonzini  <bonzini@gnu.org>
7721
7722	* lib/callin.c: Changed calls to yyparse() to parseStream().
7723	* lib/comp.c: Changed calls to yyparse() to parseStream().
7724	* lib/interp.c: Changed calls to yyparse() to parseStream().
7725	* lib/gst.y: More attempts at simplifying things around:
7726	now an expression invoking methodsFor: can be
7727	as complex as desired. In addition I changed
7728	temporaries and primitive to have a default value,
7729	so that almost-duplicated rules (e.g. `statements',
7730	`temporaries primitive statements', `temporaries
7731	statements', `temporaries primitive') can be put
7732	into a single one. Alas this causes 4 shift/reduce
7733	conflicts (2 in state 0, 2 in state 6) but Bison
7734	gracefully handles them and it makes the grammar more
7735	readable IMO.
7736	* lib/lex.c: Moved lex debugging here.  In addition, now
7737	you can compile this with NO_PARSE so that no parsing
7738	occurs - only lexical analysis.  To accomplish this, the
7739	callers need to call a function in lib/lex.c (parseStream)
7740	instead of yyparse().
7741	* lib/lib.c: Updated lex debugging and moved it to lex.c
7742
77431999-02-02  Paolo Bonzini  <bonzini@gnu.org>
7744
7745	* lib/alloc.c: Added custom allocator, currently used only under
7746	Win32.  See comment in the file.
7747	* lib/alloc.h: Added custom allocator, currently used only under
7748	Win32.  See comment in the file.
7749	* lib/sym.c: internCountedString: The symbol OOP is now read only.
7750
77511999-02-01  Paolo Bonzini  <bonzini@gnu.org>
7752
7753	* lib/oop.c: Fix in growMemory. Now it seems to work right -
7754	previously, it failed if thisContext was not a fake
7755	and the heap moved.
7756
77571999-01-29  Paolo Bonzini  <bonzini@gnu.org>
7758
7759	* lib/byte.c: Modified isSimpleReturn so that a "return literal[0]"
7760	method is optimized.
7761	* lib/comp.c: Modified isSimpleReturn (in byte.c) so that a "return
7762	literal[0]" method is optimized. The "primitive must
7763	be executed" case, which was previously identified by
7764	flags == 3, is now identified by primitiveIndex != 0.
7765
77661999-01-28  Paolo Bonzini  <bonzini@gnu.org>
7767
7768	* lib/comp.c: Moved regressionTesting to lib.c; it seems more
7769	logical to me.
7770	* lib/gst.h: fix in incrInt/decrInt: It was not converting the
7771	OOP to a long before adding 2 - so it was actually
7772	adding sizeof(OOP)*2 = 16!
7773	* lib/lib.c: To make -S work when -i was specified too.
7774	* lib/oop.c: NilOOP, trueOOP and falseOOP are now initialized in
7775	allocOOPTable(), not initOOPTable(). Actually I can't
7776	guess why they weren't there in the first place.
7777	* lib/prims.inl: Added check for already closed file in fileOp: (if
7778	fileStream->file = nilOOP, fail). Added flushPrim
7779	and getBytePrim.
7780	* lib/save.c: Removed experimentally the code that saves and
7781	restores nil, true, false and the characters:
7782	why can't we initialize them just like if we were
7783	initializing the system from scratch, without
7784	an image?
7785	* lib/sysdep.c: OpenFile, removed references to BINARY_MODE_NEEDED
7786	(I had to remove it from the configure script because
7787	it did not work correctly, at least under Cygnus'
7788	Win32 port.
7789
77901999-01-27  Paolo Bonzini  <bonzini@gnu.org>
7791
7792	* lib/dict.c: Smalltalk dictionary is now created with a larger
7793	size than it used to be (see the definition of INITIAL_SMALLTALK_SIZE).
7794	* lib/interp.c: Made the method cache an array of a struct instead of
7795	five different arrays.  A "return literal" method is
7796	optimized like "return self" and "return inst. var".
7797
77981999-01-26  Paolo Bonzini  <bonzini@gnu.org>
7799
7800	* lib/comp.c: Removed code for evaluating (parse last statement as
7801	return) - not needed since Smalltalk code implements
7802	evaluate: Also changed references to findVariable to
7803	prevent assignments into arguments.
7804	* lib/gst.y: Removed code to parse last statement as return -
7805	not needed since Smalltalk code implements evaluate:
7806	* lib/lex.c: Modified to have a variable indicating the name of
7807	the log file.
7808	* lib/lib.c: Changed -v to exit after the output, like
7809	--version. Added -l and -L to log to a file. Added
7810	long options.
7811	* lib/sym.c: Modified findVariable and localVarIndex so that
7812	assignments to arguments are detected.
7813
78141999-01-25  Paolo Bonzini  <bonzini@gnu.org>
7815
7816	* lib/dict.inl: Spiffed it up with a few register clauses.
7817	Also removed modulus operator (%) when possible.
7818	This increased performance (especially in message
7819	sends) only by 5%, but it was so easy I could not
7820	but do it!
7821
78221999-01-24  Paolo Bonzini  <bonzini@gnu.org>
7823
7824	* lib/alloc.c: Added this banner.
7825	* lib/alloc.h: Created.
7826	* lib/lex.c: Fixed lineStamp() so that the format is consistent
7827	with GCC and other GNU programs: for example,
7828	"Integer.st:115: parse error")
7829
78301999-01-22  Paolo Bonzini  <bonzini@gnu.org>
7831
7832	* lib/gst.h: Moved SIG_ARG_TYPE from sysdep.c here.  Added paranoic
7833	checking of memset arguments when bzero is used.
7834	* lib/interp.c: Moved SIG_ARG_TYPE to gst.h
7835	* lib/sysdep.c: Moved SIG_ARG_TYPE to gst.h
7836
78371999-01-18  Paolo Bonzini  <bonzini@gnu.org>
7838
7839	* lib/interp.inl: Fixed bug in large integers.  I was not considering
7840	that the product of the low-order 15 bits could exceed 15 bits!
7841
78421999-01-16  Paolo Bonzini  <bonzini@gnu.org>
7843
7844	* lib/dict.h: Added byteStreamClass.
7845	* lib/interp.c: Yesterday I removed maxSize instance variable from
7846	WriteStream, so I had to remove it from the FileStream
7847	struct, either.
7848	* lib/lib.c: Added ByteStream.st.
7849	* lib/save.c: Added byteStreamClass.
7850
78511999-01-15  Paolo Bonzini  <bonzini@gnu.org>
7852
7853	* lib/dict.c: Removed maxSize instance variable from WriteStream.
7854	Fixed missing isPipe parameter in addSTDIOObject.
7855	Added ByteStream.  Added CShortSize global.
7856
78571999-01-13  Paolo Bonzini  <bonzini@gnu.org>
7858
7859	* lib/cint.c: Added getArgc and getArgv
7860	* lib/lib.c: Added ability to get argc/argv from Smalltalk code.
7861	* lib/sysdep.c: Fixed a small & invisible error, a 'start of comment'
7862	misplaced for a 'end of comment' (note by Paolo Bonzini  <bonzini@gnu.org>:
7863	congratulations for your sharp eye!!)
7864
78651999-01-11  Paolo Bonzini  <bonzini@gnu.org>
7866
7867	* lib/dict.c: Yeah! Removed bitfields from InstanceSpec!!
7868	* lib/dict.h: Yeah! Removed bitfields from InstanceSpec!!
7869	* lib/dict.inl: Yeah! Removed bitfields from InstanceSpec!!
7870	* lib/gst.h: Yeah! Removed bitfields from InstanceSpec!!
7871	* lib/prims.inl: Yeah! Removed bitfields from InstanceSpec!!
7872
78731999-01-10  Paolo Bonzini  <bonzini@gnu.org>
7874
7875	* lib/interp.c: Good!!  First change in 1999!!  Optimized out send to
7876	super.  I renamed sendMessage to sendMessageInternal
7877	and created two macros (sendMessage and sendToSuper)
7878	in interp.inl
7879	* lib/interp.h: Good!!  First change in 1999!!  Optimized out send to
7880	super.  I renamed sendMessage to sendMessageInternal
7881	and created two macros (sendMessage and sendToSuper)
7882	in interp.inl
7883	* lib/interp.inl: Good!!  First change in 1999!!  Optimized out send to
7884	super.  I renamed sendMessage to sendMessageInternal
7885	in interp.c and created two macros (sendMessage and
7886	sendToSuper) here.
7887
78881998-12-09  Paolo Bonzini  <bonzini@gnu.org>
7889
7890	* lib/cint.c: Added my_stat for portability
7891	* lib/oop.c: Moved the code to nil out weak references *before*
7892	sweeping is done.  This is needed so that finalize
7893	methods which refer to weak objects already see nils.
7894
78951998-12-03  Paolo Bonzini  <bonzini@gnu.org>
7896
7897	* lib/prims.inl: Added ability to create subclasses of CompiledMethod
7898	(for now, cannot add instance variables)
7899
79001998-11-28  Paolo Bonzini  <bonzini@gnu.org>
7901
7902	* lib/comp.c: The method cache was not properly updated: test is
7903	1 to: 5 do: [ :i | Object compile: 'foo ^',
7904	i printString. (nil foo) printNl]
7905	Now I'm using invalidateMethodCache instead of updateMethodCache
7906	(see interp.c).
7907	* lib/interp.c: fix: Since updateMethodCache did not always work
7908	I replaced it with invalidateMethodCache, which is not as gentle but
7909	works (anyway compiles are not so frequent and it takes nothing to
7910	rebuild a good cache).  Also, thisContext's ip and sp (in sendMessage
7911	and sendBlockValue) are now updated *after* thisContextOOP is set to
7912	the newly created context.  The previous implementation caused mess if
7913	allocFakeContext() triggered a GC.
7914
79151998-11-27  Paolo Bonzini  <bonzini@gnu.org>
7916
7917	* lib/dict.c: Added the Table class variable to Character.
7918	* lib/gst.h: Added finalization.
7919	* lib/oop.c: Added finalization.  Also added lastUsedOOP which
7920	is used to shorten the loops on the OOP table at GC
7921	time It was needed because the OOP table was scanned
7922	three times: once to mark dependents of finalizable
7923	objects, once to reverse pointers (prepareForSweep),
7924	once to scan for objects to be finalized.  Now the
7925	whole GC is on average 50% faster than it used to be
7926	BEFORE having to add all these cycles.
7927	* lib/oop.inl: Created
7928	* lib/prims.inl: Added finalization primitives 256-257
7929	* lib/sym.c: Added finalizeSymbol.
7930	* lib/sym.h: Added finalizeSymbol
7931
79321998-11-26  Paolo Bonzini  <bonzini@gnu.org>
7933
7934	* lib/interp.inl: Created
7935
79361998-11-25  Paolo Bonzini  <bonzini@gnu.org>
7937
7938	* lib/dict.c: Moved many routines to dict.inl for speed.  Changed
7939	BlockClosure to a byte-subclass to save eight bytes.
7940	* lib/dict.h: Moved most things to gst.h, added dict.inl
7941	* lib/dict.inl: Created
7942	* lib/interp.c: Added primitive 104 (String hash function), inlined
7943	many things around.
7944	* lib/oop.c: Changed the way the marking system works.  Instead of
7945	two entry points (markAnOOP and markOOPRange) both
7946	relying on markAnOOPInternal and passing parameters
7947	to it through the copy stack, I have two macros
7948	(maybeMarkOOP and markOOPRange) which pass parameters
7949	to markAnOOPInternal through function arguments.
7950	markAnOOPInternal does its job calling itself
7951	recursively, doing everything on the stack without
7952	expensive mallocs.  This makes the code neater, since
7953	the whole marking system resides in a single function.
7954	* lib/prims.inl: Created from interp.c
7955	* lib/sym.c: Modified hashString to be more effective.
7956
79571998-11-24  Paolo Bonzini  <bonzini@gnu.org>
7958
7959	* lib/lib.c: Added ContextPart.st, changed to try loading .stinit
7960	and .stpre from the current directory if the HOME
7961	environment variable is not found (fix for Win32).
7962
79631998-11-11  Paolo Bonzini  <bonzini@gnu.org>
7964
7965	* lib/interp.c: Fixed bug in asObject primitive.  Was erroneously
7966	using oopAt(arg1-1) instead of oopAt(arg1).
7967
79681998-11-10  Paolo Bonzini  <bonzini@gnu.org>
7969
7970	* lib/lex.c: Fixed so that _ *inside* an identifier is OK.
7971
79721998-11-08  Paolo Bonzini  <bonzini@gnu.org>
7973
7974	* lib/byte.c: Added notNilSymbol and isNilSymbol.
7975	* lib/byte.h: Added notNilSymbol and isNilSymbol
7976	* lib/interp.c: Fixed bugs in returnWithValue (they had been there
7977	since 18 Oct...): contexts were returned to the free
7978	fake list even if they were not fake anymore (which
7979	happened if you did a snapshot).  Sooner or later, a
7980	normal object contended the same heap space with these
7981	contexts, wreaking havoc on the image. Also turned
7982	noParentContext to a macro and added notNil/isNil as
7983	bytecodes 206 and 207; these are optimized out to gain
7984	speed in some operations (e.g. Sets and Dictionaries).
7985	* lib/save.c: Added notNilSymbol and isNilSymbol
7986	* lib/sym.c: Added notNilSymbol and isNilSymbol.
7987	* lib/sym.h: Added notNilSymbol and isNilSymbol
7988
79891998-11-01  Paolo Bonzini  <bonzini@gnu.org>
7990
7991	* lib/callin.c: Added vmsgSend.  Moved mstMalloc and mstGetCData here.
7992
79931998-10-26  Paolo Bonzini  <bonzini@gnu.org>
7994
7995	* lib/gstpub.h: Added vmsgSend.
7996
79971998-10-18  Paolo Bonzini  <bonzini@gnu.org>
7998
7999	* lib/interp.c: Changed fake OOPs so that they have entries in the
8000	real OOP table.  This allows me to never realize
8001	the fake contexts unless a snapshot is being done.
8002	Less GC = more speed!!
8003	* lib/oop.c: Fake OOPs are now in the main OOP table.  Changed
8004	setOOPObject to a macro for SPEED!!
8005	* lib/oop.h: Added freeOOP(), realizeAllOOPs()
8006
80071998-10-16  Paolo Bonzini  <bonzini@gnu.org>
8008
8009	* lib/cint.c: Added stringOut return type (frees string)
8010
80111998-10-15  Paolo Bonzini  <bonzini@gnu.org>
8012
8013	* lib/interp.c: Added type 9 for CObjects and Memory (smalltalk OOP)
8014
80151998-10-12  Paolo Bonzini  <bonzini@gnu.org>
8016
8017	* lib/dict.c: Added BlockClosure.  Changed BlockContext to reflect
8018	new architecture.  Changed Float to a variable
8019	byte class.
8020	* lib/interp.c: Added support for blocks as closures (partly I wrote
8021	it, part I stole it from Steve Byrne  <sbb@gnu.org>'s never made public
8022	1.1.6 version).  Started adding support for fake
8023	block contexts (see 1   Jan  91)
8024
80251998-10-10  Paolo Bonzini  <bonzini@gnu.org>
8026
8027	* lib/interp.c: Added support for read-only objects (prims 233-234)
8028
80291998-09-26  Paolo Bonzini  <bonzini@gnu.org>
8030
8031	* lib/dict.c: Fixed allocCObject.  Added IdentitySet.
8032
80331998-09-25  Paolo Bonzini  <bonzini@gnu.org>
8034
8035	* lib/interp.c: Added a few register clauses.  Also changed
8036	implementation of "send ==" so it doesn't actually do
8037	the message sends, since == should not be overridden.
8038	* lib/lib.c: Added ValueAdapt.st, File.st, Directory.st,
8039	IdentitySet.st
8040	* lib/oop.c: Added a free list to OOP table.  This yielded, in
8041	general, good performance boosts, up to ten-fold for
8042	snippets that heavily allocate objects!! (on average,
8043	the number of bytecodes per second doubled)
8044	* lib/oop.h: Added refreshOOPFreeList(), to be used by save.c
8045
80461998-09-18  Paolo Bonzini  <bonzini@gnu.org>
8047
8048	* lib/gst.h: Started adding support for read-only objects.
8049	* lib/interp.c: Removed last vestiges of previous garbage
8050	collectors. Removing loops that were not optimized
8051	out by compilers caused a 30% performance increase
8052	(not joking!).  Y2K change...  Time>>secondClock was
8053	about to overflow.  Also fixed sendBlockValue to
8054	check argument count.
8055	* lib/oop.c: Removed all vestiges of previous GC algorithms.
8056	This was a pity because it was really instructive
8057	but I was not able to read anything before ;-).
8058	* lib/oop.h: Fixed incubator bug (incAddOOP not in braces),
8059	removed maybeMoveOOP and localMaybeMoveOOP.
8060
80611998-09-10  Paolo Bonzini  <bonzini@gnu.org>
8062
8063	* lib/dict.c: Added LargeIntegers and Fractions.  Tried to make
8064	nilFill faster.
8065	* lib/lib.c: Added LargeInteger.st, removed changes.st since its
8066	changes are incorporated in Fraction.st
8067
80681998-09-09  Paolo Bonzini  <bonzini@gnu.org>
8069
8070	* lib/interp.c: Started adding support for LargeIntegers!!!
8071
80721998-09-07  Paolo Bonzini  <bonzini@gnu.org>
8073
8074	* lib/interp.c: Added Behavior>>#flushCache (primitive 89,
8075	as in the Blue Book).  Added bounds checking to	spaceGrowRate:
8076	(between 0 and 500)
8077
80781998-09-06  Paolo Bonzini  <bonzini@gnu.org>
8079
8080	* lib/interp.c: FileStream>>nextPutAll: Primitive was giving access
8081	violations (!) if Integers were passed... definitely
8082	too greedy!  I've updated the Smalltalk code too, so
8083	that it handles the case, but anyway now the primitive
8084	fails.  On 3 Sep 98 I had broken Floats; fixed.
8085
80861998-09-03  Paolo Bonzini  <bonzini@gnu.org>
8087
8088	* lib/dict.c: Added extensions to Date, modified Collection and
8089	SequenceableCollection so they are not indexable.
8090	Removed LookupKey.
8091	* lib/interp.c: Switched to openFile; corrected bug in floating point
8092	arithmetic primitives which never failed.  basicPrint
8093	doesn't output new-line.  Also corrected so that,
8094	when aborting execution, dead contexts are ignored
8095	and don't cause "Block returning to non-existent
8096	method context" errors.
8097	* lib/lib.c: Modified to use openFile, added a few loaded modules.
8098
80991998-09-02  Paolo Bonzini  <bonzini@gnu.org>
8100
8101	*** Began development of version 1.6
8102	* lib/save.c: Switched to using openFile to open files
8103	* lib/sysdep.c: Added openFile, support for Cygnus Win32 added. A
8104	note on this is important.  Reluctantly I used Win32
8105	functions here and there.  I was not happy about that,
8106	but since it's the only way to do some things in
8107	an environment that does not fully comply to POSIX,
8108	I had to.
8109
81101995-12-16  Steve Byrne  <sbb@gnu.org>
8111
8112	* lib/comp.c: Changed name to blockCopyColonTemporariesColonSymbol.
8113	* lib/sym.c: Changed name to blockCopyColonTemporariesColonSymbol.
8114	* lib/sym.h: Changed name to blockCopyColonTemporariesColonSymbol.
8115
81161995-11-04  Steve Byrne  <sbb@gnu.org>
8117
8118	* lib/oop.c: Fixed allocObj to have what I think is the *right*
8119	algorithm -- simple, grows when needed.
8120
81211995-11-02  Steve Byrne  <sbb@gnu.org>
8122
8123	* lib/oop.c: Fixed allocObj to properly grow when not enough
8124	space is required, and to terminate if the allocation
8125	cannot succeed.
8126
81271995-10-15  Steve Byrne  <sbb@gnu.org>
8128
8129	* lib/byte.h: Added pushOuterTempVariable and storeOuterTempVariable
8130	byte codes.
8131	* lib/sym.c: Converted to the new architecture; introduced the
8132	notion of scopes.
8133	* lib/sym.h: Converted to new architecture; introduced the notion
8134	of scopes.
8135
81361995-10-14  Steve Byrne  <sbb@gnu.org>
8137
8138	* lib/gst.y: Began adding block temporary syntax.
8139	* lib/tree.c: Added support for block node type for new
8140	architecture.
8141	* lib/tree.h: Added block node type for new architecture support.
8142
81431995-09-30  Steve Byrne  <sbb@gnu.org>
8144
8145	*** Version 1.1.5 released.
8146
81471995-09-16  Steve Byrne  <sbb@gnu.org>
8148
8149	* lib/interp.c: Moved lots of system dependent functions out to
8150	sysdep.
8151	* lib/sysdep.h: Added openPipe, closePipe, getOpenFileSize.
8152
81531995-09-10  Steve Byrne  <sbb@gnu.org>
8154
8155	* lib/interp.c: Switched to fileIsReadable sysdep routine.
8156	* lib/lib.c: Added -g command line flag to suppress printing of
8157	GC messages.
8158	* lib/oop.c: Added GC torture test.  Heh heh heh!
8159	* lib/sym.c: Added incubator usage.
8160	* lib/sysdep.c: Added fileIsReadable, also setSignalHandler, and
8161	initSysdep.
8162
81631995-09-09  Steve Byrne  <sbb@gnu.org>
8164
8165	* lib/callin.c: Added incubator usage.
8166	* lib/cint.c: Added incubator support for created objects.
8167	* lib/cint.c: Removed Sun Windows hacks from the file.
8168	* lib/interp.c: Added code to use the object incubator support.
8169	* lib/interp.c: Experimentally tried to next jmp_bufs so enable proper
8170	handling of reentering the interpreter from C callout
8171	code and then calling out to more C code.
8172
81731995-09-08  Steve Byrne  <sbb@gnu.org>
8174
8175	* lib/dict.c: Added incubator support for newly created objects.
8176
81771995-09-07  Steve Byrne  <sbb@gnu.org>
8178
8179	* lib/comp.c: Added usage of OOP incubator.
8180	* lib/oop.c: Added incubator support.
8181	* lib/oop.h: Added incubator support.
8182
81831995-08-30  Steve Byrne  <sbb@gnu.org>
8184
8185	* lib/gst.h: Merged in Visual C++ changes.
8186	* lib/oop.c: Merged NT changes back in.  Code now contains some
8187	unnecessary casting and unrolled expressions (*=
8188	becomes = *) to shut the Visual C++ compiler's
8189	warnings off.
8190
81911995-08-26  Steve Byrne  <sbb@gnu.org>
8192
8193	* lib/comp.c: Merged Brad Diller's changes for dealing with parsing
8194	specially in the browser.
8195	* lib/dict.c: Added kernel and image file paths as Smalltalk
8196	accessible variables.
8197	* lib/lib.h: Added kernelFileDefaultPath and imageFileDefaultPath
8198	as exported symbols.
8199	* lib/sysdep.c: Fixed to have the __cursigmask definition be
8200	conditional on HAVE_SIGHOLD.
8201
82021995-08-20  Steve Byrne  <sbb@gnu.org>
8203
8204	* lib/oop.c: Added growMemoryTo(); it's a variant of growTo which
8205	does not involve the garbage collector.
8206	* lib/oop.c: Fixed alignSize to not double align (we don't
8207	preserve that property during GC anymore anyway,
8208	and the floating point accessing functions in dict.c
8209	which were the initial reason for having it are now
8210	sensitive to whether aligned access to doubles is
8211	required by the hardware or not.
8212	* lib/oop.h: Added growMemoryTo().
8213	* lib/save.c: Switched to using growMemoryTo in loadFromFile so
8214	that if the saved image space is larger than the
8215	normal memory space, the space is grown to fit.
8216
82171995-07-26  Steve Byrne  <sbb@gnu.org>
8218
8219	* lib/cint.c: Fixed the makeDescriptor function to issue an error if
8220	it cannot find a named C function.  Already located
8221	some bugs in UnixStream.st which have been there
8222	since it's inception.
8223
82241995-07-23  Steve Byrne  <sbb@gnu.org>
8225
8226	* lib/comp.c: Removed apostrophes in comments -- OS/2 doesnt
8227	like them (incredible!).
8228	* lib/dict.c: Added CIntSize so that C struct can understand
8229	int size.
8230	* lib/gst.h: Removed mstconfig.h!!! Code is now not conditional
8231	on the presence of config.h.
8232	* lib/interp.c: Merged in OS/2 diffs, and removed apostrophes from
8233	preprocessed-out code (OS/2's preprocessor doesn't
8234	understand backslash quoting.
8235	* lib/oop.c: Fixed #ifdefed out code to not have apostrophes
8236	(OS/2 doesn't understand).
8237	* lib/save.c: Removed extra stdio.h include
8238
82391995-07-13  Steve Byrne  <sbb@gnu.org>
8240
8241	* lib/comp.c: Removed HAVE_ALLOCA_H.
8242	* lib/save.c: Removed HAVE_ALLOCA_H include of alloca.h (done in
8243	gst.h now).
8244	* lib/sym.c: Removed HAVE_ALLOCA_H.
8245
82461995-07-11  Steve Byrne  <sbb@gnu.org>
8247
8248	* lib/cint.c: Added John Stanhope (jehu@vt.edu)'s changes for
8249	Objective-C calling (Thanks John!!!)
8250	* lib/gstpub.h: Added defineCFunc.
8251	* lib/save.c: Added John Stanhope (jehu@vt.edu)'s changes for
8252	Objective-C calling (Thanks John!!!)
8253	* lib/sym.c: Added John Stanhope (jehu@vt.edu)'s changes for
8254	Objective-C calling (Thanks John!!!)
8255	* lib/sym.h: Added John Stanhope (jehu@vt.edu)'s changes for
8256	Objective-C calling (Thanks John!!!)
8257
82581995-07-09  Steve Byrne  <sbb@gnu.org>
8259
8260	* lib/byte.c: Fixed to include proper headers.
8261	* lib/callin.c: Fixed to include correct header files.
8262	* lib/comp.c: Fixed to include proper headers and have explicit
8263	declarations.
8264	* lib/dict.c: Fixed to explictly declare functions and include
8265	proper files.
8266	* lib/interp.c: Fixed to have explicit function declarations and
8267	correct include files.
8268	* lib/lex.c: Fixed to include proper headers and have functions
8269	declared explictly.
8270	* lib/oop.h: Added lots of new externs.
8271	* lib/save.c: Fixed to have proper inclues and explicit function
8272	declarations.
8273	* lib/tree.c: Fixed to include correct files.
8274
82751995-07-08  Steve Byrne  <sbb@gnu.org>
8276
8277	* lib/lib.c: Fixed a bunch of declarations and includes so that
8278	functions are now explictly declared always.
8279
82801995-06-29  Steve Byrne  <sbb@gnu.org>
8281
8282	* lib/sym.c: Fixed pool dictionary allocation to not allocate a
8283	large number of immediately thrown away arrays.
8284
82851995-06-26  Steve Byrne  <sbb@gnu.org>
8286
8287	* lib/gst.h: Switched EMPTY_BYTES to be 8 byte into the word
8288	instead of the low bytes to make the low bytes unused
8289	for use with the mark/sweep GC.
8290
82911995-06-23  Steve Byrne  <sbb@gnu.org>
8292
8293	* lib/cint.h: Switched guard prefix to GST
8294	* lib/comp.h: Switched to GST guard prefix
8295	* lib/dict.h: Switched to GST guard prefix
8296	* lib/gst.h: Switched to GST header guard.
8297	* lib/gstpaths.h: Switched to GST header guard prefix.
8298	* lib/gstpub.h: Switched to GST header guard prefix.
8299	* lib/id.h: Switched to GST header guard prefix.
8300	* lib/interp.h: Switched to GST header guard prefix.
8301	* lib/lex.h: Switched to GST header guard prefix.
8302	* lib/lib.h: Switched to GST header guard prefix.
8303	* lib/oop.h: Switched to GST header guard prefix.
8304	* lib/save.h: Switched to GST header guard prefix.
8305	* lib/str.h: Switched to GST header guard prefix.
8306	* lib/sym.h: Switched to GST header guard prefix.
8307	* lib/sysdep.h: Switched to GST header guard prefix.
8308	* lib/tree.h: Switched to GST header guard prefix.
8309
83101995-06-15  Brad Diller  <bdiller@docent.com>
8311
8312	* lib/comp.c: Modified executeStatements() to support browser
8313	expression evaluation.  Added getByteCodeForSpecialSelector() to
8314	support some browser operations.
8315	* lib/comp.c: Store in memory the source code derived from .st
8316	files loaded outside the kernel directory.
8317	* lib/comp.h: Added getByteCodeForSpecialSelector() to support some
8318	browser operations.
8319	* lib/lex.c: Added isKernelFile() and getMethodSourceFromCurFile().
8320	These routines were provided to solve certain data
8321	integrity problem caused by accessing the source code
8322	indirectly from saved file information.
8323	* lib/lex.h: Added isKernelFile() and getMethodSourceFromCurFile().
8324
83251995-06-09  Steve Byrne  <sbb@gnu.org>
8326
8327	* lib/oop.c: Began switching to compacting mark & sweep gc.
8328	* lib/oop.h: Began the conversion to single GC space.
8329
83301995-06-06  Steve Byrne  <sbb@gnu.org>
8331
8332	* lib/byte.c: Switched to new file naming scheme.
8333	* lib/callin.c: Switched to new file naming scheme.
8334	* lib/cfuncs.c: Switched to new file naming scheme.
8335	* lib/cint.c: Switched to new file naming scheme.
8336	* lib/comp.c: Switched to new naming scheme.
8337	* lib/comp.h: Switched to new file naming scheme.
8338	* lib/dict.c: Switched to new file naming scheme.
8339	* lib/gstpub.h: Switched to new file naming scheme.
8340	* lib/id.c: Switched to new file naming scheme.
8341	* lib/interp.c: Switched to new file naming scheme.
8342	* lib/lex.c: Switched to new file naming scheme.
8343	* lib/lib.c: Switched to new naming scheme.
8344	* lib/lib.h: Switched to new file naming scheme.
8345	* lib/oop.c: Switched to new file naming scheme.
8346	* lib/save.c: Switched to new file naming scheme.
8347	* lib/str.c: Switched to new file naming scheme.
8348	* lib/sym.c: Switched to new file naming scheme.
8349	* lib/sysdep.c: Switched to new file naming scheme.
8350	* lib/tree.c: Switched to new file naming scheme.
8351
83521995-06-05  Steve Byrne  <sbb@gnu.org>
8353
8354	* lib/mstpub.h: Merged in Brad Diller's changes.
8355
83561995-05-31  Steve Byrne  <sbb@gnu.org>
8357
8358	* lib/mstcint.c: Fixed cFuncInfo to grow dynamically.
8359	* lib/mst.h: Boolean replaced with mst_Boolean, objectClass =>
8360	mst_objectClass, Object => gst_object.  This thanks
8361	to the foresightful guys at the X consortium.
8362	Thanks guys for wantonly chewing up name space.
8363	* lib/mst.h: Removed the old sysVersionMajor etc definitions --
8364	they are now defined in configure.in.
8365
83661995-05-30  Steve Byrne  <sbb@gnu.org>
8367
8368	* lib/mstcomp.c: Replaced objectClass with mst_objectClass.  Boolean =>
8369	mst_Boolean.
8370	* lib/mstcomp.h: Boolean switched to mst_Boolean.
8371	* lib/mstdict.c: Replaced objectClass with mst_objectClass to avoid
8372	conflicts with X (grrr!).  Boolean replaced with
8373	mst_Boolean.  Object replaced with gst_object.
8374	* lib/mstdict.h: Replaced objectClass with mst_objectClass to avoid
8375	conflicts with X.  Boolean => mst_Boolean. Object =>
8376	gst_object.
8377	* lib/mstinterp.c: Replaced objectClass with mst_objectClass.  Boolean =>
8378	mst_Boolean.
8379	* lib/mstinterp.h: Boolean => mst_Boolean.
8380	* lib/mstlex.c: Boolean => mst_Boolean.
8381	* lib/mstlex.h: Boolean => mst_Boolean (darn X!).
8382	* lib/mstlib.c: Boolean => mst_Boolean.
8383	* lib/mstlib.h: Boolean renamed to mst_Boolean.
8384	* lib/mstoop.c: Boolean => mst_Boolean.
8385	* lib/mstoop.h: Boolean => mst_Boolean.  Object => gst_object.
8386	* lib/mstsave.c: Boolean => mst_Boolean.  Object => gst_object.
8387	* lib/mstsave.h: Boolean => mst_Boolean.
8388	* lib/mstsym.c: Boolean => mst_Boolean.
8389	* lib/msttree.h: Boolean => mst_Boolean.
8390
83911995-05-28  Steve Byrne  <sbb@gnu.org>
8392
8393	* lib/mstdict.c: Finally hacked floatNew to deal properly on
8394	architectures where double alignment requirements
8395	are different from those of long.
8396	* lib/mstsysdep.c: Added getdtablesize for those systems such as HP
8397	which do not have this useful function.
8398	* lib/mstsysdep.c: Fixed getCurDirName to selectively use getwd or getcwd
8399	depending on what is supported.
8400
84011995-05-15  Brad Diller  <bdiller@docent.com>
8402
8403	* lib/mstinterp.c: Added primitives 256-264 to support expression
8404	evaluation and other functions for the class browser.
8405
84061995-05-07  Steve Byrne  <sbb@gnu.org>
8407
8408	* lib/mstdict.c: Added more machine specific datatype constants (size
8409	and alignment).
8410	* lib/msttree.h: Removed trailing comma from NodeType enum literals
8411	list -- some compilers are picky.
8412
84131995-04-29  Steve Byrne  <sbb@gnu.org>
8414
8415	* lib/mstdict.c: Added CDoubleAlignment as a 'global' value for the
8416	required alignment of C type 'double'.
8417	* lib/mstlib.c: Moved CType to after CObject in the load order to
8418	better reflect the type (and symbol definition)
8419	dependencies.
8420
84211995-03-31  Steve Byrne  <sbb@gnu.org>
8422
8423	* lib/mstcomp.c: Compiler now uses the initEmptyBytes macro to set
8424	the empty bytes of the byte code length of a method.
8425	* lib/mst.h: Adjusted EMPTY_BYTES related constants to vary with
8426	hardware architecture.
8427	* lib/mstinterp.c: Fixed branching backward to use signed arithmetic it
8428	was doing the computation as unsigned ints without
8429	sign extension when it was added ot a 64 bit pointer.
8430	* lib/mstoop.c: Added fflush(stdout) to some debugging funcs
8431	* lib/mstsym.c: Adjusted a reference to the empty bytes to use the
8432	new, architecture independent macro definitions.
8433
84341995-03-19  Brad Diller  <bdiller@docent.com>
8435
8436	* lib/mstcint.c: Conditionally enable GC of Smalltalk objects
8437	referenced in callouts.
8438
84391995-03-15  Brad Diller  <bdiller@docent.com>
8440
8441	* lib/mstdict.c: Added mstMalloc mstGetCData.
8442
84431995-03-01  Steve Byrne  <sbb@gnu.org>
8444
8445	* lib/mstcomp.c: Fixed makeConstantOOP to handle NIL which is passed
8446	in from empty array literals.
8447
84481995-01-21  Steve Byrne  <sbb@gnu.org>
8449
8450	* lib/mstlex.c: Some changes for architectural independence (64 bit).
8451
84521995-01-20  Steve Byrne  <sbb@gnu.org>
8453
8454	* lib/mstdict.h: Added 64 bit support.
8455	* lib/mst.h: More changes for DEC Alpha 64bit architecture.
8456	* lib/mstinterp.c: Adjusted for DEC Alpha 64bit architecture.
8457	* lib/mstinterp.h: Added padding for 64bit architectures.
8458
84591995-01-14  Steve Byrne  <sbb@gnu.org>
8460
8461	* cxtnsn/dld.c: Changed the name from DLD to USE_DLD to avoid
8462	conflicts with symbols defined by the DLD package in the future.
8463
84641995-01-05  Steve Byrne  <sbb@gnu.org>
8465
8466	* lib/mstinterp.c: Fixed a bug when copying a fake method context
8467	(ip wasn't being updated, and so was pointing to
8468	dead storage).
8469
84701995-01-02  Steve Byrne  <sbb@gnu.org>
8471
8472	* lib/mstdict.c: Fixed CType to use the new type model.
8473	* lib/mstdict.h: Switched to the new CType model.
8474	* lib/mstinterp.c: Removed primitives 147 & 148 -- they were obsolete
8475	anyway, and now with the new CType model they no
8476	longer function.
8477
84781994-12-03  Steve Byrne  <sbb@gnu.org>
8479
8480	* lib/mstinterp.c: Added code stubs for asCData: Primitives.
8481
84821994-11-16  Steve Byrne  <sbb@gnu.org>
8483
8484	* lib/mstinterp.c: Finally tracked down some problems with prims 183-185
8485	-- they were using the wrong variable to access the
8486	contents of the cobject, and it was just luck that
8487	it worked on Linux.
8488
84891994-10-08  Steve Byrne  <sbb@gnu.org>
8490
8491	* lib/mstcomp.c: Fixed some bugs related to getting a GC during
8492	compilation (literals during compilation are part of
8493	the root set, etc.).
8494	* lib/mstinterp.c: Added SystemDictionary>>growTo: And moved a few
8495	builtins around.
8496	* lib/mstsym.c: Fixed the internCountedString bug by deferring OOP
8497	allocation until all instances have ben allocated.
8498
84991994-10-02  Steve Byrne  <sbb@gnu.org>
8500
8501	* lib/mstoop.c: Made sure to turn off the free bit in moveOOP (no
8502	sense in moving an object that's freed, and moveOOP
8503	will not be called on a truly freed object; this
8504	change "repairs the damage" in cases where there is
8505	an accidental freeing occurring.
8506	* lib/mstsym.c: Fixed a bug in internCountedString that occurs other
8507	places where there is the possibility of doing a
8508	garbage collection just after a newly allocated object
8509	which has not been added to a root-set-reachable
8510	object.  The GC sees that there are no references
8511	to the new object, and marks its oop free and does
8512	not copy the just allocated object into the new
8513	current semispace.  This problem can occur anywhere
8514	these conditions occur.  Given that allocOOP moves the
8515	object to the current space if it's not already there,
8516	for this case to really occur, you have to have done
8517	the allocOOP before you call the second instantiate
8518	or other allocation primitive.
8519
85201994-09-20  Steve Byrne  <sbb@gnu.org>
8521
8522	* lib/mstinterp.c: Added empty statement to the tail of a case statement.
8523
85241994-09-15  Steve Byrne  <sbb@gnu.org>
8525
8526	*** Version 1.2.alpha1 released.
8527
85281994-09-04  Steve Byrne  <sbb@gnu.org>
8529
8530	* lib/mstcomp.c: Fixed some of the printing at the end of
8531	executeStatements to avoid dividing by zero.
8532	* lib/mstdict.c: Switched out last bzero call.
8533	* lib/mst.h: More changes -- removed some old bcopy macro
8534	definitions, and switched more towards the autoconf
8535	based implementation.
8536
85371994-09-03  Steve Byrne  <sbb@gnu.org>
8538
8539	* lib/cfuncs.c: Created.
8540	* lib/cfuncs.c: This is the first file in the distribution to not
8541	start with "mst".  This is the precursor to having
8542	short file names so that primitive operating systems
8543	can deal with an advanced system like Smalltalk :-) :-) :-).
8544	* lib/mstcint.c: Factored out initUserCFuncs to enable easier extension
8545	by developers.
8546	* lib/mstcint.c: Yanked out DLD -- it's now in the parent directory.
8547	* lib/mst.h: Switched double size out, switched to use RETSIGTYPE,
8548	and WORDS_BIGENDIAN.
8549	* lib/mst.h: Switched to having version defines coming from the
8550	config.h file, and added the edit prefix string.
8551
85521994-08-31  Steve Byrne  <sbb@gnu.org>
8553
8554	* lib/mst.h: Began switching to autoconf based approach.
8555
85561994-08-24  Steve Byrne  <sbb@gnu.org>
8557
8558	* lib/mst.h: Added symbolic constants for max and min integer
8559	values representable in a Smalltalk Integer object.
8560	* lib/mstinterp.c: Fixed Float>>truncated to do range checking and fail
8561	if converting a number that is outside the range
8562	of integers.
8563
85641994-08-21  Steve Byrne  <sbb@gnu.org>
8565
8566	* lib/mstcomp.h: Switched to using low bit int marking.
8567	* lib/mstdict.h: Switched to low order bit for int flagging.
8568	* lib/mst.h: Switched to low order bit for int flagging.
8569
85701994-07-10  Steve Byrne  <sbb@gnu.org>
8571
8572	* lib/mstlex.c: Reinstated the use of changes (it was dyked out)
8573	as an optional mechanism.
8574
85751994-07-09  Steve Byrne  <sbb@gnu.org>
8576
8577	* lib/mstdict.c: Fixed findKey to check all elements even when the
8578	dictionary is full.  Previously it would check all but
8579	the last one, which caused some bizarre compilation
8580	behavior (the last class declared didn't seem to be
8581	there as far as the compiler was concerned).
8582
85831994-06-22  Steve Byrne  <sbb@gnu.org>
8584
8585	* lib/mstcint.c: Added support for cObjectPtr type, to allow for
8586	passing CObject parameters by reference.  It is up
8587	to the client to ensure that the passed CObject type
8588	corresponds to the desired C datatype.
8589
85901994-06-20  Steve Byrne  <sbb@gnu.org>
8591
8592	* lib/mstcint.c: Fixed stringInfo to be local to the call stack,
8593	instead of using a static, to allow recursive
8594	invocations.
8595
85961994-06-11  Steve Byrne  <sbb@gnu.org>
8597
8598	* lib/mstinterp.c: Added new-style CObject accessors functions, currently
8599	in the range 182 -- 189.
8600	* lib/mstsym.c: Added cObjectPtrSymbol for new call by value parameter
8601	passing mode.
8602	* lib/mstsym.h: Added cObjectPtrSymbol.
8603
86041994-04-30  Steve Byrne  <sbb@gnu.org>
8605
8606	* lib/mstinterp.c: Added CPtr incrBy:
8607
86081994-03-19  Steve Byrne  <sbb@gnu.org>
8609
8610	* lib/mstcallin.c: Added %t and %T for more direct control over
8611	types. Also, added typeNameToOOP for mapping string
8612	type names to actual CType subclass instances.
8613
86141993-10-16  Steve Byrne  <sbb@gnu.org>
8615
8616	* lib/mstinterp.h: Changed to have 9 priority levels, as part of the
8617	fix for ProcessorScheduler>>yield.
8618
86191993-10-10  Steve Byrne  <sbb@gnu.org>
8620
8621	* lib/mstinterp.c: Doing some experimental hacks on the process system
8622	to try to recover from the case where there are no
8623	runnable processes.
8624	* lib/mstinterp.h: Fixed definition of initProcessSystem.
8625
86261993-04-04  Steve Byrne  <sbb@gnu.org>
8627
8628	* lib/mstdict.c: Made printAssociationKey more bullet-proof when passed
8629	a non-association.
8630
86311992-11-22  Steve Byrne  <sbb@gnu.org>
8632
8633	* lib/mstdict.c: Added isPipe member to FileStream.
8634	* lib/mstinterp.c: Fixed FileStream to have a buffer instance variable,
8635	and added knowledge of whether the file stream was
8636	a regular file or a pipe, so FileStream>>close could
8637	do the right thing.
8638
86391992-07-18  Steve Byrne  <sbb@gnu.org>
8640
8641	* lib/mstdict.c: Added byteArrayNew.
8642	* lib/mstdict.c: Added countedStringNew.
8643
86441992-07-16  Steve Byrne  <sbb@gnu.org>
8645
8646	* lib/mstdict.c: Added freeCObject.
8647
86481992-05-25  Steve Byrne  <sbb@gnu.org>
8649
8650	* lib/mstdict.c: Added support for Emacs caching class names.
8651	* lib/mstinterp.c: Made system interruptable when non-interactive
8652	(interrupts work, that is).
8653
86541992-02-23  Steve Byrne  <sbb@gnu.org>
8655
8656	* lib/mstcint.c: Added support for reading and writing scalar types.
8657
86581992-01-01  Steve Byrne  <sbb@gnu.org>
8659
8660	* lib/mstcallin.c: Fixed to auto-initialize Smalltalk when the public
8661	routines are invoked.
8662	* lib/mstpub.h: Created.
8663	* lib/mstlib.c: Converted to be callable as a library.
8664	* lib/mstlib.h: Renamed from mstmain.h
8665	* main.c: Created from old mstmain.c (now mstlib.c)
8666
86671991-12-31  Steve Byrne  <sbb@gnu.org>
8668
8669	* mstcallin.c: Created.
8670	* mstcallin.h: Created.
8671	* mstlex.c: Began adding support for having a changes file and
8672	pointing methods to that instead of the actual source
8673	file (which can get out of sync, and cause recompiles
8674	to lose).
8675	* mstoop.c: Added registered oops to root set.
8676	* mstoop.c: OopTable now allocated from memory instead of being
8677	stored as part of the executable.
8678
86791991-12-29  Steve Byrne  <sbb@gnu.org>
8680
8681	* mstlex.c: Added support for readline's conditional .inputrc
8682	definitions, keyed off of "Smalltalk".
8683
86841991-12-22  P. Lecoanet
8685
8686	* mstbyte.c: Fixed byteCodeLength failing to return 0
8687
86881991-12-08  Steve Byrne  <sbb@gnu.org>
8689
8690	* mstoop.c: Changed oopValid to only check the FREE bit, instead
8691	of worrying about the even odd flags, which may not
8692	be valid.
8693
86941991-11-29  Steve Byrne  <sbb@gnu.org>
8695
8696	* mstlex.c: Added fileNameOOP to hold full path name for files,
8697	so that all methods share the same file name string.
8698	Also, adjusted getCurFileName to return the full
8699	path name.
8700
87011991-11-28  Steve Byrne  <sbb@gnu.org>
8702
8703	* mstinterp.c: Added SystemDictionary byteCodeCounter primitive.
8704	* mstsysdep.c: Added getCurDirName() for allowing compiler to record
8705	the full file name that is used.
8706
87071991-11-24  Steve Byrne  <sbb@gnu.org>
8708
8709	* mstinterp.h: Context size increased to 64 (still not enough),
8710	to prevent inadvertent stomping of memory past the
8711	end of the stack.
8712
87131991-11-09  Steve Byrne  <sbb@gnu.org>
8714
8715	* mstinterp.c: Fixed new: To indicate failure when failure occurs.
8716
87171991-11-02  Steve Byrne  <sbb@gnu.org>
8718
8719	* mstinterp.c: Altered the logic in the primitive replace from code
8720	-- I don't think it was really wrong, but it wasn't
8721	as clear as it might have been.
8722	* mstinterp.c: Fixed instVarAt: To obey real stack conventions
8723	(was pushing instead of setting the stack top).
8724
87251991-10-20  Steve Byrne  <sbb@gnu.org>
8726
8727	* mstinterp.c: Added support for user level control of memory space
8728	growth rate parameters.
8729	* mstoop.c: Support for growing now fully operational (and no,
8730	it hasn't taken me over a month to track down the
8731	problems; free time has been nil).  Also removed more
8732	vestiges of the incremental GC.
8733
87341991-09-15  Steve Byrne  <sbb@gnu.org>
8735
8736	* mstdict.c: Fixed dictionaryAssociationAt: To not loop when the
8737	dictionary is full.  Thanks to Michael Richardson
8738	for the fix!
8739	* mstinterp.c: Added quitPrimitive: To allow for non-zero exit
8740	statuses.
8741	* mstoop.c: Added support for loading larger semispaces from
8742	saved images.
8743
87441991-09-14  Steve Byrne  <sbb@gnu.org>
8745
8746	* mstdict.c: Switched to global version string.
8747	* mst.h: Added edit version support.
8748	* mstinterp.h: Increased number of literals to 256, number of
8749	temporaries to 64, and number of allowable primitives
8750	to 1024 (overkill?)
8751	* mstmain.c: Added edit version support.
8752	* mstmain.h: Added edit version support.
8753	* mstsave.c: Added support for edit version.
8754
87551991-09-12  Steve Byrne  <sbb@gnu.org>
8756
8757	* mstmain.c: Fixed -I argument parsing code to properly gobble up
8758	the file name.
8759
87601991-08-04  Steve Byrne  <sbb@gnu.org>
8761
8762	* mstoop.c: Removed more vestiges of the incremental GC, began
8763	switchover to automatically growing semi-spaces.
8764
87651991-07-19  Steve Byrne  <sbb@gnu.org>
8766
8767	* mstcint.c: Started adding support for the DLD package.
8768	* mstmain.c: Started adding conditional support for the DLD
8769	package.
8770
87711991-07-06  Steve Byrne  <sbb@gnu.org>
8772
8773	* mstdict.c: Added newString (create uninitialized string of a
8774	given length).
8775
87761991-07-05  Steve Byrne  <sbb@gnu.org>
8777
8778	* mstinterp.c: Added primitive 248: `FileStream fileInLine: LineNum
8779	fileName: aString at: charPosInt'; this helps improve
8780	things for the emacs interface by making recorded
8781	information accurate, and making error locations also
8782	be accurate.
8783	* mstinterp.c: Added support for primitive 105, which is the basic
8784	fast support for doing replacement within strings.
8785	* mstlex.c: Added setStreamInfo so that stuff filed in from Emacs
8786	can have more accurate information such as the line
8787	number in the buffer instead of the line number in
8788	the temporary file.
8789
87901991-07-02  Steve Byrne  <sbb@gnu.org>
8791
8792	* mstinterp.c: Fixed handling of jump true and jump false opcodes:
8793	they now issue an error if invoked with non trueOOP
8794	or falseOOP.
8795
87961991-04-19  Steve Byrne  <sbb@gnu.org>
8797
8798	* mstcomp.c: Added skipCompilation boolean, for conditional
8799	compilation.
8800	* mstinterp.c: Added primitive to support conditional compilation.
8801
88021991-04-13  Steve Byrne  <sbb@gnu.org>
8803
8804	* mstdict.c: Added Features global variable.  This allows for
8805	conditional execution based on operating system or
8806	machine architecture, and at some point, conditional
8807	compilation.
8808
88091991-03-25  Steve Byrne  <sbb@gnu.org>
8810
8811	* mstlex.c: Added -> operator.
8812
88131991-03-24  Steve Byrne  <sbb@gnu.org>
8814
8815	* mstdict.c: Float's class definition said that it was not
8816	pointers, not words, and not indexable.  When new
8817	instances were created, they were 2 BYTES large,
8818	instead of 2 words.  Changed to have the words flag
8819	* mstlex.c: Fixed lexing of foo:= to be seen as foo :=.
8820	* mstmain.c: Added loading of changes.st
8821
88221991-03-23  Steve Byrne  <sbb@gnu.org>
8823
8824	* mstinterp.c: Fixed a bug with process switching: You can't depend
8825	on objects gotten with oopToObj after a prepareToStore
8826	into the parent object: it may have moved, and you're
8827	storing into dead storage.
8828	* mstinterp.c: Improved speed another 50% by "inlining" many of the
8829	special selectors that the compiler uses.
8830
88311991-03-17  Steve Byrne  <sbb@gnu.org>
8832
8833	* mstinterp.c: Added support for C-style interrupts (signals) and
8834	timed interrupts to help with time slicing.
8835
88361991-02-16  Steve Byrne  <sbb@gnu.org>
8837
8838	* mstcomp.c: Recursive calls to equalConstant had the arguments
8839	reversed.
8840
88411991-01-27  Steve Byrne  <sbb@gnu.org>
8842
8843	* mstinterp.c: Modified the definition of the inline-controlling
8844	macro so that inlining is always selected when compiling for
8845	debugging.
8846	* mstoop.h: Force ACCESSOR_DEBUGGING off when optimizing.
8847
88481991-01-22  Steve Byrne  <sbb@gnu.org>
8849
8850	* mstcint.c: Added putenv().
8851
88521991-01-05  Steve Byrne  <sbb@gnu.org>
8853
8854	* mstinterp.c: Converted executePrimitiveOperation to do returns as
8855	soon as possible, to not use the failed variable,
8856	and to not do double switching on int and float
8857	operations.  This simple change increased performance
8858	from ~130K bytecodes/sec (SS1+ optim) to > 200k
8859	bytecodes/sec (simple code, builtins and primitives
8860	only, no real method invocation).
8861	* mstsysdep.c: Added getMilliTime().
8862
88631991-01-01  Steve Byrne  <sbb@gnu.org>
8864
8865	* mstinterp.c: Switched to not creating MethodContexts always...just
8866	use a cache of pre-made fake method contexts and only
8867	create real method contexts when someone will get a
8868	reference to one of the method contexts.
8869
88701990-11-26  Steve Byrne  <sbb@gnu.org>
8871
8872	* mstcomp.c: Fixed whileTrue: and whileFalse: To loop only if the
8873	value returned by the receiver is the expected one,
8874	instead of if it's the boolean not of the expected
8875	value.
8876
88771990-11-24  Steve Byrne  <sbb@gnu.org>
8878
8879	* mstmain.c: Fixed to set quietExecution using || instead of |
8880	(HP doesn't like it otherwise).
8881
88821990-11-17  Steve Byrne  <sbb@gnu.org>
8883
8884	* mstcint.c: Added support for UnixStream primitives.
8885	* mstmain.c: Added UnixStream and IOCtl to kernel files.
8886
88871990-11-10  Steve Byrne  <sbb@gnu.org>
8888
8889	* mstcomp.c: Added support for retaining the latest compiled method
8890	so the interpreter can return it from the compile:
8891	primitive.
8892	* mstcomp.h: Added latestCompiledMethod, so that some of the
8893	compile methods can get the method that they just
8894	compiled and set its category.
8895
88961990-11-06  Steve Byrne  <sbb@gnu.org>
8897
8898	* mstmain.c: Added the per-user pre-image file...this may turn
8899	into a kind of site defaults thing, but this is what
8900	I've wanted for a while.
8901
89021990-10-13  Steve Byrne  <sbb@gnu.org>
8903
8904	* mstoop.c: Converted to use bit masks instead of bit fields,
8905	hoping to improve performance somewhat.
8906
89071990-10-02  Steve Byrne  <sbb@gnu.org>
8908
8909	* mstmain.c: Fixed okToLoadBinary so that it returns false if
8910	there is a Smalltalk file found locally, but there
8911	is no image file locally (the stix problem).
8912	* mstmain.h: FindImageFile was changed to return Boolean.
8913
89141990-09-21  Steve Byrne  <sbb@gnu.org>
8915
8916	* mstcomp.c: Fixed so that a block that contains no statements
8917	properly returns nil.
8918
89191990-08-21  Steve Byrne  <sbb@gnu.org>
8920
8921	* mstinterp.c: Added support for subtypes of CObject to provide
8922	direct access to C data.
8923
89241990-08-11  Steve Byrne  <sbb@gnu.org>
8925
8926	* mstcint.c: Added knowledge of byteArrayOut type.
8927
89281990-08-03  Steve Byrne  <sbb@gnu.org>
8929
8930	* mstdict.c: Added allocCObject.
8931	* mstinterp.c: Added support for primitive C object allocation
8932	routine.
8933
89341990-05-22  Steve Byrne  <sbb@gnu.org>
8935
8936	*** Version 1.1.1 released (I think. I added this on May 10th, 1999... --- pb)
8937	* mstmain.c: Improved on Doug's mapping with macro to improve
8938	readability.
8939	* mstmain.c: Short name stuff added, thanks to Doug McCallum.
8940
89411990-05-20  Steve Byrne  <sbb@gnu.org>
8942
8943	* mstcomp.c: Improved error handling...compiler errors set a flag,
8944	and execution does not occur if the expression to be
8945	executed has compilation errors.
8946	* mstinterp.c: Improved error handling when error: Or
8947	doesNotUnderstand: occurs.  Also, added ^C handling
8948	to abort execution.
8949
89501990-05-17  Steve Byrne  <sbb@gnu.org>
8951
8952	* mstsysdep.c: Added enableInterrupts and disableInterrupts.
8953	System V.3 code signal support from Doug McCallum
8954	(thanks, Doug!).
8955
89561990-05-16  Steve Byrne  <sbb@gnu.org>
8957
8958	* mstcomp.c: Added usage of emacsProcess.
8959	* mstsym.c: Changed usages of "entry" to "ent" to prevent
8960	collisions with C compilers which have this identifier
8961	as a reserved word.
8962	* mstsysdep.c: Created.
8963	* mstsysdep.h: Created.
8964
89651990-04-24  Steve Byrne  <sbb@gnu.org>
8966
8967	* mstinterp.c: Improved error handling for fopen/popen primitives.
8968	* mstlex.c: Error checking for integers too large.
8969
89701990-04-21  Steve Byrne  <sbb@gnu.org>
8971
8972	* mstdict.c: Added toByteArray.
8973	* mstsym.c: Addded byteArraySymbol.
8974
89751990-04-20  Steve Byrne  <sbb@gnu.org>
8976
8977	* mstbyte.c: Added initByteCodes to fix a robustness issue with
8978	the compiler.
8979	* mstcomp.c: Fixed compiler to reset the byte code system before
8980	using it.  The problem was if an error occurred, the
8981	old byte code stream was still in use, and further
8982	compilations were losing in a big way.
8983	* mstinterp.c: Make fileIn not close the stream that it's reading
8984	from; this is taken care of by the caller, and causes
8985	very strange behavior if we try to close it twice!
8986	* mstlex.c: Added the closeIt argument to popStream so that the
8987	closing behavior could be separated from the popping
8988	behavior (in particular, for fileIn).
8989
89901990-04-17  Steve Byrne  <sbb@gnu.org>
8991
8992	* mstsave.c: Fixing binary save to save only to the maximum used
8993	OOP slot, instead of saving the entire OOP table. This
8994	should improve load time and decrease disk storage
8995	requirements.
8996
89971990-04-08  Steve Byrne  <sbb@gnu.org>
8998
8999	* mstoop.c: Changed oopFree to oopValid to fix the bug with
9000	someInstance losing after GC's due to objects that
9001	have non-free OOP table entries, but point to freed
9002	objects.
9003	* mstoop.h: Changed oopFree to oopValid to better reflect the
9004	semantics.
9005
90061990-04-07  Steve Byrne  <sbb@gnu.org>
9007
9008	* mstinterp.c: Added declaration tracing primitive.
9009	* mstinterp.c: Fixed fileIn: To check for existence of the file
9010	before trying to open it.  Returns failure if the
9011	file cannot be accessed.
9012	* mstlex.c: Character lexing routines (such as nextChar) now
9013	return ints to get around problems on implementations
9014	that don't sign extend characters by default.
9015	* mstoop.c: Increased mem space size to 4M.  This can be decreased
9016	as necessary.
9017
90181990-03-25  Steve Byrne  <sbb@gnu.org>
9019
9020	* mstcomp.c: Changed cache hit ratio reporting to check for divide
9021	by zero, and to cast the byte counter to double
9022	(it was casting to float and relying on promotion).
9023	* mstinterp.c: Minor change for AtariSt: Decrease size of ASYNC
9024	queue size.
9025	* mstmain.c: ProcessorScheduler is too long of a name for the
9026	Atari; there are uniqueness problems.  Shortened to
9027	ProcScheduler.  Also, fixed quietExecution; wasn't
9028	set when reading from the terminal; should have been
9029	set to false (since the loading of the quiet things
9030	is over).
9031
90321990-02-24  Steve Byrne  <sbb@gnu.org>
9033
9034	* mstoop.c: Update to change log: There are no longer any
9035	explicitly allocated OOPs due to the new symbol table
9036	structure; the September 20th, 1989 comment below is now a noop.
9037
90381990-02-15  Steve Byrne  <sbb@gnu.org>
9039
9040	* mstlex.c: Added support for := as alternative assignment
9041	operator.
9042
90431990-02-11  Steve Byrne  <sbb@gnu.org>
9044
9045	* mstsave.c: Changed the header to record the size of the oop
9046	table, since trying to load back into a system with
9047	a different sized oop table loses bigtime.
9048
90491990-01-13  Steve Byrne  <sbb@gnu.org>
9050
9051	* mstcomp.c: Added support for "thisContext" as a compiler built-in
9052	variable.
9053	* mstsym.c: Added thisContextSymbol.
9054	* mstsym.h: Added thisContextSymbol.
9055
90561990-01-07  Steve Byrne  <sbb@gnu.org>
9057
9058	* mstdict.c: Added more commentary to classes, added new global
9059	Smalltalk variable: Bigendian, which allows code to
9060	be conditional based on the architecture type.
9061
90621989-12-28  Steve Byrne  <sbb@gnu.org>
9063
9064	* mstcomp.c: Compiled methods now record their exact number of
9065	byte codes.  Previously, if the byte codes didn't
9066	exactly fill to a word-boundary, there was no way
9067	to distinguish that case.  Now, with the advent of
9068	dumping byte codes from within Smalltalk, this has
9069	become a necessity.
9070
90711989-12-27  Steve Byrne  <sbb@gnu.org>
9072
9073	* mstcomp.c: Realloc literal vec wasn't reallocing in units of
9074	sizeof(OOP), so after a while, the literal vector
9075	wasn't big enough.  Typically most methods don't have
9076	a lot of literals, so this was not a problem.
9077
90781989-12-19  Steve Byrne  <sbb@gnu.org>
9079
9080	* mstinterp.c: Added suport for primitive filein (for use with
9081	autoload -- "12 gauge autoloader", A. Swartzenegger,
9082	The Terminator)
9083	* mstsym.c: Rebuilt symbol table.  Used to use the main OOP table
9084	as a symbol table, due to issues involving initial
9085	bootstrapping of the system.  Now using open hash
9086	table built of arrays and linked lists, so that no
9087	special precautions need be taken by the GC system
9088	or the image save/restore facility.
9089
90901989-10-15  Steve Byrne  <sbb@gnu.org>
9091
9092	* mstpaths.h: Created.
9093	* mstmain.c: Added support for creating an "installed" version
9094	of Smalltalk.  There is now an include file that the
9095	installer can customize for his site that provides
9096	default locations to be checked for the kernel .st
9097	files and the binary image file, but these can be
9098	overidden in two ways: a) by a file of the same name
9099	in the user's current directory, or b) environment
9100	variables SMALLTALK_KERNEL and SMALLTALK_IMAGE.
9101
91021989-10-02  Steve Byrne  <sbb@gnu.org>
9103
9104	* mstcomp.c: Fixed a bug with compilation of cascaded messages. see
9105	HACK ALERT in the file.
9106
91071989-09-23  Steve Byrne  <sbb@gnu.org>
9108
9109	* mst.h: Modifications to support operation on a DECstation 3100.
9110
91111989-09-21  Steve Byrne  <sbb@gnu.org>
9112
9113	* mstcomp.c: Made compilation of methods from strings record the
9114	source string.
9115
91161989-09-20  Steve Byrne  <sbb@gnu.org>
9117
9118	* mstoop.c: Added oop table slot GC'ing.  I'm not dealing with oop
9119	table slots that are explictly allocated; I believe
9120	that most OOP slots are not explicitly chosen and so
9121	not running the incremental reclaimer for that case
9122	shouldn't hurt us.
9123
91241989-09-13  Steve Byrne  <sbb@gnu.org>
9125
9126	* mstcomp.c: Various changes for garbage collector.
9127	* mst.h: Sigh!!! modified pushOOP and setStackTop to move
9128	the objects that they refer to to toSpace...good
9129	bye performance!
9130
91311989-09-12  Steve Byrne  <sbb@gnu.org>
9132
9133	* mstoop.c: Much of the garbage collector's operation depends on
9134	the fact that only 1 flip will occur between any two
9135	operations (such as a compilation, or a byte-code).
9136	The code would be much more complex if this were not
9137	the case, and I'm not sure that things would even be
9138	possible if this were not the case.  Anyway, there
9139	is code in this routine to check for that eventuality
9140	and to halt the system if it occurs.
9141
91421989-09-07  Steve Byrne  <sbb@gnu.org>
9143
9144	* mstdict.c: Started adding garbage collection support.
9145
91461989-09-06  Steve Byrne  <sbb@gnu.org>
9147
9148	* mstoop.c: Started implementing the garbage collector (YAY!!!)
9149
91501989-09-03  Steve Byrne  <sbb@gnu.org>
9151
9152	* mstlex.c: Added getCurFileName
9153	* mstlex.h: Added getCurFileName
9154
91551989-09-02  Steve Byrne  <sbb@gnu.org>
9156
9157	* mstcomp.c: Began adding support for the method descriptor
9158	instance variable.
9159	* mstcomp.h: Moved common compiled method structure definition
9160	here, so that the interpeter could share.
9161	* mstcomp.h: Added descriptor support
9162	* mstinterp.c: Process primitives in and working...starting to switch
9163	to compiled methods with descriptor instance variable
9164	in addition to header.
9165
91661989-08-30  Steve Byrne  <sbb@gnu.org>
9167
9168	* mstlex.c: Fixed a bug in parseIdent which was parsing foo:2 note
9169	no space) not as foo: and 2, but as a mixed up token.
9170
91711989-08-09  Steve Byrne  <sbb@gnu.org>
9172
9173	* mstinterp.c: Conversion completed.  Performance now 40k
9174	bytecodes/sec; was 43k bytecodes/sec.
9175
91761989-07-25  Steve Byrne  <sbb@gnu.org>
9177
9178	* mstsym.c: Changed undeclareName to take a parameter that
9179	controls whether the frame index is decremented
9180	or not.  It appears that each block gets its own,
9181	non-shared temporaries/arguments, so that if the
9182	block is used in a process, other blocks won't have
9183	strange things happening to their arguments.
9184
91851989-07-18  Steve Byrne  <sbb@gnu.org>
9186
9187	* mstinterp.c: Began conversion from stack based method contexts and
9188	blocks to more traditional method contexts and blocks.
9189	This change was done 1) to make call in from C easier,
9190	2) to make processs possible (they could have been
9191	implemented using stack based contexts, but somewhat
9192	space-wastefully), and 3) to conform with the more
9193	traditional definition of method contexts and block
9194	contexts.
9195
91961989-07-08  Steve Byrne  <sbb@gnu.org>
9197
9198	* mstlex.c: Added prompt when input is a terminal.  This should
9199	help Emacs's shell mode determine what has been typed
9200	as input to the system.
9201
92021989-07-04  Steve Byrne  <sbb@gnu.org>
9203
9204	* mstmain.c: Added support for user init files (in ~/.stinit),
9205	which are invoked on every startup.  Also, added
9206	support for initBlocks, which are blocks that are
9207	stored in the system and invoked on each startup
9208	(these could be used, for example, as an interim
9209	measure for declaring C callouts until the callout
9210	descriptor is converted to a Smalltalk object).
9211
92121989-06-04  Steve Byrne  <sbb@gnu.org>
9213
9214	* mstcint.c: Added Smalltalk data conversion type.
9215
92161989-05-29  Steve Byrne  <sbb@gnu.org>
9217
9218	* mstcint.c: Created.
9219	* mstcint.h: Created.
9220	* mstdict.c: Added the memory classes.  Added the FileStream about
9221	a week ago.
9222
92231989-05-26  Steve Byrne  <sbb@gnu.org>
9224
9225	* mstinterp.c: Added method cache!  Why didn't I spend the 1/2
9226	hour sooner?
9227
92281989-05-14  Steve Byrne  <sbb@gnu.org>
9229
9230	* mstlex.h: Created.
9231
92321989-04-29  Steve Byrne  <sbb@gnu.org>
9233
9234	* mstdict.c: Author changed from single to married.
9235
92361989-04-05  Steve Byrne  <sbb@gnu.org>
9237
9238	* mstdict.c: Restructured Class and Metaclass creation.  Is now
9239	table driven, and metaclasses are created containing
9240	the proper information.
9241	* mstsave.c: Modified to reflect change in classes: Now their name
9242	is a Smalltalk string; before, it was a C string that
9243	had to be saved specially.
9244
92451989-03-29  Steve Byrne  <sbb@gnu.org>
9246
9247	* mstdict.c: Removed MethodDictionary as a separate type; it is
9248	an IdentityDictionary.
9249
92501989-03-11  Steve Byrne  <sbb@gnu.org>
9251
9252	* mstdict.c: Smalltalk is now an instance of SystemDictionary.
9253
92541989-03-10  Steve Byrne  <sbb@gnu.org>
9255
9256	* mstmain.c: Added support for automatically loading image file
9257	if it's newer than and of the system source files.
9258
92591989-03-04  Steve Byrne  <sbb@gnu.org>
9260
9261	* mstmain.h: Created.
9262	* mstsave.c: Created.
9263	* mstsave.h: Created.
9264
92651989-01-24  Steve Byrne  <sbb@gnu.org>
9266
9267	* mstlex.c: Added 2 chars of push back, because 3. needs to look
9268	ahead one more character to see if its 3.DIGIT or
9269	3. next statement.
9270
92711989-01-13  Steve Byrne  <sbb@gnu.org>
9272
9273	* mstdict.c: Created.
9274	* mstdict.h: Created.
9275	* mstoop.c: Created.
9276	* mstoop.h: Created.
9277
92781989-01-07  Steve Byrne  <sbb@gnu.org>
9279
9280	* mstinterp.c: Created.
9281	* mstinterp.h: Created.
9282
92831989-01-05  Steve Byrne  <sbb@gnu.org>
9284
9285	* mstsym.c: Created.
9286
92871989-01-02  Steve Byrne  <sbb@gnu.org>
9288
9289	* mstbyte.h: Created.
9290
92911989-01-01  Steve Byrne  <sbb@gnu.org>
9292
9293	* mstcomp.c: Created.
9294	* mstcomp.h: Created.
9295	* mstsym.h: Created.
9296
92971988-12-30  Steve Byrne  <sbb@gnu.org>
9298
9299	* msttree.c: Created.
9300	* msttree.h: Created.
9301
93021988-12-29  Steve Byrne  <sbb@gnu.org>
9303
9304	* mst.h: Created.
9305
93061988-12-27  Steve Byrne  <sbb@gnu.org>
9307
9308	* mstbyte.c: Created.
9309	* mstid.c: Created.
9310	* mstid.h: Created.
9311	* mstlex.c: Created.
9312	* mstmain.c: Created.
9313	* mststr.c: Created.
9314	* mststr.h: Created.
9315
9316
9317