[squeak-dev] Re: Edgar from the Ostracism Re: Squeak 4.1 release candidate 2

Edgar J. De Cleene edgardec2005 at gmail.com
Fri Apr 9 11:03:28 UTC 2010


> On 4/9/10 6:57 AM, "Hannes Hirzel" <hannes.hirzel at gmail.com> wrote:
> 
>> Thank you for the description of the process of getting old projects
>> into Squeak 4.1. In particular I would like to see the piano roll
>> demonstration project (playing of MIDI files) working in 4.1.
>> This was always a very nice demo of the possibilities of Squeak.
>> 
>> Do you have a link to the project file? Or do we just need to dig it
>> out from an earlier release?
>> 
>> Hannes
> 
> 
> This is on FunSqueak image, ready to run.
> And the first converted .pr with old games in SqueakMap no work in 4.1 , but
> work at the time I made it.
> So I need see the changes in the image.
> 
> Later today I send some more about.
> 
> Edgar

More feedback for the old midi project.
I put into 
http://map1.squeakfoundation.org/account/package/717d8f2c-351d-4552-a4b7-311
f2e428629

More About Sound 

Some time ago.

Now do not load into last 4.1
I found someone rip ComponentLikeModel, SL3dot11 found and load from server.
But at some point SystemWindowButton was introduced to system later I do the
project and later I start SL3dot11 , so no luck to this time.

I refused to do new versions of all each time any change the game rules.
As I said, no plans, no directions ,no coordination.
If only have time for feed PharoCore with all needed for load old
projects....


Edgar

-------------- next part --------------
'From FunSqueak3.10alpha of 19 November 2007 [latest update: #1] on 4 March 2010 at 11:22:39 am'!
MorphicModel subclass: #ComponentLikeModel
	instanceVariableNames: 'pinSpecs'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Morphic-Components'!

!ComponentLikeModel methodsFor: 'components' stamp: 'di 5/1/1998 16:14'!
addPinFromSpec: pinSpec
	| pin |
	pin _ PinMorph new component: self pinSpec: pinSpec.
	self addMorph: pin.
	pin placeFromSpec.
	^ pin! !

!ComponentLikeModel methodsFor: 'components' stamp: 'di 5/2/1998 15:07'!
deleteComponent
	model removeDependent: self.
	self pinsDo: [:pin | pin delete].
	^ super delete! !

!ComponentLikeModel methodsFor: 'components' stamp: 'di 5/5/1998 00:57'!
initComponentIn: aLayout
	model _ aLayout model.
	self nameMeIn: aLayout.
	self color: Color lightCyan.
	self initPinSpecs.
	self initFromPinSpecs.
	self showPins.
	model addDependent: self! !

!ComponentLikeModel methodsFor: 'components' stamp: 'di 5/1/1998 16:31'!
initFromPinSpecs
	"no-op for default"! !

!ComponentLikeModel methodsFor: 'components' stamp: 'di 5/3/1998 20:11'!
initPinSpecs
	"no-op for default"
	pinSpecs _ Array new.
! !

!ComponentLikeModel methodsFor: 'components' stamp: 'di 4/26/1998 10:40'!
nameMeIn: aWorld
	| stem otherNames i partName className |
	className _ self class name.
	stem _ className.
	(stem size > 5 and: [stem endsWith: 'Morph'])
		ifTrue: [stem _ stem copyFrom: 1 to: stem size - 5].
	stem _ stem first asLowercase asString , stem allButFirst.
	otherNames _ Set newFrom: aWorld allKnownNames.
	i _ 1.
	[otherNames includes: (partName _ stem , i printString)]
		whileTrue: [i _ i + 1].
	self setNamePropertyTo: partName! !

!ComponentLikeModel methodsFor: 'components' stamp: 'di 5/3/1998 20:18'!
pinSpecs
	^ pinSpecs! !

!ComponentLikeModel methodsFor: 'components' stamp: 'di 5/2/1998 15:09'!
pinsDo: pinBlock
	self submorphsDo: [:m | (m isKindOf: PinMorph) ifTrue: [pinBlock value: m]]! !

!ComponentLikeModel methodsFor: 'components' stamp: 'di 5/3/1998 09:26'!
renameMe
	| otherNames newName |
	otherNames _ Set newFrom: self pasteUpMorph allKnownNames.
	newName _ FillInTheBlank request: 'Please give this new a name'
						initialAnswer: self knownName.
	newName isEmpty ifTrue: [^ nil].
	(otherNames includes: newName) ifTrue:
			[self inform: 'Sorry, that name is already used'. ^ nil].
	self setNamePropertyTo: newName! !

!ComponentLikeModel methodsFor: 'components' stamp: 'di 4/29/1998 15:16'!
showPins
	"Make up sensitized pinMorphs for each of my interface variables"
	self pinSpecs do: [:pinSpec | self addPinFromSpec: pinSpec]! !


!ComponentLikeModel methodsFor: 'dropping/grabbing' stamp: 'ar 10/5/2000 20:03'!
justDroppedInto: aMorph event: anEvent
	| theModel |
	theModel _ aMorph modelOrNil.
	((aMorph isKindOf: ComponentLayout) 
		and: [theModel isKindOf: Component]) ifFalse:
		["Disconnect prior to removal by move"
		(theModel isKindOf: Component) ifTrue: [self unwire.  model _ nil].
		^ super justDroppedInto: aMorph event: anEvent].
	theModel == model ifTrue: [^ self  "Presumably just a move"].
	self initComponentIn: aMorph.
	super justDroppedInto: aMorph event: anEvent! !


!ComponentLikeModel methodsFor: 'geometry' stamp: 'di 4/29/1998 09:49'!
extent: newExtent
	super extent: newExtent.
	self submorphsDo: [:m | (m isKindOf: PinMorph) ifTrue: [m placeFromSpec]]! !


!ComponentLikeModel methodsFor: 'initialization' stamp: 'di 5/3/1998 09:24'!
duplicate: newGuy from: oldGuy
	"oldGuy has just been duplicated and will stay in this world.  Make sure all the ComponentLikeModel requirements are carried out for the copy.  Ask user to rename it.  "

	newGuy installModelIn: oldGuy pasteUpMorph.
	newGuy copySlotMethodsFrom: oldGuy slotName.! !


!ComponentLikeModel methodsFor: 'naming' stamp: 'dgd 2/21/2003 23:01'!
choosePartName
	"When I am renamed, get a slot, make default methods, move any existing methods."

	| old |
	(self pasteUpMorph model isKindOf: Component) 
		ifTrue: 
			[self knownName ifNil: [^self nameMeIn: self pasteUpMorph]
				ifNotNil: [^self renameMe]].
	old := slotName.
	super choosePartName.
	slotName ifNil: [^self].	"user chose bad slot name"
	self model: self world model slotName: slotName.
	old isNil 
		ifTrue: [self compilePropagationMethods]
		ifFalse: [self copySlotMethodsFrom: old]
	"old ones not erased!!"! !


!ComponentLikeModel methodsFor: 'submorphs-add/remove' stamp: 'rbb 2/18/2005 13:32'!
delete
	"Delete the receiver.  Possibly put up confirming dialog.  Abort if user changes mind"

	(model isKindOf: Component) ifTrue: [^self deleteComponent].
	(model isMorphicModel) ifFalse: [^super delete].
	slotName ifNotNil: 
			[(self confirm: 'Shall I remove the slot ' , slotName 
						, '
	along with all associated methods?') 
				ifTrue: 
					[(model class selectors select: [:s | s beginsWith: slotName]) 
						do: [:s | model class removeSelector: s].
					(model class instVarNames includes: slotName) 
						ifTrue: [model class removeInstVarName: slotName]]
				ifFalse: 
					[(self 
						confirm: '...but should I at least dismiss this morph?
	[choose no to leave everything unchanged]') 
							ifFalse: [^self]]].
	super delete! !
-------------- next part --------------
'From Squeak4.1beta of 8 April 2010 [latest update: #9924] on 9 April 2010 at 7:42:30 am'!
IconicButton subclass: #SystemWindowButton
	instanceVariableNames: 'dimmed dimmedForm highlightedForm'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Morphic-Windows'!

!SystemWindowButton methodsFor: 'visual properties' stamp: 'bf 3/26/2010 09:03'!
dim
	dimmed := true.
	self restoreImage.! !

!SystemWindowButton methodsFor: 'visual properties' stamp: 'bf 3/26/2010 09:01'!
dimmedForm
	^ dimmedForm ifNil: [ dimmedForm := self firstSubmorph baseGraphic dimmed ]! !

!SystemWindowButton methodsFor: 'visual properties' stamp: 'ar 3/24/2010 20:08'!
handlesMouseOver: evt

	^ true
! !

!SystemWindowButton methodsFor: 'visual properties' stamp: 'mha 3/25/2010 23:35'!
highlight

	self firstSubmorph form: self highlightedForm
! !

!SystemWindowButton methodsFor: 'visual properties' stamp: 'bf 3/26/2010 09:01'!
highlightedForm
	^ highlightedForm ifNil: [ highlightedForm := self firstSubmorph baseGraphic lighter ]! !

!SystemWindowButton methodsFor: 'visual properties' stamp: 'ar 3/24/2010 20:07'!
mouseEnter: evt

	self highlight.
! !

!SystemWindowButton methodsFor: 'visual properties' stamp: 'ar 3/24/2010 20:07'!
mouseLeave: evt

	self restoreImage.
! !

!SystemWindowButton methodsFor: 'visual properties' stamp: 'bf 3/26/2010 10:23'!
restoreImage
	dimmed == true
		ifTrue: [self firstSubmorph form: self dimmedForm]
		ifFalse: [super restoreImage]
! !

!SystemWindowButton methodsFor: 'visual properties' stamp: 'bf 3/26/2010 09:14'!
undim
	dimmed := false..
	self isLocked ifFalse: [self restoreImage].! !

!SystemWindowButton methodsFor: 'visual properties' stamp: 'ar 3/24/2010 20:06'!
updateVisualState: evt

	(self containsPoint: evt cursorPoint)
		ifTrue: [self darken]
		ifFalse: [self restoreImage].
! !


!SystemWindowButton methodsFor: 'accessing' stamp: 'bf 3/26/2010 10:24'!
lock
	self firstSubmorph form: self dimmedForm.
	super lock! !

!SystemWindowButton methodsFor: 'accessing' stamp: 'laza 3/25/2010 14:19'!
unlock
	self restoreImage.
	super unlock! !


More information about the Squeak-dev mailing list