⭐ 欢迎来到虫虫下载站! | 📦 资源下载 📁 资源专辑 ℹ️ 关于我们
⭐ 虫虫下载站

📄 compilers-parsers.st

📁 編譯器的語法產生器
💻 ST
📖 第 1 页 / 共 3 页
字号:
	"notify a problem beyond 'here' (in lookAhead token). Don't be offEnded!!"

	^self notify: aString at: scanner mark + correctionDelta! !

!RecursiveDescentParser methodsFor: 'private'!

init: sourceString notifying: req failBlock: aBlock 

	requestor := req.
	failBlock := aBlock.
	correctionDelta := 0.
	scanner := self preferredScannerClass new.
	scanner scan: sourceString notifying: self.
	prevMark := hereMark := scanner mark.
	self advance!

initEncoder

	self subclassResponsibility!

initEncoder: anEncoder 

	encoder := anEncoder!

preferredScannerClass

	^self class preferredScannerClass! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

RecursiveDescentParser class
	instanceVariableNames: ''!


!RecursiveDescentParser class methodsFor: 'accessing'!

preferredScannerClass
	"Answer with a scanner class which is appropiate for scanning tokens used 
	by this compiler class. Should be overwritten by subclasses."

	self subclassResponsibility! !

TableDrivenParser subclass: #LL1Parser
	instanceVariableNames: 'startSymbol '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Compilers-Parsers'!
LL1Parser comment:
'=================================================
    Copyright (c) 1992 by Justin O. Graver.
    All rights reserved (with exceptions).
    For complete information evaluate "Object tgenCopyright."
=================================================

I am an LL(1) parser.

Instance Variables:
	parseTable*	<LL1ParserTable> - basic parsing mechanism.
	startSymbol  <Symbol> - my grammars start symbol.

* inherited from AbstractParser'!


!LL1Parser methodsFor: 'state accessing'!

startSymbol

	^startSymbol!

startSymbol: argument 

	startSymbol := argument! !

!LL1Parser methodsFor: 'private'!

epsilon
	"Answer an object used to represent the empty string (epsilon)."

	^'<epsilon>'!

myStartSymbol

	^self class startSymbol!

parserErrorSignal

	^LLParserTable noTransitionSignal! !

!LL1Parser methodsFor: 'exception handling'!

raiseExceptionExpectedToken: aString 

	self raiseNoTransitionExceptionErrorString: 'expecting ' , aString!

raiseExceptionUnparsedTokens

	self raiseNoTransitionExceptionErrorString: 'unparsed tokens remaining in input'!

raiseNoTransitionExceptionErrorString: aString 

	self parserErrorSignal raiseErrorString: aString! !

!LL1Parser methodsFor: 'parsing'!

parse

	| stack prod |
	stack := Stack new.
	stack push: self startSymbol.
	[stack isEmpty]
		whileFalse: [stack top isTerminal
				ifTrue: [stack top = self nextToken
						ifTrue: 
							[stack pop.
							self scanToken]
						ifFalse: [self raiseExceptionExpectedToken: stack top symbol]]
				ifFalse: 
					[prod := self productionAtNonterminal: stack pop andTerminal: self nextToken.
					prod rightHandSide reverseDo: [:sym | stack push: sym]]].
	self nextToken = self endOfInput ifFalse: [self raiseExceptionUnparsedTokens]!

parseForDerivationTreeAlternative
	"Derivation trees can be build efficiently during a top-down parse. 
	This method implements this option (see parseForDerivationTree)."

	| stack prod root parent node |
	stack := Stack new.
	root := DerivationTreeNode symbol: self startSymbol.
	stack push: root.
	[stack isEmpty]
		whileFalse: [stack top isTerminal
				ifTrue: [stack top symbol = self nextToken
						ifTrue: 
							[stack pop.
							self scanToken]
						ifFalse: [self raiseExceptionExpectedToken: stack top symbol]]
				ifFalse: 
					[prod := self productionAtNonterminal: stack top symbol andTerminal: self nextToken.
					parent := stack pop.
					prod rightHandSide isEmpty
						ifTrue: 
							[node := DerivationTreeNode symbol: self epsilon.
							parent addChild: node]
						ifFalse: [prod rightHandSide
								reverseDo: 
									[:sym | 
									node := DerivationTreeNode symbol: sym.
									parent addFirstChild: node.
									stack push: node]]]].
	self nextToken = self endOfInput ifFalse: [self raiseExceptionUnparsedTokens].
	^root!

parseWithTreeBuilder: parseTreeBuilder 
	"Rather than building the tree top-down during the parse, it's easier to save 
	the productions on a stack and build the tree bottom-up after parsing."

	| stack productionStack |
	productionStack := Stack new.
	stack := Stack new.
	stack push: self startSymbol.
	[stack isEmpty]
		whileFalse: [stack top isTerminal
				ifTrue: 
					["cancel matching tokens"
					stack top = self nextToken
						ifTrue: 
							[stack pop.
							self scanToken]
						ifFalse: [self raiseExceptionExpectedToken: stack top]]
				ifFalse: 
					["expand nonterminal"
					productionStack push: (self productionAtNonterminal: stack pop andTerminal: self nextToken)
							@ self nextTokenValue.
					productionStack top x rightHandSide reverseDo: [:sym | stack push: sym]]].
	self nextToken = self endOfInput ifFalse: [self raiseExceptionUnparsedTokens].
	productionStack do: 
		[:prod | 
		self prevToken: prod y.
		parseTreeBuilder processProduction: prod x forParser: self].
	^parseTreeBuilder result!

productionAtNonterminal: nont andTerminal: term
	^self parseTable productionAtNonterminal: nont andTerminal: term!

traceParse

	| stack prod |
	self
		 cr;
		 cr;
		 showCR: 'LL Parser trace of:  ' , self scanner contents;
		 cr.
	stack := OrderedCollection new.
	stack addFirst: self startSymbol.
	[stack isEmpty]
		whileFalse: [stack first isTerminal
				ifTrue: [stack first = self nextToken
						ifTrue: 
							[self showCR: 'cancel ''' , stack first asString, ''' from input'.
							stack removeFirst.
							self scanToken]
						ifFalse: [self error: 'raise exception:  top of stack = ''' , stack first asString , ''' next token = ''' , self nextToken asString, '''']]
				ifFalse: 
					[prod := self productionAtNonterminal: stack first andTerminal: self nextToken.
					self showCR: 'apply production ' , prod printString.
					stack removeFirst.
					prod rightHandSide reverseDo: [:sym | stack addFirst: sym]]].
	self nextToken = self endOfInput ifFalse: [self raiseExceptionUnparsedTokens]! !

!LL1Parser methodsFor: 'testing'!

performsLeftmostDerivation

	^true! !

!LL1Parser methodsFor: 'initialization'!

init

	super init.
	self startSymbol: self myStartSymbol! !

!LL1Parser methodsFor: 'scanner/parser generation'!

classInitializationMethodTextForClassNamed: name spec: grammarSpec

 | ws |
 ws := self newStreamForMethodRendering.
 ws nextPutAll: 'initialize "' , name , ' initialize  " '.
 ws cr.
 ws nextPutAll: ' "  ' , grammarSpec , ' " '.
 ws nextPut: $".
 grammarSpec do:
  [:ch |
  "double embedded double-quote characters"
  ws nextPut: ch.
  ch = $" ifTrue: [ws nextPut: $"]].
 ws nextPut: $".
 ws nextPutAll: ' |  llParserTable table gp | '.
 ws nextPutAll: self parseTable buildParseTable.
 ws nextPutAll: ' self parseTable:  llParserTable  . '.
 ws nextPutAll: ' self startSymbol:   '.
 self startSymbol printOn: ws.
 ^ws contents! !

!LL1Parser methodsFor: 'converting'!

fastParser

	^OptimizedLL1Parser buildFrom: self! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

LL1Parser class
	instanceVariableNames: 'startSymbol '!


!LL1Parser class methodsFor: 'instance creation'!

parseTable: table startSymbol: sym 

	| newParser |
	newParser := self new.
	newParser parseTable: table.
	newParser startSymbol: sym.
	^newParser! !

!LL1Parser class methodsFor: 'state accessing'!

startSymbol

	^startSymbol!

startSymbol: argument 

	startSymbol := argument! !

LL1Parser subclass: #OptimizedLL1Parser
	instanceVariableNames: 'nonterminals terminals '
	classVariableNames: 'NoTransitionSignal '
	poolDictionaries: ''
	category: 'Compilers-Parsers'!
OptimizedLL1Parser comment:
'=================================================
    Copyright (c) 1992 by Justin O. Graver.
    All rights reserved (with exceptions).
    For complete information evaluate "Object tgenCopyright."
=================================================

I am an LL(1) parser represented efficiently in Array table format.

Instance variables:
	tokenTypeTable <Array of: String>	- the integer mapping for terminals and nonterminals'!


!OptimizedLL1Parser methodsFor: 'exception handling'!

endOfInputErrorString

	^'end of input encountered'!

parserErrorSignal

	^self class noTransitionSignal!

raiseNoTransitionExceptionErrorString: aString 

	self parserErrorSignal raiseErrorString: aString!

scannerErrorSignal

	^OptimizedScanner noTransitionSignal!

standardErrorString

	^'unexpected token encountered:  '! !

!OptimizedLL1Parser methodsFor: 'private'!

parseError

	self raiseNoTransitionExceptionErrorString: (scanner tokenType == self endOfInputToken
			ifTrue: [self endOfInputErrorString]
			ifFalse: [self standardErrorString , '''' , scanner tokenType printString , ''''])! !

!OptimizedLL1Parser methodsFor: 'accessing'!

myNonterminals

	^self class nonterminals!

myTerminals

	^self class terminals!

myTokenTypeTable

	^self class tokenTypeTable! !

!OptimizedLL1Parser methodsFor: 'initialization'!

init

	super init.
	self nonterminals: self myNonterminals.
	self terminals: self myTerminals! !

!OptimizedLL1Parser methodsFor: 'parsing'!

productionAtNonterminal: nont andTerminal: term 
	| nontIndex termIndex prod |
	nontIndex := self nonterminals indexOf: nont.
	termIndex := self terminals indexOf: term.
	^(prod := (self parseTable at: nontIndex)
				at: termIndex) isNil
		ifTrue: [self raiseNoTransitionExceptionErrorString: (term = self endOfInputToken
					ifTrue: [self endOfInputErrorString]
					ifFalse: [self standardErrorString , '''' , term printString , ''''])]
		ifFalse: [prod]! !

!OptimizedLL1Parser methodsFor: 'reconstructing'!

mapProductionToInteger
	"Answer an Array of all grammar symbols - nonterminals, terminals, 
	and translation symbols."

	| transSyms |
	transSyms := Set new.
	parseTable do: [:row | row do: [:ea | ea isGrammarProduction ifTrue: [ea hasTranslation ifTrue: [transSyms add: ea translationSymbol]]]].
	^self nonterminals , self terminals , transSyms asOrderedCollection asArray!

reconstructOn: aStream 

	| prodTable n |
	prodTable := self mapProductionToInteger.
	aStream nextPutAll: 'prodTable := '.
	prodTable reconstructOn: aStream.
	aStream
		period;
		crtab;
		nextPutAll: 'self nonterminals:  (prodTable copyFrom: 1 to:  ';
		nextPutAll: (n := self nonterminals size) printString;
		nextPutAll: ').';
		crtab;
		nextPutAll: 'self terminals:  (prodTable copyFrom: ';
		nextPutAll: (n + 1) printString;
		nextPutAll: ' to: ';
		nextPutAll: (self terminals size + n) printString;
		nextPutAll: ').';
		crtab;
		nextPutAll: 'table := '.
	self parseTable reconstructOn: aStream using: prodTable.
	aStream
		period;
		crtab;
		nextPutAll: 'self constructParseTable: table  with: prodTable.';
		crtab;
		nextPutAll: 'self startSymbol: '.
	self startSymbol printOn: aStream! !

!OptimizedLL1Parser methodsFor: 'scanner/parser generation'!

classInitializationMethodTextForClassNamed: name spec: grammarSpec
 | ws |
 ws := self newStreamForMethodRendering.
 ws
  nextPutAll: 'initialize';
  crtab;
  nextPut: $";
  nextPutAll: name;
  nextPutAll: ' initialize"';
  crtab;
  nextPut: $".
 grammarSpec do:
  [:ch |
  "double embedded double-quote characters"
  ws nextPut: ch.
  ch = $" ifTrue: [ws nextPut: $"]].
 ws
  nextPut: $";
  cr;
  crtab;
  nextPutAll: '| table prodTable |';
  crtab.
 self reconstructOn: ws.
 ^ws contents! !

!OptimizedLL1Parser methodsFor: 'converting'!

changeToObjectTable: llParseTable 

	| terms objectTable |
	self nonterminals: llParseTable keys asOrderedCollection asArray.
	terms := Set new.
	llParseTable do: [:row | row
			associationsDo: 
				[:assoc | 
				terms add: assoc key.
				assoc value rightHandSide do: [:sym | sym isTerminal ifTrue: [terms add: sym]]]].
	self terminals: terms asOrderedCollection asArray.
	objectTable := Array new: self nonterminals size.
	^self convert: llParseTable to: objectTable!

convert: llParseTable to: objectTable 
	| nonterms terms row |
	nonterms := self nonterminals.
	terms := self terminals.
	llParseTable
		associationsDo: 
			[:assoc1 | 
			row := Array new: terms size.
			objectTable at: (nonterms indexOf: assoc1 key)
				put: row.
			assoc1 value associationsDo: [:assoc2 | row at: (terms indexOf: assoc2 key)
					put: assoc2 value]].
	^objectTable!

convertToTable: ll1Parser 

	self scanner: ll1Parser scanner fastScanner.
	self parseTable: (self changeToObjectTable: ll1Parser parseTable).
	self treeBuilder:  ll1Parser treeBuilder.
	self startSymbol: ll1Parser startSymbol! !

!OptimizedLL1Parser methodsFor: 'state accessing'!

nonterminals
	^nonterminals!

nonterminals: arg
	nonterminals := arg!

terminals
	^terminals!

terminals: arg
	terminals := arg! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

OptimizedLL1Parser class
	instanceVariableNames: 'nonterminals terminals '!


!OptimizedLL1Parser class methodsFor: 'class initialization'!

initialize
	"OptimizedLL1Parser initialize"

	self noTransitionSignal: (Signal new nameClass: self message: #noTransitionSymbol)! !

!OptimizedLL1Parser class methodsFor: 'instance creation'!

buildFrom: ll1Parser

	^self new convertToTable: ll1Parser! !

!OptimizedLL1Parser class methodsFor: 'state accessing'!

nonterminals 
	^nonterminals!

nonterminals: arg
	nonterminals := arg!

noTransitionSignal

	^NoTransitionSignal!

noTransitionSignal: arg

	NoTransitionSignal := arg!

terminals
	^terminals!

terminals: arg
	terminals := arg! !

!OptimizedLL1Parser class methodsFor: 'reconstructing'!

constructGrammarProduction: arg with: prodTable 

	| rhs |
	(arg at: 2) isEmpty
		ifTrue: [rhs := OrderedCollection new]
		ifFalse: 
			[rhs := OrderedCollection new.
			(arg at: 2)
				do: [:ea | rhs addLast: (prodTable at: ea)]].
	^GrammarProduction
		leftHandSide: (prodTable at: (arg at: 1))
		rightHandSide: rhs!

constructParseTable: table with: prodTable 

	| ea row |
	parseTable := Array new: table size.
	1 to: table size do: 
		[:index | 
		row := Array new: (table at: index) size.
		parseTable at: index put: row.
		1 to: (table at: index) size do: 
			[:i | 
			ea := (table at: index)
						at: i.
			ea isNil ifFalse: [ea isInteger
					ifTrue: [row at: i put: ea]
					ifFalse: [ea size == 2
							ifTrue: [row at: i put: (self constructGrammarProduction: ea with: prodTable)]
							ifFalse: [row at: i put: (self constructTransductionGrammarProduction: ea with: prodTable)]]]]]!

constructTransductionGrammarProduction: arg with: prodTable 

	| rhs |
	(arg at: 2) isEmpty
		ifTrue: [rhs := OrderedCollection new]
		ifFalse: 
			[rhs := OrderedCollection new.
			(arg at: 2)
				do: [:ea | rhs addLast: (prodTable at: ea)]].
	^TransductionGrammarProduction
		leftHandSide: (prodTable at: (arg at: 1))
		rightHandSide: rhs
		translationSymbol: (prodTable at: (arg at: 3))! !
TableDrivenParser initialize!

OptimizedLR1Parser initialize!

OptimizedLL1Parser initialize!


⌨️ 快捷键说明

复制代码 Ctrl + C
搜索代码 Ctrl + F
全屏模式 F11
切换主题 Ctrl + Shift + D
显示快捷键 ?
增大字号 Ctrl + =
减小字号 Ctrl + -