Skip to content
New issue

Have a question about this project? Sign up for a free GitHub account to open an issue and contact its maintainers and the community.

By clicking “Sign up for GitHub”, you agree to our terms of service and privacy statement. We’ll occasionally send you account related emails.

Already on GitHub? Sign in to your account

BracedCollection ready for review and integration #14845

Closed
wants to merge 3 commits into from
Closed
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
118 changes: 118 additions & 0 deletions src/AST-Core-Tests/RBLiteralCollectionParserTest.class.st
Original file line number Diff line number Diff line change
@@ -0,0 +1,118 @@
Class {
#name : 'RBLiteralCollectionParserTest',
#superclass : 'RBParserTest',
#category : 'AST-Core-Tests-Parser',
#package : 'AST-Core-Tests',
#tag : 'Parser'
}

{ #category : 'tests' }
RBLiteralCollectionParserTest >> testCollectionWithDollarCharacterIsNotLiteralArrayCollection [

| compiler |
compiler := OpalCompiler new.
self assert: (compiler evaluate:
'{ $: }' )

equals: #($:).

]

{ #category : 'tests' }
RBLiteralCollectionParserTest >> testDictionary [

| compiler dict |
compiler := OpalCompiler new.
dict := (compiler evaluate:
'{ :Dictionary #a -> 33 . #b -> 44}' ).
self assert: (dict at: #a) equals: 33

]

{ #category : 'tests' }
RBLiteralCollectionParserTest >> testDictionaryBorkenPlainText [

self should: [ { :Dictionry #a -> 33 . #b -> 44 } ] raise: Error.
self should: [ { :Se 1 . 2 } ] raise: Error.
]

{ #category : 'tests' }
RBLiteralCollectionParserTest >> testDictionaryPlainText [

| dict |
dict := { :Dictionary #a -> 33 . #b -> 44}.
self assert: (dict at: #a) equals: 33

]

{ #category : 'tests' }
RBLiteralCollectionParserTest >> testDynamicArrayIsWorking [

self assert: { } equals: #().
self assert: { 1 . 2 } equals: #(1 2).
]

{ #category : 'tests' }
RBLiteralCollectionParserTest >> testLiteralSet [

| compiler |
compiler := OpalCompiler new.
self assert: (compiler evaluate:
'{ :Set 1 . 2 . 1}' )

equals: #(1 2) asSet.

]

{ #category : 'tests' }
RBLiteralCollectionParserTest >> testNestedLiteralSet [

| compiler |
compiler := OpalCompiler new.
self assert: (compiler evaluate:
'{ :Set 1 . { :Set 2 . 2 } . 1}' )

equals: (Set new add: 1 ; add: (Set new add: 2; add: 2; yourself); add: 1 ;yourself).

]

{ #category : 'tests' }
RBLiteralCollectionParserTest >> testOrderedCollection [

| compiler |
compiler := OpalCompiler new.
self
assert: (compiler evaluate:
'{ :OrderedCollection 1 . 2 . 1 . 3}' )
equals: #(1 2 1 3) asOrderedCollection.

]

{ #category : 'tests' }
RBLiteralCollectionParserTest >> testParseDynamicArrayAgain [

| arrayNode |
arrayNode := (RBParser parseExpression: '{ 1 . 2 }').
self assert: arrayNode class equals: RBArrayNode.
self assert: arrayNode statements first value equals: 1.
self assert: arrayNode statements second value equals: 2.
]

{ #category : 'tests' }
RBLiteralCollectionParserTest >> testParseDynamicSet [

| literalCollectionNode |
literalCollectionNode := (RBParser parseExpression: '{ :Set 1 . 2 }').
self assert: literalCollectionNode class equals: RBLiteralCollectionNode.
self assert: literalCollectionNode collectionClass name equals: 'Set'.
self assert: literalCollectionNode statements first value equals: 1.
self assert: literalCollectionNode statements second value equals: 2.
]

{ #category : 'tests' }
RBLiteralCollectionParserTest >> testParseDynamicSetPlainText [

| set |
set := { :Set 1 . 2 . 2 }.
self assert: set size equals: 2
]
7 changes: 7 additions & 0 deletions src/AST-Core/ASTTypingVisitor.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -385,6 +385,13 @@ ASTTypingVisitor >> visitLiteralArrayNode: aLiteralNode [
self typeNode: aLiteralNode with: Array
]

{ #category : 'visiting' }
ASTTypingVisitor >> visitLiteralCollectionNode: aLiteralNode [

super visitLiteralCollectionNode: aLiteralNode.
self typeNode: aLiteralNode with: aLiteralNode collectionClass
]

{ #category : 'visiting' }
ASTTypingVisitor >> visitLiteralNode: aLiteralNode [

Expand Down
31 changes: 31 additions & 0 deletions src/AST-Core/RBLiteralCollectionNode.class.st
Original file line number Diff line number Diff line change
@@ -0,0 +1,31 @@
"
I represent a literal collection as in `{ :Set 1.3.1}`.
My instances knows the collection class, here `Set` in addition to the state and behavior of my superclass `RBArrayNode`.
"
Class {
#name : 'RBLiteralCollectionNode',
#superclass : 'RBArrayNode',
#instVars : [
'collectionClass'
],
#category : 'AST-Core-Nodes',
#package : 'AST-Core',
#tag : 'Nodes'
}

{ #category : 'visiting' }
RBLiteralCollectionNode >> acceptVisitor: aProgramNodeVisitor [
^ aProgramNodeVisitor visitLiteralCollectionNode: self
]

{ #category : 'accessing' }
RBLiteralCollectionNode >> collectionClass [

^ collectionClass
]

{ #category : 'accessing' }
RBLiteralCollectionNode >> collectionClass: anObject [

collectionClass := anObject
]
36 changes: 35 additions & 1 deletion src/AST-Core/RBParser.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -242,6 +242,11 @@ RBParser >> literalArrayNodeClass [
^ RBLiteralArrayNode
]

{ #category : 'private - parsing' }
RBParser >> literalCollectionNodeClass [
^ RBLiteralCollectionNode
]

{ #category : 'private - classes' }
RBParser >> literalNodeClass [
^ RBLiteralNode
Expand Down Expand Up @@ -283,6 +288,15 @@ RBParser >> parseArray [
^ node
]

{ #category : 'private - parsing' }
RBParser >> parseArrayable [
"We have { and it can be { 1 . 2} or {:Set 1. 2. }"

^ (self nextToken isSpecial: $:)
ifFalse: [ self parseArray ]
ifTrue: [ self parseLiteralCollection ]
]

{ #category : 'private - parsing' }
RBParser >> parseAssignment [
"Need one token lookahead to see if we have a ':='. This method could
Expand Down Expand Up @@ -755,6 +769,26 @@ RBParser >> parseLiteralByteArrayObject [
^self parsePrimitiveLiteral
]

{ #category : 'private - parsing' }
RBParser >> parseLiteralCollection [
":Set 1. 2 . 3 }"

| startToken node |
startToken := currentToken.
self step.
node := self literalCollectionNodeClass new.
node left: startToken start.
self step.
node collectionClass: self parseVariableNode.

self parseStatementList: false into: node untilAnyCloserOf: '}'.
(currentToken isSpecial: $})
ifFalse: [ ^ self parseEnglobingError: node statements with: startToken errorMessage: '''}'' expected'].
node right: currentToken start.
self step.
^ node
]

{ #category : 'private - parsing' }
RBParser >> parseLiterals [

Expand Down Expand Up @@ -925,7 +959,7 @@ RBParser >> parsePrimitiveObject [
ifTrue:
[currentToken value = $[ ifTrue: [^self saveCommentsDuring:[self parseBlock]].
currentToken value = $( ifTrue: [^self parseParenthesizedExpression].
currentToken value = ${ ifTrue: [^self parseArray]].
currentToken value = ${ ifTrue: [^self parseArrayable]].

"Annotations are implemented as a magic receiver '@'"
(currentToken isBinary: #@) ifTrue: [
Expand Down
6 changes: 6 additions & 0 deletions src/AST-Core/RBProgramNodeVisitor.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -106,6 +106,12 @@ RBProgramNodeVisitor >> visitLiteralArrayNode: aRBLiteralArrayNode [
aRBLiteralArrayNode contents do: [ :each | self visitNode: each ]
]

{ #category : 'visiting' }
RBProgramNodeVisitor >> visitLiteralCollectionNode: aLiteralCollectionNode [
self visitNode: aLiteralCollectionNode collectionClass.
aLiteralCollectionNode children do: [ :each | self visitNode: each ]
]

{ #category : 'visiting' }
RBProgramNodeVisitor >> visitLiteralNode: aLiteralNode [
]
Expand Down
7 changes: 7 additions & 0 deletions src/Collections-Abstract/ArrayedCollection.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -156,6 +156,13 @@ ArrayedCollection class >> withAll: aCollection [
^ (self new: aCollection size) replaceFrom: 1 to: aCollection size with: aCollection
]

{ #category : 'instance creation' }
ArrayedCollection class >> withAllForBrace: aCollection [
"Create a new collection containing all the elements from aCollection. This method is used by the literalCollection feature e.g., {:Set 1. 2 . 2}"

^ (self new: aCollection size) replaceFrom: 1 to: aCollection size with: aCollection
]

{ #category : 'adding' }
ArrayedCollection >> add: newObject [
self shouldNotImplement
Expand Down
9 changes: 9 additions & 0 deletions src/Collections-Abstract/Collection.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -134,6 +134,15 @@ Collection class >> withAll: aCollection [
yourself
]

{ #category : 'instance creation' }
Collection class >> withAllForBrace: aCollection [
"Create a new collection containing all the elements from aCollection. This method is used by the literalCollection feature e.g., {:Set 1. 2 . 2}."

^ (self new: aCollection size)
addAll: aCollection;
yourself
]

{ #category : 'enumerating' }
Collection >> & aCollection [

Expand Down
7 changes: 7 additions & 0 deletions src/Collections-Atomic/WaitfreeQueue.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -63,6 +63,13 @@ WaitfreeQueue class >> withAll: aCollection [
^ self new initializeWithAll: aCollection
]

{ #category : 'instance creation' }
WaitfreeQueue class >> withAllForBrace: aCollection [
"Answer an instance of the receiver initialized with the supplied collection of items. This method is used by the literalCollection feature e.g., {:Set 1. 2 . 2}"

^ self new initializeWithAll: aCollection
]

{ #category : 'private - accessing' }
WaitfreeQueue >> dummy [
"Answer the dummy entry of the receiver.
Expand Down
2 changes: 1 addition & 1 deletion src/Collections-Sequenceable/Heap.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -100,7 +100,7 @@ Heap class >> sortBlock: aBlock [
{ #category : 'instance creation' }
Heap class >> withAll: aCollection [
"Create a new heap with all the elements from aCollection"
^(self basicNew)
^ self basicNew
setCollection: aCollection asArray copy tally: aCollection size;
reSort;
yourself
Expand Down
27 changes: 27 additions & 0 deletions src/Collections-Unordered/Dictionary.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -196,6 +196,33 @@ Dictionary class >> newFromPairs: anArray [
^ newDictionary
]

{ #category : 'instance creation' }
Dictionary class >> withAll: anArrayOfAssociations [
"Answer an instance of me containing the same associations as the argument.
If the same key appears twice, the last one enumerated will win"

"(Dictionary withAll: {1->#a. 2->#b. 3->#c}) >>> ({1->#a. 2->#b. 3->#c} asDictionary)"

| newDictionary |
newDictionary := self new: anArrayOfAssociations size.
anArrayOfAssociations associationsDo: [:x |newDictionary add: x].
^ newDictionary
]

{ #category : 'instance creation' }
Dictionary class >> withAllForBrace: anArrayOfAssociations [
"Answer an instance of me containing the same associations as the argument.
If the same key appears twice, the last one enumerated will win.
This method is supporting {:Dictionary 1->#a. 2->#b. 3->#c}"

"(Dictionary withAllForBrace: {1->#a. 2->#b. 3->#c}) >>> ({1->#a. 2->#b. 3->#c} asDictionary)"

| newDictionary |
newDictionary := self new: anArrayOfAssociations size.
anArrayOfAssociations associationsDo: [:x |newDictionary add: x].
^ newDictionary
]

{ #category : 'comparing' }
Dictionary >> = aDictionary [
"Two dictionaries are equal if
Expand Down
9 changes: 9 additions & 0 deletions src/EnlumineurFormatter/EFFormatter.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -2181,6 +2181,15 @@ EFFormatter >> visitLiteralArrayNode: aRBArrayLiteralNode [
codeStream nextPutAll: self spacesInsideArray ] ]
]

{ #category : 'visiting' }
EFFormatter >> visitLiteralCollectionNode: aLiteralCollectionNode [
self
bracketWith: '{}'
around: [
codeStream space; nextPutAll: ':', aLiteralCollectionNode collectionClass name.
self formatArray: aLiteralCollectionNode ]
]

{ #category : 'visiting' }
EFFormatter >> visitLiteralNode: aLiteralNode [
aLiteralNode value isLiteral
Expand Down
10 changes: 10 additions & 0 deletions src/HeuristicCompletion-Model/CoASTResultSetBuilder.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -150,6 +150,16 @@ CoASTResultSetBuilder >> visitLiteralArrayNode: aRBLiteralArrayNode [
^ self visitValueNode: aRBLiteralArrayNode
]

{ #category : 'visiting' }
CoASTResultSetBuilder >> visitLiteralCollectionNode: aLiteralCollectionNode [

"I do not know what I should return but the children being a collection it does not work."
| res |
res := self visitNode: aLiteralCollectionNode collectionClass.
aLiteralCollectionNode children do: [ :each | self visitNode: each ].
^ res
]

{ #category : 'visiting' }
CoASTResultSetBuilder >> visitLiteralValueNode: aRBLiteralValueNode [

Expand Down
1 change: 1 addition & 0 deletions src/Kernel-ExtraUtils/ClassHierarchyPrinterTest.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -53,6 +53,7 @@ ClassHierarchyPrinterTest >> testOnlyRBASTNodes [
RBValueNode
RBAnnotationMarkNode
RBArrayNode
RBLiteralCollectionNode
RBAssignmentNode
RBBlockNode
RBCascadeNode
Expand Down
7 changes: 7 additions & 0 deletions src/OpalCompiler-Core/OCASTSemanticAnalyzer.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -236,6 +236,13 @@ OCASTSemanticAnalyzer >> visitInlinedBlockNode: aBlockNode [
scope := scope popScope
]

{ #category : 'visiting' }
OCASTSemanticAnalyzer >> visitLiteralCollectionNode: aLiteralCollectionNode [
aLiteralCollectionNode collectionClass parent: aLiteralCollectionNode.
super visitLiteralCollectionNode: aLiteralCollectionNode.

]

{ #category : 'visiting' }
OCASTSemanticAnalyzer >> visitMessageNode: aMessageNode [

Expand Down
9 changes: 9 additions & 0 deletions src/OpalCompiler-Core/OCASTTranslator.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -662,6 +662,15 @@ OCASTTranslator >> visitLiteralArrayNode: aRBLiteralArrayNode [
methodBuilder pushLiteral: aRBLiteralArrayNode value
]

{ #category : 'visiting' }
OCASTTranslator >> visitLiteralCollectionNode: aLiteralCollectionNode [


methodBuilder pushLiteralVariable: aLiteralCollectionNode collectionClass binding.
self visitArrayNode: aLiteralCollectionNode.
methodBuilder send: #withAllForBrace:
]

{ #category : 'visitor - double dispatching' }
OCASTTranslator >> visitLiteralNode: aLiteralNode [

Expand Down