-
Notifications
You must be signed in to change notification settings - Fork 71
/
CCompoundStatementNode.class.st
145 lines (112 loc) · 3.34 KB
/
CCompoundStatementNode.class.st
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
Class {
#name : #CCompoundStatementNode,
#superclass : #CGLRAbstractNode,
#instVars : [
'declarations',
'statements',
'needsBrackets'
],
#category : #'CAST-Nodes'
}
{ #category : #'instance creation' }
CCompoundStatementNode class >> declarations: declarations statements: statements [
^ self new
declarations: declarations;
statements: statements;
yourself
]
{ #category : #'instance creation' }
CCompoundStatementNode class >> statements: statements [
^ self new
statements: statements;
yourself
]
{ #category : #comparing }
CCompoundStatementNode >> = anObject [
"Answer whether the receiver and anObject represent the same object."
self == anObject ifTrue: [ ^ true ].
self class = anObject class ifFalse: [ ^ false ].
^ statements = anObject statements and: [
declarations = anObject declarations ]
]
{ #category : #generated }
CCompoundStatementNode >> acceptVisitor: anAbstractVisitor [
^ anAbstractVisitor visitCompoundStatement: self
]
{ #category : #adding }
CCompoundStatementNode >> add: aStatement [
statements add: aStatement
]
{ #category : #adding }
CCompoundStatementNode >> addAll: aCompoundStatement [
statements addAll: aCompoundStatement statements
]
{ #category : #generated }
CCompoundStatementNode >> declarations [
^ declarations
]
{ #category : #generated }
CCompoundStatementNode >> declarations: anOrderedCollection [
self setParents: self declarations to: nil.
declarations := anOrderedCollection.
self setParents: self declarations to: self
]
{ #category : #comparing }
CCompoundStatementNode >> hash [
"Answer an integer value that is related to the identity of the receiver."
^ statements hash bitXor: declarations hash
]
{ #category : #'generated-initialize-release' }
CCompoundStatementNode >> initialize [
super initialize.
statements := OrderedCollection new: 2.
declarations := OrderedCollection new: 2.
needsBrackets := true.
needsSeparator := false
]
{ #category : #testing }
CCompoundStatementNode >> isCompoundStatement [
^ true
]
{ #category : #testing }
CCompoundStatementNode >> isEmpty [
^ statements isEmpty or: [ statements allSatisfy: [ :e | e isEmpty ] ]
]
{ #category : #accessing }
CCompoundStatementNode >> last [
"For some unknown reason, the some compound can be empty."
[ statements last isEmpty ] whileTrue: [ statements removeAt: statements size ].
"Recursive call to get the real last if last is also a compound"
^ statements last last
]
{ #category : #accessing }
CCompoundStatementNode >> last: aCReturnStatementNode [
"We rewrite the tree recursively.
Since the last statement of a compound statement can be another compound statement,
we need to rewrite the last statement of the deepest one"
statements
at: statements size
put: (statements last last: aCReturnStatementNode)
]
{ #category : #accessing }
CCompoundStatementNode >> needsBrackets [
^ needsBrackets
]
{ #category : #accessing }
CCompoundStatementNode >> needsBrackets: anObject [
needsBrackets := anObject
]
{ #category : #testing }
CCompoundStatementNode >> needsTrailingSemicolon [
^ false
]
{ #category : #generated }
CCompoundStatementNode >> statements [
^ statements
]
{ #category : #generated }
CCompoundStatementNode >> statements: anOrderedCollection [
self setParents: self statements to: nil.
statements := anOrderedCollection.
self setParents: self statements to: self
]