STCompiler ignores current namespace change for var lookup in evals

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
6 messages Options
Reply | Threaded
Open this post in threaded view
|

STCompiler ignores current namespace change for var lookup in evals

S11001001
"Contents of file innamespace.st"
Smalltalk addSubspace: #S11Test!                                                
Namespace current: S11Test!                                                    
                                                                               
Object subclass: #Dummy                                                        
       instanceVariableNames: ''                                                
       classVariableNames: ''                                                  
       poolDictionaries: ''                                                    
       category: 'dummy category'                                              
!                                                                              
                                                                               
Dummy printNl!

"First shell run"
[smalltalk-jit]$ ./gst                                                          
GNU Smalltalk ready                                                            
                                                                               
st> FileStream fileIn: '/home/sirian/ide/tests/innamespace.st'!                
S11Test.Dummy                                                                  
FileStream

"Second shell run"
st> [smalltalk-jit]$ ./gst                                                      
GNU Smalltalk ready                                                            
                                                                               
st> PackageLoader fileInPackage: 'Compiler'!                                    
Loading package Parser                                                          
Loading package Compiler                                                        
PackageLoader                                                                  
st> FileStream fileIn: '/home/sirian/ide/tests/innamespace.st'!                
Object: STFileInParser new "<-0x4c5267e0>" error: Undefined variable 'Dummy' referenced.                                                                      
Smalltalk.Error(Smalltalk.Exception)>>#signal                                  
Smalltalk.Error(Smalltalk.Exception)>>#signal:                                  
STInST.STFileInParser(Smalltalk.Object)>>#error:                                
STInST.STFileInParser(STInST.RBParser)>>#parserError:                          
STInST.STCompiler>>#compileError:                                              
STInST.STCompiler>>#lookupName:                                                
STInST.STCompiler>>#acceptVariableNode:                                        
STInST.RBVariableNode>>#acceptVisitor:                                          
STInST.STCompiler>>#acceptMessageNode:                                          
STInST.RBMessageNode>>#acceptVisitor:                                          
optimized [] in STInST.STCompiler>>#compileStatements:                          
Smalltalk.OrderedCollection(Smalltalk.SequenceableCollection)>>#keysAndValuesDo:                                                                              
STInST.STCompiler>>#compileStatements:                                          
STInST.STCompiler>>#acceptSequenceNode:                                        
STInST.RBSequenceNode>>#acceptVisitor:                                          
STInST.STCompiler(STInST.RBProgramNodeVisitor)>>#visitNode:                    
STInST.STCompiler class>>#compile:asMethodOf:classified:parser:                
STInST.STFileInParser>>#evaluate:                                              
STInST.STFileInParser(STInST.RBParser)>>#parseDoits                            
STInST.STFileInParser(STInST.RBParser)>>#parseSmalltalk                        
STInST.STFileInParser class(STInST.RBParser class)>>#parseSmalltalkStream:onError:                                                                            
STInST.STFileInParser class(STInST.RBParser class)>>#parseSmalltalkStream:      
optimized [] in Smalltalk.Stream>>#fileIn                                      
Smalltalk.BlockClosure>>#ensure:                                                
Smalltalk.FileStream(Smalltalk.Stream)>>#fileIn                                
Smalltalk.FileStream class>>#fileIn:                                            
Smalltalk.UndefinedObject>>#executeStatements

"I am not sure of the proper protocol here, particularly as 'nil class
environment' is indeed 'Smalltalk' regardless of the current namespace.
However, the built-in compiler's behavior seems better here."

--
Stephen Compall
http://scompall.nocandysw.com/blog
##smalltalk,#gnu-smalltalk on Freenode IRC

_______________________________________________
help-smalltalk mailing list
[hidden email]
http://lists.gnu.org/mailman/listinfo/help-smalltalk

signature.asc (196 bytes) Download Attachment
Reply | Threaded
Open this post in threaded view
|

Re: STCompiler ignores current namespace change for var lookup in evals

Paolo Bonzini-3
(sorry for breaking the thread)

> "I am not sure of the proper protocol here, particularly as 'nil class
> environment' is indeed 'Smalltalk' regardless of the current namespace.
> However, the built-in compiler's behavior seems better here."

It is.  The attached patch should fix the problem, but I have not
tested it, nor applied it yet.  If you get back to me before 2.3, I
will include it (very safe, applies only to compiler), but otherwise I
won't.

Paolo

_______________________________________________
help-smalltalk mailing list
[hidden email]
http://lists.gnu.org/mailman/listinfo/help-smalltalk

compiler-fix-eval-namespace.patch (722 bytes) Download Attachment
Reply | Threaded
Open this post in threaded view
|

Re: STCompiler ignores current namespace change for var lookup in evals

S11001001
Paolo Bonzini wrote:
> It is.  The attached patch should fix the problem, but I have not
> tested it, nor applied it yet.  If you get back to me before 2.3, I
> will include it (very safe, applies only to compiler), but otherwise I
> won't.

While this fixes STCompiler>>#evaluate:parser:,
STFileInParser>>#evaluate: doesn't use that method, and can't unless you
want to expand the protocol of Behavior>>#compilerClass's answer.  OTOH,
I think it would be less than ideal to add the current namespace to the
symbol table in compile:asMethodOf:classified:parser:.

Using STCompiler>>#evaluate:parser: in the valueWithUnwind'd block would
also subtly change STFileInParser>>#evaluate:'s meaning -- because
compiler errors wouldn't cause exceptions that could escape the
evaluate: context.

(tested; same as before)

--
Stephen Compall
http://scompall.nocandysw.com/blog
##smalltalk,#gnu-smalltalk on Freenode IRC


_______________________________________________
help-smalltalk mailing list
[hidden email]
http://lists.gnu.org/mailman/listinfo/help-smalltalk
Reply | Threaded
Open this post in threaded view
|

Re: STCompiler ignores current namespace change for var lookup in evals

S11001001
Stephen Compall wrote:
> Using STCompiler>>#evaluate:parser: in the valueWithUnwind'd block would
> also subtly change STFileInParser>>#evaluate:'s meaning -- because
> compiler errors wouldn't cause exceptions that could escape the
> evaluate: context.

Here's a STCompiler class>>#compile:asMethodOf:classified:parser: (needs
also my previous change to compile:for:classified:parser:) that lets me
load the previously mentioned 'innamespace.st':

compile: methodNode asMethodOf: aBehavior classified: aString parser:
aParser
     | compiler |

     compiler := self new.

     compiler class: aBehavior parser: aParser.

 

     "Usually, when making UndefinedObject methods, you want the

     current namespace to be specially added"

     aBehavior == UndefinedObject

         ifTrue: [compiler addPool: Namespace current].

 

     ^(compiler visitNode: methodNode)

         methodCategory: aString;

         yourself

This version has the advantage of being inconsistent with desired
practice (when compiling methods truly intended for installation within
UndefinedObject), but more consistent than the failure I reported to
start this thread.

However, I am not sure that I wouldn't prefer the semantic change of
putting compilation in the valueWithUnwind (using STCompiler
class>>#evaluate:parser:) or removing it entirely.

Why shouldn't an exception during evaluation by the FileInParser (which
only happens in RBParser>>#parseDoits AFAICS) halt parsing/loading of a
stream without further intervention/resetting by clients of the
FileInParser?

--
Stephen Compall
http://scompall.nocandysw.com/blog
##smalltalk,#gnu-smalltalk on Freenode IRC


_______________________________________________
help-smalltalk mailing list
[hidden email]
http://lists.gnu.org/mailman/listinfo/help-smalltalk
Reply | Threaded
Open this post in threaded view
|

Re: Re: STCompiler ignores current namespace change for var lookup in evals

Paolo Bonzini

> However, I am not sure that I wouldn't prefer the semantic change of
> putting compilation in the valueWithUnwind (using STCompiler
> class>>#evaluate:parser:) or removing it entirely.
>
> Why shouldn't an exception during evaluation by the FileInParser (which
> only happens in RBParser>>#parseDoits AFAICS) halt parsing/loading of a
> stream without further intervention/resetting by clients of the
> FileInParser?

This is in fact inconsistent with the C parser; chunks are supposed to
be completely independent, so it's true that both compilation and
evaluation should be in the valueWithUnwind (using #evaluate:parser:).
However, this would make it a little harder to spot bugs in the
Smalltalk compiler and parser (as this would not stop the evaluation).
For example, I just found out that the Smalltalk parser does not parse _
as assignment the same way the C parser does.

I'm committing the attached patch.  It's pretty safe, so we don't need a
further RC before 2.3.  This will in fact be the last change before 2.3,
I might even make the big release later today if I have time.  :-)

Paolo

2006-12-05  Paolo Bonzini  <[hidden email]>

        * compiler/STCompiler.st: Pass current environment in evaluate:parser:,
        add #compile:asMethodOf:classified:parser:environment: and don't inline
        its functionality elsewhere.
        * compiler/StartCompiler.st: Pass current environment when compiling
        doits.

--- orig/compiler/STCompiler.st
+++ mod/compiler/STCompiler.st
@@ -115,9 +115,9 @@ evaluate: aSequenceNode parser: aParser
  source: nil;
  yourself.
 
-    cm := self new
- class: UndefinedObject parser: aParser;
- visitNode: methodNode.
+    cm := self
+ compile: methodNode asMethodOf: UndefinedObject classified: nil
+ parser: aParser environment: Namespace current.
 
     ^nil perform: cm
 ! !
@@ -125,27 +125,34 @@ evaluate: aSequenceNode parser: aParser
 !STCompiler class methodsFor: 'compilation'!
 
 compile: methodNode for: aBehavior classified: aString parser: aParser
-    | cm |
-    cm := self new
- class: aBehavior parser: aParser;
- visitNode: methodNode.
-
-    cm methodCategory: aString.
-
     ^aBehavior
  addSelector: methodNode selector
- withMethod: cm
+ withMethod: (self
+ compile: methodNode
+ asMethodOf: aBehavior
+ classified: aString
+ parser: aParser)
 !
 
 compile: methodNode asMethodOf: aBehavior classified: aString parser: aParser
-    | cm |
-    cm := self new
- class: aBehavior parser: aParser;
- visitNode: methodNode.
-
-    cm methodCategory: aString.
-
-    ^cm
+    ^self
+ compile: methodNode
+ asMethodOf: aBehavior
+ classified: aString
+ parser: aParser
+ environment: nil!
+
+compile: methodNode asMethodOf: aBehavior classified: aString parser: aParser
+    environment: aNamespace
+
+    | compiler |
+    compiler := self new.
+    compiler class: aBehavior parser: aParser.
+    aNamespace isNil ifFalse: [ compiler addPool: aNamespace ].
+
+    ^(compiler visitNode: methodNode)
+ methodCategory: aString;
+ yourself
 ! !
 
 !STCompiler methodsFor: 'private'!
@@ -168,6 +175,10 @@ addLiteral: literal
     ^symTable addLiteral: literal
 !
 
+addPool: aNamespace
+    ^symTable addPool: aNamespace
+!
+
 bytecodesFor: aBlockNode
     ^self bytecodesFor: aBlockNode atEndDo: []
 !
@@ -708,7 +719,7 @@ compileSendToSuper: aNode
     aNode arguments do: [ :each | each acceptVisitor: self ].
     self pushLiteral: destClass superclass.
     VMSpecialSelectors at: aNode selector ifPresent: [ :idx |
- self compileByte: SendSuperImmediate arg: idx.
+ self compileByte: SendImmediateSuper arg: idx.
  ^aNode
     ].
 


--- orig/compiler/StartCompiler.st
+++ mod/compiler/StartCompiler.st
@@ -116,7 +116,8 @@ evaluate: node
  compile: node
  asMethodOf: evalFor class
  classified: nil
- parser: self.
+ parser: self
+ environment: Namespace current.
 
     [ lastResult := evalFor perform: method ] valueWithUnwind.
     ^curClass notNil




_______________________________________________
help-smalltalk mailing list
[hidden email]
http://lists.gnu.org/mailman/listinfo/help-smalltalk
Reply | Threaded
Open this post in threaded view
|

Re: STCompiler ignores current namespace change for var lookup in evals

S11001001
On Tue, 2006-12-05 at 09:51 +0100, Paolo Bonzini wrote:
> I'm committing the attached patch.

Works great; thanks.  Thanks also for including the "don't inline its
functionality elsewhere" parts; makes my code cleaner.

--
Stephen Compall
http://scompall.nocandysw.com/blog

_______________________________________________
help-smalltalk mailing list
[hidden email]
http://lists.gnu.org/mailman/listinfo/help-smalltalk

signature.asc (196 bytes) Download Attachment