diff --git a/src/AST-Core/ASTVariableNode.class.st b/src/AST-Core/ASTVariableNode.class.st index 286f4fe64e1..3ecfa511e17 100644 --- a/src/AST-Core/ASTVariableNode.class.st +++ b/src/AST-Core/ASTVariableNode.class.st @@ -18,6 +18,9 @@ Class { 'variable', 'start' ], + #classVars : [ + 'UndeclaredVariableFlag' + ], #category : 'AST-Core-Nodes', #package : 'AST-Core', #tag : 'Nodes' @@ -69,6 +72,18 @@ ASTVariableNode class >> thisProcessNode [ ^ self named: #thisProcess ] +{ #category : 'accessing' } +ASTVariableNode class >> undeclaredVariableFlag [ + + ^ UndeclaredVariableFlag +] + +{ #category : 'settings - accessing' } +ASTVariableNode class >> undeclaredVariableFlag: aBoolean [ + + UndeclaredVariableFlag := aBoolean +] + { #category : 'comparing' } ASTVariableNode >> = anObject [ self == anObject ifTrue: [^true]. @@ -82,6 +97,14 @@ ASTVariableNode >> acceptVisitor: aProgramNodeVisitor [ ^ variable acceptVisitor: aProgramNodeVisitor node: self ] +{ #category : 'action' } +ASTVariableNode >> changeFlag [ + + self class undeclaredVariableFlag + ifFalse: [ self class undeclaredVariableFlag: true ] + +] + { #category : 'matching' } ASTVariableNode >> copyInContext: aDictionary [ ^ self class named: name @@ -116,7 +139,8 @@ ASTVariableNode >> initialize [ super initialize. variable := UnresolvedVariable instance. name := ''. - start := 0 + start := 0. + self class undeclaredVariableFlag: false ] { #category : 'testing' } diff --git a/src/OpalCompiler-Core/OpalCompiler.class.st b/src/OpalCompiler-Core/OpalCompiler.class.st index 70abb3ef9ad..2925b309b11 100644 --- a/src/OpalCompiler-Core/OpalCompiler.class.st +++ b/src/OpalCompiler-Core/OpalCompiler.class.st @@ -303,29 +303,30 @@ OpalCompiler >> checkNotice: aNotice [ signal. ^ true ]. - self requestor ifNotNil: [ - "A requestor is available. We are in quirks mode and are expected to do UI things." - "Reparation menu in quirks mode: + self requestor ifNotNil: [ "A requestor is available. We are in quirks mode and are expected to do UI things.""Reparation menu in quirks mode: * require a requestor (because quirks mode, and also some reparations expect a requestor) * require interactive mode (because GUI) * require method definition becase some reparation assume it's a method body" self isInteractive ifTrue: [ - aNotice reparator ifNotNil: [ :reparator | - | res | - res := reparator - requestor: requestor; - openMenu. - res ifNil: [ ^ true "reparation unneded, let AST as is" ]. - res ifFalse: [ ^ false "operation cancelled, fail" ]. - self parse: requestor text. "some reparation was done, reparse" - ^ nil ] ]. + aNotice node class undeclaredVariableFlag + ifTrue: [ ^ true ] + ifFalse: [ + aNotice reparator ifNotNil: [ :reparator | + | res | + res := reparator + requestor: requestor; + openMenu. + res ifNil: [ ^ true "reparation unneded, let AST as is" ]. + res ifFalse: [ ^ false "operation cancelled, fail" ]. + self parse: requestor text. "some reparation was done, reparse" + ^ nil ] ] ]. "Quirks mode: otherwise, push the error message to the requestor" requestor notify: aNotice messageText , ' ->' at: aNotice position in: aNotice node source. - + "Quirks mode: Then leave" ^ false ]. diff --git a/src/OpalCompiler-UI/OCCodeReparator.class.st b/src/OpalCompiler-UI/OCCodeReparator.class.st index ea5d283e0a2..e60cc2df1ec 100644 --- a/src/OpalCompiler-UI/OCCodeReparator.class.st +++ b/src/OpalCompiler-UI/OCCodeReparator.class.st @@ -146,6 +146,10 @@ OCCodeReparator >> openMenu [ labels add: 'Declare new instance variable'. actions add: [ self declareInstVar: name ] ] ifFalse: [ + labels add: 'Leave all variables undeclared'. + actions add: [ + node changeFlag. + ^ nil ]. labels add: 'Leave variable undeclared'. actions add: [ ^ nil ]. lines add: labels size. @@ -170,11 +174,13 @@ OCCodeReparator >> openMenu [ labels add: 'Cancel'. caption := 'Unknown variable: ' , name , ' please correct, or cancel:'. + choice := MorphicUIManager new chooseFrom: labels lines: lines title: caption. (actions at: choice ifAbsent: [ ^ false ]) value. + ^ true ]