Center for Research in Electronic Art Technology (CREATE)
Dept. of Music, UC Santa Barbara


Squeak Smalltalk Mailing List Archive

Send mail to majordomo@create.ucsb.edu to join.

Send mail to squeak@create.ucsb.edu to post.

Index


Date:	97 Apr 01 9:34:47 am
From:	stp (Stephen Travis Pope)
To:		squeak@create.ucsb.edu
Subject:	Squeak 1.19_beta now available!


Hello All,

I've placed the new Squeak 1.19_beta on the CREATE ftp site
(ftp://ftp.create.ucsb.edu/pub/Smalltalk/Squeak/) in the files
Squeak1.19b.sit.hqx (BinHexed StuffIt archive) and Squeak1.19b.tar.gz
(gzipped tar archive). These include a new Mac VM, an image and changes file,
and the README that's included below.

-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-

                  Happy Easter
                       from
             The Squeak Team

This is an Unofficial Release of Squeak.
By this we mean that it has not had a great deal of Q.A., and the features
provided are all in a preliminary state.  While we welcome comments and
suggestions, we do not promise ANY support.

You will be happy to find numerous new features and bug fixes...
* Many classes of the Morphic framework are operational.  Try...
	WorldMorph test open.
	Try out the ScrollThing.  Read its class comment, and that of MorphicModel.
* Much of the Socket code works.  Try the examples in Socket.
	If this is up your alley, check with us -- we have a plan for the
	next steps, but we could use some help finishing it.
* SampledSound can read AIFF files, so you can record your dog
	and use it to play the Back Fugue.  For a demo, try...
	SampledSound useCoffeeCupClink bachFugue play
* SeqCollection>>allButFirst and allButLast now match first and last
* Object>>ifNil: and ifNotNil: now aid brevity
* BitBlt bug displaying lines out of range is fixed (reported by Carl Watts)
* WarpBlt is now bit-perfect in several places where it wasn't before
	(See the consistency tests in Form magnify: and rotate:)
* Demos are included of painting with alphaBlending and anti-aliasing,
	even when your screen is in 8-bit mode (See BitBlt>examples)
* Class variables appear alphabetically in class definitions
* Searches for uses of 'super' are fixed
* Cursor keys work on the Mac, thanks to Rick Taylor
* Scoll bars are more compact, thanks to Stephen Pope
* BitBlt now has several new color modes sugested by Carl Watts
	(See the class comment)
* Display newDepth: now estimates space properly
* FFT is included with this image
* InfiniteForms now work fast enough for backgorunds.
	Try, eg, (looks better in 16 bits)...
	Preferences desktopColor: ((Form extent: 50@50 depth: 16)
			fillFromXYColorBlock:
			[:x :y |  Color r: (1.0 - (x - 0.5) abs - (y - 0.5) abs) g: 0.0
						b: 1.0-(1.0 - (x - 0.5) abs - (y - 0.5) abs)]).
	ScheduledControllers updateGray; restore.
* IdentitySets and Dictionaries now hash correctly.  Both hash
	and lookup are bundled in a solitary method for easy subclassing.
* Our Random class now follows the Park-Miller method, thanks to
	David Smith, and runs even faster than before, thanks to me.
* Spy reports now catch multiple ticks on a given (eg primitive) method.
* The spelling corrector now removes temp names properly in all cases.
* A SystemTracer has been included that is 90% the way to working

-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-=-


 Stephen Travis Pope, Center for Research in Electronic Art Technology
 (CREATE), Department of Music, U. of California, Santa Barbara (UCSB)
 Editor--Computer Music Journal, MIT Press
 stp@create.ucsb.edu,   http://www.create.ucsb.edu/~stp/



Post a reply.

Go back to index.



Date: 97 Apr 01 11:56:03 am From: Ken Gentry <kgentry@eurpd.csg.mot.com> To: squeak@create.ucsb.edu Subject: Stripping of var names & comments I have the feeling that this question has been asked MANY times, but I couldn't find an FAQ for Squeak... I type out a new method with lots of descriptive argument & temp variable names and comments, choose 'accept' and WHAMMY! I get t1, t2..., comments are gone and I find that all of my nice indention for making readable code is destroyed. Can I turn off this "optimizing" step so that I can presevre my self documenting code (and semantic intent)? Any help provided is GREATLY appreciated. Sincerely, Ken Gentry -- ______________________________________________________________________________ Ken Gentry - KD4WNV GSM Product Development Software Engineer Motorola Cellular Subscriber Group kgentry@eurpd.csg.mot.com 600 N. Hwy 45, Mail Stop DS229 Libertyville, IL 60048 Voice (847) 523-5603 Fax (847) 523-1306 pager (847) 576-0295 ID: 11298 "Program comments are for sissys! If it was hard to write, it should be hard to understand!" - Anonymous (satirical excerpt from a computer science text)

Post a reply.

Go back to index.



Date: 97 Apr 01 5:32:35 pm From: stp (Stephen Travis Pope) To: kgentry@eurpd.csg.mot.com, squeak@create.ucsb.edu In-Reply-To: Ken Gentry <kgentry@eurpd.csg.mot.com>'s letter of: 97 Apr 01 Subject: Re: Stripping of var names & comments > I type out a new method with lots of descriptive argument & temp variable > names and comments, choose 'accept' and WHAMMY! I get t1, t2..., comments are > gone and I find that all of my nice indention for making readable code is destroyed. This is not an optimization, but a sgn that there is something gravely wrong with your source and/or changes files. Make sure you have write permission to the changes file. stp _Stephen Travis Pope, Center for Research in Electronic Art Technology _(CREATE), Dept. of Music, U. of California, Santa Barbara (UCSB) _Editor, Computer Music Journal (CMJ), MIT Press _stp@create.ucsb.edu http://www.create.ucsb.edu/~stp/

Post a reply.

Go back to index.



Date: 97 Apr 01 6:29:17 pm From: Dan Ingalls <DanI@wdi.disney.com> To: Squeak@create.ucsb.edu Subject: Oops - missing method Folks - There seems to be an early April Fool's trick in the late(*) Easter Egg. Some of the Morphic examples in that image will require (in case you haven't already figured it out)... !Object methodsFor: 'testing'! notNil: notNilBlock "Support vestigial senders of notNil: " ^ self ifNotNil: notNilBlock! ! (* Hans-Martin, we decided Mrs. Mosner should have your full attention over Easter weekend ;-)

Post a reply.

Go back to index.



Date: 97 Apr 02 9:05:30 am From: "Andreas Raab" <raab@isg.cs.uni-magdeburg.de> To: stp@create.ucsb.edu Cc: squeak@create.ucsb.edu Subject: 1.19 Sockets Hi, > * Much of the Socket code works. Try the examples in Socket. > If this is up your alley, check with us -- we have a plan for the > next steps, but we could use some help finishing it. After having a first look at the net interface I was somewhat puzzled - it looks very complicated to me. I have used the BSD sockets for some time on different platforms (e.g. Unix/Windows) and thought this would be the way to go. In fact, I noticed some strange behaviour such as when accepting incoming communication request (i.e. when acting as a server). In this case BSD creates a new socket to allow the listening socket to have multiple clients. As it is implemented right now, on each incoming connection one has to start a new socket to accept further connections. Although this is not hard to do I think that a number of people will expect the BSD behaviour. BTW, there is a documentation problem in the Socket>>createNetwork:... method. It states that socketType 0 would be UDP and 1 TCP but the VM goes the other way around. Bye, Andreas -- Linear algebra is your friend - Trigonometry is your enemy. +===== Andreas Raab ============= (raab@isg.cs.uni-magdeburg.de) =====+ I Department of Simulation and Graphics Phone: +49 391 671 8065 I I University of Magdeburg, Germany Fax: +49 391 671 1164 I +=============< http://simsrv.cs.uni-magdeburg.de/~raab >=============+

Post a reply.

Go back to index.



Date: 97 Apr 02 12:11:38 pm From: Maloney <johnm@wdi.disney.com> To: "Andreas Raab" <raab@isgnw.cs.Uni-Magdeburg.DE> Cc: squeak@create.ucsb.edu In-Reply-To: <16D035466B5@isgnw.cs.uni-magdeburg.de> Subject: Re: 1.19 Sockets Andreas (and others interested in sockets): The 1.19 socket stuff is just a first pass. We've already decided to make the interface more like BSD sockets with respect to accepting incoming connections. (The Mac interface is odd-man out here, and we'll just accept the burden of conforming to the BSD conventions.) Another weakness of the current implementation is that it is not yet semaphore-based; it uses polling to discover when data has arrived, connections have been made, etc. In the longer term, each socket will have a single semaphore that will be used to to signal that something interesting has happened. The will be a "broadcast semaphore": all processes waiting on it will be awoken when it is signalled. Each process will then be responsible for checking to see if the condition for which it is waiting (e.g. data arrival) has been met and, if not, then going back to sleep on the semaphore. One could thus have Smalltalk processes sending, receiving, and watching for connection failures on the same socket. There will be a timeout mechanism to ensure that the semaphore will be signalled even if the connection has broken. The final point of uncertainty is the parameters that should be provided to the socket creation call. You'll note that network addresses are represented as arbitrary-sized byte arrays, allowing the Squeak socket interface to be used for protocols other than TCP/IP. I'd like to keep the door open to such extentions in the future without adding too much complexity. I'd be happy to hear comments from anyone who has used non-TCP/IP protocols. I'd love to hear from anyone planning to port the socket interface to another platform. -- John P.S. Thanks for pointing out the UDP/TCP comment discrepancy. I meant to make it like BSD; I'll fix either the comment or the implementation to make them consistent in the next version. >Hi, > >> * Much of the Socket code works. Try the examples in Socket. >> If this is up your alley, check with us -- we have a plan for the >> next steps, but we could use some help finishing it. > >After having a first look at the net interface I was somewhat puzzled >- it looks very complicated to me. I have used the BSD sockets for >some time on different platforms (e.g. Unix/Windows) and thought >this would be the way to go. In fact, I noticed some strange >behaviour such as when accepting incoming communication request (i.e. >when acting as a server). In this case BSD creates a new socket to >allow the listening socket to have multiple clients. As it is >implemented right now, on each incoming connection one has to start >a new socket to accept further connections. Although this is not hard >to do I think that a number of people will expect the BSD behaviour. > >BTW, there is a documentation problem in the Socket>>createNetwork:... >method. It states that socketType 0 would be UDP and 1 TCP but the VM >goes the other way around. > >Bye, > Andreas >-- >Linear algebra is your friend - Trigonometry is your enemy. >+===== Andreas Raab ============= (raab@isg.cs.uni-magdeburg.de) =====+ >I Department of Simulation and Graphics Phone: +49 391 671 8065 I >I University of Magdeburg, Germany Fax: +49 391 671 1164 I >+=============< http://simsrv.cs.uni-magdeburg.de/~raab >=============+

Post a reply.

Go back to index.



Date: 97 Apr 02 1:31:59 pm From: Dan Ingalls <DanI@wdi.disney.com> To: Squeak@create.ucsb.edu In-Reply-To: <9704011734.AA21960@tango.create.ucsb.edu> Subject: Re: Squeak 1.19_beta now available! A couple of other items... >* Searches for uses of 'super' are fixed >* IdentitySets and Dictionaries now hash correctly. Both hash > and lookup are bundled in a solitary method for easy subclassing. I forgot to credit the report of these to Paul McCullough >* BitBlt now has several new color modes sugested by Carl Watts > (See the class comment) While this is true, the BB init code still checks the old limit and fails! Sorry 'bout that. After the dust settles a bit (say in a week), I'll assemble a file of corrections to this beta, along with a new VM to make things easier. - Dan

Post a reply.

Go back to index.



Date: 97 Apr 03 9:27:54 am From: "Andreas Raab" <raab@isg.cs.uni-magdeburg.de> To: stp@create.ucsb.edu Cc: squeak@create.ucsb.edu Subject: A note on ioMSecs() Hi, I just found some interesting behaviour in the ioMSecs() call from the VM. If the value returned by the call is larger than the maximum SmallInteger value you may end up in some serious problems. In this case the value is converted into a LargePositiveInteger (which is not the problem) and may be used as the resumptionTime for a Delay (see Delay>>wait). If the Delay is activated later the Processor>>signal:atTime: primitive will fail (the value is no SmallInteger!). The problem is that this may happen in a critical protection lock forcing some odd behaviour later. I'm not sure how to deal with that. Is it essential that there are no roll-overs between to successive calls to ioMsecs()? If not, we could simply require the value returned by ioMsecs to fit into a SmallInteger. Any ideas? - Andreas -- Linear algebra is your friend - Trigonometry is your enemy. +===== Andreas Raab ============= (raab@isg.cs.uni-magdeburg.de) =====+ I Department of Simulation and Graphics Phone: +49 391 671 8065 I I University of Magdeburg, Germany Fax: +49 391 671 1164 I +=============< http://simsrv.cs.uni-magdeburg.de/~raab >=============+

Post a reply.

Go back to index.



Date: 97 Apr 03 12:04:55 pm From: Tim Rowledge <rowledge@interval.com> To: Squeak mailinglist <squeak@create.ucsb.edu> Subject: Patch for Little Endian bitblt code Whilst making sure that my little endian bitblt code worked ok with Andreas' NT port (which it does, very nicely, makes screen updates a bit faster) I discovered that a) Microsoft use 'LittleEndian' as a global variable, so I changed the #define name to LITTLE_ENDIAN b) I had failed to make the image global ImageIsLittleEndian actually be a global (it's in Undeclared) The changes are incorporated in the latest version of LEBitBlt, dated 3 April 97, on my squeak-site at sumeru (see below) tim -- Tim Rowledge: rowledge@interval.com (w) +1 (415) 856-7230 (w) tim@sumeru.stanford.edu (h) <http://sumeru.stanford.edu/tim>

Post a reply.

Go back to index.



Date: 97 Apr 03 11:29:58 pm From: Hans-Martin Mosner <hmm@heeg.de> To: squeak@create.ucsb.edu Subject: Morphic - Comments and Code Hello everybody, last evening I could spend a few hours with Morphic, and this is what came out of it: Comments: I like it, even as unfinished at it is. It's a tad sluggish, but I imagine that this will improve over time. There are 3 general points I'd like to make: 1. handling mouse events is somewhat ugly. I'd like to have a mechanism so that the Morph having the mouse focus can save some state without having to reserve inst vars for it. The SimpleButtonMorph is a good example: It has to save the color it had before activation so that it can be restored when it's finished. The hand would probably be a good place to store such dynamic state. 2. LayoutMorph must allow for the distinction between: - Morphs that are fixed in extent - Morphs that are variable in extent and can be adjusted by the LayoutMorph - Morphs that do themselves layout their submorphs. The current implementation mixes together the second and third behavior. 3. The SimpleButtonMorph should be customizable to execute its action either - when the mouse is released within the morph (current behavior) - as long as the mouse is pressed within the morph (good for scroller buttons) - as long as the mouse is pressed, even if it is outside (good for a scrollbar marker) In the scrolling code below, I've made subclasses for this, but I do not think that's the nicest solution. 4. I still don't know whether it's a good idea that every morph knows its absolute position. Sure, it avoids offset calculations when redrawing and propagating damage, but I don't see an easy solution for the problem of translating mouse events for scrolled components. If you put a button inside a ScrollClipTestMorph, you will see what I mean. If you see a good way of getting mouse events translated in this case, I would favor keeping the absolute position mechanism. It costs a little when morphs are moved, but even with moderately populated morphs the cost seems tolerable. Code: There are a couple of minor bug fixes and improvements, and two extensions. The extensions cover the following: 1. Raised and inset borders. RectangleMorph can have a borderColor of #raised or #inset, in which case its border is drawn as a 3-d border. Note that the color for the border is computed from the morph itself if it is #raised, but from its owner if it is #inset. In my eyes, this is the most reasonable visual behavior. It could be changed to accept #inset, #raised, #ownerInset and #ownerRaised for all combinations. 2. A ScrollBarMorph that can be used together with the ScrollClipTestMorph. It's still crude because the marker position etc. are not computed right. It just shows how it could look. Pardon the liberal mixed use of := and _ for assignment. The former is normally what I typed, and the latter is what was in the methods when I copied/modified them. Have fun! Hans-Martin And here is the code: -------- Fix for canvas clipping. Needed so that the ScrollClipTestMorph works. !Canvas methodsFor: 'accessing'! clipRect ^ clipRect translateBy: origin negated! ! -------- A Fix for clipped text display: !FormCanvas methodsFor: 'drawing'! text: s at: pt font: aFontSpecification color: c | para | para _ s asParagraph. para foregroundColor: ((shadowDrawing or: [form depth > 8 and: [c = Color black]]) ifTrue: [opaqueBlack] ifFalse: [c]) backgroundColor: Color none. para displayOn: form at: (pt + origin) clippingBox: clipRect rule: (self drawRule: Form paint) fillColor: (shadowDrawing ifTrue: [self drawColor: c] ifFalse: [nil]). ! ! -------- Improvement for mapping colors to two-tone patterns. This maps according to luminance. Sorry for the decompiled code in the bitPatternForDepth: method; I wrote it when the sources were not accessible, and don't have the time now to fix it up. !Color methodsFor: 'access'! luminance ^299* self privateRed + (587 * self privateGreen) + (114 * self privateBlue) / (1000*ComponentMax)! ! !Color methodsFor: 'conversions'! bitPatternForDepth: t1 | b | t1 == cachedDepth ifTrue: [^ cachedBitPattern]. cachedDepth _ t1. t1 > 1 ifTrue: [^ cachedBitPattern _ Bitmap with: (self pixelWordForDepth: t1)]. b := self luminance. b < 0.2 ifTrue: [^ cachedBitPattern _ Bitmap with: 4294967295]. b < 0.4 ifTrue: [^ cachedBitPattern _ Bitmap with: 3149642683 with: 4008636142]. b < 0.6 ifTrue: [^ cachedBitPattern _ Bitmap with: 1431655765 with: 2863311530]. b < 0.8 ifTrue: [^ cachedBitPattern _ Bitmap with: 1145324612 with: 286331153]. ^ cachedBitPattern _ Bitmap with: 0! ! -------- Fix for HeadingMorph: makes it work ok even if the border width is set. !HeadingMorph methodsFor: 'drawing'! drawOn: aCanvas | x y r center box | super drawOn: aCanvas. box := self innerBounds. 1 to: 9 do: [:i | x _ box left + ((box width * i) // 10). aCanvas line: (x@box top) to: (x@(box bottom - 1)) color: Color black. y _ box top + ((box height * i) // 10). aCanvas line: (box left@y) to: ((box right - 1)@y) color: Color black]. r _ ((box width asFloat * magnitude asFloat) / 2.0) - 1.0. center _ box center. self drawArrowFrom: center - (1@1) to: center + ((r * degrees degreesToRadians cos)@0) - (1@1) width: 3 color: (Color red) on: aCanvas. self drawArrowFrom: center - (1@1) to: center + (0@(r * degrees degreesToRadians sin)) - (1@1) width: 3 color: (Color red) on: aCanvas. self drawArrowFrom: center - (1@1) to: center + (Point r: r degrees: degrees) - (1@1) width: 3 color: Color black on: aCanvas. ! ! -------- PackingMorph initialization forgot to initialize the pointer. It's still pretty useless, but at least it doesn't crash with this fix: !PackingMorph methodsFor: 'all'! initialize super initialize. pointer := 1. padding _ 3. openToDragNDrop _ false. color _ Color r: 0.8 g: 1.0 b: 0.6. self borderWidth: 1. ! ! -------- And here comes the #raised and #inset border extension: !FormCanvas methodsFor: 'drawing'! frameRectangle: r width: w topColor: top leftColor: left rightColor: right bottomColor: bottom | rect | port combinationRule: (self drawRule: Form over); width: w; height: w. rect := r translateBy: origin. port fillColor: (self drawColor: top); frameRectTop: rect. port fillColor: (self drawColor: left); frameRectLeft: rect. port fillColor: (self drawColor: right); frameRectRight: rect. port fillColor: (self drawColor: bottom); frameRectBottom: rect. ! ! !GrafPort methodsFor: 'QuickDraw protocol'! frameRectBottom: rect | w h | w _ width. h _ height. sourceForm _ nil. destX := rect left+1. destY := rect bottom-1. width := rect width-2. height := 1. 1 to: h do: [:i | self copyBits. destX := destX+1. destY := destY-1. width := width-2]. width _ w. height _ h. ! frameRectLeft: rect | w h | w _ width. h _ height. sourceForm _ nil. width := 1. height := rect height. destX := rect left. destY := rect top. 1 to: w do: [:i | self copyBits. destX := destX+1. destY := destY+1. height := height-2]. width _ w. height _ h. ! frameRectRight: rect | w h | w _ width. h _ height. sourceForm _ nil. width := 1. height := rect height-1. destX := rect right-1. destY := rect top+1. 1 to: w do: [:i | self copyBits. destX := destX-1. destY := destY+1. height := height-2]. width _ w. height _ h. ! frameRectTop: rect | w h | w _ width. h _ height. sourceForm _ nil. destX := rect left+1. destY := rect top. width := rect width-1. height := 1. 1 to: h do: [:i | self copyBits. destX := destX+1. destY := destY+1. width := width-2]. width _ w. height _ h. ! ! !RectangleMorph methodsFor: 'drawing'! drawOn: aCanvas "Draw with inset or raised border if requested. Note: the raised border color is generated from the Morph's own color, while the inset border color is generated from its owner. This behavior is visually more consistent." | darker lighter | color ifNotNil: [aCanvas fillRectangle: bounds color: color]. borderColor == nil ifTrue: ["no need to draw" ^self]. borderWidth = 0 ifTrue: ["no border" ^self]. false ifTrue: [(aCanvas clipRect contains: (bounds insetBy: borderWidth)) ifTrue: ["area to display completely inside border" ^self]]. borderColor == #raised ifTrue: [ darker := color darker. lighter := color lighter. aCanvas frameRectangle: bounds width: borderWidth topColor: lighter leftColor: lighter rightColor: darker bottomColor: darker. ^self]. borderColor == #inset ifTrue: [ darker := owner color darker. lighter := owner color lighter. aCanvas frameRectangle: bounds width: borderWidth topColor: darker leftColor: darker rightColor: lighter bottomColor: lighter. ^self]. aCanvas frameRectangle: bounds width: borderWidth color: borderColor ! ! -------- And here is the scrolling example. To use, create a LayoutMorph, a ScrollClipTestMorph and a ScrollBarMorph. Put something into the ScrollClipTestMorph so you see the scrolling effect later on. And while you're at it, change that ugly blue color to something more friendly. Put the ScrollClipTestMorph and the ScrollBarMorph into the LayoutMorph (in that order). The scroll bar should be at the left side. Then you can use the scrollbar buttons to affect the ScrollClipTestMorph. As I said, the marker sizing etc. does not work yet. Morph subclass: #ImageMorph instanceVariableNames: 'image ' classVariableNames: '' poolDictionaries: '' category: 'Morphic-hmm'! RectangleMorph subclass: #ScrollBarMorph instanceVariableNames: 'vertical upButton downButton marker topFraction bottomFraction ' classVariableNames: 'DownArrow UpArrow ' poolDictionaries: '' category: 'Morphic-hmm'! SimpleButtonMorph subclass: #ActiveWhilePressedButtonMorph instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Morphic-hmm'! ActiveWhilePressedButtonMorph subclass: #ScrollBarMarkerMorph instanceVariableNames: 'offset ' classVariableNames: '' poolDictionaries: '' category: 'Morphic-hmm'! !ImageMorph methodsFor: 'all'! drawOn: aCanvas aCanvas image: image at: bounds origin! extent ^image extent! extent: aPoint super extent: image extent! image: anImage image := anImage. self extent: anImage extent! ! !ScrollBarMorph methodsFor: 'initialize-release'! initialize super initialize. bounds := 0@0 corner: 16@100. color := Color gray. borderColor := #inset. borderWidth := 2. topFraction := 0.1. bottomFraction := 0.5. self initializeUpButton; initializeDownButton; initializeMarker! initializeDownButton downButton := ActiveWhilePressedButtonMorph newBounds: (bounds corner- (14@14) extent: 12@12) color: Color lightGray. downButton target: self; actionSelector: #scrollDown. downButton removeAllMorphs. downButton addMorph: (ImageMorph new image: DownArrow; position: 2@2+downButton position). downButton setBorderWidth: 2 borderColor: #raised. self addMorph: downButton! initializeMarker marker := ScrollBarMarkerMorph newBounds: (bounds origin + (2@16) extent: bounds extent-(4@32)) color: Color lightGray. marker target: self; actionSelector: #scrollAbsolute:. marker removeAllMorphs. marker setBorderWidth: 2 borderColor: #raised. self computeMarker. self addMorph: marker! initializeUpButton upButton := ActiveWhilePressedButtonMorph newBounds: (bounds origin + (2@2) extent: 12@12) color: Color lightGray. upButton target: self; actionSelector: #scrollUp. upButton removeAllMorphs. upButton addMorph: (ImageMorph new image: UpArrow; position: 2@2+ upButton position). upButton setBorderWidth: 2 borderColor: #raised. self addMorph: upButton! ! !ScrollBarMorph methodsFor: 'menu'! addCustomMenuItems: aCustomMenu hand: aHandMorph super addCustomMenuItems: aCustomMenu hand: aHandMorph. aCustomMenu add: 'set scrolled morph' action: #setScrolledMorph! ! !ScrollBarMorph methodsFor: 'geometry'! computeMarker | totalArea scrolled | totalArea := self totalMarkerArea. marker bounds: (totalArea left@(totalArea top + (totalArea height * topFraction))rounded corner: totalArea right@(totalArea top + (totalArea height * bottomFraction))rounded). scrolled := self scrolledMorph. scrolled ifNotNil: [scrolled scrollOffset: 0@(topFraction negated * scrolled superFullBounds height) rounded]. ! extent: aPoint super extent: 16@(aPoint y max: 48). downButton position: bounds corner-(14@14). self computeMarker! minHeight ^48! minWidth ^16! totalMarkerArea ^upButton bounds bottomLeft corner: downButton bounds topRight! ! !ScrollBarMorph methodsFor: 'classification'! hResizing ^false! isLayoutMorph ^true! layoutInExtent: aPoint self extent: aPoint! vResizing ^true! ! !ScrollBarMorph methodsFor: 'scrolling'! scrollAbsolute: pt | area f | area := self totalMarkerArea. f := pt y - area top / area height asFloat. topFraction := (f max: 0) min: 0.9. bottomFraction := (f + 0.2 max: 0.1) min: 1. self computeMarker! scrollDown topFraction := topFraction + 0.05 min: 0.9. bottomFraction := bottomFraction + 0.05 min: 1. self computeMarker! scrolledMorph | sub i scrolled | owner == nil ifTrue: [^nil]. sub := owner submorphs. i := sub indexOf: self. i > 0 ifFalse: [^nil]. i < sub size ifFalse: [^nil]. scrolled := sub at: i+1. (scrolled isKindOf: ScrollClipTestMorph) ifFalse: [^nil]. ^scrolled ! scrollUp | scrolled | scrolled := self scrolledMorph. scrolled ifNotNil: [scrolled scrollOffset: scrolled scrollOffset + (0@2)]. topFraction := topFraction - 0.05 max: 0. bottomFraction := bottomFraction - 0.05 max: 0.1. self computeMarker! ! !ScrollBarMorph class methodsFor: 'class initialization'! initialize "ScrollBarMorph initialize" UpArrow := Form extent: 8@8 fromArray: #( 0 402653184 1006632960 2113929216 402653184 402653184 402653184 0) offset: 0@0. DownArrow := UpArrow flipBy: #vertical centerAt: 0@0! ! !ScrollClipTestMorph methodsFor: 'geometry'! superFullBounds fullBounds := nil. ^super fullBounds! ! !SimpleButtonMorph methodsFor: 'initialization'! initialize super initialize. self borderWidth: 1. self borderColor: #raised. self color: (Color r: 0.4 g: 0.8 b: 0.6). target _ nil. actionSelector _ #flash. arguments _ EmptyArray. self label: 'Flash'. ! ! !ActiveWhilePressedButtonMorph methodsFor: 'events'! mouseMove: evt (self containsPoint: evt cursorPoint) ifTrue: [self color: (oldColor mixed: 1/2 with: Color white). self performAction] ifFalse: [self color: oldColor]. ! mouseUp: evt self color: oldColor! performAction (target ~~ nil and: [actionSelector ~~ nil]) ifTrue: [ target perform: actionSelector withArguments: arguments]. ! ! !ScrollBarMarkerMorph methodsFor: 'events'! mouseDown: evt super mouseDown: evt. self color: (oldColor mixed: 1/2 with: Color white). offset := evt cursorPoint-self position! mouseMove: evt target perform: actionSelector with: evt cursorPoint - offset! ! ScrollBarMorph initialize!

Post a reply.

Go back to index.



Date: 97 Apr 05 9:48:53 am From: Ward Cunningham <ward@c2.com> To: squeak@create.ucsb.edu Subject: Portin' Plumbin' I have an old Tektronix-Smalltalk program that created icons with code like the following: ^ Form extent: 40 @ 40 fromArray: #(4 32 0 7 65504 0 1 128 0 1 128 0 1 128 0 1 128 0 1 128 0 1 128 0 1 128 0 1 128 0 1 128 0 1 65408 0 0 0 0 3 65472 0 0 0 0 3 65472 0 0 0 0 3 65472 0 0 0 0 0 1280 0 0 2560 0 0 5120 0 0 10752 0 0 21504 0 0 43520 0 0 21760 0 0 43520 0 1 21760 0 0 43648 0 1 21760 0 0 43648 0 1 21760 0 0 43648 0 0 21760 0 0 43520 0 0 5120 0 0 0 0 0 0 0 0 0 0 0 0 0 ) offset: 0 @ 0 Although this code runs on my Win95 pc without complaint under Squeak 1.18, the images don't come out right. (They are hard to describe. They are streched out vertically and appear to be wraped back over themselves.) Any leads or quick tips to guide my further investigation? Thanks. -- Ward -- Ward Cunningham v 503-245-5633 mailto:ward@c2.com f 503-246-5587 http://c2.com/

Post a reply.

Go back to index.



Date: 97 Apr 05 11:16:48 am From: Dan Ingalls <DanI@wdi.disney.com> To: Ward Cunningham <ward@c2.com> Cc: Squeak@create.ucsb.edu In-Reply-To: <334692F9.6624@c2.com> Subject: Re: Portin' Plumbin' --============_-1351853661==_============ Content-Type: text/plain; charset="us-ascii" Ward - Yes, I had this problem when porting some old software forward to Squeak. The attached method should cause such array-inits to work. It assumes, if the size of the array is too great, that it should try reconstructing it according to the old 16-bit mapping. Hope this helps (and pls let me know how Plumbin' is goin') - Dan >I have an old Tektronix-Smalltalk program that created icons with code >like the following: > > ^ Form > extent: 40 @ 40 > fromArray: #(4 32 0 7 65504 0 1 128 0 1 128 0 1 128 0 1 128 0 1 128 0 >1 128 0 1 128 0 1 128 0 1 128 0 1 65408 0 0 0 0 3 65472 0 0 0 0 3 65472 >0 0 0 0 3 65472 0 0 0 0 0 1280 0 0 2560 0 0 5120 0 0 10752 0 0 21504 0 0 >43520 0 0 21760 0 0 43520 0 1 21760 0 0 43648 0 1 21760 0 0 43648 0 1 >21760 0 0 43648 0 0 21760 0 0 43520 0 0 5120 0 0 0 0 0 0 0 0 0 0 0 0 0 ) > offset: 0 @ 0 > >Although this code runs on my Win95 pc without complaint under Squeak >1.18, the images don't come out right. (They are hard to describe. They >are streched out vertically and appear to be wraped back over >themselves.) > >Any leads or quick tips to guide my further investigation? > >Thanks. -- Ward --============_-1351853661==_============ Content-Type: text/plain; name="Form-initFromArray.st"; charset="us-ascii" Content-Disposition: attachment; filename="Form-initFromArray.st" !Form methodsFor: 'private'! initFromArray: array "Fill the bitmap from array. If the array is shorter, then cycle around in its contents until the bitmap is filled." | ax aSize array32 i j word16 | ax _ 0. aSize _ array size. aSize > bits size ifTrue: ["backward compatibility with old 16-bit bitmaps and their forms" array32 _ Array new: height * (width + 31 // 32). i _ j _ 0. 1 to: height do: [:y | 1 to: width+15//16 do: [:x16 | word16 _ array at: (i _ i + 1). x16 odd ifTrue: [array32 at: (j _ j+1) put: (word16 bitShift: 16)] ifFalse: [array32 at: j put: ((array32 at: j) bitOr: word16)]]]. ^ self initFromArray: array32]. 1 to: bits size do: [:index | (ax _ ax + 1) > aSize ifTrue: [ax _ 1]. bits at: index put: (array at: ax)]! ! --============_-1351853661==_============--

Post a reply.

Go back to index.



Date: 97 Apr 05 11:18:35 am From: "Vassili Bykov" <vbykov@cam.org> To: <squeak@create.ucsb.edu> Subject: Re: Portin' Plumbin' > From: Ward Cunningham <ward@c2.com>> > I have an old Tektronix-Smalltalk program that created icons with code > [...] > Although this code runs on my Win95 pc without complaint under Squeak > 1.18, the images don't come out right. (They are hard to describe. They > are streched out vertically and appear to be wraped back over > themselves.) > > Any leads or quick tips to guide my further investigation? Different endianness and/or different number of bits per pixel and/or different bits to pixels mapping order (that is, some systems map highest bits in a byte/word to the leftmost pixel, others--to the rightmost). This is quite possible if the array in your code is the one you used on Tektronix. --Vassili

Post a reply.

Go back to index.



Date: 97 Apr 06 7:28:20 pm From: Jecel Assumpcao Jr <jecel@lsi.usp.br> To: squeak@create.ucsb.edu Subject: Re: Morphic - Comments and Code Hans-Martin Mosner wrote: > > Hello everybody, > last evening I could spend a few hours with Morphic, and this is what came out > of it: > > Comments: > I like it, even as unfinished at it is. It's a tad sluggish, but I imagine > that this will improve over time. There are 3 general points I'd like to make: I was able to take a quick look as well. Though I didn't expect it to work, I tried running the 1.19b Mac image with a 1.18 Linux virtual machine and had a nice surprise: it ran pretty well except for complaining about missing primitives once in a while. The animations were faster than I thought they would be, given how slow my machine is (Squeak's benchmarks say it is 40 times slower than a 166MHz Pentium machine!). I was hoping to see the familiar Self demo when I called up BouncingAtomsMorph and was a bit disapointed to see how much plainer this is. On the other hand, the atoms move against a colored background - trying this in Self makes Morphics nearly grind to a halt (but that could be X's fault). In conclusion, I am really glad to see such a nice job. I hope this will set the direction for all Smalltalk implementations to follow. -- Jecel

Post a reply.

Go back to index.



Date: 97 Apr 08 1:01:12 pm From: Hans-Martin Mosner <hm.mosner@cww.de> To: Squeak Mailing List <squeak@create.ucsb.edu> Subject: 1.19 beta crashes Hello, did anybody else make the experience that Squeak 1.19 beta sometimes crashes with an unhandled #doesNotUnderstand: ? It happened 2 times on me, but I did not have the time until now to search for the cause. It happened both times when I was running Morphic, but that doesn't mean much, as I only start up 1.19 to run Morphic :-) Hans-Martin

Post a reply.

Go back to index.



Date: 97 Apr 08 1:01:14 pm From: Hans-Martin Mosner <hm.mosner@cww.de> To: Squeak Mailing List <squeak@create.ucsb.edu> Subject: More Morphic ideas Hello, I played a little with the handling of text in Morphic (StringMorphs are rather limited) and came up with 2 things: - There should be a way for a text editing morph to coalesce keyboard events. I did a simple thing in the StringMorph that just asks the event's hand whether another keyboard event is available, and avoids the recompositing and display in that case, knowing that it will receive another keyboard event in the near future. That works surprisingly well. - I tried to make a TextEditMorph that has a Paragraph for its own display, and its submorphs can be TextSelectionMorphs. The TextSelectionMorph is the one that has keyboard focus, making read-only text and multiple selection quite easy. It's not really working yet, because I did not have time enough to make the selection start and stop blocks react properly to moving, but it's a start. Do you people in the inner circle have some text editing working yet? Hans-Martin

Post a reply.

Go back to index.



Date: 97 Apr 09 12:23:19 am From: Georg Gollmann <gollmann@edvz.tuwien.ac.at> To: hm.mosner@cww.de, Squeak Mailing List <squeak@create.ucsb.edu> In-Reply-To: <334AA65B.17E6@cww.de> Subject: Re: 1.19 beta crashes At 22:11 Uhr +0200 8.4.1997, Hans-Martin Mosner wrote: >Hello, >did anybody else make the experience that Squeak 1.19 beta sometimes >crashes with an unhandled #doesNotUnderstand: ? >It happened 2 times on me, but I did not have the time until now to >search for the cause. It happened both times when I was running Morphic, >but that doesn't mean much, as I only start up 1.19 to run Morphic :-) It crashed with "Error 1" on a Mac IIsi with System 7.5.1. 1.18 ran fine albeit rather slowly. Georg ---- Dipl.Ing. Georg Gollmann TU-Wien, EDV-Zentrum phon:(+43-1) 58801 - 5848 fax: (+43-1) 587 42 11 mail:gollmann@edvz.tuwien.ac.at http://ftp.tuwien.ac.at/~go/Gollmann.html

Post a reply.

Go back to index.



Date: 97 Apr 09 2:23:31 am From: Georg Gollmann <gollmann@edvz.tuwien.ac.at> To: squeak@create.ucsb.edu Subject: String>hash Hello, I have found the String>hash method to be inadequate for my needs: - hash keys are too short, so large Sets or Dictionarys won´t work well - strings with a certain regularity, like message-ids, hash badly Coming up with a better hash function is simple (eg CRC16), but is there an established practice of changing String>hash without breaking the system ? Thanks ! Georg ---- Dipl.Ing. Georg Gollmann TU-Wien, EDV-Zentrum phon:(+43-1) 58801 - 5848 fax: (+43-1) 587 42 11 mail:gollmann@edvz.tuwien.ac.at http://ftp.tuwien.ac.at/~go/Gollmann.html

Post a reply.

Go back to index.



Date: 97 Apr 09 5:18:27 am From: Georg Gollmann <gollmann@edvz.tuwien.ac.at> To: squeak@create.ucsb.edu Subject: error handling Hello, I have made a few minor and mostly cosmetic changes to the error handling methods. Here's the comment for <http://ftp.tuwien.ac.at/~go/Squeak/errorHandling.st>: Minor cleanup of the error handling methods already present in the image. The methods ContextPart>failureCatcher: and BlockContext>ifFail: are inoperable and therefore removed. BlockContext>ifError: and BlockContext>value:ifError: have been commented, ifError: has been changed so both methods send two parameters to the error block. Also a misleading statement in the comment of Object>doesNotUnderstand is removed. TITLE errorHandling.st AUTHOR Georg Gollmann (gollmann@edvz.tuwien.ac.at) VERSION 1.0 IMAGE VERSION 1.18 PREREQUISITES none DATE April 9, 1997 Georg ---- Dipl.Ing. Georg Gollmann TU-Wien, EDV-Zentrum phon:(+43-1) 58801 - 5848 fax: (+43-1) 587 42 11 mail:gollmann@edvz.tuwien.ac.at http://ftp.tuwien.ac.at/~go/Gollmann.html

Post a reply.

Go back to index.



Date: 97 Apr 09 8:05:10 am From: Dan Ingalls <DanI@wdi.disney.com> To: hm.mosner@cww.de Cc: Squeak@create.ucsb.edu In-Reply-To: <334AA65B.17E6@cww.de> Subject: Re: 1.19 beta crashes >Hello, >did anybody else make the experience that Squeak 1.19 beta sometimes >crashes with an unhandled #doesNotUnderstand: ? >It happened 2 times on me, but I did not have the time until now to >search for the cause. It happened both times when I was running Morphic, >but that doesn't mean much, as I only start up 1.19 to run Morphic :-) Yes, we have discovered a bug in 1.19. Specifically, the clone primitive <148> can cause crashes. This is only used in new morphic code, so the rest of the system should be stable. The fix is very simple: !Object methodsFor: 'copying'! clone "Prim 148 temporarily quarantined due to a bug... <primitive: 148> self primitiveFailed" ^ self shallowCopy! ! I hope to send out several other features and fixes for 1.19 in the next day or so. _ dan

Post a reply.

Go back to index.



Date: 97 Apr 09 10:11:43 am From: Maloney <johnm@wdi.disney.com> To: hm.mosner@cww.de Cc: squeak@create.ucsb.edu In-Reply-To: <334AA7AF.47C5@cww.de> Subject: Re: More Morphic ideas Hans-Martin, Your look-ahead trick for StringMorph's is a good idea. StringMorph's were really not meant to be edited; the editing was put in just to test the keyboard focus mechanism. We do plan to make a real text editor in Morphic, one that supports multiple fonts and embedded morphs. We haven't started on it yet, but we'll probably be needing it soon. We'd be happy to look at anything you do along those lines. -- John

Post a reply.

Go back to index.



Date: 97 Apr 09 10:12:07 am From: Maloney <johnm@wdi.disney.com> To: Georg Gollmann <gollmann@edvz.tuwien.ac.at> Cc: squeak@create.ucsb.edu In-Reply-To: <v03020904af7109a21680@[128.130.36.64]> Subject: Re: String>hash Georg: Re: Coming up with a better hash function is simple (eg CRC16) Wouldn't this be rather slow, especially for long strings? I'd be inclined to try a function that combined a set of N characters evenly distributed through the string (possibly avoiding the final character which is likely to be a colon for keyword selectors). Another approach would be to use the primitive maker to turn your CRC method into a primitive. It might still be slow for long strings. I think if you change the hash function and immediately rehash all the sets and dictionary instances in the system, you should be okay. Good luck! -- John

Post a reply.

Go back to index.



Date: 97 Apr 09 10:54:38 am From: "David N. Smith" <dnsmith@watson.ibm.com> To: Georg Gollmann <gollmann@edvz.tuwien.ac.at> Cc: squeak@create.ucsb.edu In-Reply-To: <v03020904af7109a21680@[128.130.36.64]> Subject: Re: String>hash At 4:27 -0500 4/9/97, Georg Gollmann wrote: >Hello, > >I have found the String>hash method to be inadequate for my needs: > >- hash keys are too short, so large Sets or Dictionarys won=B4t work well >- strings with a certain regularity, like message-ids, hash badly > >Coming up with a better hash function is simple (eg CRC16), but is there an >established practice of changing String>hash without breaking the system ? > >Thanks ! >Georg > >---- >Dipl.Ing. Georg Gollmann TU-Wien, EDV-Zentrum > >phon:(+43-1) 58801 - 5848 >fax: (+43-1) 587 42 11 >mail:gollmann@edvz.tuwien.ac.at >http://ftp.tuwien.ac.at/~go/Gollmann.html Georg: In my Smalltalk FAQ (in some pages not yet released) I have some questions about hashing. I made up a stupid example of how not to do a hash on a string, then went to compare it with various implementations including Squeak and several (nameless) commercial products. My example was far better than ANY I found anywhere else. I got to searching further and found that #hash is usually extremely poorly implemented for most objects and in most systems. Strings universely fare poorly, to be kind. Some implementations do Floats well, but some ignore the fraction completely. (Try to build a dictionary with random numbers in the usual range [0.0-1.0) as keys when fractions are ignored!) It's kind of a dirty secret of Smalltalk. Dave _______________________________ David N. Smith dnsmith@watson.ibm.com IBM T J Watson Research Center Hawthorne, NY _______________________________ Any opinions or recommendations herein are those of the author and not of his employer.

Post a reply.

Go back to index.



Date: 97 Apr 09 8:32:01 pm From: Jecel Assumpcao Jr <jecel@lsi.usp.br> To: squeak@create.ucsb.edu Subject: Re: String>hash David N. Smith wrote: > In my Smalltalk FAQ (in some pages not yet released) I have some questions > about hashing. I made up a stupid example of how not to do a hash on a > string, then went to compare it with various implementations including > Squeak and several (nameless) commercial products. > > My example was far better than ANY I found anywhere else. I got to > searching further and found that #hash is usually extremely poorly > implemented for most objects and in most systems. Strings universely fare > poorly, to be kind. Some implementations do Floats well, but some ignore > the fraction completely. (Try to build a dictionary with random numbers in > the usual range [0.0-1.0) as keys when fractions are ignored!) > > It's kind of a dirty secret of Smalltalk. I'll take a look at your pages to see what your "bad" string hash looks like. But I was thinking about the old Forth trick of only saving the first three characters of names and the length in 32 bits. Maybe that could be used as the "seed" of a good hash? -- Jecel

Post a reply.

Go back to index.



Date: 97 Apr 10 12:32:02 am From: Georg Gollmann <gollmann@edvz.tuwien.ac.at> To: squeak@create.ucsb.edu Cc: squeak@create.ucsb.edu In-Reply-To: <v03007805af718ac7364d@[129.34.225.178]> Subject: Re: String>hash At 9:36 Uhr -0800 9.4.1997, Maloney wrote: >Wouldn't this be rather slow, especially for long strings? I'd be >inclined to try a function that combined a set of N characters evenly >distributed through the string (possibly avoiding the final character >which is likely to be a colon for keyword selectors). > >Another approach would be to use the primitive maker to turn your >CRC method into a primitive. It might still be slow for long strings. At 13:12 Uhr -0500 9.4.1997, David N. Smith wrote: >In my Smalltalk FAQ (in some pages not yet released) I have some questions >about hashing. I made up a stupid example of how not to do a hash on a >string, then went to compare it with various implementations including >Squeak and several (nameless) commercial products. STA uses CRC16 after I complained about the totally broken original hash method. CRC16 is a primitive in STA, so speed is not an issue. One could limit the hashing to the first 100 characters or so, but I don't think this is necessary since most strings used as dictionary keys will be shorter. NetNews message-ids tend to be in the range of 40 characters and one should use all of them for hashing as I have found out. For now I will make subclasses for Set and Dictionary to get timings on my new hashing method. Georg ---- Dipl.Ing. Georg Gollmann TU-Wien, EDV-Zentrum phon:(+43-1) 58801 - 5848 fax: (+43-1) 587 42 11 mail:gollmann@edvz.tuwien.ac.at http://ftp.tuwien.ac.at/~go/Gollmann.html

Post a reply.

Go back to index.



Date: 97 Apr 10 9:13:50 am From: Dan Ingalls <DanI@wdi.disney.com> To: Squeak@create.ucsb.edu Subject: Playing with 1.19 on non-Macs In case folks weren't aware, the Squeak 1.19 beta image should run fine on= 1.18 VMs. Thus Windows and Unix users can try out some of the new= features, and the VM maintainers can wait until the "real" 1.19 to move for= ward. Although there are a number of VM changes in 1.19, the only incompatible= ones that I can think of are minor nits in WarpBlt, which "only" affect= fractional pixel placement. For example Form rotateBy and magnifyBy will= be slightly off, as can be seen if you run the consistency checks (which= leave the screen unaffected with a 1.19 VM).

Post a reply.

Go back to index.



Date: 97 Apr 10 9:54:40 am From: "David N. Smith" <dnsmith@watson.ibm.com> To: Jecel Assumpcao Jr <jecel@lsi.usp.br> Cc: squeak@create.ucsb.edu In-Reply-To: <334C5A58.6A08BFD0@lsi.usp.br> Subject: Re: String>hash At 22:11 -0500 4/9/97, Jecel Assumpcao Jr wrote: >David N. Smith wrote: >> In my Smalltalk FAQ (in some pages not yet released) I have some questions >> about hashing. I made up a stupid example of how not to do a hash on a >> string, then went to compare it with various implementations including >> Squeak and several (nameless) commercial products. >> >> My example was far better than ANY I found anywhere else. I got to >> searching further and found that #hash is usually extremely poorly >> implemented for most objects and in most systems. Strings universely fare >> poorly, to be kind. Some implementations do Floats well, but some ignore >> the fraction completely. (Try to build a dictionary with random numbers in >> the usual range [0.0-1.0) as keys when fractions are ignored!) >> >> It's kind of a dirty secret of Smalltalk. > >I'll take a look at your pages to see what your "bad" string hash >looks like. > >But I was thinking about the old Forth trick of only saving the >first three characters of names and the length in 32 bits. >Maybe that could be used as the "seed" of a good hash? > >-- Jecel Yet yet!! Those pages are not yet up. I'm doing a revision but it is going slowly. Dave _______________________________ David N. Smith dnsmith@watson.ibm.com IBM T J Watson Research Center Hawthorne, NY _______________________________ Any opinions or recommendations herein are those of the author and not of his employer.

Post a reply.

Go back to index.



Date: 97 Apr 10 1:45:37 pm From: Dan Ingalls <DanI@wdi.disney.com> To: Squeak@create.ucsb.edu Subject: PNG Graphics Fellow Squeakers - We believe that PNG will become a significant public-domain graphics exchange standard and, thus, one that would be good to support in Squeak. Does anyone out there know of, or have, any Smalltalk code to suport it that they would like to contribute? - Dan

Post a reply.

Go back to index.



Date: 97 Apr 10 10:06:40 pm From: Jecel Assumpcao Jr <jecel@lsi.usp.br> To: squeak@create.ucsb.edu Subject: Alto On April, 1998, the Xerox Alto will be 25 years old (counting from first boot). I wanted to do something to celebrate, which is very strange since I never comemorate dates and have never seen an Alto myself. Anyway, here are some ideas: 1) Alto on a chip VLSI technology is sufficiently advanced that the whole original Alto could be easily implemented in a single chip. Then very cheap comemorative computers could be built that would run classics like Smalltalk-76, for example. I have seen information that is detailed enough for this to be done, but getting that classic software and the original microcode would be pretty hard (except for some people here, unless they are like me: I can't produce any software or schemetics from my projects before 1993). 2) "Spirit" of Alto on a chip Rather than an exact implementation, a chip could be a cleaned up 32 bit version of the Alto "style" machine, and it could run the direct descendent of the Alto software: Squeak (you didn't expect me to say Win95, did you?). The problem with this (for me) is that this is not how I would build a Smalltalk computer (the Mushroom is more my style) so it would be very tempting to improve here and there until it was a serious research project and everything was spoiled. One good thing about this idea is that it is "interesting" enough that I could get free silicon area to do it. 3) "Spirit" of Alto in software My spoil sport friend suggested this. Why not emulate the original Alto on PCs and Macs like they do with Apple ][s, Ataris, Sinclair machines and so on. A lot more people could try it (but would they want to, I ask). The problem of getting the original software is the same as in idea 1. I don't know why I come up with these crazy ideas, as if I didn't already have enough to do. I wouldn't want to "waste" more than a few weekends on this celebration (but I can design things pretty fast, so that should be enough for these ideas). People on this list would probably enjoy idea 2 most of all, but I would love to hear what you think. -- -----=============( Jecel Mattos de Assumpcao Jr )===========----- http://www.lsi.usp.br/~jecel/merlin.html | mailto:jecel@lsi.usp.br

Post a reply.

Go back to index.



Date: 97 Apr 10 10:06:17 pm From: Jecel Assumpcao Jr <jecel@lsi.usp.br> To: Squeak@create.ucsb.edu Subject: Re: Playing with 1.19 on non-Macs Dan Ingalls wrote: > > In case folks weren't aware, the Squeak 1.19 beta image should run fine on 1.18 VMs. Thus Windows and Unix users can try out some of the new features, and the VM maintainers can wait until the "real" 1.19 to move forward. > > Although there are a number of VM changes in 1.19, the only incompatible ones that I can think of are minor nits in WarpBlt, which "only" affect fractional pixel placement. For example Form rotateBy and magnifyBy will be slightly off, as can be seen if you run the consistency checks (which leave the screen unaffected with a 1.19 VM). In a previous message, I said that it mostly ran but seemed to use primitives that were not implemented in 1.18 VMs. That was actually the primitive 148 bug that has since been "worked around". I didn't have any crashes - just some error walkback windows popping up. -- Jecel

Post a reply.

Go back to index.



Date: 97 Apr 11 1:11:15 am From: Georg Gollmann <gollmann@edvz.tuwien.ac.at> To: squeak@create.ucsb.edu Subject: Hashing and dictionaries (again) Here are some preliminary results for my modified dictionary implementation: x := NewsAgent topicMap keys "keys are netnews message-ids and subject lines" x size 1678 y := Dictionary new: x size. Time millisecondsToRun: [ x do: [ :k | y at: k put: 0 ]] 23533 Time millisecondsToRun: [ x do: [ :k | y at: k ]] 24400 z := StringDictionary new: x size. Time millisecondsToRun: [ x do: [ :k | z at: k put: 0 ]] 15566 Time millisecondsToRun: [ x do: [ :k | z at: k ]] 16317 Notes: - StringDictionary uses crc16 instead of the original hash method. crc16 is defined as follows and not a primitive yet. crc16 | crc | crc := 0. self do: [:c | crc := (crc bitXor: (c asciiValue << 8)) bitAnd: 16rFFFF. 8 timesRepeat: [ (crc allMask: 16r8000) ifTrue: [ crc := ((crc << 1) bitXor: 16r1021) bitAnd: 16rFFFF ] ifFalse: [ crc := (crc << 1) bitAnd: 16rFFFF ]. ]. ]. ^crc - Timing for hashing is: Time millisecondsToRun: [ x do: [ :k | k hash ]] 50 Time millisecondsToRun: [ x do: [ :k | k crc16 ]] 15350 So making crc16 a primitive would improve StringDictionary considerably. - StringDictionary stores both keys and values in its array eliminating the Associations. This saves some space if the dictionary is reasonable full. In my example y uses 29112 bytes, z uses 17944 bytes. - message-ids are pretty much a worst case scenario for the original hash function. - For larger dictionaries the original hashing will do progressively worse since the hash keys are too small: (x detectMax: [ :k | k hash ]) hash 5766 (x detectMax: [ :k | k crc16 ]) crc16 65496 - I plan to fold my changes into the regular Set and Dictionary classes eventually. Will anybody make crc16 a primitive ? (I don't have a C compiler on my Mac.) Georg ---- Dipl.Ing. Georg Gollmann TU-Wien, EDV-Zentrum phon:(+43-1) 58801 - 5848 fax: (+43-1) 587 42 11 mail:gollmann@edvz.tuwien.ac.at http://ftp.tuwien.ac.at/~go/Gollmann.html

Post a reply.

Go back to index.



Date: 97 Apr 11 1:12:57 am From: Hans-Martin Mosner <hmm@heeg.de> To: Dan Ingalls <DanI@wdi.disney.com> Cc: Squeak@create.ucsb.edu Subject: Re: PNG Graphics Dan Ingalls wrote: > > Fellow Squeakers - > > We believe that PNG will become a significant public-domain graphics exchange standard and, thus, one that would be good to support in Squeak. Yes! > > Does anyone out there know of, or have, any Smalltalk code to suport it that they would like to contribute? > I don't know of any code. Are you aware of libpng, which is the reference implementation of the PNG standard? It should be possible to statically or dynamically link it to the Squeak VM. Of course that leaves the question of a Smalltalk interface. Looking at libpng.txt, I think that a C wrapper would be needed (the png functions themselves expect C jmpbuf's for error handling). However, I can imagine that the number of primitives needed and their complexity should be rather limited. Another point: libpng uses zlib for compression (the library that implements GNU zip). Zlib in itself would be a good library to have, too. I have managed to compile it under MPW as a shared library, but I did not yet implement primitives to call it. We probably will run out of primitive space quickly if every new library included gets its own 3-10 primitives. I think the 1.19beta sockets need some more. There are 2 immediately obvious solutions: 1. Multiplexing primitives. I think ParcPlace st80 v.2.3 had that for access to UNIX system call services. One primitive gets a function code and a couple of arguments. Somehow I don't like this very much... 2. Increase the primitive number range. This would require a change in the CompiledMethod header format. The header word currently has 29 bits of information. If we ever change the immediate object format to 2 tag bits, that leaves just one more bit for extending the primitive range if we don't want to radically change the format. Hans-Martin

Post a reply.

Go back to index.



Date: 97 Apr 11 2:22:56 am From: Ian Piumarta <piumarta@prof.inria.fr> To: DanI@wdi.disney.com, hmm@heeg.de Cc: Squeak@create.ucsb.edu Subject: Re: PNG Graphics Hans-Martin wrote: > 2. Increase the primitive number range. This would require a change in > the CompiledMethod header format. The header word currently has 29 bits of > information. If we ever change the immediate object format to 2 tag bits, > that leaves just one more bit for extending the primitive range if we > don't want to radically change the format. We could just get rid of the primitive response encoded in the method header entirely. [Lots of arguments in favour of this elided -- Ed. ;o)] Make <primitive N> an instruction which is executed on entry to the method. A little tweezing could delay the creation of the method context until after we know it isn't a primitive (or a quick response) method. You then have a potentially infinite range for primitives. Either a table which grows dynamically (allowing you to file-in code containing user primitives), or use a static table for "system" primitives < some N, and a hash table for "user" primitives > some N. Ian ------------------------------- projet SOR ------------------------------- Ian Piumarta, INRIA Rocquencourt, Internet: Ian.Piumarta@inria.fr BP105, 78153 Le Chesnay Cedex, FRANCE Voice: +33 1 39 63 52 87 ----------------------- Systemes a Objets Repartis -----------------------

Post a reply.

Go back to index.



Date: 97 Apr 11 5:33:56 am From: Georg Gollmann <gollmann@edvz.tuwien.ac.at> To: squeak@create.ucsb.edu Subject: Hashing and dictionaries (revisited) After looking at the compiler class message node I changed my crc16 method from using ´timesRepeat:´ to ´to:do:' (which gets optimized) and gained some performance improvement: z := StringDictionary new: x size. Time millisecondsToRun: [ x do: [ :k | z at: k put: 0 ]] 12533 Time millisecondsToRun: [ x do: [ :k | z at: k ]] 13366 Time millisecondsToRun: [ x do: [ :k | k crc16 ]] 12150 --- And now a question for the gurus: Interpreter class>initializeBytecodeTable has comments: "176-191 were sendArithmeticSelectorBytecode" "192-207 were sendCommonSelectorBytecode" does the "were" imply that those bytecodes are no longer supported by the VM, or are they no longer generated by the compiler (maybe because their functionality is achieved somehow else) ? Thanks ! Georg ---- Dipl.Ing. Georg Gollmann TU-Wien, EDV-Zentrum phon:(+43-1) 58801 - 5848 fax: (+43-1) 587 42 11 mail:gollmann@edvz.tuwien.ac.at http://ftp.tuwien.ac.at/~go/Gollmann.html

Post a reply.

Go back to index.



Date: 97 Apr 11 5:34:33 am From: Georg Gollmann <gollmann@edvz.tuwien.ac.at> To: squeak@create.ucsb.edu Subject: Private methods Maybe it´s old news for many but... ...while rummaging around in the compiler I found to my surprise that Squeak supports enforcement of private methods. Great! "If the code being compiled is trying to send a private message (e.g. 'pvtCheckForPvtSelector:') to anyone other than self, then complain to encoder." "Answer whether the receiver is a private message selector, that is, begins with 'pvt' followed by an uppercase letter, e.g. pvtStringhash." Georg ---- Dipl.Ing. Georg Gollmann TU-Wien, EDV-Zentrum phon:(+43-1) 58801 - 5848 fax: (+43-1) 587 42 11 mail:gollmann@edvz.tuwien.ac.at http://ftp.tuwien.ac.at/~go/Gollmann.html

Post a reply.

Go back to index.



Date: 97 Apr 11 6:24:10 am From: "Andreas Raab" <raab@isg.cs.uni-magdeburg.de> To: Pedro Gomes <pgomes@pc-lur.df.fct.unl.pt> Cc: squeak@create.ucsb.edu Subject: Re: Squeak Win32 Port! Pedro, thanks for the bug report. > While experimenting the examples in the source code of Squeak I came > across a bug in Graphic-Editors FormEditor in the big editors with load > and save. While saving a file to disk in that form Windows/NT replies with > an exception while accessing a invalid memory location. Looks like this is a problem in the FormEditor>>fileOutForm method. It calls Form>>writeOn: with a string as argument not a stream (as expected). Unfortunately, the nextPut: primitive seems to be unsafe which leads to the error. As an example, try "0 nextPut: 0" in a workspace, BUT SAVE YOUR IMAGE BEFORE DOING THIS!!! The new 1.19 beta version seems to have the safe code for this primitive (however its still beta and I'll wait until its released before releasing a new VM) but for now you may simply use the code from 1.19 which should fix this particular problem. 'From Squeak 1.19b of March 29, 1997 on 11 April 1997 at 2:27:47pm'! !FormEditor methodsFor: 'editing tools'! fileOutForm "Ask the user for a file name and then save the current source form (form) under that name. Does not change the tool." | fileName file | fileName _ self promptRequest: 'type a name for saving the source Form . . .'. file _ FileStream newFileNamed: fileName. file binary. form writeOn: file. file close. tool _ previousTool.! ! Hope this helps, Andreas -- Linear algebra is your friend - Trigonometry is your enemy. +===== Andreas Raab ============= (raab@isg.cs.uni-magdeburg.de) =====+ I Department of Simulation and Graphics Phone: +49 391 671 8065 I I University of Magdeburg, Germany Fax: +49 391 671 1164 I +=============< http://simsrv.cs.uni-magdeburg.de/~raab >=============+

Post a reply.

Go back to index.



Date: 97 Apr 11 8:14:38 am From: Dan Ingalls <DanI@wdi.disney.com> To: Hans-Martin Mosner <hmm@heeg.de> Cc: Squeak@create.ucsb.edu In-Reply-To: <334DF634.665D@heeg.de> Subject: Re: PNG Graphics >2. Increase the primitive number range. >This would require a change in the CompiledMethod header format. The >header word currently has 29 bits of information. If we ever change the >immediate object format to 2 tag bits, that leaves just one more bit for >extending the primitive range if we don't want to radically change the >format. I have had this on my list for months. Not that hard to do. I was going to force myself to do it using the SystemTracer so that I would get that to run again, too. Ain't but jes' so many hours in the day, tho'. - Dan

Post a reply.

Go back to index.



Date: 97 Apr 11 8:15:53 am From: Dan Ingalls <DanI@wdi.disney.com> To: Ian Piumarta <piumarta@prof.inria.fr> Cc: Squeak@create.ucsb.edu In-Reply-To: <199704110933.LAA12173@prof.inria.fr> Subject: Re: PNG Graphics >Hans-Martin wrote: > >> 2. Increase the primitive number range. This would require a change in >> the CompiledMethod header format. The header word currently has 29 bits of >> information. If we ever change the immediate object format to 2 tag bits, >> that leaves just one more bit for extending the primitive range if we >> don't want to radically change the format. > >We could just get rid of the primitive response encoded in the method header >entirely. [Lots of arguments in favour of this elided -- Ed. ;o)] Make ><primitive N> an instruction which is executed on entry to the method. >A little tweezing could delay the creation of the method context until after >we know it isn't a primitive (or a quick response) method. Yes; then we would be in a position to do lazy activation: I once did a study and found that almost 50% of all activations return before really needing their context (other than the stack). They are just storing arguments or doing simple tests that run primitively. - Dan

Post a reply.

Go back to index.



Date: 97 Apr 11 8:16:11 am From: Dan Ingalls <DanI@wdi.disney.com> To: Georg Gollmann <gollmann@edvz.tuwien.ac.at> Cc: Squeak@create.ucsb.edu In-Reply-To: <v03102801af73de246308@[128.130.36.64]> Subject: Re: Hashing and dictionaries (revisited) >And now a question for the gurus: > >Interpreter class>initializeBytecodeTable has comments: > > "176-191 were sendArithmeticSelectorBytecode" > "192-207 were sendCommonSelectorBytecode" > >does the "were" imply that those bytecodes are no longer supported by the >VM, or are they no longer generated by the compiler (maybe because their >functionality is achieved somehow else) ? No; the "were" means that, in the Blue Book, these went through common= routines of the above names and got looked up through the normal send= mechanism. Squeak now goes directly to individual bytecode handlers and= executes immediately following some simple type checks.

Post a reply.

Go back to index.



Date: 97 Apr 11 8:37:01 am From: Hans-Martin Mosner <hmm@heeg.de> To: Dan Ingalls <DanI@wdi.disney.com> Cc: Ian Piumarta <piumarta@prof.inria.fr>, Squeak@create.ucsb.edu Subject: Re: PNG Graphics (really method invocation optimization) Dan Ingalls wrote: > > [Ian Pimarta wrote:] > >We could just get rid of the primitive response encoded in the method header > >entirely. [Lots of arguments in favour of this elided -- Ed. ;o)] Make > ><primitive N> an instruction which is executed on entry to the method. > >A little tweezing could delay the creation of the method context until after > >we know it isn't a primitive (or a quick response) method. > > Yes; then we would be in a position to do lazy activation: I once did a study > and found that almost 50% of all activations return before really needing > their context (other than the stack). They are just storing arguments or doing > simple tests that run primitively. > > - Dan Even better would be to do away Context objects for activation altogether. We talked about this earlier this year. If arguments and temps are on a stack, we achieve much less overhead per method invocation: 1. No Context allocation. Agreed, Context allocation from a free list as in Squeak is quite cheap. I don't have statistics on how oven real contexts need to be instantiated because old contexts could not be reclaimed and put back into the free list. 2. No argument copying. The receiver and arguments that were pushed onto the stack by the sender of a message serve as the beginning of the frame for the new activation. This saves time and space. 3. Less fragmentation. Active contexts need only as much memory as is currently used up by their variables and the intermediate results on the stack. This is probably offset by fragmentation in the stack segment objects, though. Context objects would then only hold those variables that can outlive the activation of the context, because they are referenced in blocks. It looks as if this is what Dolphin Smalltalk does. Other Smalltalk implementation approaches have probably followed the same path. I have already looked into the possibility of doing it in Squeak, but I think it would require a complete redo of Blocks, which is therefore my current priority. Hans-Martin

Post a reply.

Go back to index.



Date: 97 Apr 11 8:47:32 am From: James McCartney <james@clyde.as.utexas.edu> To: squeak@create.ucsb.edu In-Reply-To: <v03102800af73d386e462@[128.130.36.64]> Subject: Re: Private methods At 5:24 AM -0700 4/11/97, Georg Gollmann wrote: >Maybe it=B4s old news for many but... > >...while rummaging around in the compiler I found to my surprise that >Squeak supports enforcement of private methods. Great! > >"If the code being compiled is trying to send a private message (e.g. >'pvtCheckForPvtSelector:') to anyone other than self, then complain to >encoder." > >"Answer whether the receiver is a private message selector, that is, begins >with 'pvt' followed by an uppercase letter, e.g. pvtStringhash." Hmm. One reason I often want private selectors is in the class' 'new' method in order to set or initialize values, but I want no outside access to the init/setter functions. The above enforcement scheme disallows this type of usage. --- james mccartney james@clyde.as.utexas.edu james@lcsaudio.com If you have a PowerMac check out SuperCollider, a real time synth program: ftp://mirror.apple.com//mirrors/Info-Mac.Archive/gst/snd/super-collider-demo= =2Ehqx

Post a reply.

Go back to index.



Date: 97 Apr 11 8:56:56 am From: James McCartney <james@clyde.as.utexas.edu> To: Squeak@create.ucsb.edu In-Reply-To: <v03007809af74130bb6cb@[206.16.10.79]> Subject: Re: primitive numbering At 9:31 AM -0700 4/11/97, Dan Ingalls wrote: >>2. Increase the primitive number range. >>This would require a change in the CompiledMethod header format. The >>header word currently has 29 bits of information. If we ever change the >>immediate object format to 2 tag bits, that leaves just one more bit for >>extending the primitive range if we don't want to radically change the >>format. > >I have had this on my list for months. Not that hard to do. I was going >to force myself to do it using the SystemTracer so that I would get that >to run again, too. Ain't but jes' so many hours in the day, tho'. In the audio language I am working on, all primitives are referenced by name not by number. Indices are assigned to symbols upon program startup via a registration function. This allows plug in primitives. Plug in primitives are accessed via function pointers so have an indirection cost over built in primitives. If you execute a primitive which has not been loaded you get an error. The program can check itself to see if any primitives are used but not loaded. --- james mccartney james@clyde.as.utexas.edu james@lcsaudio.com If you have a PowerMac check out SuperCollider, a real time synth program: ftp://mirror.apple.com//mirrors/Info-Mac.Archive/gst/snd/super-collider-demo.hqx

Post a reply.

Go back to index.



Date: 97 Apr 11 9:24:26 am From: James McCartney <james@clyde.as.utexas.edu> To: Squeak@create.ucsb.edu Cc: Squeak@create.ucsb.edu In-Reply-To: <334E5E4A.68F0@heeg.de> Subject: Re: PNG Graphics (really method invocation optimization) At 8:52 AM -0700 4/11/97, Hans-Martin Mosner wrote: >Even better would be to do away Context objects for activation altogether. Then you give up the possibility of going to real closures later. --- james mccartney james@clyde.as.utexas.edu james@lcsaudio.com If you have a PowerMac check out SuperCollider, a real time synth program: ftp://mirror.apple.com//mirrors/Info-Mac.Archive/gst/snd/super-collider-demo.hqx

Post a reply.

Go back to index.



Date: 97 Apr 11 10:00:02 am From: Tim Rowledge <rowledge@interval.com> To: Hans-Martin Mosner <hmm@heeg.de> Cc: Squeak mailinglist <Squeak@create.ucsb.edu>, Dan Ingalls <DanI@wdi.disney.com> In-Reply-To: <334DF634.665D@heeg.de> Subject: Re: PNG Graphics On Fri 11 Apr, Hans-Martin Mosner wrote: > 1. Multiplexing primitives. > I think ParcPlace st80 v.2.3 had that for access to UNIX system call > services. One primitive gets a function code and a couple of arguments. > Somehow I don't like this very much... On the other hand, I like this very much. It gives a really simple way to access an arbitrary range of outside functionality, somewhat like DLL&C Connect does for VisualWorks. In fact, I like it so much that Acorn Squeak has just such a p rimitive. Since the Acorn OS is entirely built on using such system calls (*everything* in the OS works via them) I can now use any capability in the machine from Squeak. For example, I could rewrite the file stuff to go direct to system calls and get around some of the restrictions of the ansi fopen/fclose stuff. Or I can call the gif/jpeg/clear/bmp decoding routines, the screen setup, anti-aliased font stuff, whatever. You get the picture. I strongly suspect that someone could make a suitable interface for Mac CFM & Windows DLL stuff. It doesn't however make much sense for high-bandwidth operations that we would normally think of as primitives. And later HMM wrote:- >Even better would be to do away Context objects for activation altogether. We talked about >this earlier this year. If arguments and temps are on a stack, we achieve much less >overhead per method invocation: >...[elided] Look at Eliot's 87 paper in OOPSLA proceedings. He presented a very simple, extremely effective and reliable scheme for this. He used it in Brouhaha, we extended it for Archimedes/ABC Smalltalk (an attempt at commercializing BHH), and I suspect it would work very well for Squeak. -- Tim Rowledge tim@sumeru.stanford.edu http://sumeru.stanford.edu/tim

Post a reply.

Go back to index.



Date: 97 Apr 11 10:19:29 am From: Georg Gollmann <gollmann@edvz.tuwien.ac.at> To: squeak@create.ucsb.edu In-Reply-To: <v03020900af742c6b0089@[128.83.113.156]> Subject: Re: Private methods At 11:03 Uhr -0700 11.4.1997, James McCartney wrote: >At 5:24 AM -0700 4/11/97, Georg Gollmann wrote: >>"If the code being compiled is trying to send a private message (e.g. >>'pvtCheckForPvtSelector:') to anyone other than self, then complain to >>encoder." >> >>"Answer whether the receiver is a private message selector, that is, begins >>with 'pvt' followed by an uppercase letter, e.g. pvtStringhash." > >Hmm. One reason I often want private selectors is in the class' 'new' >method in order to set or initialize values, but I want no outside access >to the init/setter functions. The above enforcement scheme disallows this >type of usage. > I handle this case by having the initialization methods check whether the object is pristine (the instVars are still nil). ---- Dipl.Ing. Georg Gollmann TU-Wien, EDV-Zentrum phon:(+43-1) 58801 - 5848 fax: (+43-1) 587 42 11 mail:gollmann@edvz.tuwien.ac.at http://ftp.tuwien.ac.at/~go/Gollmann.html

Post a reply.

Go back to index.



Date: 97 Apr 11 10:19:30 am From: Georg Gollmann <gollmann@edvz.tuwien.ac.at> To: squeak@create.ucsb.edu Subject: Hashing and dictionaries (revisited again) By paying closer attention to what is a (no lookup) primitive and what not I have been able to get still better timings. ----- crc16 | crc | crc := 0. self do: [:c | crc := crc bitXor: (c asciiValue bitShift: 8). 1 to: 8 do: [ :dmy | "due to compiler optimization this is a bit faster than timesRepeat:" crc := ((crc bitAnd: 16r8000) ~= 0 ifTrue: [ (crc bitShift: 1) bitXor: 16r1021 ] ifFalse: [ crc bitShift: 1 ]) bitAnd: 16rFFFF ]. ]. ^crc ---- z := StringDictionary new: x size. Time millisecondsToRun: [ x do: [ :k | z at: k put: 0 ]] 5933 Time millisecondsToRun: [ x do: [ :k | z at: k ]] 6683 This makes the modified Dictionary about four times faster for my application. Still without resorting to primitives. Have a nice weekend ! Georg ---- Dipl.Ing. Georg Gollmann TU-Wien, EDV-Zentrum phon:(+43-1) 58801 - 5848 fax: (+43-1) 587 42 11 mail:gollmann@edvz.tuwien.ac.at http://ftp.tuwien.ac.at/~go/Gollmann.html

Post a reply.

Go back to index.



Date: 97 Apr 11 10:39:09 am From: joel@ObjectPeople.com To: squeak@create.ucsb.edu Subject: Re: Private methods >Hmm. One reason I often want private selectors is in the class' 'new' >method in order to set or initialize values, but I want no outside >access to the init/setter functions. The above enforcement scheme >disallows this type of usage. Method privacy would be a good thing to turn on/off, and it would have to be smart enough to figure out messages crossing the class/instance line (as James McCartney wrote above). In general, I don't like checking for private methods, as squeak is attempting. Libraries are rarely mature enough to ensure that you'll never need to use private methods. Would be good for teaching purposes. Joel Joel Lucuik | The Object People Joel@ObjectPeople.com | Your Smalltalk Experts 613.225.8812 (V) 613.225.5943 (F) | http://www.objectpeople.on.ca "Where's the kaboom? The EARTH-SHATTERING kaboom???? -Marvin the Martian"

Post a reply.

Go back to index.



Date: 97 Apr 11 12:51:37 pm From: Tim Rowledge <rowledge@interval.com> To: James McCartney <james@clyde.as.utexas.edu> Cc: Squeak mailinglist <squeak@create.ucsb.edu> In-Reply-To: <v03020900af742c6b0089@[128.83.113.156]> Subject: Re: Private methods On Fri 11 Apr, James McCartney wrote: > Hmm. One reason I often want private selectors is in the class' 'new' > method in order to set or initialize values, but I want no outside access > to the init/setter functions. The above enforcement scheme disallows this > type of usage. Ack. True, and very inconvenient. It also disallows a subclass sending the message with 'super'. Maybe the test, currently 'receiver isSelfPsuedoVariable' could be changedto 'receiver isSuitablePrivateRecipient' which method should accept self or super or is-an-instance-of-me-or-a-subclass . Would that work for you? tim -- Tim Rowledge tim@sumeru.stanford.edu http://sumeru.stanford.edu/tim

Post a reply.

Go back to index.



Date: 97 Apr 11 1:20:44 pm From: James McCartney <james@clyde.as.utexas.edu> To: squeak@create.ucsb.edu In-Reply-To: <Marcel-1.09-0411172805-d07KL&V@diziet.interval.com> Subject: Re: Private methods At 10:28 AM -0700 4/11/97, Tim Rowledge wrote: >could be changedto >'receiver isSuitablePrivateRecipient' >which method should accept >self >or super >or is-an-instance-of-me-or-a-subclass . >Would that work for you? I haven't looked at the place in the compiler where this enforcement is made. If it is a compile time check then how would you determine if the receiver is is-an-instance-of-me-or-a-subclass? e.g. (super new) pvtSetThing: thing Technically, you can't guarantee at compile time that (super new) actually returns an object of the class. If it is a runtime check then it would be a complicated check to see if the sending method was a part of the objects ancestry, or if the sender is a block then its enclosing method is a part of the objects ancestry. Perhaps I've missed something. --- james mccartney james@clyde.as.utexas.edu james@lcsaudio.com If you have a PowerMac check out SuperCollider, a real time synth program: ftp://mirror.apple.com//mirrors/Info-Mac.Archive/gst/snd/super-collider-demo.hqx

Post a reply.

Go back to index.



Date: 97 Apr 11 2:02:51 pm From: Dan Ingalls <DanI@wdi.disney.com> To: Squeak@create.ucsb.edu Subject: 1.19c on the way... =46olks - I have just sent a new set of image, changes and Mac VM to Stephen Pope to= be placed on the UCSB web site. Here are the Squeak 1.19c Highlights: * Source code pointers have been changed so that some methods can point to= files while others get decompiled. This is useful for automatic= compilation without logged sources, and also for small systems that may= want to decompile the system while keeping full source for user-written= code. See also, comments in SystemDictionary abandonSources. * A category called 'shrinking' has been added to SystemDictionary with a= number of methods to suport making smaller images. If you close all= windows in this image, go to monochrome display, and execute Smalltalk majorShrink. 4 timesRepeat: [Smalltalk removeAllUnSentMessages]. your image size should be around 760k. We aim to do better still, but it's= harder to eliminate code bloat than it is to create it. * A number of bugs in 1.19b have been fixed including... The clone primitive <148> now works The new BitBlt modes (27-29) should now be accessible Saving new values into temps in the debugger now works FileDirectory includesKey: uses the proper delimiter Form border:width:... uses non-overlapping areas Smalltalk changesName tries harder for likely names * A number of improvements have been made to Morphic and Sound.=09 These are all in addition to the features of 1.19b announced earlier. We feel that this image is pretty stable now, and I have checked that the In= terpreterSimulator included can run its own image. Moreover, we do not plan= any more near-term changes in the VM, so VM maintainers might want to adopt= this as a new base. This is in part due to the fact that we are now= shovelling Morphic fast and furious toward casing off from MVC. Also, Ian= Piumarta is starting on a translation-accelerated VM, so we want to= minimize changes while he is at work. Finally, as you can tell from the= features above, thi constitutes a reasonable plateau from which to produce= compact and yet browsable Squeaks for the Cassiopeia, Newton, and the like.

Post a reply.

Go back to index.



Date: 97 Apr 11 2:52:58 pm From: Stefan Matthias Aust <sma@kiel.netsurf.de> To: squeak@create.ucsb.edu Subject: Re: Hashing and dictionaries (again) >crc16 > [...] Rewriting your methods like this: crc16 | crc | crc := 0. 1 to: self size do: [:i | crc := crc bitXor: ((self byteAt: i) bitShift: 8). 1 to: 8 do: [:j | crc := crc bitShift: 1. (crc bitAnd: 16r10000) == 0 ifFalse: [crc := crc bitXor: 4129]]. crc := crc bitAnd: 16rFFFF]. ^crc reduces execution time to 60%(*) of that of your original method - at least with VisualWorks. I haven't checked whether Squeak optimizes to:do: expressions - as VW will do - but using while-loops will get the optimization on both systems, I think. If I haven't got it wrong, then moving the 16rFFFF masking out of the inner loop shouldn't change the algorithm, as SmallInts are long enough and the additional bits won't affect the intermediate results. (*) I measured "ByteSymbol allInstances", about 20000 Symbols with an average length of 16. bye -- Stefan Matthias Aust // Too much truth is unhealthy... http://www.kiel.netsurf.de/users/s/sma/

Post a reply.

Go back to index.



Date: 97 Apr 11 3:09:59 pm From: Tim Rowledge <rowledge@interval.com> To: James McCartney <james@clyde.as.utexas.edu> Cc: Squeak mailinglist <squeak@create.ucsb.edu> In-Reply-To: <v03020900af746a3558f7@[128.83.113.46]> Subject: Re: Private methods On Fri 11 Apr, James McCartney wrote: > I haven't looked at the place in the compiler where this enforcement > is made. If it is a compile time check then how would you determine > if the receiver is is-an-instance-of-me-or-a-subclass? > > e.g. > > (super new) pvtSetThing: thing > > Technically, you can't guarantee at compile time that (super new) actually > returns an object of the class. True. We might be able to do enough to decide that it is probably ok and that it was an acceptable risk. Some analysis of the parsetree that determined that the temp var involved was occupied by an object returned from a send of 'self' or 'super' new/new: etc might work? Seems a bit convoluted to me. One runtime approach I have used in the past to enforce privacy, at runtime, and at some speed cost, is to make a primitive that a) checks the sender is same as the receiver (or could choose to compare classes in some way I suppose) b) FAILS if they match When all is ok, the prim failure allows the ST code to run as normal. If all is not ok the prim can do a similar job to doeNotUnderstand or cannotReturn etc. Like I said, it costs time, but for initialisation code that is probably not a big problem. James's problem could probably be solved with a version that checked the sender for being the receiver's class. -- Tim Rowledge tim@sumeru.stanford.edu http://sumeru.stanford.edu/tim

Post a reply.

Go back to index.



Date: 97 Apr 11 3:34:08 pm From: Mario Wolczko <mario@Eng.Sun.COM> To: squeak@create.ucsb.edu In-Reply-To: <17501499911343@objectpeople.com> (joel@ObjectPeople.com) Subject: Re: Private methods We tried method privacy in Self and after a while took it back out again; it was just more trouble than it was worth. Unfortunately I don't have time to go into the details right now, but perhaps John can recount the saga. Not that privacy is inherently unworkable; on the contrary, there is an alternate scheme (due to Dave Ungar I believe) that I think is good, based on method renaming). I just want to inject a note of caution, and suggest that someone check that the same mistakes are not being repeated. Mario

Post a reply.

Go back to index.



Date: 97 Apr 11 5:12:10 pm From: Marcio Marchini <mqm@magmacom.com> To: Squeak@create.ucsb.edu Subject: Re: 1.19c on the way... >* A category called 'shrinking' has been added to SystemDictionary with a number of methods to suport making smaller images. If you close all windows in this image, go to monochrome display, and execute > Smalltalk majorShrink. > 4 timesRepeat: [Smalltalk removeAllUnSentMessages]. >your image size should be around 760k. We aim to do better still, but it's harder to eliminate code bloat than it is to create it. Are you planning something similar to ENVY/Packager ? (www.oti.com) >Finally, as you can tell from the features above, thi constitutes a reasonable plateau from which to produce compact and yet browsable Squeaks for the Cassiopeia, Newton, and the like. > Any chance this will run on a Pilot (www.usr.com/palm) ? By the way, what's the main goal of Sqeak ? To be a free, multi-platform Smalltalk ? thanks ! marcio ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ http://www2.magmacom.com/~mqm

Post a reply.

Go back to index.



Date: 97 Apr 11 7:30:36 pm From: Eliot & Linda <elcm@pacbell.net> To: Hans-Martin Mosner <hmm@heeg.de> Cc: Squeak@create.ucsb.edu Subject: Re: PNG Graphics (really method invocation optimization) Hans-Martin Mosner wrote: > > Dan Ingalls wrote: > > > > [Ian Pimarta wrote:] > > >We could just get rid of the primitive response encoded in the method header > > >entirely. [Lots of arguments in favour of this elided -- Ed. ;o)] Make > > ><primitive N> an instruction which is executed on entry to the method. > > >A little tweezing could delay the creation of the method context until after > > >we know it isn't a primitive (or a quick response) method. > > > > Yes; then we would be in a position to do lazy activation: I once did a study > > and found that almost 50% of all activations return before really needing > > their context (other than the stack). They are just storing arguments or doing > > simple tests that run primitively. > > > > - Dan > > Even better would be to do away Context objects for activation altogether. We talked about > this earlier this year. If arguments and temps are on a stack, we achieve much less > overhead per method invocation: > 1. No Context allocation. > Agreed, Context allocation from a free list as in Squeak is quite cheap. I don't have > statistics on how oven real contexts need to be instantiated because old contexts could > not be reclaimed and put back into the free list. > 2. No argument copying. > The receiver and arguments that were pushed onto the stack by the sender of a message > serve as the beginning of the frame for the new activation. This saves time and space. > 3. Less fragmentation. > Active contexts need only as much memory as is currently used up by their variables and > the intermediate results on the stack. This is probably offset by fragmentation in the > stack segment objects, though. > > Context objects would then only hold those variables that can outlive the activation of > the context, because they are referenced in blocks. > > It looks as if this is what Dolphin Smalltalk does. Other Smalltalk implementation > approaches have probably followed the same path. I have already looked into the > possibility of doing it in Squeak, but I think it would require a complete redo of Blocks, > which is therefore my current priority. > > Hans-Martin While this does seem an attractive thing to do I think it has rather disastrous consequences for a number of increasingly relevant uses of Smalltalk, and provides only a small performance increase. Taking the performance increase first, "modern" (e.g. Deutsch & Schiffmann's hps, and my own BrouHaHa - now both approaching 10 years old) approaches to context implementation can reduce their costs to essentially 0 for code that doesn't use contexts, and keep the overhead for code that does to very reasonable levels. BrouHaHa is much better than hps in that it doesn't destroy stack frames when thisContext is accessed. Its worse than hps in that it doesn't use a hardware stack. But knowing both systems as I do I do know that one can combine their two best features (as I plan to do in hps (the VisualWorks engine)). E.g. the creation of a context object for an activation that is actually resident on a machine stack does not require one to dismantle the stack frame in any way. In BrouHaHa, the only operations which do require converting to the heap representation are assigning to the sender, method or receiver fields of a context; all very rare operations. Hans-Martin knows (being familiar with the internals of hps at Heeg) that the hps implemenation eagerly converts frames to contexts (easily aboidable; see BrouHaHa) and makes returns expensive. hps has to introduce an explicit test at return time for methods that may have activations that have a context object. This test checks to see if the activation has a context object and then calls a run-time routine to update the context's contents to ensure they reflect the state of the activation at return time. It can't simply change the return address to cause return to a routine that would do the same sicne an interrupt at this point could overwrite the state on the stack, causing garbage to be written to the context after processing the interrupt. This is the so-called "hybrid return" problem in hps. None of this is necessary. The only important use of contexts is for representing "active" activations. They are not essential to hold e.g. closed-over variables captured by closures that outlive their dynamic extent. This is best done via e.g. explicit vectors of closed-over variables. A closure needs to reference its enclosing method activation only so long as the method activation is active (has not returned). Consider the following simpla idea (it turns out independently invented by David Ungar for Self, and me recently musing on ways past the costs of hybrid returns). On method activation one leaves room in the frame for a slot that will hold a sequence number. When thisContext is created (e.g. for a closure's home, or through explicit use of thisContext) a context object is created. e.g. Its sender slot is set to the frame pointer with the SmallInteger tag bits set (strip the tags to get teh fp). This identifies it as a context which might have its contents on the stack. Note that a normal context object will have its sender contain either nil or another context, so the two cases are easily distinguished. In addition another field, e.g. the IP gets assigned the current "context sequence number" which is also assigned into the "sequence number" slot in the frame. The sequence number os incremented on each creation of thisContext. We also need to assign the context object to another slot in the frame so that subsequent references to thisContext access the same object. So to see if a context object refers to a frame on the stack we a) check that its sender is a SmallInteger, and b) check that the frame pointer derived from the sender field lies within the active portion of the stack (e.g. is above the sp) c) check that its sequence number agrees with that of the frame the sender field points to. Once the activation has been returned from we have to wait 2^32 references to thisContext before there's even a chance of a mismatch. For all practical purposes its impossible to misattribute such a context. So we know reliably that a context is in fact referring to a dead frame. Hence we need take no extra steps when returning from an activation that has a context object. Further, one arranges that all accesses to Context (by translating methods that have context receivers with special inst var access code, and by using special primitives for Context>at: & Context>at:put:) check on the state of the context, and either manipulate the stack activation or the context object. This approach reduces the cost of contexts to leaving two slots empty in each stack frame. This is pretty small, and can be eliminated for leaf methods. But why go to all this effort? [I actually think its _not_ a lot of effort, but contexts do have that Rabbit in the headlight sparkle that many cool ideas do]. Well, contexts provide beautiful ways of doing a) process migration - relevant in todays web-world (and process persistence) b) language extensions - building meta-interpreters with contexts is easy e.g. "I want to add delegation"; "No problem sir, let me roll-up a simulation" c) elegance - one needs access to stacks in any real system (debugging, dynamic binding in exception handling, etc) so why not use an elegant abstraction? I actually think that contexts are one of the most brilliant things Dan invented. Many people see them as expensive, but few have quantified the costs of doing without them. You don't need them often, but if you don't have them, boy are they hard to live without. So can I plead with you when you do your re-implementation of blocks to retain contexts, but discard their use in holding closed-over variables (including self)? _______________,,,^..^,,,_______________ Eliot

Post a reply.

Go back to index.



Date: 97 Apr 12 6:55:10 am From: "Andreas Raab" <raab@isg.cs.uni-magdeburg.de> To: Tim Rowledge <rowledge@interval.com> Cc: squeak@create.ucsb.edu Subject: Re: PNG Graphics Tim Rowledge <rowledge@interval.com> wrote: > On the other hand, I like this very much. It gives a really simple way > to access an arbitrary range of outside functionality, somewhat like > DLL&C Connect does for VisualWorks. In fact, I like it so much that > Acorn Squeak has just such a p rimitive. Since the Acorn OS is > entirely built on using such system calls (*everything* in the OS > works via them) I can now use any capability in the machine from > Squeak. For example, I could rewrite the file stuff to go direct to > system calls and get around some of the restrictions of the ansi > fopen/fclose stuff. Or I can call the gif/jpeg/clear/bmp decoding > routines, the screen setup, anti-aliased font stuff, whatever. You get > the picture. I strongly suspect that someone could make a suitable > interface for Mac CFM & Windows DLL stuff. I do completely agree with you. Even though Squeak is an open system we can hardly foresee what people might want to do with it. And looking at the posts at comp.lang.smalltalk there seem to be lots of people using this external access scheme. Seems I'll have to have a look at your code to get an idea of how you've done this ;-) > It doesn't however make much sense for high-bandwidth operations that > we would normally think of as primitives. No, but this is not what one would use a DLL/C thing for. As an example, I've used DLL/C for connecting realtime 3d graphics (i.e. OpenGL) with VisualWorks allowing me to merge the advantages of OO-Design with the speed of generic (or hardware accelerated) implementations of the GL. Andreas -- Linear algebra is your friend - Trigonometry is your enemy. +===== Andreas Raab ============= (raab@isg.cs.uni-magdeburg.de) =====+ I Department of Simulation and Graphics Phone: +49 391 671 8065 I I University of Magdeburg, Germany Fax: +49 391 671 1164 I +=============< http://simsrv.cs.uni-magdeburg.de/~raab >=============+

Post a reply.

Go back to index.



Date: 97 Apr 12 7:00:09 am From: "Andreas Raab" <raab@isg.cs.uni-magdeburg.de> To: Dan Ingalls <DanI@wdi.disney.com> Cc: piumarta@prof.inria.fr, squeak@create.ucsb.edu Subject: Re: 1.19c on the way... > Also, Ian Piumarta is starting on a translation-accelerated VM, so we > want to minimize changes while he is at work. Maybe I've missed something, but what exactly will this translation- accelerated VM include? Andreas -- Linear algebra is your friend - Trigonometry is your enemy. +===== Andreas Raab ============= (raab@isg.cs.uni-magdeburg.de) =====+ I Department of Simulation and Graphics Phone: +49 391 671 8065 I I University of Magdeburg, Germany Fax: +49 391 671 1164 I +=============< http://simsrv.cs.uni-magdeburg.de/~raab >=============+

Post a reply.

Go back to index.



Date: 97 Apr 13 1:04:05 am From: Dan Ingalls <DanI@wdi.disney.com> To: Marcio Marchini <mqm@magmacom.com> Cc: Squeak@create.ucsb.edu In-Reply-To: <199704120022.UAA15563@mag1.magmacom.com> Subject: Re: 1.19c on the way... >> Are you planning something similar to ENVY/Packager ? Yes, at some point down the road. For now, though, we're not so much= focussed on delivering compact applications as we are on delivering a= full-service computing environment in a small space. > Any chance this will run on a Pilot (www.usr.com/palm) ? Probably not -- not quite enough cycles, memory or screen pixels, but we're= not far off. The Cassiopeia and new Newtons are definitely capable. > By the way, what's the main goal of Sqeak ? To be a free, >multi-platform Smalltalk ? Yes but, more importantly, to be nearly all written in Squeak itself. This= then implies not only ease of portability to multiple platforms, but also= ease of analysis, maleability, and hence evolution. Also the ability to study its own operation, both at the level of the= single-step simulator and also the VM simulator (not to mention lots of= other tools for introspection, such as allinstances, allSenders,= allImplementors, allPointerReferencesTo, etc), make it a really nice tool= for academic study. I should add, though, that Squeak is now in many hands, and others may have= a different point of view about "the main goal". For the Squeak team, we= just wanted some uniform piece of software that would give us complete and= interactive control over everything from the UI down to every last pixel on= the screen and every last bit in the memory. - Dan

Post a reply.

Go back to index.



Date: 97 Apr 13 1:41:35 am From: Marcio Marchini <mqm@magmacom.com> To: Squeak@create.ucsb.edu Subject: Re: 1.19c on the way... >> Any chance this will run on a Pilot (www.usr.com/palm) ? > >Probably not -- not quite enough cycles, memory or screen pixels, but we're not far off. The Cassiopeia and new Newtons are definitely capable. > There's a neat app called Jump that will translate Java class files to a Pilot native App. Hello World is 9 Kbytes. I just thought that maybe Sqeak could have a similar tool, combining something like ENVY/Packager (.class files & main in the case of Java/Jump) and a translator to Pilot ASM. So, in some sense the VM and the user code are bundled together in a single app, a native executable. Each bytecode interpretation becomes a subroutine. If you are interested I can send you the ASM output from a program. It is quite readable (lots of comments, etc). >I should add, though, that Squeak is now in many hands, and others may have a different point of view about "the main goal". For the Squeak team, we just wanted some uniform piece of software that would give us complete and interactive control over everything from the UI down to every last pixel on the screen and every last bit in the memory. > If you don't mind my question, what is the interest from Disney in supporting the development of (Sqeak) Smalltalk ? In the latest Agents conference Dan Hillis talked about software agents, but is Sqeak Disney's agents platform ? If it is confidential, feel free to ignore the question ;-) thanks ! marcio ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ http://www2.magmacom.com/~mqm

Post a reply.

Go back to index.



Date: 97 Apr 13 4:18:43 am From: "Peter J. Goodall" <peterg@acm.org> To: squeak@create.ucsb.edu In-Reply-To: <334C5A58.6A08BFD0@lsi.usp.br> Subject: Re: String>hash Folks, It's usually a good time at this point to check Knuth's 'Sorting and Searching'. I believe he suggests a bit rotate with an xor for each character. The number of bits in the hash determines the collision probability. Should be easy to make a primitive on any platform. Digitalk (where ever they may be now) used to have terrible performance in their SymbolTable in /V286. Didn't leave enough free space, so collisions were more likely than not when the table was full. regards, Peter Goodall -- peterg@acm.org

Post a reply.

Go back to index.



Date: 97 Apr 13 10:33:45 am From: Ian Piumarta <piumarta@prof.inria.fr> To: raab@isgnw.cs.Uni-Magdeburg.DE Cc: squeak@create.ucsb.edu Subject: Re: 1.19c on the way... Andreas, > Maybe I've missed something, but what exactly will this translation- > accelerated VM include? The intention is to "include" everything that is necessary to make Squeak execute as fast as possible without sacrificing either portability or simplicity. The VM is evolving in many small stages, but the overall results will be roughly as follows: - Dynamic translation in the interpreter: bytecoded methods are translated into direct-threaded code at runtime, on demand. - [Probably] changes to the way that blocks are implemented to turn them into full closures. Several people have pointed out the desirability of this, but the real reason for doing it is that it makes the following a lot easier... - A new implementation of contexts, to make the handling of method and block contexts as similar as possible (increasing generality increases performance). This will draw on techniques that have already been proven in implementations such as Eliot's BrouHaHa and the HPS implementation of Deutsch and Schiffman -- although there are differences in the details. The core execution mechanism will be a little more complicated than the present interpreter, but the hope is that the "overall picture" will end up simpler. The above is being implemented within Squeak itself -- all of it can be expressed directly in Squeak's Smalltalk subset for translation into C to make a VM. Squeak will therefore continue to be able to simulate the execution of its own images (including the dynamic translation), and the VM will continue to compile on any system that has an ANSI C compiler. (The code is being tested under both MacOS/CW10 and Unix/gcc.) Regards, Ian ------------------------------- projet SOR ------------------------------- Ian Piumarta, INRIA Rocquencourt, Internet: Ian.Piumarta@inria.fr BP105, 78153 Le Chesnay Cedex, FRANCE Voice: +33 1 39 63 52 87 ----------------------- Systemes d'Objets Repartis -----------------------

Post a reply.

Go back to index.



Date: 97 Apr 13 9:46:50 pm From: Jecel Assumpcao Jr <jecel@lsi.usp.br> To: squeak@create.ucsb.edu Subject: dynamic translation (was: 1.19c on the way...) Ian Piumarta wrote: > - Dynamic translation in the interpreter: bytecoded methods are > translated into direct-threaded code at runtime, on demand. This sounds good, specially if it can be used to do inlining and customization (later on, of course). Just eliminating the inner bytecode interpreter probably won't help much for I doubt that a well tuned interpreter (I haven't really looked at Squeak's to see if that is the case here) takes up very little computation time. If you can make use of the C stack in the threaded code, then you might have some real gains (make the threaded code look like C code to other C code). -- Jecel

Post a reply.

Go back to index.



Date: 97 Apr 13 9:47:21 pm From: Jecel Assumpcao Jr <jecel@lsi.usp.br> To: squeak@create.ucsb.edu Subject: Re: Private methods Mario Wolczko wrote: > > We tried method privacy in Self and after a while took it back out > again; it was just more trouble than it was worth. > Unfortunately I don't have time to go into the details right now, but > perhaps John can recount the saga. > > Not that privacy is inherently unworkable; on the contrary, there is > an alternate scheme (due to Dave Ungar I believe) that I think is > good, based on method renaming). I just want to inject a note of > caution, and suggest that someone check that the same mistakes are not > being repeated. I never did bother to declare my slots as private in the old Self implementations, so I may not be remembering correctly. But it seems to me that it was the message lookup "tie breaker" rule that caused all the trouble, not the actual privacy stuff. Some of the Self problems (any object can make itself temporarily inherit from you to get to your private methods) wouldn't happen in Smalltalk. While I have no experience with them, the SmalltalkAgents namespaces look like a nice solution to several things, including privacy. -- Jecel

Post a reply.

Go back to index.



Date: 97 Apr 13 9:47:37 pm From: Jecel Assumpcao Jr <jecel@lsi.usp.br> To: Squeak@create.ucsb.edu Subject: Re: primitive numbering In Self, primitives are invoked through the normal send bytecodes but always have selectors that start with an underscore. The advantage is that you can use them anywhere in a method, not just at the start. Any primitive can take a "Fail:" block that it will execute on failure (the block can take an argument that is a string explaining what went wrong). I have considered several alternatives to this. My current idea is to have "primitive objects" rather than "primitive selectors". So we would write _arithmeticUnit add: 12 With: 21 instead (sorry about the Selfish syntax) 12 _IntegerAdd: 21 In Smalltalk we could use global variable syntax, calling the primitive object ArithmeticUnit. We could even have these objects be normal Smalltalk objects on one VM while being a primitive object on another. I haven't really thought about it, but here are some objects that seem interesting: ArithmeticUnit - we met already LogicUnit - shifts and general bitwise stuff FloatingPointUnit - for obvious things Memory - used by basicNew and friends BitBlitter - in some cases implemented in hardware OS - files and things Mac - unique Mac things Win32 - the little shop of horrors It should be easy to add new primitive objects with time (a MMX object would be popular now), eventually even dynamically. If objects are as good as we claim, why do we use primitive *functions* to do all the dirty work? -- Jecel

Post a reply.

Go back to index.



Date: 97 Apr 13 10:07:12 pm From: Tim Rowledge <rowledge@interval.com> To: Andreas Raab <raab@isgnw.cs.Uni-Magdeburg.DE> Cc: Squeak mailinglist <squeak@create.ucsb.edu> In-Reply-To: <32C0871151@isgnw.cs.uni-magdeburg.de> Subject: Re: System Calls (was PNG Graphics) On Sat 12 Apr, Andreas Raab wrote: > Tim Rowledge <rowledge@interval.com> wrote: > > On the other hand, I like this very much. ...[elided] > > I strongly suspect that someone could make a suitable > > interface for Mac CFM & Windows DLL stuff. > Seems I'll have to have a > look at your code to get an idea of how you've done this ;-) I fear my Acorn system call code won't help too much for Mac/PC, since it is so trivial to do on that platform. The invocation code for DLLCC is quite a lot more complex, since you have to build code thunks ( at least for PC) and manually load libraries and find out function addresses etc. It's doable, but not a brief weekend job! Even Daniel 'Terminator' Lanovaz took several weeks to do it... And don't even think of trying to do all the header file parsing that DLLCC does; after huge amounts of work on it at PPS, most customers kept complaining that it was too complex to put the name of the .h file in the class definition, and they wanted to type the stuff in manually. Go figure... > As an > example, I've used DLL/C for connecting realtime 3d graphics > (i.e. OpenGL) with VisualWorks allowing me to merge the advantages of > OO-Design with the speed of generic (or hardware accelerated) > implementations of the GL. Yup - that works well. You should see what Dave Leibs at neometron has done in that line; pretty cool stuff. -- Tim Rowledge tim@sumeru.stanford.edu http://sumeru.stanford.edu/tim

Post a reply.

Go back to index.



Date: 97 Apr 14 12:56:53 am From: "Andreas Raab" <raab@isg.cs.uni-magdeburg.de> To: Jecel Assumpcao Jr <jecel@lsi.usp.br> Cc: squeak@create.ucsb.edu Subject: Re: dynamic translation (was: 1.19c on the way...) > Just eliminating the inner bytecode interpreter probably > won't help much for I doubt that a well tuned interpreter > (I haven't really looked at Squeak's to see if that is > the case here) takes up very little computation time. I haven't measured this in the inlined VM, however the profiler claims about 30% of execution time in the non-inlined VM for the interpreter loop. So it may be a bit more than expected. Andreas -- Linear algebra is your friend - Trigonometry is your enemy. +===== Andreas Raab ============= (raab@isg.cs.uni-magdeburg.de) =====+ I Department of Simulation and Graphics Phone: +49 391 671 8065 I I University of Magdeburg, Germany Fax: +49 391 671 1164 I +=============< http://simsrv.cs.uni-magdeburg.de/~raab >=============+

Post a reply.

Go back to index.



Date: 97 Apr 14 2:35:37 am From: "Andreas Raab" <raab@isg.cs.uni-magdeburg.de> To: Pedro Gomes <pgomes@pc-lur.df.fct.unl.pt> Cc: squeak@create.ucsb.edu Subject: Debugging the Win32 VM (was: Squeak Win32 Port! bug ! Again !) Pedro, > Since Friday when I mailed you about the bug I got to my computer and > compilied the VM source with VC++4.2 and when I debug it step-by-step it > gives me a whole lot of 'first-class exceptions 00005Ch. Are these > exceptions handled by the program or what! It is being handled. Have a look at the sqWin32Alloc.c file. You'll find that for virtual memory management to be efficient one has to use SEH (structured exception handling). When Squeak starts, a portion of memory is reserved for its use, but NOT allocated yet. Each time Squeak needs more space it will access a previously unused region. This, in turn, will raise an exception since the memory has not yet been allocated. When the first exception at a particular memory location occurs, this portion of memory is allocated and execution continues. Note that this scheme is only used in the region of memory reserved at startup time and exceptions outside this region will be handled as usual (i.e. raising a GPF). If you wish to debug the VM you should either: a) define NO_VIRTUAL_MEMORY (in Project>>Settings>>C/C++/>>Preprocessor definitions) disabling the virtual memory management completely b) set the exception 0x0000005c to "stop if not handled" in the Debug>>Exceptions dialog box of your VC. > I noticed that if all optimizations are put in VC and code compiled to P5 > (I got one!) the execution becomes a lot faster! True, however there may be some problems when debugging such highly optimized code. I've found that you can get a _lot_ faster when setting the inline function generation to "any suitable" but you wont be able to set breakpoints at several functions (since they are inlined execution never reaches them). Hope this helps, Andreas -- Linear algebra is your friend - Trigonometry is your enemy. +===== Andreas Raab ============= (raab@isg.cs.uni-magdeburg.de) =====+ I Department of Simulation and Graphics Phone: +49 391 671 8065 I I University of Magdeburg, Germany Fax: +49 391 671 1164 I +=============< http://simsrv.cs.uni-magdeburg.de/~raab >=============+

Post a reply.

Go back to index.



Date: 97 Apr 14 2:43:49 am From: stp (Stephen Travis Pope) To: squeak@create.ucsb.edu Subject: Squeak 1.19c on the CREATE FTP site Hello all, The new version (1,19c) is on our ftp site in BinHexed StuffIt and gzipped tar formats. Look at ftp://ftp.create.ucsb.edu/pub/Smalltalk/Squeak/Squeak.1.19c.sit.hqx or ftp://ftp.create.ucsb.edu/pub/Smalltalk/Squeak/Squeak.1.19c.tar.gz stp Stephen Travis Pope, Center for Research in Electronic Art Technology (CREATE), Department of Music, U. of California, Santa Barbara (UCSB) Editor--Computer Music Journal, MIT Press stp@create.ucsb.edu, http://www.create.ucsb.edu/~stp/

Post a reply.

Go back to index.



Date: 97 Apr 14 2:52:39 am From: Hans-Martin Mosner <hmm@heeg.de> To: squeak@create.ucsb.edu Subject: Block Closures Sorry, my mail agent made me lose all the squeak mails that I got over the weekend... So I need to reply to them from memory. I seem to have made myself not clear about what I would like to do with Blocks etc. My intention is not at all to throw out the Closure semantics with the Context objects. Instead, I want to have the full semantics with a very efficient implementation. The idea (which is in some respects similar to that outlined by Eliot Miranda) works like this: For each process, we have two stacks. One is the 'operand stack' while the other is the 'call stack'. Whether they are implemented as separate objects or as one object in which the stacks grow into a common empty gap is an implementation detail. The operand stack holds only the receivers and arguments of messages and the temps of invoked methods. The advantage of this is that receivers and arguments do not have to be copied on method activation, but are simply shared. The call stack holds, for each activation, four values, which together constitute a 'call stack frame': 1. method (a CompiledMethod) 2. pc (Conceptually, a SmallInteger) 3. fp (Conceptually, a SmallInteger) This is a pointer to the slot in the operand stack where this activation's receiver is stored. 4. context (nil, or a Context object as described later) The call stack could store pc and fp as SmallIntegers so that it can be implemented with a normal Array. Another (more complicated) option would be to store pc and fp as direct pointers into memory, converting them on each access. However, this would complicate the garbage collector considerably. Both stacks are maintained strictly LIFO. Variables that can outlive the activation of the method in which they are defined (because they are referenced by a Block, for exampl) need to be stored outside of the operand stack in a Context object. A Context object has 2 fixed fields: 1. callStack (the object which implements the call stack) 2. frameIndex (a SmallInteger) A Context can check whether the part of it that resides on the operand stack is still active by looking into the call stack at the frameIndex. If the 'context' slot there is pointing to itself, it is still alive. This is similar to Eliot's concept of numbering the Contexts, but in my opinion it is simpler and avoids the small possibility of using an outdated Context when the numbering wraps. A method or block that creates variables which outlive its own activation needs to create the Context and fill it with those variables. In addition, Context objects must be created for methods that include blocks with ^ returns. Whether this is done at the beginning or lazily when it becomes obvious that the Context will be needed is an implementation detail. One option would be to add a field or instruction to the CompiledMethod that tells the VM whether this method needs a full Context and how many slots it should have. Contexts can, of course, be created at any moment for an active call frame. This allows the debugger to work on Context objects just as usual. These contexts just don't have variables stored in them. Conclusion: Maybe I'm blind, but I can't see where this scheme might break the standard Smalltalk execution semantics. Granted, it has the effect that Contexts that have been returned from are not very usable since they only keep the shared variables, but I don't see where this would make a different except in analysing 'post-mortem' stacks. As long as their frame is active, they are able to do everything that a MethodContext can do now. Hans-Martin

Post a reply.

Go back to index.



Date: 97 Apr 14 4:43:58 am From: Ian Piumarta <piumarta@prof.inria.fr> To: jecel@lsi.usp.br Cc: squeak@create.ucsb.edu Subject: Re: dynamic translation Jecel Assumpcao Jr wrote: > This sounds good, specially if it can be used to do inlining and > customization (later on, of course). The framework with which we have been experimenting seems amenable to producing different kinds of translated code, including call-threading (which is usually *slower* than direct-threading!) and the generation of native code fragments from either C source or hand-made assembler (although there are severe problems with the Mac CW compiler which doesn't allow you to put "asm(...)" in arbitrary places). Doing either of these last two causes problems with instructions that need offsets to be resolved, such as branches. The anaysis of how to do the required patching is not trivial, and must be done for every architecture/compiler that you want to support. Moving to this kind of code generation would be a big commitment. Using direct-threaded code has a number of important benefits, at least for an initial implementation of dynamic translation. Various kinds of optimisation (which are not well suited to interpreting bytecodes) are much more attractive. One example is the use of "macro" instructions, where the first instruction in a common sequence of instructions performs the work of the entire sequence. The current interpreter does this in a couple of places (look at #booleanCheat: for an example). With dynamic translation the applicability of this technique is greatly increased, and the necessary analysis of the bytecodes need only be done once -- at translation time. (Doing "peephole" optimisations in this way also eliminates the need for other irritations like "nPC to vPC" maps.) Optimisations based on self-modifying code are also easy with direct threading. For example, if we ever decide that an inline cache is appropriate then the send instruction can be broken into several different versions for immediate receivers, non-immediate receviers, and so on. This would help to make the "common case" as fast as possible at each send site. Customisation (at least in the HPS sense of the word) is trivial. This might be particularly appropriate for immediate receivers, although no expirements have been done in this area yet to get a feel for the possible gains. The equivalent of inlining might well be possible, by generating statically linked sends when the receiver is known at translation time. But this must be weighed against the cost of the "book-keeping" information that you need to keep in order fix your assumptions whenever the programmer breaks them. (However, flushing the entire translated code cache seems relatively cheap: translating a CompiledMethod is significantly faster (in the majority of cases) than executing the resulting threaded code.) > Just eliminating the inner bytecode interpreter probably > won't help much Like Andreas says, you might be surprised. Regards, Ian ------------------------------- projet SOR ------------------------------- Ian Piumarta, INRIA Rocquencourt, Internet: Ian.Piumarta@inria.fr BP105, 78153 Le Chesnay Cedex, FRANCE Voice: +33 1 39 63 52 87 ----------------------- Systemes a Objets Repartis -----------------------

Post a reply.

Go back to index.



Date: 97 Apr 14 5:30:20 am From: stp (Stephen Travis Pope) To: squeak@create.ucsb.edu Subject: Squeak 1.19d (!) on the CREATE FTP site Hello all, No, it's not a typo; just as I was up-loading 1.19c, Dan_I sent me 1.19d! The new version (1,19d) is on our ftp site in BinHexed StuffIt and gzipped tar formats. Look at ftp://ftp.create.ucsb.edu/pub/Smalltalk/Squeak/Squeak.1.19d.sit.hqx or ftp://ftp.create.ucsb.edu/pub/Smalltalk/Squeak/Squeak.1.19d.tar.gz stp Stephen Travis Pope, Center for Research in Electronic Art Technology (CREATE), Department of Music, U. of California, Santa Barbara (UCSB) Editor--Computer Music Journal, MIT Press stp@create.ucsb.edu, http://www.create.ucsb.edu/~stp/

Post a reply.

Go back to index.



Date: 97 Apr 14 10:33:00 am From: Jecel Assumpcao Jr <jecel@lsi.usp.br> To: squeak@create.ucsb.edu Subject: Re: dynamic translation Andreas Raab wrote: > I haven't measured this in the inlined VM, however the profiler > claims about 30% of execution time in the non-inlined VM for the > interpreter loop. So it may be a bit more than expected. I have looked at both the inlined and simple interpreters and think that the difference between them is very significant. In fact, I see no way to improve on the inlined case. What does your 30% number mean? If it includes the time spent in Interpret() *and* all subroutines called from it (which seems likely) then you are actually talking about the overhead for the bulk of the interpreter and we have no idea what the cost of dispatching is (it is a trivial 256 way switch, so I doubt that it amounts to much). That is what compiling to threaded code would eliminate - it would still have to push things on the stack and so on, which I am guessing accounts for most of the 30%. Of course, if your profiler is showing you the overhead of just the loop and the switch then none of what I just wrote is right. Ian Piumarta wrote: > > This sounds good, specially if it can be used to do inlining and > > customization (later on, of course). > > The framework with which we have been experimenting seems amenable to > producing different kinds of translated code, including call-threading > (which is usually *slower* than direct-threading!) and the generation of > native code fragments from either C source or hand-made assembler Just to make sure we are speaking the same language, here is what I understand by the following terms: - call threading: the code is compiled as a series of machine language call instructions. There is no inner interpreter at all - the machine's PC is the interpreter's PC as well. - direct threading: the code is compiled into an array of function pointers that are called by a code like this: while (true) (* ip++) (); On some machines we can use the stack pointer as the interpreter's PC (or ip) and the inner loop becomes a simple return instruction. - indirect threading: the code is compiled into an array of object pointers that contain a function pointer in a standard place: while (true) (* ((* ip++) + functionOffset)) (); The main advantage of this is that many objects can point to the exact same function, which can distinguish the several objects when it needs to by looking at *ip (this is like having many instances to a class). - token threading: I don't know what the difference is relative to indirect threading, though the figures on the implementation of Duff's Actor language seem to imply there is some difference. I agree that direct threading will probably yield the best results, though it is nice that your framework can handle other methods as well. -- Jecel

Post a reply.

Go back to index.



Date: 97 Apr 14 12:11:23 pm From: Dan Ingalls <DanI@wdi.disney.com> To: Squeak@create.ucsb.edu In-Reply-To: <9704141230.AA09297@tango.create.ucsb.edu> Subject: Re: Squeak 1.19d (!) on the CREATE FTP site >No, it's not a typo; just as I was up-loading 1.19c, Dan_I sent me 1.19d! Timing is everything, right? Thanks, Stephen for packaging up the files (tw= ice). The main difference between 1.19d and what I described in my earlier message= about 1.19c is the degree to which the system can now be shrunk. In the= 1.19d as it is, you can execute the following: Display newDepth: 1. Smalltalk majorShrink. TextConstants removeUnreferencedKeys. Smalltalk abandonSources. "Takes 5-10 minutes" Smalltalk lastRemoval. The result should be a 650k image which exhibits every normal aspect of= Squeak -- all flavors of code browsers, compiler, text editor with fancy= fonts and lots of commands, debugger, inspectors, single-step bytecode= simulation, MessageTally time and counts, Floats and LargeIntegers, full= color support, WarpBlt and Turtle demos. What is more, that 650k image includes the magic sources facility, which= will gladly cough up some 820k of readable source code out of those same= bits (I like to think of it as a compressed version of the sources with a= full-featured computing environment thrown in for free ;-) I remember saying last year that, when we got a chance, we would put out a= Squeak that would run in one megabyte, including the VM. Voila! What is NOT there after shrinking, you ask? The interpreter anc C= translator, music, and change sorters, the formEditor and character= recognizer, projects and the ClairVaux font set, as well as all comments= and class organizations. However, full comments and organization are= retained for code that you subsequently fileIn or write in the system, and= all changes file facilities are still there, including browsing of old vers= ions. Enjoy - Dan

Post a reply.

Go back to index.



Date: 97 Apr 14 12:33:02 pm From: Ian Piumarta <piumarta@prof.inria.fr> To: jecel@lsi.usp.br Cc: squeak@create.ucsb.edu Subject: Re: dynamic translation Jecel, > I have looked at both the inlined and simple interpreters and > think that the difference between them is very significant. In > fact, I see no way to improve on the inlined case. "...and so they summoned a qualified poet to testify under oath that truth was beauty and beauty was truth. The judges concurred -- and holding that life itself was in contempt of court, for failing to be either beautiful or true, duly confiscated it from all those there present..." Regular "nfibs" benchmark: inlined bytecode interpreter: 232516 sends per second direct-threaded translator: 363359 sends per second (Measured with an utterly naive translator -- so you can do >50% better than a switch() statement without trying very hard at all. :o) > Just to make sure we are speaking the same language, here is > what I understand by the following terms: [...] Your characterisations seem accurate. Regards, Ian ------------------------------- projet SOR ------------------------------- Ian Piumarta, INRIA Rocquencourt, Internet: Ian.Piumarta@inria.fr BP105, 78153 Le Chesnay Cedex, FRANCE Voice: +33 1 39 63 52 87 ----------------------- Systemes a Objets Repartis -----------------------

Post a reply.

Go back to index.



Date: 97 Apr 14 12:34:20 pm From: Maloney <johnm@wdi.disney.com> To: "Andreas Raab" <raab@isgnw.cs.Uni-Magdeburg.DE> Cc: squeak@create.ucsb.edu In-Reply-To: <5CC9BC0C95@isgnw.cs.uni-magdeburg.de> Subject: Re: dynamic translation (was: 1.19c on the way...) Re: >> Just eliminating the inner bytecode interpreter probably >> won't help much for I doubt that a well tuned interpreter >> (I haven't really looked at Squeak's to see if that is >> the case here) takes up very little computation time. > >I haven't measured this in the inlined VM, however the profiler >claims about 30% of execution time in the non-inlined VM for the >interpreter loop. So it may be a bit more than expected. > >Andreas I believe that the inlined Squeak VM for the PowerPC with the dispatch patch applied spends about half its time in dispatch in the worst case (a tight loop that does no sends or primitives). This breaks down to something like 7 instructions in 11 clock cycles for the dispatch and another 11 clock cycles for the predominate bytecodes (pushTemp, pushTemp, plus, compare, branch). Going to threaded code drops the dispatch overhead significantly (depending on which style of threading is done), but it also enables a class of peephole optimizations that allow special "macro" threaded coded to replace common bytecode sequences. (An example of such a sequence is "pushTemp, push 1, +, popIntoTemp"). Thus, you can get more than the x2 speedup that simply eliminating dispatch overhead would be expected to bring. An orthoganal optimization is to streamline context handling for message send-return, which Ian has also been thinking about. -- John

Post a reply.

Go back to index.



Date: 97 Apr 14 12:35:00 pm From: Maloney <johnm@wdi.disney.com> To: joel@objectpeople.com Cc: squeak@create.ucsb.edu In-Reply-To: <17501499911343@objectpeople.com> Subject: Re: Private methods >In general, I don't like checking for private methods, as squeak is >attempting. Libraries are rarely mature enough to >ensure that you'll never need to use private methods. ... >Joel Just to clarify, Squeak is NOT currently using this mechanism, although the hooks are there to allow experimentation. As Mario pointed out, we took the privacy mechanism out of Self in the interest of simplicity, and because we realized we could provide a user programming environment that hid private methods from all but the most expert system maintainers. That is, we realized that you can support the progressive revelation of the system without adding complexity to the language semantics. The Self project took some twists and turns that prevented us from fully exploring this progressive revelation idea, but I'm hoping that to resume that work in the context of Squeak. The dream is to allow users to start with a small but consistent view of the system and then gradually raise the curtain until they can see that all the facilities that they've been using are implemented in the system itself. In the Self group, we called this "the green blur" because the first time Dave Ungar drew a graph of the desired gradual learning curve he used a green white-board marker. -- John P.S. I realize that one must control the visibility of names to support good software engineering when working in large teams of programmers, and this may require some sort of privacy enforcement mechanism. However, at the moment, our focus is on making Squeak (Smalltalk) more approachable by novices, rather than on supporting software engineering. The big Smalltalk vendors already provide lots of support for professional programmers.

Post a reply.

Go back to index.



Date: 97 Apr 14 7:03:07 pm From: Kenneth Collins <shesha@televar.com> To: squeak@create.ucsb.edu Subject: any tutors out there? Hello all, I am looking for someone to help me learn Smalltalk (Squeak). I have some questions about how to do some (I think) rather basic things with/in Squeak. I am new to Smalltalk and fairly new to programming in general. I am a student of music composition and considering going into computer science as well. I could pay as much as $25-30 per "lesson/...". I subscibed to this mailing list only a couple of weeks ago so I'm not sure if it's OK to post things like this... forgive me if it's not. If you are interested, or know someone who may be interested, PLEASE contact me. Sincerely, Kenneth Collins shesha@televar.com

Post a reply.

Go back to index.



Date: 97 Apr 14 8:37:17 pm From: Jecel Assumpcao Jr <jecel@lsi.usp.br> To: squeak@create.ucsb.edu Subject: Re: dynamic translation Maloney wrote: > I believe that the inlined Squeak VM for the PowerPC with the > dispatch patch applied spends about half its time in dispatch > in the worst case (a tight loop that does no sends or primitives). > This breaks down to something like 7 instructions in 11 clock > cycles for the dispatch and another 11 clock cycles for the > predominate bytecodes (pushTemp, pushTemp, plus, compare, branch). I guess these seven instructions are roughly: increment pointer (in register?) read a byte from memory (expand to int?) check that byte is not less than 0 check that byte is not greater than 255 read a word from memory (indexed by the byte) do an indirect jump The checks are not needed in this case, of course, but I would be very surprised if any C compiler is smart enough to see that. Or does the "dispatch patch" take care of this? > Going to threaded code drops the dispatch overhead significantly > (depending on which style of threading is done), but it also > enables a class of peephole optimizations that allow special > "macro" threaded coded to replace common bytecode sequences. > (An example of such a sequence is "pushTemp, push 1, +, popIntoTemp"). > Thus, you can get more than the x2 speedup that simply eliminating > dispatch overhead would be expected to bring. I don't understand the "eliminating dispatch" part. It would seem to me that to execute the direct threaded code you need something like: increment pointer (in register?) read a word from memory do an indirect call All the common bytecodes would be leaf routines, so this call would not be more expensive than the jump on RISC machines. > An orthoganal optimization is to streamline context handling > for message send-return, which Ian has also been thinking about. That would be great. Ian wrote: > Regular "nfibs" benchmark: > > inlined bytecode interpreter: 232516 sends per second > direct-threaded translator: 363359 sends per second > > (Measured with an utterly naive translator -- so you can do >50% better > than a switch() statement without trying very hard at all. :o) That is what I don't understand. Where is this gain coming from? I suppose by "utterly naive" you mean no peephole optimizations like the ones John was talking about, no inline caching, and so on. BTW, I hope my comments haven't given the impression that I am against translation to threaded code. In fact, I have been working on this myself (in Self, where the cost of using send bytecodes for trivial things like "instance variable" access is terribly high). I am just trying to better understand the issues here. -- Jecel

Post a reply.

Go back to index.



Date: 97 Apr 14 9:34:06 pm From: "Dwight Hughes" <dhughes@intellinet.com> To: <squeak@create.ucsb.edu> Subject: Re: dynamic translation At <http://www.complang.tuwien.ac.at/forth/threaded-code.html> there is a nice assortment of info and benchmarks on the various methods of dispatch. One bit of info I found interesting was the horrible performance of the Pentium in switch-dispatch (in gcc 2.6.3 anyway) -- a factor of 4.7 times slower than direct threading!

Post a reply.

Go back to index.



Date: 97 Apr 15 9:45:34 am From: Eliot & Linda <elcm@pacbell.net> To: Jecel Assumpcao Jr <jecel@lsi.usp.br> Cc: squeak@create.ucsb.edu Subject: Re: dynamic translation (to threaded code) Jecel Assumpcao Jr wrote: > > Maloney wrote: > > I believe that the inlined Squeak VM for the PowerPC with the > > dispatch patch applied spends about half its time in dispatch > > in the worst case (a tight loop that does no sends or primitives). > > This breaks down to something like 7 instructions in 11 clock > > cycles for the dispatch and another 11 clock cycles for the > > predominate bytecodes (pushTemp, pushTemp, plus, compare, branch). > > I guess these seven instructions are roughly: > > increment pointer (in register?) > read a byte from memory (expand to int?) > check that byte is not less than 0 > check that byte is not greater than 255 > read a word from memory (indexed by the byte) > do an indirect jump > > The checks are not needed in this case, of course, but I > would be very surprised if any C compiler is smart enough > to see that. Or does the "dispatch patch" take care of this? > > > Going to threaded code drops the dispatch overhead significantly > > (depending on which style of threading is done), but it also > > enables a class of peephole optimizations that allow special > > "macro" threaded coded to replace common bytecode sequences. > > (An example of such a sequence is "pushTemp, push 1, +, popIntoTemp"). > > Thus, you can get more than the x2 speedup that simply eliminating > > dispatch overhead would be expected to bring. > > I don't understand the "eliminating dispatch" part. It would > seem to me that to execute the direct threaded code you > need something like: > > increment pointer (in register?) > read a word from memory > do an indirect call > > All the common bytecodes would be leaf routines, so this > call would not be more expensive than the jump on RISC > machines. > > > An orthoganal optimization is to streamline context handling > > for message send-return, which Ian has also been thinking about. > > That would be great. > > Ian wrote: > > Regular "nfibs" benchmark: > > > > inlined bytecode interpreter: 232516 sends per second > > direct-threaded translator: 363359 sends per second > > > > (Measured with an utterly naive translator -- so you can do >50% better > > than a switch() statement without trying very hard at all. :o) > > That is what I don't understand. Where is this gain coming > from? I suppose by "utterly naive" you mean no peephole > optimizations like the ones John was talking about, no > inline caching, and so on. The improvement comes from one less memory reference. Bytecoded dispatch involves a memory reference to get the byte followed by a memory reference to get the address followed by a jump. Direct-threaded dispatch involves only one memory reference. Note that call-threaded on a machine with a real stack involves three memory references per dispatch, one to fetch the instruction, one to push the return address, and one to pop the return address when returning from the previous opcode. On a RISC with a return address register, these last two memory references are eliminatied, giving it the same performance (bourn-out by experience with BrouHaHa on SPARC) as direct threading. The only way to boost bytecoded efficiency is to align each action routine on a power-of-two boundary and shift and index off a base address. i.e. fetch byte shift by size of action routine add constant base address (usually quicker if in a register than as a constant in the instruction) Though better than bytecode dispatch via a switch table it is insufficient to equal direct-threading. It has ttwo disadvantages: a) uses two registers to be really quick (useless on x86) b) must have one action routine for every bytecode After doing BrouHaHa's direct-threading via gcc + assembler post-processing I wrote a little framework to compare dispatch efficiencies for a simple bytecoded language, i.e.: when invoked the argument n is top-of-stack with return address below: TCODE nfib[] = { /* <ret addr> <n> */ Exchange, /* <n> <ret addr> */ Skip1IfGT1, /* (to L1) */ PopAndReturn1, /* <1> */ /* L1: */ /* <n> <ret addr> */ Duplicate, /* <n> <n> <ret addr> */ Subtract1, /* <n-1> <n> <ret addr> */ Call, (TCODE)nfib, /* <nfib n-1> <n> <ret addr> */ Exchange, /* <n> <nfib n-1> <ret addr> */ Subtract2, /* <n-2> <nfib n-1> <ret addr> */ Call, (TCODE)nfib, /* <nfib n-2> <nfib n-1> <ret addr> */ Add, /* <nfib(n-2)+nfib(n-1)> <ret addr> */ Add1, /* <nfib(n-2)+nfib(n-1)+1> <ret addr> */ ReturnTop /* <nfib(n-2)+nfib(n-1)+1> */ The framework is intended to compare dispatch, not e.g. calling conventions, etc. It has similar instruction-set optimizations as Smalltalk (e.g. push nil, return -> return nil). The same program is expressed as bytecode, shifted bytecode, call-threaded and direct threaded with and without registers for sp & ip. The framework shows that on all machines I've tried (68020/40, 486/586, SPARC, AXP, MIPS) the relative speeds of the various approaches are: slowest bytecode dispatch call-threaded (CISC) shifted bytecode dispatch call-threaded (RISC) direct threaded fastest Performance very-closely follows number of memory references. Some machines, i.e. 486 & 586 have extremely good branch performance. On a 586 without secondary cache the above program, expressed as direct-threaded code, compiled with gcc -O1 ran 2 times slower than an equivalent C program compiled with gcc -O1. On a 586 with secondary cache the gap grew to a factor 2.5. Once you add-in the necessity to do stack-limit checking, and the need to do tagged arithmetic, you get down to the 5 to 6 times slower than C you typically see with threaded-code Smalltalk implementations. However, the real win for tranlation-to-threaded-code over bytecode dispatch in Smalltalk is the ability to implement an in-line method cache. Really, its the fact that one can encode more information in 32-bits of threaded-code op plus a 32-bit parameter than in a byte plus (one or two) byte parameter. As John pointed-out one can do a whole series of peephole or strength-reduction optimizations as traslation-time (e.g. different threaded codes for accessing temps and inst vars from within a method or within a block, sends to self handled differently from sends to other objects). One can also trivially write self-modifying code without flushing the Icache since one is rewriting data-space threaded code pointers, not instructions. Eliot Moss has built a similar framework with his Smalltalk machine. His results should be more informative for Squeak. > BTW, I hope my comments haven't given the impression that I > am against translation to threaded code. In fact, I have > been working on this myself (in Self, where the cost of > using send bytecodes for trivial things like "instance > variable" access is terribly high). I am just trying to > better understand the issues here. My advice: Use direct-threaded code and treat sends-to-self specially. When you bind a send-to-self to an inst var access replace the threaded-code by a code that directly accesses the inst var. Use copy-down to ensure that self is unique. (I.e. do (some of) the things that Self did in native code). Use the following threaded-code pattern: <threaded-code> <paremeter-0> ... <parameter n> and not two separate code and parameter vectors. Cache performance is much better for the former. Write the action routines in gcc C and post-process the assembler to strip prolog and epilog. This is highly portable. e.g. porting the framework above to Windows 95 and the cygnus gnu suite took two hours. I'd still be interested in direct compilation to threaded-code, but that would defeat Dan's desire for code density. One beautiful result of BrouHaHa's translation to threaed-code was as follows: BrouHaHa ran a ParcPlace Objectworks Smalltalk-80 2.3 image with my own closure implementation. So it ran the standard Smalltalk-80 benchmarks. These involve a compiler benchmark which requires that one scan the code-cache checking linked sends to see if they need unlinking given a new method has been defined. The cost of scanning the code cache grew linearly with the size of the code cache and meant that no additional increase in speed (for the benchmarks)was gained by increasing the size of the code cache beyond 128k bytes. There was a 10% gain from 64k bytes to 128k bytes. The engine could limp along with a 32k byte code cache. So given the current 640k Squeak image a 64k translation-to-direct-threaded code cache might weigh-in at some 15% overhead for at least a factor of two performance gain. The additional 5% would come from the larger method caches that map methods to translated methods. The threaded-code action routines are similar in size to a bytecoded interpreter. _______________,,,^..^,,,_______________ Eliot

Post a reply.

Go back to index.



Date: 97 Apr 15 12:14:16 pm From: "David N. Smith" <dnsmith@watson.ibm.com> To: shesha@televar.com Cc: squeak@create.ucsb.edu In-Reply-To: <335282AE.5761@televar.com> Subject: Re: any tutors out there? At 15:17 -0400 4/14/97, Kenneth Collins wrote: >Hello all, > > I am looking for someone to help me learn Smalltalk (Squeak). I have >some questions about how to do some (I think) rather basic things >with/in Squeak. I am new to Smalltalk and fairly new to programming in >general. > I am a student of music composition and considering going into computer >science as well. I could pay as much as $25-30 per "lesson/...". > I subscibed to this mailing list only a couple of weeks ago so I'm not >sure if it's OK to post things like this... forgive me if it's not. > If you are interested, or know someone who may be interested, PLEASE >contact me. > Sincerely, > Kenneth Collins > shesha@televar.com Ken: One place to try is the newsgroup news:comp.lang.smalltalk. Beginners are more than welcome there, as are their questions. This mailing list is for Squeak implementors and gurus to discuss Squeak innards and reproduction techniques. While a Squeak-specific question is OK, the intent here is different than on comp.lang.smalltalk, where a lot of us hang out too. There are a lot of Smalltalk books which can get you over the first hump in the learning curve. My (draft) FAQ at http://www.dnsmith.com.smalltalk lists quite a few. There are none for Squeak but the old Smalltalk-80 series by Goldberg and others comes close and there are some which are not for a specific implementation. (Of course, I'll plug mine: Concepts of Object Oriented Programming, McGraw-Hill, 1991, 1st edition, $25, but there are others.) Welcome to Smalltalk... Dave _______________________________ David N. Smith dnsmith@watson.ibm.com IBM T J Watson Research Center Hawthorne, NY _______________________________ Any opinions or recommendations herein are those of the author and not of his employer.

Post a reply.

Go back to index.



Date: 97 Apr 15 2:06:51 pm From: Maloney <johnm@wdi.disney.com> To: elcm@pacbell.net Cc: squeak@create.ucsb.edu In-Reply-To: <3353B3A4.1424@pacbell.net> Subject: Re: dynamic translation (to threaded code) Eliott: Thanks for sharing the fruits of your long experience with threaded-code Smalltalk VM's. Re: > ... One can also trivially write >self-modifying code without flushing the Icache since one is rewriting >data-space threaded code pointers, not instructions. I've never built a dynamic-translation VM, but my understanding is that the cache-flushing issues can be fiendishly tricky and require one to understand the details of the caching hardware at a fairly low level. The worst case I've heard of was when the engineers at ParcPlace finally traced a caching bug to a *hardware* bug in one model of a certain vendor's processor. These stories make me feel that, for a portable system like Squeak, direct-threading (which avoids all these I-cache coherency issues, as you point out) is the preferred approach even if another 30% might be eeked out by translating to native instructions. Does that seem right? Re: Code cache size 64K to 128K seems pretty a reasonable price to pay for a doubling of performance. Did you ever see a code-cache "thrashing" phenomenon because the code working set exceeded the cache size? Ian's experiments show that translation is extremely fast on modern processors, so I would imagine that the big cost of discarding and re-translating a method might be from the loss of the inline-caches. (This is NOT the case in Self, where the optimizer can expend a lot of effort on a single optimized method.) -- John

Post a reply.

Go back to index.



Date: 97 Apr 15 7:57:41 pm From: Eliot & Linda <elcm@pacbell.net> To: Maloney <johnm@wdi.disney.com> Cc: squeak@create.ucsb.edu Subject: Re: dynamic translation (to threaded code) Hi John, > > Thanks for sharing the fruits of your long experience with > threaded-code Smalltalk VM's. Seems like the Squeakish thing to do :) > Re: > > ... One can also trivially write > >self-modifying code without flushing the Icache since one is rewriting > >data-space threaded code pointers, not instructions. > > I've never built a dynamic-translation VM, but my understanding is that > the cache-flushing issues can be fiendishly tricky and require one to > understand the details of the caching hardware at a fairly low level. > The worst case I've heard of was when the engineers at ParcPlace finally > traced a caching bug to a *hardware* bug in one model of a certain > vendor's processor. and the vendor still hasn't reported back! > These stories make me feel that, for a portable system like Squeak, > direct-threading (which avoids all these I-cache coherency issues, as you > point out) is the preferred approach even if another 30% might be eeked > out by translating to native instructions. > > Does that seem right? Yes. I have two data points. a) BrouHaHa runs at about 75% of the Objectworks 2.3 (PS) and 2.5 (HPS) engines (both Deutsch & Schiffman translators). b) Peter Deutsch told me he'd done a threaded-code engine to test the ideas in PS. It had a very similar architecture to BrouHaHa. Peter said he also got 75% of PS. He was able to calculate the overhead of the direct threaded-code jump and hence project that PS would run 33% faster. > Re: Code cache size > > 64K to 128K seems pretty a reasonable price to pay for a doubling of > performance. Did you ever see a code-cache "thrashing" phenomenon because > the code working set exceeded the cache size? Only below 64k bytes. It certainly thrashed at 32k. I'll collect and report some numbers. > Ian's experiments show that > translation is extremely fast on modern processors, so I would imagine that > the big cost of discarding and re-translating a method might be from > the loss of the inline-caches. Quite possibly. I know that BrouHaHa spends about the same ammount of time managing its code cache than translation + lookup. In fact, one might win by simply throwing away the code cache when one runs out of space. The translator would be simpler, since it could omit the code to compact and relocate references to the cache. However, one can't avoid traversing the stack to retranslate all current activations. It would be interesting to see which approach is faster. > (This is NOT the case in Self, where the > optimizer can expend a lot of effort on a single optimized method.) Indeed. But it prompts me to consider the following equations (where ~ is approx equal): HPS (direct xlate to native) / BHH (direct xlate to threaded) ~ 1.33 HotSpot (inlining xlate to native) / HPS (direct xlate to native) ~ 4 4 / 1.33 = 3 (duh!) So one would expect a Self-style dynamic type feedback inlining translator to threaded code to run considerably faster than HPS and the Squeak system we should have quite soon. Note that threaded-code dispatch should have a higher overhead in a faster system. But there may be more opportunities to peephole (i.e. to combine multiple bytecodes into one threaded code op) in such a design. Also, Intel have done an excellent job removing the need to flush instruction caches on x86. So if the world becomes more Wintel-centric threaded-code's portability/simplicity edge is blunted. But I think Squeak + portable code generation (e.g. direct threaded) has a long-term killer edge which is that its written, debugged and instrumented in Smalltalk. Imagine getting to within say a factor of 3 of C with an inlining direct threaded code architecture, and then just living within its simulation (3 x 3 = 9?). The optimizations might come thick and fast :) _______________,,,^..^,,,_______________ Eliot

Post a reply.

Go back to index.



Date: 97 Apr 15 8:12:10 pm From: "William A. Barnett-Lewis" <wlewis@mailbag.com> To: squeak@create.ucsb.edu Subject: Re: any tutors out there? >Date: Tue, 15 Apr 1997 22:23:17 -0500 >To: "David N. Smith" <dnsmith@watson.ibm.com> >From: "William A. Barnett-Lewis" <wlewis@mailbag.com> >Subject: Re: any tutors out there? > >At 03:32 PM 4/15/97 -0400, you wrote: >>At 15:17 -0400 4/14/97, Kenneth Collins wrote: >>>Hello all, >>> >>> I am looking for someone to help me learn Smalltalk (Squeak). I have >(Snip) > Sincerely, >>> Kenneth Collins >>> shesha@televar.com >>Ken: > >>One place to try is the newsgroup news:comp.lang.smalltalk. Beginners are >>more than welcome there, as are their questions. This mailing list is for >>Squeak implementors and gurus to discuss Squeak innards and reproduction >>techniques. While a Squeak-specific question is OK, the intent here is >>different than on comp.lang.smalltalk, where a lot of us hang out too. >> >>There are a lot of Smalltalk books which can get you over the first hump in >>the learning curve. My (draft) FAQ at http://www.dnsmith.com.smalltalk >>lists quite a few. There are none for Squeak but the old Smalltalk-80 >>series by Goldberg and others comes close and there are some which are not >>for a specific implementation. (Of course, I'll plug mine: Concepts of >>Object Oriented Programming, McGraw-Hill, 1991, 1st edition, $25, but there >>are others.) >> >>Welcome to Smalltalk... >> >>Dave >> >>_______________________________ >>David N. Smith >>dnsmith@watson.ibm.com >>IBM T J Watson Research Center >>Hawthorne, NY >>_______________________________ >>Any opinions or recommendations >>herein are those of the author >>and not of his employer. > >Hello, > >I've been only lurking on this list for a while, mainly due to the reasons cited by David. My primary interest has been in the lisp world, with an especial interest in the lisp machines (Interlisp esp.). Part of my facination with Squeak is frin=m that - i.e. is it possible to take the lessons you're learning here with this smalltalk VM back to a VM based lisp (like the DOS version of Medley)? Still, not knowing much about smalltalk as a language hase made for "interesting" going sometimes ... ;) > >As a result, since I keep hearing of it, is it possible that someone out there knows of a source of the 1st edition of the Blue book? It seems that, given the direction of the 1.XX versions of Squeak, this would be my best bet for finding the equivalent to Allen's "Anatomy of Lisp". > >Thanks in advance for your time and trouble. > >William > > William A. Barnett-Lewis wlewis@mailbag.com ------------------------------------------------------------------------- "We are artists. Poets paint motion and light. Historians paint stills. It can be dangerous to get history from a poet. It can also be the greatest blessing." Larry Miller Murdock -------------------------------------------------------------------------

Post a reply.

Go back to index.



Date: 97 Apr 15 8:53:38 pm From: Jecel Assumpcao Jr <jecel@lsi.usp.br> To: squeak@create.ucsb.edu Subject: Re: dynamic translation (to threaded code) John Maloney wondered about flushing the translation cache: I think that would be much better than trying to keep dependency information. In Self, I sometimes flush the compiled code cache to try to show adaptive compilation in action to people. The resulting pauses are rarely more than just a little annoying. Here is a possible heuristic for getting the most of the threaded code translator - the first time you call a method (the cache misses) you simply use the regular bytecode interpreter. The second time you call the same method (it hits the lookup cache but has no associated translated code) then you call the translator. Of course, this supposes that the lookup cache doesn't thrash much. Dwight Hughes gave a pointer to a neat page: Thanks, I really liked it (though the terminology there was different from the one I had just proposed here). Andreas Raab counted cycles and found indirect jumps too expensive: You got 3 cycles for the call instruction on the 486, but doesn't threading use an indirect call? Eliot gave a very detailed analysis of threading alternatives and an interesting example of translated code for the nfib benchmark: I agree that the difference in the number of memory accesses (specially cache misses) is the largest factor for modern CPUs. Your example is simply great, though I am not sure we can get that kind of agressive inlining and partial evaluation very soon. But I would really like to be able to generate that kind of code and to use it as the input for a native code generator in an adaptive compilation scheme. That way we wouldn't have to repeat a lot of optimizations as we would if we started all over from the original bytecodes. -- Jecel

Post a reply.

Go back to index.



Date: 97 Apr 15 8:57:59 pm From: Jecel Assumpcao Jr <jecel@lsi.usp.br> To: squeak@create.ucsb.edu Subject: Re: Private methods Maloney wrote: > The Self project took some twists and turns that prevented us from > fully exploring this progressive revelation idea, but I'm hoping that > to resume that work in the context of Squeak. The dream is to allow > users to start with a small but consistent view of the system and > then gradually raise the curtain until they can see that all the > facilities that they've been using are implemented in the system > itself. In the Self group, we called this "the green blur" because > the first time Dave Ungar drew a graph of the desired gradual > learning curve he used a green white-board marker. The debugger is a very important piece of such a system. No sense hiding most methods from novices on most browsers and then have them step through all the gory details of a to:do: implementation. This interests me a lot since I am exposing so much more of the implementation in my system. In Squeak, only those interested in examining the workings of the VM simulation have to deal with it. On a fully reflective system, on the other hand, a careless use of the debugger might land you in the middle of the implementation of basic message passing. -- Jecel

Post a reply.

Go back to index.



Date: 97 Apr 15 9:07:57 pm From: Dan Ingalls <DanI@wdi.disney.com> To: Jecel Assumpcao Jr <jecel@lsi.usp.br> Cc: Squeak@create.ucsb.edu In-Reply-To: <33544E62.2A1D609@lsi.usp.br> Subject: Re: dynamic translation (to threaded code) >Here is a possible heuristic for getting the most of the >threaded code translator - the first time you call a >method (the cache misses) you simply use the regular >bytecode interpreter. The second time you call the >same method (it hits the lookup cache but has no >associated translated code) then you call the translator. >Of course, this supposes that the lookup cache doesn't >thrash much. This sounds like a reasonable heuristic. Sometimes, though, heuristics can= be slower than the old KISS philosophy. If you instead make translation fast enough, you can translate it faster= than you can interpret it and, if there are any loops in it, you'll win for= sure. Also, if you always translate on first hit, you might be able to= throw away the bytecode engine, and use that space for more cache. I'm not= saying this is better, but it is an opposite approach that should be consid= ered. - Dan

Post a reply.

Go back to index.



Date: 97 Apr 15 11:57:02 pm From: m3rabb@stono.com (Maurice Rabb) To: squeak@create.ucsb.edu Cc: vitek jan <jvitek@cui.unige.ch> Subject: Re: dynamic translation (to threaded code) Hi, I've been lurking here for a while. Instead of using I-caching, have any of you thought about using compact dispatch tables (CDTs) in Squeak? If you aren't familiar CDTs are an innovative means of enabling a dynamic language to use a message lookup table similar to that used in C++. Jan Vitek developed the technique to its current level. Check out his publications at his web site: http://cuiwww.unige.ch/OSG/Vitek/HomePage.html This is his master's thesis: [.ps.gz] J. Vitek: Compact Dispatch Tables for Dynamically Typed Programming Languages. M. SC. University of Victoria. This is a much shorter paper on CDTs: [.ps.gz] J. Vitek, R.N. Horspool: Compact Dispatch Tables for Dynamically Typed Object Oriented Language CC'96. I recommend Jan's thesis highly. It is well written and contains a fabulous description of all of the message dispatching paradigms, and methods (inline caching, etc.) used to speed message passing. In short, CDTs can be built extremely quickly so as to be usable in a dynamic system. Though a CDT is not quite as fast as a virtual table, it is more compact. Though I last read the paper about 4 months ago, if I remember correctly, Jan's research showed that CDTs are slightly faster than the various I-caching methods, and are less complex. CDTs (along with direct-threading) would certainly be great for applications extracted for small (PDA) systems. I am curious to read your reactions. --Maurice -------------------------------- Maurice Rabb, CTO Stono Technologies, LLC Chicago, Illinois, USA tel 773.281.6003 m3rabb@stono.com

Post a reply.

Go back to index.



Date: 97 Apr 16 8:02:54 am From: Tim Rowledge <rowledge@interval.com> To: Jecel Assumpcao Jr <jecel@lsi.usp.br> Cc: Squeak mailinglist <squeak@create.ucsb.edu> In-Reply-To: <33544FC5.176BF8D2@lsi.usp.br> Subject: Re: Private methods On Tue 15 Apr, Jecel Assumpcao Jr wrote: > Maloney wrote: > > The Self project took some twists and turns that prevented us from > > fully exploring this progressive revelation idea, but I'm hoping that > > to resume that work in the context of Squeak. The dream is to allow > > users to start with a small but consistent view of the system and > > then gradually raise the curtain until they can see that all the > > facilities that they've been using are implemented in the system > > itself. In the Self group, we called this "the green blur" because > > the first time Dave Ungar drew a graph of the desired gradual > > learning curve he used a green white-board marker. > > The debugger is a very important piece of such a system. > No sense hiding most methods from novices on most browsers > and then have them step through all the gory details of > a to:do: implementation. You might like to see how LearningWorks does this sort of thing; Glenn Krasner & I did a bunch of early work on it and Adele pushed Dave Leibs into making the current, fairly impressive capability. Basically, a concept of 'vision' is spe cified and all the tools are supposed to pay enough attention to hide some things and expose others. There's a pointer to LW on my webpage. tim -- Tim Rowledge tim@sumeru.stanford.edu http://sumeru.stanford.edu/tim

Post a reply.

Go back to index.



Date: 97 Apr 16 10:22:26 am From: Mario Wolczko <mario@Eng.Sun.COM> To: jecel@lsi.usp.br Cc: squeak@create.ucsb.edu In-Reply-To: <33544E62.2A1D609@lsi.usp.br> (message from Jecel Assumpcao Jr on Wed, 16 Apr 1997 00:58:26 -0300) Subject: Re: dynamic translation (to threaded code) Jecel wrote: > I think that would be much better than trying to keep > dependency information. In Self, I sometimes flush the > compiled code cache to try to show adaptive compilation > in action to people. The resulting pauses are rarely > more than just a little annoying. This depends on how much code you have, and how much effort has been expended in obtaining it. For the kinds of threaded code implementation being discussed, flushing the cache shouldn't be too bad, because the time to refill it is small. In Self, if you flush the code cache after running a large interactive world for a long time, regenerating optimized code back to the previous state can take ten minutes or more, during which you are running less optimized code (which is noticeably slower), and also incurring many compilation pauses. The system was so painful to use in this state that I spent quite a bit of effort in implementing a mechanism to save the code cache in the snapshot, so that the system would run at full speed immediately upon startup. Mario

Post a reply.

Go back to index.



Date: 97 Apr 16 10:50:15 am From: Ian Piumarta <piumarta@prof.inria.fr> To: mario@Eng.Sun.COM Cc: squeak@create.ucsb.edu Subject: Re: dynamic translation (to threaded code) Mario, > For the kinds of threaded code > implementation being discussed, flushing the cache shouldn't be too > bad, because the time to refill it is small. About 4Mb of cache per second for naive translation on a rusty old Sparc IPX, if my memory serves me right. (It's a couple of months since I measured this, but I think a million bytecodes per second was the figure.) Slightly slower when doing the "macro instruction" optimisations, but in the current scheme we only pay for the analysis when the translator sees the affected bytecodes flying past. For all other bytecodes, that figure should be accurate. On faster machines the most significant factor limiting the refill rate is probably the bandwidth to memory. :-) Ian ------------------------------- projet SOR ------------------------------- Ian Piumarta, INRIA Rocquencourt, Internet: Ian.Piumarta@inria.fr BP105, 78153 Le Chesnay Cedex, FRANCE Voice: +33 1 39 63 52 87 ----------------------- Systemes a Objets Repartis -----------------------

Post a reply.

Go back to index.



Date: 97 Apr 16 3:41:51 pm From: Mario Wolczko <mario@Eng.Sun.COM> To: piumarta@prof.inria.fr Cc: squeak@create.ucsb.edu In-Reply-To: <199704161801.UAA22565@prof.inria.fr> (message from Ian Piumarta on Wed, 16 Apr 1997 20:01:45 +0200) Subject: Re: dynamic translation (to threaded code) > About 4Mb of cache per second for naive translation on a rusty old Sparc > IPX, if my memory serves me right. (It's a couple of months since I > measured this, but I think a million bytecodes per second was the figure.) The unit of measurement I prefer is machine cycles per translated byte of bytecode input, or per generated machine instruction (the bytecode-to-machine code expansion factor should also be quoted to make comparisons easier). Urs Hoelzle's PhD thesis contained measurements for PS and the Self non-inlining compiler, which indicate they take 50 and 400 cycles resp. per generated machine instruction (on SPARC). Your IPX runs at something around 30MHz as I recall, so a million bytecodes per second would be only 30 cycles per bytecode, which seems fast but not implausible. Incidentally, a paper to appear in June's IEEE Micro contains measurements for the SunSoft Java JITs, which come in at 700 and 1300 cycles per byte of input for SPARC and x86, resp. Each byte expands to 5 bytes when compiled on the SPARC, and 4 bytes on the x86 (including auxiliary structures in support of the machine code), so they are slower than the Self NIC; on the other hand, they are more sophisticated. > On faster machines the most significant factor limiting the refill rate > is probably the bandwidth to memory. :-) Now _that_ would be impressive ;-) Mario

Post a reply.

Go back to index.



Date: 97 Apr 17 6:59:29 pm From: lnotarfr@dc.uba.ar (Luciano Esteban Notarfrancesco) To: squeak@create.ucsb.edu Subject: improvements for integers Hi! I am new in Squeak. I installed it just two days ago, and I began to love it!!! I'm a math student, and I am implementing mathematical objetcs in Smalltalk (matrices, multivariated polynomials, etc). I'd like to contribute the Squeak project improving integer arithmetic. By this I mean improve multiplication of LargeIntegers implementing a better algorithm (Karatsuba-Offman), and a few other things, as the algorithm for factorial (yeterday night I tested other algorithm for factorial and it resulted to run about twice the speed of the old implementation, at least with "200 factorial" and "500 factorial"..). May be it could be also improved the integer division algorithm. In the multiplication case, I mentioned Karatsuba-Offman. That algorithm is very simple, and is about O(n^1.58) against the school method that is O(n^2). Also for the special case of squaring I have in mind a derivation of the Karatsuba-Offman algorithm that is better than just mutiplying by self. Another thing that could be improved is the Random class. There is a big problem with Random: it generates random float numbers, while it should generate random integers in a given interval. Suppose you want a random integer between A and B (A and B are integers, A < B). You could do: (B - A * aRandom next + A) truncated but this is wrong... floats have limited presicion, so if B - A is very big, you will lose information, and the result will not be a random integer in that interval (cause the selection will be done just in a subset of the interval, and a lot of values will be imposibles). To fix this problem in Random, the interface don't need to be changed. I'd like to know more about what is in the TODO list for Squeak, and what are all you doing now. There will be a native GUI based UI? (I mean windows managed by the native window manager). It would be nice to have widgets with different looks (Motif-like, Mac-like, Win95-like, NeXTSTEP-like, etc). Thanks a lot, Luciano.-

Post a reply.

Go back to index.



Date: 97 Apr 18 9:45:31 am From: Dan Ingalls <DanI@wdi.disney.com> To: lnotarfr@dc.uba.ar (Luciano Esteban Notarfrancesco) Cc: Squeak@create.ucsb.edu In-Reply-To: <m0wHujh-000iyoC@milagro.dc.uba.ar> Subject: Re: improvements for integers >Hi! >I am new in Squeak. I installed it just two days ago, and I began to love i= t!!! >I'm a math student, and I am implementing mathematical objetcs in >Smalltalk (matrices, multivariated polynomials, etc). Welcome. >I'd like to contribute the Squeak project improving integer arithmetic. >By this I mean improve multiplication of LargeIntegers implementing >a better algorithm (Karatsuba-Offman), and a few other things, as the >algorithm for factorial (yeterday night I tested other algorithm for >factorial and it resulted to run about twice the speed of the old >implementation, at least with "200 factorial" and "500 factorial"..). >May be it could be also improved the integer division algorithm. >In the multiplication case, I mentioned Karatsuba-Offman. That algorithm >is very simple, and is about O(n^1.58) against the school method that is >O(n^2). Also for the special case of squaring I have in mind a derivation >of the Karatsuba-Offman algorithm that is better than just mutiplying >by self. We would love to have the largeInteger arithmetic imaproved. The code that= is there right now is the result of a hasty day's work that I did a year= ago, merely porting forward from an old 16-bit system that had 13-bit= integers. If you would like to contribute improved versions of digitDiv= and digitMultiply, as well as any other obvious improvments, we will work= to include them in future Squeak releases. In terms of the goals of the project, I would say that simpler is usually= better for Squeak. We would always be happy to have code that is fast but= perhaps not the very fastest, if it is very simple and clear, and therefore= understandable by a wide number of people. (I wish we could say that all= of the system conforms to this guideline). Just to let you know, I have two mathematics-related projects that might= interest you. One is to overhaul the coercion mechanism in Squeak, which= can frequently waste a lot of time in mixed-mode arithmetic. For instance= in an inner loop it is much slower to perform <integer> + <float>, letting= the system convert, than it is to run <integer> asFloat + <float>. My goal= is to make the first case run fast enough that you would never bother to= write the second unless you wanted readers to know exactly what is going on= =2E Another project that might interest you or other Squeakers is a sort of= APL-in-Squeak that I am building. The idea is to define a set of array= classes that work like APL, and extend the coercion mechanism in the same= way as in APL. This, together with a very simple browser, could be a very= useful tool, what with Squeak's already good arithmetic, plus Squeak's= ability to extend both the types and the operations of its kernel. I would= like to use this also as a test of how small a kernel of Squeak can be. >Another thing that could be improved is the Random class. There is a big >problem with Random: it generates random float numbers, while it should >generate random integers in a given interval. Suppose you want a random >integer between A and B (A and B are integers, A < B). You could do: > (B - A * aRandom next + A) truncated >but this is wrong... floats have limited presicion, so if B - A is very >big, you will lose information, and the result will not be a random >integer in that interval (cause the selection will be done just in a >subset of the interval, and a lot of values will be imposibles). >To fix this problem in Random, the interface don't need to be >changed. You are right that our Random is limited to a spread determined by its= 32-bit arithmetic. Within that context, though, it has very good and= well-documented behavior, so we would be loth to change it. However, it= you have a better solution for studies of very large numbers, it would be= very good to have it available, either inside of Squeak if it is very= simple, or as a "goodie" that can be imported from a library by people with= such specific needs as yours. >I'd like to know more about what is in the TODO list for Squeak, and >what are all you doing now. There will be a native GUI based UI? (I mean >windows managed by the native window manager). It would be nice to have >widgets with different looks (Motif-like, Mac-like, Win95-like, >NeXTSTEP-like, etc). The core Squeak team is NOT working toward native user interfaces at the= present. On the contrary, our philosophy is to do everything in Squeak= (including even bitBlt). The reason for this is that then Squeak can very= simply be made to run on any OS, or even an any bare machine without an OS,= and it will always behave the same. (Besides Mac, WIndows and Unix, Squeak= also runs on a machine with just a bare Acorn chip, and on the Cassiopeia= hand-held PC). Top on our current TO DO list (other than our "normal" [pilot educational= software] work for Disney) is completion of the Sockets facility, and a new= UI and application construction envrionment called Morphic. Some pieces of= both are already operational in 1.19c. We hope to complete these two= projects in May. Also, Ian Piumarta, with (much) advice from others is= building a new virtual machine for Squeak with the goal of increasing= execution speed by a factor of 2-4x. He will probably have more to say= about his project and his aspirations for it in the weeks to come. This is not to say that a Squeak with native interfaces would not be a= wonderful thing. I would say this is merely waiting for things to settle= down a bit (we have changed a lot in the first few months), so that some= properly motivated group could spin off to do this without getting= hoplessly out of sync with the mainline Squeak work. Again, welcome to Squeak! - Dan

Post a reply.

Go back to index.



Date: 97 Apr 18 10:38:56 am From: Maloney <johnm@wdi.disney.com> To: lnotarfr@dc.uba.ar (Luciano Esteban Notarfrancesco) Cc: squeak@create.ucsb.edu In-Reply-To: <m0wHujh-000iyoC@milagro.dc.uba.ar> Subject: Re: improvements for integers Luciano, Welcome to Squeak! We're glad you like it. I think we'd be very interested in your improved multiplication and squaring algorithm implementations. I often use factorial as an example of a simple recursive function. Thus, I'd want a simple version of factorial to exist in the system somewhere (perhaps in class Integer and overridden in LargePositiveInteger). Squeak Floats are double-precision. The current version of Random is uses only 32-bits of the float (the constants were chosen to work well with 32-bit integers). It is the Park-Miller generator, which has been shown to have reasonably pseudo-randomness properties. Do you have in mind a random number generator with more than 32 bits? Perhaps adding a "nextInteger" method to random would suffice; that way, the calculation you mention would overflow into large integers without losing precision if A and B were large integers. We have no plans to do true native widgets, since we value being able to run the same Squeak image on different platforms with no difference in look and feel. There are situations where native widgets are desirable, however, and others in the Squeak community may be working on native widgets. Using Morphic, you could make widgets that look and feel similar to those on Motif, Mac, Win-95, or whatever. Again, we have no immediate plans to do this, but someone else may have. Thanks for your interest in contributing to Squeak! -- John P.S. Ole Agesen of the Self group did a lot of good things with large integer arithmetic in Self, including things like prime-testing and integer factoring. The source code is freely available and might be useful to you (Ole's comments are pretty good). I could probably dig out an old version if you're interested. -------------------------- >Hi! >I am new in Squeak. I installed it just two days ago, and I began to >love it!!! >I'm a math student, and I am implementing mathematical objetcs in >Smalltalk (matrices, multivariated polynomials, etc). >I'd like to contribute the Squeak project improving integer arithmetic. >By this I mean improve multiplication of LargeIntegers implementing >a better algorithm (Karatsuba-Offman), and a few other things, as the >algorithm for factorial (yeterday night I tested other algorithm for >factorial and it resulted to run about twice the speed of the old >implementation, at least with "200 factorial" and "500 factorial"..). >May be it could be also improved the integer division algorithm. >In the multiplication case, I mentioned Karatsuba-Offman. That algorithm >is very simple, and is about O(n^1.58) against the school method that is >O(n^2). Also for the special case of squaring I have in mind a derivation >of the Karatsuba-Offman algorithm that is better than just mutiplying >by self. >Another thing that could be improved is the Random class. There is a big >problem with Random: it generates random float numbers, while it should >generate random integers in a given interval. Suppose you want a random >integer between A and B (A and B are integers, A < B). You could do: > (B - A * aRandom next + A) truncated >but this is wrong... floats have limited presicion, so if B - A is very >big, you will lose information, and the result will not be a random >integer in that interval (cause the selection will be done just in a >subset of the interval, and a lot of values will be imposibles). >To fix this problem in Random, the interface don't need to be >changed. > >I'd like to know more about what is in the TODO list for Squeak, and >what are all you doing now. There will be a native GUI based UI? (I mean >windows managed by the native window manager). It would be nice to have >widgets with different looks (Motif-like, Mac-like, Win95-like, >NeXTSTEP-like, etc). > >Thanks a lot, >Luciano.- --------------------------

Post a reply.

Go back to index.



Date: 97 Apr 18 12:26:20 pm From: stp (Stephen Travis Pope) To: squeak@create.ucsb.edu Subject: Removals from the Squeak Mailing List Hello Squeakers! There have been a number of cases lately where a user's mail started bouncing. Due to the amount of traffic on the list, and the number of subscribers, my policy is to remove a user from the Squeak list after a couple of days of bounced messages. If you suddenly stop getting mail from the Squeak list (and you have reason to believe that there might have been a problem with your mail delivery), you might ask Majordomo@create.ucsb.edu who's on the Squeak list. stp _Stephen Travis Pope, Center for Research in Electronic Art Technology _(CREATE), Dept. of Music, U. of California, Santa Barbara (UCSB) _Editor, Computer Music Journal (CMJ), MIT Press _stp@create.ucsb.edu http://www.create.ucsb.edu/~stp/

Post a reply.

Go back to index.



Date: 97 Apr 18 2:39:48 pm From: "David N. Smith" <dnsmith@watson.ibm.com> To: Squeak@create.ucsb.edu In-Reply-To: <v03007809af7d5baee895@[206.16.10.79]> Subject: Re: improvements for integers At 14:02 -0400 4/18/97, Dan Ingalls wrote: >> ...SNIP... >>Another thing that could be improved is the Random class. There is a big >>problem with Random: it generates random float numbers, while it should >>generate random integers in a given interval. Suppose you want a random >>integer between A and B (A and B are integers, A < B). You could do: >> (B - A * aRandom next + A) truncated >>but this is wrong... floats have limited presicion, so if B - A is very >>big, you will lose information, and the result will not be a random >>integer in that interval (cause the selection will be done just in a >>subset of the interval, and a lot of values will be imposibles). >>To fix this problem in Random, the interface don't need to be >>changed. > >You are right that our Random is limited to a spread determined by its >32-bit arithmetic. Within that context, though, it has very good and >well-documented behavior, so we would be loth to change it. However, it >you have a better solution for studies of very large numbers, it would be >very good to have it available, either inside of Squeak if it is very >simple, or as a "goodie" that can be imported from a library by people >with such specific needs as yours. Squeak uses double precision numbers which are IEEE floats on most machines today. Select the first number below and do a 'print it'. IEEE doubles provide about 15 decimal digits of precision. That's 53 bits in the hardware representation. 32 bit integers are quite a bit smaller! The problem here isn't that floats have a limited precision but that the random number generator is based on a 31 bit generator. The algorithm is described in detail in 'Random Number Generators: Good Ones Are Hard to Find' by Stephen K. Park and Keith W. Miller (Comm. Asso. Comp. Mach., 31(10):1192--1201, 1988). The authors say that one should not use a generator that is worse. They make no claims for greatness. If you have a better generator, that has been exhaustively tested, we'd be happy to see it submitted to the Squeak library. But you should have seen the one this one replaced! ;-) Dave _______________________________ David N. Smith IBM T J Watson Research Center Hawthorne, NY _______________________________ Any opinions or recommendations herein are those of the author and not of his employer.

Post a reply.

Go back to index.



Date: 97 Apr 18 7:45:04 pm From: Jecel Assumpcao Jr <jecel@lsi.usp.br> To: Squeak@create.ucsb.edu Subject: matrixes (was: improvements for integers) Dan Ingalls wrote: > Another project that might interest you or other Squeakers is a sort of APL-in-Squeak that I am building. The idea is to define a set of array classes that work like APL, and extend the coercion mechanism in the same way as in APL. This, together with a very simple browser, could be a very useful tool, what with Squeak's already good arithmetic, plus Squeak's ability to extend both the types and the operations of its kernel. I would like to use this also as a test of how small a kernel of Squeak can be. Hooray! I always wondered why Smalltalk people insisted on making arrays of arrays instead of something like #( 5 4 6 12 15 17 21 20 21 ) shape: #( 3 3 ) Then they get nasty nested at: expressions that noone can read instead of aMatrix at: #( 2 1 ) Of course, just make every Object answer #(1) to #shape and we're in business! About coercing, it isn't easy to add Complex to the number hierarchy, for example. Once I added imprecise numbers (you know: 4.1 moreOrLess: 0.2) and things got out of hand when trying to get imprecise complex fractions ;-)

Post a reply.

Go back to index.



Date: 97 Apr 20 8:57:22 am From: Aaron Rosenzweig <recurve@xombi.wizard.net> To: Squeak@create.ucsb.edu Subject: System Browser question I'm trying to make new classes in Squeak's System Browser but I'm running into trouble. Specifically I'm going through the Quick Start tutorial that comes with Smalltalk Agents where we make a simple Employee database. The idea is to start off with a "Person" class and then "Employee" which is a subclass of Person. In the System Browser I'm able to "Add Item" in the top left window and give it the name Person. I then edited the Text Edit field in the following way... Object subclass: #Person instanceVAriableNames: 'first last middle prefix suffix birthday sex' classVariableNames: '' poolDictionaries: '' category: 'Person' I then did a "accept it" (which took me a while to figure out) and then I had a Person class in the 2nd window from the left. Now I do an "add item" in the 3rd window from the left to make two categories: "setters" & "getters" Finally when trying to make setter methods in the 4th window from the left I get "No such store" messages. Squeak looks very nice and pretty similar to Smalltalk Agents but I can't seem to figure out how to do things. --- SW Son of Ginger and Harry, Aaron Rosenzweig SW http://www.wam.umd.edu/~recurve/ SW... recurve@resourceful.com SWN?

Post a reply.

Go back to index.



Date: 97 Apr 20 12:55:59 pm From: "David N. Smith" <dnsmith@watson.ibm.com> To: Squeak@create.ucsb.edu In-Reply-To: <33582CE0.4646E34C@lsi.usp.br> Subject: Re: matrixes (was: improvements for integers) At 22:24 -0400 4/18/97, Jecel Assumpcao Jr wrote: >I always wondered why Smalltalk people insisted on making >arrays of arrays instead of something like > > #( 5 4 6 12 15 17 21 20 21 ) shape: #( 3 3 ) > >Then they get nasty nested at: expressions that noone can >read instead of > > aMatrix at: #( 2 1 ) > Don't forget non-rectangular collections like arrays of strings, arrays of ordered collections, or: random := FancyRandomStream new. a := Array new: 10. 1 to: a size do: [ :n | (a at: n) put: (Array new: (random inRange: 10 to: 20)) ] Dave _______________________________ David N. Smith IBM T J Watson Research Center Hawthorne, NY _______________________________ Any opinions or recommendations herein are those of the author and not of his employer.

Post a reply.

Go back to index.



Date: 97 Apr 20 1:05:34 pm From: "David N. Smith" <dnsmith@watson.ibm.com> To: recurve@resourceful.com Cc: Squeak@create.ucsb.edu In-Reply-To: <9704201625.AA00605@wizard.net> Subject: Re: System Browser question At 12:25 -0400 4/20/97, Aaron Rosenzweig wrote: >I'm trying to make new classes in Squeak's System Browser but I'm running >into >trouble. > >Specifically I'm going through the Quick Start tutorial that comes with >Smalltalk Agents where we make a simple Employee database. The idea is to >start off with a "Person" class and then "Employee" which is a subclass of >Person. > >In the System Browser I'm able to "Add Item" in the top left window and >give it >the name Person. > >I then edited the Text Edit field in the following way... >Object subclass: #Person > instanceVAriableNames: 'first last middle prefix suffix birthday sex' > classVariableNames: '' > poolDictionaries: '' > category: 'Person' > >I then did a "accept it" (which took me a while to figure out) and then I >had a >Person class in the 2nd window from the left. > >Now I do an "add item" in the 3rd window from the left to make two categories: >"setters" & "getters" > >Finally when trying to make setter methods in the 4th window from the left I >get "No such store" messages. > >Squeak looks very nice and pretty similar to Smalltalk Agents but I can't >seem >to figure out how to do things. > >--- >SW Son of Ginger and Harry, Aaron Rosenzweig >SW http://www.wam.umd.edu/~recurve/ >SW... recurve@resourceful.com >SWN? After you create the catagory, note that the text window has a prototype method. I usually just select it all and start typing MY method. Then do an Accept. If a category already has methods, I randomly click on one, delete it all, and type in my new one. Accept adds it to the list. Some Smalltalk systems have a menu for adding a new prototype method to the text pane, but it appears that Squeak does not. SmalltalkAgents is a bit off the edge of what is considered Smalltalk by others in that its details differ significantly. Working through a SA tutorial using Squeak may well leave you confused. Dave _______________________________ David N. Smith IBM T J Watson Research Center Hawthorne, NY _______________________________ Any opinions or recommendations herein are those of the author and not of his employer.

Post a reply.

Go back to index.



Date: 97 Apr 21 4:08:25 am From: Georg Gollmann <gollmann@edvz.tuwien.ac.at> To: squeak@create.ucsb.edu Subject: NewsAgent beta Hello, I have put an *early beta* of the Squeak port of my adaptive newsreader (aka NewsAgent) on the web: http://ftp.tuwien.ac.at/~go/Squeak/NewsAgent.st. It requires (some parts of) the auxilliary fileIn http://ftp.tuwien.ac.at/~go/Squeak/miscChanges.st. The NewsAgent monitors your netnews reading habits and ranks new messages by importance, discriminating on author and thread. Below a certain threshold uninteresting artciles are suppressed altogether. See the comment in the NewsAgent class for a few hints. Have fun ! Georg ---- Dipl.Ing. Georg Gollmann TU-Wien, EDV-Zentrum phon:(+43-1) 58801 - 5848 fax: (+43-1) 587 42 11 mail:gollmann@edvz.tuwien.ac.at http://ftp.tuwien.ac.at/~go/Gollmann.html

Post a reply.

Go back to index.



Date: 97 Apr 21 10:30:32 am From: lnotarfr@dc.uba.ar (Luciano Esteban Notarfrancesco) To: squeak@create.ucsb.edu Subject: some stuff Hi. I have some questions and remarks. 1) Squeak implements Message>>sentTo: instead of Message>>reinvokeFor:. Is not this last the standard? (or ST-80 convention) 2) Take a look at the implementation of Integer>>bitAnd:. It bitAnds all the digits of the receiver with the digits of the arguments, up to "self digitLength max: argument digitLength". It should be better to do it up to "self digitLength min: argument digitLength". 3) Object>>isLiteral in the the message categoroty 'printing', while it should be in 'testing'. These are some things I've done the last weekend: !SortedCollection methodsFor: 'accessing'! indexOf: anElement ifAbsent: exceptionBlock "Answer the index of anElement within the receiver. If the receiver does not contain anElement, answer the result of evaluating the argument, exceptionBlock." | first last middle temp | first _ 1. last _ self size. [first <= last] whileTrue: [ middle _ first + last // 2. temp _ self at: middle. (anElement = temp) ifTrue: [^middle]. (sortBlock value: temp value: anElement) ifTrue: [first _ middle + 1] ifFalse: [last _ last - 1] ]. ^ exceptionBlock value ! ! !Integer methodsFor: 'private'! head: n | result resultSize | result _ self class new: (resultSize _ self digitLength - n) neg: false. ^ result replaceFrom: 1 to: resultSize with: self startingAt: n + 1 ! tail: n | result | result _ self class new: n neg: false. ^ result replaceFrom: 1 to: n with: self startingAt: 1 ! karatsubaSquared "Squaring algorithm based on Karatsuba-Ofman algorithm for multiplication." | a b n | n _ self digitLength // 2. a _ self tail: n. b _ self head: n. ^a squared + ((a * b) bitShift: n * 8 + 1) + (b squared bitShift: n * 16) ! ! !Integer methodsFor: 'mathematical functions'! squared "Answer the square of the receiver." ^self digitLength > 25 "this is the threshold I found" ifTrue: [self karatsubaSquared] ifFalse: [self * self] ! ! !Integer methodsFor: 'private'! productUpTo: n "If n is > than the receiver, answer the product of all the integers between the receiver and the argument n, i.e. self * (self + 1) * ... * (n - 1) * n. If n equeals the receiver, answer self. And if n is < than the receiver, answer 1. NOTE: the argument is assumed to be an Integer." | m | self < n ifTrue: [ m _ self + n // 2. ^(m+1 productUpTo: n) * (self productUpTo: m) ]. self > n ifTrue: [^1] ! ! !Integer methodsFor: 'mathematical functions'! factorial "Answer the factorial of the receiver. Create an error notification if the receiver is less than 0." self = 0 ifTrue: [^1]. self < 0 ifTrue: [self error: 'factorial invalid for: ' , self printString] ifFalse: [^1 productUpTo: self] ! !

Post a reply.

Go back to index.



Date: 97 Apr 21 10:39:58 am From: lnotarfr@dc.uba.ar (Luciano Esteban Notarfrancesco) To: johnm@wdi.disney.com (Maloney) Cc: squeak@create.ucsb.edu In-Reply-To: <v03007801af7d679fe106@[206.16.10.227]> from "Maloney" at Apr 18, 97 10:33:30 am Subject: Re: improvements for integers > > I think we'd be very interested in your improved multiplication > and squaring algorithm implementations. I often use factorial as > an example of a simple recursive function. Thus, I'd want a simple > version of factorial to exist in the system somewhere (perhaps in > class Integer and overridden in LargePositiveInteger). Yes. I prefer too a simpler system than an "a bit faster and more complex" one. My factorial is still recursive (it calls #productUpTo: to do all the work, and it's recursive). > > Squeak Floats are double-precision. The current version of Random > is uses only 32-bits of the float (the constants were chosen to > work well with 32-bit integers). It is the Park-Miller generator, > which has been shown to have reasonably pseudo-randomness > properties. Do you have in mind a random number generator with > more than 32 bits? Perhaps adding a "nextInteger" method to > random would suffice; that way, the calculation you mention > would overflow into large integers without losing precision > if A and B were large integers. Yes! I saw in the 1.19d image the new Random with the nextValue method, that answers an Integer (limited precision). With this you could implement #nextIntegerFrom:to: to answer a random integer from a given interval. > > We have no plans to do true native widgets, since we value being > able to run the same Squeak image on different platforms with no > difference in look and feel. There are situations where native > widgets are desirable, however, and others in the Squeak community > may be working on native widgets. Using Morphic, you could make > widgets that look and feel similar to those on Motif, Mac, Win-95, > or whatever. Again, we have no immediate plans to do this, but > someone else may have. OK. I think this approach (the one avoiding the use of native widgets) is better... or at least I like it more. > Ole Agesen of the Self group did a lot of good things with > large integer arithmetic in Self, including things like prime-testing > and integer factoring. The source code is freely available and > might be useful to you (Ole's comments are pretty good). I could > probably dig out an old version if you're interested. Yes... I am very interested!! Tell me from where can I download it or send me a copy. Thanks. Luciano.-

Post a reply.

Go back to index.



Date: 97 Apr 21 10:42:21 am From: lnotarfr@dc.uba.ar (Luciano Esteban Notarfrancesco) To: dnsmith@watson.ibm.com (David N. Smith) Cc: squeak@create.ucsb.edu In-Reply-To: <v03102807af7d8387f4f0@[129.34.225.178]> from "David N. Smith" at Apr 18, 97 05:58:23 pm Subject: Random number generators > > Squeak uses double precision numbers which are IEEE floats on most machines > today. Select the first number below and do a 'print it'. IEEE doubles > provide about 15 decimal digits of precision. That's 53 bits in the > hardware representation. 32 bit integers are quite a bit smaller! > > The problem here isn't that floats have a limited precision but that the > random number generator is based on a 31 bit generator. > > The algorithm is described in detail in 'Random Number Generators: Good > Ones Are Hard to Find' by Stephen K. Park and Keith W. Miller (Comm. Asso. > Comp. Mach., 31(10):1192--1201, 1988). The authors say that one should not > use a generator that is worse. They make no claims for greatness. If you > have a better generator, that has been exhaustively tested, we'd be happy > to see it submitted to the Squeak library. A friend of mine implemented some random number generators for ST/V. I'll test them and probably I'll do a port to Squeak. Those random generators could be useful as goodies. > > But you should have seen the one this one replaced! ;-) I beleave I've seen it... and all the time I was talking about the old one, not the new. The last weekend I replaced the 1.18 image by the new 1.19 (running it always on the 1.18 VM for Linux), and then I saw the new Random. (oh... I have a comment: #nextValue should not be private?). Luciano.-

Post a reply.

Go back to index.



Date: 97 Apr 21 12:38:12 pm From: Eliot & Linda <elcm@pacbell.net> To: Luciano Esteban Notarfrancesco <lnotarfr@dc.uba.ar> Cc: squeak@create.ucsb.edu Subject: Re: some stuff Hi Luciano, the following has a non-obvious and oft-made bug in it: > > !SortedCollection methodsFor: 'accessing'! > > indexOf: anElement ifAbsent: exceptionBlock > "Answer the index of anElement within the receiver. If the receiver does > not contain anElement, answer the result of evaluating the argument, > exceptionBlock." > | first last middle temp | > first _ 1. > last _ self size. > [first <= last] whileTrue: [ > middle _ first + last // 2. > temp _ self at: middle. > (anElement = temp) ifTrue: [^middle]. > (sortBlock value: temp value: anElement) > ifTrue: [first _ middle + 1] > ifFalse: [last _ last - 1] > ]. > ^ exceptionBlock value > ! ! The bug is that the element at middle may be bounded on either side by elements with an equal sort-order. e.g. if the collection is sorting strings ignoring case but the collection includes strings with the same characters but differing cases then the above may not find an element. e.g. try | strings sortedStrings | strings := #('MiXeEd' 'mIxEd' 'Mixed' 'mixed' 'MIXED'). sortedStrings := strings asSortedCollection. strings collect: [:ea| sortedStrings indexOf: ea ifAbsent: ['not found']] It should be more correctly be written: !SortedCollection methodsFor: 'accessing'! indexOf: anElement ifAbsent: exceptionBlock "Answer the index of anElement within the receiver. If the receiver does not contain anElement, answer the result of evaluating the argument, exceptionBlock." | insertionIndex index obj | firstIndex > lastIndex ifTrue: [^exceptionBlock value]. insertionIndex := self indexForInserting: anElement. insertionIndex > lastIndex ifTrue: [insertionIndex := lastIndex] ifFalse: [insertionIndex < firstIndex ifTrue: [insertionIndex := firstIndex]]. index := insertionIndex. [index >= firstIndex and: [obj := self basicAt: index. anElement = obj ifTrue: [^index - firstIndex + 1]. (sortBlock value: anElement value: obj]] whileTrue: [index := index - 1]. index := insertionIndex. [index <= lastIndex and: [obj := self basicAt: index. anElement = obj ifTrue: [^index - firstIndex + 1]. [sortBlock value: obj value: anElement]] whileTrue: [index := index + 1]. ^exceptionBlock value The above method is from SmallWalker, the original version of which had exactly the same bug. _______________,,,^..^,,,_______________ Eliot & Linda

Post a reply.

Go back to index.



Date: 97 Apr 21 5:48:05 pm From: Ranjan Bagchi <ranjan.bagchi@pobox.com> To: squeak@create.ucsb.edu Subject: Compiling under Microsoft Developer Studio [Note, probably windows-version specific] Has sucessfully compiled Squeak (1.18) under Microsoft Developer Studio (VC++ 4.0)? The moment I include either InterpInline1-18a.c or InterpNoInline1-18a.c, the IDE crashes -- I'm assuming at the point VC++ is scanning the file to pull out the names of functions. Thanks, pointers appreciated.. -rj

Post a reply.

Go back to index.



Date: 97 Apr 22 12:25:06 am From: Jon@AppliedThought.com (Jon Hylands) To: squeak@create.ucsb.edu In-Reply-To: <335C0DE9.7298@pobox.com> Subject: Re: Compiling under Microsoft Developer Studio On Mon, 21 Apr 1997 18:01:29 -0700, Ranjan Bagchi = <ranjan.bagchi@pobox.com> wrote: > [Note, probably windows-version specific] >=20 > Has sucessfully compiled Squeak (1.18) under Microsoft Developer Studio > (VC++ 4.0)? Yep. > The moment I include either InterpInline1-18a.c or > InterpNoInline1-18a.c, the > IDE crashes -- I'm assuming at the point VC++ is scanning the file to > pull out the > names of functions. I found I had to add a blank line at the start of each *.h file included = in the project, or I started getting errors up the wazoo... (Don't know why, don't want to know, it just works). Later, Jon ------------------------------------------------------------------------ - Jon Hylands Jon@AppliedThought.com http://www.AppliedThought.com/jon - ------------------------------------------------------------------------ ------------- PGP Fingerprint: 72 0B 9D E3 C2 F0 5D AC ----------------- ------------------------------ E3 D3 3D D0 7B 21 2B 2E ----------------- ------------------------------------------------------------------------

Post a reply.

Go back to index.



Date: 97 Apr 22 3:05:38 am From: Pedro Gomes <pgomes@pc-lur.df.fct.unl.pt> To: Ranjan Bagchi <ranjan.bagchi@pobox.com> Cc: squeak@create.ucsb.edu In-Reply-To: <335C0DE9.7298@pobox.com> Subject: Re: Compiling under Microsoft Developer Studio I did and its great. I had the same problem with the include but instead of doing that, just open the .mak file and then VC asks if you which to convert the makefile to a v4.2 project file and you say yes and then choose the project version and make it. I came across with some crashes of the Squeak while running a V4.2 compiled executable, dont know what is wrong! Pedro Gomes -------------------------------------------------------------------------------- Pedro Miguel Marrecas Gomes | 'Make it simple, not simpler' FCT/UNL Universidade Nova de Lisboa | Albert Einstien 1879-1955 Eng.Fisica | Fisico-Matematico Alemao -------------------------------------------------------------------------------- On Mon, 21 Apr 1997, Ranjan Bagchi wrote: > [Note, probably windows-version specific] > > Has sucessfully compiled Squeak (1.18) under Microsoft Developer Studio > (VC++ 4.0)? > > The moment I include either InterpInline1-18a.c or > InterpNoInline1-18a.c, the > IDE crashes -- I'm assuming at the point VC++ is scanning the file to > pull out the > names of functions. > > Thanks, pointers appreciated.. > > -rj >

Post a reply.

Go back to index.



Date: 97 Apr 22 7:04:51 am From: Aaron Rosenzweig <recurve@xombi.wizard.net> To: Squeak@create.ucsb.edu Subject: Simple print question in Squeak. How come I can't do a: 'Hello' printOn: stdout. <<and then Command-d for "do it">> I understand the System Browser a lot better now and I looked in class "Object" to see that it did have the printOn: method. I guess there isn't a built in "stdout" stream perhaps? How do I create one or what's the equivalent? I know I can do a <<Command-p for "print it">> but I wonder why this doesn't work. Sorry for these silly questions :-) --- SW Son of Ginger and Harry, Aaron Rosenzweig SW http://www.wam.umd.edu/~recurve/ SW... recurve@resourceful.com SWN?

Post a reply.

Go back to index.



Date: 97 Apr 22 7:56:52 am From: Aaron Rosenzweig <recurve@xombi.wizard.net> To: Squeak@create.ucsb.edu Subject: Last stupid questions for today How come methods that I create in the System Browser keep renaming variable names to things like "t1, t2, etc" and also remove any comments that I had? Also, when "printOn:" is used to print a string within a method how come it prints with quotes still included? As promised, these are my last stupid questions for the day :-) --- SW Son of Ginger and Harry, Aaron Rosenzweig SW http://www.wam.umd.edu/~recurve/ SW... recurve@resourceful.com SWN?

Post a reply.

Go back to index.



Date: 97 Apr 22 8:09:25 am From: "Andreas Raab" <raab@isg.cs.uni-magdeburg.de> To: Pedro Gomes <pgomes@pc-lur.df.fct.unl.pt> Cc: squeak@create.ucsb.edu Subject: Re: Compiling under Microsoft Developer Studio > I came across with some crashes of the Squeak while running a V4.2 > compiled executable, dont know what is wrong! There is a good chance that this is due to unsafe implementation of certain byte codes (try "0 nextPut: 0") which have been fixed in 1.19. Unfortunately, I have currently very little time spared for working on the VM, but I may put a new 1.19 VM on the ftp servers in two weeks or so. Andreas -- Linear algebra is your friend - Trigonometry is your enemy. +===== Andreas Raab ============= (raab@isg.cs.uni-magdeburg.de) =====+ I Department of Simulation and Graphics Phone: +49 391 671 8065 I I University of Magdeburg, Germany Fax: +49 391 671 1164 I +=============< http://simsrv.cs.uni-magdeburg.de/~raab >=============+

Post a reply.

Go back to index.



Date: 97 Apr 22 8:28:26 am From: Aaron Rosenzweig <recurve@xombi.wizard.net> To: Squeak@create.ucsb.edu Subject: Squeak's editor question Is there a way to set Squeak to honour indenting from a previous line? --- SW Son of Ginger and Harry, Aaron Rosenzweig SW http://www.wam.umd.edu/~recurve/ SW... recurve@resourceful.com SWN?

Post a reply.

Go back to index.



Date: 97 Apr 22 8:49:10 am From: "Andreas Raab" <raab@isg.cs.uni-magdeburg.de> To: recurve@resourceful.com Cc: squeak@create.ucsb.edu Subject: Re: Simple print question in Squeak. > to see that it did have the printOn: method. I guess there isn't a built in > "stdout" stream perhaps? How do I create one or what's the equivalent? Just select "Open transcript" from the Desktop menu and then Transcript show: 'Hello World' printString. <<Do it>> > I know I can do a <<Command-p for "print it">> but I wonder why this doesn't > work. Sorry for these silly questions :-) I guess you're not using Squeak on a Mac ;-) On Windows the Command key is mapped to the left Alt key NOT to the control key. > How come methods that I create in the System Browser keep renaming > variable names to things like "t1, t2, etc" and also remove any > comments that I had? You've got a problem with your changes file. Make sure its in the same directory as your image and you have write permissions. > Also, when "printOn:" is used to print a string within a method how > come it prints with quotes still included? "printOn:" gives you a textual representation for any object. Strings print something that you can use with the "readFrom:" method, such as | stream | stream := ReadWriteStream on: String new. 'Hello World' printOn: stream. stream reset. String readFrom: stream instead of | stream | stream := ReadWriteStream on: String new. stream nextPut:$'; nextPutAll: 'Hello World'; nextPut:$' stream reset. String readFrom: stream. which would be required if the string would not be quoted. BTW, Stream>>nextPutAll: puts all elements of the argument into the receiver which is exactly like printing without quotes for strings. Andreas -- Linear algebra is your friend - Trigonometry is your enemy. +===== Andreas Raab ============= (raab@isg.cs.uni-magdeburg.de) =====+ I Department of Simulation and Graphics Phone: +49 391 671 8065 I I University of Magdeburg, Germany Fax: +49 391 671 1164 I +=============< http://simsrv.cs.uni-magdeburg.de/~raab >=============+

Post a reply.

Go back to index.



Date: 97 Apr 22 8:59:20 am From: Dan Ingalls <DanI@wdi.disney.com> To: recurve@resourceful.com Cc: Squeak@create.ucsb.edu In-Reply-To: <9704221451.AA00419@wizard.net> Subject: Re: Squeak's editor question Aaron Rosenzweig wrote: >Is there a way to set Squeak to honour indenting from a previous line? Using ctrl-return instead of return will indent up to the previous line= (with some allowance also for intervening brackets as well). You could= probably install that code as the default in your system with a bit of work= =2E Note that this feature is listed in the 'cmd-key help' window accessible= through the 'help...' choice of the screen menu, along with related= indenting assistance such as cmd-L and cmd-R. >How come methods that I create in the System Browser keep renaming variable= =20 >names to things like "t1, t2, etc" and also remove any comments that I had? This is because Squeak is not finding a .changes file on which to record= your source code. When this happens, it does its best to reconstitute the= source by decompiling the method, but it cannot reproduce temp names or= comments. You need to fetch the appropriate .changes file and put it in= the same folder as you image, and make sure it is named in a manner that= correxponds to the name of your image file. Enough people get confused about this that we will put this information into= the code that detects the absence of a .changes file. >Also, when "printOn:" is used to print a string within a method how come it= =20 >prints with quotes still included? PrintOn: tries to produce text that can be re-evaluated to produce an equal= value. If you wish to transfer exactly the characters of the string onto a= stream, then use someStream nextPutAll: theString - Dan

Post a reply.

Go back to index.



Date: 97 Apr 22 10:46:13 am From: johnson@cs.uiuc.edu (Ralph E. Johnson) To: recurve@resourceful.com, Squeak@create.ucsb.edu Subject: Re: Last stupid questions for today At 11:26 AM 4/22/97, Aaron Rosenzweig wrote: >How come methods that I create in the System Browser keep renaming variable >names to things like "t1, t2, etc" and also remove any comments that I had? This is a Frequently Asked Question is there ever was one! Is there a FAQ for Squeak? I'm sure this is on the Smalltalk FAQ. Anyway, the problem is that the image lost the changes file. Suppose your image is called latest.image. The it stores all the source that you have added in latest.changes. VisualWorks changed this to latest.im and latest.cha to fit in better with MS-DOS short file names, and I don't use Squeak on anything but a Mac, so maybe it is different on your system. How does the image lose the changes file? Maybe you deleted it. Maybe you moved the image into a new directory and didn't move the changes file. The possibilities are endless! Once you understand how this works, it is easy to handle, but it trips up lots of new Smalltalkers. >Also, when "printOn:" is used to print a string within a method how come it >prints with quotes still included? If you tell a string to printOn: a stream, it will put quotes around it. You probably want to tell the stream to nextPutAll: the string. -Ralph

Post a reply.

Go back to index.



Date: 97 Apr 22 11:48:40 am From: Maloney <johnm@wdi.disney.com> To: recurve@resourceful.com Cc: Squeak@create.ucsb.edu In-Reply-To: <9704221526.AA00469@wizard.net> Subject: Re: Last stupid questions for today Re: >How come methods that I create in the System Browser keep renaming variable >names to things like "t1, t2, etc" and also remove any comments that I had? Aaron: As others have explained, Squeak isn't finding either the sources or changes file. Be sure you have both these files along with the image and the Squeak application in the same directory (there are other ways to organize the files but this one always works). Under Windows, you have to start Squeak following the instructions in the Readme, or it doesn't find the .changes file. Here's what it says: The VM is run as follows: Squeak <imageName>.image or (after associating the ".image" extension with squeak) simply by double clicking the image. As I recall, you use the "run" menu in the Win95 file manager, which lets you specify the image name as command-line argument. I'm not a Windows user. (If you know how to "associate the ".image" extension with Squeak" in Windows, please let me know!) Cheers! -- John

Post a reply.

Go back to index.



Date: 97 Apr 23 4:16:04 am From: "Andreas Raab" <raab@isg.cs.uni-magdeburg.de> To: Maloney <johnm@wdi.disney.com> Cc: squeak@create.ucsb.edu Subject: Re: Last stupid questions for today > (If you know how to "associate the ".image" extension with Squeak" in > Windows, please let me know!) Just double click the image. A dialog will pop up asking which program to use the image with. Choose "Browse" and select Squeak.exe from the appropriate directory. Mark the "Use this program all the time" checkbox and click ok. That's all. Andreas -- Linear algebra is your friend - Trigonometry is your enemy. +===== Andreas Raab ============= (raab@isg.cs.uni-magdeburg.de) =====+ I Department of Simulation and Graphics Phone: +49 391 671 8065 I I University of Magdeburg, Germany Fax: +49 391 671 1164 I +=============< http://simsrv.cs.uni-magdeburg.de/~raab >=============+

Post a reply.

Go back to index.



Date: 97 Apr 23 7:36:36 am From: Steven Harris <sharris@thinktankinc.com> To: Squeak@create.ucsb.edu Subject: The Pilot Has anyone ported squeak to the Pilot yet? if so, where can I pick it up?

Post a reply.

Go back to index.



Date: 97 Apr 23 8:40:38 am From: Dan Ingalls <DanI@wdi.disney.com> To: sharris@thinktankinc.com Cc: Squeak@create.ucsb.edu In-Reply-To: <335D038C.24D9@thinktankinc.com> Subject: Re: The Pilot >Has anyone ported squeak to the Pilot yet? Not that we know of. >if so, where can I pick it up? I don't think it's likely in the near future. Not enough cycles and not enough pixels. You might want to check with Blair McGlashan <blair@intuitive.co.uk>, who has Squeak running quite well on the Cassiopeia handheld PC. I've had a lot of fun with it on various plane rides.

Post a reply.

Go back to index.



Date: 97 Apr 23 9:55:26 am From: lnotarfr@dc.uba.ar (Luciano Esteban Notarfrancesco) To: elcm@pacbell.net Cc: squeak@create.ucsb.edu In-Reply-To: <335BC4DF.3164@pacbell.net> from "Eliot & Linda" at Apr 21, 97 12:49:52 pm Subject: Re: some stuff > > Hi Luciano, > > the following has a non-obvious and oft-made bug in it: > > > > > !SortedCollection methodsFor: 'accessing'! > > indexOf: anElement ifAbsent: exceptionBlock [...] > > ! ! > > The bug is that the element at middle may be bounded on either side by > elements with an equal sort-order. e.g. if the collection is sorting > strings ignoring case but the collection includes strings with the same > characters but differing cases then the above may not find an element. You are right!!! Sorry... > > It should be more correctly be written: > > !SortedCollection methodsFor: 'accessing'! > indexOf: anElement ifAbsent: exceptionBlock [...] Thanks a lot. Some other methods should be implemented by SortedCollection for efficiency, such as #includes: and #occurrencesOf:. #includes can be implemented in terms of #indexOf:ifAbsent:. This way, using binary search, the speed up when working with big SortedCollections will be remarkable. > > The above method is from SmallWalker, the original version of which had > exactly the same bug. (!) Thanks again. Luciano.-

Post a reply.

Go back to index.



Date: 97 Apr 23 10:02:20 am From: Aaron Rosenzweig <recurve@xombi.wizard.net> To: Squeak@create.ucsb.edu Subject: Fess up! I want know, who was the character who put down: ChangeList browseFile: 'Elvis.st' as a useful expression <<grin>>. You can see it by choosing "help" from the desktop menu and then opening the file of useful expressions. Thanks guys (everyone!) for helping me out, I'm getting more of a feel now. My question for the day is...to read in a file should I use: (FileStream oldFileNamed: 'myfile.st') fileIn and if so, why doesn't the following work: FileStream fileIn: 'myfile.st' I've got to fess up too, I run Squeak on Apple's first PowerBook with a 33Mhz 68030 and passive matrix screen (it was also the first colour model) namely the 165c. I didn't buy it because it was colour, I bought it because it was pretty fast and a grand less than the PowerBook 180. I guess I just sounded like I was running MSWindows. --- SW Son of Ginger and Harry, Aaron Rosenzweig SW http://www.wam.umd.edu/~recurve/ SW... recurve@resourceful.com SWN?

Post a reply.

Go back to index.



Date: 97 Apr 23 10:44:49 am From: Dan Ingalls <DanI@wdi.disney.com> To: recurve@resourceful.com Cc: Squeak@create.ucsb.edu In-Reply-To: <9704231743.AA00411@wizard.net> Subject: Re: Fess up! >My question for the day is...to read in a file should I use: > (FileStream oldFileNamed: 'myfile.st') fileIn >and if so, why doesn't the following work: > FileStream fileIn: 'myfile.st' Just because noone has bothered to put this in. You should feel free to add it to your system. I almost never use the above, but rather open a fileList and, having chosen the file, use one of the two fileIn options in the list menu.

Post a reply.

Go back to index.



Date: 97 Apr 23 10:51:37 am From: Maloney <johnm@wdi.disney.com> To: sharris@thinktankinc.com Cc: Squeak@create.ucsb.edu In-Reply-To: <335D038C.24D9@thinktankinc.com> Subject: Re: The Pilot >Has anyone ported squeak to the Pilot yet? >if so, where can I pick it up? If anyone is considering doing a port of Squeak to the Pilot, I'd be happy to share what I know about the logistics of doing that. I was just talking to a Palm developer who told me some things about their application environment and memory architecture. I agree with Dan about "not enough cycles, not enough pixels" when it comes to running Squeak as a development environment. However, it might well be feasible to use the Pilot to deploy applications such as calendars and address books written in Squeak. Cycles would still be an issue, at least until we get a threaded-code virtual machine. -- John

Post a reply.

Go back to index.



Date: 97 Apr 23 11:12:19 am From: James McCartney <james@clyde.as.utexas.edu> To: Squeak@create.ucsb.edu In-Reply-To: <v03007805af840e740b4d@[206.16.10.18]> Subject: Thread preemption in native/threaded code If/when Squeak moves to a native or threaded code implementation how will you implement preemption of threads? At send-message calls? Will message sends be native function calls rather than one level as they are now? If so, how will you deal with the native stack when changing threads? --- james mccartney james@clyde.as.utexas.edu james@lcsaudio.com If you have a PowerMac check out SuperCollider, a real time synth program: ftp://mirror.apple.com//mirrors/Info-Mac.Archive/gst/snd/super-collider-demo.hqx

Post a reply.

Go back to index.



Date: 97 Apr 23 3:36:18 pm From: Ranjan Bagchi <ranjan.bagchi@pobox.com> To: Squeak@create.ucsb.edu Subject: Re: Last stupid questions for today Maloney wrote: Re: >How come methods that I create in the System Browser keep renaming variable >names to things like "t1, t2, etc" and also remove any comments that I had? Aaron: As others have explained, Squeak isn't finding either the sources or changes file. Be sure you have both these files along with the image and the Squeak application in the same directory (there are other ways to organize the files but this one always works). Under Windows, you have to start Squeak following the instructions in the Readme, or it doesn't find the .changes file. Here's what it says: The VM is run as follows: Squeak <imageName>.image or (after associating the ".image" extension with squeak) simply by double clicking the image. Just my $0.02.. You can watch the process go by executing: Smalltalk openSourceFiles This is called upon startup.. One thing which can go wrong is that the vmPath (answered by a primitive in SystemDictionary>>vmPath) gets set wrong.. when I drop the image file onto the executable, this gets set to C:\WINDOWS\, for some reason. -rj

Post a reply.

Go back to index.



Date: 97 Apr 23 3:39:29 pm From: Ranjan Bagchi <ranjan.bagchi@pobox.com> To: squeak@create.ucsb.edu Subject: Re: Compiling under Microsoft Developer Studio Ranjan Bagchi wrote: [ again.. warning, windows-specific] I wrote: > [I couldn't get it to work, it was crashing VC++] Well.. I finally compiled it. The crashing problem of the IDE problem that I'd reported wasn't due to the source code at all: When VC++ converted the makefile which shipped, it did something funky and created some sort of null project. The IDE looked pretty normal -- the only difference being that the project workspace window had a listins titled 'Classes' and 'Files' as opposed to 'Squeak Classes' and 'Squeak Files', the first word being the project name. But if you added any file -- even an empty .c file to the project, it would crash. <sigh.. shaking fist northwards towards Redmond> Anyway.. the files still wouldn't compile.. windows.h blew up because NOGDI and NOUSER were defined. The problem with NOGDI was documented on the Windows developer CD, NOUSER wasn't. Anyway.. what I'm running into now are run-time issues. Does anyone have a list of self-tests I could run to isolate various components? Moving a window seems to do bad things.. something gets hosed, even though repaints do happen. VM appears unresponsive, and my debugging window is showing a ton of access violation exceptions, which are handled elsewhere. This isn't the case with the shipping image, though, so I'd appreciate some guidance on where to look. Anyway.. once I get this compiling under VC++, I'll let everyone know. -rj

Post a reply.

Go back to index.



Date: 97 Apr 23 3:45:01 pm From: Ranjan Bagchi <ranjan.bagchi@pobox.com> To: Squeak <squeak@create.ucsb.edu> Subject: [windows] My own question I'm experiencing the following.. My changes files is the one I downloaded from the ftp sites (I=A0think).. but the source code doesn't look right -- and sometimes the browse raises the following exception Parser(Object)>>doesNotUnderstand: #classEncoding. I'm going to try and re-download a changes file and source file. This couldn't be a cr/lf mismatch thing, could it? -rj

Post a reply.

Go back to index.



Date: 97 Apr 23 6:28:46 pm From: Eliot & Linda <elcm@pacbell.net> To: Ranjan Bagchi <ranjan.bagchi@pobox.com> Cc: Squeak@create.ucsb.edu Subject: Re: Last stupid questions for today Ranjan Bagchi wrote: > > Maloney wrote: > As others have explained, Squeak isn't finding either the sources or > changes > file. Be sure you have both these files along with the image and the > Squeak > application in the same directory (there are other ways to organize > the > files but this one always works). Under Windows, you have to start > Squeak > following the instructions in the Readme, or it doesn't find the > .changes > file. Here's what it says: > > The VM is run as follows: > > Squeak <imageName>.image > > or (after associating the ".image" extension with squeak) > simply by > double clicking the image. > > Just my $0.02.. > > You can watch the process go by executing: > > Smalltalk openSourceFiles > > This is called upon startup.. One thing which can go wrong is that the > vmPath (answered by a primitive in SystemDictionary>>vmPath) gets set > wrong.. when I drop the image file onto the executable, this gets set to > C:\WINDOWS\, for some reason. I think this explains the sources problems on Windows: It used to be the case (before Windows 95 and NT 4.0) that if you double-clicked on a file that had an associated program (e.g. click on an .image file associated with the Squeak VM) then the acxcociated program would be run in the directory of the file that was clicked on. This is no longer the case under Windows 95 & NT 40. Instead, the program will (certainly under some circumstances) run in the Desktop folder. This broke ParcPlace's own Smalltalk engine. We fixed it by extracting the image file's directory from its name at start-up and cd'ing to that directory. _______________,,,^..^,,,_______________ Eliot

Post a reply.

Go back to index.



Date: 97 Apr 23 7:54:11 pm From: Marcio Marchini <mqm@magmacom.com> To: Squeak@create.ucsb.edu Subject: Re: The Pilot >If anyone is considering doing a port of Squeak to the Pilot, I'd >be happy to share what I know about the logistics of doing that. >I was just talking to a Palm developer who told me some things about >their application environment and memory architecture. The latest OS now supports "DLLs". In theory you could partition the image in components like VisualAge does (ICs). >I agree with Dan about "not enough cycles, not enough pixels" >when it comes to running Squeak as a development environment. However, >it might well be feasible to use the Pilot to deploy applications >such as calendars and address books written in Squeak. These 2 apps exist in ROM. But anything else ! ;-) (for instance, moving map software, where you can connect your Pilot to a GPS & display where you are showing vector-graphics maps). >Cycles would >still be an issue, at least until we get a threaded-code >virtual machine. As I said before, I think it makes more sense to do something like Jump. Just generate a ASM file, and the whole thing gets native. It's like a packaging step (for those familiar with ENVY/Packager). The runtime generated by Jump is quite fast. The GC is very simple, has only about 220 bytes of instructions. I could post it here if people are interested. (no, I did not implement it -- I am just a user !) marcio ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ http://www2.magmacom.com/~mqm

Post a reply.

Go back to index.



Date: 97 Apr 23 9:58:31 pm From: dave <drs@cs.wisc.edu> To: squeak@create.ucsb.edu Cc: Allen_Wirfs-Brock@Instantiations.com Subject: Starting From Scratch (Minimalism) Greetings! I need some advice on how to proceed. What I want to do is (literally) start from scratch--I want to figure out how to write an initial squeak image which has an absolutely *minimal* complement of classes--(hell, how about none at all?)--just enough to get me running; no browsers, nothing but barebones subsystem. You might think of it as doing "assembler in smalltalk," or working on the edge of the transformation from a compile-time system to a runtime one. This transformation is what interests me at the moment, and I thought a Minimalist Squeak would make a good vehicle for investigation. It's something I've thought about for a long time, but up until recently I was never in a position to try it; I didn't have working source on hand. All advice in this direction welcome... Thanks very much in advance, [BTW, please mail replies directly as I am not on the ML] Again, Thanks! dave

Post a reply.

Go back to index.



Date: 97 Apr 23 10:49:01 pm From: James McCartney <james@clyde.as.utexas.edu> To: squeak@create.ucsb.edu In-Reply-To: <33526B6F.156ECE76@lsi.usp.br> Subject: Re: dynamic translation At 10:37 AM -0700 4/14/97, Jecel Assumpcao Jr wrote: > - direct threading: the code is compiled into an array of function > pointers that are called by a code like this: > > while (true) (* ip++) (); > > On some machines we can use the stack pointer as the interpreter's > PC (or ip) and the inner loop becomes a simple return instruction. I used this approach on my earlier virtual machine. On the PowerPC, under Metrowerks' compiler at least, indirect function calls go through a piece of glue code called ptr_glue(). This function accounted for a large percentage of my runtime. Have any of the benchmarks posted by others for direct threading been done for the PowerPC? --- james mccartney james@clyde.as.utexas.edu james@lcsaudio.com If you have a PowerMac check out SuperCollider, a real time synth program: ftp://mirror.apple.com//mirrors/Info-Mac.Archive/gst/snd/super-collider-demo.hqx

Post a reply.

Go back to index.



Date: 97 Apr 23 11:01:26 pm From: James McCartney <james@clyde.as.utexas.edu> To: squeak@create.ucsb.edu In-Reply-To: <v03020900af5be84e840f@[128.83.253.38]> Subject: Re: dynamic translation At 1:18 AM -0700 3/24/97, James McCartney wrote: ^^^^^ oops bad date. >At 10:37 AM -0700 4/14/97, Jecel Assumpcao Jr wrote: > >> - direct threading: the code is compiled into an array of function >> pointers that are called by a code like this: >> >> while (true) (* ip++) (); >> >> On some machines we can use the stack pointer as the interpreter's >> PC (or ip) and the inner loop becomes a simple return instruction. > >I used this approach on my earlier virtual machine. On the PowerPC, >under Metrowerks' compiler at least, indirect function calls go >through a piece of glue code called ptr_glue(). This function accounted >for a large percentage of my runtime. Have any of the benchmarks >posted by others for direct threading been done for the PowerPC? Also I should mention that __ptr_glue() has two loads, a store and a branch. I forget what it is supposed to be doing, but it doesn't make for fast threaded interpreters. --- james mccartney james@clyde.as.utexas.edu james@lcsaudio.com If you have a PowerMac check out SuperCollider, a real time synth program: ftp://mirror.apple.com//mirrors/Info-Mac.Archive/gst/snd/super-collider-demo.hqx

Post a reply.

Go back to index.



Date: 97 Apr 24 6:47:25 am From: tim <tim@apple.com> To: "James McCartney" <james@clyde.as.utexas.edu>, <squeak@create.ucsb.edu> Subject: Re: dynamic translation James McCartney wrote: >>At 10:37 AM -0700 4/14/97, Jecel Assumpcao Jr wrote: >>I used this approach on my earlier virtual machine. On the PowerPC, >>under Metrowerks' compiler at least, indirect function calls go >>through a piece of glue code called ptr_glue(). This function accounted >>for a large percentage of my runtime. Have any of the benchmarks >>posted by others for direct threading been done for the PowerPC? > >Also I should mention that __ptr_glue() has two loads, a store and >a branch. I forget what it is supposed to be doing, but it doesn't >make for fast threaded interpreters. The ptr_glue() code is used to switch the TOC pointer register in cross-TOC calls. Since the compiler usually cannot know whether a call through a pointer will be to a routine that uses the same TOC or not, these usually have to go through the ptr_glue() code. -- Tim Olson Apple Computer, Inc. / Somerset (tim@apple.com)

Post a reply.

Go back to index.



Date: 97 Apr 24 7:27:08 am From: Maloney <johnm@wdi.disney.com> To: Marcio Marchini <mqm@magmacom.com> Cc: Squeak@create.ucsb.edu In-Reply-To: <199704240317.XAA13486@mag1.magmacom.com> Subject: Re: The Pilot What is Jump? Where could I find out more about it? Thanks! -- John > As I said before, I think it makes more sense to do >something like Jump. Just generate a ASM file, and the >whole thing gets native. It's like a packaging step (for >those familiar with ENVY/Packager). > > The runtime generated by Jump is quite fast. The GC is >very simple, has only about 220 bytes of instructions. I could >post it here if people are interested.

Post a reply.

Go back to index.



Date: 97 Apr 24 7:27:06 am From: Maloney <johnm@wdi.disney.com> To: elcm@pacbell.net Cc: Squeak@create.ucsb.edu In-Reply-To: <335EBD36.410E@pacbell.net> Subject: Re: Last stupid questions for today >It used to be the case (before Windows 95 and NT 4.0) that if you >double-clicked on a file that had an associated program (e.g. click on >an .image file associated with the Squeak VM) then the acxcociated >program would be run in the directory of the file that was clicked on. >This is no longer the case under Windows 95 & NT 40. Instead, the >program will (certainly under some circumstances) run in the Desktop >folder. This broke ParcPlace's own Smalltalk engine. We fixed it by >extracting the image file's directory from its name at start-up and >cd'ing to that directory. The Mac version of Squeak does a similar thing. It would be nice if this "drag-n-drop" staratup worked in the Windows version, since it would reduce problems for first-time users. However, I'm simply delighted to have a Windows version of Squeak that works so well once you know how to start it. So I think the main thing is just to pass the word to new users about this minor glitch and its work-around. -- John

Post a reply.

Go back to index.



Date: 97 Apr 24 7:49:53 am From: "David N. Smith" <dnsmith@watson.ibm.com> To: Squeak@create.ucsb.edu Cc: Squeak@create.ucsb.edu In-Reply-To: <199704240317.XAA13486@mag1.magmacom.com> Subject: Re: The Pilot At 23:17 -0400 4/23/97, Marcio Marchini wrote: >>Cycles would >>still be an issue, at least until we get a threaded-code >>virtual machine. > > > As I said before, I think it makes more sense to do >something like Jump. Just generate a ASM file, and the >whole thing gets native. It's like a packaging step (for >those familiar with ENVY/Packager). > > The runtime generated by Jump is quite fast. The GC is >very simple, has only about 220 bytes of instructions. I could >post it here if people are interested. > > (no, I did not implement it -- I am just a user !) > >marcio Hi: Maybe I came in late, but what is Jump? I just got a Pilot and the development system, but have yet done nothing but play with the Pilot itself. Dave _______________________________ David N. Smith IBM T J Watson Research Center Hawthorne, NY _______________________________ Any opinions or recommendations herein are those of the author and not of his employer.

Post a reply.

Go back to index.



Date: 97 Apr 24 8:53:59 am From: "Andreas Raab" <raab@isg.cs.uni-magdeburg.de> To: elcm@pacbell.net Cc: squeak@create.ucsb.edu Subject: Re: Last stupid questions for today > > I think this explains the sources problems on Windows: > > It used to be the case (before Windows 95 and NT 4.0) that if you > double-clicked on a file that had an associated program (e.g. click on > an .image file associated with the Squeak VM) then the acxcociated > program would be run in the directory of the file that was clicked on. > This is no longer the case under Windows 95 & NT 40. Instead, the > program will (certainly under some circumstances) run in the Desktop > folder. This broke ParcPlace's own Smalltalk engine. We fixed it by > extracting the image file's directory from its name at start-up and > cd'ing to that directory. This sounds very likely. I'll add it to the next VM version. However, I assume that the problem with the changes file is mainly due to the (since 1.19 fixed) bug in FileDirectory>>includesKey: Here is the method from 1.19d: --------------------------------------------------------------------- 'From Squeak 1.19d of April 13, 1997 on 24 April 1997 at 5:13:37pm' !!FileDirectory methodsFor: 'dictionary access'! includesKey:aString "Answer whether the receiver includes an element of the given name." "Note: aString may designate a file local to this directory, or it may be a full path name. Try both." ^ (StandardFileStream isAFileNamed: pathName , self pathNameDelimiter asString , aString) or: [StandardFileStream isAFileNamed: aString]! ! ------------------------------------------------------------------- This should fix the t1, t2 ... variable names and comments. Andreas -- Linear algebra is your friend - Trigonometry is your enemy. +===== Andreas Raab ============= (raab@isg.cs.uni-magdeburg.de) =====+ I Department of Simulation and Graphics Phone: +49 391 671 8065 I I University of Magdeburg, Germany Fax: +49 391 671 1164 I +=============< http://simsrv.cs.uni-magdeburg.de/~raab >=============+

Post a reply.

Go back to index.



Date: 97 Apr 24 10:00:49 am From: ken.stevens@srs.gov To: mqm@magmacom.com, johnm@wdi.disney.com Cc: Squeak@create.ucsb.edu What is Jump? Where could I find out more about it? Thanks! -- John > As I said before, I think it makes more sense to do >something like Jump. Just generate a ASM file, and the >whole thing gets native. It's like a packaging step (for >those familiar with ENVY/Packager). > > The runtime generated by Jump is quite fast. The GC is >very simple, has only about 220 bytes of instructions. I could >post it here if people are interested. Can squeak be ported to the Message Pad 2000? Ken

Post a reply.

Go back to index.



Date: 97 Apr 24 11:31:41 am From: Jecel Assumpcao Jr <jecel@lsi.usp.br> To: squeak@create.ucsb.edu Subject: InterpreterSimulation Is the Interpreter simulation supposed to run on non Mac machines? I took a quick look at it and didn't see any of the little endian stuff that is needed on my Intel boxes. I wanted to see how fast this would be on a reasonable machine to decide if I should write the second version of my tinySelf interpreter in Squeak instead of Self (using borrowed Sparcstations really cuts productivity down a lot). -- -----=============( Jecel Mattos de Assumpcao Jr )===========----- http://www.lsi.usp.br/~jecel/merlin.html | mailto:jecel@lsi.usp.br PS: DNS problems with my internet access provider have left me "mailless" since last Friday. If you sent me something during that time, please send it again.

Post a reply.

Go back to index.



Date: 97 Apr 24 3:08:52 pm From: Ian Piumarta <piumarta@prof.inria.fr> To: jecel@lsi.usp.br, squeak@create.ucsb.edu Subject: Re: InterpreterSimulation Jecel, The InterpreterSimulator is seriously broken on non big-endian machines (intel included). Last night I finally got round to fixing this. You need to change several methods to make it work properly, and the changes aren't obvious. In part, the problem is that there is no guaranteed correspondance between word objects having swapped bytes, and byte objects having swapped bytes. A very quick fix which should work for you is as follows. Save an image for simulation (clonex.image, or whatever) on the *same* platform as you want to run the simulator (this guarantees that the image read into the memory Bitmap will have its word objects the right way round). The interpreter simulator *imposes* a big-endian ordering on byte objects, so if your architecture doesn't agree (intel, for example) then you can change the #byteAt: and #byteAt:put: methods in class InterpreterSimulator to use little-endian addressing. The little-endian definitions are as follows: byteAt: byteAddress | lowBits | lowBits _ byteAddress bitAnd: 3. ^((self longAt: byteAddress - lowBits) bitShift: (0 - lowBits) * 8) bitAnd: 16rFF! ! byteAt: byteAddress put: byte | longWord shift lowBits | lowBits _ byteAddress bitAnd: 3. longWord _ self longAt: byteAddress - lowBits. shift _ (lowBits) * 8. longWord _ longWord - (longWord bitAnd: (16rFF bitShift: shift)) + (byte bitShift: shift). self longAt: byteAddress put: longWord! ! This has been working for me on an intel platform (while I'm temporarily away from my cuddly Mac ;-). Hope this helps! Regards, Ian

Post a reply.

Go back to index.



Date: 97 Apr 24 3:48:38 pm From: Allen Wirfs-Brock <Allen_Wirfs-Brock@Instantiations.com> To: drs@cs.wisc.edu Cc: squeak@create.ucsb.edu, Steve_Messick@Instantiations.com In-Reply-To: <335EEE15.45A1@cs.wisc.edu> Subject: Re: Starting From Scratch (Minimalism) Dave, What you are talking about sounds very similar to some of the things we did at Digitalk and ParcPlace. I know you already have the pointer to my paper on declaratively defining Smalltalk programs. In addition you may be interested in looking at the slides at (http://www.smalltalksystems.com/publications/awss97/INDEX.HTM) which towards the end actually report on some of the results we achieved. The "classic" way to try to create a minimal image is to try to "clone" a running image and in the process to remove all unneeded objects (including unneeded classes). A "cloner" is essentially a graph-walker that starts with the root objects of the running image and writes all desired objects out to a new image file. The cloner can have knowledge built into it such that it can be selective about which parts of the graph it writes. The cloner can also be defined such that it performs transformations upon the objects as they are written. For example, it might replace all compiled methods with compiled methods that use a different object format. Smalltalk-80 Version 1 (and Version 2, I believe) had a class named SystemTracer that was a cloner. Looking at Squeak 1.1 I do not see this class included in the image. Perhaps some member of the Squeak community can tell you whether it or a similar cloner is available. If not, perhaps you can find someone with an original V1 image or a Tektronix Smalltalk system who could file that class out for you. Warning!! The original V1 SystemTracer was buggy! Cloning generally proved to be a relatively unsatisfactory way to try to produce minimal images. There's simply too much stuff entangle in a development image to systematically determine what is "unnecessary". This lead us to an approach that has the following characteristics: A Smalltalk program is defined constructively, not destructively. You add in what you need instead of stripping out what you don't need. The program is specified declaratively, instead of imperatively. There are declarations for classes, globals, etc. instead of using reflective messages to create them. The "target" program is kept logically distinct from the program (classes) that implement the development environment. In practice what we did was build an object model of the target program that was separate from the executable object model (class objects, compiled methods, method dictionaries, etc.) which in a standard image defines both the development environment and application images. From the object model of the target program we then generate an image file that contains only the classes defined by the target program along with a very small number of runtime support data structures. In conventional terms what we have is an "intermediate" representation of the program and a "backend" that generates image files. Because the backend knows it is generating a runtime image it only needs to include support mechanisms that are actually required at application runtime. The shapes of objects known by the virtual machine (classes, method dictionaries, methods, etc.) must be maintained but for the most part behaviors or application program accessibility is not needed for these objects (unless the target program is reflective). Using these techniques we have generated functional images that can be very small. For example, in one of our implementations we generated an image for the "program" 3+4 that was < 5k total size. Images for reasonably functional utility style programs (cat, sort, etc.) that require significant class libraries to implement have been in the 50k-100K range. At ParcPlace we used this technique to regenerate the entire VisualWorks system from source code. As far as I know this was the first complete regeneration of a Xerox Smalltalk derived image since the early days of Smalltalk-76. Good luck. What you want to do is possible and I think worth while. I'll be happy to try to answer any more specific questions. Allen Wirfs-Brock Instantiations, Inc. At 12:22 AM -0500 4/24/97, dave wrote: >Greetings! > >I need some advice on how to proceed. What I want to do is (literally) >start from scratch--I want to figure out how to write an initial >squeak image which has an absolutely *minimal* complement of >classes--(hell, how about none at all?)--just enough to get me >running; no browsers, nothing but barebones subsystem. You might think >of it as doing "assembler in smalltalk," or working on the edge >of the transformation from a compile-time system to a runtime one. >This transformation is what interests me at the moment, and I thought >a Minimalist Squeak would make a good vehicle for investigation. > >It's something I've thought about for a long time, but up until >recently I was never in a position to try it; I didn't have working >source on hand. All advice in this direction welcome... > >Thanks very much in advance, > >[BTW, please mail replies directly as I am not on the ML] > >Again, Thanks! >dave

Post a reply.

Go back to index.



Date: 97 Apr 24 8:14:17 pm From: Marcio Marchini <mqm@magmacom.com> To: Squeak@create.ucsb.edu Subject: Re: The Pilot >What is Jump? Where could I find out more about it? Both Jump & Co-Pilot (a Pilot simulator that runs on the PC) can be found at http://userzweb.lightspeed.net/~gregh/pilot/ The newsgroup to discuss it is at host news.massena.com, group pilot.programmer.jump. marcio ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ http://www2.magmacom.com/~mqm

Post a reply.

Go back to index.



Date: 97 Apr 24 8:24:09 pm From: Jecel Assumpcao Jr <jecel@lsi.usp.br> To: Ian Piumarta <piumarta@prof.inria.fr> Cc: squeak@create.ucsb.edu Subject: Re: InterpreterSimulation Ian Piumarta wrote: > A very quick fix which should work for you is as follows. Save an > image for simulation (clonex.image, or whatever) on the *same* > platform as you want to run the simulator (this guarantees that the > image read into the memory Bitmap will have its word objects the right > way round). The interpreter simulator *imposes* a big-endian ordering > on byte objects, so if your architecture doesn't agree (intel, for > example) then you can change the #byteAt: and #byteAt:put: methods in > class InterpreterSimulator to use little-endian addressing. The > little-endian definitions are as follows: > [ deleted to save space ] > > This has been working for me on an intel platform (while I'm > temporarily away from my cuddly Mac ;-). > > Hope this helps! Regards, Thanks! This almost worked: I had to patch #nextLongFrom: as well (I was using an old 1.16 VM - maybe newer ones don't have this problem). On my mom's 166MHz Pentium running Squeak in Squeak resulted in 11k bytecodes per second. This is 625 slower than the host Squeak, but it is faster than some early Smalltalk-80 implementations! Anyway, it is fast enough for what I need to do. Thanks again for the tip! I have a Mac too, but I never use it as there is no way to connect a hard disk to it (remember life before the Plus :-( ). -- Jecel

Post a reply.

Go back to index.



Date: 97 Apr 24 8:24:23 pm From: Jecel Assumpcao Jr <jecel@lsi.usp.br> To: Allen Wirfs-Brock <Allen_Wirfs-Brock@Instantiations.com> Cc: drs@cs.wisc.edu, squeak@create.ucsb.edu Subject: Re: Starting From Scratch (Minimalism) Self has an interesting concept: the "empty world". When the VM starts up, it creates a minimum set of object to get things going. There isn't much you can do in an empty world - even "3+4" causes a lookup error. But you can invoke primitives ( "3 _IntAdd: 4" works, for example) and either load an image or file in the sources to recreate the image from scratch. Though I am not sure, you might also find this idea in GNU Smalltalk. In Little Smalltalk, you create two virtual machines from the sources: a normal one for daily use and a special one that can only file in all the sources and spit out an image as a result. -- Jecel

Post a reply.

Go back to index.



Date: 97 Apr 24 11:02:26 pm From: Maloney <johnm@wdi.disney.com> To: Jecel Assumpcao Jr <jecel@lsi.usp.br> Cc: squeak@create.ucsb.edu In-Reply-To: <335FA933.16081E0E@lsi.usp.br> Subject: Re: InterpreterSimulation Jecel, Squeak is probably 10 to 30 times slower than Self (when the Self code cache is warm, that is). So I would expect an interpreter running in it to be pretty slow. However, you could take the Squeak approach of debugging an interpreter written in Smalltalk and then translating that to C to get reasonable performance. You could even use the Squeak ObjectMemory module as a starting point for the tinySelf object memory. Cheers! -- John >Is the Interpreter simulation supposed to run on non Mac >machines? I took a quick look at it and didn't see any >of the little endian stuff that is needed on my Intel >boxes. > >I wanted to see how fast this would be on a reasonable >machine to decide if I should write the second version >of my tinySelf interpreter in Squeak instead of Self >(using borrowed Sparcstations really cuts productivity >down a lot). >-- >-----=============( Jecel Mattos de Assumpcao Jr )===========----- >http://www.lsi.usp.br/~jecel/merlin.html | mailto:jecel@lsi.usp.br > >PS: DNS problems with my internet access provider have left >me "mailless" since last Friday. If you sent me something >during that time, please send it again.

Post a reply.

Go back to index.



Date: 97 Apr 25 3:14:43 am From: Peter Munro <munro@lunatech.com> To: Squeak@create.ucsb.edu In-Reply-To: <199704241722.AA14238@gateway1.srs.gov> Subject: Re: Squeak on MessagePad 2000? On Thu, 24 Apr 1997 ken.stevens@srs.gov wrote: > Can squeak be ported to the Message Pad 2000? > > > Ken Well, NewtonScript is also bytecode-interpreted, so in theory, yes. One option would be to map from one to the other at the byte-code level (or ideally use a universal bytecode interpreter ;-). The user-interface classes would either have to be replaced with or mapped to Newton's view system. It's a nice idea, as applications could be built easily (and dynamically) on other systems, transported to the MP 2000 device and run there. One could, by having code blocks migrate from system to system, build a nice infrastructure for agents, which could be initiated from an MP 2000 together with mobile handset (eg GSM). Regards, Pete ---- Peter Munro <mailto:munro@lunatech.com> Lunatech Research. Committed? We should be. <http://www.lunatech.com/>

Post a reply.

Go back to index.



Date: 97 Apr 25 7:01:50 am From: stp (Stephen Travis Pope) To: Allen Wirfs-Brock <Allen_Wirfs-Brock@Instantiations.com>, drs@cs.wisc.edu Cc: squeak@create.ucsb.edu, Steve_Messick@Instantiations.com In-Reply-To: Allen Wirfs-Brock <Allen_Wirfs-Brock@Instantiations.com>'s letter of: 97 Apr 24 Subject: Re: Starting From Scratch (Minimalism) There are two topics here: cloning an image and making a minimal one. For the first part, there is a history of "image writers" that were used whenever the image format changed (most recently with the introduction of the HPS virtual machine about 10 years ago). When the format changes, it's obviously necessary to write out a new image from scratch in the new format using some tool in the old image. The SystemTracer did this. Making a minimal image is a different task. As Alan writes, Smalltalk is much different than languages that build stand-alone executables with a linker. There are tools such as the ParcPlace "whittler" that recursively run through all the classes and methods in an image and try to determine which can safely be removed to leave a base set of applications (defined by the user) operational. This tool is/was available from ParcPlace ProfSvcs. stp Stephen Travis Pope, Center for Research in Electronic Art Technology (CREATE), Department of Music, U. of California, Santa Barbara (UCSB) Editor--Computer Music Journal, MIT Press stp@create.ucsb.edu, http://www.create.ucsb.edu/~stp/

Post a reply.

Go back to index.



Date: 97 Apr 25 9:49:21 am From: Paul Fernhout <kfsoft@netins.net> To: Squeak@create.ucsb.edu Subject: Re: Squeak on MessagePad 2000? Peter Munro wrote (on putting Squeak on a Newton): > Well, NewtonScript is also bytecode-interpreted, so in theory, yes. > One option would be to map from one to the other at the byte-code > level (or ideally use a universal bytecode interpreter ;-). This a very good idea, possibly the best I've heard for the Squeak->Newton port. Two issues that might make this difficult are: * I don't think Apple has released the VM specifications or byte code specs (please correct me if I am wrong). Reverse engineering is against the license, although in Europe that would not neccessarily apply in some cases (I believe an exemption is given for reverse engineering to make compatible products, although IANAIL (extra I for international)). [Your web site said you're company, Lunatech Research, has an office in Rotterdam, the Netherlands. (That is a beautiful city; my mother is from there). So presumably you could do such reverse engineering - although you'd need to check it out with a lawyer first.] * A minor point, but the byte codes might not cover everything you need to do, especially since they were designed for prototype inheritence. So you still might have to code primitives in C++ or take a hit on interpreted NewtonScript. If you can pry the Newton C compiler out of Apple, adding small performance enhancing snippets of code is what it was designed for. Still these issues are probably resolveable with Apple's cooperation. A similar concept could be applied to doing JAVA translation. Also, you might still have some fine tuning to do to make sure the debugger works with the alternate byte codes. If you built this translator into Squeak, you could then create byte code sequences and store them in FLASH RAM, thus reducing the image size and DRAM needs. Limited DRAM being the Newton's biggest weakness as far as Squeak is concerned, and even with thing translated to NewtonScript byte codes, the image might still be too big for the free frame or C heap (~500K split between the two). 650K is the smallest I've heard for the Squeak image size - but I don't think this includes the VM - and I don't think the Newton will execute code in place in FLASH (which seems easy enough to do - so I don't see why not, but that is what I read somewhere). Here is another alternative based on your idea. In the past I had written of translating the VM to NewtonScript, although there would be possibly a big performance penalty (given various tradefoffs since NewtonScript doesn't have pointers, and compiled (faster) NewtonScript takes more DRAM (3X) than the byte codes. But, maybe we don't have to do that at all, since Squeak is written in itself. Every Newton comes with a built in NewtonScript interpreter (which I believe compiles to byte codes). What if we made a minor alteration to your idea and added a dynamic translator to Squeak to convert Smalltalk methods and blocks to NewtonScript, and then used the Newton to compile the NewtonScript and put it in Package memory (like Steve Weyer's Newt NewtonScript development system which runs native on the Newton)? Then we wouldn't have to deal with the issues of understanding the byte codes. Here is an example of doing a simple translation: The Smalltalk code: z := y sin + x cos. z > 1 ifTrue: [Transcript show: 'Z greater than 1']. would be translated to (with a Forth like inspiration): Push(Lookup('y)); SendMessage('sin, Pop()); // message, receiver Push(Lookup('x)); SendMessage('cos, Pop()); // message, receiver, pushes the result SendMessage2(Pop(), '+, Pop()); // arg, message, receiver // potential for problem if NetwonScript not always left to right eval Store('z, Pop()); Push(Lookup('z)); Push(ConstantNumber(1)); SendMessage2(Pop(), '>, Pop()); if PopBoolean() then // inline optimization - could also do as block begin Push(Lookup('Transcript)); Push(ConstantString("Z greater than 1")); SendMessage2(Pop(), 'show:, Pop()); end; The Forth like approach allows an easy compiler writing process. Something that might compile to faster code would be: local t1, t2, t3, ... t12 t1 := Lookup('y); t2 := SendMessage('sin, t1); t3 := Lookup('x); t4 := SendMessage('cos, t3); t5 := SendMessage2(t4, '+, t2); t6 := Store('z, t5); t7 := Lookup('z); t8 := ConstantNumber(1); t9 := SendMessage2(t8, '>, t7); if ConvertBoolean(t9) then begin t10 := Lookup('Transcript); t11 := ConstantString("Z greater than 1"); t12 := SendMessage2(t11, 'show:, t12); end; Or, fully optimized to minimize temporaries as: Store('z, SendMessage2(SendMessage('cos, Lookup('x)), '+, SendMessage('sin, Lookup('y)))); if ConvertBoolean(SendMessage2(ConstantNumber(1), '>, Lookup('z))) then begin SendMessage2(ConstantString("Z greater than 1"), 'show:, Lookup('Transcript)); end; Of course, there would have to be some extra code to determine the final return value, handle excpetions, deal with the debuggger, and deal with entering/leaving the method. Primitives would all be written directly in NewtonScript (although they could still be numbered and stored separately from the Smalltalk code). Of course, you wouldn't get this speed of using NewtonScript for nothing. The major drawback I can see to this translation approach would that it would bypass the VM interpreter, and so debugging and single stepping might become impossible. Actually, you could probably handle these somehow, but it would probably require extra Smalltalk and perhaps some fancy NewtonScript exception handling. But since Smalltalk has a very simple syntax, this translation system wouldn't be that hard (say compared to translating C++). I already wrote a translator once that went from Smalltalk to Pascal for our garden simulator, some of which was developed in Smalltalk. The translator didn't do 100% of Smalltalk and it relied on a commercial YACC-like tool (Sandstone Technologies's Visual Parse++) and was written in Delphi (with a YACC like Smalltalk grammar). We would probably want a translator written in NewtonScript or Smalltalk that could run on the Newton (although, I guess if we wanted play-only apps we could cross compile to the Newton somehow - but then debugging is difficult). Again, one might be able to use the same approach to translate JAVA to NewtonScript, and put the compiled results into Package Memory in FLASH RAM using a process like Newt. The call to do this is undocumented according to Steve Weyer (Newt's author), so again this might require help from Apple. Clearly your suggestion of generating NewtonScript bytecodes and dealing with the VM directly is probably more flexible and faster than translating to NewtonScript. I only suggest this alternative as something that might be easier to do because it requires less work convincing Apple to let others help make the Newton a success in ways Apple's marketers haven't planned. The approach could start with just a simple Smalltalk implementation of the basic Smalltalk syntax (maybe even without an image or many support classes). Then one could add classes and build as far as it can within the Newton's limited DRAM. If one was going to rely heavily on NewtonScript protos for views, then maybe this translator should be an add on to Steve Weyer's Newt, as is another author's VisualNewt (a GUI layout program in beta). The Smalltalk translator could just generate NewtonScript and Newt could compile it. (Newt is an excellent piece of shareware by the way - about $45 if I remember from when I registered it). However, what I really like about Smalltalk is the interactive nature - and this requires the concept of a working environment that can store temporary values from code change to code change, an interactive debugger to modify code while it runs, and some sort of version control - change log or ENVY - to see where you have been. Newt and Apple's NTK weren't built with those things in mind. Ultimately, having a complete Squeak image on the Newton using the cross-platform widgets (MVC or Morphic) would be what I would prefer - so you could write your apps on any Squeak machine, and then run them on the Newton without much change. In the past, people on this mailing list have generally suggested doing the Squeak->Newton port using C rather than NewtonScript. What do people think of these dynamic translation ideas (to NewtonScript or bytecodes)? -Paul Fernhout kfsoft@netins.net ======================================== Download a public beta release of our garden simulator at: http://www.gardenwithinsight.com

Post a reply.

Go back to index.



Date: 97 Apr 26 7:16:22 am From: Hans-Martin Mosner <hm.mosner@cww.de> To: Ranjan Bagchi <ranjan.bagchi@pobox.com> Cc: Squeak <squeak@create.ucsb.edu> Subject: Re: [windows] My own question Ranjan Bagchi wrote: > = > I'm experiencing the following.. > = > My changes files is the one I downloaded from the ftp sites (I=A0think)..= > but the source code doesn't look right -- and sometimes the browse > raises the following > exception > = > Parser(Object)>>doesNotUnderstand: #classEncoding. > = > I'm going to try and re-download a changes file and source file. This > couldn't be > a cr/lf mismatch thing, could it? > = > -rj If you downloaded the changes or sources file using text transfer, this = most certainly is a CR/LF problem. Squeak uses single CR characters for = line termination, whereas Windows uses CR/LF. The methods in the image = know the exact position in the changes file where their source is = stored. However, when the source is transmitted improperly such that = additional LF characters are introduced, these positions get out of = sync, leading to wrong method sources in mild cases and to parser errors = in sever cases. I see two possible workarounds: 1. Download the sources/changes again, this time using binary mode. If you have a reasonably fast an cheap internet connection, that's the = right thing to do. 2. Convert the sources/changes files by removing the LF characters. Oops, I just checked to see whether my code would work and noticed that = some 'legitimate' CR/LF sequences slipped into the changes file of = Squeak 1.19d: The FFT code seems to have CR/LF line terminators. = Therefore, simply stripping LF characters will not work, and at the = moment, I don't have the time to rewrite my code fragment to take care = of that. If you trouble file is the sources file, you might still use it = sucessfully, otherwise you will have to adapt it: | oldFile newFile buffer | oldFile :=3D FileStream oldFileNamed: 'Squeak1.19d.changes'. newFile :=3D FileStream newFileNamed: 'temp.changes'. buffer :=3D ByteArray new: 4096. lastWasCR :=3D false. [buffer :=3D oldFile nextInto: buffer. buffer size =3D 0] whileFalse: [newFile nextPutAll: (buffer copyWithout: 10)]. oldFile close. newFile close Hans-Martin

Post a reply.

Go back to index.



Date: 97 Apr 27 6:46:50 am From: "Andreas Raab" <raab@isg.cs.uni-magdeburg.de> To: hm.mosner@cww.de Cc: squeak@create.ucsb.edu Subject: Re: [windows] My own question > I see two possible workarounds: > > 1. Download the sources/changes again, this time using binary mode. > If you have a reasonably fast an cheap internet connection, that's the > right thing to do. It looks like this is not totally true. The changes from 1.19d (after extracting the Squeak.1.19d.tar.gz) seem to have LFs rather than CRs - and as has been pointed out simple LF to CR conversion won't help. Andreas -- Linear algebra is your friend - Trigonometry is your enemy. +===== Andreas Raab ============= (raab@isg.cs.uni-magdeburg.de) =====+ I Department of Simulation and Graphics Phone: +49 391 671 8065 I I University of Magdeburg, Germany Fax: +49 391 671 1164 I +=============< http://simsrv.cs.uni-magdeburg.de/~raab >=============+

Post a reply.

Go back to index.



Date: 97 Apr 27 8:55:50 pm From: Jecel Assumpcao Jr <jecel@lsi.usp.br> To: Maloney <johnm@wdi.disney.com> Cc: squeak@create.ucsb.edu Subject: Re: InterpreterSimulation Maloney wrote: > Squeak is probably 10 to 30 times slower than Self (when the Self > code cache is warm, that is). So I would expect an interpreter > running in it to be pretty slow. This seems about right. But I tested Squeak on the machines I normally use Self on and got these results (in millions of bytecodes per second): Sparc 10 1.7 Sparc 20 3.6 UltraSparc 5.2 And these machines are rarely as "unloaded" as they were during this test. So running Squeak on a 200 MHz K6 should reduce the gap to Self somewhat. A 300MHz PowerPC would be even better, of course, but there is no chance of me getting my hands on one ;-) > However, you could take the > Squeak approach of debugging an interpreter written in Smalltalk > and then translating that to C to get reasonable performance. I am considering it. Most of the interpreter will be written in tinySelf itself (it is a reflective implementation), so this won't give that much speedup. TinySelf won't be practical until it has a inlining compiler. > You could even use the Squeak ObjectMemory module as a starting > point for the tinySelf object memory. Unfortunately, this is where tinySelf 2 differs considerably from Squeak, tinySelf 1 and Self 4. A "partitioned" persistent object store will be used instead of the traditional image and ObjectMemory. BTW, it might be interesting to use this memory system and other parts of tinySelf with Squeak as well. Does releasing code for Squeak place any kind of restriction on using the same code in a commercial product? -- Jecel

Post a reply.

Go back to index.



Date: 97 Apr 28 8:22:25 am From: Ranjan Bagchi <ranjan.bagchi@pobox.com> To: squeak@create.ucsb.edu Subject: [windows] How I compiled under VC4 Hi everyone, Thought I'd drop a note after posting to the list last week that I wasn't able to get the image to compile (earlier in the week) and then run (later) the win32 implementation of 1.18. Two things were going on -- First, VC4 doesn't do a good job at all of importing the VC2 (I think) makefile that's on the ftp site. It creates a sort of null project which blows up when you try and add files to it.. I don't think there's a way to fix this, I just created a new project made up of the appropriate source files. Lastly -- and most insidiously -- if the DOUBLE_WORD_ALIGNMENT #define isn't set, then the word order of the floats will be wrong, and strange things will happen. Surprisingly enough, the image will start and even run, it's only when you try and move windows can you see the expected pathological behavior. A quick test, though, is to type something like '2 asFloat' in a workspace and see if the result is 2.0. Getting 0.0 was.. surprising. Anyway.. certainly was fun to read that code. -rj

Post a reply.

Go back to index.



Date: 97 Apr 29 12:37:46 am From: Hans-Martin Mosner <hmm@heeg.de> To: Squeak Mailing List <squeak@create.ucsb.edu> Subject: 1.19d and MPW MrC Hello Squeakers, this weekend, I tried to compile 1.19d under MPW. There were some trouble spots that were easily fixed but that I'd like to share with you anyway: 1. sq.h defines true and false using #define. The MPW include file <Types.h> has an enum {false, true} which breaks when sq.h has been included before (naturally). The problem only happens with sqMacNetwork.c, as far as I remember. I #undef'd the two before including the relevant files, but better would have been to include sq.h as the last file. 2. The method Interpreter>>#writeImageFile: pads out the hader by seeking after the end-of-file. This does not work with the MPW C library, causing the written image to be unusable. I fixed and reported this bug for 1.18, but somehow it did not get fixed for 1.19 :-( The fix is very simple: Instead of seeking to (headerStart+headerSize), one must write as many zero bytes as are needed. I don't have the method here, but it's a trivial fix. 3. (trivial) MPW does not have a MacHeaders.h file. I made up one for 1.18, and that one was usable for 1.19, too. Same for profiler.h. 4. (just a nit) some of the C code references unused arguments, presumably to avoid compiler warnings. Well, with MPW MrC, this *generates* compiler warnings since these expressions have no effect :-) Just switching off the appropriate warning category was ok for me. 5. The method that patches up the bytecode dispatch in the generated VM does not work for MPW MrC since that compiler uses the other of the two registers (LR, CR) for the implementation of switch() statements. Again, the method that I made for 1.18 worked just fine. The whole VM seems to be marginally slower than the delivered VM, but it is significantly smaller. That's not surprising, given that the delivered VM is a fat binary including code for PPC and 68k, but my VM is even smaller than the PPC part of the delivered VM. I did not yet test the networking code, but I don't expect any problems. I was amazed that it compiled without a hitch, though :-) Soo... it's great to be able to do VM work on an up-to-date version of Squeak. I already included my block closure VM code and am now working on the compiler part for Block closures. Still a long way to go, with debugger, decompiler and probably C translator all needing their changes... Before I forget it: That 'common code' stuff in the C translator looks very nice. Good Job! Hans-Martin

Post a reply.

Go back to index.



Date: 97 Apr 29 1:57:04 am From: Thierry Goubier <Thierry.Goubier@enst-bretagne.fr> To: squeak@create.ucsb.edu Subject: Newcomer, Persistent Store and Constraints Hello, as a newcomer on this mailing list, and to the world of Squeak also, I'd like to share a few of my ideas. I'm interested in Squeak to implement my research work, and to teach Smalltalk and objects concepts with it. I have the 1.19d version running quite well, except when I start the morph world (my Sparc doesn't seems that powerfull). I have, as a side work from my thesis, build a simple persistent store framework, and highly portable. Quite inefficient also, of course. It runs under VisualWorks by now, and should be easy to port to Squeak. I'd probably port it soon, but I'd like to discuss on a few things before. The first thing is that I rely on weak referencing to clean the remains of the store (mostly the persistent proxys). I've seen a discussion about weak referencing in the mailing list archive, bit I've not yet checked into the image to see if it was there (well, as I use the 1.18 VM, probably not). What's the state on it ? The second point is that I use, for portability, standard objects to behave like proxies (well, subclass of nil, as allways), and a become: to exchange the proxies with the persistent object. This is not efficient, but portable. How is the become: in Squeak ? Will it be fast enough, or should I look into proxy support to the image, by adding another kind of immediate object (like the persistent Smalltalk done by Hopkins). Otherwise, if you have any ideas on conccurency or transactions for a simple persistent store, I'd be interested. I'd like to use transactions to provide a generalized undo for users in my PhD thesis, but don't have an easy way of doing it (well, I'm not even able to detect if an object has been modified during a transaction, even if I have an approximation of object usage). Another subject is constraint programming. I have implemented a few solvers (first in Self, now in Smalltalk) and I'm now porting the DETAIL solver to Squeak (thanks to Hiroshi HOSOBE). I plan to implement a glyph-based user interface architecture based on constraints, but that's a long term goal. I'd also like to see the BackTalk environment ported to Squeak (and be able to combine DETAIL and BackTalk). So, I'd like to have your comments on this kind of things, even if this is not really related to the Squeak implementation in itself. Thierry. ___________________Thierry.Goubier@enst-bretagne.fr__________________ Je ne suis pas un patriote car je n'ai pas peur de l'etranger I'm not a patriot because I don't fear foreigners http://www-info.enst-bretagne.fr/~goubier/

Post a reply.

Go back to index.



Date: 97 Apr 29 4:03:59 am From: "Andreas Raab" <raab@isg.cs.uni-magdeburg.de> To: squeak@create.ucsb.edu Subject: (Fwd) Re: 1.19d and MPW MrC > Hello Squeakers, > this weekend, I tried to compile 1.19d under MPW. There were some > trouble spots that were easily fixed but that I'd like to share with you > anyway: [problems deleted] Just an additional note from my site: The declarations from sqSoundPrims.c delivered with 1.19d are not correct (primFMSoundmixSampleCountintostartingAtpan ^^^ vs. primFMSoundSampleCountintostartingAtpan). This can be easily fixed by generating the file from the VM. Andreas -- Linear algebra is your friend - Trigonometry is your enemy. +===== Andreas Raab ============= (raab@isg.cs.uni-magdeburg.de) =====+ I Department of Simulation and Graphics Phone: +49 391 671 8065 I I University of Magdeburg, Germany Fax: +49 391 671 1164 I +=============< http://simsrv.cs.uni-magdeburg.de/~raab >=============+

Post a reply.

Go back to index.



Date: 97 Apr 29 5:03:58 pm From: George Bosworth <george@parcplace.com> To: elcm@pacbell.net, Maloney <johnm@wdi.disney.com> Cc: squeak@create.ucsb.edu Subject: Re: dynamic translation (to threaded code) >Quite possibly. I know that BrouHaHa spends about the same ammount of >time managing its code cache than translation + lookup. In fact, one >might win by simply throwing away the code cache when one runs out of >space. The translator would be simpler, since it could omit the code to >compact and relocate references to the cache. However, one can't avoid >traversing the stack to retranslate all current activations. It would >be interesting to see which approach is faster. > Actually, the VSE dynamic translator took this approach of just emptying the code cache rather than restructuring it when our timing test indicated that the reorg time was significant as compared to the translation times. Note that this is only a win if the tranlation is extremely fast, which should be the case in a squeak environment. In addition, while the stack has to be traversed, the methods don't have to be retranslated right away, the return addresses can be patched to point to retranslation thunks.

Post a reply.

Go back to index.



Date: 97 Apr 30 6:15:35 am From: Peter Munro <munro@lunatech.com> To: Paul Fernhout <kfsoft@netins.net> Cc: Squeak@create.ucsb.edu In-Reply-To: <3360E7E9.4EBD@netins.net> Subject: Re: Squeak on MessagePad 2000? Hi Paul On Fri, 25 Apr 1997 12:20:41 -0500 Paul Fernhout <kfsoft@netins.net> wrote: > Peter Munro wrote (on putting Squeak on a Newton): > > Well, NewtonScript is also bytecode-interpreted, so in theory, yes. > > One option would be to map from one to the other at the byte-code > > level (or ideally use a universal bytecode interpreter ;-). > > This a very good idea, possibly the best I've heard for the > Squeak->Newton port. Thanks! :-) > Two issues that might make this difficult are: > * I don't think Apple has released the VM specifications or byte code > specs (please correct me if I am wrong). Reverse engineering is against > the license, although in Europe that would not neccessarily apply in > some cases (I believe an exemption is given for reverse engineering to > make compatible products, although IANAIL (extra I for international)). > [Your web site said you're company, Lunatech Research, has an office in > Rotterdam, the Netherlands. (That is a beautiful city; my mother is from > there). So presumably you could do such reverse engineering - although > you'd need to check it out with a lawyer first.] Well, if we were to move forward with this, then we'd prefer to work with Apple rather than reverse-engineer. > * A minor point, but the byte codes might not cover everything you need > to do, especially since they were designed for prototype inheritence. So > you still might have to code primitives in C++ or take a hit on > interpreted NewtonScript. If you can pry the Newton C compiler out of > Apple, adding small performance enhancing snippets of code is what it > was designed for. The ideal solution would be a universal byte code interpreter, which would support byte codes for NewtonScript, Smalltalk and Java. But I'm getting ahead of myself here - this would need commitment from Apple, which I doubt would happen. A C++ solution would be a second best. I don't think writing a bytecode interpreter in NewtonScript would be do-able. > ... > Here is another alternative based on your idea. > > In the past I had written of translating the VM to NewtonScript, > although there would be possibly a big performance penalty (given > various tradefoffs since NewtonScript doesn't have pointers, and > compiled (faster) NewtonScript takes more DRAM (3X) than the byte codes. > But, maybe we don't have to do that at all, since Squeak is written in > itself. > > Every Newton comes with a built in NewtonScript interpreter (which I > believe compiles to byte codes). What if we made a minor alteration to > your idea and added a dynamic translator to Squeak to convert Smalltalk > methods and blocks to NewtonScript, and then used the Newton to compile > the NewtonScript and put it in Package memory (like Steve Weyer's Newt > NewtonScript development system which runs native on the Newton)? Then > we wouldn't have to deal with the issues of understanding the byte > codes. > ... The idea of converting Smalltalk to NewtonScript is certainly flexible and gets away from adding bytecode mapping support. I like the idea of a dynamic translator, but wouldn't the translation (parsing) process itself be a bit slow? I guess I'm just one of those people who prefer the most elegant solution, even if it means asking Apple nicely for their help in this, in providing details of VM and bytecodes. Is anyone from Newton Systems Group on this list? Having said that, I think the idea merits further investigation. It would certainly be powerful... Yet another alternative, which you mentioned, is to keep Smalltalk language syntax away from the Newton and restrict its use to within the development environment, and to have the Squeak environment build the NewtonScript bytecode directly, which can then be transported to the Newton. It really depends on what's required. I'd be happy with that solution, as I could then dynamically build Newton applications from Smalltalk. That would enable Newton add-ins (eg plug-ins) which can be generated dynamically according to users' wishes. I take your point about it being easier to debug apps on the Newton. My (again, perhaps naive) mind tells me the best way to do this would be to implement the Newton using Squeak! The universal bytecode interpreter would again be helpful here, but of course this way round, we have access to the source (which only leaves the NewtonScript bytecodes...). Another idea would be an interface to the Toolkit app from Squeak... :-) Whatever, I think that Newton-Smalltalk integration is definitely worth pursuing as it can enable some very powerful apps. If that can be done with the help of either the Newton team or the Squeak team, all the better. Best regards, Pete ---------------------- Peter Munro munro@lunatech.com

Post a reply.

Go back to index.



Date: 97 Apr 30 12:13:31 pm From: Maloney <johnm@wdi.disney.com> To: Jecel Assumpcao Jr <jecel@lsi.usp.br> Cc: squeak@create.ucsb.edu In-Reply-To: <3364139D.EBA6007@lsi.usp.br> Subject: Re: InterpreterSimulation Re: >And these machines are rarely as "unloaded" as they were >during this test. So running Squeak on a 200 MHz K6 should >reduce the gap to Self somewhat. A 300MHz PowerPC would be >even better, of course, but there is no chance of me getting >my hands on one ;-) Did you try translating our benchmark into Self and timing it on the same machines? It would be interesting to know how it really compares (on this one benchmark, at least). Re: >Unfortunately, this is where tinySelf 2 differs considerably >from Squeak, tinySelf 1 and Self 4. A "partitioned" persistent >object store will be used instead of the traditional image >and ObjectMemory. Glphic CodeWorks uses such a scheme. Re: >BTW, it might be interesting to use this memory system and >other parts of tinySelf with Squeak as well. Does releasing >code for Squeak place any kind of restriction on using the >same code in a commercial product? Nope. The license says you have to publish the source code of bug fixes and ports of the Squeak system, but not new apps built on top of Squeak. And you can always use it in commercial products without paying any royalties. -- John

Post a reply.

Go back to index.



Date: 97 Apr 30 12:13:26 pm From: Maloney <johnm@wdi.disney.com> To: Thierry Goubier <Thierry.Goubier@enst-bretagne.fr> Cc: squeak@create.ucsb.edu In-Reply-To: <Pine.GSO.3.95.970429105209.10776A-100000@aphanize.enst-bretagne.fr> Subject: Re: Newcomer, Persistent Store and Constraints Thierry: Welcome to Squeak! Re: Weak References Squeak doesn't have them, but they could be simulated, I believe. Check the Squeak mail archives for the discussion of how it could be done. Also, they would not be too hard to add to the VM. :-> Re: become: Become is fairly quick in Squeak unless your image is very large. Squeak allows you a whole batch of "becomes:" in a single pass through memory, which might help quite a lot in some applications. I'd measure the speed of become: before implementing a new kind of immediate object. Re: transactions I have no great ideas except that you modify Squeak ObjectMemory to set a "dirty" bit on modified objects. There is a bit available in the object header, although there's no guarantee that we won't use that bit for something ourselves some day. Your research sounds neat! Keep us posted. You might be able to do the glyph-constraint UI on top of Morphic. I once did a constraint-based UI toolkit called ThingLab II; you can get a copy of my thesis from the University of Washington if you are interested. -- John

Post a reply.

Go back to index.



Date: 97 Apr 30 12:16:48 pm From: Maloney <johnm@wdi.disney.com> To: Hans-Martin Mosner <hmm@heeg.de> Cc: squeak@create.ucsb.edu In-Reply-To: <3365AB65.167EB0E7@heeg.de> Subject: Re: 1.19d and MPW MrC Hans-Martin, Thanks for the long and detailed message. I'm glad you did manage to get it to compile. If it is easy to do, I wonder if you could compile a 68K version of the VM using MPW and mail it to me. I've been curious for a long time to see if MPW would produce better code for the 68K. Re: >2. The method Interpreter>>#writeImageFile: pads out the hader by >seeking after the end-of-file. This does not work with the MPW C >library, causing the written image to be unusable. I fixed and reported >this bug for 1.18, but somehow it did not get fixed for 1.19 :-( >The fix is very simple: Instead of seeking to (headerStart+headerSize), >one must write as many zero bytes as are needed. I don't have the method >here, but it's a trivial fix. Yes, I remember you mentioning this. I'm sorry that I forgot to fix it for 1.19. It will be in our next version. As you say, it's trivial. Re: >4. (just a nit) some of the C code references unused arguments, >presumably to avoid compiler warnings. Well, with MPW MrC, this >*generates* compiler warnings since these expressions have no effect :-) >Just switching off the appropriate warning category was ok for me. That should be just in the socket code, which isn't done yet. You're correct, I just put in dummy references to shut up the CodeWarrior compiler. You did the right thing. Re: >5. The method that patches up the bytecode dispatch in the generated VM >does not work for MPW MrC since that compiler uses the other of the two >registers (LR, CR) for the implementation of switch() statements. >Again, the method that I made for 1.18 worked just fine. That patching code needs to figured out by hand for every compiler. Fortunately, Ian's threading VM may soon make this moot. There will be another little bit of assembly code hacking needed for each port, however, so ya' just can't win :-> Re: >The whole VM seems to be marginally slower than the delivered VM, but it >is significantly smaller. That's not surprising, given that the >delivered VM is a fat binary including code for PPC and 68k, but my VM >is even smaller than the PPC part of the delivered VM. You might try various compiler optimization settings. I found that the highest levels of optimization for CodeWarrier made the code somewhat slower. MrC is supposed to have a pretty good optimizer. Re: >I did not yet test the networking code, but I don't expect any problems. >I was amazed that it compiled without a hitch, though :-) Except for the list of hitched above, you mean. :-> Re: >Before I forget it: That 'common code' stuff in the C translator looks >very nice. Good Job! Danke! -- John

Post a reply.

Go back to index.



Send mail to the CREATE web master

[Author: Stephen Travis Pope, stp@create.ucsb.edu]
Created: 1996.11.08; LastEditDate: 1996.11.11