The Trunk: Compiler-nice.266.mcz

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

The Trunk: Compiler-nice.266.mcz

commits-2
Nicolas Cellier uploaded a new version of Compiler to project The Trunk:
http://source.squeak.org/trunk/Compiler-nice.266.mcz

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

Name: Compiler-nice.266
Author: nice
Time: 6 September 2013, 1:53:58.652 am
UUID: c5010a51-42a8-43cb-8fbe-809ec7f24da8
Ancestors: Compiler-fbs.265

Do not convert punctuation characters ( [ { } ] ) ; . ^ | asSymbol, just let the token be the Character, except in two cases:
- inside a literal array
- after a literal quote if prefAllowUnicharSymbol

=============== Diff against Compiler-fbs.265 ===============

Item was changed:
  ----- Method: Parser>>externalFunctionDeclaration (in category 'primitives') -----
  externalFunctionDeclaration
  "Parse the function declaration for a call to an external library."
  | descriptorClass callType modifier retType externalName args argType module fn |
  descriptorClass := cue environment
  valueOf: #ExternalFunction
  ifAbsent: [^ false].
  callType := descriptorClass callingConventionFor: here.
  callType == nil ifTrue:[^false].
  [modifier := descriptorClass callingConventionModifierFor: token.
  modifier notNil] whileTrue:
  [self advance.
  callType := callType bitOr: modifier].
  "Parse return type"
  self advance.
  retType := self externalType: descriptorClass.
  retType == nil ifTrue:[^self expected:'return type'].
  "Parse function name or index"
  externalName := here.
  (self match: #string)
  ifTrue:[externalName := externalName asSymbol]
  ifFalse:[(self match:#number) ifFalse:[^self expected:'function name or index']].
+ (self match: #leftParenthesis) ifFalse:[^self expected:'argument list'].
- (self matchToken: #'(') ifFalse:[^self expected:'argument list'].
  args := WriteStream on: Array new.
+ [self match: #rightParenthesis] whileFalse:[
- [here == #')'] whileFalse:[
  argType := self externalType: descriptorClass.
  argType == nil ifTrue:[^self expected:'argument'].
+ argType isVoid & argType isPointerType not ifFalse:[args nextPut: argType]].
- argType isVoid & argType isPointerType not ifFalse:[args nextPut: argType].
- ].
- (self matchToken: #')') ifFalse:[^self expected:')'].
  (self matchToken: 'module:') ifTrue:[
  module := here.
  (self match: #string) ifFalse:[^self expected: 'String'].
  module := module asSymbol].
  Smalltalk at: #ExternalLibraryFunction ifPresent:[:xfn|
  fn := xfn name: externalName
  module: module
  callType: callType
  returnType: retType
  argumentTypes: args contents.
+ self allocateLiteral: fn].
- self allocateLiteral: fn.
- ].
  (self matchToken: 'error:')
  ifTrue:
  [| errorCodeVariable |
  errorCodeVariable := here.
  (hereType == #string
  or: [hereType == #word]) ifFalse:[^self expected: 'error code (a variable or string)'].
  self advance.
  self addPragma: (Pragma keyword: #primitive:error: arguments: (Array with: 120 with: errorCodeVariable)).
  fn ifNotNil: [fn setErrorCodeName: errorCodeVariable]]
  ifFalse:
  [self addPragma: (Pragma keyword: #primitive: arguments: #(120))].
+ ^true!
- ^true
- !

Item was changed:
  ----- Method: Parser>>transformAVerticalBarIntoABinarySelector (in category 'scanning') -----
  transformAVerticalBarIntoABinarySelector
  "Transform a vertical bar into a binary selector.
  Eventually aggregate a serie of immediately following vertical bars and a binary selector.
  Note that this aggregation cannot occur at scan time, because a pair of vertical bars can be encountered in two valid constructs:
  - either as an empty temporaries specification,
  - or as a local temporaries specification in a block of arity > 0"
  here := '|'.
  hereType := #binary.
  [tokenType == #verticalBar and: [hereMark + here size = mark]]
  whileTrue: [
+ here := here , '|'.
- here := here , $|.
  hereEnd := hereEnd + 1.
  self scanToken].
  (tokenType == #binary and: [hereMark + here size = mark])
  ifTrue: [
  here := here asString , token.
  hereType := #binary.
  hereEnd := hereEnd + token size.
  self scanToken].!

Item was changed:
  ----- Method: Scanner>>scanLitVec (in category 'expression types') -----
  scanLitVec
  | s |
  s := WriteStream on: (Array new: 16).
  [tokenType == #rightParenthesis or: [tokenType == #doIt]] whileFalse:
  [tokenType == #leftParenthesis
  ifTrue:
  [self scanToken; scanLitVec]
  ifFalse:
  [(tokenType == #word or: [tokenType == #keyword or: [tokenType == #colon]])
  ifTrue:
  [self scanLitWord.
  token == #true ifTrue: [token := true].
  token == #false ifTrue: [token := false].
  token == #nil ifTrue: [token := nil]]
  ifFalse:
+ [(token isCharacter and: [tokenType ~~ #character])
+ ifTrue: [token := token asSymbol]
+ ifFalse: [(token == #-
+  and: [(self typeTableAt: hereChar) == #xDigit]) ifTrue:
+ [self scanToken.
+ token := token negated]]]].
- [(token == #-
-  and: [(self typeTableAt: hereChar) == #xDigit]) ifTrue:
- [self scanToken.
- token := token negated]]].
  s nextPut: token.
  self scanToken].
  token := s contents!

Item was changed:
  ----- Method: Scanner>>scanToken (in category 'expression types') -----
  scanToken
 
  [(tokenType := self typeTableAt: hereChar) == #xDelimiter]
  whileTrue: [self step].  "Skip delimiters fast, there almost always is one."
  mark := aheadChar == DoItCharacter
  ifTrue: [hereChar == DoItCharacter
  ifTrue: [source position + 1]
  ifFalse: [source position]]
  ifFalse: [source position - 1].
  (tokenType at: 1) == $x "x as first letter"
  ifTrue: [self perform: tokenType "means perform to compute token & type"]
+ ifFalse: [token := self step "else just unique the first char"].
- ifFalse: [token := self step asSymbol "else just unique the first char"].
  ^token!

Item was changed:
  ----- Method: Scanner>>xLitQuote (in category 'multi-character scans') -----
  xLitQuote
  "Symbols and vectors: #(1 (4 5) 2 3) #ifTrue:ifFalse: #'abc'."
  | start |
  start := mark.
  self step. "litQuote"
  self scanToken.
  tokenType == #leftParenthesis
  ifTrue: [self scanToken; scanLitVec.
  mark := start + 1.
  tokenType == #doIt
  ifTrue: [self offEnd: 'Unmatched parenthesis']]
  ifFalse: [tokenType == #leftBracket
  ifTrue: [self scanToken; scanLitByteVec.
  mark := start + 1.
  tokenType == #doIt
  ifTrue: [self offEnd: 'Unmatched bracket']]
  ifFalse: [(tokenType == #word or: [tokenType == #keyword or: [tokenType == #colon]])
  ifTrue: [self scanLitWord]
+ ifFalse: [(tokenType == #string or: [ tokenType == #verticalBar ])
- ifFalse: [tokenType == #string
  ifTrue: [token := token asSymbol]
+ ifFalse: [tokenType == #binary
+ ifFalse: [(token isCharacter and: [tokenType ~~ #character and: [self class prefAllowUnicharSymbol]])
+ ifTrue: [token := token asSymbol]
- ifFalse: [(tokenType == #binary or: [ tokenType == #verticalBar ])
- ifFalse: [(token isCharacter and: [self class prefAllowUnicharSymbol])
- ifTrue:
- [tokenType := Symbol.
- token := Symbol with: token]
  ifFalse: [self notify: 'Invalid literal character' at: start + 1]]]]]].
  mark := start.
  tokenType := #literal
 
  "#(Pen)
  #Pen
  #'Pen'
- ##Pen
- ###Pen
  "!