diff --git a/ConfigurationOfGTInspector.package/ConfigurationOfGTInspector.class/instance/versions/version103_.st b/ConfigurationOfGTInspector.package/ConfigurationOfGTInspector.class/instance/versions/version103_.st new file mode 100644 index 0000000000..a784476d53 --- /dev/null +++ b/ConfigurationOfGTInspector.package/ConfigurationOfGTInspector.class/instance/versions/version103_.st @@ -0,0 +1,16 @@ +version103: spec + + + spec for: #'common' do: [ + spec blessing: #'stable'. + spec description: 'version 1.0.3'. + spec author: 'AndreiChis'. + spec timestamp: '9/30/2014 14:52'. + spec + project: 'GlamourCore' with: '2.72'. + spec + package: #'GT-Inspector' with: 'GT-Inspector-TudorGirba.239'; + package: 'GT-InspectorExtensions-Core' with: [ + spec file: 'GT-InspectorExtensions-Core-AndreiChis.56'. + spec repository: 'http://www.smalltalkhub.com/mc/PharoExtras/GTToolsIntegration/main' ]; + package: 'GT-Tests-Inspector' with: 'GT-Tests-Inspector-TudorGirba.22'. ]. diff --git a/ConfigurationOfGTPlayground.package/ConfigurationOfGTPlayground.class/instance/versions/version103_.st b/ConfigurationOfGTPlayground.package/ConfigurationOfGTPlayground.class/instance/versions/version103_.st new file mode 100644 index 0000000000..1144d3f9f9 --- /dev/null +++ b/ConfigurationOfGTPlayground.package/ConfigurationOfGTPlayground.class/instance/versions/version103_.st @@ -0,0 +1,12 @@ +version103: spec + + + spec for: #'common' do: [ + spec blessing: #'stable'. + spec description: 'version 1.0.3 bug fixing'. + spec author: 'AndreiChis'. + spec timestamp: '10/01/2014 14:52'. + spec project: 'GTInspector' with: '1.0.3'. + spec package: 'GT-Playground' with: [ + spec file: 'GT-Playground-AndreiChis.36'. + spec repository: 'http://www.smalltalkhub.com/mc/PharoExtras/GTToolsIntegration/main' ] ] diff --git a/ConfigurationOfGlamour.package/ConfigurationOfGlamour.class/instance/versions/version272_.st b/ConfigurationOfGlamour.package/ConfigurationOfGlamour.class/instance/versions/version272_.st new file mode 100644 index 0000000000..20fd43992c --- /dev/null +++ b/ConfigurationOfGlamour.package/ConfigurationOfGlamour.class/instance/versions/version272_.st @@ -0,0 +1,36 @@ +version272: spec + + + spec for: #'common' do: [ + spec blessing: #'stable'. + spec description: 'version 2.72'. + spec author: 'AndreiChis'. + spec timestamp: '10/01/2014 14:31'. + spec + package: 'Glamour-Announcements' with: 'Glamour-Announcements-TudorGirba.7'; + package: 'Glamour-Helpers' with: 'Glamour-Helpers-AndreiChis.35'; + package: 'Glamour-Core' with: 'Glamour-Core-AndreiChis.277'; + package: 'Glamour-Presentations' with: 'Glamour-Presentations-AndreiChis.158'; + package: 'Glamour-Browsers' with: 'Glamour-Browsers-TudorGirba.104'; + package: 'Glamour-Tests-Core' with: 'Glamour-Tests-Core-AndreiChis.96'; + package: 'Glamour-Morphic-Widgets' with: [ + spec file: 'Glamour-Morphic-Widgets-AndreiChis.128'. + spec repository: 'http://www.smalltalkhub.com/mc/PharoExtras/GTToolsIntegration/main' ]; + package: 'Glamour-Morphic-Renderer' with: [ + spec file: 'Glamour-Morphic-Renderer-AndreiChis.272'. + spec repository: 'http://www.smalltalkhub.com/mc/PharoExtras/GTToolsIntegration/main' ]; + package: 'Glamour-Morphic-Pager' with: 'Glamour-Morphic-Pager-AliakseiSyrel.67'; + package: 'Glamour-Morphic-Theme' with: 'Glamour-Morphic-Theme-AndreiChis.180'; + package: 'Glamour-Tests-Morphic' with: 'Glamour-Tests-Morphic-AliakseiSyrel.115'; + package: 'Glamour-Examples' with: 'Glamour-Examples-StephanEggermont.284'; + package: 'Glamour-Rubric-Presentations' with: 'Glamour-Rubric-Presentations-AndreiChis.23'; + package: 'Glamour-Tests-Rubric' with: 'Glamour-Tests-Rubric-AndreiChis.13'; + package: 'Glamour-Tests-Resources' with: 'Glamour-Tests-Resources-AndreiChis.3'. ]. + + spec for: #'common' do: [ + spec blessing: #'stable'. + spec description: 'version 2.72'. + spec author: 'AndreiChis'. + spec timestamp: '10/01/2014 14:31'. + spec + project: 'Rubric' with: '1.2.1'. ]. diff --git a/ConfigurationOfRubric.package/ConfigurationOfRubric.class/instance/versions/version121_.st b/ConfigurationOfRubric.package/ConfigurationOfRubric.class/instance/versions/version121_.st new file mode 100644 index 0000000000..861d42cff8 --- /dev/null +++ b/ConfigurationOfRubric.package/ConfigurationOfRubric.class/instance/versions/version121_.st @@ -0,0 +1,9 @@ +version121: spec + + + spec for: #'common' do: [ + spec blessing: #'stable'. + spec description: 'version 1.2.1'. + spec author: 'AndreiChis'. + spec timestamp: '10/01/2014 14:27'. + spec package: 'Rubric' with: 'Rubric-AndreiChis.136'. ]. diff --git a/Glamour-Morphic-Renderer.package/GLMMorphicPharoCodeRenderer.class/instance/callbacks/evaluateAndPopPrintSelection.st b/Glamour-Morphic-Renderer.package/GLMMorphicPharoCodeRenderer.class/instance/callbacks/evaluateAndPopPrintSelection.st index 52f04486f7..da4f8ce4d9 100644 --- a/Glamour-Morphic-Renderer.package/GLMMorphicPharoCodeRenderer.class/instance/callbacks/evaluateAndPopPrintSelection.st +++ b/Glamour-Morphic-Renderer.package/GLMMorphicPharoCodeRenderer.class/instance/callbacks/evaluateAndPopPrintSelection.st @@ -1,5 +1,6 @@ evaluateAndPopPrintSelection - UIManager default defer: [ - GLMPrintPopper new evaluateAndOpenFromRubric: textMorph textArea - ] - \ No newline at end of file + + textMorph textArea editor evaluateSelectionAndDo: [ :result | + GLMPrintPopper installAlarmFor: [ + GLMPrintPopper new + openFromRubric: textMorph textArea withResult: result ] ] \ No newline at end of file diff --git a/Glamour-Morphic-Renderer.package/GLMMorphicRenderer.class/instance/rendering presentations/renderRubricSmalltalkCodePresentation_.st b/Glamour-Morphic-Renderer.package/GLMMorphicRenderer.class/instance/rendering presentations/renderRubricSmalltalkCodePresentation_.st deleted file mode 100644 index ff1f5f6c2c..0000000000 --- a/Glamour-Morphic-Renderer.package/GLMMorphicRenderer.class/instance/rendering presentations/renderRubricSmalltalkCodePresentation_.st +++ /dev/null @@ -1,2 +0,0 @@ -renderRubricSmalltalkCodePresentation: aPresentation - ^ GLMMorphicRubricSmalltalkCodeRenderer render: aPresentation from: self \ No newline at end of file diff --git a/Glamour-Morphic-Renderer.package/GLMMorphicRubricSmalltalkCodeRenderer.class/README.md b/Glamour-Morphic-Renderer.package/GLMMorphicRubricSmalltalkCodeRenderer.class/README.md deleted file mode 100644 index 0c12aabe48..0000000000 --- a/Glamour-Morphic-Renderer.package/GLMMorphicRubricSmalltalkCodeRenderer.class/README.md +++ /dev/null @@ -1 +0,0 @@ -A GLMMorphicRubricSmalltalkCodeRenderer is xxxxxxxxx. \ No newline at end of file diff --git a/Glamour-Morphic-Renderer.package/GLMMorphicRubricSmalltalkCodeRenderer.class/definition.st b/Glamour-Morphic-Renderer.package/GLMMorphicRubricSmalltalkCodeRenderer.class/definition.st deleted file mode 100644 index da75b3a2da..0000000000 --- a/Glamour-Morphic-Renderer.package/GLMMorphicRubricSmalltalkCodeRenderer.class/definition.st +++ /dev/null @@ -1,5 +0,0 @@ -GLMMorphicRubricTextRenderer subclass: #GLMMorphicRubricSmalltalkCodeRenderer - instanceVariableNames: '' - classVariableNames: '' - poolDictionaries: '' - category: 'Glamour-Morphic-Renderer' \ No newline at end of file diff --git a/Glamour-Morphic-Renderer.package/GLMMorphicRubricSmalltalkCodeRenderer.class/instance/rendering/morph.st b/Glamour-Morphic-Renderer.package/GLMMorphicRubricSmalltalkCodeRenderer.class/instance/rendering/morph.st deleted file mode 100644 index 485023ce16..0000000000 --- a/Glamour-Morphic-Renderer.package/GLMMorphicRubricSmalltalkCodeRenderer.class/instance/rendering/morph.st +++ /dev/null @@ -1,5 +0,0 @@ -morph - ^ RubScrolledTextMorph new - model: textModel; - beForSmalltalkCode; - yourself \ No newline at end of file diff --git a/Glamour-Morphic-Widgets.package/GLMErrorPopper.class/README.md b/Glamour-Morphic-Widgets.package/GLMErrorPopper.class/README.md index 91e54cbb56..a0789f25a2 100644 --- a/Glamour-Morphic-Widgets.package/GLMErrorPopper.class/README.md +++ b/Glamour-Morphic-Widgets.package/GLMErrorPopper.class/README.md @@ -1 +1 @@ -A GLMErrorPopper is xxxxxxxxx. \ No newline at end of file +I am a popper that displays an error message. GLMErrorPopper simpleErrorPopper \ No newline at end of file diff --git a/Glamour-Morphic-Widgets.package/GLMErrorPopper.class/class/examples/simpleErrorPopper.st b/Glamour-Morphic-Widgets.package/GLMErrorPopper.class/class/examples/simpleErrorPopper.st new file mode 100644 index 0000000000..4fbd8fba34 --- /dev/null +++ b/Glamour-Morphic-Widgets.package/GLMErrorPopper.class/class/examples/simpleErrorPopper.st @@ -0,0 +1,8 @@ +simpleErrorPopper + " + self simpleErrorPopper + " + + (GLMErrorPopper new + withString: 'error message goes here' + from: RubScrolledTextMorph new) openInWorld \ No newline at end of file diff --git a/Glamour-Morphic-Widgets.package/GLMPopper.class/README.md b/Glamour-Morphic-Widgets.package/GLMPopper.class/README.md index 53b53cd321..ccd3385b17 100644 --- a/Glamour-Morphic-Widgets.package/GLMPopper.class/README.md +++ b/Glamour-Morphic-Widgets.package/GLMPopper.class/README.md @@ -1 +1 @@ -This is a morph used for previewing print it actions. It has a special ability to delete itself either when Esc is pressed, or when the focus is lost. \ No newline at end of file +This is a morph used for displaying various notifications. It has a special ability to delete itself either when Esc is pressed, or when the focus is lost. When opened the user has to spefify a text morph whose position and cursor are user to position this morph. When triggered from a context menu action the class method installAlarmFor: should be used to open the popper as the text morph gets back the focus after the action was executed (and, hence, the popper is closed). \ No newline at end of file diff --git a/Glamour-Morphic-Widgets.package/GLMPopper.class/class/utils/installAlarmFor_.st b/Glamour-Morphic-Widgets.package/GLMPopper.class/class/utils/installAlarmFor_.st new file mode 100644 index 0000000000..fa8d19168d --- /dev/null +++ b/Glamour-Morphic-Widgets.package/GLMPopper.class/class/utils/installAlarmFor_.st @@ -0,0 +1,7 @@ +installAlarmFor: aBlock + + World + addAlarm: #value + withArguments: #() + for: aBlock + at: Time millisecondClockValue + 50. \ No newline at end of file diff --git a/Glamour-Morphic-Widgets.package/GLMPopper.class/instance/private/updateWithString_from_.st b/Glamour-Morphic-Widgets.package/GLMPopper.class/instance/private/updateWithString_from_.st index d17ff9966e..f1653e28f4 100644 --- a/Glamour-Morphic-Widgets.package/GLMPopper.class/instance/private/updateWithString_from_.st +++ b/Glamour-Morphic-Widgets.package/GLMPopper.class/instance/private/updateWithString_from_.st @@ -10,4 +10,5 @@ updateWithString: string from: aMorph aMorph takeKeyboardFocus ]; onAnnouncement: MorphLostFocus do: [ :ann | self delete. - aMorph takeKeyboardFocus ] \ No newline at end of file + "If this event is triggered then another morph already has the focus. + Do not attempt to give the focus back to the original morph" ] \ No newline at end of file diff --git a/Glamour-Morphic-Widgets.package/GLMPopperNotificationStrategy.class/README.md b/Glamour-Morphic-Widgets.package/GLMPopperNotificationStrategy.class/README.md index 09a72077d4..fc814d7cc0 100644 --- a/Glamour-Morphic-Widgets.package/GLMPopperNotificationStrategy.class/README.md +++ b/Glamour-Morphic-Widgets.package/GLMPopperNotificationStrategy.class/README.md @@ -1 +1 @@ -A GLMPopperNotificationStrategy is xxxxxxxxx. \ No newline at end of file +I opened a new popper window that displays the given notification. (I do not alter the content of the text editor.) \ No newline at end of file diff --git a/Glamour-Morphic-Widgets.package/GLMPopperNotificationStrategy.class/instance/as yet unclassified/notify_at_in_.st b/Glamour-Morphic-Widgets.package/GLMPopperNotificationStrategy.class/instance/as yet unclassified/notify_at_in_.st index 5c2e499948..cd62284126 100644 --- a/Glamour-Morphic-Widgets.package/GLMPopperNotificationStrategy.class/instance/as yet unclassified/notify_at_in_.st +++ b/Glamour-Morphic-Widgets.package/GLMPopperNotificationStrategy.class/instance/as yet unclassified/notify_at_in_.st @@ -5,5 +5,6 @@ notify: aString at: anInteger in: aStream ifFalse: [anInteger]. self editor selectFrom: pos to: pos. - (GLMErrorPopper new withString: aString from: self editor textArea owner owner owner) - openInWorld \ No newline at end of file + GLMErrorPopper installAlarmFor: [ + (GLMErrorPopper new withString: aString from: self editor textArea owner owner owner) + openInWorld ] \ No newline at end of file diff --git a/Glamour-Morphic-Widgets.package/GLMPrintPopper.class/README.md b/Glamour-Morphic-Widgets.package/GLMPrintPopper.class/README.md index 6e477ceccf..a619bda930 100644 --- a/Glamour-Morphic-Widgets.package/GLMPrintPopper.class/README.md +++ b/Glamour-Morphic-Widgets.package/GLMPrintPopper.class/README.md @@ -1 +1 @@ -A GLMPrintPopper is xxxxxxxxx. Instance Variables inspectButton: inspectButton - xxxxx \ No newline at end of file +I am a popper that displays a notification message: I can display a given object or evaluate the selection of the attached text editor. I also offer a button for inspecting the object that is displayed. GLMPrintPopper simpleObjectPopper GLMPrintPopper selectionEvaluationPopper \ No newline at end of file diff --git a/Glamour-Morphic-Widgets.package/GLMPrintPopper.class/class/examples/selectionEvaluationPopper.st b/Glamour-Morphic-Widgets.package/GLMPrintPopper.class/class/examples/selectionEvaluationPopper.st new file mode 100644 index 0000000000..fba3c57209 --- /dev/null +++ b/Glamour-Morphic-Widgets.package/GLMPrintPopper.class/class/examples/selectionEvaluationPopper.st @@ -0,0 +1,9 @@ +selectionEvaluationPopper + " + self selectionEvaluationPopper + " + GLMPrintPopper new + evaluateAndOpenFromRubric: (RubScrolledTextMorph new + beForSmalltalkCode; + updateTextWith: '1+2+4'; + setSelection: (1to:6)) \ No newline at end of file diff --git a/Glamour-Morphic-Widgets.package/GLMPrintPopper.class/class/examples/simpleObjectPopper.st b/Glamour-Morphic-Widgets.package/GLMPrintPopper.class/class/examples/simpleObjectPopper.st new file mode 100644 index 0000000000..a3ea424d5d --- /dev/null +++ b/Glamour-Morphic-Widgets.package/GLMPrintPopper.class/class/examples/simpleObjectPopper.st @@ -0,0 +1,8 @@ +simpleObjectPopper + " + self simpleObjectPopper + " + + GLMPrintPopper new + openFromRubric: RubScrolledTextMorph new + withResult: 'notification goes here'. \ No newline at end of file diff --git a/Glamour-Morphic-Widgets.package/GLMPrintPopper.class/instance/public/evaluateAndOpenFromRubric_.st b/Glamour-Morphic-Widgets.package/GLMPrintPopper.class/instance/public/evaluateAndOpenFromRubric_.st index 3e8126e375..15fbb4687f 100644 --- a/Glamour-Morphic-Widgets.package/GLMPrintPopper.class/instance/public/evaluateAndOpenFromRubric_.st +++ b/Glamour-Morphic-Widgets.package/GLMPrintPopper.class/instance/public/evaluateAndOpenFromRubric_.st @@ -1,11 +1,5 @@ evaluateAndOpenFromRubric: aMorph - | string result | - result := aMorph textArea editor evaluateSelectionAndDo: [ :x | x ]. - string := result asString. - self withString: string from: aMorph. - self width: self width + inspectButton width. - textMorph - on: $i command - do: [ result inspect ]. - inspectButton addUpAction: [ result inspect ]. - self openInWorld \ No newline at end of file + + self + openFromRubric: aMorph + withResult: aMorph textArea editor evaluateSelection \ No newline at end of file diff --git a/Glamour-Morphic-Widgets.package/GLMPrintPopper.class/instance/public/openFromRubric_withResult_.st b/Glamour-Morphic-Widgets.package/GLMPrintPopper.class/instance/public/openFromRubric_withResult_.st new file mode 100644 index 0000000000..faf807fd1a --- /dev/null +++ b/Glamour-Morphic-Widgets.package/GLMPrintPopper.class/instance/public/openFromRubric_withResult_.st @@ -0,0 +1,10 @@ +openFromRubric: aMorph withResult: anObject + | string | + string := anObject asString. + self withString: string from: aMorph. + self width: self width + inspectButton width. + textMorph + on: $i command + do: [ anObject inspect ]. + inspectButton addUpAction: [ anObject inspect ]. + self openInWorld \ No newline at end of file diff --git a/Glamour-Presentations.package/GLMPrintSelection.class/README.md b/Glamour-Presentations.package/GLMPrintSelection.class/README.md index 7632f8ed7a..f1193d359c 100644 --- a/Glamour-Presentations.package/GLMPrintSelection.class/README.md +++ b/Glamour-Presentations.package/GLMPrintSelection.class/README.md @@ -1 +1 @@ -A GLMPrintSelection is xxxxxxxxx. \ No newline at end of file +I am event indicating to the renderer to execute and print the currently selected text. \ No newline at end of file diff --git a/Glamour-Rubric-Presentations.package/GLMNewSmalltalkCodePresentation.class/README.md b/Glamour-Rubric-Presentations.package/GLMNewSmalltalkCodePresentation.class/README.md deleted file mode 100644 index b49fcf29bf..0000000000 --- a/Glamour-Rubric-Presentations.package/GLMNewSmalltalkCodePresentation.class/README.md +++ /dev/null @@ -1 +0,0 @@ -A GLMNewSmalltalkCodePresentation is xxxxxxxxx. \ No newline at end of file diff --git a/Glamour-Rubric-Presentations.package/GLMNewSmalltalkCodePresentation.class/definition.st b/Glamour-Rubric-Presentations.package/GLMNewSmalltalkCodePresentation.class/definition.st deleted file mode 100644 index 8118a02ee9..0000000000 --- a/Glamour-Rubric-Presentations.package/GLMNewSmalltalkCodePresentation.class/definition.st +++ /dev/null @@ -1,5 +0,0 @@ -GLMRubricTextPresentation subclass: #GLMNewSmalltalkCodePresentation - instanceVariableNames: '' - classVariableNames: '' - poolDictionaries: '' - category: 'Glamour-Rubric-Presentations' \ No newline at end of file diff --git a/Glamour-Rubric-Presentations.package/GLMPharoMethodPresentation.class/README.md b/Glamour-Rubric-Presentations.package/GLMPharoMethodPresentation.class/README.md index 3c0ad1fd02..9448f1a5e4 100644 --- a/Glamour-Rubric-Presentations.package/GLMPharoMethodPresentation.class/README.md +++ b/Glamour-Rubric-Presentations.package/GLMPharoMethodPresentation.class/README.md @@ -1 +1 @@ -|browser| browser := GLMTabulator new. browser row: #r1; row: #r2. browser transmit to: #r1; andShow: [ :aComposite | aComposite pharoMethod display: [ :method | method sourceCode ] ]. browser transmit to: #r2; andShow: [ :aComposite | aComposite pharoMethod display: [ :method | method sourceCode ] ; smalltalkClass: [ :method | method methodClass ] ]. browser openOn: (CompiledMethod class>>#gtExampleSimple) \ No newline at end of file +I provide support for displaying a Smalltalk method. self pharoMethodPresentationExample \ No newline at end of file diff --git a/Glamour-Rubric-Presentations.package/GLMPharoMethodPresentation.class/class/examples/pharoMethodPresentationExample.st b/Glamour-Rubric-Presentations.package/GLMPharoMethodPresentation.class/class/examples/pharoMethodPresentationExample.st new file mode 100644 index 0000000000..4ffb81ce0b --- /dev/null +++ b/Glamour-Rubric-Presentations.package/GLMPharoMethodPresentation.class/class/examples/pharoMethodPresentationExample.st @@ -0,0 +1,20 @@ +pharoMethodPresentationExample + " + self pharoMethodPresentationExample + " + + | browser | + browser := GLMTabulator new. + browser + row: #r1; + row: #r2. + browser transmit + to: #r1; + andShow: [ :aComposite | aComposite pharoMethod display: [ :method | method sourceCode ] ]. + browser transmit + to: #r2; + andShow: [ :aComposite | + aComposite pharoMethod + display: [ :method | method sourceCode ]; + smalltalkClass: [ :method | method methodClass ] ]. + browser openOn: CompiledMethod class >> #gtExampleSimple \ No newline at end of file diff --git a/Glamour-Rubric-Presentations.package/GLMPharoMethodPresentation.class/definition.st b/Glamour-Rubric-Presentations.package/GLMPharoMethodPresentation.class/definition.st index 1311f7a059..3d4cc00247 100644 --- a/Glamour-Rubric-Presentations.package/GLMPharoMethodPresentation.class/definition.st +++ b/Glamour-Rubric-Presentations.package/GLMPharoMethodPresentation.class/definition.st @@ -1,4 +1,4 @@ -GLMNewSmalltalkCodePresentation subclass: #GLMPharoMethodPresentation +GLMRubricSmalltalkCodePresentation subclass: #GLMPharoMethodPresentation instanceVariableNames: 'highlightSmalltalkContext' classVariableNames: '' poolDictionaries: '' diff --git a/Glamour-Rubric-Presentations.package/GLMPharoPlaygroundPresentation.class/README.md b/Glamour-Rubric-Presentations.package/GLMPharoPlaygroundPresentation.class/README.md index 839ccd3dcd..cbdc427304 100644 --- a/Glamour-Rubric-Presentations.package/GLMPharoPlaygroundPresentation.class/README.md +++ b/Glamour-Rubric-Presentations.package/GLMPharoPlaygroundPresentation.class/README.md @@ -1 +1 @@ -|browser| browser := GLMTabulator new. browser row: #r1; row: #r2. browser transmit to: #r1; andShow: [ :aComposite | aComposite pharoPlayground selectionAct: [ :workspace :page | workspace evaluateSelection ] on: $d entitled: 'Do it'; selectionAct: [ :workspace :page | workspace evaluateSelectionAndDo: [:result | result inspect] ] on: $i entitled: 'Inspect it'; selectionAct: [ :workspace :page | workspace evaluateSelectionAndDo: [:result | result explore] ] on: $e entitled: 'Explore it'] . browser transmit to: #r2; andShow: [ :aComposite | aComposite pharoPlayground variableBindings: [{#browser -> browser. #a->1}] ]. browser openOn: 'browser := GLMTabulator new. browser row: #r1; row: #r2. browser transmit to: #r1; andShow: [ :aComposite | aComposite workspace]. browser openOn:''self halt'' ' \ No newline at end of file +I provide support for displaying snippets of Smalltalk code (e.g. dealing with variable binding) self pharoPlaygroundPresentationExample \ No newline at end of file diff --git a/Glamour-Rubric-Presentations.package/GLMPharoPlaygroundPresentation.class/class/examples/pharoPlaygroundPresentationExample.st b/Glamour-Rubric-Presentations.package/GLMPharoPlaygroundPresentation.class/class/examples/pharoPlaygroundPresentationExample.st new file mode 100644 index 0000000000..7be4619e9e --- /dev/null +++ b/Glamour-Rubric-Presentations.package/GLMPharoPlaygroundPresentation.class/class/examples/pharoPlaygroundPresentationExample.st @@ -0,0 +1,35 @@ +pharoPlaygroundPresentationExample + " + self pharoPlaygroundPresentationExample + " + | browser | + browser := GLMTabulator new. + browser + row: #r1; + row: #r2. + browser transmit + to: #r1; + andShow: [ :aComposite | + aComposite pharoPlayground + selectionAct: [ :workspace :page | workspace evaluateSelection ] on: $d entitled: 'Do it'; + selectionAct: [ :workspace :page | workspace evaluateSelectionAndDo: [ :result | result inspect ] ] + on: $i + entitled: 'Inspect it'; + selectionAct: [ :workspace :page | workspace evaluateSelectionAndDo: [ :result | result explore ] ] + on: $e + entitled: 'Explore it' ]. + browser transmit + to: #r2; + andShow: [ :aComposite | + aComposite pharoPlayground + variableBindings: [ + {(#browser -> browser). + (#a -> 1)} ] ]. + browser + openOn: + 'browser := GLMTabulator new. +browser row: #r1; row: #r2. + +browser transmit to: #r1; andShow: [ :aComposite | + aComposite pharoPlayground]. +browser openOn:''self halt'' ' \ No newline at end of file diff --git a/Glamour-Rubric-Presentations.package/GLMPharoPlaygroundPresentation.class/definition.st b/Glamour-Rubric-Presentations.package/GLMPharoPlaygroundPresentation.class/definition.st index c0ab179a27..575910308d 100644 --- a/Glamour-Rubric-Presentations.package/GLMPharoPlaygroundPresentation.class/definition.st +++ b/Glamour-Rubric-Presentations.package/GLMPharoPlaygroundPresentation.class/definition.st @@ -1,4 +1,4 @@ -GLMNewSmalltalkCodePresentation subclass: #GLMPharoPlaygroundPresentation +GLMRubricSmalltalkCodePresentation subclass: #GLMPharoPlaygroundPresentation instanceVariableNames: 'variableBindingsBlock' classVariableNames: '' poolDictionaries: '' diff --git a/Glamour-Rubric-Presentations.package/GLMRubricSmalltalkCodePresentation.class/README.md b/Glamour-Rubric-Presentations.package/GLMRubricSmalltalkCodePresentation.class/README.md index a9aeebc694..c26c4d00bb 100644 --- a/Glamour-Rubric-Presentations.package/GLMRubricSmalltalkCodePresentation.class/README.md +++ b/Glamour-Rubric-Presentations.package/GLMRubricSmalltalkCodePresentation.class/README.md @@ -1 +1 @@ -A GLMRubricSmalltalkCodePresentation is xxxxxxxxx. \ No newline at end of file +I extend the simple Rubric text presentation with basic support for dealing with Smalltalk code. \ No newline at end of file diff --git a/Glamour-Rubric-Presentations.package/GLMNewSmalltalkCodePresentation.class/instance/actions/compileTextIn_from_andDo_.st b/Glamour-Rubric-Presentations.package/GLMRubricSmalltalkCodePresentation.class/instance/actions/compileTextIn_from_andDo_.st similarity index 100% rename from Glamour-Rubric-Presentations.package/GLMNewSmalltalkCodePresentation.class/instance/actions/compileTextIn_from_andDo_.st rename to Glamour-Rubric-Presentations.package/GLMRubricSmalltalkCodePresentation.class/instance/actions/compileTextIn_from_andDo_.st diff --git a/Glamour-Rubric-Presentations.package/GLMNewSmalltalkCodePresentation.class/instance/actions/debugSelection.st b/Glamour-Rubric-Presentations.package/GLMRubricSmalltalkCodePresentation.class/instance/actions/debugSelection.st similarity index 100% rename from Glamour-Rubric-Presentations.package/GLMNewSmalltalkCodePresentation.class/instance/actions/debugSelection.st rename to Glamour-Rubric-Presentations.package/GLMRubricSmalltalkCodePresentation.class/instance/actions/debugSelection.st diff --git a/Glamour-Rubric-Presentations.package/GLMNewSmalltalkCodePresentation.class/instance/actions/evaluateSelection.st b/Glamour-Rubric-Presentations.package/GLMRubricSmalltalkCodePresentation.class/instance/actions/evaluateSelection.st similarity index 100% rename from Glamour-Rubric-Presentations.package/GLMNewSmalltalkCodePresentation.class/instance/actions/evaluateSelection.st rename to Glamour-Rubric-Presentations.package/GLMRubricSmalltalkCodePresentation.class/instance/actions/evaluateSelection.st diff --git a/Glamour-Rubric-Presentations.package/GLMNewSmalltalkCodePresentation.class/instance/actions/evaluateSelectionAndDo_.st b/Glamour-Rubric-Presentations.package/GLMRubricSmalltalkCodePresentation.class/instance/actions/evaluateSelectionAndDo_.st similarity index 100% rename from Glamour-Rubric-Presentations.package/GLMNewSmalltalkCodePresentation.class/instance/actions/evaluateSelectionAndDo_.st rename to Glamour-Rubric-Presentations.package/GLMRubricSmalltalkCodePresentation.class/instance/actions/evaluateSelectionAndDo_.st diff --git a/Glamour-Rubric-Presentations.package/GLMNewSmalltalkCodePresentation.class/instance/actions/printSelection.st b/Glamour-Rubric-Presentations.package/GLMRubricSmalltalkCodePresentation.class/instance/actions/printSelection.st similarity index 100% rename from Glamour-Rubric-Presentations.package/GLMNewSmalltalkCodePresentation.class/instance/actions/printSelection.st rename to Glamour-Rubric-Presentations.package/GLMRubricSmalltalkCodePresentation.class/instance/actions/printSelection.st diff --git a/Glamour-Rubric-Presentations.package/GLMNewSmalltalkCodePresentation.class/instance/actions/profileSelection.st b/Glamour-Rubric-Presentations.package/GLMRubricSmalltalkCodePresentation.class/instance/actions/profileSelection.st similarity index 100% rename from Glamour-Rubric-Presentations.package/GLMNewSmalltalkCodePresentation.class/instance/actions/profileSelection.st rename to Glamour-Rubric-Presentations.package/GLMRubricSmalltalkCodePresentation.class/instance/actions/profileSelection.st diff --git a/Glamour-Rubric-Presentations.package/GLMNewSmalltalkCodePresentation.class/instance/rendering/defaultSelectionActions.st b/Glamour-Rubric-Presentations.package/GLMRubricSmalltalkCodePresentation.class/instance/rendering/defaultSelectionActions.st similarity index 100% rename from Glamour-Rubric-Presentations.package/GLMNewSmalltalkCodePresentation.class/instance/rendering/defaultSelectionActions.st rename to Glamour-Rubric-Presentations.package/GLMRubricSmalltalkCodePresentation.class/instance/rendering/defaultSelectionActions.st diff --git a/Glamour-Rubric-Presentations.package/GLMNewSmalltalkCodePresentation.class/instance/rendering/installDefaultSelectionActions.st b/Glamour-Rubric-Presentations.package/GLMRubricSmalltalkCodePresentation.class/instance/rendering/installDefaultSelectionActions.st similarity index 100% rename from Glamour-Rubric-Presentations.package/GLMNewSmalltalkCodePresentation.class/instance/rendering/installDefaultSelectionActions.st rename to Glamour-Rubric-Presentations.package/GLMRubricSmalltalkCodePresentation.class/instance/rendering/installDefaultSelectionActions.st diff --git a/Glamour-Rubric-Presentations.package/GLMRubricSmalltalkCodePresentation.class/instance/rendering/renderGlamorouslyOn_.st b/Glamour-Rubric-Presentations.package/GLMRubricSmalltalkCodePresentation.class/instance/rendering/renderGlamorouslyOn_.st deleted file mode 100644 index bbf1eb9e82..0000000000 --- a/Glamour-Rubric-Presentations.package/GLMRubricSmalltalkCodePresentation.class/instance/rendering/renderGlamorouslyOn_.st +++ /dev/null @@ -1,3 +0,0 @@ -renderGlamorouslyOn: aRenderer - self registerAnnouncements. - ^ aRenderer renderRubricSmalltalkCodePresentation: self \ No newline at end of file diff --git a/Glamour-Rubric-Presentations.package/GLMRubricTextPresentation.class/README.md b/Glamour-Rubric-Presentations.package/GLMRubricTextPresentation.class/README.md index 4dfa1eb9e5..9d36fdf422 100644 --- a/Glamour-Rubric-Presentations.package/GLMRubricTextPresentation.class/README.md +++ b/Glamour-Rubric-Presentations.package/GLMRubricTextPresentation.class/README.md @@ -1 +1 @@ -A GLMRubricTextPresentation is xxxxxxxxx. Instance Variables primarySelectionInterval: tabWidth: textSegments: withAnnotation: withColumns: withLineNumbers: wrapped: primarySelectionInterval - xxxxx tabWidth - xxxxx textSegments - xxxxx withAnnotation - xxxxx withColumns - xxxxx withLineNumbers - xxxxx wrapped - xxxxx \ No newline at end of file +A presentation that displays text using Rubric. \ No newline at end of file diff --git a/Glamour-Rubric-Presentations.package/extension/GLMCompositePresentation/instance/rubricSmalltalkCode.st b/Glamour-Rubric-Presentations.package/extension/GLMCompositePresentation/instance/rubricSmalltalkCode.st deleted file mode 100644 index 0fe944a980..0000000000 --- a/Glamour-Rubric-Presentations.package/extension/GLMCompositePresentation/instance/rubricSmalltalkCode.st +++ /dev/null @@ -1,2 +0,0 @@ -rubricSmalltalkCode - ^ self custom: GLMRubricSmalltalkCodePresentation new \ No newline at end of file diff --git a/Keys.package/Key.class/README.md b/Keys.package/Key.class/README.md deleted file mode 100644 index 2c30cf7823..0000000000 --- a/Keys.package/Key.class/README.md +++ /dev/null @@ -1 +0,0 @@ -I represent a keyboard Key. I am mapped from the platform specific keycodes into a common keycode base, by using my class side methods. \ No newline at end of file diff --git a/Keys.package/Key.class/class/class initialization/initialize.st b/Keys.package/Key.class/class/class initialization/initialize.st deleted file mode 100644 index 374cc5bed5..0000000000 --- a/Keys.package/Key.class/class/class initialization/initialize.st +++ /dev/null @@ -1,6 +0,0 @@ -initialize - self - initializeKeyTable; - initializeMacOSVirtualKeyTable; - initializeUnixVirtualKeyTable; - initializeWindowsVirtualKeyTable \ No newline at end of file diff --git a/Keys.package/Key.class/class/instance creation/value_.st b/Keys.package/Key.class/class/instance creation/value_.st deleted file mode 100644 index 1d3a12ab42..0000000000 --- a/Keys.package/Key.class/class/instance creation/value_.st +++ /dev/null @@ -1,2 +0,0 @@ -value: aKeyValue - ^KeyTable at: aKeyValue \ No newline at end of file diff --git a/Keys.package/Key.class/class/key table/initializeKeyTable.st b/Keys.package/Key.class/class/key table/initializeKeyTable.st deleted file mode 100644 index 6322ffd82e..0000000000 --- a/Keys.package/Key.class/class/key table/initializeKeyTable.st +++ /dev/null @@ -1,231 +0,0 @@ -initializeKeyTable - KeyTable := Dictionary new. - #( - 16r08f6 Function "XK_function" - 16rff08 BackSpace "XK_BackSpace" - 16rff09 Tab "XK_Tab" - 16rff0a Linefeed "XK_Linefeed" - 16rff0b Clear "XK_Clear" - 16rff0d Return "XK_Return" - 16rff13 Pause "XK_Pause" - 16rff14 Scroll_Lock "XK_Scroll_Lock" - 16rff15 Sys_Req "XK_Sys_Req" - 16rff1b Escape "XK_Escape" - 16rffff Delete "XK_Delete" - 16rff50 Home "XK_Home" - 16rff51 Left "XK_Left" - 16rff52 Up "XK_Up" - 16rff53 Right "XK_Right" - 16rff54 Down "XK_Down" - 16rfe03 Level3Shift "XK_ISO_Level3_Shift" - 16r00a1 ExclamationDown "XK_exclamdown" - 16r00bf QuestionDown "XK_questiondown" - 16r00f1 NTilde "XK_ntilde" - 16r00d1 CapitalNTilde "XK_ntilde" - 16r00ba Masculine "XK_masculine" - 16r00e7 CCedilla "XK_ccedilla" - 16r00c7 CapitalCCedilla "XK_ccedilla" - 16r00aa FeminineOrdinal "XK_ordfeminine" - 16r00b7 MiddlePoint "XK_periodcentered" - "16rff55 Prior ""XK_Prior" - 16rff55 Page_Up "XK_Page_Up" - "16rff56 Next" "XK_Next" - 16rff56 Page_Down "XK_Page_Down" - 16rff57 End "XK_End" - 16rff58 Begin "XK_Begin" - 16rff80 KP_Space "XK_KP_Space" - 16rff89 KP_Tab "XK_KP_Tab" - 16rff8d KP_Enter "XK_KP_Enter" - 16rff91 KP_F1 "XK_KP_F1" - 16rff92 KP_F2 "XK_KP_F2" - 16rff93 KP_F3 "XK_KP_F3" - 16rff94 KP_F4 "XK_KP_F4" - 16rff95 KP_Home "XK_KP_Home" - 16rff96 KP_Left "XK_KP_Left" - 16rff97 KP_Up "XK_KP_Up" - 16rff98 KP_Right "XK_KP_Right" - 16rff99 KP_Down "XK_KP_Down" - 16rff9a KP_Prior "XK_KP_Prior" - 16rff9a KP_Page_Up "XK_KP_Page_Up" - 16rff9b KP_Next "XK_KP_Next" - 16rff9b KP_Page_Down "XK_KP_Page_Down" - 16rff9c KP_End "XK_KP_End" - 16rff9d KP_Begin "XK_KP_Begin" - 16rff9e KP_Insert "XK_KP_Insert" - 16rff9f KP_Delete "XK_KP_Delete" - 16rffbd KP_Equal "XK_KP_Equal" - 16rffaa KP_Multiply "XK_KP_Multiply" - 16rffab KP_Add "XK_KP_Add" - 16rffac KP_Separator "XK_KP_Separator" - 16rffad KP_Subtract "XK_KP_Subtract" - 16rffae KP_Decimal "XK_KP_Decimal" - 16rffaf KP_Divide "XK_KP_Divide" - 16rffb0 KP_0 "XK_KP_0" - 16rffb1 KP_1 "XK_KP_1" - 16rffb2 KP_2 "XK_KP_2" - 16rffb3 KP_3 "XK_KP_3" - 16rffb4 KP_4 "XK_KP_4" - 16rffb5 KP_5 "XK_KP_5" - 16rffb6 KP_6 "XK_KP_6" - 16rffb7 KP_7 "XK_KP_7" - 16rffb8 KP_8 "XK_KP_8" - 16rffb9 KP_9 "XK_KP_9" - 16rffbe F1 "XK_F1" - 16rffbf F2 "XK_F2" - 16rffc0 F3 "XK_F3" - 16rffc1 F4 "XK_F4" - 16rffc2 F5 "XK_F5" - 16rffc3 F6 "XK_F6" - 16rffc4 F7 "XK_F7" - 16rffc5 F8 "XK_F8" - 16rffc6 F9 "XK_F9" - 16rffc7 F10 "XK_F10" - 16rffc8 F11 "XK_F11" - 16rffc9 F12 "XK_F12" - 16rffe1 Shift_L "XK_Shift_L" - 16rffe2 Shift_R "XK_Shift_R" - 16rffe3 Control_L "XK_Control_L" - 16rffe4 Control_R "XK_Control_R" - 16rffe5 Caps_Lock "XK_Caps_Lock" - 16rffe6 Shift_Lock "XK_Shift_Lock" - 16rffe7 Meta_L "XK_Meta_L" - 16rffe8 Meta_R "XK_Meta_R" - 16rffe9 Alt_L "XK_Alt_L" - 16rffea Alt_R "XK_Alt_R" - 16rffeb Super_L "XK_Super_L" - 16rffec Super_R "XK_Super_R" - 16rffed Hyper_L "XK_Hyper_L" - 16rffee Hyper_R "XK_Hyper_R" - 16rfe50 dead_grave "XK_dead_grave" - 16rfe51 dead_acute "XK_dead_acute" - 16rfe52 dead_circumflex "XK_dead_circumflex" - 16rfe53 dead_tilde "XK_dead_tilde" - 16rfe53 dead_perispomeni "XK_dead_perispomeni" - 16rfe54 dead_macron "XK_dead_macron" - 16rfe55 dead_breve "XK_dead_breve" - 16rfe56 dead_abovedot "XK_dead_abovedot" - 16rfe57 dead_diaeresis "XK_dead_diaeresis" - 16rfe58 dead_abovering "XK_dead_abovering" - 16rfe59 dead_doubleacute "XK_dead_doubleacute" - 16rfe5a dead_caron "XK_dead_caron" - 16rfe5b dead_cedilla "XK_dead_cedilla" - 16rfe5c dead_ogonek "XK_dead_ogonek" - 16rfe5d dead_iota "XK_dead_iota" - 16rfe5e dead_voiced_sound "XK_dead_voiced_sound" - 16rfe5f dead_semivoiced_sound "XK_dead_semivoiced_sound" - 16rfe60 dead_belowdot "XK_dead_belowdot" - 16rfe61 dead_hook "XK_dead_hook" - 16rfe62 dead_horn "XK_dead_horn" - 16rfe63 dead_stroke "XK_dead_stroke" - 16rfe64 dead_abovecomma "XK_dead_abovecomma" - 16rfe64 dead_psili "XK_dead_psili" - 16rfe65 dead_abovereversedcomma "XK_dead_abovereversedcomma" - 16rfe65 dead_dasia "XK_dead_dasia" - 16rfe66 dead_doublegrave "XK_dead_doublegrave" - 16rfe67 dead_belowring "XK_dead_belowring" - 16rfe68 dead_belowmacron "XK_dead_belowmacron" - 16rfe69 dead_belowcircumflex "XK_dead_belowcircumflex" - 16rfe6a dead_belowtilde "XK_dead_belowtilde" - 16rfe6b dead_belowbreve "XK_dead_belowbreve" - 16rfe6c dead_belowdiaeresis "XK_dead_belowdiaeresis" - 16rfe6d dead_invertedbreve "XK_dead_invertedbreve" - 16rfe6e dead_belowcomma "XK_dead_belowcomma" - 16rfe6f dead_currency "XK_dead_currency" - 16r0020 space "XK_space" - 16r0021 exclam "XK_exclam" - 16r0022 quotedbl "XK_quotedbl" - 16r0023 numbersign "XK_numbersign" - 16r0024 dollar "XK_dollar" - 16r0025 percent "XK_percent" - 16r0026 ampersand "XK_ampersand" - 16r0027 apostrophe "XK_apostrophe" - "16r0027 quoteright" "XK_quoteright" - 16r0028 parenleft "XK_parenleft" - 16r0029 parenright "XK_parenright" - 16r002a asterisk "XK_asterisk" - 16r002b plus "XK_plus" - 16r002c comma "XK_comma" - 16r002d minus "XK_minus" - 16r002e period "XK_period" - 16r002f slash "XK_slash" - 16r0030 zero "XK_0" - 16r0031 one "XK_1" - 16r0032 two "XK_2" - 16r0033 three "XK_3" - 16r0034 four "XK_4" - 16r0035 five "XK_5" - 16r0036 six "XK_6" - 16r0037 seven "XK_7" - 16r0038 eight "XK_8" - 16r0039 nine "XK_9" - 16r003a colon "XK_colon" - 16r003b semicolon "XK_semicolon" - 16r003c less "XK_less" - 16r003d equal "XK_equal" - 16r003e greater "XK_greater" - 16r003f question "XK_question" - 16r0040 at "XK_at" - 16r0041 A "XK_A" - 16r0042 B "XK_B" - 16r0043 C "XK_C" - 16r0044 D "XK_D" - 16r0045 E "XK_E" - 16r0046 F "XK_F" - 16r0047 G "XK_G" - 16r0048 H "XK_H" - 16r0049 I "XK_I" - 16r004a J "XK_J" - 16r004b K "XK_K" - 16r004c L "XK_L" - 16r004d M "XK_M" - 16r004e N "XK_N" - 16r004f O "XK_O" - 16r0050 P "XK_P" - 16r0051 Q "XK_Q" - 16r0052 R "XK_R" - 16r0053 S "XK_S" - 16r0054 T "XK_T" - 16r0055 U "XK_U" - 16r0056 V "XK_V" - 16r0057 W "XK_W" - 16r0058 X "XK_X" - 16r0059 Y "XK_Y" - 16r005a Z "XK_Z" - 16r005b bracketleft "XK_bracketleft" - 16r005c backslash "XK_backslash" - 16r005d bracketright "XK_bracketright" - 16r005e asciicircum "XK_asciicircum" - 16r005f underscore "XK_underscore" - 16r0060 grave "XK_grave" - "16r0060 quoteleft" "XK_quoteleft" - 16r0061 a "XK_a" - 16r0062 b "XK_b" - 16r0063 c "XK_c" - 16r0064 d "XK_d" - 16r0065 e "XK_e" - 16r0066 f "XK_f" - 16r0067 g "XK_g" - 16r0068 h "XK_h" - 16r0069 i "XK_i" - 16r006a j "XK_j" - 16r006b k "XK_k" - 16r006c l "XK_l" - 16r006d m "XK_m" - 16r006e n "XK_n" - 16r006f o "XK_o" - 16r0070 p "XK_p" - 16r0071 q "XK_q" - 16r0072 r "XK_r" - 16r0073 s "XK_s" - 16r0074 t "XK_t" - 16r0075 u "XK_u" - 16r0076 v "XK_v" - 16r0077 w "XK_w" - 16r0078 x "XK_x" - 16r0079 y "XK_y" - 16r007a z "XK_z" - 16r007b braceleft "XK_braceleft" - 16r007c bar "XK_bar" - 16r007d braceright "XK_braceright" - 16r007e asciitilde "XK_asciitilde") - pairsDo: [ :keyCode :keyname | KeyTable at: keyCode put: (self basicNew withValue: keyCode andName: keyname asUppercase) ]. \ No newline at end of file diff --git a/Keys.package/Key.class/class/macos/initializeMacOSVirtualKeyTable.st b/Keys.package/Key.class/class/macos/initializeMacOSVirtualKeyTable.st deleted file mode 100644 index 14cb6d52cd..0000000000 --- a/Keys.package/Key.class/class/macos/initializeMacOSVirtualKeyTable.st +++ /dev/null @@ -1,109 +0,0 @@ -initializeMacOSVirtualKeyTable - MacosVirtualKeyTable := Dictionary new. - MacosVirtualKeyTable - at: 16r24 put: (self value: 16rff0d); " kVK_Return = 0x24" - at: 16r30 put: (self value: 16rff09); " kVK_Tab = 0x30" - at: 16r31 put: (self value: 16rff80); " kVK_Space = 0x31" - at: 16r33 put: (self value: 16rffff); " kVK_Delete = 0x33" - at: 16r35 put: (self value: 16rff1b); " kVK_Escape = 0x35" - at: 16r37 put: (self value: 16rffe7); " kVK_Command = 0x37" - at: 16r38 put: (self value: 16rffe1); " kVK_Shift = 0x38" - at: 16r39 put: (self value: 16rffe5); " kVK_CapsLock = 0x39" - at: 16r3A put: (self value: 16rffe9); " kVK_Option = 0x3A" - at: 16r3B put: (self value: 16rffe3); " kVK_Control = 0x3B" - at: 16r3C put: (self value: 16rffe2); " kVK_RightShift = 0x3C" - at: 16r3D put: (self value: 16rffea); " kVK_RightOption = 0x3D" - at: 16r3E put: (self value: 16rffe4); " kVK_RightControl = 0x3E" - at: 16r3F put: (self value: 16r08f6); " kVK_Function = 0x3F" - at: 16r48 put: (self value: 16r48); " kVK_VolumeUp = 0x48" "Not mapped" - at: 16r49 put: (self value: 16r49); " kVK_VolumeDown = 0x49" "Not mapped" - at: 16r4A put: (self value: 16r4A); " kVK_Mute = 0x4A" "Not mapped" - at: 16r7A put: (self value: 16rffbe); " kVK_F1 = 0x7A" - at: 16r78 put: (self value: 16rffbf); " kVK_F2 = 0x78" - at: 16r63 put: (self value: 16rffc0); " kVK_F3 = 0x63" - at: 16r76 put: (self value: 16rffc1); " kVK_F4 = 0x76" - at: 16r60 put: (self value: 16rffc2); " kVK_F5 = 0x60" - at: 16r61 put: (self value: 16rffc3); " kVK_F6 = 0x61" - at: 16r62 put: (self value: 16rffc4); " kVK_F7 = 0x62" - at: 16r64 put: (self value: 16rffc5); " kVK_F8 = 0x64" - at: 16r65 put: (self value: 16rffc6); " kVK_F9 = 0x65" - at: 16r67 put: (self value: 16rffc8); " kVK_F11 = 0x67" - at: 16r6D put: (self value: 16rffc7); " kVK_F10 = 0x6D" - at: 16r6F put: (self value: 16rffc9); " kVK_F12 = 0x6F" - at: 16r72 put: (self value: 16r72); " kVK_Help = 0x72" "Not mapped" - at: 16r73 put: (self value: 16rff50); " kVK_Home = 0x73" - at: 16r74 put: (self value: 16rff55); " kVK_PageUp = 0x74" - at: 16r75 put: (self value: 16rffff); " kVK_ForwardDelete = 0x75" - at: 16r77 put: (self value: 16rff57); " kVK_End = 0x77" - at: 16r79 put: (self value: 16rff56); " kVK_PageDown = 0x79" - at: 16r7B put: (self value: 16rff96); " kVK_LeftArrow = 0x7B" - at: 16r7C put: (self value: 16rff98); " kVK_RightArrow = 0x7C" - at: 16r7D put: (self value: 16rff99); " kVK_DownArrow = 0x7D" - at: 16r7E put: (self value: 16rff97); " kVK_UpArrow = 0x7E" - at: 16r00 put: (self value: 16r41); "kVK_ANSI_A = 0x00" - at: 16r0B put: (self value: 16r42); " kVK_ANSI_B = 0x0B" - at: 16r08 put: (self value: 16r43); " kVK_ANSI_C = 0x08" - at: 16r02 put: (self value: 16r44); " kVK_ANSI_D = 0x02" - at: 16r0E put: (self value: 16r45); " kVK_ANSI_E = 0x0E" - at: 16r03 put: (self value: 16r46); " kVK_ANSI_F = 0x03" - at: 16r05 put: (self value: 16r47); " kVK_ANSI_G = 0x05" - at: 16r04 put: (self value: 16r48); " kVK_ANSI_H = 0x04" - at: 16r22 put: (self value: 16r49); " kVK_ANSI_I = 0x22" - at: 16r26 put: (self value: 16r4a); " kVK_ANSI_J = 0x26" - at: 16r28 put: (self value: 16r4b); " kVK_ANSI_K = 0x28" - at: 16r25 put: (self value: 16r4c); " kVK_ANSI_L = 0x25" - at: 16r2E put: (self value: 16r4d); " kVK_ANSI_M = 0x2E" - at: 16r2D put: (self value: 16r4e); " kVK_ANSI_N = 0x2D" - at: 16r1F put: (self value: 16r4f); " kVK_ANSI_O = 0x1F" - at: 16r23 put: (self value: 16r50); " kVK_ANSI_P = 0x23" - at: 16r0C put: (self value: 16r51); " kVK_ANSI_Q = 0x0C" - at: 16r0F put: (self value: 16r52); " kVK_ANSI_R = 0x0F" - at: 16r01 put: (self value: 16r53); " kVK_ANSI_S = 0x01" - at: 16r11 put: (self value: 16r54); " kVK_ANSI_T = 0x11" - at: 16r20 put: (self value: 16r55); " kVK_ANSI_U = 0x20" - at: 16r09 put: (self value: 16r56); " kVK_ANSI_V = 0x09" - at: 16r0D put: (self value: 16r57); " kVK_ANSI_W = 0x0D" - at: 16r07 put: (self value: 16r58); " kVK_ANSI_X = 0x07" - at: 16r10 put: (self value: 16r59); " kVK_ANSI_Y = 0x10" - at: 16r06 put: (self value: 16r5a); " kVK_ANSI_Z = 0x06" - - at: 16r1D put: (self value: 16r30); " kVK_ANSI_0 = 0x1D" - at: 16r12 put: (self value: 16r31); " kVK_ANSI_1 = 0x12" - at: 16r13 put: (self value: 16r32); " kVK_ANSI_2 = 0x13" - at: 16r14 put: (self value: 16r33); " kVK_ANSI_3 = 0x14" - at: 16r15 put: (self value: 16r34); " kVK_ANSI_4 = 0x15" - at: 16r17 put: (self value: 16r35); " kVK_ANSI_5 = 0x17" - at: 16r16 put: (self value: 16r36); " kVK_ANSI_6 = 0x16" - at: 16r1A put: (self value: 16r37); " kVK_ANSI_7 = 0x1A" - at: 16r1C put: (self value: 16r38); " kVK_ANSI_8 = 0x1C" - at: 16r19 put: (self value: 16r39); " kVK_ANSI_9 = 0x19" - - at: 16r1B put: (self value: 16r2d); " kVK_ANSI_Minus = 0x1B" - at: 16r18 put: (self value: 16r3d); " kVK_ANSI_Equal = 0x18" - at: 16r21 put: (self value: 16r5b); " kVK_ANSI_LeftBracket = 0x21" - at: 16r1E put: (self value: 16r5d); " kVK_ANSI_RightBracket = 0x1E" - at: 16r27 put: (self value: 16r27); " kVK_ANSI_Quote = 0x27" - at: 16r29 put: (self value: 16r3b); " kVK_ANSI_Semicolon = 0x29" - at: 16r2A put: (self value: 16r5c); " kVK_ANSI_Backslash = 0x2A" - at: 16r2B put: (self value: 16r2c); " kVK_ANSI_Comma = 0x2B" - at: 16r2C put: (self value: 16r2f); " kVK_ANSI_Slash = 0x2C" - at: 16r2F put: (self value: 16r2e); " kVK_ANSI_Period = 0x2F" - at: 16r32 put: (self value: 16r60); " kVK_ANSI_Grave = 0x32" - at: 16r41 put: (self value: 16rffae); " kVK_ANSI_KeypadDecimal = 0x41" - at: 16r43 put: (self value: 16rffaa); " kVK_ANSI_KeypadMultiply = 0x43" - at: 16r45 put: (self value: 16rffab); " kVK_ANSI_KeypadPlus = 0x45" - at: 16r47 put: (self value: 16r47); " kVK_ANSI_KeypadClear = 0x47" "Not mapped" - at: 16r4B put: (self value: 16rffaf); " kVK_ANSI_KeypadDivide = 0x4B" - at: 16r4C put: (self value: 16rff8d); " kVK_ANSI_KeypadEnter = 0x4C" - at: 16r4E put: (self value: 16rffad); " kVK_ANSI_KeypadMinus = 0x4E" - at: 16r51 put: (self value: 16rffbd); " kVK_ANSI_KeypadEquals = 0x51" - at: 16r52 put: (self value: 16rffb0); " kVK_ANSI_Keypad0 = 0x52" - at: 16r53 put: (self value: 16rffb1); " kVK_ANSI_Keypad1 = 0x53" - at: 16r54 put: (self value: 16rffb2); " kVK_ANSI_Keypad2 = 0x54" - at: 16r55 put: (self value: 16rffb3); " kVK_ANSI_Keypad3 = 0x55" - at: 16r56 put: (self value: 16rffb4); " kVK_ANSI_Keypad4 = 0x56" - at: 16r57 put: (self value: 16rffb5); " kVK_ANSI_Keypad5 = 0x57" - at: 16r58 put: (self value: 16rffb6); " kVK_ANSI_Keypad6 = 0x58" - at: 16r59 put: (self value: 16rffb7); " kVK_ANSI_Keypad7 = 0x59" - at: 16r5B put: (self value: 16rffb8); " kVK_ANSI_Keypad8 = 0x5B" - at: 16r5C put: (self value: 16rffb9) " kVK_ANSI_Keypad9 = 0x5C" \ No newline at end of file diff --git a/Keys.package/Key.class/class/macos/macOSVirtualKeyTable.st b/Keys.package/Key.class/class/macos/macOSVirtualKeyTable.st deleted file mode 100644 index 404561659a..0000000000 --- a/Keys.package/Key.class/class/macos/macOSVirtualKeyTable.st +++ /dev/null @@ -1,3 +0,0 @@ -macOSVirtualKeyTable - MacosVirtualKeyTable ifNil: [ self initializeMacOSVirtualKeyTable. ]. - ^MacosVirtualKeyTable \ No newline at end of file diff --git a/Keys.package/Key.class/class/macos/valueForMacOSXPlatform_.st b/Keys.package/Key.class/class/macos/valueForMacOSXPlatform_.st deleted file mode 100644 index e7f363def9..0000000000 --- a/Keys.package/Key.class/class/macos/valueForMacOSXPlatform_.st +++ /dev/null @@ -1,3 +0,0 @@ -valueForMacOSXPlatform: aKeyValue - - ^self macOSVirtualKeyTable at: aKeyValue ifAbsent: [ (self basicNew withValue: aKeyValue andName: #Unknown) ] \ No newline at end of file diff --git a/Keys.package/Key.class/class/unix/initializeUnixVirtualKeyTable.st b/Keys.package/Key.class/class/unix/initializeUnixVirtualKeyTable.st deleted file mode 100644 index c249645024..0000000000 --- a/Keys.package/Key.class/class/unix/initializeUnixVirtualKeyTable.st +++ /dev/null @@ -1,110 +0,0 @@ -initializeUnixVirtualKeyTable - UnixVirtualKeyTable := Dictionary new. - UnixVirtualKeyTable - at: Character cr asciiValue put: (self value: 16rff0d); " kVK_Return = 0x24" - at: Character tab asciiValue put: (self value: 16rff09); " kVK_Tab = 0x30" - at: Character space asciiValue put: (self value: 16rff80); " kVK_Space = 0x31" - at: Character delete asciiValue put: (self value: 16rffff); " kVK_Delete = 0x33" - at: Character escape asciiValue put: (self value: 16rff1b); " kVK_Escape = 0x35" - at: 8 put: (self value: 16rff08); " kVK_Command = 0x37" - at: -1 put: (self value: 16rffe7); " kVK_Command = 0x37" - at: 255 put: (self value: 16rffe1); " kVK_Shift = 0x38" - at: -1 put: (self value: 16rffe5); " kVK_CapsLock = 0x39" - at: 247 put: (self value: 16rffe9); " kVK_Option = 0x3A" - at: 251 put: (self value: 16rffe3); " kVK_Control = 0x3B" - at: 254 put: (self value: 16rffe2); " kVK_RightShift = 0x3C" - at: -1 put: (self value: 16rffea); " kVK_RightOption = 0x3D" - at: -1 put: (self value: 16rffe4); " kVK_RightControl = 0x3E" - at: -1 put: (self value: 16r08f6); " kVK_Function = 0x3F" - at: -1 put: (self value: 16r48); " kVK_VolumeUp = 0x48" "Not mapped" - at: -1 put: (self value: 16r49); " kVK_VolumeDown = 0x49" "Not mapped" - at: -1 put: (self value: 16r4A); " kVK_Mute = 0x4A" "Not mapped" - at: -1 put: (self value: 16rffbe); " kVK_F1 = 0x7A" - at: -1 put: (self value: 16rffbf); " kVK_F2 = 0x78" - at: -1 put: (self value: 16rffc0); " kVK_F3 = 0x63" - at: -1 put: (self value: 16rffc1); " kVK_F4 = 0x76" - at: -1 put: (self value: 16rffc2); " kVK_F5 = 0x60" - at: -1 put: (self value: 16rffc3); " kVK_F6 = 0x61" - at: -1 put: (self value: 16rffc4); " kVK_F7 = 0x62" - at: -1 put: (self value: 16rffc5); " kVK_F8 = 0x64" - at: -1 put: (self value: 16rffc6); " kVK_F9 = 0x65" - at: -1 put: (self value: 16rffc8); " kVK_F11 = 0x67" - at: -1 put: (self value: 16rffc7); " kVK_F10 = 0x6D" - at: -1 put: (self value: 16rffc9); " kVK_F12 = 0x6F" - at: -1 put: (self value: 16r72); " kVK_Help = 0x72" "Not mapped" - at: Character home asciiValue put: (self value: 16rff50); " kVK_Home = 0x73" - at: Character pageUp asciiValue put: (self value: 16rff55); " kVK_PageUp = 0x74" - at: Character delete asciiValue put: (self value: 16rffff); " kVK_ForwardDelete = 0x75" - at: Character end asciiValue put: (self value: 16rff57); " kVK_End = 0x77" - at: Character pageDown asciiValue put: (self value: 16rff56); " kVK_PageDown = 0x79" - at: Character arrowLeft asciiValue put: (self value: 16rff96); " kVK_LeftArrow = 0x7B" - at: Character arrowRight asciiValue put: (self value: 16rff98); " kVK_RightArrow = 0x7C" - at: Character arrowDown asciiValue put: (self value: 16rff99); " kVK_DownArrow = 0x7D" - at: Character arrowUp asciiValue put: (self value: 16rff97); " kVK_UpArrow = 0x7E" - at: $a asciiValue put: (self value: 16r41); "kVK_ANSI_A = 0x00" - at: $b asciiValue put: (self value: 16r42); " kVK_ANSI_B = 0x0B" - at: $c asciiValue put: (self value: 16r43); " kVK_ANSI_C = 0x08" - at: $d asciiValue put: (self value: 16r44); " kVK_ANSI_D = 0x02" - at: $e asciiValue put: (self value: 16r45); " kVK_ANSI_E = 0x0E" - at: $f asciiValue put: (self value: 16r46); " kVK_ANSI_F = 0x03" - at: $g asciiValue put: (self value: 16r47); " kVK_ANSI_G = 0x05" - at: $h asciiValue put: (self value: 16r48); " kVK_ANSI_H = 0x04" - at: $i asciiValue put: (self value: 16r49); " kVK_ANSI_I = 0x22" - at: $j asciiValue put: (self value: 16r4a); " kVK_ANSI_J = 0x26" - at: $k asciiValue put: (self value: 16r4b); " kVK_ANSI_K = 0x28" - at: $l asciiValue put: (self value: 16r4c); " kVK_ANSI_L = 0x25" - at: $m asciiValue put: (self value: 16r4d); " kVK_ANSI_M = 0x2E" - at: $n asciiValue put: (self value: 16r4e); " kVK_ANSI_N = 0x2D" - at: $o asciiValue put: (self value: 16r4f); " kVK_ANSI_O = 0x1F" - at: $p asciiValue put: (self value: 16r50); " kVK_ANSI_P = 0x23" - at: $q asciiValue put: (self value: 16r51); " kVK_ANSI_Q = 0x0C" - at: $r asciiValue put: (self value: 16r52); " kVK_ANSI_R = 0x0F" - at: $s asciiValue put: (self value: 16r53); " kVK_ANSI_S = 0x01" - at: $t asciiValue put: (self value: 16r54); " kVK_ANSI_T = 0x11" - at: $u asciiValue put: (self value: 16r55); " kVK_ANSI_U = 0x20" - at: $v asciiValue put: (self value: 16r56); " kVK_ANSI_V = 0x09" - at: $w asciiValue put: (self value: 16r57); " kVK_ANSI_W = 0x0D" - at: $x asciiValue put: (self value: 16r58); " kVK_ANSI_X = 0x07" - at: $y asciiValue put: (self value: 16r59); " kVK_ANSI_Y = 0x10" - at: $z asciiValue put: (self value: 16r5a); " kVK_ANSI_Z = 0x06" - - at: $0 asciiValue put: (self value: 16r30); " kVK_ANSI_0 = 0x1D" - at: $1 asciiValue put: (self value: 16r31); " kVK_ANSI_1 = 0x12" - at: $2 asciiValue put: (self value: 16r32); " kVK_ANSI_2 = 0x13" - at: $3 asciiValue put: (self value: 16r33); " kVK_ANSI_3 = 0x14" - at: $4 asciiValue put: (self value: 16r34); " kVK_ANSI_4 = 0x15" - at: $5 asciiValue put: (self value: 16r35); " kVK_ANSI_5 = 0x17" - at: $6 asciiValue put: (self value: 16r36); " kVK_ANSI_6 = 0x16" - at: $7 asciiValue put: (self value: 16r37); " kVK_ANSI_7 = 0x1A" - at: $8 asciiValue put: (self value: 16r38); " kVK_ANSI_8 = 0x1C" - at: $9 asciiValue put: (self value: 16r39); " kVK_ANSI_9 = 0x19" - - at: $- asciiValue put: (self value: 16r2d); " kVK_ANSI_Minus = 0x1B" - at: $= asciiValue put: (self value: 16r3d); " kVK_ANSI_Equal = 0x18" - at: $[ asciiValue put: (self value: 16r5b); " kVK_ANSI_LeftBracket = 0x21" - at: $] asciiValue put: (self value: 16r5d); " kVK_ANSI_RightBracket = 0x1E" - at: $' asciiValue put: (self value: 16r27); " kVK_ANSI_Quote = 0x27" - at: $; asciiValue put: (self value: 16r3b); " kVK_ANSI_Semicolon = 0x29" - at: $/ asciiValue put: (self value: 16r5c); " kVK_ANSI_Backslash = 0x2A" - at: $, asciiValue put: (self value: 16r2c); " kVK_ANSI_Comma = 0x2B" - at: $\ asciiValue put: (self value: 16r2f); " kVK_ANSI_Slash = 0x2C" - at: $. asciiValue put: (self value: 16r2e); " kVK_ANSI_Period = 0x2F" - at: $` asciiValue put: (self value: 16r60); " kVK_ANSI_Grave = 0x32" - at: 1 put: (self value: 16rffae); " kVK_ANSI_KeypadDecimal = 0x41" - at: 1 put: (self value: 16rffaa); " kVK_ANSI_KeypadMultiply = 0x43" - at: 1 put: (self value: 16rffab); " kVK_ANSI_KeypadPlus = 0x45" - at: 1 put: (self value: 16r47); " kVK_ANSI_KeypadClear = 0x47" "Not mapped" - at: 1 put: (self value: 16rffaf); " kVK_ANSI_KeypadDivide = 0x4B" - at: 1 put: (self value: 16rff8d); " kVK_ANSI_KeypadEnter = 0x4C" - at: 1 put: (self value: 16rffad); " kVK_ANSI_KeypadMinus = 0x4E" - at: 1 put: (self value: 16rffbd); " kVK_ANSI_KeypadEquals = 0x51" - at: 1 put: (self value: 16rffb0); " kVK_ANSI_Keypad0 = 0x52" - at: 1 put: (self value: 16rffb1); " kVK_ANSI_Keypad1 = 0x53" - at: 1 put: (self value: 16rffb2); " kVK_ANSI_Keypad2 = 0x54" - at: 1 put: (self value: 16rffb3); " kVK_ANSI_Keypad3 = 0x55" - at: 1 put: (self value: 16rffb4); " kVK_ANSI_Keypad4 = 0x56" - at: 1 put: (self value: 16rffb5); " kVK_ANSI_Keypad5 = 0x57" - at: 1 put: (self value: 16rffb6); " kVK_ANSI_Keypad6 = 0x58" - at: 1 put: (self value: 16rffb7); " kVK_ANSI_Keypad7 = 0x59" - at: 1 put: (self value: 16rffb8); " kVK_ANSI_Keypad8 = 0x5B" - at: 1 put: (self value: 16rffb9) " kVK_ANSI_Keypad9 = 0x5C" \ No newline at end of file diff --git a/Keys.package/Key.class/class/unix/unixVirtualKeyTable.st b/Keys.package/Key.class/class/unix/unixVirtualKeyTable.st deleted file mode 100644 index 435f5abc20..0000000000 --- a/Keys.package/Key.class/class/unix/unixVirtualKeyTable.st +++ /dev/null @@ -1,2 +0,0 @@ -unixVirtualKeyTable - ^KeyTable \ No newline at end of file diff --git a/Keys.package/Key.class/class/unix/valueForUnixPlatform_.st b/Keys.package/Key.class/class/unix/valueForUnixPlatform_.st deleted file mode 100644 index 186366da70..0000000000 --- a/Keys.package/Key.class/class/unix/valueForUnixPlatform_.st +++ /dev/null @@ -1,3 +0,0 @@ -valueForUnixPlatform: aKeyValue - - ^self unixVirtualKeyTable at: aKeyValue ifAbsent: [ (self basicNew withValue: aKeyValue) ] \ No newline at end of file diff --git a/Keys.package/Key.class/class/unknownKeys/unknownKeyName.st b/Keys.package/Key.class/class/unknownKeys/unknownKeyName.st deleted file mode 100644 index 21bf10376c..0000000000 --- a/Keys.package/Key.class/class/unknownKeys/unknownKeyName.st +++ /dev/null @@ -1,2 +0,0 @@ -unknownKeyName - ^#Unknown \ No newline at end of file diff --git a/Keys.package/Key.class/class/windows/initializeWindowsVirtualKeyTable.st b/Keys.package/Key.class/class/windows/initializeWindowsVirtualKeyTable.st deleted file mode 100644 index 4152364ebe..0000000000 --- a/Keys.package/Key.class/class/windows/initializeWindowsVirtualKeyTable.st +++ /dev/null @@ -1,110 +0,0 @@ -initializeWindowsVirtualKeyTable - WindowsVirtualKeyTable := Dictionary new. - WindowsVirtualKeyTable - at: 16r0d put: (self value: 16rff0d); " kVK_Return = 0x24" - at: 16r09 put: (self value: 16rff09); " kVK_Tab = 0x30" - at: 16r20 put: (self value: 16rff80); " kVK_Space = 0x31" - at: 16r2e put: (self value: 16rffff); " kVK_Delete = 0x33" - at: 16r1b put: (self value: 16rff1b); " kVK_Escape = 0x35" - at: 16r5B put: (self value: 16rff08); " kVK_Command = 0x37" - at: 16r5c put: (self value: 16rffe7); " kVK_Command = 0x37" - at: 16r10 put: (self value: 16rffe1); " kVK_Shift = 0x38" - at: 16r14 put: (self value: 16rffe5); " kVK_CapsLock = 0x39" - at: 16r12 put: (self value: 16rffe9); " kVK_Option = 0x3A" - at: 16r11 put: (self value: 16rffe3); " kVK_Control = 0x3B" - at: 16ra0 put: (self value: 16rffe2); " kVK_RightShift = 0x3C" - at: 16ra5 put: (self value: 16rffea); " kVK_RightOption = 0x3D" - at: 16ra3 put: (self value: 16rffe4); " kVK_RightControl = 0x3E" - at: -1 put: (self value: 16r08f6); " kVK_Function = 0x3F" - at: 16raf put: (self value: 16r48); " kVK_VolumeUp = 0x48" "Not mapped" - at: 16rae put: (self value: 16r49); " kVK_VolumeDown = 0x49" "Not mapped" - at: 16rad put: (self value: 16r4A); " kVK_Mute = 0x4A" "Not mapped" - at: 16r70 put: (self value: 16rffbe); " kVK_F1 = 0x7A" - at: 16r71 put: (self value: 16rffbf); " kVK_F2 = 0x78" - at: 16r72 put: (self value: 16rffc0); " kVK_F3 = 0x63" - at: 16r73 put: (self value: 16rffc1); " kVK_F4 = 0x76" - at: 16r74 put: (self value: 16rffc2); " kVK_F5 = 0x60" - at: 16r75 put: (self value: 16rffc3); " kVK_F6 = 0x61" - at: 16r76 put: (self value: 16rffc4); " kVK_F7 = 0x62" - at: 16r77 put: (self value: 16rffc5); " kVK_F8 = 0x64" - at: 16r78 put: (self value: 16rffc6); " kVK_F9 = 0x65" - at: 16r79 put: (self value: 16rffc8); " kVK_F11 = 0x67" - at: 16r7a put: (self value: 16rffc7); " kVK_F10 = 0x6D" - at: 16r7b put: (self value: 16rffc9); " kVK_F12 = 0x6F" - at: 16r2f put: (self value: 16r72); " kVK_Help = 0x72" "Not mapped" - at: 16r24 put: (self value: 16rff50); " kVK_Home = 0x73" - at: 16r21 put: (self value: 16rff55); " kVK_PageUp = 0x74" - at: 16r2e put: (self value: 16rffff); " kVK_ForwardDelete = 0x75" - at: 16r23 put: (self value: 16rff57); " kVK_End = 0x77" - at: 16r22 put: (self value: 16rff56); " kVK_PageDown = 0x79" - at: 16r1c put: (self value: 16rff96); " kVK_LeftArrow = 0x7B" - at: 16r1d put: (self value: 16rff98); " kVK_RightArrow = 0x7C" - at: 16r1f put: (self value: 16rff99); " kVK_DownArrow = 0x7D" - at: 16r1e put: (self value: 16rff97); " kVK_UpArrow = 0x7E" - at: 16r41 put: (self value: 16r41); "kVK_ANSI_A = 0x00" - at: 16r42 put: (self value: 16r42); " kVK_ANSI_B = 0x0B" - at: 16r43 put: (self value: 16r43); " kVK_ANSI_C = 0x08" - at: 16r44 put: (self value: 16r44); " kVK_ANSI_D = 0x02" - at: 16r45 put: (self value: 16r45); " kVK_ANSI_E = 0x0E" - at: 16r46 put: (self value: 16r46); " kVK_ANSI_F = 0x03" - at: 16r47 put: (self value: 16r47); " kVK_ANSI_G = 0x05" - at: 16r48 put: (self value: 16r48); " kVK_ANSI_H = 0x04" - at: 16r49 put: (self value: 16r49); " kVK_ANSI_I = 0x22" - at: 16r4a put: (self value: 16r4a); " kVK_ANSI_J = 0x26" - at: 16r4b put: (self value: 16r4b); " kVK_ANSI_K = 0x28" - at: 16r4c put: (self value: 16r4c); " kVK_ANSI_L = 0x25" - at: 16r4d put: (self value: 16r4d); " kVK_ANSI_M = 0x2E" - at: 16r4e put: (self value: 16r4e); " kVK_ANSI_N = 0x2D" - at: 16r4f put: (self value: 16r4f); " kVK_ANSI_O = 0x1F" - at: 16r50 put: (self value: 16r50); " kVK_ANSI_P = 0x23" - at: 16r51 put: (self value: 16r51); " kVK_ANSI_Q = 0x0C" - at: 16r52 put: (self value: 16r52); " kVK_ANSI_R = 0x0F" - at: 16r53 put: (self value: 16r53); " kVK_ANSI_S = 0x01" - at: 16r54 put: (self value: 16r54); " kVK_ANSI_T = 0x11" - at: 16r55 put: (self value: 16r55); " kVK_ANSI_U = 0x20" - at: 16r56 put: (self value: 16r56); " kVK_ANSI_V = 0x09" - at: 16r57 put: (self value: 16r57); " kVK_ANSI_W = 0x0D" - at: 16r58 put: (self value: 16r58); " kVK_ANSI_X = 0x07" - at: 16r59 put: (self value: 16r59); " kVK_ANSI_Y = 0x10" - at: 16r5a put: (self value: 16r5a); " kVK_ANSI_Z = 0x06" - - at: $0 asciiValue put: (self value: 16r30); " kVK_ANSI_0 = 0x1D" - at: $1 asciiValue put: (self value: 16r31); " kVK_ANSI_1 = 0x12" - at: $2 asciiValue put: (self value: 16r32); " kVK_ANSI_2 = 0x13" - at: $3 asciiValue put: (self value: 16r33); " kVK_ANSI_3 = 0x14" - at: $4 asciiValue put: (self value: 16r34); " kVK_ANSI_4 = 0x15" - at: $5 asciiValue put: (self value: 16r35); " kVK_ANSI_5 = 0x17" - at: $6 asciiValue put: (self value: 16r36); " kVK_ANSI_6 = 0x16" - at: $7 asciiValue put: (self value: 16r37); " kVK_ANSI_7 = 0x1A" - at: $8 asciiValue put: (self value: 16r38); " kVK_ANSI_8 = 0x1C" - at: $9 asciiValue put: (self value: 16r39); " kVK_ANSI_9 = 0x19" - - at: 16rbd put: (self value: 16r2d); " kVK_ANSI_Minus = 0x1B" - at: $= asciiValue put: (self value: 16r3d); " kVK_ANSI_Equal = 0x18" - at: 16rdb put: (self value: 16r5b); " kVK_ANSI_LeftBracket = 0x21" - at: 16rdd put: (self value: 16r5d); " kVK_ANSI_RightBracket = 0x1E" - at: 1 put: (self value: 16r27); " kVK_ANSI_Quote = 0x27" - at: 16rba put: (self value: 16r3b); " kVK_ANSI_Semicolon = 0x29" - at: 16rbf put: (self value: 16r5c); " kVK_ANSI_Backslash = 0x2A" - at: 16rbc put: (self value: 16r2c); " kVK_ANSI_Comma = 0x2B" - at: 16rdc put: (self value: 16r2f); " kVK_ANSI_Slash = 0x2C" - at: 16rbe put: (self value: 16r2e); " kVK_ANSI_Period = 0x2F" - at: 16rc0 put: (self value: 16r60); " kVK_ANSI_Grave = 0x32" - at: 16r6e put: (self value: 16rffae); " kVK_ANSI_KeypadDecimal = 0x41" - at: 16r6a put: (self value: 16rffaa); " kVK_ANSI_KeypadMultiply = 0x43" - at: 16r6b put: (self value: 16rffab); " kVK_ANSI_KeypadPlus = 0x45" - at: 16r0c put: (self value: 16r47); " kVK_ANSI_KeypadClear = 0x47" "Not mapped" - at: 16r6f put: (self value: 16rffaf); " kVK_ANSI_KeypadDivide = 0x4B" - at: 16r0d put: (self value: 16rff8d); " kVK_ANSI_KeypadEnter = 0x4C" - at: 16r6d put: (self value: 16rffad); " kVK_ANSI_KeypadMinus = 0x4E" - at: 1 put: (self value: 16rffbd); " kVK_ANSI_KeypadEquals = 0x51" - at: 16r60 put: (self value: 16rffb0); " kVK_ANSI_Keypad0 = 0x52" - at: 16r61 put: (self value: 16rffb1); " kVK_ANSI_Keypad1 = 0x53" - at: 16r62 put: (self value: 16rffb2); " kVK_ANSI_Keypad2 = 0x54" - at: 16r63 put: (self value: 16rffb3); " kVK_ANSI_Keypad3 = 0x55" - at: 16r64 put: (self value: 16rffb4); " kVK_ANSI_Keypad4 = 0x56" - at: 16r65 put: (self value: 16rffb5); " kVK_ANSI_Keypad5 = 0x57" - at: 16r66 put: (self value: 16rffb6); " kVK_ANSI_Keypad6 = 0x58" - at: 16r67 put: (self value: 16rffb7); " kVK_ANSI_Keypad7 = 0x59" - at: 16r68 put: (self value: 16rffb8); " kVK_ANSI_Keypad8 = 0x5B" - at: 16r69 put: (self value: 16rffb9) " kVK_ANSI_Keypad9 = 0x5C" \ No newline at end of file diff --git a/Keys.package/Key.class/class/windows/valueForWindowsPlatform_.st b/Keys.package/Key.class/class/windows/valueForWindowsPlatform_.st deleted file mode 100644 index 551a41eeb3..0000000000 --- a/Keys.package/Key.class/class/windows/valueForWindowsPlatform_.st +++ /dev/null @@ -1,3 +0,0 @@ -valueForWindowsPlatform: aKeyCode - - ^self windowsVirtualKeyTable at: aKeyCode ifAbsent: [ (self basicNew withValue: aKeyCode andName: #Unknown) ] \ No newline at end of file diff --git a/Keys.package/Key.class/class/windows/windowsVirtualKeyTable.st b/Keys.package/Key.class/class/windows/windowsVirtualKeyTable.st deleted file mode 100644 index e752c66d2b..0000000000 --- a/Keys.package/Key.class/class/windows/windowsVirtualKeyTable.st +++ /dev/null @@ -1,4 +0,0 @@ -windowsVirtualKeyTable - - WindowsVirtualKeyTable ifNil: [ self initializeWindowsVirtualKeyTable. ]. - ^WindowsVirtualKeyTable \ No newline at end of file diff --git a/Keys.package/Key.class/definition.st b/Keys.package/Key.class/definition.st deleted file mode 100644 index 8bd9fe2e35..0000000000 --- a/Keys.package/Key.class/definition.st +++ /dev/null @@ -1,5 +0,0 @@ -Object subclass: #Key - instanceVariableNames: 'value name' - classVariableNames: 'KeyTable MacosVirtualKeyTable UnixVirtualKeyTable WindowsVirtualKeyTable' - poolDictionaries: '' - category: 'Keys' \ No newline at end of file diff --git a/Keys.package/Key.class/instance/accessing/name.st b/Keys.package/Key.class/instance/accessing/name.st deleted file mode 100644 index 4dd8190dfa..0000000000 --- a/Keys.package/Key.class/instance/accessing/name.st +++ /dev/null @@ -1,2 +0,0 @@ -name - ^name \ No newline at end of file diff --git a/Keys.package/Key.class/instance/initialize-release/withValue_.st b/Keys.package/Key.class/instance/initialize-release/withValue_.st deleted file mode 100644 index d8c576e0f3..0000000000 --- a/Keys.package/Key.class/instance/initialize-release/withValue_.st +++ /dev/null @@ -1,2 +0,0 @@ -withValue: aValue - self withValue: aValue andName: self class unknownKeyName \ No newline at end of file diff --git a/Keys.package/Key.class/instance/initialize-release/withValue_andName_.st b/Keys.package/Key.class/instance/initialize-release/withValue_andName_.st deleted file mode 100644 index dcc7de4103..0000000000 --- a/Keys.package/Key.class/instance/initialize-release/withValue_andName_.st +++ /dev/null @@ -1,3 +0,0 @@ -withValue: aValue andName: aName - value := aValue. - name := aName \ No newline at end of file diff --git a/Keys.package/Key.class/instance/printing/printOn_.st b/Keys.package/Key.class/instance/printing/printOn_.st deleted file mode 100644 index e01f8e5352..0000000000 --- a/Keys.package/Key.class/instance/printing/printOn_.st +++ /dev/null @@ -1,7 +0,0 @@ -printOn: aStream - aStream - nextPutAll: 'Key '; - nextPutAll: name; - nextPutAll: ' code: ('; - nextPutAll: value asString; - nextPutAll: ')'. \ No newline at end of file diff --git a/Keys.package/Key.class/instance/testing/isUnkownKey.st b/Keys.package/Key.class/instance/testing/isUnkownKey.st deleted file mode 100644 index 03ea143b19..0000000000 --- a/Keys.package/Key.class/instance/testing/isUnkownKey.st +++ /dev/null @@ -1,2 +0,0 @@ -isUnkownKey - ^self name == self class unknownKeyName \ No newline at end of file diff --git a/Keys.package/KeyPrinterMorph.class/README.md b/Keys.package/KeyPrinterMorph.class/README.md deleted file mode 100644 index e34aebfd34..0000000000 --- a/Keys.package/KeyPrinterMorph.class/README.md +++ /dev/null @@ -1 +0,0 @@ -I am a morph that prints the keys in the keyboard events. KeyPrinterMorph new openInWorld \ No newline at end of file diff --git a/Keys.package/KeyPrinterMorph.class/definition.st b/Keys.package/KeyPrinterMorph.class/definition.st deleted file mode 100644 index c9aad45881..0000000000 --- a/Keys.package/KeyPrinterMorph.class/definition.st +++ /dev/null @@ -1,5 +0,0 @@ -Morph subclass: #KeyPrinterMorph - instanceVariableNames: '' - classVariableNames: '' - poolDictionaries: '' - category: 'Keys-Tests' \ No newline at end of file diff --git a/Keys.package/KeyPrinterMorph.class/instance/event handling/handlesKeyboard_.st b/Keys.package/KeyPrinterMorph.class/instance/event handling/handlesKeyboard_.st deleted file mode 100644 index b2efaae3d6..0000000000 --- a/Keys.package/KeyPrinterMorph.class/instance/event handling/handlesKeyboard_.st +++ /dev/null @@ -1,2 +0,0 @@ -handlesKeyboard: evt - ^ true \ No newline at end of file diff --git a/Keys.package/KeyPrinterMorph.class/instance/event handling/handlesMouseDown_.st b/Keys.package/KeyPrinterMorph.class/instance/event handling/handlesMouseDown_.st deleted file mode 100644 index 478c1222e0..0000000000 --- a/Keys.package/KeyPrinterMorph.class/instance/event handling/handlesMouseDown_.st +++ /dev/null @@ -1,2 +0,0 @@ -handlesMouseDown: evt - ^ true \ No newline at end of file diff --git a/Keys.package/KeyPrinterMorph.class/instance/event handling/keyDown_.st b/Keys.package/KeyPrinterMorph.class/instance/event handling/keyDown_.st deleted file mode 100644 index 23dfb75b7c..0000000000 --- a/Keys.package/KeyPrinterMorph.class/instance/event handling/keyDown_.st +++ /dev/null @@ -1,2 +0,0 @@ -keyDown: anEvent - UIManager default inform: anEvent key asString. \ No newline at end of file diff --git a/Keys.package/KeyPrinterMorph.class/instance/event handling/mouseDown_.st b/Keys.package/KeyPrinterMorph.class/instance/event handling/mouseDown_.st deleted file mode 100644 index e29cf72703..0000000000 --- a/Keys.package/KeyPrinterMorph.class/instance/event handling/mouseDown_.st +++ /dev/null @@ -1,3 +0,0 @@ -mouseDown: event - super mouseDown: event. - World activeHand newKeyboardFocus: self \ No newline at end of file diff --git a/Keys.package/KeyPrinterMorph.class/instance/initialize/openInWorld.st b/Keys.package/KeyPrinterMorph.class/instance/initialize/openInWorld.st deleted file mode 100644 index bc4fa155fa..0000000000 --- a/Keys.package/KeyPrinterMorph.class/instance/initialize/openInWorld.st +++ /dev/null @@ -1,2 +0,0 @@ -openInWorld - self openInWindowLabeled: 'KeyPrinter' \ No newline at end of file diff --git a/Keys.package/extension/KeyboardEvent/instance/key.st b/Keys.package/extension/KeyboardEvent/instance/key.st deleted file mode 100644 index 2328dd54f8..0000000000 --- a/Keys.package/extension/KeyboardEvent/instance/key.st +++ /dev/null @@ -1,2 +0,0 @@ -key - ^Smalltalk os keyForValue: keyValue \ No newline at end of file diff --git a/Keys.package/extension/MacOSPlatform/instance/keyForValue_.st b/Keys.package/extension/MacOSPlatform/instance/keyForValue_.st deleted file mode 100644 index dd2c0a97b0..0000000000 --- a/Keys.package/extension/MacOSPlatform/instance/keyForValue_.st +++ /dev/null @@ -1,2 +0,0 @@ -keyForValue: aKeyValue - ^Key valueForMacOSXPlatform: aKeyValue. \ No newline at end of file diff --git a/Keys.package/extension/UnixPlatform/instance/keyForValue_.st b/Keys.package/extension/UnixPlatform/instance/keyForValue_.st deleted file mode 100644 index 426ae4456f..0000000000 --- a/Keys.package/extension/UnixPlatform/instance/keyForValue_.st +++ /dev/null @@ -1,2 +0,0 @@ -keyForValue: aKeyValue - ^Key valueForUnixPlatform: aKeyValue. \ No newline at end of file diff --git a/Keys.package/extension/Win32Platform/instance/keyForValue_.st b/Keys.package/extension/Win32Platform/instance/keyForValue_.st deleted file mode 100644 index c54c70e318..0000000000 --- a/Keys.package/extension/Win32Platform/instance/keyForValue_.st +++ /dev/null @@ -1,2 +0,0 @@ -keyForValue: aKeyValue - ^Key valueForWindowsPlatform: aKeyValue. \ No newline at end of file diff --git a/Rubric.package/RubNotificationStrategy.class/README.md b/Rubric.package/RubNotificationStrategy.class/README.md index 15d3f1282e..19b87e720e 100644 --- a/Rubric.package/RubNotificationStrategy.class/README.md +++ b/Rubric.package/RubNotificationStrategy.class/README.md @@ -1 +1 @@ -A RubNotificationStrategy is xxxxxxxxx. Instance Variables editor: editor - xxxxx \ No newline at end of file +I encapsulate the logic that gets executed when, during compilation, a RubSmalltalkEditor receives a notification from the compiler. I am an abstract class. My subclasses define the actual behaviour. \ No newline at end of file diff --git a/Rubric.package/RubTextInsertionStrategy.class/README.md b/Rubric.package/RubTextInsertionStrategy.class/README.md index 0c1cc3f40e..4d68f43a2c 100644 --- a/Rubric.package/RubTextInsertionStrategy.class/README.md +++ b/Rubric.package/RubTextInsertionStrategy.class/README.md @@ -1 +1 @@ -A RubTextInsertionStrategy is xxxxxxxxx. \ No newline at end of file +I insert the notification directly in the text at the given position. (I alter the content of the text editor) \ No newline at end of file diff --git a/ScriptLoader40.package/ScriptLoader.class/instance/pharo - scripts/script276.st b/ScriptLoader40.package/ScriptLoader.class/instance/pharo - scripts/script276.st new file mode 100644 index 0000000000..aac6ef3d3c --- /dev/null +++ b/ScriptLoader40.package/ScriptLoader.class/instance/pharo - scripts/script276.st @@ -0,0 +1,331 @@ +script276 + + ^ 'AST-Core-TheIntegrator.232.mcz +AST-Interpreter-Core-TheIntegrator.130.mcz +AST-Interpreter-Test-EstebanLorenzano.93.mcz +AST-Tests-Core-TheIntegrator.43.mcz +Announcements-Core-MarcusDenker.55.mcz +Announcements-Help-TheIntegrator.10.mcz +Announcements-Tests-Core-TheIntegrator.23.mcz +Announcements-View-TheIntegrator.22.mcz +AsmJit-Core-MarcusDenker.8.mcz +AsmJit-Extension-MarcusDenker.8.mcz +AsmJit-Instructions-MarcusDenker.11.mcz +AsmJit-Operands-StephaneDucasse.14.mcz +AsmJit-StackManagement-SvenVanCaekenberghe.11.mcz +AsmJit-Tests-TheIntegrator.19.mcz +AsmJit-x86-TheIntegrator.36.mcz +Athens-Balloon-MarcusDenker.18.mcz +Athens-Cairo-TheIntegrator.77.mcz +Athens-CairoPools-MarcusDenker.13.mcz +Athens-Core-MarcusDenker.43.mcz +Athens-Examples-TheIntegrator.40.mcz +Athens-Morphic-TheIntegrator.37.mcz +Athens-Text-StephaneDucasse.14.mcz +Balloon-MarcusDenker.116.mcz +BalloonTests-MarcusDenker.3.mcz +CodeImport-MarcusDenker.46.mcz +Collections-Abstract-TheIntegrator.271.mcz +Collections-Arithmetic-MarcusDenker.13.mcz +Collections-Arrayed-EstebanLorenzano.69.mcz +Collections-Atomic-MarcusDenker.10.mcz +Collections-Native-MarcusDenker.7.mcz +Collections-Sequenceable-TheIntegrator.175.mcz +Collections-Stack-MarcusDenker.7.mcz +Collections-Streams-TheIntegrator.164.mcz +Collections-Strings-TheIntegrator.324.mcz +Collections-Support-MarcusDenker.57.mcz +Collections-Unordered-MarcusDenker.193.mcz +Collections-Weak-MarcusDenker.86.mcz +CollectionsTests-TheIntegrator.662.mcz +Compiler-TheIntegrator.562.mcz +Compression-StephaneDucasse.145.mcz +CompressionTests-TheIntegrator.29.mcz +ConfigurationCommandLineHandler-Core-MarcusDenker.25.mcz +ConfigurationCommandLineHandler-Tests-MarcusDenker.11.mcz +DebuggerActions-MarcusDenker.74.mcz +DebuggerFilters-TheIntegrator.9.mcz +DebuggerModel-TheIntegrator.100.mcz +DebuggerTests-TheIntegrator.4.mcz +Deprecated40-TheIntegrator.28.mcz +EmbeddedFreeType-TheIntegrator.7.mcz +EmbeddedFreeTypeTests-TheIntegrator.8.mcz +EmergencyEvaluator-MarcusDenker.32.mcz +FileSystem-Core-MarcusDenker.158.mcz +FileSystem-Disk-MarcusDenker.76.mcz +FileSystem-Memory-TheIntegrator.53.mcz +FileSystem-Tests-Core-MarcusDenker.82.mcz +FileSystem-Tests-Disk-MarcusDenker.20.mcz +FileSystem-Tests-Memory-SvenVanCaekenberghe.6.mcz +FileSystem-Zip-TheIntegrator.17.mcz +Files-MarcusDenker.367.mcz +FontChooser-MarcusDenker.5.mcz +FontInfrastructure-MarcusDenker.5.mcz +FontInfrastructureTests-TheIntegrator.4.mcz +FreeType-TheIntegrator.682.mcz +FreeTypeTests-SvenVanCaekenberghe.5.mcz +Fuel-TheIntegrator.795.mcz +FuelCommandLineHandler-TheIntegrator.27.mcz +FuelSystem-FileRegistry-EstebanLorenzano.3.mcz +FuelTests-TheIntegrator.379.mcz +FuelTools-Debugger-StephaneDucasse.12.mcz +GT-Inspector-TudorGirba.239.mcz +GT-InspectorExtensions-Core-AndreiChis.56.mcz +GT-Playground-AndreiChis.36.mcz +GT-Tests-Inspector-TudorGirba.22.mcz +Generated-code-non-existing-package-EstebanLorenzano.2.mcz +Glamour-Announcements-TudorGirba.7.mcz +Glamour-Browsers-TudorGirba.104.mcz +Glamour-Core-AndreiChis.277.mcz +Glamour-Examples-StephanEggermont.284.mcz +Glamour-Helpers-AndreiChis.35.mcz +Glamour-Morphic-Pager-AliakseiSyrel.67.mcz +Glamour-Morphic-Renderer-AndreiChis.270.mcz +Glamour-Morphic-Theme-AndreiChis.180.mcz +Glamour-Morphic-Widgets-AndreiChis.127.mcz +Glamour-Presentations-TudorGirba.157.mcz +Glamour-Rubric-Presentations-AndreiChis.20.mcz +Glamour-Tests-Core-AndreiChis.96.mcz +Glamour-Tests-Morphic-AliakseiSyrel.115.mcz +Glamour-Tests-Resources-AndreiChis.3.mcz +Glamour-Tests-Rubric-AndreiChis.13.mcz +Gofer-Core-TheIntegrator.225.mcz +Gofer-Tests-TheIntegrator.164.mcz +Graphics-Display Objects-EstebanLorenzano.155.mcz +Graphics-Files-TheIntegrator.58.mcz +Graphics-Fonts-EstebanLorenzano.96.mcz +Graphics-Fonts-Tests-EstebanLorenzano.3.mcz +Graphics-Primitives-MarcusDenker.148.mcz +Graphics-Resources-EstebanLorenzano.22.mcz +Graphics-Tests-MarcusDenker.54.mcz +Graphics-Transformations-MarcusDenker.10.mcz +GroupManager-TheIntegrator.70.mcz +GroupManagerUI-MarcusDenker.38.mcz +Growl-TheIntegrator.32.mcz +HelpSystem-Core-MarcusDenker.111.mcz +HelpSystem-Tests-TheIntegrator.30.mcz +HudsonBuildTools20-SvenVanCaekenberghe.59.mcz +Kernel-TheIntegrator.1860.mcz +KernelTests-TheIntegrator.689.mcz +Keymapping-Core-EstebanLorenzano.195.mcz +Keymapping-KeyCombinations-EstebanLorenzano.45.mcz +Keymapping-Pragmas-TheIntegrator.48.mcz +Keymapping-Settings-MarcusDenker.79.mcz +Keymapping-Tests-TheIntegrator.94.mcz +Keymapping-Tools-Spec-SvenVanCaekenberghe.27.mcz +Keys-TheIntegrator.11.mcz +Komitter-MarcusDenker.99.mcz +Manifest-Core-TheIntegrator.188.mcz +Manifest-CriticBrowser-TheIntegrator.159.mcz +Manifest-Resources-Tests-MarcusDenker.14.mcz +Manifest-Tests-TheIntegrator.44.mcz +MenuRegistration-TheIntegrator.74.mcz +MessageBrowserRefactoringAddition-StephaneDucasse.2.mcz +Metacello-Base-EstebanLorenzano.114.mcz +Metacello-Core-MarcusDenker.722.mcz +Metacello-FileTree-EstebanLorenzano.30.mcz +Metacello-GitHub-StephaneDucasse.33.mcz +Metacello-MC-MarcusDenker.696.mcz +Metacello-PharoCommonPlatform-StephaneDucasse.12.mcz +Metacello-Platform.pharo20-EstebanLorenzano.36.mcz +Metacello-Platform.pharo30-StephaneDucasse.6.mcz +Metacello-ProfStef-MarcusDenker.16.mcz +Metacello-Reference-EstebanLorenzano.37.mcz +Metacello-TestsCore-EstebanLorenzano.36.mcz +Metacello-TestsMC-EstebanLorenzano.388.mcz +Metacello-TestsMCCore-EstebanLorenzano.6.mcz +Metacello-TestsMCResources-TheIntegrator.15.mcz +Metacello-TestsCommonMC.pharo20-EstebanLorenzano.4.mcz +Metacello-TestsPlatform.squeakCommon-MarcusDenker.19.mcz +Metacello-ToolBox-MarcusDenker.141.mcz +Metacello-Tutorial-EstebanLorenzano.27.mcz +Monticello-TheIntegrator.961.mcz +Monticello-Tests-TheIntegrator.4.mcz +MonticelloConfigurations-MarcusDenker.70.mcz +MonticelloFileTree-Core-StephaneDucasse.173.mcz +MonticelloFileTree-FileSystem-Utilities-MarcusDenker.32.mcz +MonticelloGUI-TheIntegrator.304.mcz +MonticelloMocks-EstebanLorenzano.2.mcz +Morphic-Base-StephaneDucasse.401.mcz +Morphic-Core-TheIntegrator.115.mcz +Morphic-Examples-TheIntegrator.33.mcz +Morphic-Widgets-Basic-TheIntegrator.33.mcz +Morphic-Widgets-ColorPicker-TheIntegrator.15.mcz +Morphic-Widgets-Extra-StephaneDucasse.11.mcz +Morphic-Widgets-List-MarcusDenker.13.mcz +Morphic-Widgets-NewList-TheIntegrator.5.mcz +Morphic-Widgets-Pluggable-TheIntegrator.37.mcz +Morphic-Widgets-Scrolling-TheIntegrator.17.mcz +Morphic-Widgets-Tabs-TheIntegrator.8.mcz +Morphic-Widgets-Taskbar-TheIntegrator.5.mcz +Morphic-Widgets-Tree-TheIntegrator.18.mcz +Morphic-Widgets-Windows-TheIntegrator.34.mcz +MorphicTests-TheIntegrator.94.mcz +Multilingual-Encodings-MarcusDenker.47.mcz +Multilingual-Languages-MarcusDenker.38.mcz +Multilingual-OtherLanguages-MarcusDenker.12.mcz +Multilingual-Tests-MarcusDenker.35.mcz +Multilingual-TextConversion-MarcusDenker.68.mcz +Multilingual-TextConverterOtherLanguages-MarcusDenker.2.mcz +NECompletion-TheIntegrator.183.mcz +NECompletionTests-TheIntegrator.2.mcz +NativeBoost-Core-TheIntegrator.153.mcz +NativeBoost-Examples-CamilloBruni.16.mcz +NativeBoost-Mac-MarcusDenker.12.mcz +NativeBoost-Pools-CamilloBruni.13.mcz +NativeBoost-Tests-TheIntegrator.88.mcz +NativeBoost-Unix-MarcusDenker.17.mcz +NativeBoost-Win32-TheIntegrator.52.mcz +Nautilus-TheIntegrator.830.mcz +NautilusCommon-TheIntegrator.234.mcz +NautilusRefactoring-TheIntegrator.188.mcz +NautilusTests-TheIntegrator.2.mcz +Network-Kernel-MarcusDenker.108.mcz +Network-MIME-MarcusDenker.69.mcz +Network-Mail-StephaneDucasse.37.mcz +Network-Protocols-MarcusDenker.101.mcz +Network-UUID-MarcusDenker.29.mcz +Network-Url-MarcusDenker.99.mcz +NetworkTests-MarcusDenker.98.mcz +NewValueHolder-TheIntegrator.17.mcz +NodeNavigation-MarcusDenker.49.mcz +NonInteractiveTranscript-TheIntegrator.15.mcz +OSWindow-Core-EstebanLorenzano.18.mcz +OSWindow-SDL2-EstebanLorenzano.19.mcz +OSWindow-VM-IgorStasenko.2.mcz +OpalCompiler-Core-TheIntegrator.547.mcz +OpalCompiler-Tests-TheIntegrator.247.mcz +OpalDecompiler-TheIntegrator.23.mcz +Pharo-Help-MarcusDenker.11.mcz +Polymorph-EventEnhancements-MarcusDenker.18.mcz +Polymorph-Geometry-MarcusDenker.13.mcz +Polymorph-TaskbarIcons-MarcusDenker.40.mcz +Polymorph-Tools-Diff-TheIntegrator.156.mcz +Polymorph-Widgets-TheIntegrator.1150.mcz +ProfStef-Core-TheIntegrator.43.mcz +ProfStef-Help-SvenVanCaekenberghe.14.mcz +ProfStef-Tests-SvenVanCaekenberghe.23.mcz +RPackage-Core-TheIntegrator.382.mcz +RPackage-SystemIntegration-TheIntegrator.228.mcz +RPackage-Tests-TheIntegrator.163.mcz +RecentSubmissions-TheIntegrator.227.mcz +Refactoring-Changes-TheIntegrator.54.mcz +Refactoring-Core-TheIntegrator.252.mcz +Refactoring-Critics-TheIntegrator.134.mcz +Refactoring-Environment-TheIntegrator.44.mcz +Refactoring-Tests-Changes-MarcusDenker.38.mcz +Refactoring-Tests-Core-TheIntegrator.111.mcz +Refactoring-Tests-Critics-MarcusDenker.25.mcz +Refactoring-Tests-Environment-StephaneDucasse.11.mcz +Regex-Core-MarcusDenker.33.mcz +Regex-Help-MarcusDenker.5.mcz +Regex-Tests-Core-MarcusDenker.9.mcz +ReleaseTests-TheIntegrator.9.mcz +Ring-Core-Containers-TheIntegrator.39.mcz +Ring-Core-Kernel-TheIntegrator.201.mcz +Ring-Monticello-MarcusDenker.29.mcz +Ring-Tests-Containers-MarcusDenker.18.mcz +Ring-Tests-Kernel-TheIntegrator.80.mcz +Ring-Tests-Monticello-MarcusDenker.19.mcz +Rubric-AndreiChis.135.mcz +SUnit-Core-TheIntegrator.122.mcz +SUnit-Help-MarcusDenker.9.mcz +SUnit-Tests-MarcusDenker.37.mcz +SUnit-UI-TheIntegrator.95.mcz +SUnit-UITesting-TheIntegrator.21.mcz +ScriptLoader-Tests-TheIntegrator.4.mcz +Settings-Graphics-MarcusDenker.21.mcz +Settings-Polymorph-MarcusDenker.70.mcz +Settings-System-TheIntegrator.33.mcz +Shout-MarcusDenker.227.mcz +ShoutTests-MarcusDenker.23.mcz +Slot-TheIntegrator.481.mcz +SlotTests-MarcusDenker.93.mcz +SmartSuggestions-TheIntegrator.142.mcz +SmartSuggestionsTests-MarcusDenker.4.mcz +Spec-Core-TheIntegrator.349.mcz +Spec-Debugger-TheIntegrator.231.mcz +Spec-Examples-TheIntegrator.80.mcz +Spec-Extensions-TheIntegrator.5.mcz +Spec-Inspector-TheIntegrator.222.mcz +Spec-Layout-TheIntegrator.67.mcz +Spec-MorphicAdapters-TheIntegrator.193.mcz +Spec-PolyWidgets-TheIntegrator.44.mcz +Spec-Tests-SvenVanCaekenberghe.39.mcz +Spec-Tools-TheIntegrator.234.mcz +StartupPreferences-TheIntegrator.122.mcz +System-Announcements-TheIntegrator.96.mcz +System-Caching-MarcusDenker.6.mcz +System-CachingTests-TheIntegrator.4.mcz +System-Changes-TheIntegrator.253.mcz +System-Clipboard-SvenVanCaekenberghe.32.mcz +System-CommandLine-MarcusDenker.165.mcz +System-FilePackage-TheIntegrator.128.mcz +System-FileRegistry-SvenVanCaekenberghe.31.mcz +System-Finalization-StephaneDucasse.17.mcz +System-Hashing-StephaneDucasse.45.mcz +System-History-EstebanLorenzano.7.mcz +System-History-Tests-EstebanLorenzano.3.mcz +System-Installers-SvenVanCaekenberghe.42.mcz +System-Localization-TheIntegrator.88.mcz +System-Localization-Tests-TheIntegrator.5.mcz +System-Object Events-MarcusDenker.15.mcz +System-Platforms-MarcusDenker.57.mcz +System-Serial Port-StephaneDucasse.23.mcz +System-Settings-MarcusDenker.301.mcz +System-Sound-MarcusDenker.16.mcz +System-Support-TheIntegrator.1062.mcz +Tests-TheIntegrator.713.mcz +Text-Core-StephaneDucasse.31.mcz +Text-Diff-TheIntegrator.2.mcz +Text-Edition-TheIntegrator.51.mcz +Text-Edition-Tests-EstebanLorenzano.3.mcz +Text-Scanning-TheIntegrator.24.mcz +Text-Tests-EstebanLorenzano.7.mcz +Tool-Base-MarcusDenker.43.mcz +Tool-Browser-Old-TheIntegrator.29.mcz +Tool-Changes-TheIntegrator.18.mcz +Tool-ConfigurationBrowser-TheIntegrator.6.mcz +Tool-FileList-TheIntegrator.20.mcz +Tool-FileList-Tests-EstebanLorenzano.3.mcz +Tool-FilePackageBrowser-TheIntegrator.3.mcz +Tool-Finder-TheIntegrator.19.mcz +Tool-ImageCleaner-TheIntegrator.4.mcz +Tool-ProcessBrowser-MarcusDenker.4.mcz +Tool-Profilers-TheIntegrator.10.mcz +Tool-Spotlight-MarcusDenker.14.mcz +Tool-SystemReporter-MarcusDenker.4.mcz +Tool-Transcript-StephaneDucasse.10.mcz +Tool-Workspace-TheIntegrator.16.mcz +Tools-MarcusDenker.1496.mcz +ToolsTest-MarcusDenker.denker.71.mcz +Traits-TheIntegrator.693.mcz +Transcript-StephaneDucasse.32.mcz +UIManager-MarcusDenker.132.mcz +Unicode-Initialization-MarcusDenker.10.mcz +UpdateStreamer-Core-MarcusDenker.32.mcz +UpdateStreamer-Tests-SvenVanCaekenberghe.6.mcz +UserManager-Core-MarcusDenker.13.mcz +Versionner-Core-Announcements-MarcusDenker.11.mcz +Versionner-Core-Commands-MarcusDenker.49.mcz +Versionner-Core-DependenciesModel-TheIntegrator.95.mcz +Versionner-Core-Model-TheIntegrator.44.mcz +Versionner-Spec-Browser-EstebanLorenzano.154.mcz +Versionner-Tests-Core-Commands-MarcusDenker.13.mcz +Versionner-Tests-Core-DependenciesModel-MarcusDenker.40.mcz +Versionner-Tests-Core-Model-MarcusDenker.28.mcz +Versionner-Tests-Resources-MarcusDenker.14.mcz +Zinc-Character-Encoding-Core-SvenVanCaekenberghe.33.mcz +Zinc-Character-Encoding-Tests-SvenVanCaekenberghe.20.mcz +Zinc-FileSystem-SvenVanCaekenberghe.10.mcz +Zinc-HTTP-SvenVanCaekenberghe.407.mcz +Zinc-Resource-Meta-Core-SvenVanCaekenberghe.38.mcz +Zinc-Resource-Meta-FileSystem-SvenVanCaekenberghe.4.mcz +Zinc-Resource-Meta-Tests-SvenVanCaekenberghe.26.mcz +Zinc-System-Support-MarcusDenker.8.mcz +Zinc-Tests-SvenVanCaekenberghe.216.mcz +Zinc-Zodiac-SvenVanCaekenberghe.35.mcz +Zodiac-Core-MarcusDenker.31.mcz +Zodiac-Extra-StephaneDucasse.10.mcz +Zodiac-Tests-MarcusDenker.13.mcz' +findTokens: String lf , String cr \ No newline at end of file diff --git a/ScriptLoader40.package/ScriptLoader.class/instance/pharo - updates/update40276.st b/ScriptLoader40.package/ScriptLoader.class/instance/pharo - updates/update40276.st new file mode 100644 index 0000000000..817e744722 --- /dev/null +++ b/ScriptLoader40.package/ScriptLoader.class/instance/pharo - updates/update40276.st @@ -0,0 +1,20 @@ +update40276 + "self new update40276" + self withUpdateLog: '14128 "Print it" from Playground menu does not work + https://pharo.fogbugz.com/f/cases/14128 + +14117 merge menuSpec and menuItemSpec + https://pharo.fogbugz.com/f/cases/14117 + +14113 WorldSate stepList not properly cleaned when a morph is deleted + https://pharo.fogbugz.com/f/cases/14113 + +13641 Merge Package Key into package System-Platforms + https://pharo.fogbugz.com/f/cases/13641 + +14099 SmalllintManifestChecker duplicates RBSmalllintChecker>>#run + https://pharo.fogbugz.com/f/cases/14099'. + self loadTogether: self script276 merge: false. + self loadConfiguration: 'GTPlayground' version: '1.0.3'. +ScriptLoader new deletePackage: 'Keys'. + self flushCaches. diff --git a/ScriptLoader40.package/ScriptLoader.class/instance/public/commentForCurrentUpdate.st b/ScriptLoader40.package/ScriptLoader.class/instance/public/commentForCurrentUpdate.st index 858dae29d7..cbf153e2ad 100644 --- a/ScriptLoader40.package/ScriptLoader.class/instance/public/commentForCurrentUpdate.st +++ b/ScriptLoader40.package/ScriptLoader.class/instance/public/commentForCurrentUpdate.st @@ -1,12 +1,15 @@ commentForCurrentUpdate - ^ '14129 Use Announcer>>#when:send:to: in Spec-Debugger - https://pharo.fogbugz.com/f/cases/14129 + ^ '14128 "Print it" from Playground menu does not work + https://pharo.fogbugz.com/f/cases/14128 -14124 Remove SystemAnnouncer subclass NautilusAnnouncer - https://pharo.fogbugz.com/f/cases/14124 +14117 merge menuSpec and menuItemSpec + https://pharo.fogbugz.com/f/cases/14117 -14126 Remove SystemAnnouncer subclass GroupAnnouncer - https://pharo.fogbugz.com/f/cases/14126 +14113 WorldSate stepList not properly cleaned when a morph is deleted + https://pharo.fogbugz.com/f/cases/14113 -10148 IRVisitor and IRInterpreter - https://pharo.fogbugz.com/f/cases/10148' \ No newline at end of file +13641 Merge Package Key into package System-Platforms + https://pharo.fogbugz.com/f/cases/13641 + +14099 SmalllintManifestChecker duplicates RBSmalllintChecker>>#run + https://pharo.fogbugz.com/f/cases/14099' \ No newline at end of file