'10/24/99 8:57:28 am'! ApplicationModel subclass: #NishisTrackModel instanceVariableNames: 'trackingImages ' classVariableNames: '' poolDictionaries: '' category: 'SmalltalkLecture-Track'! View subclass: #NishisTrackView instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'SmalltalkLecture-Track'! ControllerWithMenu subclass: #NishisTrackController instanceVariableNames: 'trackState trackProcesses ' classVariableNames: '' poolDictionaries: '' category: 'SmalltalkLecture-Track'! ApplicationModel subclass: #NishisTrackModel instanceVariableNames: 'trackingImages ' classVariableNames: '' poolDictionaries: '' category: 'SmalltalkLecture-Track'! !NishisTrackModel methodsFor: 'accessing'! trackingImages trackingImages isNil ifTrue: [trackingImages := OrderedCollection new]. ^trackingImages! ! !NishisTrackModel methodsFor: 'adding'! addImage: anImage self trackingImages add: anImage! ! !NishisTrackModel methodsFor: 'interface opening'! createTrackView ^NishisTrackView model: self! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! NishisTrackModel class instanceVariableNames: ''! !NishisTrackModel class methodsFor: 'copyright'! copyright ^'Copyleft 1999 NISHIHARA Satoshi.'! system ^'Goodies'! version ^'001'! ! !NishisTrackModel class methodsFor: 'interface specs'! windowSpec "UIPainter new openOnClass: self andSelector: #windowSpec" ^#(#FullSpec #window: #(#WindowSpec #label: 'Track' #min: #(#Point 180 130 ) #bounds: #(#Rectangle 100 100 300 250 ) ) #component: #(#SpecCollection #collection: #( #(#ArbitraryComponentSpec #layout: #(#LayoutFrame 1 0 1 0 -1 1 -1 1 ) #name: #trackView #component: #createTrackView ) ) ) )! ! !NishisTrackModel class methodsFor: 'saving'! save "NishisTrackModel save." | encodingName fileName classCollection aStream | encodingName := #default. fileName := 'NishisTrackMVC.st'. classCollection := self saveClasses. aStream := (fileName asFilename withEncoding: encodingName) writeStream. [Cursor write showWhile: [| timeStamp | timeStamp := Date today shortPrintString , ' ' , Time now shortPrintString. aStream cr. aStream nextChunkPut: timeStamp printString. aStream cr; cr. (self comment isNil or: [self comment isEmpty]) ifFalse: [aStream nextChunkPut: self comment printString. aStream cr; cr]. classCollection do: [:aClass | aStream nextChunkPut: aClass definition. aStream cr; cr]. classCollection do: [:aClass | | sourceCodeStream | aStream nextPut: Character newPage. aStream cr. sourceCodeStream := SourceCodeStream on: aStream. aClass fileOutSourceOn: sourceCodeStream. aStream cr]]] valueNowOrOnUnwindDo: [aStream close]. ^classCollection! saveClasses "NishisTrackModel saveClasses." | patternCollection classCollection | patternCollection := #('*NishisTrack*'). classCollection := Smalltalk organization superclassOrder: self category. classCollection := classCollection select: [:aClass | | string something | string := aClass name asString. something := patternCollection detect: [:it | it match: string] ifNone: [nil]. something notNil]. ^classCollection! ! !NishisTrackModel class methodsFor: 'examples'! example "NishisTrackModel example." | trackModel | trackModel := NishisTrackModel new. trackModel open. ^trackModel! example1 "NishisTrackModel example1." | trackModel | trackModel := NishisTrackModel new. trackModel addImage: Image fromUser. trackModel open. ^trackModel! example2 "NishisTrackModel example2." | trackModel | trackModel := NishisTrackModel new. 3 timesRepeat: [trackModel addImage: Image fromUser]. trackModel open. ^trackModel! ! View subclass: #NishisTrackView instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'SmalltalkLecture-Track'! !NishisTrackView methodsFor: 'bounds accessing'! bounds: newBounds self controller reset! ! !NishisTrackView methodsFor: 'controller accessing'! defaultControllerClass ^NishisTrackController! ! !NishisTrackView methodsFor: 'displaying'! displayOn: graphicsContext self isOpen ifFalse: [^self]. graphicsContext paint: self backgroundColor. graphicsContext displayRectangle: graphicsContext clippingBounds. self controller trackState ifFalse: [| composedText displayPoint | composedText := 'Click red button to animate' asComposedText. displayPoint := self bounds center - composedText bounds center. graphicsContext paint: self foregroundColor. composedText displayOn: graphicsContext at: displayPoint]! ! !NishisTrackView methodsFor: 'tracking'! track: anImage delta: deltaPoint tick: delayMilliseconds | graphicsContext aPoint aVector aPixmap pixmapContext | self isOpen ifFalse: [^self]. graphicsContext := self graphicsContext. aPoint := self bounds center - anImage bounds center. aVector := deltaPoint. aPixmap := Pixmap extent: anImage extent + (deltaPoint abs * 2). pixmapContext := aPixmap graphicsContext. pixmapContext paint: self backgroundColor. pixmapContext displayRectangle: aPixmap bounds. pixmapContext copyArea: anImage bounds from: anImage asRetainedMedium graphicsContext sourceOffset: 0 @ 0 destinationOffset: deltaPoint abs asPoint. [self controller trackState and: [self isOpen]] whileTrue: [aPoint := aPoint + aVector. (aPoint x < 0 or: [aPoint x + anImage bounds width > self bounds width]) ifTrue: [aVector := aVector * (-1 @ 1)]. (aPoint y < 0 or: [aPoint y + anImage bounds height > self bounds height]) ifTrue: [aVector := aVector * (1 @ -1)]. graphicsContext copyArea: aPixmap bounds from: pixmapContext sourceOffset: 0 @ 0 destinationOffset: aPoint - deltaPoint abs asPoint. (Delay forMilliseconds: delayMilliseconds) wait]. aPixmap close! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! NishisTrackView class instanceVariableNames: ''! !NishisTrackView class methodsFor: 'copyright'! copyright ^'Copyleft 1999 NISHIHARA Satoshi.'! system ^'Goodies'! version ^'001'! ! ControllerWithMenu subclass: #NishisTrackController instanceVariableNames: 'trackState trackProcesses ' classVariableNames: '' poolDictionaries: '' category: 'SmalltalkLecture-Track'! !NishisTrackController methodsFor: 'initialize-release'! initialize super initialize. trackState := false! release self terminate. super release! reset self trackState ifTrue: [self terminate. self resume]! resume | aRandom | trackState := true. self view displayOn: self view graphicsContext. aRandom := Random new. self model trackingImages do: [:anImage | | deltaPoint delayMilliseconds aProcess | deltaPoint := 2 + (aRandom next * 2) rounded @ (2 + (aRandom next * 2) rounded). aRandom next > 0.5 ifTrue: [deltaPoint := deltaPoint * (-1 @ 1)]. aRandom next > 0.5 ifTrue: [deltaPoint := deltaPoint * (1 @ -1)]. delayMilliseconds := 10 + (aRandom next * 10) rounded. aProcess := [self view track: anImage delta: deltaPoint tick: delayMilliseconds] newProcess. trackProcesses isNil ifTrue: [trackProcesses := OrderedCollection new]. trackProcesses add: aProcess. aProcess priority: Processor activeProcess priority - 0. aProcess resume]! terminate trackState := false. trackProcesses notNil ifTrue: [trackProcesses do: [:aProcess | aProcess terminate]]. trackProcesses := nil. self view displayOn: self view graphicsContext! ! !NishisTrackController methodsFor: 'accessing'! trackState ^trackState = true! trackState: aBoolean trackState := aBoolean = true! ! !NishisTrackController methodsFor: 'control defaults'! redButtonActivity self trackState: self trackState not. self trackState ifTrue: [self resume] ifFalse: [self terminate]. self sensor waitNoButton! yellowButtonActivity | index image | index := (Menu labelArray: #('add')) startUp. (index isNil or: [index = 0]) ifTrue: [^self]. image := Image fromUser. self sensor shiftDown ifTrue: [^self]. self model addImage: image. self reset! ! !NishisTrackController methodsFor: 'event driven'! redButtonPressedEvent: event self redButtonActivity. ^nil! yellowButtonPressedEvent: event self yellowButtonActivity. ^nil! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! NishisTrackController class instanceVariableNames: ''! !NishisTrackController class methodsFor: 'copyright'! copyright ^'Copyleft 1999 NISHIHARA Satoshi.'! system ^'Goodies'! version ^'001'! !