compiler/PPCTrimmingTokenNode.st
changeset 421 7e08b31e0dae
parent 414 0eaf09920532
child 422 116d2b2af905
equal deleted inserted replaced
420:b2f2f15cef26 421:7e08b31e0dae
    23 !
    23 !
    24 
    24 
    25 child: anObject
    25 child: anObject
    26 	
    26 	
    27 	children at: 2 put: anObject
    27 	children at: 2 put: anObject
       
    28 !
       
    29 
       
    30 compileFirstWhitespace: compiler
       
    31 	compiler call: (self whitespace compileWith: compiler).
       
    32 !
       
    33 
       
    34 compileSecondWhitespace: compiler
       
    35 	| root follow |
       
    36 	root := compiler rootNode.
       
    37 	
       
    38 	follow := self followSetWithTokens.
       
    39 	
       
    40 	(follow allSatisfy: [ :e | e isKindOf: PPCTrimmingTokenNode ]) ifTrue: [  
       
    41 		compiler add: '"second water skipped because there are only trimming tokens in the follow"'
       
    42 	] ifFalse: [  
       
    43 		compiler add: '"second water compiled because some of the follow parsers are not trimming toknes"'.
       
    44 		compiler call: (self whitespace compileWith: compiler).
       
    45 	]
    28 !
    46 !
    29 
    47 
    30 compileWhitespace: compiler
    48 compileWhitespace: compiler
    31 	compiler add: 'context atWs ifFalse: ['.
    49 	compiler add: 'context atWs ifFalse: ['.
    32 	compiler indent.
    50 	compiler indent.
    93 	aSet add: self.
   111 	aSet add: self.
    94 	
   112 	
    95 	(block value: self) ifTrue: [ aCollection add: self. ^ aCollection ].
   113 	(block value: self) ifTrue: [ aCollection add: self. ^ aCollection ].
    96 	
   114 	
    97 	^ self child firstSetSuchThat: block into: aCollection openSet: aSet.
   115 	^ self child firstSetSuchThat: block into: aCollection openSet: aSet.
       
   116 !
       
   117 
       
   118 firstSets: aFirstDictionary into: aSet suchThat: aBlock
       
   119 	"PRIVATE: Try to add additional elements to the first-set aSet of the receiver, use the incomplete aFirstDictionary."
       
   120 
       
   121 	(aBlock value: self) ifFalse: [ 
       
   122 		aSet addAll: (aFirstDictionary at: self child)
       
   123 	]
    98 ! !
   124 ! !
    99 
   125 
   100 !PPCTrimmingTokenNode methodsFor:'as yet unclassified'!
   126 !PPCTrimmingTokenNode methodsFor:'as yet unclassified'!
   101 
   127 
   102 compileWith: compiler effect: effect id: id
   128 compileWith: compiler effect: effect id: id
   104 
   130 
   105 	compiler startMethod: id.
   131 	compiler startMethod: id.
   106 	compiler addVariable: 'start'.
   132 	compiler addVariable: 'start'.
   107 	compiler addVariable: 'end'.
   133 	compiler addVariable: 'end'.
   108 	
   134 	
       
   135 	"self compileFirstWhitespace: compiler."
   109 	self compileWhitespace: compiler.
   136 	self compileWhitespace: compiler.
   110 
   137 
   111 	(compiler guards and: [(guard := PPCGuard on: self) makesSense]) ifTrue: [ 
   138 	(compiler guards and: [(guard := PPCGuard on: self) makesSense]) ifTrue: [ 
   112 		compiler add: 'context atEnd ifTrue: [ ^ self error ].'.
   139 		compiler add: 'context atEnd ifTrue: [ ^ self error ].'.
   113 		guard id: id, '_guard'.
   140 		guard id: id, '_guard'.
   118 	compiler add: 'start := context position + 1.'.
   145 	compiler add: 'start := context position + 1.'.
   119 	compiler call: (self child compileWith: compiler).
   146 	compiler call: (self child compileWith: compiler).
   120 	compiler add: 'error ifTrue: [ ^ self ].'.	
   147 	compiler add: 'error ifTrue: [ ^ self ].'.	
   121 	compiler add: 'end := context position.'.
   148 	compiler add: 'end := context position.'.
   122 	
   149 	
       
   150 "	self compileSecondWhitespace: compiler."
   123 	self compileWhitespace: compiler.
   151 	self compileWhitespace: compiler.
   124 
   152 
   125 	compiler add: '^ ', tokenClass asString, ' on: (context collection) 
   153 	compiler add: '^ ', tokenClass asString, ' on: (context collection) 
   126 																start: start  
   154 																start: start  
   127 																stop: end
   155 																stop: end
   131 
   159 
   132 prefix
   160 prefix
   133 	^ #token
   161 	^ #token
   134 ! !
   162 ! !
   135 
   163 
       
   164 !PPCTrimmingTokenNode methodsFor:'comparing'!
       
   165 
       
   166 = anotherNode
       
   167 	super = anotherNode ifFalse: [ ^ false ].
       
   168 	^ tokenClass = anotherNode tokenClass.
       
   169 !
       
   170 
       
   171 hash
       
   172 	^ super hash bitXor: tokenClass hash
       
   173 ! !
       
   174