Skip to content

Commit

Permalink
30691
Browse files Browse the repository at this point in the history
12619 3 minor fixes
	https://pharo.fogbugz.com/f/cases/12619

12631 methods missing in RPackageTag
	https://pharo.fogbugz.com/f/cases/12631

12634 Update
	https://pharo.fogbugz.com/f/cases/12634

12635 Better mechanism to remove a key based on its shortcut
	https://pharo.fogbugz.com/f/cases/12635

12630 Add ScriptLoader>>#commentForIssues:
	https://pharo.fogbugz.com/f/cases/12630

http://files.pharo.org/image/30/30691.zip
  • Loading branch information
Jenkins Build Server authored and ci committed Jan 13, 2014
1 parent 2f93f86 commit 7d3699f
Show file tree
Hide file tree
Showing 82 changed files with 570 additions and 75 deletions.
@@ -1,3 +1,5 @@
removeKeymapEntry: aKeymapEntry

self commonEntries remove: aKeymapEntry.
[ self commonEntries remove: aKeymapEntry ]
on: Error
do: [ self platformEntries remove: aKeymapEntry ]
@@ -1,3 +1,3 @@
keymapForShortcut: aShortcut

^ self commonEntries keymapForShortcut: aShortcut
^ self allEntries keymapForShortcut: aShortcut
@@ -0,0 +1,3 @@
keymapForShortcut: aKey

^ category keymapForShortcut: aKey
@@ -1,7 +1,14 @@
removeKeyCombination: aShortcut
| keymap |
| keymap removalTarget |

removalTarget := self directKeymaps.

keymap := self keymapForShortcut: aShortcut.
keymap ifNil: [
self targets do: [ :e | (e keymapForShortcut: aShortcut)
ifNotNil: [ :s |
removalTarget := e category.
keymap := s ] ] ].
keymap ifNil: [ ^ self ].

self directKeymaps removeKeymapEntry: keymap
removalTarget removeKeymapEntry: keymap
@@ -1,3 +1,5 @@
autoDeselect

^ self resetListSelector notNil or: [ autoDeselect ifNil: [ true ] ]
^ autoDeselect
ifNil: [ self resetListSelector notNil ]
ifNotNil: [ autoDeselect ]
Expand Up @@ -13,6 +13,9 @@ mouseUpOnSingle: event

"No change if model is locked or receiver disabled"
row == self selectionIndex
ifTrue: [self autoDeselect ifTrue:[row = 0 ifFalse: [self changeModelSelection: 0] ]]
ifFalse: [self changeModelSelection: row].
ifTrue: [
self autoDeselect
ifTrue: [ row = 0 ifFalse: [ self changeModelSelection: 0 ] ]
ifFalse: [ self changeModelSelection: row ] ]
ifFalse: [ self changeModelSelection: row ].
Cursor normal show
@@ -0,0 +1,12 @@
basicHasUnacceptedEdits: aBoolean
"Set the hasUnacceptedEdits flag to the given value. "

Smalltalk tools userManager canEditCode
ifFalse: [ aBoolean ifTrue: [ ^ self ]].
aBoolean == hasUnacceptedEdits
ifFalse: [hasUnacceptedEdits := aBoolean.
self changed].
aBoolean
ifFalse: [hasEditingConflicts := false].
self okToStyle
ifTrue: [ self styler styleInBackgroundProcess: textMorph contents]
@@ -1,12 +1,6 @@
hasUnacceptedEdits: aBoolean
"Set the hasUnacceptedEdits flag to the given value. "

Smalltalk tools userManager canEditCode
ifFalse: [ aBoolean ifTrue: [ ^ self ]].
aBoolean == hasUnacceptedEdits
ifFalse: [hasUnacceptedEdits := aBoolean.
self changed].
aBoolean
ifFalse: [hasEditingConflicts := false].
self okToStyle
ifTrue: [ self styler styleInBackgroundProcess: textMorph contents]
(model respondsTo: #hasUnacceptedEdits:)
ifTrue: [ model hasUnacceptedEdits: aBoolean ]
ifFalse: [ self basicHasUnacceptedEdits: aBoolean ]
2 changes: 1 addition & 1 deletion Morphic-Base.package/TextMorph.class/definition.st
@@ -1,6 +1,6 @@
BorderedMorph subclass: #TextMorph
uses: TAbleToRotate
instanceVariableNames: 'textStyle text wrapFlag paragraph editor container predecessor successor backgroundColor margins'
instanceVariableNames: 'textStyle text wrapFlag paragraph editor container predecessor successor backgroundColor margins defaultColor'
classVariableNames: ''
poolDictionaries: ''
category: 'Morphic-Base-Basic'
@@ -0,0 +1,7 @@
enabled: aBoolean

aBoolean
ifTrue: [ text makeAllColor: self defaultColor ]
ifFalse: [ text makeAllColor: Color lightGray ].

self changed
@@ -1,3 +1,3 @@
defaultColor
"answer the default color/fill style for the receiver"
^ Color black

^ defaultColor ifNil: [ Color black ]
@@ -1,5 +1,6 @@
text: t textStyle: s
"Private -- for use only in morphic duplication"
text := t.
defaultColor := (t attributesAt: 1) detect: [ :e | e isKindOf: TextColor ] ifNone: [ self color ].
textStyle := s.
paragraph ifNotNil: [paragraph textStyle: s]
Expand Up @@ -2,6 +2,7 @@ text: t textStyle: s wrap: wrap color: c
predecessor: pred successor: succ
"Private -- for use only in morphic duplication"
text := t.
defaultColor := (t attributesAt: 1) detect: [ :e | e isKindOf: TextColor ].
textStyle := s.
wrapFlag := wrap.
color := c.
Expand Down
@@ -0,0 +1,2 @@
extensionCategoriesForClass: aClass
^ self package extensionCategoriesForClass: aClass
@@ -0,0 +1,2 @@
includesClass: aClass
^ self hasClassNamed: aClass name

0 comments on commit 7d3699f

Please sign in to comment.