compiling method attributes

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

compiling method attributes

S11001001
http://scompall.nocandysw.com/gst/gst-methodAttributes-comp.diff puts in
place a simple framework for compiling attributes like <cCall:...> and
<primitive:...> in STCompiler.  It also includes some fixes for
RBMethodNode>>#start, #stop and PositionableStream>>#copyFrom:to:, as
these are necessary for stream-based compilation tests.  It assumes
compiler-cascade.diff is applied.

This does not include actual compilation of any attribute tags, but it
does parse them and warn when a given type is unimplemented.

It will probably break on filing in because FileSegment can be used for
RBMethodNode's source instvar, which doesn't support copyFrom:to:.  I am
deciding whether having RBMethodNode>>#primitiveSources extract the
source with asString on each call, saving the result in the source
instvar, or something else would be the best solution.

Quick test, with Compiler loaded:

st> [UndefinedObject compile: 'float3: a arg: b arg: c
        <cCall: ''s11_float3'' returning: #int args: #(#float #float #float)>']
      on: Warning do: [:w | w messageText displayNl. w resume]!
duplicate variable name a
duplicate variable name b
duplicate variable name c
<#cCall:returning:args:> tag not yet implemented

(Wondering what's causing the "duplicate variable name" warnings.  Oh
well, some other time, more testing)

--
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
Reply | Threaded
Open this post in threaded view
|

Re: compiling method attributes

Paolo Bonzini
Stephen Compall wrote:
> http://scompall.nocandysw.com/gst/gst-methodAttributes-comp.diff puts in
> place a simple framework for compiling attributes like <cCall:...> and
> <primitive:...> in STCompiler.  It also includes some fixes for
> RBMethodNode>>#start, #stop

This one seems wrong, you need "self start + source size - 1" IMO?

  and PositionableStream>>#copyFrom:to:, as
> these are necessary for stream-based compilation tests.  It assumes
> compiler-cascade.diff is applied.

Yeah, I committed it.

> This does not include actual compilation of any attribute tags, but it
> does parse them and warn when a given type is unimplemented.

Except #primitive:, compilation of attributes is taken care by blocks
registered with the classes and returned by Class>>#pragmaHandlerFor:
(if it returns nil, the attribute has no compile-time semantics).  With
the usual bugs due to lack of good unit tests...

The blocks are evaluated passing the CompiledMethod and the attribute (a
Message), and their return value is nil or an error message.

> It will probably break on filing in because FileSegment can be used for
> RBMethodNode's source instvar, which doesn't support copyFrom:to:.

Then let's add it.  :-)

> (Wondering what's causing the "duplicate variable name" warnings.  Oh
> well, some other time, more testing)

I get them too, let's see who gets it first.

The attached patch may require some work to retrofit into your (patched)
2.3 tree, but I will backport the entire set to my arch repository later.

Thanks,

Paolo

* looking for [hidden email]--2004b/smalltalk--devo--2.2--patch-231 to compare with
* comparing to [hidden email]--2004b/smalltalk--devo--2.2--patch-231
M  compiler/RBParseNodes.st
M  compiler/RBParser.st
M  compiler/STCompiler.st
M  kernel/Class.st
M  kernel/FileSegment.st
M  kernel/PosStream.st

* modified files

--- orig/compiler/RBParseNodes.st
+++ mod/compiler/RBParseNodes.st
@@ -953,8 +953,11 @@ children
     ^self arguments copyWith: self body!
 
 primitiveSources
+    | offset |
+    offset := self start - 1.
     ^self tags
- collect: [:each | self source copyFrom: each first to: each last]!
+ collect: [:each | self source copyFrom: each first - offset
+      to: each last - offset]!
 
 isBinary
     ^(self isUnary or: [self isKeyword]) not!
@@ -991,10 +994,13 @@ source: anObject
     source := anObject!
 
 start
+    (selectorParts notNil and: [ selectorParts first start notNil ])
+ ifTrue: [ ^selectorParts first start ].
+    body start isNil ifFalse: [ ^body start ].
     ^1!
 
 stop
-    ^source size!
+    ^self start + source size - 1!
 
 tags
     ^tags isNil ifTrue: [#()] ifFalse: [tags]!


--- orig/compiler/RBParser.st
+++ mod/compiler/RBParser.st
@@ -97,6 +97,9 @@ scanner: aScanner
 addCommentsTo: aNode
     aNode comments: scanner getComments!
 
+currentToken
+    ^currentToken!
+
 nextToken
     ^nextToken isNil
  ifTrue: [nextToken := scanner next]
@@ -153,6 +156,14 @@ parseBinaryMessage
     whileTrue: [node := self parseBinaryMessageWith: node].
     ^node!
 
+parseBinaryMessageNoGreater
+    | node |
+    node := self parseUnaryMessage.
+
+    [ currentToken isBinary and: [currentToken value ~~ #>] ]
+            whileTrue: [node := self parseBinaryMessageWith: node].
+    ^node!
+
 parseBinaryMessageWith: aNode
     | binaryToken |
     binaryToken := currentToken.


--- orig/compiler/STCompiler.st
+++ mod/compiler/STCompiler.st
@@ -419,7 +419,7 @@ acceptSequenceNode: node
 !STCompiler methodsFor: 'visiting RBMethodNodes'!
 
 acceptMethodNode: node
-    | statements method |
+    | statements method attributes |
     node body addSelfReturn.
 
     depth := maxDepth := 0.
@@ -429,11 +429,12 @@ acceptMethodNode: node
     self undeclareArgumentsAndTemporaries: node.
     symTable finish.
 
+    attributes := self compileMethodAttributes: node primitiveSources.
     method := CompiledMethod
  literals: symTable literals
  numArgs: node arguments size
  numTemps: node body temporaries size
- attributes: #()
+ attributes: attributes
  bytecodes: bytecodes contents
  depth: maxDepth + node body temporaries size + node arguments size.
 
@@ -442,6 +443,12 @@ acceptMethodNode: node
  methodClass: symTable environment;
  selector: node selector.
 
+    method attributesDo: [ :ann || handler error |
+ handler := symTable environment pragmaHandlerFor: ann selector.
+ handler notNil ifTrue: [
+    error := handler value: method value: ann.
+    error notNil ifTrue: [ self compileError: error ] ] ].
+
     ^method
 ! !
 
@@ -934,4 +941,44 @@ compileStoreTemporary: number scopes: ou
  arg: number
 ! !
 
+"--------------------------------------------------------------------"
+
+!STCompiler methodsFor: 'compiling method attributes'!
+
+compileMethodAttributes: attributes
+    ^attributes asArray collect: [ :each |
+ self compileAttribute: (RBScanner on: each readStream) ]!
+
+scanTokenFrom: scanner
+    scanner atEnd
+ ifTrue: [^self compileError: 'method attributes must end with ''>'''].
+    ^scanner next!
+
+compileAttribute: scanner
+    | currentToken selectorBuilder selector arguments parser node |
+    currentToken := self scanTokenFrom: scanner.
+    (currentToken isBinary and: [currentToken value == #<])
+ ifFalse: [^self compileError:
+      'method attributes must begin with ''<'''].
+
+    selectorBuilder := WriteStream on: String new.
+    arguments := WriteStream on: Array new.
+    currentToken := self scanTokenFrom: scanner.
+    [ currentToken isBinary and: [currentToken value == #>] ] whileFalse: [
+ currentToken isKeyword
+    ifFalse: [^self compileError: 'keyword expected in method attribute'].
+ selectorBuilder nextPutAll: currentToken value.
+
+        parser := RBParser new.
+        parser errorBlock: parser errorBlock.
+        parser scanner: scanner.
+        node := parser parseBinaryMessageNoGreater.
+ node := RBSequenceNode statements: {node}.
+ arguments nextPut: (self class evaluate: node parser: parser).
+ currentToken := parser currentToken.
+    ].
+
+    selector := selectorBuilder contents asSymbol.
+    ^Message selector: selector arguments: arguments contents! !
+
 STCompiler initialize!


--- orig/kernel/Class.st
+++ mod/kernel/Class.st
@@ -496,7 +496,7 @@ registerHandler: aBlock forPragma: pragm
 pragmaHandlerFor: aSymbol
     | handler |
     pragmaHandlers isNil ifFalse: [
- handler := self pragmaHandlers at: aSymbol ifAbsent: [ nil ]
+ handler := pragmaHandlers at: aSymbol ifAbsent: [ nil ].
  handler isNil ifFalse: [ ^handler ].
     ].
     self superclass isNil ifFalse: [


--- orig/kernel/FileSegment.st
+++ mod/kernel/FileSegment.st
@@ -70,6 +70,25 @@ on: aFile startingAt: startPos for: size
 
 !FileSegment methodsFor: 'basic'!
 
+copyFrom: from to: to
+    "Answer a String containing the given subsegment of the file.  As for
+     streams, from and to are 0-based."
+    (to between: 0 and: size - 1) ifFalse: [
+        ^SystemExceptions.ArgumentOutOfRange
+    signalOn: to
+    mustBeBetween: 0
+    and: size - 1 ].
+    (from between: 0 and: to) ifFalse: [
+        from = to + 1 ifTrue: [ ^self species new ].
+        ^SystemExceptions.ArgumentOutOfRange
+    signalOn: from
+    mustBeBetween: 0
+    and: to + 1 ].
+
+    ^self withFileDo: [ :fileStream |
+ fileStream copyFrom: startPos + from to: startPos + to ]
+!
+
 asString
     "Answer a String containing the required segment of the file"
     ^self withFileDo: [ :fileStream |
@@ -139,6 +158,10 @@ hash
 
 !FileSegment methodsFor: 'private'!
 
+species
+    ^String
+!
+
 getFile
     ^file
 !



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

variable scoping (was Re: compiling method attributes)

S11001001
On Sun, 2006-12-31 at 18:19 +0100, Paolo Bonzini wrote:
> This one seems wrong, you need "self start + source size - 1" IMO?

Doh!

> Except #primitive:, compilation of attributes is taken care by blocks
> registered with the classes and returned by Class>>#pragmaHandlerFor:
> (if it returns nil, the attribute has no compile-time semantics).  With
> the usual bugs due to lack of good unit tests...
>
> The blocks are evaluated passing the CompiledMethod and the attribute (a
> Message), and their return value is nil or an error message.

Well, this is better than ... reimplementing everything ...

> > (Wondering what's causing the "duplicate variable name" warnings.  Oh
> > well, some other time, more testing)
>
> I get them too, let's see who gets it first.

http://scompall.nocandysw.com/gst/varscope-and-dupExists.diff

2006-12-31  Stephen Compall  <[hidden email]>

        * compiler/STSymTable.st: Support nested scopes, warn on
        variable shadowing, and raise compiler error if variable
        duplicated at same scope level.

The spurious 'duplicate variable name' warning was due to a boolean
inversion.

While looking for that I found something else that seemed odd:

st> [UndefinedObject compile: 'scTest |a| a := 2. [:a | a] value. ^a']
        on: Warning
        do: [:w | w messageText printNl. w resume]!
'duplicate variable name a'
Object: STFileInParser new "<-0x4c24cba0>" error: Undefined variable 'a' referenced.

I tested this in Squeak, which makes compilation fail for shadowing
names.  While this is just a change from compileWarning: to
compileError:, I decided to add variable scope-sensitivity and shadowing
instead, which seems to be what the builtin compiler does as well.

With this patch:

st> [UndefinedObject compile: 'scTest |a| a := 2. [:a | a] value. ^a']
        on: Warning
        do: [:w | w messageText printNl. w resume]!
'variable ''a'' shadows another'

> The attached patch may require some work to retrofit into your (patched)
> 2.3 tree, but I will backport the entire set to my arch repository later.

I would love to be working with arch, but...see
<[hidden email]>, or
'command-line-dependent compiler "error"' for more.

--
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
Reply | Threaded
Open this post in threaded view
|

Re: variable scoping (was Re: compiling method attributes)

Paolo Bonzini

> With this patch:
>
> st> [UndefinedObject compile: 'scTest |a| a := 2. [:a | a] value. ^a']
> on: Warning
> do: [:w | w messageText printNl. w resume]!
> 'variable ''a'' shadows another'

Applied (and mirrored!).

> I would love to be working with arch, but...see
> <[hidden email]>, or
> 'command-line-dependent compiler "error"' for more.

It should be fixed now:

http://www.mail-archive.com/help-smalltalk@.../msg00929.html

(that patch in turn had a bug -- but the arch trunk should be fine, both
2.3 and the development tree).

Paolo


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