Added:
/branches/gcc-linux/StrongtalkSource/ErrorCollection.dlt
/branches/gcc-linux/StrongtalkSource/Top.dlt
Modified:
/branches/gcc-linux/StrongtalkSource/ActivationOutliner.dlt
/branches/gcc-linux/StrongtalkSource/ClassHierarchyOutliner.dlt
/branches/gcc-linux/StrongtalkSource/ClassVMMirror.dlt
/branches/gcc-linux/StrongtalkSource/Inspector.dlt
/branches/gcc-linux/StrongtalkSource/OopsVMMirror.dlt
/branches/gcc-linux/StrongtalkSource/Unclassified.gr
/branches/gcc-linux/StrongtalkSource/VMMirror.dlt
/branches/gcc-linux/StrongtalkSource/WeakArray.dlt
/branches/gcc-linux/StrongtalkSource/world.gr
/branches/gcc-linux/build.win32/strongtalk.ncb
/branches/gcc-linux/build.win32/strongtalk.suo
=======================================
--- /dev/null
+++ /branches/gcc-linux/StrongtalkSource/ErrorCollection.dlt Sat Dec 19
12:39:38 2009
@@ -0,0 +1,34 @@
+Delta define: #ErrorCollection as: (
+(Class subclassOf: 'Error' instanceVariables: 'errors
<OrderedCollection[Error]>')) !
+
+(Delta mirrorFor: #ErrorCollection) revision: '$Revision:$'!
+
+(Delta mirrorFor: #ErrorCollection) group: 'Unclassified'!
+
+(Delta mirrorFor: #ErrorCollection)
+comment:
+''!
+
+! (Delta mirrorFor: #ErrorCollection) classSide methodsFor: 'instance
creation' !
+
+
+errors: errors <OrderedCollection[Error]>
+
+ ^ self new
+ errors: errors;
+ yourself! !
+
+! (Delta mirrorFor: #ErrorCollection) methodsFor: 'accessing' !
+
+
+errors
+
+ ^errors! !
+
+! (Delta mirrorFor: #ErrorCollection)
methodsFor: 'private-initialization' !
+
+
+errors: someErrors <OrderedCollection[Error]>
+
+ errors := OrderedCollection withAll: someErrors! !
+
=======================================
--- /dev/null
+++ /branches/gcc-linux/StrongtalkSource/Top.dlt Sat Dec 19 12:39:38 2009
@@ -0,0 +1,19 @@
+Delta define: #Top as: (
+(Class delta)) !
+
+(Delta mirrorFor: #Top) revision: '$Revision:$'!
+
+(Delta mirrorFor: #Top) group: 'Unclassified'!
+
+(Delta mirrorFor: #Top)
+comment:
+''!
+
+! (Delta mirrorFor: #Top) methodsFor: 'proxy support' !
+
+
+doesNotUnderstand: message <Message>
+
+ ^(MessageNotUnderstood message: message)
+ signal! !
+
=======================================
--- /branches/gcc-linux/StrongtalkSource/ActivationOutliner.dlt Sun Nov 15
17:53:07 2009
+++ /branches/gcc-linux/StrongtalkSource/ActivationOutliner.dlt Sat Dec 19
12:39:38 2009
@@ -195,7 +195,7 @@
^[aValue printString]
on: Error
- do: [:ex|'??instance of ', aValue class name]!
+ do: [:ex|'??instance of ', (Reflection classOf: aValue) name]!
selector ^<Symbol>
=======================================
--- /branches/gcc-linux/StrongtalkSource/ClassHierarchyOutliner.dlt Sat
Nov 1 12:10:49 2008
+++ /branches/gcc-linux/StrongtalkSource/ClassHierarchyOutliner.dlt Sat Dec
19 12:39:38 2009
@@ -641,10 +641,8 @@
up := cl.
[ up = othercl
ifTrue: [ ^true ].
- up = Object
- ] whileFalse:
- [ up := Class coerce: (up superclassIfAbsent: [ self shouldNotHappen
]) ].
- ^false!
+ up := Class coerce: (up superclassIfAbsent: [ ^false ])
+ ] repeat!
class: s <Class> isOrIsSubclassOfOneOf: matches <Cltn[Class]> ^<Boolean>
"returns true if s or one of its superclasses other than Object is in
currentMatches"
=======================================
--- /branches/gcc-linux/StrongtalkSource/ClassVMMirror.dlt Mon Sep 25
12:14:30 2006
+++ /branches/gcc-linux/StrongtalkSource/ClassVMMirror.dlt Sat Dec 19
12:39:38 2009
@@ -192,9 +192,7 @@
"Return the classes depth in the hierarchy"
-^self reflectee = Object
- ifTrue:[0]
- ifFalse:[self superclass depth + 1]
+^self superclassDepth + 1
!
@@ -401,6 +399,28 @@
superclass ^<ClassVMMirror>
^ClassVMMirror on: (self reflectee superclassIfAbsent:[^nil]).
+!
+
+superclass: class <Class>
+
+{{primitiveSetSuperclassOf: self reflectee
+ toClass: class
+ ifFail: [:err| |name|
+ class isNil
+ ifTrue: [name := nil]
+ ifFalse: [name := class name].
+ self error: 'Unable to change superclass of ', self name, ' to ',
name]}}
+!
+
+superclassDepth ^ <Integer>
+
+"Return the classes depth in the hierarchy"
+
+^self superclass isNil
+ ifTrue:[0]
+ ifFalse:[self superclass depth]
+
+
! !
! (Delta mirrorFor: #ClassVMMirror) methodsFor: 'iteration' !
=======================================
--- /branches/gcc-linux/StrongtalkSource/Inspector.dlt Sat Nov 1 12:10:49
2008
+++ /branches/gcc-linux/StrongtalkSource/Inspector.dlt Sat Dec 19 12:39:38
2009
@@ -68,7 +68,7 @@
windowTitle ^ <Str>
- ^'Inspector on ', self mirror reflectee class name! !
+ ^'Inspector on ', self mirror reflecteeClassName! !
! (Delta mirrorFor: #Inspector) methodsFor: 'control' !
@@ -386,7 +386,15 @@
updateNonsafeFields: queue <SharedQueue[Tuple[Int, Str]]>
"Compute unsafe print stings and push them on queue"
- [ self oops do: [ :t <Tuple[Int,Object]> | queue nextPut: t at1 ,, (self
printOop: t at2) ]
+ | errors |
+ errors := OrderedCollection new.
+ [ self oops do: [ :t <Tuple[Int,Object]> |
+ [queue nextPut: t at1 ,, (self printOop: t at2)]
+ on: Error
+ do: [:ex| errors add: ex.
+ ex return]].
+ errors isEmpty
+ ifFalse: [(ErrorCollection errors: errors) signal]
] ensure:[
queue close ]! !
=======================================
--- /branches/gcc-linux/StrongtalkSource/OopsVMMirror.dlt Mon Sep 25
12:14:30 2006
+++ /branches/gcc-linux/StrongtalkSource/OopsVMMirror.dlt Sat Dec 19
12:39:38 2009
@@ -36,11 +36,11 @@
safePrintString ^ <Str>
| strm <CharWriteStream> cn <Str> |
- nil = self reflectee ifTrue: [ ^nil printString ].
- true = self reflectee ifTrue: [ ^true printString ].
- false = self reflectee ifTrue: [ ^false printString ].
+ nil == self reflectee ifTrue: [ ^nil printString ].
+ true == self reflectee ifTrue: [ ^true printString ].
+ false == self reflectee ifTrue: [ ^false printString ].
strm := CharacterReadWriteStream on: (String new: 8).
- cn := self reflectee class name.
+ cn := (Reflection classOf: self reflectee) name.
strm nextPutAll: (self articleFor: cn);
nextPut: Character space;
nextPutAll: cn.
=======================================
--- /branches/gcc-linux/StrongtalkSource/Unclassified.gr Mon Sep 28
16:51:43 2009
+++ /branches/gcc-linux/StrongtalkSource/Unclassified.gr Sat Dec 19
12:39:38 2009
@@ -33,6 +33,7 @@
Delta fileIn: 'ElementSMAPPL.dlt' !
Delta fileIn: 'ElementSTRONG.dlt' !
Delta fileIn: 'Error.dlt' !
+Delta fileIn: 'ErrorCollection.dlt' !
Delta fileIn: 'ErrorTest.dlt' !
Delta fileIn: 'ExceptionSet.dlt' !
Delta fileIn: 'ExceptionSetTest.dlt' !
@@ -77,6 +78,7 @@
Delta fileIn: 'TimeT.dlt' !
Delta fileIn: 'ToolBar.dlt' !
Delta fileIn: 'ToolBarHolder.dlt' !
+Delta fileIn: 'Top.dlt' !
Delta fileIn: 'Warning.dlt' !
Delta fileIn: 'WarningTest.dlt' !
Delta fileIn: 'ZeroDivide.dlt' !
=======================================
--- /branches/gcc-linux/StrongtalkSource/VMMirror.dlt Sat Nov 1 12:10:49
2008
+++ /branches/gcc-linux/StrongtalkSource/VMMirror.dlt Sat Dec 19 12:39:38
2009
@@ -17,8 +17,9 @@
on: o <Object> ^ <VMMirror>
"This is not object-oriented at all but it keeps the VM reflection system
separate."
- | format <Symbol> |
- format := {{primitiveBehaviorVMType: o class ifFail: [:e
<CompressedSymbol> | self error: e]}}.
+ | format <Symbol> class <Behavior> |
+ class := Reflection classOf: o.
+ format := {{primitiveBehaviorVMType: class ifFail: [:e <CompressedSymbol>
| self error: e]}}.
format = #Oops ifTrue: [ ^OopsVMMirror new reflectee: o ].
format = #SmallInteger ifTrue: [ ^SmallIntegerVMMirror new reflectee: o ].
format = #Symbol ifTrue: [ ^SymbolVMMirror new reflectee: o ].
@@ -80,7 +81,11 @@
reflectee: r <Object>
- reflectee := r! !
+ reflectee := r!
+
+reflecteeClassName
+
+ ^(Reflection classOf: self reflectee) name! !
! (Delta mirrorFor: #VMMirror) methodsFor: 'iteration' !
=======================================
--- /branches/gcc-linux/StrongtalkSource/WeakArray.dlt Sun Dec 13 16:47:01
2009
+++ /branches/gcc-linux/StrongtalkSource/WeakArray.dlt Sat Dec 19 12:39:38
2009
@@ -61,10 +61,10 @@
finalizationBlock
- ^[[[self checkNotification]
+ ^[[[self checkNotification.
+ self finalizationSemaphore wait] repeat]
on: Error
- do: [:error| self handleFinalizationError: error] .
- self finalizationSemaphore wait] repeat]!
+ do: [:error| self handleFinalizationError: error]]!
finalizationPriority
@@ -87,8 +87,7 @@
hasFinalizationProcess
- ^self finalizationProcess notNil
- and: [self finalizationProcess running]!
+ ^self finalizationProcess notNil!
initFinalizationSemaphore
=======================================
--- /branches/gcc-linux/StrongtalkSource/world.gr Sat Oct 10 17:23:44 2009
+++ /branches/gcc-linux/StrongtalkSource/world.gr Sat Dec 19 12:39:38 2009
@@ -566,6 +566,7 @@
Delta fileIn: 'EqualizerWrapper.dlt' !
Delta fileIn: 'Exception.dlt' !
Delta fileIn: 'Error.dlt' !
+Delta fileIn: 'ErrorCollection.dlt' !
Delta fileIn: 'ErrorTest.dlt' !
Delta fileIn: 'EventHandler.dlt' !
Delta fileIn: 'ExampleSetTest.dlt' !
@@ -898,6 +899,7 @@
Delta fileIn: 'TokenStreamEditor.dlt' !
Delta fileIn: 'ToolBar.dlt' !
Delta fileIn: 'ToolBarHolder.dlt' !
+Delta fileIn: 'Top.dlt' !
Delta fileIn: 'Towers2Benchmark.dlt' !
Delta fileIn: 'Towers2Disk.dlt' !
Delta fileIn: 'TowersBenchmark.dlt' !
=======================================
--- /branches/gcc-linux/build.win32/strongtalk.ncb Sun Dec 6 13:12:10 2009
+++ /branches/gcc-linux/build.win32/strongtalk.ncb Sat Dec 19 12:39:38 2009
File is too large to display a diff.
=======================================
--- /branches/gcc-linux/build.win32/strongtalk.suo Sun Dec 6 13:12:10 2009
+++ /branches/gcc-linux/build.win32/strongtalk.suo Sat Dec 19 12:39:38 2009
Binary file, no diff available.