compiler/PPCSequenceNode.st
changeset 421 7e08b31e0dae
parent 392 9b297f0d949c
child 422 116d2b2af905
equal deleted inserted replaced
420:b2f2f15cef26 421:7e08b31e0dae
    33 	self children do: [ :child | 
    33 	self children do: [ :child | 
    34 		child firstSetSuchThat: block into: aCollection openSet: aSet.
    34 		child firstSetSuchThat: block into: aCollection openSet: aSet.
    35 		child acceptsEpsilon ifFalse: [ ^ aCollection ]
    35 		child acceptsEpsilon ifFalse: [ ^ aCollection ]
    36 	].
    36 	].
    37 	^ aCollection
    37 	^ aCollection
       
    38 !
       
    39 
       
    40 firstSets: aFirstDictionary into: aSet suchThat: aBlock
       
    41 	| nullable |
       
    42 	
       
    43 	"TODO JK: aBlock is ignored by now"
       
    44 	children do: [ :node |
       
    45 		nullable := false.
       
    46 		(aFirstDictionary at: node) do: [ :each |
       
    47 			each isNullable
       
    48 				ifTrue: [ nullable := true ]
       
    49 				ifFalse: [ aSet add: each ] ].
       
    50 		nullable
       
    51 			ifFalse: [ ^ self ] ].
       
    52 	aSet add: PPCSentinelNode instance
    38 ! !
    53 ! !
    39 
    54 
    40 !PPCSequenceNode methodsFor:'compiling'!
    55 !PPCSequenceNode methodsFor:'compiling'!
    41 
    56 
    42 addGuard: compiler id: id
    57 addGuard: compiler id: id
    71 	compiler addVariable: 'memento'.			
    86 	compiler addVariable: 'memento'.			
    72 	compiler add: (compiler smartRemember: self).
    87 	compiler add: (compiler smartRemember: self).
    73 	compiler add: 'retval := Array new: ', children size asString, '.'.
    88 	compiler add: 'retval := Array new: ', children size asString, '.'.
    74 	self addGuard: compiler id: id.
    89 	self addGuard: compiler id: id.
    75 
    90 
       
    91 "	Halt if: [ self name = #qualifiedName ]."
       
    92 
    76 	(1 to: children size) do: [ :idx  | |child|
    93 	(1 to: children size) do: [ :idx  | |child|
    77 		child := children at: idx.
    94 		child := children at: idx.
    78 		compiler add: 'element := '.
    95 		compiler add: 'element := '.
    79 		compiler callOnLine: (child compileWith: compiler).
    96 		compiler callOnLine: (child compileWith: compiler).
    80 	
    97 	
    83 	].
   100 	].
    84 	compiler add: '^ retval'.
   101 	compiler add: '^ retval'.
    85  ^ compiler stopMethod.
   102  ^ compiler stopMethod.
    86 ! !
   103 ! !
    87 
   104 
       
   105 !PPCSequenceNode methodsFor:'first follow next'!
       
   106 
       
   107 followSets: aFollowDictionary firstSets: aFirstDictionary into: aSet suchThat: aBlock
       
   108 	children keysAndValuesDo: [ :index :node |
       
   109 		| follow first |
       
   110 		follow := aFollowDictionary at: node.
       
   111 		index = children size
       
   112 			ifTrue: [ follow addAll: aSet ]
       
   113 			ifFalse: [
       
   114 				(self class withAll: (children 
       
   115 					copyFrom: index + 1 to: children size))
       
   116 						firstSets: aFirstDictionary
       
   117 						into: (first := IdentitySet new)
       
   118 						suchThat: aBlock.
       
   119 				(first anySatisfy: [ :each | each isNullable ])
       
   120 					ifTrue: [ follow addAll: aSet ].
       
   121 				follow addAll: (first 
       
   122 					reject: [ :each | each isNullable ]) ] ]
       
   123 ! !
       
   124 
    88 !PPCSequenceNode methodsFor:'optimizing'!
   125 !PPCSequenceNode methodsFor:'optimizing'!
    89 
   126 
    90 asFast
   127 asFast
    91 	^ PPCTokenSequenceNode new
   128 	^ PPCTokenSequenceNode new
    92 		children: children;
   129 		children: children;
    93 		name: self name;
   130 		name: self name;
       
   131 		properties: properties;
    94 		yourself
   132 		yourself
    95 ! !
   133 ! !
    96 
   134