[pe.cust.sources] Small Littletalk - Part 3 of 5

earlw@pesnta.UUCP (Earl Wallace) (06/12/85)

#! /bin/sh 
#
# This is the Little Smalltalk program that Marc Ries of the P-E Tustin Office
# acquired and passed on to me.  It should work with Perkin-Elmer's Edition VII
# and XELOS systems.
# 
# -earlw@pesnta
#
#! /bin/sh
# This is a shell archive, meaning:
# 1. Remove everything above the #! /bin/sh line.
# 2. Save the resulting text in a file.
# 3. Execute the file with /bin/sh (not csh) to create the files:
#	prelude
# This archive created: Tue Jun 11 19:06:06 1985
# By:	Earl Wallace (Perkin-Elmer Data Systems Group / Customer Service)
export PATH; PATH=/bin:$PATH
if test ! -d 'prelude'
then
	mkdir 'prelude'
fi
cd 'prelude'
if test -f 'Makefile'
then
	echo shar: will not over-write existing file "'Makefile'"
else
cat << \SHAR_EOF > 'Makefile'
.SUFFIXES : .st .p
PREPATH = /usr/src/public/lsmalltalk/prelude
BINDIR = ../bin

PARSED = class.p object.p \
string.p larray.p nil.p array.p\
boolean.p true.p false.p block.p symbol.p \
magnitude.p number.p integer.p char.p float.p radian.p point.p random.p \
collection.p bag.p set.p kcollection.p dictionary.p scollection.p interval.p \
list.p acollection.p file.p bytearray.p \
semaphore.p process.p smalltalk.p

.st.p:
	$(BINDIR)/parse $(PREPATH)/$*.st >$*.p

install: standard
	-make fastsave

bundle: *.st Makefile savescript
	bundle Makefile savescript init *.st >../prelude.bundle

standard: $(PARSED)
	cat $(PARSED) init >standard

newstd: $(PARSED)
	cat $(PARSED) >newstd

fastsave: standard
	$(BINDIR)/st -m <savescript

clean:
	-rm *.p
SHAR_EOF
if test 748 -ne "`wc -c < 'Makefile'`"
then
	echo shar: error transmitting "'Makefile'" '(should have been 748 characters)'
fi
fi # end of overwriting check
if test -f 'savescript'
then
	echo shar: will not over-write existing file "'savescript'"
else
cat << \SHAR_EOF > 'savescript'
)s stdsave
SHAR_EOF
if test 11 -ne "`wc -c < 'savescript'`"
then
	echo shar: error transmitting "'savescript'" '(should have been 11 characters)'
fi
fi # end of overwriting check
if test -f 'init'
then
	echo shar: will not over-write existing file "'init'"
else
cat << \SHAR_EOF > 'init'
smalltalk new
SHAR_EOF
if test 14 -ne "`wc -c < 'init'`"
then
	echo shar: error transmitting "'init'" '(should have been 14 characters)'
fi
fi # end of overwriting check
if test -f 'acollection.st'
then
	echo shar: will not over-write existing file "'acollection.st'"
else
cat << \SHAR_EOF > 'acollection.st'
Class ArrayedCollection :SequenceableCollection
| current |
[
       = anArray                       | i |
                (self size ~= anArray size) ifTrue: [^ false].
                i <- 0.
                self do: [:x | (x ~= (anArray at: (i <- i + 1)))
                                ifTrue: [^ false]].
		^ true
|
        at: key ifAbsent: exceptionBlock
		((key <= 0) or: [key > self size])
			ifTrue: [^ exceptionBlock value].
                ^ self at: key
|
	coerce: aCollection		| temp |
		temp <- self class new: aCollection size.
		temp replaceFrom: 1 to: aCollection size with: aCollection.
		^ temp
|
       copyFrom: start to: stop                | size temp |
		size <- stop - start + 1.
		temp <- self class new: size.
		temp replaceFrom: 1 to: size with: self startingAt: start.
		^ temp
|
        currentKey
                ^ current
| 
	deepCopy		| newobj |
		newobj <- self class new: self size.
		(1 to: self size) do:
			[:i | newobj at: i
				put: (self at: i) copy ].
		^ newobj
|
       do: aBlock
                (1 to: self size) 
		    do: [:i | current <- i. 
				aBlock value: (self at: i)]
|
       first
                current <- 1.
                ^ (current <= self size) 
			ifTrue: [ self at: current]
|
	firstKey
		^ 1
|
	lastKey
		^ self size
|
       next
                current <- current + 1.
                ^ (current <= self size) 
			ifTrue: [ self at: current]
|
	shallowCopy		| newobj |
		newobj <- self class new: self size.
		(1 to: self size) do:
			[:i | newobj at: i 
				put: (self at: i) ].
		^ newobj
]
SHAR_EOF
if test 1564 -ne "`wc -c < 'acollection.st'`"
then
	echo shar: error transmitting "'acollection.st'" '(should have been 1564 characters)'
fi
fi # end of overwriting check
if test -f 'array.st'
then
	echo shar: will not over-write existing file "'array.st'"
else
cat << \SHAR_EOF > 'array.st'
Class Array :ArrayedCollection
[
	new: aValue
		^ <primitive 114 aValue>
|
	at: aNumber
		( (aNumber < 1) or: [aNumber > <primitive 4 self> ] )
			ifTrue: [ self error: 'index error'. ^nil ].
		^ <primitive 111 self aNumber >
|
	at: aNumber put: aValue
		( (aNumber < 1) or: [aNumber > <primitive 4 self> ] )
			ifTrue: [ self error: 'index error'. ^nil ].
		<primitive 112 self aNumber aValue >.
		^ aValue
|
	printString		| value i |
		value <- ')'.
		i <- <primitive 4 self>.
		[i > 0] whileTrue: 
			[ value <- <primitive 111 self i>  printString ,
					' ', value.
				    i <- i - 1].
		^ '#( ' , value
|
	size
		^ <primitive 4 self>
]
SHAR_EOF
if test 642 -ne "`wc -c < 'array.st'`"
then
	echo shar: error transmitting "'array.st'" '(should have been 642 characters)'
fi
fi # end of overwriting check
if test -f 'bag.st'
then
	echo shar: will not over-write existing file "'bag.st'"
else
cat << \SHAR_EOF > 'bag.st'
Class Bag :Collection
| dict count |
[
        new
                dict <- Dictionary new

|       add: newElement
                dict at: newElement 
                     put: (1 + (dict at: newElement ifAbsent: [0]))

|       add: newObj withOccurrences: anInteger
                anInteger timesRepeat: [ self add: newObj ].
                ^ newObj

|       remove: oldElement ifAbsent: exceptionBlock   | i |
                i <- dict at: oldElement 
                          ifAbsent: [ ^ exceptionBlock value].
                (1 = i) ifTrue:  [dict removeKey: oldElement]
                        ifFalse: [dict at: oldElement put: i - 1 ]

|       size
                ^ dict inject: 0 into: [:x :y | x + y]

|       occurrencesOf: anElement
                ^ dict at: anElement ifAbsent: [0]

|       first
		(count <- dict first) isNil ifTrue: [^ nil].
		count <- count - 1.
		^ dict currentKey

|       next
		[count notNil] whileTrue:
		   [ (count > 0)
		        ifTrue: [count <- count - 1. ^ dict currentKey]
			ifFalse: [(count <- dict next) isNil
					ifTrue: [^ nil] ]].
		^ nil

]
SHAR_EOF
if test 1102 -ne "`wc -c < 'bag.st'`"
then
	echo shar: error transmitting "'bag.st'" '(should have been 1102 characters)'
fi
fi # end of overwriting check
if test -f 'block.st'
then
	echo shar: will not over-write existing file "'block.st'"
else
cat << \SHAR_EOF > 'block.st'
"
	Class Block.

	Note how whileTrue: and whileFalse: depend upon the parser
	optimizing the loops into control flow, rather than message
	passing.  If this were not the case, whileTrue: would have to
	be implemented using recursion, as follows:

	whileTrue: aBlock
		(self value) ifFalse: [^nil].
		aBlock value.
		^ self whileTrue: aBlock
"
Class Block
[
	newProcess
		^ <primitive 141  self>
|
	newProcessWith: argumentArray
		^ <primitive 141  self argumentArray>
|
	fork
		self newProcess resume.
		^ nil
|
	forkWith: argumentArray
		(self newProcessWith: argumentArray) resume.
		^ nil
|
	whileTrue
		^ [self value ] whileTrue: []
|
	whileTrue: aBlock
		^ [ self value ] whileTrue: [ aBlock value ]
|
	whileFalse
		^ [ self value ] whileFalse: []
|
	whileFalse: aBlock
		^ [ self value ] whileFalse: [ aBlock value ]
|
 	value
		<primitive 140  0>
|
	value: a
		<primitive 140  1>
|
	value: a value: b
		<primitive 140  2>
|
	value: a value: b value: c
		<primitive 140  3>
|
	value: a value: b value: c value: d
		<primitive 140  4>
|
	value: a value: b value: c value: d value: e
		<primitive 140  5>
]
SHAR_EOF
if test 1111 -ne "`wc -c < 'block.st'`"
then
	echo shar: error transmitting "'block.st'" '(should have been 1111 characters)'
fi
fi # end of overwriting check
if test -f 'boolean.st'
then
	echo shar: will not over-write existing file "'boolean.st'"
else
cat << \SHAR_EOF > 'boolean.st'
Class Boolean
[
        &    aBoolean   
		^ self and: [aBoolean]

|       |    aBoolean  
		^ self or: [aBoolean]

|       and: aBlock   
		^ self and: [aBlock value]

|       or:  aBlock  
		^ self or: [aBlock value]

|	eqv: aBoolean
		^ self == aBoolean

|	xor: aBoolean
		^ self ~~ aBoolean
]
SHAR_EOF
if test 297 -ne "`wc -c < 'boolean.st'`"
then
	echo shar: error transmitting "'boolean.st'" '(should have been 297 characters)'
fi
fi # end of overwriting check
if test -f 'bytearray.st'
then
	echo shar: will not over-write existing file "'bytearray.st'"
else
cat << \SHAR_EOF > 'bytearray.st'
Class ByteArray :ArrayedCollection
[
	new: size
		^ <primitive 116 size>
|
	at: index
		^ <primitive 118 self index>
|
	at: index put: value
		<primitive 119 self index value>
|
	printString	| str |
		str <- '#[ '.
		(1 to: self size)
			do: [:i | str <- str , (self at: i) printString , ' '].
		^ str , ']'
|
	size
		^ <primitive 117 self>
]

SHAR_EOF
if test 344 -ne "`wc -c < 'bytearray.st'`"
then
	echo shar: error transmitting "'bytearray.st'" '(should have been 344 characters)'
fi
fi # end of overwriting check
if test -f 'char.st'
then
	echo shar: will not over-write existing file "'char.st'"
else
cat << \SHAR_EOF > 'char.st'
Class Char :Magnitude
[
	== aChar
		^ <primitive 6 self aChar>
			ifTrue:  [<primitive 46 self aChar>]
			ifFalse: [false]
|	< aChar
		^ <primitive 6 self aChar>
			ifTrue:  [<primitive 42 self aChar>]
			ifFalse: [self compareError]
|
	= aChar
		^ <primitive 6 self aChar>
			ifTrue:  [<primitive 46 self aChar>]
			ifFalse: [self compareError]
|	> aChar
		^ <primitive 6 self aChar>
			ifTrue:  [<primitive 43 self aChar>]
			ifFalse: [self compareError]
|
	asciiValue
		^ <primitive 59 self>
|
	asLowercase
		^ <primitive 54 self>
			ifTrue:  [<primitive 57 self>]
			ifFalse: [self]
|
	asUppercase
		^ <primitive 53 self>
			ifTrue:  [<primitive 57 self>]
			ifFalse: [self]
|
	asString
		^ <primitive 58 self>
|
	compareError
		^ self error: 'char cannot be compared to non char'
|
	digitValue		| i |
		((i <- <primitive 50 self>) isNil)
			ifTrue: [self error: 'digitValue on nondigit char'].
		^ i
|
	isAlphaNumeric
		^ <primitive 56 self>
|
	isDigit
		^ self between: $0 and: $9
|
	isLetter
		^ self isLowercase or: [self isUppercase]
|
	isLowercase
		^ self between: $a and: $z 
|
	isSeparator
		^ <primitive 55 self>
|
	isUppercase
		^ (self between: $A and: $Z)
|
	isVowel
		^ <primitive 51 self>
|
	printString
		^ '$' , <primitive 58 self>
]
SHAR_EOF
if test 1255 -ne "`wc -c < 'char.st'`"
then
	echo shar: error transmitting "'char.st'" '(should have been 1255 characters)'
fi
fi # end of overwriting check
if test -f 'class.st'
then
	echo shar: will not over-write existing file "'class.st'"
else
cat << \SHAR_EOF > 'class.st'
Class Class
[
	edit
		<primitive 150 self>
|
	list
		<primitive 157 self>
|
 	new		| superclass newinstance |
		superclass <- <primitive 151 self>.
		<primitive 3 superclass >
			ifTrue: [newinstance <- superclass new ]. 
		newinstance <- <primitive 153 self newinstance >.
		<primitive 155 self #new > 
			ifTrue: [newinstance <- newinstance new].
		^ newinstance
|
 	new: aValue 		| superclass newinstance |
		superclass <- <primitive 151 self>.
		<primitive 3 superclass >
			ifTrue: [newinstance <- superclass new ]. 
		newinstance <- <primitive 153 self newinstance >.
		<primitive 155 self #new: > 
			ifTrue: [newinstance <- newinstance new: aValue ].
		^ newinstance
|
 	printString
		^ <primitive 152 self >
|
	respondsTo
		<primitive 154 self>
|
	respondsTo: aSymbol		| aClass |
		aClass <- self.
		[aClass notNil] whileTrue:
			[ <primitive 155 aClass aSymbol> ifTrue: [ ^ true ].
			 aClass <- aClass superClass ].
		^ false
|
	superClass
		^ <primitive 151 self>

|
	variables
		^ <primitive 158 self>
|
	view
		<primitive 156 self>
]
SHAR_EOF
if test 1048 -ne "`wc -c < 'class.st'`"
then
	echo shar: error transmitting "'class.st'" '(should have been 1048 characters)'
fi
fi # end of overwriting check
if test -f 'collection.st'
then
	echo shar: will not over-write existing file "'collection.st'"
else
cat << \SHAR_EOF > 'collection.st'
Class Collection
[
        addAll: aCollection
                aCollection do: [:x | self add: x ]

|
	asArray
		^ Array new: self size ;
			replaceFrom: 1 to: self size with: self
|
	asBag
                ^ Bag new addAll: self
|
	asSet
                ^ Set new addAll: self
|
	asList
                ^ List new addAllLast: self
|
	asString
		^ String new: self size ; 
			replaceFrom: 1 to: self size with: self
|
	coerce: aCollection	| newobj |
		newobj <- self new.
		aCollection do: [:x | newobj add: x].
		^ newobj
|
	collect: aBlock
		^ self inject: self class new
		       into: [:x :y | x add: (aBlock value: y). x ]
|
	deepCopy		| newobj |
		newobj <- List new .
		self do: [:x | newobj addLast: x copy ].
		^ self coerce: newobj
|
	detect: aBlock
		^ self detect: aBlock
		ifAbsent: [self error: 'no object found matching detect']

|
        detect: aBlock ifAbsent: exceptionBlock   
                self do: [:x | 
                          (aBlock value: x) ifTrue: [^ x]].
                ^ exceptionBlock value
|
 	first
		^ self error: 'subclass should implement first'
|
        includes: anObject
		self do: [:x | (x = anObject) ifTrue: [^ true]].
		^ false
|
        inject: thisValue into: binaryBlock     | last |
                last <- thisValue.
                self do: [:x | last <- binaryBlock value: last value: x].
                ^ last
|
        isEmpty
                ^ (self size = 0)
|
	occurrencesOf: anObject
		^ self inject: 0
                       into: [:x :y | (y = anObject) 
                                         ifTrue: [x + 1]
                                         ifFalse: [x] ]
|
	printString
		^ ( self inject: self class printString , ' ('
			 into: [:x :y | x , ' ' , y printString]), ' )'
|
	reject: aBlock          
		^ self select: [:x | (aBlock value: x) not ]
|
        remove: oldObject
                self remove: oldObject ifAbsent:
                  [^ self error: 
			'attempt to remove object not found in collection' ].
                ^ oldObject
|
	remove: oldObject ifAbsent: exceptionBlock
		^ (self includes: oldObject)
			ifTrue: [self remove: oldObject]
			ifFalse: exceptionBlock
|
	select: aBlock          
		^ self inject: self class new
		       into: [:x :y | (aBlock value: y) 
                                        ifTrue: [x add: y]. x]
|
	shallowCopy		| newobj |
		newobj <- List new .
		self do: [:x | newobj addLast: x].
		^ self coerce: newobj
|
	size		| i |
		i <- 0.
		self do: [:x | i <- i + 1 ].
		^ i
]
SHAR_EOF
if test 2501 -ne "`wc -c < 'collection.st'`"
then
	echo shar: error transmitting "'collection.st'" '(should have been 2501 characters)'
fi
fi # end of overwriting check
if test -f 'dictionary.st'
then
	echo shar: will not over-write existing file "'dictionary.st'"
else
cat << \SHAR_EOF > 'dictionary.st'
"
	Dictionarys are implemented using Points in order to reduce
	the number of classes in the standard prelude

	this also has the advantage of making the output appear in
		key @ value
	form
"
Class Dictionary :KeyedCollection
| hashTable currentBucket currentList |
[
	new
		hashTable <- Array new: 17
|
	hashNumber: aKey
		^ ( <primitive 5 aKey> \\ hashTable size) + 1
|
	getList: aKey			| list bucketNumber |
		bucketNumber <- self hashNumber: aKey.
		list <- hashTable at: bucketNumber.
		(list isNil)
			ifTrue: [list <- List new.
				 hashTable at: bucketNumber put: list].
		^ list

|
	at: aKey put: anObject			| list anAssoc |

		list <- self getList: aKey.
		anAssoc <- self findAssociation: aKey inList: list.
		(anAssoc isNil)
			ifTrue:  [anAssoc <- (Point new x: aKey) y: anObject.
				  list add: anAssoc]
			ifFalse: [anAssoc y: anObject].
		^ anObject
|
	at: aKey ifAbsent: exceptionBlock	| list anAssoc | 

		list <- self getList: aKey.
		anAssoc <- self findAssociation: aKey inList: list.
		(anAssoc isNil)
			ifTrue: [^ exceptionBlock value].
		^ anAssoc y
|
	removeKey: aKey ifAbsent: exceptionBlock 	| list anAssoc|
		
		list <- self getList: aKey.
		anAssoc <- self findAssociation: aKey inList: list.
		(anAssoc isNil)
			ifTrue: [^ exceptionBlock value].
		^ ( list remove: anAssoc 
			 ifAbsent: [ ^ exceptionBlock value ] ) y
|
	findAssociation: aKey inList: linkedList

		linkedList do: 
			[:item | (item x = aKey) ifTrue: [^ item]].
		^ nil
|
	first				| item |

		(1 to: 17) do: 
			[:i | ((item <- self checkBucket: i) notNil)
						ifTrue: [ ^ item y] ] .
		^ nil
|
	next				| item |

		((item <- currentList next) notNil)
			ifTrue: [ ^ item y ].
		[currentBucket < 17] whileTrue:
			[currentBucket <- currentBucket + 1.
			 ((item <- self checkBucket: currentBucket) notNil)
				ifTrue: [ ^ item y ] ].
		^ nil
|
	printString
		^ (self inject: (self class printString) , ' ( '
			into: [ :aString :aValue |
				aString , self currentKey printString ,
					' @ ' , aValue printString , ' ' ]
			) , ')'
|
	currentKey	| clist|
		^ (currentList notNil) 
			ifTrue: [clist <- currentList current.
				 (clist notNil) ifTrue: [clist x]
			        ]
|
	checkBucket: bucketNumber

		((currentList <- hashTable at: 
				(currentBucket <- bucketNumber)) isNil)
			ifTrue: [ ^ nil ].
		^ currentList first
]
SHAR_EOF
if test 2333 -ne "`wc -c < 'dictionary.st'`"
then
	echo shar: error transmitting "'dictionary.st'" '(should have been 2333 characters)'
fi
fi # end of overwriting check
if test -f 'false.st'
then
	echo shar: will not over-write existing file "'false.st'"
else
cat << \SHAR_EOF > 'false.st'
Class False :Boolean
[
        ifTrue: trueAlternativeBlock ifFalse: falseAlternativeBlock
                ^ falseAlternativeBlock value

!       ifFalse: falseAlternativeBlock ifTrue: trueAlternativeBlock
                ^ falseAlternativeBlock value

!       ifTrue: trueAlternativeBlock
                ^ nil

!       ifFalse: falseAlternativeBlock
                ^ falseAlternativeBlock value

!       not
                ^ true
]
SHAR_EOF
if test 436 -ne "`wc -c < 'false.st'`"
then
	echo shar: error transmitting "'false.st'" '(should have been 436 characters)'
fi
fi # end of overwriting check
if test -f 'file.st'
then
	echo shar: will not over-write existing file "'file.st'"
else
cat << \SHAR_EOF > 'file.st'
Class File :SequenceableCollection
[
	modeCharacter
		<primitive 133 self 0>
|
	modeInteger
		<primitive 133 self 2>
|
	modeString
		<primitive 133 self 1>
|
	at: aPosition
		<primitive 135 self aPosition>.
		^ self read
|
	at: aPosition put: anObject
		<primitive 135 self aPosition>.
		^ self write: anObject
|
	currentKey
		^ <primitive 136 self>
|
	first
		^ self at: 0
|
	next
		^ self read
|
	open: aName
		<primitive 130 self aName 'r' >
|
	open: aName for: opType
		<primitive 130 self aName opType >
|
	read
		^ <primitive 131 self>
|
	size
		^ <primitive 134 self>
|
	write: anObject
		^ <primitive 132 self anObject>
]
SHAR_EOF
if test 630 -ne "`wc -c < 'file.st'`"
then
	echo shar: error transmitting "'file.st'" '(should have been 630 characters)'
fi
fi # end of overwriting check
if test -f 'float.st'
then
	echo shar: will not over-write existing file "'float.st'"
else
cat << \SHAR_EOF > 'float.st'
Class Float :Number
[
	= aNumber
		^ <primitive 6 self aNumber>
			ifTrue:  [<primitive 66 self aNumber>]
			ifFalse: [super = aNumber]
|
	< aNumber
		^ <primitive 6 self aNumber>
			ifTrue:  [<primitive 62 self aNumber>]
			ifFalse: [super < aNumber]
|
	> aNumber
		^ <primitive 6 self aNumber>
			ifTrue:  [<primitive 63 self aNumber>]
			ifFalse: [ super > aNumber]
|
	+ aNumber
		^ <primitive 6 self aNumber>
			ifTrue:  [<primitive 60 self aNumber>]
			ifFalse: [super + aNumber]
|
	- aNumber
		^ <primitive 6 self aNumber>
			ifTrue:  [<primitive 61 self aNumber>]
			ifFalse: [super - aNumber]
|
	* aNumber
		^ <primitive 6 self aNumber>
			ifTrue:  [<primitive 68 self aNumber>]
			ifFalse: [super * aNumber]
|
	/ aNumber
		^ <primitive 6 self aNumber>
			ifTrue:  [<primitive 69 self aNumber>]
			ifFalse: [super / aNumber]
|
	^ aNumber
		^ <primitive 6 self aNumber>
			ifTrue:  [<primitive 88 self aNumber>]
			ifFalse: [super raisedTo: aNumber]
|
	arcCos
		^ Radian new: <primitive 85 self>
|
	arcSin
		^ Radian new: <primitive 84 self>
|
	arcTan
		^ Radian new: <primitive 86 self>
|
	asFloat
		^ self
|
	asString
		^ <primitive 78 self>
|
	ceiling
		^ <primitive 73 self>
|
	coerce: aNumber
		^ aNumber asFloat
|
	exp
		^ <primitive 79 self>
|
	floor
		^ <primitive 72 self>
|
	fractionPart
		^ <primitive 76 self>
|
	gamma
		^ <primitive 77 self>
|
	integerPart
		^ <primitive 75 self>
|
	ln
		^ <primitive 70 self>
|
	radix: aNumber
		^ <primitive 89 self aNumber>
|
	rounded
		^ <primitive 72 (self + 0.5)>
|
	sqrt
		^ <primitive 71 self>
|
	truncated
		^ (self < 0.0)  ifTrue:  [<primitive 73 self>]
				ifFalse: [<primitive 72 self>]
]
SHAR_EOF
if test 1655 -ne "`wc -c < 'float.st'`"
then
	echo shar: error transmitting "'float.st'" '(should have been 1655 characters)'
fi
fi # end of overwriting check
if test -f 'integer.st'
then
	echo shar: will not over-write existing file "'integer.st'"
else
cat << \SHAR_EOF > 'integer.st'
Class Integer :Number
[
	= aNumber
		^ <primitive 6 self aNumber>
			ifTrue:  [ <primitive 16 self aNumber> ]
			ifFalse: [ super = aNumber ]
|
	> aNumber
		^ <primitive 6 self aNumber>
			ifTrue:  [ <primitive 13 self aNumber> ]
			ifFalse: [ super > aNumber ]
|
	< aNumber
		^ <primitive 6 self aNumber>
			ifTrue:  [ <primitive 12 self aNumber> ]
			ifFalse: [ super < aNumber ]
|
	+ aNumber
		^ <primitive 6 self aNumber>
			ifTrue:  [ <primitive 10 self aNumber> ]
			ifFalse: [ super + aNumber ]
|
	- aNumber
		^ <primitive 6 self aNumber>
			ifTrue:  [<primitive 11 self aNumber>]
			ifFalse: [ super - aNumber ]
|
	* aNumber
		^ <primitive 6 self aNumber>
			ifTrue:  [<primitive 18 self aNumber>]
			ifFalse: [ super * aNumber ]
|
	/ aNumber
		^ self asFloat / aNumber
|
	// aNumber
		^ <primitive 6 self aNumber>
			ifTrue:  [<primitive 19 self aNumber>]
			ifFalse: [self opError]
|
	\\ aNumber			| i |
		^ <primitive 6 self aNumber>
			ifTrue:  [i <- self * ( (self < 0)
						ifTrue:  [ -1 ] 
						ifFalse: [ 1 ] ).
				  i rem: aNumber]
			ifFalse:  [self opError]
|
	allMask: anInteger
		^ anInteger = <primitive 23 self anInteger>
|
	anyMask: anInteger
		^ 0 ~= <primitive 23 self anInteger>
|
	asCharacter
		^ <primitive 36 self>
|
	asFloat
		^ <primitive 39 self >
|
	asString
		^ <primitive 37 self>
|
	bitAnd: anInteger
		^ <primitive 23 self anInteger>
|
	bitAt: anInteger
		^ <primitive 21 self anInteger>
|
	bitInvert
		^ <primitive 33 self>
|
	bitOr: anInteger
		^ <primitive 22 self anInteger>
|
	bitShift: anInteger
		^ <primitive 25 self anInteger>
|
	bitXor: anInteger
		^ <primitive 24 self anInteger>
|
	even
		^ (self rem: 2) = 0
|
	factorial
		^ <primitive 38 self>
|
	gcd: anInteger
		^ <primitive 6 self anInteger>
			ifTrue:  [<primitive 20 self anInteger>]
			ifFalse: [self opError]
|
	highBit
		^ <primitive 34 self>
|
	lcm: anInteger
		^ <primitive 6 self anInteger>
			ifTrue:  [self * anInteger quo: 
					(self gcd: anInteger)]
			ifFalse: [self opError]
|
	noMask: anInteger
		^ 0 = (self bitAnd: anInteger)
|
	odd
		^ (self rem: 2) ~= 0
|
	quo: anInteger
		^ <primitive 6 self anInteger>
			ifTrue:  [<primitive 28 self anInteger>]
			ifFalse: [self opError]
|
	radix: aNumber
		^ <primitive 26 self aNumber>
|
	rem: anInteger
		^ <primitive 6 self anInteger>
			ifTrue:  [<primitive 29 self anInteger>]
			ifFalse: [self opError]
|
	timesRepeat: aBlock		| i |
		i <- 0.
		[i < self] whileTrue:
			[aBlock value. i <- i + 1]
]
SHAR_EOF
if test 2472 -ne "`wc -c < 'integer.st'`"
then
	echo shar: error transmitting "'integer.st'" '(should have been 2472 characters)'
fi
fi # end of overwriting check
if test -f 'interval.st'
then
	echo shar: will not over-write existing file "'interval.st'"
else
cat << \SHAR_EOF > 'interval.st'
Class Interval :SequenceableCollection
| lower upper step current |
[
	from: lowerBound to: upperBound by: stepSize
		current <- lower <- lowerBound.
		upper <- upperBound.
		step  <- stepSize

|	size	
		^ ((step strictlyPositive)
			ifTrue: [upper < lower]
			ifFalse: [lower < upper] )
		   ifTrue: [ 0 ]
		   ifFalse: [upper - lower // step + 1]

|	inRange: value
		^ (step strictlyPositive)
			ifTrue: [(value >= lower) and: [value <= upper]]
			ifFalse: [(value >= upper) and: [value <= lower]]

|       first
                current <- lower.
		^ (self inRange: current) ifTrue: [current]

|       next
                current <- current + step.
		^ (self inRange: current) ifTrue: [current]

|	at: index ifAbsent: exceptionBlock	| val |
		val <- lower + (step * (index - 1)).
		^ (self inRange: val)
		   ifTrue: [ val ]
		   ifFalse: [exceptionBlock value]

|	printString
		^ 'Interval ', lower printString , ' to ',
                     upper printString , ' by ' , step printString 

|	coerce: newcollection
		^ newcollection asArray

|	at: index put: val
		^ self error: 'cannot store into Interval'

|	add: val
		^ self error: 'cannot store into Interval'

|	removeKey: key ifAbsent: exceptionBlock
		self error: 'cannot remove from Interval'.
		^ exceptionBlock value
|
	deepCopy
		^ lower to: upper by: step
|	
	shallowCopy
		^ lower to: upper by: step
]
SHAR_EOF
if test 1369 -ne "`wc -c < 'interval.st'`"
then
	echo shar: error transmitting "'interval.st'" '(should have been 1369 characters)'
fi
fi # end of overwriting check
if test -f 'kcollection.st'
then
	echo shar: will not over-write existing file "'kcollection.st'"
else
cat << \SHAR_EOF > 'kcollection.st'
Class KeyedCollection :Collection
[
	add: anElement
		^ self error: 'Must add with explicit key'
|
	addAll: aCollection
                aCollection binaryDo: [:x :y | self at: x put: y].
                ^ aCollection
|
	asDictionary			| newCollection |
		newCollection <- Dictionary new.
		self binaryDo: 
			[:key :val | newCollection at: key put: val].
		^ newCollection
|
	at: key
                ^ self at: key ifAbsent:
                   [self error:
                         (key printString , ': association not found').
                    ^ key]
|
	atAll: aCollection put: anObject
		aCollection do: [:x | self at: x put: anObject]
|
	binaryDo: aBlock                | item |
		self do: [:x | aBlock value: self currentKey
					value: x ].
                ^ nil
|
	collect: aBlock 
		^ self coerce:
		     (self inject: Dictionary new
                           into: [:x :y | x at: self currentKey
					    put: (aBlock value: y) . x ] )
|
	includesKey: key
                self at: key ifAbsent: [^ false].
                ^ true
|
	indexOf: anElement
		^ self indexOf: anElement
		ifAbsent: [self error: 'indexOf element not found']
|
	indexOf: anElement ifAbsent: exceptionBlock
                self do: [:x | (x = anElement) 
  				  ifTrue: [ ^ self currentKey ]].
                 ^ exceptionBlock value
|
	keys                             | newset |
                newset <- Set new.
                self keysDo: [:x | newset add: x].
                ^ newset
|
	keysDo: aBlock
                ^ self do: [ :x | aBlock value: self currentKey ]
|
	keysSelect: aBlock          
		^ self coerce:
		     (self inject: Dictionary new
                           into: [:x :y | (aBlock value: y currentKey)
                                           ifTrue: [x at: self currentKey
                                                      put: y]. x ] )
|
	remove: anElement
		^ self error: 'object must be removed with explicit key'
|
	removeKey: key
                ^ self removeKey: key ifAbsent:
                   [self error: 'no element associated with key'. ^ key]
|
	removeKey: key ifAbsent: exceptionBlock
		^ self error: 'subclass should implement RemoveKey:ifAbsent:'
|
	select: aBlock          
		^ self coerce:
		     (self inject: Dictionary new
                           into: [:x :y | (aBlock value: y)
                                           ifTrue: [x at: self currentKey
                                                      put: y]. x ] )
|
	values                           | newbag |
                newbag <- Bag new.
                self do: [:x | newbag add: x].
                ^ newbag
]
SHAR_EOF
if test 2628 -ne "`wc -c < 'kcollection.st'`"
then
	echo shar: error transmitting "'kcollection.st'" '(should have been 2628 characters)'
fi
fi # end of overwriting check
if test -f 'larray.st'
then
	echo shar: will not over-write existing file "'larray.st'"
else
cat << \SHAR_EOF > 'larray.st'
Class ArrayedCollection
" This is just a null version of ArrayedCollection to serve as a place
holder until the real version is read in during the prelude "
[
	nothing
		1
]

SHAR_EOF
if test 175 -ne "`wc -c < 'larray.st'`"
then
	echo shar: error transmitting "'larray.st'" '(should have been 175 characters)'
fi
fi # end of overwriting check
if test -f 'list.st'
then
	echo shar: will not over-write existing file "'list.st'"
else
cat << \SHAR_EOF > 'list.st'
"
	Lists are implemented using Points in order to
	reduce the number of classes in the standard prelude
"
Class List :SequenceableCollection
| first current |
[
	add: anItem
		first <- (Point new x: anItem ) y: first .
		^ anItem
|
	addFirst: anItem
		first <- (Point new x: anItem ) y: first .
		^ anItem
|
	addLast: anItem
		(first isNil) 
			ifTrue: [^ self addFirst: anItem].
		(self findLast) y: ((Point new x: anItem) y: nil).
		^ anItem
|
	addAllFirst: aCollection
		aCollection do: [:x | self addFirst: x]
|	
	addAllLast: aCollection
		aCollection do: [:x | self addLast: x]
|
	coerce: aCollection		| newList |
		newList <- List new.
		aCollection do: [:x | newList addLast: x].
		^ newList
|
	findLast		| item |
		((item <- first) isNil)
			ifTrue: [^ nil].
		[(item y) notNil]
			whileTrue: [item <- item y].
		^ item
|
	remove: anItem
		^ self remove: anItem 
			ifAbsent: [self error: 'cant find item']
|
	remove: anItem ifAbsent: exceptionBlock
		(first isNil) 
			ifTrue: [^ exceptionBlock value].
		self inject: nil into: [:prev :current |
			(current x == anItem)
				ifTrue: [(prev isNil)
						ifTrue: [first <- current y]
						ifFalse: [prev y: (current y)].
					 ^ anItem].
			current ] .
		^ exceptionBlock value
|
	removeError
		^ self error: 'cannot remove from an empty list'
|
	removeFirst	| item |
		(first isNil)
			ifTrue: [^ self removeError].
		item <- first.
		first <- first y.
		^ item x
|
	removeLast
		(first isNil)
			ifTrue: [^ self removeError].
		^ self remove: self last 
			ifAbsent: [self removeError]
|
	first
		^ ((current <- first) notNil) 
			ifTrue: [ current x ]
|
	next
		^ ((current <- current y) notNil)
			ifTrue: [ current x ]
|
	current
		^ current x
|
	last
		(first isNil) 
			ifTrue: [^ nil].
		^ self findLast x
|
	isEmpty
		^ first == nil
]
SHAR_EOF
if test 1802 -ne "`wc -c < 'list.st'`"
then
	echo shar: error transmitting "'list.st'" '(should have been 1802 characters)'
fi
fi # end of overwriting check
if test -f 'magnitude.st'
then
	echo shar: will not over-write existing file "'magnitude.st'"
else
cat << \SHAR_EOF > 'magnitude.st'
Class Magnitude
[
	<= arg
		^ (self < arg) or: [self = arg]

|	< arg
		^ (arg > self)

|	= arg
		^ (self > arg or: [self < arg]) not

|	~= arg
		^ (self = arg) not

|	>= arg
		^ (self > arg) or: [self = arg]

|	> arg
		^ arg < self

|	between: low and: high
		^ (self >= low) and: [self <= high]

|	min: arg
		^ (self < arg) ifTrue: [self] ifFalse: [arg]

|	max: arg
		^ (self > arg) ifTrue: [self] ifFalse: [arg]
]
SHAR_EOF
if test 416 -ne "`wc -c < 'magnitude.st'`"
then
	echo shar: error transmitting "'magnitude.st'" '(should have been 416 characters)'
fi
fi # end of overwriting check
if test -f 'nil.st'
then
	echo shar: will not over-write existing file "'nil.st'"
else
cat << \SHAR_EOF > 'nil.st'
Class UndefinedObject
[
        isNil
                ^ true
|
        notNil
                ^ false
|
        printString
                ^ 'nil'
]
SHAR_EOF
if test 150 -ne "`wc -c < 'nil.st'`"
then
	echo shar: error transmitting "'nil.st'" '(should have been 150 characters)'
fi
fi # end of overwriting check
if test -f 'number.st'
then
	echo shar: will not over-write existing file "'number.st'"
else
cat << \SHAR_EOF > 'number.st'
Class Number :Magnitude
[
	maxtype: aNumber
		^ <primitive 9 self aNumber> 
			ifTrue:  [self]
			ifFalse: [aNumber coerce: self ]
|
	= aNumber
		^ (self maxtype: aNumber) = (aNumber maxtype: self)
|
	< aNumber
		^ (self maxtype: aNumber) < (aNumber maxtype: self)
|
	> aNumber
		^ (self maxtype: aNumber) > (aNumber maxtype: self)
|
	+ aNumber
		^ (self maxtype: aNumber) + (aNumber maxtype: self)
|
	- aNumber
		^ (self maxtype: aNumber) - (aNumber maxtype: self)
|
	* aNumber
		^ (self maxtype: aNumber) * (aNumber maxtype: self)
|
	/ aNumber
		^ (self maxtype: aNumber) / (aNumber maxtype: self)
|
	^ aNumber
		^ self asFloat ^ aNumber asFloat
|
	@ aNumber
		^ ( Point new x: self ) y: aNumber
|
	abs
		^ (self < 0)
			ifTrue:  [ 0 - self ]
			ifFalse: [ self ]
|
	exp
		^ self asFloat exp
|
	gamma
		^ self asFloat gamma
|
	ln
		^ self asFloat ln
|
	log: aNumber
		^ self ln / aNumber ln
|
	negated
		^ 0 - self
|
	negative
		^ self < 0
|
	pi
		^ self * 3.1415926
|
	positive
		^ self >= 0
|
	radians
		^ Radian new: self asFloat
|
	raisedTo: aNumber
		^ self asFloat ^ aNumber asFloat
|
	reciprocal
		^ 1.00 / self
|
	roundTo: aNumber
		^ (self / aNumber) rounded * aNumber
|
	sign
		^ (self < 0)
			ifTrue: [ -1 ]
			ifFalse: [ (self > 0)
					ifTrue: [ 1 ]
					ifFalse: [ 0 ] ]
|
	sqrt
		^ self asFloat sqrt
|
	squared
		^ self * self
|
	strictlyPositive
		^ self > 0
|
	to: highValue
		^ Interval new ; from: self to: highValue by: 1
|
	to: highValue by: stepSize
		^ Interval new ; from: self to: highValue by: stepSize
|
	truncateTo: aNumber
		^ (self / aNumber) truncated * aNumber
]
SHAR_EOF
if test 1597 -ne "`wc -c < 'number.st'`"
then
	echo shar: error transmitting "'number.st'" '(should have been 1597 characters)'
fi
fi # end of overwriting check
if test -f 'object.st'
then
	echo shar: will not over-write existing file "'object.st'"
else
cat << \SHAR_EOF > 'object.st'
Class Object
[
 	== anObject
		^ <primitive 7 self anObject >
|
       ~~ x
                ^ (self == x) not
|
 	= x
		^ (self == x)
|
 	~= x
		^ (self = x) not
|
 	asString
		^ self class printString
|
        asSymbol
                ^ self asString asSymbol
|
	class
		^ <primitive 1 self >
|
        copy
                ^ self shallowCopy
|
        deepCopy		| size newobj |
		size <- <primitive 4 self>.
		(size < 0) 
			ifTrue: [^ self] "if special just copy object"
			ifFalse: [ newobj <- self class new.
			(1 to: size) do: [:i |
				<primitive 112 newobj i
					( <primitive 111 self i > copy ) > ].
				^ newobj ]
|
 	do: aBlock			| item |
		item <- self first.
		^ [item notNil] whileTrue:
			[aBlock value: item.  item <- self next]
|
	error: aString
		<primitive 122 aString self>
|
        first
                ^ self
|
        isKindOf: aClass                | objectClass |
                objectClass <- self class.
                [objectClass notNil] whileTrue:
                        [(objectClass == aClass) ifTrue: [^ true].
                         objectClass <- objectClass superClass].
                ^ false
|
        isMemberOf: aClass
                ^ aClass == self class

|
        isNil
                ^ false
|
        next
                ^ nil
|
        notNil
                ^ true
|
 	print
		<primitive 121 (self printString) >
|
 	printString
		^ self asString

|       respondsTo: cmd
                ^ self class respondsTo: cmd

|       shallowCopy		| size newobj |
		size <- <primitive 4 self>.
		(size < 0) 
			ifTrue: [^ self] "if special just copy object"
			ifFalse: [ newobj <- self class new.
				(1 to: size) do: [:i |
					<primitive 112 newobj i
						<primitive 111 self i > > ].
					^ newobj ]
]
SHAR_EOF
if test 1760 -ne "`wc -c < 'object.st'`"
then
	echo shar: error transmitting "'object.st'" '(should have been 1760 characters)'
fi
fi # end of overwriting check
if test -f 'point.st'
then
	echo shar: will not over-write existing file "'point.st'"
else
cat << \SHAR_EOF > 'point.st'
Class Point :Magnitude
| xvalue yvalue |
[
	< aPoint
		^ (xvalue < aPoint x) and: [yvalue < aPoint y]
|
	<= aPoint
		^ (xvalue <= aPoint x) and: [yvalue < aPoint y]
|
	>= aPoint
		^ (xvalue >= aPoint x) and: [yvalue >= aPoint y]
|
	= aPoint
		^ (xvalue = aPoint x) and: [yvalue = aPoint y]
|
	* scale
		^ (Point new x: (xvalue * scale)) y: (yvalue * scale)
|
	+ delta
		^ (Point new x: (xvalue + delta x)) y: (yvalue + delta y)
|
	- delta
		^ (Point new x: (xvalue - delta x)) y: (yvalue - delta y)
|
	/ scale
		^ (Point new x: (xvalue / scale)) y: (yvalue / scale)
|
	// scale
		^ (Point new x: (xvalue // scale)) y: (yvalue // scale)
|
	abs
		^ (Point new x: xvalue abs) y: (yvalue abs)
|
	asString
		^ xvalue asString , ' @ ' , (yvalue asString)
|
	dist: aPoint
		^ ((xvalue - aPoint x) squared + 
			(yvalue - aPoint y) squared) sqrt
|
	max: aPoint
		^ (Point new x: (xvalue max: aPoint x))
			y: (yvalue max: aPoint y)
|
	min: aPoint
		^ (Point new x: (xvalue min: aPoint x))
			y: (yvalue min: aPoint y)
|
	printString
		^ xvalue printString , ' @ ' , (yvalue printString)
|
	transpose
		^ (Point new x: yvalue) y: xvalue
|
	x
		^ xvalue
|
	x: aValue
		xvalue <- aValue
|
	x: xValue y: yValue
		xvalue <- xValue.
		yvalue <- yValue
|
	y
		^ yvalue
|
	y: aValue
		yvalue <- aValue
]
SHAR_EOF
if test 1288 -ne "`wc -c < 'point.st'`"
then
	echo shar: error transmitting "'point.st'" '(should have been 1288 characters)'
fi
fi # end of overwriting check
if test -f 'process.st'
then
	echo shar: will not over-write existing file "'process.st'"
else
cat << \SHAR_EOF > 'process.st'
Class  Process

[  block
	(self state == #TERMINATED)
	    ifTrue: [self termErr: 'block'.  ^ nil].
	<primitive 145  self 2>.
	^ self state

|  resume
	(self state == #TERMINATED)
	    ifTrue: [self termErr: 'resume'.  ^ nil].
	<primitive 145  self 0>.
	^ self state

|  suspend
	(self state == #TERMINATED)
	    ifTrue: [self termErr: 'suspend'.  ^ nil].
	<primitive 145  self 1>.
	^ self state

|  state  | pstate |
	pstate <- <primitive 146  self>.
	(pstate = 0) ifTrue: [pstate <- #READY.  ^ pstate].
	(pstate = 1) ifTrue: [pstate <- #SUSPENDED.  ^ pstate].
	(pstate = 2) ifTrue: [pstate <- #BLOCKED.  ^ pstate].
	(pstate = 3) ifTrue: [pstate <- #BLOCKED.  ^ pstate].
	(pstate >= 4) ifTrue: [pstate <- #TERMINATED.  ^ pstate]

|  terminate
	<primitive 142  self>.
	^ self state

|  termErr: msgName
	('Cannot ',msgName,' a terminated process.') print

|  unblock
	(self state == #TERMINATED)
	    ifTrue: [self termErr: 'unblock'.  ^ nil].
	<primitive 145  self 3>.
	^ self state

|  yield
	^ nil
]
SHAR_EOF
if test 1003 -ne "`wc -c < 'process.st'`"
then
	echo shar: error transmitting "'process.st'" '(should have been 1003 characters)'
fi
fi # end of overwriting check
if test -f 'radian.st'
then
	echo shar: will not over-write existing file "'radian.st'"
else
cat << \SHAR_EOF > 'radian.st'
Class Radian :Magnitude
| value |
[
        new: x
                value <- <primitive 80 (x asFloat) >

|	< arg
		^ value < arg asFloat

|	= arg
		^ value = arg asFloat

|       sin
                ^ <primitive 81 value>

|       cos
                ^ <primitive 82 value>

|       tan
                ^ <primitive 81 value> / <primitive 82 value>

|       asFloat
                ^ value

|       printString
                ^ value asString , ' radians'
]
SHAR_EOF
if test 459 -ne "`wc -c < 'radian.st'`"
then
	echo shar: error transmitting "'radian.st'" '(should have been 459 characters)'
fi
fi # end of overwriting check
if test -f 'random.st'
then
	echo shar: will not over-write existing file "'random.st'"
else
cat << \SHAR_EOF > 'random.st'
Class Random
| seed |
[
        new
                seed <- 1
|
	randomize
		seed <- <primitive 161>
|
        first
                ^ <primitive 32 (seed <- <primitive 35 seed > ) >
|
        next
                ^ <primitive 32 (seed <- <primitive 35 seed > ) >
|
	between: low and: high
		^ (self next * (high - low)) + low
|
	randInteger: limit
		^ (self next * limit) truncated + 1
|
	next: n			| newa |
		newa <- Array new: n.
		(1 to: n) do: [:x | newa at: x put: self next].
		^ newa
]
SHAR_EOF
if test 494 -ne "`wc -c < 'random.st'`"
then
	echo shar: error transmitting "'random.st'" '(should have been 494 characters)'
fi
fi # end of overwriting check
if test -f 'scollection.st'
then
	echo shar: will not over-write existing file "'scollection.st'"
else
cat << \SHAR_EOF > 'scollection.st'
Class SequenceableCollection :KeyedCollection
[
	, aCollection
		^ self coerce: (List new ; 
					addAllLast: self ;
					addAllLast: aCollection )
|
        collect: aBlock 
		^ self coerce:
		     (self inject: List new
                           into: [:x :y | x addLast: (aBlock value: y) . x ] )
|
	copyFrom: start to: stop                | newcol |
                newcol <- List new.
		(start to: stop) do: [:i | newcol addLast: (self at: i)].
                ^ self coerce: newcol
|
	copyWith: newElement
		^ self coerce: (List new ; 
					addAllLast: self ;
					addLast: newElement )
|
	copyWithout: oldElement                 | newcol |
                newcol <- List new.
                self do: [ :x | (x == oldElement) 
                                ifFalse: [ newcol addLast: x ]].
                ^ self coerce: newcol
|
	equals: aSubCollection startingAt: anIndex      | i |
                i <- 0.
                self do: [:x |
                        (x = (aSubCollection at: (anIndex + i)
                                            ifAbsent: [^ false]))
                                ifFalse: [^ false].
                        i <- i + 1].
                ^ true
|
	findFirst: aBlock
		^ self findFirst: aBlock 
			ifAbsent: [self error: 'first element not found']
|
	findFirst: aBlock ifAbsent: exceptionBlock
                self do: [:x | (aBlock value: x) 
				ifTrue: [ ^ self currentKey]].
                ^ exceptionBlock value
|
	findLast: aBlock
		self findLast: aBlock
			ifAbsent: [self error: 'last element not found']
|
	findLast: aBlock ifAbsent: exceptionBlock
                self reverseDo: [:x | (aBlock value: x) 
                                        ifTrue: [ ^ self currentKey]].
                ^ exceptionBlock value
|
	indexOfSubCollection: aSubCollection 
	startingAt: anIndex 
	ifAbsent: exceptionBlock  			| n m |

                n <- anIndex.
                m <- self size - aSubCollection size.
                [n <= m] whileTrue:
                        [(aSubCollection equals: self startingAt: n)
                                ifTrue: [^ n].
                         n <- n + 1].
                ^ exceptionBlock value
|
	indexOfSubCollection: aSubCollection startingAt: anIndex
                ^ self indexOfSubCollection: aSubCollection 
		       startingAt: anIndex
                       ifAbsent: [ self error: 'element not found'. nil]
|
	last
                ^ (0 = self size) ifFalse: [ self at: self lastKey ]
|
	replaceFrom: start to: stop with: repcol
		repcol inject: start
		       into: [:x :y | self at: x put: y. x + 1]
|
	replaceFrom: first to: stop with: repcol startingAt: repStart | i |
                i <- 0 .
                [(first + i) <= stop] whileTrue:
                        [self at: (first + i)
                              put: (repcol at: i + repStart).
			 i <- i + 1 ]
|
        reverseDo: aBlock                       | n m |
                n <- self lastKey.  m <- self firstKey.
                [n >= m] whileTrue:
                        [(self includesKey: n) ifTrue:
                                [aBlock value: (self at: n)].
                         n <- n - 1].
                ^ nil
|
	reversed                | newar i |
                newar <- Array new: (i <- self size).
                self do: [:x | newar at: i put: x. i <- i - 1].
                ^ self coerce: newar
|
	select: aBlock          
		^ self coerce:
		     (self inject: List new
                           into: [:x :y | (aBlock value: y)
                                           ifTrue: [x addLast: y]. x ] )
|
	sort
		^ self sort: [:x :y | x <= y]
|
	sort: sortBlock		| index temp newArray |
		newArray <- self asArray.
		(2 to: newArray size) do:
		  [ :highIndex | index <- highIndex - 1.
			[(index >= 1) and:
			   [(sortBlock value: (newArray at: index)
				      value: (newArray at: (index + 1))) not]]
			   whileTrue: [temp <- newArray at: index.
				       newArray at: index 
						put: (newArray at: index + 1).
				       newArray at: index + 1 put: temp.
				       index <- index - 1 ]].
		^ self coerce: newArray

|
	with: aSequenceableCollection do: aBlock        | arg1 arg2 |
                arg1 <- self first. arg2 <- aSequenceableCollection first.
                [ arg1 notNil] whileTrue:
                        [ aBlock value: arg1 value: arg2.
                          arg1 <- self next.
                          arg2 <- aSequenceableCollection next].
                ^ nil

]
SHAR_EOF
if test 4499 -ne "`wc -c < 'scollection.st'`"
then
	echo shar: error transmitting "'scollection.st'" '(should have been 4499 characters)'
fi
fi # end of overwriting check
if test -f 'semaphore.st'
then
	echo shar: will not over-write existing file "'semaphore.st'"
else
cat << \SHAR_EOF > 'semaphore.st'
Class  Semaphore :List
| excessSignals |

[  new
	excessSignals <- 0

|  new: aNumber
	excessSignals <- aNumber

|  signal
	<primitive 148>.	"start atomic action"
	(self isEmpty)
	  ifTrue: [excessSignals <- excessSignals + 1]
	  ifFalse: [self removeFirst unblock].
	<primitive 149>		"end atomic action"

|  wait
	<primitive 148>.	"start atomic actions"
	(excessSignals = 0)
	  ifTrue: [self addLast: selfProcess.
		   selfProcess block]
	  ifFalse: [excessSignals <- excessSignals - 1].
	<primitive 149>		"end atomic actions"
]
SHAR_EOF
if test 530 -ne "`wc -c < 'semaphore.st'`"
then
	echo shar: error transmitting "'semaphore.st'" '(should have been 530 characters)'
fi
fi # end of overwriting check
if test -f 'set.st'
then
	echo shar: will not over-write existing file "'set.st'"
else
cat << \SHAR_EOF > 'set.st'
Class Set :Collection
| list |
[
        new
                list <- List new

|       add: newElement
		(list includes: newElement)
			ifFalse: [list add: newElement]

|       remove: oldElement ifAbsent: exceptionBlock
		list remove: oldElement ifAbsent: exceptionBlock

|       size
                ^ list size

|       occurrencesOf: anElement
                ^ (list includes: anElement) ifTrue: [1] ifFalse: [0]

|       first
                ^ list first

|       next
                ^ list next
]
SHAR_EOF
if test 506 -ne "`wc -c < 'set.st'`"
then
	echo shar: error transmitting "'set.st'" '(should have been 506 characters)'
fi
fi # end of overwriting check
if test -f 'smalltalk.st'
then
	echo shar: will not over-write existing file "'smalltalk.st'"
else
cat << \SHAR_EOF > 'smalltalk.st'
Class Smalltalk :Dictionary
[
	date
		^ <primitive 160 >
|
	debug: n
		^ <primitive 8 2 n>
|
	display
		^ <primitive 8 1 1>
|
	displayAssign
		^ <primitive 8 1 2>
|
	doPrimitive: primNumber withArguments: argArray
		^ <primitive 30 primNumber argArray>
|
	noDisplay
		^ <primitive 8 1 0>
|
	perform: aMessage withArguments: argArray
		^ <primitive 143 argArray aMessage >
|
	sh: command
		^ <primitive 125 command >
|
	time: aBlock		| start |
		start <- <primitive 161>.
		aBlock value.
		^ <primitive 161> - start
]
SHAR_EOF
if test 517 -ne "`wc -c < 'smalltalk.st'`"
then
	echo shar: error transmitting "'smalltalk.st'" '(should have been 517 characters)'
fi
fi # end of overwriting check
if test -f 'string.st'
then
	echo shar: will not over-write existing file "'string.st'"
else
cat << \SHAR_EOF > 'string.st'
Class String :ArrayedCollection
[
	, aString
		^ <primitive 103 self aString>
|
	= aString
		^ <primitive 6 self aString>
			ifTrue:  [<primitive 101 self aString> = 0]
			ifFalse: [self compareError]
|
	< aString
		^ <primitive 6 self aString>
			ifTrue:  [<primitive 101 self aString> < 0]
			ifFalse: [self compareError]
|
	<=  aString
		^ <primitive 6 self aString>
			ifTrue:  [<primitive 101 self aString> <= 0]
			ifFalse: [self compareError]
|
	>=  aString
		^ <primitive 6 self aString>
			ifTrue:  [<primitive 101 self aString> >= 0]
			ifFalse: [self compareError]
|
	>  aString
		^ <primitive 6 self aString>
			ifTrue:  [<primitive 101 self aString> > 0]
			ifFalse: [self compareError]
|
	asSymbol
		^ <primitive 108 self>
|
	at: aNumber
		^ <primitive 104 self aNumber>
|
	at: aNumber put: aChar
		<primitive 105 self aNumber aChar>
|
	compareError
		^ self error: 'strings can only be compared to strings'
|
	copyFrom: start to: stop
		^ <primitive 106 self start (stop - start + 1) >
|
	copyFrom: start length: len
		^ <primitive 106 self start len >
|
	deepCopy
		^ <primitive 107 self >
|
	new: size
		^ <primitive 115 size>
|
	printString
		^ <primitive 109 self>
|
	print
		<primitive 121 self>
|
	size
		^ <primitive 100 self>
|
	sameAs: aString
		^ <primitive 6 self aString>
			ifTrue:  [<primitive 102 self aString>]
			ifFalse: [self compareError]
]
SHAR_EOF
if test 1376 -ne "`wc -c < 'string.st'`"
then
	echo shar: error transmitting "'string.st'" '(should have been 1376 characters)'
fi
fi # end of overwriting check
if test -f 'symbol.st'
then
	echo shar: will not over-write existing file "'symbol.st'"
else
cat << \SHAR_EOF > 'symbol.st'
Class Symbol
[
	== aSymbol
		^ <primitive 6 self aSymbol >
			ifTrue:  [<primitive 91 self aSymbol >]
			ifFalse: [false]
|
	printString
		^ <primitive 92 self>
|
	asString
		^ <primitive 93 self>
]

SHAR_EOF
if test 200 -ne "`wc -c < 'symbol.st'`"
then
	echo shar: error transmitting "'symbol.st'" '(should have been 200 characters)'
fi
fi # end of overwriting check
if test -f 'test.st'
then
	echo shar: will not over-write existing file "'test.st'"
else
cat << \SHAR_EOF > 'test.st'
Class Test
| var |
[
	printString
		^ 'test value ', var printString
|
	set: aVal
		var <- aVal
]

SHAR_EOF
if test 99 -ne "`wc -c < 'test.st'`"
then
	echo shar: error transmitting "'test.st'" '(should have been 99 characters)'
fi
fi # end of overwriting check
if test -f 'tests.st'
then
	echo shar: will not over-write existing file "'tests.st'"
else
cat << \SHAR_EOF > 'tests.st'
Class One
| two |
[
	start
		^ self one
|
	one
		two <- Two new.
		two two: self
|
	three
		two four
]
Class Two
[
	two: back
		back three
|
	four
		'in four' print.
		self gak
]

SHAR_EOF
if test 180 -ne "`wc -c < 'tests.st'`"
then
	echo shar: error transmitting "'tests.st'" '(should have been 180 characters)'
fi
fi # end of overwriting check
if test -f 'true.st'
then
	echo shar: will not over-write existing file "'true.st'"
else
cat << \SHAR_EOF > 'true.st'
Class True :Boolean
[
        ifTrue: trueAlternativeBlock ifFalse: falseAlternativeBlock
                ^ trueAlternativeBlock value

!       ifFalse: falseAlternativeBlock ifTrue: trueAlternativeBlock
                ^ trueAlternativeBlock value

!       ifTrue: trueAlternativeBlock
                ^ trueAlternativeBlock value

!       ifFalse: falseAlternativeBlock
                ^ nil

|       not
                ^ false
]
SHAR_EOF
if test 433 -ne "`wc -c < 'true.st'`"
then
	echo shar: error transmitting "'true.st'" '(should have been 433 characters)'
fi
fi # end of overwriting check
if test -f 'class.p'
then
	echo shar: will not over-write existing file "'class.p'"
else
cat << \SHAR_EOF > 'class.p'
temp <- <primitive 110 10 >
<primitive 112 temp 1		" view " \
	#( #[ 32 250 1 156 242 245] \
	#(  ) ) >

<primitive 112 temp 2		" variables " \
	#( #[ 32 250 1 158 243 245] \
	#(  ) ) >

<primitive 112 temp 3		" superClass " \
	#( #[ 32 250 1 151 243 245] \
	#(  ) ) >

<primitive 112 temp 4		" respondsTo: " \
	#( #[ 32 114 34 162 247 18 34 33 250 2 155 247 2 91 243 \
 242 34 10 46 241 114 242 249 22 242 92 243 245] \
	#(  ) ) >

<primitive 112 temp 5		" respondsTo " \
	#( #[ 32 250 1 154 242 245] \
	#(  ) ) >

<primitive 112 temp 6		" printString " \
	#( #[ 32 250 1 152 243 245] \
	#(  ) ) >

<primitive 112 temp 7		" new: " \
	#( #[ 32 250 1 151 114 34 250 1 3 247 4 34 160 241 115 \
 242 32 35 250 2 153 115 32 48 250 2 155 247 5 35 \
 33 176 241 115 242 35 243 245] \
	#( #new:  ) ) >

<primitive 112 temp 8		" new " \
	#( #[ 32 250 1 151 113 33 250 1 3 247 4 33 160 241 114 \
 242 32 34 250 2 153 114 32 48 250 2 155 247 4 34 \
 160 241 114 242 34 243 245] \
	#( #new  ) ) >

<primitive 112 temp 9		" list " \
	#( #[ 32 250 1 157 242 245] \
	#(  ) ) >

<primitive 112 temp 10		" edit " \
	#( #[ 32 250 1 150 242 245] \
	#(  ) ) >

<primitive 98 #Class \
	<primitive 97 #Class #Object #/u/smalltalk/prelude/class.st \
	#(  ) \
	#( #view #variables #superClass #respondsTo: #respondsTo #printString #new: #new #list #edit  ) \
	temp 4 4 > >

SHAR_EOF
if test 1351 -ne "`wc -c < 'class.p'`"
then
	echo shar: error transmitting "'class.p'" '(should have been 1351 characters)'
fi
fi # end of overwriting check
if test -f 'object.p'
then
	echo shar: will not over-write existing file "'object.p'"
else
cat << \SHAR_EOF > 'object.p'
temp <- <primitive 110 21 >
<primitive 112 temp 1		" shallowCopy " \
	#( #[ 32 250 1 4 113 33 80 199 247 4 32 243 248 26 242 \
 32 164 160 114 81 33 178 225 3 11 34 35 32 35 250 \
 2 111 250 3 112 243 179 242 34 243 242 245] \
	#(  ) ) >

<primitive 112 temp 2		" respondsTo: " \
	#( #[ 32 164 33 11 41 243 245] \
	#(  ) ) >

<primitive 112 temp 3		" printString " \
	#( #[ 32 10 16 243 245] \
	#(  ) ) >

<primitive 112 temp 4		" print " \
	#( #[ 32 169 250 1 121 242 245] \
	#(  ) ) >

<primitive 112 temp 5		" notNil " \
	#( #[ 91 243 245] \
	#(  ) ) >

<primitive 112 temp 6		" next " \
	#( #[ 93 243 245] \
	#(  ) ) >

<primitive 112 temp 7		" isNil " \
	#( #[ 92 243 245] \
	#(  ) ) >

<primitive 112 temp 8		" isMemberOf: " \
	#( #[ 33 32 164 181 243 245] \
	#(  ) ) >

<primitive 112 temp 9		" isKindOf: " \
	#( #[ 32 164 114 34 162 247 16 34 33 181 247 2 91 243 242 \
 34 10 46 241 114 242 249 20 242 92 243 245] \
	#(  ) ) >

<primitive 112 temp 10		" first " \
	#( #[ 32 243 245] \
	#(  ) ) >

<primitive 112 temp 11		" error: " \
	#( #[ 33 32 250 2 122 242 245] \
	#(  ) ) >

<primitive 112 temp 12		" do: " \
	#( #[ 32 166 114 34 162 247 11 33 34 180 242 32 167 241 114 \
 242 249 15 243 245] \
	#(  ) ) >

<primitive 112 temp 13		" deepCopy " \
	#( #[ 32 250 1 4 113 33 80 199 247 4 32 243 248 28 242 \
 32 164 160 114 81 33 178 225 3 13 34 35 32 35 250 \
 2 111 10 20 250 3 112 243 179 242 34 243 242 245] \
	#(  ) ) >

<primitive 112 temp 14		" copy " \
	#( #[ 32 10 42 243 245] \
	#(  ) ) >

<primitive 112 temp 15		" class " \
	#( #[ 32 250 1 1 243 245] \
	#(  ) ) >

<primitive 112 temp 16		" asSymbol " \
	#( #[ 32 10 16 10 17 243 245] \
	#(  ) ) >

<primitive 112 temp 17		" asString " \
	#( #[ 32 164 169 243 245] \
	#(  ) ) >

<primitive 112 temp 18		" ~= " \
	#( #[ 32 33 201 172 243 245] \
	#(  ) ) >

<primitive 112 temp 19		" = " \
	#( #[ 32 33 181 243 245] \
	#(  ) ) >

<primitive 112 temp 20		" ~~ " \
	#( #[ 32 33 181 172 243 245] \
	#(  ) ) >

<primitive 112 temp 21		" == " \
	#( #[ 32 33 250 2 7 243 245] \
	#(  ) ) >

<primitive 98 #Object \
	<primitive 97 #Object #Object #/u/smalltalk/prelude/object.st \
	#(  ) \
	#( #shallowCopy #respondsTo: #printString #print #notNil #next #isNil #isMemberOf: #isKindOf: #first #error: #do: #deepCopy #copy #class #asSymbol #asString #~= #= #~~ #==  ) \
	temp 4 7 > >

SHAR_EOF
if test 2344 -ne "`wc -c < 'object.p'`"
then
	echo shar: error transmitting "'object.p'" '(should have been 2344 characters)'
fi
fi # end of overwriting check
if test -f 'string.p'
then
	echo shar: will not over-write existing file "'string.p'"
else
cat << \SHAR_EOF > 'string.p'
temp <- <primitive 110 18 >
<primitive 112 temp 1		" sameAs: " \
	#( #[ 32 33 250 2 6 247 7 32 33 250 2 102 248 4 242 \
 32 10 19 243 245] \
	#(  ) ) >

<primitive 112 temp 2		" size " \
	#( #[ 32 250 1 100 243 245] \
	#(  ) ) >

<primitive 112 temp 3		" print " \
	#( #[ 32 250 1 121 242 245] \
	#(  ) ) >

<primitive 112 temp 4		" printString " \
	#( #[ 32 250 1 109 243 245] \
	#(  ) ) >

<primitive 112 temp 5		" new: " \
	#( #[ 33 250 1 115 243 245] \
	#(  ) ) >

<primitive 112 temp 6		" deepCopy " \
	#( #[ 32 250 1 107 243 245] \
	#(  ) ) >

<primitive 112 temp 7		" copyFrom:length: " \
	#( #[ 32 33 34 250 3 106 243 245] \
	#(  ) ) >

<primitive 112 temp 8		" copyFrom:to: " \
	#( #[ 32 33 34 33 193 81 192 250 3 106 243 245] \
	#(  ) ) >

<primitive 112 temp 9		" compareError " \
	#( #[ 32 48 188 243 245] \
	#( 'strings can only be compared to strings'  ) ) >

<primitive 112 temp 10		" at:put: " \
	#( #[ 32 33 34 250 3 105 242 245] \
	#(  ) ) >

<primitive 112 temp 11		" at: " \
	#( #[ 32 33 250 2 104 243 245] \
	#(  ) ) >

<primitive 112 temp 12		" asSymbol " \
	#( #[ 32 250 1 108 243 245] \
	#(  ) ) >

<primitive 112 temp 13		" > " \
	#( #[ 32 33 250 2 6 247 9 32 33 250 2 101 80 204 248 \
 4 242 32 10 19 243 245] \
	#(  ) ) >

<primitive 112 temp 14		" >= " \
	#( #[ 32 33 250 2 6 247 9 32 33 250 2 101 80 203 248 \
 4 242 32 10 19 243 245] \
	#(  ) ) >

<primitive 112 temp 15		" <= " \
	#( #[ 32 33 250 2 6 247 9 32 33 250 2 101 80 200 248 \
 4 242 32 10 19 243 245] \
	#(  ) ) >

<primitive 112 temp 16		" < " \
	#( #[ 32 33 250 2 6 247 9 32 33 250 2 101 80 199 248 \
 4 242 32 10 19 243 245] \
	#(  ) ) >

<primitive 112 temp 17		" = " \
	#( #[ 32 33 250 2 6 247 9 32 33 250 2 101 80 201 248 \
 4 242 32 10 19 243 245] \
	#(  ) ) >

<primitive 112 temp 18		" , " \
	#( #[ 32 33 250 2 103 243 245] \
	#(  ) ) >

<primitive 98 #String \
	<primitive 97 #String #ArrayedCollection #/u/smalltalk/prelude/string.st \
	#(  ) \
	#( #sameAs: #size #print #printString #new: #deepCopy #copyFrom:length: #copyFrom:to: #compareError #at:put: #at: #asSymbol #> #>= #<= #< #= #,  ) \
	temp 3 5 > >

SHAR_EOF
if test 2112 -ne "`wc -c < 'string.p'`"
then
	echo shar: error transmitting "'string.p'" '(should have been 2112 characters)'
fi
fi # end of overwriting check
if test -f 'larray.p'
then
	echo shar: will not over-write existing file "'larray.p'"
else
cat << \SHAR_EOF > 'larray.p'
temp <- <primitive 110 1 >
<primitive 112 temp 1		" nothing " \
	#( #[ 81 242 245] \
	#(  ) ) >

<primitive 98 #ArrayedCollection \
	<primitive 97 #ArrayedCollection #Object #/u/smalltalk/prelude/larray.st \
	#(  ) \
	#( #nothing  ) \
	temp 1 2 > >

SHAR_EOF
if test 250 -ne "`wc -c < 'larray.p'`"
then
	echo shar: error transmitting "'larray.p'" '(should have been 250 characters)'
fi
fi # end of overwriting check
if test -f 'nil.p'
then
	echo shar: will not over-write existing file "'nil.p'"
else
cat << \SHAR_EOF > 'nil.p'
temp <- <primitive 110 3 >
<primitive 112 temp 1		" printString " \
	#( #[ 48 243 245] \
	#( 'nil'  ) ) >

<primitive 112 temp 2		" notNil " \
	#( #[ 92 243 245] \
	#(  ) ) >

<primitive 112 temp 3		" isNil " \
	#( #[ 91 243 245] \
	#(  ) ) >

<primitive 98 #UndefinedObject \
	<primitive 97 #UndefinedObject #Object #/u/smalltalk/prelude/nil.st \
	#(  ) \
	#( #printString #notNil #isNil  ) \
	temp 1 2 > >

SHAR_EOF
if test 409 -ne "`wc -c < 'nil.p'`"
then
	echo shar: error transmitting "'nil.p'" '(should have been 409 characters)'
fi
fi # end of overwriting check
if test -f 'array.p'
then
	echo shar: will not over-write existing file "'array.p'"
else
cat << \SHAR_EOF > 'array.p'
temp <- <primitive 110 5 >
<primitive 112 temp 1		" size " \
	#( #[ 32 250 1 4 243 245] \
	#(  ) ) >

<primitive 112 temp 2		" printString " \
	#( #[ 48 113 32 250 1 4 114 34 80 204 247 21 32 34 250 \
 2 111 169 49 11 17 33 11 17 113 34 81 193 241 114 \
 242 249 26 242 50 33 11 17 243 245] \
	#( ')' ' ' '#( '  ) ) >

<primitive 112 temp 3		" at:put: " \
	#( #[ 33 81 199 251 6 33 32 250 1 4 204 247 6 32 48 \
 188 242 93 243 242 32 33 34 250 3 112 242 34 243 245 \
] \
	#( 'index error'  ) ) >

<primitive 112 temp 4		" at: " \
	#( #[ 33 81 199 251 6 33 32 250 1 4 204 247 6 32 48 \
 188 242 93 243 242 32 33 250 2 111 243 245] \
	#( 'index error'  ) ) >

<primitive 112 temp 5		" new: " \
	#( #[ 33 250 1 114 243 245] \
	#(  ) ) >

<primitive 98 #Array \
	<primitive 97 #Array #ArrayedCollection #/u/smalltalk/prelude/array.st \
	#(  ) \
	#( #size #printString #at:put: #at: #new:  ) \
	temp 3 4 > >

SHAR_EOF
if test 904 -ne "`wc -c < 'array.p'`"
then
	echo shar: error transmitting "'array.p'" '(should have been 904 characters)'
fi
fi # end of overwriting check
if test -f 'boolean.p'
then
	echo shar: will not over-write existing file "'boolean.p'"
else
cat << \SHAR_EOF > 'boolean.p'
temp <- <primitive 110 6 >
<primitive 112 temp 1		" xor: " \
	#( #[ 32 33 182 243 245] \
	#(  ) ) >

<primitive 112 temp 2		" eqv: " \
	#( #[ 32 33 181 243 245] \
	#(  ) ) >

<primitive 112 temp 3		" or: " \
	#( #[ 32 251 2 33 165 243 245] \
	#(  ) ) >

<primitive 112 temp 4		" and: " \
	#( #[ 32 252 2 33 165 243 245] \
	#(  ) ) >

<primitive 112 temp 5		" | " \
	#( #[ 32 251 1 33 243 245] \
	#(  ) ) >

<primitive 112 temp 6		" & " \
	#( #[ 32 252 1 33 243 245] \
	#(  ) ) >

<primitive 98 #Boolean \
	<primitive 97 #Boolean #Object #/u/smalltalk/prelude/boolean.st \
	#(  ) \
	#( #xor: #eqv: #or: #and: #| #&  ) \
	temp 2 3 > >

SHAR_EOF
if test 634 -ne "`wc -c < 'boolean.p'`"
then
	echo shar: error transmitting "'boolean.p'" '(should have been 634 characters)'
fi
fi # end of overwriting check
if test -f 'true.p'
then
	echo shar: will not over-write existing file "'true.p'"
else
cat << \SHAR_EOF > 'true.p'
temp <- <primitive 110 5 >
<primitive 112 temp 1		" not " \
	#( #[ 92 243 245] \
	#(  ) ) >

<primitive 112 temp 2		" ifFalse: " \
	#( #[ 93 243 245] \
	#(  ) ) >

<primitive 112 temp 3		" ifTrue: " \
	#( #[ 33 165 243 245] \
	#(  ) ) >

<primitive 112 temp 4		" ifFalse:ifTrue: " \
	#( #[ 34 165 243 245] \
	#(  ) ) >

<primitive 112 temp 5		" ifTrue:ifFalse: " \
	#( #[ 33 165 243 245] \
	#(  ) ) >

<primitive 98 #True \
	<primitive 97 #True #Boolean #/u/smalltalk/prelude/true.st \
	#(  ) \
	#( #not #ifFalse: #ifTrue: #ifFalse:ifTrue: #ifTrue:ifFalse:  ) \
	temp 3 2 > >

SHAR_EOF
if test 577 -ne "`wc -c < 'true.p'`"
then
	echo shar: error transmitting "'true.p'" '(should have been 577 characters)'
fi
fi # end of overwriting check
if test -f 'false.p'
then
	echo shar: will not over-write existing file "'false.p'"
else
cat << \SHAR_EOF > 'false.p'
temp <- <primitive 110 5 >
<primitive 112 temp 1		" not " \
	#( #[ 91 243 245] \
	#(  ) ) >

<primitive 112 temp 2		" ifFalse: " \
	#( #[ 33 165 243 245] \
	#(  ) ) >

<primitive 112 temp 3		" ifTrue: " \
	#( #[ 93 243 245] \
	#(  ) ) >

<primitive 112 temp 4		" ifFalse:ifTrue: " \
	#( #[ 33 165 243 245] \
	#(  ) ) >

<primitive 112 temp 5		" ifTrue:ifFalse: " \
	#( #[ 34 165 243 245] \
	#(  ) ) >

<primitive 98 #False \
	<primitive 97 #False #Boolean #/u/smalltalk/prelude/false.st \
	#(  ) \
	#( #not #ifFalse: #ifTrue: #ifFalse:ifTrue: #ifTrue:ifFalse:  ) \
	temp 3 2 > >

SHAR_EOF
if test 580 -ne "`wc -c < 'false.p'`"
then
	echo shar: error transmitting "'false.p'" '(should have been 580 characters)'
fi
fi # end of overwriting check
if test -f 'block.p'
then
	echo shar: will not over-write existing file "'block.p'"
else
cat << \SHAR_EOF > 'block.p'
temp <- <primitive 110 14 >
<primitive 112 temp 1		" value:value:value:value:value: " \
	#( #[ 85 250 1 140 242 245] \
	#(  ) ) >

<primitive 112 temp 2		" value:value:value:value: " \
	#( #[ 84 250 1 140 242 245] \
	#(  ) ) >

<primitive 112 temp 3		" value:value:value: " \
	#( #[ 83 250 1 140 242 245] \
	#(  ) ) >

<primitive 112 temp 4		" value:value: " \
	#( #[ 82 250 1 140 242 245] \
	#(  ) ) >

<primitive 112 temp 5		" value: " \
	#( #[ 81 250 1 140 242 245] \
	#(  ) ) >

<primitive 112 temp 6		" value " \
	#( #[ 80 250 1 140 242 245] \
	#(  ) ) >

<primitive 112 temp 7		" whileFalse: " \
	#( #[ 32 165 246 5 33 165 242 249 9 243 245] \
	#(  ) ) >

<primitive 112 temp 8		" whileFalse " \
	#( #[ 32 165 246 4 93 242 249 8 243 245] \
	#(  ) ) >

<primitive 112 temp 9		" whileTrue: " \
	#( #[ 32 165 247 5 33 165 242 249 9 243 245] \
	#(  ) ) >

<primitive 112 temp 10		" whileTrue " \
	#( #[ 32 165 247 4 93 242 249 8 243 245] \
	#(  ) ) >

<primitive 112 temp 11		" forkWith: " \
	#( #[ 32 33 11 35 10 40 242 93 243 245] \
	#(  ) ) >

<primitive 112 temp 12		" fork " \
	#( #[ 32 10 33 10 40 242 93 243 245] \
	#(  ) ) >

<primitive 112 temp 13		" newProcessWith: " \
	#( #[ 32 33 250 2 141 243 245] \
	#(  ) ) >

<primitive 112 temp 14		" newProcess " \
	#( #[ 32 250 1 141 243 245] \
	#(  ) ) >

<primitive 98 #Block \
	<primitive 97 #Block #Object #/u/smalltalk/prelude/block.st \
	#(  ) \
	#( #value:value:value:value:value: #value:value:value:value: #value:value:value: #value:value: #value: #value #whileFalse: #whileFalse #whileTrue: #whileTrue #forkWith: #fork #newProcessWith: #newProcess  ) \
	temp 6 3 > >

SHAR_EOF
if test 1632 -ne "`wc -c < 'block.p'`"
then
	echo shar: error transmitting "'block.p'" '(should have been 1632 characters)'
fi
fi # end of overwriting check
if test -f 'symbol.p'
then
	echo shar: will not over-write existing file "'symbol.p'"
else
cat << \SHAR_EOF > 'symbol.p'
temp <- <primitive 110 3 >
<primitive 112 temp 1		" asString " \
	#( #[ 32 250 1 93 243 245] \
	#(  ) ) >

<primitive 112 temp 2		" printString " \
	#( #[ 32 250 1 92 243 245] \
	#(  ) ) >

<primitive 112 temp 3		" == " \
	#( #[ 32 33 250 2 6 247 7 32 33 250 2 91 248 2 242 \
 92 243 245] \
	#(  ) ) >

<primitive 98 #Symbol \
	<primitive 97 #Symbol #Object #/u/smalltalk/prelude/symbol.st \
	#(  ) \
	#( #asString #printString #==  ) \
	temp 2 4 > >

SHAR_EOF
if test 452 -ne "`wc -c < 'symbol.p'`"
then
	echo shar: error transmitting "'symbol.p'" '(should have been 452 characters)'
fi
fi # end of overwriting check
if test -f 'magnitude.p'
then
	echo shar: will not over-write existing file "'magnitude.p'"
else
cat << \SHAR_EOF > 'magnitude.p'
temp <- <primitive 110 9 >
<primitive 112 temp 1		" max: " \
	#( #[ 32 33 204 247 3 32 248 2 242 33 243 245] \
	#(  ) ) >

<primitive 112 temp 2		" min: " \
	#( #[ 32 33 199 247 3 32 248 2 242 33 243 245] \
	#(  ) ) >

<primitive 112 temp 3		" between:and: " \
	#( #[ 32 33 203 252 3 32 34 200 243 245] \
	#(  ) ) >

<primitive 112 temp 4		" > " \
	#( #[ 33 32 199 243 245] \
	#(  ) ) >

<primitive 112 temp 5		" >= " \
	#( #[ 32 33 204 251 3 32 33 201 243 245] \
	#(  ) ) >

<primitive 112 temp 6		" ~= " \
	#( #[ 32 33 201 172 243 245] \
	#(  ) ) >

<primitive 112 temp 7		" = " \
	#( #[ 32 33 204 251 3 32 33 199 172 243 245] \
	#(  ) ) >

<primitive 112 temp 8		" < " \
	#( #[ 33 32 204 243 245] \
	#(  ) ) >

<primitive 112 temp 9		" <= " \
	#( #[ 32 33 199 251 3 32 33 201 243 245] \
	#(  ) ) >

<primitive 98 #Magnitude \
	<primitive 97 #Magnitude #Object #/u/smalltalk/prelude/magnitude.st \
	#(  ) \
	#( #max: #min: #between:and: #> #>= #~= #= #< #<=  ) \
	temp 3 4 > >

SHAR_EOF
if test 980 -ne "`wc -c < 'magnitude.p'`"
then
	echo shar: error transmitting "'magnitude.p'" '(should have been 980 characters)'
fi
fi # end of overwriting check
if test -f 'number.p'
then
	echo shar: will not over-write existing file "'number.p'"
else
cat << \SHAR_EOF > 'number.p'
temp <- <primitive 110 30 >
<primitive 112 temp 1		" truncateTo: " \
	#( #[ 32 33 190 10 47 33 194 243 245] \
	#(  ) ) >

<primitive 112 temp 2		" to:by: " \
	#( #[ 5 46 160 241 32 33 34 131 0 242 243 245] \
	#( #from:to:by:  ) ) >

<primitive 112 temp 3		" to: " \
	#( #[ 5 46 160 241 32 33 81 131 0 242 243 245] \
	#( #from:to:by:  ) ) >

<primitive 112 temp 4		" strictlyPositive " \
	#( #[ 32 80 204 243 245] \
	#(  ) ) >

<primitive 112 temp 5		" squared " \
	#( #[ 32 32 194 243 245] \
	#(  ) ) >

<primitive 112 temp 6		" sqrt " \
	#( #[ 32 175 10 43 243 245] \
	#(  ) ) >

<primitive 112 temp 7		" sign " \
	#( #[ 32 80 199 247 3 90 248 11 242 32 80 204 247 3 81 \
 248 2 242 80 243 245] \
	#(  ) ) >

<primitive 112 temp 8		" roundTo: " \
	#( #[ 32 33 190 10 41 33 194 243 245] \
	#(  ) ) >

<primitive 112 temp 9		" reciprocal " \
	#( #[ 48 32 190 243 245] \
	#( 1.00  ) ) >

<primitive 112 temp 10		" raisedTo: " \
	#( #[ 32 175 33 175 11 16 243 245] \
	#(  ) ) >

<primitive 112 temp 11		" radians " \
	#( #[ 5 54 32 175 176 243 245] \
	#(  ) ) >

<primitive 112 temp 12		" positive " \
	#( #[ 32 80 203 243 245] \
	#(  ) ) >

<primitive 112 temp 13		" pi " \
	#( #[ 32 48 194 243 245] \
	#( 3.1415926  ) ) >

<primitive 112 temp 14		" negative " \
	#( #[ 32 80 199 243 245] \
	#(  ) ) >

<primitive 112 temp 15		" negated " \
	#( #[ 80 32 193 243 245] \
	#(  ) ) >

<primitive 112 temp 16		" log: " \
	#( #[ 32 10 32 33 10 32 190 243 245] \
	#(  ) ) >

<primitive 112 temp 17		" ln " \
	#( #[ 32 175 10 32 243 245] \
	#(  ) ) >

<primitive 112 temp 18		" gamma " \
	#( #[ 32 175 10 26 243 245] \
	#(  ) ) >

<primitive 112 temp 19		" exp " \
	#( #[ 32 175 10 23 243 245] \
	#(  ) ) >

<primitive 112 temp 20		" abs " \
	#( #[ 32 80 199 247 5 80 32 193 248 2 242 32 243 245] \
	#(  ) ) >

<primitive 112 temp 21		" @ " \
	#( #[ 5 53 160 32 11 50 33 11 51 243 245] \
	#(  ) ) >

<primitive 112 temp 22		" ^ " \
	#( #[ 32 175 33 175 11 16 243 245] \
	#(  ) ) >

<primitive 112 temp 23		" / " \
	#( #[ 32 33 11 34 33 32 11 34 190 243 245] \
	#(  ) ) >

<primitive 112 temp 24		" * " \
	#( #[ 32 33 11 34 33 32 11 34 194 243 245] \
	#(  ) ) >

<primitive 112 temp 25		" - " \
	#( #[ 32 33 11 34 33 32 11 34 193 243 245] \
	#(  ) ) >

<primitive 112 temp 26		" + " \
	#( #[ 32 33 11 34 33 32 11 34 192 243 245] \
	#(  ) ) >

<primitive 112 temp 27		" > " \
	#( #[ 32 33 11 34 33 32 11 34 204 243 245] \
	#(  ) ) >

<primitive 112 temp 28		" < " \
	#( #[ 32 33 11 34 33 32 11 34 199 243 245] \
	#(  ) ) >

<primitive 112 temp 29		" = " \
	#( #[ 32 33 11 34 33 32 11 34 201 243 245] \
	#(  ) ) >

<primitive 112 temp 30		" maxtype: " \
	#( #[ 32 33 250 2 9 247 3 32 248 4 242 33 32 191 243 \
 245] \
	#(  ) ) >

<primitive 98 #Number \
	<primitive 97 #Number #Magnitude #/u/smalltalk/prelude/number.st \
	#(  ) \
	#( #truncateTo: #to:by: #to: #strictlyPositive #squared #sqrt #sign #roundTo: #reciprocal #raisedTo: #radians #positive #pi #negative #negated #log: #ln #gamma #exp #abs #@ #^ #/ #* #- #+ #> #< #= #maxtype:  ) \
	temp 3 6 > >

SHAR_EOF
if test 3046 -ne "`wc -c < 'number.p'`"
then
	echo shar: error transmitting "'number.p'" '(should have been 3046 characters)'
fi
fi # end of overwriting check
if test -f 'integer.p'
then
	echo shar: will not over-write existing file "'integer.p'"
else
cat << \SHAR_EOF > 'integer.p'
temp <- <primitive 110 31 >
<primitive 112 temp 1		" timesRepeat: " \
	#( #[ 80 114 34 32 199 247 11 33 165 242 34 81 192 241 114 \
 242 249 16 242 245] \
	#(  ) ) >

<primitive 112 temp 2		" rem: " \
	#( #[ 32 33 250 2 6 247 7 32 33 250 2 29 248 4 242 \
 32 10 35 243 245] \
	#(  ) ) >

<primitive 112 temp 3		" radix: " \
	#( #[ 32 33 250 2 26 243 245] \
	#(  ) ) >

<primitive 112 temp 4		" quo: " \
	#( #[ 32 33 250 2 6 247 7 32 33 250 2 28 248 4 242 \
 32 10 35 243 245] \
	#(  ) ) >

<primitive 112 temp 5		" odd " \
	#( #[ 32 82 205 80 202 243 245] \
	#(  ) ) >

<primitive 112 temp 6		" noMask: " \
	#( #[ 80 32 33 197 201 243 245] \
	#(  ) ) >

<primitive 112 temp 7		" lcm: " \
	#( #[ 32 33 250 2 6 247 10 32 33 194 32 33 11 27 206 \
 248 4 242 32 10 35 243 245] \
	#(  ) ) >

<primitive 112 temp 8		" highBit " \
	#( #[ 32 250 1 34 243 245] \
	#(  ) ) >

<primitive 112 temp 9		" gcd: " \
	#( #[ 32 33 250 2 6 247 7 32 33 250 2 20 248 4 242 \
 32 10 35 243 245] \
	#(  ) ) >

<primitive 112 temp 10		" factorial " \
	#( #[ 32 250 1 38 243 245] \
	#(  ) ) >

<primitive 112 temp 11		" even " \
	#( #[ 32 82 205 80 201 243 245] \
	#(  ) ) >

<primitive 112 temp 12		" bitXor: " \
	#( #[ 32 33 250 2 24 243 245] \
	#(  ) ) >

<primitive 112 temp 13		" bitShift: " \
	#( #[ 32 33 250 2 25 243 245] \
	#(  ) ) >

<primitive 112 temp 14		" bitOr: " \
	#( #[ 32 33 250 2 22 243 245] \
	#(  ) ) >

<primitive 112 temp 15		" bitInvert " \
	#( #[ 32 250 1 33 243 245] \
	#(  ) ) >

<primitive 112 temp 16		" bitAt: " \
	#( #[ 32 33 250 2 21 243 245] \
	#(  ) ) >

<primitive 112 temp 17		" bitAnd: " \
	#( #[ 32 33 250 2 23 243 245] \
	#(  ) ) >

<primitive 112 temp 18		" asString " \
	#( #[ 32 250 1 37 243 245] \
	#(  ) ) >

<primitive 112 temp 19		" asFloat " \
	#( #[ 32 250 1 39 243 245] \
	#(  ) ) >

<primitive 112 temp 20		" asCharacter " \
	#( #[ 32 250 1 36 243 245] \
	#(  ) ) >

<primitive 112 temp 21		" anyMask: " \
	#( #[ 80 32 33 250 2 23 202 243 245] \
	#(  ) ) >

<primitive 112 temp 22		" allMask: " \
	#( #[ 33 32 33 250 2 23 201 243 245] \
	#(  ) ) >

<primitive 112 temp 23		" \\ " \
	#( #[ 32 33 250 2 6 247 18 32 32 80 199 247 3 90 248 \
 2 242 81 194 114 34 33 205 248 4 242 32 10 35 243 \
 245] \
	#(  ) ) >

<primitive 112 temp 24		" // " \
	#( #[ 32 33 250 2 6 247 7 32 33 250 2 19 248 4 242 \
 32 10 35 243 245] \
	#(  ) ) >

<primitive 112 temp 25		" / " \
	#( #[ 32 175 33 190 243 245] \
	#(  ) ) >

<primitive 112 temp 26		" * " \
	#( #[ 32 33 250 2 6 247 7 32 33 250 2 18 248 5 242 \
 32 33 145 0 243 245] \
	#( #*  ) ) >

<primitive 112 temp 27		" - " \
	#( #[ 32 33 250 2 6 247 7 32 33 250 2 11 248 5 242 \
 32 33 145 0 243 245] \
	#( #-  ) ) >

<primitive 112 temp 28		" + " \
	#( #[ 32 33 250 2 6 247 7 32 33 250 2 10 248 5 242 \
 32 33 145 0 243 245] \
	#( #+  ) ) >

<primitive 112 temp 29		" < " \
	#( #[ 32 33 250 2 6 247 7 32 33 250 2 12 248 5 242 \
 32 33 145 0 243 245] \
	#( #<  ) ) >

<primitive 112 temp 30		" > " \
	#( #[ 32 33 250 2 6 247 7 32 33 250 2 13 248 5 242 \
 32 33 145 0 243 245] \
	#( #>  ) ) >

<primitive 112 temp 31		" = " \
	#( #[ 32 33 250 2 6 247 7 32 33 250 2 16 248 5 242 \
 32 33 145 0 243 245] \
	#( #=  ) ) >

<primitive 98 #Integer \
	<primitive 97 #Integer #Number #/u/smalltalk/prelude/integer.st \
	#(  ) \
	#( #timesRepeat: #rem: #radix: #quo: #odd #noMask: #lcm: #highBit #gcd: #factorial #even #bitXor: #bitShift: #bitOr: #bitInvert #bitAt: #bitAnd: #asString #asFloat #asCharacter #anyMask: #allMask: #\\ #// #/ #* #- #+ #< #> #=  ) \
	temp 3 5 > >

SHAR_EOF
if test 3531 -ne "`wc -c < 'integer.p'`"
then
	echo shar: error transmitting "'integer.p'" '(should have been 3531 characters)'
fi
fi # end of overwriting check
if test -f 'char.p'
then
	echo shar: will not over-write existing file "'char.p'"
else
cat << \SHAR_EOF > 'char.p'
temp <- <primitive 110 18 >
<primitive 112 temp 1		" printString " \
	#( #[ 48 32 250 1 58 11 17 243 245] \
	#( '$'  ) ) >

<primitive 112 temp 2		" isVowel " \
	#( #[ 32 250 1 51 243 245] \
	#(  ) ) >

<primitive 112 temp 3		" isUppercase " \
	#( #[ 32 48 49 218 243 245] \
	#( $A $Z  ) ) >

<primitive 112 temp 4		" isSeparator " \
	#( #[ 32 250 1 55 243 245] \
	#(  ) ) >

<primitive 112 temp 5		" isLowercase " \
	#( #[ 32 48 49 218 243 245] \
	#( $a $z  ) ) >

<primitive 112 temp 6		" isLetter " \
	#( #[ 32 10 28 251 3 32 10 29 243 245] \
	#(  ) ) >

<primitive 112 temp 7		" isDigit " \
	#( #[ 32 48 49 218 243 245] \
	#( $0 $9  ) ) >

<primitive 112 temp 8		" isAlphaNumeric " \
	#( #[ 32 250 1 56 243 245] \
	#(  ) ) >

<primitive 112 temp 9		" digitValue " \
	#( #[ 32 250 1 50 241 113 161 247 3 32 48 188 242 33 243 \
 245] \
	#( 'digitValue on nondigit char'  ) ) >

<primitive 112 temp 10		" compareError " \
	#( #[ 32 48 188 243 245] \
	#( 'char cannot be compared to non char'  ) ) >

<primitive 112 temp 11		" asString " \
	#( #[ 32 250 1 58 243 245] \
	#(  ) ) >

<primitive 112 temp 12		" asUppercase " \
	#( #[ 32 250 1 53 247 6 32 250 1 57 248 2 242 32 243 \
 245] \
	#(  ) ) >

<primitive 112 temp 13		" asLowercase " \
	#( #[ 32 250 1 54 247 6 32 250 1 57 248 2 242 32 243 \
 245] \
	#(  ) ) >

<primitive 112 temp 14		" asciiValue " \
	#( #[ 32 250 1 59 243 245] \
	#(  ) ) >

<primitive 112 temp 15		" > " \
	#( #[ 32 33 250 2 6 247 7 32 33 250 2 43 248 4 242 \
 32 10 19 243 245] \
	#(  ) ) >

<primitive 112 temp 16		" = " \
	#( #[ 32 33 250 2 6 247 7 32 33 250 2 46 248 4 242 \
 32 10 19 243 245] \
	#(  ) ) >

<primitive 112 temp 17		" < " \
	#( #[ 32 33 250 2 6 247 7 32 33 250 2 42 248 4 242 \
 32 10 19 243 245] \
	#(  ) ) >

<primitive 112 temp 18		" == " \
	#( #[ 32 33 250 2 6 247 7 32 33 250 2 46 248 2 242 \
 92 243 245] \
	#(  ) ) >

<primitive 98 #Char \
	<primitive 97 #Char #Magnitude #/u/smalltalk/prelude/char.st \
	#(  ) \
	#( #printString #isVowel #isUppercase #isSeparator #isLowercase #isLetter #isDigit #isAlphaNumeric #digitValue #compareError #asString #asUppercase #asLowercase #asciiValue #> #= #< #==  ) \
	temp 2 4 > >

SHAR_EOF
if test 2174 -ne "`wc -c < 'char.p'`"
then
	echo shar: error transmitting "'char.p'" '(should have been 2174 characters)'
fi
fi # end of overwriting check
if test -f 'float.p'
then
	echo shar: will not over-write existing file "'float.p'"
else
cat << \SHAR_EOF > 'float.p'
temp <- <primitive 110 25 >
<primitive 112 temp 1		" truncated " \
	#( #[ 32 48 199 247 6 32 250 1 73 248 5 242 32 250 1 \
 72 243 245] \
	#( 0.0  ) ) >

<primitive 112 temp 2		" sqrt " \
	#( #[ 32 250 1 71 243 245] \
	#(  ) ) >

<primitive 112 temp 3		" rounded " \
	#( #[ 32 48 192 250 1 72 243 245] \
	#( 0.5  ) ) >

<primitive 112 temp 4		" radix: " \
	#( #[ 32 33 250 2 89 243 245] \
	#(  ) ) >

<primitive 112 temp 5		" ln " \
	#( #[ 32 250 1 70 243 245] \
	#(  ) ) >

<primitive 112 temp 6		" integerPart " \
	#( #[ 32 250 1 75 243 245] \
	#(  ) ) >

<primitive 112 temp 7		" gamma " \
	#( #[ 32 250 1 77 243 245] \
	#(  ) ) >

<primitive 112 temp 8		" fractionPart " \
	#( #[ 32 250 1 76 243 245] \
	#(  ) ) >

<primitive 112 temp 9		" floor " \
	#( #[ 32 250 1 72 243 245] \
	#(  ) ) >

<primitive 112 temp 10		" exp " \
	#( #[ 32 250 1 79 243 245] \
	#(  ) ) >

<primitive 112 temp 11		" coerce: " \
	#( #[ 33 175 243 245] \
	#(  ) ) >

<primitive 112 temp 12		" ceiling " \
	#( #[ 32 250 1 73 243 245] \
	#(  ) ) >

<primitive 112 temp 13		" asString " \
	#( #[ 32 250 1 78 243 245] \
	#(  ) ) >

<primitive 112 temp 14		" asFloat " \
	#( #[ 32 243 245] \
	#(  ) ) >

<primitive 112 temp 15		" arcTan " \
	#( #[ 5 54 32 250 1 86 176 243 245] \
	#(  ) ) >

<primitive 112 temp 16		" arcSin " \
	#( #[ 5 54 32 250 1 84 176 243 245] \
	#(  ) ) >

<primitive 112 temp 17		" arcCos " \
	#( #[ 5 54 32 250 1 85 176 243 245] \
	#(  ) ) >

<primitive 112 temp 18		" ^ " \
	#( #[ 32 33 250 2 6 247 7 32 33 250 2 88 248 5 242 \
 32 33 145 0 243 245] \
	#( #raisedTo:  ) ) >

<primitive 112 temp 19		" / " \
	#( #[ 32 33 250 2 6 247 7 32 33 250 2 69 248 5 242 \
 32 33 145 0 243 245] \
	#( #/  ) ) >

<primitive 112 temp 20		" * " \
	#( #[ 32 33 250 2 6 247 7 32 33 250 2 68 248 5 242 \
 32 33 145 0 243 245] \
	#( #*  ) ) >

<primitive 112 temp 21		" - " \
	#( #[ 32 33 250 2 6 247 7 32 33 250 2 61 248 5 242 \
 32 33 145 0 243 245] \
	#( #-  ) ) >

<primitive 112 temp 22		" + " \
	#( #[ 32 33 250 2 6 247 7 32 33 250 2 60 248 5 242 \
 32 33 145 0 243 245] \
	#( #+  ) ) >

<primitive 112 temp 23		" > " \
	#( #[ 32 33 250 2 6 247 7 32 33 250 2 63 248 5 242 \
 32 33 145 0 243 245] \
	#( #>  ) ) >

<primitive 112 temp 24		" < " \
	#( #[ 32 33 250 2 6 247 7 32 33 250 2 62 248 5 242 \
 32 33 145 0 243 245] \
	#( #<  ) ) >

<primitive 112 temp 25		" = " \
	#( #[ 32 33 250 2 6 247 7 32 33 250 2 66 248 5 242 \
 32 33 145 0 243 245] \
	#( #=  ) ) >

<primitive 98 #Float \
	<primitive 97 #Float #Number #/u/smalltalk/prelude/float.st \
	#(  ) \
	#( #truncated #sqrt #rounded #radix: #ln #integerPart #gamma #fractionPart #floor #exp #coerce: #ceiling #asString #asFloat #arcTan #arcSin #arcCos #^ #/ #* #- #+ #> #< #=  ) \
	temp 2 4 > >

SHAR_EOF
if test 2739 -ne "`wc -c < 'float.p'`"
then
	echo shar: error transmitting "'float.p'" '(should have been 2739 characters)'
fi
fi # end of overwriting check
if test -f 'radian.p'
then
	echo shar: will not over-write existing file "'radian.p'"
else
cat << \SHAR_EOF > 'radian.p'
temp <- <primitive 110 8 >
<primitive 112 temp 1		" printString " \
	#( #[ 16 10 16 48 11 17 243 245] \
	#( ' radians'  ) ) >

<primitive 112 temp 2		" asFloat " \
	#( #[ 16 243 245] \
	#(  ) ) >

<primitive 112 temp 3		" tan " \
	#( #[ 16 250 1 81 16 250 1 82 190 243 245] \
	#(  ) ) >

<primitive 112 temp 4		" cos " \
	#( #[ 16 250 1 82 243 245] \
	#(  ) ) >

<primitive 112 temp 5		" sin " \
	#( #[ 16 250 1 81 243 245] \
	#(  ) ) >

<primitive 112 temp 6		" = " \
	#( #[ 16 33 175 201 243 245] \
	#(  ) ) >

<primitive 112 temp 7		" < " \
	#( #[ 16 33 175 199 243 245] \
	#(  ) ) >

<primitive 112 temp 8		" new: " \
	#( #[ 33 175 250 1 80 96 245] \
	#(  ) ) >

<primitive 98 #Radian \
	<primitive 97 #Radian #Magnitude #/u/smalltalk/prelude/radian.st \
	#(  #value ) \
	#( #printString #asFloat #tan #cos #sin #= #< #new:  ) \
	temp 2 3 > >

SHAR_EOF
if test 848 -ne "`wc -c < 'radian.p'`"
then
	echo shar: error transmitting "'radian.p'" '(should have been 848 characters)'
fi
fi # end of overwriting check
if test -f 'point.p'
then
	echo shar: will not over-write existing file "'point.p'"
else
cat << \SHAR_EOF > 'point.p'
temp <- <primitive 110 21 >
<primitive 112 temp 1		" y: " \
	#( #[ 33 97 245] \
	#(  ) ) >

<primitive 112 temp 2		" y " \
	#( #[ 17 243 245] \
	#(  ) ) >

<primitive 112 temp 3		" x:y: " \
	#( #[ 33 96 34 97 245] \
	#(  ) ) >

<primitive 112 temp 4		" x: " \
	#( #[ 33 96 245] \
	#(  ) ) >

<primitive 112 temp 5		" x " \
	#( #[ 16 243 245] \
	#(  ) ) >

<primitive 112 temp 6		" transpose " \
	#( #[ 5 53 160 17 11 50 16 11 51 243 245] \
	#(  ) ) >

<primitive 112 temp 7		" printString " \
	#( #[ 16 169 48 11 17 17 169 11 17 243 245] \
	#( ' @ '  ) ) >

<primitive 112 temp 8		" min: " \
	#( #[ 5 53 160 16 33 10 49 207 11 50 17 33 10 50 207 \
 11 51 243 245] \
	#(  ) ) >

<primitive 112 temp 9		" max: " \
	#( #[ 5 53 160 16 33 10 49 12 16 11 50 17 33 10 50 \
 12 16 11 51 243 245] \
	#(  ) ) >

<primitive 112 temp 10		" dist: " \
	#( #[ 16 33 10 49 193 10 44 17 33 10 50 193 10 44 192 \
 10 43 243 245] \
	#(  ) ) >

<primitive 112 temp 11		" asString " \
	#( #[ 16 10 16 48 11 17 17 10 16 11 17 243 245] \
	#( ' @ '  ) ) >

<primitive 112 temp 12		" abs " \
	#( #[ 5 53 160 16 173 11 50 17 173 11 51 243 245] \
	#(  ) ) >

<primitive 112 temp 13		" // " \
	#( #[ 5 53 160 16 33 11 18 11 50 17 33 11 18 11 51 \
 243 245] \
	#(  ) ) >

<primitive 112 temp 14		" / " \
	#( #[ 5 53 160 16 33 190 11 50 17 33 190 11 51 243 245 \
] \
	#(  ) ) >

<primitive 112 temp 15		" - " \
	#( #[ 5 53 160 16 33 10 49 193 11 50 17 33 10 50 193 \
 11 51 243 245] \
	#(  ) ) >

<primitive 112 temp 16		" + " \
	#( #[ 5 53 160 16 33 10 49 192 11 50 17 33 10 50 192 \
 11 51 243 245] \
	#(  ) ) >

<primitive 112 temp 17		" * " \
	#( #[ 5 53 160 16 33 194 11 50 17 33 194 11 51 243 245 \
] \
	#(  ) ) >

<primitive 112 temp 18		" = " \
	#( #[ 16 33 10 49 201 252 5 17 33 10 50 201 243 245] \
	#(  ) ) >

<primitive 112 temp 19		" >= " \
	#( #[ 16 33 10 49 203 252 5 17 33 10 50 203 243 245] \
	#(  ) ) >

<primitive 112 temp 20		" <= " \
	#( #[ 16 33 10 49 200 252 5 17 33 10 50 199 243 245] \
	#(  ) ) >

<primitive 112 temp 21		" < " \
	#( #[ 16 33 10 49 199 252 5 17 33 10 50 199 243 245] \
	#(  ) ) >

<primitive 98 #Point \
	<primitive 97 #Point #Magnitude #/u/smalltalk/prelude/point.st \
	#(  #xvalue #yvalue ) \
	#( #y: #y #x:y: #x: #x #transpose #printString #min: #max: #dist: #asString #abs #// #/ #- #+ #* #= #>= #<= #<  ) \
	temp 3 4 > >

SHAR_EOF
if test 2339 -ne "`wc -c < 'point.p'`"
then
	echo shar: error transmitting "'point.p'" '(should have been 2339 characters)'
fi
fi # end of overwriting check
if test -f 'random.p'
then
	echo shar: will not over-write existing file "'random.p'"
else
cat << \SHAR_EOF > 'random.p'
temp <- <primitive 110 7 >
<primitive 112 temp 1		" next: " \
	#( #[ 5 30 33 176 114 81 33 178 225 3 6 34 35 32 167 \
 208 243 179 242 34 243 245] \
	#(  ) ) >

<primitive 112 temp 2		" randInteger: " \
	#( #[ 32 167 33 194 10 47 81 192 243 245] \
	#(  ) ) >

<primitive 112 temp 3		" between:and: " \
	#( #[ 32 167 34 33 193 194 33 192 243 245] \
	#(  ) ) >

<primitive 112 temp 4		" next " \
	#( #[ 16 250 1 35 241 96 250 1 32 243 245] \
	#(  ) ) >

<primitive 112 temp 5		" first " \
	#( #[ 16 250 1 35 241 96 250 1 32 243 245] \
	#(  ) ) >

<primitive 112 temp 6		" randomize " \
	#( #[ 250 0 161 96 245] \
	#(  ) ) >

<primitive 112 temp 7		" new " \
	#( #[ 81 96 245] \
	#(  ) ) >

<primitive 98 #Random \
	<primitive 97 #Random #Object #/u/smalltalk/prelude/random.st \
	#(  #seed ) \
	#( #next: #randInteger: #between:and: #next #first #randomize #new  ) \
	temp 4 6 > >

SHAR_EOF
if test 880 -ne "`wc -c < 'random.p'`"
then
	echo shar: error transmitting "'random.p'" '(should have been 880 characters)'
fi
fi # end of overwriting check
if test -f 'collection.p'
then
	echo shar: will not over-write existing file "'collection.p'"
else
cat << \SHAR_EOF > 'collection.p'
temp <- <primitive 110 23 >
<primitive 112 temp 1		" size " \
	#( #[ 80 113 32 225 2 6 33 81 192 241 113 243 179 242 33 \
 243 245] \
	#(  ) ) >

<primitive 112 temp 2		" shallowCopy " \
	#( #[ 5 48 160 113 32 225 2 5 33 34 11 22 243 179 242 \
 32 33 191 243 245] \
	#(  ) ) >

<primitive 112 temp 3		" select: " \
	#( #[ 32 32 164 160 226 2 11 33 35 180 247 3 34 35 189 \
 242 34 243 215 243 245] \
	#(  ) ) >

<primitive 112 temp 4		" remove:ifAbsent: " \
	#( #[ 32 33 11 30 247 6 32 33 11 39 248 3 242 34 165 \
 243 245] \
	#(  ) ) >

<primitive 112 temp 5		" remove: " \
	#( #[ 32 33 224 4 32 48 188 244 216 242 33 243 245] \
	#( 'attempt to remove object not found in collection'  ) ) >

<primitive 112 temp 6		" reject: " \
	#( #[ 32 225 2 5 33 34 180 172 243 11 44 243 245] \
	#(  ) ) >

<primitive 112 temp 7		" printString " \
	#( #[ 32 32 164 169 48 11 17 226 1 9 33 49 11 17 34 \
 169 11 17 243 215 50 11 17 243 245] \
	#( ' (' ' ' ' )'  ) ) >

<primitive 112 temp 8		" occurrencesOf: " \
	#( #[ 32 80 226 2 13 35 33 201 247 5 34 81 192 248 2 \
 242 34 243 215 243 245] \
	#(  ) ) >

<primitive 112 temp 9		" isEmpty " \
	#( #[ 32 163 80 201 243 245] \
	#(  ) ) >

<primitive 112 temp 10		" inject:into: " \
	#( #[ 33 115 32 225 4 7 34 35 36 211 241 115 243 179 242 \
 35 243 245] \
	#(  ) ) >

<primitive 112 temp 11		" includes: " \
	#( #[ 32 225 2 8 34 33 201 247 2 91 244 243 179 242 92 \
 243 245] \
	#(  ) ) >

<primitive 112 temp 12		" first " \
	#( #[ 32 48 188 243 245] \
	#( 'subclass should implement first'  ) ) >

<primitive 112 temp 13		" detect:ifAbsent: " \
	#( #[ 32 225 3 8 33 35 180 247 2 35 244 243 179 242 34 \
 165 243 245] \
	#(  ) ) >

<primitive 112 temp 14		" detect: " \
	#( #[ 32 33 224 4 32 48 188 243 223 243 245] \
	#( 'no object found matching detect'  ) ) >

<primitive 112 temp 15		" deepCopy " \
	#( #[ 5 48 160 113 32 225 2 7 33 34 10 20 11 22 243 \
 179 242 32 33 191 243 245] \
	#(  ) ) >

<primitive 112 temp 16		" collect: " \
	#( #[ 32 32 164 160 226 2 8 34 33 35 180 189 242 34 243 \
 215 243 245] \
	#(  ) ) >

<primitive 112 temp 17		" coerce: " \
	#( #[ 32 160 114 33 225 3 4 34 35 189 243 179 242 34 243 \
 245] \
	#(  ) ) >

<primitive 112 temp 18		" asString " \
	#( #[ 5 58 32 163 176 241 81 32 163 32 131 0 242 243 245 \
] \
	#( #replaceFrom:to:with:  ) ) >

<primitive 112 temp 19		" asList " \
	#( #[ 5 48 160 32 11 20 243 245] \
	#(  ) ) >

<primitive 112 temp 20		" asSet " \
	#( #[ 5 57 160 32 11 19 243 245] \
	#(  ) ) >

<primitive 112 temp 21		" asBag " \
	#( #[ 5 32 160 32 11 19 243 245] \
	#(  ) ) >

<primitive 112 temp 22		" asArray " \
	#( #[ 5 30 32 163 176 241 81 32 163 32 131 0 242 243 245 \
] \
	#( #replaceFrom:to:with:  ) ) >

<primitive 112 temp 23		" addAll: " \
	#( #[ 33 225 2 4 32 34 189 243 179 242 245] \
	#(  ) ) >

<primitive 98 #Collection \
	<primitive 97 #Collection #Object #/u/smalltalk/prelude/collection.st \
	#(  ) \
	#( #size #shallowCopy #select: #remove:ifAbsent: #remove: #reject: #printString #occurrencesOf: #isEmpty #inject:into: #includes: #first #detect:ifAbsent: #detect: #deepCopy #collect: #coerce: #asString #asList #asSet #asBag #asArray #addAll:  ) \
	temp 5 7 > >

SHAR_EOF
if test 3180 -ne "`wc -c < 'collection.p'`"
then
	echo shar: error transmitting "'collection.p'" '(should have been 3180 characters)'
fi
fi # end of overwriting check
if test -f 'bag.p'
then
	echo shar: will not over-write existing file "'bag.p'"
else
cat << \SHAR_EOF > 'bag.p'
temp <- <primitive 110 8 >
<primitive 112 temp 1		" next " \
	#( #[ 17 162 247 27 17 80 204 247 9 17 81 193 97 16 171 \
 243 248 10 242 16 167 241 97 161 247 2 93 243 242 249 \
 31 242 93 243 245] \
	#(  ) ) >

<primitive 112 temp 2		" first " \
	#( #[ 16 166 241 97 161 247 2 93 243 242 17 81 193 97 16 \
 171 243 245] \
	#(  ) ) >

<primitive 112 temp 3		" occurrencesOf: " \
	#( #[ 16 33 224 2 80 243 213 243 245] \
	#(  ) ) >

<primitive 112 temp 4		" size " \
	#( #[ 16 80 226 1 4 33 34 192 243 215 243 245] \
	#(  ) ) >

<primitive 112 temp 5		" remove:ifAbsent: " \
	#( #[ 16 33 224 3 34 165 244 213 115 81 35 201 247 6 16 \
 33 11 40 248 7 242 16 33 35 81 193 208 242 245] \
	#(  ) ) >

<primitive 112 temp 6		" add:withOccurrences: " \
	#( #[ 34 224 4 32 33 189 243 183 242 33 243 245] \
	#(  ) ) >

<primitive 112 temp 7		" add: " \
	#( #[ 16 33 81 16 33 224 2 80 243 213 192 208 242 245] \
	#(  ) ) >

<primitive 112 temp 8		" new " \
	#( #[ 5 40 160 96 245] \
	#(  ) ) >

<primitive 98 #Bag \
	<primitive 97 #Bag #Collection #/u/smalltalk/prelude/bag.st \
	#(  #dict #count ) \
	#( #next #first #occurrencesOf: #size #remove:ifAbsent: #add:withOccurrences: #add: #new  ) \
	temp 4 8 > >

SHAR_EOF
if test 1200 -ne "`wc -c < 'bag.p'`"
then
	echo shar: error transmitting "'bag.p'" '(should have been 1200 characters)'
fi
fi # end of overwriting check
if test -f 'set.p'
then
	echo shar: will not over-write existing file "'set.p'"
else
cat << \SHAR_EOF > 'set.p'
temp <- <primitive 110 7 >
<primitive 112 temp 1		" next " \
	#( #[ 16 167 243 245] \
	#(  ) ) >

<primitive 112 temp 2		" first " \
	#( #[ 16 166 243 245] \
	#(  ) ) >

<primitive 112 temp 3		" occurrencesOf: " \
	#( #[ 16 33 11 30 247 3 81 248 2 242 80 243 245] \
	#(  ) ) >

<primitive 112 temp 4		" size " \
	#( #[ 16 163 243 245] \
	#(  ) ) >

<primitive 112 temp 5		" remove:ifAbsent: " \
	#( #[ 16 33 34 216 242 245] \
	#(  ) ) >

<primitive 112 temp 6		" add: " \
	#( #[ 16 33 11 30 246 3 16 33 189 242 245] \
	#(  ) ) >

<primitive 112 temp 7		" new " \
	#( #[ 5 48 160 96 245] \
	#(  ) ) >

<primitive 98 #Set \
	<primitive 97 #Set #Collection #/u/smalltalk/prelude/set.st \
	#(  #list ) \
	#( #next #first #occurrencesOf: #size #remove:ifAbsent: #add: #new  ) \
	temp 3 4 > >

SHAR_EOF
if test 788 -ne "`wc -c < 'set.p'`"
then
	echo shar: error transmitting "'set.p'" '(should have been 788 characters)'
fi
fi # end of overwriting check
if test -f 'kcollection.p'
then
	echo shar: will not over-write existing file "'kcollection.p'"
else
cat << \SHAR_EOF > 'kcollection.p'
temp <- <primitive 110 18 >
<primitive 112 temp 1		" values " \
	#( #[ 5 32 160 113 32 225 2 4 33 34 189 243 179 242 33 \
 243 245] \
	#(  ) ) >

<primitive 112 temp 2		" select: " \
	#( #[ 32 32 5 40 160 226 2 13 33 35 180 247 5 34 32 \
 171 35 208 242 34 243 215 191 243 245] \
	#(  ) ) >

<primitive 112 temp 3		" removeKey:ifAbsent: " \
	#( #[ 32 48 188 243 245] \
	#( 'subclass should implement RemoveKey:ifAbsent:'  ) ) >

<primitive 112 temp 4		" removeKey: " \
	#( #[ 32 33 224 6 32 48 188 242 33 244 217 243 245] \
	#( 'no element associated with key'  ) ) >

<primitive 112 temp 5		" remove: " \
	#( #[ 32 48 188 243 245] \
	#( 'object must be removed with explicit key'  ) ) >

<primitive 112 temp 6		" keysSelect: " \
	#( #[ 32 32 5 40 160 226 2 14 33 35 171 180 247 5 34 \
 32 171 35 208 242 34 243 215 191 243 245] \
	#(  ) ) >

<primitive 112 temp 7		" keysDo: " \
	#( #[ 32 225 2 5 33 32 171 180 243 179 243 245] \
	#(  ) ) >

<primitive 112 temp 8		" keys " \
	#( #[ 5 57 160 113 32 225 2 4 33 34 189 243 11 32 242 \
 33 243 245] \
	#(  ) ) >

<primitive 112 temp 9		" indexOf:ifAbsent: " \
	#( #[ 32 225 3 9 35 33 201 247 3 32 171 244 243 179 242 \
 34 165 243 245] \
	#(  ) ) >

<primitive 112 temp 10		" indexOf: " \
	#( #[ 32 33 224 4 32 48 188 243 214 243 245] \
	#( 'indexOf element not found'  ) ) >

<primitive 112 temp 11		" includesKey: " \
	#( #[ 32 33 224 2 92 244 213 242 91 243 245] \
	#(  ) ) >

<primitive 112 temp 12		" collect: " \
	#( #[ 32 32 5 40 160 226 2 10 34 32 171 33 35 180 208 \
 242 34 243 215 191 243 245] \
	#(  ) ) >

<primitive 112 temp 13		" binaryDo: " \
	#( #[ 32 225 3 6 33 32 171 35 211 243 179 242 93 243 245 \
] \
	#(  ) ) >

<primitive 112 temp 14		" atAll:put: " \
	#( #[ 33 225 3 5 32 35 34 208 243 179 242 245] \
	#(  ) ) >

<primitive 112 temp 15		" at: " \
	#( #[ 32 33 224 10 32 33 169 48 11 17 188 242 33 244 213 \
 243 245] \
	#( ': association not found'  ) ) >

<primitive 112 temp 16		" asDictionary " \
	#( #[ 5 40 160 113 32 226 2 5 33 34 35 208 243 11 23 \
 242 33 243 245] \
	#(  ) ) >

<primitive 112 temp 17		" addAll: " \
	#( #[ 33 226 2 5 32 34 35 208 243 11 23 242 33 243 245 \
] \
	#(  ) ) >

<primitive 112 temp 18		" add: " \
	#( #[ 32 48 188 243 245] \
	#( 'Must add with explicit key'  ) ) >

<primitive 98 #KeyedCollection \
	<primitive 97 #KeyedCollection #Collection #/u/smalltalk/prelude/kcollection.st \
	#(  ) \
	#( #values #select: #removeKey:ifAbsent: #removeKey: #remove: #keysSelect: #keysDo: #keys #indexOf:ifAbsent: #indexOf: #includesKey: #collect: #binaryDo: #atAll:put: #at: #asDictionary #addAll: #add:  ) \
	temp 4 9 > >

SHAR_EOF
if test 2622 -ne "`wc -c < 'kcollection.p'`"
then
	echo shar: error transmitting "'kcollection.p'" '(should have been 2622 characters)'
fi
fi # end of overwriting check
if test -f 'dictionary.p'
then
	echo shar: will not over-write existing file "'dictionary.p'"
else
cat << \SHAR_EOF > 'dictionary.p'
temp <- <primitive 110 12 >
<primitive 112 temp 1		" checkBucket: " \
	#( #[ 16 33 241 97 177 241 98 161 247 2 93 243 242 18 166 \
 243 245] \
	#(  ) ) >

<primitive 112 temp 2		" currentKey " \
	#( #[ 18 162 247 11 18 10 21 113 33 162 247 3 33 10 49 \
 243 245] \
	#(  ) ) >

<primitive 112 temp 3		" printString " \
	#( #[ 32 32 164 169 48 11 17 226 1 17 33 32 171 169 11 \
 17 49 11 17 34 169 11 17 50 11 17 243 215 51 11 \
 17 243 245] \
	#( ' ( ' ' @ ' ' ' ')'  ) ) >

<primitive 112 temp 4		" next " \
	#( #[ 18 167 241 113 162 247 4 33 10 50 243 242 17 5 17 \
 199 247 20 17 81 192 97 32 17 11 24 241 113 162 247 \
 4 33 10 50 243 242 249 26 242 93 243 245] \
	#(  ) ) >

<primitive 112 temp 5		" first " \
	#( #[ 81 5 17 178 225 2 14 32 34 11 24 241 113 162 247 \
 4 33 10 50 244 243 179 242 93 243 245] \
	#(  ) ) >

<primitive 112 temp 6		" findAssociation:inList: " \
	#( #[ 34 225 3 10 35 10 49 33 201 247 2 35 244 243 179 \
 242 93 243 245] \
	#(  ) ) >

<primitive 112 temp 7		" removeKey:ifAbsent: " \
	#( #[ 32 33 11 28 115 32 33 35 222 116 36 161 247 3 34 \
 165 243 242 35 36 224 3 34 165 244 216 10 50 243 245 \
] \
	#(  ) ) >

<primitive 112 temp 8		" at:ifAbsent: " \
	#( #[ 32 33 11 28 115 32 33 35 222 116 36 161 247 3 34 \
 165 243 242 36 10 50 243 245] \
	#(  ) ) >

<primitive 112 temp 9		" at:put: " \
	#( #[ 32 33 11 28 115 32 33 35 222 116 36 161 247 15 5 \
 53 160 33 11 50 34 11 51 116 35 36 189 248 5 242 \
 36 34 11 51 242 34 243 245] \
	#(  ) ) >

<primitive 112 temp 10		" getList: " \
	#( #[ 32 33 11 29 115 16 35 177 114 34 161 247 8 5 48 \
 160 114 16 35 34 208 242 34 243 245] \
	#(  ) ) >

<primitive 112 temp 11		" hashNumber: " \
	#( #[ 33 250 1 5 16 163 195 81 192 243 245] \
	#(  ) ) >

<primitive 112 temp 12		" new " \
	#( #[ 5 30 5 17 176 96 245] \
	#(  ) ) >

<primitive 98 #Dictionary \
	<primitive 97 #Dictionary #KeyedCollection #/u/smalltalk/prelude/dictionary.st \
	#(  #hashTable #currentBucket #currentList ) \
	#( #checkBucket: #currentKey #printString #next #first #findAssociation:inList: #removeKey:ifAbsent: #at:ifAbsent: #at:put: #getList: #hashNumber: #new  ) \
	temp 5 6 > >

SHAR_EOF
if test 2139 -ne "`wc -c < 'dictionary.p'`"
then
	echo shar: error transmitting "'dictionary.p'" '(should have been 2139 characters)'
fi
fi # end of overwriting check
if test -f 'scollection.p'
then
	echo shar: will not over-write existing file "'scollection.p'"
else
cat << \SHAR_EOF > 'scollection.p'
temp <- <primitive 110 21 >
<primitive 112 temp 1		" with:do: " \
	#( #[ 32 166 115 33 166 116 35 162 247 15 34 35 36 211 242 \
 32 167 115 33 167 241 116 242 249 19 242 93 243 245] \
	#(  ) ) >

<primitive 112 temp 2		" sort: " \
	#( #[ 32 174 116 82 36 163 178 225 5 51 37 81 193 114 34 \
 81 203 252 11 33 36 34 177 36 34 81 192 177 211 172 \
 247 28 36 34 177 115 36 34 36 34 81 192 177 208 242 \
 36 34 81 192 35 208 242 34 81 193 241 114 242 249 46 \
 243 179 242 32 36 191 243 245] \
	#(  ) ) >

<primitive 112 temp 3		" sort " \
	#( #[ 32 226 1 4 33 34 200 243 11 46 243 245] \
	#(  ) ) >

<primitive 112 temp 4		" select: " \
	#( #[ 32 32 5 48 160 226 2 12 33 35 180 247 4 34 35 \
 11 22 242 34 243 215 191 243 245] \
	#(  ) ) >

<primitive 112 temp 5		" reversed " \
	#( #[ 5 30 32 163 241 114 176 113 32 225 3 11 33 34 35 \
 208 242 34 81 193 241 114 243 179 242 32 33 191 243 245 \
] \
	#(  ) ) >

<primitive 112 temp 6		" reverseDo: " \
	#( #[ 32 10 31 114 32 10 25 115 34 35 203 247 20 32 34 \
 11 52 247 5 33 32 34 177 180 242 34 81 193 241 114 \
 242 249 25 242 93 243 245] \
	#(  ) ) >

<primitive 112 temp 7		" replaceFrom:to:with:startingAt: " \
	#( #[ 80 117 33 37 192 34 200 247 19 32 33 37 192 35 37 \
 36 192 177 208 242 37 81 192 241 117 242 249 26 242 245 \
] \
	#(  ) ) >

<primitive 112 temp 8		" replaceFrom:to:with: " \
	#( #[ 35 33 226 4 9 32 36 37 208 242 36 81 192 243 215 \
 242 245] \
	#(  ) ) >

<primitive 112 temp 9		" last " \
	#( #[ 80 32 163 201 246 5 32 32 10 31 177 243 245] \
	#(  ) ) >

<primitive 112 temp 10		" indexOfSubCollection:startingAt: " \
	#( #[ 32 33 34 224 6 32 48 188 242 93 243 131 1 243 245 \
] \
	#( 'element not found' #indexOfSubCollection:startingAt:ifAbsent:  ) ) >

<primitive 112 temp 11		" indexOfSubCollection:startingAt:ifAbsent: " \
	#( #[ 34 116 32 163 33 163 193 117 36 37 200 247 17 33 32 \
 36 221 247 2 36 243 242 36 81 192 241 116 242 249 22 \
 242 35 165 243 245] \
	#(  ) ) >

<primitive 112 temp 12		" findLast:ifAbsent: " \
	#( #[ 32 225 3 9 33 35 180 247 3 32 171 244 243 11 42 \
 242 34 165 243 245] \
	#(  ) ) >

<primitive 112 temp 13		" findLast: " \
	#( #[ 32 33 224 4 32 48 188 243 220 242 245] \
	#( 'last element not found'  ) ) >

<primitive 112 temp 14		" findFirst:ifAbsent: " \
	#( #[ 32 225 3 9 33 35 180 247 3 32 171 244 243 179 242 \
 34 165 243 245] \
	#(  ) ) >

<primitive 112 temp 15		" findFirst: " \
	#( #[ 32 33 224 4 32 48 188 243 219 243 245] \
	#( 'first element not found'  ) ) >

<primitive 112 temp 16		" equals:startingAt: " \
	#( #[ 80 115 32 225 4 22 36 33 34 35 192 224 2 92 244 \
 213 201 246 2 92 244 242 35 81 192 241 115 243 179 242 \
 91 243 245] \
	#(  ) ) >

<primitive 112 temp 17		" copyWithout: " \
	#( #[ 5 48 160 114 32 225 3 10 35 33 181 246 4 34 35 \
 11 22 243 179 242 32 34 191 243 245] \
	#(  ) ) >

<primitive 112 temp 18		" copyWith: " \
	#( #[ 32 5 48 160 241 32 11 20 242 241 33 11 22 242 191 \
 243 245] \
	#(  ) ) >

<primitive 112 temp 19		" copyFrom:to: " \
	#( #[ 5 48 160 115 33 34 178 225 4 7 35 32 36 177 11 \
 22 243 179 242 32 35 191 243 245] \
	#(  ) ) >

<primitive 112 temp 20		" collect: " \
	#( #[ 32 32 5 48 160 226 2 9 34 33 35 180 11 22 242 \
 34 243 215 191 243 245] \
	#(  ) ) >

<primitive 112 temp 21		" , " \
	#( #[ 32 5 48 160 241 32 11 20 242 241 33 11 20 242 191 \
 243 245] \
	#(  ) ) >

<primitive 98 #SequenceableCollection \
	<primitive 97 #SequenceableCollection #KeyedCollection #/u/smalltalk/prelude/scollection.st \
	#(  ) \
	#( #with:do: #sort: #sort #select: #reversed #reverseDo: #replaceFrom:to:with:startingAt: #replaceFrom:to:with: #last #indexOfSubCollection:startingAt: #indexOfSubCollection:startingAt:ifAbsent: #findLast:ifAbsent: #findLast: #findFirst:ifAbsent: #findFirst: #equals:startingAt: #copyWithout: #copyWith: #copyFrom:to: #collect: #,  ) \
	temp 6 9 > >

SHAR_EOF
if test 3846 -ne "`wc -c < 'scollection.p'`"
then
	echo shar: error transmitting "'scollection.p'" '(should have been 3846 characters)'
fi
fi # end of overwriting check
if test -f 'interval.p'
then
	echo shar: will not over-write existing file "'interval.p'"
else
cat << \SHAR_EOF > 'interval.p'
temp <- <primitive 110 13 >
<primitive 112 temp 1		" shallowCopy " \
	#( #[ 16 17 18 212 243 245] \
	#(  ) ) >

<primitive 112 temp 2		" deepCopy " \
	#( #[ 16 17 18 212 243 245] \
	#(  ) ) >

<primitive 112 temp 3		" removeKey:ifAbsent: " \
	#( #[ 32 48 188 242 34 165 243 245] \
	#( 'cannot remove from Interval'  ) ) >

<primitive 112 temp 4		" add: " \
	#( #[ 32 48 188 243 245] \
	#( 'cannot store into Interval'  ) ) >

<primitive 112 temp 5		" at:put: " \
	#( #[ 32 48 188 243 245] \
	#( 'cannot store into Interval'  ) ) >

<primitive 112 temp 6		" coerce: " \
	#( #[ 33 174 243 245] \
	#(  ) ) >

<primitive 112 temp 7		" printString " \
	#( #[ 48 16 169 11 17 49 11 17 17 169 11 17 50 11 17 \
 18 169 11 17 243 245] \
	#( 'Interval ' ' to ' ' by '  ) ) >

<primitive 112 temp 8		" at:ifAbsent: " \
	#( #[ 16 18 33 81 193 194 192 115 32 35 11 31 247 3 35 \
 248 3 242 34 165 243 245] \
	#(  ) ) >

<primitive 112 temp 9		" next " \
	#( #[ 19 18 192 99 32 19 11 31 247 1 19 243 245] \
	#(  ) ) >

<primitive 112 temp 10		" first " \
	#( #[ 16 99 32 19 11 31 247 1 19 243 245] \
	#(  ) ) >

<primitive 112 temp 11		" inRange: " \
	#( #[ 18 170 247 10 33 16 203 252 3 33 17 200 248 9 242 \
 33 17 203 252 3 33 16 200 243 245] \
	#(  ) ) >

<primitive 112 temp 12		" size " \
	#( #[ 18 170 247 5 17 16 199 248 4 242 16 17 199 247 3 \
 80 248 9 242 17 16 193 18 11 18 81 192 243 245] \
	#(  ) ) >

<primitive 112 temp 13		" from:to:by: " \
	#( #[ 33 241 96 99 34 97 35 98 245] \
	#(  ) ) >

<primitive 98 #Interval \
	<primitive 97 #Interval #SequenceableCollection #/u/smalltalk/prelude/interval.st \
	#(  #lower #upper #step #current ) \
	#( #shallowCopy #deepCopy #removeKey:ifAbsent: #add: #at:put: #coerce: #printString #at:ifAbsent: #next #first #inRange: #size #from:to:by:  ) \
	temp 4 5 > >

SHAR_EOF
if test 1805 -ne "`wc -c < 'interval.p'`"
then
	echo shar: error transmitting "'interval.p'" '(should have been 1805 characters)'
fi
fi # end of overwriting check
if test -f 'list.p'
then
	echo shar: will not over-write existing file "'list.p'"
else
cat << \SHAR_EOF > 'list.p'
temp <- <primitive 110 17 >
<primitive 112 temp 1		" isEmpty " \
	#( #[ 16 93 181 243 245] \
	#(  ) ) >

<primitive 112 temp 2		" last " \
	#( #[ 16 161 247 2 93 243 242 32 10 24 10 49 243 245] \
	#(  ) ) >

<primitive 112 temp 3		" current " \
	#( #[ 17 10 49 243 245] \
	#(  ) ) >

<primitive 112 temp 4		" next " \
	#( #[ 17 10 50 241 97 162 247 3 17 10 49 243 245] \
	#(  ) ) >

<primitive 112 temp 5		" first " \
	#( #[ 16 241 97 162 247 3 17 10 49 243 245] \
	#(  ) ) >

<primitive 112 temp 6		" removeLast " \
	#( #[ 16 161 247 4 32 10 37 243 242 32 32 10 30 224 4 \
 32 10 37 243 216 243 245] \
	#(  ) ) >

<primitive 112 temp 7		" removeFirst " \
	#( #[ 16 161 247 4 32 10 37 243 242 16 113 16 10 50 96 \
 33 10 49 243 245] \
	#(  ) ) >

<primitive 112 temp 8		" removeError " \
	#( #[ 32 48 188 243 245] \
	#( 'cannot remove from an empty list'  ) ) >

<primitive 112 temp 9		" remove:ifAbsent: " \
	#( #[ 16 161 247 3 34 165 243 242 32 93 226 3 31 17 10 \
 49 33 181 247 21 35 161 247 7 17 10 50 241 96 248 \
 7 242 35 17 10 50 11 51 242 33 244 242 17 243 215 \
 242 34 165 243 245] \
	#(  ) ) >

<primitive 112 temp 10		" remove: " \
	#( #[ 32 33 224 4 32 48 188 243 216 243 245] \
	#( 'cant find item'  ) ) >

<primitive 112 temp 11		" findLast " \
	#( #[ 16 241 113 161 247 2 93 243 242 33 10 50 162 247 8 \
 33 10 50 241 113 242 249 14 242 33 243 245] \
	#(  ) ) >

<primitive 112 temp 12		" coerce: " \
	#( #[ 5 48 160 114 33 225 3 5 34 35 11 22 243 179 242 \
 34 243 245] \
	#(  ) ) >

<primitive 112 temp 13		" addAllLast: " \
	#( #[ 33 225 2 5 32 34 11 22 243 179 242 245] \
	#(  ) ) >

<primitive 112 temp 14		" addAllFirst: " \
	#( #[ 33 225 2 5 32 34 11 21 243 179 242 245] \
	#(  ) ) >

<primitive 112 temp 15		" addLast: " \
	#( #[ 16 161 247 5 32 33 11 21 243 242 32 10 24 5 53 \
 160 33 11 50 93 11 51 11 51 242 33 243 245] \
	#(  ) ) >

<primitive 112 temp 16		" addFirst: " \
	#( #[ 5 53 160 33 11 50 16 11 51 96 33 243 245] \
	#(  ) ) >

<primitive 112 temp 17		" add: " \
	#( #[ 5 53 160 33 11 50 16 11 51 96 33 243 245] \
	#(  ) ) >

<primitive 98 #List \
	<primitive 97 #List #SequenceableCollection #/u/smalltalk/prelude/list.st \
	#(  #first #current ) \
	#( #isEmpty #last #current #next #first #removeLast #removeFirst #removeError #remove:ifAbsent: #remove: #findLast #coerce: #addAllLast: #addAllFirst: #addLast: #addFirst: #add:  ) \
	temp 5 8 > >

SHAR_EOF
if test 2388 -ne "`wc -c < 'list.p'`"
then
	echo shar: error transmitting "'list.p'" '(should have been 2388 characters)'
fi
fi # end of overwriting check
if test -f 'acollection.p'
then
	echo shar: will not over-write existing file "'acollection.p'"
else
cat << \SHAR_EOF > 'acollection.p'
temp <- <primitive 110 12 >
<primitive 112 temp 1		" shallowCopy " \
	#( #[ 32 164 32 163 176 113 81 32 163 178 225 2 7 33 34 \
 32 34 177 208 243 179 242 33 243 245] \
	#(  ) ) >

<primitive 112 temp 2		" next " \
	#( #[ 16 81 192 96 16 32 163 200 247 3 32 16 177 243 245 \
] \
	#(  ) ) >

<primitive 112 temp 3		" lastKey " \
	#( #[ 32 163 243 245] \
	#(  ) ) >

<primitive 112 temp 4		" firstKey " \
	#( #[ 81 243 245] \
	#(  ) ) >

<primitive 112 temp 5		" first " \
	#( #[ 81 96 16 32 163 200 247 3 32 16 177 243 245] \
	#(  ) ) >

<primitive 112 temp 6		" do: " \
	#( #[ 81 32 163 178 225 2 8 34 96 33 32 34 177 180 243 \
 179 242 245] \
	#(  ) ) >

<primitive 112 temp 7		" deepCopy " \
	#( #[ 32 164 32 163 176 113 81 32 163 178 225 2 9 33 34 \
 32 34 177 10 20 208 243 179 242 33 243 245] \
	#(  ) ) >

<primitive 112 temp 8		" currentKey " \
	#( #[ 16 243 245] \
	#(  ) ) >

<primitive 112 temp 9		" copyFrom:to: " \
	#( #[ 34 33 193 81 192 115 32 164 35 176 116 36 81 35 32 \
 33 132 0 242 36 243 245] \
	#( #replaceFrom:to:with:startingAt:  ) ) >

<primitive 112 temp 10		" coerce: " \
	#( #[ 32 164 33 163 176 114 34 81 33 163 33 131 0 242 34 \
 243 245] \
	#( #replaceFrom:to:with:  ) ) >

<primitive 112 temp 11		" at:ifAbsent: " \
	#( #[ 33 80 200 251 4 33 32 163 204 247 3 34 165 243 242 \
 32 33 177 243 245] \
	#(  ) ) >

<primitive 112 temp 12		" = " \
	#( #[ 32 163 33 163 202 247 2 92 243 242 80 114 32 225 3 \
 14 35 33 34 81 192 241 114 177 202 247 2 92 244 243 \
 179 242 91 243 245] \
	#(  ) ) >

<primitive 98 #ArrayedCollection \
	<primitive 97 #ArrayedCollection #SequenceableCollection #/u/smalltalk/prelude/acollection.st \
	#(  #current ) \
	#( #shallowCopy #next #lastKey #firstKey #first #do: #deepCopy #currentKey #copyFrom:to: #coerce: #at:ifAbsent: #=  ) \
	temp 5 7 > >

SHAR_EOF
if test 1809 -ne "`wc -c < 'acollection.p'`"
then
	echo shar: error transmitting "'acollection.p'" '(should have been 1809 characters)'
fi
fi # end of overwriting check
if test -f 'file.p'
then
	echo shar: will not over-write existing file "'file.p'"
else
cat << \SHAR_EOF > 'file.p'
temp <- <primitive 110 13 >
<primitive 112 temp 1		" write: " \
	#( #[ 32 33 250 2 132 243 245] \
	#(  ) ) >

<primitive 112 temp 2		" size " \
	#( #[ 32 250 1 134 243 245] \
	#(  ) ) >

<primitive 112 temp 3		" read " \
	#( #[ 32 250 1 131 243 245] \
	#(  ) ) >

<primitive 112 temp 4		" open:for: " \
	#( #[ 32 33 34 250 3 130 242 245] \
	#(  ) ) >

<primitive 112 temp 5		" open: " \
	#( #[ 32 33 48 250 3 130 242 245] \
	#( 'r'  ) ) >

<primitive 112 temp 6		" next " \
	#( #[ 32 10 36 243 245] \
	#(  ) ) >

<primitive 112 temp 7		" first " \
	#( #[ 32 80 177 243 245] \
	#(  ) ) >

<primitive 112 temp 8		" currentKey " \
	#( #[ 32 250 1 136 243 245] \
	#(  ) ) >

<primitive 112 temp 9		" at:put: " \
	#( #[ 32 33 250 2 135 242 32 34 11 49 243 245] \
	#(  ) ) >

<primitive 112 temp 10		" at: " \
	#( #[ 32 33 250 2 135 242 32 10 36 243 245] \
	#(  ) ) >

<primitive 112 temp 11		" modeString " \
	#( #[ 32 81 250 2 133 242 245] \
	#(  ) ) >

<primitive 112 temp 12		" modeInteger " \
	#( #[ 32 82 250 2 133 242 245] \
	#(  ) ) >

<primitive 112 temp 13		" modeCharacter " \
	#( #[ 32 80 250 2 133 242 245] \
	#(  ) ) >

<primitive 98 #File \
	<primitive 97 #File #SequenceableCollection #/u/smalltalk/prelude/file.st \
	#(  ) \
	#( #write: #size #read #open:for: #open: #next #first #currentKey #at:put: #at: #modeString #modeInteger #modeCharacter  ) \
	temp 3 4 > >

SHAR_EOF
if test 1377 -ne "`wc -c < 'file.p'`"
then
	echo shar: error transmitting "'file.p'" '(should have been 1377 characters)'
fi
fi # end of overwriting check
if test -f 'bytearray.p'
then
	echo shar: will not over-write existing file "'bytearray.p'"
else
cat << \SHAR_EOF > 'bytearray.p'
temp <- <primitive 110 5 >
<primitive 112 temp 1		" size " \
	#( #[ 32 250 1 117 243 245] \
	#(  ) ) >

<primitive 112 temp 2		" printString " \
	#( #[ 48 113 81 32 163 178 225 2 13 33 32 34 177 169 11 \
 17 49 11 17 241 113 243 179 242 33 50 11 17 243 245 \
] \
	#( '#[ ' ' ' ']'  ) ) >

<primitive 112 temp 3		" at:put: " \
	#( #[ 32 33 34 250 3 119 242 245] \
	#(  ) ) >

<primitive 112 temp 4		" at: " \
	#( #[ 32 33 250 2 118 243 245] \
	#(  ) ) >

<primitive 112 temp 5		" new: " \
	#( #[ 33 250 1 116 243 245] \
	#(  ) ) >

<primitive 98 #ByteArray \
	<primitive 97 #ByteArray #ArrayedCollection #/u/smalltalk/prelude/bytearray.st \
	#(  ) \
	#( #size #printString #at:put: #at: #new:  ) \
	temp 3 6 > >

SHAR_EOF
if test 712 -ne "`wc -c < 'bytearray.p'`"
then
	echo shar: error transmitting "'bytearray.p'" '(should have been 712 characters)'
fi
fi # end of overwriting check
if test -f 'semaphore.p'
then
	echo shar: will not over-write existing file "'semaphore.p'"
else
cat << \SHAR_EOF > 'semaphore.p'
temp <- <primitive 110 4 >
<primitive 112 temp 1		" wait " \
	#( #[ 250 0 148 242 16 80 201 247 10 32 95 11 22 242 95 \
 10 18 248 6 242 16 81 193 241 96 242 250 0 149 242 \
 245] \
	#(  ) ) >

<primitive 112 temp 2		" signal " \
	#( #[ 250 0 148 242 32 10 27 247 7 16 81 192 241 96 248 \
 6 242 32 10 38 10 48 242 250 0 149 242 245] \
	#(  ) ) >

<primitive 112 temp 3		" new: " \
	#( #[ 33 96 245] \
	#(  ) ) >

<primitive 112 temp 4		" new " \
	#( #[ 80 96 245] \
	#(  ) ) >

<primitive 98 #Semaphore \
	<primitive 97 #Semaphore #List #/u/smalltalk/prelude/semaphore.st \
	#(  #excessSignals ) \
	#( #wait #signal #new: #new  ) \
	temp 2 4 > >

SHAR_EOF
if test 648 -ne "`wc -c < 'semaphore.p'`"
then
	echo shar: error transmitting "'semaphore.p'" '(should have been 648 characters)'
fi
fi # end of overwriting check
if test -f 'process.p'
then
	echo shar: will not over-write existing file "'process.p'"
else
cat << \SHAR_EOF > 'process.p'
temp <- <primitive 110 8 >
<primitive 112 temp 1		" yield " \
	#( #[ 93 243 245] \
	#(  ) ) >

<primitive 112 temp 2		" unblock " \
	#( #[ 32 10 45 48 181 247 7 32 49 11 47 242 93 243 242 \
 32 83 250 2 145 242 32 10 45 243 245] \
	#( #TERMINATED 'unblock'  ) ) >

<primitive 112 temp 3		" termErr: " \
	#( #[ 48 33 11 17 49 11 17 168 242 245] \
	#( 'Cannot ' ' a terminated process.'  ) ) >

<primitive 112 temp 4		" terminate " \
	#( #[ 32 250 1 142 242 32 10 45 243 245] \
	#(  ) ) >

<primitive 112 temp 5		" state " \
	#( #[ 32 250 1 146 113 33 80 201 247 4 48 113 33 243 242 \
 33 81 201 247 4 49 113 33 243 242 33 82 201 247 4 \
 50 113 33 243 242 33 83 201 247 4 50 113 33 243 242 \
 33 84 203 247 4 51 113 33 243 242 245] \
	#( #READY #SUSPENDED #BLOCKED #TERMINATED  ) ) >

<primitive 112 temp 6		" suspend " \
	#( #[ 32 10 45 48 181 247 7 32 49 11 47 242 93 243 242 \
 32 81 250 2 145 242 32 10 45 243 245] \
	#( #TERMINATED 'suspend'  ) ) >

<primitive 112 temp 7		" resume " \
	#( #[ 32 10 45 48 181 247 7 32 49 11 47 242 93 243 242 \
 32 80 250 2 145 242 32 10 45 243 245] \
	#( #TERMINATED 'resume'  ) ) >

<primitive 112 temp 8		" block " \
	#( #[ 32 10 45 48 181 247 7 32 49 11 47 242 93 243 242 \
 32 82 250 2 145 242 32 10 45 243 245] \
	#( #TERMINATED 'block'  ) ) >

<primitive 98 #Process \
	<primitive 97 #Process #Object #/u/smalltalk/prelude/process.st \
	#(  ) \
	#( #yield #unblock #termErr: #terminate #state #suspend #resume #block  ) \
	temp 2 4 > >

SHAR_EOF
if test 1481 -ne "`wc -c < 'process.p'`"
then
	echo shar: error transmitting "'process.p'" '(should have been 1481 characters)'
fi
fi # end of overwriting check
if test -f 'smalltalk.p'
then
	echo shar: will not over-write existing file "'smalltalk.p'"
else
cat << \SHAR_EOF > 'smalltalk.p'
temp <- <primitive 110 9 >
<primitive 112 temp 1		" time: " \
	#( #[ 250 0 161 114 33 165 242 250 0 161 34 193 243 245] \
	#(  ) ) >

<primitive 112 temp 2		" sh: " \
	#( #[ 33 250 1 125 243 245] \
	#(  ) ) >

<primitive 112 temp 3		" perform:withArguments: " \
	#( #[ 34 33 250 2 143 243 245] \
	#(  ) ) >

<primitive 112 temp 4		" noDisplay " \
	#( #[ 81 80 250 2 8 243 245] \
	#(  ) ) >

<primitive 112 temp 5		" doPrimitive:withArguments: " \
	#( #[ 33 34 250 2 30 243 245] \
	#(  ) ) >

<primitive 112 temp 6		" displayAssign " \
	#( #[ 81 82 250 2 8 243 245] \
	#(  ) ) >

<primitive 112 temp 7		" display " \
	#( #[ 81 81 250 2 8 243 245] \
	#(  ) ) >

<primitive 112 temp 8		" debug: " \
	#( #[ 82 33 250 2 8 243 245] \
	#(  ) ) >

<primitive 112 temp 9		" date " \
	#( #[ 250 0 160 243 245] \
	#(  ) ) >

<primitive 98 #Smalltalk \
	<primitive 97 #Smalltalk #Dictionary #/u/smalltalk/prelude/smalltalk.st \
	#(  ) \
	#( #time: #sh: #perform:withArguments: #noDisplay #doPrimitive:withArguments: #displayAssign #display #debug: #date  ) \
	temp 3 3 > >

SHAR_EOF
if test 1062 -ne "`wc -c < 'smalltalk.p'`"
then
	echo shar: error transmitting "'smalltalk.p'" '(should have been 1062 characters)'
fi
fi # end of overwriting check
if test -f 'standard'
then
	echo shar: will not over-write existing file "'standard'"
else
cat << \SHAR_EOF > 'standard'
temp <- <primitive 110 10 >
<primitive 112 temp 1		" view " \
	#( #[ 32 250 1 156 242 245] \
	#(  ) ) >

<primitive 112 temp 2		" variables " \
	#( #[ 32 250 1 158 243 245] \
	#(  ) ) >

<primitive 112 temp 3		" superClass " \
	#( #[ 32 250 1 151 243 245] \
	#(  ) ) >

<primitive 112 temp 4		" respondsTo: " \
	#( #[ 32 114 34 162 247 18 34 33 250 2 155 247 2 91 243 \
 242 34 10 46 241 114 242 249 22 242 92 243 245] \
	#(  ) ) >

<primitive 112 temp 5		" respondsTo " \
	#( #[ 32 250 1 154 242 245] \
	#(  ) ) >

<primitive 112 temp 6		" printString " \
	#( #[ 32 250 1 152 243 245] \
	#(  ) ) >

<primitive 112 temp 7		" new: " \
	#( #[ 32 250 1 151 114 34 250 1 3 247 4 34 160 241 115 \
 242 32 35 250 2 153 115 32 48 250 2 155 247 5 35 \
 33 176 241 115 242 35 243 245] \
	#( #new:  ) ) >

<primitive 112 temp 8		" new " \
	#( #[ 32 250 1 151 113 33 250 1 3 247 4 33 160 241 114 \
 242 32 34 250 2 153 114 32 48 250 2 155 247 4 34 \
 160 241 114 242 34 243 245] \
	#( #new  ) ) >

<primitive 112 temp 9		" list " \
	#( #[ 32 250 1 157 242 245] \
	#(  ) ) >

<primitive 112 temp 10		" edit " \
	#( #[ 32 250 1 150 242 245] \
	#(  ) ) >

<primitive 98 #Class \
	<primitive 97 #Class #Object #/u/smalltalk/prelude/class.st \
	#(  ) \
	#( #view #variables #superClass #respondsTo: #respondsTo #printString #new: #new #list #edit  ) \
	temp 4 4 > >

temp <- <primitive 110 21 >
<primitive 112 temp 1		" shallowCopy " \
	#( #[ 32 250 1 4 113 33 80 199 247 4 32 243 248 26 242 \
 32 164 160 114 81 33 178 225 3 11 34 35 32 35 250 \
 2 111 250 3 112 243 179 242 34 243 242 245] \
	#(  ) ) >

<primitive 112 temp 2		" respondsTo: " \
	#( #[ 32 164 33 11 41 243 245] \
	#(  ) ) >

<primitive 112 temp 3		" printString " \
	#( #[ 32 10 16 243 245] \
	#(  ) ) >

<primitive 112 temp 4		" print " \
	#( #[ 32 169 250 1 121 242 245] \
	#(  ) ) >

<primitive 112 temp 5		" notNil " \
	#( #[ 91 243 245] \
	#(  ) ) >

<primitive 112 temp 6		" next " \
	#( #[ 93 243 245] \
	#(  ) ) >

<primitive 112 temp 7		" isNil " \
	#( #[ 92 243 245] \
	#(  ) ) >

<primitive 112 temp 8		" isMemberOf: " \
	#( #[ 33 32 164 181 243 245] \
	#(  ) ) >

<primitive 112 temp 9		" isKindOf: " \
	#( #[ 32 164 114 34 162 247 16 34 33 181 247 2 91 243 242 \
 34 10 46 241 114 242 249 20 242 92 243 245] \
	#(  ) ) >

<primitive 112 temp 10		" first " \
	#( #[ 32 243 245] \
	#(  ) ) >

<primitive 112 temp 11		" error: " \
	#( #[ 33 32 250 2 122 242 245] \
	#(  ) ) >

<primitive 112 temp 12		" do: " \
	#( #[ 32 166 114 34 162 247 11 33 34 180 242 32 167 241 114 \
 242 249 15 243 245] \
	#(  ) ) >

<primitive 112 temp 13		" deepCopy " \
	#( #[ 32 250 1 4 113 33 80 199 247 4 32 243 248 28 242 \
 32 164 160 114 81 33 178 225 3 13 34 35 32 35 250 \
 2 111 10 20 250 3 112 243 179 242 34 243 242 245] \
	#(  ) ) >

<primitive 112 temp 14		" copy " \
	#( #[ 32 10 42 243 245] \
	#(  ) ) >

<primitive 112 temp 15		" class " \
	#( #[ 32 250 1 1 243 245] \
	#(  ) ) >

<primitive 112 temp 16		" asSymbol " \
	#( #[ 32 10 16 10 17 243 245] \
	#(  ) ) >

<primitive 112 temp 17		" asString " \
	#( #[ 32 164 169 243 245] \
	#(  ) ) >

<primitive 112 temp 18		" ~= " \
	#( #[ 32 33 201 172 243 245] \
	#(  ) ) >

<primitive 112 temp 19		" = " \
	#( #[ 32 33 181 243 245] \
	#(  ) ) >

<primitive 112 temp 20		" ~~ " \
	#( #[ 32 33 181 172 243 245] \
	#(  ) ) >

<primitive 112 temp 21		" == " \
	#( #[ 32 33 250 2 7 243 245] \
	#(  ) ) >

<primitive 98 #Object \
	<primitive 97 #Object #Object #/u/smalltalk/prelude/object.st \
	#(  ) \
	#( #shallowCopy #respondsTo: #printString #print #notNil #next #isNil #isMemberOf: #isKindOf: #first #error: #do: #deepCopy #copy #class #asSymbol #asString #~= #= #~~ #==  ) \
	temp 4 7 > >

temp <- <primitive 110 18 >
<primitive 112 temp 1		" sameAs: " \
	#( #[ 32 33 250 2 6 247 7 32 33 250 2 102 248 4 242 \
 32 10 19 243 245] \
	#(  ) ) >

<primitive 112 temp 2		" size " \
	#( #[ 32 250 1 100 243 245] \
	#(  ) ) >

<primitive 112 temp 3		" print " \
	#( #[ 32 250 1 121 242 245] \
	#(  ) ) >

<primitive 112 temp 4		" printString " \
	#( #[ 32 250 1 109 243 245] \
	#(  ) ) >

<primitive 112 temp 5		" new: " \
	#( #[ 33 250 1 115 243 245] \
	#(  ) ) >

<primitive 112 temp 6		" deepCopy " \
	#( #[ 32 250 1 107 243 245] \
	#(  ) ) >

<primitive 112 temp 7		" copyFrom:length: " \
	#( #[ 32 33 34 250 3 106 243 245] \
	#(  ) ) >

<primitive 112 temp 8		" copyFrom:to: " \
	#( #[ 32 33 34 33 193 81 192 250 3 106 243 245] \
	#(  ) ) >

<primitive 112 temp 9		" compareError " \
	#( #[ 32 48 188 243 245] \
	#( 'strings can only be compared to strings'  ) ) >

<primitive 112 temp 10		" at:put: " \
	#( #[ 32 33 34 250 3 105 242 245] \
	#(  ) ) >

<primitive 112 temp 11		" at: " \
	#( #[ 32 33 250 2 104 243 245] \
	#(  ) ) >

<primitive 112 temp 12		" asSymbol " \
	#( #[ 32 250 1 108 243 245] \
	#(  ) ) >

<primitive 112 temp 13		" > " \
	#( #[ 32 33 250 2 6 247 9 32 33 250 2 101 80 204 248 \
 4 242 32 10 19 243 245] \
	#(  ) ) >

<primitive 112 temp 14		" >= " \
	#( #[ 32 33 250 2 6 247 9 32 33 250 2 101 80 203 248 \
 4 242 32 10 19 243 245] \
	#(  ) ) >

<primitive 112 temp 15		" <= " \
	#( #[ 32 33 250 2 6 247 9 32 33 250 2 101 80 200 248 \
 4 242 32 10 19 243 245] \
	#(  ) ) >

<primitive 112 temp 16		" < " \
	#( #[ 32 33 250 2 6 247 9 32 33 250 2 101 80 199 248 \
 4 242 32 10 19 243 245] \
	#(  ) ) >

<primitive 112 temp 17		" = " \
	#( #[ 32 33 250 2 6 247 9 32 33 250 2 101 80 201 248 \
 4 242 32 10 19 243 245] \
	#(  ) ) >

<primitive 112 temp 18		" , " \
	#( #[ 32 33 250 2 103 243 245] \
	#(  ) ) >

<primitive 98 #String \
	<primitive 97 #String #ArrayedCollection #/u/smalltalk/prelude/string.st \
	#(  ) \
	#( #sameAs: #size #print #printString #new: #deepCopy #copyFrom:length: #copyFrom:to: #compareError #at:put: #at: #asSymbol #> #>= #<= #< #= #,  ) \
	temp 3 5 > >

temp <- <primitive 110 1 >
<primitive 112 temp 1		" nothing " \
	#( #[ 81 242 245] \
	#(  ) ) >

<primitive 98 #ArrayedCollection \
	<primitive 97 #ArrayedCollection #Object #/u/smalltalk/prelude/larray.st \
	#(  ) \
	#( #nothing  ) \
	temp 1 2 > >

temp <- <primitive 110 3 >
<primitive 112 temp 1		" printString " \
	#( #[ 48 243 245] \
	#( 'nil'  ) ) >

<primitive 112 temp 2		" notNil " \
	#( #[ 92 243 245] \
	#(  ) ) >

<primitive 112 temp 3		" isNil " \
	#( #[ 91 243 245] \
	#(  ) ) >

<primitive 98 #UndefinedObject \
	<primitive 97 #UndefinedObject #Object #/u/smalltalk/prelude/nil.st \
	#(  ) \
	#( #printString #notNil #isNil  ) \
	temp 1 2 > >

temp <- <primitive 110 5 >
<primitive 112 temp 1		" size " \
	#( #[ 32 250 1 4 243 245] \
	#(  ) ) >

<primitive 112 temp 2		" printString " \
	#( #[ 48 113 32 250 1 4 114 34 80 204 247 21 32 34 250 \
 2 111 169 49 11 17 33 11 17 113 34 81 193 241 114 \
 242 249 26 242 50 33 11 17 243 245] \
	#( ')' ' ' '#( '  ) ) >

<primitive 112 temp 3		" at:put: " \
	#( #[ 33 81 199 251 6 33 32 250 1 4 204 247 6 32 48 \
 188 242 93 243 242 32 33 34 250 3 112 242 34 243 245 \
] \
	#( 'index error'  ) ) >

<primitive 112 temp 4		" at: " \
	#( #[ 33 81 199 251 6 33 32 250 1 4 204 247 6 32 48 \
 188 242 93 243 242 32 33 250 2 111 243 245] \
	#( 'index error'  ) ) >

<primitive 112 temp 5		" new: " \
	#( #[ 33 250 1 114 243 245] \
	#(  ) ) >

<primitive 98 #Array \
	<primitive 97 #Array #ArrayedCollection #/u/smalltalk/prelude/array.st \
	#(  ) \
	#( #size #printString #at:put: #at: #new:  ) \
	temp 3 4 > >

temp <- <primitive 110 6 >
<primitive 112 temp 1		" xor: " \
	#( #[ 32 33 182 243 245] \
	#(  ) ) >

<primitive 112 temp 2		" eqv: " \
	#( #[ 32 33 181 243 245] \
	#(  ) ) >

<primitive 112 temp 3		" or: " \
	#( #[ 32 251 2 33 165 243 245] \
	#(  ) ) >

<primitive 112 temp 4		" and: " \
	#( #[ 32 252 2 33 165 243 245] \
	#(  ) ) >

<primitive 112 temp 5		" | " \
	#( #[ 32 251 1 33 243 245] \
	#(  ) ) >

<primitive 112 temp 6		" & " \
	#( #[ 32 252 1 33 243 245] \
	#(  ) ) >

<primitive 98 #Boolean \
	<primitive 97 #Boolean #Object #/u/smalltalk/prelude/boolean.st \
	#(  ) \
	#( #xor: #eqv: #or: #and: #| #&  ) \
	temp 2 3 > >

temp <- <primitive 110 5 >
<primitive 112 temp 1		" not " \
	#( #[ 92 243 245] \
	#(  ) ) >

<primitive 112 temp 2		" ifFalse: " \
	#( #[ 93 243 245] \
	#(  ) ) >

<primitive 112 temp 3		" ifTrue: " \
	#( #[ 33 165 243 245] \
	#(  ) ) >

<primitive 112 temp 4		" ifFalse:ifTrue: " \
	#( #[ 34 165 243 245] \
	#(  ) ) >

<primitive 112 temp 5		" ifTrue:ifFalse: " \
	#( #[ 33 165 243 245] \
	#(  ) ) >

<primitive 98 #True \
	<primitive 97 #True #Boolean #/u/smalltalk/prelude/true.st \
	#(  ) \
	#( #not #ifFalse: #ifTrue: #ifFalse:ifTrue: #ifTrue:ifFalse:  ) \
	temp 3 2 > >

temp <- <primitive 110 5 >
<primitive 112 temp 1		" not " \
	#( #[ 91 243 245] \
	#(  ) ) >

<primitive 112 temp 2		" ifFalse: " \
	#( #[ 33 165 243 245] \
	#(  ) ) >

<primitive 112 temp 3		" ifTrue: " \
	#( #[ 93 243 245] \
	#(  ) ) >

<primitive 112 temp 4		" ifFalse:ifTrue: " \
	#( #[ 33 165 243 245] \
	#(  ) ) >

<primitive 112 temp 5		" ifTrue:ifFalse: " \
	#( #[ 34 165 243 245] \
	#(  ) ) >

<primitive 98 #False \
	<primitive 97 #False #Boolean #/u/smalltalk/prelude/false.st \
	#(  ) \
	#( #not #ifFalse: #ifTrue: #ifFalse:ifTrue: #ifTrue:ifFalse:  ) \
	temp 3 2 > >

temp <- <primitive 110 14 >
<primitive 112 temp 1		" value:value:value:value:value: " \
	#( #[ 85 250 1 140 242 245] \
	#(  ) ) >

<primitive 112 temp 2		" value:value:value:value: " \
	#( #[ 84 250 1 140 242 245] \
	#(  ) ) >

<primitive 112 temp 3		" value:value:value: " \
	#( #[ 83 250 1 140 242 245] \
	#(  ) ) >

<primitive 112 temp 4		" value:value: " \
	#( #[ 82 250 1 140 242 245] \
	#(  ) ) >

<primitive 112 temp 5		" value: " \
	#( #[ 81 250 1 140 242 245] \
	#(  ) ) >

<primitive 112 temp 6		" value " \
	#( #[ 80 250 1 140 242 245] \
	#(  ) ) >

<primitive 112 temp 7		" whileFalse: " \
	#( #[ 32 165 246 5 33 165 242 249 9 243 245] \
	#(  ) ) >

<primitive 112 temp 8		" whileFalse " \
	#( #[ 32 165 246 4 93 242 249 8 243 245] \
	#(  ) ) >

<primitive 112 temp 9		" whileTrue: " \
	#( #[ 32 165 247 5 33 165 242 249 9 243 245] \
	#(  ) ) >

<primitive 112 temp 10		" whileTrue " \
	#( #[ 32 165 247 4 93 242 249 8 243 245] \
	#(  ) ) >

<primitive 112 temp 11		" forkWith: " \
	#( #[ 32 33 11 35 10 40 242 93 243 245] \
	#(  ) ) >

<primitive 112 temp 12		" fork " \
	#( #[ 32 10 33 10 40 242 93 243 245] \
	#(  ) ) >

<primitive 112 temp 13		" newProcessWith: " \
	#( #[ 32 33 250 2 141 243 245] \
	#(  ) ) >

<primitive 112 temp 14		" newProcess " \
	#( #[ 32 250 1 141 243 245] \
	#(  ) ) >

<primitive 98 #Block \
	<primitive 97 #Block #Object #/u/smalltalk/prelude/block.st \
	#(  ) \
	#( #value:value:value:value:value: #value:value:value:value: #value:value:value: #value:value: #value: #value #whileFalse: #whileFalse #whileTrue: #whileTrue #forkWith: #fork #newProcessWith: #newProcess  ) \
	temp 6 3 > >

temp <- <primitive 110 3 >
<primitive 112 temp 1		" asString " \
	#( #[ 32 250 1 93 243 245] \
	#(  ) ) >

<primitive 112 temp 2		" printString " \
	#( #[ 32 250 1 92 243 245] \
	#(  ) ) >

<primitive 112 temp 3		" == " \
	#( #[ 32 33 250 2 6 247 7 32 33 250 2 91 248 2 242 \
 92 243 245] \
	#(  ) ) >

<primitive 98 #Symbol \
	<primitive 97 #Symbol #Object #/u/smalltalk/prelude/symbol.st \
	#(  ) \
	#( #asString #printString #==  ) \
	temp 2 4 > >

temp <- <primitive 110 9 >
<primitive 112 temp 1		" max: " \
	#( #[ 32 33 204 247 3 32 248 2 242 33 243 245] \
	#(  ) ) >

<primitive 112 temp 2		" min: " \
	#( #[ 32 33 199 247 3 32 248 2 242 33 243 245] \
	#(  ) ) >

<primitive 112 temp 3		" between:and: " \
	#( #[ 32 33 203 252 3 32 34 200 243 245] \
	#(  ) ) >

<primitive 112 temp 4		" > " \
	#( #[ 33 32 199 243 245] \
	#(  ) ) >

<primitive 112 temp 5		" >= " \
	#( #[ 32 33 204 251 3 32 33 201 243 245] \
	#(  ) ) >

<primitive 112 temp 6		" ~= " \
	#( #[ 32 33 201 172 243 245] \
	#(  ) ) >

<primitive 112 temp 7		" = " \
	#( #[ 32 33 204 251 3 32 33 199 172 243 245] \
	#(  ) ) >

<primitive 112 temp 8		" < " \
	#( #[ 33 32 204 243 245] \
	#(  ) ) >

<primitive 112 temp 9		" <= " \
	#( #[ 32 33 199 251 3 32 33 201 243 245] \
	#(  ) ) >

<primitive 98 #Magnitude \
	<primitive 97 #Magnitude #Object #/u/smalltalk/prelude/magnitude.st \
	#(  ) \
	#( #max: #min: #between:and: #> #>= #~= #= #< #<=  ) \
	temp 3 4 > >

temp <- <primitive 110 30 >
<primitive 112 temp 1		" truncateTo: " \
	#( #[ 32 33 190 10 47 33 194 243 245] \
	#(  ) ) >

<primitive 112 temp 2		" to:by: " \
	#( #[ 5 46 160 241 32 33 34 131 0 242 243 245] \
	#( #from:to:by:  ) ) >

<primitive 112 temp 3		" to: " \
	#( #[ 5 46 160 241 32 33 81 131 0 242 243 245] \
	#( #from:to:by:  ) ) >

<primitive 112 temp 4		" strictlyPositive " \
	#( #[ 32 80 204 243 245] \
	#(  ) ) >

<primitive 112 temp 5		" squared " \
	#( #[ 32 32 194 243 245] \
	#(  ) ) >

<primitive 112 temp 6		" sqrt " \
	#( #[ 32 175 10 43 243 245] \
	#(  ) ) >

<primitive 112 temp 7		" sign " \
	#( #[ 32 80 199 247 3 90 248 11 242 32 80 204 247 3 81 \
 248 2 242 80 243 245] \
	#(  ) ) >

<primitive 112 temp 8		" roundTo: " \
	#( #[ 32 33 190 10 41 33 194 243 245] \
	#(  ) ) >

<primitive 112 temp 9		" reciprocal " \
	#( #[ 48 32 190 243 245] \
	#( 1.00  ) ) >

<primitive 112 temp 10		" raisedTo: " \
	#( #[ 32 175 33 175 11 16 243 245] \
	#(  ) ) >

<primitive 112 temp 11		" radians " \
	#( #[ 5 54 32 175 176 243 245] \
	#(  ) ) >

<primitive 112 temp 12		" positive " \
	#( #[ 32 80 203 243 245] \
	#(  ) ) >

<primitive 112 temp 13		" pi " \
	#( #[ 32 48 194 243 245] \
	#( 3.1415926  ) ) >

<primitive 112 temp 14		" negative " \
	#( #[ 32 80 199 243 245] \
	#(  ) ) >

<primitive 112 temp 15		" negated " \
	#( #[ 80 32 193 243 245] \
	#(  ) ) >

<primitive 112 temp 16		" log: " \
	#( #[ 32 10 32 33 10 32 190 243 245] \
	#(  ) ) >

<primitive 112 temp 17		" ln " \
	#( #[ 32 175 10 32 243 245] \
	#(  ) ) >

<primitive 112 temp 18		" gamma " \
	#( #[ 32 175 10 26 243 245] \
	#(  ) ) >

<primitive 112 temp 19		" exp " \
	#( #[ 32 175 10 23 243 245] \
	#(  ) ) >

<primitive 112 temp 20		" abs " \
	#( #[ 32 80 199 247 5 80 32 193 248 2 242 32 243 245] \
	#(  ) ) >

<primitive 112 temp 21		" @ " \
	#( #[ 5 53 160 32 11 50 33 11 51 243 245] \
	#(  ) ) >

<primitive 112 temp 22		" ^ " \
	#( #[ 32 175 33 175 11 16 243 245] \
	#(  ) ) >

<primitive 112 temp 23		" / " \
	#( #[ 32 33 11 34 33 32 11 34 190 243 245] \
	#(  ) ) >

<primitive 112 temp 24		" * " \
	#( #[ 32 33 11 34 33 32 11 34 194 243 245] \
	#(  ) ) >

<primitive 112 temp 25		" - " \
	#( #[ 32 33 11 34 33 32 11 34 193 243 245] \
	#(  ) ) >

<primitive 112 temp 26		" + " \
	#( #[ 32 33 11 34 33 32 11 34 192 243 245] \
	#(  ) ) >

<primitive 112 temp 27		" > " \
	#( #[ 32 33 11 34 33 32 11 34 204 243 245] \
	#(  ) ) >

<primitive 112 temp 28		" < " \
	#( #[ 32 33 11 34 33 32 11 34 199 243 245] \
	#(  ) ) >

<primitive 112 temp 29		" = " \
	#( #[ 32 33 11 34 33 32 11 34 201 243 245] \
	#(  ) ) >

<primitive 112 temp 30		" maxtype: " \
	#( #[ 32 33 250 2 9 247 3 32 248 4 242 33 32 191 243 \
 245] \
	#(  ) ) >

<primitive 98 #Number \
	<primitive 97 #Number #Magnitude #/u/smalltalk/prelude/number.st \
	#(  ) \
	#( #truncateTo: #to:by: #to: #strictlyPositive #squared #sqrt #sign #roundTo: #reciprocal #raisedTo: #radians #positive #pi #negative #negated #log: #ln #gamma #exp #abs #@ #^ #/ #* #- #+ #> #< #= #maxtype:  ) \
	temp 3 6 > >

temp <- <primitive 110 31 >
<primitive 112 temp 1		" timesRepeat: " \
	#( #[ 80 114 34 32 199 247 11 33 165 242 34 81 192 241 114 \
 242 249 16 242 245] \
	#(  ) ) >

<primitive 112 temp 2		" rem: " \
	#( #[ 32 33 250 2 6 247 7 32 33 250 2 29 248 4 242 \
 32 10 35 243 245] \
	#(  ) ) >

<primitive 112 temp 3		" radix: " \
	#( #[ 32 33 250 2 26 243 245] \
	#(  ) ) >

<primitive 112 temp 4		" quo: " \
	#( #[ 32 33 250 2 6 247 7 32 33 250 2 28 248 4 242 \
 32 10 35 243 245] \
	#(  ) ) >

<primitive 112 temp 5		" odd " \
	#( #[ 32 82 205 80 202 243 245] \
	#(  ) ) >

<primitive 112 temp 6		" noMask: " \
	#( #[ 80 32 33 197 201 243 245] \
	#(  ) ) >

<primitive 112 temp 7		" lcm: " \
	#( #[ 32 33 250 2 6 247 10 32 33 194 32 33 11 27 206 \
 248 4 242 32 10 35 243 245] \
	#(  ) ) >

<primitive 112 temp 8		" highBit " \
	#( #[ 32 250 1 34 243 245] \
	#(  ) ) >

<primitive 112 temp 9		" gcd: " \
	#( #[ 32 33 250 2 6 247 7 32 33 250 2 20 248 4 242 \
 32 10 35 243 245] \
	#(  ) ) >

<primitive 112 temp 10		" factorial " \
	#( #[ 32 250 1 38 243 245] \
	#(  ) ) >

<primitive 112 temp 11		" even " \
	#( #[ 32 82 205 80 201 243 245] \
	#(  ) ) >

<primitive 112 temp 12		" bitXor: " \
	#( #[ 32 33 250 2 24 243 245] \
	#(  ) ) >

<primitive 112 temp 13		" bitShift: " \
	#( #[ 32 33 250 2 25 243 245] \
	#(  ) ) >

<primitive 112 temp 14		" bitOr: " \
	#( #[ 32 33 250 2 22 243 245] \
	#(  ) ) >

<primitive 112 temp 15		" bitInvert " \
	#( #[ 32 250 1 33 243 245] \
	#(  ) ) >

<primitive 112 temp 16		" bitAt: " \
	#( #[ 32 33 250 2 21 243 245] \
	#(  ) ) >

<primitive 112 temp 17		" bitAnd: " \
	#( #[ 32 33 250 2 23 243 245] \
	#(  ) ) >

<primitive 112 temp 18		" asString " \
	#( #[ 32 250 1 37 243 245] \
	#(  ) ) >

<primitive 112 temp 19		" asFloat " \
	#( #[ 32 250 1 39 243 245] \
	#(  ) ) >

<primitive 112 temp 20		" asCharacter " \
	#( #[ 32 250 1 36 243 245] \
	#(  ) ) >

<primitive 112 temp 21		" anyMask: " \
	#( #[ 80 32 33 250 2 23 202 243 245] \
	#(  ) ) >

<primitive 112 temp 22		" allMask: " \
	#( #[ 33 32 33 250 2 23 201 243 245] \
	#(  ) ) >

<primitive 112 temp 23		" \\ " \
	#( #[ 32 33 250 2 6 247 18 32 32 80 199 247 3 90 248 \
 2 242 81 194 114 34 33 205 248 4 242 32 10 35 243 \
 245] \
	#(  ) ) >

<primitive 112 temp 24		" // " \
	#( #[ 32 33 250 2 6 247 7 32 33 250 2 19 248 4 242 \
 32 10 35 243 245] \
	#(  ) ) >

<primitive 112 temp 25		" / " \
	#( #[ 32 175 33 190 243 245] \
	#(  ) ) >

<primitive 112 temp 26		" * " \
	#( #[ 32 33 250 2 6 247 7 32 33 250 2 18 248 5 242 \
 32 33 145 0 243 245] \
	#( #*  ) ) >

<primitive 112 temp 27		" - " \
	#( #[ 32 33 250 2 6 247 7 32 33 250 2 11 248 5 242 \
 32 33 145 0 243 245] \
	#( #-  ) ) >

<primitive 112 temp 28		" + " \
	#( #[ 32 33 250 2 6 247 7 32 33 250 2 10 248 5 242 \
 32 33 145 0 243 245] \
	#( #+  ) ) >

<primitive 112 temp 29		" < " \
	#( #[ 32 33 250 2 6 247 7 32 33 250 2 12 248 5 242 \
 32 33 145 0 243 245] \
	#( #<  ) ) >

<primitive 112 temp 30		" > " \
	#( #[ 32 33 250 2 6 247 7 32 33 250 2 13 248 5 242 \
 32 33 145 0 243 245] \
	#( #>  ) ) >

<primitive 112 temp 31		" = " \
	#( #[ 32 33 250 2 6 247 7 32 33 250 2 16 248 5 242 \
 32 33 145 0 243 245] \
	#( #=  ) ) >

<primitive 98 #Integer \
	<primitive 97 #Integer #Number #/u/smalltalk/prelude/integer.st \
	#(  ) \
	#( #timesRepeat: #rem: #radix: #quo: #odd #noMask: #lcm: #highBit #gcd: #factorial #even #bitXor: #bitShift: #bitOr: #bitInvert #bitAt: #bitAnd: #asString #asFloat #asCharacter #anyMask: #allMask: #\\ #// #/ #* #- #+ #< #> #=  ) \
	temp 3 5 > >

temp <- <primitive 110 18 >
<primitive 112 temp 1		" printString " \
	#( #[ 48 32 250 1 58 11 17 243 245] \
	#( '$'  ) ) >

<primitive 112 temp 2		" isVowel " \
	#( #[ 32 250 1 51 243 245] \
	#(  ) ) >

<primitive 112 temp 3		" isUppercase " \
	#( #[ 32 48 49 218 243 245] \
	#( $A $Z  ) ) >

<primitive 112 temp 4		" isSeparator " \
	#( #[ 32 250 1 55 243 245] \
	#(  ) ) >

<primitive 112 temp 5		" isLowercase " \
	#( #[ 32 48 49 218 243 245] \
	#( $a $z  ) ) >

<primitive 112 temp 6		" isLetter " \
	#( #[ 32 10 28 251 3 32 10 29 243 245] \
	#(  ) ) >

<primitive 112 temp 7		" isDigit " \
	#( #[ 32 48 49 218 243 245] \
	#( $0 $9  ) ) >

<primitive 112 temp 8		" isAlphaNumeric " \
	#( #[ 32 250 1 56 243 245] \
	#(  ) ) >

<primitive 112 temp 9		" digitValue " \
	#( #[ 32 250 1 50 241 113 161 247 3 32 48 188 242 33 243 \
 245] \
	#( 'digitValue on nondigit char'  ) ) >

<primitive 112 temp 10		" compareError " \
	#( #[ 32 48 188 243 245] \
	#( 'char cannot be compared to non char'  ) ) >

<primitive 112 temp 11		" asString " \
	#( #[ 32 250 1 58 243 245] \
	#(  ) ) >

<primitive 112 temp 12		" asUppercase " \
	#( #[ 32 250 1 53 247 6 32 250 1 57 248 2 242 32 243 \
 245] \
	#(  ) ) >

<primitive 112 temp 13		" asLowercase " \
	#( #[ 32 250 1 54 247 6 32 250 1 57 248 2 242 32 243 \
 245] \
	#(  ) ) >

<primitive 112 temp 14		" asciiValue " \
	#( #[ 32 250 1 59 243 245] \
	#(  ) ) >

<primitive 112 temp 15		" > " \
	#( #[ 32 33 250 2 6 247 7 32 33 250 2 43 248 4 242 \
 32 10 19 243 245] \
	#(  ) ) >

<primitive 112 temp 16		" = " \
	#( #[ 32 33 250 2 6 247 7 32 33 250 2 46 248 4 242 \
 32 10 19 243 245] \
	#(  ) ) >

<primitive 112 temp 17		" < " \
	#( #[ 32 33 250 2 6 247 7 32 33 250 2 42 248 4 242 \
 32 10 19 243 245] \
	#(  ) ) >

<primitive 112 temp 18		" == " \
	#( #[ 32 33 250 2 6 247 7 32 33 250 2 46 248 2 242 \
 92 243 245] \
	#(  ) ) >

<primitive 98 #Char \
	<primitive 97 #Char #Magnitude #/u/smalltalk/prelude/char.st \
	#(  ) \
	#( #printString #isVowel #isUppercase #isSeparator #isLowercase #isLetter #isDigit #isAlphaNumeric #digitValue #compareError #asString #asUppercase #asLowercase #asciiValue #> #= #< #==  ) \
	temp 2 4 > >

temp <- <primitive 110 25 >
<primitive 112 temp 1		" truncated " \
	#( #[ 32 48 199 247 6 32 250 1 73 248 5 242 32 250 1 \
 72 243 245] \
	#( 0.0  ) ) >

<primitive 112 temp 2		" sqrt " \
	#( #[ 32 250 1 71 243 245] \
	#(  ) ) >

<primitive 112 temp 3		" rounded " \
	#( #[ 32 48 192 250 1 72 243 245] \
	#( 0.5  ) ) >

<primitive 112 temp 4		" radix: " \
	#( #[ 32 33 250 2 89 243 245] \
	#(  ) ) >

<primitive 112 temp 5		" ln " \
	#( #[ 32 250 1 70 243 245] \
	#(  ) ) >

<primitive 112 temp 6		" integerPart " \
	#( #[ 32 250 1 75 243 245] \
	#(  ) ) >

<primitive 112 temp 7		" gamma " \
	#( #[ 32 250 1 77 243 245] \
	#(  ) ) >

<primitive 112 temp 8		" fractionPart " \
	#( #[ 32 250 1 76 243 245] \
	#(  ) ) >

<primitive 112 temp 9		" floor " \
	#( #[ 32 250 1 72 243 245] \
	#(  ) ) >

<primitive 112 temp 10		" exp " \
	#( #[ 32 250 1 79 243 245] \
	#(  ) ) >

<primitive 112 temp 11		" coerce: " \
	#( #[ 33 175 243 245] \
	#(  ) ) >

<primitive 112 temp 12		" ceiling " \
	#( #[ 32 250 1 73 243 245] \
	#(  ) ) >

<primitive 112 temp 13		" asString " \
	#( #[ 32 250 1 78 243 245] \
	#(  ) ) >

<primitive 112 temp 14		" asFloat " \
	#( #[ 32 243 245] \
	#(  ) ) >

<primitive 112 temp 15		" arcTan " \
	#( #[ 5 54 32 250 1 86 176 243 245] \
	#(  ) ) >

<primitive 112 temp 16		" arcSin " \
	#( #[ 5 54 32 250 1 84 176 243 245] \
	#(  ) ) >

<primitive 112 temp 17		" arcCos " \
	#( #[ 5 54 32 250 1 85 176 243 245] \
	#(  ) ) >

<primitive 112 temp 18		" ^ " \
	#( #[ 32 33 250 2 6 247 7 32 33 250 2 88 248 5 242 \
 32 33 145 0 243 245] \
	#( #raisedTo:  ) ) >

<primitive 112 temp 19		" / " \
	#( #[ 32 33 250 2 6 247 7 32 33 250 2 69 248 5 242 \
 32 33 145 0 243 245] \
	#( #/  ) ) >

<primitive 112 temp 20		" * " \
	#( #[ 32 33 250 2 6 247 7 32 33 250 2 68 248 5 242 \
 32 33 145 0 243 245] \
	#( #*  ) ) >

<primitive 112 temp 21		" - " \
	#( #[ 32 33 250 2 6 247 7 32 33 250 2 61 248 5 242 \
 32 33 145 0 243 245] \
	#( #-  ) ) >

<primitive 112 temp 22		" + " \
	#( #[ 32 33 250 2 6 247 7 32 33 250 2 60 248 5 242 \
 32 33 145 0 243 245] \
	#( #+  ) ) >

<primitive 112 temp 23		" > " \
	#( #[ 32 33 250 2 6 247 7 32 33 250 2 63 248 5 242 \
 32 33 145 0 243 245] \
	#( #>  ) ) >

<primitive 112 temp 24		" < " \
	#( #[ 32 33 250 2 6 247 7 32 33 250 2 62 248 5 242 \
 32 33 145 0 243 245] \
	#( #<  ) ) >

<primitive 112 temp 25		" = " \
	#( #[ 32 33 250 2 6 247 7 32 33 250 2 66 248 5 242 \
 32 33 145 0 243 245] \
	#( #=  ) ) >

<primitive 98 #Float \
	<primitive 97 #Float #Number #/u/smalltalk/prelude/float.st \
	#(  ) \
	#( #truncated #sqrt #rounded #radix: #ln #integerPart #gamma #fractionPart #floor #exp #coerce: #ceiling #asString #asFloat #arcTan #arcSin #arcCos #^ #/ #* #- #+ #> #< #=  ) \
	temp 2 4 > >

temp <- <primitive 110 8 >
<primitive 112 temp 1		" printString " \
	#( #[ 16 10 16 48 11 17 243 245] \
	#( ' radians'  ) ) >

<primitive 112 temp 2		" asFloat " \
	#( #[ 16 243 245] \
	#(  ) ) >

<primitive 112 temp 3		" tan " \
	#( #[ 16 250 1 81 16 250 1 82 190 243 245] \
	#(  ) ) >

<primitive 112 temp 4		" cos " \
	#( #[ 16 250 1 82 243 245] \
	#(  ) ) >

<primitive 112 temp 5		" sin " \
	#( #[ 16 250 1 81 243 245] \
	#(  ) ) >

<primitive 112 temp 6		" = " \
	#( #[ 16 33 175 201 243 245] \
	#(  ) ) >

<primitive 112 temp 7		" < " \
	#( #[ 16 33 175 199 243 245] \
	#(  ) ) >

<primitive 112 temp 8		" new: " \
	#( #[ 33 175 250 1 80 96 245] \
	#(  ) ) >

<primitive 98 #Radian \
	<primitive 97 #Radian #Magnitude #/u/smalltalk/prelude/radian.st \
	#(  #value ) \
	#( #printString #asFloat #tan #cos #sin #= #< #new:  ) \
	temp 2 3 > >

temp <- <primitive 110 21 >
<primitive 112 temp 1		" y: " \
	#( #[ 33 97 245] \
	#(  ) ) >

<primitive 112 temp 2		" y " \
	#( #[ 17 243 245] \
	#(  ) ) >

<primitive 112 temp 3		" x:y: " \
	#( #[ 33 96 34 97 245] \
	#(  ) ) >

<primitive 112 temp 4		" x: " \
	#( #[ 33 96 245] \
	#(  ) ) >

<primitive 112 temp 5		" x " \
	#( #[ 16 243 245] \
	#(  ) ) >

<primitive 112 temp 6		" transpose " \
	#( #[ 5 53 160 17 11 50 16 11 51 243 245] \
	#(  ) ) >

<primitive 112 temp 7		" printString " \
	#( #[ 16 169 48 11 17 17 169 11 17 243 245] \
	#( ' @ '  ) ) >

<primitive 112 temp 8		" min: " \
	#( #[ 5 53 160 16 33 10 49 207 11 50 17 33 10 50 207 \
 11 51 243 245] \
	#(  ) ) >

<primitive 112 temp 9		" max: " \
	#( #[ 5 53 160 16 33 10 49 12 16 11 50 17 33 10 50 \
 12 16 11 51 243 245] \
	#(  ) ) >

<primitive 112 temp 10		" dist: " \
	#( #[ 16 33 10 49 193 10 44 17 33 10 50 193 10 44 192 \
 10 43 243 245] \
	#(  ) ) >

<primitive 112 temp 11		" asString " \
	#( #[ 16 10 16 48 11 17 17 10 16 11 17 243 245] \
	#( ' @ '  ) ) >

<primitive 112 temp 12		" abs " \
	#( #[ 5 53 160 16 173 11 50 17 173 11 51 243 245] \
	#(  ) ) >

<primitive 112 temp 13		" // " \
	#( #[ 5 53 160 16 33 11 18 11 50 17 33 11 18 11 51 \
 243 245] \
	#(  ) ) >

<primitive 112 temp 14		" / " \
	#( #[ 5 53 160 16 33 190 11 50 17 33 190 11 51 243 245 \
] \
	#(  ) ) >

<primitive 112 temp 15		" - " \
	#( #[ 5 53 160 16 33 10 49 193 11 50 17 33 10 50 193 \
 11 51 243 245] \
	#(  ) ) >

<primitive 112 temp 16		" + " \
	#( #[ 5 53 160 16 33 10 49 192 11 50 17 33 10 50 192 \
 11 51 243 245] \
	#(  ) ) >

<primitive 112 temp 17		" * " \
	#( #[ 5 53 160 16 33 194 11 50 17 33 194 11 51 243 245 \
] \
	#(  ) ) >

<primitive 112 temp 18		" = " \
	#( #[ 16 33 10 49 201 252 5 17 33 10 50 201 243 245] \
	#(  ) ) >

<primitive 112 temp 19		" >= " \
	#( #[ 16 33 10 49 203 252 5 17 33 10 50 203 243 245] \
	#(  ) ) >

<primitive 112 temp 20		" <= " \
	#( #[ 16 33 10 49 200 252 5 17 33 10 50 199 243 245] \
	#(  ) ) >

<primitive 112 temp 21		" < " \
	#( #[ 16 33 10 49 199 252 5 17 33 10 50 199 243 245] \
	#(  ) ) >

<primitive 98 #Point \
	<primitive 97 #Point #Magnitude #/u/smalltalk/prelude/point.st \
	#(  #xvalue #yvalue ) \
	#( #y: #y #x:y: #x: #x #transpose #printString #min: #max: #dist: #asString #abs #// #/ #- #+ #* #= #>= #<= #<  ) \
	temp 3 4 > >

temp <- <primitive 110 7 >
<primitive 112 temp 1		" next: " \
	#( #[ 5 30 33 176 114 81 33 178 225 3 6 34 35 32 167 \
 208 243 179 242 34 243 245] \
	#(  ) ) >

<primitive 112 temp 2		" randInteger: " \
	#( #[ 32 167 33 194 10 47 81 192 243 245] \
	#(  ) ) >

<primitive 112 temp 3		" between:and: " \
	#( #[ 32 167 34 33 193 194 33 192 243 245] \
	#(  ) ) >

<primitive 112 temp 4		" next " \
	#( #[ 16 250 1 35 241 96 250 1 32 243 245] \
	#(  ) ) >

<primitive 112 temp 5		" first " \
	#( #[ 16 250 1 35 241 96 250 1 32 243 245] \
	#(  ) ) >

<primitive 112 temp 6		" randomize " \
	#( #[ 250 0 161 96 245] \
	#(  ) ) >

<primitive 112 temp 7		" new " \
	#( #[ 81 96 245] \
	#(  ) ) >

<primitive 98 #Random \
	<primitive 97 #Random #Object #/u/smalltalk/prelude/random.st \
	#(  #seed ) \
	#( #next: #randInteger: #between:and: #next #first #randomize #new  ) \
	temp 4 6 > >

temp <- <primitive 110 23 >
<primitive 112 temp 1		" size " \
	#( #[ 80 113 32 225 2 6 33 81 192 241 113 243 179 242 33 \
 243 245] \
	#(  ) ) >

<primitive 112 temp 2		" shallowCopy " \
	#( #[ 5 48 160 113 32 225 2 5 33 34 11 22 243 179 242 \
 32 33 191 243 245] \
	#(  ) ) >

<primitive 112 temp 3		" select: " \
	#( #[ 32 32 164 160 226 2 11 33 35 180 247 3 34 35 189 \
 242 34 243 215 243 245] \
	#(  ) ) >

<primitive 112 temp 4		" remove:ifAbsent: " \
	#( #[ 32 33 11 30 247 6 32 33 11 39 248 3 242 34 165 \
 243 245] \
	#(  ) ) >

<primitive 112 temp 5		" remove: " \
	#( #[ 32 33 224 4 32 48 188 244 216 242 33 243 245] \
	#( 'attempt to remove object not found in collection'  ) ) >

<primitive 112 temp 6		" reject: " \
	#( #[ 32 225 2 5 33 34 180 172 243 11 44 243 245] \
	#(  ) ) >

<primitive 112 temp 7		" printString " \
	#( #[ 32 32 164 169 48 11 17 226 1 9 33 49 11 17 34 \
 169 11 17 243 215 50 11 17 243 245] \
	#( ' (' ' ' ' )'  ) ) >

<primitive 112 temp 8		" occurrencesOf: " \
	#( #[ 32 80 226 2 13 35 33 201 247 5 34 81 192 248 2 \
 242 34 243 215 243 245] \
	#(  ) ) >

<primitive 112 temp 9		" isEmpty " \
	#( #[ 32 163 80 201 243 245] \
	#(  ) ) >

<primitive 112 temp 10		" inject:into: " \
	#( #[ 33 115 32 225 4 7 34 35 36 211 241 115 243 179 242 \
 35 243 245] \
	#(  ) ) >

<primitive 112 temp 11		" includes: " \
	#( #[ 32 225 2 8 34 33 201 247 2 91 244 243 179 242 92 \
 243 245] \
	#(  ) ) >

<primitive 112 temp 12		" first " \
	#( #[ 32 48 188 243 245] \
	#( 'subclass should implement first'  ) ) >

<primitive 112 temp 13		" detect:ifAbsent: " \
	#( #[ 32 225 3 8 33 35 180 247 2 35 244 243 179 242 34 \
 165 243 245] \
	#(  ) ) >

<primitive 112 temp 14		" detect: " \
	#( #[ 32 33 224 4 32 48 188 243 223 243 245] \
	#( 'no object found matching detect'  ) ) >

<primitive 112 temp 15		" deepCopy " \
	#( #[ 5 48 160 113 32 225 2 7 33 34 10 20 11 22 243 \
 179 242 32 33 191 243 245] \
	#(  ) ) >

<primitive 112 temp 16		" collect: " \
	#( #[ 32 32 164 160 226 2 8 34 33 35 180 189 242 34 243 \
 215 243 245] \
	#(  ) ) >

<primitive 112 temp 17		" coerce: " \
	#( #[ 32 160 114 33 225 3 4 34 35 189 243 179 242 34 243 \
 245] \
	#(  ) ) >

<primitive 112 temp 18		" asString " \
	#( #[ 5 58 32 163 176 241 81 32 163 32 131 0 242 243 245 \
] \
	#( #replaceFrom:to:with:  ) ) >

<primitive 112 temp 19		" asList " \
	#( #[ 5 48 160 32 11 20 243 245] \
	#(  ) ) >

<primitive 112 temp 20		" asSet " \
	#( #[ 5 57 160 32 11 19 243 245] \
	#(  ) ) >

<primitive 112 temp 21		" asBag " \
	#( #[ 5 32 160 32 11 19 243 245] \
	#(  ) ) >

<primitive 112 temp 22		" asArray " \
	#( #[ 5 30 32 163 176 241 81 32 163 32 131 0 242 243 245 \
] \
	#( #replaceFrom:to:with:  ) ) >

<primitive 112 temp 23		" addAll: " \
	#( #[ 33 225 2 4 32 34 189 243 179 242 245] \
	#(  ) ) >

<primitive 98 #Collection \
	<primitive 97 #Collection #Object #/u/smalltalk/prelude/collection.st \
	#(  ) \
	#( #size #shallowCopy #select: #remove:ifAbsent: #remove: #reject: #printString #occurrencesOf: #isEmpty #inject:into: #includes: #first #detect:ifAbsent: #detect: #deepCopy #collect: #coerce: #asString #asList #asSet #asBag #asArray #addAll:  ) \
	temp 5 7 > >

temp <- <primitive 110 8 >
<primitive 112 temp 1		" next " \
	#( #[ 17 162 247 27 17 80 204 247 9 17 81 193 97 16 171 \
 243 248 10 242 16 167 241 97 161 247 2 93 243 242 249 \
 31 242 93 243 245] \
	#(  ) ) >

<primitive 112 temp 2		" first " \
	#( #[ 16 166 241 97 161 247 2 93 243 242 17 81 193 97 16 \
 171 243 245] \
	#(  ) ) >

<primitive 112 temp 3		" occurrencesOf: " \
	#( #[ 16 33 224 2 80 243 213 243 245] \
	#(  ) ) >

<primitive 112 temp 4		" size " \
	#( #[ 16 80 226 1 4 33 34 192 243 215 243 245] \
	#(  ) ) >

<primitive 112 temp 5		" remove:ifAbsent: " \
	#( #[ 16 33 224 3 34 165 244 213 115 81 35 201 247 6 16 \
 33 11 40 248 7 242 16 33 35 81 193 208 242 245] \
	#(  ) ) >

<primitive 112 temp 6		" add:withOccurrences: " \
	#( #[ 34 224 4 32 33 189 243 183 242 33 243 245] \
	#(  ) ) >

<primitive 112 temp 7		" add: " \
	#( #[ 16 33 81 16 33 224 2 80 243 213 192 208 242 245] \
	#(  ) ) >

<primitive 112 temp 8		" new " \
	#( #[ 5 40 160 96 245] \
	#(  ) ) >

<primitive 98 #Bag \
	<primitive 97 #Bag #Collection #/u/smalltalk/prelude/bag.st \
	#(  #dict #count ) \
	#( #next #first #occurrencesOf: #size #remove:ifAbsent: #add:withOccurrences: #add: #new  ) \
	temp 4 8 > >

temp <- <primitive 110 7 >
<primitive 112 temp 1		" next " \
	#( #[ 16 167 243 245] \
	#(  ) ) >

<primitive 112 temp 2		" first " \
	#( #[ 16 166 243 245] \
	#(  ) ) >

<primitive 112 temp 3		" occurrencesOf: " \
	#( #[ 16 33 11 30 247 3 81 248 2 242 80 243 245] \
	#(  ) ) >

<primitive 112 temp 4		" size " \
	#( #[ 16 163 243 245] \
	#(  ) ) >

<primitive 112 temp 5		" remove:ifAbsent: " \
	#( #[ 16 33 34 216 242 245] \
	#(  ) ) >

<primitive 112 temp 6		" add: " \
	#( #[ 16 33 11 30 246 3 16 33 189 242 245] \
	#(  ) ) >

<primitive 112 temp 7		" new " \
	#( #[ 5 48 160 96 245] \
	#(  ) ) >

<primitive 98 #Set \
	<primitive 97 #Set #Collection #/u/smalltalk/prelude/set.st \
	#(  #list ) \
	#( #next #first #occurrencesOf: #size #remove:ifAbsent: #add: #new  ) \
	temp 3 4 > >

temp <- <primitive 110 18 >
<primitive 112 temp 1		" values " \
	#( #[ 5 32 160 113 32 225 2 4 33 34 189 243 179 242 33 \
 243 245] \
	#(  ) ) >

<primitive 112 temp 2		" select: " \
	#( #[ 32 32 5 40 160 226 2 13 33 35 180 247 5 34 32 \
 171 35 208 242 34 243 215 191 243 245] \
	#(  ) ) >

<primitive 112 temp 3		" removeKey:ifAbsent: " \
	#( #[ 32 48 188 243 245] \
	#( 'subclass should implement RemoveKey:ifAbsent:'  ) ) >

<primitive 112 temp 4		" removeKey: " \
	#( #[ 32 33 224 6 32 48 188 242 33 244 217 243 245] \
	#( 'no element associated with key'  ) ) >

<primitive 112 temp 5		" remove: " \
	#( #[ 32 48 188 243 245] \
	#( 'object must be removed with explicit key'  ) ) >

<primitive 112 temp 6		" keysSelect: " \
	#( #[ 32 32 5 40 160 226 2 14 33 35 171 180 247 5 34 \
 32 171 35 208 242 34 243 215 191 243 245] \
	#(  ) ) >

<primitive 112 temp 7		" keysDo: " \
	#( #[ 32 225 2 5 33 32 171 180 243 179 243 245] \
	#(  ) ) >

<primitive 112 temp 8		" keys " \
	#( #[ 5 57 160 113 32 225 2 4 33 34 189 243 11 32 242 \
 33 243 245] \
	#(  ) ) >

<primitive 112 temp 9		" indexOf:ifAbsent: " \
	#( #[ 32 225 3 9 35 33 201 247 3 32 171 244 243 179 242 \
 34 165 243 245] \
	#(  ) ) >

<primitive 112 temp 10		" indexOf: " \
	#( #[ 32 33 224 4 32 48 188 243 214 243 245] \
	#( 'indexOf element not found'  ) ) >

<primitive 112 temp 11		" includesKey: " \
	#( #[ 32 33 224 2 92 244 213 242 91 243 245] \
	#(  ) ) >

<primitive 112 temp 12		" collect: " \
	#( #[ 32 32 5 40 160 226 2 10 34 32 171 33 35 180 208 \
 242 34 243 215 191 243 245] \
	#(  ) ) >

<primitive 112 temp 13		" binaryDo: " \
	#( #[ 32 225 3 6 33 32 171 35 211 243 179 242 93 243 245 \
] \
	#(  ) ) >

<primitive 112 temp 14		" atAll:put: " \
	#( #[ 33 225 3 5 32 35 34 208 243 179 242 245] \
	#(  ) ) >

<primitive 112 temp 15		" at: " \
	#( #[ 32 33 224 10 32 33 169 48 11 17 188 242 33 244 213 \
 243 245] \
	#( ': association not found'  ) ) >

<primitive 112 temp 16		" asDictionary " \
	#( #[ 5 40 160 113 32 226 2 5 33 34 35 208 243 11 23 \
 242 33 243 245] \
	#(  ) ) >

<primitive 112 temp 17		" addAll: " \
	#( #[ 33 226 2 5 32 34 35 208 243 11 23 242 33 243 245 \
] \
	#(  ) ) >

<primitive 112 temp 18		" add: " \
	#( #[ 32 48 188 243 245] \
	#( 'Must add with explicit key'  ) ) >

<primitive 98 #KeyedCollection \
	<primitive 97 #KeyedCollection #Collection #/u/smalltalk/prelude/kcollection.st \
	#(  ) \
	#( #values #select: #removeKey:ifAbsent: #removeKey: #remove: #keysSelect: #keysDo: #keys #indexOf:ifAbsent: #indexOf: #includesKey: #collect: #binaryDo: #atAll:put: #at: #asDictionary #addAll: #add:  ) \
	temp 4 9 > >

temp <- <primitive 110 12 >
<primitive 112 temp 1		" checkBucket: " \
	#( #[ 16 33 241 97 177 241 98 161 247 2 93 243 242 18 166 \
 243 245] \
	#(  ) ) >

<primitive 112 temp 2		" currentKey " \
	#( #[ 18 162 247 11 18 10 21 113 33 162 247 3 33 10 49 \
 243 245] \
	#(  ) ) >

<primitive 112 temp 3		" printString " \
	#( #[ 32 32 164 169 48 11 17 226 1 17 33 32 171 169 11 \
 17 49 11 17 34 169 11 17 50 11 17 243 215 51 11 \
 17 243 245] \
	#( ' ( ' ' @ ' ' ' ')'  ) ) >

<primitive 112 temp 4		" next " \
	#( #[ 18 167 241 113 162 247 4 33 10 50 243 242 17 5 17 \
 199 247 20 17 81 192 97 32 17 11 24 241 113 162 247 \
 4 33 10 50 243 242 249 26 242 93 243 245] \
	#(  ) ) >

<primitive 112 temp 5		" first " \
	#( #[ 81 5 17 178 225 2 14 32 34 11 24 241 113 162 247 \
 4 33 10 50 244 243 179 242 93 243 245] \
	#(  ) ) >

<primitive 112 temp 6		" findAssociation:inList: " \
	#( #[ 34 225 3 10 35 10 49 33 201 247 2 35 244 243 179 \
 242 93 243 245] \
	#(  ) ) >

<primitive 112 temp 7		" removeKey:ifAbsent: " \
	#( #[ 32 33 11 28 115 32 33 35 222 116 36 161 247 3 34 \
 165 243 242 35 36 224 3 34 165 244 216 10 50 243 245 \
] \
	#(  ) ) >

<primitive 112 temp 8		" at:ifAbsent: " \
	#( #[ 32 33 11 28 115 32 33 35 222 116 36 161 247 3 34 \
 165 243 242 36 10 50 243 245] \
	#(  ) ) >

<primitive 112 temp 9		" at:put: " \
	#( #[ 32 33 11 28 115 32 33 35 222 116 36 161 247 15 5 \
 53 160 33 11 50 34 11 51 116 35 36 189 248 5 242 \
 36 34 11 51 242 34 243 245] \
	#(  ) ) >

<primitive 112 temp 10		" getList: " \
	#( #[ 32 33 11 29 115 16 35 177 114 34 161 247 8 5 48 \
 160 114 16 35 34 208 242 34 243 245] \
	#(  ) ) >

<primitive 112 temp 11		" hashNumber: " \
	#( #[ 33 250 1 5 16 163 195 81 192 243 245] \
	#(  ) ) >

<primitive 112 temp 12		" new " \
	#( #[ 5 30 5 17 176 96 245] \
	#(  ) ) >

<primitive 98 #Dictionary \
	<primitive 97 #Dictionary #KeyedCollection #/u/smalltalk/prelude/dictionary.st \
	#(  #hashTable #currentBucket #currentList ) \
	#( #checkBucket: #currentKey #printString #next #first #findAssociation:inList: #removeKey:ifAbsent: #at:ifAbsent: #at:put: #getList: #hashNumber: #new  ) \
	temp 5 6 > >

temp <- <primitive 110 21 >
<primitive 112 temp 1		" with:do: " \
	#( #[ 32 166 115 33 166 116 35 162 247 15 34 35 36 211 242 \
 32 167 115 33 167 241 116 242 249 19 242 93 243 245] \
	#(  ) ) >

<primitive 112 temp 2		" sort: " \
	#( #[ 32 174 116 82 36 163 178 225 5 51 37 81 193 114 34 \
 81 203 252 11 33 36 34 177 36 34 81 192 177 211 172 \
 247 28 36 34 177 115 36 34 36 34 81 192 177 208 242 \
 36 34 81 192 35 208 242 34 81 193 241 114 242 249 46 \
 243 179 242 32 36 191 243 245] \
	#(  ) ) >

<primitive 112 temp 3		" sort " \
	#( #[ 32 226 1 4 33 34 200 243 11 46 243 245] \
	#(  ) ) >

<primitive 112 temp 4		" select: " \
	#( #[ 32 32 5 48 160 226 2 12 33 35 180 247 4 34 35 \
 11 22 242 34 243 215 191 243 245] \
	#(  ) ) >

<primitive 112 temp 5		" reversed " \
	#( #[ 5 30 32 163 241 114 176 113 32 225 3 11 33 34 35 \
 208 242 34 81 193 241 114 243 179 242 32 33 191 243 245 \
] \
	#(  ) ) >

<primitive 112 temp 6		" reverseDo: " \
	#( #[ 32 10 31 114 32 10 25 115 34 35 203 247 20 32 34 \
 11 52 247 5 33 32 34 177 180 242 34 81 193 241 114 \
 242 249 25 242 93 243 245] \
	#(  ) ) >

<primitive 112 temp 7		" replaceFrom:to:with:startingAt: " \
	#( #[ 80 117 33 37 192 34 200 247 19 32 33 37 192 35 37 \
 36 192 177 208 242 37 81 192 241 117 242 249 26 242 245 \
] \
	#(  ) ) >

<primitive 112 temp 8		" replaceFrom:to:with: " \
	#( #[ 35 33 226 4 9 32 36 37 208 242 36 81 192 243 215 \
 242 245] \
	#(  ) ) >

<primitive 112 temp 9		" last " \
	#( #[ 80 32 163 201 246 5 32 32 10 31 177 243 245] \
	#(  ) ) >

<primitive 112 temp 10		" indexOfSubCollection:startingAt: " \
	#( #[ 32 33 34 224 6 32 48 188 242 93 243 131 1 243 245 \
] \
	#( 'element not found' #indexOfSubCollection:startingAt:ifAbsent:  ) ) >

<primitive 112 temp 11		" indexOfSubCollection:startingAt:ifAbsent: " \
	#( #[ 34 116 32 163 33 163 193 117 36 37 200 247 17 33 32 \
 36 221 247 2 36 243 242 36 81 192 241 116 242 249 22 \
 242 35 165 243 245] \
	#(  ) ) >

<primitive 112 temp 12		" findLast:ifAbsent: " \
	#( #[ 32 225 3 9 33 35 180 247 3 32 171 244 243 11 42 \
 242 34 165 243 245] \
	#(  ) ) >

<primitive 112 temp 13		" findLast: " \
	#( #[ 32 33 224 4 32 48 188 243 220 242 245] \
	#( 'last element not found'  ) ) >

<primitive 112 temp 14		" findFirst:ifAbsent: " \
	#( #[ 32 225 3 9 33 35 180 247 3 32 171 244 243 179 242 \
 34 165 243 245] \
	#(  ) ) >

<primitive 112 temp 15		" findFirst: " \
	#( #[ 32 33 224 4 32 48 188 243 219 243 245] \
	#( 'first element not found'  ) ) >

<primitive 112 temp 16		" equals:startingAt: " \
	#( #[ 80 115 32 225 4 22 36 33 34 35 192 224 2 92 244 \
 213 201 246 2 92 244 242 35 81 192 241 115 243 179 242 \
 91 243 245] \
	#(  ) ) >

<primitive 112 temp 17		" copyWithout: " \
	#( #[ 5 48 160 114 32 225 3 10 35 33 181 246 4 34 35 \
 11 22 243 179 242 32 34 191 243 245] \
	#(  ) ) >

<primitive 112 temp 18		" copyWith: " \
	#( #[ 32 5 48 160 241 32 11 20 242 241 33 11 22 242 191 \
 243 245] \
	#(  ) ) >

<primitive 112 temp 19		" copyFrom:to: " \
	#( #[ 5 48 160 115 33 34 178 225 4 7 35 32 36 177 11 \
 22 243 179 242 32 35 191 243 245] \
	#(  ) ) >

<primitive 112 temp 20		" collect: " \
	#( #[ 32 32 5 48 160 226 2 9 34 33 35 180 11 22 242 \
 34 243 215 191 243 245] \
	#(  ) ) >

<primitive 112 temp 21		" , " \
	#( #[ 32 5 48 160 241 32 11 20 242 241 33 11 20 242 191 \
 243 245] \
	#(  ) ) >

<primitive 98 #SequenceableCollection \
	<primitive 97 #SequenceableCollection #KeyedCollection #/u/smalltalk/prelude/scollection.st \
	#(  ) \
	#( #with:do: #sort: #sort #select: #reversed #reverseDo: #replaceFrom:to:with:startingAt: #replaceFrom:to:with: #last #indexOfSubCollection:startingAt: #indexOfSubCollection:startingAt:ifAbsent: #findLast:ifAbsent: #findLast: #findFirst:ifAbsent: #findFirst: #equals:startingAt: #copyWithout: #copyWith: #copyFrom:to: #collect: #,  ) \
	temp 6 9 > >

temp <- <primitive 110 13 >
<primitive 112 temp 1		" shallowCopy " \
	#( #[ 16 17 18 212 243 245] \
	#(  ) ) >

<primitive 112 temp 2		" deepCopy " \
	#( #[ 16 17 18 212 243 245] \
	#(  ) ) >

<primitive 112 temp 3		" removeKey:ifAbsent: " \
	#( #[ 32 48 188 242 34 165 243 245] \
	#( 'cannot remove from Interval'  ) ) >

<primitive 112 temp 4		" add: " \
	#( #[ 32 48 188 243 245] \
	#( 'cannot store into Interval'  ) ) >

<primitive 112 temp 5		" at:put: " \
	#( #[ 32 48 188 243 245] \
	#( 'cannot store into Interval'  ) ) >

<primitive 112 temp 6		" coerce: " \
	#( #[ 33 174 243 245] \
	#(  ) ) >

<primitive 112 temp 7		" printString " \
	#( #[ 48 16 169 11 17 49 11 17 17 169 11 17 50 11 17 \
 18 169 11 17 243 245] \
	#( 'Interval ' ' to ' ' by '  ) ) >

<primitive 112 temp 8		" at:ifAbsent: " \
	#( #[ 16 18 33 81 193 194 192 115 32 35 11 31 247 3 35 \
 248 3 242 34 165 243 245] \
	#(  ) ) >

<primitive 112 temp 9		" next " \
	#( #[ 19 18 192 99 32 19 11 31 247 1 19 243 245] \
	#(  ) ) >

<primitive 112 temp 10		" first " \
	#( #[ 16 99 32 19 11 31 247 1 19 243 245] \
	#(  ) ) >

<primitive 112 temp 11		" inRange: " \
	#( #[ 18 170 247 10 33 16 203 252 3 33 17 200 248 9 242 \
 33 17 203 252 3 33 16 200 243 245] \
	#(  ) ) >

<primitive 112 temp 12		" size " \
	#( #[ 18 170 247 5 17 16 199 248 4 242 16 17 199 247 3 \
 80 248 9 242 17 16 193 18 11 18 81 192 243 245] \
	#(  ) ) >

<primitive 112 temp 13		" from:to:by: " \
	#( #[ 33 241 96 99 34 97 35 98 245] \
	#(  ) ) >

<primitive 98 #Interval \
	<primitive 97 #Interval #SequenceableCollection #/u/smalltalk/prelude/interval.st \
	#(  #lower #upper #step #current ) \
	#( #shallowCopy #deepCopy #removeKey:ifAbsent: #add: #at:put: #coerce: #printString #at:ifAbsent: #next #first #inRange: #size #from:to:by:  ) \
	temp 4 5 > >

temp <- <primitive 110 17 >
<primitive 112 temp 1		" isEmpty " \
	#( #[ 16 93 181 243 245] \
	#(  ) ) >

<primitive 112 temp 2		" last " \
	#( #[ 16 161 247 2 93 243 242 32 10 24 10 49 243 245] \
	#(  ) ) >

<primitive 112 temp 3		" current " \
	#( #[ 17 10 49 243 245] \
	#(  ) ) >

<primitive 112 temp 4		" next " \
	#( #[ 17 10 50 241 97 162 247 3 17 10 49 243 245] \
	#(  ) ) >

<primitive 112 temp 5		" first " \
	#( #[ 16 241 97 162 247 3 17 10 49 243 245] \
	#(  ) ) >

<primitive 112 temp 6		" removeLast " \
	#( #[ 16 161 247 4 32 10 37 243 242 32 32 10 30 224 4 \
 32 10 37 243 216 243 245] \
	#(  ) ) >

<primitive 112 temp 7		" removeFirst " \
	#( #[ 16 161 247 4 32 10 37 243 242 16 113 16 10 50 96 \
 33 10 49 243 245] \
	#(  ) ) >

<primitive 112 temp 8		" removeError " \
	#( #[ 32 48 188 243 245] \
	#( 'cannot remove from an empty list'  ) ) >

<primitive 112 temp 9		" remove:ifAbsent: " \
	#( #[ 16 161 247 3 34 165 243 242 32 93 226 3 31 17 10 \
 49 33 181 247 21 35 161 247 7 17 10 50 241 96 248 \
 7 242 35 17 10 50 11 51 242 33 244 242 17 243 215 \
 242 34 165 243 245] \
	#(  ) ) >

<primitive 112 temp 10		" remove: " \
	#( #[ 32 33 224 4 32 48 188 243 216 243 245] \
	#( 'cant find item'  ) ) >

<primitive 112 temp 11		" findLast " \
	#( #[ 16 241 113 161 247 2 93 243 242 33 10 50 162 247 8 \
 33 10 50 241 113 242 249 14 242 33 243 245] \
	#(  ) ) >

<primitive 112 temp 12		" coerce: " \
	#( #[ 5 48 160 114 33 225 3 5 34 35 11 22 243 179 242 \
 34 243 245] \
	#(  ) ) >

<primitive 112 temp 13		" addAllLast: " \
	#( #[ 33 225 2 5 32 34 11 22 243 179 242 245] \
	#(  ) ) >

<primitive 112 temp 14		" addAllFirst: " \
	#( #[ 33 225 2 5 32 34 11 21 243 179 242 245] \
	#(  ) ) >

<primitive 112 temp 15		" addLast: " \
	#( #[ 16 161 247 5 32 33 11 21 243 242 32 10 24 5 53 \
 160 33 11 50 93 11 51 11 51 242 33 243 245] \
	#(  ) ) >

<primitive 112 temp 16		" addFirst: " \
	#( #[ 5 53 160 33 11 50 16 11 51 96 33 243 245] \
	#(  ) ) >

<primitive 112 temp 17		" add: " \
	#( #[ 5 53 160 33 11 50 16 11 51 96 33 243 245] \
	#(  ) ) >

<primitive 98 #List \
	<primitive 97 #List #SequenceableCollection #/u/smalltalk/prelude/list.st \
	#(  #first #current ) \
	#( #isEmpty #last #current #next #first #removeLast #removeFirst #removeError #remove:ifAbsent: #remove: #findLast #coerce: #addAllLast: #addAllFirst: #addLast: #addFirst: #add:  ) \
	temp 5 8 > >

temp <- <primitive 110 12 >
<primitive 112 temp 1		" shallowCopy " \
	#( #[ 32 164 32 163 176 113 81 32 163 178 225 2 7 33 34 \
 32 34 177 208 243 179 242 33 243 245] \
	#(  ) ) >

<primitive 112 temp 2		" next " \
	#( #[ 16 81 192 96 16 32 163 200 247 3 32 16 177 243 245 \
] \
	#(  ) ) >

<primitive 112 temp 3		" lastKey " \
	#( #[ 32 163 243 245] \
	#(  ) ) >

<primitive 112 temp 4		" firstKey " \
	#( #[ 81 243 245] \
	#(  ) ) >

<primitive 112 temp 5		" first " \
	#( #[ 81 96 16 32 163 200 247 3 32 16 177 243 245] \
	#(  ) ) >

<primitive 112 temp 6		" do: " \
	#( #[ 81 32 163 178 225 2 8 34 96 33 32 34 177 180 243 \
 179 242 245] \
	#(  ) ) >

<primitive 112 temp 7		" deepCopy " \
	#( #[ 32 164 32 163 176 113 81 32 163 178 225 2 9 33 34 \
 32 34 177 10 20 208 243 179 242 33 243 245] \
	#(  ) ) >

<primitive 112 temp 8		" currentKey " \
	#( #[ 16 243 245] \
	#(  ) ) >

<primitive 112 temp 9		" copyFrom:to: " \
	#( #[ 34 33 193 81 192 115 32 164 35 176 116 36 81 35 32 \
 33 132 0 242 36 243 245] \
	#( #replaceFrom:to:with:startingAt:  ) ) >

<primitive 112 temp 10		" coerce: " \
	#( #[ 32 164 33 163 176 114 34 81 33 163 33 131 0 242 34 \
 243 245] \
	#( #replaceFrom:to:with:  ) ) >

<primitive 112 temp 11		" at:ifAbsent: " \
	#( #[ 33 80 200 251 4 33 32 163 204 247 3 34 165 243 242 \
 32 33 177 243 245] \
	#(  ) ) >

<primitive 112 temp 12		" = " \
	#( #[ 32 163 33 163 202 247 2 92 243 242 80 114 32 225 3 \
 14 35 33 34 81 192 241 114 177 202 247 2 92 244 243 \
 179 242 91 243 245] \
	#(  ) ) >

<primitive 98 #ArrayedCollection \
	<primitive 97 #ArrayedCollection #SequenceableCollection #/u/smalltalk/prelude/acollection.st \
	#(  #current ) \
	#( #shallowCopy #next #lastKey #firstKey #first #do: #deepCopy #currentKey #copyFrom:to: #coerce: #at:ifAbsent: #=  ) \
	temp 5 7 > >

temp <- <primitive 110 13 >
<primitive 112 temp 1		" write: " \
	#( #[ 32 33 250 2 132 243 245] \
	#(  ) ) >

<primitive 112 temp 2		" size " \
	#( #[ 32 250 1 134 243 245] \
	#(  ) ) >

<primitive 112 temp 3		" read " \
	#( #[ 32 250 1 131 243 245] \
	#(  ) ) >

<primitive 112 temp 4		" open:for: " \
	#( #[ 32 33 34 250 3 130 242 245] \
	#(  ) ) >

<primitive 112 temp 5		" open: " \
	#( #[ 32 33 48 250 3 130 242 245] \
	#( 'r'  ) ) >

<primitive 112 temp 6		" next " \
	#( #[ 32 10 36 243 245] \
	#(  ) ) >

<primitive 112 temp 7		" first " \
	#( #[ 32 80 177 243 245] \
	#(  ) ) >

<primitive 112 temp 8		" currentKey " \
	#( #[ 32 250 1 136 243 245] \
	#(  ) ) >

<primitive 112 temp 9		" at:put: " \
	#( #[ 32 33 250 2 135 242 32 34 11 49 243 245] \
	#(  ) ) >

<primitive 112 temp 10		" at: " \
	#( #[ 32 33 250 2 135 242 32 10 36 243 245] \
	#(  ) ) >

<primitive 112 temp 11		" modeString " \
	#( #[ 32 81 250 2 133 242 245] \
	#(  ) ) >

<primitive 112 temp 12		" modeInteger " \
	#( #[ 32 82 250 2 133 242 245] \
	#(  ) ) >

<primitive 112 temp 13		" modeCharacter " \
	#( #[ 32 80 250 2 133 242 245] \
	#(  ) ) >

<primitive 98 #File \
	<primitive 97 #File #SequenceableCollection #/u/smalltalk/prelude/file.st \
	#(  ) \
	#( #write: #size #read #open:for: #open: #next #first #currentKey #at:put: #at: #modeString #modeInteger #modeCharacter  ) \
	temp 3 4 > >

temp <- <primitive 110 5 >
<primitive 112 temp 1		" size " \
	#( #[ 32 250 1 117 243 245] \
	#(  ) ) >

<primitive 112 temp 2		" printString " \
	#( #[ 48 113 81 32 163 178 225 2 13 33 32 34 177 169 11 \
 17 49 11 17 241 113 243 179 242 33 50 11 17 243 245 \
] \
	#( '#[ ' ' ' ']'  ) ) >

<primitive 112 temp 3		" at:put: " \
	#( #[ 32 33 34 250 3 119 242 245] \
	#(  ) ) >

<primitive 112 temp 4		" at: " \
	#( #[ 32 33 250 2 118 243 245] \
	#(  ) ) >

<primitive 112 temp 5		" new: " \
	#( #[ 33 250 1 116 243 245] \
	#(  ) ) >

<primitive 98 #ByteArray \
	<primitive 97 #ByteArray #ArrayedCollection #/u/smalltalk/prelude/bytearray.st \
	#(  ) \
	#( #size #printString #at:put: #at: #new:  ) \
	temp 3 6 > >

temp <- <primitive 110 4 >
<primitive 112 temp 1		" wait " \
	#( #[ 250 0 148 242 16 80 201 247 10 32 95 11 22 242 95 \
 10 18 248 6 242 16 81 193 241 96 242 250 0 149 242 \
 245] \
	#(  ) ) >

<primitive 112 temp 2		" signal " \
	#( #[ 250 0 148 242 32 10 27 247 7 16 81 192 241 96 248 \
 6 242 32 10 38 10 48 242 250 0 149 242 245] \
	#(  ) ) >

<primitive 112 temp 3		" new: " \
	#( #[ 33 96 245] \
	#(  ) ) >

<primitive 112 temp 4		" new " \
	#( #[ 80 96 245] \
	#(  ) ) >

<primitive 98 #Semaphore \
	<primitive 97 #Semaphore #List #/u/smalltalk/prelude/semaphore.st \
	#(  #excessSignals ) \
	#( #wait #signal #new: #new  ) \
	temp 2 4 > >

temp <- <primitive 110 8 >
<primitive 112 temp 1		" yield " \
	#( #[ 93 243 245] \
	#(  ) ) >

<primitive 112 temp 2		" unblock " \
	#( #[ 32 10 45 48 181 247 7 32 49 11 47 242 93 243 242 \
 32 83 250 2 145 242 32 10 45 243 245] \
	#( #TERMINATED 'unblock'  ) ) >

<primitive 112 temp 3		" termErr: " \
	#( #[ 48 33 11 17 49 11 17 168 242 245] \
	#( 'Cannot ' ' a terminated process.'  ) ) >

<primitive 112 temp 4		" terminate " \
	#( #[ 32 250 1 142 242 32 10 45 243 245] \
	#(  ) ) >

<primitive 112 temp 5		" state " \
	#( #[ 32 250 1 146 113 33 80 201 247 4 48 113 33 243 242 \
 33 81 201 247 4 49 113 33 243 242 33 82 201 247 4 \
 50 113 33 243 242 33 83 201 247 4 50 113 33 243 242 \
 33 84 203 247 4 51 113 33 243 242 245] \
	#( #READY #SUSPENDED #BLOCKED #TERMINATED  ) ) >

<primitive 112 temp 6		" suspend " \
	#( #[ 32 10 45 48 181 247 7 32 49 11 47 242 93 243 242 \
 32 81 250 2 145 242 32 10 45 243 245] \
	#( #TERMINATED 'suspend'  ) ) >

<primitive 112 temp 7		" resume " \
	#( #[ 32 10 45 48 181 247 7 32 49 11 47 242 93 243 242 \
 32 80 250 2 145 242 32 10 45 243 245] \
	#( #TERMINATED 'resume'  ) ) >

<primitive 112 temp 8		" block " \
	#( #[ 32 10 45 48 181 247 7 32 49 11 47 242 93 243 242 \
 32 82 250 2 145 242 32 10 45 243 245] \
	#( #TERMINATED 'block'  ) ) >

<primitive 98 #Process \
	<primitive 97 #Process #Object #/u/smalltalk/prelude/process.st \
	#(  ) \
	#( #yield #unblock #termErr: #terminate #state #suspend #resume #block  ) \
	temp 2 4 > >

temp <- <primitive 110 9 >
<primitive 112 temp 1		" time: " \
	#( #[ 250 0 161 114 33 165 242 250 0 161 34 193 243 245] \
	#(  ) ) >

<primitive 112 temp 2		" sh: " \
	#( #[ 33 250 1 125 243 245] \
	#(  ) ) >

<primitive 112 temp 3		" perform:withArguments: " \
	#( #[ 34 33 250 2 143 243 245] \
	#(  ) ) >

<primitive 112 temp 4		" noDisplay " \
	#( #[ 81 80 250 2 8 243 245] \
	#(  ) ) >

<primitive 112 temp 5		" doPrimitive:withArguments: " \
	#( #[ 33 34 250 2 30 243 245] \
	#(  ) ) >

<primitive 112 temp 6		" displayAssign " \
	#( #[ 81 82 250 2 8 243 245] \
	#(  ) ) >

<primitive 112 temp 7		" display " \
	#( #[ 81 81 250 2 8 243 245] \
	#(  ) ) >

<primitive 112 temp 8		" debug: " \
	#( #[ 82 33 250 2 8 243 245] \
	#(  ) ) >

<primitive 112 temp 9		" date " \
	#( #[ 250 0 160 243 245] \
	#(  ) ) >

<primitive 98 #Smalltalk \
	<primitive 97 #Smalltalk #Dictionary #/u/smalltalk/prelude/smalltalk.st \
	#(  ) \
	#( #time: #sh: #perform:withArguments: #noDisplay #doPrimitive:withArguments: #displayAssign #display #debug: #date  ) \
	temp 3 3 > >

smalltalk new
SHAR_EOF
if test 52853 -ne "`wc -c < 'standard'`"
then
	echo shar: error transmitting "'standard'" '(should have been 52853 characters)'
fi
fi # end of overwriting check
if test -f 'stdsave'
then
	echo shar: will not over-write existing file "'stdsave'"
else
cat << \SHAR_EOF > 'stdsave'
ol spacellLast:From:reysSelect:emoveKey:alue:h
l!l'l-()[]!|.;>enhighlow error: %dbA2.10000000D'y.s	85/03/06Lt char!
(]    r""!["
.r\   r""s #s 0#!s# q!!r "r 0"r"   ! ![\ q!P  rQ!"# #op" !) 
 y[]\!  r""!["
.r\ ! z r"!" r q!P  rQ!
"# #o
p" 
*  

  ! ! ! ! ! !f 
 d y m!s k !"j !"!Qj 0 !"i !h l !	 !eP 
 !	 !eP 
 !	 !eP 
 !	 !eP 
 !	 !eP 
 !gQ0\[ 0q r"P "o1!q"Qr2!!Q!  0] !"p"!Q!  0] !o!r ! ! ! ! ! !\]!"![!]!"UTSRQP !	 ] !	 ] !#
(] !
/! !  ] \ ! !.\ ! ! ! ! ! "!  ! ! ! ! !!  ! ! !
)!. !"+ PZ PQP 
 !
 0  !6  P 0 PP P ! 
  
 
 PP  5 2!3 ! !"! " !"! " !"! " !"! " !"! " !"! " !"! " !	 ! Pr" !"Qr ! ! 
# ! ! ! 
# RPP ! !
 ! ! 
# " ! ! 
# & RP ! ! ! ! ! ! % ' $! !0 : !  PZQr"! 
# ! ! 
# ! ! ! ! ! 
 01 8 2q 0! 0 : 5 9  6 9  ; ! !+ 
 ! !. 
 ! !* 
 0 I H G 0H !Y F K M L H O! I N 6 T6 U!P ! !X !0QRRQ!!!P`!a!`"a!`52305!
12!
235!
12!
23!
1
,!
2
,
+
0
5235!2!35!2!35!
12!
235!
12!
235!2!3!
1!
2!
1!
2!
1!
2!
1!
2!rQ!"# " !
/Q "!!#` #`  !  "!#" r!"#": Q  a]]!`c"a#bP!"!"sQ#!(!#Q" !!!Q!P(`9q !" !!QP!"!!0` q !"!  (
!#" #" 0 ! 0! 0  (!#" #" !  	#! " ! 0 !\[  (
" !#" ! #]! #" !
 !0!(q !"#!! "#! 00r!"#"!ab]
q!!
1  0! 1"23q!
2Qa q!
2]Q "q!
2]"
#
1!#] !s !#t$"#$"
2 !s !#t$"$
2 !s !#t$5!2"3t#$$"3" !s#r"0r#""!Q` s!t#"#$ s!t] tR$3%Qr"Q!$"$"Q$"s$"$"Q$"Q#"Qr. $ !".  0!#"#" rq !"#"Qr ! 
r 
s"# "4! ""Qr]Pu!%" !%#%$%Qu#!	 $%$QP   
 !" 0]"t !u$%! $$$Qt# 	!# *" ! 0 	!# " ! 0Ps $!"#\\#Qs[0r 
#!"# " 0 !0s!"# $ #  0	"!#" 0 ! 0" 0 0!012!Qs ##"c c 
!!	!!P	QY0p`
1
1
2a
1a
1 
%  
 
% 
%q
2`!
1 0" ]
1!#
2`#
23!" ! 0q]!
2!
2q!! "! " ! 
5!2]33!5!23`!5!23`!Q "`! "  qQ !" "!Q`   QQ`    qQ 	!" "
!"!Qs #t$Q# !$ P  ! "1 ! 
$ Q R P u0qQ 
! "1q!2 !"w !v!t __
Q`Q` 
&
0-0 1/] S 
-0!1  
- q!P0q!!Q1q!!R2q!!S2q!!T3q! 
-0 1/] Q 
- 
-0 1/] P 
- 
-0 1/] R 
-

ittle Smalltalk
	`pp`pa`	#(  ) ) >

<primitive 112 temp 6		" displayAssign " \
	#( #[ 81 82 250 2 8 243 245] \
	#(  ) ) >

<primitive 112 temp 7		" display " \
	#( #[ 81 81 250 2 8 243 245] \
	#(  ) ) >

<primitive 112 temp 8		" debug: " \
	#( #[ 82 33 250 2 8 243 245] \
	#(  ) ) >

<primitive 112 temp 9		" date " \
	#( #[ 250 0 160 243 245] \
	#(  ) ) >

<primitive 98 #Smalltalk \
	<primitive 97 #Smalltalk #Dictionary #/u/smalltalk/prelude/smalltalk.st \
	#(  ) \
	#( #time: #sh: #perform:withArguments: #noDisplay #doPrimitive:withArguments: #displayAssign #display #debug: #date  ) \
	temp 3 3 > >

smalltalk new
time: " \
	#( #[ 250 0 161 114 33 165 242 250 0 161 34 193 243 245] \
	#(  ) ) >

<primitive 112 temp 2		" sh: " \
	#( #[ 33 250 1 125 243 245] \
	#(  ) ) >

<primitive 112 temp 3		" perform:withArguments: " \
	#( #[ 34 33 250 2 143 243 245] \
	#(  ) ) >

<primitive 112 temp 4		" noDisplay " \
	#( #[ 81 80 250 2 8 243 245] \
	#(  ) ) >

<primitive 112 temp 5		" doPrimitive:withArguments: " \
(ollectioney element not found`pSHAR_EOF
echo shar: a missing newline was added to "'stdsave'"
echo shar: 34164 control characters may be missing from "'stdsave'"
if test 65608 -ne "`wc -c < 'stdsave'`"
then
	echo shar: error transmitting "'stdsave'" '(should have been 65608 characters)'
fi
fi # end of overwriting check
cd ..
#	End of shell archive
exit 0