Skip to content

Commit

Permalink
dc: add errors for unknown selectors, autocompl for symbols
Browse files Browse the repository at this point in the history
  • Loading branch information
tom95 committed Oct 7, 2023
1 parent 73943d2 commit 14f0306
Show file tree
Hide file tree
Showing 10 changed files with 288 additions and 41 deletions.
209 changes: 176 additions & 33 deletions packages/DomainCode-Parser/DCBlock.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -257,7 +257,7 @@ DCBlock class >> smalltalkCollapseBlocks [
^ {
[:x | x language = SBTSSmalltalk].
[:x | x type = #block].
[:x | x sourceString size > 400].
[:x | x sourceString size > 3000].
[:x | x installPassiveReplacement: DCCollapsed new]}
]
Expand All @@ -271,6 +271,16 @@ DCBlock class >> smalltalkCollapseBlocksOnDoubleClick [
[:x | x installPassiveReplacement: DCCollapsed new]}
]
{ #category : #'smalltalk - helpers' }
DCBlock class >> smalltalkCreateClassFor: aBlock [
aBlock sandblockEditor do: (SBStCreateClassCommand new
name: aBlock contents;
source: aBlock;
editor: aBlock sandblockEditor;
artefact: aBlock containingArtefact)
]
{ #category : #smalltalk }
DCBlock class >> smalltalkCreateNewMethod [
<query: #shortcut>
Expand Down Expand Up @@ -323,6 +333,78 @@ DCBlock class >> smalltalkDeclaration [
{#args. id. decl}]}
]
{ #category : #'smalltalk - helpers' }
DCBlock class >> smalltalkDeclareBlockLocal: aBlock [
| block decl |
decl := DCBlock new
type: #identifier;
addMorphBack: (DCText new contents: aBlock contents).
block := aBlock orAnyParent: {#block. #method}.
block childSandblocks
detect: [:b | b type = #temporaries]
ifFound: [:temporaries |
aBlock sandblockEditor do: (SBInsertCommand new
morph: decl;
container: temporaries;
index: temporaries submorphCount)]
ifNone: [ | index |
index := block children findFirst: [:s | s treeLabel = '|'].
aBlock sandblockEditor do: (SBInsertCommand new
morph: (DCBlock new
type: #temporaries;
addMorphBack: (DCText new contents: '|');
addMorphBack: decl;
addMorphBack: (DCText new contents: '|'));
index: (index = 0 ifTrue: [2] ifFalse: [index + 1]);
container: block)]
]
{ #category : #'smalltalk - helpers' }
DCBlock class >> smalltalkDeclareClassVariable: aBlock [
aBlock sandblockEditor do: (SBStDeclareClassVarCommand new
class: aBlock containingArtefact methodClass theNonMetaClass;
name: aBlock contents;
source: aBlock)
]
{ #category : #'smalltalk - helpers' }
DCBlock class >> smalltalkDeclareInstanceVariable: aBlock [
aBlock sandblockEditor do: (SBStDeclareInstVarCommand new
class: aBlock containingArtefact methodClass;
name: aBlock contents;
source: aBlock)
]
{ #category : #'smalltalk - helpers' }
DCBlock class >> smalltalkDeclareTemporary: aBlock [
| block decl |
decl := DCBlock new
type: #identifier;
addMorphBack: (DCText new contents: aBlock contents).
block := aBlock orAnyParent: {#method}.
block childSandblocks
detect: [:b | b type = #temporaries]
ifFound: [:temporaries |
aBlock sandblockEditor do: (SBInsertCommand new
morph: decl;
container: temporaries;
index: temporaries submorphCount)]
ifNone: [ | index |
index := block children findFirst: [:s | s treeLabel = '|'].
aBlock sandblockEditor do: (SBInsertCommand new
morph: (DCBlock new
type: #temporaries;
addMorphBack: (DCText new contents: '|');
addMorphBack: decl;
addMorphBack: (DCText new contents: '|'));
index: (index = 0 ifTrue: [2] ifFalse: [index + 1]);
container: block)]
]
{ #category : #smalltalk }
DCBlock class >> smalltalkFlagMarker [
<query: #always>
Expand Down Expand Up @@ -398,13 +480,11 @@ DCBlock class >> smalltalkInsertArg [
#(#First #Second #Third #Fourth #Fifith) withIndexDo: [:name :index |
x registerShortcut: #use, name, #Argument do: [
{
[:block | | id |
id := DCQuery
script: {self smalltalkMethodArguments. [:args | (args at: index) contents]}
with: block.
(block type = #identifier or: [block sandblockEditor mode = #command])
ifTrue: [block replaceWith: id, ' ']
ifFalse: [block insert: id, ' ']]}]]]}
[:block |
(DCQuery script: {self smalltalkMethodArguments. [:args | (args at: index) contents]} with: block) ifNotNil: [:id |
(block type = #identifier or: [block sandblockEditor mode = #command])
ifTrue: [block replaceWith: id, ' ']
ifFalse: [block insert: id, ' ']]]}]]]}
]
{ #category : #smalltalk }
Expand Down Expand Up @@ -448,13 +528,19 @@ DCBlock class >> smalltalkMessageSendAutoCompletion [
^ {
[:x | x isSelected].
[:x | "only autocomplete for the first message part (just after receiver)"
x siblingIndex = 2].
[:x | (DCQuery script: self smalltalkMessageSendSelector with: x) ifNotNil: [:res | res, {x}]].
[:selector :message :part |
part addSuggestions: ((self sortedSuggestions: Symbol allSymbols for: selector addAll: false max: 10) collect: [:sel |
DCSuggestionItem new
selector: sel label: 'send' source: ((sel allSatisfy: #isSpecial) ifTrue: [sel, ' __sb'] ifFalse: [
(sel includes: $:)
ifTrue: [((sel splitBy: ':') allButLast collect: [:p | p, ': __sb']) joinSeparatedBy: ' ']
ifTrue: [
((sel splitBy: ':') allButLast collectWithIndex: [:p :index |
p, ((index = 1 and: [part nextBlock ifNotNil: #isExpression ifNil: [false]])
ifTrue: [':']
ifFalse: [': __sb'])]) joinSeparatedBy: ' ']
ifFalse: [sel]]);
completionAction: [:editor |
editor selection parent
Expand Down Expand Up @@ -492,7 +578,7 @@ DCBlock class >> smalltalkMethodSelector [
ifNone: [nil]]}
]
{ #category : #nil }
{ #category : #smalltalk }
DCBlock class >> smalltalkRunTest [
<query: #save>
Expand Down Expand Up @@ -536,6 +622,25 @@ DCBlock class >> smalltalkSelector [
with: x]}
]
{ #category : #'smalltalk - helpers' }
DCBlock class >> smalltalkSelectorWithPlaceholders: aString [
(aString allSatisfy: #isSpecial) ifTrue: [^ aString, ' __sb'].
(aString includes: $:) ifFalse: [^ aString].
^ ((aString splitBy: ':') allButLast collect: [:part | part, ': __sb']) joinSeparatedBy: ' '
]
{ #category : #smalltalk }
DCBlock class >> smalltalkSymbolAutocompletion [
<query: #type>
^ {
[:x | x isSelected].
[:x | x language = SBTSSmalltalk].
[:x | x type = #symbol].
[:x | x addSuggestions: ((self sortedSuggestions: Symbol allSymbols for: x contents allButFirst addAll: false max: 10) collect: [:sel | DCSuggestionItem new selector: sel label: 'symbol' source: sel])]}
]
{ #category : #smalltalk }
DCBlock class >> smalltalkToggleBoolean [
<query: #doubleClick>
Expand All @@ -560,29 +665,57 @@ DCBlock class >> smalltalkUndeclaredVariable [
[:x |
x reportError: (SBErrorDecorator new
message: 'undeclared variable';
fixActions: (x contents first isUppercase
ifTrue: [
{
SBCodeAction
labeled: 'Declare class var'
for: x
do: [:block | self smalltalkDeclareClassVariable: block].
SBCodeAction
labeled: 'Create class ', x contents
for: x
do: [:block | self smalltalkCreateClassFor: block]}]
ifFalse: [
{
SBCodeAction
labeled: 'Declare block-local'
for: x
do: [:block | self smalltalkDeclareBlockLocal: block].
SBCodeAction
labeled: 'Declare method temporary'
for: x
do: [:block | self smalltalkDeclareTemporary block].
SBCodeAction
labeled: 'Declare instance variable'
for: x
do: [:block | self smalltalkDeclareInstanceVariable: block]}]))]}
]
{ #category : #smalltalk }
DCBlock class >> smalltalkUnknownSelector [
<query: #type>
^ {
self smalltalkMessageSendSelector.
[:selector :message | (Symbol lookup: selector) isNil].
[:selector :message |
message children second reportError: (SBErrorDecorator new
message: 'unknown message';
fixActions: {
SBCodeAction labeled: 'Declare block-local' for: x do: [:node | | block decl |
decl := DCBlock new
type: #identifier;
addMorphBack: (DCText new contents: node contents).
block := node orAnyParent: {#block. #method}.
block childSandblocks
detect: [:b | b type = #temporaries]
ifFound: [:temporaries |
node sandblockEditor do: (SBInsertCommand new
morph: decl;
container: temporaries;
index: temporaries submorphCount)]
ifNone: [ | index |
index := block children findFirst: [:s | s treeLabel = '|'].
node sandblockEditor do: (SBInsertCommand new
morph: (DCBlock new
type: #temporaries;
addMorphBack: (DCText new contents: '|');
addMorphBack: decl;
addMorphBack: (DCText new contents: '|'));
index: (index = 0 ifTrue: [2] ifFalse: [index + 1]);
container: block)]]})]}
SBCodeAction labeled: 'Create method on ...' for: message do: [:node | | method class |
class := UIManager default chooseClassOrTrait.
class ifNotNil: [
self halt.
method := DCSmalltalkMethod
newWith: (self smalltalkSelectorWithPlaceholders: selector)
in: class.
node sandblockEditor do: (SBEditorOpenMorphCommand new
morph: method;
editor: node sandblockEditor;
isUnsaved: true;
yourself)]].
SBCodeAction labeled: 'Confirm selector' for: message do: [:node | node selector asSymbol]})]}
]
{ #category : #smalltalk }
Expand Down Expand Up @@ -638,7 +771,7 @@ DCBlock class >> smalltalkWatch [
expr := message children third.
{
expr type = 'parenthesized_expression'
ifTrue: [expr children first]
ifTrue: [expr children second]
ifFalse: [expr]}]
initDo: [:w :expr | w addMorphBack: expr]]}
]
Expand Down Expand Up @@ -1213,6 +1346,14 @@ DCBlock >> isBlockBody [
^ self language ifNotNil: [:l | l blockBodyTypes includes: self type] ifNil: [false]
]
{ #category : #'as yet unclassified' }
DCBlock >> isExpression [
(self type = #ERROR and: [self submorphCount = 1]) ifTrue: [^ self firstSubmorph isExpression].
^ self language expressionTypes anySatisfy: [:type | self language instance grammar is: self type subtypeOf: type]
]
{ #category : #hierarchy }
DCBlock >> isOrHasParent: aCollectionOrSymbol [
Expand Down Expand Up @@ -1503,6 +1644,8 @@ DCBlock >> printTreeOn: aStream indent: aNumber [
{ #category : #'as yet unclassified' }
DCBlock >> queryAll: aString [
self assert: (aString includes: $@) description: 'query needs a capture (@) to be useful'.
^ Array streamContents: [:stream |
self allChildrenDo: [:block |
block isTSMorph ifTrue: [
Expand Down
38 changes: 38 additions & 0 deletions packages/DomainCode-Parser/DCEditTest.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -62,6 +62,44 @@ c.' language: SBTSSmalltalk.
c .' equals: editor childSandblocks first sourceString
]

{ #category : #'as yet unclassified' }
DCEditTest >> testSmalltalkEditMessageWithAutoCompl [

| block editor |
block := DCSmalltalkMethod newWith: 'a
a with: 3' in: self class.
editor := self editorAndWorldFor: block.
(block method queryAll: '(keyword) @') first
select;
clearInput.
self type: 'with' in: editor.
self tick.
editor handle: (SBTest keyboardEvent: Character tab).
self assert: 'a
a with: 3' equals: block method sourceString
]

{ #category : #'as yet unclassified' }
DCEditTest >> testSmalltalkFillPlaceholderWithArg [

| block editor |
block := DCSmalltalkMethod newWith: 'a: arg
a' in: self class.
editor := self editorAndWorldFor: block.
block lastDeepChild startInputAtEnd.
self type: ' with' in: editor.
self tick.
editor handle: (SBTest keyboardEvent: Character tab).
self tick.
editor handle: (SBTest keyboardEvent: $1 shift: false command: true).
self assert: 'a: arg
a with: arg' equals: block method sourceString
]

{ #category : #'as yet unclassified' }
DCEditTest >> testSmalltalkSwapStatementsWithEmpty [

Expand Down
6 changes: 6 additions & 0 deletions packages/DomainCode-Parser/DCJumpPlaceholder.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -44,6 +44,12 @@ DCJumpPlaceholder >> pasteReplace [
do: [:new :edit | self applyEdit: edit source: new cursorAt: cursorIndex + str size]]
]

{ #category : #'as yet unclassified' }
DCJumpPlaceholder >> type [

^ #identifier
]

{ #category : #'as yet unclassified' }
DCJumpPlaceholder >> valid [

Expand Down
4 changes: 3 additions & 1 deletion packages/DomainCode-Parser/DCQueryState.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -122,7 +122,9 @@ DCQueryState >> queueUpdateQueriesFor: aSymbol [
{ #category : #'as yet unclassified' }
DCQueryState >> reportError: aDecorator for: aBlock [

(newDecorators at: aBlock ifAbsentPut: [OrderedCollection new]) add: aDecorator
| errors |
errors := newDecorators at: aBlock ifAbsentPut: [OrderedCollection new].
(errors noneSatisfy: [:e | e message = aDecorator message]) ifTrue: [errors add: aDecorator]
]

{ #category : #'as yet unclassified' }
Expand Down
Loading

0 comments on commit 14f0306

Please sign in to comment.