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


Squeak Smalltalk Mailing List Archive

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

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

Index


Date:	97 Mar 01 12:59:45 am
From:	Hans-Martin Mosner <hm.mosner@cww.de>
To:		Squeak Mailing List <squeak@create.ucsb.edu>
Subject:	Typed Smalltalk and RTL

Hi Squeakers,

Does anybody know whether the code generator used in Typed Smalltalk is 
available somewhere?

I've just read the papers on RTL and code generating, and it seems that 
it could be a reasonable route to primitives defined in Squeak.

However, reinventing the wheel is not what I'd want to do. So, if the TS 
classes are available from UIUC, it might make much more sense to 
integrate them with Squeak.

Any ideas?

Hans-Martin



Post a reply.

Go back to index.



Date: 97 Mar 01 4:31:19 am From: johnson@cs.uiuc.edu (Ralph E. Johnson) To: hm.mosner@cww.de, Squeak Mailing List <squeak@create.ucsb.edu> Subject: Re: Typed Smalltalk and RTL Well, I'm the one to ask about them. I've got the code around, I just have to make it available. I told someone else recently that I would do it, but the problem is that I am currently too busy to think, and that has lower priority. I'll try to put it somewhere public in a few weeks. -Ralph

Post a reply.

Go back to index.



Date: 97 Mar 12 11:00:23 am From: Dan Ingalls <DanI@wdi.disney.com> To: Squeak@create.ucsb.edu Subject: A couple of fixes --============_-1353928361==_============ Content-Type: text/plain; charset="us-ascii" Folks - Herewith a couple of fixes to 1.18... InfiniteFormFix-di.cs: Loads a default color map when the patternForm has a different depth from the form on which this is being displayed. Most particularly affects screen background when using a background form with a depth different from the Display. GrayFix-di.cs: Fixes Color initializeNames so that it only stores into lightGray once, and that one is correct (it used to be lighter than veryLightGray!!). Also adds brown and orange, since we already had lightBrown and lightOrange. We continue to make progress on sockets and our Morphic/Fabrik replacement for MVC. What else is going on "out there"? - Dan --============_-1353928361==_============ Content-Type: text/plain; name="InfiniteFormFix-di.cs"; charset="us-ascii" Content-Disposition: attachment; filename="InfiniteFormFix-di.cs" 'From Squeak 1.18 of December 12, 1996 on 11 March 1997 at 11:48:07 am'! "Change Set: InfiniteFormFix-di Date: 11 March 1997 Author: Dan Ingalls Loads a default color map when the patternForm has a different depth from the form on which this is being displayed. Most particularly affects screen background when using a background form with a depth different from the Display "! !InfiniteForm methodsFor: 'displaying'! displayOn: aDisplayMedium at: aDisplayPoint clippingBox: clipRectangle rule: ruleInteger fillColor: aForm "This is the real display message, but it doesn't get used until the new display protocol is installed." | targetBox patternBox bb | (patternForm class == Pattern) ifTrue: ["Use patternForm as a mask for BitBlt" aDisplayMedium fill: clipRectangle rule: ruleInteger fillColor: patternForm. ^ self]. (patternForm isKindOf: Form) ifFalse: ["A Color-like thing. Use patternForm as a mask for BitBlt" aDisplayMedium fill: clipRectangle rule: ruleInteger fillColor: patternForm. ^ self]. "Do it iteratively" targetBox _ aDisplayMedium boundingBox intersect: clipRectangle. patternBox _ patternForm boundingBox. bb _ BitBlt destForm: aDisplayMedium sourceForm: patternForm fillColor: aForm combinationRule: ruleInteger destOrigin: 0@0 sourceOrigin: 0@0 extent: patternBox extent clipRect: clipRectangle. patternForm depth = aDisplayMedium depth ifFalse: [bb colorMap: (Color defaultColorMapFrom: patternForm depth to: aDisplayMedium depth)]. (targetBox left truncateTo: patternBox width) to: targetBox right - 1 by: patternBox width do: [:x | (targetBox top truncateTo: patternBox height) to: targetBox bottom - 1 by: patternBox height do: [:y | bb destOrigin: x@y; copyBits]]! displayOnPort: aPort at: aDisplayPoint | targetBox patternBox saveMap | (patternForm class == Pattern) ifTrue: ["Use patternForm as a mask for BitBlt" aPort fill: aPort clipRect fillColor: patternForm rule: Form over. ^ self]. (patternForm isKindOf: Form) ifFalse: ["A Color-like thing. Use patternForm as a mask for BitBlt" aPort fill: aPort clipRect fillColor: patternForm rule: Form over. ^ self]. "Do it iteratively" targetBox _ aPort clipRect. patternBox _ patternForm boundingBox. aPort sourceForm: patternForm; combinationRule: Form over; sourceRect: (0@0 extent: patternBox extent). saveMap _ aPort colorMap. patternForm depth = aPort destForm depth ifFalse: [aPort colorMap: (Color defaultColorMapFrom: patternForm depth to: aPort destForm depth)]. (targetBox left truncateTo: patternBox width) to: targetBox right - 1 by: patternBox width do: [:x | (targetBox top truncateTo: patternBox height) to: targetBox bottom - 1 by: patternBox height do: [:y | aPort destOrigin: x@y; copyBits]]. aPort colorMap: saveMap! ! --============_-1353928361==_============ Content-Type: text/plain; name="GrayFix-di.cs"; charset="us-ascii" Content-Disposition: attachment; filename="GrayFix-di.cs" 'From Squeak 1.18 of December 12, 1996 on 11 March 1997 at 11:11:17 am'! "Change Set: GrayFix-di Date: 11 March 1997 Author: Dan Ingalls Fixes Color initializeNames so that it only stores into lightGray once, and that one is correct (it used to be lighter than veryLightGray!!). Also adds brown and orange, since we already had lightBrown and lightOrange."! !Color class methodsFor: 'colors'! names "Return a list of names of colors. An OrderedCollection of symbols. 6/14/96 tk" " Color names doWithIndex: [:name :i | Display fill: (0@(i*22) extent: 100@22) fillColor: (Color perform: name). name displayAt: 10@(i*22+4)] " ^ ColorNames! ! !Color class methodsFor: 'class initialization'! initializeNames "Set values of the named colors. 6/13/96 tk Color initializeNames" ColorNames _ OrderedCollection new. #(white black gray yellow red green blue cyan magenta - veryDarkGray darkGray - - lightGray veryLightGray ) doWithIndex: [:colorPut :i | colorPut == #- ifFalse: [self named: colorPut put: (IndexedColors at: i)]]. #(brown orange lightBlue lightBrown lightCyan lightGreen lightMagenta lightOrange lightRed lightYellow) with: "Color fromUser first bitAnd: 255" #(149 229 219 206 147 207 254 236 248 249) do: [:colorPut :i | self named: colorPut put: (IndexedColors at: i+1)]. ! ! Color initializeNames! --============_-1353928361==_============--

Post a reply.

Go back to index.



Date: 97 Mar 12 11:19:50 am From: James McCartney <james@clyde.as.utexas.edu> To: Dan Ingalls <DanI@wdi.disney.com>, Squeak@create.ucsb.edu In-Reply-To: <v03007801af4caf657617@[206.16.10.79]> Subject: Re: A couple of fixes At 11:15 AM -0800 3/12/97, Dan Ingalls wrote: >We continue to make progress on sockets and our Morphic/Fabrik replacement >for MVC. What else is going on "out there"? What is "Morphic/Fabrik" ? --- james mccartney james@clyde.as.utexas.edu james@lcsaudio.com If you have a PowerMac check out SuperCollider, a real time synth program: ftp://mirror.apple.com//mirrors/Info-Mac.Archive/gst/snd/super-collider-demo.hqx

Post a reply.

Go back to index.



Date: 97 Mar 12 2:40:57 pm From: "David N. Smith" <dnsmith@watson.ibm.com> To: Dan Ingalls <DanI@wdi.disney.com> Cc: Squeak@create.ucsb.edu In-Reply-To: <v03007801af4caf657617@[206.16.10.79]> Subject: Re: A couple of fixes At 14:15 -0500 3/12/97, Dan Ingalls wrote: >We continue to make progress on sockets and our Morphic/Fabrik replacement >for MVC. I know what Fabrik is. What's Morphic? Dave _______________________________ David N. Smith dnsmith@watson.ibm.com IBM T J Watson Research Center Hawthorne, NY _______________________________ Any opinions or recommendations herein are those of the author and not of his employer.

Post a reply.

Go back to index.



Date: 97 Mar 12 2:42:35 pm From: "David N. Smith" <dnsmith@watson.ibm.com> To: James McCartney <james@clyde.as.utexas.edu> Cc: Squeak@create.ucsb.edu In-Reply-To: <l03010d00af4cc369ba7b@[128.83.249.27]> Subject: Re: A couple of fixes At 15:33 -0500 3/12/97, James McCartney wrote: >At 11:15 AM -0800 3/12/97, Dan Ingalls wrote: > >>We continue to make progress on sockets and our Morphic/Fabrik replacement >>for MVC. What else is going on "out there"? > >What is "Morphic/Fabrik" ? > > > --- james mccartney Fabrik is described in a paper in the 88 OOPSLA Proceedings. It's neat! Here is the abstract: Fabrik: A Visual Programming Environment Dan Ingalls Scott Wallace Yu-Ying Chow Frank Ludolph Ken Doyle Apple Computer Inc. 20525 Mariani Avenue Cupertino CA 95014 ABSTRACT: Fabrik is a visual programming environment - a kit of computational and user- interface components that can be "wired" together to build new components and useful applications. Fabrik diagrams utilize bidirectional dataflow connections as a shorthand for multiple paths of flow. Built on object-oriented foundations, Fabrik components can compute arbitrary objects as outputs. Music and animation can be programmed in this way and the user interface can even be extended by generating graphical structures that depend on other data. An interactive type system guards against meaningless connections. As with simple dataflow, each Fabrik component can be compiled into an object with access methods corresponding to each of the possible paths of data propagation. _______________________________ David N. Smith dnsmith@watson.ibm.com IBM T J Watson Research Center Hawthorne, NY _______________________________ Any opinions or recommendations herein are those of the author and not of his employer.

Post a reply.

Go back to index.



Date: 97 Mar 12 4:06:59 pm From: Aaron Rosenzweig <recurve@xombi.wizard.net> To: Squeak@create.ucsb.edu Subject: Re: Fabrik Wow, I'm confused....you mean Squeak has some extensions that make it similar to Prograph? How many data-flow languages are there out there? --- SW Son of Ginger and Harry, Aaron Rosenzweig SW http://www.wam.umd.edu/~recurve/ SW... recurve@resourceful.com SWN?

Post a reply.

Go back to index.



Date: 97 Mar 12 4:23:57 pm From: Dan Ingalls <DanI@wdi.disney.com> To: recurve@resourceful.com Cc: Squeak@create.ucsb.edu In-Reply-To: <9703130030.AA00761@wizard.net> Subject: Re: Fabrik Aaron Rosenzweig wrote... >Wow, I'm confused....you mean Squeak has some extensions that make it= similar =20 >to Prograph? No, we are building a new graphics sub-system for Squeak that will have a= structure similar to those used in Fabrik (a bidirectional hookup language= built in Smalltalk-80) and Morphic (a concrete graphical manipulation= system built in SELF). What we are building should answer many people's= needs for an interactive application construction facility in Squeak. - Dan

Post a reply.

Go back to index.



Date: 97 Mar 12 10:52:15 pm From: Travis Griggs <tkc@bmi.net> To: Squeak@create.ucsb.edu Subject: Howdy and a question This is exciting, I can sit at home and do Smalltalk on my PowerMac (narry a glitch yet). It seems the fires of innovation around Smalltalk must be light'in up again :). I want to play with the bowels of how Smalltalk scans source code and creates compiled methods. My game plan *was* to create a subclass of Compiler and Parser (called MyCompiler and MyParser). Then I created a MyTest class. The only thing I overrode in MyCompiler was the class side method parserClass. I also changed some methods in Compiler that referred directly to Parser, rather than 'self class parserClass.' Finally, on the class side of MyTest, I added the method compilerClass which returns MyCompiler. I figured this would allow me a platform of throwing in self halts in the parse/scan/compile processes for my little Test class without obviously affecting the entire system. But I find that instances of MyCompiler don't even ever get created (I tried to trap on new) when accepting methods into MyTest. What am I missing? If you've walked this path before, can you offer words of direction? -- Travis or Kerrin Griggs Key Technology (509) 529-2161 tkc@bmi.net (509) 527-8743

Post a reply.

Go back to index.



Date: 97 Mar 13 12:24:43 am From: Hans-Martin Mosner <hmm@heeg.de> To: Dan Ingalls <DanI@wdi.disney.com> Cc: Squeak@create.ucsb.edu Subject: Re: A couple of fixes Dan Ingalls wrote: > What else is going on "out there"? I'm waiting for Ralph Johnson's Typed Smalltalk stuff to appear on the UIUC server. Then I'd like to integrate it into Squeak to get the ability to dynamically compile primitives into machine language. My 3-d stuff will have to wait until after that, because I figured out that using the normal Squeak VM generation process just takes me too long to debug the primitives... In the meantime, I'm trying to move the system from 1 SmallInteger tag bit to 2 tag bits, allowing for other immediate classes. The first additional immediate classes would be Character and SmallPoint (for integer coordinates in the range -2048..2047). SmallFloats would be possible, but I question their usefulness because the precision would be quite limited. Another idea is to make nil, true, false immediate. This could possibly speed up some operations in the VM since they would deal with constants instead of variables. Probably the speedup isn't worth it, though. A possible outline for tag bits is: ....00: normal object pointer ....11: SmallInteger ....10: forbidden ....01: other immediate classes 000001: UndefinedObject 000101: False 001001: True 001101: Character 010001: SmallPoint This is similar to the ParcPlace scheme, except that VisualWorks has only Character as an additional immediate class. I don't know how many additional tag bits should be significant for the other immediate classes. Using 6 additional bits would leave 24 bits for the value. Using only 4 would increase the SmallPoint range to -4096..4095, which is probably good, but at the same time it would reduce the number of possible additional immediate classes from 64 to 16. Hans-Martin

Post a reply.

Go back to index.



Date: 97 Mar 13 2:04:55 am From: Michael Rueger <michael@ISG.CS.Uni-Magdeburg.De> To: hmm@heeg.de (Hans-Martin Mosner) Cc: Squeak@create.ucsb.edu In-Reply-To: <3327BCD3.648A@heeg.de> from "Hans-Martin Mosner" at Mar 13, 97 09:37:39 am Subject: Immediate classes (was: Re: fixes) > In the meantime, I'm trying to move the system from 1 SmallInteger > tag bit to 2 tag bits, allowing for other immediate classes. The > first additional immediate classes would be Character and > SmallPoint (for integer coordinates in the range -2048..2047). > SmallFloats would be possible, but I question their usefulness > because the precision would be quite limited. But wouldn't the speedup in float calculations be worth it? > Another idea is to make nil, true, false immediate. This could > possibly speed up some operations in the VM since they would deal > with constants instead of variables. Probably the speedup isn't > worth it, though. Hmmm, aren't nil, false, true known to the VM anyhow as hard coded pointer values? What would be the benefit of immediate classes here? Michael -- + Michael Rueger +++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ + Universitaet Magdeburg FIN-ISG Universitaetsplatz 2 D-39106 Magdeburg + + voice: ++49-(0)391-67-18760 fax: ++49-(0)391-67-11164 + + michael@isg.cs.uni-magdeburg.de http://simsrv.cs.uni-magdeburg.de/~michael + ++++ remember the times when sex was safe and motorbikes were not ++++++++++++

Post a reply.

Go back to index.



Date: 97 Mar 13 2:39:51 am From: Hans-Martin Mosner <hmm@heeg.de> To: Michael Rueger <michael@ISG.CS.Uni-Magdeburg.De> Cc: Squeak@create.ucsb.edu Subject: Re: Immediate classes (was: Re: fixes) Michael Rueger wrote: > > ... > > SmallFloats would be possible, but I question their usefulness > > because the precision would be quite limited. > > But wouldn't the speedup in float calculations be worth it?Yes, but getting seriously inexact results quickly is probably not what you want. 32-bit floating point is already considered inadequate for anything but games by some people :-) How would they look at 26-bit or 28-bit floats? A better solution, IMHO, would be to have a class FloatArray that can be used as a container for float values, and the much-wished-for primitive compiler that would know how to deal with these. Then a matrix transposition method could look like: !FloatArray methodsFor: 'arithmetic'! sum "compute the sum of all elements." | sum | <primitive> sum := 0.0. 1 to: self size do: [:i | sum := sum + (self at: i) ]. ^sum ! ! The compiler would notice that only the return statement would need to create a real Float object. Everything in between can be done with the machine's floating point unit or library, without creating a Float object at all. The critical numerical operations could be coded as compiled primitives, leaving the normal Float operations for mixed-class arithmetics where it should not hurt too much. > > > Another idea is to make nil, true, false immediate. This could > > possibly speed up some operations in the VM since they would deal > > with constants instead of variables. Probably the speedup isn't > > worth it, though. > > Hmmm, aren't nil, false, true known to the VM anyhow as hard coded > pointer values? What would be the benefit of immediate classes here? They are not hard coded, but depend on the position of the image in memory. This means that whenever the VM has to use one of these values, it has to load it from a global variable in which they were stored at image startup. One place where it hurts is the conditional jump: the object on top of stack has to be compared with true or false first (depending on the kind of conditional jump), and if it's not equal, it has to be compared with the other one, too, to detect the case where a non-boolean is the receiver of ifTrue:ifFalse:. This makes 2 memory accesses. Having well-known immediate values both avoids the memory access and opens up the possibility for the compiler to use 'quick' instructions that deal with 8-bit or 16-bit immediate operands. Hans-Martin

Post a reply.

Go back to index.



Date: 97 Mar 13 6:29:42 am From: James McCartney <james@clyde.as.utexas.edu> To: Squeak@create.ucsb.edu In-Reply-To: <199703131016.LAA08369@escher.cs.uni-magdeburg.de> Subject: Re: Immediate classes (was: Re: fixes) At 11:14 AM +0100 3/13/97, Michael Rueger wrote: >> In the meantime, I'm trying to move the system from 1 SmallInteger >> tag bit to 2 tag bits, allowing for other immediate classes. The >> first additional immediate classes would be Character and >> SmallPoint (for integer coordinates in the range -2048..2047). >> SmallFloats would be possible, but I question their usefulness >> because the precision would be quite limited. > >But wouldn't the speedup in float calculations be worth it? I have a virtual machine which uses 8 byte doubles as slots and puts integers, object pointers, in the lower 32 bits of a Not-A-Number. There are a few bits in the upper 32 bits which can be used as a tag below the sign and exponent fields which flag a NaN. Since my language deals with floats as the most common data type the 8 bytes vs 4 bytes is a good trade. One advantage is that after the tag is checked no further masking is necessary to remove it since the lower 32 bits are clean. --- james mccartney james@clyde.as.utexas.edu james@lcsaudio.com If you have a PowerMac check out SuperCollider, a real time synth program: ftp://mirror.apple.com//mirrors/Info-Mac.Archive/gst/snd/super-collider-demo.hqx

Post a reply.

Go back to index.



Date: 97 Mar 13 1:19:18 pm From: Jecel Assumpcao Jr <jecel@lsi.usp.br> To: Squeak@create.ucsb.edu Subject: what's happening (was: A couple of fixes) Hans-Martin Mosner wrote: > Dan Ingalls wrote: > > What else is going on "out there"? My Squeak port to my ARM prototype is stopped as I am working full time on a tinySelf interpreter in Self. At least I got the hardware working again and the Linux bootp server is running, so it is just a matter of finding some time to work on it. > I'm waiting for Ralph Johnson's Typed Smalltalk stuff to appear > on the UIUC server. Then I'd like to integrate it into Squeak to > get the ability to dynamically compile primitives into machine > language. This would be a very good solution, though being able to compile anything to machine language would be even better. > My 3-d stuff will have to wait until after that, because I figured > out that using the normal Squeak VM generation process just takes > me too long to debug the primitives... I wanted to build a 3D prototype in Squeak as well, but as you say the turn around time is too long. I might get better results working directly in C. My idea for adapting to different hardware capacities is to have a series of renderers in increasing image quality and decreasing rendering speed. Every time something changes on the screen, that area is added to all the renderers' damage list. Then the first renderer is called (it works by simply warping pixels from other areas on the screen or otherwise filling with constant colors). It it even empties its damage list, then the second renderer (a traditional textured polygon scanner) is called, and if it ever finishes then the third (a raytracer?) is called and so on. So the system shows you the best image it can, given your CPU power, scene stability, other activities, etc... Clearly this is much better to develop in Smalltalk than in C, so I am looking for a way around the difficulties you point out (doing it in Self on an UltraSparc might be an option for me). > [immediate values] Having at least 16 bits for characters is a good idea, for Unicode is becoming more and more popular. Does the Apple worldscript thing use 24 bits? -- Jecel

Post a reply.

Go back to index.



Date: 97 Mar 13 1:19:31 pm From: Jecel Assumpcao Jr <jecel@lsi.usp.br> To: Squeak@create.ucsb.edu Subject: Re: Fabrik Dan Ingalls wrote: > > Aaron Rosenzweig wrote... > > >Wow, I'm confused....you mean Squeak has some extensions that make it similar > >to Prograph? > > No, we are building a new graphics sub-system for Squeak that will have a structure similar to those used in Fabrik (a bidirectional hookup language built in Smalltalk-80) and Morphic (a concrete graphical manipulation system built in SELF). What we are building should answer many people's needs for an interactive application construction facility in Squeak. > > - Dan Some good things about Morphic ============================== I have been programing in Self and using the morphic graphics framework, and teaching two students with it. Previously I had dome some programming with the classical Smalltalk model (what Squeak has) and Smalltalk/X and had taken a good look at Smalltalk Express, Smalltalk MT and Dolphin Smalltalk - three approaches to dealing with the Windows graphics model. There is simply no comparison!! With morphic, you take more time imagining what to do than trying to do it. It has the right blend of being able to do things "manually" or doing them by programming. The TeX-like layout system does most of what you want to do at a fraction of the cost of a full constraint system. Morphs bundle the view and controllers, and even the model into a much more understandable and compact framework. Some bad things about Morphic ============================= This "bundling the model" might not work as well for complex applications without multiple inheritance. It is so easy to break - the fun of major inheritance structure changes via drag-and-drop has a nasty side effect of making so easy to "currupt the prototypes" by accident. This wouldn't happen in a Smalltalk version, however. And there are lots of ways to have a bad method bring down a "world". The idea of creating a separate window (world) where the debugger can normally run while fixing the offending method is pretty neat - we were able to recover from all of the disasters the students faced (I didn't have as many problems myself - I guess I know what not to do...). This depends on morphic not being the machine's native GUI - an alternative would be to have the main loop replace any undrawable morphs with a flashing red square (using code that is as unbreakable as possible). That would allow the debugger to work in the damaged world. Using morphic without a true persistent object system is very frustrating. The Self transporter can't handle complex morphs and the special code to save morphs is a bit hard to use. The great thing is to be able to have morphs that were created "by hand" in your application directly, instead of have to generate creation code as in most window builders. But you have to have a way to move these morphs across snapshots (images). The morphic system avoids most invisible supporting graphics objects, which makes it much more concrete. But this makes it hard to share information - like making two morphs always be the same color, for example. One way around this would be the ability to select sets of morphs to apply changes to (this is a problem with manually changing morphs - when changing them under program control the lack of "wrappers" doesn't really matter as much). Things that might be neat in Fabric =================================== It has been such a long time since I read about Fabric that most of what I am about to write might be simply silly. I want to alway gain more power as we move on to newer systems. So it is frustrating not to be able to do something like this in most GUI based OSes: grep jecel httpd.log | awk - '{print $7}' | sort | uniq -c | sort | tail This shows me which of my web pages are the ten most popular. I can do all kinds of neat things like this. Granted, most unix users couldn't, but I don't see why I shouldn't have this power in a Smalltalk system. True, with the right methods and classes I could type something like this in a text pane and "print it" to get my answer. But I would rather string together little blocks, Fabric-style, to get this. Another frustration for a power user in a modern system is the lack of control over configuration. When the CD stops working in Win95, I can look at the devices "tree" and see that the CD-ROM driver has somehow become attached to the third IDE driver, when it should be using the second. Wouldn't it be wonderful if these drivers were connected as Fabric blocks and I could simply drag the connection to the right place? One problem with integrating controllers and view in morphic is the loss of flexibility. It would be good to have a more sophisticated event system than simply being able to "subscribe" to a set of events. I would love it if events would pass through a network of filters to be transformed into ever higher levels. These filters would be connected into a graph and would only get events from their inputs when someone needed their outputs (more of a demand driven than dataflow style). The application could "dip" into this event stream anywhere it was convenient. It could just be interested in getting text from the user (independently if is was typed, spoken, drawn with a pen, scanned in...) or it might want to see mouse (or pen) movements in a paint program. I am currently evaluating if CORBA's event system can be twisted into something like this (it seems that it can), but this really looks like a job for Fabric. Of course, there are the things that Fabric was actually designed for (a PARTS style app builder, right?), but I never have as much fun as trying to come up with new uses for programs. -- Jecel

Post a reply.

Go back to index.



Date: 97 Mar 13 4:04:24 pm From: "Dwight Hughes" <dhughes@intellinet.com> To: "Hans-Martin Mosner" <hmm@heeg.de> Cc: <Squeak@create.ucsb.edu> Subject: Re: A couple of fixes Hans-Martin Mosner wrote (amongst a lot more): > A possible outline for tag bits is: > ....00: normal object pointer > ....11: SmallInteger > ....10: forbidden > ....01: other immediate classes > 000001: UndefinedObject > 000101: False > 001001: True > 001101: Character > 010001: SmallPoint Interesting. I will have to think through your various proposals, but a quick thought: wouldn't a change of tag bits to ....00: SmallInteger ....11: normal object pointer .... instead be more advantageous? SmallIntegers could then be used directly for arithmetic and bitwise logic, and they will directly address 32 bit aligned addresses.

Post a reply.

Go back to index.



Date: 97 Mar 14 7:11:27 am From: Blair McGlashan <blair@intuitive.co.uk> To: 'Squeak List' <Squeak@create.ucsb.edu> Subject: Squeak on Windows CE I have been working on a port of Squeak to Windows CE (you know, the = eventual outcome of the "Window for Washing Machines" project:)) based = on Andreas' Win32 version, and I now have a first cut running inside the = VC++ NT4.0 emulator. Unfortunately I do not have the cross-compilers at present (I'm joining = the beta programme by fax at this very minute, having signed my life = away), so I am unable to test it out on one of the real little machines = just yet. Curses! I was wondering, therefore, if there was anybody out there who did have = the VC++ cross-compiler beta, and would like to try out the preliminary = version? Also I'd like to gauge how much interest there is in running Squeak on = CE based handhelds such as the Cassiopeia? The screen is small and there = is no colour, but, hey, what other development environments could be = squeezed onto a machine with only 4Mb total writable storage? Lastly, any advice on image shrinking apart from that in the startup = help workspaces? I've obviously had to compact out all the changes and = ditch the sources file. The eventual result of my efforts, I hope, will be a setup.exe which can = be run on one's desktop machine to completely install squeak on one's = HPC. I guess we'll also need some tools to help with synchronisation of = changes between desktop and HPC, but I don't want to worry about that = just yet! Blair McGlashan blair@intuitive.co.uk

Post a reply.

Go back to index.



Date: 97 Mar 14 8:09:30 am From: Dan Ingalls <DanI@wdi.disney.com> To: Blair McGlashan <blair@intuitive.co.uk> Cc: Squeak@create.ucsb.edu In-Reply-To: <01BC308B.9EDAD460@Blair> Subject: Re: Squeak on Windows CE >I have been working on a port of Squeak to Windows CE (you know, the= eventual outcome of the "Window for Washing Machines" project:)) based on= Andreas' Win32 version, and I now have a first cut running inside the VC++= NT4.0 emulator. Great. >Also I'd like to gauge how much interest there is in running Squeak on CE= based handhelds such as the Cassiopeia? The screen is small and there is no= colour, but, hey, what other development environments could be squeezed= onto a machine with only 4Mb total writable storage? Exactly. I'm personally extremely interested, and glad to hear you are= pursuing it. We've been watching all the PDA's for enough speed and space= to do it. What's the processor speed on the Cassiopeia? >Lastly, any advice on image shrinking apart from that in the startup help= workspaces? I've obviously had to compact out all the changes and ditch the= sources file. Are you aware of the "magic sources" facility that I put in Squeak a couple= of months ago? It gives you full sources with tempnames (but no comments)= from decompilation. It should not be hard to cause it to keep new changes= (with comments) on a file so that work you did on the road wouldn't be= compromised. See Smalltalk abandonSources, and the comment therein. >The eventual result of my efforts, I hope, will be a setup.exe which can be= run on one's desktop machine to completely install squeak on one's HPC. I= guess we'll also need some tools to help with synchronisation of changes= between desktop and HPC, but I don't want to worry about that just yet! I agree -- regular fileOuts should satisfy most needs in this regard. This sounds like a really fun project. John and I have already committed to= produce a seriously stripped-down image for a Newton port, as soon as it= became operational. Looks like you might be the first to actually take us= up on the offer. - Dan

Post a reply.

Go back to index.



Date: 97 Mar 14 8:38:15 am From: Maloney <johnm@wdi.disney.com> To: "David N. Smith" <dnsmith@watson.ibm.com> Cc: Squeak@create.ucsb.edu In-Reply-To: <v03007804af4ce36662ee@[129.34.225.178]> Subject: Re: A couple of fixes Re: I know what Fabrik is. What's Morphic? Morphic is the UI framework of the Self 4.0 system, architected by Randy Smith and myself with help from the rest of the Self group. Morphic was heavily influenced by Randy's prior work with the Alternate Reality Kit. Morphic strives to make everything the user sees in the UI-- menus, scrollbars, buttons, and perhaps even individual characters-- be concrete, manipulatable objects. For example, if you liked some item in a Morphic menu, you could grab the menu and extract that item, which is just a button after all. You could then use that button in some UI you were building. For example, you might turn the "dismiss" menu item into the close box for a dialog box you were building. The Self version of Morphic also supports multiple users working in a large, scrollable space dubbed "Kansas" (i.e., a large flat space inhabited by multiple people with Oz-ian overtones). Morphic was demo-ed at the 1994 OOPSLA and UIST conferences and described in papers at both those conferences the following year. The Squeak version of Morphic will not immediately support multiple users but is quite similar to the Self version in other respects. -- John

Post a reply.

Go back to index.



Date: 97 Mar 14 9:42:06 am From: Blair McGlashan <blair@intuitive.co.uk> To: 'Dan Ingalls' <DanI@wdi.disney.com> Cc: "'Squeak@create.ucsb.edu'" <Squeak@create.ucsb.edu> Subject: RE: Squeak on Windows CE [Dan]>...What's the processor speed on the Cassiopeia? Hmmm. Not precisely sure about that. It's a 32-bit RISC processor from = Hitachi called the SH3 which is available in 45 and 60Mhz speeds, but = which of them is in the Cassiopeia is not specified. The performance = seems (in the words of Rolls-Royce) "adequate". I haven't been able to = download any benchmarking software to it yet, so it's a bit difficult to = make any objective comparisons, but it certainly seems to run the = built-in apps (including Pocket Excel) OK. Some of the other HPCs use differenct CPUs, some even have a 64-bit MIPS = R4000, so I guess they'll be fast enough! [Blair]>>Lastly, any advice on image shrinking apart from that in the = startup help workspaces? I've obviously had to compact out all the = changes and ditch the sources file. [Dan]>Are you aware of the "magic sources" facility that I put in Squeak = a couple of months ago? It gives you full sources with tempnames (but = no comments) from decompilation. It should not be hard to cause it to = keep new changes (with comments) on a file so that work you did on the = road wouldn't be compromised. See Smalltalk abandonSources, and the = comment therein. Aha, I remember seeing something about that - it sounds like the very = thing! At the moment I'm having a problem with the source files anyway, in that = Windows CE has no drive letters, and no concept of a default or current = directory, so the DosFileDirectory class doesn't work correctly for CE. = It tries to open <path>:squeak1-18.changes and squeak1-18.changes. The = latter works on Win32 since it picks up the changes file from the = current directory (it always fails to open the absolute path), but not = on CE. Did I also see something about making the scrollbars a bit thinner, as = I'm a bit short of real-estate on a 480x240 display? [Blair]>>I guess we'll also need some tools to help with synchronisation = of changes between desktop and HPC, but I don't want to worry about that = just yet! [Dan]>I agree -- regular fileOuts should satisfy most needs in this = regard. One of the interesting things about CE is that it is designed to be used = in conjunction with a desktop machine, and hence has a built-in database = which can be automatically synchronised with the desktop (I'm not sure = how conflicts are resolved). Of course this would not be portable off = Win32. [Dan]>This sounds like a really fun project. John and I have already = committed to produce a seriously stripped-down image for a Newton port, = as soon as it became operational. Looks like you might be the first to = actually take us up on the offer. It is. I'm going to have to take a plane ride somewhere just so I can = type a method comment beginning with the words "I am writing this = introduction in an airplane at 35,000 feet..."! Overall I think the 4Mb HPCs and the OS are easily powerful enough to = run a mini-Smalltalk. Even the standard (sourceless) image will probably = fit, but obviously, the smaller the better. I will let you know when it's time to head off to Fry's with $599 in = your wallet 8-). Regards Blair

Post a reply.

Go back to index.



Date: 97 Mar 14 10:14:39 am From: Dan Ingalls <DanI@wdi.disney.com> To: Blair McGlashan <blair@intuitive.co.uk> Cc: Squeak@create.ucsb.edu In-Reply-To: <01BC30A0.ACB6C110@Blair> Subject: RE: Squeak on Windows CE >Did I also see something about making the scrollbars a bit thinner, as I'm= a bit short of real-estate on a 480x240 display? This can be found in goodies/gui/SmallColoredScrollBars.st on Stephen Pop's= web site. You may also want to experiment with small fonts. In 1.18, there is an= optional font-set named Clairvaux accessible via cmd-shift-k in the editor.= It has a very small but readable size available as cmd-5. Also cmd-9 will= display any font scrunched horizontally. Right now there isn't a SIMPLE way to convert the whole system to a new set= of fonts, but it's also not all that hard either. Let us know if you need= help on this. - Dan

Post a reply.

Go back to index.



Date: 97 Mar 14 11:00:12 am From: James McCartney <james@clyde.as.utexas.edu> To: Squeak@create.ucsb.edu In-Reply-To: <01BC30A0.ACB6C110@Blair> Subject: RE: Squeak on Windows CE At 5:53 PM +0000 3/14/97, Blair McGlashan wrote: >It is. I'm going to have to take a plane ride somewhere just so I can type >a method comment beginning with the words "I am writing this introduction >in an airplane at 35,000 feet..."! You can already do that with a laptop. What you should write is: "I am writing this introduction in an airplane lavatory at 35,000 feet..."! --- james mccartney james@clyde.as.utexas.edu james@lcsaudio.com If you have a PowerMac check out SuperCollider, a real time synth program: ftp://mirror.apple.com//mirrors/Info-Mac.Archive/gst/snd/super-collider-demo.hqx

Post a reply.

Go back to index.



Date: 97 Mar 14 11:04:17 am From: Tim Rowledge <rowledge@interval.com> To: Blair McGlashan <blair@intuitive.co.uk> Cc: Squeak mailinglist <squeak@create.ucsb.edu> In-Reply-To: <01BC30A0.ACB6C110@Blair> Subject: RE: Squeak on Windows CE On Fri 14 Mar, Blair McGlashan wrote: > [Dan]>...What's the processor speed on the Cassiopeia? > > Hmmm. Not precisely sure about that. It's a 32-bit RISC processor from Hitachi called > the SH3 which is available in 45 and 60Mhz speeds Assuming the memory system does a good job of keeping up with the CPU, you should hope to see about 1.5mbytecodes/sec on the Integer>benchmark test; this gues boughtto you by scaling the performance I get on my 200MHz ARM, which is quite similar to the Hitachi > At the moment I'm having a problem with the source files anyway, in that Windows CE ha > s no drive letters, and no concept of a default or current directory, so the DosFileDi > rectory class doesn't work correctly for CE. I had to cope with a similar situation on the Acorn filesystem and the following changes seemed to help:- !FileDirectory methodsFor: 'dictionary access'! includesKey: aString "Answer whether the receiver includes an element of the given name." "Note: aString may designate a file local to this directory, or it may be a full path name. Try both." ^ StandardFileStream isAFileNamed: (self fullNameFor: aString)! ! > Overall I think the 4Mb HPCs and the OS are easily powerful enough to run a mini-Small > talk. Even the standard (sourceless) image will probably fit, but obviously, the small > er the better. How much free memory do you end up with on Wince? Assuming say 150Kb for the VM, 1.5Mb for the current image and 1Mb of headroom for a useful config, as long as you get>2.75Mb free after startup it should go ok. -- Tim Rowledge tim@sumeru.stanford.edu http://sumeru.stanford.edu/tim

Post a reply.

Go back to index.



Date: 97 Mar 14 12:36:24 pm From: "David N. Smith" <dnsmith@watson.ibm.com> To: Squeak@create.ucsb.edu In-Reply-To: <199703131016.LAA08369@escher.cs.uni-magdeburg.de> Subject: Re: Immediate classes (was: Re: fixes) At 5:14 -0500 3/13/97, Michael Rueger wrote: >> In the meantime, I'm trying to move the system from 1 SmallInteger >> tag bit to 2 tag bits, allowing for other immediate classes. The >> first additional immediate classes would be Character and >> SmallPoint (for integer coordinates in the range -2048..2047). >> SmallFloats would be possible, but I question their usefulness >> because the precision would be quite limited. > >But wouldn't the speedup in float calculations be worth it? NO! 32 bits is not enough, there are problems and costs deciding just how to represent a smaller float (how short, how to round properly, how to expand to 32 bits for hardware to actually perform the calculations, do intermetiate calculations stay at 32 bits, etc. > >> Another idea is to make nil, true, false immediate. This could >> possibly speed up some operations in the VM since they would deal >> with constants instead of variables. Probably the speedup isn't >> worth it, though. > >Hmmm, aren't nil, false, true known to the VM anyhow as hard coded >pointer values? What would be the benefit of immediate classes here? > >Michael IBM Smalltalk has a number of immediate objects: true, false, nil, Characters (0:65535), SmallIntegers Object pointers have a 2-bit tag (at least on platforms I've checked and I think it is the case for all platforms). I don't know the benefits derived from this, but I assume (!?) that there were some or OTI would not have done it. (Yeah, I know the old saying about assumptions!) Dave _______________________________ David N. Smith dnsmith@watson.ibm.com IBM T J Watson Research Center Hawthorne, NY _______________________________ Any opinions or recommendations herein are those of the author and not of his employer.

Post a reply.

Go back to index.



Date: 97 Mar 14 12:45:25 pm From: Dan.Nichols@TXIVGRGATE.sprint.com To: squeak@create.ucsb.edu Subject: re: Squeak on Windows CE I, for one, think this is a great idea! That might push me over the edge to actually buy one of the gizmos. Dan

Post a reply.

Go back to index.



Date: 97 Mar 14 12:50:09 pm From: "David N. Smith" <dnsmith@watson.ibm.com> To: Squeak@create.ucsb.edu In-Reply-To: <3327BCD3.648A@heeg.de> Subject: Re: A couple of fixes At 3:37 -0500 3/13/97, Hans-Martin Mosner wrote: >Dan Ingalls wrote: >> What else is going on "out there"? > >...snip... >In the meantime, I'm trying to move the system from 1 SmallInteger >tag bit to 2 tag bits, allowing for other immediate classes. The >first additional immediate classes would be Character and >SmallPoint (for integer coordinates in the range -2048..2047). >...snip... > >A possible outline for tag bits is: >....00: normal object pointer >....11: SmallInteger >....10: forbidden >....01: other immediate classes >000001: UndefinedObject >000101: False >001001: True >001101: Character >010001: SmallPoint >...snip... > > >Hans-Martin Note the SmallPoint changes the semantics of #== for small points. It's probably not important in real life but it is not a transparent change. (But it also makes #= faster since it can be defined as #==). I'd suggest making its range be as large as possible so that it can be truly taken advantage of. A range of 16K is much better than 2k since it allows more code like this to work fast for a wider range of values: SmallPoint>>+ aSmallPoint ^ (x + aSmallPoint x) @ (y + aSmallPoint y) This does not have to allocate a new point through the general alocation mechanism since #@ would be a primitive usually answering a SmallPoint. People play lots of tricks to avoid creating new points. This lets them stop worrying when points are known to be 'small'. Dave _______________________________ David N. Smith dnsmith@watson.ibm.com IBM T J Watson Research Center Hawthorne, NY _______________________________ Any opinions or recommendations herein are those of the author and not of his employer.

Post a reply.

Go back to index.



Date: 97 Mar 14 1:00:23 pm From: "David N. Smith" <dnsmith@watson.ibm.com> To: Squeak@create.ucsb.edu In-Reply-To: <3327DC75.796@heeg.de> Subject: Re: Immediate classes (was: Re: fixes) At 5:52 -0500 3/13/97, Hans-Martin Mosner wrote: >Michael Rueger wrote: >> > ... >> > SmallFloats would be possible, but I question their usefulness >> > because the precision would be quite limited. >> >> But wouldn't the speedup in float calculations be worth it? > >Yes, but getting seriously inexact results quickly is probably not what >you want. >32-bit floating point is already considered inadequate for anything but >games by >some people :-) How would they look at 26-bit or 28-bit floats? >A better solution, IMHO, would be to have a class FloatArray that can be >used as a >container for float values, >...snip... > >Hans-Martin Note that 64-bit machines can encode both 32-bit and 64-bit floats. In fact, all object pointers might be encoded inside a 64-bit Not-A-Number; double floats would thus be the normal object pointer values and only if they are a (possibly special) NAN would the be an object pointer. The object pointer would then encode whatever it wants to encode, including full 32-bit floats. The downside is that the maximum integer length is about 40 bits as is the maximum object pointer (ignoring encoding bits for the moment). I did a presentation at the Smalltalk Extensions workshop at OOPSLA in 1996. A revised version of the white paper is at: http://www.dnsmith.com/dnsmith/Smalltalk It covers a number of floating point extensions to Smalltalk, including floating-point arrays. It's based mainly on IEEE floats. Dave _______________________________ David N. Smith dnsmith@watson.ibm.com IBM T J Watson Research Center Hawthorne, NY _______________________________ Any opinions or recommendations herein are those of the author and not of his employer.

Post a reply.

Go back to index.



Date: 97 Mar 14 1:12:57 pm From: "David N. Smith" <dnsmith@watson.ibm.com> To: Blair McGlashan <blair@intuitive.co.uk> Cc: "'Squeak List'" <Squeak@create.ucsb.edu> In-Reply-To: <01BC308B.9EDAD460@Blair> Subject: Re: Squeak on Windows CE At 10:23 -0500 3/14/97, Blair McGlashan wrote: >I have been working on a port of Squeak to Windows CE (you know, the >eventual outcome of the "Window for Washing Machines" project:)) based on >Andreas' Win32 version, and I now have a first cut running inside the VC++ >NT4.0 emulator. > >Unfortunately I do not have the cross-compilers at present (I'm joining >the beta programme by fax at this very minute, having signed my life >away), so I am unable to test it out on one of the real little machines >just yet. Curses! > >I was wondering, therefore, if there was anybody out there who did have >the VC++ cross-compiler beta, and would like to try out the preliminary >version? > >Also I'd like to gauge how much interest there is in running Squeak on CE >based handhelds such as the Cassiopeia? The screen is small and there is >no colour, but, hey, what other development environments could be squeezed >onto a machine with only 4Mb total writable storage? > >Lastly, any advice on image shrinking apart from that in the startup help >workspaces? I've obviously had to compact out all the changes and ditch >the sources file. > >The eventual result of my efforts, I hope, will be a setup.exe which can >be run on one's desktop machine to completely install squeak on one's HPC. >I guess we'll also need some tools to help with synchronisation of changes >between desktop and HPC, but I don't want to worry about that just yet! > >Blair McGlashan >blair@intuitive.co.uk I've had an HP100 for years and have successfully run Smalltalk/V (the original DOS version) on it. Since the HP100 is a pocked-sized clone of an IBM PC/XT, including all screen modes except real color, everything just runs. The only problem is that it requires a mouse to be really usable and the mouse and cords were as big and heavy as the HP100 itself, and clumsy. If it just had one of those IBM Red Eraserheads or, a track ball it would have been lovely. (I even ran Digitalk Methods on an HP95 just to show it would work. The HP95 was a semi-XT clone with a virtual 25x80 character display but only 16x40 real characters. One scrolled the real screen around on the virtual display. But it did run...) I'm looking forward to the HP entry in the pocket windows market this summer and would love to have Squeak on it. Dave _______________________________ David N. Smith dnsmith@watson.ibm.com IBM T J Watson Research Center Hawthorne, NY _______________________________ Any opinions or recommendations herein are those of the author and not of his employer.

Post a reply.

Go back to index.



Date: 97 Mar 16 9:25:05 pm From: Dan Ingalls <DanI@wdi.disney.com> To: Squeak@create.ucsb.edu Subject: Five Easy Pieces --============_-1353545271==_============ Content-Type: text/plain; charset="us-ascii" Attached are five short fileIns with various fixes/tweaks for Squeak 1.18... TwoFixes-di.cs One fix for long replacements in SeqColl>>copyReplaceAll(tokens), and the other for Rectangle>>containsRect:, which never can have worked since it was written, years ago! allButFirstAndLast-di.cs Useful complements to the first and last methods in SequencableCollection. TempNameFix-di.cs Fixes an error that occasionally occurs when more than one temporary name is removed automatically by the programmer assistance facilities. VersionsFix-di.cs Fixes an occasional bug caused when the sources scanner attempted to parse a non-existent back link in the sources file. The fix is to only attempt this in changes files, where there should be no problem. FileListStuff-di.cs Causes FileLists to display a summary of file info in the current folder when no file is selected. The information can thus be copied as text for use elsewhere (I pasted the file names in this message that way). Enjoy - Dan --============_-1353545271==_============ Content-Type: text/plain; name="TwoFixes-di.cs"; charset="us-ascii" Content-Disposition: attachment; filename="TwoFixes-di.cs" 'From Squeak 1.18 of December 12, 1996 on 16 March 1997 at 9:34:28 pm'! "Change Set: TwoFixes Date: 16 March 1997 Author: Dan Ingalls One fix for long replacements in SeqColl>>copyReplaceAll(tokens), and the other for Rectangle>>containsRect:, which never can have worked since it was written, years ago!!"! !Rectangle methodsFor: 'testing'! containsRect: aRect "Answer whether aRect is within the receiver (OK to coincide)." ^ aRect origin >= origin and: [aRect corner <= corner] ! ! !SequenceableCollection methodsFor: 'private'! copyReplaceAll: oldSubstring with: newSubstring asTokens: ifTokens "Answer a copy of the receiver in which all occurrences of oldSubstring have been replaced by newSubstring. ifTokens (valid for Strings only) specifies that the characters surrounding the recplacement must not be alphanumeric. Bruce Simth, 12/8/96: startSearch must be incremented by 1 and not newSubstring if ifTokens is true. See example below. " | aString startSearch currentIndex endIndex | (ifTokens and: [(self isKindOf: String) not]) ifTrue: [self error: 'Token replacement only valid for Strings']. aString _ self. startSearch _ 1. [(currentIndex _ aString indexOfSubCollection: oldSubstring startingAt: startSearch) > 0] whileTrue: [endIndex _ currentIndex + oldSubstring size - 1. (ifTokens not or: [(currentIndex = 1 or: [(aString at: currentIndex-1) isAlphaNumeric not]) and: [endIndex = aString size or: [(aString at: endIndex+1) isAlphaNumeric not]]]) ifTrue: [aString _ aString copyReplaceFrom: currentIndex to: endIndex with: newSubstring. startSearch _ currentIndex + newSubstring size] ifFalse: [ ifTokens ifTrue: [startSearch _ currentIndex + 1] ifFalse: [startSearch _ currentIndex + newSubstring size]]]. ^ aString "Test case: 'test te string' copyReplaceAll: 'te' with: 'longone' asTokens: true " ! ! --============_-1353545271==_============ Content-Type: text/plain; name="allButFirstAndLast-di.cs"; charset="us-ascii" Content-Disposition: attachment; filename="allButFirstAndLast-di.cs" 'From Squeak 1.18 of December 12, 1996 on 16 March 1997 at 9:03:15 pm'! "Change Set: allButFirstAndLast Date: 16 March 1997 Author: Dan Ingalls Useful complements to the first and last methods in SequencableCollection"! !SequenceableCollection methodsFor: 'accessing'! allButFirst ^ self copyFrom: 2 to: self size! allButLast ^ self copyFrom: 1 to: self size - 1! ! --============_-1353545271==_============ Content-Type: text/plain; name="TempNameFix-di.cs"; charset="us-ascii" Content-Disposition: attachment; filename="TempNameFix-di.cs" 'From Squeak 1.18 of December 12, 1996 on 16 March 1997 at 9:01:53 pm'! "Change Set: TempNameFix Date: 16 March 1997 Author: Dan Ingalls Fixes an error that occasionally occurs when more than one temporary name is removed automatically by the programmer assistance facilities."! !Parser methodsFor: 'error correction'! removeUnusedTemps | str end start | str _ requestor text string. ((tempsMark between: 1 and: str size) and: [(str at: tempsMark) = $|]) ifFalse: [^ self]. encoder unusedTempNames do: [:temp | ((PopUpMenu labels: 'yes\no' withCRs) startUpWithCaption: ((temp , ' appears to be unused in this method. OK to remove it?') asText makeBoldFrom: 1 to: temp size)) = 1 ifTrue: [(encoder encodeVariable: temp) isUndefTemp ifTrue: [end _ tempsMark. ["Beginning at right temp marker..." start _ end - temp size + 1. end < temp size or: [temp = (str copyFrom: start to: end) and: [(str at: start-1) isSeparator]]] whileFalse: ["Search left for the unused temp" end _ requestor nextTokenFrom: end direction: -1]. end < temp size ifFalse: [(str at: start-1) = $ ifTrue: [start _ start-1]. requestor correctFrom: start to: end with: ''. str _ str copyReplaceFrom: start to: end with: ''. tempsMark _ tempsMark - (end-start+1)]] ifFalse: [PopUpMenu notify: 'You''ll first have to remove the statement where it''s stored into']]]! ! --============_-1353545271==_============ Content-Type: text/plain; name="VersionsFix-di.cs"; charset="us-ascii" Content-Disposition: attachment; filename="VersionsFix-di.cs" 'From Squeak 1.18 of December 12, 1996 on 16 March 1997 at 8:58:38 pm'! "Change Set: VersionsFix Date: 16 March 1997 Author: Dan Ingalls Fixes an occasional bug caused when the sources scanner attempted to parse a non-existent back link in the sources file. The fix is to only attempt this in changes files, where there should be no problem"! !ChangeList methodsFor: 'scanning'! scanVersionsOf: method class: class meta: meta category: category selector: selector | position prevPos prevFileIndex preamble tokens sourceFilesCopy | changeList _ OrderedCollection new. list _ OrderedCollection new. listIndex _ 0. position _ method filePosition. sourceFilesCopy _ SourceFiles collect: [:x | x isNil ifTrue: [ nil ] ifFalse: [x readOnlyCopy]]. file _ sourceFilesCopy at: method fileIndex. [position notNil & file notNil] whileTrue: [file position: (0 max: position-150). "Skip back to before the preamble" [file position < (position-1)] "then pick it up from the front" whileTrue: [preamble _ file nextChunk]. "Preamble is likely a linked method preamble, if we're in a changes file (not the sources file). Try to parse it for prior source position and file index" prevPos _ nil. ((file == sourceFilesCopy first) not and: [(preamble at: (preamble findLast: [:c | c isAlphaNumeric])) isDigit "Only tokenize if preamble ends with a digit"]) ifTrue: [tokens _ Scanner new scanTokens: preamble] ifFalse: [tokens _ Array new "ie cant be back ref"]. ((tokens size between: 7 and: 8) and: [(tokens at: tokens size-5) = #methodsFor:]) ifTrue: [prevPos _ tokens at: tokens size-2. prevPos = 0 ifTrue: [prevPos _ nil] "Zero means no source" ifFalse: [prevFileIndex _ tokens last]]. self addItem: (ChangeRecord new file: file position: position type: #method class: class name category: category meta: meta) text: class name , (meta ifTrue: [' class '] ifFalse: [' ']) , selector. position _ prevPos. prevPos notNil ifTrue: [file _ sourceFilesCopy at: prevFileIndex]]. sourceFilesCopy do: [:x | x notNil ifTrue: [x close]]. listSelections _ Array new: list size withAll: false! ! --============_-1353545271==_============ Content-Type: text/plain; name="FileListStuff-di.cs"; charset="us-ascii" Content-Disposition: attachment; filename="FileListStuff-di.cs" 'From Squeak 1.18 of December 12, 1996 on 16 March 1997 at 8:56:46 pm'! "Change Set: FileListStuff Date: 16 March 1997 Author: Dan Ingalls Causes FileLists to display a summary of file info in the current folder when no file is selected. The information can thus be copied as text for use elsewhere."! !FileList methodsFor: 'list access'! toggleFileListIndex: anInteger "Select the file name in the receiver's list whose index is the argument, anInteger. If the current selection index is already anInteger, deselect it." | item name | listIndex = anInteger ifTrue: [listIndex _ 0. fileName _ nil] ifFalse: [listIndex _ anInteger. item _ list at: anInteger. item first = $( ifTrue: "remove size or date" [item _ item copyFrom: (item indexOf: $)) + 2 to: item size]. (item endsWith: self folderString) ifTrue: ["remove [...] folder string and open the folder" name _ item copyFrom: 1 to: item size - self folderString size. listIndex _ 0. ^ self directory: (FileDirectory newOnPath: (directory fullNameFor: name))] ifFalse: ["open the file selected" self setFileName: item]]. self changed: #fileListIndex! ! !FileList methodsFor: 'private'! defaultContents list == nil ifTrue: [^ String new]. ^ String streamContents: [:s | s nextPutAll: 'NO FILE SELECTED'; cr. s nextPutAll: ' -- Folder Summary --'; cr. list do: [:item | s nextPutAll: item; cr]]! readContentsBrief: brevity "Read the contents of the receiver's selected file." listIndex = 0 ifTrue: [^self defaultContents] ifFalse: [^ super readContentsBrief: brevity]! ! --============_-1353545271==_============--

Post a reply.

Go back to index.



Date: 97 Mar 17 4:34:53 am From: Blair McGlashan <blair@intuitive.co.uk> To: 'Tim Rowledge' <rowledge@interval.com> Cc: 'Squeak List' <Squeak@create.ucsb.edu> Subject: RE: Squeak on Windows CE Tim Rowledge wrote: >I had to cope with a similar situation on the Acorn filesystem and >the following changes seemed to help:- >!FileDirectory methodsFor: 'dictionary access'! >includesKey: aString > "Answer whether the receiver includes an element of the given name." > "Note: aString may designate a file local to this directory, or it may be a full path name. Try both." > > ^ StandardFileStream isAFileNamed: (self fullNameFor: aString)! ! Ta. Now all I have to do is to define dir_Lookup() correctly! >How much free memory do you end up with on Wince? Assuming say 150Kb >for the VM, 1.5Mb for the current image and 1Mb of headroom for a >useful config, as long as you get>2.75Mb free after startup it should >go ok. At least 3Mb, allowing for contacts, diary, and documents, etc. The VM looks like it will be < 100k. Blair

Post a reply.

Go back to index.



Date: 97 Mar 17 4:41:20 am From: Blair McGlashan <blair@intuitive.co.uk> To: 'James McCartney' <james@clyde.as.utexas.edu> Cc: 'Squeak List' <Squeak@create.ucsb.edu> Subject: RE: Squeak on Windows CE [Blair]>>It is. I'm going to have to take a plane ride somewhere just so = I can type >>a method comment beginning with the words "I am writing this = introduction >>in an airplane at 35,000 feet..."! [James]>You can already do that with a laptop. What you should write is: >"I am writing this introduction in an airplane lavatory at 35,000 = feet..."! James You're obviously important enough to be sitting in business class. If = you were back in scumbag class with me, you'd probably object to my = elbows being in your face as I desperately typed away on my laptop = before the batteries went dead :). Blair

Post a reply.

Go back to index.



Date: 97 Mar 18 6:13:41 am From: "Andreas Raab" <raab@isg.cs.uni-magdeburg.de> To: Blair McGlashan <blair@intuitive.co.uk> Cc: squeak@create.ucsb.edu Subject: RE: Squeak Windows CE Port Hi Blair, Sorry for being somewhat late with my reply. It's been busy days here. But now for the CE issues: > > This is strange. What interfaces are present in CE? Is there wave > > audio support at all? > > Yes there is. Wave files can be played using sndPlaySound(), > but the lower level interfaces which allow one to manipulate wave > structures are not exposed at the SDK level Is there any winmm.dll in CE? Its the usual place for all of the multi media functions. If there is one, the low-level functions should be there as well. If not, we'll have to deal with sndPlaySound (which can also play sounds from memory as far as I can remember). [Color] > CE supports 2-bit grayscale. I notice that there isn't a 2-bit depth > at present. I was initially intending to limit it to 1-bit mono. The reason for not having 2-bit color depth is actually that the SetDIBitsToDevice() functions needs a valid BITMAPINFOHEADER structure and I have found that quite some cards do not like the non-standard 2 bits (note that BMP-files can not have a depth of 2 bits). My ATI card does well with 2 bits but others (like Matrox or Spea) don't. > Will I have to support all the bit depths? No, probably not. There is actually no need for other depths if you can only display 2 bits of grayscale. And I doubt that true color displays will become available soon on this market ;-) > Your use of StretchDIBitsToDevice() is an interesting way of getting > around all that messing with memory DCs, although the latter has the > advantage that specification of a source/dest rectangle with > Bit(Stretch)Blt() does work, so the clipping would presumably not be > necessary. I think I will have to fall back on BitBlt anyway, because > I don't think StretchDIBitsToDevice() is supported on CE. You may go this way, in particular if you're planning to support only one or two color depths. My primary goal was to support most of the color depths (such as 24 bit even if the display is only 8 bit and vice versa). This, in turn, would require to convert the bitmaps manually when using the BitBlt() or SetBitmapBits() so I decided to go for the device independent representation and leave the task of bitmap conversion to the display driver. [Power Management] > back to it. I was responsible for the dispatching of Windows messages > in Dolphin (which is event driven), and this puts itself to sleep > using a MsgWaitForMultipleObjects() from the idle process. This would be the best solution. However, the problem is that the io polling is called from several locations throughout the VM and not only from the primitive. If we _would_ know that the VM is waiting for the InputSemaphore then we could put this idle loop there. > Obviously suspending gracefully is easier in Dolphin than Squeak > because it is not designed to be portable, and it is event driven. I > would be happy to offer any help I can with this problem (or any > other, for that matter). I would also appreciate some help concerning the issue. > - CE does have a minimal C runtime library, but it does not include > the file I/O routines, so I will have to rewrite these to use the > Windows file I/O functions (which are mostly fairly similar). This is exactly what VC++ uses in its RTL. It should be no problem to get rid of these functions in my port of the VM. [Source handling] > - Have completely separate source files for Windows CE and Win32? > - Use conditional compilation, and some separate modules where > necessary? If somehow possible, I would prefer to use conditional compilation. So we can benefit from the developments of each other. > Also, it is sometimes possible to use the existing code by > implementing a pseudo version of the C runtime function, but I am a > bit reluctant to do that because space really is at a premium, and I > cannot provide an completely accurate implementation in the space > available, which might cause confusion later. We could use some of the code from GNUs RTL if this is not a legal problem. > - CE supports Unicode ONLY. Squeak is ANSI only (?). > This means it is necessary to translate > back and forth between single and double byte characters on occassion, > and unfortunately MultiByteToWideChar() and its opposite are not > supported! Did you notice that the ANSI part of Unicode has simply a high byte of zero? So, converting Ansi from and to Unicode is fairly simple. > My one remaining problem (at least until I try to start running it:) > is the absence of StretchDIBitsToDevice(). I am going to have to use > DIBSECTIONs, which, I am sure you aware, allow one to manipulate their > bits directly. I guess that it is not possible for me to actually > provide the bitmap used by Squeak for its internal blitting, as if I > could then I could create the DIBSECTION just once. You could do the same trick I've used. Simply reverse the image bits inplace provide it to the DIB function and then reverse it back. However, you should notice that the location of the bitmap displayed may change according to modifications of the window. > As it is I think I > will have to create one on the fly (in order to save the space of a > complete duplicate bitmap), and copy across the changed part of the > Squeak bitmap when painting. Any comments? I don't know how much space is needed for this, but it's probably worth trying. > At the moment I'm having a problem with the source files anyway, in > that Windows CE has no drive letters, and no concept of a default or > current directory, so the DosFileDirectory class doesn't work You may try to change the path delimiter to the unix forward slash. This will change the VM to use UnixFileDirectory (i.e. no drive letters) and should work well on Win32. Note that I do not know whether CE supports both delimiter types. Andreas -- Linear algebra is your friend - Trigonometry is your enemy. +===== Andreas Raab ============= (raab@isg.cs.uni-magdeburg.de) =====+ I Department of Simulation and Graphics Phone: +49 391 671 8065 I I University of Magdeburg, Germany Fax: +49 391 671 1164 I +=============< http://simsrv.cs.uni-magdeburg.de/~raab >=============+

Post a reply.

Go back to index.



Date: 97 Mar 18 8:37:58 pm From: Phillip Piper <jppiper@ozemail.com.au> To: Hans-Martin Mosner <hmm@heeg.de> Cc: Squeak@create.ucsb.edu Subject: Re: A couple of fixes At 09:37 13/03/97 +0100, Hans-Martin Mosner wrote: >A possible outline for tag bits is: >....00: normal object pointer >....11: SmallInteger >....10: forbidden >....01: other immediate classes What's the 'forbidden' tag bit for? Regards, Phillip ------------------------------------------------------------------ Phillip Piper jppiper@ozemail.com.au CompuTechnics Pty Ltd. "Java: the simple elegence of C++; the blinding speed of Smalltalk"

Post a reply.

Go back to index.



Date: 97 Mar 18 9:18:43 pm From: Phillip Piper <jppiper@ozemail.com.au> To: Hans-Martin Mosner <hmm@heeg.de> Cc: Squeak@create.ucsb.edu Subject: Re: A couple of fixes At 09:37 13/03/97 +0100, Hans-Martin Mosner wrote: >A possible outline for tag bits is: >....00: normal object pointer >....11: SmallInteger >....10: forbidden >....01: other immediate classes What's the 'forbidden' tag bit for? Regards, Phillip ------------------------------------------------------------------- Phillip Piper jppiper@ozemail.com.au (preferred) CompuTechnics Pty Ltd phillip.piper@computechnics.com.au "Java: the simple elegence of C++; the blinding speed of Smalltalk"

Post a reply.

Go back to index.



Date: 97 Mar 19 12:09:10 am From: Hans-Martin Mosner <hmm@heeg.de> To: Phillip Piper <jppiper@ozemail.com.au> Cc: Squeak@create.ucsb.edu Subject: Re: A couple of fixes Phillip Piper wrote: > > At 09:37 13/03/97 +0100, Hans-Martin Mosner wrote: > > >A possible outline for tag bits is: > >....00: normal object pointer > >....11: SmallInteger > >....10: forbidden > >....01: other immediate classes > > What's the 'forbidden' tag bit for? > There are two reasons that this is a forbidden tag bit combination: 1. the lowest bit indicates that and object is immediate, and the next bit indicates that it is a SmallInteger. SmallIntegers are always immediate, so it does not make sense to have the second bit on without the first. 2. The mark-and-sweep algorithm uses the bit combination as a sentinel value to avoid walking into the header part of an object. This means that it is not only unreasonable but actually impossible with the current memory management system (which I don't dare to touch) to use ...10 as a valid tag bit combination. Hans-Martin

Post a reply.

Go back to index.



Date: 97 Mar 19 10:29:32 am From: Dan Ingalls <DanI@wdi.disney.com> To: Squeak@create.ucsb.edu Subject: Alpha Blend Hack --============_-1353325386==_============ Content-Type: text/plain; charset="us-ascii" Content-Transfer-Encoding: quoted-printable =46olks - Ted Kaehler and I have been playing with translucent colors. As you may be= aware squeak has limited support for translucency, but only in 32-bit color= =2E The attached goodie shows how you can do alpha blending in any pixel depth= by copying into a 32-bit buffer, blending there, and then color-mapping the= result back down to, eg, 8 bits. After blending red across the top of the screen in 10 different alphas (but= you only see 6 if you're in 8-bit mode because the 8-bit color cube is only= 6x6x6), the demo goes into a little paint loop in which you can scribble= all over the screen using a brush that leaves translucent paint around the= edges. This is done with a travelling buffer so as to avoid the need for a= 32-bit copy of the entire screen. Enjoy - Dan and Ted --============_-1353325386==_============ Content-Type: text/plain; name="BitBlt_class-alphaBlendDemo.st"; charset="us-ascii" Content-Disposition: attachment; filename="BitBlt_class-alphaBlendDemo.st" 'From Squeak 1.18 of December 12, 1996 on 19 March 1997 at 9:12:45 am'! !BitBlt class methodsFor: 'examples'! alphaBlendDemo "To run this demo, use... Display restoreAfter: [BitBlt alphaBlendDemo] Displays 10 alphas, then lets you paint. Option-Click to stop painting." "This code exhibits alpha blending in any display depth by performing the blend in an off-screen buffer with 32-bit pixels, and then copying the result back onto the screen with an appropriate color map. - tk 3/10/97" "This version uses a sliding buffer for painting that keeps pixels in 32 bits as long as they are in the buffer, so as not to lose info by converting down to display resolution and back up to 32 bits at each operation. - di 3/15/97" | brush buff dispToBuff buffToDisplay mapDto32 map32toD prevP p brushToBuff theta buffRect buffSize buffToBuff brushRect delta newBuffRect bitsPerColor mask updateRect | "First compute color maps if any (nils are fine for RGB)" (Display depth <= 8) ifTrue: [mapDto32 _ (Color defaultColorMapFrom: Display depth to: 32) copy. "Use 4 bits per color to map down from 32 bits to 8 or less" "Following code copied from Color>>defaultColorMapFrom:" bitsPerColor _ 4. "... except for this" map32toD _ Bitmap new: (1 bitShift: bitsPerColor*3). mask _ (1 bitShift: bitsPerColor) - 1. 0 to: map32toD size - 1 do: [:i | map32toD at: i+1 put: ((Color red: ((i bitShift: 0 - (bitsPerColor*2)) bitAnd: mask) green: ((i bitShift: 0 - bitsPerColor) bitAnd: mask) blue: ((i bitShift: 0) bitAnd: mask) range: mask) pixelValueForDepth: Display depth)]]. "Now display 10 different alphas, across top of screen" buff _ Form extent: 500@50 depth: 32. dispToBuff _ BitBlt toForm: buff. dispToBuff colorMap: mapDto32. dispToBuff copyFrom: (50@10 extent: 500@50) in: Display to: 0@0. 1 to: 10 do: [:i | dispToBuff fill: (50*(i-1)@0 extent: 50@50) fillColor: (Color red alpha: i/10) rule: Form blend]. buffToDisplay _ BitBlt toForm: Display. buffToDisplay colorMap: map32toD. buffToDisplay copyFrom: buff boundingBox in: buff to: 50@10. "Create a brush with radially varying alpha" brush _ Form extent: 30@30 depth: 32. 1 to: 5 do: [:i | brush fillShape: (Form dotOfSize: brush width*(6-i)//5) fillColor: (Color red alpha: 0.02 * i - 0.01) at: brush extent // 2]. "Now paint with the brush using alpha blending." buffSize _ 100. buff _ Form extent: brush extent + buffSize depth: 32. "Travelling 32-bit buffer" dispToBuff _ BitBlt toForm: buff. "This is from Display to buff" dispToBuff colorMap: mapDto32. brushToBuff _ BitBlt toForm: buff. "This is from brush to buff" brushToBuff sourceForm: brush; sourceOrigin: 0@0. brushToBuff combinationRule: Form blend. buffToBuff _ BitBlt toForm: buff. "This is for slewing the buffer" [Sensor yellowButtonPressed] whileFalse: [prevP _ nil. buffRect _ Sensor cursorPoint - (buffSize // 2) extent: buff extent. dispToBuff copyFrom: buffRect in: Display to: 0@0. [Sensor redButtonPressed] whileTrue: ["Here is the painting loop" p _ Sensor cursorPoint - (brush extent // 2). (prevP == nil or: [prevP ~= p]) ifTrue: [prevP == nil ifTrue: [prevP _ p]. (p farFrom: prevP by: buffSize) ifTrue: ["Stroke too long to fit in buffer -- clip to buffer, and next time through will do more of it" theta _ (p-prevP) theta. p _ ((theta cos@theta sin) * buffSize asFloat + prevP) truncated]. brushRect _ p extent: brush extent. (buffRect containsRect: brushRect) ifFalse: ["Brush is out of buffer region. Scroll the buffer, and fill vacated regions from the display" delta _ brushRect amountToTranslateWithin: buffRect. buffToBuff copyFrom: buff boundingBox in: buff to: delta. newBuffRect _ buffRect translateBy: delta negated. (newBuffRect areasOutside: buffRect) do: [:r | dispToBuff copyFrom: r in: Display to: r origin - newBuffRect origin]. buffRect _ newBuffRect]. "Interpolate from prevP to p..." brushToBuff drawFrom: prevP - buffRect origin to: p - buffRect origin. "Update (only) the altered pixels of the destination" updateRect _ (p min: prevP) corner: (p max: prevP) + brush extent. buffToDisplay copy: updateRect from: updateRect origin - buffRect origin in: buff. prevP _ p]]]! ! --============_-1353325386==_============--

Post a reply.

Go back to index.



Date: 97 Mar 20 7:36:14 am From: Blair McGlashan <blair@intuitive.co.uk> To: 'Andreas Raab' <raab@isg.cs.uni-magdeburg.de> Cc: 'Squeak List' <Squeak@create.ucsb.edu> Subject: RE: Squeak Windows CE Port Andreas, >Is there any winmm.dll in CE? Its the usual place for all of the=20 >multi media functions. If there is one, the low-level functions=20 >should be there as well. If not, we'll have to deal with sndPlaySound=20 >(which can also play sounds from memory as far as I can remember). No. I have left out the sound for now, since it is not critical. >The reason for not having 2-bit color depth is actually that the=20 >SetDIBitsToDevice() functions needs a valid BITMAPINFOHEADER=20 >structure and I have found that quite some cards do not like the=20 >non-standard 2 bits (note that BMP-files can not have a depth of 2=20 >bits). My ATI card does well with 2 bits but others (like Matrox or=20 >Spea) don't. Yes, I noticed that I cannot create a 2-bit DIBSECTION with my I128. = I've implemented the 2-bit depth for CE, but I don't know whether it = works yet. >> Will I have to support all the bit depths? >No, probably not. There is actually no need for other depths if=20 >you can only display 2 bits of grayscale. And I doubt that true color=20 >displays will become available soon on this market ;-) I'm sure you are right! >> Your use of StretchDIBitsToDevice() is an interesting way of getting >> around all that messing with memory DCs, although the latter has the >> advantage that specification of a source/dest rectangle with >> Bit(Stretch)Blt() does work, so the clipping would presumably not be >> necessary. I think I will have to fall back on BitBlt anyway, because >> I don't think StretchDIBitsToDevice() is supported on CE. >You may go this way, in particular if you're planning to support only=20 >one or two color depths. My primary goal was to support most of the=20 >color depths (such as 24 bit even if the display is only 8 bit and=20 >vice versa). This, in turn, would require to convert the bitmaps=20 >manually when using the BitBlt() or SetBitmapBits() so I decided to=20 >go for the device independent representation and leave the task of=20 >bitmap conversion to the display driver. Unfortunately StretchDIBitsToDevice() is definitely not supported on CE, = so I cannot rely on this to do the depth translation for me. In order to = save space (and effort) I am not intending to perform any such = conversion at this stage, and will only support the 1 and 2-bit depths. = Since the handheld is such a specialized device, with very limited = memory (certainly not enough for Squeak to maintain a bitmap for a high = colour screen) I think this is the right approach. >[Power Management] >> back to it. I was responsible for the dispatching of Windows messages >> in Dolphin (which is event driven), and this puts itself to sleep >> using a MsgWaitForMultipleObjects() from the idle process. >This would be the best solution. However, the problem is that the io=20 >polling is called from several locations throughout the VM and not=20 >only from the primitive. If we _would_ know that the VM is waiting for=20 >the InputSemaphore then we could put this idle loop there. >> Obviously suspending gracefully is easier in Dolphin than Squeak >> because it is not designed to be portable, and it is event driven. I >> would be happy to offer any help I can with this problem (or any >> other, for that matter). >I would also appreciate some help concerning the issue. It sounds like a difficult problem with no easy solution. How about = getting the/an idle process to inform the VM when it thinks there is no = work to do? Any suggestions anybody? >> - CE does have a minimal C runtime library, but it does not include >> the file I/O routines, so I will have to rewrite these to use the >> Windows file I/O functions (which are mostly fairly similar).=20 >This is exactly what VC++ uses in its RTL. It should be no problem to=20 >get rid of these functions in my port of the VM. As the VM generated from 1.18 image now includes use of fopen(), = ftell(), etc, I have written limited versions of these which are as = compact as possible. These also work with the full Win32 version, but I = think it would be better to link the full CRT functions in that case. >>[Source handling] >> - Have completely separate source files for Windows CE and Win32?=20 >> - Use conditional compilation, and some separate modules where >> necessary? >If somehow possible, I would prefer to use conditional compilation.=20 >So we can benefit from the developments of each other. That's what I've done up to now. The only problem is that it makes some = of the modules a bit messy. >> Also, it is sometimes possible to use the existing code by >> implementing a pseudo version of the C runtime function, but I am a >> bit reluctant to do that because space really is at a premium, and I >> cannot provide an completely accurate implementation in the space >> available, which might cause confusion later. >We could use some of the code from GNUs RTL if this is not a legal=20 >problem. 1.18 forced my hand there, as I mention above. >> - CE supports Unicode ONLY. Squeak is ANSI only (?).=20 >> This means it is necessary to translate >> back and forth between single and double byte characters on = occassion, >> and unfortunately MultiByteToWideChar() and its opposite are not >> supported!=20 >Did you notice that the ANSI part of Unicode has simply a high byte=20 >of zero? So, converting Ansi from and to Unicode is fairly simple. That's what I've done. > My one remaining problem (at least until I try to start running it:) > is the absence of StretchDIBitsToDevice(). I am going to have to use > DIBSECTIONs, which, I am sure you aware, allow one to manipulate their > bits directly. I guess that it is not possible for me to actually > provide the bitmap used by Squeak for its internal blitting, as if I > could then I could create the DIBSECTION just once.=20 >You could do the same trick I've used. Simply reverse the image bits=20 >inplace provide it to the DIB function and then reverse it back. >However, you should notice that the location of the bitmap displayed=20 >may change according to modifications of the window. Yes, at the moment I'm copying the entire Squeak bitmap into a = DIBSECTION for simplicty, but I'm intending to just reverse the affected = rectangle of bits out directly into the dynamically created DIB, so I = don't need to modify the Squeak bitmap at all. >> As it is I think I >> will have to create one on the fly (in order to save the space of a >> complete duplicate bitmap), and copy across the changed part of the >> Squeak bitmap when painting. Any comments? >I don't know how much space is needed for this, but it's probably=20 >worth trying. It works fine, in fact. The bitmaps are quite small because of the = limited bit depth, and speed doesn't seem to be a problem. >> At the moment I'm having a problem with the source files anyway, in >> that Windows CE has no drive letters, and no concept of a default or >> current directory, so the DosFileDirectory class doesn't work >You may try to change the path delimiter to the unix forward slash. >This will change the VM to use UnixFileDirectory (i.e. no drive >letters) and should work well on Win32. Note that I do not know whether >CE supports both delimiter types. I've got this working OK now - I changed the file search primitive, and = modified FileDirectory>>includesKey: to fix the bug caused by it = hardcoding the Mac path delimiter. Thanks for your help.=20 I should have a setup program for installing Squeak onto Cassiopeia's on = Monday, as I have just received the cross-compiler from Microsoft. Regards Blair=00=00

Post a reply.

Go back to index.



Date: 97 Mar 21 5:53:07 am From: Hans-Martin Mosner <hmm@heeg.de> To: squeak@create.ucsb.edu Subject: Immediate Classes Dies ist eine mehrteilige Nachricht im MIME-Format. --------------1BB147DF20A5 Content-Type: text/plain; charset=us-ascii Content-Transfer-Encoding: 7bit Hello, now I've got the 2 tag bits code basically working. The files at http://www.heeg.de/~hmm/squeak/2tagbits can be filed in to change the VM and image from 1 SmallInteger tag bit to 2 tag bits, opening the possibility for up to 16 additional immediate classes at the moment. There is also a file-in implementing SmallPoint (really rough at the moment). Look at it, play with it, tell me what you think about it! Hans-Martin --------------1BB147DF20A5 Content-Type: text/html; charset=us-ascii Content-Transfer-Encoding: 7bit <BASE HREF="http://www.heeg.de/~hmm/squeak/2tagbits/"> <title>How to change your Squeak to 2 tag bits and more immediate classes</title> <h1>How to change your Squeak to 2 tag bits and more immediate classes</h1> <blockquote> Hans-Martin Mosner<br> <<a href="mailto:hmm@heeg.de">hmm@heeg.de</a>> (at work),<br> <<a href="mailto:hm.mosner@cww.de">hm.mosner@cww.de</a>> (at home)<br> March 20, 1997 </blockquote> To do this, you need to be able to re-create your Squeak VM from the Smalltalk sources in Squeak. I've tried to make the process as easy as possible, and the changes to the VM should applicable even if you have modified it with your own primitives. <p> There are 4 files: <hr> <ul> <li><a href="VM-2TagBits.cs">VM-2TagBits.cs</a><br> This changes your VM. You should file it into the image in which you generate your VM, and then build a new VM. Be sure to backup everything, as this change is radical!<br> The new VM will have an image format version of 6503 as opposed to 6502, so you won't be able to run images saved by this VM with any older VM. The new VM will be able to read old images, but the images won't run correctly unless <b>SmallInt-2TagBits.cs</b> has been filed in first. The reason for this is that the old SmallIntegers are converted to the new format by simply shifting them 1 bit to the left. If they are not in the appropriate range, their value will change.<br> In the new VM, primitives 126 and 127 are defined to support more immediate classes. They are used by <b>MoreImmediateClasses.cs</b>. <li><a href="SmallInt-2TagBits.cs">SmallInt-2TagBits.cs</a><br> This scans the image for SmallIntegers that would not fit into the range that SmallInts will have after the 2-tag-bit conversion. These SmallIntegers are converted into LargeIntegers. The file-in also changes the SmallInteger minVal and maxVal methods to check for the actual range ofSmallIntegers on image startup. An image prepared with these changes will still be ok to use with an older VM, but when you want to save it for conversion by a 2-tag-bit VM, you should execute "<code>SmallInteger prepareFor2BitTags</code>" before saving to make certain that no SmallIntegers will be incorrectly converted. <li><a href="MoreImmediateClasses.cs">MoreImmediateClasses.cs</a><br> The code in this file-in supports the creation of more immediate objects. Currently it consists of 2 primitives that are used to convert between SmallIntegers and other immediate values, plus somecode to register Immediate classes with the CompactClasses Array (which will be extended from 31 to 47 entries for this purpose). <li><a href="SmallPoint.cs">SmallPoint.cs</a><br> This is an example of how the mechanism can be used. It modifies the methods in class Point so that only the getters and setters for x and y access the instance variables directly. Then a new subclass SmallPoint is defined. You can use instances of the class just like normal points, but the VM is not yet aware of them. Be warned that this has not been fully tested! </ul> <hr> SmallCharacters and other funny and useful things are left as an exercise for the reader... <p> Have fun with this. I hope it will make it into the next Squeak release. <p> Hans-Martin --------------1BB147DF20A5--

Post a reply.

Go back to index.



Date: 97 Mar 21 6:59:11 am From: Dan Ingalls <DanI@wdi.disney.com> To: ssadams@us.ibm.com Cc: Squeak@create.ucsb.edu In-Reply-To: <5040100002156074000002L042*@MHS> Subject: After 2.0 [Squeakers - We are hoping to get 2.0 out in May, and I thought all would be= interested in the answer to this query from Sam Adams] >On 2.0, all the enhancements sound exciting. What do you think will be the >fate of pre-2.0 images? I wouldn't expect anyone to worry about updating >pre-2.0 images in the future, but do you plan to keep them functional on ne= w >VMs? I am very interested in getting to the new stuff, but I want to prese= rve >and work in MVC-based images with all my ported code as well. As I wrote in the earlier message, we'll do a double release; one in the old= MVC style, and one that is Morphic-based, event-driven, etc. For those who= don't want to go forward, that would be the time to archive the Squeak MVC= image, sources, and VM. We would not make any effort to maintain VMs for= the MVC fork but, if there's a lot of interest in that version, someone= will probably come forward to maintain and enhance it. =20 We plan to convert all the MVC apps (browsers, mostly) in the current image= to Morphic, and we don't want to spend more than a week doing it, so we= will make porting of existing apps as easy as possible. Even though it's= against our religion, we'll probably even write down some guidelines about= how how to do it, and all the existing apps will be there as examples of= how the new environment works. Obviously, we hope most people will find= this new framework compelling as soon as they get used to it. - Dan

Post a reply.

Go back to index.



Date: 97 Mar 21 10:35:21 am From: Hans-Martin Mosner <hm.mosner@cww.de> To: Hans-Martin Mosner <hmm@heeg.de> Cc: squeak@create.ucsb.edu Subject: Re: Immediate Classes Sorry, I goofed up. After filing in VM-2BitTags.cs, you need to execute Interpreter patchInitializePrimitiveTable to patch the initializePrimitiveTable method. I'll fix the files on our server after the weekend when I get back to work. Hans-Martin

Post a reply.

Go back to index.



Date: 97 Mar 21 2:14:09 pm From: charnley@interval.com (Don Charnley) To: Squeak@create.ucsb.edu Subject: recursive block error detection Squeak precludes the recursive execution of block contexts. The Interpreter comments imply this is caught by the vm, and it is not. The following changes catch this, in a slightly more gentle way than without having them installed. An additional patch to cannotReturn: is included here, for any one interested (some recursive block executions 'exit' through there). An example test case is the following: ********************* | counter | counter := [ : x | x = 0 ifTrue: [^0] ifFalse: [^counter value: (x - 1)]]. counter value: 1 ********************* !Interpreter methodsFor: 'control primitives'! primitiveValue | blockContext blockArgumentCount initialIP | blockContext _ self stackValue: argumentCount. blockArgumentCount _ self argumentCountOfBlock: blockContext. self success: argumentCount = blockArgumentCount. ((blockContext = activeContext) | (((self fetchPointer: InstructionPointerIndex ofObject: blockContext) ~= (self fetchPointer: InitialIPIndex ofObject: blockContext)) & ((self fetchPointer: InstructionPointerIndex ofObject: blockContext) ~= (self splObj: NilObject)))) ifTrue: [successFlag _ false]. "catch illegal recursions" successFlag ifTrue: [self transfer: argumentCount fromIndex: self stackPointerIndex - argumentCount + 1 ofObject: activeContext toIndex: TempFrameStart ofObject: blockContext. "Assume: The call to transfer:... makes blockContext a root if necessary, allowing use to use unchecked stored in the following code." self pop: argumentCount + 1. initialIP _ self fetchPointer: InitialIPIndex ofObject: blockContext. self storePointerUnchecked: InstructionPointerIndex ofObject: blockContext withValue: initialIP. self storeStackPointerValue: argumentCount inContext: blockContext. self storePointerUnchecked: CallerIndex ofObject: blockContext withValue: activeContext. self newActiveContext: blockContext]! ! !Interpreter methodsFor: 'control primitives'! primitiveValueWithArgs | argumentArray blockContext blockArgumentCount arrayClass arrayArgumentCount initialIP | argumentArray _ self popStack. blockContext _ self popStack. blockArgumentCount _ self argumentCountOfBlock: blockContext. arrayClass _ self fetchClassOf: argumentArray. self success: (arrayClass = (self splObj: ClassArray)). successFlag ifTrue: [arrayArgumentCount _ self fetchWordLengthOf: argumentArray. self success: arrayArgumentCount = blockArgumentCount]. ((blockContext = activeContext) | (((self fetchPointer: InstructionPointerIndex ofObject: blockContext) ~= (self fetchPointer: InitialIPIndex ofObject: blockContext)) & ((self fetchPointer: InstructionPointerIndex ofObject: blockContext) ~= (self splObj: NilObject)))) ifTrue: [successFlag _ false]. "catch illegal recursions" successFlag ifTrue: [self transfer: arrayArgumentCount fromIndex: 0 ofObject: argumentArray toIndex: TempFrameStart ofObject: blockContext. "Assume: The call to transfer:... makes blockContext a root if necessary, allowing use to use unchecked stored in the following code." initialIP _ self fetchPointer: InitialIPIndex ofObject: blockContext. self storePointerUnchecked: InstructionPointerIndex ofObject: blockContext withValue: initialIP. self storeStackPointerValue: arrayArgumentCount inContext: blockContext. self storePointerUnchecked: CallerIndex ofObject: blockContext withValue: activeContext. self newActiveContext: blockContext] ifFalse: [self unPop: 2]! ! !BlockContext methodsFor: 'private'! cannotReturn: arg "Kills off processes that didn't terminate properly" "Display reverse; reverse." "<-- So we can catch the suspend bug" self error: 'cannot return error -- proceed at your own risk'. Processor terminateActive! ! I am not on the Squeak mailing list. Please excuse any improprieties in this posting. don

Post a reply.

Go back to index.



Date: 97 Mar 22 3:37:25 am From: Hans-Martin Mosner <hm.mosner@cww.de> To: Squeak Mailing List <squeak@create.ucsb.edu> Subject: Immediate Characters Hi Squeakers, Immediate Characters are just around the corner... There is still some problem in the code that converts images to use immediate characters, but I think that I can solve it over the weekend. Given a 2-byte string class and appropriate text rendering functions, Unicode could be accessible to Squeak soon... Probably there will be support in the VM for SmallPoints as well after the weekend, I don't know yet whether there will be enough time. Enough for today... Hans-Martin

Post a reply.

Go back to index.



Date: 97 Mar 24 1:21:37 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 Mar 21 Subject: Re: After 2.0 > We plan to convert all the MVC apps (browsers, mostly) in the current image > to Morphic... I'll certainly gladly port my DisplayList and DisplayListView framework to the Morphic/event-driven basis! stp Stephen Travis Pope, Center for Research in Electronic Art Technology (CREATE), Department of Music, U. of California, Santa Barbara (UCSB) Editor--Computer Music Journal, MIT Press stp@create.ucsb.edu, http://www.create.ucsb.edu/~stp/

Post a reply.

Go back to index.



Date: 97 Mar 25 12:36:11 pm From: ken.stevens@srs.gov To: Squeak@create.ucsb.edu, charnley@interval.com Subject: Fractions Squeaks handling of fractions seems to be inconsistent with the smalltalk model. For instance: (1/3) + (1/3) should return 2/3, instead it returns the float value. Is this intentional in squeaks implementation or am I missing something? Thanks, Ken

Post a reply.

Go back to index.



Date: 97 Mar 25 1:43:24 pm From: Tim Rowledge <rowledge@interval.com> To: ken.stevens@srs.gov Cc: Squeak mailinglist <Squeak@create.ucsb.edu> In-Reply-To: <199703252045.AA00199@gateway1.srs.gov> Subject: Re: Fractions On Tue 25 Mar, ken.stevens@srs.gov wrote: > > > Squeaks handling of fractions seems to be inconsistent with the smalltalk model. > For instance: (1/3) + (1/3) should return 2/3, instead it returns the float > value. Is this intentional in squeaks implementation or am I missing something? All you've missed is that the printString for Fractions produces a Float; if you inspect the answer instead, you'll see it is a Fraction as you expected. Sometimes I like this, sometimes I don't.... -- Tim Rowledge: rowledge@interval.com (w) +1 (415) 856-7230 (w) tim@sumeru.stanford.edu (h) <http://sumeru.stanford.edu/tim>

Post a reply.

Go back to index.



Date: 97 Mar 26 12:04:51 am From: Hans-Martin Mosner <hmm@heeg.de> To: ken.stevens@srs.gov Cc: Squeak@create.ucsb.edu, charnley@interval.com Subject: Re: Fractions ken.stevens@srs.gov wrote: > > Squeaks handling of fractions seems to be inconsistent with the smalltalk model. > For instance: (1/3) + (1/3) should return 2/3, instead it returns the float > value. Is this intentional in squeaks implementation or am I missing something? > > Thanks, > > Ken Fractions work right, they only print wrong. If you inspect the result of your expression, you see that it is really a fraction. I was also greatly surprised by this behavior. In most cases (especially for large numerators and denominators) this is preferable to the conventional way, because it gives you a better idea about the magnitude of the fraction. However, there should be a slight hint that what you're seeing is really not a Float but a Fraction... Hans-Martin

Post a reply.

Go back to index.



Date: 97 Mar 26 8:27:03 am From: "David N. Smith" <dnsmith@watson.ibm.com> To: Squeak@create.ucsb.edu In-Reply-To: <3338DAFE.B30@heeg.de> Subject: Re: Fractions At 3:14 -0500 3/26/97, Hans-Martin Mosner wrote: >ken.stevens@srs.gov wrote: >> >> Squeaks handling of fractions seems to be inconsistent with the >>smalltalk model. >> For instance: (1/3) + (1/3) should return 2/3, instead it returns the float >> value. Is this intentional in squeaks implementation or am I missing >>something? >> >> Thanks, >> >> Ken > >Fractions work right, they only print wrong. If you inspect the result of >your expression, you see that it is really a fraction. I was also greatly >surprised by this behavior. In most cases (especially for large numerators >and denominators) this is preferable to the conventional way, because it >gives you a better idea about the magnitude of the fraction. However, there >should be a slight hint that what you're seeing is really not a Float but a >Fraction... > >Hans-Martin Ugh. I hadn't seen this one. I agree they print wrong. Fractions should print as fractions. It is certainly easy enough to add an asFloat if you want to see an approximate value but if the fraction won't print as a fraction how do you ever tell (short of an inspector) just what the result really is? It looks like the code was there and right but that someone has 'fixed' it wrong: printOn: aStream self asFloat printOn: aStream "aStream nextPut: $(. numerator printOn: aStream. aStream nextPut: $/. denominator printOn: aStream. aStream nextPut: $)" Dave _______________________________ David N. Smith dnsmith@watson.ibm.com IBM T J Watson Research Center Hawthorne, NY _______________________________ Any opinions or recommendations herein are those of the author and not of his employer.

Post a reply.

Go back to index.



Date: 97 Mar 26 9:40:17 am From: kgarrels@rhein-neckar.netsurf.de (Kai Garrels) To: Squeak@create.ucsb.edu (Squeak) In-Reply-To: <9703240921.AA11660@tango.create.ucsb.edu> Subject: Re: After 2.0 > > We plan to convert all the MVC apps (browsers, mostly) in the current image > > to Morphic... Everybody is talking about Morphic...what is it? Where can I learn about it? Thanks for some hints. bye, kai -- Kai Garrels Mannheim Germany

Post a reply.

Go back to index.



Date: 97 Mar 26 11:29:05 am From: ken.stevens@srs.gov To: Squeak@create.ucsb.edu, kgarrels@rhein-neckar.netsurf.de Subject: Re[2]: After 2.0 Where do I get a description of 2.0 Thanks, Ken _______________________________________________________________________________ Subject: Re: After 2.0 From: kgarrels@rhein-neckar.netsurf.de at Mailhub Date: 3/26/97 1:52 PM > > We plan to convert all the MVC apps (browsers, mostly) in the current image > > to Morphic... Everybody is talking about Morphic...what is it? Where can I learn about it? Thanks for some hints. bye, kai -- Kai Garrels Mannheim Germany

Post a reply.

Go back to index.



Date: 97 Mar 26 2:14:19 pm From: Maloney <johnm@wdi.disney.com> To: ken.stevens@srs.gov Cc: Squeak@create.ucsb.edu, kgarrels@rhein-neckar.netsurf.de In-Reply-To: <199703261936.AA14219@gateway1.srs.gov> Subject: Re[2]: After 2.0 Ken and Kai: Your best bet is to read the OOPSLA'95 and UIST'95 papers about the Self version of Morphic. You can also read the Morphic manual in the Self 4.0 release, reachable via: http://self.sunlabs.com/ The Squeak version of Morphic is different in details, but similar in philosophy to the Self version. -- John >Where do I get a description of 2.0 > > >Thanks, > > >Ken >_______________________________________________________________________________ >Subject: Re: After 2.0 >From: kgarrels@rhein-neckar.netsurf.de at Mailhub >Date: 3/26/97 1:52 PM > >> > We plan to convert all the MVC apps (browsers, mostly) in the current image >> > to Morphic... > >Everybody is talking about Morphic...what is it? Where can I learn about >it? > >Thanks for some hints. > >bye, >kai >-- >Kai Garrels >Mannheim >Germany

Post a reply.

Go back to index.



Date: 97 Mar 27 12:54:29 am From: Hans-Martin Mosner <hmm@heeg.de> To: Maloney <johnm@wdi.disney.com> Cc: Squeak@create.ucsb.edu Subject: Re: Re[2]: After 2.0 John Maloney wrote: > > Ken and Kai: > > Your best bet is to read the OOPSLA'95 and UIST'95 papers about the Self version > of Morphic. You can also read the Morphic manual in the Self 4.0 release, > reachable via: > > http://self.sunlabs.com/ > > The Squeak version of Morphic is different in details, but similar in > philosophy to the Self version. > > -- John >From the tutorial and the screenshots, I think that this is exactly what I would love for UI work in Squeak... One thing that bothers me though: Saving morphs in the Self version seems to be kind of tricky. For Squeak, I'd like to have the morphs compiled into classes for easy file-out/in and browsing. In VisualWorks, which stores UI designs in methods, it is possible to use the browsing tools to see what messages are sent from the user interface etc. (With the sad exception of aspect paths. Why didn't they use literal arrays for them?) Another worry is the updating mechanism. Somewhere in the part of the tutorial dealing with saving and loading of morphs, it is mentioned that the value updating mechanism of the loaded morph needs to be restarted. This sounds a lot like a polling process that regularly looks for a value change in the underlying object. Please tell me it ain't so! Hans-Martin

Post a reply.

Go back to index.



Date: 97 Mar 27 2:00:18 am From: Michael Rueger <michael@ISG.CS.Uni-Magdeburg.De> To: hmm@heeg.de (Hans-Martin Mosner) Cc: Squeak@create.ucsb.edu In-Reply-To: <333A390C.178E@heeg.de> from "Hans-Martin Mosner" at Mar 27, 97 10:08:28 am Subject: Re: Re[2]: After 2.0 > One thing that bothers me though: Saving morphs in the Self version seems to > be kind of tricky. For Squeak, I'd like to have the morphs compiled into > classes for easy file-out/in and browsing. Hmmm, we use an external storage mechanism, which makes it easy to store and retrieve UIDefinitions at runtime (e.g. language dependent). Another more conceptual point: UIDefinitions are data, not source code, that's why I never really liked the VW mechanism. > In VisualWorks, which stores UI designs in methods, it is possible to use the > browsing tools to see what messages are sent from the user interface etc. OK, this is an advantage, although it won't be too difficult to browse through the data. Michael -- + Michael Rueger ------------------------------------------------------------+ + Universitaet Magdeburg FIN-ISG Universitaetsplatz 2 D-39106 Magdeburg + + voice: ++49-(0)391-67-18760 fax: ++49-(0)391-67-11164 + + michael@isg.cs.uni-magdeburg.de http://simsrv.cs.uni-magdeburg.de/~michael + +++++ You Can Take My Mac When You Pry My Cold Dead Fingers Off the Mouse ++++

Post a reply.

Go back to index.



Date: 97 Mar 27 7:40:14 am From: Dan Ingalls <DanI@wdi.disney.com> To: Hans-Martin Mosner <hmm@heeg.de> Cc: Squeak@create.ucsb.edu In-Reply-To: <333A390C.178E@heeg.de> Subject: Re: Re[2]: After 2.0 >From the tutorial and the screenshots, I think that this [Morphic] is exactly >what I would love for UI work in Squeak... >One thing that bothers me though: Saving morphs in the Self version seems to >be kind of tricky. For Squeak, I'd like to have the morphs compiled into >classes for easy file-out/in and browsing. This is exactly what I felt, and it is how Morphic will work in Squeak. If there is significant interest, John and i could send out an early version for comments and criticism. - Dan

Post a reply.

Go back to index.



Date: 97 Mar 27 7:45:42 am From: Hans-Martin Mosner <hmm@heeg.de> To: Dan Ingalls <DanI@wdi.disney.com> Cc: Squeak@create.ucsb.edu Subject: Re: Re[2]: After 2.0 Dan Ingalls wrote: > If there is significant interest, John and i could send out an early version > for comments and criticism. Significant interest? I've not heard such an understatement in the last 5 years... You could make me very happy (and my wife very unhappy :-( ) if you sent out something so that I can play with it over the Easter weekend... Even if not, the prospect of getting a user interface that is both nicer to look at and nicer to work with is very exciting. Hans-Martin

Post a reply.

Go back to index.



Date: 97 Mar 27 8:10:55 am From: stp (Stephen Travis Pope) To: DanI@wdi.disney.com Cc: Squeak@create.ucsb.edu Subject: Re: Re[2]: After 2.0 > If there is significant interest, John and i could send out an early version > for comments and criticism. YES!

Post a reply.

Go back to index.



Date: 97 Mar 27 9:20:10 am From: Maloney <johnm@wdi.disney.com> To: Hans-Martin Mosner <hmm@heeg.de> Cc: Squeak@create.ucsb.edu In-Reply-To: <333A390C.178E@heeg.de> Subject: Polling in Morphic Re: >Another worry is the updating mechanism. Somewhere in the part of the tutorial >dealing with saving and loading of morphs, it is mentioned that the value >updating mechanism of the loaded morph needs to be restarted. This sounds a >lot like a polling process that regularly looks for a value change in the >underlying object. Please tell me it ain't so! Morphs can have a "step" method that is run periodically. This supports animations and simulations and generally keeps things lively. The World keeps a list of the morphs that want to be stepped, and it is this list that must be amended when loading a saved morph. (It's a bit like restarting the life processes of a brine shrimp that has been dried out and then reconstituted.) You're right that the stepping mechanism was also used in the Self version of Morphic to watch for changes in objects. There are times when such polling is appropriate. It is unobtrusive; it can be used to observe the result of sending any message, not just a slot accessor (for example, you can observe the center of a rectangle, which is a computed, or "virtual," slot); and it can be used to watch for changes outside of the system itself, such as the arrival of new mail. Obviously overuse of polling is inefficient, but if you adjust the sampling interval appropriately and only update the display when values actually change, the overhead is extremely low. Furthermore, other mechanisms can be used where appropriate to reduce reliance on polling. For example, MVC-style dependents notification works for models that expect to be viewed and thus report their changes. This reduces the use of polling to "unanticipated observing". And, of course, polling is typically used only for a small number of on-screen displays. More exotic schemes like transparant forwarders can be used to catch changes in objects that weren't written to be viewed, but they have these schemes have their disadvantages as well; they may slow down messages sent to the watched object, they can be hard to debug, and they introduce complexity, and they can be difficult to apply to composite objects that allow clients to change subparts directly (e.g., to watch a rectangle you need transparant forwarders for its origin and corner points, as well as the rectangle itself). -- John

Post a reply.

Go back to index.



Date: 97 Mar 28 3:50:16 pm From: James McCartney <james@clyde.as.utexas.edu> To: Squeak@create.ucsb.edu In-Reply-To: <v03007803af5efedb9ebc@[129.34.225.178]> Subject: commutative math ops on non Numbers Say you want to implement a class that is not a kind of Number but that is able to respond to binary operators +,-,*,/, et al, and have it able to interoperate with Numbers. The usual method of retry:coerce when used on non Numbers does a " ^ argument perform: arith with: self " which will not work for non commutative operators like - and /. So what is a good way to implement this in Smalltalk? A straight implementation of double dispatch by adding selectors would generate a huge number of methods, so I want to avoid that if possible. retry: arith coercing: argument (argument isKindOf: Number) ifTrue: [self generality < argument generality ifTrue: [^ (argument coerce: self) perform: arith with: argument] ifFalse: [^ self perform: arith with: (self coerce: argument)]] ifFalse: [^ argument perform: arith with: self] --- james mccartney james@clyde.as.utexas.edu james@lcsaudio.com If you have a PowerMac check out SuperCollider, a real time synth program: ftp://mirror.apple.com//mirrors/Info-Mac.Archive/gst/snd/super-collider-demo.hqx

Post a reply.

Go back to index.



Date: 97 Mar 28 6:42:40 pm From: Eliot & Linda <elcm@pacbell.net> To: James McCartney <james@clyde.as.utexas.edu> Cc: Squeak@create.ucsb.edu Subject: Re: commutative math ops on non Numbers James McCartney wrote: > > Say you want to implement a class that is not a kind of Number > but that is able to respond to binary operators +,-,*,/, et al, > and have it able to interoperate with Numbers. > > The usual method of retry:coerce when used on non Numbers > does a " ^ argument perform: arith with: self " which will not work > for non commutative operators like - and /. > > So what is a good way to implement this in Smalltalk? A straight > implementation of double dispatch by adding selectors would generate > a huge number of methods, so I want to avoid that if possible. > > retry: arith coercing: argument > > (argument isKindOf: Number) > ifTrue: > [self generality < argument generality > ifTrue: [^ (argument coerce: self) perform: arith with: argument] > ifFalse: [^ self perform: arith with: (self coerce: argument)]] > ifFalse: [^ argument perform: arith with: self] > > --- james mccartney james@clyde.as.utexas.edu james@lcsaudio.com > If you have a PowerMac check out SuperCollider, a real time synth program: > ftp://mirror.apple.com//mirrors/Info-Mac.Archive/gst/snd/super-collider-demo.hqx Here's what I did. It's not general, since it only copes with Infinity but you may be able to extend it: !Infinity methodsFor: 'coercing'! retryReverseOf: aSymbol with: aNumber "Try the reverse of the arithmetic operation aSymbol with the receiver. (i.e. do the same as aNumber perform: aSymbol with: self) assuming that the receiver is more general than aNumber." (aSymbol == #* or: [aSymbol == #+ or: [aSymbol == #= or: [aSymbol == #~=]]]) ifTrue: [^self perform: aSymbol with: aNumber]. (aSymbol == #- and: [aNumber isFinite]) ifTrue: [ ^positive ifTrue: [Infinity negative] ifFalse: [Infinity positive]]. (aSymbol == #/ and: [aNumber isFinite]) ifTrue: [^0]. (aSymbol == #< and: [aNumber isFinite]) ifTrue: [^positive]. (aSymbol == #> and: [aNumber isFinite]) ifTrue: [^positive not]. self errorUndefinedResult: aSymbol! ! !ArithmeticValue methodsFor: 'coercing'! retry: aSymbol coercing: aNumber "Arithmetic represented by the symbol, aSymbol, could not be performed with the receiver and the argument, aNumber, because of the differences in representation. Coerce either the receiver or the argument, depending on which has higher generality, and try again. If the generalities are the same, then this message should not have been sent so an error notification is provided." (#= == aSymbol and: [aNumber respondsToArithmetic not]) ifTrue: [^false]. self generality < aNumber generality ifTrue: [aNumber isInfinite ifTrue: [^aNumber retryReverseOf: aSymbol with: self] ifFalse: [^(aNumber coerce: self) perform: aSymbol with: aNumber]]. self generality > aNumber generality ifTrue: [^self perform: aSymbol with: (self coerce: aNumber)]. ^self class raise: #errorSignal receiver: self selector: #retry:coercing: args: (Array with: aSymbol with: aNumber) errorString: 'coercion attempt failed'! ! _______________,,,^..^,,,_______________ Eliot

Post a reply.

Go back to index.



Date: 97 Mar 29 8:53:10 am From: johnson@cs.uiuc.edu (Ralph E. Johnson) To: James McCartney <james@clyde.as.utexas.edu> Cc: Squeak@create.ucsb.edu Subject: Re: commutative math ops on non Numbers James McCartney wrote: > So what is a good way to implement this in Smalltalk? A straight > implementation of double dispatch by adding selectors would generate > a huge number of methods, so I want to avoid that if possible. I would do it with double dispatch. Double dispatch will NOT generate a huge number of methods if you do it properly. If you arrange your class hierarchy properly, you can have a single method in a superclass handle a lot of different classes. retry:coerce: is wrong because arithmetic objects do not form a total order. For example, Scalar * Matrix is not the same thing as coercing a Scalar to be a Matrix and then using Matrix * Matrix. It is a different algorithm. arithmetic.st in the Smalltalk archive worked for R2.5 (or was it R2.3?) before ParcPlace added double dispatching to the image. Kurt Heble did it, and he had infinity, infinitesimals, matrices, functions, complex numbers, and I don't know what all. The PP code is similar because someone used his code, but his code predates the PP code, so there is no problem in using it. I'm sure it will take a little adapting, but it should be adaptable. Double dispatching is a little faster than retry:coerce:, too. Kurt and I wrote a paper that was in JOOP back in 1989 that explained how to do double-dispatch and minimize methods. I found a copy of it in Word, but Word 6.01 will not read it. I'll see if I can find an older copy and convert it into something that I can post. -Ralph

Post a reply.

Go back to index.



Date: 97 Mar 29 9:03:38 am From: James McCartney <james@clyde.as.utexas.edu> To: Squeak@create.ucsb.edu In-Reply-To: <v01540b00af62809e5693@[130.126.27.250]> Subject: Re: commutative math ops on non Numbers At 10:05 AM -0700 3/29/97, Ralph E. Johnson wrote: >James McCartney wrote: >> So what is a good way to implement this in Smalltalk? A straight >> implementation of double dispatch by adding selectors would generate >> a huge number of methods, so I want to avoid that if possible. > >I would do it with double dispatch. Double dispatch will NOT >generate a huge number of methods if you do it properly. If you >arrange your class hierarchy properly, you can have a single >method in a superclass handle a lot of different classes. Yes this is what I wound up doing. I did figure out how to do it with very few additional methods. And it should be faster than retry:coerce: Thanks to those who've helped. --- james mccartney james@clyde.as.utexas.edu james@lcsaudio.com If you have a PowerMac check out SuperCollider, a real time synth program: ftp://mirror.apple.com//mirrors/Info-Mac.Archive/gst/snd/super-collider-demo.hqx

Post a reply.

Go back to index.



Date: 97 Mar 29 9:44:05 am From: Dan Ingalls <DanI@wdi.disney.com> To: James McCartney <james@clyde.as.utexas.edu> Cc: Squeak@create.ucsb.edu In-Reply-To: <v03020900af628f70421b@[128.83.177.178]> Subject: Re: commutative math ops on non Numbers >At 6:20 PM -0700 3/28/97, Dan Ingalls wrote: >>I think the double dispatch is the way to go. It's not such a huge number= of >>selectors (many things are commutative, and you can also funnel a lot >>through a >>coerce: -like mechanism, but without the generality hack (ugh)). I did th= at >>for arithmetic in the ST that became VisualWorks, and it did very nicely. = I >>plan to do it for Squeak, but it keeps getting pushed down from the top of= my >>stack. > >james mccartney responded: >I'll need to think about it some more. Coerce will not always work in >the situations I am thinking of because Integer + MyType produces a >different result from MyType + MyType. You can't coerce and get the >same result. So I'd need methods like: > >Integer>>addMyType: aMyType > >MyType>>addInteger: anInteger > >And so on with Float, Complex, etc. In other words it *would* become a >huge number of methods. Or am I missing some simplification? Well, there's no such thing as a free lunch but, to the extent that there is= some uniformity over your operations, you can minimize the proliferation by= funneling the type conversion through a double dispatch, and not have to= provide that fan-out on all the operations. That's what I meant by my= comment above. SmallInt>>+ aNum <prim for SmallInts> ^ aNum argAddedTo: (aNum coerce: self) MyType>>+ aNum ST code here checks for addable args, and does them, else... ^ aNum argAddedTo: (aNum coerce: self) So, in every number class you have a method for every arith op that expects= any kind of number as its arg. These methods perform the op if possible= and pass themselves, coerced, back to the argument if not. There's no way= around this part, right? Then, in addition, you have a reversed version of every op that knows its= argument has been appropriately coerced. In fact, you really only need= these for the non-commutative ops (argAddedTo: probably looks the same as= +, but argSubtractedFrom does not look the same as -). =46inally, you need either one or N coercion methods for each of the N= types, depending on how fast you want things to go. The sketch above uses= only one coerce: method, but it has to check every type (although you can= order the tests and, typically the first checks for SmallInt or Float= almost always succeed). A slightly faster way is to do coercion with a= true double dispatch, so that the fail statement in SmallInt says ^ aNum argAddedTo: aNum coerceSmallInt, and the fail statement in MyType looks like ^ aNum argAddedTo: aNum coerceMyType. This requires potentially N-1 coercion methods in each of the N types,= although methods are only really needed for each of the types of lesser gen= erality. So the total number of methods required for this approach is between 1 and= two per operation in each type, plus either 1 or something less than N for = coercion. - Dan

Post a reply.

Go back to index.



Date: 97 Mar 29 12:13:12 pm From: James McCartney <james@clyde.as.utexas.edu> To: Dan Ingalls <DanI@wdi.disney.com> Cc: Squeak@create.ucsb.edu In-Reply-To: <v03007804af62f9eb3b25@[206.16.10.79]> Subject: Re: commutative math ops on non Numbers This is what I wound up doing. It only requires one additional method per class in each class. The method performBinaryOp:onTypeX: methods should work for all binary operators. Hopefully I've not missed something. to execute SmallInt + Complex requires: --- SmallInt>>+ aNumber <primitive> ^aNumber performBinaryOp: #+ onInteger: self --- Complex>>performBinaryOp: aSelector onInteger: anInteger "coerce the integer" ^anInteger asComplex perform: aSelector with: this --- --- to execute Complex + SmallInt: --- Complex>>+ aNumber (aNumber isMemberOf: Complex) ifTrue: [ ^Complex real: (real + aNumber real) imag: (imag + aNumber imag) ] ifFalse: [ ^aNumber performBinaryOp: #+ onComplex: self ] --- SmallInt>>performBinaryOp: aSelector onComplex: aComplex "coerce myself" ^aComplex perform: aSelector with: self asComplex --- --- As an example, now something like this is possible: adding Collections and numbers --- OrderedCollection>>+ theOperand | index minSize newColl | (theOperand isKindOf: OrderedCollection) ifTrue: "add two collections item by item" minSize _ self size min: theOperand size. index _ 0. newColl _ self species new. [ index < minSize ] whileTrue: [ newColl add: (self at: index) + (theOperand at: index) ]. ^newColl ] ifFalse: [ "will add a value to every item in the collection" ^theOperand performBinaryOp: #+ onOrderedCollection: self ] --- Number>>performBinaryOp: aSelector onOrderedCollection: aCollection ^aCollection collect: [ :item | item perform: aSelector with: self ] --- OrderedCollection>>performBinaryOp: aSelector onInteger: anInteger ^aCollection collect: [ :item | self perform: aSelector with: item ] --- In cases like the above where simple coercion will not suffice, then the class implementing the performBinaryOp:onTypeX: function will have to know about operations in the other class which breaks modularity. However in this case I am trying to simulate double dispatch and in languages with double dispatch like Dylan, CLOS, the classes do not own their methods anyway, so in a way it conforms to the paradigm it is trying to emulate, rather than the usual Smalltalk practice. (Note: I am just translating to Smalltalk above. I'm actually working in another language.) --- james mccartney james@clyde.as.utexas.edu james@lcsaudio.com If you have a PowerMac check out SuperCollider, a real time synth program: ftp://mirror.apple.com//mirrors/Info-Mac.Archive/gst/snd/super-collider-demo.hqx

Post a reply.

Go back to index.



Date: 97 Mar 29 12:27:32 pm From: James McCartney <james@clyde.as.utexas.edu> To: Squeak@create.ucsb.edu Subject: Re: commutative math ops on non Numbers >--- >OrderedCollection>>performBinaryOp: aSelector onInteger: anInteger > > ^aCollection collect: [ :item | self perform: aSelector with: item ] >--- Sorry, that should've been: ^self collect: [ :item | anInteger perform: aSelector with: item ] --- james mccartney james@clyde.as.utexas.edu james@lcsaudio.com If you have a PowerMac check out SuperCollider, a real time synth program: ftp://mirror.apple.com//mirrors/Info-Mac.Archive/gst/snd/super-collider-demo.hqx

Post a reply.

Go back to index.



Date: 97 Mar 29 8:42:45 pm From: johnson@cs.uiuc.edu (Ralph E. Johnson) To: Squeak@create.ucsb.edu Subject: Re: commutative math ops on non Numbers I was able to read the paper on double dispatching, and made a Postscript version of it avaliable by ftp from st.cs.uiuc.edu in /pub/papers/patterns/double-dispatch.ps -Ralph

Post a reply.

Go back to index.



Date: 97 Mar 29 11:40:08 pm From: James McCartney <james@clyde.as.utexas.edu> To: Squeak@create.ucsb.edu In-Reply-To: <v01540b01af6345b87bab@[130.126.27.215]> Subject: Re: commutative math ops on non Numbers At 9:54 PM -0700 3/29/97, Ralph E. Johnson wrote: >I was able to read the paper on double dispatching, and made a >Postscript version of it avaliable by ftp from st.cs.uiuc.edu in >/pub/papers/patterns/double-dispatch.ps Thanks for this. I like my scheme better. It produces far fewer methods than the one you propose and it allows operations between objects which are completely unrelated by inheritance. The performBinaryOp:onTypeX: scheme only requires one method per class that a class can interact with and that can be reduced by exploiting inheritance. By using perform: I only have to write one method per class, not one method per selector. --- james mccartney james@clyde.as.utexas.edu james@lcsaudio.com If you have a PowerMac check out SuperCollider, a real time synth program: ftp://mirror.apple.com//mirrors/Info-Mac.Archive/gst/snd/super-collider-demo.hqx

Post a reply.

Go back to index.



Date: 97 Mar 31 1:33:03 pm From: Watts@interval.com (Carl G. Watts) To: DanI@wdi.disney.com Cc: stBug@interval.com, squeak@create.ucsb.edu Subject: Bug in Form border:width:rule:fillColor: in Squeak 1.18 Dan, There is a bug in Form border:width:rule:fillColor: in Squeak 1.18 The problem is it calculates overlapping rectangles. So combination rules like Form reverse don't work. Following is a fixed version that doesn't calculate overlapping rectangles. Carl Watts !Form methodsFor: 'bordering'! border: rect width: borderWidth rule: rule fillColor: fillColor "Paint a border whose rectangular area is defined by rect. The width of the border of each side is borderWidth. Uses fillColor for drawing the border." | blt | blt _ (BitBlt toForm: self) combinationRule: rule; fillColor: fillColor. blt sourceOrigin: 0@0. blt destOrigin: rect origin. blt width: rect width; height: borderWidth; copyBits. blt destY: rect corner y - borderWidth; copyBits. blt destY: rect origin y + borderWidth. blt height: rect height - borderWidth - borderWidth; width: borderWidth; copyBits. blt destX: rect corner x - borderWidth; copyBits! !

Post a reply.

Go back to index.



Send mail to the CREATE web master

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