Created
May 16, 2014 09:01
-
-
Save philippeback/f43447ec2bddcd3f9b84 to your computer and use it in GitHub Desktop.
Spotlight Changes
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
KMCategory subclass: #SpotlightShortcuts | |
instanceVariableNames: '' | |
classVariableNames: '' | |
poolDictionaries: '' | |
category: 'Tools-Spotlight'! | |
!SpotlightShortcuts commentStamp: 'TorstenBergmann 2/4/2014 20:43' prior: 0! | |
A shortcut for spotlight! | |
!SpotlightShortcuts methodsFor: 'keymaps' stamp: 'MarcusDenker 9/11/2013 13:23'! | |
keymapToggle | |
<shortcut> | |
^ KMKeymap | |
shortcut: Character cr shift | |
action: [ Spotlight toggle ]! ! | |
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! | |
SpotlightShortcuts class | |
instanceVariableNames: ''! | |
!SpotlightShortcuts class commentStamp: '<historical>' prior: 0! | |
! | |
!SpotlightShortcuts class methodsFor: 'as yet unclassified' stamp: 'MarcusDenker 9/11/2013 15:30'! | |
isGlobalCategory | |
^ true! ! | |
Morph subclass: #Spotlight | |
instanceVariableNames: 'searchText model search' | |
classVariableNames: 'Current' | |
poolDictionaries: '' | |
category: 'Tools-Spotlight'! | |
!Spotlight commentStamp: '<historical>' prior: 0! | |
I'm a morph who searchs classes and implementors in an easy way (it is a "code completion" morph in a cool place and with better "enter" handling). | |
To activate it just press shift+enter! | |
!Spotlight methodsFor: 'accessing' stamp: 'EstebanLorenzano 1/21/2012 14:03'! | |
label | |
^'Search' translated! ! | |
!Spotlight methodsFor: 'accessing' stamp: 'EstebanLorenzano 1/21/2012 12:11'! | |
model | |
^model ifNil: [ model := StringHolder new ]! ! | |
!Spotlight methodsFor: 'showing' stamp: 'EstebanLorenzano 7/4/2012 10:46'! | |
close | |
self delete. ! ! | |
!Spotlight methodsFor: 'showing' stamp: 'PhilippeBack 5/16/2014 10:32'! | |
open | |
"self left: Display width - self width. | |
self top: 0." | |
self borderColor: Color yellow. | |
self left: ((Display width - self width) / 2) asInteger. | |
self top: ((Display height - self height) /2) asInteger. | |
super openInWorld. | |
search takeKeyboardFocus.! ! | |
!Spotlight methodsFor: 'initialization' stamp: 'GuillermoPolito 8/5/2013 10:21'! | |
initialize | |
super initialize. | |
self beSticky. | |
self | |
layoutPolicy: TableLayout new; | |
listDirection: #leftToRight; | |
wrapCentering: #center; | |
hResizing: #spaceFill; | |
vResizing: #spaceFill; | |
layoutInset: self defaultLayoutInset ; | |
cellInset: 5. | |
self addMorphBack: Smalltalk ui icons smallFindIcon asMorph. | |
search := self createSearchMorph | |
crAction: [ :text | self accepted ]; | |
yourself. | |
self addMorphBack: search. | |
self | |
bindKeyCombination: Character escape | |
toAction: [ self close ].! ! | |
!Spotlight methodsFor: 'private' stamp: 'EstebanLorenzano 2/8/2013 15:15'! | |
symbolIsPackage: symbol | |
^RPackage organizer includesPackageNamed: symbol asString! ! | |
!Spotlight methodsFor: 'private' stamp: 'PhilippeBack 5/16/2014 10:50'! | |
resolveSymbol: symbol | |
(self symbolIsSelector: symbol) ifTrue: [ | |
^self systemNavigation browseAllImplementorsOf: symbol findSelector ]. | |
(self symbolIsClass: symbol) ifTrue: [ | |
^Smalltalk tools browser openOnClass: (Smalltalk globals at: symbol) ]. | |
(self symbolIsPackage: symbol) ifTrue: [ | |
^Smalltalk tools browser openOnPackage: (RPackage organizer packageNamed: symbol asString) ]. | |
(Smalltalk globals includesKey: symbol) ifTrue: [ | |
^ (Smalltalk globals at: symbol) inspect]. | |
self inform: ('There is no recognizable symbol named ', self model contents)! ! | |
!Spotlight methodsFor: 'private' stamp: 'MarcusDenker 3/25/2013 17:00'! | |
symbolIsClass: symbol | |
Smalltalk globals | |
at: symbol | |
ifPresent: [ :val | ^val isBehavior or: [ val isTrait ] ] | |
ifAbsent: [ ^false ]! ! | |
!Spotlight methodsFor: 'private' stamp: 'EstebanLorenzano 2/8/2013 15:13'! | |
symbolIsSelector: symbol | |
self flag: #todo. "I would like to have a better way to detect selectors..." | |
^symbol first isLowercase! ! | |
!Spotlight methodsFor: 'private' stamp: 'SvenVanCaekenberghe 3/25/2014 14:05'! | |
resolveExpression: string | |
(self class compiler evaluate: string) inspect! ! | |
!Spotlight methodsFor: 'initialize' stamp: 'PhilippeBack 5/16/2014 10:35'! | |
defaultBounds | |
^0@0 corner: 500@32! ! | |
!Spotlight methodsFor: 'initialize' stamp: 'PhilippeBack 5/16/2014 10:36'! | |
defaultLayoutInset | |
^3! ! | |
!Spotlight methodsFor: 'initialize' stamp: 'PhilippeBack 5/16/2014 10:41'! | |
createSearchMorph | |
| morph | | |
morph := PluggableTextFieldMorph new | |
on: self model | |
text: #contents | |
accept: #contents: | |
readSelection: nil | |
menu: nil; | |
convertTo: String; | |
alwaysAccept: true; | |
acceptOnCR: true; | |
autoAccept: true; | |
getEnabledSelector: nil; | |
font: Smalltalk ui theme textFont; | |
cornerStyle: (Smalltalk ui theme textEntryCornerStyleIn: self); | |
hResizing: #spaceFill; | |
vResizing: #rigid; | |
borderStyle: (BorderStyle inset width: 0); | |
color: self theme backgroundColor; | |
selectionColor: Smalltalk ui theme selectionColor ; | |
hideScrollBarsIndefinitely; | |
extent: 24@(Smalltalk ui theme textFont height + 8); | |
setBalloonText: nil. | |
morph textMorph: (SpotlightTextMorphForFieldView new | |
contents: ''; | |
yourself). | |
morph ghostText: 'Class|Selector to find or :<expr> to inspect'. | |
morph on: #keyStroke send: #localHandleKeystroke: to: self. | |
morph textMorph | |
onAnnouncement: MorphLostFocus | |
do: [ self delete ]. | |
morph textMorph | |
autoFit: true; | |
wrapFlag: false; | |
margins: (4@1 corner: 4@1). | |
^morph! ! | |
!Spotlight methodsFor: 'initialize' stamp: 'PhilippeBack 5/16/2014 10:35'! | |
defaultBorderColor | |
^ self theme windowColor! ! | |
!Spotlight methodsFor: 'initialize' stamp: 'EstebanLorenzano 5/1/2014 01:46'! | |
defaultColor | |
^ self theme spotlightWindowColor.! ! | |
!Spotlight methodsFor: 'events' stamp: 'BenjaminVanRyseghem 6/28/2012 17:51'! | |
updateContentsWithMenu | |
Smalltalk tools codeCompletion uniqueInstance selectedAndClose | |
ifNotNil: [ :selected | | |
search textMorph | |
newContents: (selected reject: [ :each | each = Character space ]); | |
acceptContents ].! ! | |
!Spotlight methodsFor: 'events' stamp: 'GuillermoPolito 6/28/2013 13:32'! | |
localHandleKeystroke: evt | |
"Answer whether we locally handle the keyStroke event. | |
Disregard tabs for now." | |
| crAction | | |
search textMorph acceptContents. | |
crAction := search textMorph crAction. | |
(search autoAccept and: [ evt keyCharacter = Character cr and: [ crAction notNil ] ]) | |
ifTrue: [ | |
self updateContentsWithMenu. | |
(crAction isKindOf: MessageSend) | |
ifTrue: [ crAction value] | |
ifFalse: [ crAction value: search text]. | |
^true]. | |
^false! ! | |
!Spotlight methodsFor: 'submorphs-add/remove' stamp: 'EstebanLorenzano 7/4/2012 10:47'! | |
delete | |
"Ensure menu es closed. | |
This is ugly, but is a remaining of Pluggable structure, which sucks anyway." | |
self updateContentsWithMenu. | |
super delete. | |
Current := nil! ! | |
!Spotlight methodsFor: 'opening' stamp: 'SvenVanCaekenberghe 3/25/2014 14:05'! | |
accepted | |
| input | | |
self close. | |
input := self model contents trimBoth. | |
input isEmpty ifTrue: [ ^self ]. | |
input first = $: | |
ifTrue: [ self resolveExpression: input allButFirst ] | |
ifFalse: [ self resolveSymbol: input asSymbol ]! ! | |
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! | |
Spotlight class | |
instanceVariableNames: ''! | |
!Spotlight class commentStamp: '<historical>' prior: 0! | |
! | |
!Spotlight class methodsFor: 'keymappings' stamp: 'MarcusDenker 9/11/2013 13:15'! | |
toggle | |
Current | |
ifNotNil: [ Current close. Current := nil ] | |
ifNil: [ (Current := self new) open ]! ! | |
TextMorphForFieldView subclass: #SpotlightTextMorphForFieldView | |
instanceVariableNames: '' | |
classVariableNames: '' | |
poolDictionaries: '' | |
category: 'Tools-Spotlight'! | |
!SpotlightTextMorphForFieldView commentStamp: '<historical>' prior: 0! | |
I'm a TextMorphForFieldView who prevents losing focus when tab is pressed (so I can trigger OCompletion) | |
I'm kind a hack, because if form (morph) does not has more than one element, it shouldnt try to rotate the focus, but well... life is hard :) | |
! | |
!SpotlightTextMorphForFieldView methodsFor: 'events handling' stamp: 'EstebanLorenzano 8/1/2012 11:27'! | |
localHandleKeystroke: evt | |
"Answer whether we locally handle the keyStroke event. | |
Disregard tabs for now." | |
(self editView keystrokeFromTextMorph: evt) | |
ifTrue: [^ true]. | |
(self autoAccept and: [evt keyCharacter = Character cr and: [self crAction notNil]]) | |
ifTrue: [(self crAction isKindOf: MessageSend) | |
ifTrue: [ self crAction value] | |
ifFalse: [self crAction value: self text].. | |
^ true]. | |
^false! ! |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment