help-smalltalk
[Top][All Lists]
Advanced

[Date Prev][Date Next][Thread Prev][Thread Next][Date Index][Thread Index]

[Help-smalltalk] [PATCH] Decouple parsing and interpreting


From: Paolo Bonzini
Subject: [Help-smalltalk] [PATCH] Decouple parsing and interpreting
Date: Fri, 08 Jun 2007 13:05:52 +0200
User-agent: Thunderbird 2.0.0.0 (Macintosh/20070326)

This patch refactors whole-file parsing out of RBParser and into a subclass, and extracts the parsing actions into another hierarchy STParsingDriver. The new hierarchy effectively implements a Strategy pattern.

The new hierarchy is like this

   RBParser
      STFileParser
         STFileInParser
   STParsingDriver
      STEvaluationDriver (new name of the old STFileInParser)
      STInterpreter
         STClassLoader
            SyntaxConverter

The compiler hierarchy is not affected by the change.

This way, the actual parsing is independent of the actions. In the future, this will allow one to write for example a SqueakFileInParser, XMLFileInParser, and plug them into the newly-born conversion tool to convert Squeak or VisualWorks XML to the GNU Smalltalk syntax.

Paolo
2007-06-08  Paolo Bonzini  <address@hidden>

        * compiler/RBParser.st: Move file-in related stuff...
        * compiler/STFileParser.st: ... here.  Add STParsingDriver hierarchy.
        * compiler/STLoader.st: Make STInterpreter an STParsingDriver.
        * compiler/StartCompiler.st: Rename STFileInParser to STEvaluationDriver
        and make it a subclass of STParsingDriver.  

        * scripts/Convert.st: Adjust for new STParsingDriver hierarchy.
        * scripts/GenLibDoc.st: Likewise.

* looking for address@hidden/smalltalk--devo--2.2--patch-389 to compare with
* comparing to address@hidden/smalltalk--devo--2.2--patch-389
A  compiler/.arch-ids/STFileParser.st.id
A  compiler/STFileParser.st
M  scripts/Convert.st
M  compiler/RBParser.st
M  compiler/STLoader.st
M  compiler/StartCompiler.st
M  packages.xml.in
M  scripts/GenLibDoc.st

* modified files

--- orig/compiler/RBParser.st
+++ mod/compiler/RBParser.st
@@ -54,12 +54,6 @@ parseExpression
     self atEnd ifFalse: [self parserError: 'Unknown input at end'].
     ^node!
 
-parseSmalltalk
-    [ self parseDoits ]
-        whileTrue: [ self parseMethodDefinitionList ].
-
-    ^self result!
-
 parseMethod: aString 
     | node |
     node := self parseMethod.
@@ -257,45 +251,6 @@ parseCascadeMessage
                                    temp]])].
     ^RBCascadeNode messages: messages semicolons: semicolons!
 
-parseDoits
-    " Parses the stuff to be executed until a
-        ! <class expression> methodsFor: <category string> ! "
-
-    | node method start stop comments source |
-
-    [
-       self atEnd ifTrue: [ ^false ].
-       comments := scanner getComments.
-       start := comments isNil
-               ifTrue: [ currentToken start - 1 ]
-               ifFalse: [ comments first first - 1 ].
-       
-       tags := nil.
-       node := self parseStatements: false.
-       node comments isNil
-           ifTrue: [ node comments: comments ]
-           ifFalse: [
-               comments isNil ifFalse: [ node comments: node comments, 
comments ] ].
-
-        "One -1 accounts for base-1 vs. base-0 (as above), the
-         other drops the bang because we have a one-token lookahead."
-       stop := currentToken start - 2.
-
-        method := RBMethodNode selectorParts: #() arguments: #().
-        source := scanner stream copyFrom: start to: stop.
-       source := MappedCollection collection: source map: (1 - start to: stop).
-        method source: source.
-        node parent: method.
-
-        scanner stripSeparators.           "gobble doit terminating bang"
-        self step.           "gobble doit terminating bang"
-               node statements size > 0 and: [ self evaluate: node ]
-               
-    ]   whileFalse.
-
-    ^true
-!
-
 parseKeywordMessage
     ^self parseKeywordMessageWith: self parseBinaryMessage!
 
@@ -344,33 +299,6 @@ parseMethod
     methodNode category: methodCategory.
     ^methodNode!
 
-parseMethodDefinitionList
-    "Called after first !, expecting a set of bang terminated
-     method definitions, followed by a bang"
-
-    | node start stop |
-
-    [   scanner atEnd or: [ currentToken isSpecial
-          and: [ currentToken value == $! ] ] ] whileFalse: [
-
-       start := currentToken start - 1.
-        tags := nil.
-        node := self parseMethod.
-
-        "One -1 accounts for base-1 vs. base-0 (as above), the
-         other drops the bang because we have a one-token lookahead."
-       stop := currentToken start - 2.
-        node source: (scanner stream segmentFrom: start to: stop).
-
-        scanner stripSeparators.
-        self step.           "gobble method terminating bang"
-        self compile: node
-    ].
-    scanner stripSeparators.
-    self step.
-    self endMethodList
-!
-
 parseOptimizedExpression
     | position node |
     position := currentToken start.
@@ -544,23 +472,6 @@ parseVariableNode
     self step.
     ^node! !
 
-!RBParser methodsFor: 'overridable - parsing file-ins'!
-
-compile: node
-    "do nothing by default"
-!
-
-endMethodList
-    "do nothing by default"
-!
-
-evaluate: node
-    "This should be overridden because its result affects the parsing
-     process: true means 'start parsing methods', false means 'keep
-     evaluating'. By default, always answer false."
-    ^false
-! !
-
 !RBParser methodsFor: 'testing'!
 
 atEnd
@@ -626,40 +537,6 @@ parseRewriteMethod: aString onError: aBl
     parser initializeParserWith: aString type: #rewriteOn:errorBlock:.
     ^parser parseMethod: aString!
 
-parseSmalltalk: aString 
-    ^self parseSmalltalk: aString onError: nil!
-
-parseSmalltalk: aString onError: aBlock 
-    | parser |
-    parser := self new.
-    parser errorBlock: aBlock.
-    parser initializeParserWith: aString type: #on:errorBlock:.
-    parser parseSmalltalk.
-    ^parser result!
-
-parseSmalltalkStream: aStream 
-    ^self parseSmalltalkStream: aStream onError: nil!
-
-parseSmalltalkStream: aStream onError: aBlock 
-    | parser |
-    parser := self new.
-    parser errorBlock: aBlock.
-    parser initializeParserWithStream: aStream type: #on:errorBlock:.
-    parser parseSmalltalk.
-    ^parser result!
-
-parseSmalltalkFileIn: aFilename
-    ^self parseSmalltalkFileIn: aFilename onError: nil!
-
-parseSmalltalkFileIn: aFilename onError: aBlock 
-    | parser file |
-    file := FileStream open: aFilename mode: FileStream read.
-    parser := self new.
-    parser errorBlock: aBlock.
-    parser initializeParserWithStream: file type: #on:errorBlock:.
-    parser parseSmalltalk.
-    ^parser result!
-
 !RBParser class methodsFor: 'parsing'!
 
 parseMethodPattern: aString 
@@ -711,13 +588,12 @@ ignoreComments
     saveComments := false!
 
 next
-    | token ch |
+    | token |
     buffer reset.
     tokenStart := stream position.
-    ch := currentCharacter.
     characterType == #eof ifTrue: [^RBToken start: tokenStart + 1].    "The 
EOF token should occur after the end of input"
     token := self scanToken.
-    ch == $! ifFalse: [ self stripSeparators ].
+    self stripSeparators.
     ^token!
 
 nextPut: anObject 
@@ -1318,29 +1194,3 @@ isVariable: aString 
     ^scanner atEnd! !
 
 RBScanner initialize!
-
-
-!PositionableStream methodsFor: 'compiling'!
-
-name
-    "Answer a string that represents what the receiver is streaming on"
-    ^'(%1 %2)' bindWith: self species article with: self species name
-!
-
-segmentFrom: startPos to: endPos
-    "Answer an object that, when sent #asString, will yield the result
-     of sending `copyFrom: startPos to: endPos' to the receiver"
-    ^self copyFrom: startPos to: endPos
-! !
-
-!FileStream methodsFor: 'compiling'!
-
-segmentFrom: startPos to: endPos
-    "Answer an object that, when sent #asString, will yield the result
-     of sending `copyFrom: startPos to: endPos' to the receiver"
-    ^FileSegment
-       on: self name
-       startingAt: startPos
-       for: endPos - startPos + 1.
-! !
-


--- orig/compiler/STLoader.st
+++ mod/compiler/STLoader.st
@@ -28,7 +28,7 @@
 |
  ======================================================================"
 
-RBParser subclass: #STInterpreter
+STParsingDriver subclass: #STInterpreter
        instanceVariableNames: ''
        classVariableNames: ''
        poolDictionaries: ''


--- orig/compiler/StartCompiler.st
+++ mod/compiler/StartCompiler.st
@@ -29,17 +29,17 @@
  ======================================================================"
 
 
-RBParser subclass: #STFileInParser
+STParsingDriver subclass: #STEvaluationDriver
        instanceVariableNames: 'curCategory curClass curCompilerClass evalFor 
lastResult method'
        classVariableNames: ''
        poolDictionaries: ''
        category: 'System-Compiler'
 !
 
-STFileInParser comment:
-'I am a STParser that compiles code that you file in.'!
+STEvaluationDriver comment:
+'I am an STParsingDriver that compiles code that you file in.'!
 
-!STFileInParser class methodsFor: 'accessing'!
+!STEvaluationDriver class methodsFor: 'accessing'!
 
 methodsFor: aString compiler: compilerClass class: aClass
     | ctx |
@@ -75,19 +75,14 @@ methodsFor: aString compiler: compilerCl
        yourself
 ! !
 
-!STFileInParser methodsFor: 'accessing'!
+!STEvaluationDriver methodsFor: 'accessing'!
 
 evalFor: anObject
     evalFor := anObject
 !
 
-lastResult
-    ^lastResult
-!
-
 result
-    "This is what #parseSmalltalk answers"
-    ^method
+    ^lastResult
 !
 
 methodsFor: aString compiler: compilerClass class: aClass
@@ -96,7 +91,7 @@ methodsFor: aString compiler: compilerCl
     curCompilerClass := compilerClass
 ! !
 
-!STFileInParser methodsFor: 'overrides'!
+!STEvaluationDriver methodsFor: 'overrides'!
 
 compile: node
     method := curCompilerClass
@@ -136,14 +131,21 @@ compilerClass
     ^STInST.STCompiler
 !
 
+evaluatorClass
+    "This method is present for symmetry with #parserClass.  It
+     specifies the class that will be used to drive evaluation
+     of Smalltalk source code."
+    ^STInST.STFileInParser
+!
+
 parserClass
     "This method specifies which class will be used by an
-     STFileInParser to parse method definition chunk.  An instance of
+     STEvaluationDriver to parse method definition chunk.  An instance of
      the class will be created and sent #parseMethodDefinitionList,
      or the same will be done with the currently active parser
      (the one that parsed the doit that sent #methodsFor:) if
      this method answers nil."
-    ^STInST.STFileInParser
+    ^STInST.RBParser
 ! !
 
 
@@ -155,60 +157,61 @@ parserClass
 fileIn
     [
        STInST.STSymbolTable nowInsideFileIn.
-       STInST.STFileInParser parseSmalltalkStream: self ]
+       STInST.STEvaluationDriver new
+           parseSmalltalkStream: self
+           with: STInST.STFileInParser ]
+
            ensure: [ STInST.STSymbolTable nowOutsideFileIn ]
 ! !
 
 !Smalltalk.Behavior methodsFor: 'compiling'!
 
 evalString: aString to: anObject
-    ^STInST.STFileInParser new
-       errorBlock: nil;
-       initializeParserWith: aString type: #on:errorBlock:;
-       evalFor: anObject;
-       parseSmalltalk;
-       lastResult
+    ^STInST.STEvaluationDriver new
+       parseSmalltalk: aString with: self evaluatorClass
 !
 
 evalString: aString to: anObject ifError: aBlock
-    ^STInST.STFileInParser new
+    ^STInST.STEvaluationDriver new
+       parseSmalltalk: aString
+       with: self evaluatorClass
        errorBlock: [ :l :m |
            ^aBlock value: 'a Smalltalk String' value: l value: m.
-       ];
-       initializeParserWith: aString type: #on:errorBlock:;
-       evalFor: anObject;
-       parseSmalltalk;
-       lastResult
+       ]
 !
 
 compileString: aString
-    | codeWithHeader |
-    codeWithHeader := WriteStream on: (String new: aString size + 50).
-    codeWithHeader
-       nextPut: $!;
-       print: self;
-       nextPutAll: ' methodsFor: nil!';
-       nextPutAll: aString;
-       nextPutAll: '! !'.
-
-    ^STInST.STFileInParser parseSmalltalkStream: codeWithHeader readStream
+    | parser source |
+    source := aString isString
+       ifTrue: [ aString ]
+       ifFalse: [ source := aString contents ].
+    parser := self parserClass new.
+    parser initializeParserWith: source type: #on:errorBlock:.
+
+    ^self compilerClass
+       compile: (parser parseMethod: source)
+       for: self
+       classified: nil
+       parser: parser
 !
 
 compileString: aString ifError: aBlock
-    | codeWithHeader |
-    codeWithHeader := WriteStream on: (String new: aString size + 50).
-    codeWithHeader
-       nextPut: $!;
-       print: self;
-       nextPutAll: ' methodsFor: nil!';
-       nextPutAll: aString;
-       nextPutAll: '! !'.
-
-    ^STInST.STFileInParser
-       parseSmalltalkStream: codeWithHeader readStream
-       onError: [ :f :l :m |
-           ^aBlock value: 'a Smalltalk ', aString class printString value: l - 
1 value: m.
-       ]
+    | parser source |
+    source := aString isString
+       ifTrue: [ aString ]
+       ifFalse: [ source := aString contents ].
+
+    parser := self parserClass new.
+    parser errorBlock: [ :m :l |
+                   ^aBlock value: 'a Smalltalk ', aString class printString
+                       value: l - 1 value: m ].
+    parser initializeParserWith: source type: #on:errorBlock:.
+
+    ^self compilerClass
+       compile: (parser parseMethod: source)
+       for: self
+       classified: nil
+       parser: parser
 !
 
 basicMethodsFor: category ifTrue: condition
@@ -223,7 +226,7 @@ methodsFor: aString
 !
 
 methodsFor: aString ifTrue: realCompile
-    self parserClass
+    self evaluatorClass
        methodsFor: aString
        compiler: (realCompile
            ifTrue: [ self compilerClass ]


--- orig/packages.xml.in
+++ mod/packages.xml.in
@@ -389,6 +389,7 @@
   <filein>ParseTreeSearcher.st</filein>
   <filein>RBFormatter.st</filein>
   <filein>OrderedSet.st</filein>
+  <filein>STFileParser.st</filein>
   <filein>STCompLit.st</filein>
   <filein>STSymTable.st</filein>
   <filein>STCompiler.st</filein>


--- orig/scripts/Convert.st
+++ mod/scripts/Convert.st
@@ -140,7 +140,7 @@ EmittedEntity subclass: EmittedEval [
 
 
 STInST.STClassLoader subclass: SyntaxConverter [
-    | stuffToEmit classesToEmit inStream outStream |
+    | stuffToEmit classesToEmit outStream |
     
     <comment: 'A class loader that creates a set of "EmittedEntity"
     based on the contents of the given file being loaded.
@@ -151,34 +151,31 @@ STInST.STClassLoader subclass: SyntaxCon
     
     SyntaxConverter class >> convertStream: in to: out [
         <catogory: 'instance creation'>
-        ^super new initializeWithInStream: in withOutStream: out.
+        ^self convertStream: in with: STInST.STFileInParser to: out
     ]
     
-    initializeWithInStream: in withOutStream: out [
+    SyntaxConverter class >> convertStream: in with: aParserClass to: out [
+        <catogory: 'instance creation'>
+        ^self new
+           outStream: out;
+           parseSmalltalkStream: in with: aParserClass;
+           doEmitStuff.        
+    ]
+    
+    initialize [
         <category: 'initialization'>
-        super initializeParserWithStream: in type: #on:errorBlock:.
+       super initialize.
         stuffToEmit := OrderedSet new.
         classesToEmit := Dictionary new.
-        inStream := in.
-        outStream := out.
-        
-        self parseSmalltalk
     ]
-    
-    parseSmalltalk [
-        <category: 'overrides'>
-        
-        | ret |
-        
-        ret := super parseSmalltalk.
-        self doEmitStuff.        
-        ^ret
+
+    outStream: out [
+        outStream := out.
     ]
     
     evaluate: node [
         <category: 'overrides'>
 
-       "FIXME: there's a bug in RBParser.st"
        node comments isEmpty ifFalse: [
            stuffToEmit add: (EmittedComments comments: node comments source: 
node source) ].
 


--- orig/scripts/GenLibDoc.st
+++ mod/scripts/GenLibDoc.st
@@ -52,6 +52,8 @@ source := files fold: [ :old :each | old
 "Go!"
 Smalltalk addSubspace: namespace.
 Namespace current: (Smalltalk at: namespace).
-classes := STInST.STClassLoader parseSmalltalkStream: source.
+classes := STInST.STClassLoader new
+       parseSmalltalkStream: source
+       with: STInST.STFileInParser.
 Namespace current: Smalltalk.
 ClassPublisher.Texinfo publishAll: classes onFile: outTexinfo!



* added files

--- /dev/null
+++ mod/compiler/STFileParser.st
@@ -0,0 +1,295 @@
+"======================================================================
+|
+|   Smalltalk in Smalltalk file-in driver
+|
+|
+ ======================================================================"
+
+
+"======================================================================
+|
+| Copyright 1999,2000,2001,2002,2003,2006,2007 Free Software Foundation, Inc.
+| Written by Paolo Bonzini.
+|
+| This file is part of GNU Smalltalk.
+|
+| GNU Smalltalk is free software; you can redistribute it and/or modify it
+| under the terms of the GNU General Public License as published by the Free
+| Software Foundation; either version 2, or (at your option) any later version.
+| 
+| GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT
+| ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS
+| FOR A PARTICULAR PURPOSE.  See the GNU General Public License for more
+| details.
+| 
+| You should have received a copy of the GNU General Public License along with
+| GNU Smalltalk; see the file COPYING.  If not, write to the Free Software
+| Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA.  
+|
+ ======================================================================"
+
+
+RBParser subclass: #STFileParser
+    instanceVariableNames: 'driver'
+    classVariableNames: ''
+    poolDictionaries: ''
+    category: 'Refactory-Parser'!
+
+Object subclass: #STParsingDriver
+    instanceVariableNames: 'parser'
+    classVariableNames: ''
+    poolDictionaries: ''
+    category: 'Refactory-Parser'!
+
+STFileParser subclass: #STFileInParser
+    instanceVariableNames: ''
+    classVariableNames: ''
+    poolDictionaries: ''
+    category: 'Refactory-Parser'!
+
+
+
+
+!STFileParser methodsFor: 'accessing'!
+
+driver
+    ^driver!
+
+driver: aSTParsingDriver
+    driver := aSTParsingDriver.
+    driver parser: self!
+
+parseSmalltalk
+    self subclassResponsibility!
+
+!STFileParser methodsFor: 'overridable - parsing file-ins'!
+
+compile: node
+    driver compile: node
+!
+
+endMethodList
+    driver endMethodList
+!
+
+evaluate: node
+    "This should be overridden because its result affects the parsing
+     process: true means 'start parsing methods', false means 'keep
+     evaluating'. By default, always answer false."
+    ^driver evaluate: node
+! !
+
+!STFileParser class methodsFor: 'accessing'!
+
+parseSmalltalk: aString with: aDriver
+    ^self parseSmalltalk: aString with: aDriver onError: nil!
+
+parseSmalltalk: aString with: aDriver onError: aBlock 
+    | parser |
+    parser := self new.
+    parser errorBlock: aBlock.
+    parser initializeParserWith: aString type: #on:errorBlock:.
+    parser driver: aDriver.
+    ^parser parseSmalltalk!
+
+parseSmalltalkStream: aStream with: aDriver
+    ^self parseSmalltalkStream: aStream with: aDriver onError: nil!
+
+parseSmalltalkStream: aStream with: aDriver onError: aBlock 
+    | parser |
+    parser := self new.
+    parser errorBlock: aBlock.
+    parser initializeParserWithStream: aStream type: #on:errorBlock:.
+    parser driver: aDriver.
+    ^parser parseSmalltalk! !
+
+!STFileInParser methodsFor: 'private-parsing'!
+
+parseSmalltalk
+    [ self parseDoits ]
+        whileTrue: [ self parseMethodDefinitionList ].
+
+    ^driver result!
+
+scannerClass
+    ^STFileScanner! !
+
+!STFileInParser methodsFor: 'private-parsing'!
+
+parseDoits
+    " Parses the stuff to be executed until a
+        ! <class expression> methodsFor: <category string> ! "
+
+    | node method start stop comments source |
+
+    [
+       self atEnd ifTrue: [ ^false ].
+       comments := scanner getComments.
+       start := comments isNil
+               ifTrue: [ currentToken start - 1 ]
+               ifFalse: [ comments first first - 1 ].
+       
+       tags := nil.
+       node := self parseStatements: false.
+       node comments isNil
+           ifTrue: [ node comments: comments ]
+           ifFalse: [
+               comments isNil ifFalse: [ node comments: node comments, 
comments ] ].
+
+        "One -1 accounts for base-1 vs. base-0 (as above), the
+         other drops the bang because we have a one-token lookahead."
+       stop := currentToken start - 2.
+
+        method := RBMethodNode selectorParts: #() arguments: #().
+        source := scanner stream copyFrom: start to: stop.
+       source := MappedCollection collection: source map: (1 - start to: stop).
+        method source: source.
+        node parent: method.
+
+        scanner stripSeparators.           "gobble doit terminating bang"
+        self step.           "gobble doit terminating bang"
+       node statements size > 0 and: [ self evaluate: node ]
+               
+    ]   whileFalse.
+
+    ^true
+!
+
+parseMethodDefinitionList
+    "Called after first !, expecting a set of bang terminated
+     method definitions, followed by a bang"
+
+    | node start stop |
+
+    [   scanner atEnd or: [ currentToken isSpecial
+          and: [ currentToken value == $! ] ] ] whileFalse: [
+
+       start := currentToken start - 1.
+        tags := nil.
+        node := self parseMethod.
+
+        "One -1 accounts for base-1 vs. base-0 (as above), the
+         other drops the bang because we have a one-token lookahead."
+       stop := currentToken start - 2.
+        node source: (scanner stream segmentFrom: start to: stop).
+
+        scanner stripSeparators.
+        self step.           "gobble method terminating bang"
+        self compile: node
+    ].
+    scanner stripSeparators.
+    self step.
+    self endMethodList
+! !
+
+!STParsingDriver methodsFor: 'starting the parsing'!
+
+parseSmalltalk: aString with: aParserClass
+    ^aParserClass parseSmalltalk: aString with: self!
+
+parseSmalltalk: aString with: aParserClass onError: aBlock 
+    ^aParserClass parseSmalltalk: aString with: self onError: aBlock!
+
+parseSmalltalkStream: aStream with: aParserClass
+    ^aParserClass parseSmalltalkStream: aStream with: self!
+
+parseSmalltalkStream: aStream with: aParserClass onError: aBlock 
+    ^aParserClass parseSmalltalkStream: aStream with: self onError: aBlock!
+
+parseSmalltalkFileIn: aFilename with: aParserClass
+    ^self parseSmalltalkFileIn: aFilename with: aParserClass onError: nil!
+
+parseSmalltalkFileIn: aFilename with: aParserClass onError: aBlock 
+    | parser file |
+    file := FileStream open: aFilename mode: FileStream read.
+    [ self parseSmalltalkStream: file with: aParserClass onError: aBlock ]
+       ensure: [ file close ]! !
+
+!STParsingDriver methodsFor: 'accessing'!
+
+errorBlock
+    ^parser errorBlock
+!
+
+parserWarning: aString
+    parser parserWarning: aString
+!
+
+parserError: aString
+    parser parserError: aString
+!
+
+parser
+    ^parser!
+
+parser: aSTFileParser
+    parser := aSTFileParser! !
+
+!STParsingDriver methodsFor: 'overridable - parsing file-ins'!
+
+result
+    "return self by default"
+    ^self
+!
+
+compile: node
+    "do nothing by default"
+!
+
+endMethodList
+    "do nothing by default"
+!
+
+evaluate: node
+    "This should be overridden because its result affects the parsing
+     process: true means 'start parsing methods', false means 'keep
+     evaluating'. By default, always answer false."
+    ^false
+! !
+
+RBScanner subclass: #STFileScanner
+    instanceVariableNames: ''
+    classVariableNames: ''
+    poolDictionaries: ''
+    category: 'Refactory-Parser'!
+
+
+
+!STFileScanner methodsFor: 'accessing'!
+
+next
+    | token ch |
+    buffer reset.
+    tokenStart := stream position.
+    ch := currentCharacter.
+    characterType == #eof ifTrue: [^RBToken start: tokenStart + 1].    "The 
EOF token should occur after the end of input"
+    token := self scanToken.
+    ch == $! ifFalse: [ self stripSeparators ].
+    ^token!
+
+
+
+!PositionableStream methodsFor: 'compiling'!
+
+name
+    "Answer a string that represents what the receiver is streaming on"
+    ^'(%1 %2)' bindWith: self species article with: self species name
+!
+
+segmentFrom: startPos to: endPos
+    "Answer an object that, when sent #asString, will yield the result
+     of sending `copyFrom: startPos to: endPos' to the receiver"
+    ^self copyFrom: startPos to: endPos
+! !
+
+!FileStream methodsFor: 'compiling'!
+
+segmentFrom: startPos to: endPos
+    "Answer an object that, when sent #asString, will yield the result
+     of sending `copyFrom: startPos to: endPos' to the receiver"
+    ^FileSegment
+       on: self name
+       startingAt: startPos
+       for: endPos - startPos + 1.
+! !
+


reply via email to

[Prev in Thread] Current Thread [Next in Thread]