The Trunk: MorphicExtras-mt.157.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
1 message Options
Reply | Threaded
Open this post in threaded view
|

The Trunk: MorphicExtras-mt.157.mcz

commits-2
Marcel Taeumel uploaded a new version of MorphicExtras to project The Trunk:
http://source.squeak.org/trunk/MorphicExtras-mt.157.mcz

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

Name: MorphicExtras-mt.157
Author: mt
Time: 4 March 2015, 9:10:14.479 pm
UUID: 0b806ef9-9fe4-4a42-a854-bd1a7c18f358
Ancestors: MorphicExtras-mt.156

Reverted eToys-specific changes in AnimatedImageMorph but kept its working core in #step for displaying animated gifs.

=============== Diff against MorphicExtras-mt.156 ===============

Item was changed:
  ImageMorph subclass: #AnimatedImageMorph
+ instanceVariableNames: 'images delays stepTime nextTime imageIndex'
- instanceVariableNames: 'images delays stepTime nextTime imageIndex stepper'
  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 removed:
- ----- 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.
  ^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.
  ^reader forms size = 1
  ifTrue: [ ImageMorph new image: reader forms first ]
  ifFalse: [ self new fromReader: reader ]!

Item was added:
+ ----- 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]!

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')
- buttonLabel: 'open gif')
  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"!

Item was removed:
- ----- 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>>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 reset.!
- self step!

Item was changed:
  ----- Method: AnimatedImageMorph>>initialize (in category 'private') -----
  initialize
  nextTime := Time millisecondClockValue.
  imageIndex := 1.
  stepTime := 10.
- stepper :=true.
  super initialize!

Item was added:
+ ----- Method: AnimatedImageMorph>>reset (in category 'private') -----
+ reset
+
+ imageIndex := 0.
+ self image: (Form extent: images first extent depth: 32).
+ self step.!

Item was removed:
- ----- 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
+ | d form |
+ images isEmpty ifTrue: [^ self].
+
+ nextTime > Time millisecondClockValue
+ ifTrue: [^self].
+ " self changed."
+ imageIndex > 0 ifTrue: [
-     | 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@0 rule: (self isOpaque ifTrue: [Form paint] ifFalse: [Form erase])].
+ form := images at: (imageIndex := imageIndex \\ images size + 1).
+ form displayOn: self image at: 0@0 rule: Form paint.
+ self changed.
+ d := (delays at: imageIndex) ifNil: [0].
+ nextTime := Time millisecondClockValue + d
+ !
-         form displayOn: self image at: 0@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@0 rule: Form paint.
-     self changed.
-     delay := (delays at: imageIndex) ifNil: [0].
-     nextTime := Time millisecondClockValue +delay!

Item was changed:
  ----- Method: AnimatedImageMorph>>stepTime: (in category 'stepping and presenter') -----
  stepTime: anInteger
+ stepTime := anInteger!
- stepTime _ anInteger!

Item was removed:
- ----- Method: AnimatedImageMorph>>steppingString (in category 'stepping and presenter') -----
- steppingString
- ^ (stepper
- ifTrue: ['<on>']
- ifFalse: ['<off>']), 'stepping' translated!

Item was removed:
- ----- Method: AnimatedImageMorph>>toggleStepping (in category 'stepping and presenter') -----
- toggleStepping
- self wantsSteps
- ifTrue: [stepper := stepper not].
- stepper ifTrue:[self startStepping]
- ifFalse:[self stopStepping].
-
-     !