[squeak-dev] The Inbox: ShoutCore-ul.68.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Jul 30 15:00:11 UTC 2019


Levente Uzonyi uploaded a new version of ShoutCore to project The Inbox:
http://source.squeak.org/inbox/ShoutCore-ul.68.mcz

==================== Summary ====================

Name: ShoutCore-ul.68
Author: ul
Time: 30 July 2019, 4:54:51.155525 pm
UUID: c4f9bfa4-c725-48d5-beb1-4805e5e0efd2
Ancestors: ShoutCore-ul.67, ShoutCore-ct.66

- merged with ShoutCore-ct.66
- extracted most instance variable initialization before parsing to SHParserST80 >> #initializeInstanceVariables
- improved #parseString
- implemented #= and #hash for SHRange

=============== Diff against ShoutCore-ul.67 ===============

Item was changed:
  Object subclass: #SHParserST80
+ 	instanceVariableNames: 'classOrMetaClass source workspace arguments sourcePosition currentToken currentTokenFirst temporaries instanceVariables errorBlock currentTokenSourcePosition bracketDepth ranges environment allowUnderscoreAssignments allowUnderscoreSelectors allowBlockArgumentAssignment parseAMethod currentTokenType context'
- 	instanceVariableNames: 'classOrMetaClass source workspace arguments sourcePosition currentToken currentTokenFirst temporaries instanceVariables errorBlock currentTokenSourcePosition bracketDepth ranges environment allowUnderscoreAssignments allowUnderscoreSelectors allowBlockArgumentAssignment parseAMethod currentTokenType'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'ShoutCore-Parsing'!
  
+ !SHParserST80 commentStamp: 'ul 7/30/2019 00:31' prior: 0!
- !SHParserST80 commentStamp: 'ul 7/18/2019 21:12' prior: 0!
  I am a Smalltalk method / expression parser.
  
  Rather than creating an Abstract Syntax Tree, I create a sequence of SHRanges (in my 'ranges' instance variable), which represent the tokens within the String I am parsing.
  
  I am used by a SHTextStylerST80 to parse method source strings.
  I am able to parse incomplete / incorrect methods, and so can be used to parse methods that are being edited.
  
  Instance Variables
  	allowBlockArgumentAssignment:		<Boolean>
  	allowUnderscoreAssignments:		<Boolean>
  	allowUnderscoreSelectors:		<Boolean>
  	arguments:		<OrderedCollection<OrderedCollection<String>|nil>
  	bracketDepth:		<Integer>
  	classOrMetaClass:		<Class|nil>
  	currentToken:		<String|nil>
  	currentTokenFirst:		<Character>
  	currentTokenSourcePosition:		<Integer|nil>
  	currentTokenType:		<Symbol|nil>
  	environment:		<Environment>
  	errorBlock:		<Block>
  	instanceVariables:		<Array>
  	parseAMethod:		<Boolean>
  	ranges:		<OrderedCollection<SHRange>>
  	source:		<String>
  	sourcePosition:		<Integer>
  	temporaries:		<OrderedCollection<OrderedCollection<String>|nil>
  	workspace:		<Workspace|nil>
+ 	context:		<Context|nil>
  
  allowBlockArgumentAssignment
  	The value cached at the beginning of parsing of Scanner allowBlockArgumentAssignment.
  
  allowUnderscoreAssignments
  	The value cached at the beginning of parsing of Scanner allowUnderscoreAsAssignment.
  
  allowUnderscoreSelectors
  	The value cached at the beginning of parsing of Scanner prefAllowUnderscoreSelectors.
  
  arguments
  	This OrderedCollection has an element for each scope encapsulating the current scope.
  	The current scope's arguments are stored in the last element. The first element holds the outermost scope's arguments.
  	Each element is nil when the corresponding scope doesn't have any arguments, and the element is an OrderedCollection with the names of the arguments declared at the given scope when there's at least one.
  	The size of this variable is the same as the size of temporaries.
  
  bracketDepth
  	Stores the number of unclosed brackets "("  and parentheses "[" before the current sourcePosition.
  
  classOrMetaClass
  	The Class or MetaClass instance, class and pool variables should be looked up during parsing or nil when not parsing code in the context of a class (e.g. when parsing code written in a Workspace). Having this set doesn't mean a method is being parsed.
  
  currentToken
  	The token being analyzed for which the next range should be created for.
  
  currentTokenFirst
  	The first character of currentToken cached for quick access or a space character when there are no more tokens to parse.
  	Being always a Character helps avoiding extra checks.
  
  currentTokenSourcePosition
  	The position of source the current token starts at or nil when there are no more tokens to process.
  
  currentTokenType
  	The type of the current token calculated lazily by #currentTokenType. When it has been calculated, Its value is one of #keyword, #assignment, #ansiAssignment, #binary, #name, #other and occasionally #invalid.
  
  environment
  	The Environment globals and classes should be looked up at during parsing when classOrMetaClass is nil. Its value is Smalltalk globals by default.
  
  errorBlock
  	A block used to quickly stop parsing in case of an unrecoverable parse error.
  
  instanceVariables
  	An Array with the instance variable names of classOrMetaClass or an empty Array when classOrMetaClass is nil.
  
  parseAMethod
  	A way to tell the parser to parse source as a code snippet instead of a method. Mainly used by inspectors.
  
  ranges
  	The SHRanges parsed by the parser.
  
  source
  	The source code as a String to be parsed.
  
  sourcePosition
  	souce is treated as a stream by the parser. This variable stores the stream position.
  
  temporaries
  	This OrderedCollection has an element for each scope encapsulating the current scope.
  	The current scope's temporaries are stored in the last element. The first element holds the outermost scope's temporaries.
  	Each element is nil when the corresponding scope doesn't have any temporary variables, and the element is an OrderedCollection with the names of the temporaries declared at the given scope when there's at least one.
  	The size of this variable is the same as the size of arguments.
  
  workspace
  	The Workspace in whose context variables should be looked up during parsing or nil when not parsing code in a workspace.
  
+ context
+ 	The Context in which variables should be looked up during parsing or nil when not parsing within a context.
  
  Example (explore it):
  
  	ranges := SHParserST80 new
  		classOrMetaClass: Object;
  		source: 'testMethod ^self';
  		parse;
  		ranges
  		
  Benchmark (print it):
  
  	SHParserST80 benchmark!

Item was changed:
  ----- Method: SHParserST80>>initializeInstanceVariables (in category 'parse support') -----
  initializeInstanceVariables
  
  	instanceVariables := classOrMetaClass 
  		ifNil: [ #() ]
+ 		ifNotNil: [ classOrMetaClass allInstVarNames asArray ].
+ 	allowUnderscoreAssignments := Scanner allowUnderscoreAsAssignment.
+ 	allowUnderscoreSelectors := Scanner prefAllowUnderscoreSelectors.
+ 	allowBlockArgumentAssignment := Scanner allowBlockArgumentAssignment.
+ 	sourcePosition := 1.
+ 	arguments
+ 		ifNil: [ arguments := OrderedCollection with: nil ]
+ 		ifNotNil: [ arguments reset; addLast: nil ].
+ 	temporaries
+ 		ifNil: [ temporaries := OrderedCollection with: nil ]
+ 		ifNotNil: [ temporaries reset; addLast: nil ].
+ 	context ifNotNil: [
+ 		| contextArgumentCount contextVariableNames | 
+ 		contextArgumentCount := context numArgs.
+ 		contextVariableNames := context tempNames asOrderedCollection.
+ 		contextArgumentCount > 0 ifTrue: [
+ 			arguments at: 1 put: (contextVariableNames first: contextArgumentCount) ].
+ 		contextArgumentCount < contextVariableNames size ifTrue: [
+ 			temporaries at: 1 put: (contextVariableNames allButFirst: contextArgumentCount) ] ].
+ 	bracketDepth := 0.
+ 	ranges
+ 		ifNil: [ ranges := OrderedCollection new: 40 "Covers over 80% of all methods." ]
+ 		ifNotNil: [ ranges reset ]!
- 		ifNotNil: [ classOrMetaClass allInstVarNames asArray ]!

Item was changed:
  ----- Method: SHParserST80>>parse: (in category 'parse') -----
  parse: isAMethod 
+ 	"Parse the receiver's text. If isAMethod is true then treat text as a method, if false as an expression with no message pattern"
- 	"Parse the receiver's text. If isAMethod is true
-     then treat text as a method, if false as an
-     expression with no message pattern"
  
  	self initializeInstanceVariables.
+ 	errorBlock := [^false]. "This must be defined in this method, as the goal is to return from this method in case of an error."
- 	allowUnderscoreAssignments := Scanner allowUnderscoreAsAssignment.
- 	allowUnderscoreSelectors := Scanner prefAllowUnderscoreSelectors.
- 	allowBlockArgumentAssignment := Scanner allowBlockArgumentAssignment.
- 	sourcePosition := 1.
- 	arguments
- 		ifNil: [ arguments := OrderedCollection with: nil ]
- 		ifNotNil: [ arguments reset; addLast: nil ].
- 	temporaries
- 		ifNil: [ temporaries := OrderedCollection with: nil ]
- 		ifNotNil: [ temporaries reset; addLast: nil ].
- 	bracketDepth := 0.
- 	ranges
- 		ifNil: [ ranges := OrderedCollection new: 40 "Covers over 80% of all methods." ]
- 		ifNotNil: [ ranges reset ].
- 	errorBlock := [^false].
  	self scanNext.
  	isAMethod ifTrue: [
  		self
  			parseMessagePattern;
  			parsePragmaSequence ].
  	self parseTemporaries.
  	isAMethod ifTrue: [ self parsePragmaSequence ].
  	self parseStatementList.
  	currentToken ifNotNil: [ self fail ].
  	^true!

Item was changed:
  ----- Method: SHParserST80>>parseString (in category 'parse') -----
  parseString
- 	| first c last |
- 	first := sourcePosition.
  	
+ 	| stringStart |
+ 	stringStart := sourcePosition - 1.
+ 	[
+ 		(sourcePosition := source indexOf: $' startingAt: sourcePosition) = 0 ifTrue: [
- 	[(c := self currentChar)
- 		ifNil: [
  			self
+ 				addRangeType: #unfinishedString start: stringStart end: source size;
- 				addRangeType: #unfinishedString start: first - 1 end: source size;
  				fail ": 'unfinished string'"].
+ 		self peekChar == $'
- 	c ~~ $' or: [
- 		self peekChar == $' 
  			ifTrue: [
  				sourcePosition := sourcePosition + 1.
+ 				true ]
+ 			ifFalse: [ false ] ] 
+ 		whileTrue: [ sourcePosition := sourcePosition + 1 ].
+ 	sourcePosition := sourcePosition + 1.
+ 	self scanPast: #string start: stringStart end: sourcePosition - 1!
- 				true]
- 			ifFalse: [false]]
- 	] whileTrue: [sourcePosition := sourcePosition + 1].
- 	last := sourcePosition.
- 	self
- 		nextChar;
- 		scanPast: #string start: first - 1 end: last!

Item was changed:
  ----- Method: SHParserST80>>rangesIn:classOrMetaClass:workspace:environment: (in category 'parse') -----
  rangesIn: sourceString classOrMetaClass: aBehaviour workspace: aWorkspace  environment: anEnvironmentOrNil
+ 	^ self rangesIn: sourceString classOrMetaClass: aBehaviour workspace: aWorkspace environment: anEnvironmentOrNil context: nil!
- 	anEnvironmentOrNil ifNotNil: [environment := anEnvironmentOrNil].
- 	self
- 		workspace: aWorkspace;
- 		classOrMetaClass: aBehaviour;
- 		source: sourceString.
- 	self parse.
- 	^ranges!

Item was added:
+ ----- Method: SHParserST80>>rangesIn:classOrMetaClass:workspace:environment:context: (in category 'parse') -----
+ rangesIn: sourceString classOrMetaClass: aBehaviour workspace: aWorkspace  environment: anEnvironmentOrNil context: aContextOrNil
+ 	anEnvironmentOrNil ifNotNil: [environment := anEnvironmentOrNil].
+ 	aContextOrNil ifNotNil: [context := aContextOrNil].
+ 	self
+ 		workspace: aWorkspace;
+ 		classOrMetaClass: aBehaviour;
+ 		source: sourceString.
+ 	self parse.
+ 	^ranges!

Item was added:
+ ----- Method: SHRange>>= (in category 'comparing') -----
+ = anObject
+ 
+ 	anObject class == SHRange ifFalse: [ ^false ].
+ 	type = anObject type ifFalse: [ ^false ].
+ 	start = anObject start ifFalse: [ ^false ].
+ 	end = anObject end ifFalse: [ ^false ].
+ 	^true!

Item was added:
+ ----- Method: SHRange>>hash (in category 'comparing') -----
+ hash
+ 
+ 	^(((self class hash + type hash) hashMultiply + start) hashMultiply + end) hashMultiply!

Item was changed:
  SHTextStyler subclass: #SHTextStylerST80
+ 	instanceVariableNames: 'classOrMetaClass workspace font parser formatAssignments environment sourceMap processedSourceMap pixelHeight attributesByPixelHeight parseAMethod context'
- 	instanceVariableNames: 'classOrMetaClass workspace font parser formatAssignments environment sourceMap processedSourceMap pixelHeight attributesByPixelHeight parseAMethod'
  	classVariableNames: 'SyntaxHighlightingAsYouType SyntaxHighlightingAsYouTypeAnsiAssignment SyntaxHighlightingAsYouTypeLeftArrowAssignment TextAttributesByPixelHeight'
  	poolDictionaries: ''
  	category: 'ShoutCore-Styling'!
  
  !SHTextStylerST80 commentStamp: 'tween 8/27/2004 10:55' prior: 0!
  I style Smalltalk methods and expressions.
  
  My 'styleTable' class instance var holds an array ofArrays which control how each token is styled/coloured. See my defaultStyleTable class method for its structure.
  My styleTable can be changed by either modifying the defaultStyleTable class method and then executing SHTextStylerST80 initialize ; or by giving me a new styleTable through my #styleTable: class method.
  
  My 'textAttributesByPixelSize' class instance var contains a dictionary of dictionaries.
  	The key is a pixelSize and the value a Dictionary from token type Symbol to TextAttribute array.
  	It is created/maintained automatically.
  	
  I also install these 3 preferences when my class initialize method is executed....
  	#syntaxHighlightingAsYouType  - controls whether methods are styled in browsers
  	#syntaxHighlightingAsYouTypeAnsiAssignment - controls whether assignments are formatted to be :=
  	#syntaxHighlightingAsYouTypeLeftArrowAssignment - controls whether assignments are formatted to be _
  
  I reimplement #unstyledTextFrom: so that TextActions are preserved in the unstyled text 
  	
  	
  	
  	
  	 
  	
  !

Item was added:
+ ----- Method: SHTextStylerST80>>context: (in category 'accessing') -----
+ context: aContext
+ 	context := aContext!

Item was changed:
  ----- Method: SHTextStylerST80>>rangesIn:setWorkspace: (in category 'private') -----
  rangesIn: aText setWorkspace: aBoolean
  	"Answer a collection of SHRanges by parsing aText.
  	When formatting it is not necessary to set the workspace, and this can make the parse take less time, so aBoolean specifies whether the parser should be given the workspace"
  
  	| shoutParserClass |
  	"Switch parsers if we have to"
  	shoutParserClass := (classOrMetaClass ifNil:[Object]) shoutParserClass.
  	parser class == shoutParserClass ifFalse:[parser := shoutParserClass new].
  	parser parseAMethod: parseAMethod.
  	^parser 
  		rangesIn: aText asString 
  		classOrMetaClass: classOrMetaClass 
  		workspace: (aBoolean ifTrue:[workspace])  
  		environment: environment
+ 		context: context!
- !



More information about the Squeak-dev mailing list