[Pkg] The Trunk: EToys-nice.107.mcz

commits at source.squeak.org commits at source.squeak.org
Fri Sep 6 20:47:33 UTC 2013


Nicolas Cellier uploaded a new version of EToys to project The Trunk:
http://source.squeak.org/trunk/EToys-nice.107.mcz

==================== Summary ====================

Name: EToys-nice.107
Author: nice
Time: 6 September 2013, 10:45:39.884 pm
UUID: d34e55cf-a15b-4d42-a1e6-215ca864d07e
Ancestors: EToys-nice.106

Better ask the UIManager to inform: rather than Utilities.
Use Character null now that it exists.

=============== Diff against EToys-nice.106 ===============

Item was changed:
  ----- Method: EToyProjectRenamerMorph>>validateTheProjectName (in category 'as yet unclassified') -----
  validateTheProjectName
  
  	| proposed |
  
  	proposed := (namedFields at: 'projectname') contents string withBlanksTrimmed.
  	proposed isEmpty ifTrue: [
  		self inform: 'I do need a name for the project' translated.
  		^false
  	].
  	proposed size > 24 ifTrue: [
  		self inform: 'Please make the name 24 characters or less' translated.
  		^false
  	].
  	(Project isBadNameForStoring: proposed) ifTrue: [
  		self inform: 'Please remove any funny characters from the name' translated.
  		^false
  	].
  	proposed = theProject name ifTrue: [^true].
  	(ChangesOrganizer changeSetNamed: proposed) ifNotNil: [
+ 		UIManager default inform: 'Sorry that name is already used' translated.
- 		Utilities inform: 'Sorry that name is already used' translated.
  		^false
  	].
  	^true!

Item was changed:
  ----- Method: SyntaxMorph>>splitAtCapsAndDownshifted: (in category 'alans styles') -----
  splitAtCapsAndDownshifted: aString
  
  	self flag: #yoCharCases.
  
  	^String streamContents: [ :strm |
  		aString do: [ :each | 
  			each = $: ifFalse: [
+ 				each isUppercase ifTrue: [strm nextPut: Character null;  
+ 						 	nextPut: Character null; 
+ 						 	nextPut: Character null; 
- 				each isUppercase ifTrue: [strm nextPut: (Character value: 0);  
- 						 	nextPut: (Character value: 0); 
- 						 	nextPut: (Character value: 0); 
  							nextPut: each asLowercase]
  					ifFalse: [strm nextPut: each]
  			].
  		]
  	].!

Item was changed:
  ----- Method: SyntaxUpdatingStringMorph>>drawOn: (in category 'drawing') -----
  drawOn: aCanvas
  
  	| tempForm strm where chars wid spaceWidth putLigature topOfLigature sizeOfLigature colorOfLigature dots charZero canvas f |
  
  	tempForm := Form extent: self extent depth: aCanvas depth.
  	canvas := tempForm getCanvas.
  	f := self fontToUse.
  	spaceWidth := f widthOf: Character space.
  	strm := ReadStream on: contents.
+ 	charZero := Character null.	"a marker for center dot ·"
- 	charZero := Character value: 0.	"a marker for center dot ·"
  	where := 0 at 0.
  	topOfLigature := self height // 2 - 1.
  	sizeOfLigature := (spaceWidth-2)@(spaceWidth-2).
  	colorOfLigature := Color black alpha: 0.45	"veryLightGray".
  	dots := OrderedCollection new.
  	putLigature := [
  		dots add: ((where x + 1) @ topOfLigature extent: sizeOfLigature).
  		where := where + (spaceWidth at 0)].
  	strm peek = charZero ifTrue: [
  		strm next.
  		putLigature value].
  	[strm peek = charZero] whileTrue: [strm next].
  	[strm atEnd] whileFalse: [
  		chars := strm upTo: charZero.
  		wid := f widthOfString: chars.
  		canvas drawString: chars at: where.
  		where := where + (wid at 0).
  		strm atEnd ifFalse: [putLigature value.
  			[strm peek = charZero] whileTrue: [strm next]].
  	].
  	aCanvas paintImage: tempForm at: self topLeft.
  	dots do: [ :each |
  		aCanvas 
  			fillRectangle: (each translateBy: self topLeft) 
  			fillStyle: colorOfLigature.
  	].
  !



More information about the Packages mailing list