Skip to content

Commit

Permalink
20459
Browse files Browse the repository at this point in the history
  • Loading branch information
Jenkins Build Server authored and ci committed Feb 2, 2013
1 parent 6dfa753 commit b83bda6
Show file tree
Hide file tree
Showing 18 changed files with 341 additions and 71 deletions.
@@ -0,0 +1,5 @@
class initialization
flushMethodCache
"We do not named this method flushCache because it would override an important class methods."

Definitions := nil.
@@ -1,4 +1,4 @@
class initialization
shutDown
"Free up all cached monticello method definitions"
Definitions := nil.
self flushMethodCache
Expand Up @@ -4,11 +4,12 @@
"className:classIsMeta:selector:category:timeStamp:source:" : "ab 7/26/2003 02:05",
"className:selector:category:timeStamp:source:" : "ab 4/1/2003 01:40",
"cleanUp" : "StephaneDucasse 3/9/2010 16:34",
"flushMethodCache" : "StephaneDucasse 12/28/2012 21:31",
"forMethodReference:" : "CamilloBruni 6/2/2012 00:14",
"initialize" : "ab 8/22/2003 18:14",
"initializersEnabled" : "PavelKrivanek 6/22/2011 11:40",
"initializersEnabled:" : "PavelKrivanek 6/22/2011 11:40",
"shutDown" : "CamilloBruni 6/2/2012 00:13" },
"shutDown" : "StephaneDucasse 12/28/2012 21:31" },
"instance" : {
"=" : "CamilloBruni 2/28/2012 13:44",
"accept:" : "ab 7/18/2003 21:47",
Expand Down
Expand Up @@ -2,4 +2,4 @@ operations
newVersion
^ (self requestVersionNameAndMessageWithSuggestion: self uniqueVersionName) ifNotNil:
[:pair |
self newVersionWithName: pair first message: pair last].
self newVersionWithName: pair first trimBoth message: pair last].
Expand Up @@ -25,7 +25,7 @@
"merge:" : "StephaneDucasse 4/27/2010 11:52",
"merged:" : "CamilloBruni 1/19/2012 16:12",
"needsSaving" : "avi 2/13/2004 20:02",
"newVersion" : "marcus.denker 11/10/2008 10:04",
"newVersion" : "StephaneDucasse 12/19/2012 14:21",
"newVersionWithMessage:" : "AndrewBlack 9/4/2009 14:09",
"newVersionWithName:message:" : "CamilloBruni 3/2/2012 13:42",
"nextVersionName" : "MiguelCoba 7/25/2009 02:01",
Expand Down
@@ -0,0 +1,3 @@
accessing
hasExtensions
^self extensionClassNames notEmpty
@@ -0,0 +1,3 @@
listing
packageOrganizations
^ items select: [:ea | ea isOrganizationDefinition]
@@ -1,4 +1,6 @@
listing
visibleCategories
^ (self packageClasses collect: [:ea | ea category])
asSet asSortedCollection add: self extensionsCategory; yourself.
^ ((self packageOrganizations gather: [:ea | ea categories]),
(self packageClasses collect: [:ea | ea category]),
(self hasExtensions ifTrue: [{self extensionsCategory}] ifFalse: [#()]))
asSet asSortedCollection
Expand Up @@ -20,6 +20,7 @@
"defaultLabel" : "ab 7/19/2003 21:31",
"extensionClassNames" : "cwp 7/10/2003 20:23",
"extensionsCategory" : "ab 7/5/2003 23:41",
"hasExtensions" : "bf 8/21/2012 21:38",
"inspectSelection" : "cwp 7/10/2003 18:03",
"loadCategorySelection" : "nk 4/17/2004 09:53",
"loadClassSelection" : "nk 4/30/2004 15:06",
Expand All @@ -35,6 +36,7 @@
"methodsForSelectedProtocol" : "stephaneducasse 2/4/2006 20:47",
"packageClassNames" : "ab 7/18/2003 15:48",
"packageClasses" : "ab 7/18/2003 15:48",
"packageOrganizations" : "StephaneDucasse 12/28/2012 19:55",
"protocolList" : "cwp 7/10/2003 19:07",
"protocolListMenu:" : "tbn 7/6/2010 17:10",
"protocolSelection" : "cwp 7/10/2003 19:35",
Expand All @@ -54,7 +56,7 @@
"switchIsInstance" : "stephaneducasse 2/4/2006 20:47",
"text" : "lr 3/20/2010 21:05",
"text:" : "cwp 7/11/2003 00:30",
"visibleCategories" : "ab 7/18/2003 15:48",
"visibleCategories" : "bf 8/21/2012 21:42",
"visibleClasses" : "ab 7/18/2003 15:48",
"visibleMethods" : "cwp 7/10/2003 19:46",
"visibleProtocols" : "stephaneducasse 2/4/2006 20:47",
Expand Down
@@ -1,63 +1,53 @@
selection
buildSelectionBlocksFrom: topLeft to: bottomRight
buildSelectionBlocksFrom: topLeft to: bottomRight
| viewedString primary topLeftBlk bottomRightBlk findReplaceIntervals secondarySelectionIntervals startIdx stopIdx |
Display depth = 1
ifTrue: [^ self].
ifTrue: [ ^ self ].
Display depth = 2
ifTrue: [^ self].
ifTrue: [ ^ self ].
primary := selectionStart notNil
ifTrue: [selectionStart stringIndex to: selectionStop stringIndex - 1]
ifFalse: [0 to: -1].
ifTrue: [ selectionStart stringIndex to: selectionStop stringIndex - 1 ]
ifFalse: [ 0 to: -1 ].
topLeftBlk := self characterBlockAtPoint: topLeft.
bottomRightBlk := self characterBlockAtPoint: bottomRight.
startIdx := topLeftBlk stringIndex.
stopIdx := bottomRightBlk stringIndex.
viewedString := (self text copyFrom: startIdx to: stopIdx) asString.
self theme currentSettings haveSecondarySelectionTextColor
ifTrue: [self text removeAttribute: TextSelectionColor secondarySelection].
self theme currentSettings haveFindReplaceSelectionTextColor
ifTrue: [self text removeAttribute: TextSelectionColor findReplaceSelection].
ifTrue: [ self text removeAttribute: TextSelectionColor secondarySelection ].
self theme currentSettings haveFindReplaceSelectionTextColor
ifTrue: [ self text removeAttribute: TextSelectionColor findReplaceSelection ].
findReplaceIntervals := #().
extraSelectionBlocks := Array
streamContents: [:strm |
findReplaceSelectionRegex
ifNotNil: [findReplaceIntervals := findReplaceSelectionRegex matchingRangesIn: viewedString.
findReplaceIntervals := (findReplaceIntervals
collect: [:r | r + topLeftBlk stringIndex - 1])
reject: [:r | primary size > 0
and: [(r includes: primary first)
or: [primary includes: r first]]].
findReplaceIntervals
do: [:r |
self theme currentSettings haveFindReplaceSelectionTextColor
ifTrue: [
self text
addAttribute: TextSelectionColor findReplaceSelection
from: r first
to: r last].
strm
nextPut: (ParagraphSelectionBlock
first: (self characterBlockForIndex: r first)
last: (self characterBlockForIndex: r last + 1)
color: self findReplaceSelectionColor)]].
secondarySelection
ifNotNil: [secondarySelectionIntervals := viewedString allRangesOfSubString: secondarySelection.
secondarySelectionIntervals := (secondarySelectionIntervals
collect: [:r | r + topLeftBlk stringIndex - 1])
reject: [:i | (findReplaceIntervals includes: i)
or: [i = primary]].
secondarySelectionIntervals
do: [:r |
self theme currentSettings haveSecondarySelectionTextColor
ifTrue: [
self text
addAttribute: TextSelectionColor secondarySelection
from: r first
to: r last].
strm
nextPut: (ParagraphSelectionBlock
first: (self characterBlockForIndex: r first)
last: (self characterBlockForIndex: r last + 1)
color: self secondarySelectionColor)]]].
streamContents: [ :strm |
findReplaceSelectionRegex
ifNotNil: [
findReplaceIntervals := findReplaceSelectionRegex matchingRangesIn: viewedString.
findReplaceIntervals := (findReplaceIntervals collect: [ :r | r + topLeftBlk stringIndex - 1 ])
reject: [ :r | primary size > 0 and: [ (r includes: primary first) or: [ primary includes: r first ] ] ].
findReplaceIntervals
do: [ :r |
self theme currentSettings haveFindReplaceSelectionTextColor
ifTrue: [ self text addAttribute: TextSelectionColor findReplaceSelection from: r first to: r last ].
strm
nextPut:
(ParagraphSelectionBlock
first: (self characterBlockForIndex: r first)
last: (self characterBlockForIndex: r last + 1)
color: self findReplaceSelectionColor) ] ].
secondarySelection
ifNotNil: [
secondarySelectionIntervals := secondarySelection
reject: [ :i | (findReplaceIntervals includes: i) or: [ i = primary ] ].
secondarySelectionIntervals
do: [ :r |
self theme currentSettings haveSecondarySelectionTextColor
ifTrue: [ self text addAttribute: TextSelectionColor secondarySelection from: r first to: r last ].
strm
nextPut:
(ParagraphSelectionBlock
first: (self characterBlockForIndex: r first)
last: (self characterBlockForIndex: r last + 1)
color: self secondarySelectionColor) ] ] ].
findReplaceSelectionRegex := nil.
secondarySelection := nil
@@ -0,0 +1,3 @@
access
secondarySelection
^ secondarySelection
3 changes: 2 additions & 1 deletion Morphic.package/Paragraph.class/methodProperties.json
Expand Up @@ -8,7 +8,7 @@
"adjustLineIndicesBy:" : "di 11/8/97 15:47",
"adjustRightX" : "di 10/26/97 15:57",
"adjustedFirstCharacterIndex" : "di 11/16/97 09:02",
"buildSelectionBlocksFrom:to:" : "AlainPlantec 9/15/2011 17:25",
"buildSelectionBlocksFrom:to:" : "ThierryGoubier 12/21/2012 19:09",
"caretRect" : "tbn 8/5/2009 09:50",
"caretWidth" : "AlainPlantec 10/24/2010 14:30",
"centered" : "di 10/25/97 19:26",
Expand Down Expand Up @@ -59,6 +59,7 @@
"replaceFrom:to:with:" : "FernandoOlivero 3/14/2010 22:29",
"replaceFrom:to:with:displaying:" : "di 4/28/1999 10:14",
"rightFlush" : "di 10/25/97 19:26",
"secondarySelection" : "ThierryGoubier 12/20/2012 22:10",
"secondarySelection:" : "AlainPlantec 9/15/2011 15:57",
"secondarySelectionColor" : "AlainPlantec 9/15/2011 15:57",
"selectionBarColor" : "AlainPlantec 9/15/2011 15:57",
Expand Down
Expand Up @@ -3,18 +3,20 @@ refreshExtraSelection
| fullRefreshNeeded |
fullRefreshNeeded := self useSelectionBar.
self useFindReplaceSelection
ifTrue: [fullRefreshNeeded := true.
ifTrue: [
fullRefreshNeeded := true.
self findText isEmpty
ifTrue: [self paragraph findReplaceSelectionRegex: nil]
ifFalse: [self paragraph findReplaceSelectionRegex: self findRegex]].
ifTrue: [ self paragraph findReplaceSelectionRegex: nil ]
ifFalse: [ self paragraph findReplaceSelectionRegex: self findRegex ] ].
self useSecondarySelection
ifTrue: [fullRefreshNeeded := true.
self selection isEmptyOrNil
ifTrue: [self paragraph secondarySelection: nil]
ifFalse: [self paragraph secondarySelection: self selection asString]].
fullRefreshNeeded
ifTrue: [self paragraph extraSelectionChanged.
ifTrue: [
fullRefreshNeeded := true.
(self paragraph secondarySelection isNil and: [ self selection isEmptyOrNil not ])
ifTrue: [ self paragraph secondarySelection: (self text asString allRangesOfSubString: self selection asString) ] ].
fullRefreshNeeded
ifTrue: [
self paragraph extraSelectionChanged.
"> Alain: should be that :
> self paragraph extraSelectionRects do: [:r | self invalidRect: r]
> but it doesn't work"
self invalidRect: self bounds]
self invalidRect: self bounds ]
Expand Up @@ -36,7 +36,7 @@
"paragraph" : "AlainPlantec 2/21/2011 17:23",
"preferredKeyboardPosition" : "AlainPlantec 11/8/2010 22:14",
"redoTypeIn:interval:" : "AlainPlantec 11/8/2010 22:14",
"refreshExtraSelection" : "AlainPlantec 11/17/2010 16:02",
"refreshExtraSelection" : "ThierryGoubier 12/20/2012 22:27",
"replaceAll:with:" : "AlainPlantec 11/10/2010 21:30",
"replaceAll:with:startingAt:" : "AlainPlantec 11/11/2010 23:44",
"replaceSelectionWith:" : "AlainPlantec 11/10/2010 23:52",
Expand Down
@@ -1,6 +1,10 @@
public
commentForCurrentUpdate
^ 'Issue 7179: Fixed AsmJit extension methods
http://code.google.com/p/pharo/issues/detail?id=7179
^ '- Issue 7170: Open up the API for secondarySelection in editor/TextMorphForEditView. Thanks Thierry Goubier
http://code.google.com/p/pharo/issues/detail?id=7170
'
- Issue 7182: Extensions shown only when there are extensions
http://code.google.com/p/pharo/issues/detail?id=7182
- improve the MCClassDefinition cache reseting protocol'

0 comments on commit b83bda6

Please sign in to comment.