[comp.arch] skip instructions

jthomas@nmsu.edu (James Thomas) (05/02/91)

(I'm sorry if this is an alt.folklore.computers question, but :-)

Is there a reference (or more) describing why SKIP instructions have mostly
disappeared from instruction sets?  The 704x and 709x had them, so the
PDP-6 had them (and maybe therefore the PDP-8 inherited them).  Now the
HP-PA has them hiding in the guise of the nullify bit.  Are conditional
branches generically more useful?

Thanks,
Jim

joeo@masscomp.westford.ccur.com (Joe Orost) (05/02/91)

Motorola, in their bulletin to 68040 compiler writers, recommended using the 
TRAP.F with size WORD or LONG as a skip instruction.  They said it has
better performance than the corresponding jump or BRA.  Looks like a
blast-from-the-past is back in fashion!

				regards,
				joe

--

 Full-Name:  Joseph M. Orost
 Email:	     joeo@tinton.ccur.com
 Phone:      (908) 758-7284         Fax: (908) 758-7113
 US Mail:    MS 322; Concurrent Computer Corporation; 106 Apple St
             Tinton Falls, NJ 07724

He feeds on fear... and the pleasures.") (05/04/91)

In article <1182@opus.NMSU.Edu> jthomas@nmsu.edu (James Thomas) writes:
>Is there a reference (or more) describing why SKIP instructions have mostly
>disappeared from instruction sets?  The 704x and 709x had them, so the
>PDP-6 had them (and maybe therefore the PDP-8 inherited them).  Now the
>HP-PA has them hiding in the guise of the nullify bit.  Are conditional
>branches generically more useful?

SPARC also has them, in the guise of annulled branches.  In current
implementations they're no faster than any other branch, and I don't think
the Sun compilers make an effort to use them.

--
David DiGiacomo, MIPS Computer Systems, Sunnyvale, CA  dd@mips.com

hrubin@pop.stat.purdue.edu (Herman Rubin) (05/04/91)

In article <3027@spim.mips.COM>, dd@mips.com ("BOB requires a human host!  He feeds on fear... and the pleasures.") writes:
> In article <1182@opus.NMSU.Edu> jthomas@nmsu.edu (James Thomas) writes:
> >Is there a reference (or more) describing why SKIP instructions have mostly
> >disappeared from instruction sets?  The 704x and 709x had them, so the
> >PDP-6 had them (and maybe therefore the PDP-8 inherited them).  Now the
> >HP-PA has them hiding in the guise of the nullify bit.  Are conditional
> >branches generically more useful?
> 
> SPARC also has them, in the guise of annulled branches.  In current
> implementations they're no faster than any other branch, and I don't think
> the Sun compilers make an effort to use them.

I am somewhat surprised that they are not more common on RISCs.  An advantage
of a skip instruction over a branch is that the skip does not need an address,
and so more versatility is available with the same hardware.  Probably even
better would be an instruction which has a conditional forward branch to a
nearby instruction, quite possibly even in the current stack.  I suggest that
it might be possible for some of this to be due with consideration of doing
both simultaneously, and avoiding much branch cost.
-- 
Herman Rubin, Dept. of Statistics, Purdue Univ., West Lafayette IN47907-1399
Phone: (317)494-6054
hrubin@l.cc.purdue.edu (Internet, bitnet)   {purdue,pur-ee}!l.cc!hrubin(UUCP)

gd@geovision.gvc.com (Gord Deinstadt) (05/05/91)

James Thomas writes:
>Is there a reference (or more) describing why SKIP instructions have mostly
>disappeared from instruction sets?
Conditional branch instructions were a big step forward in CISC days;
they accomplished in one instruction what had previously taken two.
The original reason for skips was, I think, that instructions were much
shorter in those days - there wasn't room for a branch address and a
condition field in the same instruction.  The PDP-11 had conditional branches
but only 8 bits for the offset, in a 16-bit word.  The PDP-8 used skips
and had a 12-bit word.  I don't know about mainframes.

Herman Rubin writes:
>I am somewhat surprised that they are not more common on RISCs.
In a pipelined machine, would it not be more efficient to just deactivate
a couple of instructions rather than go through the pain of a forward
branch?  In other words just keep grinding forward, but inhibiting
execution for a specified number of cycles, rather than trying to
change course.  There would be no branch delay slot.
--
Gord Deinstadt  gdeinstadt@geovision

dik@cwi.nl (Dik T. Winter) (05/05/91)

In article <1545@geovision.gvc.com> gd@geovision.gvc.com (Gord Deinstadt) writes:
 > In a pipelined machine, would it not be more efficient to just deactivate
 > a couple of instructions rather than go through the pain of a forward
 > branch?  In other words just keep grinding forward, but inhibiting
 > execution for a specified number of cycles, rather than trying to
 > change course.

Interestingly, this is what a very old (and not very RISC) machine did.
I am talking about the Electrologica X8 of 60s vintage.  It had a single
condition bit.  (Nearly) Every instruction had a 2 bit field that encoded
one of the following:
	Execute always
	Execute if condition is Yes
	Execute if condition is No
	Execute but do not deliver result
also there was a 2 bit field that encoded how the condition would be set:
	Do not set
	Set on positive
	Set on zero
	Set on even parity
It was easy to ge jumpless abs and max and so on:
	M[x] = abs(M[y])
translates to (A is a register, M[.] is a reference to memory):
	   A = M[y], P		Set condition if positive
	N, A = -A		If negative, negate
	   M[x] = A
And M[x] = max(M[y], M[z]) translates to:
	   A = M[y]
	U, A - M[z], P		Set condition to A-M[z] but do not store
	N, A = M[z]		If negative get M[z]
	   M[z] = A

Apart from the assembler syntax which is very different from your kitchen
variety (Herman Rubin would like it; I did like it, just as I like the
Cray assembler syntax), there are a number of problems with these conditional
executions with RISC architectures.  In general the condition following
instruction immediately follow the condition setting instructions.  This
again might impose a delay on pipelined machines.  Although, because you
can inhibit exceptions and result storing on condition following instructions
that ought not to be executed, this delay might be minimal (and possibly
even zero).  It becomes more tricky if a condition following instruction is
also condition setting (you must inhibit the condition setting also).

What I have seen from it, it works very well, and leads to cleaner code in
a number of situations.  E.g. the C code
	M[a] = (M[b] >= 0 ? M[c] : M[d]);
translates to:
	U, A = M[b], P		Set condition if M[b] positive
	Y, A = M[c]		If yes get M[c]
	N, A = M[d]		Else get M[d]
	   M[a] = A
And here we find the biggest problem I think, how to cater with a condition
following instruction that does a load?  We really want it to abort as soon
as the condition is known to be false.
--
dik t. winter, cwi, amsterdam, nederland
dik@cwi.nl

my@berlioz.nsc.com (Michael Yip) (05/05/91)

In article  (Dik T. Winter) writes:
>In article (Gord Deinstadt) writes:
> > In a pipelined machine, would it not be more efficient to just deactivate
> > a couple of instructions rather than go through the pain of a forward
> > branch?  In other words just keep grinding forward, but inhibiting
> > execution for a specified number of cycles, rather than trying to
> > change course.
>
>Interestingly, this is what a very old (and not very RISC) machine did.
>I am talking about the Electrologica X8 of 60s vintage.  It had a single
>condition bit.  (Nearly) Every instruction had a 2 bit field that encoded
>one of the following:
> [[[Stuff deleted]]]

Actually, at least one of the RISC architecture on the market does that.
That is the Arcon RISC chip.  I think that the chip is currently fab by
VLSI Technology and it is also available as a standard cell.

The Arcon RISC chip has one (or two??) conditional execution bit in each
instruction and depends on the condition set by previous instructions, the
instruction may behaves just like a NOP.  For small branchs, it is a very
good idea.  However, I don't think that this will work with super-scalar
architecture at all (without pain).

-- Mike
   my@berlioz.nsc.com

johnl@iecc.cambridge.ma.us (John R. Levine) (05/06/91)

In article <1182@opus.NMSU.Edu> jthomas@nmsu.edu (James Thomas) writes:
>Is there a reference (or more) describing why SKIP instructions have mostly
>disappeared from instruction sets?

It seems to me the real reason was variable length instructions.  DEC
machines up through the PDP-10 all had fixed length single word
instructions, so it was obvious what skipping one would mean.  Ditto the IBM
scientific machines up through the 7094, and their clones such as the GE
635.  The IBM 360 and PDP-11 both had variable length instructions and
condition codes.

Variable length instructions make skips a lot less appealing.  I once used a
machine that had single word skips but a combination of one and two word
instructions (Varian 620, for you historians) and some impressively strange
bugs resulted from skipping into the middle of a two-word instruction.

When viewed as a condition prefix on an arbitrary instruction, a skip is a
pretty nice construct, and I expect would be easy to teach a whizbang
optimizer to use.  Now that fixed length instructions are coming back, I
expect that we'll see more skips again.

-- 
John R. Levine, IECC, POB 349, Cambridge MA 02238, +1 617 492 3869
johnl@iecc.cambridge.ma.us, {ima|spdcc|world}!iecc!johnl
Cheap oil is an oxymoron.

sef@kithrup.COM (Sean Eric Fagan) (05/06/91)

In article <1991May5.162722.29507@berlioz.nsc.com> my@berlioz.nsc.com (Michael Yip) writes:
>The Arcon RISC chip has one (or two??) conditional execution bit in each
>instruction and depends on the condition set by previous instructions

There are four bits in every instruction (the first four, in fact).  If I
could find my ARM manual, I could even tell you what they were 8-(.

I figured out a way, once, to make gcc use them (peepholing, of course).
From the manual, I think I decided that it was really only worthwhile if the
branch would skip over four or fewer instructions.

-- 
Sean Eric Fagan  | "I made the universe, but please don't blame me for it;
sef@kithrup.COM  |  I had a bellyache at the time."
-----------------+           -- The Turtle (Stephen King, _It_)
Any opinions expressed are my own, and generally unpopular with others.

dik@cwi.nl (Dik T. Winter) (05/06/91)

In article <1991May05.180933.23091@kithrup.COM> sef@kithrup.COM (Sean Eric Fagan) writes:
 > In article <1991May5.162722.29507@berlioz.nsc.com> my@berlioz.nsc.com (Michael Yip) writes:
 > >The Arcon RISC chip has one (or two??) conditional execution bit in each
-->     Acorn
 > >instruction and depends on the condition set by previous instructions
 > 
 > There are four bits in every instruction (the first four, in fact).  If I
 > could find my ARM manual, I could even tell you what they were 8-(.
Just the standard set (carry, equal, greater, high, etc.).  Also there is a bit
that tells whether the conditions should be set or not.
 > 
 > I figured out a way, once, to make gcc use them (peepholing, of course).
 > From the manual, I think I decided that it was really only worthwhile if the
 > branch would skip over four or fewer instructions.
True enough.  But that is really a function of the depth of the pipeline, and
the delay incurred using branches.  Also I do think that plain peepholing is
not enough to really make good use of the feature.  When used well you can
get very compact codes for a number of common cases (see the abs and max
example I gave in another post for another machine with this feature).

I believe that conditional execution is a more useful feature than skips.
Skips allow only the single next instruction to be skipped, and in most
cases I have seen that was a branch.  Of course conditional skips make
conditional branches unneeded.

I have seen mentioned that SPARC and HPPA had skip's.  For the SPARC that is
of course not true.  A skip implies that the result of the current operation
tells whether the next instruction has to be executed or not.  This is not
true on the SPARC.  Also the HP-PA annul bit does not count as a skip in
this sense.  The only HP-PA instructions that could be interpreted as skips
are the 'ADD AND BRANCH' instructions.  But in general the branching
instructions are just that: conditional branches.  The only machine I know
(this is a disclaimer) with true skips is the NOVA.
--
dik t. winter, cwi, amsterdam, nederland
dik@cwi.nl

ccplumb@rose.waterloo.edu (Colin Plumb) (05/06/91)

sef@kithrup.COM (Sean Eric Fagan) wrote:
> There are four bits in every instruction (the first four, in fact).  If I
> could find my ARM manual, I could even tell you what they were 8-(.

The high 4 bits in each instruction are a condition.  If the condition is
false, even illegal encodings are ignored.

For the trivia-minded,

0000 - EQ - Z=1
0001 - NE - Z=0
0010 - CS - C=1
0011 - CC - C=0
0100 - MI - N=1
0101 - PL - N=0
0110 - VS - V=1
0111 - VC - V=0
1000 - HI - C=1 & Z=0
1001 - LS - C=0 | Z=1
1010 - GE - N=V
1011 - LT - N!=V
1100 - GT - Z=0 & N=V
1101 - LE - Z=1 | N!=V
1110 - AL - Always
1111 - NV - Never

There are 16 registers, R15 is the PC and condition code register.  The low
2 bits are mode (00 = user) and the upper 6 are NZCVIF, I = IRQ disable,
F = FIRQ disable.

After this comes an operation:
00IxxxxSssssdddd222222222222 - ALU op d = s op 2
000000ASdddd3333ssss10012222 - Multiply d = s op 2 (+ 3 if A=1)
01IPUBWLssssdddd222222222222 - Load/store - d <-> [s +/- 2]
100PUSWLssssmmmmmmmmmmmmmmmm - multi-reg trasnfer (m = mask, s = base reg)
101Ldddddddddddddddddddddddd - branch (link to R14 if L=1).  PC += d*4.
110                          - coprocessor
1110                         - coprocessor
1111xxxxxxxxxxxxxxxxxxxxxxxx - SWI

On the ALU ops and multiply, the condition codes are set iff S=1.
The 12-bit src2 field and the I bit determine the second ALU input.
If I=1, src2 is an immediate value, of the form rrrriiiiiiii, and
the value is the zero-extended byte i rotated right 2*d bits.  Note
that the 8 ALU status bits fit into such a field.  If I=1, src2
is either ssssstt0rrrr, register r shifted (type t) by s bits
(tt = 00 for LSL, 01 for LSR, 10 for ASR, 11 for ROR), or
ssss0tt1rrrr, where ssss is the register holding the shift count.
(One extra cycle for this form.)

The ALU ops are xxx = 
0000 AND
0001 EOR
0010 SUB dest = src1 - src2
0011 RSB dest = src2 - src1
0100 ADD
0101 ADC
0110 SBC
0111 RSC (reverse sub with carry)
1000 TST as add, but dest unchanged
1001 TEQ as EOR, but dest unchanged
1010 CMP as SUB, but dest unchanged
1011 CMN as ADD, but dest unchanged
1100 ORR logical OR
1101 MOV dest = src2
1110 BIC dest = src1 & ~src2
1111 MVN dest = -src2

if dest=R15, if S=0, only the 24 PC bits are affected.  If S=1, all
32 bits are written (28 in user mode; mode bits and IRQ disables are
unwriteable).o

On the load/stores, the flag bits mean the following:
L - 1=load, 0=store
W - if 1, write result of address computation back to src1 register
B - 1=byte, 0=word
U - 1=ALU computes src1+src2, 0=ALU computes src1-src2
P - 1=src1 op src2 used as memory address; 0 = src1 used as memory address,
    and src1 op src2 only used for writeback (post-indexing).

On the multi-register load/stores, the bits mean the same thing, except that
they're repeated for each bit set in the mask, and the offset is always 4.
Multi-register transfer has an S bit, which controls loading the condition
codes.  If clear, only the PC is loaded (resulting in a jump).

Except for the lack of signed loads and halfword addressing, it's a
great chip.

Oh, yes, each of the 4 processor states (user,  supervisor, IRQ, FIRQ)
has its own copy of R14 (link register) and R13 (usually used as stack
pointer).  FIRQ also has its own R8, R9, R10, R11 and R12.  An interrupt
is a branch and link to a different state's R14.
-- 
	-Colin

burley@albert.gnu.ai.mit.edu (Craig Burley) (05/06/91)

For what it's worth, one of the arguments I heard way back when as to why
branches were better than skips: "it is much easier to verify program
correctness when the architecture does not have skip instructions".

For the record, I never had any idea what that really meant.  :-)
--

James Craig Burley, Software Craftsperson    burley@gnu.ai.mit.edu

jesup@cbmvax.commodore.com (Randell Jesup) (05/06/91)

In article <1545@geovision.gvc.com> gd@geovision.gvc.com (Gord Deinstadt) writes:
>In a pipelined machine, would it not be more efficient to just deactivate
>a couple of instructions rather than go through the pain of a forward
>branch?  In other words just keep grinding forward, but inhibiting
>execution for a specified number of cycles, rather than trying to
>change course.  There would be no branch delay slot.

	See the Acorn ARM architecture, which I believe has this (encoded
off condition flags - all (or almost all) instructions can be conditionally
executed based on condition codes in order to avoid short forward branches.
(Of course, I may have mis-remembered it, in which case there will be 12 
different rebuttals).

-- 
Randell Jesup, Keeper of AmigaDos, Commodore Engineering.
{uunet|rutgers}!cbmvax!jesup, jesup@cbmvax.commodore.com  BIX: rjesup  
Disclaimer: Nothing I say is anything other than my personal opinion.
Thus spake the Master Ninjei: "To program a million-line operating system
is easy, to change a man's temperament is more difficult."
(From "The Zen of Programming")  ;-)

dik@cwi.nl (Dik T. Winter) (05/07/91)

In article <3449@charon.cwi.nl> I write:
 >                     Also the HP-PA annul bit does not count as a skip in
 > this sense.  The only HP-PA instructions that could be interpreted as skips
 > are the 'ADD AND BRANCH' instructions.
This is of course not true.  There are many more instruction with conditional
nullification.  So they really count as skip's.

Red face etc.
--
dik t. winter, cwi, amsterdam, nederland
dik@cwi.nl

edwardm@hpcuhe.cup.hp.com (Edward McClanahan) (05/07/91)

James Thomas writes:

> Is there a reference (or more) describing why SKIP instructions have mostly
> disappeared from instruction sets?  The 704x and 709x had them, so the
> PDP-6 had them (and maybe therefore the PDP-8 inherited them).  Now the
> HP-PA has them hiding in the guise of the nullify bit.  Are conditional
> branches generically more useful?

HP-PA only has 32 bit instructions, the first 6 bits of which are the "major
op-code" (thus ranging from 0 to 63).  The so-called "nullify bit" can be
applied to many instructions (as well as "condition checks").  I suppose an
alternative would be to define the major op-codes to be 7 (or 8 or 9...) bits
to include the "nullify bit".  The comparison:

  present HP-PA   modified HP-PA   meaning
  =============   ==============   =======

  BL   target,r2  BL   target,r2   Branch-and-link, execute following instr.
  BL,N target,r2  BLN  target,r2   Branch-and-link, don't execute following

  OR    r1,r2,r3  OR    r1,r2,r3   OR R1 with R2 sticking result in R3
                                   Always execute following instruction
  OR,TR r1,r2,r3  ORN   r1,r2,r3   OR R1 with R2 sticking result in R3
                                   Never execute following instruction
  OR,<  r1,r2,r3  ORLT  r1,r2,r3   OR R1 with R2 sticking result in R3
                                   Only execute next instr. if R1<R2 (signed)

  etc...

The point is, for HP-PA the lack of a specific SKIP instruction is purely
an Assembler syntax issue (in fact, there is no NO-OP in HP-PA, but since
R0 has value 0 and is a black hole, "OR r0,r0,r0" fills the same role; there
are many other pseudo-ops defined in the HP-PA Assembler).

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

  Edward McClanahan
  Hewlett Packard Company     -or-     edwardm@cup.hp.com
  Mail Stop 42UN
  11000 Wolfe Road                     Phone: (480)447-5651
  Cupertino, CA  95014                 Fax:   (408)447-5039

rbw00@ccc.amdahl.com ( 213 Richard Wilmot) (05/09/91)

>It seems to me the real reason was variable length instructions.  DEC
>machines up through the PDP-10 all had fixed length single word
>instructions, so it was obvious what skipping one would mean.  Ditto the IBM
>scientific machines up through the 7094, and their clones such as the GE
>635.  The IBM 360 and PDP-11 both had variable length instructions and
>condition codes.
>
>Variable length instructions make skips a lot less appealing.  I once used a
>machine that had single word skips but a combination of one and two word
>instructions (Varian 620, for you historians) and some impressively strange
>bugs resulted from skipping into the middle of a two-word instruction.
>
Oooh. Skipping into the middle of instructions. Honeywell built a 
family of machines starting with the H200 which were punctuation
machines. Storage manipulation started at an address and continued
until the source had a specified punctuation mark (two extra, non-data
bits) set (on). This was really dreamy for compilers and text manipulation.
Addresses were of several different lengths and there were instructions
to change the current address width (CAM: Change Addressing Mode).
Instructions consisted of opcode followed by register [?] and 
displacements (of the correct length for current addressing mode)
[this is from my hazy memory - didn't have room for those manuals].
Instruction would begin extraction and execution on seeing the word
mark that was set at the end of every instruction. So you could
have fully coded instructions that were presently off because their
word marks (in the preceding instructions) were not set, then
your program would turn those instructions on by setting the punctuation
bit. But if you branched to one of these instruction addresses then it
would extract and execute from the following word mark. So instructions
not preceded by word marks were turned off unless they were branched to.
Dijkstra?? :-)   GOTOs worked, they always did something.

Punctuation machines were fun. We need to bring them back to handle
null terminated strings. :-))



>John R. Levine, IECC, POB 349, Cambridge MA 02238, +1 617 492 3869
>johnl@iecc.cambridge.ma.us, {ima|spdcc|world}!iecc!johnl
>Cheap oil is an oxymoron.


-- 
  Dick Wilmot  | I declaim that Amdahl might disclaim any of my claims.
                 (408) 746-6108

kers@hplb.hpl.hp.com (Chris Dollin) (05/09/91)

I seem to remember that the CTL Modular 1 had skip instructions (possibly
branch instructions as well). Since I think I've lost my assembler manual, the
following may be inaccurate.

One of the instructions allowed all sorts of tests on the (few) machine
registers; if the test succeeded, the next instruction was skipped.
(Instrcutions were 16 bits long.) *However*, there was a way of extending the
instruction (I think one of the registers pointed at an extension word), in
which case more operations were available, *and* the skip could be 1, 2, or 4
(I think) instructions - a strange hybrid of skip & branch.

Skip instructions are a jolly neat way of making arbitrary instructions
conditional if you can't make arbitrary instructions conditional (as it were).
--

Regards,    "If anything anyone locks, they'll find it all ready in stocks."
Kers.       ----------------------------------------------------------------

jallen@eeserv1.ic.sunysb.edu (Joseph Allen) (05/10/91)

In article <1991May05.174307.8952@iecc.cambridge.ma.us> johnl@iecc.cambridge.ma.us (John R. Levine) writes:
>In article <1182@opus.NMSU.Edu> jthomas@nmsu.edu (James Thomas) writes:
>>Is there a reference (or more) describing why SKIP instructions have mostly

>When viewed as a condition prefix on an arbitrary instruction, a skip is a
>pretty nice construct, and I expect would be easy to teach a whizbang
>optimizer to use.  Now that fixed length instructions are coming back, I
>expect that we'll see more skips again.

Yes! lets get rid of those icky condition flags.  How about a "hop"
instruction?   A register to register/immediate compare with condition flags
and a short branch field.  Sounds CISCy but could the compare fit in the time
wasted to dump the pipeline?  I.E., so if it's 2 cycles it wouldn't matter
since it's replacing a compare and a branch.

Also, when are we going to see multiple error return points from OS calls? 
I.E., if no error goto return point+1, if error goto return point+0 which
contains a jump to the error handler.  DEC20 people know what I'm talking
about.

>John R. Levine, IECC, POB 349, Cambridge MA 02238, +1 617 492 3869
>johnl@iecc.cambridge.ma.us, {ima|spdcc|world}!iecc!johnl
>Cheap oil is an oxymoron.

-- 
/*  jallen@ic.sunysb.edu  */     /* Amazing */     /* Joe Allen 129.49.12.74 */
int a[1817];main(z,p,q,r){for(p=80;q+p-80;p-=2*a[p])for(z=9;z--;)q=3&(r=time(0)
+r*57)/7,q=q?q-1?q-2?1-p%79?-1:0:p%79-77?1:0:p<1659?79:0:p>158?-79:0,q?!a[p+q*2
]?a[p+=a[p+=q]=q]=q:0:0;for(;q++-1817;)printf(q%79?"%c":"%c\n"," #"[!a[q-1]]);}

torek@elf.ee.lbl.gov (Chris Torek) (05/10/91)

In article <1991May10.004650.7258@sbcs.sunysb.edu>
jallen@eeserv1.ic.sunysb.edu (Joseph Allen) writes:
>Also, when are we going to see multiple error return points from OS calls? 
>I.E., if no error goto return point+1, if error goto return point+0 which
>contains a jump to the error handler.

This is a nice idea, but the ret+0/1 is a bit limiting.  On the SPARC,
in which the system call number is passed in %g1 and %g2..%g7 are in
essence `wasted', it might be more reasonable to have the success-return
address passed in %g2.  That is, instead of:

		.globl	_read
	_read:
		mov	SYS_read, %g1	! read
		t	0		! read(%o0, %o1, %o2)
		bcc	1f		! if success, go return
		 .empty			! next instr okay in delay slot
		set	cerror, %g1
		jmp	%g1		! jump cerror
		 nop
	1:	retl			! success: jump to [%o7+8]
		 nop			! nothing to do in delay slot

we would have:

		.globl	_read
	_read:
		mov	SYS_read, %g1	! read
		add	%o7, 8, %g2	! success return
		t	0		! read(%o0, %o1, %o2)
		set	cerror, %g1
		jmp	%g1
		 nop

I will probably do this with a `high bit' in %g1 since it is not compatible
with SunOS (i.e.,
	#define RETFLAG 0x800
	_read: mov SYS_read+RETFLAG, %g1 ! read, return to %g2 on success
or something like that).

Actually, since the return is invariably a `retl' (return to %o7+8) I
might just make it use %o7+8.  This will save one whole instruction on
failure returns (oh boy :-) ).
-- 
In-Real-Life: Chris Torek, Lawrence Berkeley Lab CSE/EE (+1 415 486 5427)
Berkeley, CA		Domain:	torek@ee.lbl.gov

hrubin@pop.stat.purdue.edu (Herman Rubin) (05/10/91)

In article <1991May10.004650.7258@sbcs.sunysb.edu>, jallen@eeserv1.ic.sunysb.edu (Joseph Allen) writes:
> In article <1991May05.174307.8952@iecc.cambridge.ma.us> johnl@iecc.cambridge.ma.us (John R. Levine) writes:
> >In article <1182@opus.NMSU.Edu> jthomas@nmsu.edu (James Thomas) writes:

			...........................

> Yes! lets get rid of those icky condition flags.  How about a "hop"
> instruction?

Why get rid of condition flags?  Other than the condition register, they take
up little space, and also they cost essentially nothing.  Looking at one or
two bits is certainly cheaper than comparing two quantities, even if they are
in registers.  Overflow and carry are useful.

-- 
Herman Rubin, Dept. of Statistics, Purdue Univ., West Lafayette IN47907-1399
Phone: (317)494-6054
hrubin@l.cc.purdue.edu (Internet, bitnet)   {purdue,pur-ee}!l.cc!hrubin(UUCP)

kenton@abyss.zk3.dec.com (Jeff Kenton OSG/UEG) (05/10/91)

In article <1991May10.004650.7258@sbcs.sunysb.edu>,
jallen@eeserv1.ic.sunysb.edu (Joseph Allen) writes:
|> 
|> Also, when are we going to see multiple error return points from OS calls? 
|> I.E., if no error goto return point+1, if error goto return point+0 which
|> contains a jump to the error handler.  DEC20 people know what I'm talking
|> about.
|> 

Unix system calls on the Motorola 88000 do exactly that.

-----------------------------------------------------------------------------
==	jeff kenton		Consulting at kenton@decvax.dec.com        ==
==	(617) 894-4508			(603) 881-0011			   ==
-----------------------------------------------------------------------------

peter@ficc.ferranti.com (peter da silva) (05/10/91)

In article <1991May10.004650.7258@sbcs.sunysb.edu>, jallen@eeserv1.ic.sunysb.edu (Joseph Allen) writes:
> Also, when are we going to see multiple error return points from OS calls? 

You mean like fork() on the PDP-11?
-- 
Peter da Silva; Ferranti International Controls Corporation; +1 713 274 5180;
Sugar Land, TX  77487-5012;         `-_-' "Have you hugged your wolf, today?"

pkl@ee.mu.OZ.AU (Peter LAWREY) (05/17/91)

In article <12162@mentor.cc.purdue.edu> hrubin@pop.stat.purdue.edu (Herman Rubin) writes:
>In article <1991May10.004650.7258@sbcs.sunysb.edu>, jallen@eeserv1.ic.sunysb.edu (Joseph Allen) writes:
>> In article <1991May05.174307.8952@iecc.cambridge.ma.us> johnl@iecc.cambridge.ma.us (John R. Levine) writes:
>> >In article <1182@opus.NMSU.Edu> jthomas@nmsu.edu (James Thomas) writes:
>
>Why get rid of condition flags?  Other than the condition register, they take

Condition flags are difficult to handle with out of order execution, interupts.
etc. To hold a condition you must save the PC,IR and the Condtion codes
for each stage of your pipeline. Also such things as multi-word operations are
made very rarely. You can have a trap on overflow or skip if no overflow
instruction that avoid these. But this occurs rarely in most programs.