3.3.2. Linkage to Externally Compiled and Assembled Routines

Version I.5, September 1978

page167 The UCSD Pascal I.5 system supports a facility for integrating externally compiled and assembled routines and data structures. Use of separately compiled structures allows the user to create files of frequently used routines. After a structure is compiled, the user adds it to a library, using the librarian. Files that reference that structure need not compile it directly into their code file, rather, the linker copies the existing code into the host code file. Separate compilation or assembly is supported in these areas: between portions of programs written in Pascal; between assembly language routines and Pascal hosts; and finally, between assembly language routines. Each of these areas is discussed in turn by the following sections.

3.3.2.1. Pascal to Pascal Linkages — Units

A UNIT is a group of interdependent procedures, functions, and associated data structures which perform a specialized task. Whenever this task is needed within a program, the program indicates that it USES the UNIT. A UNIT consists of two parts, the INTERFACE part, which declares constants, types, variables, procedures and functions that are public and can be used by the host program, and the IMPLEMENTATION part, which declares constants, types, variables, procedures and functions that are private. These are not available to the host program and are used by the UNIT. The INTERFACE part declares how the program will communicate with the UNIT while the IMPLEMENTATION part defines how the UNIT will accomplish its task.

TURTLEGRAPHICS (example B) is a UNIT which enables the user to draw pictures using a graphics turtle. The INTERFACE consists of procedures like MOVE, TURN and PENCOLOR, which allow the user to move the turtle and change colors. TURTLEGRAPHICS also employs DRAWLINE, an externally assembled procedure, to draw the lines and the turtle.

page168 A program that uses TURTLEGRAPHICS has no need for DRAWLINE, and, consequently, DRAWLINE is private to that UNIT.

PROGRAM DRAWPOLYGON;
USES TURTLEGRAPHICS;
VAR I: INTEGER;
    SIZE, NUMSIDES: INTEGER;

BEGIN
  INITTURTLE; (* Initialize the UNIT's variables *)
  WRITE('What size polygon?');
  READLN(SIZE);
  WRITE('How many sides?');
  READLN(NUMSIDES);
  FOR I = 1 TO NUMSIDES DO
  BEGIN
    MOVE(SIZE);
    TURN(360 DIV NUMSIDES);
  END;
END.
Sample A

A program must indicate the UNITs that it USES before the LABEL declaration part of the program. At the occurrence of a USES statement, the compiler references the INTERFACE part of the UNIT as though it were part of the host text itself. Therefore all public constants, types, variables, functions, and procedures are global. Name conflicts may arise if the user defines an identifier that has already been defined by the UNIT. Procedures and functions may not USE UNITs locally.

UNIT TURTLEGRAPHICS;
  INTERFACE
    TYPE
      TGCOLOR = (NONE, WHITE, BLACK, REVERSE);

  PROCEDURE INITTURTLE;
  PROCEDURE TURN(RELANGLE: INTEGER);
  PROCEDURE MOVE(RELDISTANCE: INTEGER);
  PROCEDURE MOVETO(X, Y: INTEGER);
  PROCEDURE TURNTO(ANGLE: INTEGER);
  PROCEDURE PENCOLOR(PCOLOR: TGCOLOR);
page169
IMPLEMENTATION
  CONST
    TERXSIZE = 319;
    TERYSIZE = 239;
    RADCONST = 57.29578;

  TYPE
    SCREEN = PACKED
               ARRAY [0..TERXSIZE, 0..TERYSIZE] OF BOOLEAN;
  VAR
    (* Private variables *)
    TGXPOS: INTEGER;
    TGYPOS: INTEGER;
    TGHEADING: INTEGER;
    TGPEN: TGCOLOR;

    I, J: INTEGER;
    S: SCREEN;

  (* Externally assembled procedure *)
  PROCEDURE DRAWLINE(VAR RADAR: INTEGER; VAR S: SCREEN;
                     ROW, XO, YO, DX, DY, PEN: INTEGER);
    EXTERNAL; (* External declaration *)

  PROCEDURE INITTURTLE;
  BEGIN
    FILLCHAR(SCREEN, SIZEOF(SCREEN), 0);
    UNITWRITE(3, SCREEN, 63);
    HEADING := 0;
    TGXPOS := 0;
    TGYPOS := 0;
  END;

  PROCEDURE MOVE; (* Public procedure, parameters declared above *)
  BEGIN
    MOVETO(ROUND(TURTLEX + DIST * COS(TURTLEANGLE / RADCONST),
           ROUND(TURTLEY + DIST * SIN(TURTLEANGLE / RADCONST));
  END;
page170
  PROCEDURE MOVETO;
  VAR R: INTEGER;
  BEGIN
    DRAWLINE(H, S, 20, 160 + TURTLEX, 120 - TURTLEY,
             X - TURTLEX, TURTLEY - Y, ORD(TURTLEPEN));
  END;

  PROCEDURE TURN; (* Public procedure, parameters declared above *)
  BEGIN
    HEADING := (HEADING + RELANGLE) mod 360;
  END;

  PROCEDURE TURNTO;
  BEGIN
    HEADING := ANGLE;
  END;

  PROCEDURE PENCOLOR;
  BEGIN
    TGPEN := PCOLOR;
  END;
END. (* End of unit *)
Example B

Example B is a skeleton for a TURTLEGRAPHICS UNIT. Note that the procedures MOVE, TURN, and INITTURTLE, and the TYPE TGCOLOR, are declared in the INTERFACE part and are available for use by the host program. Since the procedure DRAWLINE is not part of the INTERFACE, it is private, and may not be used by the host. The syntax for a UNIT definition is shown below. The declarations of routine headings in the INTERFACE part are similar to forward declarations; therefore, when the corresponding bodies are defined in the IMPLEMENTATION part, formal parameter specifications are not repeated.

A UNIT may also USE another UNIT, in which case the USES declaration must appear at the beginning of the INTERFACE part. In example C, PICTUREGRAPHICS indicates in the INTERFACE part that it USES TURTLEGRAPHICS. Note that the program USEGRAPHICS, which USES PICTUREGRAPHICS, indicates that it USES TURTLEGRAPHICS before using PICTUREGRAPHICS. It is important that the INTERFACE part of TURTLEGRPLPHICS be defined before PICTUREGRAPHICS makes references to it, therefore this ordering is required.

page171 Note: Variables of type FILE must be declared in the INTERFACE part of a UNIT. A FILE declared in the IMPLEMENTATION part will cause a syntax error upon compilation. This is due to the nature of generation of initialization code for FILEs.

PROGRAM USEGRAPHICS;

UNIT PICTUREGRAPHICS;
INTERFACE
  USES TURTLEGRAPHICS; (* TURTLEGRAPHICS is defined in the
  TYPE                 (* *SYSTEM.LIBRARY, see section III below *)
    PVECTOR = ^VECTOR;
    VECTOR = RECORD
               DELHEADING: INTEGER;
               DELDISTANCE: INTEGER;
               PENDOWN: BOOLEAN;
               NEXTVEC: PVECTOR
             END; (* record *)
  VAR
    START: PVECTOR; (* Head of list of lines *)
    HEAP: ^INTEGER;

  PROCEDURE MAKESUBPICTURE;

  PROCEDURE DRAWSUBPICTURE;

IMPLEMENTATION

  PROCEDURE MAKESUBPICTURE;
  BEGIN
    (* Calculates next subpicture and stores on heap *)
  END;

  PROCEDURE DRAWSUBPICTURE;
  BEGIN
    LPVEC := START; (* Start at beginning of list *)
    WHILE LPVEC <> NIL DO (* and draw each that's there *)
      WITH LPVEC^ DO
        BEGIN
          TURN(DELHEADING);
          MOVE(DELDISTANCE);
          IF PENDGI4N
            THEN TGPEN := WHITE
            ELSE TGPEN := NONE;
          LPVEC := NEXTVEC;
        END;
  END; (* drawsubpicture *)
page172
  END;

USES TURTLEGRAPHICS, PICTUREGRAPHICS; (* picturegraphics uses *)

BEGIN (* turtlegraphics *)
  INITTURTLE;
  REPEAT
    MARK(HEAP);
    MAKESUBPICTURE;
    DRAWSUBPICTURE;
    RELEASE(HEAP);
  UNTIL START = NIL;
END.
Example C

< Compilation unit > ::= < Program heading > ; { < Unit definition > ; }
< Uses part > < Block > |
< Unit definition > { ; < Unit definition > }.
< Unit definition > ::= < unit heading > ;
< Interface part >
< Implementation part > End
< Unit heading > ::= Unit < Unit identifier > |
Separate unit < Unit identifier >
< Unit identifier > ::= < Identifier >
< Interface part > ::= Interface
< Uses part >
< Constant definition part >
< Type definition part >
< Variable declaration part >
< Procedure heading > | < Function heading >
< Implementation part> ::= Implementation
< Label declaration part >
< Constant definition part >
< Type definition part >
< Variable declaration part >
< Procedure and Function declaration part >
< Uses part > ::= Uses < Unit identifier >
{ , < Unit identifier > } ; | < Empty >

See Section 5.9 for Syntax diagrams.

Diagram D

page173 The user may define a UNIT in-line, after the heading of the host program. In this case the user compiles both the UNIT, and the host program together. Any subsequent changes in the UNIT or host program require the user to recompile both. The user may also define and compile a UNIT (or a group of UNITs) separately, and use the library manager to store it (or them) in a library. After compiling a host program that uses such a UNIT, the user must link that UNIT into the code file by executing the LINKER. Trying to R(un an unlinked code file will cause the LINKER to run automatically, trying to X(ecute an unlinked file causes the system to remind you to link the file.

Changes in a host program require only that the user recompile the program and link in the UNIT. Changes in the IMPLEMENTATION part of a UNIT only require the user to compile the UNIT, and then to relink all compilation units that use that UNIT. Changes in the INTERFACE part of a UNIT require that the user recompile both the UNIT and all compilation units that use that UNIT. In this case all these compilation units must again be linked. For more information see section 1.8 LINKER or section 4.2 LIBRARIAN.

The compiler generates LINKER information in the contiguous blocks following the code for a program that uses UNITs. This information contains locations of references to externally defined identifiers. Section 1.8 explains the format of this information.

3.3.3.2. Pascal to Assembly Language Linkages — External Procedures

External procedures are separately assembled assembly language procedures or separately compiled procedures, stored in a LIBRARY on disk. Host programs that require external procedures must have them linked into the compiled code file. Typically the user writes external procedures in assembly language, to handle low-level operations that Pascal is not designed to provide. External assembly language procedures are also used for their comparative speed in ‘real time’ applications.

page174 A host program declares that a procedure is external in much the same way as a procedure is declared FORWARD. A standard heading is provided, followed by the keyword EXTERNAL. Calls to the external procedure use standard Pascal syntax, and the compiler checks that calls to the external agree in type and number of parameters with the external declaration. It is the user's responsibility to assure that the assembly language procedure respects the Pascal external declaration. The linker checks only that the number of words of parameters agree between the Pascal and assembly language declarations. For more information see section 1.8 Linker and 1.9 Assembler.

The conventions of the surrounding system concerning register use and calling sequences must be respected by writers of assembly language routines. These conventions for the PDP-11 and Z80/8080 implementations are given here.

First, for the PDP-11, registers R0 and R1 are available for use; any others affected by a routine must be saved on entry and restored on exit. The following call and return sequence is recommended for procedures. It has the advantage that calls can be made directly from assembly language as well as from Pascal.

        .PROC ENTRY, 2

PARAM1  .EQU    6         ;Offset for first parameter
PARAM2  .EQU    4         ;Offset for second pa ranter
RETADDR .EQU    2         ;Offset for return address
OLDR5   .EQU    0         ;Offset for original value of R5
LOCAL1  .EQU   -2         ;Offset for first local
LOCAL2  .EQU   -4         ;Offset for second local

        MOV     R5, -(SP) ;Save contents of R5
        MOV     SP, R5    ;Use R5 to get at locals and parameters
        CLR     -(SP)     ;Reserve and Initialize
        CLR     -(SF)     ;Two local variables
        .
        .
        ;Inside routine
        MOV     PARAM(R5), LOCAL1(R5) ;Sample statement
        .
        .
EXIT:   MOV     R5, SP    ;Cut back to entry SP
        MOV     (SP)+, R5 ;Restore previous R5
        MOV     (SP)+, R0 ;Get return address
        ADD     #NPARAMS, SP ;Discard parameters, number of bytes
        JMP @R0           ;Return to caller

page175 In Z80 assembly language routines, all registers are available for use, and the recommended interface sequence follows: (This code would work for both 8080s and Z80s. Optimizations are possible if the Z80 instructions are available.)

       .PROC   ENTRY, 2
       .PRIVATE RETADDR, LOCAL1, LOCAL2, PARAM1, PARAM2
       ;Reserve static storage for this routine.  Much easier to
       ;reference objects like this rather than relative to
       ;register as on PDP-11
       POP     HL              ;Get return address
       LD      (RETADDR), HL   ;and save it
       POP     HL              ;Get and save PARAM2
       LD      (PARAM2), HL
       POP     HL              ;Get and save PARAM1
       LD      (PARAM1), HL
       .
       .
       LD      HL, (PARAM2)    ;Move PARAM2
       LD      (LOCAL1), HL    ;to LOCAL1
       .
       .
EXIT:  LD      HL, (RETADDR)   ;Get return address
       JP      (HL)
       .END

For assembly language functions (.FUNCs) the sequence is essentially the same, except that:

  1. Two words of zeros are pushed by the compiler after any parameters are put on the stack.
  2. After the stack has been completely cleaned up at the routine exit time, the .FUNC must push the function result on the stack.

Here is an example of an external assembly language procedure, and a program that uses it. This example takes a very primitive approach to interrupt handling (which might still be useful in some applications). There is no provision for handling interrupts from the device where a collected buffer is being written to disk. Support for continuous interrupts would be more complex, involving multiple buffers and exclusion mechanism to assure that buffer switching would occur reliably. The Project intends eventually to provide synchronization capabilities at the Pascal level, so that interrupt handling can be accomplished with greater convenience and safety. page176

         .PROC    DRCOLLECT, 0      ;Name of routine for use by linker.
         .CONST   DRBUFLENG         ;Public constant.
         .PUBLIC  DRBUFFER          ;Public variable.

DRADDR   .EQU     16777O
DRVECT   .EQU     14O
         MOV      #HANDLE, #DRVECT  ;Load address of interrupt
         MOV      #34O, #DRVECT+2   ;handler and set priority.
         MOV      #DRBUFLENG, R0    ;Load R0 with size of buffer.
         MOV      #DRBUFFER, R1     ;Load R1 with address of buffer.
         BIS      #100, @#DRADDR    ;Enable interrupts on DR interface.

LOOP:    TST      R0                ;Exit loop when buffer full.
         BNE      LOOP
         BIC      #100, #DRADDR     ;Disable interrupts.
         RTS      PC                ;Return to PASCAL host program.
HANDLE:  MOV      @#DRADDR+2, (R1)+ ;Load buffer with next word,
         DEC      R0                ;increment R1, decrement R0.
         RTI                        ;Return from interrupt.

Here is the Pascal code it would be called from:

PROGRAM COLLECTDATA;
  CONST
    DRBUFLENG = 256;

  TYPE
    DATABUFFER = ARRAY [1..DRBUFLENG] OF INTEGER;

  VAR
    I: Integer;
    DRBUFFER: DATABUFFER;
    DATAFILE: FILE OF DATABUFFER;

  PROCEDURE DRCOLLECT;
  EXTERNAL;

BEGIN (* of Collect Data *)
  REWRITE(DATAFILE, 'SAMPLE.DATA');
  FOR I := 1 TO 10 DO
    BEGIN
      DRCOLLECT;
      DATAFILE^ := DRBUFFER;
      PUT(DATAFILE)
    END;
  CLOSE(DATAFILE, LOCK);
END.

page177 3.3.2.3. Assembly Language to Assembly Language Linkages

The third way in which separate routines may share data structures and subroutines is by linkage from assembly language to assembly language. This is made possible through the use of the .DEF and .REF pseudo-ops provided in the UCSD assemblers. These generate link information that allows two separately assembled procedures to be L(inked together. One possible use for this will be the linking of separate routines and drivers in constructing new UCSD interpreters.

The following are very abbreviated versions of two assembly language routines which make separate references. They are used externally by the UNIT PSGRAPHICS:

The first routine declares three public variables and declares a .DEF for a label to be referenced by the second routine (Note that this is only a skeleton of the actual MOVETO routine):

        .PROC   MOVETO, 6       ; THE 3 REAL PARAMETERS OCCUPY 6 WORDS

        ; PROCEDURE MOVETO(X, Y, Z: REAL);
        ;
        ; COMPUTES A NEW PSXPOS & PSYPOS FROM PSMATP AND
        ; AN ASSUMED 1.0 AS THE INPUT VECTOR HOMOGENEOUS
        ; COORDINATE...
        ;
        ;  (X Y Z 1) dot PSMATP^ = (X' Y' Z' W')
        ;  PSXPOS := X' / W';
        ;  PSYPOS := Y' / W';

        ; THESE ARE GLOBALS IN THE PASCAL HOST
        .PUBLIC PSXPOS
        .PUBLIC PSYPOS
        .PUBLIC PSMATP

        ; MOVETO ENTRY POINT

        MOV     R5, -(SP)       ; R5 USED AS FRAME POINTER
        MOV     SP, R5
        MOV     #PSMATP, R0     ; R0 IS TOS MATRIX POINTER

; PARAMETER DISPLACEMENTS FROM R5 FRAME POINTER
X       .EQU    14
Y       .EQU    10
Z       .EQU    4
W       .EQU    -4
        ;
        ; COMPUTE W', HOMOGENEOUS COORD
        ; AND LEAVE IT ON STACK
        ;
page178
        ; COMPUTE PSXPOS
        ;
        ; NOW COMPUTE PSYPOS
        ;
        ;
        ; CLEAN UP STACK AND RETURN
        ;
ROUND:  ; ROUND REAL ON STACK TO INTEGER
        ; IF < 0 THEN SUBTRACT 0.5 ELSE
        ; ADD 0.5, THEN TRUNCATE.

        .END

The second routine references the first routine as well as the separately assembled DRAWLINE routine. MOVETO must be linked into LINETO before the routine can be linked in as an external procedure to a PASCAL UNIT or PROGRAM.

        .PROC   LINETO, 6       ; PARAMETERS OCCUPY 6 WORDS

        ; PROCEDURE LINETO(X, Y, Z: REAL);
        ;
        ; DRAWS A LINE FROM THE LAST POINT CONTAINED IN
        ; PSXPOS & PSYPOS TO THE NEW TRANSFORMED POINT
        ; GIVEN BY X, Y and Z...
        ;
        ; SAVEX := PSXPOS;
        ; SAVEY := PSYPOS;
        ; MOVETO(X, Y, Z);
        ; DRAWLINE(JUNK, PSBUFP^, 20, 160 + SAVEX, 120 - SAVEY,
        ;          PSXPOS-SAVEX, SAVEY-PSYPOS, 1);
        ;
        .PUBLIC PSXPOS
        .PUBLIC PSYPOS
        .FUBLIC PSBUFP
        .PRIVATE RANGE

        .REF    MOVETO
        .REF    DRAWLINE

        ;LINETO ENTRY POINT
page179
        MOV     R5, -(SP)
        MOV     SP, R5          ; USE R5 AS STACK FRAME POINTER
SAVEX  .EQU     -2
SAVEY  .EQU     -4
X      .EQU     14
Y      .EQU     10
Z      .EQU     4
       ;
       ; SAVEX := PSXPOS;
       ; SAVEY := PSYPOS;
       ;
       ; MOVEID(X, Y, 2);
       ;
       JSR     PC, s@#MOVETO
       ;
       ; DRAWLINE(...);
       ;
       JSR     PC, @#DRAWLINE
       ;
       ; ALL DONE... RETURN
       ;
       JMP     @R0

       .END

For examples and more information see section 1.9 Assembler.
page180


This page last regenerated Sun Jul 25 01:09:12 2010.