[squeak-dev] The Trunk: Morphic-cmm.510.mcz

commits at source.squeak.org commits at source.squeak.org
Sat Jan 8 21:58:28 UTC 2011


Chris Muller uploaded a new version of Morphic to project The Trunk:
http://source.squeak.org/trunk/Morphic-cmm.510.mcz

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

Name: Morphic-cmm.510
Author: cmm
Time: 8 January 2011, 3:57:18.364 pm
UUID: 9aba5fcb-53a6-4b03-aeae-827d7aea8857
Ancestors: Morphic-bp.509

*** Please load Graphics-cmm.174 first.  ***

- Merged Morphic-bp.509.
- Copied release notes to Welcome workspace.

=============== Diff against Morphic-MAD.507 ===============

Item was removed:
- Object subclass: #LayoutFrame
- 	instanceVariableNames: 'leftFraction leftOffset topFraction topOffset rightFraction rightOffset bottomFraction bottomOffset'
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'Morphic-Layouts'!
- 
- !LayoutFrame commentStamp: '<historical>' prior: 0!
- I define a frame for positioning some morph in a proportional layout.
- 
- Instance variables:
- 	leftFraction 
- 	topFraction 
- 	rightFraction 
- 	bottomFraction 	<Float>		The fractional distance (between 0 and 1) to place the morph in its owner's bounds
- 	leftOffset 
- 	topOffset 
- 	rightOffset 
- 	bottomOffset 	<Integer>	Fixed pixel offset to apply after fractional positioning (e.g., "10 pixel right of the center of the owner")!

Item was removed:
- ----- Method: LayoutFrame class>>classVersion (in category 'accessing') -----
- classVersion
- 	^1 "changed treatment of bottomOffset and rightOffset"
- !

Item was removed:
- ----- Method: LayoutFrame class>>fractions: (in category 'instance creation') -----
- fractions: fractionsOrNil
- 	^self fractions: fractionsOrNil offsets: nil!

Item was removed:
- ----- Method: LayoutFrame class>>fractions:offsets: (in category 'instance creation') -----
- fractions: fractionsOrNil offsets: offsetsOrNil
- 
- 	| fractions offsets |
- 
- 	fractions := fractionsOrNil ifNil: [0 at 0 extent: 0 at 0].
- 	offsets := offsetsOrNil ifNil: [0 at 0 extent: 0 at 0].
- 	^self new
- 		topFraction: fractions top offset: offsets top;
- 		leftFraction: fractions left offset: offsets left;
- 		bottomFraction: fractions bottom offset: offsets bottom;
- 		rightFraction: fractions right offset: offsets right
- !

Item was removed:
- ----- Method: LayoutFrame class>>offsets: (in category 'instance creation') -----
- offsets: offsetsOrNil
- 	^self fractions: nil offsets: offsetsOrNil!

Item was removed:
- ----- Method: LayoutFrame>>bottomFraction (in category 'accessing') -----
- bottomFraction
- 	^bottomFraction!

Item was removed:
- ----- Method: LayoutFrame>>bottomFraction: (in category 'accessing') -----
- bottomFraction: aNumber
- 	bottomFraction := aNumber!

Item was removed:
- ----- Method: LayoutFrame>>bottomFraction:offset: (in category 'accessing') -----
- bottomFraction: aNumber offset: anInteger
- 
- 	bottomFraction := aNumber.
- 	bottomOffset := anInteger!

Item was removed:
- ----- Method: LayoutFrame>>bottomOffset (in category 'accessing') -----
- bottomOffset
- 	^bottomOffset!

Item was removed:
- ----- Method: LayoutFrame>>bottomOffset: (in category 'accessing') -----
- bottomOffset: anInteger
- 	bottomOffset := anInteger!

Item was removed:
- ----- Method: LayoutFrame>>convertToCurrentVersion:refStream: (in category 'objects from disk') -----
- convertToCurrentVersion: varDict refStream: smartRefStrm
- 	| className oldClassVersion |
- 
- 	"JW 2/1/2001"
- 	"Since class version isn't passed in varDict, look it up through smartRefSrm."
- 	className := varDict at: #ClassName.
- 	oldClassVersion := (smartRefStrm structures at: className) first.
- 	(oldClassVersion = 0) ifTrue: [ self negateBottomRightOffsets ].
- 	^super convertToCurrentVersion: varDict refStream: smartRefStrm.
- !

Item was removed:
- ----- Method: LayoutFrame>>layout:in: (in category 'layout') -----
- layout: oldBounds in: newBounds
- 	"Return the proportional rectangle insetting the given bounds"
- 	| left right top bottom |
- 	leftFraction ifNotNil:[
- 		left := newBounds left + (newBounds width * leftFraction).
- 		leftOffset ifNotNil:[left := left + leftOffset]].
- 	rightFraction ifNotNil:[
- 		right := newBounds right - (newBounds width * (1.0 - rightFraction)).
- 		rightOffset ifNotNil:[right := right + rightOffset]].
- 	topFraction ifNotNil:[
- 		top := newBounds top + (newBounds height * topFraction).
- 		topOffset ifNotNil:[top := top + topOffset]].
- 	bottomFraction ifNotNil:[
- 		bottom := newBounds bottom - (newBounds height * (1.0 - bottomFraction)).
- 		bottomOffset ifNotNil:[bottom := bottom + bottomOffset]].
- 	left ifNil:[ right 
- 			ifNil:[left := oldBounds left. right := oldBounds right]
- 			ifNotNil:[left := right - oldBounds width]].
- 	right ifNil:[right := left + oldBounds width].
- 	top ifNil:[ bottom 
- 			ifNil:[top := oldBounds top. bottom := oldBounds bottom]
- 			ifNotNil:[top := bottom - oldBounds height]].
- 	bottom ifNil:[bottom := top + oldBounds height].
- 	^(left rounded @ top rounded) corner: (right rounded @ bottom rounded)!

Item was removed:
- ----- Method: LayoutFrame>>leftFraction (in category 'accessing') -----
- leftFraction
- 	^leftFraction!

Item was removed:
- ----- Method: LayoutFrame>>leftFraction: (in category 'accessing') -----
- leftFraction: aNumber
- 	leftFraction := aNumber!

Item was removed:
- ----- Method: LayoutFrame>>leftFraction:offset: (in category 'accessing') -----
- leftFraction: aNumber offset: anInteger
- 
- 	leftFraction := aNumber.
- 	leftOffset := anInteger!

Item was removed:
- ----- Method: LayoutFrame>>leftOffset (in category 'accessing') -----
- leftOffset
- 	^leftOffset!

Item was removed:
- ----- Method: LayoutFrame>>leftOffset: (in category 'accessing') -----
- leftOffset: anInteger
- 	leftOffset := anInteger!

Item was removed:
- ----- Method: LayoutFrame>>minExtentFrom: (in category 'layout') -----
- minExtentFrom: minExtent
- 	"Return the minimal extent the given bounds can be represented in"
- 	| width height left right top bottom |
- 	left := leftFraction ifNil: [0.0].
- 	right := rightFraction ifNil: [1.0].
- 	width := left = right
- 		ifTrue: [0]
- 		ifFalse: [minExtent x / (right - left)].
- 	top := topFraction ifNil: [0.0].
- 	bottom := bottomFraction ifNil: [1.0].
- 	height := bottom = top
- 		ifTrue: [0]
- 		ifFalse: [minExtent y / (bottom - top)].
- 	leftOffset ifNotNil:[width := width + leftOffset].
- 	rightOffset ifNotNil:[width := width + rightOffset].
- 	topOffset ifNotNil:[height := height + topOffset].
- 	bottomOffset ifNotNil:[height := height + bottomOffset].
- 	^width truncated @ height truncated!

Item was removed:
- ----- Method: LayoutFrame>>negateBottomRightOffsets (in category 'objects from disk') -----
- negateBottomRightOffsets
- 
- 	bottomOffset ifNotNil: [ bottomOffset := bottomOffset negated ].
- 	rightOffset ifNotNil: [ rightOffset := rightOffset negated ].
- 
- !

Item was removed:
- ----- Method: LayoutFrame>>rightFraction (in category 'accessing') -----
- rightFraction
- 	^rightFraction!

Item was removed:
- ----- Method: LayoutFrame>>rightFraction: (in category 'accessing') -----
- rightFraction: aNumber
- 	rightFraction := aNumber!

Item was removed:
- ----- Method: LayoutFrame>>rightFraction:offset: (in category 'accessing') -----
- rightFraction: aNumber offset: anInteger
- 
- 	rightFraction := aNumber.
- 	rightOffset := anInteger!

Item was removed:
- ----- Method: LayoutFrame>>rightOffset (in category 'accessing') -----
- rightOffset
- 	^rightOffset!

Item was removed:
- ----- Method: LayoutFrame>>rightOffset: (in category 'accessing') -----
- rightOffset: anInteger
- 	rightOffset := anInteger!

Item was removed:
- ----- Method: LayoutFrame>>topFraction (in category 'accessing') -----
- topFraction
- 	^topFraction!

Item was removed:
- ----- Method: LayoutFrame>>topFraction: (in category 'accessing') -----
- topFraction: aNumber
- 	topFraction := aNumber!

Item was removed:
- ----- Method: LayoutFrame>>topFraction:offset: (in category 'accessing') -----
- topFraction: aNumber offset: anInteger
- 
- 	topFraction := aNumber.
- 	topOffset := anInteger!

Item was removed:
- ----- Method: LayoutFrame>>topOffset (in category 'accessing') -----
- topOffset
- 	^topOffset!

Item was removed:
- ----- Method: LayoutFrame>>topOffset: (in category 'accessing') -----
- topOffset: anInteger
- 	topOffset := anInteger!

Item was changed:
  ----- Method: TheWorldMainDockingBar>>helpMenuOn: (in category 'submenu - help') -----
  helpMenuOn: aDockingBar
  
  	aDockingBar addItem: [ :it |
  		it	contents: 'Help' translated;
  			addSubMenu: [ :menu |  'Todo'.
  				menu addItem:[:item|
  					item
  						contents: 'Online Resources' translated;
  						help: 'Online resources for Squeak' translated;
  						target: self;
  						icon: MenuIcons smallHelpIcon;
  						selector: #showWelcomeText:label:in:;
  						arguments: {
  							#squeakOnlineResources. 
  							'Squeak Online Resources'. 
  							(140 at 140 extent: 560 at 360)
  						}].
  				menu addItem:[:item|
  					item
  						contents: 'Keyboard Shortcuts' translated;
  						help: 'Keyboard bindings used in Squeak' translated;
  						target: Utilities;
  						selector: #openCommandKeyHelp ].
  				menu addItem:[:item|
  					item
  						contents: 'Font Size Summary' translated;
  						help: 'Font size summary from the old Squeak 3.10.2 help menu.' translated;
  						target: TextStyle;
  						selector: #fontSizeSummary ].
  				menu addItem:[:item|
  					item
  						contents: 'Useful Expressions' translated;
  						help: 'Useful expressions from the old Squeak 3.10.2 help menu.' translated;
  						target: Utilities;
  						selector: #openStandardWorkspace ].
  				menu addLine.
  				menu addItem:[:item|
  					item
  						contents: 'Extending the system' translated;
  						help: 'Includes code snippets to evaluate for extending the system' translated;
  						target: self;
  						icon: MenuIcons smallHelpIcon;
  						selector: #showWelcomeText:label:in:;
  						arguments: {
  							#extendingTheSystem. 
  							'How to extend the system'. 
  							(140 at 140 extent: 560 at 360)
  						}].
  				menu addLine.
  				menu addItem:[:item|
  					item
  						contents: 'Welcome Workspaces' translated;
  						help: 'The Welcome Workspaces' translated;
  						addSubMenu:[:submenu| self welcomeWorkspacesOn: submenu]].
+ 				(Smalltalk classNamed: #HelpBrowser) ifNotNil: [:classHelpBrowser |
+ 					(Smalltalk classNamed: #TerseGuideHelp) ifNotNil: [:classTerseGuideHelp |
+ 						menu addLine.
+ 						menu addItem: [:item |
+ 							item
+ 								contents: 'Terse Guide to Squeak' translated;
+ 								help: 'concise information about language and environment' translated;
+ 								target: classHelpBrowser;
+ 								selector: #openOn:;
+ 								arguments: { classTerseGuideHelp }]].
- 				(Smalltalk classNamed: #HelpBrowser) ifNotNil: 
- 					[:classHelpBrowser|
  					menu addLine.
+ 					menu addItem: [:item |
- 					menu addItem: [ :item |
  						item
- 							contents: 'Terse Guide to Squeak' translated;
- 							help: 'concise information about language and environment' translated;
- 							target: classHelpBrowser;
- 							selector: #openOn:;
- 							arguments: { TerseGuideHelp } ].
- 					menu addLine.
- 					menu addItem: [ :item |
- 						item
  							contents: 'Help Browser' translated;
  							help: 'Integrated Help System' translated;
  							target: classHelpBrowser;
+ 							selector: #open]]]]!
- 							selector: #open ] ].
- 			]].
- 	!

Item was changed:
  ----- Method: TheWorldMainDockingBar>>welcomeToSqueak42 (in category 'submenu - help') -----
  welcomeToSqueak42
+ 	^'This is a list of the main achievements that went into the trunk image.
- 	^'Squeak 4.2
- 		Welcome to Squeak - a free, open Smalltalk system.
  
+ Ready for next-generation VM
+ A new virtual-machine, known as "Cog", is about to be released for Squeak.  It''s a complete rewrite from the ground-up, employing a Context-to-Stack mapping design onto which a JIT compiler for Intel-compatible hardware results in, roughly, a 3X, across-the-board performance improvement.  Specific Benchmarks vary much more widely (from 1x to 5x, with some people claiming 10x for specifics.
- Needs to be updated:
  
+ Significant class-library and IDE improvements
+ Many enhancements, fixes, documentation and performance improvements to the class-library and IDE tools.  A new number parser allows greater flexibility in the expression of numbers.  Finalization enhancements.
- Squeak 4.1 combines the license change occuring in the 4.0 release with the development work that has been going on while the relicensing process took place. Here are the highlights of the changes that resulted in Squeak 4.1:
  
+ An efficient window-resizing gesture allows Squeak windows to be quickly and easily manipulated, much like modern "tabletop" technologies.
- User Interface
- We have adapted the ''face lift'' look originally developed for Newspeak. For those of us who like colored windows (quite a few as it turns out) you can switch between uniform and colored windows in the ''Extras'' menu under ''Window Colors''.
  
+ There were also many enhancements to the internal text editor.
- The new menu bar makes Squeak much easier to discover than before. The process of transitioning from the world menu is not complete yet, there are still items that can only be accessed from the world menu (i.e., by clicking on the desktop). 
  
+ High-precision Clock
+ Squeak''s internal timer clock has been improved from millisecond to microsecond level precision. 
- The search field integrated in the menu bar allows for direct navigation to classes and methods - simply type in a partial class or method name and see what happens.
  
+ A Tidier image
+ A tidier image and code-base. Introduced a cleanUp protocol, removed the last direct users of CrLfFileStream, j3 support, SyntaxError, and more. Various packages and fonts can now be unloaded, if a smaller image is desired.
- A new set of inexpensive sub-pixel antialiased fonts derived from the DejaVu fonts (''Bitmap DejaVu'' in the font chooser) has been added. True type font support has been upgraded to operate directly on files on disk without the need to load the entire file into memory.
  
+ The last of the underscore assignments have been replaced with ANSI assignments.
- A new set of text editors has been added, which allowed us to decouple the Morphic and MVC implementations for improved modularity. Morphic now has regular blinking insertion point cursors instead of the (virtually invisible) static cursor previously.
  
+ There was also a significant refactoring and unification of Smalltalk and SmalltalkImage globals. 
- Compiler
- Squeak 4.1 includes the closure implementation from Cog as a prerequisite for full Cog adoption later. With this implementation Squeak finally has ''full'' closures, allowing classic recursive examples like the following to work:
  
+ stdio interface
+ Squeak now includes an API for accessing the operating system stdio (supported only on newer VM''s). 
- 	fac := [:n| n > 1 ifTrue:[n * (fac value: n-1)] ifFalse:[1]].
- 	fac value: 5.
  
+ Industrial command-line interface
+ The command-line interface has been improved to properly support relative-path qualification to the input script. 
- Support for literal ByteArray syntax has been added. Byte arrays can now be written as #[1 2 3] instead of #(1 2 3) asByteArray  avoiding the need for conversion.
  
+ Compatible with signature Squeak packages
+ This version of the Squeak platform is compatible with several unique packages like Croquet[*], Tweak, Seaside, muO, Magma, and more.  See "Extending the System" under the Help menu for more information.
- Selectors including minus are now parsed correctly, for example 3 <- 4 is now parsed as (3) <- (4) instead of (3) < (-4). White space is no longer allowed after an unary minus to denote a negative number literal.
  
+ Better Documentation
+ HelpSystem has been added to the core image to provide a light-weight framework for improved documentation. It can be accessed via Help>>Help Browser. Various bits of documentation, including how to load some important packages, has been added.
- Development
- Syntax highlighting, based on Shout, is now included in all Squeak tools by default. For workspaces, it can be explicitly disabled in the window menu (press the blue button; entry ''syntax highlighting'').
  
+ SUnit
+ All test cases now have an associated timeout after which the test is considered failed. The purpose of the timeout is to catch issues like infinite loops, unexpected user input etc. in automated test environments. Timeouts can be set on an individual test basis using the <timeout: seconds> tag or for an entire test case by implementing the #defaultTimeout method.
- Sources and changes files are no longer limited to 32MB max size. ExpandedSourceFileArray provides an implementation for source files of arbitrary length, based on the CompiledMethodTrailer changes.
  
+ Graphics
+ Reading PNG images has been significantly sped up for some common cases. The improvements are in 50-200x range and heavily affect interactive uses of such files.
- MessageTrace has been added, allowing senders and implementors to be viewed without opening new windows all the time.  It utilizes a new AlternatePluggableListMorphOfMany, which allows quick and easy customization of the list. A quick adoption of DependencyBrowser has been added allowing to browse dependencies between packages.
  
+ Stricter Rectangles assert screen coordinate orientation. Empty Rectangles no longer #intersect: anything. 
- Core Libraries
- Sets can now store nil just as any other collection. The collection hierachy has been refactored to have both Set and Dictionary a subclass of HashedCollection instead of having Dictionary a subclass of Set. Squeak now uses a better distributed scaledIdentityHash for identity sets and dictionaries.
  
+ Support for translucent fonts.
- StandardFilestream now performs read-buffering, dramatically speading up some operations like "Object compileAll" (2x improvement) as well as various other operations (scanning change lists etc).
  
+ MVC
+ Support for classic MVC has been restored to Squeak.  MVC provides a primitive, but ultra-high-speed user-interface based on classic model-view-controller architecture.
- A new traits implementation has been added. The implementation is significantly smaller and simpler than the old version and can be unloaded and reloaded without loss of information (i.e., traits flattened during unload are restored during traits reloading).
- 
- A new extensible number parser hierharchy has been introduced NumberParser and its subclasses provide support for parsing and building numbers from strings and streams.
- 
- A new general cleanup protocol has been added. The cleanUp protocol takes an optional argument to indicate whether we''re doing an aggressive cleanup (which involves deleting projects, change sets, and possibly other destructive actions) or a more gentle cleanup that''s only supposed to clean out transient caches.
- 
- SystemDictionary and SmalltalkImage have been refactored. Smalltalk is now an instance of SmalltalkImage, representing a facade for system-wide queries and actions. SmalltalkImage contains a global environment, an instance of SystemDictionary, which the environment used by classes. Thus, SmalltalkImage current == Smalltalk, Object environment == Smalltalk globals.
- 
- Modularity
- The following packages have been made reloadable: ReleaseBuilder, ScriptLoader, 311Deprecated, 39Deprecated, Universes, SMLoader, SMBase, Installer-Core, VersionNumberTests, VersionNumber, Services-Base, PreferenceBrowser, Nebraska, CollectionsTests, GraphicsTests, KernelTests, MorphicTests, MultilingualTests, NetworkTests, ToolsTests, TraitsTests, XML-Parser, Traits, SystemChangeNotification-Tests, FlexibleVocabularies, EToys, Protocols, Tests, SUnitGUI. To unload all of these, execute:
- 
- 	Smalltalk unloadAllKnownPackages.
  !!
+ ]style[(73 28 394 48 416 20 100 14 408 15 103 33 115 1 1 41 206 20 247 5 369 8 303 5 170),bu,,bu,,bu,,bu,,bu,,bu,,bu,,bu,,bu,,bu,,bu,,bu,!!' readStream nextChunkText!
- ]style[(11 54 21 228 14 920 251 2 8 309 376 2 11 206 529 2 14 302 197 1113 10 1 50 479)a2cblue;bFBitmap DejaVu Sans#14,c005005005bFBitmap DejaVu Sans#14,FBitmap DejaVu Sans#14bcred;,FBitmap DejaVu Sans#14,FBitmap DejaVu Sans#14bu,FBitmap DejaVu Sans#14,,FBitmap DejaVu Sans#14,FBitmap DejaVu Sans#14bu,FBitmap DejaVu Sans#14,,FBitmap DejaVu Sans#14,FBitmap DejaVu Sans#14bu,FBitmap DejaVu Sans#14,,FBitmap DejaVu Sans#14,FBitmap DejaVu Sans#14bu,FBitmap DejaVu Sans#14,f1,,bu,,FBitmap DejaVu Sans#14,!!' readStream nextChunkText!




More information about the Squeak-dev mailing list