[squeak-dev] The Trunk: MorphicExtras-mt.156.mcz

Tobias Pape Das.Linux at gmx.de
Wed Mar 4 19:07:46 UTC 2015


Hi.

quick review.

On 04.03.2015, at 18:04, commits at source.squeak.org wrote:

> Marcel Taeumel uploaded a new version of MorphicExtras to project The Trunk:
> http://source.squeak.org/trunk/MorphicExtras-mt.156.mcz
> 
> ==================== Summary ====================
> 
> Name: MorphicExtras-mt.156
> Author: mt
> Time: 4 March 2015, 7:04:52.068 pm
> UUID: 1b149c50-aaf7-b043-86e1-ce80d88bc68b
> Ancestors: MorphicExtras-mt.155
> 
> Uses eToys' implementation of AnimatedImageMorph, which works fine with animated GIFs now.
> 
> =============== Diff against MorphicExtras-mt.155 ===============
> 
> Item was changed:
>  ImageMorph subclass: #AnimatedImageMorph
> + 	instanceVariableNames: 'images delays stepTime nextTime imageIndex stepper'
> - 	instanceVariableNames: 'images delays stepTime nextTime imageIndex formsAreDiffs'
>  	classVariableNames: ''
>  	poolDictionaries: ''
>  	category: 'MorphicExtras-AdditionalMorphs'!
> 
>  !AnimatedImageMorph commentStamp: '<historical>' prior: 0!
>  I am an ImageMorph that can hold more than one image. Each image has its own delay time.!
> 
> Item was added:
> + ----- Method: AnimatedImageMorph class>>additionsToViewerCategories (in category 'class initialization') -----
> + additionsToViewerCategories
> + 	"Answer a list of (<categoryName> <list of category specs>) pairs that characterize the phrases this kind of morph wishes to add to various Viewer categories."
> + 	^ #(
> + 
> + 	(#'graphics' 
> + 		(
> + 		(slot isGifPlaying 'Whether the gif is playing' 
> + 			Boolean readWrite Player getGifPlaying Player setGifPlaying:)
> + 		(slot opaque 'Whether the gif opaque' 
> + 			Boolean readWrite Player getOpaque Player setOpaque:) 
> + 		
> + 	))
> + 
> + )
> + !
> 
> Item was changed:
>  ----- Method: AnimatedImageMorph class>>fromGIFFileNamed: (in category 'instance creation') -----
>  fromGIFFileNamed: fileName
>  	| reader |
> + 	reader _ AnimatedGIFReadWriter formsFromFileNamed: fileName.
> - 	reader := AnimatedGIFReadWriter formsFromFileNamed: fileName.

Should be changed back.

>  	^reader forms size = 1
>  		ifTrue: [ ImageMorph new image: reader forms first ]
>  		ifFalse: [ self new fromReader: reader ]!
> 
> Item was changed:
>  ----- Method: AnimatedImageMorph class>>fromStream: (in category 'instance creation') -----
>  fromStream: aStream
>  	| reader |
> + 	reader _ AnimatedGIFReadWriter formsFromStream: aStream.
> - 	reader := AnimatedGIFReadWriter formsFromStream: aStream.

Should be changed back.

>  	^reader forms size = 1
>  		ifTrue: [ ImageMorph new image: reader forms first ]
>  		ifFalse: [ self new fromReader: reader ]!
> 
> Item was removed:
> - ----- Method: AnimatedImageMorph class>>initialize (in category 'class initialization') -----
> - initialize
> - 	"register the receiver in the global registries"
> - 	self environment
> - 		at: #FileList
> - 		ifPresent: [:cl | cl registerFileReader: self]!

This remove should be reverted.


> 
> Item was changed:
>  ----- Method: AnimatedImageMorph class>>serviceOpenGIFInWindow (in category 'fileIn/Out') -----
>  serviceOpenGIFInWindow
>  	"Answer a service for opening a gif graphic in a window"
>  	^ (SimpleServiceEntry
>  		provider: self
>  		label: 'open the graphic as a morph'
>  		selector: #openGIFInWindow:
>  		description: 'open a GIF graphic file as a morph'
> + 		buttonLabel: 'open gif')
> - 		buttonLabel: 'open')
>  		argumentGetter: [:fileList | fileList readOnlyStream]!
> 
> Item was changed:
>  ----- Method: AnimatedImageMorph class>>services (in category 'fileIn/Out') -----
>  services
>  	^ Array
>  		with: self serviceOpenGIFInWindow
>  		"with: Form serviceImageImports"
> + 		"with: Form serviceImageAsBackground"!
> - 		with: Form serviceImageAsBackground!

While virtually no one uses services, I think this can stay  without the comment

> 
> Item was added:
> + ----- Method: AnimatedImageMorph>>addCustomMenuItems:hand: (in category 'stepping and presenter') -----
> + addCustomMenuItems: aMenu hand: aHand
> + 	super addCustomMenuItems: aMenu hand: aHand.
> + 	aMenu addUpdating: #steppingString action: #toggleStepping!
> 
> Item was removed:
> - ----- Method: AnimatedImageMorph>>formsAreDiffs (in category 'accessing') -----
> - formsAreDiffs
> - 	"Should the forms be drawn on top of each other to produce the frame?"
> - 	^ formsAreDiffs ifNil: [false]!
> 
> Item was removed:
> - ----- Method: AnimatedImageMorph>>formsAreDiffs: (in category 'accessing') -----
> - formsAreDiffs: aBoolean
> - 
> - 	formsAreDiffs := aBoolean.
> - 	self reset.!
> 
> Item was added:
> + ----- Method: AnimatedImageMorph>>fromArray: (in category 'private') -----
> + fromArray: reader 
> + 	images := reader first.
> + 	delays := reader second.
> + 	imageIndex := 0.
> + 	self
> + 		image: (Form extent: images first extent depth: 32).
> + 	self isOpaque: true.
> + 	self step!
> 
> Item was changed:
>  ----- Method: AnimatedImageMorph>>fromReader: (in category 'private') -----
> + fromReader: reader 
> - fromReader: reader
> - 
>  	images := reader forms.
>  	delays := reader delays.
> + 	imageIndex := 0.
> + 	self
> + 		image: (Form extent: images first extent depth: 32).
> + 	self isOpaque: true.
> + 	self step!
> - 	self reset.!
> 
> Item was changed:
>  ----- Method: AnimatedImageMorph>>initialize (in category 'private') -----
>  initialize
>  	nextTime := Time millisecondClockValue.
>  	imageIndex := 1.
>  	stepTime := 10.
> + 	stepper :=true.
>  	super initialize!
> 
> Item was removed:
> - ----- Method: AnimatedImageMorph>>reset (in category 'private') -----
> - reset
> - 
> - 	imageIndex := 0.
> - 	self image: (Form extent: images first extent depth: 32).
> - 	self step.!
> 
> Item was added:
> + ----- Method: AnimatedImageMorph>>setStepping: (in category 'stepping and presenter') -----
> + setStepping: aBoolean
> + self wantsSteps ifFalse:[^false].
> + stepper := aBoolean.
> + stepper ifTrue:[self startStepping]
> + 				ifFalse:[self stopStepping].
> + 	
> +     !
> 
> Item was changed:
>  ----- Method: AnimatedImageMorph>>step (in category 'stepping and presenter') -----
>  step
> +     | form delay |
> + 	stepper ifFalse:[ self stopStepping].
> +     images isEmpty
> +         ifTrue: [^ self].
> +     nextTime > Time millisecondClockValue
> +         ifTrue: [^self].
> +     imageIndex > 0 ifTrue: [
> + 		form := images at: imageIndex.
> +         form displayOn: self image at: 0 at 0 rule: 
> + 															((self isOpaque) ifTrue:[Form paint] ifFalse:[Form erase]).
> +     ].
> +     imageIndex _ imageIndex \\ images size + 1.
> +     form := images at: imageIndex.
> +     form displayOn: self image at: 0 at 0 rule: Form paint.
> +     self changed.
> +     delay := (delays at: imageIndex) ifNil: [0].
> +     nextTime := Time millisecondClockValue +delay!
> - 	| d next |
> - 	images isEmpty ifTrue: [^ self].
> - 		
> - 	nextTime > Time millisecondClockValue
> - 		ifTrue: [^self].
> - 	self changed .
> - 	next := images at: (imageIndex := imageIndex \\ images size + 1).
> - 	self formsAreDiffs
> - 		ifFalse: [self image: next]
> - 		ifTrue: [self image getCanvas translucentImage: next at: next offset]..
> - 	self changed . 
> - 	d := (delays at: imageIndex) ifNil: [0].
> - 	nextTime := Time millisecondClockValue + d
> - !
> 
> Item was changed:
>  ----- Method: AnimatedImageMorph>>stepTime: (in category 'stepping and presenter') -----
>  stepTime: anInteger
> + 	stepTime _ anInteger!
> - 	stepTime := anInteger!

Should be changed back.


> Item was added:
> + ----- Method: AnimatedImageMorph>>steppingString (in category 'stepping and presenter') -----
> + steppingString
> + 	^ (stepper
> + 		ifTrue: ['<on>']
> + 		ifFalse: ['<off>']), 'stepping' translated!
> 
> Item was added:
> + ----- Method: AnimatedImageMorph>>toggleStepping (in category 'stepping and presenter') -----
> + toggleStepping
> + 	self wantsSteps
> + 		ifTrue: [stepper := stepper not].
> + 	stepper ifTrue:[self startStepping]
> + 				ifFalse:[self stopStepping].
> + 	
> +     !
> 
> 



More information about the Squeak-dev mailing list