SystemOrganization addCategory: #'ECompletion-Model'! SystemOrganization addCategory: #'ECompletion-Pharo'! SystemOrganization addCategory: #'ECompletion-Tests'! SystemOrganization addCategory: #'ECompletion-View'! !CodeHolder methodsFor: '*ecompletion-override' stamp: 'bar 12/13/2004 14:39'! contentsChanged super contentsChanged. self changed: #annotation. self completionController closeMenu! ! !CodeHolder methodsFor: '*ecompletion' stamp: 'bar 11/30/2004 16:10'! receiverClass ^ self selectedClassOrMetaClass! ! !String methodsFor: '*ecompletion' stamp: 'lr 7/4/2009 10:42'! beginsWithEmpty: prefix caseSensitive: aBoolean "Answer whether the receiver begins with the given prefix string. The comparison is case-sensitive." | matchTable | prefix isEmpty ifTrue: [ ^ true ]. self size < prefix size ifTrue: [ ^ false ]. matchTable := aBoolean ifTrue: [ CaseSensitiveOrder ] ifFalse: [ CaseInsensitiveOrder ]. ^ (self findSubstring: prefix in: self startingAt: 1 matchTable: matchTable) = 1! ! !String methodsFor: '*ecompletion' stamp: 'lr 7/4/2009 10:42'! indexOfFirstUppercaseCharacter | position found input | position := 0. found := false. input := ReadStream on: self. [ input atEnd | found ] whileFalse: [ input next isUppercase ifTrue: [ found := true ]. position := position + 1 ]. found ifTrue: [ ^ position ] ifFalse: [ ^ 0 ]! ! !String methodsFor: '*ecompletion' stamp: 'lr 7/4/2009 10:42'! occursInWithEmpty: prefix caseSensitive: aBoolean "Answer whether the receiver begins with the given prefix string. The comparison is case-sensitive." | matchTable | prefix isEmpty ifTrue: [ ^ true ]. self size < prefix size ifTrue: [ ^ false ]. matchTable := aBoolean ifTrue: [ CaseSensitiveOrder ] ifFalse: [ CaseInsensitiveOrder ]. ^ (self findSubstring: prefix in: self startingAt: 1 matchTable: matchTable) > 0! ! !String methodsFor: '*ecompletion' stamp: 'lr 7/4/2009 10:42'! wordBefore: anIndex | sep tok | tok := false. sep := anIndex. [ sep > 0 and: [ (self at: sep) tokenish ] ] whileTrue: [ tok := true. sep := sep - 1 ]. ^ tok ifTrue: [ self copyFrom: sep + 1 to: anIndex ] ifFalse: [ String new ]! ! Morph subclass: #ECDetailMorph instanceVariableNames: 'title description arrowPosition label' classVariableNames: '' poolDictionaries: '' category: 'ECompletion-View'! !ECDetailMorph commentStamp: '' prior: 0! I display some detail information for a selected ECEntry in the ECMenuMorph. The content I show, is provided by an ECDetailContentProvider subclass. ! !ECDetailMorph class methodsFor: 'as yet unclassified' stamp: 'bar 3/3/2006 16:14'! height ^ ECMenuMorph itemHeight * 15.5! ! !ECDetailMorph class methodsFor: 'as yet unclassified' stamp: 'bar 3/3/2006 22:45'! width ^ ECMenuMorph itemWidth * 2.0! ! !ECDetailMorph methodsFor: 'drawing' stamp: 'bar 3/3/2006 22:45'! bounds ^ super bounds topLeft extent: self class width @ self class height! ! !ECDetailMorph methodsFor: 'drawing' stamp: 'lr 7/4/2009 10:42'! contentBounds | factor rectangle | factor := ECMenuMorph itemHeight. rectangle := self bounds top: self bounds top + 3. rectangle := rectangle left: rectangle left + (factor * 2.0). rectangle := rectangle bottom: rectangle bottom - factor. ^ rectangle! ! !ECDetailMorph methodsFor: 'drawing' stamp: 'bar 2/26/2006 11:48'! defaultColor ^ ECMenuMorph backgroundColor. ! ! !ECDetailMorph methodsFor: 'accessing' stamp: 'bar 3/1/2006 16:30'! descriptionBounds ^ self contentBounds top: self contentBounds top + 30! ! !ECDetailMorph methodsFor: 'drawing' stamp: 'lr 7/4/2009 10:42'! drawArrowOn: aCanvas | point factor poligon | factor := ECMenuMorph itemHeight. point := arrowPosition. poligon := OrderedCollection new. poligon add: point. poligon add: (point := point translateBy: (factor / 2) @ 0). poligon add: (point := point translateBy: 0 @ (factor * -0.5)). poligon add: (point := point translateBy: factor @ factor). poligon add: (point := point translateBy: (factor * -1) @ factor). poligon add: (point := point translateBy: 0 @ (factor * -0.5)). poligon add: (point := point translateBy: (factor * -0.5) @ 0). aCanvas drawPolygon: poligon fillStyle: ECMenuMorph scrollColor! ! !ECDetailMorph methodsFor: 'drawing' stamp: 'lr 7/4/2009 10:42'! drawMessageOn: aCanvas | factor rectangle width browseMessage | factor := ECMenuMorph itemHeight. rectangle := self bounds top: self bounds bottom - factor. rectangle := rectangle left: self contentBounds left. aCanvas line: rectangle topLeft + (0 @ 2) to: rectangle topRight + (-3 @ 2) color: Color darkGray. rectangle := rectangle top: rectangle top + 3. aCanvas drawString: '<- close detail' in: rectangle font: ECMenuMorph messageFont color: Color darkGray. browseMessage := 'browse ->'. width := ECMenuMorph messageFont widthOfString: browseMessage. aCanvas drawString: browseMessage in: (rectangle left: rectangle right - width) font: ECMenuMorph messageFont color: Color darkGray! ! !ECDetailMorph methodsFor: 'drawing' stamp: 'bar 3/2/2006 21:16'! drawOn: aCanvas super drawOn: aCanvas. arrowPosition ifNotNil: [ self drawArrowOn: aCanvas. self drawMessageOn: aCanvas]! ! !ECDetailMorph methodsFor: 'accessing' stamp: 'bar 3/20/2006 15:33'! entryDescription: anECEntryDescription | categoryContents entryDescription | entryDescription := anECEntryDescription. title contents: (entryDescription title ifNil: [description bounds: self titleBounds. String new] ifNotNil: [description bounds: self descriptionBounds. entryDescription title]). description contentsWrapped: entryDescription description. categoryContents := entryDescription label. label contents: categoryContents! ! !ECDetailMorph methodsFor: 'accessing' stamp: 'lr 8/15/2010 09:33'! initialize | childBounds | super initialize. childBounds := self contentBounds. label := StringMorph contents: '' font: ECMenuMorph messageFont. label bounds: childBounds. self addMorph: label. title := StringMorph contents: '' font: ECMenuMorph titleFont. title bounds: self titleBounds. self addMorph: title. description := TextMorph new. description autoFit: false. description bounds: self descriptionBounds. description borderWidth: 0. self addMorph: description! ! !ECDetailMorph methodsFor: 'drawing' stamp: 'bar 3/20/2006 15:37'! position: aPoint menuWidth: anInteger | y x | arrowPosition := aPoint. y := aPoint y + self class height. y := y > Display height ifTrue: [Display height - self class height] ifFalse: [aPoint y - ECMenuMorph itemHeight]. x := aPoint x. x := x + self class width > Display width ifTrue: [arrowPosition := (self positionOnLeft: anInteger) @ aPoint y. arrowPosition x] ifFalse: [x]. self position: x @ y! ! !ECDetailMorph methodsFor: 'private' stamp: 'bar 3/3/2006 23:01'! positionOnLeft: anInteger ^ arrowPosition x - self class width - anInteger ! ! !ECDetailMorph methodsFor: 'accessing' stamp: 'bar 3/1/2006 16:31'! titleBounds ^ self contentBounds top: self contentBounds top + 10! ! Morph subclass: #ECMenuMorph instanceVariableNames: 'selected firstVisible titleStringMorph controller context pageHeight detailMorph detailPosition' classVariableNames: '' poolDictionaries: '' category: 'ECompletion-View'! !ECMenuMorph commentStamp: '' prior: 0! I show the possible completions in a menu like appearance. The user may choose an entry from my list and complete the word he was typing in the editor. I'm showed with the Tab key and will be deleted when with ESC key or when a successful completion occurs. The following keystrokes are supported: Ctrl-Space or Tab: Open a new morph. Tab requires at least one character in front of the cursor. When already open complete the selected entry. Esc: Close me Ctrl+u: Change to untyped mode, so I show all selectors of all classes in the system and the variables that are accessible to the current context. Arrow Up: Move one entry up. Arrow Down: Move one entry down Enter: (like Ctrl-Space and Tab): Complete with the selected item and close the morph any letter or digit: Narrow the completion further Ctrl+t: Toggle the expand flag. When expand is disabled, you don't see selectors belonging to Object and ProtoObject. ! !ECMenuMorph class methodsFor: 'preferences-colors' stamp: 'lr 8/15/2010 09:22'! backgroundColor ^ (UITheme current settings menuColor ifNil: [ Color white ]) alpha: 0.8! ! !ECMenuMorph class methodsFor: 'instance creation' stamp: 'bar 12/13/2004 11:34'! controller: aECController position: aPoint | newObject | newObject := self new. newObject setController: aECController position: aPoint. ^ newObject! ! !ECMenuMorph class methodsFor: 'preferences' stamp: 'lr 9/26/2010 17:48'! convertToSHSymbol: aSymbol ^ (SHTextStylerST80 new attributesFor: aSymbol) notNil ifTrue: [ aSymbol ] ifFalse: [ #default ]! ! !ECMenuMorph class methodsFor: 'preferences' stamp: 'lr 8/15/2010 09:30'! itemHeight ^ (self selectFontFor: #default) height + 2! ! !ECMenuMorph class methodsFor: 'preferences' stamp: 'lr 3/31/2010 23:09'! itemWidth ^ 250! ! !ECMenuMorph class methodsFor: 'preferences' stamp: 'lr 3/31/2010 23:08'! maxLength ^ 20! ! !ECMenuMorph class methodsFor: 'preferences-fonts' stamp: 'lr 8/15/2010 09:27'! messageFont ^ StandardFonts codeFont! ! !ECMenuMorph class methodsFor: 'preferences' stamp: 'lr 3/26/2010 14:35'! scrollArrowSize ^ 8! ! !ECMenuMorph class methodsFor: 'preferences-colors' stamp: 'lr 3/26/2010 14:34'! scrollColor ^ UITheme current settings selectionColor! ! !ECMenuMorph class methodsFor: 'preferences' stamp: 'lr 7/4/2009 10:42'! selectColorFor: aSymbol | attribute | attribute := self convertToSHSymbol: aSymbol. ^ (SHTextStylerST80 new attributesFor: attribute) first color! ! !ECMenuMorph class methodsFor: 'preferences-fonts' stamp: 'lr 8/15/2010 09:28'! selectFontFor: aSymbol | emphasized attributes | attributes := SHTextStylerST80 new attributesFor: (self convertToSHSymbol: aSymbol). emphasized := attributes size > 1 ifTrue: [ attributes second emphasisCode ] ifFalse: [ 0 ]. ^ StandardFonts menuFont emphasized: emphasized! ! !ECMenuMorph class methodsFor: 'preferences-fonts' stamp: 'lr 8/15/2010 09:26'! titleFont ^ StandardFonts windowTitleFont! ! !ECMenuMorph methodsFor: 'actions' stamp: 'bar 3/3/2006 16:28'! browse (self selectedEntry browseWith: context) ifTrue: [controller closeMenu]! ! !ECMenuMorph methodsFor: 'initialization' stamp: 'lr 3/26/2010 11:20'! createTitle | titleString transformationMorph | titleString := context model title ifNil: [ ^ self ]. titleStringMorph := StringMorph new. titleStringMorph font: self class titleFont. titleStringMorph contents: titleString. transformationMorph := TransformationMorph new. transformationMorph rotationDegrees: -90.0. transformationMorph offset: 0 @ titleStringMorph width negated. transformationMorph addMorph: titleStringMorph. self addMorph: transformationMorph! ! !ECMenuMorph methodsFor: 'paging' stamp: 'bar 2/21/2006 21:32'! currentPage ^(self selected - 1 // self pageHeight ) + 1.! ! !ECMenuMorph methodsFor: 'private' stamp: 'bar 12/13/2004 13:41'! delete super delete. controller menuClosed! ! !ECMenuMorph methodsFor: 'drawing' stamp: 'bar 3/12/2006 14:41'! detailMessage ^ detailMorph ifNil: ['ctrl-h=help | -> open detail'] ifNotNil: ['ctrl-h=help | <- close detail']! ! !ECMenuMorph methodsFor: 'accessing' stamp: 'bar 3/12/2006 10:46'! detailPosition: aPoint detailPosition := aPoint. self triggerEvent: #positionChanged! ! !ECMenuMorph methodsFor: 'drawing' stamp: 'lr 7/4/2009 10:42'! drawBottomScrollArrowOn: aCanvas | aPoligon point arrowHeight | point := self bounds bottomLeft translateBy: 6 @ -12. arrowHeight := self class scrollArrowSize. aPoligon := Array with: point with: (point translateBy: arrowHeight @ 0) with: (point translateBy: (arrowHeight / 2) @ arrowHeight). aCanvas drawPolygon: aPoligon fillStyle: self class scrollColor! ! !ECMenuMorph methodsFor: 'drawing' stamp: 'lr 3/28/2008 10:47'! drawMessageOn: aCanvas in: rectangle self hasMessage ifFalse: [ ^ self ]. context model isEmpty ifFalse: [ aCanvas line: rectangle topLeft + (0 @ 2) to: rectangle topRight + (-3 @ 2) color: Color darkGray ]. self drawModelMessageOn: aCanvas in: rectangle. self drawPageCountMessageOn: aCanvas in: rectangle! ! !ECMenuMorph methodsFor: 'drawing' stamp: 'lr 7/4/2009 10:42'! drawModelMessageOn: aCanvas in: rectangle | message | message := context model hasMessage ifTrue: [ context model message , ' | ctrl-h=help' ] ifFalse: [ self detailMessage ]. aCanvas drawString: message in: (rectangle insetBy: 3) font: self class messageFont color: Color darkGray! ! !ECMenuMorph methodsFor: 'drawing' stamp: 'lr 7/4/2009 10:42'! drawOn: aCanvas | rectangle model | super drawOn: aCanvas. rectangle := self bounds copy. rectangle bottom: rectangle top + self class itemHeight. rectangle := rectangle left: rectangle left + 20. model := context model. self extent: self extent. self firstVisible > 1 ifTrue: [ self drawTopScrollArrowOn: aCanvas ]. self lastVisible ~= self itemsCount ifTrue: [ self drawBottomScrollArrowOn: aCanvas ]. model notEmpty ifTrue: [ self firstVisible to: self lastVisible do: [ :index | | symbol type string | symbol := model entries at: index. string := symbol contents. type := symbol type. index = self selected ifTrue: [ | rect | rect := rectangle withBottom: rectangle top + self class itemHeight. aCanvas fillRectangle: rect color: self class scrollColor. self detailPosition: rect topRight ]. aCanvas drawString: string in: (rectangle insetBy: 1) font: (self selectFont: type) color: (self selectColor: type). rectangle := self prepareRectForNextRow: rectangle ] ]. self drawMessageOn: aCanvas in: rectangle! ! !ECMenuMorph methodsFor: 'drawing' stamp: 'lr 7/4/2009 10:42'! drawPageCountMessageOn: aCanvas in: rectangle | msg font msgWidth | self pageCount > 1 ifFalse: [ ^ self ]. msg := self currentPage printString , '/' , self pageCountString. font := self class messageFont. msgWidth := font widthOfString: msg. aCanvas drawString: msg in: (rectangle translateBy: (rectangle width - msgWidth - 3) @ 3) font: font color: Color darkGray! ! !ECMenuMorph methodsFor: 'drawing' stamp: 'bar 11/19/2004 20:54'! drawTopScrollArrowOn: aCanvas | aPoligon point arrowHeight | arrowHeight := self class scrollArrowSize. point := self bounds topLeft translateBy: 6 @ 11. aPoligon := Array with: point with: (point translateBy: arrowHeight @ 0) with: (point translateBy: arrowHeight / 2 @ arrowHeight negated). aCanvas drawPolygon: aPoligon fillStyle: self class scrollColor. ! ! !ECMenuMorph methodsFor: 'actions' stamp: 'bar 2/20/2006 17:26'! end self gotoPage: self pageCount. self changed.! ! !ECMenuMorph methodsFor: 'actions' stamp: 'bar 12/16/2004 11:36'! expand context model toggleExpand. self narrowCompletion! ! !ECMenuMorph methodsFor: 'private' stamp: 'bar 12/13/2004 11:46'! firstVisible ^firstVisible min: context model entryCount! ! !ECMenuMorph methodsFor: 'paging' stamp: 'lr 9/26/2010 17:48'! gotoPage: anInteger | item | item := (anInteger - 1) * self pageHeight + 1. item >= self itemsCount ifTrue: [ ^ self ]. item := item max: 1. firstVisible := item. self selected: firstVisible! ! !ECMenuMorph methodsFor: 'event handling' stamp: 'bar 3/31/2006 16:07'! handleMouseEnter: anEvent self activeHand newKeyboardFocus: controller editor morph. anEvent wasHandled: true. ! ! !ECMenuMorph methodsFor: 'drawing' stamp: 'bar 3/12/2006 14:47'! hasMessage ^ true ! ! !ECMenuMorph methodsFor: 'accessing' stamp: 'lr 8/15/2010 11:15'! height | count | count := self class maxLength. self visible ifTrue: [ | height | height := World height - self bounds topLeft y. World submorphs do: [ :each | each class = TaskbarMorph ifTrue: [ height := height - each height ] ]. count := height // self class itemHeight - 1 min: count ]. ^ count asInteger isZero ifTrue: [ 1 ] ifFalse: [ count ]! ! !ECMenuMorph methodsFor: 'actions' stamp: 'bar 3/12/2006 14:37'! help ECHelpMorph new openInWorld! ! !ECMenuMorph methodsFor: 'actions' stamp: 'lr 7/4/2009 10:42'! hideDetail detailMorph ifNil: [ ^ self ]. self removeMorph: detailMorph. detailMorph delete. detailMorph := nil. self changed! ! !ECMenuMorph methodsFor: 'actions' stamp: 'bar 2/20/2006 17:26'! home self gotoPage: 1. self changed! ! !ECMenuMorph methodsFor: 'initialization' stamp: 'lr 8/15/2010 09:20'! initialize super initialize. self color: self class backgroundColor. self on: #mouseDown send: #delete to: self. self when: #positionChanged send: #updateDetail to: self! ! !ECMenuMorph methodsFor: 'actions' stamp: 'bar 12/13/2004 15:04'! insertCompletion: aString | caret old pos editor | editor := controller editor. caret := editor caret. editor selectInvisiblyFrom: caret - context completionToken size to: caret - 1. old := editor selection. editor zapSelectionWith: aString. pos := caret + (aString copyUpTo: $ ) size + 1 - old size. editor selectAt: pos. editor morph invalidRect: editor morph bounds! ! !ECMenuMorph methodsFor: 'actions' stamp: 'bar 3/3/2006 16:30'! insertSelected context model isEmpty ifTrue: [^ false]. self insertCompletion: (context model completionAt: self selected). self delete. ^ true! ! !ECMenuMorph methodsFor: 'private' stamp: 'bar 12/13/2004 16:14'! isClosed ^ owner isNil! ! !ECMenuMorph methodsFor: 'private' stamp: 'bar 12/13/2004 11:47'! itemsCount ^context model entryCount! ! !ECMenuMorph methodsFor: 'private' stamp: 'bar 10/17/2004 15:15'! lastVisible ^ (self firstVisible + self height-1) min: (self itemsCount).! ! !ECMenuMorph methodsFor: 'actions' stamp: 'bar 12/5/2004 22:23'! moveDown self selected: self selected + 1. (self selected > self lastVisible and: [self selected <= self itemsCount]) ifTrue: [firstVisible := firstVisible + 1]. self changed! ! !ECMenuMorph methodsFor: 'actions' stamp: 'bar 12/13/2004 15:05'! moveUp (self selected = 0 and: [self firstVisible = 1]) ifTrue: [^ self]. self selected: self selected - 1. self selected < self firstVisible ifTrue: [firstVisible := firstVisible - 1]. self changed. ! ! !ECMenuMorph methodsFor: 'actions' stamp: 'lr 7/4/2009 10:42'! narrowCompletion | model | self selected: 0. firstVisible := 1. model := context model. model narrowWith: context completionToken. (model entries size = 1 and: [ context completionToken notEmpty ]) ifTrue: [ self insertCompletion: (model completionAt: 1). self delete. ^ false ]. model notEmpty ifTrue: [ self selected: 1 ]. self show. ^ true! ! !ECMenuMorph methodsFor: 'paging' stamp: 'bar 3/30/2006 14:21'! pageCount | count | self itemsCount == self pageHeight ifTrue: [^ 1]. count := self itemsCount // self pageHeight. (self itemsCount \\ self pageHeight) > 0 ifTrue:[count := count + 1]. ^count! ! !ECMenuMorph methodsFor: 'paging' stamp: 'cmm 1/8/2007 21:09'! pageCountString ^ self itemsCount = 501 ifTrue: [ 'more' ] ifFalse: [ self pageCount asString ]! ! !ECMenuMorph methodsFor: 'actions' stamp: 'bar 2/20/2006 17:24'! pageDown self gotoPage: self currentPage + 1. self changed. ! ! !ECMenuMorph methodsFor: 'paging' stamp: 'bar 2/20/2006 17:53'! pageHeight ^pageHeight.! ! !ECMenuMorph methodsFor: 'actions' stamp: 'bar 2/20/2006 17:26'! pageUp self gotoPage: self currentPage - 1. self changed. ! ! !ECMenuMorph methodsFor: 'drawing' stamp: 'bar 1/6/2005 08:44'! prepareRectForNextRow: aRectangle ^aRectangle translateBy: 0 @ self class itemHeight! ! !ECMenuMorph methodsFor: 'title' stamp: 'bar 12/13/2004 14:16'! removeTitle titleStringMorph ifNil: [^ self]. self removeMorph: titleStringMorph owner. titleStringMorph := nil! ! !ECMenuMorph methodsFor: 'drawing' stamp: 'bar 8/12/2005 23:12'! selectColor: type ^ self class selectColorFor: type! ! !ECMenuMorph methodsFor: 'drawing' stamp: 'bar 8/12/2005 22:43'! selectFont: aSymbol ^ self class selectFontFor: aSymbol! ! !ECMenuMorph methodsFor: 'accessing' stamp: 'lr 7/4/2009 10:42'! selected "Answer the value of selected" selected ifNil: [ selected := self firstVisible ]. ^ selected! ! !ECMenuMorph methodsFor: 'accessing' stamp: 'lr 7/4/2009 10:42'! selected: aNumber "Set the value of selected" context model notEmpty ifTrue: [ ((1 to: self itemsCount) includes: aNumber) ifTrue: [ aNumber ~= selected ifTrue: [ selected := aNumber ] ] ]! ! !ECMenuMorph methodsFor: 'accessing' stamp: 'bar 3/3/2006 16:30'! selectedEntry ^ context model entries at: self selected! ! !ECMenuMorph methodsFor: 'initialization' stamp: 'bar 3/31/2006 09:34'! setController: aECController position: aPoint controller := aECController. context := controller context. self createTitle. self position: aPoint - (20 @ 0). self narrowCompletion ifTrue: [self openInWorld]. ! ! !ECMenuMorph methodsFor: 'drawing' stamp: 'lr 7/4/2009 10:42'! show | extent height | firstVisible := 1. height := self visibleItemsCount * self class itemHeight. pageHeight := self height asInteger. self hasMessage ifTrue: [ height := height + self class itemHeight ]. titleStringMorph ifNotNil: [ height := height max: titleStringMorph width + 30 ]. extent := self class itemWidth @ height. self extent: extent. self changed! ! !ECMenuMorph methodsFor: 'actions' stamp: 'lr 7/4/2009 10:42'! showDetail detailMorph ifNotNil: [ ^ self browse ]. self itemsCount isZero ifTrue: [ ^ self ]. detailMorph := ECDetailMorph new. self addMorph: detailMorph. self updateDetail! ! !ECMenuMorph methodsFor: 'actions' stamp: 'bar 12/20/2004 23:21'! switchToUntyped context switchToUntyped. self removeTitle; narrowCompletion; changed! ! !ECMenuMorph methodsFor: 'private' stamp: 'bar 3/3/2006 22:52'! updateDetail detailMorph ifNil: [^ self]. detailMorph entryDescription: (self selectedEntry descriptionWith: context). detailMorph position: detailPosition menuWidth: self width. detailMorph show! ! !ECMenuMorph methodsFor: 'private' stamp: 'pk 6/3/2004 16:31'! visibleItemsCount. ^ self lastVisible - self firstVisible + 1! ! !StringHolder methodsFor: '*ecompletion' stamp: 'dr 10/30/2008 21:01'! completionController | controller | controller := self triggerEvent: #getCompletionController. controller ifNil:[ controller := self initializeCompletionController ]. ^controller! ! !StringHolder methodsFor: '*ecompletion' stamp: 'bar 12/15/2004 09:30'! createCompletionController ^ ECController model: self! ! !StringHolder methodsFor: '*ecompletion' stamp: 'lr 3/26/2010 13:44'! guessTypeForName: aString ^ nil! ! !StringHolder methodsFor: '*ecompletion' stamp: 'lr 7/4/2009 10:42'! initializeCompletionController | controller | controller := self createCompletionController. self when: #getCompletionController evaluate: (MessageSend receiver: controller selector: #yourself). ^ controller! ! !StringHolder methodsFor: '*ecompletion' stamp: 'bar 11/30/2004 16:08'! receiverClass ^nil! ! !Workspace methodsFor: '*ecompletion' stamp: 'lr 7/4/2009 10:42'! completionAdditionals | additionals | additionals := SortedCollection new. bindings ifNotNil: [ bindings keysDo: [ :each | additionals add: (ECLocalEntry contents: each type: #local) ] ]. ^ additionals! ! !Workspace methodsFor: '*ecompletion' stamp: 'bar 12/15/2004 09:30'! createCompletionController ^ECWorkspaceController model: self! ! !Workspace methodsFor: '*ecompletion' stamp: 'lr 3/26/2010 13:55'! guessTypeForName: aString | binding | bindings isNil ifFalse: [ binding := bindings at: aString ifAbsent: [ nil ]. binding isNil ifFalse: [ ^ binding class ] ]. ^ super guessTypeForName: aString! ! !Workspace methodsFor: '*ecompletion' stamp: 'bar 12/16/2004 11:24'! hasBindingOf: aString ^(self guessTypeForName: aString) notNil! ! !Workspace methodsFor: '*ecompletion' stamp: 'bar 12/16/2004 11:26'! hasBindingThatBeginsWith: aString ^false! ! !ParagraphEditor methodsFor: '*ecompletion' stamp: 'bar 10/18/2004 07:09'! caret ^self startBlock stringIndex! ! !ParagraphEditor methodsFor: '*ecompletion' stamp: 'bar 12/13/2004 15:28'! isCaretBehindChar | pos | pos := self caret - 1. ^ pos < 1 ifTrue: [false] ifFalse: [(self text at: pos) isAlphaNumeric]! ! !ParagraphEditor methodsFor: '*ecompletion' stamp: 'lr 9/26/2010 17:51'! selectionPosition: aString | caret position bottomLeft topLeft | caret := self startBlock stringIndex. position := [ self selectAt: caret - aString size. bottomLeft := paragraph selectionRects first bottomLeft. topLeft := self morph owner submorphBounds topLeft. topLeft + bottomLeft ] ensure: [ self selectAt: caret ]. ^ position! ! !ParagraphEditor methodsFor: '*ecompletion' stamp: 'bar 12/18/2004 23:46'! wordAtCaret ^paragraph text asString wordBefore: self caret -1 ! ! !Symbol methodsFor: '*ecompletion' stamp: 'lr 9/26/2010 17:50'! separateKeywords ^ self isKeyword ifFalse: [ self ] ifTrue: [ String streamContents: [ :stream | (self findTokens: $:) do: [ :each | stream nextPutAll: each; nextPut: $: ] separatedBy: [ stream nextPutAll: ' ' ] ] ]! ! !SHRange methodsFor: '*ecompletion' stamp: 'bar 1/9/2005 13:20'! asType type = #symbol ifTrue: [^ Symbol]. type = #character ifTrue: [^ Character]. type = #string ifTrue: [^ String]. type = #number ifTrue: [^ Number]. type = #true ifTrue: [^ Smalltalk at: #True]. type = #false ifTrue: [^ Smalltalk at: #False]. type = #arrayEnd ifTrue: [^ Array]. self isBlockEnd ifTrue: [^ BlockContext]. ^ nil! ! !SHRange methodsFor: '*ecompletion' stamp: 'lr 9/26/2010 17:48'! includesPosition: aNumber ^ aNumber between: start and: end! ! !SHRange methodsFor: '*ecompletion' stamp: 'bar 1/9/2005 13:14'! isArgument ^ type = #methodArg! ! !SHRange methodsFor: '*ecompletion' stamp: 'bar 1/9/2005 14:51'! isAssignment ^#(#assignment #ansiAssignment ) includes: type! ! !SHRange methodsFor: '*ecompletion' stamp: 'bar 3/2/2006 21:27'! isBinary ^type == #binary! ! !SHRange methodsFor: '*ecompletion' stamp: 'bar 1/6/2005 22:22'! isBlockEnd ^ type beginsWith: 'blockEnd'! ! !SHRange methodsFor: '*ecompletion' stamp: 'bar 1/6/2005 22:21'! isBlockStart ^type beginsWith: 'blockStart'! ! !SHRange methodsFor: '*ecompletion' stamp: 'bar 9/20/2006 08:29'! isBlockTemporary ^#(#blockPatternTempVar #blockPatternArg) includes: type! ! !SHRange methodsFor: '*ecompletion' stamp: 'bar 8/9/2005 23:04'! isClassVariable ^ type = #classVar! ! !SHRange methodsFor: '*ecompletion' stamp: 'bar 1/9/2005 13:20'! isConstant ^ self isBlockEnd or: [#(#false #true #string #number #symbol #character #arrayEnd ) includes: type]! ! !SHRange methodsFor: '*ecompletion' stamp: 'bar 1/9/2005 13:06'! isGlobal ^type = #globalVar! ! !SHRange methodsFor: '*ecompletion' stamp: 'bar 1/9/2005 13:13'! isInstanceVariable ^ type = #instVar! ! !SHRange methodsFor: '*ecompletion' stamp: 'bar 3/9/2006 10:10'! isKeyword ^ type == #keyword or:[type == #undefinedKeyword]! ! !SHRange methodsFor: '*ecompletion' stamp: 'bar 1/6/2005 13:56'! isOpening ^ ((type beginsWith: 'blockStart') or: [type beginsWith: 'leftParenthesis']) ! ! !SHRange methodsFor: '*ecompletion' stamp: 'bar 1/9/2005 13:05'! isSelf ^type = #self! ! !SHRange methodsFor: '*ecompletion' stamp: 'bar 1/9/2005 14:37'! isSeparator ^ #(#methodTempBar #statementSeparator #patternUnary #patternArg #blockPatternArg #blockArgsBar #return #primitiveOrExternalCallEnd) includes: type! ! !SHRange methodsFor: '*ecompletion' stamp: 'bar 1/9/2005 13:05'! isSuper ^type = #super! ! !SHRange methodsFor: '*ecompletion' stamp: 'bar 1/9/2005 13:03'! isTemporaryVariable ^ #(#tempVar #blockTempVar workspaceVar ) includes: type! ! !SHRange methodsFor: '*ecompletion' stamp: 'bar 1/6/2005 13:18'! isUnfinished ^#(#unfinishedString #unfinishedComment ) includes: type! ! !SHRange methodsFor: '*ecompletion' stamp: 'bar 1/9/2005 13:13'! isVariable ^ self isTemporaryVariable or: [self isInstanceVariable or: [self isSelf or:[self isSuper]]]! ! !SHRange methodsFor: '*ecompletion' stamp: 'bar 3/2/2006 21:26'! isVariablesOnly ^ self isAssignment or: [self isVariable or: [self isConstant or: [self isSeparator or:[self isBinary]]]]! ! !TextMorph methodsFor: '*ecompletion-override' stamp: 'damiencassou 4/25/2009 14:47'! keyStroke: evt "Handle a keystroke event." | action completionAllowed stringHolder | stringHolder := editor ifNotNil:[editor model]. completionAllowed := ECController allowModel: stringHolder. completionAllowed ifTrue: [(stringHolder completionController handleKeystrokeBefore: evt editor: editor) ifTrue: [^ self]]. evt keyValue = 13 ifTrue: [action := self crAction. action ifNotNil: ["Note: Code below assumes that this was some input field reacting on CR. Break the keyboard focus so that the receiver can be safely deleted." evt hand newKeyboardFocus: nil. ^ action value]]. self handleInteraction: [editor keystroke: evt]. self updateFromParagraph. super keyStroke: evt. "sends to keyStroke event handler, if any" "Narrow the completion with any of the keys" completionAllowed ifTrue: [stringHolder completionController handleKeystrokeAfter: evt editor: editor]! ! !Behavior methodsFor: '*ecompletion' stamp: 'dc 5/8/2007 15:32'! allSelectorsForCompletionWithout: behaviors | selectors | selectors := IdentitySet new. self withAllSuperclassesDo: [:class | (behaviors includes: class) ifFalse: [selectors addAll: class selectors.]]. ^ selectors asOrderedCollection ! ! InstructionClient subclass: #ECVarTypeGuesser instanceVariableNames: 'types receiverClass variableName found currentMethod hasSend contextCount' classVariableNames: '' poolDictionaries: '' category: 'ECompletion-Model'! !ECVarTypeGuesser commentStamp: '' prior: 0! I'm an InstructionClient that tries to guess the type of a given instance variable name of a class. ! ECVarTypeGuesser subclass: #ECClassVarTypeGuesser instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'ECompletion-Model'! !ECClassVarTypeGuesser methodsFor: 'as yet unclassified' stamp: 'lr 7/4/2009 10:42'! methodRefs | theClass classVarAssoc | theClass := receiverClass classThatDefinesClassVariable: variableName. classVarAssoc := theClass classPool associationAt: variableName asSymbol. classVarAssoc value ifNil: [ ^ SystemNavigation new allCallsOn: classVarAssoc ] ifNotNil: [ ^ classVarAssoc value class ]! ! !ECClassVarTypeGuesser methodsFor: 'as yet unclassified' stamp: 'lr 7/4/2009 10:42'! popIntoLiteralVariable: anAssociation anAssociation key == variableName asSymbol ifTrue: [ found := true ] ifFalse: [ self reset ]! ! !ECClassVarTypeGuesser methodsFor: 'as yet unclassified' stamp: 'bar 8/11/2005 13:07'! popIntoReceiverVariable: offset self reset! ! !ECClassVarTypeGuesser methodsFor: 'as yet unclassified' stamp: 'bar 8/11/2005 13:14'! send: selector super: supered numArgs: numberArguments ! ! ECVarTypeGuesser subclass: #ECInstVarTypeGuesser instanceVariableNames: 'varIndex' classVariableNames: '' poolDictionaries: '' category: 'ECompletion-Model'! !ECInstVarTypeGuesser commentStamp: '' prior: 0! I'm a simple InstructionClient that tries to guess the type of a given instance variable name of a class. ! !ECInstVarTypeGuesser methodsFor: 'as yet unclassified' stamp: 'lr 9/26/2010 17:44'! methodRefs | theClass selectors | theClass := receiverClass classThatDefinesInstanceVariable: variableName. theClass ifNil: [ ^ nil ]. selectors := theClass whichSelectorsStoreInto: variableName. ^ selectors collect: [ :each | MethodReference new setStandardClass: theClass methodSymbol: each ]! ! !ECInstVarTypeGuesser methodsFor: 'bytecode decoding' stamp: 'lr 7/4/2009 10:42'! popIntoReceiverVariable: offset varIndex = offset ifTrue: [ found := true ] ifFalse: [ self reset ]! ! !ECInstVarTypeGuesser methodsFor: 'as yet unclassified' stamp: 'lr 7/4/2009 10:42'! prepare: aCompiledMethod | theClass | super prepare: aCompiledMethod. theClass := aCompiledMethod actualClass. varIndex := (theClass allInstVarNames indexOf: variableName) - 1! ! !ECVarTypeGuesser class methodsFor: 'as yet unclassified' stamp: 'bar 12/9/2004 18:37'! getClassFromTypeSuggestingName: aString | firstUppercaseLetter className aStream aClass | aStream := WriteStream on: String new. aStream nextPut: aString first asUppercase. aStream nextPutAll: (aString copyFrom: 2 to: aString size). className := aStream contents. aClass := Smalltalk at: className asSymbol ifAbsent: []. (aClass isKindOf: Class) ifTrue: [^ aClass]. firstUppercaseLetter := aString indexOfFirstUppercaseCharacter. className := firstUppercaseLetter > 1 ifTrue: [aString copyFrom: firstUppercaseLetter to: aString size] ifFalse: [^ nil]. aClass := Smalltalk at: className asSymbol ifAbsent: []. (aClass isKindOf: Class) ifTrue: [^ aClass]. ^ nil! ! !ECVarTypeGuesser class methodsFor: 'as yet unclassified' stamp: 'bar 12/8/2004 13:47'! variableName: aString class: aClass ^self variableName: aString source: nil class: aClass ! ! !ECVarTypeGuesser class methodsFor: 'as yet unclassified' stamp: 'lr 7/4/2009 10:42'! variableName: aString source: sourceString class: aClass | newInstance | newInstance := self basicNew initialize. newInstance setVariableName: aString source: sourceString class: aClass. ^ newInstance! ! !ECVarTypeGuesser methodsFor: 'bytecode decoding' stamp: 'lr 7/4/2009 10:42'! blockReturnTop contextCount := contextCount - 1! ! !ECVarTypeGuesser methodsFor: 'bytecode decoding' stamp: 'lr 7/4/2009 10:42'! computeVarType | info tempNames name | types ifEmpty: [ ^ nil ]. info := types first. (hasSend and: [ info isDefinedByMessageSend not ]) ifTrue: [ info type: nil. ^ info ]. info isDefinedByTemporary not ifTrue: [ ^ info ]. tempNames := (receiverClass compilerClass new parse: currentMethod getSourceFromFile asString in: receiverClass notifying: nil) tempNames. name := tempNames at: info temporaryOffset + 1. info type: (self class getClassFromTypeSuggestingName: name). ^ info! ! !ECVarTypeGuesser methodsFor: 'instance creation' stamp: 'bar 12/13/2004 17:26'! initialize super initialize. types := OrderedCollection new. hasSend := false. contextCount := 0! ! !ECVarTypeGuesser methodsFor: 'bytecode decoding' stamp: 'bar 12/1/2004 21:47'! interpretNextInstructionUsing: aScanner found := false. aScanner interpretNextInstructionFor: self. ^found ! ! !ECVarTypeGuesser methodsFor: 'public' stamp: 'bar 3/20/2006 15:59'! methodRefs ^Array new! ! !ECVarTypeGuesser methodsFor: 'public' stamp: 'bar 3/20/2006 15:21'! perform | infos infosOfMethod methodRefs | variableName isEmpty ifTrue: [^ nil]. methodRefs := self methodRefs. methodRefs ifNil: [^ nil]. methodRefs isBehavior ifTrue: [^ methodRefs]. contextCount := 0. infos := SortedCollection sortBlock: [:a :b | a priority <= b priority]. methodRefs do: [:each | self prepare: each. infosOfMethod := self typeOfVarIn: each compiledMethod. infos addAll: infosOfMethod]. infos notEmpty ifTrue: [^ infos first type]. ^ nil! ! !ECVarTypeGuesser methodsFor: 'bytecode decoding' stamp: 'bar 8/11/2005 13:03'! popIntoLiteralVariable: anAssociation "Remove Top Of Stack And Store Into Literal Variable bytecode." self reset! ! !ECVarTypeGuesser methodsFor: 'bytecode decoding' stamp: 'bar 12/13/2004 17:08'! popIntoTemporaryVariable: offset "Remove Top Of Stack And Store Into Temporary Variable bytecode." self reset ! ! !ECVarTypeGuesser methodsFor: 'bytecode decoding' stamp: 'bar 8/11/2005 13:19'! prepare: aCompiledMethod ! ! !ECVarTypeGuesser methodsFor: 'bytecode decoding' stamp: 'lr 7/4/2009 10:42'! pushActiveContext "Push Active Context On Top Of Its Own Stack bytecode." contextCount := contextCount + 1! ! !ECVarTypeGuesser methodsFor: 'bytecode decoding' stamp: 'lr 7/4/2009 10:42'! pushConstant: value "Push Constant, value, on Top Of Stack bytecode." | info | contextCount > 0 ifTrue: [ ^ self ]. value ifNotNil: [ info := ECTypeInfo definedByLiteral: value class. types add: info ]! ! !ECVarTypeGuesser methodsFor: 'bytecode decoding' stamp: 'bar 12/13/2004 17:15'! pushLiteralVariable: anAssociation "Push Contents Of anAssociation On Top Of Stack bytecode." | info | contextCount > 0 ifTrue:[^self]. info := ECTypeInfo definedByMessageSend: anAssociation value. types add: info! ! !ECVarTypeGuesser methodsFor: 'bytecode decoding' stamp: 'bar 12/13/2004 17:15'! pushTemporaryVariable: offset "Push Contents Of Temporary Variable Whose Index Is the argument, offset, On Top Of Stack bytecode." | info | contextCount > 0 ifTrue:[^self]. info := ECTypeInfo definedByTemporaryVar: offset. types add: info! ! !ECVarTypeGuesser methodsFor: 'private' stamp: 'bar 12/13/2004 17:14'! reset contextCount > 0 ifTrue:[^self]. types reset. hasSend := false.! ! !ECVarTypeGuesser methodsFor: 'bytecode decoding' stamp: 'bar 12/13/2004 17:15'! send: selector super: supered numArgs: numberArguments "Send Message With Selector, selector, bytecode. The argument, supered, indicates whether the receiver of the message is specified with 'super' in the source method. The arguments of the message are found in the top numArguments locations on the stack and the receiver just below them." contextCount > 0 ifTrue:[^self]. hasSend := true! ! !ECVarTypeGuesser methodsFor: 'instance creation' stamp: 'bar 12/13/2004 13:55'! setVariableName: aString source: aSourceString class: aClass variableName := aString. receiverClass := aClass! ! !ECVarTypeGuesser methodsFor: 'bytecode decoding' stamp: 'lr 7/4/2009 10:42'! typeOfVarIn: aMethod "Answer whether the receiver references an instance variable." | scanner end type infos | scanner := InstructionStream on: aMethod. end := scanner method endPC. currentMethod := aMethod. infos := OrderedCollection new. [ scanner pc <= end ] whileTrue: [ (self interpretNextInstructionUsing: scanner) ifTrue: [ type := self computeVarType. type ifNotNil: [ infos add: type ] ] ]. ^ infos! ! !Debugger methodsFor: '*ecompletion' stamp: 'lr 3/26/2010 13:53'! guessTypeForName: aString | index object | index := self selectedContext tempNames indexOf: aString ifAbsent: [ nil ]. object := index isNil ifFalse: [ self selectedContext namedTempAt: index ] ifTrue: [ index := self receiver class allInstVarNames indexOf: aString ifAbsent: [ ^ super guessTypeForName: aString ]. self receiver instVarAt: index ]. ^ object class ! ! TestCase subclass: #ECClassVarTypeGuesserTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'ECompletion-Tests'! !ECClassVarTypeGuesserTest methodsFor: 'as yet unclassified' stamp: 'lr 7/4/2009 10:42'! guessVariable: aString in: aClass expected: theClassExpected | typeGuesser result | typeGuesser := ECClassVarTypeGuesser variableName: aString class: aClass. result := typeGuesser perform. self assert: result == theClassExpected! ! !ECClassVarTypeGuesserTest methodsFor: 'as yet unclassified' stamp: 'bar 8/11/2005 13:14'! testClassVar self guessVariable: 'ClassVar' in: ECTestClass expected: ByteString! ! !ECClassVarTypeGuesserTest methodsFor: 'as yet unclassified' stamp: 'bar 8/11/2005 13:57'! testDependentsFieldsClassVar self guessVariable: 'DependentsFields' in: ECTestClass expected: WeakIdentityKeyDictionary! ! !ECClassVarTypeGuesserTest methodsFor: 'as yet unclassified' stamp: 'bar 8/11/2005 13:23'! testSuperClassVar self guessVariable: 'SuperClassVar' in: ECTestClass expected: Dictionary ! ! TestCase subclass: #ECContextTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'ECompletion-Tests'! !ECContextTest methodsFor: 'private' stamp: 'lr 7/4/2009 10:42'! checkUntypedVariablesOnly: aString | context model | context := self createContextFor: aString at: aString size. self assert: context isVariablesOnly. model := context model. self assert: model hasMessage not. self assert: (model entriesOfType: #instVar) notEmpty. context narrowWith: 'a'. self assert: (model entriesOfType: #selector) isEmpty! ! !ECContextTest methodsFor: 'private' stamp: 'bar 12/13/2004 15:46'! createContextFor: aString at: anInteger ^ ECContext controller: ECController new class: ECTestClass source: aString position: anInteger! ! !ECContextTest methodsFor: 'as yet unclassified' stamp: 'lr 7/4/2009 10:42'! testBlockTemporaries | text temps context | text := 'testIt | a b c | a _ [ :each | |d | ^d]. ^self'. context := self createContextFor: text at: 39. temps := context temporaries collect: [ :each | each contents ]. self assert: temps size = 5. self assert: temps first = 'a'. self assert: temps second = 'b'. self assert: temps third = 'c'. self assert: temps fourth = 'each'. self assert: temps fifth = 'd'! ! !ECContextTest methodsFor: 'as yet unclassified' stamp: 'lr 7/4/2009 10:42'! testBlockTemporariesBoxed | text temps context | text := 'testIt | a b c | a _ [ :each | |d | d = a ifTrue:[ |x| ] ifFalse:[ |y|. ^self'. context := self createContextFor: text at: 73. temps := context temporaries collect: [ :each | each contents ]. self assert: temps size = 6. self assert: temps first = 'a'. self assert: temps second = 'b'. self assert: temps third = 'c'. self assert: temps fourth = 'each'. self assert: temps fifth = 'd'. self assert: temps sixth = 'y'! ! !ECContextTest methodsFor: 'as yet unclassified' stamp: 'bar 12/11/2004 23:42'! testCompletionToken | text context | text := 'testIt: aRectangle | abc | test. abc daf'. context := self createContextFor: text at: text size. self assert: context completionToken = 'daf'! ! !ECContextTest methodsFor: 'as yet unclassified' stamp: 'bar 12/12/2004 10:06'! testCompletionTokenEmpty | text context | text := 'testIt: aRectangle | abc | test. abc daf '. context := self createContextFor: text at: text size. self assert: context completionToken = ''! ! !ECContextTest methodsFor: 'as yet unclassified' stamp: 'bar 12/13/2004 10:40'! testCreateModel | text context | text := 'testIt: aRectangle aRectangle printS'. context := self createContextFor: text at: text size. self assert: context createModel class == ECTypedModel. text := 'testIt:'. context := self createContextFor: text at: text size. self assert: context createModel class = ECOverrideModel. text := 'testIt: rect rect is'. context := self createContextFor: text at: text size. self assert: context createModel class = ECUntypedModel! ! !ECContextTest methodsFor: 'as yet unclassified' stamp: 'bar 1/6/2005 22:00'! testEmpty self createContextFor: '' at: 0! ! !ECContextTest methodsFor: 'as yet unclassified' stamp: 'lr 7/4/2009 10:42'! testInTheMiddelOfAWord | text context | text := 'hagada'. context := self createContextFor: text at: 4. self assert: context completionToken = 'haga'! ! !ECContextTest methodsFor: 'as yet unclassified' stamp: 'lr 7/4/2009 10:42'! testReceiverArgument | text context | text := 'testIt: aRectangle aRectangle printS'. context := self createContextFor: text at: text size. self assert: context receiverClass == Rectangle. text := 'testIt: rect rect is'. context := self createContextFor: text at: text size. self assert: context receiverClass isNil! ! !ECContextTest methodsFor: 'as yet unclassified' stamp: 'bar 12/13/2004 09:45'! testReceiverCascade | text context | text := 'testIt | b | b _ Stream new. b nextPutAll: ''test''; nextPut: $c; s'. context := self createContextFor: text at: text size. self assert: context receiverClass == Stream. text := 'testIt | b | b _ Stream new nextPutAll: ''test''; nextPut: $c with: true; s'. context := self createContextFor: text at: text size. self assert: context receiverClass == Stream. text := 'testIt: aStream | test | aStream nextPutAll: ''test''; nextPut: $c with: true; s'. context := self createContextFor: text at: text size. self assert: context receiverClass == Stream. text := 'testIt: aStream aStream nextPutAll: ''test''; nextPut: $c with: true; s'. context := self createContextFor: text at: text size. self assert: context receiverClass == Stream! ! !ECContextTest methodsFor: 'as yet unclassified' stamp: 'lr 7/4/2009 10:42'! testReceiverClassVar | text context | text := 'testIt ClassVar '. context := self createContextFor: text at: text size. self assert: context receiverClass == ByteString! ! !ECContextTest methodsFor: 'as yet unclassified' stamp: 'bar 12/12/2004 23:03'! testReceiverConstant | text context | text := 'testIt 15r16 printS'. context := self createContextFor: text at: text size. self assert: context receiverClass == Number. text := 'testIt ''test'' printS'. context := self createContextFor: text at: text size. self assert: context receiverClass == String. text := 'testIt true ifTrue:'. context := self createContextFor: text at: text size. self assert: context receiverClass == True. text := 'testIt false "this is it" printStr'. context := self createContextFor: text at: text size. self assert: context receiverClass == False. text := 'testIt a _ [ :test | test * test ] v'. context := self createContextFor: text at: text size. self assert: context receiverClass == BlockContext. text := 'testIt $c as'. context := self createContextFor: text at: text size. self assert: context receiverClass == Character. text := 'testIt #gaga as'. context := self createContextFor: text at: text size. self assert: context receiverClass == Symbol. text := 'testIt #( 1 2 3) as'. context := self createContextFor: text at: text size. self assert: context receiverClass == Array. ! ! !ECContextTest methodsFor: 'as yet unclassified' stamp: 'bar 12/12/2004 22:38'! testReceiverGlobal | text context | text := 'testIt Dictionary n'. context := self createContextFor: text at: text size. self assert: context receiverClass == Dictionary class. ! ! !ECContextTest methodsFor: 'as yet unclassified' stamp: 'bar 12/12/2004 23:05'! testReceiverGlobalVarNew | text context | text := 'testIt Dictionary new a'. context := self createContextFor: text at: text size. self assert: context receiverClass == Dictionary. ! ! !ECContextTest methodsFor: 'as yet unclassified' stamp: 'lr 7/4/2009 10:42'! testReceiverTempVar | text context | text := 'testIt | aha | aha _ ''test''. aha p'. context := self createContextFor: text at: text size. self assert: context receiverClass == String. text := 'testIt | aha | ah _ ''test''. ah p'. context := self createContextFor: text at: text size. self assert: context receiverClass isNil. text := 'testIt | aha | aha _ constantString. aha p'. context := self createContextFor: text at: text size. self assert: context receiverClass == ByteString. text := 'testIt | aha | aha _ constant asDate. aha p'. context := self createContextFor: text at: text size. self assert: context receiverClass isNil. text := 'testIt | aha bili | aha _ constantString. bili _ aha. bili p'. context := self createContextFor: text at: text size. self assert: context receiverClass == ByteString. text := 'testIt | aha bili | aha _ constantString. bili _ aha _ 15. bili p'. context := self createContextFor: text at: text size. self assert: context receiverClass = Number. text := 'testIt | aha bili | aha _ constantString. bili _ 15. bili _ aha. bili p'. context := self createContextFor: text at: text size. self assert: context receiverClass == Number. text := 'testIt [ :each | |a| a _ 16. a print'. context := self createContextFor: text at: text size. self assert: context receiverClass == Number. text := 'testIt [ :each | |a| a _ Dictionary new. a print'. context := self createContextFor: text at: text size. self assert: context receiverClass == Dictionary. text := 'testIt [ :each | |a| a _ Dictionary. a print'. context := self createContextFor: text at: text size. self assert: context receiverClass == Dictionary class! ! !ECContextTest methodsFor: 'as yet unclassified' stamp: 'bar 12/13/2004 16:28'! testReceiverTempVar2 | text context | text := 'openMenuFor: aParagraphEditor | theMenu | context := ECContext controller: self class: model receiverClass source: aParagraphEditor text string position: aParagraphEditor caret - 1. editor := aParagraphEditor. theMenu := ECMenuMorph controller: self position: (aParagraphEditor selectionPosition: context completionToken). theMenu isClosed ifFalse: [menuMorph := theMenu]. theMenu o'. context := self createContextFor: text at: text size. self assert: context receiverClass == ECMenuMorph! ! !ECContextTest methodsFor: 'as yet unclassified' stamp: 'lr 7/4/2009 10:42'! testTemporaries | text temps context | text := 'testIt: aRectangle | a b c | a _ [ :each | |d | ^d]. ^self'. context := self createContextFor: text at: text size. temps := context temporaries collect: [ :each | each contents ]. self assert: temps size = 4. self assert: temps first = 'aRectangle'. self assert: temps second = 'a'. self assert: temps third = 'b'. self assert: temps fourth = 'c'! ! !ECContextTest methodsFor: 'as yet unclassified' stamp: 'lr 7/4/2009 10:42'! testUnfinishedString | text context | text := 'testIt: aRectangle | a b c | self test: ''test it and so'. context := self createContextFor: text at: text size. self assert: context completionToken = 'so'! ! !ECContextTest methodsFor: 'as yet unclassified' stamp: 'lr 7/4/2009 10:42'! testUntypedSelectorsOnly | text context model | text := 'testIt: aRectangle | ab bc bd | ab '. context := self createContextFor: text at: text size. model := context model. self assert: model hasMessage. self assert: model message = 'press key for selectors'. context narrowWith: 'a'. self assert: (model entriesOfType: #selector) notEmpty. self assert: (model entriesOfType: #local) isEmpty. self assert: (model entriesOfType: #instance) isEmpty! ! !ECContextTest methodsFor: 'as yet unclassified' stamp: 'bar 3/9/2006 10:10'! testUntypedVarsOnly self checkUntypedVariablesOnly: 'testIt '. self checkUntypedVariablesOnly: '+ aTest '. self checkUntypedVariablesOnly: 'gaga: aTest '. self checkUntypedVariablesOnly: 'gaga ^ '. self checkUntypedVariablesOnly: 'testIt a ifTrue:[ '. self checkUntypedVariablesOnly: 'testIt a ifTrue:[ :each'. self checkUntypedVariablesOnly: 'testIt a ifTrue:[ :each |'. self checkUntypedVariablesOnly: 'testIt a ifTrue:[ :each | '. self checkUntypedVariablesOnly: 'testIt '. self checkUntypedVariablesOnly: 'testIt ab _'. self checkUntypedVariablesOnly: 'testIt ab _ '. self checkUntypedVariablesOnly: 'self compare: '. self checkUntypedVariablesOnly: 'self compare: x caseSensitive: '. self checkUntypedVariablesOnly: 'self gaga: x gugu: ('. self checkUntypedVariablesOnly: 'testIt a _ 15 + '. self checkUntypedVariablesOnly: 'testIt self hugatada: '! ! TestCase subclass: #ECEntryTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'ECompletion-Tests'! !ECEntryTest methodsFor: 'as yet unclassified' stamp: 'lr 7/4/2009 10:42'! testCompletion | entry | entry := ECSelectorEntry contents: 'makeItHappen' type: #unary:. self assert: entry completion = #makeItHappen! ! !ECEntryTest methodsFor: 'as yet unclassified' stamp: 'lr 7/4/2009 10:42'! testInstance | entry | entry := ECInstVarEntry contents: 'abc' type: #instVar:. self assert: entry isInstance! ! !ECEntryTest methodsFor: 'as yet unclassified' stamp: 'lr 7/4/2009 10:42'! testLocal | entry | entry := ECLocalEntry contents: 'abc' type: #patternArg:. self assert: entry contents = 'abc'. self assert: entry type = #patternArg:. self assert: entry isLocal! ! !ECEntryTest methodsFor: 'as yet unclassified' stamp: 'lr 7/4/2009 10:42'! testPrintOn | entry | entry := ECSelectorEntry contents: 'compute' type: #unary:. self assert: 'ECSelectorEntry(compute,unary:)' = entry printString! ! TestCase subclass: #ECInstVarTypeGuesserTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'ECompletion-Tests'! !ECInstVarTypeGuesserTest methodsFor: 'private' stamp: 'lr 7/4/2009 10:42'! guessVariable: aString in: aClass expected: theClassExpected | typeGuesser result | typeGuesser := ECInstVarTypeGuesser variableName: aString class: aClass. result := typeGuesser perform. self assert: result == theClassExpected! ! !ECInstVarTypeGuesserTest methodsFor: 'testing' stamp: 'bar 3/30/2006 17:06'! testComplexInit self guessVariable: 'complexInit' in: ECTestClass expected: nil! ! !ECInstVarTypeGuesserTest methodsFor: 'testing' stamp: 'bar 12/13/2004 10:41'! testComplexInit2 self guessVariable: 'complexInit2' in: ECTestClass expected: Dictionary! ! !ECInstVarTypeGuesserTest methodsFor: 'testing' stamp: 'bar 12/13/2004 13:46'! testConstantArray self guessVariable: 'constantArray' in: ECTestClass expected: Array! ! !ECInstVarTypeGuesserTest methodsFor: 'testing' stamp: 'bar 12/13/2004 13:46'! testConstantBoolean self guessVariable: 'constantBoolean' in: ECTestClass expected: True! ! !ECInstVarTypeGuesserTest methodsFor: 'testing' stamp: 'bar 12/13/2004 13:47'! testConstantInteger self guessVariable: 'constantInteger' in: ECTestClass expected: SmallInteger! ! !ECInstVarTypeGuesserTest methodsFor: 'testing' stamp: 'bar 12/13/2004 13:47'! testConstantIntegerNil self guessVariable: 'constantNil' in: ECTestClass expected: nil! ! !ECInstVarTypeGuesserTest methodsFor: 'testing' stamp: 'bar 8/6/2005 22:33'! testConstantString self guessVariable: 'constantString' in: ECTestClass expected: ByteString! ! !ECInstVarTypeGuesserTest methodsFor: 'testing' stamp: 'bar 8/4/2005 21:30'! testConstantSymbol self guessVariable: 'constantSymbol' in: ECTestClass expected: ByteSymbol! ! !ECInstVarTypeGuesserTest methodsFor: 'testing' stamp: 'bar 12/13/2004 16:42'! testGlobalVarKeyword self guessVariable: 'globalVarKeyword' in: ECTestClass expected: SortedCollection! ! !ECInstVarTypeGuesserTest methodsFor: 'testing' stamp: 'bar 12/13/2004 17:19'! testGlobalVarKeyword2 self guessVariable: 'globalVarKeyword2' in: ECTestClass expected: SortedCollection! ! !ECInstVarTypeGuesserTest methodsFor: 'testing' stamp: 'bar 12/13/2004 13:47'! testMessageSend self guessVariable: 'messageSend' in: ECTestClass expected: Dictionary! ! !ECInstVarTypeGuesserTest methodsFor: 'testing' stamp: 'bar 2/20/2006 15:12'! testMessageSend2 self guessVariable: 'messageSend2' in: ECTestClass expected: nil! ! !ECInstVarTypeGuesserTest methodsFor: 'testing' stamp: 'bar 12/13/2004 13:48'! testSuperWithAnotherInit self guessVariable: 'superInstVar' in: ECTestClass expected: Dictionary! ! !ECInstVarTypeGuesserTest methodsFor: 'testing' stamp: 'bar 12/13/2004 13:48'! testTypeSuggestingParameter self guessVariable: 'typeSuggestingParameter2' in: ECTestClass expected: Rectangle! ! TestCase subclass: #ECOverrideModelTest instanceVariableNames: 'model' classVariableNames: '' poolDictionaries: '' category: 'ECompletion-Tests'! !ECOverrideModelTest methodsFor: 'testing' stamp: 'bar 12/13/2004 10:41'! setUp model := ECOverrideModel class: ECTestClass. model toggleExpand! ! !ECOverrideModelTest methodsFor: 'testing' stamp: 'bar 12/6/2004 17:10'! testCompletionAt | completion | completion := model completionAt: 2. self assert: completion = 'toBeOverriden: anArgument super toBeOverriden: anArgument'! ! !ECOverrideModelTest methodsFor: 'testing' stamp: 'lr 7/3/2010 16:32'! testCompletionAtWithReturn | completion | completion := model completionAt: 3. self assert: completion = 'toBeOverridenWithReturn ^ super toBeOverridenWithReturn'! ! !ECOverrideModelTest methodsFor: 'testing' stamp: 'bar 12/6/2004 17:10'! testExpand | size | size := model entries size. self assert: size == model entries size! ! !ECOverrideModelTest methodsFor: 'testing' stamp: 'bar 12/6/2004 17:11'! testOverride | selectors | self assert: model notEmpty. self assert: model entries size = 3. selectors := model entriesOfType: #selector. self assert: (selectors includes: #toBeOverriden:). self assert: (selectors includes: #initialize). self assert: (selectors includes: #toBeOverridenWithReturn)! ! !ECOverrideModelTest methodsFor: 'testing' stamp: 'bar 12/13/2004 10:46'! testTitle self assert: '(override) ECTestSuperClass' = model title! ! TestCase subclass: #ECStringSortingTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'ECompletion-Tests'! !ECStringSortingTest methodsFor: 'as yet unclassified' stamp: 'lr 3/17/2010 20:15'! testCaseSensitiveMap | map colon o | map := String classPool at: #CaseSensitiveOrder. colon := map at: $: asciiValue + 1. o := map at: $O asciiValue + 1. self assert: colon > o! ! !ECStringSortingTest methodsFor: 'as yet unclassified' stamp: 'bar 8/6/2005 20:55'! testCompare self assert: ('at:' compare: 'atOne' caseSensitive: false) == 1! ! !ECStringSortingTest methodsFor: 'as yet unclassified' stamp: 'lr 3/17/2010 20:15'! testCompareWithCase self assert: ('at:' compare: 'atOne' caseSensitive: true) == 3! ! TestCase subclass: #ECTypedModelTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'ECompletion-Tests'! !ECTypedModelTest methodsFor: 'as yet unclassified' stamp: 'lr 7/4/2009 10:42'! testExpand | model selectors | model := ECTypedModel class: ECTestClass. self assert: (model entriesOfType: #locals) isEmpty. self assert: (model entriesOfType: #instance) isEmpty. model toggleExpand. selectors := model entriesOfType: #selector. self assert: selectors size == 6. self assert: (selectors includes: #initialize). self assert: (selectors includes: #lowPriorityOverrides:). self assert: (selectors includes: #testIt:). model toggleExpand. selectors := model entriesOfType: #selector. self assert: selectors size > 100. self assert: (selectors includes: #instVarAt:). self assert: (selectors includes: #initialize). self assert: (selectors includes: #lowPriorityOverrides:). self assert: (selectors includes: #testIt:). self assert: (selectors includes: #instVarAt:). model toggleExpand. selectors := model entriesOfType: #selector. self assert: selectors size == 6! ! !ECTypedModelTest methodsFor: 'as yet unclassified' stamp: 'bar 12/17/2004 22:44'! testMessage | model | model := ECTypedModel class: ECTestClass. self shouldnt: model hasMessage. model narrowWith: 'hagadagadu'. self assert: model hasMessage. self assert: model message = 'no completions found'! ! !ECTypedModelTest methodsFor: 'as yet unclassified' stamp: 'bar 12/13/2004 10:45'! testTitle | model | model := ECTypedModel class: ECTestClass. self assert: 'ECTestClass' = model title! ! !ECTypedModelTest methodsFor: 'as yet unclassified' stamp: 'bar 12/13/2004 10:41'! testTyped | model selectors | model := ECTypedModel class: ECTestClass. self assert: (model entriesOfType: #locals) size == 0. self assert: (model entriesOfType: #instance) size == 0. selectors := model entriesOfType: #selector. self assert: selectors size > 0. self assert: (selectors includes: #initialize). self assert: (selectors includes: #lowPriorityOverrides:). self assert: (selectors includes: #testIt:). model narrowWith: 'low'. selectors := model entriesOfType: #selector. self deny: (selectors includes: #initialize). self assert: (selectors includes: #lowPriorityOverrides:). self deny: (selectors includes: #testIt:)! ! TestCase subclass: #ECUntypedModelTest instanceVariableNames: 'prefValueCase' classVariableNames: '' poolDictionaries: '' category: 'ECompletion-Tests'! !ECUntypedModelTest methodsFor: 'testing' stamp: 'lr 3/17/2010 20:10'! setUp prefValueCase := ECPreferences caseSensitive. ECPreferences caseSensitive: true! ! !ECUntypedModelTest methodsFor: 'testing' stamp: 'lr 3/17/2010 20:10'! tearDown ECPreferences caseSensitive: prefValueCase! ! !ECUntypedModelTest methodsFor: 'testing' stamp: 'lr 7/4/2009 10:42'! testAdditionalLocals | model locals | model := ECUntypedModel class: ECTestClass temporaries: (OrderedCollection with: (ECLocalEntry contents: 'a' type: #local) with: (ECLocalEntry contents: 'b' type: #local)) additionals: (Array with: (ECLocalEntry contents: 'veryImp' type: #local)) variables: true selectors: true. locals := model entriesOfType: #local. self assert: (locals includes: 'veryImp')! ! !ECUntypedModelTest methodsFor: 'testing' stamp: 'lr 7/4/2009 10:42'! testCaseSensitive | model locals | self assert: ECPreferences caseSensitive. model := ECUntypedModel class: ECTestClass temporaries: OrderedCollection new. locals := model entriesOfType: #instVar. self assert: locals size == 17. self assert: (locals includes: 'third'). self assert: (locals includes: 'constantInteger'). self assert: (locals includes: 'complexInit2'). self assert: (locals includes: 'typeSuggestingParameter'). model narrowWith: 'fo'! ! !ECUntypedModelTest methodsFor: 'testing' stamp: 'lr 3/17/2010 20:12'! testCaseSensitivity | model instances | self assert: ECPreferences caseSensitive. model := ECUntypedModel class: ECTestClass temporaries: OrderedCollection new. model narrowWith: 'typesugg'. self assert: model isEmpty. ECPreferences caseSensitive: false. model narrowWith: 'typesugg'. instances := model entriesOfType: #instVar. self assert: instances size == 2. self assert: (instances includes: 'typeSuggestingParameter'). model narrowWith: 'dict'. self assert: model notEmpty. self assert: ((model entriesOfType: #selector) includes: 'Dictionary')! ! !ECUntypedModelTest methodsFor: 'testing' stamp: 'bar 12/13/2004 10:40'! testEmpty | model | model := ECUntypedModel new. self assert: model isEmpty. self assert: model entries isEmpty. self assert: model entryCount == 0! ! !ECUntypedModelTest methodsFor: 'testing' stamp: 'lr 7/4/2009 10:42'! testForClassInstVars | model locals | model := ECUntypedModel class: ECTestClass temporaries: OrderedCollection new. locals := model entriesOfType: #instVar. self assert: locals size == 17. self assert: (locals includes: 'third'). self assert: (locals includes: 'constantInteger'). self assert: (locals includes: 'complexInit2'). self assert: (locals includes: 'typeSuggestingParameter'). locals := model entriesOfType: #self. self assert: (locals includes: 'self'). locals := model entriesOfType: #super. self assert: (locals includes: 'super'). model narrowWith: 'fo'. locals := model entriesOfType: #instVar. self assert: locals size == 1. self assert: (locals includes: 'fourth')! ! !ECUntypedModelTest methodsFor: 'testing' stamp: 'lr 7/4/2009 10:42'! testForClassLocals | model locals temps | temps := #('loc1' 'x2' 'bar' 'var' ) collect: [ :each | ECLocalEntry contents: each type: #local ]. model := ECUntypedModel class: ECTestClass temporaries: temps. locals := model entriesOfType: #local. self assert: locals size == 4. self assert: (locals includes: 'loc1'). self assert: (locals includes: 'x2'). self assert: (locals includes: 'bar'). self assert: (locals includes: 'var'). model narrowWith: 'l'. locals := model entriesOfType: #local. self assert: locals size == 1. self assert: (locals includes: 'loc1')! ! !ECUntypedModelTest methodsFor: 'testing' stamp: 'lr 7/4/2009 10:42'! testForClassVars | model classVars | model := ECUntypedModel class: ECTestClass temporaries: OrderedCollection new. classVars := model entriesOfType: #classVar. self assert: classVars size >= 2. self assert: (classVars includes: 'SuperClassVar'). self assert: (classVars includes: 'ClassVar')! ! !ECUntypedModelTest methodsFor: 'testing' stamp: 'lr 7/4/2009 10:42'! testMessage | model | model := ECUntypedModel class: ECTestClass temporaries: #('a' 'b' ). self assert: model notEmpty. self assert: model hasMessage. self assert: model message = 'press key for selectors'. model narrowWith: 'b'. self shouldnt: model hasMessage. model narrowWith: ''. self assert: model hasMessage. self assert: model message = 'press key for selectors'. model narrowWith: 'hagadagadu'. self assert: model hasMessage. self assert: model message = 'no completions found'. model := ECUntypedModel new. self assert: model hasMessage. self assert: model message = 'press key for selectors'! ! !ECUntypedModelTest methodsFor: 'testing' stamp: 'bar 12/13/2004 10:40'! testNarrowWith | count model | model := ECUntypedModel new. self assert: model isEmpty. model narrowWith: 'b'. count := model entryCount. self assert: count == model entries size. self assert: count > 100. model narrowWith: 'bar'. self assert: count > model entryCount. model narrowWith: 'barXXXX'. self assert: model isEmpty. model narrowWith: 'b'. self assert: count == model entryCount. model narrowWith: 'save'. self assert: model isEmpty not. model narrowWith: ''. self assert: model isEmpty! ! !ECUntypedModelTest methodsFor: 'testing' stamp: 'bar 12/13/2004 10:40'! testNoEntriesWithSpace | model separatorEntry | model := ECUntypedModel new. self assert: model isEmpty. model narrowWith: 'b'. separatorEntry := model entries detect: [:each | (each value asString detect: [:char | char isSeparator] ifNone: []) notNil] ifNone: []. self assert: separatorEntry isNil! ! !ECUntypedModelTest methodsFor: 'testing' stamp: 'bar 12/13/2004 14:03'! testTitle | model | model := ECUntypedModel class: ECTestClass temporaries: #(). self assert: model title isNil! ! SystemWindow subclass: #ECHelpMorph instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'ECompletion-View'! !ECHelpMorph commentStamp: '' prior: 0! I am a system window that displays the keybindings of eCompletion. The text is static and generated in the class methods.! !ECHelpMorph class methodsFor: 'private' stamp: 'bar 3/30/2006 14:27'! explanationAttributes ^{TextIndent spaceUsed; tabs: 2}! ! !ECHelpMorph class methodsFor: 'help-text' stamp: 'lr 7/4/2009 10:42'! helpText | stream | stream := TextStream on: Text new. self section: 'character completion' on: stream. self shortcut: 'works on' text: ' [] {} () <> '''' ""' on: stream. self shortcut: 'usage 1' text: 'enter open character - closing character is entered as well' on: stream. self shortcut: 'usage 2' text: 'select some text, enter a smart character and the selected text get surrounded by the opening and closing character.' on: stream. self section: 'open/close menu' on: stream. self shortcut: 'ctrl-space or tab' text: 'open the completion menu' on: stream. self shortcut: 'ESC' text: 'close menu' on: stream. self shortcut: 'ctrl-h' text: 'open this help' on: stream. self section: 'menu navigation' on: stream. self shortcut: 'Arrows up/down' text: 'move the selection up and down' on: stream. self shortcut: 'Page up/down' text: 'page up and down' on: stream. self shortcut: 'Home/End' text: 'move to first or last page of the menu' on: stream. self section: 'show details and browse' on: stream. self shortcut: 'right arrow (detail closed)' text: 'show details about the selected item. This may be the type of the variable, the source of a method or the implementors of the selector.' on: stream. self shortcut: 'right arrow (detail open)' text: 'open a new browser for the selected item.' on: stream. self shortcut: 'left arrow' text: 'close the details' on: stream. self section: 'changing menu contents' on: stream. self shortcut: 'ctrl-u' text: 'switch to untyped mode in a typed menu' on: stream. self shortcut: 'ctrl-t' text: 'filter out methods of class Object in a typed menu. press again to make the reappear.' on: stream. self shortcut: 'alphanumeric character' text: 'filter the menu to the given input' on: stream. self shortcut: 'backspace' text: 'delete an input character, adjust menu to the new input.' on: stream. self section: 'inserting completion' on: stream. self shortcut: 'ctrl-space or tab' text: 'close the menu and insert selected completion. if there only one item left in the menu this done automaticly.' on: stream. ^ stream contents! ! !ECHelpMorph class methodsFor: 'private' stamp: 'bar 3/12/2006 12:26'! section: aString on: aTextStream aTextStream withAttributes: self sectionAttributes do: [aTextStream nextPutAll: aString]. aTextStream cr! ! !ECHelpMorph class methodsFor: 'private' stamp: 'bar 3/12/2006 12:14'! sectionAttributes ^ {TextEmphasis bold}! ! !ECHelpMorph class methodsFor: 'private' stamp: 'bar 3/12/2006 14:30'! shortcut: aString text: secondString on: aTextStream aTextStream withAttributes: self shortcutAttributes do: [aTextStream nextPutAll: aString; cr]. aTextStream withAttributes: self explanationAttributes do: [aTextStream nextPutAll: secondString; cr]. ! ! !ECHelpMorph class methodsFor: 'private' stamp: 'bar 3/30/2006 14:27'! shortcutAttributes ^ {TextIndent spaceUsed; tabs: 1. TextEmphasis italic }! ! !ECHelpMorph methodsFor: 'initialize' stamp: 'bar 3/12/2006 14:26'! contents ^self class helpText ! ! !ECHelpMorph methodsFor: 'initialize' stamp: 'bar 3/12/2006 13:04'! defaultColor ^ ECMenuMorph backgroundColor! ! !ECHelpMorph methodsFor: 'initialize' stamp: 'bar 3/20/2006 15:35'! initialize "textMorph _ TextMorph new contents: self class helpText; yourself. self addMorph: textMorph" | text | super initialize. self setLabel: 'eCompletion Keyboard Help'. "self height: ECMenuMorph itemHeight * 60." text := PluggableTextMorph on: self text: #contents accept: nil readSelection: nil menu: nil. self addMorph: text frame: (0 @ 0 corner: 1.0 @ 1.0). text lock.! ! Object subclass: #ECContext instanceVariableNames: 'source position theClass ranges completionIndex recurseCount receiverClass completionToken model controller variables selectors' classVariableNames: '' poolDictionaries: '' category: 'ECompletion-Model'! !ECContext commentStamp: '' prior: 0! A completion is started by the ECController. The controller creates me to compute the context of the completion. The most important information about the context are the receiverClass and the completionToken. I create a ECModel or subclass when requested by the 'model' method. I use SHParser and SHRange to parse the text input.! !ECContext class methodsFor: 'instance creation' stamp: 'bar 4/11/2005 11:23'! controller: aECController class: aClass source: aString position: anInteger ^ self basicNew initialize setController: aECController class: aClass source: aString position: anInteger! ! !ECContext methodsFor: 'private-temporaries' stamp: 'lr 7/4/2009 10:42'! blockTemporaries | blocks range vars | blocks := OrderedCollection new. 1 to: completionIndex - 1 do: [ :index | range := ranges at: index. self handleBlockStack: blocks with: range. range isBlockTemporary ifTrue: [ vars := blocks last. vars add: range ] ]. ^ self convertBlocksToVariables: blocks! ! !ECContext methodsFor: 'private-compute-index' stamp: 'bar 1/6/2005 22:06'! checkForZeroPosition ^ (position = 0 or: [ranges isEmpty]) and: [self insertEmptyRangeAt: 1 start: 0 end: 1. true]! ! !ECContext methodsFor: 'private-receiver-guessing' stamp: 'bar 1/9/2005 14:55'! checkImpossibleReceiver ^ self isSelectorsAndVariables ifTrue: [self configureSelectorsAndVariables] ifFalse: [self isVariablesOnly ifTrue: [self configureVariablesOnly] ifFalse: [self isSelectorsOnly and: [self configureSelectorsOnly]]]. ! ! !ECContext methodsFor: 'accessing' stamp: 'lr 7/4/2009 10:42'! completionToken completionToken ifNil: [ | range | range := ranges at: completionIndex. completionToken := self sourceOf: range stopAt: position. completionToken := completionToken wordBefore: completionToken size ]. ^ completionToken! ! !ECContext methodsFor: 'private' stamp: 'lr 7/4/2009 10:42'! compute completionIndex := self computeIndexOfPosition. receiverClass := self computeReceiverClass! ! !ECContext methodsFor: 'private-compute-index' stamp: 'lr 7/4/2009 10:42'! computeIndexOfPosition | current | self checkForZeroPosition ifTrue: [ ^ 1 ]. 1 to: ranges size do: [ :index | current := ranges at: index. (current includesPosition: position) ifTrue: [ ^ index ] ifFalse: [ current end > position ifTrue: [ ^ self createEmptyRangeForGapAt: index ] ] ]. ^ self createEmptyRangeAtTail! ! !ECContext methodsFor: 'private' stamp: 'bar 1/9/2005 11:35'! computeReceiverClass | previous found | recurseCount := 0. completionIndex = 1 ifTrue: [^nil]. found := self checkImpossibleReceiver. found ifTrue: [^nil]. previous := ranges at: completionIndex - 1. previous type = #cascadeSeparator ifTrue: [^self guessCascadeReceiver: completionIndex - 1]. (previous type = #unary and: [(self sourceOf: previous) = 'new' and: [completionIndex > 2]]) ifTrue: [previous := ranges at: completionIndex - 2. previous type = #globalVar ifTrue: [^self guessTypeOf: completionIndex - 2] ifFalse: [self configureSelectorsOnly. ^nil]]. ^self guessTypeOf: completionIndex - 1! ! !ECContext methodsFor: 'private-configure' stamp: 'bar 1/9/2005 11:35'! configureSelectorsAndVariables variables := true. selectors := true. ^true! ! !ECContext methodsFor: 'private-configure' stamp: 'bar 1/9/2005 11:35'! configureSelectorsOnly variables := false. selectors := true. ^true! ! !ECContext methodsFor: 'private-configure' stamp: 'bar 1/9/2005 11:34'! configureVariablesOnly variables := true. selectors := false. ^true! ! !ECContext methodsFor: 'private-temporaries' stamp: 'lr 7/4/2009 10:42'! convertBlocksToVariables: anOrderedCollection | result blockStack | blockStack := anOrderedCollection. result := OrderedCollection new. blockStack do: [ :each | result addAll: each ]. ^ result! ! !ECContext methodsFor: 'private-compute-index' stamp: 'lr 7/4/2009 10:42'! createEmptyRangeAtTail | previous | previous := ranges last. ranges add: (SHRange start: previous end + 1 end: source size type: #empty). ^ ranges size! ! !ECContext methodsFor: 'private-compute-index' stamp: 'lr 7/4/2009 10:42'! createEmptyRangeForGapAt: index | current previous | current := ranges at: index. previous := ranges at: index - 1. self insertEmptyRangeAt: index start: previous end + 1 end: current start - 1. ^ index! ! !ECContext methodsFor: 'accessing' stamp: 'dr 10/30/2008 17:15'! createModel | modelClass | self receiverClass ifNotNil: [^ ECTypedModel class: receiverClass]. (controller workspace isNil and: [theClass notNil]) ifTrue: [completionIndex = 1 ifTrue: [^ ECOverrideModel class: theClass]]. modelClass := ECUntypedModel. (controller model respondsTo: #modelClass) ifTrue: [controller model modelClass ifNotNilDo: [:class | modelClass := class]]. ^ modelClass class: theClass temporaries: self temporaries additionals: controller additionals variables: variables selectors: selectors! ! !ECContext methodsFor: 'private' stamp: 'bar 1/6/2005 14:35'! createRanges | parser | parser := SHParserST80 new. ranges := parser rangesIn: source classOrMetaClass: theClass workspace: controller workspace environment: nil. ranges := ranges select: [:each | each type ~= #comment]! ! !ECContext methodsFor: 'private-roel-typer' stamp: 'lr 3/26/2010 15:04'! findCommonSuperclass: aCollection | current | aCollection isEmpty ifTrue: [ ^ nil ]. current := aCollection first. aCollection do: [ :class | [ class includesBehavior: current ] whileFalse: [ current := current superclass ] ]. ^ current! ! !ECContext methodsFor: 'private' stamp: 'bar 1/9/2005 14:51'! findSourceRangeFor: aNumber aNumber to: ranges size by: 2 do: [:index | index + 3 > ranges size ifTrue: [^ nil]. (ranges at: index + 1) isAssignment ifTrue: [(ranges at: index + 3) type = #statementSeparator ifTrue: [^ index + 2] ifFalse: [(ranges at: index + 2) type = #globalVar ifTrue: [^ index + 2] ifFalse: [(ranges at: index + 1) isAssignment ifFalse: [^ nil]]]]]! ! !ECContext methodsFor: 'private-type-guessing' stamp: 'lr 7/4/2009 10:42'! guessArgument: aSHRange | name | name := self sourceOf: aSHRange. (name = 'html' and: [ (Smalltalk at: #WARenderCanvas ifAbsent: [ ]) notNil ]) ifTrue: [ ^ Smalltalk at: #WARenderCanvas ]. ^ ECInstVarTypeGuesser getClassFromTypeSuggestingName: name! ! !ECContext methodsFor: 'private' stamp: 'lr 7/4/2009 10:42'! guessCascadeReceiver: aNumber | type | aNumber to: 1 by: -1 do: [ :index | type := (ranges at: index) type. ((#(#statementSeparator #assignment #ansiAssignment ) includes: type) or: [ (type beginsWith: 'pattern') or: [ type beginsWith: 'methodTemp' ] ]) ifTrue: [ ^ self guessTypeOf: index + 1 ] ]. ^ nil! ! !ECContext methodsFor: 'private' stamp: 'damiencassou 7/18/2009 08:05'! guessClassVarClass: aSHRange | aClass name | name := self sourceOf: aSHRange. aClass := controller guessTypeFor: name. aClass ifNotNil: [^ aClass]. ^ (ECClassVarTypeGuesser variableName: name class: theClass theMetaClass) perform! ! !ECContext methodsFor: 'private-type-guessing' stamp: 'lr 7/4/2009 10:42'! guessGlobal: aNumber | aClass | aClass := Smalltalk at: (self sourceOf: (ranges at: aNumber)) asSymbol ifAbsent: [ ^ nil ]. aClass isBehavior ifFalse: [ ^ nil ]. aNumber = (completionIndex - 1) ifTrue: [ ^ aClass class ]. (ranges size >= (aNumber + 1) and: [ (ranges at: aNumber + 1) type = #statementSeparator ]) ifTrue: [ ^ aClass class ]. ^ aClass! ! !ECContext methodsFor: 'private' stamp: 'lr 7/4/2009 10:42'! guessInstVarClass: aSHRange | aClass name | name := self sourceOf: aSHRange. aClass := controller guessTypeFor: name. aClass ifNotNil: [ ^ aClass ]. aClass := self guessWithRoelTyper: name class: theClass. aClass ifNotNil: [ ^ aClass ]. ^ (ECInstVarTypeGuesser variableName: name class: theClass) perform! ! !ECContext methodsFor: 'private' stamp: 'bar 3/1/2006 13:52'! guessTempVarClass: aSHRange ^self guessTempVarClass: (self sourceOf: aSHRange) type: aSHRange type. ! ! !ECContext methodsFor: 'private' stamp: 'lr 7/4/2009 10:42'! guessTempVarClass: aString type: aSymbol | current type varName varType sourceIndex aClass | aClass := controller guessTypeFor: aString. aClass ifNotNil: [ ^ aClass ]. varName := aString. varType := aSymbol. 1 to: completionIndex do: [ :index | current := ranges at: index. (current type = varType and: [ (self sourceOf: current) = varName and: [ index + 3 <= ranges size ] ]) ifTrue: [ (sourceIndex := self findSourceRangeFor: index) notNil ifTrue: [ type := self guessTypeOf: sourceIndex. type ifNotNil: [ ^ type ] ] ] ]. ^ nil! ! !ECContext methodsFor: 'private-type-guessing' stamp: 'lr 7/4/2009 10:42'! guessTypeOf: aNumber | range | self configureSelectorsOnly. recurseCount > 10 ifTrue: [ ^ nil ]. recurseCount := recurseCount + 1. range := ranges at: aNumber. ^ range isSelf ifTrue: [ theClass ] ifFalse: [ range isSuper ifTrue: [ theClass superclass ] ifFalse: [ range isConstant ifTrue: [ range asType ] ifFalse: [ range isArgument ifTrue: [ self guessArgument: range ] ifFalse: [ range isTemporaryVariable ifTrue: [ self guessTempVarClass: range ] ifFalse: [ range isInstanceVariable ifTrue: [ self guessInstVarClass: range ] ifFalse: [ range isClassVariable ifTrue: [ self guessClassVarClass: range ] ifFalse: [ range isGlobal ifTrue: [ self guessGlobal: aNumber ] ] ] ] ] ] ] ]! ! !ECContext methodsFor: 'private-roel-typer' stamp: 'lr 3/26/2010 15:16'! guessWithRoelTyper: aString class: aClass | typeCollector typeClass typeInfo types type | typeCollector := Smalltalk classNamed: #TypeCollector. typeCollector ifNil: [ ^ nil ]. typeClass := aClass whichClassDefinesInstVar: aString. typeClass ifNil: [ ^ nil ]. typeInfo := (typeCollector typeInstvarsOfClass: typeClass) at: aString asSymbol ifAbsent: [ ^ nil ]. types := typeInfo types size <= 2 ifTrue: [ typeInfo types ] ifFalse: [ typeInfo types intersection: typeInfo assignments ]. type := types isEmpty ifFalse: [ self findCommonSuperclass: types ]. ^ type == Object ifFalse: [ type ]! ! !ECContext methodsFor: 'private-temporaries' stamp: 'lr 7/4/2009 10:42'! handleBlockStack: aCollection with: aSHRange | range blockStack | range := aSHRange. blockStack := aCollection. range isBlockStart ifTrue: [ blockStack add: OrderedCollection new ] ifFalse: [ range isBlockEnd ifTrue: [ blockStack removeLast ] ]! ! !ECContext methodsFor: 'initialize-release' stamp: 'lr 7/4/2009 10:42'! initialize super initialize. source := String new. position := 0. recurseCount := 0. variables := true. selectors := true. ranges := OrderedCollection new. completionIndex := 0. completionToken := nil! ! !ECContext methodsFor: 'private-compute-index' stamp: 'bar 1/6/2005 22:04'! insertEmptyRangeAt: index start: start end: end ranges add: (SHRange start: start end: end type: #empty) beforeIndex: index! ! !ECContext methodsFor: 'private-receiver-guessing' stamp: 'bar 1/9/2005 11:33'! isSelectorsAndVariables | current | current := ranges at: completionIndex. ^current isUnfinished! ! !ECContext methodsFor: 'private-receiver-guessing' stamp: 'bar 1/9/2005 11:33'! isSelectorsOnly | previous | previous := ranges at: completionIndex - 1. ^previous isOpening! ! !ECContext methodsFor: 'private-receiver-guessing' stamp: 'lr 7/4/2009 10:42'! isVariablesOnly | current previous | current := ranges at: completionIndex. ^ current isVariablesOnly or: [ current isOpening or: [ previous := ranges at: completionIndex - 1. previous isOpening or: [ previous isSeparator or: [ previous isKeyword or: [ previous isAssignment or: [ previous isBinary ] ] ] ] ] ]! ! !ECContext methodsFor: 'accessing' stamp: 'lr 7/4/2009 10:42'! model model isNil ifTrue: [ model := self createModel ]. ^ model! ! !ECContext methodsFor: 'action' stamp: 'lr 7/4/2009 10:42'! narrowWith: aString completionToken := aString. model ifNotNil: [ model narrowWith: aString ]! ! !ECContext methodsFor: 'private' stamp: 'bar 12/13/2004 15:32'! receiverClass ^ receiverClass! ! !ECContext methodsFor: 'initialize-release' stamp: 'lr 7/4/2009 10:42'! setController: aECController class: aClass source: aString position: anInteger controller := aECController. theClass := aClass. source := aString. position := anInteger. self createRanges. self compute! ! !ECContext methodsFor: 'private' stamp: 'bar 3/1/2006 13:25'! sourceOf: aSHRange ^aSHRange isString ifTrue: [aSHRange] ifFalse: [self sourceOf: aSHRange stopAt: aSHRange end]! ! !ECContext methodsFor: 'private' stamp: 'bar 12/18/2004 23:55'! sourceOf: aSHRange stopAt: aNumber ^ aSHRange type = #empty ifTrue: [String new] ifFalse: [source copyFrom: aSHRange start to: aNumber]! ! !ECContext methodsFor: 'action' stamp: 'bar 1/9/2005 11:35'! switchToUntyped receiverClass := nil. self configureSelectorsAndVariables. model := self createModel! ! !ECContext methodsFor: 'accessing' stamp: 'lr 7/4/2009 10:42'! temporaries | tempRanges | tempRanges := ranges select: [ :each | #(#patternTempVar #patternArg ) includes: each type ]. tempRanges addAll: self blockTemporaries. ^ tempRanges collect: [ :each | ECLocalEntry contents: (self sourceOf: each) type: each type ]! ! !ECContext methodsFor: 'accessing' stamp: 'bar 2/26/2006 09:04'! theClass ^theClass! ! Object subclass: #ECController instanceVariableNames: 'model menuMorph editor context inverseMapping' classVariableNames: '' poolDictionaries: '' category: 'ECompletion-View'! !ECController commentStamp: '' prior: 0! I live as an instance variable in a Browser, Debugger, Workspace or other window. I'm the glue between all participants of the completion system. I create the ECContext and pass myself to the ECMenuMorph. I process the keyboard events and pass them to the ECMenuMorph or close the morph if needed.! !ECController class methodsFor: 'testing' stamp: 'lr 5/11/2010 12:54'! allowModel: aModel ^ aModel respondsTo: #completionController! ! !ECController class methodsFor: 'instance creation' stamp: 'bar 12/13/2004 12:05'! model: aStringHolder ^self new setModel: aStringHolder! ! !ECController methodsFor: 'accessing' stamp: 'bar 12/16/2004 11:13'! additionals ^ nil! ! !ECController methodsFor: 'menu morph' stamp: 'bar 12/13/2004 15:09'! closeMenu menuMorph ifNotNil: [menuMorph delete]! ! !ECController methodsFor: 'accessing' stamp: 'bar 12/13/2004 12:08'! context ^context! ! !ECController methodsFor: 'accessing' stamp: 'bar 12/13/2004 17:34'! editor ^ editor. ! ! !ECController methodsFor: 'type guessing' stamp: 'lr 3/26/2010 13:44'! guessTypeFor: aString ^ model isNil ifFalse: [ model guessTypeForName: aString ]! ! !ECController methodsFor: 'keyboard' stamp: 'lr 8/15/2010 09:34'! handleKeystrokeAfter: aKeyboardEvent editor: aParagraphEditor (aParagraphEditor isNil or: [ self isMenuOpen not ]) ifTrue: [ ^ self ]. self setModel: aParagraphEditor model. context narrowWith: aParagraphEditor wordAtCaret. menuMorph narrowCompletion! ! !ECController methodsFor: 'keyboard' stamp: 'lr 9/5/2010 19:56'! handleKeystrokeBefore: aKeyboardEvent editor: aParagraphEditor "I return a boolean. true when I have handled the event and no futher processing is needed by the caller." | keyValue controlKeyPressed isSpaceKey | editor := aParagraphEditor. self setModel: editor model. keyValue := aKeyboardEvent keyValue. controlKeyPressed := aKeyboardEvent controlKeyPressed. isSpaceKey := #(0 32 ) includes: keyValue. "Ctrl-Space or Tab for open" self isMenuOpen ifFalse: [(isSpaceKey & controlKeyPressed or: [keyValue = 9 and: [editor isCaretBehindChar and: [controlKeyPressed not]]]) ifTrue: [self openMenuFor: editor. ^ true] ifFalse: [(self smartInput: keyValue) ifNotNil: [^ true]]. ^ false]. "Home" keyValue = 1 ifTrue: [menuMorph home. ^ true]. "End" (keyValue = 4 and: [controlKeyPressed not]) ifTrue: [menuMorph end. ^ true]. "Right-Arrow" keyValue = 29 ifTrue: [menuMorph showDetail. ^ true]. "Left Arrow" keyValue = 28 ifTrue: [menuMorph hideDetail. ^ true]. "Arrow up" keyValue = 30 ifTrue: [menuMorph moveUp. ^ true]. "Arrow down" keyValue = 31 ifTrue: [menuMorph moveDown. ^ true]. "Page up" keyValue = 11 ifTrue: [menuMorph pageUp. ^ true]. "Page down" keyValue = 12 ifTrue: [menuMorph pageDown. ^ true]. "Tab or Ctrl-Space" (keyValue = 13 or: [isSpaceKey & controlKeyPressed or: [keyValue = 9]]) ifTrue: [menuMorph insertSelected ifTrue: [^ true]]. "Ctrl-h" (keyValue = 104 and: [ aKeyboardEvent commandKeyPressed ]) ifTrue: [ menuMorph help. ^ true ]. "Ctrl-t" (keyValue = 116 and: [ aKeyboardEvent commandKeyPressed ]) ifTrue: [ menuMorph expand. ^ true ]. "Ctrl-u" (keyValue = 117 and: [ aKeyboardEvent commandKeyPressed ]) ifTrue: [ menuMorph switchToUntyped. ^ true ]. "All keys but the alphanumeric chars (without command and control ) and the backspace key do close the menu" keyValue = 8 ifTrue: [editor isCaretBehindChar not ifTrue: [self closeMenu]. ^ false]. (controlKeyPressed not & aKeyboardEvent commandKeyPressed not and: [aKeyboardEvent keyCharacter isAlphaNumeric]) ifFalse: [self closeMenu. ^ keyValue = 27]. ^ false! ! !ECController methodsFor: 'keyboard' stamp: 'bar 3/3/2006 17:34'! invalidateEditorMorph editor morph invalidRect: editor morph bounds. ! ! !ECController methodsFor: 'menu morph' stamp: 'bar 12/13/2004 11:06'! isMenuOpen ^menuMorph notNil! ! !ECController methodsFor: 'menu morph' stamp: 'damiencassou 7/27/2009 09:53'! menuClosed menuMorph := nil. context := nil.! ! !ECController methodsFor: 'accessing' stamp: 'dr 10/30/2008 17:00'! model ^model! ! !ECController methodsFor: 'menu morph' stamp: 'bar 3/31/2006 09:41'! openMenuFor: aParagraphEditor | theMenu | context := ECContext controller: self class: model selectedClassOrMetaClass source: aParagraphEditor text string position: aParagraphEditor caret - 1. editor := aParagraphEditor. theMenu := ECMenuMorph controller: self position: (aParagraphEditor selectionPosition: context completionToken). theMenu isClosed ifFalse: [menuMorph := theMenu]. ! ! !ECController methodsFor: 'initialize-release' stamp: 'lr 7/4/2009 10:42'! setModel: aStringHolder model := aStringHolder! ! !ECController methodsFor: 'keyboard' stamp: 'lr 7/31/2010 22:38'! smartBackspace | opposite | editor hasSelection ifTrue: [ ^ nil ]. opposite := self smartCharactersMapping at: (editor text at: editor startIndex - 1 ifAbsent: [ ^ nil ]) ifAbsent: [ ^ nil ]. opposite = (editor text at: editor stopIndex ifAbsent: [ ^ nil ]) ifFalse: [ ^ nil ]. editor selectInvisiblyFrom: editor startIndex - 1 to: editor stopIndex. editor zapSelectionWith: String new. self invalidateEditorMorph. ^ true ! ! !ECController methodsFor: 'keyboard' stamp: 'lr 8/5/2010 18:46'! smartCharacter: aCharacter | opposite previous next | editor hasSelection ifTrue: [ opposite := self smartCharactersMapping at: aCharacter ifAbsent: [ ^ nil ]. editor zapSelectionWith: (String with: aCharacter) , (editor selection) , (String with: opposite). editor selectFrom: editor stopIndex to: editor stopIndex - 1. self invalidateEditorMorph. ^ true ]. opposite := self smartCharactersMapping at: aCharacter ifAbsent: [ self smartInverseMapping at: aCharacter ifAbsent: [ ^ nil ]. editor blinkPrevParen: aCharacter. (editor text at: editor startIndex ifAbsent: [ ^ nil ]) = aCharacter ifFalse: [ ^ nil ]. editor selectFrom: editor startIndex + 1 to: editor startIndex. self invalidateEditorMorph. ^ true ]. previous := editor text at: editor startIndex - 1 ifAbsent: [ Character space ]. next := editor text at: editor startIndex ifAbsent: [ Character space ]. (previous isSeparator or: [ next isSeparator ]) ifFalse: [ ^ nil ]. (opposite = aCharacter and: [ next = aCharacter ]) ifTrue: [ editor selectFrom: editor startIndex + 1 to: editor startIndex. self invalidateEditorMorph. ^ true ]. editor zapSelectionWith: (String with: aCharacter with: opposite). editor selectFrom: editor startIndex + 1 to: editor startIndex. self invalidateEditorMorph. ^ true! ! !ECController methodsFor: 'settings' stamp: 'lr 7/31/2010 18:15'! smartCharacters ^ ECPreferences smartCharacters ! ! !ECController methodsFor: 'settings' stamp: 'lr 7/31/2010 18:22'! smartCharactersMapping ^ ECPreferences smartCharactersMapping ! ! !ECController methodsFor: 'keyboard' stamp: 'lr 7/31/2010 18:15'! smartInput: anInteger self smartCharacters ifFalse: [ ^ nil ]. ^ anInteger = 8 ifTrue: [ self smartBackspace ] ifFalse: [ self smartCharacter: anInteger asCharacter ]! ! !ECController methodsFor: 'settings' stamp: 'lr 7/31/2010 19:03'! smartInverseMapping ^ inverseMapping ifNil: [ inverseMapping := Dictionary new. self smartCharactersMapping keysAndValuesDo: [ :key :value | inverseMapping at: value put: key ]. inverseMapping ]! ! !ECController methodsFor: 'accessing' stamp: 'bar 12/15/2004 09:23'! workspace ^nil! ! ECController subclass: #ECWorkspaceController instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'ECompletion-View'! !ECWorkspaceController commentStamp: '' prior: 0! I'm a specialized controller, that works with Workspaces.! !ECWorkspaceController methodsFor: 'accessing' stamp: 'bar 12/16/2004 11:14'! additionals ^ self workspace completionAdditionals! ! !ECWorkspaceController methodsFor: 'accessing' stamp: 'bar 12/15/2004 09:23'! workspace ^model! ! Object subclass: #ECEntry instanceVariableNames: 'contents type description' classVariableNames: '' poolDictionaries: '' category: 'ECompletion-Model'! !ECEntry commentStamp: 'bar 10/5/2005 23:31' prior: 0! I represent a completion entry that is management by a ECModel and shown in the ECMenuMorph as a menu entry.! ECEntry subclass: #ECClassVarEntry instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'ECompletion-Model'! !ECClassVarEntry methodsFor: 'as yet unclassified' stamp: 'bar 3/1/2006 15:27'! guessTypeWith: anECContext ^ anECContext guessClassVarClass: contents! ! !ECClassVarEntry methodsFor: 'as yet unclassified' stamp: 'bar 3/1/2006 15:40'! label ^ 'class variable'! ! !ECEntry class methodsFor: 'as yet unclassified' stamp: 'bar 8/13/2005 18:55'! contents: aString type: aSymbol ^ self new setContents: aString type: aSymbol! ! !ECEntry methodsFor: 'as yet unclassified' stamp: 'bar 10/5/2005 22:35'! <= aECEntry ^ contents <= aECEntry contents! ! !ECEntry methodsFor: 'as yet unclassified' stamp: 'lr 3/29/2008 10:39'! browseWith: anECContext type := self guessTypeWith: anECContext. type ifNil: [^ false]. SystemNavigation default browseClass: type. ^ true! ! !ECEntry methodsFor: 'as yet unclassified' stamp: 'bar 8/14/2005 21:44'! completion ^ self contents asSymbol! ! !ECEntry methodsFor: 'as yet unclassified' stamp: 'bar 8/13/2005 18:56'! contents ^contents! ! !ECEntry methodsFor: 'as yet unclassified' stamp: 'bar 10/5/2005 22:36'! contentsAsSymbol ^ contents asSymbol ! ! !ECEntry methodsFor: 'detail information' stamp: 'lr 7/4/2009 10:42'! createDescriptionWith: anECContext | clazz | clazz := self guessTypeWith: anECContext. ^ clazz ifNil: [ ECEntryDescription label: self label ] ifNotNil: [ ECEntryDescription label: self label title: clazz printString description: clazz comment ]! ! !ECEntry methodsFor: 'as yet unclassified' stamp: 'lr 7/4/2009 10:42'! descriptionWith: anECContext description ifNotNil: [ ^ description ]. ^ description := self createDescriptionWith: anECContext! ! !ECEntry methodsFor: 'as yet unclassified' stamp: 'bar 3/1/2006 15:27'! guessTypeWith: anECContext ^ nil! ! !ECEntry methodsFor: 'as yet unclassified' stamp: 'bar 3/2/2006 17:50'! isInstance ^ false! ! !ECEntry methodsFor: 'as yet unclassified' stamp: 'bar 3/2/2006 17:51'! isLocal ^ false! ! !ECEntry methodsFor: 'as yet unclassified' stamp: 'bar 3/2/2006 17:51'! isSelector ^ false! ! !ECEntry methodsFor: 'as yet unclassified' stamp: 'bar 3/1/2006 15:40'! label ^ 'unknown'! ! !ECEntry methodsFor: 'as yet unclassified' stamp: 'bar 8/13/2005 19:08'! printOn: aStream aStream nextPutAll: self class name; nextPut: $(; nextPutAll: contents; nextPut: $,; nextPutAll: type; nextPut: $)! ! !ECEntry methodsFor: 'as yet unclassified' stamp: 'lr 7/4/2009 10:42'! setContents: aString type: aSymbol contents := aString. type := aSymbol! ! !ECEntry methodsFor: 'as yet unclassified' stamp: 'bar 8/13/2005 18:56'! type ^type! ! ECEntry subclass: #ECGlobalEntry instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'ECompletion-Model'! !ECGlobalEntry methodsFor: 'as yet unclassified' stamp: 'bar 3/20/2006 15:20'! guessTypeWith: anECContext | globalEntry | globalEntry := Smalltalk at: contents ifAbsent: [^ nil]. globalEntry isBehavior ifTrue: [^ globalEntry]. globalEntry ifNotNil: [^ globalEntry class]. ^ nil! ! !ECGlobalEntry methodsFor: 'as yet unclassified' stamp: 'bar 3/1/2006 15:41'! label ^ 'global'! ! ECEntry subclass: #ECInstVarEntry instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'ECompletion-Model'! !ECInstVarEntry methodsFor: 'as yet unclassified' stamp: 'bar 3/1/2006 15:27'! guessTypeWith: anECContext ^ anECContext guessInstVarClass: contents! ! !ECInstVarEntry methodsFor: 'as yet unclassified' stamp: 'bar 3/2/2006 17:51'! isInstance ^true! ! !ECInstVarEntry methodsFor: 'as yet unclassified' stamp: 'bar 3/1/2006 15:41'! label ^ 'instance variable'! ! ECEntry subclass: #ECLocalEntry instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'ECompletion-Model'! !ECLocalEntry methodsFor: 'as yet unclassified' stamp: 'bar 3/1/2006 15:27'! guessTypeWith: anECContext ^ (anECContext guessTempVarClass: contents type: type) ifNil: [anECContext guessArgument: contents]! ! !ECLocalEntry methodsFor: 'as yet unclassified' stamp: 'bar 3/2/2006 17:51'! isLocal ^true! ! !ECLocalEntry methodsFor: 'as yet unclassified' stamp: 'bar 3/1/2006 15:41'! label ^ 'local variable'! ! ECEntry subclass: #ECSelectorEntry instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'ECompletion-Model'! !ECSelectorEntry methodsFor: 'private' stamp: 'damiencassou 1/6/2009 14:04'! browseWith: anECContext ^ self findMethodWith: anECContext do: [ :class :method | Browser fullOnClass: class selector: method selector. true ] ifAbsent: [ :selector | (SystemBrowser default name beginsWith: 'OB') ifTrue: [OBImplementorsBrowser openRoot: (OBSelectorNode on: selector).] ifFalse: [self systemNavigation browseAllImplementorsOf: selector]. true ]! ! !ECSelectorEntry methodsFor: 'as yet unclassified' stamp: 'bar 3/8/2006 21:42'! createDescriptionWith: anECContext ^ self findMethodWith: anECContext do: [:clazz :method | self methodSourceDescription: clazz method: method ] ifAbsent: [:selector | self implementorsDescription: selector]! ! !ECSelectorEntry methodsFor: 'private' stamp: 'bar 3/20/2006 16:15'! findMethodWith: anECContext do: foundBlock ifAbsent: notfoundBlock | theClass result implementors | theClass := anECContext model theClass. result := theClass ifNil: [implementors := self systemNavigation allImplementorsOf: contents. implementors size == 1 ifTrue: [| ref | ref := implementors first. self lookupSelector: ref methodSymbol class: ref actualClass] ifFalse: [^ notfoundBlock value: contents]] ifNotNil: [self lookupSelector: contents class: theClass]. ^ foundBlock value: result first value: result second! ! !ECSelectorEntry methodsFor: 'private' stamp: 'lr 7/4/2009 10:42'! implementorsDescription: aSymbol | implementors output | output := WriteStream on: String new. implementors := self systemNavigation allImplementorsOf: aSymbol. implementors isEmpty ifTrue: [ ^ ECEntryDescription label: 'symbol' title: '(no implementors)' description: 'This is just symbol.' ]. implementors do: [ :each | output nextPutAll: each classSymbol printString; cr ]. ^ ECEntryDescription label: self label title: '(Implementors)' description: output contents! ! !ECSelectorEntry methodsFor: 'as yet unclassified' stamp: 'bar 3/2/2006 21:52'! label ^ 'method'! ! !ECSelectorEntry methodsFor: 'private' stamp: 'bar 3/20/2006 15:38'! lookupSelector: aSymbol class: aClass "Look up the given selector in my methodDictionary. Return the corresponding method if found. Otherwise chase the superclass chain and try again. Return nil if no method is found." | lookupClass | lookupClass := aClass. [lookupClass isNil] whileFalse: [(lookupClass includesSelector: aSymbol) ifTrue: [^ Array with: lookupClass with: (lookupClass compiledMethodAt: aSymbol)]. lookupClass := lookupClass superclass]. ^ nil! ! !ECSelectorEntry methodsFor: 'as yet unclassified' stamp: 'bar 3/30/2006 14:17'! methodSourceDescription: aClass method: aCompiledMethod | styler | styler := SHTextStylerST80 new. styler classOrMetaClass: aClass. ^ ECEntryDescription label: self label title: aClass printString description: (styler styledTextFor: (self methodSourceOn: aCompiledMethod ) asText)! ! !ECSelectorEntry methodsFor: 'private' stamp: 'rjl 12/11/2008 21:07'! methodSourceOn: aCompiledMethod ^ aCompiledMethod getSourceFor: aCompiledMethod selector in: aCompiledMethod methodClass! ! ECEntry subclass: #ECSelfEntry instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'ECompletion-Model'! !ECSelfEntry methodsFor: 'as yet unclassified' stamp: 'bar 3/1/2006 15:27'! guessTypeWith: anECContext ^ anECContext theClass! ! !ECSelfEntry methodsFor: 'as yet unclassified' stamp: 'bar 3/1/2006 15:42'! label ^ 'self'! ! ECEntry subclass: #ECSuperEntry instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'ECompletion-Model'! !ECSuperEntry methodsFor: 'as yet unclassified' stamp: 'bar 3/1/2006 15:27'! guessTypeWith: anECContext ^ anECContext theClass ifNotNil: [anECContext theClass superclass]! ! !ECSuperEntry methodsFor: 'as yet unclassified' stamp: 'bar 3/1/2006 15:42'! label ^ 'super'! ! Object subclass: #ECEntryDescription instanceVariableNames: 'title description label' classVariableNames: '' poolDictionaries: '' category: 'ECompletion-Model'! !ECEntryDescription class methodsFor: 'as yet unclassified' stamp: 'bar 3/2/2006 22:01'! label: firstString ^ self new setLabel: firstString title: '(unknown)' description: nil! ! !ECEntryDescription class methodsFor: 'as yet unclassified' stamp: 'bar 3/1/2006 15:39'! label: firstString title: secondString description: thirdString ^ self new setLabel: firstString title: secondString description: thirdString! ! !ECEntryDescription methodsFor: 'accessing' stamp: 'bar 3/2/2006 22:02'! description ( description isNil or:[description isEmpty]) ifTrue:[^'-']. ^ description! ! !ECEntryDescription methodsFor: 'accessing' stamp: 'bar 3/1/2006 15:39'! label ^ label! ! !ECEntryDescription methodsFor: 'initialize-release' stamp: 'lr 7/4/2009 10:42'! setLabel: firstString title: secondString description: thirdString label := firstString. title := secondString. description := thirdString! ! !ECEntryDescription methodsFor: 'accessing' stamp: 'bar 3/1/2006 15:20'! title ^ title! ! Object subclass: #ECModel instanceVariableNames: 'clazz selectors narrowString entries' classVariableNames: '' poolDictionaries: '' category: 'ECompletion-Model'! !ECModel commentStamp: '' prior: 0! I'm an abstract class that stores the entries to be completed.! !ECModel class methodsFor: 'instance creation' stamp: 'lr 7/4/2009 10:42'! class: aClass | newInstance | newInstance := self basicNew initialize. newInstance setClass: aClass. ^ newInstance! ! !ECModel methodsFor: 'private' stamp: 'lr 7/4/2009 10:42'! addToEntries: aCollection | temp caseSensitive | caseSensitive := ECPreferences caseSensitive. temp := aCollection select: [ :each | each contents occursInWithEmpty: narrowString caseSensitive: caseSensitive ]. entries addAll: temp! ! !ECModel methodsFor: 'accessing' stamp: 'bar 12/4/2004 17:21'! at: aNumber ^ entries at: aNumber ! ! !ECModel methodsFor: 'action' stamp: 'dr 10/30/2008 21:05'! completionAt: aNumber ^ (self at: aNumber) completion separateKeywords , ' '! ! !ECModel methodsFor: 'accessing' stamp: 'bar 12/4/2004 17:20'! entries ^entries! ! !ECModel methodsFor: 'accessing' stamp: 'lr 7/4/2009 10:42'! entriesOfType: aSymbol | collection | collection := entries select: [ :each | each type == aSymbol ]. ^ collection collect: [ :each | each contents ]! ! !ECModel methodsFor: 'accessing' stamp: 'bar 12/4/2004 17:21'! entryCount ^entries size! ! !ECModel methodsFor: 'accessing' stamp: 'bar 12/17/2004 22:45'! hasMessage ^ self message notNil! ! !ECModel methodsFor: 'initialize-release' stamp: 'bar 4/11/2005 11:22'! initialize self reset! ! !ECModel methodsFor: 'accessing' stamp: 'bar 12/6/2004 14:18'! initializeSelectors self subclassResponsibility ! ! !ECModel methodsFor: 'testing' stamp: 'bar 3/3/2006 17:00'! isEmpty ^ entries isEmpty! ! !ECModel methodsFor: 'accessing' stamp: 'bar 1/6/2005 08:25'! message ^self isEmpty ifTrue: ['no completions found'] ifFalse: [nil]! ! !ECModel methodsFor: 'private' stamp: 'bar 12/4/2004 17:40'! narrowString: aString narrowString := aString! ! !ECModel methodsFor: 'action' stamp: 'bar 12/6/2004 11:53'! narrowWith: aString self subclassResponsibility ! ! !ECModel methodsFor: 'testing' stamp: 'bar 12/4/2004 17:22'! notEmpty ^self isEmpty not! ! !ECModel methodsFor: 'private' stamp: 'lr 7/4/2009 10:42'! reset self resetSelectors. self resetEntries. narrowString := String new! ! !ECModel methodsFor: 'private' stamp: 'lr 7/4/2009 10:42'! resetEntries entries := OrderedCollection new! ! !ECModel methodsFor: 'private' stamp: 'damiencassou 4/17/2009 15:29'! resetSelectors selectors := (SortedCollection new: 500) sortBlock: [ :a :b | | scoreA scoreB | scoreA := scoreB := 0. (a contents beginsWithEmpty: narrowString caseSensitive: ECPreferences caseSensitive) ifFalse: [ scoreA := 2 ]. (b contents beginsWithEmpty: narrowString caseSensitive: ECPreferences caseSensitive) ifFalse: [ scoreB := 2 ]. a contents < b contents ifTrue: [ scoreB := scoreB + 1 ] ifFalse: [ scoreA := scoreA + 1 ]. scoreA < scoreB ]! ! !ECModel methodsFor: 'initialize-release' stamp: 'bar 1/6/2005 08:54'! setClass: aClass clazz := aClass. self initializeSelectors. self narrowWith: String new! ! !ECModel methodsFor: 'action' stamp: 'bar 3/1/2006 15:48'! theClass ^nil! ! !ECModel methodsFor: 'action' stamp: 'bar 12/6/2004 14:44'! title ^nil! ! !ECModel methodsFor: 'initialize-release' stamp: 'bar 12/5/2004 23:17'! toggleExpand ! ! ECModel subclass: #ECTypedModel instanceVariableNames: 'expanded' classVariableNames: '' poolDictionaries: '' category: 'ECompletion-Model'! !ECTypedModel commentStamp: '' prior: 0! I'm the model for a typed completion, that means when a receiver class is known. I only have selectors. I have an expand toggle: When false I filter out Object and ProtoObject selectors. The default value is true.! ECTypedModel subclass: #ECOverrideModel instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'ECompletion-Model'! !ECOverrideModel commentStamp: '' prior: 0! I'm used when completing a method override. I contain all selectors of the superclass minus the already implemented selectors of the current class. When a completion occurs I complete a method template with a send to super.! !ECOverrideModel methodsFor: 'action' stamp: 'lr 6/19/2010 12:45'! completionAt: aNumber | output source declaration | source := self methodSourceAt: aNumber. declaration := (source lineCorrespondingToIndex: 1) withoutTrailingBlanks. output := WriteStream on: String new. output nextPutAll: declaration; cr; tab. (source includesSubString: 'subclassResponsibility') ifFalse: [ (source includes: $^) ifTrue: [ output nextPutAll: '^ ' ]. output nextPutAll: 'super '; nextPutAll: declaration ]. ^ output contents! ! !ECOverrideModel methodsFor: 'initialize-release' stamp: 'lr 7/4/2009 10:42'! initializeSelectors self initializeSelectorsFor: clazz superclass. clazz methodDictionary keysDo: [ :each | | entry | entry := selectors detect: [ :ea | ea contentsAsSymbol == each ] ifNone: [ ]. entry notNil ifTrue: [ selectors remove: entry ifAbsent: [ ] ] ]! ! !ECOverrideModel methodsFor: 'private' stamp: 'lr 6/19/2010 12:49'! methodAt: aNumber ^ clazz lookupSelector: (self at: aNumber) contentsAsSymbol! ! !ECOverrideModel methodsFor: 'private' stamp: 'lr 6/19/2010 12:49'! methodSourceAt: aNumber ^ (self methodAt: aNumber) getSourceFromFile asString! ! !ECOverrideModel methodsFor: 'action' stamp: 'bar 12/6/2004 15:02'! title ^ '(override) ' , clazz superclass name! ! !ECTypedModel methodsFor: 'initialize-release' stamp: 'lr 3/17/2010 19:49'! initialize super initialize. expanded := true! ! !ECTypedModel methodsFor: 'private' stamp: 'bar 12/6/2004 14:19'! initializeSelectors self initializeSelectorsFor: clazz! ! !ECTypedModel methodsFor: 'private' stamp: 'lr 3/17/2010 19:50'! initializeSelectorsFor: aClass |excludedClasses| selectors reset. excludedClasses := (expanded ifTrue: [#()] ifFalse: [Object withAllSuperclasses]). selectors addAll: ((aClass allSelectorsForCompletionWithout: excludedClasses) collect: [:each | ECSelectorEntry contents: each type: #selector])! ! !ECTypedModel methodsFor: 'action' stamp: 'cmm 1/6/2007 21:49'! narrowWith: aString self narrowString: aString ; initializeSelectors. entries reset. self addToEntries: selectors! ! !ECTypedModel methodsFor: 'action' stamp: 'bar 3/1/2006 15:49'! theClass ^clazz! ! !ECTypedModel methodsFor: 'action' stamp: 'bar 12/6/2004 14:44'! title ^clazz name! ! !ECTypedModel methodsFor: 'action' stamp: 'lr 7/4/2009 10:42'! toggleExpand expanded := expanded not. self initializeSelectors. self narrowWith: narrowString! ! ECModel subclass: #ECUntypedModel instanceVariableNames: 'instVars localVars includeVariables includeSelectors classVars' classVariableNames: '' poolDictionaries: '' category: 'ECompletion-Model'! !ECUntypedModel commentStamp: '' prior: 0! When no receiver class is known, I'm the right model. I store all temporary variables, instance variables of the selected class and all selectors in system. For performance reasons I only collect selectors when at least one character is known.! ECUntypedModel subclass: #ECUnseparatedModel instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'ECompletion-Model'! !ECUnseparatedModel methodsFor: 'action' stamp: 'dr 10/30/2008 17:06'! completionAt: aNumber ^ (self at: aNumber) completion! ! !ECUntypedModel class methodsFor: 'instance creation' stamp: 'bar 12/20/2004 09:02'! class: aClass temporaries: aCollection ^self class: aClass temporaries: aCollection additionals: #() variables: true selectors: true! ! !ECUntypedModel class methodsFor: 'instance creation' stamp: 'lr 7/4/2009 10:42'! class: aClass temporaries: aCollection additionals: additionalCollection variables: variablesBoolean selectors: selectorsBoolean | newInstance | newInstance := self basicNew initialize. newInstance setClass: aClass temporaries: aCollection additionals: additionalCollection variables: variablesBoolean selectors: selectorsBoolean. ^ newInstance! ! !ECUntypedModel methodsFor: 'private' stamp: 'lr 9/26/2010 17:45'! addAdditionals: aCollection aCollection ifNotNil: [aCollection do: [:each | each isLocal ifTrue: [localVars add: each value] ifFalse: [each isInstance ifTrue: [instVars add: each value] ifFalse: [each isSelector ifTrue: [selectors add: each value]]]]]! ! !ECUntypedModel methodsFor: 'private' stamp: 'cmm 1/6/2007 21:43'! addSelectors self initializeSelectors. self addToEntries: selectors! ! !ECUntypedModel methodsFor: 'private' stamp: 'bar 10/5/2005 23:05'! addVariables includeVariables ifFalse: [^ self]. self addToEntries: localVars. self addToEntries: instVars. self addToEntries: classVars! ! !ECUntypedModel methodsFor: 'initialize-release' stamp: 'lr 7/4/2009 10:42'! initialize super initialize. localVars := SortedCollection new. instVars := SortedCollection new. classVars := SortedCollection new. includeSelectors := true. includeVariables := true! ! !ECUntypedModel methodsFor: 'initialize-release' stamp: 'lr 9/5/2010 23:41'! initializeClassVars (clazz isNil or: [ includeVariables not ]) ifTrue: [ ^ self ]. classVars := clazz theNonMetaClass allClassVarNames asSortedCollection. classVars := classVars collect: [ :each | ECClassVarEntry contents: each type: #classVar ]! ! !ECUntypedModel methodsFor: 'initialize-release' stamp: 'lr 7/4/2009 10:42'! initializeInstVars (clazz isNil or: [ includeVariables not ]) ifTrue: [ ^ self ]. instVars := clazz allInstVarNames asSortedCollection. instVars := instVars collect: [ :each | ECInstVarEntry contents: each type: #instVar ]. instVars add: (ECSelfEntry contents: 'self' type: #self). instVars add: (ECSuperEntry contents: 'super' type: #super)! ! !ECUntypedModel methodsFor: 'private' stamp: 'lr 3/17/2010 19:54'! initializeSelectors self resetSelectors. includeSelectors ifFalse: [ Smalltalk keysAndValuesDo: [ :each :class | selectors add: (ECGlobalEntry contents: each type: #globalVar) ]. ^ self ]. narrowString ifEmpty: [ ^ self ]. ECSymbols contains: narrowString caseSensitive: ECPreferences caseSensitive do: [ :each | (includeVariables or: [ each first isLowercase ]) ifTrue: [ selectors add: (ECSelectorEntry contents: each type: #selector). selectors size > 500 ifTrue: [ ^ self ] ] ]! ! !ECUntypedModel methodsFor: 'accessing' stamp: 'cmm 1/8/2007 21:01'! message ^ (includeSelectors and: [ narrowString isEmpty ]) ifTrue: [ selectors size = 500 ifTrue: [ 'more...' ] ifFalse: [ 'press key for selectors' ] ] ifFalse: [ super message ]! ! !ECUntypedModel methodsFor: 'initialize-release' stamp: 'bar 4/11/2005 11:42'! narrowString: aString (narrowString isEmpty or: [aString isEmpty or: [aString first ~= narrowString first]]) ifTrue: [self reset]. super narrowString: aString! ! !ECUntypedModel methodsFor: 'action' stamp: 'bar 4/11/2005 11:35'! narrowWith: aString self narrowString: aString. self resetEntries. self addVariables. self addSelectors! ! !ECUntypedModel methodsFor: 'initialize-release' stamp: 'lr 7/4/2009 10:42'! setClass: aClass temporaries: aCollection additionals: additionalCollection variables: variablesBoolean selectors: selectorsBoolean includeVariables := variablesBoolean. includeSelectors := selectorsBoolean. clazz := aClass. self initializeInstVars. self initializeClassVars. includeVariables ifTrue: [ localVars := aCollection. self addAdditionals: additionalCollection ] ifFalse: [ localVars := OrderedCollection new ]. self resetEntries; addVariables; addSelectors! ! Object subclass: #ECPreferences instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'ECompletion-Pharo'! ECPreferences class instanceVariableNames: 'enabled caseSensitive smartCharacters smartCharactersMapping'! ECPreferences class instanceVariableNames: 'enabled caseSensitive smartCharacters smartCharactersMapping'! !ECPreferences class methodsFor: 'accessing' stamp: 'TestRunner 3/17/2010 20:03'! caseSensitive ^ caseSensitive ! ! !ECPreferences class methodsFor: 'accessing' stamp: 'TestRunner 3/17/2010 20:03'! caseSensitive: aBoolean caseSensitive := aBoolean! ! !ECPreferences class methodsFor: 'accessing' stamp: 'TestRunner 3/17/2010 20:03'! enabled ^ enabled ! ! !ECPreferences class methodsFor: 'accessing' stamp: 'TestRunner 3/17/2010 20:03'! enabled: aBoolean enabled := aBoolean! ! !ECPreferences class methodsFor: 'initialization' stamp: 'lr 5/11/2010 12:52'! initialize enabled := caseSensitive := smartCharacters := true. smartCharactersMapping := Dictionary new. smartCharactersMapping at: $( put: $); at: $[ put: $]; at: ${ put: $}; at: $" put: $"; at: $' put: $'! ! !ECPreferences class methodsFor: 'settings' stamp: 'lr 8/15/2010 14:28'! settingsOn: aBuilder (aBuilder group: #'eCompletion: Code Completion') target: self; parentName: #codeBrowsing; with: [ (aBuilder setting: #enabled) order: 0; label: 'Enabled'; description: 'Enable or disable code completion in browsers, debuggers and workspaces.'. (aBuilder setting: #caseSensitive) label: 'Case Sensitive'; description: 'Decide if you want eCompletion to be case sensitive or not.'. (aBuilder setting: #smartCharacters) label: 'Smart Characters'; description: 'Decide if you want eCompletion to use smart characters, e.g, to automatically close brackets.' ]! ! !ECPreferences class methodsFor: 'accessing' stamp: 'TestRunner 3/17/2010 20:03'! smartCharacters ^ smartCharacters! ! !ECPreferences class methodsFor: 'accessing' stamp: 'TestRunner 3/17/2010 20:03'! smartCharacters: aBoolean smartCharacters := aBoolean! ! !ECPreferences class methodsFor: 'accessing' stamp: 'lr 5/11/2010 12:51'! smartCharactersMapping ^ smartCharactersMapping! ! !ECPreferences class methodsFor: 'accessing' stamp: 'lr 5/11/2010 12:52'! smartCharactersMapping: aDictionary smartCharactersMapping := aDictionary! ! Object subclass: #ECSymbols instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'ECompletion-Pharo'! !ECSymbols class methodsFor: 'as yet unclassified' stamp: 'lr 3/17/2010 20:19'! contains: aString caseSensitive: aBoolean do: aBlock Symbol allSymbolTablesDo: [ :each | ((each includes: $ ) not and: [ each includesSubstring: aString caseSensitive: aBoolean ]) ifTrue: [ aBlock value: each ] ]! ! !ECSymbols class methodsFor: 'as yet unclassified' stamp: 'lr 7/6/2010 18:28'! startsWith: aChar caseSensitive: aBoolean do: aBlock | char caseInSensitive firstChar | caseInSensitive := aBoolean not. firstChar := caseInSensitive ifTrue: [ aChar asLowercase ] ifFalse: [ aChar ]. Symbol allSymbolTablesDo: [ :each | | size | size := each size. char := size > 0 ifTrue: [ each first ]. (char notNil and: [ (char == firstChar or: [ caseInSensitive and: [ char asLowercase == firstChar ] ]) and: [ (each findAnySubStr: '- ' startingAt: 2) > size ] ]) ifTrue: [ aBlock value: each ] ]! ! Object subclass: #ECTestSuperClass instanceVariableNames: 'superInstVar' classVariableNames: 'SuperClassVar' poolDictionaries: '' category: 'ECompletion-Tests'! !ECTestSuperClass commentStamp: '' prior: 0! I'm only for SUnit TestCases.! ECTestSuperClass subclass: #ECTestClass instanceVariableNames: 'third fourth typeSuggestingParameter messageSend messageSend2 typeSuggestingParameter2 complexInit complexInit2 constantInteger constantSymbol constantArray constantBoolean constantString constantNil globalVarKeyword globalVarKeyword2' classVariableNames: 'ClassVar' poolDictionaries: '' category: 'ECompletion-Tests'! !ECTestClass commentStamp: '' prior: 0! I'm only for SUnit TestCases.! !ECTestClass class methodsFor: 'as yet unclassified' stamp: 'lr 7/4/2009 10:42'! initialize super initialize. ClassVar := 'Any string'! ! !ECTestClass methodsFor: 'as yet unclassified' stamp: 'bar 12/13/2004 17:41'! initialize: aRectangle constantInteger := 15. constantString := 'Ruben'. constantSymbol := #Symbol. constantArray := #(15 16 17 28 ). constantBoolean := true. typeSuggestingParameter := aRectangle. messageSend := Dictionary new. messageSend2 := aRectangle origin. globalVarKeyword := SortedCollection sortBlock: [:a :b | a <= b]. globalVarKeyword2 := SortedCollection new: 15. constantNil := nil. typeSuggestingParameter2 := nil. complexInit := 15 > 16 ifTrue: [#Symbol] ifFalse: ['String']. complexInit2 := Dictionary new: aRectangle origin x. ! ! !ECTestClass methodsFor: 'as yet unclassified' stamp: 'bar 12/13/2004 17:29'! lowPriorityOverrides: aRectangle messageSend := aRectangle. typeSuggestingParameter2 := aRectangle. ! ! !ECTestClass methodsFor: 'as yet unclassified' stamp: 'bar 12/9/2004 19:40'! testIt: anArgument | loc1 x2 t | x2 := [:bar :var | var < bar]. loc1 := constantArray. x2 value: loc1. t := 15. ^ x2! ! !ECTestSuperClass class methodsFor: 'as yet unclassified' stamp: 'lr 7/4/2009 10:42'! initialize SuperClassVar := Dictionary new! ! !ECTestSuperClass methodsFor: 'as yet unclassified' stamp: 'lr 7/4/2009 10:42'! initialize superInstVar := Dictionary new! ! !ECTestSuperClass methodsFor: 'as yet unclassified' stamp: 'bar 12/6/2004 08:44'! testIt: aString self subclassResponsibility ! ! !ECTestSuperClass methodsFor: 'as yet unclassified' stamp: 'bar 12/6/2004 08:45'! toBeOverriden: anArgument 15 > 16 ifTrue: [self sample * anArgument ]! ! !ECTestSuperClass methodsFor: 'as yet unclassified' stamp: 'bar 12/6/2004 16:19'! toBeOverridenWithReturn ^ 'saga'! ! Object subclass: #ECTypeInfo instanceVariableNames: 'type kind temporaryOffset' classVariableNames: '' poolDictionaries: '' category: 'ECompletion-Model'! !ECTypeInfo commentStamp: '' prior: 0! I'm used in ECInstVarTypeGuesser to store found type informations.! !ECTypeInfo class methodsFor: 'as yet unclassified' stamp: 'bar 12/2/2004 11:52'! definedByLiteral: aClass | newInstance | newInstance := self new. newInstance setType: aClass kind: 1. ^ newInstance! ! !ECTypeInfo class methodsFor: 'as yet unclassified' stamp: 'bar 12/2/2004 11:52'! definedByMessageSend: aClass | newInstance | newInstance := self new. newInstance setType: aClass kind: 2. ^ newInstance! ! !ECTypeInfo class methodsFor: 'as yet unclassified' stamp: 'bar 12/2/2004 12:02'! definedByTemporaryVar: anInteger | newInstance | newInstance := self new. newInstance setType: nil kind: 3. newInstance temporaryOffset: anInteger. ^ newInstance! ! !ECTypeInfo methodsFor: 'as yet unclassified' stamp: 'bar 12/2/2004 11:47'! isDefinedByMessageSend ^kind == 2! ! !ECTypeInfo methodsFor: 'as yet unclassified' stamp: 'bar 12/2/2004 11:47'! isDefinedByTemporary ^ kind == 3! ! !ECTypeInfo methodsFor: 'as yet unclassified' stamp: 'bar 12/2/2004 12:01'! priority ^kind! ! !ECTypeInfo methodsFor: 'as yet unclassified' stamp: 'bar 12/2/2004 12:01'! setType: aClass kind: anInteger type := aClass. kind := anInteger! ! !ECTypeInfo methodsFor: 'as yet unclassified' stamp: 'bar 12/2/2004 12:02'! temporaryOffset ^temporaryOffset! ! !ECTypeInfo methodsFor: 'as yet unclassified' stamp: 'lr 7/4/2009 10:42'! temporaryOffset: anInteger temporaryOffset := anInteger! ! !ECTypeInfo methodsFor: 'as yet unclassified' stamp: 'bar 12/2/2004 11:44'! type ^type! ! !ECTypeInfo methodsFor: 'as yet unclassified' stamp: 'lr 7/4/2009 10:42'! type: aClass type := aClass! ! ECPreferences initialize! ECTestClass initialize! ECTestSuperClass initialize!