Skip to content

Commit

Permalink
40276
Browse files Browse the repository at this point in the history
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

http://files.pharo.org/image/40/40276.zip
  • Loading branch information
Jenkins Build Server authored and ci committed Oct 1, 2014
1 parent f821362 commit 6d0d667
Show file tree
Hide file tree
Showing 78 changed files with 559 additions and 697 deletions.
@@ -0,0 +1,16 @@
version103: spec
<version: '1.0.3' imports: #('1.0-baseline' )>

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'. ].
@@ -0,0 +1,12 @@
version103: spec
<version: '1.0.3' imports: #('1.0-baseline' )>

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' ] ]
@@ -0,0 +1,36 @@
version272: spec
<version: '2.72' imports: #('2.91-baseline' )>

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'. ].
@@ -0,0 +1,9 @@
version121: spec
<version: '1.2.1' imports: #('0.2-baseline' )>

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'. ].
@@ -1,5 +1,6 @@
evaluateAndPopPrintSelection
UIManager default defer: [
GLMPrintPopper new evaluateAndOpenFromRubric: textMorph textArea
]


textMorph textArea editor evaluateSelectionAndDo: [ :result |
GLMPrintPopper installAlarmFor: [
GLMPrintPopper new
openFromRubric: textMorph textArea withResult: result ] ]

This file was deleted.

This file was deleted.

This file was deleted.

This file was deleted.

@@ -1 +1 @@
A GLMErrorPopper is xxxxxxxxx.
I am a popper that displays an error message.GLMErrorPopper simpleErrorPopper
Expand Down
@@ -0,0 +1,8 @@
simpleErrorPopper
"
self simpleErrorPopper
"

(GLMErrorPopper new
withString: 'error message goes here'
from: RubScrolledTextMorph new) openInWorld
2 changes: 1 addition & 1 deletion 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.
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).
Expand Down
@@ -0,0 +1,7 @@
installAlarmFor: aBlock

World
addAlarm: #value
withArguments: #()
for: aBlock
at: Time millisecondClockValue + 50.
Expand Up @@ -10,4 +10,5 @@ updateWithString: string from: aMorph
aMorph takeKeyboardFocus ];
onAnnouncement: MorphLostFocus do: [ :ann |
self delete.
aMorph takeKeyboardFocus ]
"If this event is triggered then another morph already has the focus.
Do not attempt to give the focus back to the original morph" ]
@@ -1 +1 @@
A GLMPopperNotificationStrategy is xxxxxxxxx.
I opened a new popper window that displays the given notification. (I do not alter the content of the text editor.)
Expand Up @@ -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
GLMErrorPopper installAlarmFor: [
(GLMErrorPopper new withString: aString from: self editor textArea owner owner owner)
openInWorld ]
@@ -1 +1 @@
A GLMPrintPopper is xxxxxxxxx.Instance Variables inspectButton: <Object>inspectButton - xxxxx
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
Expand Down
@@ -0,0 +1,9 @@
selectionEvaluationPopper
"
self selectionEvaluationPopper
"
GLMPrintPopper new
evaluateAndOpenFromRubric: (RubScrolledTextMorph new
beForSmalltalkCode;
updateTextWith: '1+2+4';
setSelection: (1to:6))
@@ -0,0 +1,8 @@
simpleObjectPopper
"
self simpleObjectPopper
"

GLMPrintPopper new
openFromRubric: RubScrolledTextMorph new
withResult: 'notification goes here'.
@@ -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

self
openFromRubric: aMorph
withResult: aMorph textArea editor evaluateSelection
@@ -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
@@ -1 +1 @@
A GLMPrintSelection is xxxxxxxxx.
I am event indicating to the renderer to execute and print the currently selected text.

This file was deleted.

This file was deleted.

@@ -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)
I provide support for displaying a Smalltalk method.self pharoMethodPresentationExample
Expand Down
@@ -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
@@ -1,4 +1,4 @@
GLMNewSmalltalkCodePresentation subclass: #GLMPharoMethodPresentation
GLMRubricSmalltalkCodePresentation subclass: #GLMPharoMethodPresentation
instanceVariableNames: 'highlightSmalltalkContext'
classVariableNames: ''
poolDictionaries: ''
Expand Down
@@ -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'' '
I provide support for displaying snippets of Smalltalk code (e.g. dealing with variable binding)self pharoPlaygroundPresentationExample
Expand Down
@@ -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'' '
@@ -1,4 +1,4 @@
GLMNewSmalltalkCodePresentation subclass: #GLMPharoPlaygroundPresentation
GLMRubricSmalltalkCodePresentation subclass: #GLMPharoPlaygroundPresentation
instanceVariableNames: 'variableBindingsBlock'
classVariableNames: ''
poolDictionaries: ''
Expand Down
@@ -1 +1 @@
A GLMRubricSmalltalkCodePresentation is xxxxxxxxx.
I extend the simple Rubric text presentation with basic support for dealing with Smalltalk code.

This file was deleted.

@@ -1 +1 @@
A GLMRubricTextPresentation is xxxxxxxxx.Instance Variables primarySelectionInterval: <Object> tabWidth: <Object> textSegments: <Object> withAnnotation: <Object> withColumns: <Object> withLineNumbers: <Object> wrapped: <Object>primarySelectionInterval - xxxxxtabWidth - xxxxxtextSegments - xxxxxwithAnnotation - xxxxxwithColumns - xxxxxwithLineNumbers - xxxxxwrapped - xxxxx
A presentation that displays text using Rubric.
Expand Down

This file was deleted.

1 change: 0 additions & 1 deletion Keys.package/Key.class/README.md

This file was deleted.

This file was deleted.

2 changes: 0 additions & 2 deletions Keys.package/Key.class/class/instance creation/value_.st

This file was deleted.

0 comments on commit 6d0d667

Please sign in to comment.