[comp.sys.apple] Computer languages on the various Apple Corp computers

nelson@pro-europa.cts.com (Nelson Minar) (05/22/89)

David Wood (cs472226@umbc5.umbc.edu (I think)), in his posting concerning the
latest APDA log, brought up the fact that there are more languages for the Mac
and the GS than the //.

The reason for this is simple - high-level languages are terribly impractical
on the 6502 based //. They are fairly tough to make run on the 65816. Take a
look at Aztec C sometime on a //e - its miserable. For the same <new> price
one can purchase a halfway decent IBM (yech) system that will run Turbo C 2.0,
a quite wonderful package. The // line lacks the power to effectively run high
level languages..

nelson@pro-europa.cts.com                                  cogito ergo non sum
...!crash!pnet01!pro-nsfmat!pro-europa!nelson

blochowi@cat28.CS.WISC.EDU (Jason Blochowiak) (05/23/89)

In article <8905211959.AA07195@crash.cts.com> pnet01!pro-nsfmat!pro-europa!nelson@nosc.mil writes:
> [...]
>The reason for this is simple - high-level languages are terribly impractical
>on the 6502 based //. They are fairly tough to make run on the 65816.
	I agree with the bit about doing high-level languages on the 6502, but
not about the 65816 - it has support for stackframes, large data sets, and
pretty much everything else necessary for high-level languages. Sure, the
65816 doesn't have ops that are as powerful as, say, the 68000, but, gee, isn't
that what RISC is all about?

>nelson@pro-europa.cts.com                                  cogito ergo non sum

 ------------------------------------------------------------------------------
		Jason Blochowiak (blochowi@garfield.cs.wisc.edu)
		       "It beats working" - Harrison Ford
 ------------------------------------------------------------------------------

gwyn@smoke.BRL.MIL (Doug Gwyn) (05/24/89)

In article <2821@puff.cs.wisc.edu> blochowi@cat28.CS.WISC.EDU (Jason Blochowiak) writes:
>65816 doesn't have ops that are as powerful as, say, the 68000, but, gee, isn't
>that what RISC is all about?

The 65816 is by no reasonable stretch of the concept an implementation
of a "RISC" architecture.  RISC != underpowered.

The main drawbacks to implementing compilers and run-time support for
the 65816 are that its memory segmentation is way too visible.

kevin@claris.com (Kevin Watts) (05/24/89)

From article <2821@puff.cs.wisc.edu>, by blochowi@cat28.CS.WISC.EDU (Jason Blochowiak):
> In article <8905211959.AA07195@crash.cts.com> pnet01!pro-nsfmat!pro-europa!nelson@nosc.mil writes:
>>The reason for this is simple - high-level languages are terribly impractical
>>on the 6502 based //. They are fairly tough to make run on the 65816.
> 	I agree with the bit about doing high-level languages on the 6502, but
> not about the 65816 - it has support for stackframes, large data sets, and
> pretty much everything else necessary for high-level languages. Sure, the
> 65816 doesn't have ops that are as powerful as, say, the 68000, but, gee, isn't
> that what RISC is all about?
> 
>>nelson@pro-europa.cts.com
> 		Jason Blochowiak (blochowi@garfield.cs.wisc.edu)

Sorry, but the 65816 is quite inadequate for high-level languages.  The main
problem is it's severe shortage of registers, which is why it's NOT a RISC
chip - they have LOTS of registers.  Yes, it does have stackframe support,
but large data sets are extremely cumbersome - anything over 64K requires
struggling like crazy to obtain any sort of reasonable performance, and
because of the bank restrictions even 64K can be difficult to obtain.
Crossing a bank boundary on a 65816 produces very messy code.  In some
ways the restrictions of the 65816 remind me of the problems with the
Intel chips (before the 80386), but at least there segments can begin
on any paragraph (16 byte) boundary.
Oh, and I expect that some people will claim that direct (zero) page space
provides sufficiently rapid access that it's equivalent to having 256 bytes
of registers - there's some validity to such a claim, but it won't work
at all if the direct page register is used to set up a stack frame, which
is essential for a high level language and pretty much so in any sizable
hand-coded assembler project.  Also, there isn't a true general register
anywhere, which really constrains high-level languages.

-- 
 Kevin Watts        ! Any opinions expressed here are my own, and are not
 Claris Corporation ! neccessarily shared by anyone else.  Unless they are
 kevin@claris.com   ! patently absurd, in which case they're not mine either.

jazzman@claris.com (Sydney R. Polk) (05/24/89)

From article <2821@puff.cs.wisc.edu>, by blochowi@cat28.CS.WISC.EDU (Jason Blochowiak):
> In article <8905211959.AA07195@crash.cts.com> pnet01!pro-nsfmat!pro-europa!nelson@nosc.mil writes:
>> [...]
>>The reason for this is simple - high-level languages are terribly impractical
>>on the 6502 based //. They are fairly tough to make run on the 65816.
> 	I agree with the bit about doing high-level languages on the 6502, but
> not about the 65816 - it has support for stackframes, large data sets, and
> pretty much everything else necessary for high-level languages. Sure, the
> 65816 doesn't have ops that are as powerful as, say, the 68000, but, gee, isn't
> that what RISC is all about?
The main problems I see with the 65816 are as follows:

-  You say it has support for stack frames.  However, the stack is small
(64K) and can only be put in special memory (bank 0) which is taken up
by tool memory and firmware.  Furthermore, the only way I know of to 
have stack frames is the way we do it, with the D register pointing at
the start of your local space.  This means losing a cycle per access,
as D will not usually be page-aligned, and it means a 256 byte limit on
your local space.

- It is very hard to write a compiler with 1 and two thirds registers (X
and Y are both one-third).  It is incredibly difficult to write an
efficient compiler with only one general purpose register.

- The chip is missing some addressing modes which make doing somethings
very difficult.  For instance, the only addressing mode on jsl is 
long.  This means you have to write self-modifying code to do a long
jump table.

- The chip only works with 16 bit quantities at a time most of the time.
You have to put the processor status into 8-bit mode to do character
and string processing.

- If you plan on having more than 64K of data space, it is very difficult
to decide whether an address should be stored short (16 bits, in same
bank) or long (24 bits).  You can't have all short, because you can
only address 64K with short addressing.  But doing everything long addressing
really slows the compiled code down a bunch.

- A RISC chip usually has an incredible number of registers, say 256, and
as such, is perfect for compilers.  This chip has one, so is not
really a RISC chip.

- A chip that has no hardware multiply is not going to do arithmetic very
fast, much less floating point.

- Enforcing an absolute limit of 64K per code segment is not very friendly,
and will break an awful lot of programs on other platforms.

We have had some experience with the APW and MPW C compilers on this machine,
and after all of the problems we've had, we still prefer assembly.  This
is in addition to the fact that the compiled code runs two to three times
as slow as the assembly.  I'm sorry, but with this machine's clock speed,
we cannot afford to waste the time.  The code also compiles about 50% larger.
We also don't have the disk space.

AppleWorks GS is big as it is.  We have optimized a hell of a lot of
assembly code.  I honestly believe that it is not possible to do a project
as large as AWGS on a compiler on the 65816, it is just to difficult to
write a reasonable compiler.

And yes, I have written a small compiler before.

-- 
Syd Polk           | Wherever you go, there you are.
jazzman@claris.com | Let the music be your light.
GO 'STROS!         | These opinions are mine.  Any resemblence to other
GO RICE!           |  opinions, real or fictitious, is purely coincidence.

dlyons@Apple.COM (David Lyons) (05/24/89)

In article <10204@claris.com> kevin@claris.com (Kevin Watts) writes:
[...]
>Sorry, but the 65816 is quite inadequate for high-level languages.  The main
>problem is it's severe shortage of registers, which is why it's NOT a RISC
>chip - they have LOTS of registers.  Yes, it does have stackframe support,
>but large data sets are extremely cumbersome - anything over 64K requires
>struggling like crazy to obtain any sort of reasonable performance, and
>because of the bank restrictions even 64K can be difficult to obtain.
>Crossing a bank boundary on a 65816 produces very messy code. [...]

It isn't all *that* bad...writing in high-level languages is certainly possible.

Crossing bank boundaries is not a problem.  Code segments can't do it, but
data segments can.  I really don't like global variables much at all in the
first place, so the Bank register doesn't bother me much.  I just use long
addressing when I really want to use global variables, and that way I don't
have to worry about setting it in content-draw procedures, etc.  Most of my
accesses are to direct page.

('course, in programs with a fairly small amount of code, I just put everything
in one segment and set B=K.)

My favorite addressing mode, by the way, is [xx],Y.  No bank restrictions, just
an offset from a 3-byte pointer on direct page.

> Kevin Watts        ! Any opinions expressed here are my own, and are not
> Claris Corporation ! neccessarily shared by anyone else.  Unless they are
> kevin@claris.com   ! patently absurd, in which case they're not mine either.

 --Dave Lyons, Apple Computer, Inc.          |   DAL Systems
   AppleLink--Apple Edition: DAVE.LYONS      |   P.O. Box 875
   AppleLink--Personal Edition: Dave Lyons   |   Cupertino, CA 95015-0875
   GEnie: D.LYONS2 or DAVE.LYONS         CompuServe: 72177,3233
   Internet/BITNET:  dlyons@apple.com    UUCP:  ...!ames!apple!dlyons

   My opinions are my own, not Apple's.

dlyons@Apple.COM (David Lyons) (05/24/89)

In article <10206@claris.com> jazzman@claris.com (Sydney R. Polk) writes:
>[...] However, the stack is small
>(64K) and can only be put in special memory (bank 0) which is taken up
>by tool memory and firmware. [...]

You've got 46K in bank 0, minus whatever you need to give to the toolbox, and
minus about 10K for GS/OS, leaving you at least 30K for a stack if you really
want it.

>- The chip is missing some addressing modes which make doing somethings
>very difficult.  For instance, the only addressing mode on jsl is 
>long.  This means you have to write self-modifying code to do a long
>jump table.

You can look up an address-minus-one in a table, push it on the stack, and
then RTS or RTL to it.  Works slick.

>Syd Polk           | Wherever you go, there you are.
>jazzman@claris.com | Let the music be your light.
>GO 'STROS!         | These opinions are mine.  Any resemblence to other
>GO RICE!           |  opinions, real or fictitious, is purely coincidence.

 --Dave Lyons, Apple Computer, Inc.          |   DAL Systems
   AppleLink--Apple Edition: DAVE.LYONS      |   P.O. Box 875
   AppleLink--Personal Edition: Dave Lyons   |   Cupertino, CA 95015-0875
   GEnie: D.LYONS2 or DAVE.LYONS         CompuServe: 72177,3233
   Internet/BITNET:  dlyons@apple.com    UUCP:  ...!ames!apple!dlyons

   My opinions are my own, not Apple's.

jazzman@claris.com (Sydney R. Polk) (05/24/89)

From article <31464@apple.Apple.COM>, by dlyons@Apple.COM (David Lyons):
> Crossing bank boundaries is not a problem.  Code segments can't do it, but
> data segments can.  I really don't like global variables much at all in the
> first place, so the Bank register doesn't bother me much.  I just use long
> addressing when I really want to use global variables, and that way I don't
> have to worry about setting it in content-draw procedures, etc.  Most of my
> accesses are to direct page.
> 
> ('course, in programs with a fairly small amount of code, I just put everything
> in one segment and set B=K.)
> 
> My favorite addressing mode, by the way, is [xx],Y.  No bank restrictions, just
> an offset from a 3-byte pointer on direct page.
Which brings up another problem.  All of the pointers used in long indirection
have to be in the zero bank, which means that the precious local space is
taken up by pointers the compiler needs as opposed to any local variables
that the user needs in a procedure.  Also, the above mentioned addressing
mode *is* useful in a dynamic memory environment; however, it is much slower
than (XX),y, or several others that you can use when the data bank is
guaranteed.

-- 
Syd Polk           | Wherever you go, there you are.
jazzman@claris.com | Let the music be your light.
GO 'STROS!         | These opinions are mine.  Any resemblence to other
GO RICE!           |  opinions, real or fictitious, is purely coincidence.

cs472226@umbc5.umbc.edu (David Wood (CS472226)) (05/24/89)

In article <10204@claris.com> kevin@claris.com (Kevin Watts) writes:
>
>Sorry, but the 65816 is quite inadequate for high-level languages.  The main
>problem is it's severe shortage of registers, which is why it's NOT a RISC
>chip - they have LOTS of registers.  Yes, it does have stackframe support,
>but large data sets are extremely cumbersome - anything over 64K requires
>struggling like crazy to obtain any sort of reasonable performance, and
>because of the bank restrictions even 64K can be difficult to obtain.
>Crossing a bank boundary on a 65816 produces very messy code.  In some
>ways the restrictions of the 65816 remind me of the problems with the
>Intel chips (before the 80386), but at least there segments can begin
>on any paragraph (16 byte) boundary.
>Oh, and I expect that some people will claim that direct (zero) page space
>provides sufficiently rapid access that it's equivalent to having 256 bytes
>of registers - there's some validity to such a claim, but it won't work
>at all if the direct page register is used to set up a stack frame, which
>is essential for a high level language and pretty much so in any sizable
>hand-coded assembler project.  Also, there isn't a true general register
>anywhere, which really constrains high-level languages.

   There is a possible solution for that...
   Let's say you absolutely positively MUST set up a stack space (sounds
reasonable for most languages I've seen). You have the stack register
pointed at a large block of memory... Why does it ALL have to be
reserved for the stack?
   Why not shave off 2, 4, 8, 16, or however many bytes of storage above
the bottom of the stack at the end of the page (stacks build down) and
reserve it for those values that you would otherwise contain in
registers? I'm not completely familiar with the 816 instruction set (and
I don't carry my reference library around), but I think there are single
instructions which read and write to the DP fast enough to support
register emulation.

> Kevin Watts        ! Any opinions expressed here are my own, and are not
> Claris Corporation ! neccessarily shared by anyone else.  Unless they are
> kevin@claris.com   ! patently absurd, in which case they're not mine either.

   The solution is simple ...maybe too simple.

                                                    -David Wood
************************************************************************
*  A Mind is a Terrible Thing  ***  Attention: I WAS WRONG ABOUT THE   *
* to have Oozing out          ***  PUMPKINIZATION DATE OF THIS ACCOUNT *
* your ears...               *******************************************
*      -- The League of     ***  This account vaporizes on Friday,     * 
*         Sadistic         ***  MAY 26! Conventional mail address is:  * 
*         Telepaths       ***  7 SYCAMORE CT. GRASONVILLE, MD 21638    *
************************************************************************

brianw@microsoft.UUCP (Brian Willoughby) (05/25/89)

In article <8905211959.AA07195@crash.cts.com> pnet01!pro-nsfmat!pro-europa!nelson@nosc.mil writes:
>David Wood (cs472226@umbc5.umbc.edu (I think)), in his posting concerning the
>latest APDA log, brought up the fact that there are more languages for the Mac
>and the GS than the //.
>
>The reason for this is simple - high-level languages are terribly impractical
>on the 6502 based //. They are fairly tough to make run on the 65816. Take a
>look at Aztec C sometime on a //e - its miserable. For the same <new> price
>one can purchase a halfway decent IBM (yech) system that will run Turbo C 2.0,
>a quite wonderful package. The // line lacks the power to effectively run high
>level languages..
>
>nelson@pro-europa.cts.com                                  cogito ergo non sum
>...!crash!pnet01!pro-nsfmat!pro-europa!nelson

I must disagree with the above statement on several counts:

First of all, Aztec C could be much improved, even on a 6502-based //e. 
A great deal of time is wasted pushing objects on the 'real' stack, only
to COPY them byte-by-byte to a software stack. I must admit that a
software stack is slower, but it can be optimized better than in Aztec.
Also, the A,X and Y registers are loaded with preset values at each
function boundary (i.e. when a function returns), thus prohibiting
register passing of variables. I got so tired of the slow text from
Aztec's printf() that I hand-coded an assembly language version that
followed the same C protocols of a control statement and variable
parameters. The result: my printf() fills the entire screen with text in
the blink of an eye. If only I had time to rewrite the entire library,
but then the rest of the code wouldn't be optimized, either. We need a
newer generation C compiler for the non-GS.

Second, the 65816 overcomes several of the remaining restrictions to
high level languages on the 6502. There are 128 variable size 'register'
variables that can be instantly switched by reloading the Direct Page
pointer. The stack is a true 16 bits, allowing faster and smaller code
for dealing with the stack. Also, several 16 bit push instructions have
been added for pushing addresses and relative addresses - perfect for
pushing string addresses in C. The 65816 also runs up to 8 MHz, which
competes with a fictional IBM/XT running at 38.16 MHz (considering that
the 4.77 MHz 8086 was stomped by a 1 MHz 6502). Of course the 80386 is
more efficient (takes fewer clock cycles to do the same thing) than an
8086, so this figure would have to be adjusted.

Third, regarding the IBM. The 80x86 programming model does not include
general purpose registers, has a segmented architecture and breaks a few
other C standards. You don't get the full speed of general purpose
registers (like on the 68000) because the C 'register' is implemented by
moving SI and DI registers back and forth between the working registers
AX, BX, CX and DX. This lack of processor power didn't stop Borlin from
creating a C which added support for segmented address (a real pain
when your program grows outside of 64K, or the data area grows beyond
64K, OR the stack gets too much pushed on it). The 8086 is quite
inefficient with data larger than 64K, because every address must load
two registers before you can access it.

Finally, (since some of you will obviously point out that the PC-based
software runs faster) the reason the Apple II suffers in high-level
languages is that a far smaller group has been attacking the problem
when compared to the PC clones. Microsoft, Borlin, several smaller
companies, and IBM themselves have devoted a greater number of people
to overcome the problems with the 80x86. The result being that I can
use Turbo C to generate better assembly code (usually) than I could
hand-code. It is inexcusable that I can find several errors in
efficiency when looking at Aztec C's Apple II code output. Being an EE,
I have never written a compiler, but it seems like some of the wizards
of the CS field could do much better if they wrote a REAL compiler for
the Apple II.

P.S. the PRICE of a IBM PC clone system, or of a PC-based compiler,
has nothing to do with high-level languages on the II. It just happens
that there is (unfortunately) a higher demand for the PC, so it gets
most of the attention, and all the discounts of high volume. With the
Apple II, its a Catch 22; no one writes software because of the lack of
decent high-level language support, and no one writes serious compilers
because there isn't a high market (yet) for writing programs on the II
(at least not compared to the money they'll make on compatible software).

Brian Willoughby                        ...!uw-beaver!microsoft!brianw
                or                      microsoft!brianw@uunet.UU.NET
                or just                 brianw@microsoft.UUCP

kevin@claris.com (Kevin Watts) (05/25/89)

From article <2075@umbc3.UMBC.EDU>, by cs472226@umbc5.umbc.edu (David Wood (CS472226)):
> In article <10204@claris.com> kevin@claris.com (Kevin Watts) writes:
>>
>>		[using the direct page as 'registers'] won't work
>>at all if the direct page register is used to set up a stack frame, which
>>is essential for a high level language and pretty much so in any sizable
>>hand-coded assembler project.
> 
>    Why not shave off 2, 4, 8, 16, or however many bytes of storage above
> the bottom of the stack at the end of the page (stacks build down) and
> reserve it for those values that you would otherwise contain in
> registers? ...

The problem is not space (in practice only a few K bytes are required for
a stack unless you're using recursion heavily), but the addressing modes
of the 65816.  Although the stack may be of any size up to 64K, in bank 0,
only 256 bytes at a time may be accessed efficiently.  Which 256 bytes is
controlled by the direct page register, which contains a word indicating
the bottom of the 256 byte range.  A stack frame, for those who don't know,
is set up by a routine when it is called.  It allows easy access to parameters
passed on the stack and local variables allocated on the stack.  On the
65816 the direct page register is the way to do this.  Here's some sample
code for a routine that takes two words as parameters and needs two longs
of local space:  (I'm using the C calling conventions and jsr/rts for
simplicity - the IIGS ToolBox routines use Pascal conventions and jsl/rtl)

Calling sequence:
	pea	#1234		; push 1st parameter
	pea	#5678		; push 2nd parameter
	jsr	MyRoutine
	pla			; pop the parameters off the stack
	pla

	.
	.


MyRoutine	PROC
Par1	equ	15
Par2	equ	13
Local1	equ	5
Local2	equ	1
	phd			; save old direct page register
	tsc			; transfer stack ptr to accumulator
	sec			; create stack space for
	sbc	#8		; our locals (two longs = 8 bytes)
	tcs			; transfer accumulator back to stack ptr
	tcd			; set up direct page for stack frame

; now the stack looks like this: (with offsets from the 'top' of the stack)
; +15	| $1234	| <- Par1
; +13	| $5678	| <- Par2
; +11	| addr  | <- return address
; +9	| old d	| <- saved direct page value
;	|	|
; +5	|	| <- Local1
;	|	|
; +1	|	| <- Local2
; S ->		  <- D

	lda	Par1
	clc
	adc	Par2
	sta	Local1
	.
	.

	tsc
	clc
	adc	#8
	tcs
	pld
	rts


Well, I've wandered a bit, but I hope this is useful.  The point is that
the direct page register is changing on every procedure call, so it can't
be used to indicate a static 'set of registers' in bank 0.  If you don't
need stack frames anywhere (i.e. pass all parameters in registers or
globals, don't use any local variables - generally poor programming
practices and virtually impossible if you want recursion), then it would
definitely make sense to allocate up to 256 bytes in bank 0 and keep
the direct page register permanently pointing to it, thereby providing
a small but fast set of global variables - fast enough to consider
'registers' if you like.  The same tricks can be managed even if you
do need stack frames, but only at the cost of frequently saving, setting
and restoring the direct page register; it's usually faster not to bother.

(In case it's not clear, there's no direct relationship between the stack
and the direct page - only using the direct page register to set up a
stack frame creates one)

-- 
 Kevin Watts        ! Any opinions expressed here are my own, and are not
 Claris Corporation ! neccessarily shared by anyone else.  Unless they are
 kevin@claris.com   ! patently absurd, in which case they're not mine either.

toth@tellab5.tellabs.CHI.IL.US (Joseph G. Toth Jr.) (05/26/89)

I don't want to get into the relative merits of different processors
and operating systems, as the arguments against native code generation
have been going on for some time and all seem to agree that the 6502,
65c02 and the 65816 aren't the easiest processers to handle.

The major question in my mind involves the ability to program in a
high level language (eg, Pascal, Fortran, "C", Forth, etc) on an Apple //.

Why can't a P.SYSTEM be generated that operates like BASIC.SYSTEM be generated.
P-Code interpreters are fairly small, and can operate nicely on the 6502
processor (even with all its limitations). Apple Pascal is a P-Code environment
where the major obstacle is its non ProDOS disk I/O architecture.

It would use ProDOS as its operating environment (Disk I/O).
It could be launched with an added parameter of the program to run
  (the same as in BASIC.SYSTEM) or every program could execute a peice of
  startup code that loads the P.SYSTEM then passes control to the system
  with a pointer to the start of the P-Code executable.
The P.SYSTEM would terminate itself when the P-Code executable reaches
  a termination point by executing the standard QUIT code.

Once a usable P.SYSTEM is developed (Apple Pascal could be used as a basis
  for determining the minimum functionality required), any number of compilers
  could be generated that generate P-Code executables (or even intermediates
  if you want to be able to link things together, probably preferable).
  The thoughts are breathtaking;
     PASM.SYSTEM  - A P-Code Assembler
     PPAS.SYSTEM  - A Pascal Compiler
     PC.SYSTEM    - A "C" code compiler
     PFORT.SYSTEM - A Fortran Compiler
     <almost any other language you care to name>
  Each of which would accept a filename which is the name of a standard TXT
  file to be used in the compile, and output the linkable as a different
  filetype (POB - P-Code object, maybe)
  in the same

     PLINK.SYSTEM - A linker that takes the output from any of the above
		    and generates an executable (filetype PEX - P-code
		    executable, maybe).

It seems to me that since there are already is a P-Code interpreter and
a Pascal compiler that generates P-Code (and Fortran from what I hear)
that run on an Apple //, that they (Claris ???) could adapt the existing 
packages to fit the above scenario.

A system like this I could see paying for.

I once before complained about Mad Apple Forth, and made the statement that
it was an interpreter.  My main problem with using MAF was that once in the
interpreter, it used a non-ProDOS disk for internal operations (its utilities),
not that it was an interpreter.  It just seems to be a bit much to be required
to insert a specific disk in Drive 6 Slot 2 before being able to run an
application (no ifs, and or buts - you need to insert that disk ro run) when
I could fit everything on a single mass storage device if it was truly ProDOS.

The same complaints hold true for Apple Pascal (and the freeware hyper_C)
except that they are even worse in that you can't simply QUIT back to ProDOS,
you have to re-boot (open-apple/control/reset, I hate seeing people turn the
power off/on to do a re-boot).

I guess that these are just pipe-dreams, much the same as hoping that
the ProDOS based hyper_C is made freeware.

-- 
------------------------------------------------+---------------------
Maybe I shouldn't have done it, sarcasm is so   | Joseph G. Toth Jr.
seldom understood.  Don't FLAME on me, please.  | uunet!tellab5!toth

lmb7421@ultb.UUCP (L.M. Barstow) (06/01/89)

 In article <10204@claris.com> kevin@claris.com (Kevin Watts) writes:
>
>		[using the direct page as 'registers'] won't work
>at all if the direct page register is used to set up a stack frame, which
>is essential for a high level language and pretty much so in any sizable
>hand-coded assembler project.

Kevin also follows up in <10211@claris.com> with a pseudo-C compiled
example of a stack frame (very concise...nice, Kevin)

I believe there is a way around the vast majority of the direct-register
problem in the Stack relative adressing mode.  I'll admit, you can't
perform some operations with stack relative (shift operations are the
big one), and they are a little slower, but I think a register area
would be most helpful for improved performance, and would be willing to
assign the direct page to that purpose, using Stack relative for regular
variables in a stack frame (it was probably the reason for the adressing
mode anyway).

These ramblings do not imply knowledge of life, only practice with an
assembler.  I have been wrong before, I'm sure I'll be wrong again.

-- 
Les Barstow     LMB7421@RITVAX.BITNET
...rutgers!rochester!ritcv!ultb!lmb7421.UUCP
"I know you think you know what you thought I said, but
you don't realize that what you thought I said was not what I meant"

kevin@claris.com (Kevin Watts) (06/06/89)

From article <861@ultb.UUCP>, by lmb7421@ultb.UUCP (L.M. Barstow):
> I believe there is a way around the vast majority of the direct-register
> problem in the Stack relative adressing mode.  I'll admit, you can't
> perform some operations with stack relative (shift operations are the
> big one), and they are a little slower, but I think a register area
> would be most helpful for improved performance, and would be willing to
> assign the direct page to that purpose, using Stack relative for regular
> variables in a stack frame (it was probably the reason for the adressing
> mode anyway).

Hmm, good point.  My initial reponse to this was "but this doesn't work if
I push anything onto the stack during the routine", but then I remembered
that this discussion is mostly about high-level languages, which don't use
the grungy hacks I find myself using in assembly to get decent performance.
All in all, I think this is a very practical way to implement a high-level
language on the 65816.  Performance will be a little slow, but not too bad,
and I still wouldn't want to deal with long data references, but the
picture's better than I thought.  Code space is still going to be a
problem, but no worse than most chips.  Oh well, memory prices are falling
again.

-- 
 Kevin Watts        ! Any opinions expressed here are my own, and are not
 Claris Corporation ! neccessarily shared by anyone else.  Unless they are
 kevin@claris.com   ! patently absurd, in which case they're not mine either.