The Inbox: Compiler-mtf.105.mcz

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

The Inbox: Compiler-mtf.105.mcz

commits-2
Matthew Fulmer uploaded a new version of Compiler to project The Inbox:
http://source.squeak.org/inbox/Compiler-mtf.105.mcz

==================== Summary ====================

Name: Compiler-mtf.105
Author: mtf
Time: 21 January 2010, 9:44:00.22 pm
UUID: 9dab5866-b3a2-4433-8727-d50266a7d832
Ancestors: Compiler-ul.104

Added support for positional messages and matrix expressions, from cobalt. Used in OpenGL

=============== Diff against Compiler-ul.104 ===============

Item was added:
+ ----- Method: Parser>>matrixExpression: (in category 'expression types') -----
+ matrixExpression: primary
+ "primaryExpression [ ... ] -> index node"
+ | start rcvrNode selector args msgStart msgStop |
+ self primaryExpression ifFalse:[^false].
+ (hereType == #leftBracket) ifFalse:[^primary].
+ start := self startOfNextToken.
+ rcvrNode := parseNode.
+ selector := WriteStream on: (String new: 32).
+ args := OrderedCollection new.
+ [ self advance.
+ parseNode := nil.
+ self primaryExpression ifFalse:[^self expected:'expression'].
+ args size = 0
+ ifTrue:[selector nextPutAll:'matrixAt:']
+ ifFalse:[selector nextPutAll:'at:'].
+ args add: parseNode.
+ here == #, ] whileTrue.
+ (self match: #rightBracket) ifFalse:[^self expected:']'].
+
+ msgStart := start.
+ msgStop := self endOfLastToken.
+ (primary not and:[hereType == #leftArrow]) ifTrue:[
+ selector nextPutAll:'put:'.
+ start := self startOfNextToken.
+ self advance.
+ self expression ifFalse: [^self expected: 'Expression'].
+ (parseNode isKindOf: BlockNode) ifFalse:[
+ parseNode := BlockNode new
+ arguments: #()
+ statements: (OrderedCollection with: parseNode)
+ returns: false
+ from: encoder.
+ ].
+ args add: parseNode].
+ parseNode := MessageNode new
+ receiver: rcvrNode
+ selector: selector contents asSymbol
+ arguments: args
+ precedence: 1
+ from: encoder
+ sourceRange: (msgStart to: msgStop).
+ primary ifTrue:[^true].
+ (self messagePart: 3 repeat: true)
+ ifTrue: [hereType == #semicolon ifTrue: [self cascade]].
+ ^ true!

Item was changed:
  ----- Method: Parser>>messagePart:repeat: (in category 'expression types') -----
  messagePart: level repeat: repeat
 
+ | start receiver selector args precedence words keywordStart type |
- | start receiver selector args precedence words keywordStart |
  [receiver := parseNode.
  (hereType == #keyword and: [level >= 3])
  ifTrue:
  [start := self startOfNextToken.
  selector := WriteStream on: (String new: 32).
  args := OrderedCollection new.
  words := OrderedCollection new.
  [hereType == #keyword]
  whileTrue:
  [keywordStart := self startOfNextToken + requestorOffset.
  selector nextPutAll: self advance.
  words addLast: (keywordStart to: self endOfLastToken + requestorOffset).
+ (self matrixExpression: true) ifFalse: [^self expected: 'Argument'].
- self primaryExpression ifFalse: [^self expected: 'Argument'].
  self messagePart: 2 repeat: true.
  args addLast: parseNode].
  (Symbol hasInterned: selector contents ifTrue: [ :sym | selector := sym])
  ifFalse: [ selector := self correctSelector: selector contents
  wordIntervals: words
  exprInterval: (start to: self endOfLastToken)
  ifAbort: [ ^ self fail ] ].
  precedence := 3]
  ifFalse: [((hereType == #binary or: [hereType == #verticalBar])
  and: [level >= 2])
  ifTrue:
  [start := self startOfNextToken.
+ selector := self advance asSymbol.
+ (self matrixExpression: true) ifFalse: [^self expected: 'Argument'].
- selector := self advance asOctetString asSymbol.
- self primaryExpression ifFalse: [^self expected: 'Argument'].
  self messagePart: 1 repeat: true.
  args := Array with: parseNode.
  precedence := 2]
+ ifFalse: [(hereType == #word or:[hereType == #positionalMessage])
- ifFalse: [hereType == #word
  ifTrue:
  [start := self startOfNextToken.
+ type := hereType.
  selector := self advance.
+ type == #word ifTrue:[
+ args := #().
+ ] ifFalse:[
+ args := self positionalArgs.
+ selector := selector,'/', args size printString.
+ ].
- args := #().
  words := OrderedCollection with: (start  + requestorOffset to: self endOfLastToken + requestorOffset).
  (Symbol hasInterned: selector ifTrue: [ :sym | selector := sym])
  ifFalse: [ selector := self correctSelector: selector
  wordIntervals: words
  exprInterval: (start to: self endOfLastToken)
  ifAbort: [ ^ self fail ] ].
  precedence := 1]
  ifFalse: [^args notNil]]].
  parseNode := MessageNode new
  receiver: receiver
  selector: selector
  arguments: args
  precedence: precedence
  from: encoder
  sourceRange: (start to: self endOfLastToken).
  repeat]
  whileTrue: [].
+ ^true
+ !
- ^true!

Item was added:
+ ----- Method: Parser>>positionalArgs (in category 'positional messages') -----
+ positionalArgs
+ "Parse a series of positional arguments, separated by comma."
+ | args |
+ (hereType == #rightParenthesis) ifTrue:[self advance. ^#()].
+ args := WriteStream on: (Array new: 3).
+ [
+ self positionalArgsExpression ifFalse:[^self expected: 'argument'].
+ args nextPut: parseNode.
+ hereType == #rightParenthesis ifTrue:[self advance. ^args contents].
+ here == #, ifFalse:[^self expected: 'comma'].
+ self advance.
+ ] repeat.
+ !

Item was added:
+ ----- Method: Parser>>positionalArgsExpression (in category 'positional messages') -----
+ positionalArgsExpression
+ "Just like #expression just keep track of commas"
+ (hereType == #word and: [tokenType == #leftArrow])
+ ifTrue: [^ self assignment: self variable].
+ hereType == #leftBrace
+ ifTrue: [self braceExpression]
+ ifFalse: [self primaryExpression ifFalse: [^ false]].
+ (here == #, or:[hereType == #rightParenthesis]) ifTrue:[^true].
+ ^self positionalMessagePart: 3 repeat: true!

Item was added:
+ ----- Method: Parser>>positionalMessagePart:repeat: (in category 'positional messages') -----
+ positionalMessagePart: level repeat: repeat
+ "Just like #messagePart but keep track of comma"
+ | start receiver selector args precedence words keywordStart type |
+ [receiver := parseNode.
+ (hereType == #keyword and: [level >= 3])
+ ifTrue:
+ [start := self startOfNextToken.
+ selector := WriteStream on: (String new: 32).
+ args := OrderedCollection new.
+ words := OrderedCollection new.
+ [hereType == #keyword]
+ whileTrue:
+ [keywordStart := self startOfNextToken + requestorOffset.
+ selector nextPutAll: self advance.
+ words addLast: (keywordStart to: self endOfLastToken + requestorOffset).
+ self primaryExpression ifFalse: [^self expected: 'Argument'].
+ self messagePart: 2 repeat: true.
+ args addLast: parseNode].
+ (Symbol hasInterned: selector contents ifTrue: [ :sym | selector := sym])
+ ifFalse: [ selector := self correctSelector: selector contents
+ wordIntervals: words
+ exprInterval: (start to: self endOfLastToken)
+ ifAbort: [ ^ self fail ] ].
+ precedence := 3]
+ ifFalse: [((hereType == #binary or: [hereType == #verticalBar])
+ and: [level >= 2 and:[here ~= #,]])
+ ifTrue:
+ [start := self startOfNextToken.
+ selector := self advance asSymbol.
+ self primaryExpression ifFalse: [^self expected: 'Argument'].
+ self messagePart: 1 repeat: true.
+ args := Array with: parseNode.
+ precedence := 2]
+ ifFalse: [(hereType == #word or:[hereType == #positionalMessage])
+ ifTrue:
+ [start := self startOfNextToken.
+ type := hereType.
+ selector := self advance.
+ type == #word ifTrue:[
+ args := #().
+ ] ifFalse:[
+ args := self positionalArgs.
+ selector := selector,'/', args size printString.
+ ].
+ words := OrderedCollection with: (start  + requestorOffset to: self endOfLastToken + requestorOffset).
+ (Symbol hasInterned: selector ifTrue: [ :sym | selector := sym])
+ ifFalse: [ selector := self correctSelector: selector
+ wordIntervals: words
+ exprInterval: (start to: self endOfLastToken)
+ ifAbort: [ ^ self fail ] ].
+ precedence := 1]
+ ifFalse: [^args notNil]]].
+ parseNode := MessageNode new
+ receiver: receiver
+ selector: selector
+ arguments: args
+ precedence: precedence
+ from: encoder
+ sourceRange: (start to: self endOfLastToken).
+ repeat]
+ whileTrue: [].
+ ^true!


Reply | Threaded
Open this post in threaded view
|

Re: The Inbox: Compiler-mtf.105.mcz

Igor Stasenko
>
> Added support for positional messages and matrix expressions, from cobalt. Used in OpenGL
>

Personally i would implement these syntax extensions is separate
Parser/Class subclasses
and then put them in use locally by classes which using them, by
redefining  #parserClass/compilerClass.

I don't think that everyone will be happy seeing these syntax
extensions enabled by default.
Let us keep base syntax in core classes. Compiler and Parser code
already clobbered enough up to the point to be completely thrown out
and replaced by implementation from scratch :)


--
Best regards,
Igor Stasenko AKA sig.

Reply | Threaded
Open this post in threaded view
|

Re: The Inbox: Compiler-mtf.105.mcz

Frank Shearar
On 2011/01/11 23:29, Igor Stasenko wrote:

>>
>> Added support for positional messages and matrix expressions, from cobalt. Used in OpenGL
>>
>
> Personally i would implement these syntax extensions is separate
> Parser/Class subclasses
> and then put them in use locally by classes which using them, by
> redefining  #parserClass/compilerClass.
>
> I don't think that everyone will be happy seeing these syntax
> extensions enabled by default.
> Let us keep base syntax in core classes. Compiler and Parser code
> already clobbered enough up to the point to be completely thrown out
> and replaced by implementation from scratch :)

I'd like to see the syntax for these expressions in the relevant places.
Positional messages I presume mean foo(1,2,3), but what does a matrix
expression look like?

I don't mind syntax extensions, as long as we don't go crazy with them.
Of course, like Igor points out, we can go as crazy as we like without
upsetting other parts of the system by using #parserClass/compilerClass
(like OMeta does, for instance, using a completely different language in
its methods).

frank

Reply | Threaded
Open this post in threaded view
|

Re: The Inbox: Compiler-mtf.105.mcz

Tapple Gao
On Wed, Jan 12, 2011 at 12:27:40PM +0000, Frank Shearar wrote:

> On 2011/01/11 23:29, Igor Stasenko wrote:
> >>
> >> Added support for positional messages and matrix expressions, from cobalt. Used in OpenGL
> >>
> >
> > Personally i would implement these syntax extensions is separate
> > Parser/Class subclasses
> > and then put them in use locally by classes which using them, by
> > redefining  #parserClass/compilerClass.
> >
> > I don't think that everyone will be happy seeing these syntax
> > extensions enabled by default.
> > Let us keep base syntax in core classes. Compiler and Parser code
> > already clobbered enough up to the point to be completely thrown out
> > and replaced by implementation from scratch :)
>
> I'd like to see the syntax for these expressions in the relevant places.
> Positional messages I presume mean foo(1,2,3), but what does a matrix
> expression look like?
>
> I don't mind syntax extensions, as long as we don't go crazy with them.
> Of course, like Igor points out, we can go as crazy as we like without
> upsetting other parts of the system by using #parserClass/compilerClass
> (like OMeta does, for instance, using a completely different language in
> its methods).
>
> frank
>

this is no longer needed. Andreas removed the positional
methods from OpenGL a while ago (without me noticing), and I
moved this out of the inbox.

As for matrix expressions, I have no idea either

--
Matthew Fulmer (a.k.a. Tapple)