[ANN] BabySRE (Squeak Reverse Engineering) posted on SqueakMap

Lic. Edgar J. De Cleene edgardec2001 at yahoo.com.ar
Tue Dec 28 20:36:56 UTC 2004


On 28/12/04 15:09, "Joseph Frippiat" <joseph.frippiat at skynet.be> wrote:

> Hi,
> 
> I took a fresh Squeak3.8g-6527 image.
> I opened a SqueakMap Package Loader.
> I installed MCInstaller 11, Monticello 223, Refactoring Browser 3.8.13 .
> Then I tried to install Connectors 2.1-173 and I got this message :
> 
> --- Message begin ---
> This package depends on the following classes:
> AlansTextPlusMorph
> You must resolve these dependencies before you will be able to load these
> definitions:
> AlansTextPlusMorph class>>initialize
> AlansTextPlusMorph class>>unload
> AlansTextPlusMorph>>releaseCachedState
> AlansTextPlusMorph>>step
> AlansTextPlusMorph>>visibleMorphs
> AlansTextPlusMorph>>visibleMorphs:
> 
> Select Proceed to continue, or close this window to cancel the operation.
> --- Message end ---
> 
> I will try to find that class.
> 
> Joseph
> 
> ----- Original Message -----
> From: "Ned Konz" <ned at squeakland.org>
> To: "The general-purpose Squeak developers list"
> <squeak-dev at lists.squeakfoundation.org>
> Sent: Wednesday, December 22, 2004 5:25 AM
> Subject: Re: [ANN] BabySRE (Squeak Reverse Engineering) posted on SqueakMap
> 
> 
>> On Tuesday 21 December 2004 12:37 pm, hjh-sqlist at lexdb.net wrote:
>>> e) base image plus MC, RFB, Conn1.9, SRE
>>> If somebody other is successful assembling a 3.8gamma image with
>>> Monticello, RFB, Connectors and SRE without the aforementioned limit I
>>> will
>>> happily provide webspace that other poeple can get started right away.
>>> This
>>> will be for a few months as I think later we will have better solutions
>>> (New version of SqueakMap).
>> 
>> I routinely use a 3.8g image with MC, RFB, and Connectors2. It happens to
>> be
>> derived from the Squeakland image, but it still works.
>> 
>> -- 
>> Ned Konz
>> http://bike-nomad.com/squeak/
>> 
>> 
>> 
>> 
>> -- 
>> No virus found in this incoming message.
>> Checked by AVG Anti-Virus.
>> Version: 7.0.298 / Virus Database: 265.6.4 - Release Date: 22/12/2004
>> 
> 
> 
> 
> -- 
> No virus found in this outgoing message.
> Checked by AVG Anti-Virus.
> Version: 7.0.298 / Virus Database: 265.6.5 - Release Date: 26/12/2004
> 
> 

Joseph :
AlansTextPlusMorph was removed because changes to ScrollPane.
I send a fileOut , fileIn in your image and try again.
Hope not other changed or removed class was needed, but if load stop again
look missing class in earlier Squeak images (3.7 or 3.6), fileOut and
fileOut for a quick and dirty solution until Ned changes code.

Edgar

-------------- next part --------------
'From Squeak3.7 of ''4 September 2004'' [latest update: #5988] on 28 December 2004 at 5:30:29 pm'!
ScrollPane subclass: #AlansTextPlusMorph
	instanceVariableNames: 'theTextMorph thePasteUp'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Morphic-GeeMail'!
!AlansTextPlusMorph commentStamp: '<historical>' prior: 0!
The code is here, but the class you really want to use is GeeMailMorph (nicer name).!


!AlansTextPlusMorph methodsFor: 'access' stamp: 'RAA 9/6/2000 16:25'!
wantsSlot

	^false! !


!AlansTextPlusMorph methodsFor: 'as yet unclassified' stamp: 'dgd 8/30/2003 20:50'!
addGeeMailMenuItemsTo: menu

	self flag: #convertToBook.	"<-- no longer used"
	menu 
		addUpdating: #showPageBreaksString action: #togglePageBreaks;
		addUpdating: #keepScrollbarString action: #toggleKeepScrollbar;
		addLine;
		add: 'Print...' translated action: #printPSToFile;
		addLine.
	thePasteUp allTextPlusMorphs size = 1 ifTrue: [
		menu add: 'make 1-column book' translated selector: #makeBookStyle: argument: 1.
		menu add: 'make 2-column book' translated selector: #makeBookStyle: argument: 2.
		menu add: 'make 3-column book' translated selector: #makeBookStyle: argument: 3.
		menu add: 'make 4-column book' translated selector: #makeBookStyle: argument: 4.
	] ifFalse: [
		menu add: 'make a galley of me' translated action: #makeGalleyStyle.
	].
	^menu! !

!AlansTextPlusMorph methodsFor: 'as yet unclassified' stamp: 'RAA 10/30/2000 15:06'!
adjustPasteUpSize

	| newBottom |

	thePasteUp ifNil: [^self].
	newBottom _ thePasteUp bottom max: thePasteUp boundingBoxOfSubmorphs bottom + 20.
	thePasteUp height: (newBottom - thePasteUp top max: self height).
	thePasteUp width: (thePasteUp width max: scroller innerBounds width - 5).! !

!AlansTextPlusMorph methodsFor: 'as yet unclassified' stamp: 'RAA 5/3/2001 17:42'!
allTextPlusMorphs

	^thePasteUp allTextPlusMorphs! !

!AlansTextPlusMorph methodsFor: 'as yet unclassified' stamp: 'RAA 10/3/2000 12:03'!
convertToBook

	GeeBookMorph new 
		geeMail: thePasteUp;
		rebuildPages;
		openInWorld! !

!AlansTextPlusMorph methodsFor: 'as yet unclassified' stamp: 'RAA 2/21/2001 12:57'!
keepScrollBarAlways

	^self valueOfProperty: #keepScrollBarAlways ifAbsent: [false]! !

!AlansTextPlusMorph methodsFor: 'as yet unclassified' stamp: 'RAA 2/21/2001 12:59'!
keepScrollbarString

	^self keepScrollBarAlways ifTrue: ['<on>scrollbar stays up'] ifFalse: ['<off>scrollbar stays up']! !

!AlansTextPlusMorph methodsFor: 'as yet unclassified' stamp: 'RAA 12/5/2001 11:15'!
makeBookStyle: nColumns

	| all totalWidth second columnWidth currY prev columnHeight currX currColumn pageBreakRectangles r rm columnGap pageGap starter |

	pageBreakRectangles _ OrderedCollection new.
	all _ thePasteUp allTextPlusMorphs.
	all size = 1 ifFalse: [^self].
	Cursor wait show.
	starter _ prev _ all first.
	totalWidth _ self width - 16.
	columnGap _ 32.
	pageGap _ 16.
	columnWidth _ totalWidth - (columnGap * (nColumns - 1)) // nColumns.
	columnHeight _ self height - 12.
	currY _ 4.
	currX _ 4.
	currColumn _ 1.
	prev
		position: currX at currY;
		width: columnWidth.
	[
		second _ prev makeSuccessorMorph.
		thePasteUp addMorphBack: second.
		prev 
			setProperty: #autoFitContents toValue: false;
			height: columnHeight.
		(currColumn _ currColumn + 1) <= nColumns ifTrue: [
			currX _ currX + columnWidth + columnGap.
		] ifFalse: [
			r _ 4@(prev bottom + 4) corner: (self right - 4 @ (prev bottom + pageGap - 4)).
			rm _ RectangleMorph new bounds: r; color: (Color gray alpha: 0.3); borderWidth: 0.
			pageBreakRectangles add: rm beSticky.
			thePasteUp addMorphBack: rm.
			currColumn _ 1.
			currX _ 4.
			currY _ prev bottom + pageGap.
		].
		second 
			autoFit: true;
			position: currX at currY;
			width: columnWidth.
		prev recomposeChain.		"was commented"
		prev _ second.
		prev height > columnHeight
	] whileTrue.
	prev autoFit: true.
	thePasteUp height: (prev bottom + 20 - self top).
	self layoutChanged.
	self setProperty: #pageBreakRectangles toValue: pageBreakRectangles.
	thePasteUp allTextPlusMorphs do: [ :each |
		each repositionAnchoredMorphs
	].
	Cursor normal show.
! !

!AlansTextPlusMorph methodsFor: 'as yet unclassified' stamp: 'RAA 11/30/2001 12:12'!
makeGalleyStyle

	| all first theRest |

	(self valueOfProperty: #pageBreakRectangles ifAbsent: [#()]) do: [ :each |
		each delete
	].
	self removeProperty: #pageBreakRectangles.
	all _ thePasteUp allTextPlusMorphs.
	first _ all select: [ :x | x predecessor isNil].
	first size = 1 ifFalse: [^self].
	Cursor wait show.
	first _ first first.
	theRest _ all reject: [ :x | x predecessor isNil].
	theRest do: [ :each | each delete].
	first autoFit: true.
	first width: self width - 8.
	first recomposeChain.
	first repositionAnchoredMorphs.
	Cursor normal show.
! !

!AlansTextPlusMorph methodsFor: 'as yet unclassified' stamp: 'ar 10/6/2000 16:36'!
mouseUp: evt inMorph: aMorph

	evt hand grabMorph: aMorph	"old instances may have a handler we no longer use"! !

!AlansTextPlusMorph methodsFor: 'as yet unclassified' stamp: 'RAA 5/7/2001 13:25'!
pageRectanglesForPrinting

	| pageBreaks prevBottom pageRects r |

	pageBreaks _ self valueOfProperty: #pageBreakRectangles ifAbsent: [^nil].
	prevBottom _ 0.
	pageRects _ pageBreaks collect: [ :each |
		r _ 0 at prevBottom corner: self width @ each top.
		prevBottom _ each bottom.
		r
	].
	pageRects add: (0 at prevBottom corner: self width @ thePasteUp bottom).
	^pageRects! !

!AlansTextPlusMorph methodsFor: 'as yet unclassified' stamp: 'RAA 5/4/2001 09:21'!
scrollSelectionIntoView: event alignTop: alignTop inTextMorph: tm
	"Scroll my text into view if necessary and return true, else return false"

	| selRects delta selRect rectToTest transform cpHere |

	selRects _ tm paragraph selectionRects.
	selRects isEmpty ifTrue: [^ false].
	rectToTest _ selRects first merge: selRects last.
	transform _ scroller transformFrom: self.
	(event notNil and: [event isMouse and: [event anyButtonPressed]]) ifTrue:  "Check for autoscroll"
		[cpHere _ transform localPointToGlobal: event cursorPoint.
		cpHere y <= self top
			ifTrue: [rectToTest _ selRects first topLeft extent: 2 at 2]
			ifFalse: [cpHere y >= self bottom
					ifTrue: [rectToTest _ selRects last bottomRight extent: 2 at 2]
					ifFalse: [^ false]]].
	selRect _ transform localBoundsToGlobal: rectToTest.
	selRect height > bounds height
		ifTrue: [^ false].  "Would not fit, even if we tried to scroll"
	alignTop ifTrue: [
		self scrollBy: 0@(bounds top - selRect top).
		^ true
	].
	selRect bottom > bounds bottom ifTrue: [
		self scrollBy: 0@(bounds bottom - selRect bottom - 30).
		^ true
	].
	(delta _ selRect amountToTranslateWithin: self bounds) y ~= 0 ifTrue: [
		"Scroll end of selection into view if necessary"
		self scrollBy: 0 at delta y.
		^ true].
	^ false! !

!AlansTextPlusMorph methodsFor: 'as yet unclassified' stamp: 'RAA 5/3/2001 13:06'!
scrollToPage: pageNumber

	| rects oneRect |

	rects _ self valueOfProperty: #pageBreakRectangles ifAbsent: [#()].
	oneRect _ rects at: pageNumber - 1 ifAbsent: [0 at 0 extent: 0 at 0].
	self scrollToYAbsolute: oneRect bottom.
! !

!AlansTextPlusMorph methodsFor: 'as yet unclassified' stamp: 'RAA 5/3/2001 13:01'!
scrollToYAbsolute: yValue

	| transform transformedPoint |

	transform _ scroller transformFrom: self.
	transformedPoint _ transform localPointToGlobal: 0 at yValue.

	self scrollBy: 0@(bounds top - transformedPoint y).
! !

!AlansTextPlusMorph methodsFor: 'as yet unclassified' stamp: 'RAA 2/20/2001 17:10'!
showPageBreaksString

	^(thePasteUp ifNil: [^'???']) showPageBreaksString! !

!AlansTextPlusMorph methodsFor: 'as yet unclassified' stamp: 'RAA 2/21/2001 12:58'!
toggleKeepScrollbar

	self setProperty: #keepScrollBarAlways toValue: self keepScrollBarAlways not! !

!AlansTextPlusMorph methodsFor: 'as yet unclassified' stamp: 'RAA 2/20/2001 17:12'!
togglePageBreaks

	(thePasteUp ifNil: [^self]) togglePageBreaks! !


!AlansTextPlusMorph methodsFor: 'dropping/grabbing' stamp: 'RAA 9/7/2000 11:42'!
wantsDroppedMorph: aMorph event: evt
	"Return true if the receiver wishes to accept the given morph, which is being dropped by a hand in response to the given event. The default implementation returns false.
NOTE: the event is assumed to be in global (world) coordinates."

	^false! !


!AlansTextPlusMorph methodsFor: 'event handling' stamp: 'RAA 5/3/2001 17:33'!
handlesMouseDown: evt

	^evt yellowButtonPressed ! !


!AlansTextPlusMorph methodsFor: 'geometry' stamp: 'JW 2/21/2001 22:54'!
extraScrollRange
	^ bounds height
! !


!AlansTextPlusMorph methodsFor: 'initialization' stamp: 'dgd 2/14/2003 22:24'!
defaultColor
	"answer the default color/fill style for the receiver"
	^ Color white! !

!AlansTextPlusMorph methodsFor: 'initialization' stamp: 'gm 3/10/2003 22:58'!
initialize
	"initialize the state of the receiver"
	super initialize.
	""
	self initializeThePasteUp.
	self position: 100 at 100.
	self extent: Display extent // 3.
	self useRoundedCorners.
	! !

!AlansTextPlusMorph methodsFor: 'initialization' stamp: 'jam 3/9/2003 16:38'!
initializeThePasteUp
"initialize the receiver's thePasteUp"
	thePasteUp _ TextPlusPasteUpMorph new borderWidth: 0;
				 color: color.
	scroller addMorph: thePasteUp! !


!AlansTextPlusMorph methodsFor: 'layout' stamp: 'RAA 3/5/2001 23:19'!
doLayoutIn: layoutBounds
	"layout has changed. update scroll deltas or whatever else"

	self adjustPasteUpSize.
	scroller ifNotNil: [self setScrollDeltas].
	super doLayoutIn: layoutBounds.
! !


!AlansTextPlusMorph methodsFor: 'menu' stamp: 'RAA 5/3/2001 17:50'!
getMenu: shiftKeyState

	| menu |

	self flag: #convertToBook.	"<-- no longer used"

	menu _ MenuMorph new defaultTarget: self.
	self addGeeMailMenuItemsTo: menu.
	^menu! !


!AlansTextPlusMorph methodsFor: 'menus' stamp: 'RAA 5/3/2001 17:50'!
addCustomMenuItems: aCustomMenu hand: aHandMorph

	super addCustomMenuItems: aCustomMenu hand: aHandMorph.
	self addGeeMailMenuItemsTo: aCustomMenu.! !


!AlansTextPlusMorph methodsFor: 'scroll bar events' stamp: 'nk 4/28/2004 10:22'!
scrollBarValue: scrollValue

	| newPt pageBreaks topOfPage |

	scroller hasSubmorphs ifFalse: [^ self].
	newPt _ -3 @ (self vLeftoverScrollRange * scrollValue).

	pageBreaks _ self valueOfProperty: #pageBreakRectangles ifAbsent: [#()].
	pageBreaks isEmpty ifTrue: [
		^scroller offset: newPt.
	].
	topOfPage _ pageBreaks inject: (0 at 0 corner: 0 at 0) into: [ :closest :each |
		(each bottom - newPt y) abs < (closest bottom - newPt y) abs ifTrue: [
			each 
		] ifFalse: [
			closest 
		].
	].
	topOfPage ifNotNil: [
		newPt _ newPt x @ topOfPage bottom.
		scrollBar value: newPt y / self vLeftoverScrollRange.
	].
	scroller offset: newPt.! !


!AlansTextPlusMorph methodsFor: 'scrolling' stamp: 'nk 4/28/2004 10:14'!
vHideScrollBar

	self keepScrollBarAlways ifTrue: [^self].
	^super vHideScrollBar! !


!AlansTextPlusMorph methodsFor: '*morphic-Postscript Canvases' stamp: 'RAA 5/7/2001 12:20'!
printPSToFile

	thePasteUp printer
		geeMail: self;
		doPages! !

"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

AlansTextPlusMorph class
	instanceVariableNames: ''!

!AlansTextPlusMorph class methodsFor: 'new-morph participation' stamp: 'RAA 9/10/2000 12:52'!
includeInNewMorphMenu

	^ false		"to encourage the use of GeeMail instead"! !


More information about the Squeak-dev mailing list