Send mail to the CREATE web master
Index
Date: 97 Jun 01 9:51:43 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: <33908AAE.6CB481B9@lsi.usp.br>
Subject: Re: Teaching Smalltalk
At 16:31 -0400 5/31/97, Jecel Assumpcao Jr wrote:
>...SNIP....
>
>One problem they had with Smalltalk was its integrated
>nature - even a trivial example might lead (by accident)
>into an exploration of low level stuff way before the
>students are ready for it. The instructors found it
>nearly impossible to break the material down into isolated
>chunks (special browsers and debuggers can help with
>this).
***FLAME***
God help us, they've got to stamp out any chance of letting someone learn
things by self-guided exploration rather than by forcing rigid adherence to
a lesson plan.
Some day those poor students have to learn that LIFE is a self-guided
exploration, that sometimes things get complex, and that sometimes you
simply have to back off and say "I'll remember this and look at it later".
***END FLAME***
Thanks, now I feel better...
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.
Date: 97 Jun 01 12:53:51 pm
From: "David N. Smith" <dnsmith@watson.ibm.com>
To: squeak@create.ucsb.edu
Subject: sqrt of negative numbers
Try:
-1.0 sqrt
It doesn't work, it runs out of memory, and is a mess.
The interpreter code is:
primitiveSquareRoot
| rcvr |
self var: #rcvr declareC: 'double rcvr'.
rcvr _ self popFloat.
successFlag
ifTrue: [self pushFloat: (self cCode: 'sqrt(rcvr)')]
ifFalse: [self unPop: 1]
Shouldn't the primitive test for rcrv being non-negative? (I'm new at this
level of Squeak and may have something obvious wrong.)
primitiveSquareRoot
| rcvr |
self var: #rcvr declareC: 'double rcvr'.
rcvr _ self popFloat.
self success: rcrv >= 0.0.
successFlag
ifTrue: [self pushFloat: (self cCode: 'sqrt(rcvr)')]
ifFalse: [self unPop: 1]
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.
Date: 97 Jun 01 1:37:02 pm
From: dave <drs@cs.wisc.edu>
To: squeak@create.ucsb.edu
Subject: Re: Teaching Smalltalk
Contra DNS, The problem Jecel describes is, in fact, a legitimate
critique of smalltalk from the standpoint of teaching as well
as design.
For a high-level discussion of the technical side, see OOPSLA '96,
"A Declarative Model for Defining Smalltalk Programs," by Allen
Wirfs-Brock, where he outlines some of the problems of system
complexity and the difficulty of isolating particular components
for study or transport.
dave
David N. Smith wrote:
>
> At 16:31 -0400 5/31/97, Jecel Assumpcao Jr wrote:
> >...SNIP....
> >
> >One problem they had with Smalltalk was its integrated
> >nature - even a trivial example might lead (by accident)
> >into an exploration of low level stuff way before the
> >students are ready for it. The instructors found it
> >nearly impossible to break the material down into isolated
> >chunks (special browsers and debuggers can help with
> >this).
>
> ***FLAME***
>
> God help us, they've got to stamp out any chance of letting someone learn
> things by self-guided exploration rather than by forcing rigid adherence to
> a lesson plan.
>
> Some day those poor students have to learn that LIFE is a self-guided
> exploration, that sometimes things get complex, and that sometimes you
> simply have to back off and say "I'll remember this and look at it later".
>
> ***END FLAME***
>
> Thanks, now I feel better...
>
> 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.
Date: 97 Jun 02 2:13:07 am
From: "Andreas Raab" <raab@isg.cs.uni-magdeburg.de>
To: squeak@create.ucsb.edu
Subject: Concepts for 3d graphics
Hi Squeakers,
Inspired by Hans-Martins work on the triangleBits primitive I've
started to work on some 3d extensions. So far, I've integrated flat
and gouraud shading as well as z-buffering (texture mapping will come
in the future).
What I'm thinking about right now is: How can 3d graphics naturally
integrated into Squeaks visualization philosophy? In other words,
should there be a model-view concept (say the model is the polygon
mesh, the view a specific renderer) should there be a 3dMorph or what?
Although there are several other approaches to OO 3d graphics I would
like to discuss the issue, since we could try to make "something completely
different" ;-)
Bye,
Andreas
PS. Because my rasterizer code is not yet ready to be translated into C
code it's incredibly slow ... makes about .1 to .5 frames on my PPro200 ;-)
--
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 >=============+
Date: 97 Jun 02 2:43:15 am
From: "Andreas Raab" <raab@isg.cs.uni-magdeburg.de>
To: squeak@create.ucsb.edu
Subject: 2 problems
Hi,
Just to report two problems:
1) Anyone ever tried to using #perform: with an arbitrary number?!
Looks like this crashes the system (try "nil perform: 0").
2) I found this while trying to replace #startUpWithCaption:
with #startUpWithCaptionCentered: in PopupMenu>>startup. This crashes
if you use the screen menu since the #startUpWithCaption: method
is re-implemented in SelectionMenu but not #startUpWithCaptionCentered:
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 >=============+
Date: 97 Jun 02 3:03:19 am
From: "Andreas Raab" <raab@isg.cs.uni-magdeburg.de>
To: squeak@create.ucsb.edu
Subject: Re: 2 problems
Oops,
my mailer looks like having problems with attachments. Here are
the startUpCenteredWithCaption: methods for EmphasizedMenu and
SelectionMenu.
--------------------------------------------------------------------
'From Squeak 1.19d of April 13, 1997 on 2 June 1997 at 11:21:25 am'!
!EmphasizedMenu methodsFor: 'display'!
startUpCenteredWithCaption: captionOrNil
self setEmphasis.
^ super startUpCenteredWithCaption: captionOrNil! !
!SelectionMenu methodsFor: 'basic control sequence'!
startUpCenteredWithCaption: captionOrNil
"Overridden to return inner values from manageMarker"
| selectedItem |
self displayAt: Sensor cursorPoint - (frame width//2@0)
withCaption: captionOrNil
during: [Sensor cursorPoint: marker center.
[Sensor anyButtonPressed] whileFalse: [].
[Sensor anyButtonPressed]
whileTrue: [selectedItem _ self manageMarker]].
^ selectedItem! !
--------------------------------------------------------------------
--
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 >=============+
Date: 97 Jun 02 4:12:39 am
From: Hans-Martin Mosner <hmm@heeg.de>
To: Andreas Raab <raab@isgnw.cs.Uni-Magdeburg.DE>
Cc: squeak@create.ucsb.edu
Subject: Re: 2 problems
Andreas Raab wrote:
> 1) Anyone ever tried to using #perform: with an arbitrary number?!
> Looks like this crashes the system (try "nil perform: 0").
The primitivePerform and primitivePerformWithArgs do not check for
non-integerness of the message selector. This crashes the method lookup
where the interpreter tries to read the hash bits from the message
selector's object header.
I don't have a running Squeak here in which to fix the problem, but it's
not difficult.
Interestingly, perform:withArgs: correctly checks that the second
argument is indeed an Array. ParcPlace VisualWorks didn't at one time
(might have been VW 1.0) which caused quite a bit of head scratching
until I found out that some code was doing "self perform: selector
withArgs: 0"
Hans-Martin
Date: 97 Jun 02 7:31:02 am
From: Dan Ingalls <DanI@wdi.disney.com>
To: "Andreas Raab" <raab@isgnw.cs.Uni-Magdeburg.DE>
Cc: Squeak@create.ucsb.edu
In-Reply-To: <EC12A866EA@isgnw.cs.uni-magdeburg.de>
Subject: Re: 2 problems
>1) Anyone ever tried to using #perform: with an arbitrary number?!
> Looks like this crashes the system (try "nil perform: 0").
This will be fixed in the next release. To quote from my May 12 message=
regarding one of three fileIns...
VMfixes-di.cs
Sundry fixes and improvements to the VM. Speeds up BitBlt 'paint' mode when=
the source is zero.
=46ixes a problem reported by Paul McCullough and Don Charnley, so that the=
VM now checks for recursive evaluation of blocks (currently crashes). =
Fixes two problems reported by Carl Watts: perform now checks that its=
selector is not an immediate object (currently crashes), and perform also=
adjusts its argument count at the correct time so that the=
doesNotUnderstand facility works properly. Also includes minor=
improvements to related error messages.
Date: 97 Jun 02 8:09:48 am
From: David Casseres <casseres@apple.com>
To: <squeak@create.ucsb.edu>
Subject: Re: Teaching Smalltalk
Jecel Assumpcao Jr posted this quote from Journal of Object Oriented
Programming (JOOP) ( Vol 3 No 4 ):
>One side effect from the move from Pascal to Smalltalk
>was that the students with previous experience in programming
>paid more attention because the language was as new to
>them as to their "novice" classmates.
>
>One problem they had with Smalltalk was its integrated
>nature - even a trivial example might lead (by accident)
>into an exploration of low level stuff way before the
>students are ready for it. The instructors found it
>nearly impossible to break the material down into isolated
>chunks (special browsers and debuggers can help with
>this).
Hmm. Back when Apple was one of the few places receiving Smalltalk-80
images from PARC, they came without source code or code documentation, so
we were totally dependent on decompilation (it's actually amazing how
much you can do that way!). I was a technical writer with some Pascal
proficiency, trying to write a Smalltalk manual, and I had to do quite a
bit of rooting around in the low-level stuff. A lot of it seemed pretty
scarey to me.
Well, one day we got a new image and the decompiler was broken! My
curiosity got the better of me and I started digging down into things to
find out how the thing was supposed to work. After about a day of this,
I fixed the decompiler and got on with my "real" work. This was my
epiphany with Smalltalk, and it led to my becoming a fairly proficient
Smalltalk programmer and ultimately to a new career as a software
engineer.
So I think this "problem" with Smalltalk may actually be an advantage, if
the learner is sufficiently motivated.
Cheers,
David
Date: 97 Jun 02 8:15:22 am
From: Ian Piumarta <piumarta@prof.inria.fr>
To: traymond@craftedsmalltalk.com
Cc: johnm@wdi.disney.com, boris@dialogue.msu.su, squeak@create.ucsb.edu
In-Reply-To: <v03007801afa78ddeadc1@[206.16.10.216]> (message from Maloney on
Tue, 20 May 1997 09:21:33 -0800)
Subject: Re: OS/2 port of Squeak?
At 1:23 PM -0400 5/19/97, Terry Raymond wrote:
>I just subscribed to this list and would like to know if there is an
>OS/2 port of Squeak or is there one in progress?
Boris Shingarov (boris@dialogue.msu.su) has made an OS/2 port of Squeak1.18.
I've placed a copy of his modifications in:
ftp://alix.inria.fr/pub/squeak/unix/os2patch.zip
(this should be mirrored automatically to the other two sites in due course).
Here is the README from his patches:
This archive contains the patch to compile Squeak-1.18 on OS/2.
Squeak is indeed very portable so it was pretty straightforward
to make it compile on OS/2. I couldn't wait to tell this good
news to the world, so I didn't play with it to see whether everything
is OK, but the fact is - it does work.
Prerequisites:
1) Ian Piumarta's UNIX port of Squeak v.1.18
2) EMX 0.9c + gcc v2.7.2
3) XFree86 for OS/2 (w/programmer's kit).
This patch adds no new functionality. In particular, no attempt was
(yet) made to provide PMX or PM support - so it will run with XFree86
only. (However, I do plan to add support for native PM widgets, as well
as to add other OS/2-specific features.)
Boris G. Shingarov
<boris@dialogue.msu.su>
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 -----------------------
Date: 97 Jun 02 8:31:07 am
From: lnotarfr@dc.uba.ar (Luciano Esteban Notarfrancesco)
To: squeak@create.ucsb.edu
Subject: Squeak now runs on OS/2 (fwd)
Forwarded message:
> From visualage.dialogue.msu.su!boris Sun Jun 1 21:10:17 1997
> Date: Mon, 2 Jun 1997 09:26:08 +0400
> From: "Boris G. Chr. Shingarov" <boris@visualage.dialogue.msu.su>
> Message-Id: <199706020526.JAA08545@visualage.dialogue.msu.su>
> To: annaval@vnet.ibm.com, Anton_Bakharevsky@charon.cargill.com,
> baranov@minas.rosmail.com, fritzo@vnet.ibm.com, lnotarfr@dc.uba.ar,
> mairi_cairney@uk.ibm.com, nikolais@vnet.ibm.com, orlovv@vnet.ibm.com,
> remeev@moscou.dialogue.msu.su, Vincent_Dijkstra@be.ibm.com
> Subject: Squeak now runs on OS/2
>
> Dear Friends,
>
> I just tried to compile Squeak on OS/2. That went pretty straightforward.
> I put the (few) diffs to ftp://visualage.dialogue.msu.su/pub/smalltalk/squeak.
>
> Enjoy!
>
> Boris G. Chr. Shingarov
> <boris@dialogue.msu.su>
>
Date: 97 Jun 02 8:43:50 am
From: lnotarfr@dc.uba.ar (Luciano Esteban Notarfrancesco)
To: squeak@create.ucsb.edu
Subject: More speed ups for Fractions
I reimplemented #< and #squared for Fractions.
I've got the following results:
Fraction>>#<
for Fractions with SmallIntegers: 10-18 times faster
for Fractions with LargeIntegers not so bigs: about 10 times faster
for Fractions with big LargeIntegers: about 18 times faster
Fraction>>#squared
for Fractions with SmallIntegers: 5.3 times faster
for Fractions with "small" LargeIntegers: 1.75 times faster
for Fractions with big LargeIntegers: 28 times faster
(in this last case Karatsuba squaring was used for big LargeIntegers;
I sent to the list the Karatsuba squaring method some time ago).
--- Luciano.
'From Squeak 1.19d of April 13, 1997 on 1 June 1997 at 3:31:50 pm'!
!Fraction methodsFor: 'comparing'!
< aNumber
aNumber isFraction
ifTrue: [^ numerator * aNumber denominator < (denominator * aNumber numerator)]
ifFalse: [^ (aNumber adaptFraction: self) < aNumber adaptToFraction]!
!Fraction methodsFor: 'mathematical functions'!
sqrt
"Answer the square root of the receiver."
^ numerator sqrt / denominator sqrt!
squared
"Answer the square of the receiver."
^ Fraction
numerator: numerator squared
denominator: denominator squared! !
Date: 97 Jun 02 8:44:13 am
From: lnotarfr@dc.uba.ar (Luciano Esteban Notarfrancesco)
To: squeak@create.ucsb.edu
Subject: Problems with floorLog:
I've found some problems with floorLog:.
When you ask for the floorLog of an integer
anInteger floorLog: radix
you get
anInteger asFloat floorLog: radix.
This is certainly wrong, as the following example shows:
x _ 1000000000000000000000000000000000.
x floorLog: 10
32
x * 10 floorLog: 10
34
For integers with more than 33 decimal digits floorLog: begins to fail.
It's allways the same recurrent problem: overflow when converting
a LargeInteger to Float (as Dave pointed out a couple of days ago).
I fixed this implementing Integer>>#floorLog:. For SmallIntegers, the
new floorLog: seems to be faster, and for LargeIntegers the old one
seems to be slighly faster... but the difference is at most a factor
of 2. For the case of radix=2 or radix=256, the new Integer>>#floorLog:
is thousands of times faster.
Furthermore, I implemented Fraction>>#floorLog: using Integer>>#floorLog:,
and doing that I discovered a bug in Float>>#floorLog: : it fails for
floats between 0 and 1. I fixed that and I added also a check for
the receiver's sign (the logarithm of a negative number is complex... and
we do not have complex numbers yet).
I don't understand at all why my Fraction>>#floorLog: works... since
in general
floor (log(a / b)) != floor(log(a)) - floor(log(b)).
I ran some tests like this:
randomFractions do: [ :each |
(each floorLog: 10) = (each asFloat floorLog: 10)
ifFalse: [self halt]
]
and every time it failed it was fault of Float>>#floorLog:. ;)
--- Luciano.
'From Squeak 1.19d of April 13, 1997 on 1 June 1997 at 3:31:50 pm'!
!Float methodsFor: 'mathematical functions'!
floorLog: radix
"Answer (self log: radix) floor."
| approx radixSquared |
self negative ifTrue: [self error: 'floorLog: not defined for negative numbers'].
radix <= 1 ifTrue: [self error: 'floorLog: not defined for radix <= 1'].
self < 1 ifTrue: [^(self reciprocal floorLog: radix) negated].
self < radix ifTrue: [^0].
self < (radixSquared _ radix squared) ifTrue: [^1].
approx _ 2 * (self floorLog: radixSquared). "binary recursion"
^approx + (self / (radix raisedTo: approx) floorLog: radix)! !
!Fraction methodsFor: 'mathematical functions'!
floorLog: radix
"Answer (self log: radix) floor."
^ (numerator floorLog: radix) - (denominator floorLog: radix)! !
!Integer methodsFor: 'mathematical functions'!
floorLog: radix
"Answer (self log: radix) floor."
| approx radixSquared |
self negative ifTrue: [^self error: 'floorLog: not defined for negative numbers'].
radix <= 1 ifTrue: [self error: 'floorLog: not defined for radix <= 1'].
radix = 16rFF ifTrue: [^self digitLength - 1].
radix = 2 ifTrue: [^self highBit - 1].
self < radix ifTrue: [^0].
self < (radixSquared _ radix squared) ifTrue: [^1].
approx _ 2 * (self floorLog: radixSquared). "binary recursion"
^approx + (self // (radix raisedTo: approx) floorLog: radix)! !
Date: 97 Jun 02 8:44:32 am
From: lnotarfr@dc.uba.ar (Luciano Esteban Notarfrancesco)
To: squeak@create.ucsb.edu
Subject: Float>>asTrueFraction revisited
I changed Float>>#asTrueFraction, and the new one runs between 9
and 43 times faster than the old one.
Furthermore, I found some problems with Float>>#truncated: when
I tryed to get a random element from a big interval it failed
(the VM stoped with a floating point error). I tryed something
like this (surely not exactly this):
(1000000000000000000000000000000 to:
100000000000000000000000000000000000000000000000000000000000000000)
atRandom.
So I reimplemented Float>>#truncated in terms of Float>>#asTrueFraction.
--- Luciano.
'From Squeak 1.19d of April 13, 1997 on 1 June 1997 at 3:31:50 pm'!
!Float methodsFor: 'truncation and round off'!
truncated
"Answer with a SmallInteger equal to the value of the receiver without
its fractional part. The primitive fails if the truncated value cannot be
represented as a SmallInteger. In that case, the code below will compute
a LargeInteger truncated value. Essential. See Object documentation
whatIsAPrimitive. "
<primitive: 51>
^ self asTrueFraction truncated! !
!Float methodsFor: 'converting'!
asTrueFraction
"Answer a fraction that EXACTLY represents self,
a double precision IEEE floating point number.
(It tears an IEEE float into its components; it
assumes 'correct' byte ordering; runs on PPC.)
Thanks to David N. Smith"
| shifty sign expPart fractionPart exp fraction zeroBitsCount result |
shifty _ ((self at: 1) bitShift: 32) bitOr: (self at: 2).
sign _ (shifty bitShift: -63) = 0 ifTrue: [1] ifFalse: [-1].
expPart _ (shifty bitShift: -52) bitAnd: 16r7FF.
fractionPart _ shifty bitAnd: 16r000FFFFFFFFFFFFF.
"If I am zero..."
(expPart = 0) & (fractionPart = 0) ifTrue: [^ 0].
"... if not, determine the exponent and the mantiza"
fraction _ fractionPart bitOr: 16r0010000000000000.
exp _ 16r433 - expPart.
result _ exp negative ifTrue: [
sign * fraction bitShift: exp negated
] ifFalse: [
zeroBitsCount _ 0.
[(fraction bitAnd: (1 bitShift: zeroBitsCount)) = 0 and: [exp > 0]]
whileTrue: [zeroBitsCount _ zeroBitsCount + 1. exp _ exp - 1].
Fraction
numerator: (sign * fraction bitShift: zeroBitsCount negated)
denominator: (2 raisedToInteger: exp)
].
"Validate that the dismemberment was correct and answer the result."
result asFloat = self
ifFalse: [self error: 'asFraction validation failed'].
^ result! !
Date: 97 Jun 02 9:17:46 am
From: "David N. Smith" <dnsmith@watson.ibm.com>
To: lnotarfr@dc.uba.ar (Luciano Esteban Notarfrancesco)
Cc: squeak@create.ucsb.edu
In-Reply-To: <m0wYSoY-000j1BC@milagro.dc.uba.ar>
Subject: Re: Float>>asTrueFraction revisited
At 4:50 -0400 6/2/97, Luciano Esteban Notarfrancesco wrote:
>I changed Float>>#asTrueFraction, and the new one runs between 9
>and 43 times faster than the old one.
Slick! Thanks!
I presume that the code is public domain?
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.
Date: 97 Jun 02 9:49:13 am
From: Tim Rowledge <rowledge@interval.com>
To: Squeak mailinglist <squeak@create.ucsb.edu>
In-Reply-To: <5040100004825929000002L092*@MHS>
Subject: RE: Smalltalk Ballon.....was Teaching Smalltalk
On Sat 31 May, Sam Adams wrote:
> B> By logo I assume you mean the balloon from BYTE cover? But I couldn't get
> B> access to it _without_ the BYTE heading. Do you know any source? All other
> B> renditions I have seen are, uhmm, rather ugly, I'd say ...
>
> Leandro wrote:
> >Of course, I did meant the BYTE balloon. I don't know any source without the
> >heading. I have read somewhere in the Net form Ralph Johnson that "Someone
> >should talk with Robert Tinney about making his cover into a poster". Probably
> >that poster exists (in such case please don't forget that I WANT MINE!). At any
> >case, I consider the heading as part of a testimonial form of art.
>
> I have an old catalog from Georg Heeg that has a clean image of the Smalltalk
> balloon on the over. It looks like the original artwork sans BYTE heading.
> Perhaps they have a source for the art. Anyone over there listening?
> On the teaching issue, I always found that a little magic was worth a mountain
> of logic when it came to convincing folks about the value of Smalltalk.
I have put a PostScript ( supposedley an encapsulated PS file, but I
don't have any way to check it out myself) file of the version of the
Byte balloon I did someyears ago on my website. Try <http://sumeru.
stanford.edu/tim/pooters/STballn2.ps>. It has been used to make some
T-shirts that you might have seen around at OOPSLA and PPS user con.s
over the last couple of years. The default size is set for A4 paper,
but I believe that EPS is supposed to let you transform it? If anyone
wants a particular sized version, or a GIF file, whatever, let me
know.
It worked out pretty well and has one big advantage over any attempt
to scan Tinney's original artwork - it's my copyright and I happily
grant any of you permission to use it. The Byte cover is copyright
Byte and they are *quite* protective about it.
For those interested, there is a poster version that was done as a
limited edition by Byte (all gone now) on archival paper and signed
by Tinney. I have #232 of 500, signed by Adele, Alan, Dan, Larry &
Glenn :-) I have heard that Chris Macie (probably macie@parcplace.
com ?) has a small number stashed away.
--
Tim Rowledge: rowledge@interval.com (w) +1 (415) 856-7230 (w)
tim@sumeru.stanford.edu (h) <http://sumeru.stanford.edu/tim>
Date: 97 Jun 02 9:49:12 am
From: Tim Rowledge <rowledge@interval.com>
To: Squeak mailinglist <squeak@create.ucsb.edu>
In-Reply-To: <33908AAE.6CB481B9@lsi.usp.br>
Subject: Re: Teaching Smalltalk
If you're working on teaching, you should also take a look at LearningWorks, since it's specifically intended to help here. Now, if you like it and want to keep to Squeak, maybe we should port it over....
<http://learningworks.neometron.com>
--
Tim Rowledge: rowledge@interval.com (w) +1 (415) 856-7230 (w)
tim@sumeru.stanford.edu (h) <http://sumeru.stanford.edu/tim>
Date: 97 Jun 02 10:02:01 am
From: Travis Griggs <tgriggs@keyww.com>
To: "squeak@create.ucsb.edu" <squeak@create.ucsb.edu>,
"'drs@cs.wisc.edu'"
<drs@cs.wisc.edu>
Subject: RE: Teaching Smalltalk
LearningWorks also attempts to address this issue by allowing the =
various learning courses to have a scope or "vision" of what is relevant =
to the course. I've just started playing with LearningWorks, and like =
Squeak, it is a good thing for the Smalltalk community.
Travis Griggs
Key Technology
----------
From: dave
Sent: Sunday, June 01, 1997 1:59 PM
To: squeak@create.ucsb.edu
Subject: Re: Teaching Smalltalk
Contra DNS, The problem Jecel describes is, in fact, a legitimate
critique of smalltalk from the standpoint of teaching as well=20
as design.
For a high-level discussion of the technical side, see OOPSLA '96,
"A Declarative Model for Defining Smalltalk Programs," by Allen
Wirfs-Brock, where he outlines some of the problems of system
complexity and the difficulty of isolating particular components
for study or transport.=20
dave
Date: 97 Jun 02 10:02:51 am
From: Maloney <johnm@wdi.disney.com>
To: "Andreas Raab" <raab@isgnw.cs.Uni-Magdeburg.DE>, squeak@create.ucsb.edu
In-Reply-To: <EB92B836A4@isgnw.cs.uni-magdeburg.de>
Subject: Re: Concepts for 3d graphics
Andreas,
Three-D interfaces are qualitatively different from 2-D ones.
Thus, if you want to build a 3-D morphic, I would start from
scratch (perhaps incorporating some of the same design ideas).
To get started, however, you could make a 3-D Window Morph
that was a view onto a 3-D scene. It's mouse handling would
translate into manipulation of the 3-D objects.
Your performance seems pretty good for being entirely in
Squeak!
-- John
At 11:38 AM +0000 6/2/97, Andreas Raab wrote:
>Hi Squeakers,
>
>Inspired by Hans-Martins work on the triangleBits primitive I've
>started to work on some 3d extensions. So far, I've integrated flat
>and gouraud shading as well as z-buffering (texture mapping will come
>in the future).
>
>What I'm thinking about right now is: How can 3d graphics naturally
>integrated into Squeaks visualization philosophy? In other words,
>should there be a model-view concept (say the model is the polygon
>mesh, the view a specific renderer) should there be a 3dMorph or what?
>
>Although there are several other approaches to OO 3d graphics I would
>like to discuss the issue, since we could try to make "something completely
>different" ;-)
>
>Bye,
> Andreas
>
>PS. Because my rasterizer code is not yet ready to be translated into C
>code it's incredibly slow ... makes about .1 to .5 frames on my PPro200 ;-)
Date: 97 Jun 02 10:11:49 am
From: Randal Schwartz <merlyn@stonehenge.com>
To: Tim Rowledge <rowledge@interval.com>
Cc: Squeak mailinglist <squeak@create.ucsb.edu>
In-Reply-To: Tim Rowledge's message of Mon, 02 Jun 1997 09:58:38 -0700
Subject: Re: Smalltalk Ballon.....was Teaching Smalltalk
>>>>> "Tim" == Tim Rowledge <rowledge@interval.com> writes:
Tim> I have put a PostScript ( supposedley an encapsulated PS file, but I
Tim> don't have any way to check it out myself) file of the version of the
Tim> Byte balloon I did someyears ago on my website.
[...]
Tim> It worked out pretty well and has one big advantage over any attempt
Tim> to scan Tinney's original artwork - it's my copyright and I happily
Tim> grant any of you permission to use it. The Byte cover is copyright
Tim> Byte and they are *quite* protective about it.
Well, I hate to rain on your parade (or balloon), but technically,
Byte could still claim a copyright infringement on *your* art as a
"derived work" depending on the strength of their legal team.
Unless you can demonstrate that you came up with the balloon
independently of anything Byte did. And you've just nullified that
claim in public by the way you said what you said above.
So, before the rest of us go adopting that image, we'd better get an
explicit waiver from Byte for Tim's balloon.
Just another guy who makes a living from copyrighted material,
--
Name: Randal L. Schwartz / Stonehenge Consulting Services (503)777-0095
Keywords: Perl training, UNIX[tm] consulting, video production, skiing, flying
Email: <merlyn@stonehenge.com> Snail: (Call) PGP-Key: (finger merlyn@ora.com)
Web: <A HREF="http://www.stonehenge.com/merlyn/">My Home Page!</A>
Quote: "I'm telling you, if I could have five lines in my .sig, I would!" -- me
Date: 97 Jun 02 10:41:17 am
From: "David N. Smith" <dnsmith@watson.ibm.com>
To: Tim Rowledge <rowledge@interval.com>
Cc: Squeak mailinglist <squeak@create.ucsb.edu>
In-Reply-To: <Marcel-1.08-0602165838-06cKL&V@goldskin.interval.com>
Subject: RE: Smalltalk Ballon.....was Teaching Smalltalk
At 12:58 -0400 6/2/97, Tim Rowledge wrote:
>...
>I have put a PostScript ( supposedley an encapsulated PS file, but I
>don't have any way to check it out myself) file of the version of the
>Byte balloon I did someyears ago on my website. Try <http://sumeru.
>stanford.edu/tim/pooters/STballn2.ps>. It has been used to make some
>T-shirts that you might have seen around at OOPSLA and PPS user con.s
>over the last couple of years. The default size is set for A4 paper,
>but I believe that EPS is supposed to let you transform it? If anyone
>wants a particular sized version, or a GIF file, whatever, let me
>know.
> ...
>For those interested, there is a poster version that was done as a
>limited edition by Byte (all gone now) on archival paper and signed
>by Tinney. I have #232 of 500, signed by Adele, Alan, Dan, Larry &
>Glenn :-) I have heard that Chris Macie (probably macie@parcplace.
>com ?) has a small number stashed away.
Tim:
I got the file and looked inside. A quick scan smells like EPS (but I'm no
expert). It won't print on my LexMark Optra R+ (using DropPS) and there is
no error message. It won't load into Mac Illustrator 7.0. (Must have been
created on some odd English machine?)
I tried printing it by loading the PS into Mac WORD 5.1 and marking the
text as PostScript. When printed it is offended by the command 'alyr'
(which is right at the front). My PS manual is hard to get at but that
doesn't offhand smell like a PS command. HELP!
I have 3-4 virgin copies of the original Byte issue stashed away, saving
them for some special time or situation or bribe. If Chris still has some
posters, I bet he's doing the same thing.
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.
Date: 97 Jun 02 10:58:03 am
From: John M McIntosh <johnmci@ibm.net>
To: squeak@create.ucsb.edu
Subject: Re: Smalltalk Ballon.....was Teaching Smalltalk
>Randal Schwartz wrote:
> Well, I hate to rain on your parade (or balloon), but technically,
> Byte could still claim a copyright infringement on *your* art as a
> "derived work" depending on the strength of their legal team.
Actually Robert Tinney owns the copyright on the art work, not Byte.
Having been down this path before (I made some t-shirts a while back),
I've his
phone number somewhere. If anyone wants it please email me. He did have
a Web site but I can't find it anymore... Getting permission was easy,
he
was glad to see the interest
Also see http://www.barnaby.com/limited.html for some more examples
of his artwork.
--
====================================================================
John M. McIntosh <johnmci@ibm.net>
1-250-655-0653, 1-250-655-1726 (fax)
Corporate Smalltalk Consulting Ltd.
====================================================================
Various Smalltalk dialects -> VisualWorks, VisualWave
Macintosh custom programming
PGP Key: 1024/FC4EB80D Fingerprint=91E3FFB705465252 B701F7EEF2C2A6F6
====================================================================
Date: 97 Jun 02 11:11:18 am
From: Stefan Matthias Aust <sma@kiel.netsurf.de>
To: squeak@create.ucsb.edu
Subject: RE: Smalltalk Ballon.....was Teaching Smalltalk
>I have an old catalog from Georg Heeg that has a clean image of the Smalltalk
>balloon on the over. It looks like the original artwork sans BYTE heading.
>Perhaps they have a source for the art. Anyone over there listening?
He has indeed a large poster showing that balloon. I saw it this year that
cebit'97 fair. Perhaps you ask him personally at georg@heeg.de, but
Hans-Martin probably knowns best has he's working that that company :-)
If anybody ever plans to print this poster again, count me in. I'd love to
get my fingers on that.
bye
--
Stefan Matthias Aust // Planet Claire has pink air!
http://www.kiel.netsurf.de/users/s/sma/
Date: 97 Jun 02 11:20:18 am
From: Sehyo Chang <sehyo@netcom.com>
To: squeak@create.ucsb.edu
Subject: Re: Concepts for 3d graphics
I think maybe using standard 3-D interface may give better performance
such as OpenGL/QuickDraw3D.
I just started using Squeak. Remind me of classic Smalltalk.
I like to add windowing system, is there some standard c interface
in Squeak?
-- sehyo chang
At 11:38 AM 6/2/97 +0000, you wrote:
>Hi Squeakers,
>
>Inspired by Hans-Martins work on the triangleBits primitive I've
>started to work on some 3d extensions. So far, I've integrated flat
>and gouraud shading as well as z-buffering (texture mapping will come
>in the future).
>
>What I'm thinking about right now is: How can 3d graphics naturally
>integrated into Squeaks visualization philosophy? In other words,
>should there be a model-view concept (say the model is the polygon
>mesh, the view a specific renderer) should there be a 3dMorph or what?
>
>Although there are several other approaches to OO 3d graphics I would
>like to discuss the issue, since we could try to make "something completely
>different" ;-)
>
>Bye,
> Andreas
>
>PS. Because my rasterizer code is not yet ready to be translated into C
>code it's incredibly slow ... makes about .1 to .5 frames on my PPro200 ;-)
>--
>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 >=============+
>
>
--------------------
Sehyo Chang
Virtual Enteprise Technology, inc.
sehyo@netcom.com
Date: 97 Jun 02 11:36:36 am
From: Tim Rowledge <rowledge@interval.com>
To: Squeak mailinglist <squeak@create.ucsb.edu>
In-Reply-To: <8chgfghpp1.fsf@gadget.cscaper.com>
Subject: Re: Smalltalk Ballon.....was Teaching Smalltalk
On Mon 02 Jun, Randal Schwartz wrote:
> Well, I hate to rain on your parade (or balloon), but technically,
> Byte could still claim a copyright infringement on *your* art as a
> "derived work" depending on the strength of their legal team.
So far as I understand copyright law, my cartoon representation is
ok. It's no different to all those varieties of 'American Gothic'; ie
it's clearly intended to represent a similar scene but is not a copy.
And given John McIntosh's experience I doubt we'll have any problems
anyway.!!
I've placed a new copy on the website, this time a plain PS file that
definitely prints ok on my LJ5ps.
--
Tim Rowledge: rowledge@interval.com (w) +1 (415) 856-7230 (w)
tim@sumeru.stanford.edu (h) <http://sumeru.stanford.edu/tim>
Date: 97 Jun 02 12:28:12 pm
From: Jecel Assumpcao Jr <jecel@lsi.usp.br>
To: squeak@create.ucsb.edu
Subject: Re: Teaching Smalltalk
dave wrote:
>
> Contra DNS, The problem Jecel describes is, in fact, a legitimate
> critique of smalltalk from the standpoint of teaching as well
> as design.
>
> For a high-level discussion of the technical side, see OOPSLA '96,
> "A Declarative Model for Defining Smalltalk Programs," by Allen
> Wirfs-Brock, where he outlines some of the problems of system
> complexity and the difficulty of isolating particular components
> for study or transport.
Actually, I was just quoting the authors of the Carleton
paper, so I don't feel the least bit flamed even though
I agree with them in general.
This has been discussed here before:
On Tue, 15 Apr 1997 22:51:44 -0700 Tim Rowledge <rowledge@interval.com>
wrote:
> 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
I just tried this with Smalltalk Express and Squeak:
| x t |
x := #(4 6 8 10) asOrderedCollection.
t := 0.
self halt.
x do: [ :i | t := t + i ].
^ t
Things were a bit messy with the Squeak debugger, but it was pretty
understandable. The Smalltalk Express debugger was much better -
just "hopping" all the time gave a reasonable view of code execution.
The idea here was that you can't avoid peeking into how Smalltalk
implements #do: in OrderedCollection. Due to tricks played by the
compiler, you don't get to see how #while:, #<= or #+ are
implemented. In Self all these things are normal messages, and
the debugger happily steps into the corresponding code all the
way down to some hairy primitive calls. I can tell you this makes
novices quickly learn to avoid the debugger, and try to fix things
by trial and error instead!
-- Jecel
Date: 97 Jun 02 12:32:19 pm
From: "David N. Smith" <dnsmith@watson.ibm.com>
To: Tim Rowledge <rowledge@interval.com>
Cc: Squeak mailinglist <squeak@create.ucsb.edu>
In-Reply-To: <Marcel-1.08-0602190504-339KL&V@goldskin.interval.com>
Subject: Re: Smalltalk Ballon.....was Teaching Smalltalk
At 15:05 -0400 6/2/97, Tim Rowledge wrote:
>On Mon 02 Jun, Randal Schwartz wrote:
>
>> Well, I hate to rain on your parade (or balloon), but technically,
>> Byte could still claim a copyright infringement on *your* art as a
>> "derived work" depending on the strength of their legal team.
>So far as I understand copyright law, my cartoon representation is
>ok. It's no different to all those varieties of 'American Gothic'; ie
>it's clearly intended to represent a similar scene but is not a copy.
>And given John McIntosh's experience I doubt we'll have any problems
>anyway.!!
>
>I've placed a new copy on the website, this time a plain PS file that
>definitely prints ok on my LJ5ps.
>--
>Tim Rowledge: rowledge@interval.com (w) +1 (415) 856-7230 (w)
> tim@sumeru.stanford.edu (h) <http://sumeru.stanford.edu/tim>
That one both pints on my Optra and loads into Illustrator, thought in B&W.
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.
Date: 97 Jun 02 1:46:12 pm
From: Kate Sherwood <ducky@best.com>
To: squeak@create.ucsb.edu
Subject: Re: Smalltalk Ballon.....was Teaching Smalltalk
Tim Rowledge said:
> So far as I understand copyright law, my cartoon representation is
> ok. It's no different to all those varieties of 'American Gothic'; ie
> it's clearly intended to represent a similar scene but is not a copy.
Ummmm you have to be careful there. *Parody* is specifically allowed under
copyright law. You might have trouble claiming that the balloon is parody.
(Also, works created before 1978 had a 28-year copyright limit with one
renewal period of 28 years allowed. So a max of 56 years from creation.
American Gothic was painted in 1932, so the copyright ran out on or
before 1988. (It is now life-of-the-author-plus-50-years.)
On the other hand, you probably aren't in much danger. Copyright damages are
assessed based on how much money the copyright holder
loses (double damage if it can be proven to be with knowledge) from the
violation. On the other other hand, the copyright holder can elect to
get statuatory damages (basically the court decides comes up with
a number between $500 and $20,000). Because Tim's balloon is not-for-profit,
does not use the original artwork, and only uses a portion of the idea,
he's probably not in too much trouble.
John McIntosh
> Actually Robert Tinney owns the copyright on the art work, not Byte.
>From the US Government copyright site,
: In the case of works made for hire, the employer and not the employee is
: considered to be the author.
Artists can of course write things into their contracts that say that
they retain the rights.
See http://lcweb.loc.gov/copyright/circs/circ01.html for more on copyright
law.
(*DISCLAIMER* I am not a lawyer.)
Date: 97 Jun 02 1:48:51 pm
From: Dan Ingalls <DanI@wdi.disney.com>
To: Randal Schwartz <merlyn@stonehenge.com>
Cc: Squeak@create.ucsb.edu
In-Reply-To: <8chgfghpp1.fsf@gadget.cscaper.com>
Subject: Re: Smalltalk Ballon.....was Teaching Smalltalk
>>>>>> "Tim" =3D=3D Tim Rowledge <rowledge@interval.com> writes:
>
>Tim> I have put a PostScript ( supposedley an encapsulated PS file, but I
>Tim> don't have any way to check it out myself) file of the version of the
>Tim> Byte balloon I did someyears ago on my website.
>[...]
>Tim> It worked out pretty well and has one big advantage over any attempt
>Tim> to scan Tinney's original artwork - it's my copyright and I happily
>Tim> grant any of you permission to use it. The Byte cover is copyright
>Tim> Byte and they are *quite* protective about it.
>
>Well, I hate to rain on your parade (or balloon), but technically,
>Byte could still claim a copyright infringement on *your* art as a
>"derived work" depending on the strength of their legal team.
>
>Unless you can demonstrate that you came up with the balloon
>independently of anything Byte did. And you've just nullified that
>claim in public by the way you said what you said above.
>
>So, before the rest of us go adopting that image, we'd better get an
>explicit waiver from Byte for Tim's balloon.
Well, we should be in pretty good shape. The balloon was my idea. When=
Byte came to Xerox to do the 8/81 issue, I suggested the entire layout,=
including the relationship to the island (which did come from a prior=
August issue so there might be problems with it). Having loved the=
Mysterious Island of Jules Verne (a coincidence that Alan loved 20k Under=
the Sea), the balloon was my vehicle of choice for ST's escape from the=
ivory tower. So, the concept is mine (and hereby freely granted to=
anyone), and as long as the artwork is not a direct copy of Tinney's=
balloon, there should be no problem.
However, I still really like the job Tinney did on it. I photographed my=
lithograph and blew it up to 30x40, and it makes a spectacular poster (the=
litho texture makes the poster look like canvas). If there was a buck to=
be made, my guess is that Tinney would let us run off a limited edition of=
such a poster -- as John McIntosh says, he should appreciate the interest =
[John - pls do send me his #, and I'll check it out].
- D
Date: 97 Jun 02 3:18:21 pm
From: Maloney <johnm@wdi.disney.com>
To: Sehyo Chang <sehyo@netcom.com>
Cc: squeak@create.ucsb.edu
In-Reply-To: <1.5.4.32.19970602204346.0091ec28@netcom18.netcom.com>
Subject: Re: Concepts for 3d graphics
>I think maybe using standard 3-D interface may give better performance
>such as OpenGL/QuickDraw3D.
>
>I just started using Squeak. Remind me of classic Smalltalk.
>I like to add windowing system, is there some standard c interface
>in Squeak?
>
>-- sehyo chang
You can certainly write your own primitives and link them into the VM.
We don't have a package that generates arg conversion code
automatically, however.
We do have a way of translating a restricted set of Smalltalk into C.
(Look at how the sound generation primitives are done, for example.)
-- John
Date: 97 Jun 02 7:03:19 pm
From: Eliot & Linda <elcm@pacbell.net>
To: Hans-Martin Mosner <hmm@heeg.de>
Cc: squeak@create.ucsb.edu
Subject: Re: 2 problems
Hans-Martin Mosner wrote:
>
> Andreas Raab wrote:
> > 1) Anyone ever tried to using #perform: with an arbitrary number?!
> > Looks like this crashes the system (try "nil perform: 0").
>
> The primitivePerform and primitivePerformWithArgs do not check for
> non-integerness of the message selector. This crashes the method lookup
> where the interpreter tries to read the hash bits from the message
> selector's object header.
> I don't have a running Squeak here in which to fix the problem, but it's
> not difficult.
Its actually quite useful to be able to use SmallIntegers as message
selectors. I had to fix my BrouHaHa bytecode interpreter for the Active
Book company to do just this. It enabled them to produce a
significantly smaller image. So can I suggest that the thing to fix is
the method dictionary search algorithm so its tolerant of immediates?
If immediates have a 2 bit tag then masking off the bottom 2 bits
derives a suitably aligned index without shifts.
> Interestingly, perform:withArgs: correctly checks that the second
> argument is indeed an Array. ParcPlace VisualWorks didn't at one time
> (might have been VW 1.0) which caused quite a bit of head scratching
> until I found out that some code was doing "self perform: selector
> withArgs: 0"
>
> Hans-Martin
check what Squeak does with the following :)
| args |
args _ Array new: 2.
args at: 1 put: #perform:withArguments:.
args at: 2 put: args.
args perform: args first withArguments: args
who said primitives aren't recursive??
Correct fix left as an exercise to the reader.
_______________,,,^..^,,,_______________
Eliot
Date: 97 Jun 02 8:19:01 pm
From: Dan Ingalls <DanI@wdi.disney.com>
To: elcm@pacbell.net
Cc: Squeak@create.ucsb.edu
In-Reply-To: <3393813C.1E68@pacbell.net>
Subject: Re: 2 problems
>Its actually quite useful to be able to use SmallIntegers as message
>selectors. I had to fix my BrouHaHa bytecode interpreter for the Active
>Book company to do just this. It enabled them to produce a
>significantly smaller image. So can I suggest that the thing to fix is
>the method dictionary search algorithm so its tolerant of immediates?
>If immediates have a 2 bit tag then masking off the bottom 2 bits
>derives a suitably aligned index without shifts.
You are correct about the compactness, and unintentional use of integers would still get appropriately diagnosed, so I shall make the change you suggest next time I get the chance. Thanks for the idea.
- D
Date: 97 Jun 02 9:00:16 pm
From: Leandro Caniglia <caniglia@mate.dm.uba.ar>
To: 'Squeak' <squeak@create.ucsb.edu>
Subject: Sugar
Hi Squeakers!
This night, we have just founded SUGAR, the Smalltalk User Group of =
ARgentina. Ten people were in our first meeting, all of them with many =
years of experience in Smalltalk developments. I'm glad, I'm very happy. =
It was really important for us.
Good night squeakers...
Saludos,
Leandro
Date: 97 Jun 02 9:04:11 pm
From: "Dwight Hughes" <dhughes@intellinet.com>
To: <elcm@pacbell.net>, "Hans-Martin Mosner" <hmm@heeg.de>
Cc: <squeak@create.ucsb.edu>
Subject: A possibly dumb question [Re: 2 problems]
| From: Eliot & Linda <elcm@pacbell.net>
|
| Hans-Martin Mosner wrote:
| >
| > Andreas Raab wrote:
| > > 1) Anyone ever tried to using #perform: with an arbitrary number?!
| > > Looks like this crashes the system (try "nil perform: 0").
| >
| > The primitivePerform and primitivePerformWithArgs do not check for
| > non-integerness of the message selector. This crashes the method lookup
| > where the interpreter tries to read the hash bits from the message
| > selector's object header.
| > I don't have a running Squeak here in which to fix the problem, but
it's
| > not difficult.
|
| Its actually quite useful to be able to use SmallIntegers as message
| selectors. I had to fix my BrouHaHa bytecode interpreter for the Active
| Book company to do just this. It enabled them to produce a
| significantly smaller image. So can I suggest that the thing to fix is
| the method dictionary search algorithm so its tolerant of immediates?
| If immediates have a 2 bit tag then masking off the bottom 2 bits
| derives a suitably aligned index without shifts.
[ snip ]
Is there a good reason why SmallIntegers have been tagged b1 or b11 and
object pointers b0 or b00 since the beginning of Smalltalk and not vice
versa? It seems to me, naively, that having SmallIntegers tagged as b00
would have several advantages - no masking required to use them in
certain bitwise logic or most arithmetic, and direct use as an index
as above, to begin with.
-- Dwight
Date: 97 Jun 03 12:13:29 am
From: Hans-Martin Mosner <hmm@heeg.de>
To: Dwight Hughes <dhughes@intellinet.com>
Cc: squeak@create.ucsb.edu
Subject: Re: A possibly dumb question
Dwight Hughes wrote:
>
> Is there a good reason why SmallIntegers have been tagged b1 or b11 and
> object pointers b0 or b00 since the beginning of Smalltalk and not vice
> versa? It seems to me, naively, that having SmallIntegers tagged as b00
> would have several advantages - no masking required to use them in
> certain bitwise logic or most arithmetic, and direct use as an index
> as above, to begin with.
>
> -- Dwight
I think the good reason for this is that object pointers can be used as
pointers when encoded like this. The VM generally does much more object
pointer related stuff than integer stuff (think of garbage collection).
Some of the first Smalltalk implementations had indeed other conventions
for encoding SmallIntegers and other oops, especially since the oop
space
was very limited in 16-bit machines. I think that some version of the
Dorado implementation had 48k objects and limited the SmallInteger range
to -8192..8191. I saw The Analyst running on a Dorado at Xerox SIS a
long
time ago, and it must have been such a beast. They probably used not the
low bits but the high bits of an oop for SmallInteger tagging.
Hans-Martin
Date: 97 Jun 03 4:22:59 am
From: "Andreas Raab" <raab@isg.cs.uni-magdeburg.de>
To: Sehyo Chang <sehyo@netcom.com>
Cc: squeak@create.ucsb.edu
Subject: Re: Concepts for 3d graphics
> I think maybe using standard 3-D interface may give better performance
> such as OpenGL/QuickDraw3D.
You're definitely right - but I just loved the idea to building my
own 3d graphics engine (something any CG guy should at least do
once). And if so - why not in Smalltalk ;-)
But seriously, there is actually good reason to build such an engine
directly in Squeak. I've been using OpenGL from VW for quite some
time and found it very difficult to integrate 3d objects into 2d
views - actually you've always a separate view for the 3d world.
Building the engine in Squeak should enable us to directly integrate
3d objects in - for instance - Morphic environments.
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 >=============+
Date: 97 Jun 03 2:18:04 pm
From: Dan Ingalls <DanI@wdi.disney.com>
To: Squeak@create.ucsb.edu
Subject: A couple of VM changes
--============_-1346744639==_============
Content-Type: text/plain; charset="us-ascii"
These will be in the next release, but I thought some folks might want early access.
The methods in BItBltSImulation provide clipping for WarpBlt (it never worked before), as well as improved treatement of transparency when doing smoothing.
The methods in Interpreter implement Eliot Miranda's suggestion that SmallIntegers be acceptable as selectors (for the specific purpose of making compact images).
- Dan
--============_-1346744639==_============
Content-Type: text/plain; name="WarpAndVMFixes-di.cs"; charset="us-ascii"
Content-Transfer-Encoding: quoted-printable
Content-Disposition: attachment; filename="WarpAndVMFixes-di.cs"
'From Squeak 1.19d of April 13, 1997 on 3 June 1997 at 2:31:01 pm'!
"Change Set: WarpFix
Date: 3 June 1997
Author: Dan Ingalls
=46ixed WarpBlt clipping, and used it to advantage in TransformMorph display=
=2E
Made WarpBlt handle transparency independently of pixel averaging.
Used this to greatly simplify SketchMorph rotate and scale.
Made VM tolerate SmallIntegers as message selectors to allow for
shrunken images with Symbols eliminated
"!
!BitBltSimulation methodsFor: 'inner loop'!
warpLoop
| skewWord halftoneWord mergeWord destMask startBits
deltaP12x deltaP12y deltaP43x deltaP43y pAx pAy
xDelta yDelta pBx pBy smoothingCount sourceMapOop nSteps t |
"This version of the inner loop traverses an arbirary quadrilateral
source, thus producing a general affine transformation."
=20
(interpreterProxy fetchWordLengthOf: bitBltOop) >=3D (BBWarpBase+12)
ifFalse: [^ interpreterProxy primitiveFail].
nSteps _ height-1. nSteps <=3D 0 ifTrue: [nSteps _ 1].
pAx _ interpreterProxy fetchIntegerOrTruncFloat: BBWarpBase ofObject: bitBl=
tOop.
t _ interpreterProxy fetchIntegerOrTruncFloat: BBWarpBase+3 ofObject: bitBl=
tOop.
deltaP12x _ self deltaFrom: pAx to: t nSteps: nSteps.
deltaP12x < 0 ifTrue: [pAx _ t - (nSteps*deltaP12x)].
pAy _ interpreterProxy fetchIntegerOrTruncFloat: BBWarpBase+1 ofObject: bit=
BltOop.
t _ interpreterProxy fetchIntegerOrTruncFloat: BBWarpBase+4 ofObject: bitBl=
tOop.
deltaP12y _ self deltaFrom: pAy to: t nSteps: nSteps.
deltaP12y < 0 ifTrue: [pAy _ t - (nSteps*deltaP12y)].
pBx _ interpreterProxy fetchIntegerOrTruncFloat: BBWarpBase+9 ofObject: bit=
BltOop.
t _ interpreterProxy fetchIntegerOrTruncFloat: BBWarpBase+6 ofObject: bitBl=
tOop.
deltaP43x _ self deltaFrom: pBx to: t nSteps: nSteps.
deltaP43x < 0 ifTrue: [pBx _ t - (nSteps*deltaP43x)].
pBy _ interpreterProxy fetchIntegerOrTruncFloat: BBWarpBase+10 ofObject: bi=
tBltOop.
t _ interpreterProxy fetchIntegerOrTruncFloat: BBWarpBase+7 ofObject: bitBl=
tOop.
deltaP43y _ self deltaFrom: pBy to: t nSteps: nSteps.
deltaP43y < 0 ifTrue: [pBy _ t - (nSteps*deltaP43y)].
interpreterProxy failed ifTrue: [^ false]. "ie if non-integers above"
interpreterProxy argCount =3D 2
ifTrue: [smoothingCount _ interpreterProxy stackIntegerValue: 1.
sourceMapOop _ interpreterProxy stackValue: 0.
sourceMapOop =3D interpreterProxy nilObject
ifTrue: [sourcePixSize < 16 ifTrue:
["color map is required to smooth non-RGB dest"
^ interpreterProxy primitiveFail]]
ifFalse: [(interpreterProxy fetchWordLengthOf: sourceMapOop)
< (1 << sourcePixSize) ifTrue:
["sourceMap must be long enough for sourcePixSize"
^ interpreterProxy primitiveFail]]]
ifFalse: [smoothingCount _ 1.
sourceMapOop _ interpreterProxy nilObject].
startBits _ pixPerWord - (dx bitAnd: pixPerWord-1).
nSteps _ width-1. nSteps <=3D 0 ifTrue: [nSteps _ 1].
=20
destY to: clipY-1 do:
[ :i | "Advance increments if there was clipping in y"
pAx _ pAx + deltaP12x.
pAy _ pAy + deltaP12y.
pBx _ pBx + deltaP43x.
pBy _ pBy + deltaP43y].
1 to: bbH do:
[ :i | "here is the vertical loop..."
xDelta _ self deltaFrom: pAx to: pBx nSteps: nSteps.
xDelta >=3D 0 ifTrue: [sx _ pAx] ifFalse: [sx _ pBx - (nSteps*xDelta)].
yDelta _ self deltaFrom: pAy to: pBy nSteps: nSteps.
yDelta >=3D 0 ifTrue: [sy _ pAy] ifFalse: [sy _ pBy - (nSteps*yDelta)].
destX to: clipX-1 do:
[:word | "Advance increments if there was clipping in x"
sx _ sx + xDelta.
sy _ sy + yDelta].
noHalftone
ifTrue: [halftoneWord _ AllOnes]
ifFalse: [halftoneWord _ interpreterProxy longAt: (halftoneBase + (dy+i-1=
\\ halftoneHeight * 4))].
destMask _ mask1.
"pick up first word"
bbW < startBits
ifTrue: [skewWord _ self warpSourcePixels: bbW
xDeltah: xDelta yDeltah: yDelta
xDeltav: deltaP12x yDeltav: deltaP12y
smoothing: smoothingCount sourceMap: sourceMapOop.
skewWord _ skewWord
bitShift: (startBits - bbW)*destPixSize]
ifFalse: [skewWord _ self warpSourcePixels: startBits
xDeltah: xDelta yDeltah: yDelta
xDeltav: deltaP12x yDeltav: deltaP12y
smoothing: smoothingCount sourceMap: sourceMapOop].
=20
1 to: nWords do:
[ :word | "here is the inner horizontal loop..."
mergeWord _ self merge: (skewWord bitAnd: halftoneWord)
with: ((interpreterProxy longAt: destIndex) bitAnd: destMask).
interpreterProxy longAt: destIndex
put: ((destMask bitAnd: mergeWord)
bitOr:
(destMask bitInvert32 bitAnd: (interpreterProxy longAt: destIndex))).
destIndex _ destIndex + 4.
word >=3D (nWords - 1) ifTrue:
[word =3D nWords ifFalse:
["set mask for last word in this row"
destMask _ mask2.
skewWord _ self warpSourcePixels: pixPerWord
xDeltah: xDelta yDeltah: yDelta
xDeltav: deltaP12x yDeltav: deltaP12y
smoothing: smoothingCount sourceMap: sourceMapOop]]
ifFalse:
["use fullword mask for inner loop"
destMask _ AllOnes.
skewWord _ self warpSourcePixels: pixPerWord
xDeltah: xDelta yDeltah: yDelta
xDeltav: deltaP12x yDeltav: deltaP12y
smoothing: smoothingCount sourceMap: sourceMapOop].
].
pAx _ pAx + deltaP12x.
pAy _ pAy + deltaP12y.
pBx _ pBx + deltaP43x.
pBy _ pBy + deltaP43y.
destIndex _ destIndex + destDelta]! !
!BitBltSimulation methodsFor: 'pixel mapping'!
smoothPix: n atXf: xf yf: yf dxh: dxh dyh: dyh dxv: dxv dyv: dyv
pixPerWord: srcPixPerWord pixelMask: sourcePixMask
sourceMap: sourceMap
| sourcePix r g b x y rgb bitsPerColor d nPix maxPix |
r _ g _ b _ 0. "Separate r, g, b components"
maxPix _ n*n.
x _ xf. y _ yf.
nPix _ 0. "actual number of pixels (not clipped and not transparent)"
0 to: n-1 do:
[:i |
0 to: n-1 do:
[:j |
sourcePix _ (self sourcePixAtX: x + (dxh*i) + (dxv*j) >> BinaryPoint
y: y + (dyh*i) + (dyv*j) >> BinaryPoint
pixPerWord: srcPixPerWord)
bitAnd: sourcePixMask.
(combinationRule=3D25 "PAINT" and: [sourcePix =3D 0]) ifFalse: =20
["If not clipped and not transparent, then tally rgb values"
nPix _ nPix + 1.
sourcePixSize < 16
ifTrue: ["Get 24-bit RGB values from sourcemap table"
rgb _ (interpreterProxy fetchWord: sourcePix ofObject: sourceMap)=
bitAnd: 16rFFFFFF]
ifFalse: ["Already in RGB format"
sourcePixSize =3D 32
ifTrue: [rgb _ sourcePix bitAnd: 16rFFFFFF]
ifFalse: ["Note could be faster"
rgb _ self rgbMap: sourcePix from: 5 to: 8]].
r _ r + ((rgb >> 16) bitAnd: 16rFF).
g _ g + ((rgb >> 8) bitAnd: 16rFF).
b _ b + (rgb bitAnd: 16rFF).
]].
].
(nPix =3D 0 or: [combinationRule=3D25 "PAINT" and: [nPix < (maxPix//2)]])
ifTrue: [^ 0 "All pixels were 0, or most were transparent"].
colorMap ~=3D interpreterProxy nilObject
ifTrue: [bitsPerColor _ cmBitsPerColor]
ifFalse: [destPixSize =3D 16 ifTrue: [bitsPerColor _ 5].
destPixSize =3D 32 ifTrue: [bitsPerColor _ 8]].
d _ 8 - bitsPerColor.
rgb _ ((r // nPix >> d) << (bitsPerColor*2))
+ ((g // nPix >> d) << bitsPerColor)
+ ((b // nPix >> d)).
rgb =3D 0 ifTrue: [
"only generate zero if pixel is really transparent"
(r + g + b) > 0 ifTrue: [rgb _ 1]].
colorMap ~=3D interpreterProxy nilObject
ifTrue: [^ interpreterProxy fetchWord: rgb ofObject: colorMap]
ifFalse: [^ rgb]
! !
!Canvas methodsFor: 'copying'!
copyOrigin: aPoint clipRect: aRectangle
"Return a copy of this canvas with the given origin. The clipping rectangle=
of this canvas is the intersection of the given rectangle and the=
receiver's current clipping rectangle. This allows the clipping rectangles=
of nested clipping morphs to be composed."
^ self copy setOrigin: aPoint clipRect: aRectangle! !
!Form methodsFor: 'scaling, rotation'!
rotateBy: deg magnify: scale smoothing: cellSize
"Rotate the receiver by the indicated number of degrees and magnify. =
3/26/97 tk"
"rot is the destination form, big enough for any angle."
| side rot warp r1 pts p bigSide |
side _ 1 + ((width*width) + (height*height)) asFloat sqrt asInteger.
bigSide _ (side * scale) rounded.
rot _ Form extent: bigSide@bigSide depth: self depth.
warp _ (WarpBlt toForm: rot)
sourceForm: self;
colorMap: (self colormapIfNeededForDepth: depth);
cellSize: cellSize; "installs a new colormap if cellSize > 1"
combinationRule: Form paint.
r1 _ (0@0 extent: side@side) align: (side@side)//2 with: self boundingBox c=
enter.
"Rotate the corners of the source rectangle."=20
pts _ r1 innerCorners collect:
[:pt | p _ pt - r1 center.
(r1 center x asFloat + (p x asFloat*deg degreeCos) + (p y asFloat*deg=
degreeSin)) @
(r1 center y asFloat - (p x asFloat*deg degreeSin) + (p y asFloat*deg degr=
eeCos))].
warp copyQuad: pts toRect: rot boundingBox.
^ rot
"
| a f | f _ Form fromDisplay: (0@0 extent: 200@200). a _ 0.
[Sensor anyButtonPressed] whileFalse:
[((Form fromDisplay: (Sensor cursorPoint extent: 130@66))
rotateBy: (a _ a+5) magnify: 0.75 smoothing: 2) display].
f display
"! !
!FormCanvas methodsFor: 'private'!
setOrigin: aPoint clipRect: aRectangle
super setOrigin: aPoint clipRect: aRectangle.
port clipRect: aRectangle
! !
!FormCanvas methodsFor: 'copying'!
warpFrom: sourceQuad toRect: destRect
^ (WarpBlt toForm: port destForm)
combinationRule: Form paint;
sourceQuad: sourceQuad destRect: (destRect translateBy: origin);
clipRect: clipRect! !
!Interpreter methodsFor: 'message sending'!
lookupMethodInDictionary: dictionary
"This method lookup tolerates integers as Dictionary keys to support
execution of images in which Symbols have been compacted out"
| length index mask wrapAround nextSelector methodArray |
self inline: true.
length _ self fetchWordLengthOf: dictionary.
mask _ length - SelectorStart - 1.
(self isIntegerObject: messageSelector)
ifTrue:
[index _ (mask bitAnd: (self integerValueOf: messageSelector)) + SelectorS=
tart]
ifFalse:
[index _ (mask bitAnd: (self hashBitsOf: messageSelector)) + SelectorStart=
].
"It is assumed that there are some nils in this dictionary, and search will
stop when one is encountered. However, if there are no nils, then wrapArou=
nd
will be detected the second time the loop gets to the end of the table."
wrapAround _ false.
[true] whileTrue:
[nextSelector _ self fetchPointer: index
ofObject: dictionary.
nextSelector=3DnilObj ifTrue: [^false].
nextSelector=3DmessageSelector
ifTrue: [methodArray _ self fetchPointer: MethodArrayIndex
ofObject: dictionary.
newMethod _ self fetchPointer: index - SelectorStart
ofObject: methodArray.
primitiveIndex _ self primitiveIndexOf: newMethod.
^true].
index _ index + 1.
index =3D length
ifTrue: [wrapAround ifTrue: [^false].
wrapAround _ true.
index _ SelectorStart]]! !
!Interpreter methodsFor: 'control primitives'!
primitivePerform
| performSelector newReceiver selectorIndex |
performSelector _ messageSelector.
messageSelector _ self stackValue: argumentCount - 1.
newReceiver _ self stackValue: argumentCount.
"NOTE: the following lookup may fail and be converted to #doesNotUnderstand=
:,
so we must adjust argument count now, so that would work."
argumentCount _ argumentCount - 1.
self lookupMethodInClass: (self fetchClassOf: newReceiver).
self success: (self argumentCountOf: newMethod) =3D argumentCount.
successFlag
ifTrue: [selectorIndex _ self stackPointerIndex - argumentCount.
self transfer: argumentCount
fromIndex: selectorIndex + 1
ofObject: activeContext
toIndex: selectorIndex
ofObject: activeContext.
self pop: 1.
self executeNewMethod. "Recursive xeq affects successFlag"
successFlag _ true]
ifFalse: [argumentCount _ argumentCount + 1.
messageSelector _ performSelector]!
primitivePerformWithArgs
| thisReceiver performSelector argumentArray arraySize index cntxSize |
argumentArray _ self popStack.
arraySize _ self fetchWordLengthOf: argumentArray.
cntxSize _ self fetchWordLengthOf: activeContext.
self success: (self stackPointerIndex + arraySize) < cntxSize.
self assertClassOf: argumentArray is: (self splObj: ClassArray).
successFlag
ifTrue: [performSelector _ messageSelector.
messageSelector _ self popStack.
thisReceiver _ self stackTop.
argumentCount _ arraySize.
index _ 1.
[index <=3D argumentCount]
=09 whileTrue:
[self push: (self fetchPointer: index - 1 ofObject: argumentArray).
index _ index + 1].
self lookupMethodInClass: (self fetchClassOf: thisReceiver).
self success: (self argumentCountOf: newMethod) =3D argumentCount.
successFlag
ifTrue: [self executeNewMethod. "Recursive xeq affects successFlag"
successFlag _ true]
ifFalse: [self unPop: argumentCount.
self push: messageSelector.
self push: argumentArray.
argumentCount _ 2.
messageSelector _ performSelector]]
ifFalse: [self unPop: 1]! !
!SketchEditorMorph methodsFor: 'actions & preps'!
rotateBy: initialPoint
"Left-right is rotation, up-down is scale. 3/26/97 tk Slider at top of=
window. 4/3/97 tk"
| pt temp amt smooth |
pt _ initialPoint - canvasRectangle center.
"cy _ canvasRectangle width * 45 // 100."
smooth _ paintingForm depth > 8 ifTrue: [2] ifFalse: [2].
"When smoothing is 1, no problems with black halo in 16 bits (color mixing)=
"
[Sensor redButtonPressed] whileTrue:
[amt _ pt x abs < 12 ifTrue: [0 "detent"] ifFalse: [pt x - (12 * pt x abs=
// pt x)].
temp _ buff rotateBy: amt * 1.8 + cumRot magnify: cumMag smoothing: smooth.
temp displayOn: paintingForm at: (paintingForm center - temp center + buff =
offset).
rotationButton destX: amt - 6 + (canvasRectangle width // 2) + composite x.
self render: paintingForm boundingBox.
pt _ Sensor mousePoint - canvasRectangle center.
dirty _ true].
cumRot _ amt * 1.8 + cumRot. "what we settled on"!
rotateScalePrep
"Make a source that is the paintingForm. Work from that. 3/26/97 tk"
| newBox field |
paintingForm width > 120=20
ifTrue: [newBox _ paintingForm innerPixelRectFor: 0 orNot: true.
"minimum size"
newBox _ newBox insetBy:=20
((18 - newBox width max: 0)//2) @ ((18 - newBox height max: 0)//2) * -1]
ifFalse: [newBox _ paintingForm boundingBox].
newBox _ newBox expandBy: 1.
buff _ Form extent: newBox extent depth: paintingForm depth.
buff offset: newBox center - paintingForm center.
buff copyBits: newBox from: paintingForm at: 0@0=20
clippingBox: buff boundingBox rule: Form over fillColor: nil.
"Could just run up owner chain asking colorUsed, but may not be embedded"
field _ self world findA: PlayfieldMorph.
field ifNil: [field _ self world]. "Right color for edge of object to merge=
with"
cumRot _ 0.0. cumMag _ 1.0. "start over"
!
scaleBy: initialPoint
"up-down is scale. 3/26/97 tk Now a slider on the right 4/3/97 tk"
| pt temp cy oldRect amt |
pt _ initialPoint - canvasRectangle center.
cy _ canvasRectangle height * 0.5.
temp _ buff.
[Sensor redButtonPressed] whileTrue:
[oldRect _ temp boundingBox.
amt _ pt y abs < 12 ifTrue: [1.0 "detent"] ifFalse: [pt y- (12 * pt y abs=
// pt x)].
temp _ buff rotateBy: cumRot magnify: (amt asFloat / cy + 1.0) * cumMag=20
smoothing: 2.
oldRect width > temp width ifTrue: ["shrinking"
oldRect _ oldRect translateBy: (paintingForm center - oldRect center +=
buff offset).
paintingForm fill: (oldRect expandBy: 1@1) rule: Form over fillColor:=
Color transparent].
temp displayOn: paintingForm at: (paintingForm center - temp center + buff =
offset).
scaleButton destY: pt y - 6 + (canvasRectangle height // 2) + composite y.
self render: paintingForm boundingBox.
pt _ Sensor mousePoint - canvasRectangle center.
dirty _ true].
cumMag _ cumMag * (amt asFloat / cy + 1.0). "what we settled on"! !
!WarpBlt methodsFor: 'primitives'!
sourceQuad: pts destRect: aRectangle
| fixedPt1 |
sourceX _ sourceY _ 0.
self destRect: aRectangle.
fixedPt1 _ (pts at: 1) x isInteger ifTrue: [16384] ifFalse: [16384.0].
p1x _ (pts at: 1) x * fixedPt1.
p2x _ (pts at: 2) x * fixedPt1.
p3x _ (pts at: 3) x * fixedPt1.
p4x _ (pts at: 4) x * fixedPt1.
p1y _ (pts at: 1) y * fixedPt1.
p2y _ (pts at: 2) y * fixedPt1.
p3y _ (pts at: 3) y * fixedPt1.
p4y _ (pts at: 4) y * fixedPt1.
p1z _ p2z _ p3z _ p4z _ 16384. "z-warp ignored for now"
!
warpBitsSmoothing: n sourceMap: sourceMap
| deltaP12 deltaP43 pA pB deltaPAB sp fixedPtOne picker poker pix nSteps |
<primitive: 147>
(width < 1) | (height < 1) ifTrue: [^ self].
fixedPtOne _ 16384. "1.0 in fixed-pt representation"
n > 1 ifTrue:
[(destForm depth < 16 and: [colorMap =3D=3D nil])
ifTrue: ["color map is required to smooth non-RGB dest"
^ self primitiveFail].
pix _ Array new: n*n].
nSteps _ height-1 max: 1.
deltaP12 _ (self deltaFrom: p1x to: p2x nSteps: nSteps)
@ (self deltaFrom: p1y to: p2y nSteps: nSteps).
pA _ (self startFrom: p1x to: p2x offset: nSteps*deltaP12 x)
@ (self startFrom: p1y to: p2y offset: nSteps*deltaP12 y).
deltaP43 _ (self deltaFrom: p4x to: p3x nSteps: nSteps)
@ (self deltaFrom: p4y to: p3y nSteps: nSteps).
pB _ (self startFrom: p4x to: p3x offset: nSteps*deltaP43 x)
@ (self startFrom: p4y to: p3y offset: nSteps*deltaP43 y).
picker _ BitBlt bitPeekerFromForm: sourceForm.
poker _ BitBlt bitPokerToForm: destForm.
poker clipRect: self clipRect.
nSteps _ width-1 max: 1.
destY to: destY+height-1 do:
[:y |
deltaPAB _ (self deltaFrom: pA x to: pB x nSteps: nSteps)
@ (self deltaFrom: pA y to: pB y nSteps: nSteps).
sp _ (self startFrom: pA x to: pB x offset: nSteps*deltaPAB x)
@ (self startFrom: pA y to: pB y offset: nSteps*deltaPAB x).
destX to: destX+width-1 do:
[:x |=20
n =3D 1
ifTrue:
[Transcript cr; print: sp // fixedPtOne asPoint.
poker pixelAt: x@y
put: (picker pixelAt: sp // fixedPtOne asPoint)]
ifFalse:
[0 to: n-1 do:
[:dx | 0 to: n-1 do:
[:dy |
pix at: dx*n+dy+1 put:
(picker pixelAt: sp
+ (deltaPAB*dx//n)
+ (deltaP12*dy//n)
// fixedPtOne asPoint)]].
poker pixelAt: x@y put: (self mixPix: pix
sourceMap: sourceMap
destMap: colorMap)].
sp _ sp + deltaPAB].
pA _ pA + deltaP12.
pB _ pB + deltaP43]! !
--============_-1346744639==_============--
Date: 97 Jun 03 5:30:48 pm
From: "Alex.Kouznetsov" <alex@create.ucsb.edu>
To: squeak@create.ucsb.edu
Subject: Mailing list problems on 6/3
Hello all,
the squeak@create.ucsb.edu list was upset most of the time 6/3 from about
6am until shortly after 1pm (PST). It is now functioning OK but some
messages may've been lost. (don't blame your mailer). Sorry for the
inconvinience.
Alex
Date: 97 Jun 03 8:16:00 pm
From: Eliot & Linda <elcm@pacbell.net>
To: squeak@create.ucsb.edu
Subject: Re: A possibly dumb question [Re: 2 problems]
Dwight Hughes wrote:
> Is there a good reason why SmallIntegers have been tagged b1 or b11 and
> object pointers b0 or b00 since the beginning of Smalltalk and not vice
> versa? It seems to me, naively, that having SmallIntegers tagged as b00
> would have several advantages - no masking required to use them in
> certain bitwise logic or most arithmetic, and direct use as an index
> as above, to begin with.
I can't speak for others, but in my case it was the naturalness of
having object pointers be pointers. I've yet to get around to making
what I suspect is the correct choice of b00 or b000. I think I'm
correct in thinking that most commodity microprocessor instruction sets
provide for an indirection that adds a small integral constant offset
with no cost in instruction size or time. hence it costs nothing
to remove the tag (by subtracting) during indirection through the
pointer.
I hear that numerous LISP implementations have used b00 integer tags to
good effect.
[For those that don't know the issues, having zero tags for integers
allows significantly cheaper implementation of addition, subtraction and
multiplication, and usually no extra cost in indirection through a
pointer.]
One reason to having object pointers be pointers in a C based
implementation is the difficulty of type-checing inadvertent use of
integers. e.g. imagine you use something like the following for
accessing object fields:
#define fieldOf(op,i) ((objectBody *)((long)(op)-3)[i])
If you inadvertently write fieldOf(7) the compiler won't warn you.
However, GCC supports statement expressions (or expression statements or
whatever) which provide a declaration scope within an expression, so you
can write the following, which will type-error if you don't pass an
object pointer:
#define fieldOf(op,i) \
({ oop _tmpop = (op); \
(objectBody *)((long)(op)-3)[i]; \
})
BTW, is it true that "OOP" stands for "Ordinary Object Pointer"? If
not, what's oops' etymology?
_______________,,,^..^,,,_______________
Eliot
Date: 97 Jun 04 12:26:07 am
From: "Hal Hildebrand" <horus@pacbell.net>
To: <elcm@pacbell.net>, <squeak@create.ucsb.edu>
Subject: Re: A possibly dumb question [Re: 2 problems]
Eliot,
>BTW, is it true that "OOP" stands for "Ordinary Object Pointer"? If
>not, what's oops' etymology?
My understanding is that OOP stands for Object Oriented Pointer. Don't
know where I picked it up from, but that's been my intepretation for years
now.
Hal
__
Time is when the day is like a play by Sartre
When it seems that book burning's in perfect order
http://www.hellblazer.com (Web)
mailto:hal@parcplace.com (Business)
mailto:horus@pacbell.net (Personal)
Date: 97 Jun 04 2:44:02 am
From: Carl E Gundel <carlg@world.std.com>
To: squeak@create.ucsb.edu
In-Reply-To: <199706040751.AAA07927@mail-gw2.pacbell.net>
Subject: Re: A possibly dumb question [Re: 2 problems]
On Wed, 4 Jun 1997, Hal Hildebrand wrote:
> >BTW, is it true that "OOP" stands for "Ordinary Object Pointer"? If
> >not, what's oops' etymology?
>
> My understanding is that OOP stands for Object Oriented Pointer. Don't
> know where I picked it up from, but that's been my intepretation for years
> now.
I've always read OOP as object oriented programming.
Carl
------------------------------------------------------------------
Carl Gundel carlg@world.std.com Shoptalk Systems 508-872-5315
author of Liberty BASIC, a 1996 PC Magazine Awards Finalist!
http://world.std.com/~carlg/basic.html
------------------------------------------------------------------
Date: 97 Jun 04 6:08:09 am
From: Dan Ingalls <DanI@wdi.disney.com>
To: elcm@pacbell.net
Cc: Squeak@create.ucsb.edu
In-Reply-To: <3394E3DC.32A@pacbell.net>
Subject: Re: A possibly dumb question [Re: 2 problems]
[NOTE: the following discussion is about the OOP as an acronym for a=
pointer, not for OO programming]
>BTW, is it true that "OOP" stands for "Ordinary Object Pointer"? If
>not, what's oops' etymology?
Here's my understanding of how this unfolded...
=46rom the beginning, (ie 1972 on) we found ourselves using the phrase=
"object pointer" in the early Smalltalk work. No problem.
Then around 1974 Ted Kaehler and I invented a virtual memeory made expressly=
for objects, called OOZE (Object Oriented Zoned Environment). We found we=
were having to talk about "OOZE object pointers" a lot, to specify the=
semantics of an object pointer whose referent might of might not be in=
memory. This, being pentasyllabic, finally pushed us over the acronym=
cliff to coin "OOP".
We got so used to "OOP" as an object pointer, that we kept using it after we=
dropped OOZE in ST-78 and -80. When we released ST-80 to our collaborating=
companies, they picked up the word, and eventually asked us what it really=
meant. We described the above, and explained that, after OOZE, we=
supposed, it could mean "Ordinary Object Pointer".
That's the truth.
=46rankly, I think "Ordinary Object Pointer" is much too ordinary. It's a=
little late, but I'm sure this group could waste a few thousand dollars of=
quality time coming up with something a little better.
;-)
Date: 97 Jun 04 7:25:56 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: <33930E65.7501BA95@lsi.usp.br>
Subject: Re: Teaching Smalltalk
At 14:18 -0400 6/2/97, Jecel Assumpcao Jr wrote:
> ...SNIP...
>I just tried this with Smalltalk Express and Squeak:
>
> | x t |
> x := #(4 6 8 10) asOrderedCollection.
> t := 0.
> self halt.
> x do: [ :i | t := t + i ].
> ^ t
>
>Things were a bit messy with the Squeak debugger, but it was pretty
>understandable. The Smalltalk Express debugger was much better -
>just "hopping" all the time gave a reasonable view of code execution.
>
>The idea here was that you can't avoid peeking into how Smalltalk
>implements #do: in OrderedCollection. Due to tricks played by the
>compiler, you don't get to see how #while:, #<= or #+ are
>implemented. In Self all these things are normal messages, and
>the debugger happily steps into the corresponding code all the
>way down to some hairy primitive calls. I can tell you this makes
>novices quickly learn to avoid the debugger, and try to fix things
>by trial and error instead!
>
>-- Jecel
But there is a great learning experience here, and an instructor who is
either on her/his toes (or experienced), can turn this into something very
positive. No student should be allowed to become afraid of the debugger but
should learn how to use the debugger properly. An experience with going a
bit deeper inside than she/he wants at the moment can both open the door to
learning how to debug at the level needed, and teach how to 'look inside'
when one wants to.
Another lesson here is for the implementer of the debugger, who might find
it useful to add an option which prevents too easily stepping into
specified classes/applications, with the default classes being the system
as delivered.
Which is most useful depends on whether the student is in a class (or
otherwise in a guided learning enviornment) or is learning by exploring.
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.
Date: 97 Jun 04 7:36:45 am
From: "David N. Smith" <dnsmith@watson.ibm.com>
To: elcm@pacbell.net
Cc: Hans-Martin Mosner <hmm@heeg.de>, squeak@create.ucsb.edu
In-Reply-To: <3393813C.1E68@pacbell.net>
Subject: Re: 2 problems
At 22:28 -0400 6/2/97, Eliot & Linda wrote:
>check what Squeak does with the following :)
>
> | args |
> args _ Array new: 2.
> args at: 1 put: #perform:withArguments:.
> args at: 2 put: args.
> args perform: args first withArguments: args
>
>who said primitives aren't recursive??
>
>Eliot
VW2.5 (Mac) and IBM/ST 3.0 both hang. Interesting bug, only an implementor
would ever think of it.
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.
Date: 97 Jun 04 8:49:09 am
From: Eliot & Linda <elcm@pacbell.net>
To: Dan Ingalls <DanI@wdi.disney.com>
Cc: Squeak@create.ucsb.edu
Subject: Re: A possibly dumb question [Re: 2 problems]
Dan Ingalls wrote:
>
> [NOTE: the following discussion is about the OOP as an acronym for a pointer, not for OO programming]
>
> >BTW, is it true that "OOP" stands for "Ordinary Object Pointer"? If
> >not, what's oops' etymology?
>
> Here's my understanding of how this unfolded...
>
> From the beginning, (ie 1972 on) we found ourselves using the phrase "object pointer" in the early Smalltalk work. No problem.
>
> Then around 1974 Ted Kaehler and I invented a virtual memeory made expressly for objects, called OOZE (Object Oriented Zoned Environment). We found we were having to talk about "OOZE object pointers" a lot, to specify the semantics of an object pointer whose referent might of might not be in memory. This, being pentasyllabic, finally pushed us over the acronym cliff to coin "OOP".
>
> We got so used to "OOP" as an object pointer, that we kept using it after we dropped OOZE in ST-78 and -80. When we released ST-80 to our collaborating companies, they picked up the word, and eventually asked us what it really meant. We described the above, and explained that, after OOZE, we supposed, it could mean "Ordinary Object Pointer".
>
> That's the truth.
>
> Frankly, I think "Ordinary Object Pointer" is much too ordinary. It's a little late, but I'm sure this group could waste a few thousand dollars of quality time coming up with something a little better.
>
> ;-)
Then
Outre Object Pointer
is the only possible choice ;-)
[Ian - I can't generate an acute - pardonne moi]
_______________,,,^..^,,,_______________
Eliot
Date: 97 Jun 04 9:08:32 am
From: Jecel Assumpcao Jr <jecel@lsi.usp.br>
To: Hal Hildebrand <horus@pacbell.net>
Cc: elcm@pacbell.net, squeak@create.ucsb.edu
Subject: oop (was: A possibly dumb question)
Hal Hildebrand wrote:
>
> Eliot,
>
> >BTW, is it true that "OOP" stands for "Ordinary Object Pointer"? If
> >not, what's oops' etymology?
>
> My understanding is that OOP stands for Object Oriented Pointer. Don't
> know where I picked it up from, but that's been my intepretation for years
> now.
>
> Hal
In page 252 of the Loom paper in the "green book" we read:
The identifier of an object is called an Oop, which stands
for "object pointer."
On page 192 we see that Berkeley oops were:
15 14 .............. 1 0
0 < object table index>
1 < small integer >
rather than the blue book's:
15 14 .............. 1 0
< object table index > 0
< small integer > 1
The reason for this was that small integers became all negative
and non referece counted oops (invalid Oop, nil, true and false)
now have values 0 to 3. A single signed comparison (x<4) could
eliminate them all in one, fast step.
-- Jecel
Loom paper = LOOM - Large Object Oriented Memory for Smalltalk-80
Systems
Ted Kaehler
Glenn Krasner
pages 251-271 of the green book
Berkeley Smalltalk: Who Knows Where the Time Goes?
David M. Ungar
David A. Patterson
pages 189-206 of the green book
green book = Smalltalk-80: Bits of History, Words of Advice
Gleen Krasner, editor
1983, Addison-Wesley
ISBN 0-201-11669-3
blue book = Smalltalk-80: The Language and Its Implementation
Adele Goldberg
David Robson
1983, Addison-Wesley
ISBN 0-201-11371-6
Date: 97 Jun 04 10:07:33 am
From: Ian Piumarta <piumarta@prof.inria.fr>
To: DanI@wdi.disney.com, elcm@pacbell.net
Cc: Squeak@create.ucsb.edu
Subject: Re: A possibly dumb question [Re: 2 problems]
> it could mean "Ordinary Object Pointer"
Is it the _object_ that's ordinary, or the _pointer_?
What, then, constitute[sd] a _special_ object (or pointer)?
And where can I go to get my poodle clipped in Burbank??? ;-)
Ian
Date: 97 Jun 04 12:33:24 pm
From: "Dwight Hughes" <dhughes@intellinet.com>
To: "Squeak" <squeak@create.ucsb.edu>
Subject: What does Squeak need?
Something I would like to see is everyone's opinions on
what Squeak most needs, or areas where you consider it
weakest, or where it has the most unrealized potential.
(Not including just making it somewhat faster without
greatly complicating it or greatly compromising portability
-- I think that is a given.)
I ask this because I would like to know where one might
most productively apply ones hacking time while potentially
benefiting Squeak as a whole.
BTW, I want to thank everyone for their patient and thoughtful
replies to my question about SmallInteger tags.
-- Dwight
Date: 97 Jun 04 1:02:42 pm
From: "David N. Smith" <dnsmith@watson.ibm.com>
To: "Dwight Hughes" <dhughes@intellinet.com>
Cc: "Squeak" <squeak@create.ucsb.edu>
In-Reply-To: <199706041959.OAA17506@sibyl.intellinet.com>
Subject: Re: What does Squeak need?
At 16:02 -0400 6/4/97, Dwight Hughes wrote:
>Something I would like to see is everyone's opinions on
>what Squeak most needs, or areas where you consider it
>weakest, or where it has the most unrealized potential.
>(Not including just making it somewhat faster without
>greatly complicating it or greatly compromising portability
>-- I think that is a given.)
>
>I ask this because I would like to know where one might
>most productively apply ones hacking time while potentially
>benefiting Squeak as a whole.
>
>BTW, I want to thank everyone for their patient and thoughtful
>replies to my question about SmallInteger tags.
>
>-- Dwight
Maybe this would be a good time to list what people are doing. I was about
to suggest a new garbage collector, but don't know if anyone is working on
one or if the mark-sweep collector is better for Squeak for some reason I
don't see offhand.
---
I, and several others, are slowly (and somewhat at random) going through
Number and its subclasses and looking for problems and places that need
improvement.
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.
Date: 97 Jun 04 1:29:58 pm
From: Joel Lucuik <Joel@ObjectPeople.com>
To: "Dwight Hughes" <dhughes@intellinet.com>
Cc: Squeak@create.ucsb.edu
Subject: Re: What does Squeak need?
Some Ideas (not sure how many are NEEDED):
- make a version to fit in 300K or so (very lite-incl. all allocated RAM).
- class loaders, to work like a plug-in for the web. (response to Java)
- Dictionary and Set equality testing options. (don't assume =)
- deepCopy done right (recursive, stopping at system objects such as
classes, special cased for collections)
- class/global stubs with demand-loading and delayed unloading (could work
with the class loaders mentioned before).
- simple method versioning (class versioning if you're ambitious).
I'll send more later......
Joel
At 03:02 PM 6/4/97 -0500, you wrote:
>Something I would like to see is everyone's opinions on
>what Squeak most needs, or areas where you consider it
>weakest, or where it has the most unrealized potential.
>(Not including just making it somewhat faster without
>greatly complicating it or greatly compromising portability
>-- I think that is a given.)
>
>I ask this because I would like to know where one might
>most productively apply ones hacking time while potentially
>benefiting Squeak as a whole.
>
>BTW, I want to thank everyone for their patient and thoughtful
>replies to my question about SmallInteger tags.
>
>-- Dwight
>
Date: 97 Jun 04 1:49:47 pm
From: gregory@eng.adaptec.com (Greg Gritton x2386)
To: squeak@create.ucsb.edu, dhughes@intellinet.com
Subject: Re: What does Squeak need?
Hi,
One area of improvement that would make Squeak more useful for real
applications is to better tie Squeak into native windowing systems.
At least in X-windows, all Squeak windows appear in one X-window.
It would be very useful if squeak could bring up separate X-windows.
Admittedly, this is a lot of work to add, particularly if compatibility
with X-windows, MAC, Microsoft Windows, etc., is added.
Perhaps Squeak could be tied into a portable windowing interface,
such as Tk, to simplify the process.
Greg Gritton
> From owner-squeak@create.ucsb.edu Wed Jun 4 13:55:36 1997
> From: "Dwight Hughes" <dhughes@intellinet.com>
> To: "Squeak" <squeak@create.ucsb.edu>
> Subject: What does Squeak need?
> Date: Wed, 4 Jun 1997 15:02:48 -0500
> X-Msmail-Priority: Normal
> X-Priority: 3
> X-Mailer: Microsoft Internet Mail 4.70.1161
> Mime-Version: 1.0
> Content-Type> : > text/plain> ; > charset=ISO-8859-1>
> Content-Transfer-Encoding: 7bit
> Sender: owner-squeak@create.ucsb.edu
> Content-Length: 580
>
> Something I would like to see is everyone's opinions on
> what Squeak most needs, or areas where you consider it
> weakest, or where it has the most unrealized potential.
> (Not including just making it somewhat faster without
> greatly complicating it or greatly compromising portability
> -- I think that is a given.)
>
> I ask this because I would like to know where one might
> most productively apply ones hacking time while potentially
> benefiting Squeak as a whole.
>
> BTW, I want to thank everyone for their patient and thoughtful
> replies to my question about SmallInteger tags.
>
> -- Dwight
>
Date: 97 Jun 04 2:22:37 pm
From: Sehyo Chang <sehyo@netcom.com>
To: squeak@create.ucsb.edu
Subject: Re: What does Squeak need?
A major improvement I like to see in Squeak is support for
Native windowing system and threads. However, in order to do
that we should have dll/c interface. Writing primitive code
seems to be inefficient.
I started writing 'ExternalLibrary' class library. It's purpose
is to load and unload DLL libraries such as Win32. However,
I haven't decided how to structure smalltalk-c interface. Any
ideas?
-- sehyo chang
>
>Maybe this would be a good time to list what people are doing. I was about
>to suggest a new garbage collector, but don't know if anyone is working on
>one or if the mark-sweep collector is better for Squeak for some reason I
>don't see offhand.
>
>---
>
>I, and several others, are slowly (and somewhat at random) going through
>Number and its subclasses and looking for problems and places that need
>improvement.
>
>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.
>
>
>
>
--------------------
Sehyo Chang
Virtual Enteprise Technology, inc.
sehyo@netcom.com
Date: 97 Jun 04 2:42:32 pm
From: oliver@fritz.co.traverse.com (Christopher Oliver)
To: dhughes@intellinet.com (Dwight Hughes)
Cc: squeak@create.ucsb.edu
In-Reply-To: <199706041959.OAA17506@sibyl.intellinet.com> from "Dwight Hughes" at Jun 4, 97 03:02:48 pm
Subject: Re: What does Squeak need?
> Something I would like to see is everyone's opinions on
> what Squeak most needs, or areas where you consider it
> weakest, or where it has the most unrealized potential.
Provide well documented simple mechanisms for integrating external
functionality into the VM. I.e. Squeak would benefit from a clear
foreign function interface.
Sincerely,
--
Christopher Oliver Traverse Communications
Systems Coordinator 223 Grandview Pkwy, Suite 108
oliver@traverse.com Traverse City, Michigan, 49684
"You can even make Emacs look just like vi -- but why?" - C. Musciano
Date: 97 Jun 04 3:57:35 pm
From: Chris Hanson <chanson@mcs.com>
To: squeak@create.ucsb.edu
In-Reply-To: <1.5.4.32.19970604114559.0093bb54@netcom18.netcom.com>
Subject: Re: What does Squeak need?
At 4:48 PM -0500 6/4/97, Sehyo Chang wrote:
>I started writing 'ExternalLibrary' class library. It's purpose
>is to load and unload DLL libraries such as Win32. However,
>I haven't decided how to structure smalltalk-c interface. Any
>ideas?
Look at what SmalltalkAgents does with its external code interface. I'm
not sure how to explain it, but it appears very natural to use.
(SmalltalkAgents is a wonderful environment; I've never done more than play
in it, though, since QKS has never actually finished it...)
Date: 97 Jun 04 8:44:24 pm
From: "Hal Hildebrand" <horus@pacbell.net>
To: "Squeak" <squeak@create.ucsb.edu>,
"Dwight Hughes" <dhughes@intellinet.com>
Subject: Re: What does Squeak need?
>Something I would like to see is everyone's opinions on
>what Squeak most needs, or areas where you consider it
>weakest, or where it has the most unrealized potential.
>(Not including just making it somewhat faster without
>greatly complicating it or greatly compromising portability
>-- I think that is a given.)
In my order of preference:
1) Namespaces (Absolute must)
2) Foreign Language Interface (Absolute must)
3) Faster Interpreter (target 70% of the speed of VW)
4) Smaller core (<300K is a good number) a headless squeak...
Hal
__
Time is when the day is like a play by Sartre
When it seems that book burning's in perfect order
http://www.hellblazer.com (Web)
mailto:hal@parcplace.com (Business)
mailto:horus@pacbell.net (Personal)
Date: 97 Jun 04 9:53:59 pm
From: "Hal Hildebrand" <horus@pacbell.net>
To: "Squeak mailing list" <squeak@create.ucsb.edu>
Subject: Squeak wish list
How could I have fogotten this one,
0) Proposed ANSI standard exceptions
And this one
5) ANSI compliant Squeak base package
__
Time is when the day is like a play by Sartre
When it seems that book burning's in perfect order
http://www.hellblazer.com (Web)
mailto:hal@parcplace.com (Business)
mailto:horus@pacbell.net (Personal)
Date: 97 Jun 04 11:06:06 pm
From: Ian Piumarta <piumarta@prof.inria.fr>
To: squeak@create.ucsb.edu
Subject: Re: What does Squeak need?
Squeakers,
> Admittedly, this is a lot of work to add, particularly if compatibility
> with X-windows, MAC, Microsoft Windows, etc., is added.
> Perhaps Squeak could be tied into a portable windowing interface,
> such as Tk, to simplify the process.
I already have the beginnings of this (a "SmallTk" framework and some
working tools, e.g. system browser) but have no time to pursue it at the
moment. If anyone is really serious about continuing the work, let me
know and I'll invest the (not insignificant) time needed to file it all
out and comment it enough that you can get started with it.
It was mostly an experiment, so I guess the whole lot would need to be
reworked to make something serious for Squeak. Part of the job *WOULD*
include hacking on the event dispatch mechanism in tcl/tk itself (three
times, once for each supported platform), to transfer some of the event
control (but not event gathering or dispatch, per se) into Squeak.
However, my opinion is that it would be far better to wait until Squeak
goes event driven (which has been on the cards for a long time) before
attempting this work, which would give a much more suitable starting
point. Otherwise you'd waste most of your time and energy trying to
arbitrate in the civil war between tcl/tk's violently intrinsic
event-driven model and Squeak's polling model.
What's rather neat about it is that with about 20 lines of "option"
configuration you can make the user interface look just about any way you
want it to. By default it's horrible and "klunky" -- but has a pure
Motif look and feel. Changing a few options and the interface is almost
indistinguishable from that of ParcPlace. (4.1, that is -- I dunno if
it's changed recently since "we academics" are way too poor to afford the
license. Sniff. ;)
> A major improvement I like to see in Squeak is support for
> Native windowing system and threads. However, in order to do
> that we should have dll/c interface. Writing primitive code
> seems to be inefficient.
Doing this portably is going to be tricky. Most versions of Unix support
one or both of:
- some randomly organised vendor-specific threads library;
- POSIX "standard" threads.
Only the second of these makes sense for a truly portable implementation.
(One day, if not already, MacOS, Windoze, and any other "serious" OS will
have to support POSIX threads -- so there is the potential for having a
single implementation for all the supported platforms.) Given that,
there are two further problems:
- "standard" earns the quotation marks: there are many different
implementations of POSIX threads out there, conforming to
different (subtly incompatible) drafts of the standard;
- POSIX threads are severely deficient from a Smalltalk point of
view. For example, implementing #suspend and #resume is *very*
difficult, and often requires knowledge of the internals of
the implementation for a particular platform. (E.g. under DEC
OSF/1 the POSIX threads are implemented over Mach threads, which
support [largely undocumented] calls to suspend/resume threads.)
Obviously this is non-portable, even between different versions
of the OS on the *same* platform!
I suspect Eliot could tell a horror story or two concerning native
threads...
> I started writing 'ExternalLibrary' class library. It's purpose
> is to load and unload DLL libraries such as Win32. However,
> I haven't decided how to structure smalltalk-c interface. Any
> ideas?
On the other hand, doing this portably could be much more
straightforward. Unix has the "dlopen" interface for manipulating
dynamic libraries. It's crude and simple, but it's one of the few things
which is almost identical in every flavour of Unix (and there's even a
highly portable GNU implementation, should a particular vendor "let us
down"). If you avoid any nifty features that might exist in Windoze for
handling DLLs (that have no counterparts in the dlopen library), then
making it work in all of the Unix ports will be trivial.
(The Mac I don't really know about -- the "programmers manual" is a
[full!] CD-ROM containing tens of huge "books" filled with obscure words
and acronyms that I can'y even begin to guess about. But I suspect
there's an equivalent to dlopen somewhere. In which case, add its
interface to the required intersection.)
In the light of all of the above, I'd like to propose "Item Zero" in the
list of things that Squeak needs (or maybe I should say, "things that
Squeak must never lose"):
0) portability.
Have a good day! (Mine started badly -- woke up *way* too early! ;-)
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 -----------------------
Date: 97 Jun 05 1:51:20 am
From: "Hal Hildebrand" <horus@pacbell.net>
To: <squeak@create.ucsb.edu>, "Ian Piumarta" <piumarta@prof.inria.fr>
Subject: Re: What does Squeak need?
Ian,
>In the light of all of the above, I'd like to propose "Item Zero" in the
>list of things that Squeak needs (or maybe I should say, "things that
>Squeak must never lose"):
>
>0) portability.
Agreed. However, one must clearly and concisely define what one means by
portability. Portability of the GUI can be defined in many different ways.
Portability of an ExternalInterface is easier to achieve than a portable
GUI that has the look and feel of the host GUI. By an order of magnitude,
at least.
VisualWorks has struggled with a portable GUI for years, and now Java is
struggling with the same issue. VisualAge has achieved a large measure of
a portable GUI with native look and feel. There are a great many libraries
for providing portable GUI's for other languages. It's interesting to
examine these examples, and glean what we can from the experiences. It's
also important to realize that many person centurys (millenia?) of hard
work have gone into solving this problem and it's questionable as to
whether we've managed to come up with an acceptable solution at all.
One possible definition of portability of the GUI is either the
intersection of of target host GUI's, or the union thereof. In the case of
the intersection, the result is the "lowest common denominator" widgets and
thingies GUI's have to offer. Choosing this definition of portability is
fairly easy to accomplish, but you end up with a very limited GUI -- one
that certainly won't meet the needs of application programmers, who require
the latest whiz bang control that is available on Windows or whatever the
platform may be.
Choosing the union of GUI capabilities ultimately requires a great deal of
emulation, and quite a bit of thought to the architecture. Host GUI's are
notoriously fussy, and their subtle differences can drive you nuts trying
to rectify and abstract. Blood sacrifices are often required.
One could take the current route of Squeak, and emulate everything, and
build the entire GUI in Squeak; perhaps updating the style, and creating an
entirely new GUI. This provides portability, but doesn't give you access
to the underlying host GUI controls that application programmers slobber
for.
Portability always means compromise. Some price must be paid. Engineering
is the art of compromise. What you can and can't live without. The art of
having your cake and eating it too.
I agree that we must strive to maintain portability, but if you bow too low
to any god, you lose sight of what your real goal is. The goals are
different for different people, and people make different tradeoffs.
Squeak is a tremendous opportunity to map out a new solution space, without
the high priesthood (or worse) of some comercial concern making the
engineering tradeoffs for us.
It'll be very interesting to see what Squeak ends up with, and how it
evolves.
Hal
__
Time is when the day is like a play by Sartre
When it seems that book burning's in perfect order
http://www.hellblazer.com (Web)
mailto:hal@parcplace.com (Business)
mailto:horus@pacbell.net (Personal)
Date: 97 Jun 05 9:22:22 am
From: Adam Bridge <abridge@wheel.dcn.davis.ca.us>
To: "Dan Ingalls" <DanI@wdi.disney.com>
Cc: <Squeak@create.ucsb.edu>
Subject: Moving Squeak
A few months ago I had considered moving Squeak to the BeOS but when
Apple announced the NeXT deal I thought that Rhapsody would make a better
target and quit working on the BeOS for the most part.
The Objective-C language looks like an interesting match with Squeak.
Now, I'm going to start working on the port. Are there instructions out
there or recommendations from Squeakers who have ported to other
platforms? I'd certainly like to hear from anyone who has moved to a new
platform.
Is there a test suite against which the installation can be verified
(besides running against itself, of course)?
I'll be moving to the Prelude to Rhapsody on a 200MHz pentium first and,
when the DR1 release hits the street, to the Mac.
If anyone else is contemplating this perhaps we could talk? If it's
someone from Apple I'll gladly defer to more experienced folks.
Thanks,
Adam Bridge
Date: 97 Jun 05 10:36:57 am
From: tim <tim@apple.com>
To: "Adam Bridge" <abridge@wheel.dcn.davis.ca.us>,
"Dan Ingalls" <DanI@wdi.disney.com>
Cc: <Squeak@create.ucsb.edu>
Subject: Re: Moving Squeak
Adam Bridge wrote:
>A few months ago I had considered moving Squeak to the BeOS but when
>Apple announced the NeXT deal I thought that Rhapsody would make a better
>target and quit working on the BeOS for the most part.
>
>The Objective-C language looks like an interesting match with Squeak.
Yes, Obj-C has borrowed a lot from the Smalltalk model.
>Now, I'm going to start working on the port. Are there instructions out
>there or recommendations from Squeakers who have ported to other
>platforms? I'd certainly like to hear from anyone who has moved to a new
>platform.
The biggest issue to moving onto OPENSTEP/Rhapsody will be interfacing
with the AppKit for the native window/view/mouse/cursor operations, and
resolving Squeak's "polling" design and event loop with the AppKit's [App
run] loop and Display Postscript's event-driven design. You should
probably start with Ian's UNIX port as a base.
-- tim
Date: 97 Jun 05 11:47:03 am
From: Sehyo Chang <sehyo@netcom.com>
To: squeak@create.ucsb.edu
Subject: Re: What does Squeak need?
>
>In the light of all of the above, I'd like to propose "Item Zero" in the
>list of things that Squeak needs (or maybe I should say, "things that
>Squeak must never lose"):
>
> 0) portability.
>
>
I think we should all strieve toward having portable Squeak. However,
we should'n sacrifice some functionality because not all features are
available in all platforms. We should make compromise when it is called
for. After all if squeak is experiment then we should first try to find
out what's is possible before making up our mind.
Given there is only 3 most used windowing standards Mac,Win95,Motif/CDE,
and they are very similar, we should be able to abstract out 90% of native
widgets.
For other 10%, we can provide hooks so they can use native widgets but
let them know it is non portable. We can probably migrate them to common
classes
once we have better idea how to incorporate them.
For threads, we should probably use WindowNT and Solaris as reference model,
since none of other OS has robust implementation as they do. We should provide
portable layer so you can always run on other platform but fixed the problem as
they come.
Important thing is let get Smalltalk modernized in look and feel. If Java camps
were able to do this then smalltalk should have at least those features.
-- sehyo chang
--------------------
Sehyo Chang
Virtual Enteprise Technology, inc.
sehyo@netcom.com
Date: 97 Jun 05 1:58:53 pm
From: Stefan Matthias Aust <sma@kiel.netsurf.de>
To: squeak@create.ucsb.edu
Subject: Re: What does Squeak need?
>In my order of preference:
>
>1) Namespaces (Absolute must)
I second this and would add the suggestion to use Squeak as platform to
search for other solution to fix some of the problems of Smalltalk in
contrast to other languages. Squeak would be a great testing platform for
new ideas, I think.
>2) Foreign Language Interface (Absolute must)
That's a "nice to have" in my eyes, but not the 1st priority. For me,
Smalltalk always seemed to be a little too autistic in its way of ignoring
the rest of the world, doing everything by its own and being very
self-centric (pun intended, even it's dificult in a foreign language :-).
The reason for this is of course very understandable based on Smalltalk's
history, but a modern Smalltalk should be open, should be different.
I wouldn't vote for a native window system. The somewhat funny reason is,
that VisualWorks users (and perhaps not-VisualWorks users even more) always
demanded native widgets. Sun's Java then showed how native widgets can be
done right (peer classes and abstract widget classes) but Java users now
demand emulated widgets. Perhaps people are never satisfied with the thing
they have... :)
Being a professional VW user, I've come to the oppinion that emulated
widgets have more advantages than disadvantages. It's very easy to modify or
add functionality to widgets or even create new widgets - if the frameworks
is written with this in mind. VW's framework has become very crowded and the
newer additions show a poor understanding of the whole framework (IMHO). But
Squeak has the chance with a new (perhaps easier) framework like Morphic to
become better here.
>3) Faster Interpreter (target 70% of the speed of VW)
Yes, of course, but I'd like to have true closures first. (As Ian explained,
they will also speed up execution a bit). I think, there're still areas of
possible improvements. Why, for example, is Squeak's VM a true stack machine?
Blair McGlashan told me that the VisualSmalltalk VM had a special tailored
instruction set which uses a few registers (I don't know for what, so I'd
suggest topOfStack and self) for speed. This might reduce the VM stack
access, which is very expensive as this means accessing global memory. A
better compiler could also do massive inlining. One effect would be a speed
up of do: loops and other enumerations.
>4) Smaller core (<300K is a good number) a headless squeak...
I think (to go back to 1.) Smalltalk needs to get modulerazible, built from
small components with have clearly defined interfaces. Smalltalk needs a
package concept. Currently, a classical image is one big (black) monolithic
block of objects. That's ideal for 1-man development but worse for
everything else.
And some more wishes to add:
1a) An even better Debugger. Perhaps debugging is the most important part
of developing in Smalltalk. Perhaps Smalltalk's debugger was once leading.
But other languages' IDEs catch up. I'd like to get true (conditional)
breakpoints (not only 'self halt'). I'd like to have these handly little
tooltip windows showing the current value of a variable. I'd like to step
in/over and _out of_ a method. I'd like to see the returned object before
leaving a method. I'd like to debug block closures easier, without carefully
sending through the implementation of #do:.
1b) An even better IDE. Smalltalk's typical IDE is perhaps still leading,
but products like for example VisualAge for Java are again catching up. I
have to admit, VA/Java really impressed me. It has a very functional, good
looking set of browsers which use all kinds of "modern" widgets like trees
and tabs. They are linked in a very logical way and support both browsing
and editing. Things, which are currently defacto-standard are syntax
hilighting (not very difficult in Smalltalk and helpful anyway (look at
Dolphin Smalltalk)), icons, trees and tooltips (I like the helpful tooltips
of Microsoft's new VB 5.0 very much - just type an object name and the
system opens a list of applicable methods - perhaps not easy to do in a
language without type-annotated variables), hyperlinks (why not document
everything in HTML?) and (hell, where did this sentence started?) support
for project based development.
6) I'd like to have an optional type system. No, I've no intention to start
a flame war "static vs. dynamic types" but sometimes, I think, it's useful
to have type annotation for documenting and for building and specifiying
components. It should be optional, not mandatory. Perhaps, something, you
add before delivering a component, after the first trial&error development
cycle. However this hypotetically type system shouldn't have no direct
relation to classes as this it much too restricting. A simple type checker
is easy build, however, one has to find a way to annotate types to methods,
parameters and variables.
Okay, I'll shut up now,
bye (and thank you for listening)
--
Stefan Matthias Aust // Planet Claire has pink air!
http://www.kiel.netsurf.de/users/s/sma/
Date: 97 Jun 05 4:58:43 pm
From: dave <drs@cs.wisc.edu>
To: squeak@create.ucsb.edu
Subject: Re: What does Squeak need?
Hal Hildebrand wrote:
>
> Ian,
>
> >In the light of all of the above, I'd like to propose "Item Zero" in the
> >list of things that Squeak needs (or maybe I should say, "things that
> >Squeak must never lose"):
> >
> >0) portability.
>
> Agreed. However, one must clearly and concisely define what one means by
> portability.
It's hard to believe you guys are talking about portability. In a system
that
a) does it's own bit blit b) handles it's own object space c) uses no
native
widgets I think full portability (as much as is rational) has been
achieved.
We're casually working between mac and windows. What more do you want?
;-)
I would like to strike a different chord and suggest what Squeak needs
is
not a proliferation of features or even more speed. Speed _almost_ seems
acceptible on my meager 66 MHz machine; so it must be fine on a 300 MHz
PowerPC.
No, what I want is to see the system specialized into a variety of uses.
For instance there might be a system devoted entirely to music, and one
devoted entirely to networking, and so on. What we have here is a
generalized
programming system, but without (if you will excuse the pun) a
programme.
(I.e., a rationale beyond itself). After all, originally smalltalk was
in every sense a programmatic attempt to construct an "interim
dynabook,"
sort of an interactive notebook. The software concepts all came out of a
particular domain having to do with the humanization of computation.
Then, at a slightly later stage, the problem domain shifted, from
discovering
_how_ to create a dynabook to figuring out how to _sell_ the system,
make it into a commercial product which could be applied in a commercial
situation. Nothing wrong with that. Still, these are different domains.
I hope everyone agrees that a commerical product has to solve different
types of problems than a free, experimental one.
So to my mind,
>1) Namespaces (Absolute must)
>2) Foreign Language Interface (Absolute must)
>3) Faster Interpreter (target 70% of the speed of VW)
>4) Smaller core (<300K is a good number) a headless squeak...
1) When namespaces were first presented as an addition to the C++
standard,
Stroustrup said they could be implemented in "a few hours." However,
years
later, namespaces are partially implemented and few know how to use
them.
My solution (differentiating systems) solves this problem inherently.
2) Ditto. This is properly an example of a differentiation rather than
a feature. As
I said, in the effort to placate an international customer base, a com-
mercial implementation needs this; but a free experimental one doesn't.
Instead of language _support_ what we need are distinct versions, or,
better, the ability to generate distinct versions in an easy way. A
kit smalltalk. Roll your own. I think this is the key.
3) I'd rather buy a bigger machine.
4) Yes, yes, yes...
-----------------------------
dave
Date: 97 Jun 05 6:09:58 pm
From: Les Tyrrell <tyrrell@avalanche.ncsa.uiuc.edu>
To: squeak@create.ucsb.edu
Cc: tyrrell@csl.ncsa.uiuc.edu
Subject: Re: What does Squeak need?
Early last December Dan Ingalls asked the question, "How are we doing?".
This was pretty much along the same lines as the question, "What does Squeak need?",
so I am posting slightly revised parts of my previous reply to Dan. It's a bit
longish...
You will see that there is a bit of ANGST involved- much of which is alleviated by the
knowledge that Squeak represents the opportunity to change some of this, without
having to start from scratch. Also, you may find some of my ideas a bit radical.
That's ok with me!
-------------BEGIN----------------
Since I've had only a little time to work with Squeak, I am directing most of my comments
towards Smalltalk in general, with the understanding that these are things I am willing to
go to a great deal of effort to change to make them better, and it is great to have
something like Squeak on which to experiment.
> What do you like best about Squeak?
> Openness, maleability/portability because of being written mostly in itself, something else?
"Openness" is a big plus as well as a big problem... see below. But I do want this.
> What do you like least about Squeak?
> Performance, support, bugs, something else?
"Performance" would be the most troublesome problem- My impression is that there is a need
to simultaneously support both "slow but platform-independent" while simultaneously allowing
"fast but highly coupled to a particular target platform", probably within the same image.
"Bugs" are a symptom. I feel that Smalltalk suffers from a problem wherein every new
"package" you might want to add to your system is not content to simply provide new
classes- in almost every case it seems that the base classes are also modified in some
way. Personally, I see this as a BIG problem. Some means needs to be found wherein
new subsystems can be brought into an image, and run, WITHOUT having any possible
impact on any other subsystems, now or in the future. I feel that this is CRITICAL.
To this I will add the issue of "Security". I feel that this will become, in the very near future,
a BIG problem. In particular, I can envision a world in which there are all these Squeak
machines out there, interconnected to each other in a web of thier own, each having thier
own persistent object storage. Each could then act as thier own server for a Squeak site
( like a web site, but who knows what it could be... ). You could have objects migrating
from machine to machine ( plenty of research has been done, so this is a "given" potential ).
Something needs to be done so that objects and subsystems can migrate in a secure manner.
Smalltalk, especially a completely open Smalltalk like Squeak, would seem to make this a bit of
a challenge- how do you maintain the security and integrity of a package that is migrated or
copied to another Smalltalk system ( that is, how can you use that package in another system,
while simultaneously insuring that under no circumstances can that package EVER be opened,
exposing its internals to a programmer. And how do you insure that under no circumstances
could that package be used as a virus? )
> For what do you mainly use Squeak?
> Teaching, recreational programming, big business, adventure games, rocket design, something else?
I have an interest in understanding more about the very large scale collaborative development
of very large, complex systems. So Squeak is an interesting case for that. I also hope to be
able to try some things out, building and deploying tools and environments for Smalltalk
( and Squeak ). As for rocket design... I AM a "rocket scientist" ( Aerospace Engineer, actually )
by training, so why not. Actually, I would like to see Smalltalk make more inroads into the
Engineering communtities. This means that I would like to see Smalltalk be both highly adaptable
AND fast. I want it ALL! I don't require that a particular system be both, AT THE SAME TIME.
It is good enough if it is highly malleable during development, and VERY FAST after "deployment".
I would like it to be done in a manner where a single environment supported both modes
simultaneously, or more correctly stated, that "very fast" and "very malleable" systems could
co-exist simultaneously in the same enviroment, interacting with each other seamlessly.
Perhaps along those lines, as an example consider the way that Squeak currently has a
description of it's own Interpreter and BitBlt written in a Smalltalk dialect. Suppose
that these were instead some system that I wanted to think about in Smalltalk-like
terms, but wanted to have speed as well. Currently, it appears that the procedure is
to translate that system along with other VM stuff to C using the built-in translator,
and then compile the C code to construct a new VM. Instead, I would like to just
sort of point at the system and say "make this fast", with the new "fast" version
simply being installed into the existing VM. I have no idea how this would be done,
but that is the way I'd like it to work. I'd also like the option of pointing to a "fast"
system and saying, "that's ok, it doesn't have to be fast anymore" and have that
system revert back to the normal Smalltalk way of life.
But I'd still want the option of building the VM as it is done now in Squeak.
> What direction(s) would you most like to see Squeak go?
> Higher performance, pluggable host UIF, dynamite game machine kernel,
> multimedia playground, something else?
All of these are of interest- for instance, the game machine and multimedia directions would
provide stresses that should force some of the improvements I'm after. I am working on
UI stuff, since my Master's thesis involves a highly interactive environment which I would
like to be able to port painlessly to all existing Smalltalk systems.
But as for what I have had in mind...
1) N DAMMIT!!!
This is a way of expressing my frustration that Smalltalk, while highly malleable and very
expressive, appears to suffer from its origins as a SINGLE-user environment, sitting
on a SINGLE machine, intended to be a highly personalized system ( this is my impression,
anyway ). I really like the idea of highly-personalized computation environments- the big
problems come when we try to share "packages" ( for lack of a better term ) as these
personalizations get in the way- so some means needs to be found to allow the peaceful
co-existence of these things. I have already seen this as a big problem while working for
a company that was using several different third-party products, in several different combinations,
for several different project teams. We really need to clean this up.
Another issue is that I want to see a world in which the SINGLE monolithic image is no longer
the norm - I want to be able to swap "packages" in and out at will, with no ill effects. I want
to be able to totally, radically, _completely_ change the character of my enviroment, quickly,
and with no ill effects, without "leaving" that environment.
I would like to see a world in which there are all these Squeak machines lying around, all capable
of seamlessly communicating with each other, each forming part of a world-wide distributed
object computation and information system. I don't see this being a great problem, but for
the pervasive "singularity"-ness of existing Smalltalk systems- my impression is that the
system is strongly oriented towards the single, isolated environment for a single user.
I would like to see it become a system in which this is still "apparently" the case- but which
then allows the seamless integration of components from other environments all over the world.
It could then become both a distributed information system ( as in the WWW ) as well as a
distributed, massively parrellel ( if so desired ) computation system ( perhaps like Legion ).
For that, it would be useful to allow both very fast, and very malleable components in the
same environment at the same time.
Another issue with the single monolithic image is that in 1980, that image could easily be as
large as all available storage space. I don't think this is a very likely thing anymore, since
disks are very huge compared to 1980 while the images are not much larger. And now,
we can factor in an entire world's worth of disk space, which I seriously doubt will ever
be consumed by a single image. So I would like to see a scheme in which individual
environments can easily fragment and coalesce, with these fragments being globally
( in the REAL global sense ) shareable with other environments.
> We find it hard to take full advantage of contributions to Squeak from the
> larger community. This is partly because we simply don't have time to try
> everything out. Please list your "Top N" recommendations for inclusion in
> future Squeak releases. [Rate as 10=really good/got to have it, down to
> 0=a real mistake to include it]. Giving reasons always helps (smaller,
> faster, does more)
I am more inclined to believe that rather than try to "control" the evolution of the baseline
Squeak system perhaps the best approach is to try to evolve Squeak into an environment
in which a vast multitude can make significant contributions in a safe manner. That is, rather
than influence Squeak's evolution directly, instead influence the framework within which
Squeak evolves. Things of this nature could include putting information such as
Squeak architectural descriptions, or information about how to port Squeak on the WWW.
It would also help if Squeak's development environment were more supportive of large
scale collaborative development ( I have an interest in this, and am working on
this sort of thing ).
In terms of process, I would like to see Squeak become a model of highly effective, very large
scale collaborative development. Lots of research has been done on this sort of thing, but
my impression is that little of this seems to have made its way into the Smalltalk community.
Again, I would guess that the "SINGLE" orientation is the culprit, as large-scale team
development requires much different support than a single-user system.
I feel there will be many variants of Squeak, some which will survive and
others that will not. Let the "market" decide, let each find its own niche.
> Similarly there is some decent code in the Smalltalk Archive at UIUC.
> Would you strongly advocate the inclusion of any of these in future Squeak
> releases? Again, please list with you rating.
>
> Any other things you would like to say?
This is 1996, going on 1997, and not 1980. Let's look towards 2001 and beyond. A lot
has been learned since 1980- lets make use of that knowledge, while also preserving the
heritage of Smalltalk-80. Allow the next-generation Squeak to be many things,
simultaneously, to many people, simultaneously.
> Who would like to build a simple high-preformance VM for Squeak?
> Is there any way we can help?
Perhaps "patterns" or any other means of transferring the expertise of the intracacies and
pitfalls of building high-performance VMs. I feel that we do need these, and hope that
there are ways that we can make this as painless as possible ( ie, the development environment
should directly support such knowledge-transfer efforts ).
> Upcoming releases, for your info:
> We are working internally on 1.18 to be released around 12/15. It will
> feature:
> Fixes to formatter, simulator and a few other things
Make the "formatter" configurable, and separate it from the objects which are generating
the bytecodes. For that matter, how difficult would it be to separate the objects which are
generating the bytecodes from the objects which represent the parse tree? Parse trees
have many uses, of which bytecode generation is only one.
> We hope to have another release by the end of the year, with the focus being:
> Sockets
YES!
> Anything else you would contribute if we could help you do it?
Starting in January, I hope to spend more time on a user-interface framework that is meant
to make minimal use of existing Smalltalk classes in order to suport a direct-manipulation
OOUI. This may or may not have much merit, but it is something that I want for my own
use anyway. The goal is to provide an environment that I can migrate easily between all
existing dialects of Smalltalk.
I am also working on software development and refactoring tools which will ultimately make
use of that environment, so that these will be vendor-independent to the greatest extent
possible. I'm hoping that these will be a step towards the tools needed for the construction
and refactoring of very large Smalltalk systems.
> Thanks for your time.
> - Dan, for the Squeak Team
>
Thanks for the opportunities!
Les Tyrrell
tyrrell@csl.ncsa.uiuc.edu http://ispace.ncsa.uiuc.edu/~tyrrell/
------------------END--------------------
The last bits about the OOUI and development tools still holds- the most progress
has been made with the development tools, since these have the potential to be
useful in later stages of addressing my concerns. Part of that effort has been directed
towards providing "Modules". I currently use them to detect just the sort of problems
I hint at above- ie, what is this "package" going to try to do to my precious image,
BEFORE it does it? So the modules are coming along nicely, and will be an important
part of the development tools I'm working on. I also have some preliminary
( ie, it's in my head and I need to write it down ) ideas about supporting the design stage of
a development effort, but until I actually write them down and make them a bit less abstract
there really isn't much to be said about that.
The OOUI stuff also is progressing, not at the rate I'd like, but starting to shape up.
Nothing that can be drawn on a screen, but other infrastructure things are looking promising.
I'm actually developing in VisualWorks, but I try to keep it vendor-independent
to ease porting to other Smalltalk platforms ( especially Squeak ).
Oh yeah, and finally Squeak needs a new name- something like "Velociraptor" ;^)
Let's not be modest! After all, who knows what power can be found in hype?
( BTW, "Pinhead" would be a lousy name... so let's not consider using it ).
Les
Closing thought: Smalltalk ( and Squeak ) is an environment, not just a language.
There is no need to constrain our thoughts about what we could do with this.
Date: 97 Jun 05 6:11:20 pm
From: oliver@fritz.co.traverse.com (Christopher Oliver)
To: squeak@create.ucsb.edu
Subject: Re: What does Squeak need?
Dave wrote:
> 2) Ditto. This is properly an example of a differentiation rather than
> a feature. As
> I said, in the effort to placate an international customer base, a com-
> mercial implementation needs this; but a free experimental one doesn't.
> Instead of language _support_ what we need are distinct versions, or,
> better, the ability to generate distinct versions in an easy way. A
> kit smalltalk. Roll your own. I think this is the key.
It seems you are saying that Squeak's sole audience should be VM hackers,
or to put it another way, Squeak has no obligation to be a good tool.
I think application writers, some of whom aren't commercial, are a worthy
audience even if they don't hack VMs. Don't slap them if the face!
There are a lot of nice free libraries (consider the new transaction
protected Berkeley DB) which would be nice to integrate without being
a VM guru. Virtually all of the Lisps and Schemes I work with allow
me to trivially hang C code on the side, and hence not only are they
fun to code in, they are useful tools as well. Let's not forget that a
nice toy can also be a great tool.
Sincerely,
--
Christopher Oliver Traverse Communications
Systems Coordinator 223 Grandview Pkwy, Suite 108
oliver@traverse.com Traverse City, Michigan, 49684
"You can even make Emacs look just like vi -- but why?" - C. Musciano
Date: 97 Jun 06 5:16:57 am
From: "Andreas Raab" <raab@isg.cs.uni-magdeburg.de>
To: oliver@fritz.co.traverse.com (Christopher Oliver)
Cc: squeak@create.ucsb.edu
Subject: Re: What does Squeak need?
> Dave wrote:
> > 2) Ditto. This is properly an example of a differentiation rather than
> > a feature. As
> > I said, in the effort to placate an international customer base, a com-
> > mercial implementation needs this; but a free experimental one doesn't.
> > Instead of language _support_ what we need are distinct versions, or,
> > better, the ability to generate distinct versions in an easy way. A
> > kit smalltalk. Roll your own. I think this is the key.
Oliver replied:
> It seems you are saying that Squeak's sole audience should be VM hackers,
> or to put it another way, Squeak has no obligation to be a good tool.
> I think application writers, some of whom aren't commercial, are a worthy
> audience even if they don't hack VMs. Don't slap them if the face!
> There are a lot of nice free libraries (consider the new transaction
> protected Berkeley DB) which would be nice to integrate without being
> a VM guru. Virtually all of the Lisps and Schemes I work with allow
> me to trivially hang C code on the side, and hence not only are they
> fun to code in, they are useful tools as well. Let's not forget that a
> nice toy can also be a great tool.
I agree with both of you. "Rolling your own Smalltalk" is a great
idea - but only usable by VM hackers. But instead of requiring that
everything we wish to integrate has to be brought down into the VM we
should also incorporate language support. And, by the way, is it
really that difficult?! Given a properly designed interfacing
mechanism it shouldn't be a big deal to build a language specific
front end. Any opinions?
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 >=============+
Date: 97 Jun 06 5:58:13 am
From: jecel@lsi.usp.br (Jecel Mattos de Assumpcao Jr.)
To: squeak@create.ucsb.edu
Subject: Re: What does Squeak need?
Some people wish for native GUI components and foreign language
interfaces. These are good suggestions, but let's not forget
that there is Smalltalk Express that already does both these
things. Sure, a single system that does everything would be
nice, but in the mean time Squeak should seek its own unique
strong points.
-- Jecel
Date: 97 Jun 06 6:38:43 am
From: "Hal Hildebrand" <horus@pacbell.net>
To: <squeak@create.ucsb.edu>
Subject: Re: What does Squeak need?
From: dave <drs@cs.wisc.edu>
>It's hard to believe you guys are talking about portability. In a system
>that
>a) does it's own bit blit b) handles it's own object space c) uses no
>native
>widgets I think full portability (as much as is rational) has been
>achieved.
>We're casually working between mac and windows. What more do you want?
>;-)
Agreed. But, this is why I've ported the Squeak interpreter to VW. It's a
20 year old interface. Quaint, but I do believe we've managed to learn
something useful in the intervening time period.
It's more of a discussion than an argument. It's bound to happen sooner or
later, as the GUI is where the user interacts with the system, and
developers are one of the biggest users of the system.
>I would like to strike a different chord and suggest what Squeak needs
>is
>not a proliferation of features or even more speed. Speed _almost_ seems
>acceptible on my meager 66 MHz machine; so it must be fine on a 300 MHz
>PowerPC.
I guess we have a different acceptance threshold. It really depends on
what you're doing as to whether you find it acceptable or not. I find it
amazing that it works as fast as it does, and that's pretty cool. However,
for anything I'd like to actually do with it, it's speed is too slow.
As I said, it's a matter of personal preference, which is why Squeak is
cool. No one is dictating anything here. It's just opinions. If you
don't agree, then not much is forced upon one.
>No, what I want is to see the system specialized into a variety of uses.
I whole heartedly agree with that statement.
>I hope everyone agrees that a commerical product has to solve different
>types of problems than a free, experimental one.
This is an excellent point.
>1) When namespaces were first presented as an addition to the C++
>standard,
>Stroustrup said they could be implemented in "a few hours." However,
>years
>later, namespaces are partially implemented and few know how to use
>them.
>My solution (differentiating systems) solves this problem inherently.
Not really. IBM's VisualAge 4.0 already has namespaces, VW will have
namespaces in the next release. It really isn't a big deal in ST.
Comparing difficulties in ST to C++ is a bit alien in my book... Java
already has namespaces. They are incredibly useful. If you don't have
them, you get into nasty integration clashes, and it sucks up a lot of time
just dealing with them.
>2) Ditto. This is properly an example of a differentiation rather than
>a feature. As
>I said, in the effort to placate an international customer base, a com-
>mercial implementation needs this; but a free experimental one doesn't.
>Instead of language _support_ what we need are distinct versions, or,
>better, the ability to generate distinct versions in an easy way. A
>kit smalltalk. Roll your own. I think this is the key.
I think I didn't make my self clear here. Sorry about that. What I'm
talking about is the interface to other computer languages. The equivalent
to DLL&C connect in VisualWorks.
>3) I'd rather buy a bigger machine.
I'd rather make better use of my own. However, I can see your point.
>4) Yes, yes, yes...
It's definitely needed to make your idea of "specialization into a variety
of uses"
Anyways, thanks for commenting.
Hal
__
Time is when the day is like a play by Sartre
When it seems that book burning's in perfect order
http://www.hellblazer.com (Web)
mailto:hal@parcplace.com (Business)
mailto:horus@pacbell.net (Personal)
Date: 97 Jun 06 6:46:39 am
From: "Hal Hildebrand" <horus@pacbell.net>
To: "Squeak mailing list" <squeak@create.ucsb.edu>
Subject: Re: What does Squeak need?
All,
My point
>2) Foreign Language Interface (Absolute must)
Is supposed to be the equivalent to DLL&C connect. Not an internationalizat
ion feature. Sorry for the confusion...
Hal
__
Time is when the day is like a play by Sartre
When it seems that book burning's in perfect order
http://www.hellblazer.com (Web)
mailto:hal@parcplace.com (Business)
mailto:horus@pacbell.net (Personal)
Date: 97 Jun 06 6:51:54 am
From: Joel Lucuik <Joel@ObjectPeople.com>
To: jecel@lsi.usp.br (Jecel Mattos de Assumpcao Jr.)
Cc: Squeak@create.ucsb.edu
Subject: Re: What does Squeak need?
I'm not sure what everyone else meant by foreign language interfaces.
I think integrating a C/C++ compiler into the squeak environment
would be useful.
Actually viewing the code of a C/C++ Component within Squeak and talking
to it using an extended syntax:
Person>>printName
<<aCNamePrinter printName: 'myName' asParameter>>
CNamePrinter>>(void) printName: char *name
{
printLn( name );
return();
}
This may get complex in the VM, but I'm not a VM Guru. I would
hope that this <<...>> syntax could be treated similar to a primitive.
The debugger probably couldn't handle it, or you'd have to launch a C debugger
or something gross like that.
Joel
At 10:24 AM 6/6/97 -0300, you wrote:
>Some people wish for native GUI components and foreign language
>interfaces. These are good suggestions, but let's not forget
>that there is Smalltalk Express that already does both these
>things. Sure, a single system that does everything would be
>nice, but in the mean time Squeak should seek its own unique
>strong points.
>
>-- Jecel
>
Date: 97 Jun 06 7:54:38 am
From: "William A. Barnett-Lewis" <wlewis@mailbag.com>
To: squeak@create.ucsb.edu
Subject: Re: What does Squeak need?
While I really enjoy futzing with a "classic" st-80, if someone wanted to
explain (pointers to papers, etc) how to implement Lisp in smalltalk, I'd be
game to give it a try as an additional personality for squeak.
Two reasons: 1) that's my all time fav language & 2) the neat symbolism of
it; after all st-72 started off written in Lisp ;>
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
-------------------------------------------------------------------------
Date: 97 Jun 06 8:04:40 am
From: "William A. Barnett-Lewis" <wlewis@mailbag.com>
To: <squeak@create.ucsb.edu>
Subject: Re: What does Squeak need?
>Date: Fri, 06 Jun 1997 10:27:56 -0500
>To: "Hal Hildebrand" <horus@pacbell.net>
>From: "William A. Barnett-Lewis" <wlewis@mailbag.com>
>Subject: Re: What does Squeak need?
>
>At 07:01 AM 6/6/97 -0700, you wrote:
>(snip)
>>Agreed. But, this is why I've ported the Squeak interpreter to VW. It's a
>>20 year old interface. Quaint, but I do believe we've managed to learn
>>something useful in the intervening time period.
>>
>>It's more of a discussion than an argument. It's bound to happen sooner or
>>later, as the GUI is where the user interacts with the system, and
>>developers are one of the biggest users of the system.
>
>Well, that's the theory... yet I find when I teach someone who's never used
a GUI before, the old Interlisp/Genera/SmallTalk GUI's are still easier for
them to begin using. The only advances in ease seem to have been made by
Apple in the origional Mac & that was at the price of sacrificing power.
Maybe there are better interfaces out there & I haven't been exposed to them?
>
>Just another personal opinion, but I'd be happier if drastic changes to the
squeak gui either didn't happen or were optional.
>
>(snip)
>>Hal
>>__
>>Time is when the day is like a play by Sartre
>>When it seems that book burning's in perfect order
>>http://www.hellblazer.com (Web)
>>mailto:hal@parcplace.com (Business)
>>mailto:horus@pacbell.net (Personal)
>
>William
Arghhh...after 20 years, you'd think I could run an e-mail program well
enough to send the message to the list rather than just to who I am
responding to...
Sheepishly,
Willia,
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
-------------------------------------------------------------------------
Date: 97 Jun 06 8:35:09 am
From: Ian Piumarta <piumarta@prof.inria.fr>
To: wlewis@mailbag.com
Cc: squeak@create.ucsb.edu
Subject: Making Smalltalk with a Lisp
William,
> if someone wanted to explain (pointers to papers, etc) how to implement Lisp
> in smalltalk, I'd be game to give it a try as an additional personality for
> squeak.
I did this for ObjectWorks a few years back. Look in
ftp://st.cs.uiuc.edu/pub/Smalltalk/MANCHESTER/manchester/4.1/lisp/
There's a "doc" subdirectory which contains DVI and postscript versions of a
paper, which I still haven't finished, on the techniques of embedding functional
languages in Smalltalk.
The performance was reasonable -- some programs even ran faster in Lisp than
their equivalent Smalltalk counterparts. (I think this isn't true any more: I
vaguely recall mentioning it to Eliot a long time ago and he tracked down and
"fixed" the bits in VW which were causing the performance discrepancies! ;-)
Porting it to Squeak should be easy, as long as you're familiar with the UI
components in both ParcPlace Smalltalk and Squeak. Stefan Matthias Aust has
ported it to VW2.5, if that's any help.
I started work on another version, which had support for variable numbers of
arguments and the like, but never finished it. If you're interested in the
techniques then I'd be happy to file-out and send you the relevant subclasses of
BlockContext. ;)
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 -----------------------
Date: 97 Jun 06 9:09:30 am
From: "Dwight Hughes" <dhughes@intellinet.com>
To: <squeak@create.ucsb.edu>, "William A. Barnett-Lewis" <wlewis@mailbag.com>
Subject: Re: What does Squeak need?
| From: William A. Barnett-Lewis <wlewis@mailbag.com>
|
| While I really enjoy futzing with a "classic" st-80, if someone wanted to
| explain (pointers to papers, etc) how to implement Lisp in smalltalk, I'd
be
| game to give it a try as an additional personality for squeak.
|
| Two reasons: 1) that's my all time fav language & 2) the neat symbolism
of
| it; after all st-72 started off written in Lisp ;>
|
| William
I don't know about papers, but there is source code for several varieties
of Lisp at:
ftp://st.cs.uiuc.edu/pub/Smalltalk/MANCHESTER/manchester/4.1/lisp/
It's for PP4.1, but should be useful.
-- Dwight
Date: 97 Jun 06 9:30:58 am
From: jecel@lsi.usp.br (Jecel Mattos de Assumpcao Jr.)
To: Joel@ObjectPeople.com
Cc: Squeak@create.ucsb.edu
Subject: Re: What does Squeak need?
What you want is already available in Smalltalk X (not
the freeware version, though). It isn't as easy to
use as you would like.
On the other hand, if you don't mind recompiling the whole
virtual machine and restarting you already have this in
Squeak as well - look at how the interpreter classes incluid
bits of C here and there...
> I'm not sure what everyone else meant by foreign language interfaces.
> I think integrating a C/C++ compiler into the squeak environment
> would be useful.
>
> Actually viewing the code of a C/C++ Component within Squeak and talking
> to it using an extended syntax:
>
> Person>>printName
> <<aCNamePrinter printName: 'myName' asParameter>>
>
> CNamePrinter>>(void) printName: char *name
> {
> printLn( name );
> return();
> }
>
> This may get complex in the VM, but I'm not a VM Guru. I would
> hope that this <<...>> syntax could be treated similar to a primitive.
>
> The debugger probably couldn't handle it, or you'd have to launch a C debugger
> or something gross like that.
>
> Joel
Date: 97 Jun 06 9:40:48 am
From: jecel@lsi.usp.br (Jecel Mattos de Assumpcao Jr.)
To: squeak@create.ucsb.edu, wlewis@mailbag.com
Subject: Re: What does Squeak need?
> While I really enjoy futzing with a "classic" st-80, if someone wanted to
> explain (pointers to papers, etc) how to implement Lisp in smalltalk, I'd be
> game to give it a try as an additional personality for squeak.
>
> Two reasons: 1) that's my all time fav language & 2) the neat symbolism of
> it; after all st-72 started off written in Lisp ;>
>
> William
> William A. Barnett-Lewis
> wlewis@mailbag.com
Lisp used to be my favorite language too, before I learned
Smalltalk some 15 years ago.
I think that the first Smalltalk was written in Basic (Dan?).
It has a very Lisp-like syntax (with a bit of Logo thrown in
(you might have noticed that parenthesis don't bother me)).
All the examples I ever saw of Smalltalk-72 in various
papers involved the infamous CONS cell...
-- Jecel
Date: 97 Jun 06 10:16:27 am
From: "William A. Barnett-Lewis" <wlewis@mailbag.com>
To: Ian Piumarta <piumarta@prof.inria.fr>
Cc: squeak@create.ucsb.edu
Subject: Re: Making Smalltalk with a Lisp
At 06:00 PM 6/6/97 +0200, you wrote:
>William,
(Snip)
>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 -----------------------
Ian,
Thank you very much for the pointer. There's a lot of "stuff" there that'll
keep me happily busy for awhile. I'm not, yet?, as familier w/ smalltalk as
I probably should be to try something like this...Oh, well, nothing new there.
Still, knowing this was done once & that it work is half the battle in itself.
Thanks again.
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
-------------------------------------------------------------------------
Date: 97 Jun 06 11:05:30 am
From: Tim Rowledge <rowledge@interval.com>
To: Hal Hildebrand <horus@pacbell.net>
Cc: Squeak mailing list <squeak@create.ucsb.edu>
In-Reply-To: <199706061412.HAA16296@mail-gw3.pacbell.net>
Subject: Re: What does Squeak need?
On Fri 06 Jun, Hal Hildebrand wrote:
> All,
>
> My point
>
> >2) Foreign Language Interface (Absolute must)
>
> Is supposed to be the equivalent to DLL&C connect. Not an internationalizat
> ion feature. Sorry for the confusion...
For a really, really, minimal version of this, grab http://sumeru.stanford.EDU/tim/pooters/SqFiles/deltas/sqRPCWindo.c and http://sumeru.stanford.EDU/tim/pooters/SqFiles/deltas/syscallST.st and look for ioSystemCall. It's loosely based on
the system call in eliot's BHH VM, which is in turn loosely based on Tek's Smalltalk, which in turn is probably based on something else.
Obviously it's intended for my Acorn RiscOS port, but it might give you a legup too something more sophisticated; or at least show you what you want to avoid!
Somebody else can worry about parsing .h files......
tim
--
Tim Rowledge: rowledge@interval.com (w) +1 (415) 856-7230 (w)
tim@sumeru.stanford.edu (h) <http://sumeru.stanford.edu/tim>
Date: 97 Jun 06 1:37:50 pm
From: Sam Adams <ssadams@us.ibm.com>
To: <squeak@create.ucsb.edu>
Subject: Re: What does Squeak need?
Dwight wrote:
>
> Something I would like to see is everyone's opinions on
> what Squeak most needs, or areas where you consider it
> weakest, or where it has the most unrealized potential.
> (Not including just making it somewhat faster without
> greatly complicating it or greatly compromising portability
> -- I think that is a given.)
>
> I ask this because I would like to know where one might
> most productively apply ones hacking time while potentially
> benefiting Squeak as a whole.
Greg Gritton wrote:
>One area of improvement that would make Squeak more useful for real
>applications is to better tie Squeak into native windowing systems.
>At least in X-windows, all Squeak windows appear in one X-window.
>It would be very useful if squeak could bring up separate X-windows.
>Admittedly, this is a lot of work to add, particularly if compatibility
>with X-windows, MAC, Microsoft Windows, etc., is added.
>Perhaps Squeak could be tied into a portable windowing interface,
>such as Tk, to simplify the process.
Here's an idea for a relatively simple way for Squeak to handle multiple host
windows. Allow for multiple DisplayScreen instances mapped to OS windows.
Each child window could have its own DisplayScreen or could be mapped from a
common DisplayScreen. This is not too different than the way projects feel. I
doesn't get you native look and feel, but I think the price of that is too high
if it means losing easy programmer control of the bitmaps and views. This idea
might produce some interesting UIs, like MVC views or Morphic worlds managed 1
per OS window.
Regards,
Sam
Date: 97 Jun 06 2:00:43 pm
From: Sam Adams <ssadams@us.ibm.com>
To: <squeak@create.ucsb.edu>
Subject: Project Goodie
Squeakers,
Here's a little goodie that really jazzes up those dull looking Project
windows. It provides a thumbnail graphic of the project desktop, including
any graphics written to DisplayScreen. Love that scaling with smoothing for
color bitmaps!
I've tried this on 1.19 and it works. Support methods include some additions
to Form and its metaclass to support depth control and a set of shrinkBy
methods.
Enjoy,
Sam
'From Squeak 1.16 of October 17, 1996 on 6 June 1997 at 4:05:26 pm'!
Model subclass: #Project
instanceVariableNames: 'projectWindows projectChangeSet projectTranscript
projectHolder displayDepth desktop '
classVariableNames: 'CurrentProject '
poolDictionaries: ''
category: 'Interface-Projects'!
!Form methodsFor: 'scaling, rotation'!
shrink: aRectangle by: scale smoothing: cellSize
"2/19/97 ssa added for shrinkBy support"
^ self magnify: aRectangle by: 1.0/scale smoothing: cellSize!
shrinkBy: scale
"2/19/97 ssa - added for compatibility."
"(Form fromUser shrinkBy: 2) display"
^self shrink: self boundingBox by: scale
!
shrinkBy: scale smoothing: cellSize
"2/19/97 ssa - added for compatibility."
"(Form fromUser shrinkBy: 2 smoothing: 3) display"
^self shrink: self boundingBox by: scale smoothing: cellSize
! !
!Form class methodsFor: 'instance creation'!
extent: extentPoint offset: offsetPoint depth: anInteger
"Answer an instance of me with a blank bitmap."
^ (self basicNew setExtent: extentPoint depth: anInteger)
offset: offsetPoint!
fromDisplay: aRectangle depth: aDepth
"11/4/96 ssa - Answer an instance of me with bitmap initialized from the area
of the
display screen defined by aRectangle."
^ (self extent: aRectangle extent depth: aDepth)
fromDisplay: aRectangle!
fromUser: aPoint depth: anInteger
"2/19/97 ssa added to allow depth control"
"Answer an instance of me with bitmap initialized from the area of the
display screen designated by the user. The grid for selecting an area is
aPoint."
^ self fromDisplay: (Rectangle fromUser: aPoint) depth: anInteger!
fromUserWithDepth: anInteger
"2/19/97 ssa added to allow depth control"
"Answer an instance of me with bitmap initialized from the area of the
display screen designated by the user. The grid for selecting an area is
1@1."
^self fromUser: 1 @ 1 depth: anInteger
" (Form fromUserWithDepth:1 )browse.
(Form fromUserWithDepth:4 )browse.
(Form fromUserWithDepth:8 )browse.
(Form fromUserWithDepth:16 )browse.
"! !
!Project methodsFor: 'accessing'!
desktop
"2/25/97 ssa - answer my last known desktop bitmap"
^desktop!
desktop: aForm
"2/25/97 ssa - set my last known desktop bitmap"
desktop _ aForm! !
!Project methodsFor: 'menu messages'!
exit
"Leave the current project and return to the project
in which this one was created."
self desktop: (Form fromDisplay: Display boundingBox depth: Display depth).
projectHolder enter! !
!ProjectView methodsFor: 'displaying'!
displayView
"2/25/97 ssa - change to use project desktop, if any"
| scale rect topLeft |
super displayView.
self label = model name
ifFalse: [super relabel: model name].
self isCollapsed ifTrue: [^ self].
Display fill: self insetDisplayBox fillColor: Color lightGray.
scale _ self insetDisplayBox extent / Display extent.
topLeft _ self insetDisplayBox topLeft.
model desktop isNil
ifTrue:[self displayViewOutlines]
ifFalse:[model desktop extent = Display extent
ifTrue:[model desktop: (model desktop shrinkBy: scale smoothing:3)].
model desktop
displayOn: Display
at: topLeft
clippingBox: self insetDisplayBox]!
displayViewOutlines
| scale rect topLeft |
super displayView.
self label = model name
ifFalse: [super relabel: model name].
self isCollapsed ifTrue: [^ self].
Display fill: self insetDisplayBox fillColor: Color lightGray.
scale _ self insetDisplayBox extent / Display extent.
topLeft _ self insetDisplayBox topLeft.
model views reverseDo:
[:v | rect _ (v displayBox scaleBy: scale) rounded
translateBy: topLeft.
Display fill: rect fillColor: v backgroundColor;
border: rect width: 1;
border: (rect topLeft extent: rect width@3) width: 1.
]! !
Date: 97 Jun 06 2:11:19 pm
From: jecel@lsi.usp.br (Jecel Mattos de Assumpcao Jr.)
To: squeak@create.ucsb.edu
Subject: Re: What does Squeak need?
Sam Adams <ssadams@us.ibm.com> wrote:
> Here's an idea for a relatively simple way for Squeak to handle multiple host
> windows. Allow for multiple DisplayScreen instances mapped to OS windows.
> Each child window could have its own DisplayScreen or could be mapped from a
> common DisplayScreen. This is not too different than the way projects feel. I
> doesn't get you native look and feel, but I think the price of that is too high
> if it means losing easy programmer control of the bitmaps and views. This idea
> might produce some interesting UIs, like MVC views or Morphic worlds managed 1
> per OS window.
In Self you can make the system move any morph to its
own window, which is very much like this. I would
prefer it if any morph (not just a worldMorph) could
be mapped to an OS window. That would be simpler and
would feel closer to a native application (in the current
system you can resize the window and move the morph
around in it).
Multiple DisplayScreens are needed anyway, if only to support multiple
monitors on reasonable hardware that can use them.
Being able to map any morph to a whole hardware screen is
also useful for building kiosk systems or for games. Also,
mapping a whole Smalltalk window (or desktop) to an OS
window has the undesirable effect of having nested "decorations"
(title and scroll bars, and so on). To fake a native window
we should be able to map a "naked" subpane.
BTW, Smalltalk X is a good example of how preferences can make
the language implemented widgets match the underlying OS's
(or not, if the user prefers another style). I see native
windows as just a nice area to blast bits to. The only exception
is that it is hard to get good native-looking menus or menu bars
this way.
-- Jecel
Date: 97 Jun 06 4:30:28 pm
From: lnotarfr@dc.uba.ar (Luciano Esteban Notarfrancesco)
To: squeak@create.ucsb.edu
Subject: Re: What does Squeak need?
I'll be short:
I'd like to have exception handling and a better debuger.
I don't like native widgets. I don't care about name spaces.
Regards,
Luciano.-
Date: 97 Jun 06 5:03:55 pm
From: "Terry Raymond" <traymond@craftedsmalltalk.com>
To: "squeak" <squeak@create.ucsb.edu>
Subject: Re: What does Squeak need? - GUI discussion
Hi
It seems to me that the GUI discussion has split into to "camps",
use native widgets, and use emulated widgets. Considering that
I use VW I prefer emulated widgets, I think they are more flexible
and portable.
However, my reason to post this is to, point out that one of Smalltalk's
greatest strengths is its flexibility, and suggest that maybe we can think
of a GUI framework that is not too complicated, ala VW, but permits
emulated widgets and native widgets. My first thought is to create
a framework that uses dlls for the windowing primitives so they
can be tailored for a specific platform. My next thought is to use
something like slls and an abstract framework for the smalltalk part
of the GUI. By using slls only the appropriate smalltalk code will
be in the image so we can minimize image growth.
Comments anyone?
Terry Raymond
Crafted Smalltalk
(401) 846-6573 http://www.craftedsmalltalk.com
Date: 97 Jun 06 9:32:24 pm
From: Leandro Caniglia <caniglia@mate.dm.uba.ar>
To: 'Squeak' <squeak@create.ucsb.edu>
Subject: Non-visual Smalltalk
Many people is working or speaking or thinking arround graphics issues. =
It's OK, but why nobody is interested in a non-visual Smalltalk? I think =
that an enterely non-visual environment has chances to be done. Gestural =
and sound devices could be used for making real the Smalltalk HAL dream. =
It would be nice to talk in Smalltalk.
Saludos,
Leandro
Date: 97 Jun 06 9:32:19 pm
From: Leandro Caniglia <caniglia@mate.dm.uba.ar>
To: 'Squeak' <squeak@create.ucsb.edu>
Subject: #gcd: method for large integers
Hi you all.
Some time ago I sent to the list some changes to the #gcd: method. Those =
changes were improvements in the cases of small and large integers but =
for large integers a still better algorithm is described in the Knuth's =
book (Vol 2). The examples I've tried showed me that the new algorithm =
runs beteween 35% and 300% faster (when the present #gcd: is modified as =
I indicated in a former message). For completeness, I repeat here the =
changes in the general #gcd: for the Integer class and give my =
transcription of the new #gcd: improvement for the LargePositiveInteger =
class.
Saludos,
Leandro
-----------
'From Squeak 1.19d of April 13, 1997 on 6 June 1997 at 11:06:55 pm'!
!LargePositiveInteger methodsFor: 'mathematical functions'!
gcdL: aNumber=20
"Euclid's algorithm for large number (see Knuth Vol 2)."
| u v uu vv a b c d q t ww |
uu _ self abs max: aNumber abs.
vv _ self abs min: aNumber abs.
[vv isKindOf: SmallInteger]
whileFalse:
[u _ uu.
v _ vv.
[u isKindOf: SmallInteger]
whileFalse:
[u _ u bitShift: -8.
v _ v bitShift: -8].
a _ 1.
b _ 0.
c _ 0.
d _ 1.
[v + c ~=3D 0
and: [v + d ~=3D 0 and: [(q _ u + a // (v + c)) =3D (u + b // (v + =
d))]]]
whileTrue:
[t _ a - (q * c).
a _ c.
c _ t.
t _ b - (q * d).
b _ d.
d _ t.
t _ u - (q * v).
u _ v.
v _ t].
b =3D 0
ifTrue:
[t _ uu \\ vv.
uu _ vv.
vv _ t]
ifFalse:
[t _ a * uu.
t _ t + (b * vv).
ww _ c * uu.
ww _ ww + (d * vv).
uu _ t.
vv _ ww]].
^ vv gcd1: uu! !
-------
'From Squeak 1.19d of April 13, 1997 on 6 June 1997 at 11:46:22 pm'!
!Integer methodsFor: 'mathematical functions'!
gcd1: anInteger
"Answer the greatest common divisor of the receiver and n. Uses Roland
Silver's algorithm (see Knuth, Vol. 2)."
| m n d t |
n _ self abs max: anInteger abs.
m _ self abs min: anInteger abs.
m =3D 0 ifTrue: [^n].
(n _ n \\ m) =3D 0 ifTrue: [^m].
"*** No more differences with the current version of #gcd: follow this =
line ***"
"easy test, speeds up rest"
d _ 0.
[n even and: [m even]]
whileTrue:
[d _ d + 1.
n _ n bitShift: -1.
m _ m bitShift: -1].
[n even]
whileTrue: [n _ n bitShift: -1].
[m even]
whileTrue: [m _ m bitShift: -1].
[m =3D n]
whileFalse:
[m > n
ifTrue:
[m _ m - n]
ifFalse:
[t _ m.
m _ n - m.
n _ t].
"Make sure larger gets replaced"
[m even]
whileTrue: [m _ m bitShift: -1]].
d =3D 0 ifTrue: [^m].
^m bitShift: d! !
Date: 97 Jun 07 12:37:21 am
From: Nickolay Saukh <nms@nns.ru>
To: squeak@create.ucsb.edu
Subject: Re: What does Squeak need?
Unicode as base character set.
Date: 97 Jun 07 7:46:02 am
From: "Hal Hildebrand" <horus@pacbell.net>
To: "squeak" <squeak@create.ucsb.edu>
Subject: Re: What does Squeak need? - GUI discussion
Terry,
>It seems to me that the GUI discussion has split into to "camps",
>use native widgets, and use emulated widgets. Considering that
>I use VW I prefer emulated widgets, I think they are more flexible
>and portable.
I think the camps are inevitable, and this is why the quest for portability
steps on a lot of toes. A lot of people who use VW prefere the emulated
widgets, but emulated widgets are one of the biggest barriers to new
sales.
My whole point on discussing the portability issue is to bring up these
differences. It's way to easy to get going along the primrose path and
suddenly find out that you're the only one in a purple suit and a big red
target on your chest (bummer of a birth mark, Hal). At least this way, we
can discuss our differences and find out where we all stand, and where we
need to compromise -- before the fact.
I've seen people kill over GUI issues. On both sides. Relationships break
up, divorces, countries go to war over look and feel issues. Okay, it's
not that bad... But this issue usually gets personal really quick.
Hal
__
Time is when the day is like a play by Sartre
When it seems that book burning's in perfect order
http://www.hellblazer.com (Web)
mailto:hal@parcplace.com (Business)
mailto:horus@pacbell.net (Personal)
Date: 97 Jun 07 7:51:02 am
From: Stefan Matthias Aust <sma@kiel.netsurf.de>
To: squeak@create.ucsb.edu
Subject: Re: What does Squeak need?
--=====================_865689373==_
Content-Type: text/plain; charset="us-ascii"
William A. Barnett-Lewis wrote:
>While I really enjoy futzing with a "classic" st-80, if someone wanted to
>explain (pointers to papers, etc) how to implement Lisp in smalltalk, I'd be
>game to give it a try as an additional personality for squeak.
Look at Ian's Lisp-in-Smalltalk package which is available at the Smalltalk
archive at http://st-www.cs.uiuc.edu/. Yoshi's [I'm afraid, I don't remember
the exact spelling of that Japanese guy] Smalltalk goodies also include a
Lisp and a Prolog system written in Smalltalk. You can find a link to his
page at http://www.oti.com/jeffspg/smaltalk.htm.
In a nutshell, it's not that complicate to write such a Lisp system. Lisp
has a very simple syntax and it can be broken down to only a handful
constructs called special forms. You can then bootstrap a full lisp system
starting with some basic lisp primitives like car, cdr, cons, cons?, eq?,
lambda, define, apply, ...
The basic idea is to compile Lisp programs into Smalltalk bytecode which can
be executed by the Smalltalk VM. Because you probably don't want to emit
bytecodes yourself, you will translate Lisp expressions into semantically
equivalent Smalltalk (source code) expressions which are then compiled by
the normal Smalltalk compiler into bytecode. As you can replace a class'
compiler you can integrate a Lisp system seamless into your Smalltalk
environment. For subclasses of (say) LispObject you will use a different
compiler which takes Lisp sources and compiles them. You can use all normal
tools likes browsers and inspectors with your new Lisp subsystem.
Subclassing the Debugger to be able to debug Lisp source is more difficult,
though.
A LispCompiler consists of the following components:
1. A LispReader which breaks a piece of Lisp source into tokens like
primitive datatypes (Fixnum, Symbol, the nil constant) and syntax characters
(like "(", ")" and ".") and answers lisp expressions represented as cons
nodes of primitives.
2. A LispEnumerator, which traverses the tree of cons nodes, detects the
special forms and generates equivalent Smalltalk source code, then compiles
the code and adds it to the system.
3. A LispSystem runtime environment which holds global bindings and compiled
methods (or compiled block closures).
Here's a very simple Lisp dialect which has only symbols (atoms) and nil as
primitive types and cons as compound data type. The EBNF of Lisp expressions
looks like this:
expression = nil
| atom
| "(" expression-list
expression-list = ")"
| expression expression-list
| "." expression ")"
We need the following special forms (...I think. I'm writing this right from
memory). Nearly everything else can be constructed from this in Lisp.
(quote P) --> answer P, unevaluated.
(define P Q) --> create a new global binding (P, Q). P must be an atom.
(lambda P Q) --> create unnamed function. Elements of list P are taken as
parameters, Q is taken as sequence of lisp expressions.
Answer the created function abstraction.
(ifeq P Q X Y) --> answer X if P is identical to Q and Y otherwise.
The above function is motivated by the fact that I don't want to provide
special true or false values inside the core. Most Lisp systems use nil for
false and a special, self evaluating symbol T as true. ifeq is special in
that is only evaluates X if the evaluated P and Q are identical and
evaluates Y only if they are not identical.
(P Q1 ... Qn) --> evaluate P (which must be a function abstraction) and
all Qi (0<=i<=n) in that order. Then apply function,
using the results of Qi as actual parameters of P.
This is the Scheme-style function application primitive. An ordinary lisp
style application will not evaluate P but take it as name to look up a bound
function object.
(primitive "code") --> Can only be used inside a lambda when compiling.
The "code" is copied literally. Fail if executed.
This will help us to implement the primitive functions.
I've attached a small Smalltalk program I hacked together yesterday night to
demonstrate these concept. I developed it with VisualWorks, but it runs with
Squeak with the following minor modifications:
1. Implement the quite obvious methods #isSymbol and #isString or replace their
occurence in #translate... with #isKindOf:. 2. Change System>>printOn: to
emit a "#" before the symbol text. (BTW, symbol handling by Squeak seems to
be broken - or at least dubious)
The interpreter works, try
LispSystem current executeString: '(cons (quote a) (quote (b c)))'
or LispSystem current executeString: '(equal (quote (a b)) (quote (a b)))'
but has one defect. It doesn't handle the binding of local variables
correctly. This is easily fixed by introducting an environment while
translating. Perhaps, I'll fix that in a future version.
bye
--=====================_865689373==_
Content-Type: text/plain; charset="us-ascii"
'From Squeak 1.19d of April 13, 1997 on 7 June 1997 at 3:55:21 pm'!
Object subclass: #LispCons
instanceVariableNames: 'car cdr '
classVariableNames: ''
poolDictionaries: ''
category: 'Lisp'!
Object subclass: #LispSystem
instanceVariableNames: 'bindings '
classVariableNames: 'Current '
poolDictionaries: ''
category: 'Lisp'!
!Object methodsFor: 'lisp-extensions'!
asLispObject
LispSystem failSignal raise!
car
LispSystem failSignal raise!
cdr
LispSystem failSignal raise!
isLispCons
^false! !
!LispCons methodsFor: 'accessing'!
car
^car!
car: anObject
car := anObject!
cdr
^cdr!
cdr: anObject
cdr := anObject! !
!LispCons methodsFor: 'converting'!
asLispObject
^self! !
!LispCons methodsFor: 'enumerating'!
do: aBlock
aBlock value: self car.
self cdr isLispCons ifTrue: [self cdr do: aBlock]! !
!LispCons methodsFor: 'printing'!
printOn: aStream
| cons |
aStream nextPut: $#; nextPut: $(.
cons := self.
[aStream print: cons car; space.
cons cdr isLispCons]
whileTrue: [cons := cons cdr].
cons cdr isNil ifFalse: [aStream
nextPutAll: ' . ';
print: cons cdr;
space].
aStream skip: -1; nextPut: $)! !
!LispCons methodsFor: 'testing'!
isLispCons
^true! !
!LispCons class methodsFor: 'instance creation'!
car: anObject
^self new car: anObject!
car: anObject cdr: anotherObject
^self new car: anObject; cdr: anotherObject!
cdr: anObject
^self new cdr: anObject! !
!LispSystem methodsFor: 'accessing'!
at: aSymbol
"Answer value associated with global name aSymbol."
| b |
(b := self bindingAt: aSymbol) notNil ifTrue: [^b cdr].
^nil!
at: aSymbol put: anObject
"Bind value anObject to global name aSymbol. (Replace existing binding or create new.)"
| b |
(b := self bindingAt: aSymbol) notNil
ifTrue: [b cdr: anObject]
ifFalse: [self bind: anObject to: aSymbol].
^anObject! !
!LispSystem methodsFor: 'translating'!
translate2: sexpr
"Bad hack to fix the scoping problem somewhat. All translating methods actually need an
environment of local bound variables to destinguish local from global variable references."
sexpr isSymbol ifTrue: [^sexpr asString].
^self translate: sexpr!
translate: sexpr
"A better solution is a double dispatch but I don't want to spread the code
over the class hierarchy. If the sexpr is neither nil nor an atom, we assume
a proper list."
| sform |
sexpr isNil ifTrue: [^'nil'].
sexpr isSymbol ifTrue: [^'(LispSystem current at: #' , sexpr , ')'].
sexpr isString ifTrue: [^sexpr printString].
sform := sexpr car.
sform == #quote ifTrue: [^self translateQuote: sexpr].
sform == #define ifTrue: [^self translateDefine: sexpr].
sform == #lambda ifTrue: [^self translateLambda: sexpr].
sform == #if ifTrue: [^self translateIf: sexpr].
sform == #primitive ifTrue: [^self translatePrimitive: sexpr].
^self translateApplication: sexpr!
translateApplication: sexpr
"Private - (P Q1 ... Qn) --> apply P (which must be a function and P's parameters must match n)"
| s n cons |
s := self translate: sexpr car.
n := self length: (cons := sexpr cdr).
n = 0 ifTrue: [^s , ' value'].
n < 4
ifTrue:
[n
timesRepeat:
[s := s , ' value: ' , (self translate2: cons car).
cons := cons cdr].
^'(' , s , ')'].
s := s , ' valueWithArguments: (Array new '.
n
timesRepeat:
[s := s , 'add: ' , (self translate2: cons car) , '; '.
cons := cons cdr].
^'(' , s , 'yourself)'!
translateDefine: sexpr
"Private - (define P Q) --> create a new global binding (P, Q). P must be an atom."
^'(LispSystem current at: #' , sexpr cdr car , ' put: ' , (self translate: sexpr cdr cdr car) , ')'!
translateIf: sexpr
"Private - (if P Q R) --> evaluate and answer Q if P is not identical to nil and R otherwise."
^'(' , (self translate2: sexpr cdr car) , ' notNil ifTrue: [' , (self translate2: sexpr cdr cdr car) , '] ifFalse: [' , (self translate2: sexpr cdr cdr cdr car) , '])'!
translateLambda: sexpr
"Private - (lambda P Q1 ... Qn) --> create and answer unnamed function abstraction."
| s p |
s := '['.
p := sexpr cdr car.
p notNil
ifTrue:
[p do: [:each | s := s , ' :' , each].
s := s , ' | '].
^s , (self translateSequence: sexpr cdr cdr) , ']'!
translatePrimitive: sexpr
"Private - (primitive 'code') --> emit code."
^sexpr cdr car!
translateQuote: sexpr
"Private - (quote P) --> answer P, unevaluated."
^sexpr cdr car printString , ' asLispObject'!
translateSequence: sexpr
"Private - (P1 ... Pn) --> evaluate P1 .. Pn and answer result of Pn."
^sexpr isLispCons
ifTrue: [(self translate2: sexpr car)
, '. ' , (self translateSequence: sexpr cdr)]
ifFalse: ['']! !
!LispSystem methodsFor: 'private'!
bind: anObject to: aSymbol
"Private - Create and add a binding (aSymbol, anObject)."
bindings := LispCons car: (LispCons car: aSymbol cdr: anObject) cdr: bindings!
bindingAt: aSymbol
"Private - Answer the binding of aSymbol or nil if no binding is found."
bindings notNil ifTrue: [
bindings do: [:each | each car == aSymbol ifTrue: [^each]]].
^nil!
isProperList: sexpr
"Private - Answer true if sexpr is a proper list, that is a sequence of cons cells ended with nil."
^(self length: sexpr) notNil!
length: sexpr
"Private - Answer the length of the list or nil, if sexpr isn't a proper list."
| cons count |
cons := sexpr.
count := 0.
[cons isLispCons]
whileTrue:
[cons := cons cdr.
count := count + 1].
^cons isNil
ifTrue: [count]
ifFalse: [nil]! !
!LispSystem methodsFor: 'executing'!
execute: anObject
"Convert anObject into a Lisp object, take it as code which can be translated and finally execute the
translated Smalltalk code."
^self class evaluatorClass new
evaluate: (self translate: anObject asLispObject)
in: nil
"receiver:" to: self
notifying: nil
ifFail: [LispSystem failSignal raise]!
executeString: aString
"Take aString as Lisp program, execute it, answer the result - a Lisp object."
^(Scanner new scanTokens: aString)
inject: nil into: [:result :each | self execute: each asLispObject]! !
!LispSystem class methodsFor: 'accessing'!
current
Current isNil ifTrue: [Current := self new].
^Current!
failSignal
"^Object errorSignal"
self error: 'lisp execution failed'! !
!LispSystem class methodsFor: 'class initialization'!
initialize
"Bootstrap."
"self initialize"
self current executeString: '
(define T (quote T))
(define car (lambda (p) (primitive ''p car'')))
(define cdr (lambda (p) (primitive ''p cdr'')))
(define cons (lambda (p q) (primitive ''LispCons car: p cdr: q'')))
(define consp (lambda (p) (primitive ''p isLispCons ifTrue: [p] ifFalse: [nil]'')))
(define eq (lambda (p q) (primitive ''p == q ifTrue: [LispSystem current at: #T] ifFalse: [nil]'')))
(define not (lambda (p) (if p nil T)))
(define atom (lambda (p) (not (consp p))))
(define equal (lambda (p q)
(if (consp p)
(if (consp q)
(if (equal (car p) (car q)) (equal (cdr p) (cdr q)) nil)
nil)
(eq p q))))'!
initializeMore
self current executeString: '
(define fixnump (lambda (n) (primitive ''n isInteger ifTrue: [n] ifFalse: [nil]'')))
(define + (lambda (n m) (primitive ''n + m'')))
(define - (lambda (n m) (primitive ''n - m'')))
(define * (lambda (n m) (primitive ''n * m'')))
(define / (lambda (n m) (primitive ''n // m'')))
(define = (lambda (n m) (primitive ''n = m'')))
(define < (lambda (n m) (primitive ''n < m'')))
(define /= (lambda (n m) (not (= n m))))'! !
!SequenceableCollection methodsFor: 'lisp-extensions'!
asLispObject
| list cons |
self isEmpty ifTrue: [^nil].
list := cons := LispCons car: self first asLispObject.
2 to: self size do: [:index | #'.' == (self at: index)
ifTrue:
[cons cdr: (self at: index + 1) asLispObject.
^list]
ifFalse:
[cons cdr: (LispCons car: (self at: index) asLispObject).
cons := cons cdr]].
^list! !
!String methodsFor: 'lisp-extensions'!
asLispObject
^self! !
!UndefinedObject methodsFor: 'lisp-extensions'!
asLispObject
^self! !
LispSystem initialize!
--=====================_865689373==_
Content-Type: text/plain; charset="us-ascii"
--
Stefan Matthias Aust // Planet Claire has pink air!
http://www.kiel.netsurf.de/users/s/sma/
--=====================_865689373==_--
Date: 97 Jun 07 9:50:52 am
From: Dan Ingalls <DanI@wdi.disney.com>
To: Squeak@create.ucsb.edu
Subject: Sundry VM changes
--============_-1346415087==_============
Content-Type: text/plain; charset="us-ascii"
Content-Transfer-Encoding: quoted-printable
The attached file includes a number of fixes to the VM. Several of these=
are repeats of an earlier file that I sent out around the time of the=
interruption of Squeak mail service, so I thought it best to repeat. To=
quote from the preamble...
=46ixed WarpBlt clipping so source skips over to clipX, Y if clipped.
Made WarpBlt handle transparency independently of pixel averaging.
Made VM tolerate SmallIntegers as message selectors to allow for
shrunken images with Symbols eliminated
Includes fix for Float truncated that we did a while ago.
=46ixes Float>>sqrt so that it fails for negative recievers.
Also fixes Bitmap primFill: so that it will accept 32-bit integers.
=46ixes at: and at:put: so that they fail for receiver being a SmallInteger
NOTE: We have gone to a new changes file format that includes time and=
author stamps on all changes. Therefore you need the first little fileIn=
if you wish to read the second. All of this is in a new image that we hope=
to have out for test and comment in a day or two.
- Dan
--============_-1346415087==_============
Content-Type: text/plain; name="ClassDescripti...odsForstamp.st"; charset="us-ascii"
Content-Disposition: attachment; filename="ClassDescripti...odsForstamp.st"
'From Squeak 1.19d of April 13, 1997 on 6 June 1997 at 10:10:12 am'!
!ClassDescription methodsFor: 'fileIn/Out'!
methodsFor: categoryName stamp: changeStamp
^ self methodsFor: categoryName! !
--============_-1346415087==_============
Content-Type: text/plain; name="VMFixes6=3-di.cs"; charset="us-ascii"
Content-Disposition: attachment; filename="VMFixes6=3-di.cs"
'From Squeak 1.19d of April 13, 1997 on 7 June 1997 at 10:04:39 am'!
"Change Set: WarpFix
Date: 3 June 1997
Author: Dan Ingalls
Fixed WarpBlt clipping so source skips over to clipX, Y if clipped.
Made WarpBlt handle transparency independently of pixel averaging.
Made VM tolerate SmallIntegers as message selectors to allow for
shrunken images with Symbols eliminated
Includes fix for Float truncated that we did a while ago.
Fixes Float>>sqrt so that it fails for negative recievers.
Also fixes Bitmap primFill: so that it will accept 32-bit integers.
Fixes at: and at:put: so that they fail for receiver being a SmallInteger
"!
!BitBltSimulation methodsFor: 'inner loop'!
warpLoop
| skewWord halftoneWord mergeWord destMask startBits
deltaP12x deltaP12y deltaP43x deltaP43y pAx pAy
xDelta yDelta pBx pBy smoothingCount sourceMapOop nSteps t |
"This version of the inner loop traverses an arbirary quadrilateral
source, thus producing a general affine transformation."
(interpreterProxy fetchWordLengthOf: bitBltOop) >= (BBWarpBase+12)
ifFalse: [^ interpreterProxy primitiveFail].
nSteps _ height-1. nSteps <= 0 ifTrue: [nSteps _ 1].
pAx _ interpreterProxy fetchIntegerOrTruncFloat: BBWarpBase ofObject: bitBltOop.
t _ interpreterProxy fetchIntegerOrTruncFloat: BBWarpBase+3 ofObject: bitBltOop.
deltaP12x _ self deltaFrom: pAx to: t nSteps: nSteps.
deltaP12x < 0 ifTrue: [pAx _ t - (nSteps*deltaP12x)].
pAy _ interpreterProxy fetchIntegerOrTruncFloat: BBWarpBase+1 ofObject: bitBltOop.
t _ interpreterProxy fetchIntegerOrTruncFloat: BBWarpBase+4 ofObject: bitBltOop.
deltaP12y _ self deltaFrom: pAy to: t nSteps: nSteps.
deltaP12y < 0 ifTrue: [pAy _ t - (nSteps*deltaP12y)].
pBx _ interpreterProxy fetchIntegerOrTruncFloat: BBWarpBase+9 ofObject: bitBltOop.
t _ interpreterProxy fetchIntegerOrTruncFloat: BBWarpBase+6 ofObject: bitBltOop.
deltaP43x _ self deltaFrom: pBx to: t nSteps: nSteps.
deltaP43x < 0 ifTrue: [pBx _ t - (nSteps*deltaP43x)].
pBy _ interpreterProxy fetchIntegerOrTruncFloat: BBWarpBase+10 ofObject: bitBltOop.
t _ interpreterProxy fetchIntegerOrTruncFloat: BBWarpBase+7 ofObject: bitBltOop.
deltaP43y _ self deltaFrom: pBy to: t nSteps: nSteps.
deltaP43y < 0 ifTrue: [pBy _ t - (nSteps*deltaP43y)].
interpreterProxy failed ifTrue: [^ false]. "ie if non-integers above"
interpreterProxy argCount = 2
ifTrue: [smoothingCount _ interpreterProxy stackIntegerValue: 1.
sourceMapOop _ interpreterProxy stackValue: 0.
sourceMapOop = interpreterProxy nilObject
ifTrue: [sourcePixSize < 16 ifTrue:
["color map is required to smooth non-RGB dest"
^ interpreterProxy primitiveFail]]
ifFalse: [(interpreterProxy fetchWordLengthOf: sourceMapOop)
< (1 << sourcePixSize) ifTrue:
["sourceMap must be long enough for sourcePixSize"
^ interpreterProxy primitiveFail]]]
ifFalse: [smoothingCount _ 1.
sourceMapOop _ interpreterProxy nilObject].
startBits _ pixPerWord - (dx bitAnd: pixPerWord-1).
nSteps _ width-1. nSteps <= 0 ifTrue: [nSteps _ 1].
destY to: clipY-1 do:
[ :i | "Advance increments if there was clipping in y"
pAx _ pAx + deltaP12x.
pAy _ pAy + deltaP12y.
pBx _ pBx + deltaP43x.
pBy _ pBy + deltaP43y].
1 to: bbH do:
[ :i | "here is the vertical loop..."
xDelta _ self deltaFrom: pAx to: pBx nSteps: nSteps.
xDelta >= 0 ifTrue: [sx _ pAx] ifFalse: [sx _ pBx - (nSteps*xDelta)].
yDelta _ self deltaFrom: pAy to: pBy nSteps: nSteps.
yDelta >= 0 ifTrue: [sy _ pAy] ifFalse: [sy _ pBy - (nSteps*yDelta)].
destX to: clipX-1 do:
[:word | "Advance increments if there was clipping in x"
sx _ sx + xDelta.
sy _ sy + yDelta].
noHalftone
ifTrue: [halftoneWord _ AllOnes]
ifFalse: [halftoneWord _ interpreterProxy longAt: (halftoneBase + (dy+i-1 \\ halftoneHeight * 4))].
destMask _ mask1.
"pick up first word"
bbW < startBits
ifTrue: [skewWord _ self warpSourcePixels: bbW
xDeltah: xDelta yDeltah: yDelta
xDeltav: deltaP12x yDeltav: deltaP12y
smoothing: smoothingCount sourceMap: sourceMapOop.
skewWord _ skewWord
bitShift: (startBits - bbW)*destPixSize]
ifFalse: [skewWord _ self warpSourcePixels: startBits
xDeltah: xDelta yDeltah: yDelta
xDeltav: deltaP12x yDeltav: deltaP12y
smoothing: smoothingCount sourceMap: sourceMapOop].
1 to: nWords do:
[ :word | "here is the inner horizontal loop..."
mergeWord _ self merge: (skewWord bitAnd: halftoneWord)
with: ((interpreterProxy longAt: destIndex) bitAnd: destMask).
interpreterProxy longAt: destIndex
put: ((destMask bitAnd: mergeWord)
bitOr:
(destMask bitInvert32 bitAnd: (interpreterProxy longAt: destIndex))).
destIndex _ destIndex + 4.
word >= (nWords - 1) ifTrue:
[word = nWords ifFalse:
["set mask for last word in this row"
destMask _ mask2.
skewWord _ self warpSourcePixels: pixPerWord
xDeltah: xDelta yDeltah: yDelta
xDeltav: deltaP12x yDeltav: deltaP12y
smoothing: smoothingCount sourceMap: sourceMapOop]]
ifFalse:
["use fullword mask for inner loop"
destMask _ AllOnes.
skewWord _ self warpSourcePixels: pixPerWord
xDeltah: xDelta yDeltah: yDelta
xDeltav: deltaP12x yDeltav: deltaP12y
smoothing: smoothingCount sourceMap: sourceMapOop].
].
pAx _ pAx + deltaP12x.
pAy _ pAy + deltaP12y.
pBx _ pBx + deltaP43x.
pBy _ pBy + deltaP43y.
destIndex _ destIndex + destDelta]! !
!BitBltSimulation methodsFor: 'pixel mapping'!
smoothPix: n atXf: xf yf: yf dxh: dxh dyh: dyh dxv: dxv dyv: dyv
pixPerWord: srcPixPerWord pixelMask: sourcePixMask
sourceMap: sourceMap
| sourcePix r g b x y rgb bitsPerColor d nPix maxPix |
r _ g _ b _ 0. "Separate r, g, b components"
maxPix _ n*n.
x _ xf. y _ yf.
nPix _ 0. "actual number of pixels (not clipped and not transparent)"
0 to: n-1 do:
[:i |
0 to: n-1 do:
[:j |
sourcePix _ (self sourcePixAtX: x + (dxh*i) + (dxv*j) >> BinaryPoint
y: y + (dyh*i) + (dyv*j) >> BinaryPoint
pixPerWord: srcPixPerWord)
bitAnd: sourcePixMask.
(combinationRule=25 "PAINT" and: [sourcePix = 0]) ifFalse:
["If not clipped and not transparent, then tally rgb values"
nPix _ nPix + 1.
sourcePixSize < 16
ifTrue: ["Get 24-bit RGB values from sourcemap table"
rgb _ (interpreterProxy fetchWord: sourcePix ofObject: sourceMap) bitAnd: 16rFFFFFF]
ifFalse: ["Already in RGB format"
sourcePixSize = 32
ifTrue: [rgb _ sourcePix bitAnd: 16rFFFFFF]
ifFalse: ["Note could be faster"
rgb _ self rgbMap: sourcePix from: 5 to: 8]].
r _ r + ((rgb >> 16) bitAnd: 16rFF).
g _ g + ((rgb >> 8) bitAnd: 16rFF).
b _ b + (rgb bitAnd: 16rFF).
]].
].
(nPix = 0 or: [combinationRule=25 "PAINT" and: [nPix < (maxPix//2)]])
ifTrue: [^ 0 "All pixels were 0, or most were transparent"].
colorMap ~= interpreterProxy nilObject
ifTrue: [bitsPerColor _ cmBitsPerColor]
ifFalse: [destPixSize = 16 ifTrue: [bitsPerColor _ 5].
destPixSize = 32 ifTrue: [bitsPerColor _ 8]].
d _ 8 - bitsPerColor.
rgb _ ((r // nPix >> d) << (bitsPerColor*2))
+ ((g // nPix >> d) << bitsPerColor)
+ ((b // nPix >> d)).
rgb = 0 ifTrue: [
"only generate zero if pixel is really transparent"
(r + g + b) > 0 ifTrue: [rgb _ 1]].
colorMap ~= interpreterProxy nilObject
ifTrue: [^ interpreterProxy fetchWord: rgb ofObject: colorMap]
ifFalse: [^ rgb]
! !
!Interpreter methodsFor: 'message sending'!
lookupMethodInDictionary: dictionary
"This method lookup tolerates integers as Dictionary keys to support
execution of images in which Symbols have been compacted out"
| length index mask wrapAround nextSelector methodArray |
self inline: true.
length _ self fetchWordLengthOf: dictionary.
mask _ length - SelectorStart - 1.
(self isIntegerObject: messageSelector)
ifTrue:
[index _ (mask bitAnd: (self integerValueOf: messageSelector)) + SelectorStart]
ifFalse:
[index _ (mask bitAnd: (self hashBitsOf: messageSelector)) + SelectorStart].
"It is assumed that there are some nils in this dictionary, and search will
stop when one is encountered. However, if there are no nils, then wrapAround
will be detected the second time the loop gets to the end of the table."
wrapAround _ false.
[true] whileTrue:
[nextSelector _ self fetchPointer: index
ofObject: dictionary.
nextSelector=nilObj ifTrue: [^false].
nextSelector=messageSelector
ifTrue: [methodArray _ self fetchPointer: MethodArrayIndex
ofObject: dictionary.
newMethod _ self fetchPointer: index - SelectorStart
ofObject: methodArray.
primitiveIndex _ self primitiveIndexOf: newMethod.
^true].
index _ index + 1.
index = length
ifTrue: [wrapAround ifTrue: [^false].
wrapAround _ true.
index _ SelectorStart]]! !
!Interpreter methodsFor: 'float primitives'!
primitiveSquareRoot
| rcvr |
self var: #rcvr declareC: 'double rcvr'.
rcvr _ self popFloat.
self success: rcvr >= 0.0.
successFlag
ifTrue: [self pushFloat: (self cCode: 'sqrt(rcvr)')]
ifFalse: [self unPop: 1]! !
!Interpreter methodsFor: 'float primitives' stamp: '6/7/97 09:59 di'!
primitiveTruncated
| rcvr frac trunc |
self var: #rcvr declareC: 'double rcvr'.
self var: #frac declareC: 'double frac'.
self var: #trunc declareC: 'double trunc'.
rcvr _ self popFloat.
successFlag ifTrue: [
self cCode: 'frac = modf(rcvr, &trunc)'.
self cCode: 'success((-1073741824.0 <= trunc) && (trunc <= 1073741823.0))'.
].
successFlag
ifTrue: [self cCode: 'pushInteger((int) trunc)']
ifFalse: [self unPop: 1]! !
!Interpreter methodsFor: 'array and stream primitives'!
commonAt: stringy
"This version of at: is called from the special byteCode, from
primitiveAt, and from primStringAt. The boolean 'stringy'
indicates that the result should be converted to a Character."
| index rcvr result |
self inline: true.
index _ self stackTop.
rcvr _ self stackValue: 1.
(self isIntegerObject: index) & (self isIntegerObject: rcvr) not ifTrue: [
index _ self integerValueOf: index.
result _ self stObject: rcvr at: index.
(stringy and: [successFlag]) ifTrue: [result _ self characterForAscii: result].
] ifFalse: [
successFlag _ false.
].
successFlag ifTrue: [
self pop: 2 thenPush: result.
] ifFalse: [
stringy
ifTrue: [self failSpecialPrim: 63]
ifFalse: [self failSpecialPrim: 60].
].! !
!Interpreter methodsFor: 'array and stream primitives'!
commonAtPut: stringy
"See the comment in commonAt:."
| value valToStore index rcvr |
self inline: true.
value _ valToStore _ self stackTop.
index _ self stackValue: 1.
rcvr _ self stackValue: 2.
(self isIntegerObject: index) & (self isIntegerObject: rcvr) not ifTrue: [
index _ self integerValueOf: index.
stringy ifTrue: [valToStore _ self asciiOfCharacter: value].
self stObject: rcvr at: index put: valToStore.
] ifFalse: [
successFlag _ false.
].
successFlag ifTrue: [
self pop: 3 thenPush: value.
] ifFalse: [
stringy
ifTrue: [self failSpecialPrim: 64]
ifFalse: [self failSpecialPrim: 61].
].! !
!Interpreter methodsFor: 'control primitives'!
primitivePerform
| performSelector newReceiver selectorIndex |
performSelector _ messageSelector.
messageSelector _ self stackValue: argumentCount - 1.
newReceiver _ self stackValue: argumentCount.
"NOTE: the following lookup may fail and be converted to #doesNotUnderstand:,
so we must adjust argument count now, so that would work."
argumentCount _ argumentCount - 1.
self lookupMethodInClass: (self fetchClassOf: newReceiver).
self success: (self argumentCountOf: newMethod) = argumentCount.
successFlag
ifTrue: [selectorIndex _ self stackPointerIndex - argumentCount.
self transfer: argumentCount
fromIndex: selectorIndex + 1
ofObject: activeContext
toIndex: selectorIndex
ofObject: activeContext.
self pop: 1.
self executeNewMethod. "Recursive xeq affects successFlag"
successFlag _ true]
ifFalse: [argumentCount _ argumentCount + 1.
messageSelector _ performSelector]! !
!Interpreter methodsFor: 'control primitives'!
primitivePerformWithArgs
| thisReceiver performSelector argumentArray arraySize index cntxSize |
argumentArray _ self popStack.
arraySize _ self fetchWordLengthOf: argumentArray.
cntxSize _ self fetchWordLengthOf: activeContext.
self success: (self stackPointerIndex + arraySize) < cntxSize.
self assertClassOf: argumentArray is: (self splObj: ClassArray).
successFlag
ifTrue: [performSelector _ messageSelector.
messageSelector _ self popStack.
thisReceiver _ self stackTop.
argumentCount _ arraySize.
index _ 1.
[index <= argumentCount]
whileTrue:
[self push: (self fetchPointer: index - 1 ofObject: argumentArray).
index _ index + 1].
self lookupMethodInClass: (self fetchClassOf: thisReceiver).
self success: (self argumentCountOf: newMethod) = argumentCount.
successFlag
ifTrue: [self executeNewMethod. "Recursive xeq affects successFlag"
successFlag _ true]
ifFalse: [self unPop: argumentCount.
self push: messageSelector.
self push: argumentArray.
argumentCount _ 2.
messageSelector _ performSelector]]
ifFalse: [self unPop: 1]! !
!Interpreter methodsFor: 'sound primitives' stamp: '6/7/97 09:59 di'!
primitiveConstantFill
"Fill the receiver, which must be an indexable bytes or words objects, with the given integer value."
| fillValue rcvr rcvrIsBytes end i |
fillValue _ self positive32BitValueOf: self stackTop.
rcvr _ self stackValue: 1.
self success: (self isWordsOrBytes: rcvr).
rcvrIsBytes _ self isBytes: rcvr.
rcvrIsBytes ifTrue: [
self success: ((fillValue >= 0) and: [fillValue <= 255]).
].
successFlag ifTrue: [
end _ rcvr + (self sizeBitsOf: rcvr).
i _ rcvr + BaseHeaderSize.
rcvrIsBytes ifTrue: [
[i < end] whileTrue: [
self byteAt: i put: fillValue.
i _ i + 1.
].
] ifFalse: [
[i < end] whileTrue: [
self longAt: i put: fillValue.
i _ i + 4.
].
].
self pop: 1. "pop fillValue; leave rcvr on stack"
].
! !
!WarpBlt methodsFor: 'primitives'!
sourceQuad: pts destRect: aRectangle
| fixedPt1 |
sourceX _ sourceY _ 0.
self destRect: aRectangle.
fixedPt1 _ (pts at: 1) x isInteger ifTrue: [16384] ifFalse: [16384.0].
p1x _ (pts at: 1) x * fixedPt1.
p2x _ (pts at: 2) x * fixedPt1.
p3x _ (pts at: 3) x * fixedPt1.
p4x _ (pts at: 4) x * fixedPt1.
p1y _ (pts at: 1) y * fixedPt1.
p2y _ (pts at: 2) y * fixedPt1.
p3y _ (pts at: 3) y * fixedPt1.
p4y _ (pts at: 4) y * fixedPt1.
p1z _ p2z _ p3z _ p4z _ 16384. "z-warp ignored for now"
! !
!WarpBlt methodsFor: 'primitives'!
warpBitsSmoothing: n sourceMap: sourceMap
| deltaP12 deltaP43 pA pB deltaPAB sp fixedPtOne picker poker pix nSteps |
<primitive: 147>
(width < 1) | (height < 1) ifTrue: [^ self].
fixedPtOne _ 16384. "1.0 in fixed-pt representation"
n > 1 ifTrue:
[(destForm depth < 16 and: [colorMap == nil])
ifTrue: ["color map is required to smooth non-RGB dest"
^ self primitiveFail].
pix _ Array new: n*n].
nSteps _ height-1 max: 1.
deltaP12 _ (self deltaFrom: p1x to: p2x nSteps: nSteps)
@ (self deltaFrom: p1y to: p2y nSteps: nSteps).
pA _ (self startFrom: p1x to: p2x offset: nSteps*deltaP12 x)
@ (self startFrom: p1y to: p2y offset: nSteps*deltaP12 y).
deltaP43 _ (self deltaFrom: p4x to: p3x nSteps: nSteps)
@ (self deltaFrom: p4y to: p3y nSteps: nSteps).
pB _ (self startFrom: p4x to: p3x offset: nSteps*deltaP43 x)
@ (self startFrom: p4y to: p3y offset: nSteps*deltaP43 y).
picker _ BitBlt bitPeekerFromForm: sourceForm.
poker _ BitBlt bitPokerToForm: destForm.
poker clipRect: self clipRect.
nSteps _ width-1 max: 1.
destY to: destY+height-1 do:
[:y |
deltaPAB _ (self deltaFrom: pA x to: pB x nSteps: nSteps)
@ (self deltaFrom: pA y to: pB y nSteps: nSteps).
sp _ (self startFrom: pA x to: pB x offset: nSteps*deltaPAB x)
@ (self startFrom: pA y to: pB y offset: nSteps*deltaPAB x).
destX to: destX+width-1 do:
[:x |
n = 1
ifTrue:
[Transcript cr; print: sp // fixedPtOne asPoint.
poker pixelAt: x@y
put: (picker pixelAt: sp // fixedPtOne asPoint)]
ifFalse:
[0 to: n-1 do:
[:dx | 0 to: n-1 do:
[:dy |
pix at: dx*n+dy+1 put:
(picker pixelAt: sp
+ (deltaPAB*dx//n)
+ (deltaP12*dy//n)
// fixedPtOne asPoint)]].
poker pixelAt: x@y put: (self mixPix: pix
sourceMap: sourceMap
destMap: colorMap)].
sp _ sp + deltaPAB].
pA _ pA + deltaP12.
pB _ pB + deltaP43]! !
--============_-1346415087==_============--
Date: 97 Jun 07 4:05:23 pm
From: lstrand@concentric.net
To: "Squeak" <squeak@create.ucsb.edu>
Subject: Re: What does Squeak need?
I would like to express a contrary viewpoint. I want to be totally
immersed in the Smalltalk environment. To hell with the rest of the
world! So what I think Squeak needs is a full-screen mode. (Perhaps
this already exists, and I just haven't discovered it?) Better yet, why
not have a standalone, bootable Squeak OS? :-)
On a more serious note, I suggest the "Translation to C" portion of the
system be implemented using the Visitor pattern. Translating to
something other than C should be as easy as subclassing a Translator
class.
On the subject of translation, has there ever been a compiled version of
Smalltalk? Or is this considered too expensive in terms of code space?
--Leif
Date: 97 Jun 07 8:13:43 pm
From: Joe McGuckin <joe@via.net>
To: Squeak@create.ucsb.edu
Subject: Can't find sources problem
I'm running 1.19b. The VM is in the same directory as the
image & source & changes file. If I add addition code, the vriable names
& comments get lost. Also, I can't view the sources of the image.
duke% ls -lt
total 11366
-rw-r--r-- 1 joe joe 1560908 Jun 7 20:19 clone.image
-rw-rw-r-- 1 joe joe 1682736 Jun 6 20:41 Squeak1.19d.image
-rw-rw-r-- 1 joe joe 1926023 Jun 6 20:04 SqueakV1.sources
-rw-rw-r-- 1 joe joe 1470279 Jun 6 20:04 Squeak1.19d.changes
drwxr-xr-x 2 joe joe 1024 Jun 6 20:02 Squeak1.19b/
-rw-r--r-- 1 joe joe 1425015 Apr 10 22:23 Squeak1.19b.changes
-rw-r--r-- 1 joe joe 3302400 Apr 2 04:36 Squeak1.19b.tar
-rwxr-xr-x 1 joe joe 213816 Jan 27 11:50 Squeak*
What's the problem? If I need to set something in the image, please
specify exactly what I need to type in.
Thanks!
joe
Date: 97 Jun 08 3:07:51 am
From: Ian Piumarta <piumarta@prof.inria.fr>
To: joe@via.net
Cc: Squeak@create.ucsb.edu
Subject: Re: Can't find sources problem
Joe,
> -rw-r--r-- 1 joe joe 1560908 Jun 7 20:19 clone.image
> -rw-rw-r-- 1 joe joe 1682736 Jun 6 20:41 Squeak1.19d.image
> -rw-rw-r-- 1 joe joe 1926023 Jun 6 20:04 SqueakV1.sources
> -rw-rw-r-- 1 joe joe 1470279 Jun 6 20:04 Squeak1.19d.changes
Which image are you running? If it's the default one (clone.image) then
there is no changes file "clone.changes", which is your problem. Try
starting the VM with
./Squeak Squeak1.19d.image
If you're doing this already then the problem is more serious and I don't
really know what might be causing it without looking at an execution
trace, etc. (You don't say what OS you're using, so I can't suggest the
relevant command to show you where the VM is looking for for the files.)
The sources file "SqueakV1.sources" should be found whatever the name of
the image -- but beware that a lot of the image sources are in the
changes file as there has been considerable development since the
.sources file was "frozen". To check this, you need to look at some
really *old* methods -- e.g. the arithmetic selectors in SmallInteger.
It's very important to keep your image and changes files together, with
the same prefix. Don't rename them manually if you can avoid it -- it's
safest to always use the "save as" option from a running image to create
a copy with a different name. CompiledMethods in the image contain
"pointers" into the .sources and .changes files. If they get "out of
sync", you'll see gibberish for any methods whose sources are in the
.changes file.
Send me email if the above doesn't cure your problem.
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 -----------------------
Date: 97 Jun 08 10:49:59 am
From: "David N. Smith" <dnsmith@watson.ibm.com>
To: squeak@create.ucsb.edu
Subject: Complements for shifting (LONG)
All:
Left bit shifts of negative numbers does not work the same as if the value
was in a register. Here is a test which shifts some bits left by 1 for ten
repititions. Results are shown for Squeak, IBM V3, and VW 2.5. Note how
Squeak right fills with one bits.
| i n |
n := 1.
i := 2r-101.
10 timesRepeat: [
Transcript cr; show: n printString, ' ',
((i bitAnd: 16rFFFF) printStringBase: 2).
n := n + 1.
i := i << 1 ].
1 2r1111111111111011
2 2r1111111111110111
3 2r1111111111101111
4 2r1111111111011111
5 2r1111111110111111
6 2r1111111101111111
7 2r1111111011111111
8 2r1111110111111111
9 2r1111101111111111
10 2r1111011111111111 "Squeak 1.19d"
1 1111111111111011
2 1111111111110110
3 1111111111101100
4 1111111111011000
5 1111111110110000
6 1111111101100000
7 1111111011000000
8 1111110110000000
9 1111101100000000
10 1111011000000000 "VW"
1 2r1111111111111011
2 2r1111111111110110
3 2r1111111111101100
4 2r1111111111011000
5 2r1111111110110000
6 2r1111111101100000
7 2r1111111011000000
8 2r1111110110000000
9 2r1111101100000000
10 2r1111011000000000 "IBM 3.0"
The problem is in the SmallInteger method:
bitShift: arg
"Primitive. Answer an Integer whose value is the receiver's value
shifted
left by the number of bits indicated by the argument. Negative
arguments
shift right.
Essential. See Object documentation whatIsAPrimitive."
<primitive: 17>
self < 0 ifTrue: [^ -1 - (-1-self bitShift: arg)].
^ super bitShift: arg
The ifTrue: clause incorrectly converts from twos complement negative to
positive. Here is a test which shows a better way to do it (last line). The
results are shown and they agree with VW and IBM.
| i n |
n := 1.
i := 2r-101.
10 timesRepeat: [
Transcript cr; show: n printString, ' ',
((i bitAnd: 16rFFFF) printStringBase: 2).
n := n + 1.
i := 0 - (0-i bitShift: 1) ]
1 2r1111111111111011
2 2r1111111111110110
3 2r1111111111101100
4 2r1111111111011000
5 2r1111111110110000
6 2r1111111101100000
7 2r1111111011000000
8 2r1111110110000000
9 2r1111101100000000
10 2r1111011000000000 "Squeak 1.19"
Now, modifying the method to use this new technique produces:
bitShift2: arg
"Primitive. Answer an Integer whose value is the receiver's value
shifted
left by the number of bits indicated by the argument. Negative
arguments
shift right.
Essential. See Object documentation whatIsAPrimitive."
<primitive: 17>
self < 0 ifTrue: [^ 0 - (0-self bitShift: arg)].
^ super bitShift: arg
Rerunning the initial test using bitShift2:
| i n |
n := 1.
i := 2r-101.
10 timesRepeat: [
Transcript cr; show: n printString, ' ',
((i bitAnd: 16rFFFF) printStringBase: 2).
n := n + 1.
i := i bitShift2: 1 ].
1 2r1111111111111011
2 2r1111111111110110
3 2r1111111111101100
4 2r1111111111011000
5 2r1111111110110000
6 2r1111111101100000
7 2r1111111011000000
8 2r1111110110000000
9 2r1111101100000000
10 2r1111011000000000
I suspect that whom ever wrote the original method confused two methods of
obtaining a two's complement:
(1) Invert all the bits and add 1.
(2) Subtract the value from zero.
Dave
PS: There is something bizare with long negative integers, but I've not had
time to look at it.
First, a long negative integer prints OK:
2r-11111111111111111111111111111111111111111111111101 printStringBase: 2
'-2r11111111111111111111111111111111111111111111111101'
But take a bitAnd of the bits and print that!
(2r-11111111111111111111111111111111111111111111111101 bitAnd:
2r11111111111111111111111111111111111111111111111111) printStringBase: 2
'2r11'
Where did that come from????
Then consider the loop from earlier, but with our new large negative integer:
| i n |
n := 1.
i := 2r-11111111111111111111111111111111111111111111111101.
10 timesRepeat: [
Transcript cr; show: n printString, ' ',
((i bitAnd: 16rFFFFFFFFFFFFFFFFFFFF) printStringBase: 2).
n := n + 1.
i := i bitShift: 1 ].
1 2r11111100000000000000000000000000000000000000000000000011
2 2r11111000000000000000000000000000000000000000000000000110
3 2r11110000000000000000000000000000000000000000000000001100
4 2r11100000000000000000000000000000000000000000000000011000
5 2r11000000000000000000000000000000000000000000000000110000
6 2r10000000000000000000000000000000000000000000000001100000
7 2r11000000
8 2r1111111000000000000000000000000000000000000000000000000110000000
9 2r1111110000000000000000000000000000000000000000000000001100000000
10 2r1111100000000000000000000000000000000000000000000000011000000000
Note that the mask is MUCH longer than the base 2 value.
Does this make sense? I haven't been drinking, mu glasses are relatively
clean, and while my mind is going I still remember my name. Bob, it's been
Bob all day now.
Hasn't it?
_______________________________
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.
Date: 97 Jun 09 4:51:04 am
From: "Boris G. Chr. Shingarov" <boris@visualage.dialogue.msu.su>
To: squeak@create.ucsb.edu
Subject: Immediate Objects
Dear Squeakers,
Here is another suggestion about VM optimization.
I 'ld be glad to see votes like Good / Bad / Neutral.
The idea is to make use of the second bit in the object pointer
for some immediate objects just as we use the first (LSB) bit
for 31bit Integers. So the format of object pointer will be
like this:
xxxxxxxx xxxxxxxx xxxxxxxx xxxxxxx1 Integer
xxxxxxxx xxxxxxxx xxxxxxxx xxxxxx00 ObjectHeader*
00000000 00000000 00000000 00xx1110 nil/true/false depend on xx
also maybe
xxxxxxxx xxxxxxxx 00000000 00000110 16bit word (e.g., DBCS char?)
or something like that...
I think someone already considered this, and I'm curious why this
is not in the VM. I'm not sure it will speed things like isNil
or ifTrue up, but it will eliminate some extra operations during
compaction. Or am I missing some critical drawback to my approach?
Boris
<boris@dialogue.msu.su>
Date: 97 Jun 09 5:40:29 am
From: Ian Piumarta <piumarta@prof.inria.fr>
To: boris@visualage.dialogue.msu.su
Cc: squeak@create.ucsb.edu
Subject: Re: Immediate Objects
> I 'ld be glad to see votes like Good / Bad / Neutral.
Good and bad.
> xxxxxxxx xxxxxxxx xxxxxxxx xxxxxxx1 Integer
> xxxxxxxx xxxxxxxx xxxxxxxx xxxxxx00 ObjectHeader*
> 00000000 00000000 00000000 00xx1110 nil/true/false depend on xx
> xxxxxxxx xxxxxxxx 00000000 00000110 16bit word (e.g., DBCS char?)
The problem is that encoding more things as immediates slows down
message sending (and any other operation which has to fetch the class of
an object). In the Interpreter this is bad (although fetching the class
is currently [watch this space! ;)] only a relatively small part of the
send overhead -- plus you can reduce the impact by keeping an array of
encoded classes, indexed by the low N bits of an immediate pointer,
similar to the way compact classes are encoded in object headers at the
moment).
With a dynamic translator it's probably much more of a good idea. With
an inline cache, the translated code can use "linked sends" where the
class of the receiver is predicted based on the class of the previous
receiver -- when the check succeeds, the send "short cuts" directly to
the destination method. The send opcodes can be specialised for each
kind of immediate value, and can therefore employ a very efficient check
on the class of the receiver. When the check fails, the send site is
"relinked" and the send opcode overwritten with a *different* one,
appropriate for the new receiver class (one flavour of each send opcode
for each immediate type, plus another for the general non-immediate
case). The send overhead at call sites THAT EXHIBIT LOW POLYMORPHISM is
then essentially constant, regardless of the number of immediate
encodings used -- you only pay the price for decoding the class fully
when the inline cache misses.
The problem with all of this is that beauty is not always truth. The
only way to really know whether a particular optimisation gains or loses
performance is to try it. For the immediate encodings, that's
potentially a lot of work for something which *might* not gain you much
at all in the long run.
The "smaller image" argument doesn't hold water either -- immediate
values tend to be those for which only a single, immutable instance
appears in the image. The only case I can think of in which you would
definitely gain would be avoiding 2^16 instances of UnicodeCharacter.
Ian
(Sheilds up Lt. Worf!)
------------------------------- 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 -----------------------
Date: 97 Jun 09 5:57:49 am
From: Hans-Martin Mosner <hmm@heeg.de>
To: "Boris G. Chr. Shingarov" <boris@visualage.dialogue.msu.su>
Cc: squeak@create.ucsb.edu
Subject: Re: Immediate Objects
Boris G. Chr. Shingarov wrote:
...
> The idea is to make use of the second bit in the object pointer
> for some immediate objects just as we use the first (LSB) bit
> for 31bit Integers. So the format of object pointer will be
> like this:
> xxxxxxxx xxxxxxxx xxxxxxxx xxxxxxx1 Integer
> xxxxxxxx xxxxxxxx xxxxxxxx xxxxxx00 ObjectHeader*
> 00000000 00000000 00000000 00xx1110 nil/true/false depend on xx
> also maybe
> xxxxxxxx xxxxxxxx 00000000 00000110 16bit word (e.g., DBCS char?)
> or something like that...
>
> I think someone already considered this, and I'm curious why this
> is not in the VM. I'm not sure it will speed things like isNil
> or ifTrue up, but it will eliminate some extra operations during
> compaction. Or am I missing some critical drawback to my approach?
There has been some discussion on this topic, and I even did a VM
change to allow for 2-bit tags.
One difference between my approach and yours is that I avoided the
xx10 bit combination since that is used as a sentinel value by the
garbage collector. That leaves us with
......00 ObjectHeader*
......11 SmallInteger
......01 other immediate objects
Now the discussion is open as to how the bits in these other
immediate objects should be used.
Nil/true/false as immediates is one option, two-byte characters
(read: UNICODE!) another.
A very good idea is to implement fixed point numbers. Their
range and exactness should be quite sufficient to use them in
window layout and other graphical operations, effectively
replacing slow Float operations with faster Integer ops.
Immediate floats are less attractive since the length of their
mantissa would be so limited that they'd be almost unusable.
An idea that I had was to use some immediates for references
to shared objects such as Symbols and global variable associations,
making the implementation of separate communicating object spaces
easier.
If you'd like to try this out, I have the changes needed to do it at
http://www.heeg.de/~hmm/squeak/2tagbits/
Note that this was for 1.18, not the current 1.19 VM. It should be
possible to incorporate it manually, though.
Hans-Martin
Date: 97 Jun 09 7:23:47 am
From: Joel Lucuik <Joel@ObjectPeople.com>
To: "Ted K." <tedk@wdi.disney.com>
Cc: Squeak@create.ucsb.edu
Subject: Re: DeepCopy
At 09:20 AM 6/6/97 -0700, you wrote:
>Joel,
>
>What is the special case needed for collections?
If you deepCopy a dictionary using the original recursive
mechanism, the positions get screwed because the hash values of the keys
are different in the deepCopy.
You have to copy the dictionary, then add the deepCopies of the components.
>
>
>System objects, like Display and Fonts, should be shared also. I am going
to handle >this by inserting them into the IdentityDictionary at the start
of copying. They map >to themselves instead of a copy. They are in the
dictionary as if they had already >been encountered in the tree search.
I would recommend making deepCopy call 'deepCopy: identityDictionary',
where deepCopy: can be overridden.
Override deepCopy: to return self for Displays and Fonts. Its cleaner (in
my opinion) and more efficient.
Date: 97 Jun 09 9:25:23 am
From: gregory@eng.adaptec.com (Greg Gritton x2386)
To: boris@visualage.dialogue.msu.su, hmm@heeg.de
Cc: squeak@create.ucsb.edu
Subject: Re: Immediate Objects
Hi,
One of the reasons floating point calculations are so slow
in most versions of smalltalk is that new object have to be
created to store the result of every floating-point operation.
This results in significant time and space overhead.
Although hard to avoid for double-precision match, it would
be nice to be able to store single-precision floating point
numbers directly in the object pointer in a similar way
that Small Integers are stored. Self also uses this method.
In addition, a seperate tag for Unicode values would also
be quite useful, so we don't have thousands of unicode objects
floating around.
Self's tags are something like
......00 ObjectPointer
......01 SmallInteger
......10 Float
......11 ObjectHeader
We could use something like:
.......1 SmallInteger
.....000 ObjectPointer
.....010 Reserved for GC
.....100 Float
.....110 Unicode, and/or other reserved value
A 29-bit float would permit a 1-bit sign, 7-bit exponent, and 21-bit
mantissa. This would give a 6+ decimal digit significance to the
mantissa, rather than the 24-bit, 7+ digit, mantissa normally used
for single-precision float. Double-precision floats should still be
available to higher-precision calculations.
The disadvantage of this method is that it requires more complex
tags and adds another type of floating point number.
It also requires that objects be aligned to 8-byte boundaries.
The advantage would be faster and less memory intensive single-precision
floating-point and unicode operations. Double-precision floating
point operations might also be speeded up slightly, as objects
allocated at 8-byte boundaries, with 8-bytes for the hader (4 byte
header + 4 byte class pointer) would mean that the data portion
of an object is also 8-byte aligned.
If requiring 8-byte alignment for objects is considered a significant
disadvantage, the following alternative encoding could be used.
......00 ObjectPointer
......01 SmallInteger
......10 Reserved for GC
.....011 Float
.....111 Unicode, and/or other reserved value
This is the disadvantage of requiring a more complex test for SmallIntegers
as well as reducing their range.
I don't know if using the reserved values for True, False, ect.
really has much value. There are very few of these special objects.
On the other hand, there are many possible Float or Unicode values.
Greg Gritton
> From owner-squeak@create.ucsb.edu Mon Jun 9 07:39:05 1997
> Date: Mon, 09 Jun 1997 14:53:01 +0200
> From: Hans-Martin Mosner <hmm@heeg.de>
> Organization: Georg Heeg Objektorientierte Systeme
> X-Mailer: Mozilla 3.01Gold (X11; I; SunOS 4.1.3 sun4c)
> Mime-Version: 1.0
> To: "Boris G. Chr. Shingarov" <boris@visualage.dialogue.msu.su>
> Cc: squeak@create.ucsb.edu
> Subject: Re: Immediate Objects
> Content-Type> : > text/plain> ; > charset=us-ascii>
> Content-Transfer-Encoding: 7bit
> Sender: owner-squeak@create.ucsb.edu
> Content-Length: 2137
>
> Boris G. Chr. Shingarov wrote:
> ...
> > The idea is to make use of the second bit in the object pointer
> > for some immediate objects just as we use the first (LSB) bit
> > for 31bit Integers. So the format of object pointer will be
> > like this:
> > xxxxxxxx xxxxxxxx xxxxxxxx xxxxxxx1 Integer
> > xxxxxxxx xxxxxxxx xxxxxxxx xxxxxx00 ObjectHeader*
> > 00000000 00000000 00000000 00xx1110 nil/true/false depend on xx
> > also maybe
> > xxxxxxxx xxxxxxxx 00000000 00000110 16bit word (e.g., DBCS char?)
> > or something like that...
> >
> > I think someone already considered this, and I'm curious why this
> > is not in the VM. I'm not sure it will speed things like isNil
> > or ifTrue up, but it will eliminate some extra operations during
> > compaction. Or am I missing some critical drawback to my approach?
>
> There has been some discussion on this topic, and I even did a VM
> change to allow for 2-bit tags.
> One difference between my approach and yours is that I avoided the
> xx10 bit combination since that is used as a sentinel value by the
> garbage collector. That leaves us with
> ......00 ObjectHeader*
> ......11 SmallInteger
> ......01 other immediate objects
>
> Now the discussion is open as to how the bits in these other
> immediate objects should be used.
>
> Nil/true/false as immediates is one option, two-byte characters
> (read: UNICODE!) another.
>
> A very good idea is to implement fixed point numbers. Their
> range and exactness should be quite sufficient to use them in
> window layout and other graphical operations, effectively
> replacing slow Float operations with faster Integer ops.
>
> Immediate floats are less attractive since the length of their
> mantissa would be so limited that they'd be almost unusable.
>
> An idea that I had was to use some immediates for references
> to shared objects such as Symbols and global variable associations,
> making the implementation of separate communicating object spaces
> easier.
>
> If you'd like to try this out, I have the changes needed to do it at
> http://www.heeg.de/~hmm/squeak/2tagbits/
>
> Note that this was for 1.18, not the current 1.19 VM. It should be
> possible to incorporate it manually, though.
>
> Hans-Martin
>
Date: 97 Jun 09 11:50:42 am
From: Leandro Caniglia <caniglia@mate.dm.uba.ar>
To: 'Squeak' <squeak@create.ucsb.edu>
Subject: RE: Complements for shifting (LONG)
David N. Smith wrote
>bitShift2: arg
> "Primitive. Answer an Integer whose value is the receiver's value =
shifted
> left by the number of bits indicated by the argument. Negative =
arguments
> shift right.
> Essential. See Object documentation whatIsAPrimitive."
>
> <primitive: 17>
> self < 0 ifTrue: [^ 0 - (0-self bitShift: arg)].
> ^ super bitShift: arg
You are right. Doing this you are multiplying by 2 when arg is 1, by 4 =
when arg is 2 and so on. Answering [-1 - (-1-self bitShift: arg)] is =
wrong.
>PS: There is something bizare with long negative integers, but I've not =
had
>time to look at it.
>(2r-11111111111111111111111111111111111111111111111101 bitAnd:
>2r11111111111111111111111111111111111111111111111111) printStringBase: =
2
>'2r11'
>Where did that come from????
That came from the representation of the negative receiver of the =
message.The representation should be something like this:
your number -> - =
0....011111111111111111111111111111111111111111111111101
represents as -> =
1....100000000000000000000000000000000000000000000000011
thus, masking it you obtain: 11. So, the answer from Squeak seems to be =
right.
>Then consider the loop from earlier, but with our new large negative =
integer:
>
>| i n |
>n :=3D 1.
>i :=3D 2r-11111111111111111111111111111111111111111111111101.
>10 timesRepeat: [
> Transcript cr; show: n printString, ' ',
> ((i bitAnd: 16rFFFFFFFFFFFFFFFFFFFF) printStringBase: 2).
> n :=3D n + 1.
> i :=3D i bitShift: 1 ].
>
>
>1 2r11111100000000000000000000000000000000000000000000000011
>2 2r11111000000000000000000000000000000000000000000000000110
>3 2r11110000000000000000000000000000000000000000000000001100
>4 2r11100000000000000000000000000000000000000000000000011000
>5 2r11000000000000000000000000000000000000000000000000110000
>6 2r10000000000000000000000000000000000000000000000001100000
>7 2r11000000
>8 2r1111111000000000000000000000000000000000000000000000000110000000
>9 2r1111110000000000000000000000000000000000000000000000001100000000
>10 2r1111100000000000000000000000000000000000000000000000011000000000
>
>Note that the mask is MUCH longer than the base 2 value.
>
>Does this make sense?
The results that I've got in my Squeak 1.19d [Windows version] were =
correct and different from these you obtained!
Saludos,
Leandro
Date: 97 Jun 09 1:10:43 pm
From: Maloney <johnm@wdi.disney.com>
To: gregory@eng.adaptec.com (Greg Gritton x2386)
Cc: squeak@create.ucsb.edu
In-Reply-To: <9706091647.AA24233@eng.adaptec.com>
Subject: Floats
Greg:
Re:
>Although hard to avoid for double-precision match, it would
>be nice to be able to store single-precision floating point
>numbers directly in the object pointer in a similar way
>that Small Integers are stored. Self also uses this method.
>In addition, a seperate tag for Unicode values would also
>be quite useful, so we don't have thousands of unicode objects
>floating around.
People that I've talked to who are serious about number crunching
don't bother with single precision floats and tend to be
mistrustful of anything but pure IEEE. I think Self made the best
possible choice by giving up bits in the exponent rather than the
mantissa, but users still wanted to be able to depend on numerical
methods that had been carefully analyzed and tested against
the IEEE float spec.
A different approach would be to implement a FloatVector type
along with primitives for the most common vector operations
(vector sum, dot and cross products, multiplication by a scalor, etc.).
These primitives would modify the vector in place, thus avoiding
allocation costs.
Finally, it is always worth trying one's computation with Squeak's
existing Floats. Even with the allocation and GC costs, they are
surprisingly fast. And, they are real IEEE double-precision Floats.
-- John
Date: 97 Jun 09 1:30:30 pm
From: "David N. Smith" <dnsmith@watson.ibm.com>
To: gregory@eng.adaptec.com (Greg Gritton x2386)
Cc: boris@visualage.dialogue.msu.su, hmm@heeg.de, squeak@create.ucsb.edu
In-Reply-To: <9706091647.AA24233@eng.adaptec.com>
Subject: Re: Immediate Objects
At 12:47 -0400 6/9/97, Greg Gritton x2386 wrote:
>Hi,
>
>One of the reasons floating point calculations are so slow
>in most versions of smalltalk is that new object have to be
>created to store the result of every floating-point operation.
>This results in significant time and space overhead.
>
>Although hard to avoid for double-precision match, it would
>be nice to be able to store single-precision floating point
>numbers directly in the object pointer in a similar way
>that Small Integers are stored. Self also uses this method.
>In addition, a seperate tag for Unicode values would also
>be quite useful, so we don't have thousands of unicode objects
>floating around.
>
>Self's tags are something like
>......00 ObjectPointer
>......01 SmallInteger
>......10 Float
>......11 ObjectHeader
>
>We could use something like:
>.......1 SmallInteger
>.....000 ObjectPointer
>.....010 Reserved for GC
>.....100 Float
>.....110 Unicode, and/or other reserved value
>
>A 29-bit float would permit a 1-bit sign, 7-bit exponent, and 21-bit
>mantissa. This would give a 6+ decimal digit significance to the
>mantissa, rather than the 24-bit, 7+ digit, mantissa normally used
>for single-precision float. Double-precision floats should still be
>available to higher-precision calculations.
>
>The disadvantage of this method is that it requires more complex
>tags and adds another type of floating point number.
>It also requires that objects be aligned to 8-byte boundaries.
>The advantage would be faster and less memory intensive single-precision
>floating-point and unicode operations. Double-precision floating
>point operations might also be speeded up slightly, as objects
>allocated at 8-byte boundaries, with 8-bytes for the hader (4 byte
>header + 4 byte class pointer) would mean that the data portion
>of an object is also 8-byte aligned.
>
>If requiring 8-byte alignment for objects is considered a significant
>disadvantage, the following alternative encoding could be used.
>
>......00 ObjectPointer
>......01 SmallInteger
>......10 Reserved for GC
>.....011 Float
>.....111 Unicode, and/or other reserved value
>
>This is the disadvantage of requiring a more complex test for SmallIntegers
>as well as reducing their range.
>
>I don't know if using the reserved values for True, False, ect.
>really has much value. There are very few of these special objects.
>On the other hand, there are many possible Float or Unicode values.
>
>Greg Gritton
>
Small floats are already too small. The only sensible way to make one
smaller is to remove bits from the exponent and leave the fraction alone
since this means you can actually quickly convert one to a single, do the
operation, and convert back if the exponent still fits, without having to
worry about proper rounding and other nastys. It also leaves values encoded
in a NAN (Not-A-Number) unchanged.
However, this makes a float with with a 5 bit exponent, one of which is
essentially the sign. Since the exponent is base-2, this means that the
values have a very limited exponent range, and probably very limited use.
Remember: floats are designed for problems which have large exponent ranges.
No one doing computations likes single precision, using it only when memory
limits forces it to be used. A 29-bit (or even 30-bit) value is hopeless.
When Squeak goes to a 64-bit object pointer, then there is hope. All object
http://www.dnsmith.com/dnsmith/Smalltalk/index.html
Then download the OOPSLA workshop paper on floating-point extensions. It
describes a bit more about how to encode everything as a double.
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.
Date: 97 Jun 09 1:31:25 pm
From: "David N. Smith" <dnsmith@watson.ibm.com>
To: Maloney <johnm@wdi.disney.com>
Cc: gregory@eng.adaptec.com (Greg Gritton x2386), squeak@create.ucsb.edu
In-Reply-To: <v03007802afc2161a4c5c@[206.16.10.72]>
Subject: Re: Floats
At 17:36 -0400 6/9/97, Maloney wrote:
>Greg:
>
>Re:
>>Although hard to avoid for double-precision match, it would
>>be nice to be able to store single-precision floating point
>>numbers directly in the object pointer in a similar way
>>that Small Integers are stored. Self also uses this method.
>>In addition, a seperate tag for Unicode values would also
>>be quite useful, so we don't have thousands of unicode objects
>>floating around.
>
>People that I've talked to who are serious about number crunching
>don't bother with single precision floats and tend to be
>mistrustful of anything but pure IEEE. I think Self made the best
>possible choice by giving up bits in the exponent rather than the
>mantissa, but users still wanted to be able to depend on numerical
>methods that had been carefully analyzed and tested against
>the IEEE float spec.
>
>A different approach would be to implement a FloatVector type
>along with primitives for the most common vector operations
>(vector sum, dot and cross products, multiplication by a scalor, etc.).
>These primitives would modify the vector in place, thus avoiding
>allocation costs.
>
>Finally, it is always worth trying one's computation with Squeak's
>existing Floats. Even with the allocation and GC costs, they are
>surprisingly fast. And, they are real IEEE double-precision Floats.
>
> -- John
Amen. I agree completely.
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.
Date: 97 Jun 11 7:02:35 am
From: "David N. Smith" <dnsmith@watson.ibm.com>
To: squeak@create.ucsb.edu
In-Reply-To: <v03102802afc09acbc7ed@[129.34.225.178]>
Subject: Re: Complements for shifting (LONG)
At 14:17 -0400 6/8/97, David N. Smith wrote:
>All:
>
>Left bit shifts of negative numbers does not work the same as if the value
>was in a register. Here is a test which shifts some bits left by 1 for ten
>repititions. Results are shown for Squeak, IBM V3, and VW 2.5. Note how
>Squeak right fills with one bits.
>
>...SNIP...
My mistake. I had made a suggested fix to #bitAnd: and then forgotten it
was there. I should have removed it and tested further before I posted.
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.
Date: 97 Jun 11 1:48:42 pm
From: "David N. Smith" <dnsmith@watson.ibm.com>
To: squeak@create.ucsb.edu
Yawn, another asTrueFraction method.
This one is the combined efforts of Luciano Esteban Notarfrancesco, who
suggested (and implemented) some serious performance improvements, and
myself. The 'base version' in the table below is the one Dan distributed
some time ago and not the one I sent around a few weeks ago. The timings
below are on a PPC9500/200 and represent 1000 invocations.
Float pi 1.0e200 1.0e-200
-------- ------- --------
New version 1230 3380 3900
Base version 8860 7100 31350
Timings are identical for negative numbers.
The improvements come from avoiding #gcd: when possible, and generally
paying attention to what we were doing.
The algorithm needs to know the number of low-order zero bits, and rather
then building it in I added a lowBit method to Integer (actually two, one
for SmallInteger that actually does the work). They parallel the way
highBit works.
!Float methodsFor: 'converting'!
asTrueFraction
" Answer a fraction that EXACTLY represents self,
a double precision IEEE floating point number.
Floats are stored in the same form on all platforms.
(Does not handle gradual underflow or NANs.)
By David N. Smith with significant performance
improvements by Luciano Esteban Notarfrancesco.
(Version of 11April97)"
| shifty sign expPart exp fraction fractionPart result zeroBitsCount |
" Extract the bits of an IEEE double float "
shifty := ((self basicAt: 1) bitShift: 32) + (self basicAt: 2).
" Extract the sign and the biased exponent "
sign := (shifty bitShift: -63) = 0 ifTrue: [1] ifFalse: [-1].
expPart := (shifty bitShift: -52) bitAnd: 16r7FF.
" Extract fractional part; answer 0 if this is a true 0.0 value "
fractionPart := shifty bitAnd: 16r000FFFFFFFFFFFFF.
( expPart=0 and: [ fractionPart=0 ] ) ifTrue: [ ^ 0 ].
" Replace omitted leading 1 in fraction "
fraction := fractionPart bitOr: 16r0010000000000000.
"Unbias exponent: 16r3FF is bias; 52 is fraction width"
exp := 16r3FF + 52 - expPart.
" Form the result. When exp>52, the exponent is adjusted by
the number of trailing zero bits in the fraction to minimize
the (huge) time otherwise spent in #gcd:. "
exp negative
ifTrue: [
result := sign * fraction bitShift: exp negated ]
ifFalse: [
zeroBitsCount _ fraction lowBit - 1.
exp := exp - zeroBitsCount.
exp <= 0
ifTrue: [
zeroBitsCount := zeroBitsCount + exp.
"exp := 0." " Not needed; exp not
refernced again "
result := sign * fraction bitShift:
zeroBitsCount negated ]
ifFalse: [
result := Fraction
numerator: (sign * fraction
bitShift: zeroBitsCount negated)
denominator: (1 bitShift:
exp) ] ].
" Validate the result (low cost; optional); answer result "
(result asFloat = self)
ifFalse: [self error: 'asTrueFraction validation failed' ].
^ result ! !
!SmallInteger methodsFor: 'bit manipulation'!
lowBit
" Answer the index of the low order one bit.
2r00101000 lowBit (Answers: 4)
2r-00101000 lowBit (Answers: 4)
First we skip bits in groups of 4, then single bits.
While not optimal, this is a good tradeoff; long
integer #lowBit always invokes us with bytes."
| n result |
n := self.
n = 0 ifTrue: [ ^ 0 ].
result := 1.
[ (n bitAnd: 16rF) = 0 ]
whileTrue: [
result := result + 4.
n := n bitShift: -4 ].
[ (n bitAnd: 1) = 0 ]
whileTrue: [
result := result + 1.
n := n bitShift: -1 ].
^ result! !
!Integer methodsFor: 'bit manipulation'!
lowBit
"Answer the index of the low order bit of this number."
| index |
self = 0 ifTrue: [ ^ 0 ].
index := 1.
[ (self digitAt: index) = 0 ]
whileTrue:
[ index := index + 1 ].
^ (self digitAt: index) lowBit + (8 * (index - 1))! !
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.
Date: 97 Jun 12 1:37:58 pm
From: "David N. Smith" <dnsmith@watson.ibm.com>
To: squeak@create.ucsb.edu
Subject: PPC Development Environment
All:
I know I've seen it someplace obvious, but I cannot find it now. What is
the preferred C/C++ development environment for Squeak on a PPC?
Thanks,
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.
Date: 97 Jun 12 3:13:23 pm
From: lnotarfr@dc.uba.ar (Luciano Esteban Notarfrancesco)
To: jecel@lsi.usp.br (Jecel Mattos de Assumpcao Jr.)
Cc: squeak@create.ucsb.edu
In-Reply-To: <199706062131.SAA04753@bia.usp.br> from "Jecel Mattos de Assumpcao Jr." at Jun 6, 97 06:31:45 pm
Subject: Morphs and native windows
> In Self you can make the system move any morph to its
> own window, which is very much like this. I would
> prefer it if any morph (not just a worldMorph) could
> be mapped to an OS window. That would be simpler and
> would feel closer to a native application (in the current
> system you can resize the window and move the morph
> around in it).
I like this a lot. Is someone working on this? Is the working
Morphic group going this way?
This should be easy to do in any plataform. It's quite simple
and generic.
Luciano.-
Date: 97 Jun 12 4:10:21 pm
From: Maloney <johnm@wdi.disney.com>
To: "David N. Smith" <dnsmith@watson.ibm.com>
Cc: squeak@create.ucsb.edu
In-Reply-To: <v03102801afc613e604ce@[9.2.186.178]>
Subject: Re: PPC Development Environment
>All:
>
>I know I've seen it someplace obvious, but I cannot find it now. What is
>the preferred C/C++ development environment for Squeak on a PPC?
>
>Thanks,
>
>Dave
We used CodeWarrior. Others have had success with Apple's MPW.
I believe someone has also compiled or cross-compiled it using
Gnu's gcc compiler.
-- John
Date: 97 Jun 13 4:35:50 am
From: Ian Piumarta <piumarta@prof.inria.fr>
To: dnsmith@watson.ibm.com, johnm@wdi.disney.com
Cc: squeak@create.ucsb.edu
Subject: Re: PPC Development Environment
> I believe someone has also compiled or cross-compiled it using
> Gnu's gcc compiler.
That would be me (with help from our local MacGuru ;-).
GCC under MachTen produces an XCOFF file which can be imported (suitably
renamed) into a CodeWarrior project and linked with the rest of the
regular stuff.
Significant juggling with include files was necessary to make this work.
Ian
Date: 97 Jun 14 9:59:10 am
From: Stefan Matthias Aust <sma@kiel.netsurf.de>
To: squeak@create.ucsb.edu
Subject: Small bug in Formatter code
Hi!
I think, I've detected a small bug inside the formatter code. I tried to
decompile the method Object>>caseOf: (I've no source code)
The MacroPrinters class variable of MessageNode is initialized with
#printCase:indent:. This method doesn't exists and it must probably changed
to #printCaseOn:indent:.
But now #printCaseOn:indent: sends #casesForwardDo: to its first argument,
which is a TempVariableNode and not a BraceNode, the only node that
understands #casesForwardDo:.
bye
--
Stefan Matthias Aust // Planet Claire has pink air!
http://www.kiel.netsurf.de/users/s/sma/
Date: 97 Jun 14 12:29:15 pm
From: "Boris G. Chr. Shingarov" <boris@visualage.dialogue.msu.su>
To: squeak@create.ucsb.edu
Subject: OS/2
Dear Squeakers,
A refresh for Squeak OS/2 patch is on
ftp://visualage.dialogue.msu.su/pub/smalltalk/squeak.
(these are bug fixes; see Readme.os2 inside)
Boris
Date: 97 Jun 15 12:51:01 pm
From: "Andreas Raab" <raab@isg.cs.uni-magdeburg.de>
To: "Bob" <mailbox@home.com>
Cc: squeak@create.ucsb.edu
Subject: Re: Urgent Help: A bug in your Squeak port??!
Hi,
> I have the "Squeak1-19d.changes" file in the SAME folder as "squeak.exe".
> However, upon opening Squeak a dialog box appears every time stating
> "Squeak Warning: The Squeak changes file could not be found. OK". How do
> you get Squeak to find the changes file?
You should copy the changes into the same directory where your image
resides. The executable can actually be anywhere. If this doesn't
work, send me a note.
> My other question is -- how to change the default font size for use of
> Squeak on high-res (ex: 20 inch) monitors where the text is microscopic?
> Can you e-mail me the code and instructions to set the default font to the
> built-in 12 or 18 point sizes? This would make all screen text and menus
> (browsers, workspace, etc.) appear in the new font size setting.
>
> I know you can toggle with ALT-1,2,3,4 and CTRL-K but I want a permanent
> change in size for ALL text. If your code can include a new GUI menu for
> global change of the default font size that will be great. Even just a
> piece of code to accomplish the global size change through a "do It" will
> be fine. Will a global font size change cause any "side effects"?
I'm not sure about this, but I'll forward the question to the squeak
mailing list. Probably someone there can help you.
> Also, Is there any documentation as to how Squeak differs from Smalltalk-80
> and how the Win32 Squeak port differs from the Mac version?
Win32 Squeak differs from Mac mainly by not supporting 2 bit color
depth (however 1,4,8,16 and 32 bit are supported). Except from this
there _should_ be no difference (even the networking primitives from
1.19 are already supported). If you find anything which is not as it
should send me a note.
> What are your plans for enhancements to your port?
The "port" itself will not be enhanced much. Most of the development
is concerned with portable enhancements which will be rapidly available on
all supported platforms when released.
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 >=============+
Date: 97 Jun 15 12:53:20 pm
From: "Andreas Raab" <raab@isg.cs.uni-magdeburg.de>
To: squeak@create.ucsb.edu
Subject: Font styles and sizes
Hi,
I just got an email with a question about permanently changing font
styles and sizes. Since I couldn't rapidly figure out how to do it
I'd be happy if anyone could comment on this.
Bob wrote:
> My other question is -- how to change the default font size for use of
> Squeak on high-res (ex: 20 inch) monitors where the text is microscopic?
> Can you e-mail me the code and instructions to set the default font to the
> built-in 12 or 18 point sizes? This would make all screen text and menus
> (browsers, workspace, etc.) appear in the new font size setting.
>
> I know you can toggle with ALT-1,2,3,4 and CTRL-K but I want a permanent
> change in size for ALL text. If your code can include a new GUI menu for
> global change of the default font size that will be great. Even just a
> piece of code to accomplish the global size change through a "do It" will
> be fine. Will a global font size change cause any "side effects"?
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 >=============+
Date: 97 Jun 15 1:38:47 pm
From: "David N. Smith" <dnsmith@watson.ibm.com>
To: squeak@create.ucsb.edu
Subject: Writing into a ReadStream
Try this in 1.19d:
| s |
s := ReadStream on: 'asdf'.
s next: 2 put: $z.
s contents
It answers:
'zzdf'
I suspect that ReadStream should report an error ;-)
Dave
(Cheezzzee, what is he doing that he finds this junk????)
_______________________________
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.
Date: 97 Jun 16 8:33:07 am
From: Dan Ingalls <DanI@wdi.disney.com>
To: "Andreas Raab" <raab@isgnw.cs.Uni-Magdeburg.DE>
Cc: Squeak@create.ucsb.edu
In-Reply-To: <22E40F47AAB@isgnw.cs.uni-magdeburg.de>
Subject: Re: Font styles and sizes
>I just got an email with a question about permanently changing font
>styles and sizes. Since I couldn't rapidly figure out how to do it
>I'd be happy if anyone could comment on this.
>
>Bob wrote:
>> My other question is -- how to change the default font size for use of
>> Squeak on high-res (ex: 20 inch) monitors where the text is microscopic?
>> Can you e-mail me the code and instructions to set the default font to the
>> built-in 12 or 18 point sizes? This would make all screen text and menus
>> (browsers, workspace, etc.) appear in the new font size setting.
>>
>> I know you can toggle with ALT-1,2,3,4 and CTRL-K but I want a permanent
>> change in size for ALL text. If your code can include a new GUI menu for
>> global change of the default font size that will be great. Even just a
>> piece of code to accomplish the global size change through a "do It" will
>> be fine. Will a global font size change cause any "side effects"?
Since this is a frequent request, I'll do my best to answer, and make a note to make this easy in the next release.
Here is the current default font set...
TextStyle default fontArray
(a StrikeFont(NewYork10)
a StrikeFont(NewYork12)
a StrikeFont(NewYork18)
a StrikeFont(NewYork24) )
First change the def of SSView labelHeight as follows...
labelHeight
^ (LabelStyle fontAt: 2) height + 4
Now the following do-its should make the default font be 18-pt...
TextConstants at: #DefaultTextStyle put:
(TextStyle fontArray: (#(3 4 1 2) collect: [:i | TextStyle default fontAt: i])).
PopUpMenu initialize. "Change this method for difft menu font"
ListParagraph initialize. "Change this method for difft ListPane font"
StandardSystemView initialize. "Change this method for difft Window label font"
"Note you may also want to change label: and labelHeight"
You will need to re-open most windows to get the updated effect.
Note that I tested this only in our lates un-released system, but it should work in 1.19.
However, I highly recommend including the window label change that I posted.
Let me know of problems or improvements.
- Dan
Date: 97 Jun 16 11:05:07 am
From: Dan Ingalls <DanI@wdi.disney.com>
To: "Andreas Raab" <raab@isgnw.cs.Uni-Magdeburg.DE>
Cc: Squeak@create.ucsb.edu
In-Reply-To: <22E40F47AAB@isgnw.cs.uni-magdeburg.de>
Subject: Re: Font styles and sizes
--============_-1345633044==_============
Content-Type: text/plain; charset="us-ascii"
P.S.
1. The example code I gave in the last message gives you 18-points as the default, which may be too extreme. Obviously, you could equally easily do...
>TextConstants at: #DefaultTextStyle put:
> (TextStyle fontArray: (#(2 3 4 1) collect: [:i | TextStyle default fontAt: i])).
...to make your default font be 12-point instead of 10 (but not 18).
2. Also note that this hacky way of doing it cannot be repeated, because it rearranges the fonts in TextStyle default.
3. As with any such image hacks, you should save your image, make this change, and then check it out well before saving it as your image of choice.
4. Finally, in case you want, but don't have the label change to which I alluded (makes squeak labels look less mac-like, but not like anything else in particular), I've attached that.
- Dan
--============_-1345633044==_============
Content-Type: text/plain; name="NewLabels-di.cs"; charset="us-ascii"
Content-Disposition: attachment; filename="NewLabels-di.cs"
'From Squeak 1.19d of April 13, 1997 on 2 May 1997 at 4:07:16 pm'!
!StandardSystemView methodsFor: 'label access'!
setLabelRegion
"Always follows view width"
labelFrame region: (0 @ 0 extent: self displayBox width @ self labelHeight).! !
!StandardSystemView methodsFor: 'displaying'!
deEmphasizeLabel
"Un-Highlight the label."
self displayLabelBackground: false.
self displayLabelText.!
displayLabelBackground: emphasized
"Clear or emphasize the inner region of the label"
| r1 r2 r3 c3 c2 c1 |
emphasized ifFalse:
["Just clear the label if not emphasized"
^ Display fill: (self labelDisplayBox insetBy: 2) fillColor: self labelColor].
r1 _ self labelDisplayBox insetBy: 2.
r2 _ r1 insetBy: 0@2.
r3 _ r2 insetBy: 0@3.
c3 _ self labelColor.
c2 _ c3 darker.
c1 _ c2 darker darker.
Display fill: r1 fillColor: c1.
Display fill: r2 fillColor: c2.
Display fill: r3 fillColor: c3.
" Here is the Mac racing stripe code
stripes _ Bitmap with: (self labelColor pixelWordForDepth: Display depth)
with: (Form black pixelWordForDepth: Display depth).
self windowOrigin y even ifTrue: [stripes swap: 1 with: 2].
Display fill: (self labelDisplayBox insetBy: 3) fillColor: stripes.
"!
displayLabelText
"The label goes in the center of the window"
| labelRect |
labelText foregroundColor: self foregroundColor
backgroundColor: self labelColor.
labelRect _ self labelTextRegion.
Display fill: (labelRect expandBy: 3@0) fillColor: self labelColor.
labelText displayOn: Display at: labelRect topLeft clippingBox: labelRect
rule: labelText rule fillColor: labelText fillColor!
emphasizeLabel
"Highlight the label."
self displayLabelBackground: true.
self displayLabelBoxes.
self displayLabelText.! !
!StandardSystemView methodsFor: 'label access'!
labelHeight
^ (LabelStyle fontAt: 2) height + 4! !
StandardSystemView removeSelector: #displayRacingStripes!
--============_-1345633044==_============--
Date: 97 Jun 16 11:43:34 am
From: Dan Ingalls <DanI@wdi.disney.com>
To: Squeak@create.ucsb.edu
Subject: Possible source of crashes - fixed
--============_-1345630758==_============
Content-Type: text/plain; charset="us-ascii"
The attached fileIn fixes the problem of crashes due to encountering an (otherwise benign) error immediately after changing projects or changing display depth.
It was due to antediluvian code in ControlManager>>deactive that nilled the active controller process for no apparent reason. This resulted in a crash if a debugger got scheduled before any other window change.
I have tried this code in 1.19, and it "should" work in 1.18 as well.
- Dan
--============_-1345630758==_============
Content-Type: text/plain; name="DeactivateFix-di.cs"; charset="us-ascii"
Content-Transfer-Encoding: quoted-printable
Content-Disposition: attachment; filename="DeactivateFix-di.cs"
'From Squeak 1.19d of April 13, 1997 on 16 June 1997 at 11:50:52 am'!
"Change Set: DeactivateFix
Date: 16 June 1997
Author: Dan Ingalls
Does away with antediluvian code in Controlmanager deactivate which caused=
the activeControllerProcess to be nilled out. This had been called at=
every project change and every call on Display newDepth:, and would cause a=
crash of Squeak if an error occurred between that time and the next window =
change."!
!ClassDescription methodsFor: 'fileIn/Out'!
methodsFor: categoryName stamp: changeStamp
^ self methodsFor: categoryName! !
!ControlManager class methodsFor: 'snapshots' stamp: 'di 6/16/97 11:42'!
shutDown "Saves space in snapshots"
ScheduledControllers unCacheWindows! !
!DisplayScreen methodsFor: 'private' stamp: 'di 6/16/97 11:36'!
newDepth: pixelSize
"
Display newDepth: 8.
Display newDepth: 1.
"
self newDepthNoRestore: pixelSize.
ScheduledControllers unCacheWindows; restore.! !
!Project methodsFor: 'menu messages' stamp: 'di 6/16/97 11:39'!
saveState
"Save the current state in me prior to switching projects"
world isMorph ifTrue: [world _ World]
ifFalse: [world _ ScheduledControllers.
ScheduledControllers unCacheWindows].
changeSet _ Smalltalk changes.
transcript _ Transcript.
displayDepth _ Display depth.
! !
ControlManager removeSelector: #deactivate!
--============_-1345630758==_============--
Date: 97 Jun 16 5:29:24 pm
From: "Dwight Hughes" <dwighth@intellinet.com>
To: <Squeak@create.ucsb.edu>
Subject: Using Symantec C/C++?
Has anyone successfully used Symantec C/C++ 7.5 (or earlier)
to compile the VM files for Win95/NT? I'm using it because
it's good and, more importantly, "free" (for me anyway) --
but I am having problems getting the sqWin32Directory.c file
to compile. The struct _finddata_t is "undefined" and I can't
seem to find any equivalents to use. Am I overlooking
something obvious?
Suggestions appreciated.
-- Dwight
Date: 97 Jun 16 7:22:36 pm
From: dave <drs@cs.wisc.edu>
To: Dwight Hughes <dwighth@intellinet.com>
Cc: squeak@create.ucsb.edu
Subject: Re: Using Symantec C/C++?
Dwight Hughes wrote:
>
> Has anyone successfully used Symantec C/C++ 7.5 (or earlier)
> to compile the VM files for Win95/NT? I'm using it because
> it's good and, more importantly, "free" (for me anyway) --
> but I am having problems getting the sqWin32Directory.c file
> to compile. The struct _finddata_t is "undefined" and I can't
> seem to find any equivalents to use. Am I overlooking
> something obvious?
>
> Suggestions appreciated.
>
> -- Dwight
No, I re-compiled using a win32 port of GCC and found I had to
re-write portions of sqWin32Directory also (and a few other
places, too.)
I think using win32 functions would have been more appropriate here.
Andreas drew heavily on the MS C library, and this puts anybody
without VC at something of a disadvantage. win32 has (paradoxically
I guess) become a lingua franca.
I think I used used FindFirstFile, FindNextFile, and WIN32_FIND_DATA
for that part of the code. If you need links to the on-line
documentation at MS, let me know.
Regards,
Dave
Date: 97 Jun 16 8:00:04 pm
From: "Dwight Hughes" <dwighth@intellinet.com>
To: <drs@cs.wisc.edu>
Cc: <squeak@create.ucsb.edu>
Subject: Re: Using Symantec C/C++?
| From: dave <drs@cs.wisc.edu>
|
| Dwight Hughes wrote:
| >
| > Has anyone successfully used Symantec C/C++ 7.5 (or earlier)
| > to compile the VM files for Win95/NT? I'm using it because
| > it's good and, more importantly, "free" (for me anyway) --
| > but I am having problems getting the sqWin32Directory.c file
| > to compile. The struct _finddata_t is "undefined" and I can't
| > seem to find any equivalents to use. Am I overlooking
| > something obvious?
| >
| > Suggestions appreciated.
| >
| > -- Dwight
|
| No, I re-compiled using a win32 port of GCC and found I had to
| re-write portions of sqWin32Directory also (and a few other
| places, too.)
| I think using win32 functions would have been more appropriate here.
| Andreas drew heavily on the MS C library, and this puts anybody
| without VC at something of a disadvantage. win32 has (paradoxically
| I guess) become a lingua franca.
|
| I think I used used FindFirstFile, FindNextFile, and WIN32_FIND_DATA
| for that part of the code. If you need links to the on-line
| documentation at MS, let me know.
|
| Regards,
| Dave
Ahhh, I was afraid of that. I think I have enough info in the various
help files to get something done with this approach.
Thanks.
-- Dwight
(BTW, would you mind sharing your version of sqWin32Directory.c? I'm
not picky about how beautiful it might or might not be.)
Date: 97 Jun 17 4:21:41 am
From: "Andreas Raab" <raab@isg.cs.uni-magdeburg.de>
To: squeak@create.ucsb.edu
Cc: "Bob" <mailbox@home.com>
Subject: [Win32] - small VM fix
Hi,
some of you may have noted that even if the changes files are there
the VM complains about a missing changes file. This happens only on
Win95 (and only under certain circumstances). While it is no
problem (you can just ignore this warning) it's still annoying and
I've provided a fixed VM for this on
http://isgwww.cs.uni-magdeburg.de/~raab/squeak/beta
ftp://ftp.cs.uni-magdeburg.de/pub/Smalltalk/free/squeak/win32/beta
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 >=============+
Date: 97 Jun 18 9:12:20 pm
From: Joe McGuckin <joe@via.net>
To: Squeak@create.ucsb.edu
Subject: I'm looking for some simple Squeak apps...
I'm looking for some example application to take apart so
I can see how they work.
Something with a GUI interface - yet simple.
Any suggestions?
joe
Date: 97 Jun 18 10:23:56 pm
From: Ward Cunningham <ward@c2.com>
To: Joe McGuckin <joe@via.net>
Cc: Squeak@create.ucsb.edu
Subject: Re: I'm looking for some simple Squeak apps...
Joe McGuckin wrote:
>
> I'm looking for some example application to take apart so
> I can see how they work.
> Something with a GUI interface - yet simple.
Plumbin' was written for this very purpose. It's a decade old but may
still be useful. And it has a web page:
http://c2.com/doc/plumbin/
Regards. -- Ward
--
Ward Cunningham
v 503-245-5633 mailto:ward@c2.com
f 503-246-5587 http://c2.com/
Date: 97 Jun 19 9:51:10 am
From: Tim Rowledge <rowledge@interval.com>
To: Ward Cunningham <ward@c2.com>
Cc: Squeak mailinglist <Squeak@create.ucsb.edu>, Joe McGuckin <joe@via.net>
In-Reply-To: <33A8C7D1.74B4@c2.com>
Subject: Re: I'm looking for some simple Squeak apps...
On Wed 18 Jun, Ward Cunningham wrote:
> Plumbin' was written for this very purpose. It's a decade old but
may
> still be useful.
Just tried this out, and boy, it brings back memories of days gone
by. I remember seeing this for the first time..... ah, well. Don't
suppose you have the extended version that did signal processing
simulation stuff?
Anyway, I just wanted to point out that it still has the bug I found
way back when whereby a faucet/tee/two spouts pipe run causes
infinite recursion; basically the pressure calculating bounces back
and forth between the two spouts and the faucet anytime you turn it
on or off. A fix that stops the problem (but that may well not truly
be 'correct' in simulation terms) is to change the
Faucet>bottomPressure method to read
bottomPressure
^open
ifTrue:[ 20.0]
ifFalse: [0.0]
which at least stops the bouncing.
I *love* Smalltalk.
--
Tim Rowledge: rowledge@interval.com (w) +1 (415) 856-7230 (w)
tim@sumeru.stanford.edu (h) <http://sumeru.stanford.edu/tim>
Date: 97 Jun 19 9:37:10 pm
From: Leandro Caniglia <caniglia@mate.dm.uba.ar>
To: 'Squeak' <squeak@create.ucsb.edu>
Subject: On the #gcd: method
Hi.
Some time ago, I suggested a few simple changes to the #gcd: method of =
the class Integer. These changes used the same (binary) algorithm of the =
actual version and improve the speed of evaluation in an appreciable =
factor. Today I compared the speed of evaluation between the binary =
(actual) algorithm and the traditional one:
oldGcd: anInteger
| a b r |
b _ anInteger abs.
a _ self abs.
[a =3D 0] whileFalse: [
r _ b \\ a.
b _ a.
a _ r].
^b
Surprisingly enough, the traditional algorithm happened to be 7 to 15 =
times faster than the binary one. I think that the binary algorithm is =
OK for implementations in assembler, where the bit shifts are very fast =
operations. Here is the test I used to compare the evaluation times.
testGcd
"Compare the implementations of #gcd: and #oldGcd."
| delta initial interval random t t0 answer oldT |
delta _ 100.
initial _ 100000000.
answer _ FillInTheBlank
request: 'Magnitude of the numbers'
initialAnswer: initial printString.
answer isNil ifFalse: [initial _ answer asNumber].
interval _ (initial to: initial + delta).
random _ (1 to: delta) collect: [:each |
interval atRandom @ interval atRandom].
t _ Time millisecondsToRun: [random do: [:each | each x gcd: each y]].
oldT _ Time millisecondsToRun: [random do: [:each | each x oldGcd: each =
y]].
t0 _ Time millisecondsToRun: [random do: [:each | each x. each y]].
^ oldT =3D t0
ifTrue: ['#gcd: ', t printString, ', #oldGcd: ', oldT printString]
ifFalse: ['#gcd: / #oldGcd: ', (t - t0 / oldT - t0) asFloat =
printString]
Saludos,
Leandro
Date: 97 Jun 23 9:29:14 am
From: Dan Ingalls <DanI@wdi.disney.com>
To: Squeak@create.ucsb.edu
Subject: Number hackers: Help with 1.2?
We have made a lot of progress, and I want to put a new release out soon=
(this week).
=2E..BUT...
I haven't had the time to sort through the numerous changes to improve=
LargeInteger operations, and the other related numerical tweaks. Is there=
someone out there willing to assemble a consistent set of changes relative=
to the 1.19d image for me? It would be especially nice if this could=
include some small set of do-its or test methods so I can tell if it all=
works properly in the forthcoming release.
YOUR PROMPT ASSISTANCE WOULD BE GREATLY APPRECIATED
The new release will include several fairly major changes, namely...
"Pure" Points and Rectangles
The new arithmetic coercion
A whole new pass through color in support of transparency
MaskedForm goes away
ColorForm added (a Form plus its own colormap)
Much of Morphic working (scrollbars, lists, a browser and inspector,=
polygons and splines)
Changes file maintains time and author stamps
Numerous VM fixes and improvements
My goal is to release this with both Mac and Windows VMs, and include=
methods to remove various major susbsystems to produce smaller images, as=
we have in the past.
Thanks in advance for your help.
- Dan
Date: 97 Jun 24 1:23:32 am
From: "Peter J. Goodall" <peterg@acm.org>
To: "squeak@create.ucsb.edu" <squeak@create.ucsb.edu>
Subject: Re: Smalltalk Ballon.....was Teaching Smalltalk
There was a gothic looking black and white balloon bitmap shipped with
'The Analyst' from XSIS. Last seen by me in about 1990.
Dan Ingalls wrote:
Well, we should be in pretty good shape. The balloon was my idea. When
Byte came to Xerox to do the 8/81 issue, I suggested the entire layout,
including the relationship to the island (which did come from a prior
August issue so there might be problems with it). Having loved the
Mysterious Island of Jules Verne (a coincidence that Alan loved 20k
Under the Sea), the balloon was my vehicle of choice for ST's escape
from the ivory tower. So, the concept is mine (and hereby freely
granted to
> However, I still really like the job Tinney did on it. I photographed
> my lithograph and blew it up to 30x40, and it makes a spectacular
> poster (the litho texture makes the poster look like canvas). If
> there was a buck to be made, my guess is that Tinney would let us run
> off a limited edition of such a poster -- as John McIntosh says, he
> should appreciate the interest [John - pls do send me his #, and I'll
> check it out].
>
> - D
Date: 97 Jun 24 1:33:00 am
From: "Peter J. Goodall" <peterg@acm.org>
To: "squeak@create.ucsb.edu" <squeak@create.ucsb.edu>
Subject: Re: What does Squeak need?
Dwight Hughes wrote:
> Something I would like to see is everyone's opinions on
> what Squeak most needs, or areas where you consider it
> weakest, or where it has the most unrealized potential.
I would very much like to see squeak support something akin to the
interface specifications in Java. We did something similar at K.S.C.
Doesn't interfere with the run-time behavior, but sure helps in design,
and rediscovering design. Also significantly reduces your 'browsing
radius'.
Date: 97 Jun 24 7:56:13 pm
From: Ken Collins <shesha@televar.com>
To: Squeak@create.ucsb.edu
Subject: Beginner Question.
Hi Squeakers!
Can someone tell me what is happening when, in a Browser, I highlight
any of these:
Collections - Text
Graphics - Primitives
Graphics - Display Objects
Graphics - Editors
Graphics - Support
Interface - Menus
Kernel - Objects
System - Support
System - Files
and then I choose printOut (or fileOut) from the pop-up menu? I can't
seem to get complete printOuts in my Squeak folder and don't understand
what is happening.
Also, I found something new by only highlighting (still in a browser):
Kernel - Objects
then
instance area/button
then
Object
then
casing
then
caseOf:
This is the first time I have seen red in a scroll bar and I am
wondering why this is happening.
I am running Squeak 1.19d (with 10 Megs RAM allotted it) on a PowerMac
8100/100.
Thanks Much,
KEN
Date: 97 Jun 24 11:24:01 pm
From: Hans-Martin Mosner <hm.mosner@cww.de>
To: shesha@televar.com
Cc: Squeak@create.ucsb.edu
Subject: Re: Beginner Question.
Dies ist eine mehrteilige Nachricht im MIME-Format.
--------------2CBD19FD368B
Content-Type: text/plain; charset=iso-8859-1
Content-Transfer-Encoding: quoted-printable
Ken Collins wrote:
> =
> Hi Squeakers!
> =
[...]
> Also, I found something new by only highlighting (still in a brow=
ser):
> =
> Kernel - Objects
> then
> instance area/button
> then
> Object
> then
> casing
> then
> caseOf:
> =
> This is the first time I have seen red in a scroll bar and I am
> wondering why this is happening.
First I wondered what you mean by "red in a scroll bar"... Then I tried =
to reproduce your sypmtoms, without success first. At last I held the =
shift key down when accessing the method, and voil=E1, I got it.
You seem to have been running without the sources file, so your system =
tries to decompile the method for you. However, this is broken for =
methods with the selector caseOf:otherwise: (a fix for it is appended to =
this mail). Now Squeak opens an error notifier window (which should be =
much more prominent than the little red in the scroll bar...), and this =
causes the browser window to be de-emphasized (all selections in lists =
are reversed). The reversing of the line 'casing' in the protocol pane =
reverses the corresponding area in the method pane scrollbar, too, which =
turns part of the scrollbar area red.
I wonder why you did not notice the notifier window...
Hans-Martin
--------------2CBD19FD368B
Content-Type: text/plain; charset=us-ascii; x-mac-type="54455854"; x-mac-creator="522A6368"
Content-Transfer-Encoding: 7bit
Content-Disposition: inline; filename="caseOfFix.st"
!MessageNode class methodsFor: 'class initialization'!
initialize "MessageNode initialize"
MacroSelectors _
#(ifTrue: ifFalse: ifTrue:ifFalse: ifFalse:ifTrue:
and: or:
whileFalse: whileTrue: whileFalse whileTrue
to:do: to:by:do:
caseOf: caseOf:otherwise: as: ).
MacroTransformers _
#(transformIfTrue: transformIfFalse: transformIfTrueIfFalse: transformIfFalseIfTrue:
transformAnd: transformOr:
transformWhile: transformWhile: transformWhile: transformWhile:
transformToDo: transformToDo:
transformCase: transformCase: transformAs: ).
MacroEmitters _
#(emitIf:on:value: emitIf:on:value: emitIf:on:value: emitIf:on:value:
emitIf:on:value: emitIf:on:value:
emitWhile:on:value: emitWhile:on:value: emitWhile:on:value: emitWhile:on:value:
emitToDo:on:value: emitToDo:on:value:
emitCase:on:value: emitCase:on:value: emitAs:on:value: ).
MacroSizers _
#(sizeIf:value: sizeIf:value: sizeIf:value: sizeIf:value:
sizeIf:value: sizeIf:value:
sizeWhile:value: sizeWhile:value: sizeWhile:value: sizeWhile:value:
sizeToDo:value: sizeToDo:value:
sizeCase:value: sizeCase:value: sizeAs:value: ).
MacroPrinters _
#(printIfOn:indent: printIfOn:indent: printIfOn:indent: printIfOn:indent:
printIfOn:indent: printIfOn:indent:
printWhileOn:indent: printWhileOn:indent: printWhileOn:indent: printWhileOn:indent:
printToDoOn:indent: printToDoOn:indent:
printCaseOn:indent: printCaseOn:indent: printAsOn:indent: )! !
MessageNode initialize!
!MessageNode methodsFor: 'printing'!
printOn: aStream indent: level
| printer |
special > 0 ifTrue: [printer _ MacroPrinters at: special].
(printer == #printCaseOn:indent:) ifTrue:
[(arguments first isKindOf: BraceNode)
ifTrue: [^self printCaseOn: aStream indent: level]
ifFalse: [printer _ nil "avoid using it later"]].
receiver == nil
ifFalse: [receiver printOn: aStream indent: level precedence: precedence].
printer == nil
ifFalse:
[self perform: printer with: aStream with: level]
ifTrue:
[self
printKeywords: selector key
arguments: arguments
on: aStream
indent: level]! !
--------------2CBD19FD368B--
Date: 97 Jun 25 7:22:09 pm
From: Dan Ingalls <DanI@wdi.disney.com>
To: Squeak@create.ucsb.edu
In-Reply-To: <v03007816afd461679bd2@[206.16.10.79]>
Subject: Re: Number hackers: Help with 1.2?
=46olks -
I've decided to opt for stability (since nothing major is broken, and the=
numerophiles know the fixes already), and put out 1.2 without overhauling=
LargeIntegers. It would be a great service, though, if one of the number=
hackers would assemble, at his or her leisure, a new set of changes=
relative to 1.2 that we could test a bit, and then include in the next rele=
ase.
It's coming, it's coming...
- Dan
Date: 97 Jun 25 7:22:14 pm
From: Dan Ingalls <DanI@wdi.disney.com>
To: Squeak@create.ucsb.edu
Subject: Wavelets, etc.
Folks -
I'm gearing up to put a wavelets (this is a modern extension of Fourier analysis) package into Squeak.
Our interests are to be able to...
Compress speech
Analyze speech
Synthesize speech with various (fanciful?) voices
Analyze music, in terms of which instrument was playing what pitch and
amplitude at each moment in time
Synthesize music
Questions:
Can you suggest any really nice (clean, simple, efficient) existing packages
that we should look at? Needless to say, they must be non-proprietary.
Do you know of anything even better that we should be looking at?
Thanks in advance.
- Dan
Date: 97 Jun 26 12:52:35 am
From: "Andreas Raab" <raab@isg.cs.uni-magdeburg.de>
To: Dan Ingalls <DanI@wdi.disney.com>
Cc: squeak@create.ucsb.edu
Subject: Re: Wavelets, etc.
> I'm gearing up to put a wavelets (this is a modern extension
> of Fourier analysis) package into Squeak.
Sounds great! I'll be happy to try it since there are many areas in
Computer Graphics where wavelets can be used efficiently. And it'll
be fun doing that in Squeak ;-)
> Our interests are to be able to...
> Compress speech
> Analyze speech
> Synthesize speech with various (fanciful?) voices
> Analyze music, in terms of which instrument was playing what pitch and
> amplitude at each moment in time
> Synthesize music
For CG you could add:
* image compression and retrieval (see the great article by
David Salesin at SIGGRAPH 95)
* Multiresolution curves for editing free-form surfaces
* Wavelet analysis for mesh simplification
* ...
> Questions:
> Can you suggest any really nice (clean, simple, efficient) existing packages
> that we should look at? Needless to say, they must be non-proprietary.
> Do you know of anything even better that we should be looking at?
I don't know of any freely available package, however, I may check
the wavelet digest to see if there is any. On the other hand, there
was a good article in IEEE Computer Graphics and Applications about
the basics of wavelets.
To the second question the answer is a clear "No". Wavelets are way
to cool to leave them out!
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 >=============+
Date: 97 Jun 26 6:35:04 am
From: Leandro Caniglia <caniglia@mate.dm.uba.ar>
To: 'Squeak' <squeak@create.ucsb.edu>
Subject: LargeInteger bug
Hi!
Try this
(2 raisedToInteger: 31) // 1047
I obtain an error message :-(
The problem seems to be in the #digitDiv:neg: method. The code there is a transcription
of "Algorithm D" on page 257 in Knuth's vol 2. I have not the time to think about this problem right now. Would anybody confirm this bug?
Saludos,
Leandro
Date: 97 Jun 26 7:04:27 am
From: "David N. Smith" <dnsmith@watson.ibm.com>
To: Leandro Caniglia <caniglia@mate.dm.uba.ar>
Cc: "'Squeak'" <squeak@create.ucsb.edu>
In-Reply-To: <01BC8221.2A28CD60@ts1-bsas-linea03.microstar.com.ar>
Subject: Re: LargeInteger bug
At 7:06 -0400 6/26/97, Leandro Caniglia wrote:
>Hi!
>
>Try this
>
> (2 raisedToInteger: 31) // 1047
>
>I obtain an error message :-(
>
>The problem seems to be in the #digitDiv:neg: method. The code there is a
>transcription
>of "Algorithm D" on page 257 in Knuth's vol 2. I have not the time to
>think about this problem right now. Would anybody confirm this bug?
>
>Saludos,
>Leandro
I just tried it and I get no error, just a value of 2051082. I'm on 1.19d
and have not added any updates (except asTrueFraction).
(2 raisedToInteger: 31) // 1047
2051082
_______________________________
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.
Date: 97 Jun 26 7:29:43 pm
From: lnotarfr@dc.uba.ar (Luciano Esteban Notarfrancesco)
To: DanI@wdi.disney.com (Dan Ingalls)
Cc: squeak@create.ucsb.edu
In-Reply-To: <v03007806afd791575489@[206.16.10.79]> from "Dan Ingalls" at Jun 25, 97 07:40:32 pm
Subject: Re: Wavelets, etc.
>
> Folks -
>
> I'm gearing up to put a wavelets (this is a modern extension of Fourier analysis) package into Squeak.
>
> Our interests are to be able to...
> Compress speech
> Analyze speech
> Synthesize speech with various (fanciful?) voices
GOOD!!!
Leandro has been thinking for a while on the concept of a non-visual
Smalltalk, involing an interface with a speach analyzer/synthesizer.
He should send a mail to the list talking a bit more about this.
The wavelets package will be included in the next (1.2) release?
Luciano.-
Date: 97 Jun 26 9:47:06 pm
From: Leandro Caniglia <caniglia@mate.dm.uba.ar>
To: 'Squeak' <squeak@create.ucsb.edu>
Subject: RE: LargeInteger bug
Sory. It was my fault.
Saludos,
Leandro
Date: 97 Jun 27 9:52:46 am
From: stp (Stephen Travis Pope)
To: Dan Ingalls <DanI@wdi.disney.com>
Cc: Squeak@create.ucsb.edu
In-Reply-To: Dan Ingalls <DanI@wdi.disney.com>'s letter of: 97 Jun 25
Subject: Re: Wavelets, etc.
Hi!
I've placed the C source code for Clif Kussmaul's PubDom wavelets package on
our ftp site in ftp://ftp.create.ucsb.edu/pub/stp/wavelets.tar. There's a
c-code library there that includes the basic wavelet transform, as well as
loads of GUI functions, etc.
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/
Date: 97 Jun 28 7:18:41 am
From: johnson@cs.uiuc.edu (Ralph E. Johnson)
To: Squeak@create.ucsb.edu
Subject: Smalltalk University
I've been thinking about things that could help the Smalltalk community.
One of the ideas I've been calling "Smalltalk University". The idea is
to get a list of advanced Smalltalk courses and the people who would
teach them. The idea is NOT to start a new company or hand out degrees,
but just to encourage people to create advanced courses and companies
to keep on training their Smalltalk developers. Courses could be about
particular class libraries, how to apply Smalltalk in a particular domain,
patterns, or advanced development topics. I'd manage a web page that
listed the courses and their teachers.
There are all sorts of questions about how to run something like this,
but I am going to postpone them til later. First, I am looking for people
who are interested in participating. If you are interested, or if you
think someone else should be interested, please let me know.
-Ralph
Date: 97 Jun 28 10:45:54 am
From: Leandro Caniglia <caniglia@mate.dm.uba.ar>
To: "'David N. Smith'" <dnsmith@watson.ibm.com>
Cc: 'Squeak' <squeak@create.ucsb.edu>
Subject: RE: LargeInteger bug
Dave.
Luciano told me that the problem with my proofs (see below) comes from =
your patch to the SmallInteger>>bitShift: method. Do you remember? You =
sugested to replace=20
1 - (1 - self bitShift: arg)
with
0 - (0 - self bitShift: arg).
I completely agree with your patch but something went wrong with the #// =
method. I'm sorry, I have not the time to say something more about this =
question.
----------
From: David N. Smith
Sent: Jueves 26 de Junio de 1997 11:36
To: Leandro Caniglia
Cc: 'Squeak'
Subject: Re: LargeInteger bug
>I just tried it and I get no error, just a value of 2051082. I'm on =
1.19d
>and have not added any updates (except asTrueFraction).
>(2 raisedToInteger: 31) // 1047
>2051082
Date: 97 Jun 28 5:35:01 pm
From: William Kohl <billk@hypercon.com>
To: "Ralph E. Johnson" <johnson@cs.uiuc.edu>
Cc: Squeak@create.ucsb.edu
Subject: Re: Smalltalk University
Ralph E. Johnson wrote:
> I've been thinking about things that could help the Smalltalk
> community.
> One of the ideas I've been calling "Smalltalk University". The idea
> is
> to get a list of advanced Smalltalk courses and the people who would
> teach them. The idea is NOT to start a new company or hand out
> degrees,
> but just to encourage people to create advanced courses and companies
> to keep on training their Smalltalk developers. Courses could be
> about
> particular class libraries, how to apply Smalltalk in a particular
> domain,
> patterns, or advanced development topics. I'd manage a web page that
> listed the courses and their teachers.
>
> There are all sorts of questions about how to run something like this,
>
> but I am going to postpone them til later. First, I am looking for
> people
> who are interested in participating. If you are interested, or if you
>
> think someone else should be interested, please let me know.
>
> -Ralph
I'd like to make a few additional suggestions.
1. Have a list of instructors in major cities and as many smaller cities
as possible.
2. Make it a virtual university in this sense
a. instructors accept a small number of students in their home town
b. students and instructors communicate by e-mail (or phone) except
perhaps a few initial meetings
c. Smalltalk Express is the language (unless other agreed upon by
student and instructor)
d. Courses could range from printed material to the instructor
guiding a student through one of the available books on ST programming
What seems important is connecting desiring student to willing
instructor. I think that there are lots of us in the ST community who
would like to become involved and if you multiple that number by say 5
-10 (students per year), that should have a noticable impact on the pool
of available ST programmers.
Date: 97 Jun 29 8:06:42 am
From: "David N. Smith" <dnsmith@watson.ibm.com>
To: Leandro Caniglia <caniglia@mate.dm.uba.ar>
Cc: "'Squeak'" <squeak@create.ucsb.edu>
In-Reply-To: <01BC83D6.B06E4D30@NOTUNG>
Subject: RE: LargeInteger bug
At 11:18 -0400 6/28/97, Leandro Caniglia wrote:
>Dave.
>Luciano told me that the problem with my proofs (see below) comes from
>your patch to the SmallInteger>>bitShift: method. Do you remember? You
>sugested to replace
>
> 1 - (1 - self bitShift: arg)
>with
> 0 - (0 - self bitShift: arg).
>
>I completely agree with your patch but something went wrong with the #//
>method. I'm sorry, I have not the time to say something more about this
>question.
>
>----------
>From: David N. Smith
>Sent: Jueves 26 de Junio de 1997 11:36
>To: Leandro Caniglia
>Cc: 'Squeak'
>Subject: Re: LargeInteger bug
>
>>I just tried it and I get no error, just a value of 2051082. I'm on 1.19d
>>and have not added any updates (except asTrueFraction).
>
>>(2 raisedToInteger: 31) // 1047
>>2051082
Leandro:
Yep, you are right. I installed my #bitShift: as the default, where it
should have been all along. Your example fails and in a monster of a method
that would take quite a while to untangle.
If there is a new implementation for large integers about to be released it
will hopefully replace the failing routine (Integer>>#digitDiv:neg:) which
is called by #quo:. It uses #bitShift:s all over the place and has probably
adapted itself to the broken version of #bitShift:.
It ends up trying to store an integer 257 into a byte, which doesn't work well.
I did see a cute bit of code in #quo::
self negative == aNumber negative == false
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.
Date: 97 Jun 29 5:24:00 pm
From: Dan Ingalls <DanI@wdi.disney.com>
To: Squeak@create.ucsb.edu
Subject: Squeak 1.2 now available
=46olks -
We are hereby releasing Version 1.2 of Squeak. We are putting it in Stephen=
Pope's drop box and look for him to send out a message with the exact file=
paths when all is installed. The 1.2 release includes VMs for both Mac=
(PPC and 68k) and Windows 95.
As always, some things remain undone, but we feel the system is in a fairly=
stable state, with nearly three months worth of bug fixes and improvements.
The major features of Version 1.2 (since 1.19) include...
Elimination of most side-effects in Points and Rectangles
More efficient arithmetic coercion
A whole new pass through color in support of transparency
MaskedForm removed
ColorForm (a Form plus its own colormap) added
Much of Morphic works (scrollbars, lists, browser shell, inspector,=
polygons and splines)
Changes file maintains time and author stamps automatically
PrintOut menu items produce html for printing from web browser
(these html files can also be filed in)
Numerous VM fixes and improvements
Bugs fixed in perform:, block value:, Object at:
BitBlt now tolerates Float parameters
Several problems in Float and Fraction have been fixed, and several mild=
ones remain.
Most of the Socket support is now operational, and several examples are pro=
vided.
The image is somewhat larger (around 1.9Mb), since it includes both MVC and=
a fairly complete Morphic system with several running examples. However it=
is still right around a megabyte if you pare back the interpreter and=
Morphic, and you can get under 650k by executing Smalltalk>>majorShrink.
While the Morphic application construction kit is not complete, we are=
interested in all comments and suggestions relating to the Morphic=
architecture as it stands.
Enjoy
- The Squeak Team
Date: 97 Jun 29 7:50:14 pm
From: Dan Ingalls <DanI@wdi.disney.com>
To: Squeak@create.ucsb.edu
Subject: Some backward compatibility
--============_-1344478076==_============
Content-Type: text/plain; charset="us-ascii"
Content-Transfer-Encoding: quoted-printable
=46olks -
The Version 1.2 image should only be run with its accompanying VM for a=
number of reasons. However, if you are running on a platform for which=
there is not yet a new VM, I offer the attached fileIn.
I have succeeded in running the Version 1.2 image with a 1.19 interpreter=
(1.18 would probably also work), after filing in this file (and it will run=
well enough to do a fileIn already ;-). Even the Morphic demos work. Of=
course we make no guarantees about performance or integrity, but if you=
want to play around with 1.2 before you can get a new VM, this should help.
Enjoy
- Dan
--============_-1344478076==_============
Content-Type: text/plain; name="BackCompat-di.cs"; charset="us-ascii"
Content-Disposition: attachment; filename="BackCompat-di.cs"
'From Squeak 1.2 of June 29, 1997 on 29 June 1997 at 8:08:39 pm'!"Change Set: BackCompat
Date: 29 June 1997
Author: Dan Ingalls
A rough attempt to make a Version 1.2 image run with a 1.19 interpreter.
"!
!Object methodsFor: 'copying' stamp: 'di 6/29/97 19:11'!
clone
<primitive: 148>
^ self shallowCopy! !
!BitBlt methodsFor: 'copying' stamp: 'di 6/29/97 19:12'!
copyBits
"Primitive. Perform the movement of bits from the source form to the
destination form. Fail if any variables are not of the right type (Integer,
Float, or Form) or if the combination rule is not implemented.
In addition to the original 16 combination rules, this BitBlt supports
16 fail (to simulate paint)
17 fail (to simulate mask)
18 sourceWord + destinationWord
19 sourceWord - destinationWord
20 rgbAdd: sourceWord with: destinationWord
21 rgbSub: sourceWord with: destinationWord
22 rgbDiff: sourceWord with: destinationWord
23 tallyIntoMap: destinationWord
24 alphaBlend: sourceWord with: destinationWord
25 pixPaint: sourceWord with: destinationWord
26 pixMask: sourceWord with: destinationWord
27 rgbMax: sourceWord with: destinationWord
28 rgbMin: sourceWord with: destinationWord
29 rgbMin: sourceWord bitInvert32 with: destinationWord
"
<primitive: 96>
"Check for unimplmented rules"
combinationRule = Form oldPaint ifTrue: [^ self paintBits].
combinationRule = Form oldErase1bitShape ifTrue: [^ self eraseBits].
"Convert all numeric parameters to integers and try again."
destX _ destX asInteger.
destY _ destY asInteger.
width _ width asInteger.
height _ height asInteger.
sourceX _ sourceX asInteger.
sourceY _ sourceY asInteger.
clipX _ clipX asInteger.
clipY _ clipY asInteger.
clipWidth _ clipWidth asInteger.
clipHeight _ clipHeight asInteger.
^ self copyBitsAgain! !
!Color class methodsFor: 'class initialization' stamp: 'di 6/29/97 19:49'!
initializeIndexedColors
"Build an array of colors corresponding to the fixed colormap used
for display depths of 1, 2, 4, or 8 bits."
"Color initializeIndexedColors"
| a index grayVal |
a _ Array new: 256.
"1-bit colors (monochrome)"
a at: 1 put: (Color r: 1.0 g: 1.0 b: 1.0). "white or transparent"
a at: 2 put: (Color r: 0.0 g: 0.0 b: 0.0). "black"
"additional colors for 2-bit color"
a at: 3 put: (Color r: 0.5 g: 0.5 b: 0.5). "50% gray"
a at: 4 put: (Color r: 1.0 g: 1.0 b: 0.0). "yellow"
"additional colors for 4-bit color"
a at: 5 put: (Color r: 1.0 g: 0.0 b: 0.0). "red"
a at: 6 put: (Color r: 0.0 g: 1.0 b: 0.0). "green"
a at: 7 put: (Color r: 0.0 g: 0.0 b: 1.0). "blue"
a at: 8 put: (Color r: 0.0 g: 1.0 b: 1.0). "cyan"
a at: 9 put: (Color r: 1.0 g: 0.0 b: 1.0). "magenta"
a at: 10 put: (Color r: 0.125 g: 0.125 b: 0.125). "1/8 gray"
a at: 11 put: (Color r: 0.125 g: 0.125 b: 0.125). "1/8 gray"
a at: 12 put: (Color r: 0.25 g: 0.25 b: 0.25). "2/8 gray"
a at: 13 put: (Color r: 0.375 g: 0.375 b: 0.375). "3/8 gray"
a at: 14 put: (Color r: 0.625 g: 0.625 b: 0.625). "5/8 gray"
a at: 15 put: (Color r: 0.75 g: 0.75 b: 0.75). "6/8 gray"
a at: 16 put: (Color r: 0.875 g: 0.875 b: 0.875). "7/8 gray"
"additional colors for 8-bit color"
"24 more shades of gray (1/32 increments but not repeating 1/8 increments)"
index _ 17.
1 to: 31 do: [:v |
(v \\ 4) = 0 ifFalse: [
grayVal _ v / 32.0.
a at: index put: (Color r: grayVal g: grayVal b: grayVal).
index _ index + 1]].
"The remainder of color table defines a color cube with six steps
for each primary color. Note that the corners of this cube repeat
previous colors, but this simplifies the mapping between RGB colors
and color map indices. This color cube spans indices 40 through 255
(indices 41-256 in this 1-based array)."
0 to: 5 do: [:r |
0 to: 5 do: [:g |
0 to: 5 do: [:b |
index _ 41 + ((36 * r) + (6 * b) + g).
index > 256 ifTrue: [
self error: 'index out of range in color table compuation'].
a at: index put: (Color r: r g: g b: b range: 5)]]].
IndexedColors _ a.
! !
Color shutDown.
Color initializeIndexedColors.
Color initializeGrayToIndexMap.
Color allSubInstancesDo: [:c | c flushCache].
!
--============_-1344478076==_============--
Date: 97 Jun 29 9:00:21 pm
From: Jecel Assumpcao Jr <jecel@lsi.usp.br>
To: Squeak@create.ucsb.edu
Subject: Re: Smalltalk University
Great idea. It is hard to make advanced courses not tied
to some particular dialect.
The main thing would be to create good course material -
slides and workbooks, as well as example programs and
exercises. I have been asked to give Smalltalk courses
several times, but I only accepted once (and it didn't
work out too well) because I didn't have time to create
all this stuff.
So the best way to start is to make a list of the needed
courses, order them by some priority and then start
creating the need materials. I know that if I could
study some ready made slides for a day I could give
a good quality course on any Smalltalk related subject.
For those who have a harder time doing this (I know
several people who are like this) it would be great
to have a video tape of someone else giving the course.
I have given a lot of thought about using Smalltalk
(actually the Self dialect) as a first programming
language with an "online tutor". The Smalltalk
University would be a fantastic complement for this.
-- Jecel
Date: 97 Jun 29 9:00:15 pm
From: Jecel Assumpcao Jr <jecel@lsi.usp.br>
To: Squeak@create.ucsb.edu
Subject: Re: Wavelets, etc.
My (very little) experience with wavelets has been in
image compression - I haven't seen it applied to sound.
I did play around with Linear Predictive Coding for
voice - it might be nice to have that too.
And how about all that neat music stuff in Smalltalk
(I think it was called Mode or Smoke or something like that -
Stephen?)? I never tried it because it only ran on
ParcPlace Smalltalk. Would it be a good thing to have
in Squeak?
BTW, I just got sound working in Smalltalk Express and
it is pathetic compared to what is already in Squeak.
-- Jecel
Date: 97 Jun 29 11:40:49 pm
From: stp (Stephen Travis Pope)
To: Jecel Assumpcao Jr <jecel@lsi.usp.br>, Squeak@create.ucsb.edu
In-Reply-To: Jecel Assumpcao Jr <jecel@lsi.usp.br>'s letter of: 97 Jun 29
Subject: Re: Wavelets, etc.
Jecel wrote:
> And how about all that neat music stuff in Smalltalk?
The new version of MODE (now called "Siren") is on its way, and will be posted
to the net real soon.
Is there anybody out there working with (or interested in) MIDI in Squeak?
stp
_Stephen Travis Pope, stp@create.ucsb.edu, http://www.create.ucsb.edu/~stp/
_Center for Research in Electronic Art Technology (CREATE)
_Department of Music, Univ. of California, Santa Barbara (UCSB)
(Random anagram of my name = vanish top peep rest)
Date: 97 Jun 29 11:40:52 pm
From: stp (Stephen Travis Pope)
To: Squeak@create.ucsb.edu
In-Reply-To: Dan Ingalls <DanI@wdi.disney.com>'s letter of: 97 Jun 29
Subject: Re: Squeak 1.2 now available
The new Squeak 1.20 files from Dan and John are in
ftp://ftp.create.ucsb.edu/pub/Smalltalk/Squeak/1.2
enjoy!
stp
_Stephen Travis Pope, stp@create.ucsb.edu, http://www.create.ucsb.edu/~stp/
_Center for Research in Electronic Art Technology (CREATE)
_Department of Music, Univ. of California, Santa Barbara (UCSB)
(Random anagram of my name = save thine spot prep)
Date: 97 Jun 30 9:19:23 pm
From: Tim Rowledge <rowledge@interval.com>
To: Squeak mailinglist <squeak@create.ucsb.edu>
Subject: Sq1.20 for Acorn
Well it took an hour or so, but Squeak 1.20 is now running on my Acorn RPC; except for the socket stuff! The differences between my image and the relaese one arenow little more than adding RiscOSDirectory, little-endian bitblt and Acorn d
isplay handling.
It's about 20% faster than 1.18, hitting 6.5m on the Integer>benchmark and 312k on the Integer>benchFib methods. Cool!
Just two questions so far:-
why did you drop the faster bitblt dispatching that HMM did?
what is the getAttributes intended for; and how? I can see some
possiblities, but I wonder what the original intention was.
tim
--
Tim Rowledge tim@sumeru.stanford.edu http://sumeru.stanford.edu/tim
stp@create.ucsb.edu]
Created: 1996.11.08; LastEditDate: 1996.11.11