[squeak-dev] The Trunk: MorphicExtras-nice.206.mcz

commits at source.squeak.org commits at source.squeak.org
Wed Apr 26 21:05:27 UTC 2017


Nicolas Cellier uploaded a new version of MorphicExtras to project The Trunk:
http://source.squeak.org/trunk/MorphicExtras-nice.206.mcz

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

Name: MorphicExtras-nice.206
Author: nice
Time: 26 April 2017, 11:05:07.705923 pm
UUID: d16239c9-452c-4885-93f9-0e7f7d6c59f8
Ancestors: MorphicExtras-ul.205

Classify a few 'as yet unclassified' methods

=============== Diff against MorphicExtras-ul.205 ===============

Item was changed:
+ ----- Method: AbstractMediaEventMorph>>endTime (in category 'accessing') -----
- ----- Method: AbstractMediaEventMorph>>endTime (in category 'as yet unclassified') -----
  endTime
  
  	^endTimeInScore ifNil: [startTimeInScore + 100]!

Item was changed:
+ ----- Method: DescriptionForPartsBin>>categories (in category 'accessing') -----
- ----- Method: DescriptionForPartsBin>>categories (in category 'access') -----
  categories
  	"Answer the categoryList of the receiver"
  
  	^ categoryList!

Item was changed:
+ ----- Method: DescriptionForPartsBin>>documentation (in category 'accessing') -----
- ----- Method: DescriptionForPartsBin>>documentation (in category 'access') -----
  documentation
  	"Answer the documentation of the receiver"
  
  	^ documentation!

Item was changed:
+ ----- Method: DescriptionForPartsBin>>formalName (in category 'accessing') -----
- ----- Method: DescriptionForPartsBin>>formalName (in category 'access') -----
  formalName
  	"Answer the formalName of the receiver"
  
  	^ formalName!

Item was changed:
+ ----- Method: DescriptionForPartsBin>>globalReceiverSymbol (in category 'accessing') -----
- ----- Method: DescriptionForPartsBin>>globalReceiverSymbol (in category 'access') -----
  globalReceiverSymbol
  	"Answer the globalReceiverSymbol of the receiver"
  
  	^ globalReceiverSymbol!

Item was changed:
+ ----- Method: DescriptionForPartsBin>>nativitySelector (in category 'accessing') -----
- ----- Method: DescriptionForPartsBin>>nativitySelector (in category 'access') -----
  nativitySelector
  	"Answer the nativitySelector of the receiver"
  
  	^ nativitySelector!

Item was changed:
+ ----- Method: DescriptionForPartsBin>>translatedCategories (in category 'accessing') -----
- ----- Method: DescriptionForPartsBin>>translatedCategories (in category 'access') -----
  translatedCategories
  	"Answer translated the categoryList of the receiver"
  	^ self categories
  		collect: [:each | each translated]!

Item was changed:
+ ----- Method: EnvelopeLineMorph>>vertices:borderWidth:borderColor: (in category 'initialization') -----
- ----- Method: EnvelopeLineMorph>>vertices:borderWidth:borderColor: (in category 'as yet unclassified') -----
  vertices: verts borderWidth: bw borderColor: bc 
  	super initialize.
  	vertices := verts.
  	
  	borderWidth := bw.
  	borderColor := bc.
  	closed := false.
  	arrows := #none.
  	self computeBounds!

Item was changed:
+ ----- Method: FancyMailComposition>>subject (in category 'accessing') -----
- ----- Method: FancyMailComposition>>subject (in category 'access') -----
  subject
  
  	^subject
  
  	!

Item was changed:
+ ----- Method: FancyMailComposition>>subject: (in category 'accessing') -----
- ----- Method: FancyMailComposition>>subject: (in category 'access') -----
  subject: x
  
  	subject := x.
  	self changed: #subject.
  	^true!

Item was changed:
+ ----- Method: FancyMailComposition>>to (in category 'accessing') -----
- ----- Method: FancyMailComposition>>to (in category 'access') -----
  to
  
  	^to!

Item was changed:
+ ----- Method: FancyMailComposition>>to: (in category 'accessing') -----
- ----- Method: FancyMailComposition>>to: (in category 'access') -----
  to: x
  
  	to := x.	
  	self changed: #to.
  	^true
  	!

Item was changed:
+ ----- Method: FlexMorph>>changeBorderColor: (in category 'menus') -----
- ----- Method: FlexMorph>>changeBorderColor: (in category 'as yet unclassified') -----
  changeBorderColor: evt
  	| aHand |
  	aHand := evt ifNotNil: [evt hand] ifNil: [self primaryHand].
  	self changeColorTarget: self selector: #borderColor: originalColor: self borderColor hand: aHand.!

Item was changed:
+ ----- Method: FlexMorph>>changeBorderWidth: (in category 'menus') -----
- ----- Method: FlexMorph>>changeBorderWidth: (in category 'as yet unclassified') -----
  changeBorderWidth: evt
  	| handle origin aHand |
  	aHand := evt ifNil: [self primaryHand] ifNotNil: [evt hand].
  	origin := aHand position.
  	handle := HandleMorph new forEachPointDo:
  		[:newPoint | handle removeAllMorphs.
  		handle addMorph:
  			(LineMorph from: origin to: newPoint color: Color black width: 1).
  		self borderWidth: (newPoint - origin) r asInteger // 5].
  	aHand attachMorph: handle.
  	handle startStepping!

Item was changed:
+ ----- Method: FlexMorph>>loadOriginalForm (in category 'private') -----
- ----- Method: FlexMorph>>loadOriginalForm (in category 'as yet unclassified') -----
  loadOriginalForm
  
  	originalForm ifNil: [self updateFromOriginal].
  !

Item was changed:
+ ----- Method: FlexMorph>>originalMorph (in category 'accessing') -----
- ----- Method: FlexMorph>>originalMorph (in category 'as yet unclassified') -----
  originalMorph
  
  	^ originalMorph!

Item was changed:
+ ----- Method: FlexMorph>>originalMorph: (in category 'accessing') -----
- ----- Method: FlexMorph>>originalMorph: (in category 'as yet unclassified') -----
  originalMorph: aMorph
  
  	originalMorph := aMorph.
  	scalePoint := 0.25 at 0.25.
  	self updateFromOriginal.!

Item was changed:
+ ----- Method: FlexMorph>>updateFromOriginal (in category 'private') -----
- ----- Method: FlexMorph>>updateFromOriginal (in category 'as yet unclassified') -----
  updateFromOriginal
  
  	| intermediateForm |
  	intermediateForm := originalMorph imageForm offset: 0 at 0.
  	intermediateForm border: intermediateForm boundingBox
  		widthRectangle: (borderWidth corner: borderWidth+1)
  		rule: Form over fillColor: borderColor.
  	self form: intermediateForm.
  	originalMorph fullReleaseCachedState!

Item was changed:
+ ----- Method: GraphicalMenu>>argument (in category 'accessing') -----
- ----- Method: GraphicalMenu>>argument (in category 'as yet unclassified') -----
  argument
  	^argument!

Item was changed:
+ ----- Method: GraphicalMenu>>argument: (in category 'accessing') -----
- ----- Method: GraphicalMenu>>argument: (in category 'as yet unclassified') -----
  argument: anObject
  	argument := anObject!

Item was changed:
+ ----- Method: GraphicalMenu>>cancel (in category 'event handling') -----
- ----- Method: GraphicalMenu>>cancel (in category 'as yet unclassified') -----
  cancel
  	coexistWithOriginal
  		ifTrue:
  			[self delete]
  		ifFalse:
  			[owner replaceSubmorph: self topRendererOrSelf by: target]!

Item was changed:
+ ----- Method: GraphicalMenu>>downArrowHit (in category 'event handling') -----
- ----- Method: GraphicalMenu>>downArrowHit (in category 'as yet unclassified') -----
  downArrowHit
  	currentIndex := currentIndex - 1.
  	(currentIndex < 1) ifTrue:  [currentIndex := formChoices size].
  	self updateThumbnail
  	
  !

Item was changed:
+ ----- Method: GraphicalMenu>>okay (in category 'event handling') -----
- ----- Method: GraphicalMenu>>okay (in category 'as yet unclassified') -----
  okay
  	| nArgs |
  	target ifNotNil:[
  		nArgs := selector numArgs.
  		nArgs = 1 ifTrue:[target perform: selector with: (formChoices at: currentIndex)].
  		nArgs = 2 ifTrue:[target perform: selector with: (formChoices at: currentIndex) with: argument]].
  	coexistWithOriginal
  		ifTrue:
  			[self delete]
  		ifFalse:
  			[owner replaceSubmorph: self topRendererOrSelf by: target]!

Item was changed:
+ ----- Method: GraphicalMenu>>selector (in category 'accessing') -----
- ----- Method: GraphicalMenu>>selector (in category 'as yet unclassified') -----
  selector
  	^selector!

Item was changed:
+ ----- Method: GraphicalMenu>>selector: (in category 'accessing') -----
- ----- Method: GraphicalMenu>>selector: (in category 'as yet unclassified') -----
  selector: aSymbol
  	selector := aSymbol!

Item was changed:
+ ----- Method: GraphicalMenu>>upArrowHit (in category 'event handling') -----
- ----- Method: GraphicalMenu>>upArrowHit (in category 'as yet unclassified') -----
  upArrowHit
  	currentIndex := currentIndex + 1.
  	(currentIndex > formChoices size) ifTrue: [currentIndex := 1].
  	self updateThumbnail
  	
  !

Item was changed:
+ ----- Method: InterimSoundMorph>>addGraphic (in category 'initialization') -----
- ----- Method: InterimSoundMorph>>addGraphic (in category 'as yet unclassified') -----
  addGraphic
  
  	graphic := SketchMorph withForm: self speakerGraphic.
  	graphic position: bounds center - (graphic extent // 2).
  	self addMorph: graphic.
  !

Item was changed:
+ ----- Method: InterimSoundMorph>>sound (in category 'accessing') -----
- ----- Method: InterimSoundMorph>>sound (in category 'as yet unclassified') -----
  sound
  
  	^ sound
  !

Item was changed:
+ ----- Method: InterimSoundMorph>>sound: (in category 'accessing') -----
- ----- Method: InterimSoundMorph>>sound: (in category 'as yet unclassified') -----
  sound: aSound
  
  	sound := aSound.
  !

Item was changed:
+ ----- Method: InterimSoundMorph>>speakerGraphic (in category 'initialization') -----
- ----- Method: InterimSoundMorph>>speakerGraphic (in category 'as yet unclassified') -----
  speakerGraphic
  
  	^ Form
  		extent: 19 at 18
  		depth: 8
  		fromArray: #(0 0 1493172224 2816 0 0 0 1493172224 11 0 0 138 1493172224 184549376 184549376 0 35509 2315255808 720896 720896 0 9090522 2315255808 2816 720896 0 2327173887 2315255819 2816 720896 138 3051028442 2315255819 2816 2816 1505080590 4294957786 2315255808 184549387 2816 3053453311 4292532917 1493172224 184549387 2816 1505080714 3048584629 1493172224 184549387 2816 9079434 3048584629 1493172224 184549387 2816 138 2327164341 1493172235 2816 2816 0 2324346293 1493172235 2816 720896 0 9079477 1493172224 2816 720896 0 35466 1493172224 720896 720896 0 138 0 184549376 184549376 0 0 0 11 0 0 0 0 2816 0)
  		offset: 0 at 0
  !

Item was changed:
+ ----- Method: MultiResolutionCanvas>>deferredMorphs (in category 'accessing') -----
- ----- Method: MultiResolutionCanvas>>deferredMorphs (in category 'as yet unclassified') -----
  deferredMorphs
  
  	^deferredMorphs!

Item was changed:
+ ----- Method: MultiResolutionCanvas>>deferredMorphs: (in category 'accessing') -----
- ----- Method: MultiResolutionCanvas>>deferredMorphs: (in category 'as yet unclassified') -----
  deferredMorphs: aCollection
  
  	deferredMorphs := aCollection!

Item was changed:
+ ----- Method: MultiResolutionCanvas>>initializeFrom: (in category 'initialize-release') -----
- ----- Method: MultiResolutionCanvas>>initializeFrom: (in category 'as yet unclassified') -----
  initializeFrom: aFormCanvas
  
  	origin := aFormCanvas origin.
  	clipRect := aFormCanvas privateClipRect.
  	form := aFormCanvas form.
  	port := aFormCanvas privatePort.
  	shadowColor := aFormCanvas shadowColor.
  !

Item was changed:
+ ----- Method: SoundEventMorph>>sound: (in category 'accessing') -----
- ----- Method: SoundEventMorph>>sound: (in category 'as yet unclassified') -----
  sound: aSound
  
  	sound := aSound.
  	self setBalloonText: 'a sound of duration ',(sound duration printShowingMaxDecimalPlaces: 1),' seconds'.!

Item was changed:
+ ----- Method: SoundLoopMorph>>addCursorMorph (in category 'initialization') -----
- ----- Method: SoundLoopMorph>>addCursorMorph (in category 'as yet unclassified') -----
  addCursorMorph
  	self addMorph:
  		(cursor := (RectangleMorph
  				newBounds: (self innerBounds topLeft extent: 1 at self innerBounds height)
  				color: Color red)
  						borderWidth: 0)!

Item was changed:
+ ----- Method: SoundLoopMorph>>allowSubmorphExtraction (in category 'dropping/grabbing') -----
- ----- Method: SoundLoopMorph>>allowSubmorphExtraction (in category 'as yet unclassified') -----
  allowSubmorphExtraction
  
  	^ true!

Item was changed:
+ ----- Method: SoundLoopMorph>>buildSound (in category 'playing') -----
- ----- Method: SoundLoopMorph>>buildSound (in category 'as yet unclassified') -----
  buildSound
  	"Build a compound sound for the next iteration of the loop."
  
  	| mixer soundMorphs |
  	mixer := MixedSound new.
  	mixer add: (RestSound dur: (self width - (2 * borderWidth)) / 128.0).
  	soundMorphs := self submorphs select: [:m | m respondsTo: #sound].
  	soundMorphs do: [:m |
  		| startTime pan |
  		startTime := (m position x - (self left + borderWidth)) / 128.0.
  		pan := (m position y - (self top + borderWidth)) asFloat / (self height - (2 * borderWidth) - m height).
  		mixer add: ((RestSound dur: startTime), m sound copy) pan: pan].
  	^ mixer
  !

Item was changed:
+ ----- Method: SoundLoopMorph>>play (in category 'playing') -----
- ----- Method: SoundLoopMorph>>play (in category 'as yet unclassified') -----
  play
  	"Play this sound to the sound ouput port in real time."
  
  	self reset.
  	SoundPlayer playSound: self.
  !

Item was changed:
+ ----- Method: SquishedNameMorph>>colorAroundName (in category 'drawing') -----
- ----- Method: SquishedNameMorph>>colorAroundName (in category 'as yet unclassified') -----
  colorAroundName
  
  	^Color gray: 0.8!

Item was changed:
+ ----- Method: SquishedNameMorph>>fontForName (in category 'drawing') -----
- ----- Method: SquishedNameMorph>>fontForName (in category 'as yet unclassified') -----
  fontForName
  
  	^(TextStyle default fontOfSize: 15) emphasized: 1
  !

Item was changed:
+ ----- Method: SquishedNameMorph>>isEditingName (in category 'drawing') -----
- ----- Method: SquishedNameMorph>>isEditingName (in category 'as yet unclassified') -----
  isEditingName
  
  	^((self findA: UpdatingStringMorph) ifNil: [^false]) hasFocus
  !

Item was changed:
+ ----- Method: SquishedNameMorph>>stringToShow (in category 'drawing') -----
- ----- Method: SquishedNameMorph>>stringToShow (in category 'as yet unclassified') -----
  stringToShow
  
  	(target isNil or: [getSelector isNil]) ifTrue: [^'????'].
  	^target perform: getSelector!

Item was changed:
+ ----- Method: SquishedNameMorph>>target:getSelector:setSelector: (in category 'initialization') -----
- ----- Method: SquishedNameMorph>>target:getSelector:setSelector: (in category 'as yet unclassified') -----
  target: aTarget getSelector: symbol1 setSelector: symbol2
  
  	target := aTarget.
  	getSelector := symbol1.
  	setSelector := symbol2.!

Item was changed:
+ ----- Method: StoryboardBookMorph>>changeTiltFactor: (in category 'private') -----
- ----- Method: StoryboardBookMorph>>changeTiltFactor: (in category 'as yet unclassified') -----
  changeTiltFactor: x
  
  	currentPage changeTiltFactor: x.
  	panAndTiltFactor := x.
  
  !

Item was changed:
+ ----- Method: StoryboardBookMorph>>changeZoomFactor: (in category 'private') -----
- ----- Method: StoryboardBookMorph>>changeZoomFactor: (in category 'as yet unclassified') -----
  changeZoomFactor: x
  
  	currentPage changeZoomFactor: x.
  	zoomFactor := x.!

Item was changed:
+ ----- Method: StoryboardBookMorph>>getTiltFactor (in category 'private') -----
- ----- Method: StoryboardBookMorph>>getTiltFactor (in category 'as yet unclassified') -----
  getTiltFactor
  
  	^panAndTiltFactor ifNil: [panAndTiltFactor := 0.5].!

Item was changed:
+ ----- Method: StoryboardBookMorph>>getZoomFactor (in category 'private') -----
- ----- Method: StoryboardBookMorph>>getZoomFactor (in category 'as yet unclassified') -----
  getZoomFactor
  
  	^zoomFactor ifNil: [zoomFactor := 0.5]!

Item was changed:
+ ----- Method: StoryboardBookMorph>>offsetX (in category 'accessing') -----
- ----- Method: StoryboardBookMorph>>offsetX (in category 'as yet unclassified') -----
  offsetX
  
  	^currentPage offsetX!

Item was changed:
+ ----- Method: StoryboardBookMorph>>offsetX: (in category 'accessing') -----
- ----- Method: StoryboardBookMorph>>offsetX: (in category 'as yet unclassified') -----
  offsetX: aNumber
  
  	currentPage offsetX: aNumber!

Item was changed:
+ ----- Method: StoryboardBookMorph>>offsetY (in category 'accessing') -----
- ----- Method: StoryboardBookMorph>>offsetY (in category 'as yet unclassified') -----
  offsetY
  
  	^currentPage offsetY!

Item was changed:
+ ----- Method: StoryboardBookMorph>>offsetY: (in category 'accessing') -----
- ----- Method: StoryboardBookMorph>>offsetY: (in category 'as yet unclassified') -----
  offsetY: aNumber
  
  	currentPage offsetY: aNumber!

Item was changed:
+ ----- Method: StoryboardBookMorph>>scale (in category 'accessing') -----
- ----- Method: StoryboardBookMorph>>scale (in category 'as yet unclassified') -----
  scale
  
  	^currentPage scale!

Item was changed:
+ ----- Method: StoryboardBookMorph>>scale: (in category 'accessing') -----
- ----- Method: StoryboardBookMorph>>scale: (in category 'as yet unclassified') -----
  scale: aValue
  
  	currentPage scale: aValue!

Item was changed:
+ ----- Method: TextOnCurve>>composeLinesFrom:withLines:atY: (in category 'composition') -----
- ----- Method: TextOnCurve>>composeLinesFrom:withLines:atY: (in category 'as yet unclassified') -----
  composeLinesFrom: startingIndex withLines: startingLines atY: startingY 
  	"Here we determine the 'lines' of text that will fit along each segment of the curve. For each line, we determine its rectangle, then the dest wuadrilateral that it willbe rotated to.  Then, we take the outer hull to determine a dest rectangle for WarpBlt.  In addition we need the segment pivot point and angle, from which the source quadrilateral may be computed."
  
  	| charIndex scanner line firstLine curveSegments segIndex pa pb segLen lineRect textSegments segDelta segAngle destRect destQuad i oldBounds |
  	(oldBounds := container bounds) ifNotNil: [curve invalidRect: oldBounds].
  	charIndex := startingIndex.
  	lines := startingLines.
  	curveSegments := curve lineSegments.
  	container textDirection < 0 
  		ifTrue: 
  			[curveSegments := curveSegments reversed 
  						collect: [:seg | Array with: (seg second) with: seg first]].
  	textSegments := OrderedCollection new.
  	scanner := SegmentScanner new text: text textStyle: textStyle.
  	segIndex := 1.	"For curves, segIndex is just an index."
  	firstLine := true.
  	pa := curveSegments first first.
  	[charIndex <= text size and: [segIndex <= curveSegments size]] whileTrue: 
  			[curve isCurve ifFalse: [pa := (curveSegments at: segIndex) first].
  			pb := (curveSegments at: segIndex) last.
  			segDelta := pb - pa.	"Direction of this segment"
  			segLen := segDelta r.
  			lineRect := 0 @ 0 extent: segLen asInteger @ textStyle lineGrid.
  			line := scanner 
  						composeFrom: charIndex
  						inRectangle: lineRect
  						firstLine: firstLine
  						leftSide: true
  						rightSide: true.
  			line setRight: scanner rightX.
  			line width > 0 
  				ifTrue: 
  					[lines addLast: line.
  					segAngle := segDelta theta.
  					destQuad := line rectangle corners collect: 
  									[:p | 
  									(p translateBy: pa - (0 @ (line baseline + container baseline))) 
  										rotateBy: segAngle negated
  										about: pa].
  					destRect := Rectangle encompassing: destQuad.
  					textSegments addLast: (Array 
  								with: destRect truncated
  								with: pa
  								with: segAngle).
  					pa := pa + ((pb - pa) * line width / segLen).
  					charIndex := line last + 1].
  			segIndex := segIndex + 1.
  			firstLine := false].
  	lines isEmpty 
  		ifTrue: 
  			["No space in container or empty text"
  
  			line := (TextLine 
  						start: startingIndex
  						stop: startingIndex - 1
  						internalSpaces: 0
  						paddingWidth: 0)
  						rectangle: (0 @ 0 extent: 10 @ textStyle lineGrid);
  						lineHeight: textStyle lineGrid baseline: textStyle baseline.
  			lines := Array with: line.
  			textSegments addLast: (Array 
  						with: (curve vertices first extent: line rectangle extent)
  						with: curve vertices first
  						with: 0.0)].
  	"end of segments, now attempt word break."
  	lines last last < text size 
  		ifTrue: 
  			[
  			[lines size > 1 
  				and: [(text at: (i := lines last last) + 1) ~= Character space]] 
  					whileTrue: 
  						[i = lines last first 
  							ifTrue: 
  								[lines removeLast.
  								textSegments removeLast]
  							ifFalse: [lines last stop: i - 1]]].
  	lines := lines asArray.
  	container textSegments: textSegments asArray.
  	curve invalidRect: container bounds.
  	^maxRightX!

Item was changed:
+ ----- Method: TextOnCurve>>extent (in category 'accessing') -----
- ----- Method: TextOnCurve>>extent (in category 'access') -----
  extent
  	^ curve bounds extent!

Item was changed:
+ ----- Method: TextOnCurve>>pointInLine:forDestPoint:segStart:segAngle: (in category 'private') -----
- ----- Method: TextOnCurve>>pointInLine:forDestPoint:segStart:segAngle: (in category 'as yet unclassified') -----
  pointInLine: line forDestPoint: p segStart: segStart segAngle: segAngle
  	^ (p rotateBy: segAngle about: segStart)
  			translateBy: (0@(line baseline + container baseline)) - segStart!

Item was changed:
+ ----- Method: TextOnCurve>>releaseCachedState (in category 'caching') -----
- ----- Method: TextOnCurve>>releaseCachedState (in category 'as yet unclassified') -----
  releaseCachedState
  	super releaseCachedState.
  	CachedWarpMap := CachedWarpDepth := CachedWarpColor := nil!

Item was changed:
+ ----- Method: TextOnCurve>>textOwner: (in category 'accessing') -----
- ----- Method: TextOnCurve>>textOwner: (in category 'access') -----
  textOwner: theCurve
  	curve := theCurve!

Item was changed:
+ ----- Method: TextOnCurve>>textSegmentsDo: (in category 'private') -----
- ----- Method: TextOnCurve>>textSegmentsDo: (in category 'as yet unclassified') -----
  textSegmentsDo: blockForLineDestPivotAngle 
  	| segments segSpec |
  	(segments := container textSegments) ifNil: [^self].
  	1 to: lines size
  		do: 
  			[:i | 
  			segSpec := segments at: i.
  			blockForLineDestPivotAngle 
  				value: (lines at: i)
  				value: (segSpec first)
  				value: (segSpec second)
  				value: (segSpec third)]!

Item was changed:
+ ----- Method: TextOnCurve>>warpMapForDepth:withTransparentFor: (in category 'private') -----
- ----- Method: TextOnCurve>>warpMapForDepth:withTransparentFor: (in category 'as yet unclassified') -----
  warpMapForDepth: destDepth withTransparentFor: bkgndColor 
  	(CachedWarpDepth = destDepth and: [CachedWarpColor = bkgndColor]) 
  		ifTrue: 
  			["Map is OK as is -- return it"
  
  			^CachedWarpMap].
  	(CachedWarpMap isNil or: [CachedWarpDepth ~= destDepth]) 
  		ifTrue: 
  			["Have to recreate the map"
  
  			CachedWarpMap := Color computeColormapFrom: 32 to: destDepth.
  			CachedWarpDepth := destDepth]
  		ifFalse: 
  			["Map is OK, if we restore prior color substiution"
  
  			CachedWarpMap at: (CachedWarpColor indexInMap: CachedWarpMap)
  				put: (CachedWarpColor pixelValueForDepth: destDepth)].
  	"Now map the background color into transparent, and return the new map"
  	CachedWarpColor := bkgndColor.
  	CachedWarpMap at: (CachedWarpColor indexInMap: CachedWarpMap) put: 0.
  	^CachedWarpMap!

Item was changed:
+ ----- Method: TextOnCurveContainer>>baseline (in category 'accessing') -----
- ----- Method: TextOnCurveContainer>>baseline (in category 'as yet unclassified') -----
  baseline
  	baseline ifNil: [^ 0].
  	^ baseline!

Item was changed:
+ ----- Method: TextOnCurveContainer>>baseline: (in category 'accessing') -----
- ----- Method: TextOnCurveContainer>>baseline: (in category 'as yet unclassified') -----
  baseline: newBaseline
  	baseline := newBaseline!

Item was changed:
+ ----- Method: TextOnCurveContainer>>bounds (in category 'accessing') -----
- ----- Method: TextOnCurveContainer>>bounds (in category 'as yet unclassified') -----
  bounds
  	textSegments ifNil: [^nil].
  	^textSegments inject: (textSegments first first)
  		into: [:bnd :each | bnd merge: (each first)]!

Item was changed:
+ ----- Method: TextOnCurveContainer>>paragraphClass (in category 'accessing') -----
- ----- Method: TextOnCurveContainer>>paragraphClass (in category 'as yet unclassified') -----
  paragraphClass
  	^ TextOnCurve!

Item was changed:
+ ----- Method: TextOnCurveContainer>>releaseCachedState (in category 'caching') -----
- ----- Method: TextOnCurveContainer>>releaseCachedState (in category 'as yet unclassified') -----
  releaseCachedState
  	textSegments := nil.!

Item was changed:
+ ----- Method: TextOnCurveContainer>>textDirection (in category 'accessing') -----
- ----- Method: TextOnCurveContainer>>textDirection (in category 'as yet unclassified') -----
  textDirection
  	^ textDirection!

Item was changed:
+ ----- Method: TextOnCurveContainer>>textDirection: (in category 'accessing') -----
- ----- Method: TextOnCurveContainer>>textDirection: (in category 'as yet unclassified') -----
  textDirection: plusOrMinusOne
  	textDirection := plusOrMinusOne!

Item was changed:
+ ----- Method: TextOnCurveContainer>>textSegments (in category 'accessing') -----
- ----- Method: TextOnCurveContainer>>textSegments (in category 'as yet unclassified') -----
  textSegments
  	^ textSegments!

Item was changed:
+ ----- Method: TextOnCurveContainer>>textSegments: (in category 'accessing') -----
- ----- Method: TextOnCurveContainer>>textSegments: (in category 'as yet unclassified') -----
  textSegments: segments
  	textSegments := segments!

Item was changed:
+ ----- Method: TextOnCurveContainer>>top (in category 'accessing') -----
- ----- Method: TextOnCurveContainer>>top (in category 'as yet unclassified') -----
  top
  	^ 1  "for compatibility"!

Item was changed:
+ ----- Method: TextOnCurveContainer>>translateBy: (in category 'transforming') -----
- ----- Method: TextOnCurveContainer>>translateBy: (in category 'as yet unclassified') -----
  translateBy: delta 
  	textSegments isNil ifTrue: [^self].
  	textSegments := textSegments collect: 
  					[:ls | 
  					Array 
  						with: (ls first translateBy: delta)
  						with: (ls second translateBy: delta)
  						with: ls third]!

Item was changed:
+ ----- Method: TransformationB2Morph>>useRegularWarpBlt: (in category 'accessing') -----
- ----- Method: TransformationB2Morph>>useRegularWarpBlt: (in category 'as yet unclassified') -----
  useRegularWarpBlt: aBoolean
  
  	useRegularWarpBlt := aBoolean!

Item was changed:
+ ----- Method: ZASMStepsMorph>>getStepCount (in category 'accessing') -----
- ----- Method: ZASMStepsMorph>>getStepCount (in category 'as yet unclassified') -----
  getStepCount
  
  	^[self contents asNumber] ifError: [ :a :b | 10]
  	
  !

Item was changed:
+ ----- Method: ZASMStepsMorph>>setStepCount: (in category 'accessing') -----
- ----- Method: ZASMStepsMorph>>setStepCount: (in category 'as yet unclassified') -----
  setStepCount: n
  
  	self contents: n printString.
  
  !



More information about the Squeak-dev mailing list