SmaCC__SmaCCScannerScanner.st
changeset 1 b8cca2663544
child 15 8b8cd1701c33
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/SmaCC__SmaCCScannerScanner.st	Thu Apr 10 09:11:12 2008 +0000
@@ -0,0 +1,194 @@
+"{ Package: 'stx:goodies/smaCC' }"
+
+"{ NameSpace: SmaCC }"
+
+SmaCCScanner subclass:#SmaCCScannerScanner
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'SmaCC-Scanner Generator'
+!
+
+SmaCCScannerScanner comment:'SmaCCScannerScanner is the scanner for the scanner definition'
+!
+
+
+!SmaCCScannerScanner class methodsFor:'generated-comments'!
+
+scannerDefinitionComment
+
+	"<backslashcharacter>	:	\\ [^cx] | \\ c [A-Z] | \\ x [0-9A-Fa-f]{1,4} ;
+<characterblock>	: \[ ([^\]\\] | <backslashcharacter> )+ \] ;
+<whitespace>	:	[\ \t\v\r\n]+ ;
+<tokenname>	:	\< [a-zA-Z_] \w* \> ;
+<comment>	:	\# [^\r\n]* ;
+<repeat>	:	\{ [0-9]* \, [0-9]* \} ;
+<character>	:	[^\ \t\v\\\r\n\{\(\[\.] ; 
+<anycharacter>	: \. ;"
+! !
+
+!SmaCCScannerScanner methodsFor:'generated-scanner'!
+
+scan1
+	
+	[self step.
+	currentCharacter <= $[ or: [currentCharacter >= $^]] whileTrue.
+	currentCharacter == $\ ifTrue: [^self scan2].
+	currentCharacter == $] ifTrue: [^self recordAndReportMatch: #(10)].
+	^self reportLastMatch
+!
+
+scan2
+	self step.
+	(currentCharacter <= $b 
+		or: [(currentCharacter between: $d and: $w) or: [currentCharacter >= $y]]) 
+			ifTrue: [^self scan1].
+	currentCharacter == $c 
+		ifTrue: 
+			[self step.
+			(currentCharacter between: $A and: $Z) ifTrue: [^self scan1].
+			^self reportLastMatch].
+	currentCharacter == $x 
+		ifTrue: 
+			[self step.
+			(currentCharacter isHexDigit or: [currentCharacter between: $a and: $f]) 
+				ifTrue: [^self scan1].
+			^self reportLastMatch].
+	^self reportLastMatch
+!
+
+scanForToken
+        self step.
+        (currentCharacter <= (Character value:16r8) "$" or: 
+                        [currentCharacter == (Character value:16rC) "$" or: 
+                                        [(currentCharacter between: (Character value:16rE) "$" and: (Character value:16r1F) "$") or: 
+                                                        [(currentCharacter between: $!! and: $") or: 
+                                                                        [(currentCharacter between: $$ and: $') or: 
+                                                                                        [(currentCharacter between: $, and: $-) or: 
+                                                                                                        [(currentCharacter between: $/ and: $9) or: 
+                                                                                                                        [(currentCharacter between: $= and: $>) or: 
+                                                                                                                                        [(currentCharacter between: $@ and: $Z) 
+                                                                                                                                                or: [(currentCharacter between: $] and: $z) or: [currentCharacter >= $}]]]]]]]]]]) 
+                ifTrue: [^self recordAndReportMatch: #(15)].
+        ((currentCharacter between: (Character tab) "$  " and: (Character value:16r0B) "$") 
+                or: [currentCharacter == Character cr "$
+" or: [currentCharacter == Character space "$ "]]) 
+                        ifTrue: 
+                                [
+                                [self recordMatch: #whitespace.
+                                self step.
+                                (currentCharacter between: Character tab "$     " and: (Character value:16r0B)"$") 
+                                        or: [currentCharacter == Character cr "$
+" or: [currentCharacter == Character space "$ "]]] 
+                                                whileTrue.
+                                ^self reportLastMatch].
+        currentCharacter == $# 
+                ifTrue: 
+                        [self recordMatch: #comment.
+                        self step.
+                        (currentCharacter <= Character tab "$   " 
+                                or: [(currentCharacter between: (Character value:16r0B)"$" and: (Character value:16r0C)"$") or: [currentCharacter >= (Character value:16r0E)"$"]]) 
+                                        ifTrue: 
+                                                [
+                                                [self recordMatch: #comment.
+                                                self step.
+                                                currentCharacter <= Character tab "$    " 
+                                                        or: [(currentCharacter between: (Character value:16r0B)"$" and: (Character value:16r0C) "$") or: [currentCharacter >= (Character value:16r0E)"$"]]] 
+                                                                whileTrue.
+                                                ^self reportLastMatch].
+                        ^self reportLastMatch].
+        currentCharacter == $( ifTrue: [^self recordAndReportMatch: #(4)].
+        currentCharacter == $) ifTrue: [^self recordAndReportMatch: #(1 15)].
+        currentCharacter == $* ifTrue: [^self recordAndReportMatch: #(2 15)].
+        currentCharacter == $+ ifTrue: [^self recordAndReportMatch: #(6 15)].
+        currentCharacter == $. ifTrue: [^self recordAndReportMatch: #(16)].
+        currentCharacter == $: ifTrue: [^self recordAndReportMatch: #(5 15)].
+        currentCharacter == $; ifTrue: [^self recordAndReportMatch: #(7 15)].
+        currentCharacter == $< 
+                ifTrue: 
+                        [self recordMatch: #(15).
+                        self step.
+                        ((currentCharacter between: $A and: $Z) 
+                                or: [currentCharacter == $_ or: [currentCharacter between: $a and: $z]]) 
+                                        ifTrue: 
+                                                [
+                                                [self step.
+                                                currentCharacter isHexDigit or: 
+                                                                [(currentCharacter between: $G and: $Z) 
+                                                                        or: [currentCharacter == $_ or: [currentCharacter between: $a and: $z]]]] 
+                                                                whileTrue.
+                                                currentCharacter == $> ifTrue: [^self recordAndReportMatch: #(12)].
+                                                ^self reportLastMatch].
+                        ^self reportLastMatch].
+        currentCharacter == $? ifTrue: [^self recordAndReportMatch: #(8 15)].
+        currentCharacter == $[ 
+                ifTrue: 
+                        [self step.
+                        (currentCharacter <= $[ or: [currentCharacter >= $^]) ifTrue: [^self scan1].
+                        currentCharacter == $\ ifTrue: [^self scan2].
+                        ^self reportLastMatch].
+        currentCharacter == $\ 
+                ifTrue: 
+                        [self step.
+                        (currentCharacter <= $b 
+                                or: [(currentCharacter between: $d and: $w) or: [currentCharacter >= $y]]) 
+                                        ifTrue: [^self recordAndReportMatch: #(9)].
+                        currentCharacter == $c 
+                                ifTrue: 
+                                        [self step.
+                                        (currentCharacter between: $A and: $Z) ifTrue: [^self recordAndReportMatch: #(9)].
+                                        ^self reportLastMatch].
+                        currentCharacter == $x 
+                                ifTrue: 
+                                        [self step.
+                                        (currentCharacter isHexDigit or: [currentCharacter between: $a and: $f]) 
+                                                ifTrue: 
+                                                        [self recordMatch: #(9).
+                                                        self step.
+                                                        (currentCharacter isHexDigit or: [currentCharacter between: $a and: $f]) 
+                                                                ifTrue: 
+                                                                        [self recordMatch: #(9).
+                                                                        self step.
+                                                                        (currentCharacter isHexDigit or: [currentCharacter between: $a and: $f]) 
+                                                                                ifTrue: 
+                                                                                        [self recordMatch: #(9).
+                                                                                        self step.
+                                                                                        (currentCharacter isHexDigit or: [currentCharacter between: $a and: $f]) 
+                                                                                                ifTrue: [^self recordAndReportMatch: #(9)].
+                                                                                        ^self reportLastMatch].
+                                                                        ^self reportLastMatch].
+                                                        ^self reportLastMatch].
+                                        ^self reportLastMatch].
+                        ^self reportLastMatch].
+        currentCharacter == ${ 
+                ifTrue: 
+                        [
+                        [self step.
+                        currentCharacter isDigit] whileTrue.
+                        currentCharacter == $, 
+                                ifTrue: 
+                                        [
+                                        [self step.
+                                        currentCharacter isDigit] whileTrue.
+                                        currentCharacter == $} ifTrue: [^self recordAndReportMatch: #(14)].
+                                        ^self reportLastMatch].
+                        ^self reportLastMatch].
+        currentCharacter == $| ifTrue: [^self recordAndReportMatch: #(3 15)].
+        ^self reportLastMatch
+! !
+
+!SmaCCScannerScanner methodsFor:'generated-tokens'!
+
+emptySymbolTokenId
+	^18
+!
+
+errorTokenId
+	^17
+! !
+
+!SmaCCScannerScanner class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /opt/data/cvs/stx/goodies/smaCC/SmaCC__SmaCCScannerScanner.st,v 1.1 2006-02-09 21:18:41 vranyj1 Exp $'
+! !