Skip to content

Commit

Permalink
50153
Browse files Browse the repository at this point in the history
15890 some cleaning
	https://pharo.fogbugz.com/f/cases/15890

15072 Senders and implementors do not work when one parameter is a string containing :
	https://pharo.fogbugz.com/f/cases/15072

15899 Remove destructive example
	https://pharo.fogbugz.com/f/cases/15899

15897 Load new Workspace from AlainPlantec/WorkspaceRevisited
	https://pharo.fogbugz.com/f/cases/15897

http://files.pharo.org/image/50/50153.zip
  • Loading branch information
Jenkins Build Server authored and ci committed Jul 6, 2015
1 parent 5d9ea00 commit fef56f2
Show file tree
Hide file tree
Showing 117 changed files with 276 additions and 347 deletions.
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
version
"Answer a Monticello version of the receiver."

^ self repository goferVersionFrom: self
^ self repository versionFrom: self name

This file was deleted.

This file was deleted.

Original file line number Diff line number Diff line change
@@ -1,2 +1,2 @@
goferVersionFrom: aVersionReference
^ self dictionary detect: [ :version | version info name = aVersionReference name ]
versionFrom: aVersionReferenceString
^ self dictionary detect: [ :version | version info name = aVersionReferenceString ]
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
versionFromFileNamed: aString
| v |
v := self cache
at: aString
ifAbsent: [ self loadVersionFromFileNamed: aString ].
self updateCachedVersionFromFileName: aString with: v.
^ v
versionFromFileNamed: aFileName
| version |
version := self cache
at: aFileName
ifAbsent: [ self loadVersionFromFileNamed: aFileName ].
self updateCachedVersionFromFileName: aFileName with: version.
^ version
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
versionFromRepositoryFromFileNamed: aString
| v |
v := self cache
at: aString
ifAbsent: [ self loadNotCachedVersionFromFileNamed: aString ].
self updateCachedVersionFromFileName: aString with: v.
^ v
versionFromRepositoryFromFileNamed: aFileName
| version |
version := self cache
at: aFileName
ifAbsent: [ self loadNotCachedVersionFromFileNamed: aFileName ].
self updateCachedVersionFromFileName: aFileName with: version.
^ version
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
versionFrom: aVersionReferenceString
^ self loadVersionFromFileNamed: aVersionReferenceString , '.mcz'
Original file line number Diff line number Diff line change
@@ -1,3 +1,5 @@
versionInfoFromFileNamed: aString
self cache at: aString ifPresent: [:v | ^ v info].
^ self loadVersionInfoFromFileNamed: aString
versionInfoFromFileNamed: aFileName
self cache
at: aFileName
ifPresent: [:version | ^ version info].
^ self loadVersionInfoFromFileNamed: aFileName
Original file line number Diff line number Diff line change
@@ -1,2 +1,2 @@
versionNameFromFileName: aString
^ (aString copyUpToLast: $.) copyUpTo: $(
versionNameFromFileName: aFileName
^ (aFileName copyUpToLast: $.) copyUpTo: $(
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
versionFrom: aVersionReferenceString
self error: 'Unable to load from ' , self printString
Original file line number Diff line number Diff line change
@@ -1,9 +1,9 @@
goferVersionFrom: aVersionReference
versionFrom: aVersionReferenceString
"until we no longer find .tree directories in the wild"

((self readableFileNames collect: [ :fileName | self fileDirectoryOn: fileName ])
select: [ :packageDirectory | self fileUtils directoryExists: packageDirectory ])
collect: [ :packageDirectory |
(self versionInfoForPackageDirectory: packageDirectory) name = aVersionReference name
(self readableFileNames collect: [ :fileName | self fileDirectoryOn: fileName ])
select: [ :packageDirectory | self fileUtils directoryExists: packageDirectory ]
thenCollect: [ :packageDirectory |
(self versionInfoForPackageDirectory: packageDirectory) name = aVersionReferenceString
ifTrue: [ ^ self loadVersionFromFileNamed: (self fileUtils directoryName: packageDirectory) ] ].
^ nil

This file was deleted.

This file was deleted.

Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
script50152
script50153

^ 'AST-Core-TheIntegrator.314.mcz
AST-Tests-Core-TheIntegrator.70.mcz
Expand Down Expand Up @@ -94,7 +94,7 @@ Glamour-Tests-Core-AliakseiSyrel.104.mcz
Glamour-Tests-Morphic-AndreiChis.124.mcz
Glamour-Tests-Resources-AndreiChis.3.mcz
Glamour-Tests-Rubric-AndreiChis.14.mcz
Gofer-Core-TheIntegrator.228.mcz
Gofer-Core-TheIntegrator.230.mcz
Gofer-Tests-TheIntegrator.164.mcz
Graphics-Canvas-TheIntegrator.2.mcz
Graphics-Display Objects-TheIntegrator.161.mcz
Expand Down Expand Up @@ -147,10 +147,10 @@ Metacello-TestsCommonMC.pharo20-EstebanLorenzano.4.mcz
Metacello-TestsPlatform.squeakCommon-MarcusDenker.19.mcz
Metacello-ToolBox-MarcusDenker.141.mcz
Metacello-Tutorial-EstebanLorenzano.27.mcz
Monticello-TheIntegrator.1036.mcz
Monticello-TheIntegrator.1039.mcz
Monticello-Tests-TheIntegrator.16.mcz
MonticelloConfigurations-MarcusDenker.70.mcz
MonticelloFileTree-Core-TheIntegrator.184.mcz
MonticelloFileTree-Core-TheIntegrator.186.mcz
MonticelloFileTree-FileSystem-Utilities-MarcusDenker.32.mcz
MonticelloGUI-TheIntegrator.361.mcz
MonticelloMocks-EstebanLorenzano.2.mcz
Expand All @@ -177,7 +177,7 @@ Multilingual-OtherLanguages-TheIntegrator.15.mcz
Multilingual-Tests-TheIntegrator.38.mcz
Multilingual-TextConversion-TheIntegrator.70.mcz
Multilingual-TextConverterOtherLanguages-MarcusDenker.2.mcz
NECompletion-TheIntegrator.201.mcz
NECompletion-TheIntegrator.202.mcz
NECompletion-Tests-TheIntegrator.2.mcz
NativeBoost-Core-TheIntegrator.168.mcz
NativeBoost-Examples-CamilloBruni.16.mcz
Expand Down Expand Up @@ -268,7 +268,7 @@ Spec-MorphicAdapters-TheIntegrator.214.mcz
Spec-PolyWidgets-TheIntegrator.59.mcz
Spec-Tests-TheIntegrator.47.mcz
Spec-Tools-TheIntegrator.274.mcz
StartupPreferences-TheIntegrator.133.mcz
StartupPreferences-TheIntegrator.135.mcz
System-Announcements-TheIntegrator.100.mcz
System-Caching-TheIntegrator.26.mcz
System-CachingTests-TheIntegrator.14.mcz
Expand All @@ -295,7 +295,7 @@ System-VMEvents-TheIntegrator.5.mcz
Tests-TheIntegrator.734.mcz
Text-Core-TheIntegrator.35.mcz
Text-Diff-StephaneDucasse.4.mcz
Text-Edition-TheIntegrator.89.mcz
Text-Edition-TheIntegrator.91.mcz
Text-Edition-Tests-EstebanLorenzano.3.mcz
Text-Scanning-TheIntegrator.26.mcz
Text-Tests-EstebanLorenzano.7.mcz
Expand All @@ -313,7 +313,7 @@ Tool-Profilers-TheIntegrator.17.mcz
Tool-SystemReporter-TheIntegrator.12.mcz
Tool-Transcript-TheIntegrator.14.mcz
Tool-TxWorkspace-TorstenBergmann.5.mcz
Tool-Workspace-TheIntegrator.26.mcz
Tool-Workspace-TheIntegrator.28.mcz
Tools-TheIntegrator.1503.mcz
ToolsTest-MarcusDenker.denker.71.mcz
Traits-TheIntegrator.799.mcz
Expand Down

This file was deleted.

Original file line number Diff line number Diff line change
@@ -0,0 +1,15 @@
update50153
"self new update50153"
self withUpdateLog: '15890 some cleaning
https://pharo.fogbugz.com/f/cases/15890
15072 Senders and implementors do not work when one parameter is a string containing :
https://pharo.fogbugz.com/f/cases/15072
15899 Remove destructive example
https://pharo.fogbugz.com/f/cases/15899
15897 Load new Workspace from AlainPlantec/WorkspaceRevisited
https://pharo.fogbugz.com/f/cases/15897'.
self loadTogether: self script50153 merge: false.
self flushCaches.
Original file line number Diff line number Diff line change
@@ -1,12 +1,12 @@
commentForCurrentUpdate
^ '7008 Shared Pools to be treated like dictionaries still necessary?
https://pharo.fogbugz.com/f/cases/7008
^ '15890 some cleaning
https://pharo.fogbugz.com/f/cases/15890
15886 Find class dialog from a scope nautilus window shows all classes
https://pharo.fogbugz.com/f/cases/15886
15072 Senders and implementors do not work when one parameter is a string containing :
https://pharo.fogbugz.com/f/cases/15072
15889 do not call asOrderedCollection on compiled methods
https://pharo.fogbugz.com/f/cases/15889
15899 Remove destructive example
https://pharo.fogbugz.com/f/cases/15899
15892 Cleanups: clean annotation handling + rename HookGenerator2
https://pharo.fogbugz.com/f/cases/15892'
15897 Load new Workspace from AlainPlantec/WorkspaceRevisited
https://pharo.fogbugz.com/f/cases/15897'

This file was deleted.

Original file line number Diff line number Diff line change
@@ -1,3 +1,7 @@
selectedSelector
"Try to make a selector out of the current text selection"
^self selection string findSelector
| node |
node := RBParser parseFaultyExpression: self selection string.
node isMessage
ifTrue: [ ^ node selector ]
ifFalse: [ ^ node name ]
1 change: 1 addition & 0 deletions Tool-Workspace.package/RubWorkspaceBar.class/README.md
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
A bottom bar to change the editing mode, switch with/without line numbers and switch wrapping mode
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
key
^ #workspaceBar
5 changes: 5 additions & 0 deletions Tool-Workspace.package/RubWorkspaceBar.class/definition.st
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
RubScrolledTextSideRuler subclass: #RubWorkspaceBar
instanceVariableNames: 'row wrappingPolicyMorph editingModeMorph lineNumbersDisplayMorph'
classVariableNames: ''
poolDictionaries: ''
category: 'Tool-Workspace'
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
backgroundColor
^ self paragraphProvider backgroundColor darker
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
fontToUse
^ RubAbstractTextArea lineNumbersFont
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
level
^ 1
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
textColor
^ self textArea lineNumbersTextColor muchDarker
Original file line number Diff line number Diff line change
@@ -0,0 +1,6 @@
updateContents
row ifNil: [ ^self ].
wrappingPolicyMorph contents: self wrappingPolicyLabel.
editingModeMorph contents: self editingModeLabel.
lineNumbersDisplayMorph contents: self lineNumbersDisplayLabel.
row bounds: self innerBounds
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
computedHeightFrom: aRectangle
^ row ifNil: [0] ifNotNil: [row height]
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
computedWidthFrom: aRectangle
^ aRectangle width
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
manageLayoutInBounds: aRectangle
| ret |
ret := super manageLayoutInBounds: aRectangle.
self updateContents.
^ ret
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
initialize
super initialize.
self side: #bottom.
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
chooseEditingMode: anEvent
self modeListMenu invokeAt: anEvent position in: self world.
self updateContents
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
editingModeLabel
^ self paragraphProvider editingMode label
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
editingModeLabelMorph
^ StringMorph
contents: self editingModeLabel
font: self fontToUse
Original file line number Diff line number Diff line change
@@ -0,0 +1,8 @@
modeListMenu
"Answer the menu to be presented to select an editing mode"

| menu |
menu := MenuMorph new.
menu add: 'Plain text' target: self selector: #switchToPlainTextMode.
menu add: 'Smalltalk scripting' target: self selector: #switchToSmalltalkScriptingMode.
^ menu
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
switchToPlainTextMode
self paragraphProvider beForPlainText
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
switchToSmalltalkScriptingMode
self paragraphProvider beForSmalltalkScripting
Original file line number Diff line number Diff line change
@@ -0,0 +1,6 @@
changeLineNumbersDisplay
self paragraphProvider lineNumbersRuler
ifNil: [ self paragraphProvider withLineNumbers ]
ifNotNil: [ self paragraphProvider withoutLineNumbers ].
self paragraphProvider manageLayout.
self updateContents
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
lineNumbersDisplayLabel
^ self paragraphProvider lineNumbersRuler
ifNil: [ '+L' ]
ifNotNil: [ 'L' ]
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
lineNumbersDisplayLabelMorph
^ StringMorph
contents: self lineNumbersDisplayLabel
font: self fontToUse
Original file line number Diff line number Diff line change
@@ -0,0 +1,6 @@
changeWrappingPolicy
self paragraphProvider wrapped
ifTrue: [ self paragraphProvider beNotWrapped ]
ifFalse: [ self paragraphProvider beWrapped ].
self updateContents.
self paragraphProvider changed
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
wrappingPolicyLabel
^ self paragraphProvider wrapped
ifTrue: [ 'W' ]
ifFalse: [ 'NW' ]
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
wrappingPolicyLabelMorph
^ StringMorph
contents: self wrappingPolicyLabel
font: self fontToUse
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
spacer: anInteger
^ Morph new
borderWidth: 0;
color: Color transparent;
extent: anInteger@3

0 comments on commit fef56f2

Please sign in to comment.