Skip to content

Commit

Permalink
50580
Browse files Browse the repository at this point in the history
17113 Context menu in SyntaxErrorDebugger broken
	https://pharo.fogbugz.com/f/cases/17113

17558 Update Rubric: In Linux some shortcuts use alt, some others ctrl
	https://pharo.fogbugz.com/f/cases/17558

17561 Add a release test to test the presence of critical classes in startup list
	https://pharo.fogbugz.com/f/cases/17561

http://files.pharo.org/image/50/50580.zip
  • Loading branch information
Jenkins Build Server authored and ci committed Feb 11, 2016
1 parent c137f86 commit 954c211
Show file tree
Hide file tree
Showing 20 changed files with 115 additions and 182 deletions.
Original file line number Diff line number Diff line change
@@ -0,0 +1,9 @@
version27: spec
<version: '2.7' imports: #('2.1-baseline' )>

spec for: #'common' do: [
spec blessing: #'stable'.
spec description: ''.
spec author: 'Guille Polito'.
spec timestamp: '9 February 2016'.
spec package: 'Rubric' with: 'Rubric-NicolaiHess.335'. ].
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
hasStartUpOrShutDownMethod: aClass
| keySelectors |
keySelectors := #(#startUp #startUp: #shutDown #shutDown:).
^ (aClass selectors includesAny: keySelectors)
or: [ aClass class selectors includesAny: keySelectors ]
Original file line number Diff line number Diff line change
@@ -0,0 +1,11 @@
testKeyClassesArePresentInStartupList
| keyClasses registeredHandlers |
keyClasses := #(#Delay #ProcessorScheduler #InputEventFetcher #ExternalObject #Alien #FFICallbackThunk #FFIMethodRegistry #Stdio #OSPlatform #UUIDGenerator #DiskStore #SmalltalkImage #WeakArray #BasicCommandLineHandler).
registeredHandlers := SessionManager default startupList
collect: #handledId.

keyClasses do: [ :className |
self assert: (registeredHandlers includes: className).
self assert: (self hasStartUpOrShutDownMethod: (Smalltalk globals at: className)) ].

self assert: (registeredHandlers includes: #UIManagerSessionHandler).
2 changes: 1 addition & 1 deletion Rubric.package/RubDisplayScanner.class/README.md
Original file line number Diff line number Diff line change
@@ -1 +1 @@
Please comment me using the following template inspired by Class Responsibility Collaborator (CRC) design:For the Class part: State a one line summary. For example, "I represent a paragraph of text".For the Responsibility part: Three sentences about my main responsibilities - what I do, what I know.For the Collaborators Part: State my main collaborators and one line about how I interact with them. Public API and Key Messages- message one - message two - (for bonus points) how to create instances. One simple example is simply gorgeous. Internal Representation and Key Implementation Points. Instance Variables backgroundColor: <Object> bitBlt: <Object> fillBlt: <Object> foregroundColor: <Object> ignoreColorChanges: <Object> lineHeight: <Object> lineY: <Object> morphicOffset: <Object> runX: <Object> Implementation Points
Please comment me using the following template inspired by Class Responsibility Collaborator (CRC) design:For the Class part: State a one line summary. For example, "I represent a paragraph of text".For the Responsibility part: Three sentences about my main responsibilities - what I do, what I know.For the Collaborators Part: State my main collaborators and one line about how I interact with them. Public API and Key Messages- message one - message two - (for bonus points) how to create instances. One simple example is simply gorgeous. Internal Representation and Key Implementation Points. Instance Variables backgroundColor: <Object> bitBlt: <Object> defaultTextColor: <Object> fillBlt: <Object> foregroundColor: <Object> ignoreColorChanges: <Object> lineHeight: <Object> lineY: <Object> morphicOffset: <Object> runX: <Object> Implementation Points
Expand Down
2 changes: 1 addition & 1 deletion Rubric.package/RubDisplayScanner.class/definition.st
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
RubCharacterScanner subclass: #RubDisplayScanner
instanceVariableNames: 'bitBlt lineY runX foregroundColor backgroundColor fillBlt lineHeight morphicOffset ignoreColorChanges'
instanceVariableNames: 'bitBlt lineY runX foregroundColor backgroundColor fillBlt lineHeight morphicOffset ignoreColorChanges defaultTextColor'
classVariableNames: ''
poolDictionaries: ''
category: 'Rubric-TextScanning'
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
defaultTextColor
defaultTextColor ifNil: [ defaultTextColor := Smalltalk ui theme textColor ].
^ defaultTextColor
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
setFont
foregroundColor := self defaultTextColor.
super setFont. "Sets font and emphasis bits, and maybe foregroundColor"
font installOn: bitBlt foregroundColor: foregroundColor backgroundColor: Color transparent.
text ifNotNil:[
Expand Down
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
buildShortcutsOn: aBuilder
"We are defining the bindings twice because we want to support
both Cmd and Ctrl for Windows and Linux. This should happen at least as long as in the development environment
both Cmd and meta for Windows and Linux. This should happen at least as long as in the development environment
both of these are supported.
We list both variations explicitly because we want to be able to see the action code when inspecting the morph.
Expand All @@ -9,114 +9,70 @@ buildShortcutsOn: aBuilder
<keymap>
(aBuilder shortcut: #querySymbol)
category: RubSmalltalkEditor name
default: $q ctrl
do: [ :target | target editor querySymbol: nil ]
description: 'Query symbol'.
(aBuilder shortcut: #querySymbol)
category: RubSmalltalkEditor name
default: $q command
default: $q meta
do: [ :target | target editor querySymbol: nil ]
description: 'Query symbol'.

(aBuilder shortcut: #browseIt)
category: RubSmalltalkEditor name
default: $b ctrl
do: [ :target | target editor browseIt: nil ]
description: 'Browse'.
(aBuilder shortcut: #browseItCommand)
category: RubSmalltalkEditor name
default: $b command
default: $b meta
do: [ :target | target editor browseIt: nil ]
description: 'Browse'.

(aBuilder shortcut: #doIt)
category: RubSmalltalkEditor name
default: $d ctrl
do: [ :target | target editor doIt: nil ]
description: 'Do it'.
(aBuilder shortcut: #doItCommand)
category: RubSmalltalkEditor name
default: $d command
default: $d meta
do: [ :target | target editor doIt: nil ]
description: 'Do it'.

(aBuilder shortcut: #inspectIt)
category: RubSmalltalkEditor name
default: $i ctrl
default: $i meta
do: [ :target | target editor inspectIt: nil ]
description: 'Inspect it'.

(aBuilder shortcut: #basicInspectIt)
category: RubSmalltalkEditor name
default: $i shift ctrl
do: [ :target | target editor basicInspectIt ]
description: 'Basic Inspect it'.
(aBuilder shortcut: #basicInspectItCommand)
category: RubSmalltalkEditor name
default: $i shift command
default: $i meta shift
do: [ :target | target editor basicInspectIt ]
description: 'Basic Inspect it'.
(aBuilder shortcut: #inspectItCommand)
category: RubSmalltalkEditor name
default: $i command
do: [ :target | target editor inspectIt: nil ]
description: 'Inspect it'.

(aBuilder shortcut: #implementorsOfIt)
category: RubSmalltalkEditor name
default: $m ctrl
do: [ :target | target editor implementorsOfIt: nil ]
description: 'Implementors of it'.
(aBuilder shortcut: #implementorsOfItCommand)
category: RubSmalltalkEditor name
default: $m command
default: $m meta
do: [ :target | target editor implementorsOfIt: nil ]
description: 'Implementors of it'.

(aBuilder shortcut: #senderOfIt)
category: RubSmalltalkEditor name
default: $n ctrl
do: [ :target | target editor sendersOfIt: nil ]
description: 'Senders of it'.
(aBuilder shortcut: #senderOfItCommand)
category: RubSmalltalkEditor name
default: $n command
default: $n meta
do: [ :target | target editor sendersOfIt: nil ]
description: 'Senders of it'.

(aBuilder shortcut: #printIt)
category: RubSmalltalkEditor name
default: $p ctrl
do: [ :target | target editor printIt ]
description: 'Print it'.
(aBuilder shortcut: #printItCommand)
category: RubSmalltalkEditor name
default: $p command
default: $p meta
do: [ :target | target editor printIt ]
description: 'Print it'.

(aBuilder shortcut: #debugIt)
category: RubSmalltalkEditor name
default: $d shift ctrl
do: [ :target | target editor debugIt: nil ]
description: 'Debug it'.
(aBuilder shortcut: #debugItCommand)
category: RubSmalltalkEditor name
default: $d shift command
default: $d meta shift
do: [ :target | target editor debugIt: nil ]
description: 'Debug it'.

(aBuilder shortcut: #referencesToIt)
category: RubSmalltalkEditor name
default: $n shift ctrl
do: [ :target | target editor referencesToIt: nil ]
description: 'References to it'.
(aBuilder shortcut: #referencesToItCommand)
category: RubSmalltalkEditor name
default: $n shift command
default: $n meta shift
do: [ :target | target editor referencesToIt: nil ]
description: 'References to it'.

(aBuilder shortcut: #methodStringsContainingIt)
category: RubSmalltalkEditor name
default: $e shift ctrl | $e shift command mac
do: [ :target | target editor methodStringsContainingIt: nil ]
description: 'Method strings containing it'.
(aBuilder shortcut: #methodStringsContainingItCommand)
category: RubSmalltalkEditor name
default: $e shift command
default: $e meta shift
do: [ :target | target editor methodStringsContainingIt: nil ]
description: 'Method strings containing it'.

(aBuilder shortcut: #format)
category: RubSmalltalkEditor name
default: PharoShortcuts current formatCodeShortcut
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -8,144 +8,78 @@ buildShortcutsOn: aBuilder
<keymap>
(aBuilder shortcut: #cancel)
category: RubTextEditor name
default: $l ctrl
do: [ :target | target editor cancel ]
description: 'Cancel unsaved editings'.
(aBuilder shortcut: #cancelCommand)
category: RubTextEditor name
default: $l command
default: $l meta
do: [ :target | target editor cancel ]
description: 'Cancel unsaved editings'.

(aBuilder shortcut: #accept)
category: RubTextEditor name
default: $s ctrl
do: [ :target | target editor accept ]
description: 'Accept unsaved editings'.
(aBuilder shortcut: #acceptCommand)
category: RubTextEditor name
default: $s command
default: $s meta
do: [ :target | target editor accept ]
description: 'Accept unsaved editings'.

(aBuilder shortcut: #selectAll)
category: RubTextEditor name
default: $a ctrl
do: [ :target | target editor selectAll: nil ]
description: 'Select all'.
(aBuilder shortcut: #selectAllCommand)
category: RubTextEditor name
default: $a command
default: $a meta
do: [ :target | target editor selectAll: nil ]
description: 'Select all'.

(aBuilder shortcut: #copySelection)
category: RubTextEditor name
default: $c ctrl
do: [ :target | target editor copySelection ]
description: 'Copy selection'.
(aBuilder shortcut: #copySelectionCommand)
category: RubTextEditor name
default: $c command
default: $c meta
do: [ :target | target editor copySelection ]
description: 'Copy selection'.

(aBuilder shortcut: #paste)
category: RubTextEditor name
default: $v ctrl
do: [ :target | target editor paste ]
description: 'Paste'.
(aBuilder shortcut: #pasteCommand)
category: RubTextEditor name
default: $v command
default: $v meta
do: [ :target | target editor paste ]
description: 'Paste'.


(aBuilder shortcut: #cut)
category: RubTextEditor name
default: $x ctrl
do: [ :target | target editor cut ]
description: 'Cut selection'.
(aBuilder shortcut: #cutCommand)
category: RubTextEditor name
default: $x command
default: $x meta
do: [ :target | target editor cut ]
description: 'Cut selection'.

(aBuilder shortcut: #undo)
(aBuilder shortcut: #undometa)
category: RubTextEditor name
default: $z ctrl
do: [ :target | target editor undo ]
description: 'Undo'.
(aBuilder shortcut: #undoCommand)
category: RubTextEditor name
default: $z command
default: $z meta
do: [ :target | target editor undo ]
description: 'Undo'.

(aBuilder shortcut: #redo)
category: RubTextEditor name
default: $z shift ctrl
do: [ :target | target editor redo ]
description: 'Redo'.
(aBuilder shortcut: #redoCommand)
(aBuilder shortcut: #redometa)
category: RubTextEditor name
default: $z shift command
default: $z meta shift
do: [ :target | target editor redo ]
description: 'Redo'.

(aBuilder shortcut: #find)
category: RubTextEditor name
default: $f ctrl
do: [ :target | target editor find: nil ]
description: 'Find text'.
(aBuilder shortcut: #find)
category: RubTextEditor name
default: $f command
default: $f meta
do: [ :target | target editor find: nil ]
description: 'Find text'.

(aBuilder shortcut: #findAgain)
(aBuilder shortcut: #findAgainmeta)
category: RubTextEditor name
default: $g ctrl
do: [ :target | target editor findAgain: nil ]
description: 'Find text again'.
(aBuilder shortcut: #findAgainCommand)
category: RubTextEditor name
default: $g command
default: $g meta
do: [ :target | target editor findAgain: nil ]
description: 'Find text again'.

(aBuilder shortcut: #indent)
category: RubTextEditor name
default: $r shift ctrl
do: [ :target | target editor indent: nil ]
description: 'Indent'.
(aBuilder shortcut: #indentCommand)
category: RubTextEditor name
default: $r shift command
default: $r meta shift
do: [ :target | target editor indent: nil ]
description: 'Indent'.

(aBuilder shortcut: #outdent)
category: RubTextEditor name
default: $l shift ctrl
do: [ :target | target editor outdent: nil ]
description: 'Outdent'.
(aBuilder shortcut: #outdentCommand)
category: RubTextEditor name
default: $l shift command
default: $l meta shift
do: [ :target | target editor outdent: nil ]
description: 'Outdent'.

(aBuilder shortcut: #compareToClipboard)
category: RubTextEditor name
default: $c shift ctrl
do: [ :target | target editor compareToClipboard: nil ]
description: 'Compare selection to clipboard'.
(aBuilder shortcut: #compareToClipboard)
category: RubTextEditor name
default: $c shift command
default: $c meta shift
do: [ :target | target editor compareToClipboard: nil ]
description: 'Compare selection to clipboard'.
description: 'Compare selection to clipboard'.
Original file line number Diff line number Diff line change
Expand Up @@ -5,9 +5,9 @@ exampleWithCustomShortcut

"define a custom shortcut - notice the call to textArea"

text textArea removeKeyCombination: $s command.
text textArea removeKeyCombination: $s meta.
text setText: 'Hit cmd $s to revert the text'.
text textArea on:$s command do:[
text textArea on: $s meta do:[
text setText: text text asString reverse].

window := StandardWindow new.
Expand Down
Loading

0 comments on commit 954c211

Please sign in to comment.