Skip to content

Commit

Permalink
fixes #2803
Browse files Browse the repository at this point in the history
  • Loading branch information
MarcusDenker committed Mar 12, 2019
1 parent 8335f03 commit 68ff01d
Show file tree
Hide file tree
Showing 2 changed files with 18 additions and 5 deletions.
13 changes: 8 additions & 5 deletions src/AST-Core/RBParser.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -438,12 +438,15 @@ RBParser >> parseCascadeMessage [

{ #category : #'error handling' }
RBParser >> parseErrorNode: aMessageString [
| sourceString |
currentToken isError
| sourceString errorPosition |
currentToken isError
ifTrue: [ ^ RBParseErrorNode errorMessage: currentToken cause value: currentToken value at: currentToken start ].
sourceString := source copyFrom: self errorPosition to: source size.
^ RBParseErrorNode
errorMessage: aMessageString value: sourceString at: self errorPosition
errorPosition := self errorPosition.
"the error at the end means in some cases that the start of the error is before"
aMessageString = ''')'' expected'
ifTrue: [ errorPosition := source findLastOccurrenceOfString: '(' startingAt: 1 ].
sourceString := source copyFrom: errorPosition to: source size.
^ RBParseErrorNode errorMessage: aMessageString value: sourceString at: self errorPosition
]

{ #category : #accessing }
Expand Down
10 changes: 10 additions & 0 deletions src/AST-Tests-Core/RBFormatterTest.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -83,6 +83,16 @@ RBFormatterTest >> testParseError [

]

{ #category : #testing }
RBFormatterTest >> testParseError2 [
| inputSource errorNode |
"parse error nodes should have the faulty code"
inputSource := '( 1 + 2'.
errorNode := RBParser parseFaultyExpression: inputSource.
self assert: errorNode source equals: errorNode formattedCode

]

{ #category : #testing }
RBFormatterTest >> testPreserveLiteralArrayFormat [
| inputSource literalArrayNode |
Expand Down

0 comments on commit 68ff01d

Please sign in to comment.