ftp.nice.ch/pub/next/developer/languages/smalltalk/smalltalk.1.2.alpha5.s.tar.gz#/smalltalk-1.2.alpha5

Array.st
 
ArrayColl.st
 
Association.st
 
Autoload.st
 
Bag.st
 
Behavior.st
 
BlkContext.st
 
Boolean.st
 
Browser.st
 
BypassStream.st
 
ByteArray.st
 
ByteMemory.st
 
CDeclNode.st
 
CExpressionNode.st
 
CFuncs.st
 
COPYING
 
CObject.st
 
CPP.st
 
CPStrConc.st
 
CPStrUnq.st
 
CParseType.st
 
CStruct.st
 
CSymbol.st
 
CSymbolTable.st
 
CTok.st
 
CToken.st
 
CTreeBuilder.st
 
CType.st
 
CTypeParser.st
 
ChangeLog
 
Character.st
 
Class.st
 
ClassDescr.st
 
Collection.st
 
CompildMeth.st
 
CompilerTokens.st
 
DLD.st
 
Date.st
 
Debugger.st
 
Delay.st
 
Dictionary.st
 
ExpansionStream.st
 
ExpansionStreamStack.st
 
False.st
 
FileSegment.st
 
FileStream.st
 
Float.st
 
Fraction.st
 
Host.st
 
INSTALL
 
IOCtl.st
 
IdentDict.st
 
IndentedStream.st
 
Integer.st
 
Interval.st
 
LineStream.st
 
LineToTokenStream.st
 
LineTokenStream.st
 
Link.st
 
LinkedList.st
 
LookupKey.st
 
Magnitude.st
 
Makefile
 
Makefile.defs
 
Makefile.defs.in
 
Makefile.in
 
Makefile.rules
 
MappedColl.st
 
Memory.st
 
Message.st
 
Metaclass.st
 
MethodInfo.st
 
MthContext.st
 
Number.st
 
Object.st
 
OrderColl.st
 
ParseNodes.st
 
Parser.st
 
Point.st
 
PosStream.st
 
ProcSched.st
 
Process.st
 
PushBackStream.st
 
README
 
README-1.2
 
README-1.2.alpha5
 
README.DOS
 
RParseNodes.st
 
RWStream.st
 
Random.st
 
ReadStream.st
 
Rectangle.st
 
STCompLit.st
 
STCompiler.st
 
STSymTable.st
 
STVarDefn.st
 
Semaphore.st
 
SeqCollect.st
 
Set.st
 
SharedQueue.st
 
SortCollect.st
 
Stream.st
 
StreamStack.st
 
String.st
 
SymLink.st
 
Symbol.st
 
SysDict.st
 
Time.st
 
Token.st
 
TokenStream.st
 
True.st
 
UndefObject.st
 
UnixStream.st
 
Variable.st
 
WordMemory.st
 
WriteStream.st
 
acconfig.h
[View acconfig.h] 
bison.el
 
blox/
 
browse.el
 
buildgst.bat
 
builtins.st
 
cfuncs.c
[View cfuncs.c] 
changes.st
 
config.cache
 
config.h
[View config.h] 
config.h.in
 
config.log
 
config.status
 
configure
 
configure.in
 
contrib/
 
cpt.st
 
createMake
 
cxtnsn/
 
dev-t.st
 
dldtst.st
 
eval.st
 
examples/
 
fileout-ps.st
 
getcppsyms.c
[View getcppsyms.c] 
hilit-st.el
 
info/
 
initialize.st
 
install-sh
 
int.st
 
it.st
 
large-expr.st
 
lib/
 
main.c
[View main.c] 
mkinstalldirs
 
mt.st
 
mt2.st
 
objc/
 
st-changelog.el
 
st.el
 
stamp-h
 
stamp-h.in
 
stix/
 
t.st
 
tcp/
 
tdl.st
 
test/
 
testCPT.st
 
testXParse.st
 
testcompile.st
 
tok.st
 
tpars.st
 
tstCPT.st
 
tstdl2.st
 

README

GNU Smalltalk version 1.2
by Steve Byrne

*** NOTE
*** THIS DOCUMENT IS OUT OF DATE FOR 1.2  
*** SEE README-1.2 FOR A QUICK INTRO TO 1.2 FEATURES  


The files in this directory and its subdirectories constitute the complete
source code for GNU Smalltalk.  The files are organized as follows:

.		The source files, both .st (Smalltalk) and C files
config		Various supported platforms
contrib		Contributed software
examples	Some working example Smalltalk files
test		Regression testing files
stix		SmallTalk Interface to X

About GNU Smalltalk

GNU Smalltalk attempts to be a reasonably faithful implementation of
Smalltalk-80 {tm ParcPlace Systems} as described in the "Blue Book", also known
as "Smalltalk-80: the Language and its Implementation", by Adele Goldberg and
David Robson.  The syntax that the language accepts and the byte codes that the
virtual machine interprets are exactly as they appear in the Blue Book.  Most
of the primitives are the same as well, although due to the differing nature of
the implementation some of the primitives haven't been implemented, and other
new ones have been.


The current implementation has the following features:

  * Incremental garbage collector
  * Binary image save capability
  * C-callout (allows Smalltalk to invoke user-written C code and pass
    parameters to it)
  * GNU Emacs editing mode
  * Highly portable C code implementation
  * Optional byte code compilation tracing and byte code execution tracing
  * Automatically loaded per-user initialization files



Installing GNU Smalltalk

Please see the file mst.texinfo which contains the information on how to 
install GNU Smalltalk, and general documentation about the features of
the system.


Bugs

To report bugs or suggestions (or even offer assistance :-) ), send mail
to bug-gnu-smalltalk@prep.ai.mit.edu.  If there is sufficient traffic, I
will set up a gnu.smalltalk newsgroup as well.

README-1.2

Brief overview of new features with version 1.2:

Emacs editing
  * bugs fixed
  * many Smalltalk mode commands are now available in the Smalltalk "shell"
    mode 
  * new browser mode
    once Smalltalk is built, you can invoke the browser from a Smalltalk mode
    buffer by doing C-C C-B C-H (Browse Hierarchy).  Commands in first window
    are:
        space (browse all instance methods)
        d     (browse direct methods),
	i     (browse indirect only methods),
	c     (browse class methods (all)).
    From the generated method browser window, use space to select the
    definition of the particular method, move to a different line, hit space
    again to see that method's definition, etc.
    The key bindings are likely to change to get more regular with time, and
    there may be a way to see the class definition.
  * C-c C-s shows all classes where the selector that's under the cursor is
    defined, type a space to jump to the definition in the chosen class.
  * Do c-c c-b c-o to load class names, then
       c-c c-b c-d browses direct methods of a class (reads class name with
		   completion)
       c-c c-b c-i browses indirect methods
       c-c c-b c-c browses class methods
  * C-c c-t defines a map which toggles various tracing facilities in the
	    running Smalltalk:
	      c-d    for declaration tracing
	      c-e    for execution tracing
	      c-v    for verbose executation tracing

  * there are probably other undiscovered treasures waiting to be found in the
    emacs editing mode.  c-c d is your friend!!!

Initialization files
  * $HOME/.stpre is loaded before building the basic mst.im image
  * $HOME/.stinit is loaded each time smalltalk starts up, whether or not
    it build the saved mst.im image during the run, and is loaded after the
    binary image has been saved.
  

Sun examples

C Pointer hacking
  * provides direct access to C data structures including
    o  long (unsigned too)
    o  short (unsigned too)
    o  char (unsigned too) & byte type 
    o  float (and double)
    o  string (NUL terminated sequence of char * )
    o  arrays of any type
    o  pointers to any type (I'm not happy with the  semantics of this; it's
       likely to change)
    o  structs containing any fixed size types
       
    Example struct decl in C:  (see sun/Sound.st for example usage)

	struct audio_prinfo {
		unsigned	channels;
		unsigned	precision;
		unsigned	encoding;

		unsigned	gain;
		unsigned	port;
		unsigned	_xxx[4];

		unsigned	samples;
		unsigned	eof;
		unsigned char	pause;
		unsigned char	error;
		unsigned char	waiting;
		unsigned char	_ccc[3];

		unsigned char	open;
		unsigned char	active;
	};

	struct audio_info {
		audio_prinfo_t	play;
		audio_prinfo_t	record;
		unsigned	monitor_gain;
		unsigned	_yyy[4];
	};

    Equivalent in Smalltalk:
	CStruct newStruct: #AudioPrinfo
		declaration: #((sampleRate uLong)
				   (channels uLong)
				   (precision uLong)
				   (encoding uLong)
				   (gain uLong)
				   (port uLong)
				   (xxx (array uLong 4))
				   (samples uLong)
				   (eof uLong)
				   (pause uChar)
				   (error uChar)
				   (waiting uChar)
				   (ccc (array uChar 3))
				   (open uChar)
				   (active uChar))
	!

	CStruct newStruct: #AudioInfo
		declaration: #((play AudioPrinfo)
				   (record AudioPrinfo)
				   (monitorGain uLong)
				   (yyy (array uLong 4))
				   )
	!
			   


C Callin
  * needs no explicit initialization 
  * can initialize with command line arguments if desired (so as to control
    when the smalltalk initialization occurs)
  * smalltalk need not be main 

Stix
  * Provides full access to X protocol
  * doesn't currently have support for resources
  * ICCCM support not working yet
  * See stix/README

Dynamic Linking
  * based on the GNU DLD library
  * allows Smalltalk to dynamically load and reference C code
  * Has an example of use at the bottom

README-1.2.alpha5

$Revision: 1.3 $
Dear Alpha People:

Here is the Alpha 5 release.  It contains:

* Brad Diller's GUI Based Browser (finally).  See the README in blox for
  details on how to run it.  This looks, acts, etc. like the traditional
  Smalltalk class browser.  Brad has done a tremendous job, both in the actual
  writing of this code, and taking care of the thousand-and-one detail with
  ensuring that it can be released without complications.  Congratulations
  Brad!!! 

* WindowNT/Visual C++  port now available: smalltalk-nt-1.2.alpha5.tar.gz
  Be sure to untar it onto a file system which understands long file names
  (i.e. not a regular DOS file system).

* Optimization via the --with-optimize flag to configure.  Once you've
  configured optimization on, compiles from then on will use the -O flag and
  define the OPTIMIZE preprocessor symbol

* The system has compiled on OS/2 -- I haven't integrated the makefile changes
  completely yet back into the source base.

* Most of the system dependencies have been moved into sysdep.c.

* Calling #new: on a non-indexable array now generates an error; sending  #new
  to an indexable array now generates an error

* I believe indexing outside of the bounds of an array now causes an error

* defining a C function which has not been registered via defineCFunc now
  prints a warning message.

* the .info file is now part of the distribution -- you no longer need to run
  makeinfo to get it.

* added the -g flag to suppress GC flip messages.

* lots of clean up to the make files

* uses the Makefiles.defs/Makefiles.rules to factor out the common parts of
  Makefiles, and puts Makefile.body in the subdirectories which just contains
  the subdirectory specific targets.

* makeinfo is not required -- system should deal gracefully if makeinfo is not
  present. 

* added extra X location configure functionality; previously, it wasn't finding
  some of the X includes on Solaris.

* configure now understands -enable-gc-torture. This causes the
  garbage collector to run with *each* allocation of storage.

* if you use the GC torture (using the --enable-gc-torture config operation,
  you can arrange for the GC torturing to run only for a given range of code.
  startGCTorture (only defined when GC torturing is present) begins the torture
  test, and stopGCTorture stops it.  Invocations of these functions can be
  nested; the outermost ones dominate.


======================================================================
[Here's the section on the new incubator support from oop.h.

Incubator support.

The incubator concept provides a mechanism to protect newly created
objects from being accidentally garbage collected before they can be
attached to some object which is reachable from the root set.

[It is very likely that this interface will move to gstpub.h as part
of the public interface at some point in the future.]

When to use this interface.
---------------------------

If you are creating some set of objects which will not be immediately (that means, 
before the next object is allocated from the Smalltalk memory system) be
attached to an object which is still "live" (reachable from the root set
of objects), you'll need to use this interface.

The interface provides the following operations:

void     incAddOOP(OOP anOOP)
    Adds a new object to the protected set.

IncPtr   incSavePointer()
    Retrieves the current incubator pointer.  Think of the incubator as a
    stack, and this operation returns the current stack pointer for later
    use (restoration) with the incSetPointer function.

void     incRestoresPointer(IncPtr ptr)
    Sets (restores) the incubator pointer to the given pointer value.

Usage:

Typically, when you are within a function which allocates more than one
object at a time, either directly or indirectly, you'd want to use the 
incubator mechanism.  First you'd save a copy of the current pointer
in a local variable.  Then, for each object you allocate (except the last, 
if you want to be optimal), after you create the object you add it to 
the incubator's list.  When you return, you need to restore the 
incubator's pointer to the value you got with incSavePointer using
the incRestorePointer function.

Here's an example from cint.c:

The old code was (the comments are added for this example):

  desc = (CFuncDescriptor)newInstanceWith(cFuncDescriptorClass, numArgs);
  desc->cFunction = cObjectNew(funcAddr);    // 1
  desc->cFunctionName = stringNew(funcName); // 2
  desc->numFixedArgs = fromInt(numArgs);
  desc->returnType = classifyTypeSymbol(returnTypeOOP, true);
  for (i = 1; i <= numArgs; i++) {
    desc->argTypes[i - 1] = classifyTypeSymbol(arrayAt(argsOOP, i), false);
  }

  return (allocOOP(desc));

"desc" is originally allocated via newInstance with.  At "1", more storage is
allocated, and the garbage collector has the potential to run and free (since
no live object is referring to it) desc's storage.  At "2" another object
is allocated, and again the potential for losing both desc and desc->cFunction
is there if the GC runs (this actually happened!).  

To fix this code to use the incubator, modify it like this:


  OOP     descOOP;
  IncPtr  ptr;


  incPtr = incSavePointer();
  desc = (CFuncDescriptor)newInstanceWith(cFuncDescriptorClass, numArgs);
  descOOP = allocOOP(desc);
  incAddOOP(descOOP);
  
  desc->cFunction = cObjectNew(funcAddr);
  incAddOOP(desc->cFunction);

  desc->cFunctionName = stringNew(funcName); 
  // since none of the rest of the function (or the functions it calls)
  // allocates any storage, we don't have to add desc->cFunctionName
  // to the incubator's set of objects, although we could if we wanted
  // to be completely safe against changes to the implementations of
  // the functions called from this function.

  desc->numFixedArgs = fromInt(numArgs);
  desc->returnType = classifyTypeSymbol(returnTypeOOP, true);
  for (i = 1; i <= numArgs; i++) {
    desc->argTypes[i - 1] = classifyTypeSymbol(arrayAt(argsOOP, i), false);
  }

  incRestorePointer(ptr);
  return (descOOP);


Note that it is permissible for a couple of functions to cooperate with
their use of the incubator.  For example, say function A allocates
some objects, then calls function B which allocates some more objects,
and then control returns to A where it does some more execution with the 
allocated objects.  If B is only called by A, B can leave the management
of the incubator pointer up to A, and just register the objects it
allocates with the incubator.  When A does a incRestorePointer, it automatically
clears out the objects that B has registered from the incubator's set of
objects as well; the incubator doesn't know about functions A & B, so as
far as it is concerned, all of the registered objects were registered from
the same function.

[Implementation note: Macros are only used here for speed, since this is
used in relatively busy code and function call overhead would have
measurable impact on the system's performance.  Three global variables are
used instead of one global struct for similar reasons.]

======================================================================


Next on the agenda:

  Alpha6
  * switch to new context model (another a big size reduction)
  * document new C type model
  
  Alpha7
  * finish DEC Alpha work
  * tcp abstraction 
  * argc smalltalk-accessible and modifyable from Smalltalk
  * need to complete Smalltalk in Smalltalk compiler

  Alpha8
  * port blox to Windows
  * some other Windows hacks.
  * finish updating DLD integration

  Alpha9
  * add long integer support
  * write documentation
  * finish callin interface

Still to do:
* browser
* fix st.el bugs.
* extend test suite

NOTE:  You'll receive 1 warning message when compiling on Solaris (maybe it's
fixed by 2.4 or 2.5) about gettimeofday not being defined.  It's their bug --
their man page says it's defined by sys/time.h, but it's not; in fact, it's not
defined *anywhere* in /usr/include or any of its subdirectories!

NOTE: If you rerun autoconf, you'll see these messages:
    configure.in:98: warning: AC_TRY_RUN called without default to allow cross compiling
    configure.in:122: warning: AC_TRY_RUN called without default to allow cross compiling
    configure.in:123: warning: AC_TRY_RUN called without default to allow cross compiling

These are coming from high level macros within the autoconf system that I don't
seem to be able to override.  They are harmless, according to the autoconf
documentation, so just ignore them.

[Since it's not included in the documentation yet, here's the blurb on the C
data representation stuff again.  In addition:

CObjects holds a pointer to a C type variable.  The variable have been
allocated from Smalltalk by doing "<type> new", where <type> is a CType
subclass instance, or it may have been returned through the C callout mechanism
as a return value.  Thinking about this facet of the implementation (that
CObject point to C objects) tends to confuse me when I'm thinking about having
CObjects which are of type (say) long* ... so I try to think of CObject as just
representing a C data object and not thinking about the implementation.  To
talk about the *type* "long*", you'd create an instance of CPtrCType, since all
CType instances represent C types (not C objects), via

    CPtrCType elementType: CLongType.  "use the existing CLongCType instance"

To allocate one of these C objects, you'd do:

    longPtr _ (CPtrCType elementType: CLongType) new.

Now you have a C variable of type "long*" accessible from longPtr.


CStructs are CType subclasses, because their instances describe C data types.
Right now, you can create a CStruct instance using:

    CStruct newStruct: #AudioPrinfo
	    declaration: #((sampleRate uLong)	    "unsigned long sampleRate;"
			   (channels uLong)         "unsigned long channels;"
			   (precision uLong)        
			   (encoding uLong)
			   (gain uLong)
			   (port uLong)
			   (xxx (array uLong 4))    "unsigned long xxx[4]"
			   (samples uLong)
			   (eof uLong)
			   (pause uChar)            "unsigned char pause"
			   (error uChar)
			   (waiting uChar)
			   (ccc (array uChar 3))
			   (open uChar)
			   (active uChar))
!


This creates a new subclass of CStruct called AudioPrinfo with the given
fields.  For simple scalar types, just list the type name after the variable.
Here's the set of scalars names:

    typeMap at: #long put: #CLongType; 
	    at: #uLong put: #CULongType;
	    at: #char put: #CCharType;
	    at: #uChar put: #CUCharType;
	    at: #short put: #CShortType;
	    at: #uShort put: #CUShortType;
	    at: #float put: #CFloatType;
	    at: #double put: #CDoubleType;
	    at: #string put: #CStringType.

AudioPrinfo has methods defined on it like:

    #sampleRate
    #channels   

etc.  These access the various data members.  The array element accessors (xxx,
ccc) just return a pointer to the array itself.  To have a pointer to a type,
use:

        (example (ptr long))

The objects returned by using the fields are CObjects; there is no implicit
value fetching currently.  For example, suppose you somehow got ahold of an
instance of class AudioPrinfo as described above (the instance is a CObject
subclass and points to a real C structure somewhere).  Let's say you stored
this object in variable "audioInfo".  To get the current gain value, do

    audioInfo gain value

to change the gain value in the structure, do

    audioInfo gain value: 255

The structure member message just answers a CObject instance, so you can hang
onto it to directly refer to that structure member, or you can use the #value
or #value: methods to access or change the value of the member.

Note that this is the same kind of access you get if you use the #addressAt:
method on CStrings or CArrays or CPtrs -- they return a CObject which points
to a C object of the right type and you need to use #value and #value: to
access and modify the actual C variable.
]

Here's a brief tour of the new C data type manipulation system:

CType -- used to represent C data types themselves (no storage, just the type).
There are subclasses called things like C<mumble>CType, one for each of the C
"scalar" types (includes strings, pointers, and arrays).  The instances can
answer their size and alignment.  Their "valueType" is the underlying type of
data.  It's either an integer, which is interpreted by the interpreter as the
scalar type, or the underlying element type, which is another CType subclass
instance. 

To make life easier, there are global variables which hold onto instances of
the basic C scalar types: C<mumble>Type (not C<mumble>*C*Type).  These can be
used whereever a C datatype is used.  If you had an array of strings, the
elements would be CStringType's (a specific instance of a C data type).

CObject is the base class of the instances of C data.  It has a subclass called
CScalar, which has subclasses called C<mumble>.  These subclasses can answer
size and alignment information.  

Scalars fetch their value when sent the #value message, and change their value
when sent the #value: message.

CStrings can be indexed using #at: (with a zero based index, which returns a
Smalltalk Character instance corresponding to the indexed element of the
string.

To change the value at a given index, use #at:put:.

To produce a pointer to a character, use #addressAt:.

To dereference the string (like *(char *)foo), use #deref -- returns an object
of type CChar (not a Character instance).  To replace the first character in
the string, use #deref: and pass in a CChar instance.  These operations aren't
real useful for CStrings, but they are present for completeness and for
symmetry with pointers (after all, you can say "*string" in C and get the first
character of the string, and you can say "*string = 'f').

#+ (integer) returns a CChar object pointing to *integer* bytes from the start
of the string.

#- (intOrPtr) if integer is given, acts like #+. If pointer is given, returns
the difference between the two pointers.

#incr, #decr, #incrBy:, #decrBy: adjusts the string forward, backward by either
1 or by n characters.  Only the pointer to the string is changed; the actual
characters in the string remain untouched.

#replaceWith: aString  replaces the string the instance points to with the new
string.  Actually copies the bytes from the Smalltalk String instance aString
into the C string object, and null terminates.  Be sure that the C string has
enough room!  You can also use a Smalltalk ByteArray as the data source.


CArrays represent an array of some C data.  The underlying element type is
provided by the CType subclass instance associated with the CArray instance.  
They have #at: and #at:put: operations just like Strings. #at: returns a
Smalltalk datatype for the given element of the array (if the element type is a
scalar, otherwise it returns a CObject subclass instance whose type is that of
the element type); #at:put: works similarly.  #addressAt: returns a CObject
subclass instance no matter what, which you then can send #value or or #value:
to get or set its value.  CArray's also support #deref, #+ and #- with
equivalent semantics to CString.

CPtrs work similar to CArrays (as you might expect -- they try to reflect the
kinds of operations you can do to the corresponding C types).  CPtr's also have
#value and #value: which get or change the underlying value that's pointed to.
Like CStrings, they have #incr, #decr, #incrBy: and #decrBy:.  They also have
#+ and #- which do what you'd expect.



To create instances of the CObject subclasses, create or use a CType instance,
and send it the #new message.  Or, have the return type from a C callout
function be the desired CType subclass instance.

Steve
sbb@gnu.ai.mit.edu
<A HREF="http://reality.sgi.com/employees/sbb"> Steve's Home Page </A>
<A HREF="http://reality.sgi.com/employees/sbb/what-now.html"> Smalltalk Alpha
download Page </A>

README.DOS

9 July 1995

This is the first release of GNU Smalltalk which compiles directly on DOS from
the same sources as the regular distribution.

To build the system, you *must* install the distribution into a top level
directory whose name is that of the .tgz or .zip file; i.e. if the file is
gst12a4.tgz then the directory you install into must be c:\gst12a4 (or d: or
whatever).  If you don't do this, the paths in lib\gstpaths.h will be incorrect
and if you run Smalltalk from anywhere other than the main Smalltalk directory,
it will have problems locating the Smalltalk kernel files and the Smalltalk
saved image.

You'll need to have the latest DJGPP compiler installed and operating to build
GNU Smalltalk on DOS.  If you have it installed and working, you should be able
to type:

    buildgst

in the top level Smalltalk directory, and GNU Smalltalk should be build without
errors or warnings.  

Since the system is compiled with DJGPP, the amount of memory that Smalltalk
can use is limited to the amount of physical memory available PLUS the amount
of disk space available in the DJGPP paging area.  I've personally let the
interpreter grow to 14 M using a program specifically designed to test growing
the memory system and the garbage collector; the default memory requirements as
shipped are 1M for the Smalltalk main memory (no semispaces anymore) and some
amount for the OOP table.

These are the contents of the former NiCE NeXT User Group NeXTSTEP/OpenStep software archive, currently hosted by Netfuture.ch.