Move method's literals form literalArray to indexed instvars.
authorStefan Vogel <sv@exept.de>
Fri, 28 Jun 1996 17:32:42 +0200
changeset 1493 33e226c7d187
parent 1492 50be184036e3
child 1494 dab70fc90ebc
Move method's literals form literalArray to indexed instvars.
Block.st
CompCode.st
CompiledCode.st
ImmutableArray.st
Method.st
--- a/Block.st	Fri Jun 28 15:47:23 1996 +0200
+++ b/Block.st	Fri Jun 28 17:32:42 1996 +0200
@@ -10,6 +10,8 @@
  hereby transferred.
 "
 
+'From Smalltalk/X, Version:2.10.9 on 25-jun-1996 at 14:32:20'                   !
+
 CompiledCode subclass:#Block
 	instanceVariableNames:'home nargs sourcePos initialPC'
 	classVariableNames:'InvalidNewSignal'
@@ -17,7 +19,7 @@
 	category:'Kernel-Methods'
 !
 
-!Block class methodsFor:'documentation'!
+!Block  class methodsFor:'documentation'!
 
 copyright
 "
@@ -300,7 +302,7 @@
 "
 ! !
 
-!Block class methodsFor:'initialization'!
+!Block  class methodsFor:'initialization'!
 
 initialize
     "create signals raised by various errors"
@@ -314,7 +316,7 @@
     "Modified: 22.4.1996 / 16:34:20 / cg"
 ! !
 
-!Block class methodsFor:'instance creation'!
+!Block  class methodsFor:'instance creation'!
 
 code:codeAddress byteCode:bCode numArgs:numArgs sourcePosition:sourcePos initialPC:initialPC literals:literals dynamic:dynamic
     "create a new cheap (homeless) block.
@@ -322,14 +324,17 @@
 
     |newBlock|
 
-    newBlock := super basicNew code:codeAddress 
-			   byteCode:bCode
-			   numArgs:numArgs
-		     sourcePosition:sourcePos
-			  initialPC:initialPC
-			   literals:literals
-			    dynamic:dynamic.
+    newBlock := (super basicNew:(literals size)) 
+                           code:codeAddress 
+                           byteCode:bCode
+                           numArgs:numArgs
+                     sourcePosition:sourcePos
+                          initialPC:initialPC
+                           literals:literals
+                            dynamic:dynamic.
     ^ newBlock
+
+    "Modified: 24.6.1996 / 12:36:48 / stefan"
 !
 
 new
@@ -344,7 +349,7 @@
     ^ InvalidNewSignal raise.
 ! !
 
-!Block class methodsFor:'queries'!
+!Block  class methodsFor:'queries'!
 
 isBuiltInClass
     "return true if this class is known by the run-time-system.
@@ -1098,10 +1103,11 @@
     nargs := numArgs.
     sourcePos := srcPos.
     initialPC := iPC.
-    literals := lits.
+    self literals:lits.
     self dynamic:dynamic
 
     "Modified: 23.4.1996 / 16:05:30 / cg"
+    "Modified: 24.6.1996 / 12:37:37 / stefan"
 !
 
 initialPC:initial 
@@ -1276,9 +1282,9 @@
     ^ self value        "the real logic is in Context>>unwind"
 ! !
 
-!Block class methodsFor:'documentation'!
+!Block  class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/Block.st,v 1.57 1996-05-18 15:25:04 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Block.st,v 1.58 1996-06-28 15:32:20 stefan Exp $'
 ! !
 Block initialize!
--- a/CompCode.st	Fri Jun 28 15:47:23 1996 +0200
+++ b/CompCode.st	Fri Jun 28 17:32:42 1996 +0200
@@ -10,17 +10,17 @@
  hereby transferred.
 "
 
-'From Smalltalk/X, Version:2.10.9 on 11-jun-1996 at 16:33:14'                   !
+'From Smalltalk/X, Version:2.10.9 on 25-jun-1996 at 22:25:18'                   !
 
-ExecutableFunction subclass:#CompiledCode
-	instanceVariableNames:'flags byteCode literals'
+ExecutableFunction variableSubclass:#CompiledCode
+	instanceVariableNames:'flags byteCode'
 	classVariableNames:'NoByteCodeSignal InvalidByteCodeSignal InvalidInstructionSignal
 		BadLiteralsSignal NonBooleanReceiverSignal ArgumentSignal'
 	poolDictionaries:''
 	category:'Kernel-Methods'
 !
 
-!CompiledCode class methodsFor:'documentation'!
+!CompiledCode  class methodsFor:'documentation'!
 
 copyright
 "
@@ -50,7 +50,10 @@
 
       flags       <SmallInteger>    special flag bits coded in a number
       byteCode    <ByteArray>       bytecode if its an interpreted codeobject
-      literals    <Array>           the block/methods literal array
+
+      The block/methods literals are stored in the indexed instance variables.
+      If there is only one indexed instvar, it contains a reference to an
+      Object containing the literals.
 
 
     [Class variables:]
@@ -73,7 +76,7 @@
 "
 ! !
 
-!CompiledCode class methodsFor:'initialization'!
+!CompiledCode  class methodsFor:'initialization'!
 
 initialize
     "create signals raised by various errors"
@@ -107,7 +110,38 @@
     "Modified: 22.4.1996 / 16:33:38 / cg"
 ! !
 
-!CompiledCode class methodsFor:'Signal constants'!
+!CompiledCode  class methodsFor:'instance creation'!
+
+new
+    "create a new method with an inirect literal array
+     stored in the first and only indexed instvar"
+
+    ^ self basicNew:1.
+
+    "Created: 24.6.1996 / 17:21:46 / stefan"
+!
+
+new:numberOfLiterals
+    "create a new method with numberOfLiterals.
+     Implementation note:
+        If (self size) == 1, the only literal is an indirect literal
+        containing an array of literals. Otherwise the literals
+        are stored in self.
+    "
+
+    |nlits|
+
+    nlits := numberOfLiterals.
+    nlits <= 1 ifTrue:[
+        nlits := nlits + 1.
+    ].
+    ^ self basicNew:nlits.
+
+    "Created: 24.6.1996 / 17:20:13 / stefan"
+    "Modified: 25.6.1996 / 14:25:14 / stefan"
+! !
+
+!CompiledCode  class methodsFor:'Signal constants'!
 
 argumentSignal
     "return the signal raised when something's wrong with the
@@ -122,7 +156,7 @@
     ^ ExecutionErrorSignal
 ! !
 
-!CompiledCode class methodsFor:'queries'!
+!CompiledCode  class methodsFor:'queries'!
 
 isBuiltInClass
     "return true if this class is known by the run-time-system.
@@ -141,10 +175,99 @@
     ^ byteCode
 !
 
+changeLiteral:aLiteral to:newLiteral
+    "change aLiteral to newLiteral"
+
+    |lits|
+
+    self size == 1 ifTrue:[
+        lits := self at:1.
+    ] ifFalse:[
+        lits := self.
+    ].
+
+    1 to:(lits size) do:[:i|
+        (lits at:i) == aLiteral ifTrue:[
+            lits at:i put:newLiteral.
+            ^ true.
+        ].
+    ].
+    ^ false.
+
+    "Created: 24.6.1996 / 15:08:11 / stefan"
+    "Modified: 24.6.1996 / 17:07:56 / stefan"
+!
+
+do:aBlock
+    "same as #literalsDo:, in order to get common protocol with Array"
+
+    ^ self literalsDo:aBlock
+
+    "Modified: 25.6.1996 / 22:16:44 / stefan"
+!
+
 literals
     "return the literal array"
 
-    ^ literals
+    self size == 1 ifTrue:[
+        ^ self at:1.
+    ] ifFalse:[
+        |sz lits|
+
+        lits := Array new:(sz := self size).
+        1 to:sz do:[:i|
+            lits at:i put:(self at:i).
+        ].
+        ^ lits.
+    ].
+
+    "
+     (CompiledCode compiledMethodAt:#literals) literals
+    "
+
+    "Modified: 24.6.1996 / 17:12:06 / stefan"
+!
+
+literalsDetect:aBlock ifNone:exceptionBlock
+    "execute a one arg block for each of our literals.
+     return the first literal for which aBlock returns true"
+
+    |lits|
+
+    self size == 1 ifTrue:[
+        lits := self at:1.
+    ] ifFalse:[
+        lits := self.
+    ].
+
+    1 to:(lits size) do:[:i|
+        (aBlock value:(lits at:i)) ifTrue:[
+            ^ lits at:i.
+        ].
+    ].
+    ^ exceptionBlock value.
+
+    "Created: 24.6.1996 / 14:27:35 / stefan"
+    "Modified: 24.6.1996 / 17:13:02 / stefan"
+!
+
+literalsDo:aBlock
+    "execute a one arg block for each of our literals"
+
+    |lits|
+
+    self size == 1 ifTrue:[
+        lits := self at:1.
+    ] ifFalse:[
+        lits := self.
+    ].
+
+    1 to:(lits size) do:[:i|
+        aBlock value:(lits at:i)
+    ].
+
+    "Created: 24.6.1996 / 14:17:12 / stefan"
+    "Modified: 24.6.1996 / 17:13:28 / stefan"
 ! !
 
 !CompiledCode methodsFor:'converting'!
@@ -272,7 +395,23 @@
 literals:aLiteralArray 
     "set the literal array for evaluation - DANGER ALERT"
 
-    literals := aLiteralArray
+    |i|
+
+    aLiteralArray isNil ifTrue:[
+        ^ self.
+    ].
+
+    self size == 1 ifTrue:[
+        self at:1 put:aLiteralArray.
+    ] ifFalse:[
+        i := 1.
+        aLiteralArray do:[:literal|
+            self at:i put:literal.
+            i := i + 1.
+        ].
+    ].
+
+    "Modified: 25.6.1996 / 22:13:08 / stefan"
 !
 
 markFlag
@@ -304,6 +443,12 @@
 
     __INST(flags) = __MKSMALLINT(newFlags);
 %}
+!
+
+test
+   ^ #(1 2 3)
+
+    "Created: 24.6.1996 / 17:02:45 / stefan"
 ! !
 
 !CompiledCode methodsFor:'queries'!
@@ -354,41 +499,43 @@
     |symbolSet|
 
     symbolSet := IdentitySet new.
-    literals notNil ifTrue:[
-	literals do: [ :lit |
-	    lit isSymbol ifTrue: [
-		symbolSet add: lit
-	    ] ifFalse: [
-		lit isArray ifTrue: [
-		    lit traverse: [ :el |
-			el isSymbol ifTrue: [symbolSet add: el]
-		    ]
-		]
-	    ]
-	]
+    self literalsDo: [ :lit |
+        lit isSymbol ifTrue: [
+            symbolSet add: lit
+        ] ifFalse: [
+            lit isArray ifTrue: [
+                lit traverse: [ :el |
+                    el isSymbol ifTrue: [symbolSet add: el]
+                ]
+            ]
+        ]
     ].
     ^ symbolSet
 
     "
      (CompiledCode compiledMethodAt:#messages) messages 
     "
+
+    "Modified: 25.6.1996 / 22:24:20 / stefan"
 !
 
 referencesGlobal:aGlobalSymbol
     "return true, if this method references the global
      bound to aGlobalSymbol."
 
-    |lits|
+    ^ (self literalsDetect:[:lit| lit == aGlobalSymbol] ifNone:[false]) ~~ false.
 
-    (lits := self literals) isNil ifTrue:[^ false].
-    ^ (lits identityIndexOf:aGlobalSymbol startingAt:1) ~~ 0
+    "
+     (CompiledCode compiledMethodAt:#referencesGlobal:) referencesGlobal:#literalsDetect:ifNone:
+     (CompiledCode compiledMethodAt:#referencesGlobal:) referencesGlobal:#bla
+    "
 
-    "Created: 16.4.1996 / 16:36:32 / cg"
+    "Modified: 24.6.1996 / 15:41:59 / stefan"
 ! !
 
-!CompiledCode class methodsFor:'documentation'!
+!CompiledCode  class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/Attic/CompCode.st,v 1.30 1996-06-12 22:10:44 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Attic/CompCode.st,v 1.31 1996-06-28 15:32:22 stefan Exp $'
 ! !
 CompiledCode initialize!
--- a/CompiledCode.st	Fri Jun 28 15:47:23 1996 +0200
+++ b/CompiledCode.st	Fri Jun 28 17:32:42 1996 +0200
@@ -10,17 +10,17 @@
  hereby transferred.
 "
 
-'From Smalltalk/X, Version:2.10.9 on 11-jun-1996 at 16:33:14'                   !
+'From Smalltalk/X, Version:2.10.9 on 25-jun-1996 at 22:25:18'                   !
 
-ExecutableFunction subclass:#CompiledCode
-	instanceVariableNames:'flags byteCode literals'
+ExecutableFunction variableSubclass:#CompiledCode
+	instanceVariableNames:'flags byteCode'
 	classVariableNames:'NoByteCodeSignal InvalidByteCodeSignal InvalidInstructionSignal
 		BadLiteralsSignal NonBooleanReceiverSignal ArgumentSignal'
 	poolDictionaries:''
 	category:'Kernel-Methods'
 !
 
-!CompiledCode class methodsFor:'documentation'!
+!CompiledCode  class methodsFor:'documentation'!
 
 copyright
 "
@@ -50,7 +50,10 @@
 
       flags       <SmallInteger>    special flag bits coded in a number
       byteCode    <ByteArray>       bytecode if its an interpreted codeobject
-      literals    <Array>           the block/methods literal array
+
+      The block/methods literals are stored in the indexed instance variables.
+      If there is only one indexed instvar, it contains a reference to an
+      Object containing the literals.
 
 
     [Class variables:]
@@ -73,7 +76,7 @@
 "
 ! !
 
-!CompiledCode class methodsFor:'initialization'!
+!CompiledCode  class methodsFor:'initialization'!
 
 initialize
     "create signals raised by various errors"
@@ -107,7 +110,38 @@
     "Modified: 22.4.1996 / 16:33:38 / cg"
 ! !
 
-!CompiledCode class methodsFor:'Signal constants'!
+!CompiledCode  class methodsFor:'instance creation'!
+
+new
+    "create a new method with an inirect literal array
+     stored in the first and only indexed instvar"
+
+    ^ self basicNew:1.
+
+    "Created: 24.6.1996 / 17:21:46 / stefan"
+!
+
+new:numberOfLiterals
+    "create a new method with numberOfLiterals.
+     Implementation note:
+        If (self size) == 1, the only literal is an indirect literal
+        containing an array of literals. Otherwise the literals
+        are stored in self.
+    "
+
+    |nlits|
+
+    nlits := numberOfLiterals.
+    nlits <= 1 ifTrue:[
+        nlits := nlits + 1.
+    ].
+    ^ self basicNew:nlits.
+
+    "Created: 24.6.1996 / 17:20:13 / stefan"
+    "Modified: 25.6.1996 / 14:25:14 / stefan"
+! !
+
+!CompiledCode  class methodsFor:'Signal constants'!
 
 argumentSignal
     "return the signal raised when something's wrong with the
@@ -122,7 +156,7 @@
     ^ ExecutionErrorSignal
 ! !
 
-!CompiledCode class methodsFor:'queries'!
+!CompiledCode  class methodsFor:'queries'!
 
 isBuiltInClass
     "return true if this class is known by the run-time-system.
@@ -141,10 +175,99 @@
     ^ byteCode
 !
 
+changeLiteral:aLiteral to:newLiteral
+    "change aLiteral to newLiteral"
+
+    |lits|
+
+    self size == 1 ifTrue:[
+        lits := self at:1.
+    ] ifFalse:[
+        lits := self.
+    ].
+
+    1 to:(lits size) do:[:i|
+        (lits at:i) == aLiteral ifTrue:[
+            lits at:i put:newLiteral.
+            ^ true.
+        ].
+    ].
+    ^ false.
+
+    "Created: 24.6.1996 / 15:08:11 / stefan"
+    "Modified: 24.6.1996 / 17:07:56 / stefan"
+!
+
+do:aBlock
+    "same as #literalsDo:, in order to get common protocol with Array"
+
+    ^ self literalsDo:aBlock
+
+    "Modified: 25.6.1996 / 22:16:44 / stefan"
+!
+
 literals
     "return the literal array"
 
-    ^ literals
+    self size == 1 ifTrue:[
+        ^ self at:1.
+    ] ifFalse:[
+        |sz lits|
+
+        lits := Array new:(sz := self size).
+        1 to:sz do:[:i|
+            lits at:i put:(self at:i).
+        ].
+        ^ lits.
+    ].
+
+    "
+     (CompiledCode compiledMethodAt:#literals) literals
+    "
+
+    "Modified: 24.6.1996 / 17:12:06 / stefan"
+!
+
+literalsDetect:aBlock ifNone:exceptionBlock
+    "execute a one arg block for each of our literals.
+     return the first literal for which aBlock returns true"
+
+    |lits|
+
+    self size == 1 ifTrue:[
+        lits := self at:1.
+    ] ifFalse:[
+        lits := self.
+    ].
+
+    1 to:(lits size) do:[:i|
+        (aBlock value:(lits at:i)) ifTrue:[
+            ^ lits at:i.
+        ].
+    ].
+    ^ exceptionBlock value.
+
+    "Created: 24.6.1996 / 14:27:35 / stefan"
+    "Modified: 24.6.1996 / 17:13:02 / stefan"
+!
+
+literalsDo:aBlock
+    "execute a one arg block for each of our literals"
+
+    |lits|
+
+    self size == 1 ifTrue:[
+        lits := self at:1.
+    ] ifFalse:[
+        lits := self.
+    ].
+
+    1 to:(lits size) do:[:i|
+        aBlock value:(lits at:i)
+    ].
+
+    "Created: 24.6.1996 / 14:17:12 / stefan"
+    "Modified: 24.6.1996 / 17:13:28 / stefan"
 ! !
 
 !CompiledCode methodsFor:'converting'!
@@ -272,7 +395,23 @@
 literals:aLiteralArray 
     "set the literal array for evaluation - DANGER ALERT"
 
-    literals := aLiteralArray
+    |i|
+
+    aLiteralArray isNil ifTrue:[
+        ^ self.
+    ].
+
+    self size == 1 ifTrue:[
+        self at:1 put:aLiteralArray.
+    ] ifFalse:[
+        i := 1.
+        aLiteralArray do:[:literal|
+            self at:i put:literal.
+            i := i + 1.
+        ].
+    ].
+
+    "Modified: 25.6.1996 / 22:13:08 / stefan"
 !
 
 markFlag
@@ -304,6 +443,12 @@
 
     __INST(flags) = __MKSMALLINT(newFlags);
 %}
+!
+
+test
+   ^ #(1 2 3)
+
+    "Created: 24.6.1996 / 17:02:45 / stefan"
 ! !
 
 !CompiledCode methodsFor:'queries'!
@@ -354,41 +499,43 @@
     |symbolSet|
 
     symbolSet := IdentitySet new.
-    literals notNil ifTrue:[
-	literals do: [ :lit |
-	    lit isSymbol ifTrue: [
-		symbolSet add: lit
-	    ] ifFalse: [
-		lit isArray ifTrue: [
-		    lit traverse: [ :el |
-			el isSymbol ifTrue: [symbolSet add: el]
-		    ]
-		]
-	    ]
-	]
+    self literalsDo: [ :lit |
+        lit isSymbol ifTrue: [
+            symbolSet add: lit
+        ] ifFalse: [
+            lit isArray ifTrue: [
+                lit traverse: [ :el |
+                    el isSymbol ifTrue: [symbolSet add: el]
+                ]
+            ]
+        ]
     ].
     ^ symbolSet
 
     "
      (CompiledCode compiledMethodAt:#messages) messages 
     "
+
+    "Modified: 25.6.1996 / 22:24:20 / stefan"
 !
 
 referencesGlobal:aGlobalSymbol
     "return true, if this method references the global
      bound to aGlobalSymbol."
 
-    |lits|
+    ^ (self literalsDetect:[:lit| lit == aGlobalSymbol] ifNone:[false]) ~~ false.
 
-    (lits := self literals) isNil ifTrue:[^ false].
-    ^ (lits identityIndexOf:aGlobalSymbol startingAt:1) ~~ 0
+    "
+     (CompiledCode compiledMethodAt:#referencesGlobal:) referencesGlobal:#literalsDetect:ifNone:
+     (CompiledCode compiledMethodAt:#referencesGlobal:) referencesGlobal:#bla
+    "
 
-    "Created: 16.4.1996 / 16:36:32 / cg"
+    "Modified: 24.6.1996 / 15:41:59 / stefan"
 ! !
 
-!CompiledCode class methodsFor:'documentation'!
+!CompiledCode  class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CompiledCode.st,v 1.30 1996-06-12 22:10:44 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/CompiledCode.st,v 1.31 1996-06-28 15:32:22 stefan Exp $'
 ! !
 CompiledCode initialize!
--- a/ImmutableArray.st	Fri Jun 28 15:47:23 1996 +0200
+++ b/ImmutableArray.st	Fri Jun 28 17:32:42 1996 +0200
@@ -10,6 +10,8 @@
  hereby transferred.
 "
 
+'From Smalltalk/X, Version:2.10.9 on 25-jun-1996 at 14:32:57'                   !
+
 Array subclass:#ImmutableArray
 	instanceVariableNames:''
 	classVariableNames:''
@@ -17,7 +19,7 @@
 	category:'System-Compiler-Support'
 !
 
-!ImmutableArray class methodsFor:'documentation'!
+!ImmutableArray  class methodsFor:'documentation'!
 
 copyright
 "
@@ -115,14 +117,17 @@
     "find the method that contains me"
 
     Method allSubInstances do:[:aMethod |
-	|lits|
-
-	lits := aMethod literals.
-	(lits notNil and:[(lits identityIndexOf:self) ~~ 0]) ifTrue:[
-	    ^ aMethod
-	]
+        (aMethod referencesGlobal:self) ifTrue:[
+            ^ aMethod.
+        ].
     ].
     ^ nil
+
+    " 
+      #(1 2 3) creator
+    "
+
+    "Modified: 24.6.1996 / 15:36:28 / stefan"
 !
 
 notifyStoreError
@@ -183,8 +188,8 @@
     ^ super becomeNil
 ! !
 
-!ImmutableArray class methodsFor:'documentation'!
+!ImmutableArray  class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/ImmutableArray.st,v 1.14 1996-04-25 17:09:46 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/ImmutableArray.st,v 1.15 1996-06-28 15:32:42 stefan Exp $'
 ! !
--- a/Method.st	Fri Jun 28 15:47:23 1996 +0200
+++ b/Method.st	Fri Jun 28 17:32:42 1996 +0200
@@ -10,6 +10,8 @@
  hereby transferred.
 "
 
+'From Smalltalk/X, Version:2.10.9 on 25-jun-1996 at 14:32:15'                   !
+
 CompiledCode subclass:#Method
 	instanceVariableNames:'source sourcePosition category package'
 	classVariableNames:'PrivateMethodSignal LastFileReference LastSourceFileName
@@ -18,7 +20,7 @@
 	category:'Kernel-Methods'
 !
 
-!Method class methodsFor:'documentation'!
+!Method  class methodsFor:'documentation'!
 
 copyright
 "
@@ -135,7 +137,7 @@
 "
 ! !
 
-!Method class methodsFor:'initialization'!
+!Method  class methodsFor:'initialization'!
 
 initialize
     "create signals"
@@ -150,7 +152,7 @@
     "Modified: 22.4.1996 / 16:34:38 / cg"
 ! !
 
-!Method class methodsFor:'Signal constants'!
+!Method  class methodsFor:'Signal constants'!
 
 privateMethodSignal
     "return the signal raised when a private/protected method is called
@@ -159,7 +161,7 @@
     ^ PrivateMethodSignal
 ! !
 
-!Method class methodsFor:'binary storage'!
+!Method  class methodsFor:'binary storage'!
 
 binaryDefinitionFrom: stream manager: manager
     "read my definition from stream."
@@ -201,30 +203,31 @@
     sourceFilename := manager nextObject.
     sourcePos := manager nextObject.
     sourcePos isNil ifTrue:[
-	source := manager nextObject.
+        source := manager nextObject.
     ].
     code := manager nextObject.
 
     snapId == ObjectMemory snapshotID ifTrue:[
-	ObjectMemory incrementSnapshotID
+        ObjectMemory incrementSnapshotID
     ].
 
-    m := Method basicNew.
+    m := Method basicNew:(lits size).
     cat notNil ifTrue:[m category:cat].
     m flags:flags.
     m literals:lits.
     m byteCode:code.
     sourcePos isNil ifTrue:[
-	m source:source
+        m source:source
     ] ifFalse:[
-	m sourceFilename:sourceFilename position:sourcePos
+        m sourceFilename:sourceFilename position:sourcePos
     ].
     ^ m
 
     "Created: 16.1.1996 / 14:44:08 / cg"
+    "Modified: 24.6.1996 / 12:29:35 / stefan"
 ! !
 
-!Method class methodsFor:'queries'!
+!Method  class methodsFor:'queries'!
 
 isBuiltInClass
     "return true if this class is known by the run-time-system.
@@ -254,7 +257,7 @@
 %}
 ! !
 
-!Method class methodsFor:'special'!
+!Method  class methodsFor:'special'!
 
 flushSourceStreamCache
     LastSourceFileName := nil
@@ -2122,9 +2125,9 @@
     "Created: 17.9.1995 / 15:01:14 / claus"
 ! !
 
-!Method class methodsFor:'documentation'!
+!Method  class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/Method.st,v 1.90 1996-06-17 15:22:34 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Method.st,v 1.91 1996-06-28 15:32:23 stefan Exp $'
 ! !
 Method initialize!