File: VMM38b4-64bit-image2-ikp.1.cs

package info (click to toggle)
squeak-vm 1%3A4.10.2.2614-4.1
  • links: PTS, VCS
  • area: main
  • in suites: stretch
  • size: 13,284 kB
  • ctags: 15,344
  • sloc: ansic: 75,096; cs: 11,191; objc: 5,494; sh: 3,170; asm: 1,533; cpp: 449; pascal: 372; makefile: 366; awk: 103
file content (174 lines) | stat: -rw-r--r-- 6,570 bytes parent folder | download | duplicates (6)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
'From Squeak3.8gamma of ''24 November 2004'' [latest update: #6548] on 31 March 2005 at 11:13:52 am'!
"Change Set:		VMM38b4-64bit-image2-ikp
Date:			2005-03-31
Author:			ian.piumarta@squeakland.org

Changes relative to 3.8g-6548 that add 64-bit support to the image.  File in VMM38b4-64bit-image1 BEFORE this file."!


!Class methodsFor: 'subclass creation' stamp: 'di 10/6/2004 10:54'!
variableLongSubclass: t instanceVariableNames: f 
	classVariableNames: d poolDictionaries: s category: cat
	"This is the standard initialization message for creating a new class as a 
	subclass of an existing class (the receiver) in which the subclass is to 
	have indexable word-sized nonpointer variables."
	^(ClassBuilder new)
		superclass: self
		variableLongSubclass: t
		instanceVariableNames: f
		classVariableNames: d
		poolDictionaries: s
		category: cat
! !


!ClassBuilder methodsFor: 'class format' stamp: 'di 10/6/2004 10:51'!
computeFormat: type instSize: newInstSize forSuper: newSuper ccIndex: ccIndex
	"Compute the new format for making oldClass a subclass of newSuper.
	Return the format or nil if there is any problem."
	| instSize isVar isPointers isWeak |
	instSize _ newInstSize + (newSuper ifNil:[0] ifNotNil:[newSuper instSize]).
	instSize > 254 ifTrue:[
		self error: 'Class has too many instance variables (', instSize printString,')'.
		^nil].
	type == #compiledMethod
		ifTrue:[^CompiledMethod instSpec].
	type == #normal ifTrue:[isVar _ isWeak _ false. isPointers _ true].
	type == #weak ifTrue:[isVar _ isWeak _ isPointers _ true].
	type == #variable ifTrue:[isVar _ isPointers _ true. isWeak _ false].
	type == #bytes ifTrue:[isVar _ true. isPointers _ isWeak _ false].
	type == #words ifTrue:[isVar _ true. isPointers _ isWeak _ false].
	type == #longs ifTrue:[isVar _ true. isPointers _ isWeak _ false].
	(isPointers not and:[instSize > 0]) ifTrue:[
		self error:'A non-pointer class cannot have instance variables'.
		^nil].
	^(self format: instSize 
		variable: isVar 
		words: type 
		pointers: isPointers 
		weak: isWeak) + (ccIndex bitShift: 11).! !

!ClassBuilder methodsFor: 'class format' stamp: 'di 10/6/2004 10:49'!
format: nInstVars variable: isVar words: fieldType pointers: isPointers weak: isWeak
	"Compute the format for the given instance specfication."
	| cClass instSpec sizeHiBits fmt |
	self flag: #instSizeChange.
"
Smalltalk browseAllCallsOn: #instSizeChange.
Smalltalk browseAllImplementorsOf: #fixedFieldsOf:.
Smalltalk browseAllImplementorsOf: #instantiateClass:indexableSize:.
"
"
	NOTE: This code supports the backward-compatible extension to 8 bits of instSize.
	For now the format word is...
		<2 bits=instSize//64><5 bits=cClass><4 bits=instSpec><6 bits=instSize\\64><1 bit=0>
	But when we revise the image format, it should become...
		<5 bits=cClass><4 bits=instSpec><8 bits=instSize><1 bit=0>
"
	sizeHiBits _ (nInstVars+1) // 64.
	cClass _ 0.  "for now"
	instSpec _ isWeak
		ifTrue:[4]
		ifFalse:[isPointers
				ifTrue: [isVar
						ifTrue: [nInstVars>0 ifTrue: [3] ifFalse: [2]]
						ifFalse: [nInstVars>0 ifTrue: [1] ifFalse: [0]]]
				ifFalse: [fieldType == #longs ifTrue: [7] ifFalse:
							[fieldType == #words ifTrue: [6] ifFalse:
							[fieldType == #bytes ifTrue: [8]
							ifFalse: [self error: 'bad fieldType']]]]].
	fmt _ sizeHiBits.
	fmt _ (fmt bitShift: 5) + cClass.
	fmt _ (fmt bitShift: 4) + instSpec.
	fmt _ (fmt bitShift: 6) + ((nInstVars+1)\\64).  "+1 since prim size field includes header"
	fmt _ (fmt bitShift: 1). "This shift plus integer bit lets wordSize work like byteSize"
	^fmt! !

!ClassBuilder methodsFor: 'public' stamp: 'di 10/6/2004 10:53'!
superclass: aClass
	variableLongSubclass: t instanceVariableNames: f 
	classVariableNames: d poolDictionaries: s category: cat
	"This is the standard initialization message for creating a new class as a 
	subclass of an existing class in which the subclass is to 
	have indexable word-sized nonpointer variables."
	(aClass instSize > 0)
		ifTrue: [^self error: 'cannot make a word subclass of a class with named fields'].
	(aClass isVariable and: [aClass isBytes])
		ifTrue: [^self error: 'cannot make a word subclass of a class with byte fields'].
	(aClass isVariable and: [aClass isPointers])
		ifTrue: [^self error: 'cannot make a word subclass of a class with pointer fields'].

	^self 
		name: t
		inEnvironment: aClass environment
		subclassOf: aClass
		type: #longs
		instanceVariableNames: f
		classVariableNames: d
		poolDictionaries: s
		category: cat! !


!CompiledMethod methodsFor: 'accessing' stamp: 'di 6/29/2004 12:28'!
initialPC
	"Answer the program counter for the receiver's first bytecode."

	^ (self numLiterals + 1) * Smalltalk wordSize + 1
! !


!FileList methodsFor: 'private' stamp: 'di 7/2/2004 11:35'!
readContentsHex: brevity
	"retrieve the contents from the external file unless it is too long.
	  Don't create a file here.  Check if exists."
	| f size data hexData s |

	f := directory oldFileOrNoneNamed: self fullName. 
	f == nil ifTrue: [^ 'For some reason, this file cannot be read' translated].
	((size := f size)) > 5000 & brevity
		ifTrue: [data := f next: 10000. f close. brevityState := #briefHex]
		ifFalse: [data := f contentsOfEntireFile. brevityState := #fullHex].

	s := WriteStream on: (String new: data size*4).
	0 to: data size-1 by: 16 do:
		[:loc | s nextPutAll: loc hex; space;
			nextPut: $(; print: loc; nextPut: $); space; tab.
		loc+1 to: (loc+16 min: data size) do: [:i | s nextPutAll: (data at: i) hex; space].
		s tab; nextPutAll: '|' , ((data copyFrom: loc+1 to: (loc+16 min: data size)) copyReplaceAll: Character cr asString with: '/') asString , '|'.
		s cr].
	hexData := s contents.

	^ contents := ((size > 5000) & brevity
		ifTrue: ['File ''{1}'' is {2} bytes long.
You may use the ''get'' command to read the entire file.

Here are the first 5000 characters...
------------------------------------------
{3}
------------------------------------------
... end of the first 5000 characters.' translated format: {fileName. size. hexData}]
		ifFalse: [hexData]).
! !


!Form methodsFor: 'other' stamp: 'di 6/19/2004 12:25'!
bitsSize64
	| pixPerWord |
	depth == nil ifTrue: [depth _ 1].
	pixPerWord _ 64 // self depth.
	^ width + pixPerWord - 1 // pixPerWord * height
"
 | nBytes nBytes64 | nBytes _ nBytes64 _ 0.
Form allInstances , ColorForm allinstances do:
	[:f | f unhibernate.
	nBytes _ nBytes + (f bitsSize*4).
	nBytes64 _ nBytes64 + (f bitsSize64*8).
	f hibernate].
{nBytes. nBytes64}
"! !


!Text methodsFor: 'accessing' stamp: 'ikp 3/31/2005 07:52'!
stamp
	^'unknown'! !