Skip to content

Commit

Permalink
Remove unnecessary tests
Browse files Browse the repository at this point in the history
Add conditional inspection tabs
  • Loading branch information
Hernán Morales Durand committed Sep 7, 2023
1 parent 5a35135 commit e41ee03
Show file tree
Hide file tree
Showing 2 changed files with 20 additions and 43 deletions.
41 changes: 0 additions & 41 deletions smalltalksrc/Slang-Tests/SlangBasicTranslationTest.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -229,12 +229,6 @@ SlangBasicTranslationTest >> testAssignementAsExpressionWithExpressionBlockWithL
equals: 'y = (foo(1, 2), foo(3, 4), foo(5, 6), a)'
]

{ #category : #'tests-blocks' }
SlangBasicTranslationTest >> testAssignmentNodeIsExpression [

self assert: TAssignmentNode new isExpression.
]

{ #category : #'tests-inlinemethod' }
SlangBasicTranslationTest >> testBasicInlineAsSpecified [

Expand Down Expand Up @@ -1947,23 +1941,6 @@ SlangBasicTranslationTest >> testNonContiguousCaseStatementWithSameBodyAreCollap
}'
]
{ #category : #tests }
SlangBasicTranslationTest >> testParseNodeNotExpressions [
self deny: TBraceCaseNode new isExpression.
self deny: TConstantNode new isExpression.
self deny: TDefineNode new isExpression.
self deny: TGoToNode new isExpression.
self deny: TInlineNode new isExpression.
self deny: TLabeledCommentNode new isExpression.
self deny: TReturnNode new isExpression.
self deny: TVariableNode new isExpression.
self deny: TCaseStmtNode new isExpression.
]
{ #category : #'tests-blocks' }
SlangBasicTranslationTest >> testReturnBlockValueValueValue [
Expand Down Expand Up @@ -4797,12 +4774,6 @@ SlangBasicTranslationTest >> testSendNoMask [
self assert: translation equals: '(a & 1) == 0'
]
{ #category : #tests }
SlangBasicTranslationTest >> testSendNodeIsExpression [
self assert: TSendNode new isExpression.
]
{ #category : #'tests-builtins' }
SlangBasicTranslationTest >> testSendNot [
Expand Down Expand Up @@ -6165,12 +6136,6 @@ SlangBasicTranslationTest >> testSendWordSize [
self assert: translation equals: 'BytesPerWord'
]
{ #category : #tests }
SlangBasicTranslationTest >> testStatementListNodeIsExpression [
self assert: TStatementListNode new isExpression.
]
{ #category : #'tests-builtins' }
SlangBasicTranslationTest >> testStructFieldIsRenamedWithReservedWord [
"Tests if the struct field is renamed when it's a reserved word"
Expand Down Expand Up @@ -6559,12 +6524,6 @@ SlangBasicTranslationTest >> testSwitchStatementWithNoDefaultStatement [
}'
]
{ #category : #tests }
SlangBasicTranslationTest >> testSwitchStmtNodeIsExpression [
self assert: TSwitchStmtNode new isExpression.
]
{ #category : #'tests-assignment' }
SlangBasicTranslationTest >> testTranslateBlockAssignmentWithManyStatement [
Expand Down
22 changes: 20 additions & 2 deletions smalltalksrc/VMMaker-Tools/TParseNode.extension.st
Original file line number Diff line number Diff line change
Expand Up @@ -2,24 +2,42 @@ Extension { #name : #TParseNode }

{ #category : #'*VMMaker-Tools' }
TParseNode >> inspectNode [
<inspectorPresentationOrder: 912 title: 'C (AST)'>
<inspectorPresentationOrder: 912 title: 'C (Not Expr)'>

^ SpTextPresenter new
text: (String streamContents: [ : stream |
(self asCASTIn: self newCodeGeneratorForInspection) prettyPrintOn: stream ]);
yourself
]

{ #category : #'*VMMaker-Tools' }
TParseNode >> inspectNodeContext: aContext [

aContext active: self isExpression not.
aContext
title: 'C';
withoutEvaluator
]

{ #category : #'*VMMaker-Tools' }
TParseNode >> inspectNodeExpression [
<inspectorPresentationOrder: 910 title: 'C (AST Expr)'>
<inspectorPresentationOrder: 912 title: 'C (Expression)'>

^ SpTextPresenter new
text: (String streamContents: [ : stream |
(self asCASTExpressionIn: self newCodeGeneratorForInspection) prettyPrintOn: stream ]);
yourself
]

{ #category : #'*VMMaker-Tools' }
TParseNode >> inspectNodeExpressionContext: aContext [

aContext active: self isExpression.
aContext
title: 'C (Expr)';
withoutEvaluator
]

{ #category : #'*VMMaker-Tools' }
TParseNode >> inspectionTree [
<inspectorPresentationOrder: 35 title: 'Tree'>
Expand Down

0 comments on commit e41ee03

Please sign in to comment.