@@ -2,13 +2,153 @@ Class {
22 #name : ' SpurContiguousObjStack' ,
33 #superclass : ' SpurNewSpaceSpace' ,
44 #instVars : [
5- ' top'
5+ ' top' ,
6+ ' initialSize' ,
7+ ' memoryManager' ,
8+ ' objectMemory'
69 ],
710 #category : ' VMMaker-SpurMemoryManager' ,
811 #package : ' VMMaker' ,
912 #tag : ' SpurMemoryManager'
1013}
1114
15+ { #category : ' translation' }
16+ SpurContiguousObjStack class >> filteredInstVarNames [
17+
18+ ^ super filteredInstVarNames copyWithoutAll: #(memoryManager objectMemory)
19+ ]
20+
21+ { #category : ' adding' }
22+ SpurContiguousObjStack >> addToStack: anOop [
23+
24+ self top = self limit ifTrue: [ self extendObjStack ].
25+
26+ objectMemory longAt: self top put: anOop.
27+ self top: self top + objectMemory bytesPerOop.
28+ ]
29+
30+ { #category : ' C library simulation' }
31+ SpurContiguousObjStack >> calloc: num _: size [
32+
33+ < doNotGenerate>
34+ ^ self malloc: num * size
35+ ]
36+
37+ { #category : ' adding' }
38+ SpurContiguousObjStack >> extendObjStack [
39+
40+ | newTop newSize newStart newLimit |
41+
42+ " We double the size of the stack"
43+ newSize := ((self limit - self start) / objectMemory wordSize) * 2 .
44+
45+ newStart := objectMemory realloc: self start _: (objectMemory wordSize * newSize).
46+ newStart ifNil: [
47+ objectMemory error: ' Imposible to extend SpurContiguousObjStack' ].
48+
49+ newLimit := newStart asInteger + (newSize * objectMemory wordSize).
50+
51+ newTop := (self top - self start) + newStart asInteger.
52+
53+ self
54+ start: newStart asInteger;
55+ limit: newLimit.
56+
57+ self top: newTop
58+ ]
59+
60+ { #category : ' C library simulation' }
61+ SpurContiguousObjStack >> free: anAddress [
62+
63+ < doNotGenerate>
64+ memoryManager free: anAddress
65+ ]
66+
67+ { #category : ' freeing' }
68+ SpurContiguousObjStack >> freeObjectStack [
69+
70+ objectMemory free: self start.
71+ self start: 0 .
72+ self top: 0 .
73+ ]
74+
75+ { #category : ' accessing' }
76+ SpurContiguousObjStack >> initialSize [
77+
78+ ^ initialSize
79+ ]
80+
81+ { #category : ' accessing' }
82+ SpurContiguousObjStack >> initialSize: anObject [
83+
84+ initialSize := anObject
85+ ]
86+
87+ { #category : ' initialization' }
88+ SpurContiguousObjStack >> initializeWithAtLeast: anInitialSizeIfNotProvided onError: onErrorBlock [
89+
90+ " Initialize the queue so that
91+ - start points at the beginning of the allocated chunk,
92+ - limit points to the last potential entry
93+ - top is by default the start"
94+
95+ < inline: true >
96+
97+ | allocation |
98+
99+ (self initialSize isNil or : [ self initialSize = 0 ])
100+ ifTrue: [ self initialSize: anInitialSizeIfNotProvided ].
101+
102+ allocation := objectMemory malloc: (objectMemory sizeof: #' void *' ) * self initialSize.
103+
104+ allocation ifNil: [ onErrorBlock value ].
105+
106+ self
107+ start: allocation asInteger;
108+ limit: allocation asInteger
109+ + ((objectMemory sizeof: #' void *' ) * self initialSize).
110+
111+ self top: self start
112+ ]
113+
114+ { #category : ' C library simulation' }
115+ SpurContiguousObjStack >> malloc: size [
116+ < doNotGenerate>
117+ | address region |
118+
119+ size = 0 ifTrue: [ ^ nil ].
120+
121+ address := memoryManager allocate: size.
122+ region := memoryManager regionAtAddress: address.
123+ ^ CNewArrayAccessor new
124+ setObject: region;
125+ address: address;
126+ yourself
127+ ]
128+
129+ { #category : ' accessing' }
130+ SpurContiguousObjStack >> memoryManager: anObject [
131+ < doNotGenerate>
132+ memoryManager := anObject
133+ ]
134+
135+ { #category : ' accessing' }
136+ SpurContiguousObjStack >> objectMemory: anObject [
137+ < doNotGenerate>
138+ objectMemory := anObject
139+ ]
140+
141+ { #category : ' enumerating' }
142+ SpurContiguousObjStack >> objectStackDo: aFullBlockClosure [
143+
144+ < inline: true >
145+
146+ self start
147+ to: self top - objectMemory bytesPerOop
148+ by: objectMemory bytesPerOop
149+ do: [ :anAddress | aFullBlockClosure value: (objectMemory longAt: anAddress) ]
150+ ]
151+
12152{ #category : ' printing' }
13153SpurContiguousObjStack >> printOn: aStream [
14154 < doNotGenerate>
0 commit comments