Cute Tricks on the UNIVAC® 1100
or
I Never Woulda Thoughta…

Walter Gilbert
University of Maryland
Administrative Computer Center
Edition One: March 1974
Edition Two: Sept 1974
Edition Three: March 1975


The following is a series of programming “tricks” that I have acquired or developed throughout my experience on the UNIVAC 1108. I hope that they will prove to be worthwhile here and there to others. Many of them have been contributed in response to earlier editions of this document. If any one has any similar contributions to make to this collection, we might be able to turn this into a regular publication which I, at least initially, would be glad to compile. Send them to:

Walter Gilbert
Obsolete address elided by editor.

Do it today and you'll feel better for it tomorrow.

Note: save this copy because the next edition (4) will not include anything that has been in the previous 3 editions: three “strikes” and out.

1.   @USE TPF$, …

This is probably one of the most generally useful item herein contained and also one of the most obvious (once you have seen it). When manipulating a program file frequently in a run, especially from demand, it can be very convenient to attach the name “TPF$” to it so that it becomes your default file.

    @USE    TPF$,PROGRAM*FILE.

Many of the advantages are obvious. This technique can be particularly useful for MAP'ing because you can write your maps so that they work in any file by not having to point them at your specific program file. John Walker of ISD (Calif) has found a very good reason for @FREE'ing your original TPF$ before attaching the name to another file. It will only happen in an unusual sequence of events but it would do weird and wonderful things to both files.


2.   C$$OM

(Corr. Ed. 2)

If you dislike writing ER's to COM$ because of the nuisance involved, here is a little PROC which allows you to do it all in one line. It generates the call in line, and the three-word packet and literal, if given, under the LIT counter. Examples:

        C$$OM       12,('CONSOLE MSG.').

        C$$OM       22,MSG1.

        C$$OM       6,MSG2,10,ANSWER.

The PROC:

P       PROC        1,2.
C$$OM*  NAME.
        L,U         A0,(($))+((P(1,1),P(1,2)));
                    -((P(1,3),P(1,4)+(P(1,3)=0)*($+1)))+1.
        ER          COM$.
        END.


3. Test-and-Set

Here is a trick that is useful in multiactivity programs where there is a possibility that an activity may become locked in a test-and-set loop. This is particularly valuable while debugging or if a test-and-set word is being shared between realtime and non-realtime activities. (What can happen is that if an RT activity hits a test-and-set word set by a non-realtime activity, the non-RT activity will never regain control again to clear the lock and your system will suddenly go into a blank stare.) The concept is instead of directly executing the TS instruction, execute it remotely via the “EX” instruction using index incrementation. If the lock is set, the interrupt occurs and the Exec requeues the activity at the “EX” instruction. However, when control is regained, the “EX” is no longer pointing at the “TS” so control can be recaptured by the program. The following is an example of how this could be used.

        .  .  .
        .  .  .
        L,U         A0,TSWORD.      POINT A0 AT A TS WORD
        LMJ         X11,TANDS.      GO DO A TEST AND SET
        .  .  .
        .  .  .
        .  .  .
        .  .  .
.  THE TEST AND SET SUBROUTINE
.
TS      TS          0,A0.           EX POINTS HERE 1ST TIME
        JGD         A2,TS2.         EX POINTS HERE 2ND TIME
TANDS*  L,U         A2,11.          TEST THE LOCK 12 TIMES
TS2     L           A1,(1,0).
        EX          TS,*A1.         EX EITHER TS OR JGD
        JP          A2,0,X11.       JUMP IF LOCK PASSED
                                    . CODE GOES HERE TO DO
                                    . SOMETHING ABOUT THE
                                    . LOCK WHICH HAS BEEN HIT
                                    . 12 TIMES IN A ROW.


4. Character Manipulation in FORTRAN

By use of the two DEFINE statements given below, FORTRAN can be convinced to address characters packed six per words as if each were in a word by itself. It makes character farbling almost nice.

        INTEGER WORDS( ... )
        DEFINE WWW(I) = WORDS(I)
        DEFINE CHARS(I) = FLD(6*MOD(I+5,6),6,WWW((I+5)/6))

There two DEFINEs, the first solely to pacify FORTRAN, enable you to use the CHAR(...) like any other dimensioned variable (almost) with the effect being

        CHARS(1) => FLD( 0,6,WORDS(1))
        CHARS(2) => FLD( 6,6,WORDS(1))
        CHARS(3) => FLD(12,6,WORDS(1))
        .   .   .   .
        CHARS(6) => FLD(30,6,WORDS(1))
        CHARS(7) => FLD( 0,6,WORDS(2))
        .   .   .   .
        ETC.

Example:

5       READ(5,10,END=999)(WORDS(I),I=1,12))
10      FORMAT(12A6)
        DO 20 M=1,72                @FIND 1ST NONBLANK IN LINE
20      IF(CHARS(M).NE.1R ) GO TO 30
        GO TO 5                     @(BLANK LINE)
30      IF(M.EQ.1) GO TO 60
        DO 40 I=M,72                @LEFT JUSTIFY THE LINE
40      CHARS(I-M+1) = CHARS(I)
        DO 50 I=2,M                 @SPACE FILL THE END
50      CHARS(74-I) = 1R
60      ...

This method can be adapted to other subdivisions of words besides characters, vis:

Quarterwords:

        INTEGER WORDS( ... )
        WWW(I) = WORDS(I)
        QTR(I) = FLD(9*MOD(I+3,4),9,WWW((I+3)/4))

Bits:

        INTEGER WORDS( ... )
        WWW(I) = WORDS(I)
        BITS(I) = FLD(MOD(I+35,36),1,WWW((I+35)/36))


5. Validating Numeric Characters

Note that this algorithm has been changed from that in edition one because it would fail if all six digits were nines (due to the old +0 −0 problem of one's complement).

How many times have you struggled over the problem of determining whether or not all six FIELDATA characters in a word are numerals. Never again. With the following five instructions, all six can be validated in one deft stroke. Try it.

        LN      A0,<WORD>.                THE WORD TO CHECK
        ANU     A0,(060606060606).
        OR      A0,A1.
        AND     A1,(0606060606060).
        JNZ     A2,<ERROR>.               JUMP IF ANY NON-NUMERIC

The proof is left as an exercise for the reader. By changing the masks, any subset of characters in the word can be validated to be numeric. Also, other contiguous series of characters can be checked in a similar manner. The following will validate that the word being tested contains only FIELDATA letters of the alphabet and no others.

        L       A0,<WORD>.
        ANU     A0,(060606060606).
        OR      A0,A1.
        AND     A1,(0404040404040).
        JNZ     A2,<ERROR>.

The numeric test can be written in FORTRAN simply as follows:

        DATA M0,M9/'000000','999999'/
        .  .  .
        IF(AND(M0,OR(BOOL(-WD),M9+BOOL(-WD))))99,,99


6. Adding and Subtracting in FIELDATA

They said it couldn't be done, but … the 1100 can do nines complement addition and subtraction directly in FIELDATA without conversion to binary and without messy loops to handle the characters (digits) one at a time. In the following examples, the values are assumed to be full words of six FIELDATA numerals, left filled with “0”s if necessary. The code in Example 5 is useful to guarantee that the characters being manipulated are indeed FIELDATA numerals, “0” to “9”.

Addition:

        L       A0,<WORD1>.           LOAD 6 FIELDATA NUMRALS
        A       A0,<WORD2>.           ADD ANOTHER WORD OF NUMERALS
        A       A0,(0252525252525).   GENERATE THE CARRIES
        AND     A0,(0606060606060).   PICK OUT CARRIES
        SSC     A1,3.                 POSITION THE CARRIES
        AN      A0,A1.                EFFECT THE CARRIES
        OR      A0,(0606060606060).   RESULT IN A1

Subtraction: (only six instructions)

        L       A0,<WORD1>.
        AN      A0,<WORD2>.
        AND     A0,(0606060606060)    GENERATE CARRIES
        SSC     A1,3.
        AN      A0,A1.                EFFECT THE CARRIES
        OR      A0,(0606060606060).   RESULT IN A1

Form Nines Complement:

        L       A0,(0252525252525).
        AN      A0,<WORD>.            SIGN NOW CHANGED

Double Precision (12 digit) Addition:

        DL      A0,<WORDS1>.
        DA      A0,<WORDS2>.
        DA      A0,(0252525252525252525252525).
        DL      A2,A0.
        OR      A3,(0171717171717).
        OR      A2,(0171717171717).
        DAN     A0,A3.                (TWO AN'S FASTER HERE)
        DSC     A3,3.
        DAN     A0,A3.                (ALSO HERE)
        DAN     A0,(0060606060606060606060606). RESULT IN A0 & A1.

(Ed. 2) Floyd Linn of Houston provided the improvements to the add and sub algorithms—they are each one line shorter than in the original version.


7. Converting a Number from FIELDATA to Binary

The following 10 instructions will convert a word of six FIELDATA numerals in A0 to their binary equivalent in A1. I believe that this is the fastest way to do this on an 1108.

This algorithm is applicable to many different computers, not just the UNIVAC 1108. I have known this concept for so long I am uncertain if it is original.

        AND     A0,(0171717171717).   STRIP OFF 'ZONE' BITS
        AND     A1,(-0,0,-0,0,-0,0).  EXTRACT ALTERNATE DIGITS
        MF      A2,(54*/29).
        AN      A1,A2.                3 PAIRS OF DIGITS CONVERTED
        AND     A1,(0,-0,0).
        MF      A2,((1*/12-100)*/23).
        AN      A1,A2.                RIGHT 4 DIGITS NOW DONE
        AND     A1,(-0,0,0).
        MF      A2,((1*/24-10000)*/11).
        AN      A1,A2.                DONE. RESULT IN A1, ORIGINAL IN A0.


8. Sequential character load, store, etc.

A frequent reason for dropping into assembly language is to scan a string of characters packed six per word. There are probably as many character-fetch methods as there are programmers, however, I feel that the following method is both the fastest and the most economical of registers—it requires only three, total. This code came from the Computer Science Center of the University of Maryland.

To initialize the scan:

        L       X11,(1,LOAD).
        L       A1,(1,STRING).

To load a character into A0

        EX      0,*X11.

The “subroutine”:

        L,S6    A0,0,*A1.
        LMJ     X11,0,X11.
LOAD    L,S1    A0,0,A1.
        L,S2    A0,0,A1.
        L,S3    A0,0,A1.
        L,S4    A0,0,A1.
        L,S5    A0,0,A1.
        LMJ     X11,LOAD-2.


9. “CDU

In the world of useless instructions, CDU, Characteristic Difference to Upper, ranks very high (and very rank). However, since the advent of the mighty quarterword, it has suddenly become marginally useful, if you go in for that sort of thing. Observe:

        CDU     A0,(0).

has the effect of peeling out the leftmost quarterword in A0 and putting it into A1, right justified and zero filled.

        .  .  .
        .  .  .
LOC1    L       A0,<...>,*X1.         LOAD WORD OF QUARTERWORDS
        L,U     R3,3.
LOC2    CDU     A0,R3.                QTRWD TO A1
        .  .  FARBLE  .  .
        .  .  FARBLE  .  .
        LSSC    A0,9.
        JGD     R3,LOC2.
        JGD     ...,LOC1.


10. Writing Partial Words in FORTRAN

If you write FORTRAN programs that make heavy use of halfwords, sixths, quarters and thirds, the following FORTRAN PROC is a great convenience and also makes the code much more readable.

AXR PROC
        DEFINE S1(I) = FLD( 0, 6,I)
        DEFINE S2(I) = FLD( 6, 6,I)
        DEFINE S3(I) = FLD(12, 6,I)
        DEFINE S4(I) = FLD(18, 6,I)
        DEFINE S5(I) = FLD(24, 6,I)
        DEFINE S6(I) = FLD(30, 6,I)
        DEFINE Q1(I) = FLD( 0, 9,I)
        DEFINE Q2(I) = FLD( 9, 9,I)
        DEFINE Q3(I) = FLD(18, 9,I)
        DEFINE Q4(I) = FLD(27, 9,I)
        DEFINE T1(I) = FLD( 0,12,I)
        DEFINE T2(I) = FLD(12,12,I)
        DEFINE T3(I) = FLD(24,12,I)
        DEFINE H1(I) = FLD( 0,18,I)
        DEFINE H2(I) = FLD(18,18,I)
END

Now common partial words can be referenced easily:

    INCLUDE AXR
    . . .
    . . .
    S3(VAL) = S2(PTR)+S6(TABLE(I))
    IF(H1(ITEM).EQ.0) ...


11. Negative U-Field Addresses

Everyone who learns the assembly language of the 1100 after knowing the assembly language of another vendor's hardware is struck by the fact that the U-field in an instruction cannot be a negative offset. One frequently needs to write instructions like

        L       A0,-1,X10.

but has to accomplish his needs some other way. However, there is an occasion on the 1100 where instructions like the above are possible within limits. Since all shift instructions only interpret the rightmost seven bits of the computed shift count, it is possible to fake a negative offset by the following:


    SSL     A0,-1,A3.       ==>     SSL    A0,0777,A3.
    LDSL    A10,-2,X1.      ==>     LDSL   A10,0776,X1.

            ETC.                           ETC.

as long as the computed shift count remains positive.


12. How to Tell if Quarter Word Mode is On

(John Walker, ISD)

Sometimes you write a subroutine which must be executed in quarter word mode, and you wish to make sure it's been called in the correct mode. This can be accomplished in one instruction without destroying any registers by:

        TP,T1   $.                    IS QUARTER WORD MODE ON?
        J       THIRDW.
        <QUARTER WORD MODE RETURN>

Obviously, a “TN” instruction will reverse the test.


13. How to Set a Flag Nonzero

(John Walker, ISD)

Sometimes the need arises to set a flag nonzero when register contents may not be assumed or changed. UNIVAC's PROC to turn on diagnostic dumps provides a three instruction sequence for this. Much better is the following:

        SA,S1   A0,<CELL>
        SNA,S2  A0,<CELL>

This will always set T1 of the word nonzero. If in quarter word mode, replace S1 and S2 with Q1 and Q2 to set H1 nonzero. If speed is of the essence, H1 and H2 will be faster.


14. How to Tell if a Run Is Demand

(John Walker and Walter J. Gilbert)

While the type of a run is passed in A4 at program initiation time, it is difficult for a reentrant subroutine to determine if it has been called from a demand run unless the user knows that Exec register R14 (octal 0136) always contains the type and level of the executing activity. The type will always be 4 for a demand run.

        LA      A0,0136 (TAL)         LOAD TYPE AND LEVEL
        TOP,U   A0,0300               IS IT A DEMAND RUN?
        J       DEMAND                YES. DO FUNNY THINGS
        <BATCH RUN>                   DO STRAIGHT-LACED THINGS

(Note: this will not work beyond Exec level 31!)


15. Character Addressing in Assembly Code

(John Walker, ISD)

It is frequently convenient to be able to address characters whose numbers are known at assembly time without the nuisance of counting words and sixths. This assembly FUNC provides such a facility in a manner parallel to Walt Gilbert's CHARS DEFINE for FORTRAN (Trick #4):

COLUMN*         FUNC
B       EQU     COLUMN(1)-1
A       EQUF    B/6,,13-(B-(B/6)*6)
        END     A
Examples of use:
        LA      A0,IMAGE+COLUMN(10)   LOAD COLUMN 10 OF IMAGE
        LA      A3,COLUMN(4),X2       LOAD FOURTH COLUMN OF BUFFER

Note that this FUNC may be easily rewritten to address quarter words.


16. High Speed Alphanumeric (Unsigned) Comparison

It is frequently desirable to compare two 36-bit quantities as unsigned values. The 1100 offers no direct test instructions to accomplish this (other than MASL, MASG, which are supererogatory for our purposes). This trick was discovered in the DOD COBOL library, but has spread very slowly. The following instructions will do it:

        LA      A0,<FIRST>            LOAD FIRST VALUE
        ANA     A0,<SECOND>           SUBTRACT SECOND FROM FIRST
        JZ      A0,EQUAL              IF DIFFERENCE ZERO, THEY'RE EQUAL
        JC      GREATER               IF CARRY SET, FIRST > SECOND
.       <LESS>                        IF CARRY NOT SET, FIRST < SECOND

(John Walker)


17. Recursive Procedures in FORTRAN

(Ted Tenny, Lockheed)

Although FORTRAN subroutines are not recursive, the “ASSIGN” statement with the assigned “GO TO” statement can be used to implement a recursion scheme, by saving return addresses on a pushdown stack. Here's how:

        INTEGER PSTACK, TOP, RTNADR
        COMMON TOP, PSTACK(256)
        .
        .
        .
COMMENT:  STATEMENT 102 BEGINS A RECURSIVE PROCEDURE;
  102   CALL PUSH(RTNADR)
        .
        .
        .
          [PROCEDURE BODY]
        .
        .
        .
        CALL POP(RTNADR)
        GO TO RTNADR
COMMENT:  END OF PROCEDURE;
        .
        .
        .
COMMENT:  CALL TO THE RECURSIVE PROCEDURE AT STATEMENT 102;
        ASSIGN 104 TO RTNADR
        GO TO 102
  104   CONTINUE
        .
        .
        .
        SUBROUTINE PUSH(ITEM)
        INTEGER PSTACK, TOP
        COMMON TOP, PSTACK(256)
        TOP = TOP + 1
        IF (TOP.GT.256)  CALL PSDUMP
        PSTACK(TOP) = ITEM
        RETURN

        SUBROUTINE POP(ITEM)
        INTEGER PSTACK, TOP
        COMMON TOP, PSTACK(256)
        IF(TOP.EQ.0) CALL PSDUMP
        ITEM = PSTACK(TOP)
        TOP = TOP - 1
        RETURN

The “ASSIGN” statement and the unconditional “GO TO” behave like the machine instructions which the compiler generates for an ordinary subroutine call, i.e. they save the return address and transfer control to the subroutine. What's different is that the return address is then stored on a pushdown stack instead of in a fixed location. This makes recursion possible. Note that all of the recursive procedures must belong to the same FORTRAN compilation, since “RTNADR” must be recognized and treated as a local address by the FORTRAN compiler.

Procedures implemented in this fashion are without arguments. The subroutines “PUSH” and “POP” can be used to save and retrieve local variables within a procedure, and they could be extended to transmit the values of simple arguments.


18. Conversion from Binary to FIELDATA Octal

(D. Zave, EXEC 8 Code)
BINOCT.      BINARY TO OCTAL CONVERSION
        AND     A0,(0707070707070).
        LSSC    A1,3.
        A       A1,('000000').        THESE 12 INSTRUCTION
        LR      R2,(0700070007).      CONVERT A BINARY WORD
        MLU     A1,A0.                IN A0 TO A 12-DIGIT
        LR      R2,(0707770777077).   FIELDATA OCTAL EQUIVALENT
        MLU     A0,A1.                IN A1 &A2.
        SSC     A1,30.                THE ORIGINAL WORD IN
        DSC     A1,48.                A0 IS NOT CHANGED
        SSC     A2,12.
        DSC     A1,12.
        SSC     A1,24.


19. One-Time Execution of a Block of Code

(Walter Colquitt, Sigma Corp.)

It is frequently required to execute some special initializing code the first time a routine is used, and only the first time. The following two lines of “self-destructing” code accomplish this. Note that the address fields of both instructions will be changed ultimately.

        SLJ     $.
        J       INITCODE.


20. Setting Up an Entire Subscripted List

(Carlos Ballantyne, SIA)

The following PROC allows the easy building of entire subscripted lists with arbitrary names. In all cases, entry zero contains the number of entries in the list.

                           P PROC *1
                           EQTL* NAME
                           I DO P(1),DFN(I) EQU P(1,I)
                           DFN(0) EQU P(1)
                           * EQU DFN
                            END
                           .
                           A EQTL 2,4,6,5
000000 04 02 04 06 05 00    +A(0),A(1),A(2),A(3),A(4),A(5)
                            END


21. Two Digit Binary to FIELDATA Decimal

(Ivan H. Mann, III EPA)

This is the shortest way to convert a positive binary integer less than 100 to FIELDATA.

        DSL     A0,36.                ORIGINAL VALUE IN A0
        DI,U    A0,10.
        LSSL    A0,6.                 POSITION LEFT DIGIT
        A,U     A1,06060,A0.          DONE


22. Fastest Possible Binary Search on 1108

(Walter Gilbert, UMD)

Given a table of integers sorted low to high, this is the fastest way of finding a particular entry.

        SZ      X11.                  TOP OF TABLE
        L,U     A0,N-1.               N=TABLE LENGTH
        L,U     A1,(N-1)/2.           TABLE MIDPOINT
        L       A2,VALUE.             VALUE TO SEARCH FOR
        L       A4,LSC((N-1)/16).     # OF BINARY LEVELS TO GO
                                      . SEE NOTES BELOW
        J       ANU.                  WE'RE OFF!
LOOP    S       A1,X11,A3.            EITHER (A1)=> X11 OR (A1)=> A0
        AU      A0,X11.               COMPUTE NEW MIDPOINT
        SSL     A1,1.
ANU     ANU     A2,TABLE,A1.          COMPARE
        SSL     A3,35.                ISOLATE SIGN BIT
        JGD     A4,LOOP.
        S       A1,X11,A3.            END OF BINARY SECTION
        AN      A0,X11.
        LXI,U   X11,1.                SETUP FOR SEARCH OF
        L,U     R1,1,A0.              8 TO 16 WORDS
        SE      A2,TABLE,*X11.
        J       NOFIND.
        L,U     A0,TABLE-1,X11.       FOUND! ADDR IN A0

Note: for dynamic table sizes, the value on line 5 is computed:

        LSC     A3,A0.
        L,U     A3,35.
        ANU     A3,A4.
        SSL     A4,4.

For fixed table sizes, the value on line 5 is computed by the following FUNC:

F       FUNC.
LSC*    NAME.
I(0)    EQU     0.
I       DO 18, DO 1*/(I-1)-1<F(1) ,I(0) EQU I.
        END     I(0).


23. Test for a Variety of Characters

There is a fast way to test if a character belongs to a particular set of characters without multiple tests or using a table. Since a FIELDATA character can have a value of 0 to 63, we can assign a bit in a double word to each character and build a mask which is used:

        L       A0,<CHAR>
        L       A1,<MASK>
        DSC     A1,0,A0
        JNB     A2,NOFIND

A few masks are:

   CHARACTERS                MASK                 COMMENTS
   ----------                ----                 --------
A-Z,0-9,$-          017770010137777777700    FILE NAME CHARACTERS
0-9,!JKLMNOPQR      017771000000077700000    OVERPUNCHED SIGN

where the rightmost bit (bit 0) represents “@”, and the rest proceed to the left from there.


Glossary

In the era in which this document was compiled, each major computer manufacturer had their own private nomenclature for objects for which generally accepted terms have emerged over the succeeding years. If your memory of UNIVAC-speak is tad rusty, the following table provides present-day equivalents for those used herein.

When reading the assembly language examples, it may help to consult the instruction set reference.

UNIVAC Term Contemporary Equivalent
Activity Process or Thread
ER Operating System Call
Exec, EXEC-8 Operating System
Map Linker / Link Instructions
Multiactivity Multi-threaded
PROC or FUNC Assembler Macro
Program File Directory
Run Job
U-Field Address Field (of instruction)
/* Left shift operator (Assembler)

About this Edition

The original editions of this document circulated widely within the UNIVAC systems programming community in the mid 1970s. Walt Gilbert's original collection of “cute tricks” spurred a flurry of submissions by others, culminating in this edition which was originally distributed in March 1975.

This electronic edition was prepared by John Walker in November 1999, and is based on an nth generation photocopy of the original kindly supplied by Kent Walker (no relation), a fellow UNIVAC systems programmer in the 1970s who is now an engineer at Space Systems/Loral in California. Having been originally printed on a gnarly 1970s UNIVAC line printer, then copied numerous times, I wasn't able to scan and OCR the paper document, so there was no alternative but to retype it. The original text was formatted by UNIVAC DOC and was, consequently, all upper case. Given the need to re-keyboard the text, I decided to convert the descriptive text to upper and lower case in the interest of readability; the code examples remain in upper case as they were originally presented. A couple of obvious typos in the text have been corrected; the code examples are verbatim. I have added links, where appropriate, to other documents related to topics discussed herein.

UNIVAC has been, over the years, a registered trademark of Eckert-Mauchly Computer Corporation, Remington Rand Corporation, Sperry Rand Corporation, Sperry Corporation, and Unisys Corporation.