Lola RISC FPGA

Lola was designed as a simple, easily learnable hardware description language for describing synchronous, digital circuits. In addition to its use in a digital design course for second year computer science students at ETH Zürich, the Institute for Computer Systems uses it as a hardware description language for describing hardware designs in general and coprocessor applications in particular.
The purpose of Lola is to statically describe the structure and functionality of hardware components and of the connections between them. A Lola text is composed of declarations and statements. It describes the hardware on the gate level in the form of signal assignments. Signals are combined using operators and assigned to other signals. Signals and the respective assignments can be grouped together into types. An instance of a type is a hardware component. Types can be composed of instances of other types, thereby supporting a hierarchical design style and they can be generic (e.g. parametrizable with the word-width of a circuit).

The Lola System is a toolbox consisting of various modules whose commands serve to specify, implement, and test digital circuits. These notes explain its structure to the user of Lola and to the implementer of additional tools. The system’s base is a module containing the definition of the central data structure used to describe digital circuits. Its name is LSB (Lola System Base). Typically, such a data structure is generated from a Lola text by the compiler, and thereafter used as argument for further processing steps, such as simplification, analysis, comparison, simulation, and layout generation. Fig. 1 gives an overview of the described components and their interdependence.

Lola-2: A Logic Description Language, Language description

Lola-2: Translating from Lola to Verilog

Tools for Digital Circuit Design using FPGAs
H Eberle and S. Gehring and S. Ludwig and N.Wirth,  1994
This collection of five papers describes concept and facilities of a  system to aid in the design of digital circuits. It is being used in classes and laboratories for circuit design, and also for the development of prototype circuits in research projects. The collection comprises the report on the Lola language for specifying digital circuits, an introduction to field programmable gate arrays (FPGA) and the Atmel 6000 architecture, the user manual of the CL layout editor, the user manual of the CL design checker, and the description of two FPGA extension boards for Ceres-3.

A Laboratory for a Digital Design Course Using FPGAs
Stephan Gehring Stefan Ludwig Niklaus Wirth, 1994
In our digital design laboratory we have replaced the traditional wired circuit modules by workstations equipped with an extension board containing a single FPGA. This hardware is supplemented with a set of software tools consisting of a compiler for the circuit specification language Lola, a graphical layout editor for design entry, and a checker to verify conformity of a layout with its specification in Lola. The new laboratory has been used with considerable success in digital design courses for computer science students. Not only is this solution much cheaper than collections of modules to be wired, but it also allows for more substantial and challenging exercises.

Lola Compiler for Project Oberon, 2013 Edition
LSS.Mod
LSB.Mod
LSP.Mod
LSC.Mod
LSV.Mod
SmallPrograms.Lola

Lola Definition of RISC5 Computer
RISC5.Lola
LeftShifter.Lola
RightShifter.Lola
Multiplier.Lola
Divider.Lola
FPAdder.Lola
FPMultiplier.Lola
FPDivider.Lola
RISC5Top.Lola
PS2.Lola
MouseP.Lola
RS232R.Lola
RS232T.Lola
SPI.Lola
VID.Lola
DCMX3.v

FPGA-related Work

Hardware Design with Field Programmable Gate Arrays (FPGAs), 1990-1999
Similarity and difference between hardware and software design always had intreagued Wirth as a topic. With the emergence of programmable logic devices, the gap between the two fields narrowed. A project to familiarize a team with the new possibilities was established, and research in design methods using the new devices was started. It led to a set of design tools, including a specification language (Debora, B. Heeb), its compiler with several “back ends” for printed circuits boards, PLDs, and FPGAs. The usefulness of these tools was demonstrated by applying them in the construction of a workstation (Chamaeleon, also Ceres-3). The construction process starting from a textual specification and ending with a board layout and PLD programs was automated, and it required almost no manual intervention.
Wirth realized early, that FPGAs would be particularly useful as a field for experimentation in learning digital circuit design, replacing expensive, pluggable circuit modules by programmable cells. He equipped 25 Ceres-3 workstations in a student laboratory with an FPGA and uses them intensively in a digital design class. Along with a new project in tool design went the formulation of his language Lola, specifically tailored to the need of teaching in a systematic manner, dispensing with the myriads of side-issues inherent in commercial HDLs. The tool set consists of a compiler converting the program (circuit) text into an abstract data structure suitable for further processing, an editor for constructing circuits implemented by the FPGA, i.e. for generating a layout, and a checker comparing the specification in Lola with the layout.

The TRM: Experiments in Computer System Design
The Design of a RISC Architecture and its Implementation with an FPGA
– [RISC0.v]
– [RISC0Top.v]
– [PROM.v]
– [DRAM.v]
– [Multiplier.v]
– [Multiplier1.v]
– [Divider.v]
– [RISC0.ucf]
– [RS232R.v]
– [RS232T.v]
StandalonePrograms.Mod
RISC Architecture
Three Counters

PICL

The Language PICL and its Implementation, Niklaus Wirth, 20. Sept. 2007

PICL is a small, experimental language for the PIC single-chip microcomputer. The class of computers which PIC represents is characterized by a wordlength of 8, a small set of simple instructions, a small memory of at most 1K cells for data and equally much for the program, and by integrated ports for input and output. They are typically used for small programs for control or data acquisition systems, also called embedded systems. Their programs are mostly permanent and do not change.
All these factors call for programming with utmost economy. The general belief is that therefore programming in a high-level language is out of the question. Engineers wish to be in total control of a program, and therefore shy away from complex languages and compiler generating code that often is unpredictable and/or obscure.
We much sympathize with this reservation and precaution, particularly in view of the overwhelming size and complexity of common languages and their compilers. We therefore decided to investigate, whether or not a language could be designed in such a way that the reservations would be unjustified, and the language would indeed be beneficial for programmers even of tiny systems.
We chose the PIC processor, because it is widely used, features the typical limitations of such single-chip systems, and seems to have been designed without consideration of high-level language application. The experiment therefore appeared as a challenge to both language design and implementation.
The requirements for such a language were that it should be small and regular, structured and not verbose, yet reflecting the characteristics of the underlying processor.

Documents:
A Microcontroller System for Experimentation, description, parts of which are published on this page.
PICL: A Programming Language for the Microcontroller PIC, EBNF
The Language PICL and its Implementation, Code generation.
PICL Scanner, Oberon source
PICL Parser, Code Generator, Oberon source

The Language PICL
The language is concisely defined in a separate report. Here we merely point out its particular characteristics which distinguish it from conventional languages. Like conventional languages, however, it consist of constant, variable, and procedure declarations, followed by statements of various forms. The simplest forms, again like in conventional languages, are the assignment and the procedure call. Assignments consist of a destination variable and an expression. The latter is restricted to be a variable, a constant, or an operator and its operand pair. No concatenation of operations and no parentheses are provided. This is in due consideration of the PIC’s simple facilities and ALU architecture. Examples can be found in the section on code patterns below. Conditional and repetitive statements are given the modern forms suggested by E. W. Dijkstra. They may appear as somewhat cryptic. However, given the small sizes of programs, this seemed to be appropriate.

Conditional statements have the form shown at the left and explained in terms of conventional notation to the right.

[cond -> StatSeq]                     IF cond THEN Statseq END
[cond -> StatSeq0|* StatSeq1 ]        IF cond THEN Statseq0 ELSE StatSeq1 END
[cond0 -> StatSeq0|cond1 -> StatSeq1] IF cond0 THEN Statseq0 ELSIF cond1 THEN StatSeq1END

Repetitive statements have the form:

{cond -> StatSeq}                     WHILE cond DO Statseq END
{cond0 -> StatSeq0|cond1 -> StatSeq1} WHILE cond0 DO Statseq0 ELSIF cond1 DO StatSeq1END

There is also the special case mirroring a restricted form of for statement. Details will be
explained in the section on code patterns below.

{| ident, xpression -> StatSeq}

The PICL Compiler
The compiler consists of two modules, the scanner, and the parser and code generator. The scanner recognizes symbols in the source text. The parser uses the straight-forward method of syntax analysis by recursive descent. It maintains a linear list of declared identifiers for constants, variables, and procedures.

Example

MODULE RepeatStat;
  INT x, y;
BEGIN
  REPEAT x := x + 10; y := y - 1 UNTIL y = 0;
  REPEAT DEC y UNTIL y = 0
END RepeatStat.

0 0000300A MOVLW 10
1 0000078C ADDWF 1 12 x := x + 10
2 00003001 MOVLW 1
3 0000028D SUBWF 1 13
4 0000080D MOVFW 0 13 y := y - 1
5 00001D03 BTFSS 2 3 = 0 ?
6 00002800 GOTO 0
7 00000B8D DECFSZ 1 13 y := y – 1; = 0?
8 00002807 GOTO 7

Example

The following procedures serve for sending and receiving a byte. Transmission occurs over a 3-wire connection, using the conventional hand-shake protocol. Port A.3 is an output. It serves for signaling a request to receive a bit. Port B.6 is an input and serves for transmittithe data. B.7 is usually in the receiving mode and switched to output only when a byte is to be sent. In the idle state, both request and acknowledge signals are high (1).

PROCEDURE Send(INT x);
  INT n;
BEGIN ?B.6;                     wait for ack = 1
  !S.5; !~B.7; !~S.5; n := 8;   switch B.7 to output
  REPEAT 
    IFx.0 -> !B.7 ELSE !~B.7 END; apply data
    !~A.3; issue request
    ?~B.6; wait for ack
    !A.3; ROR x; reset req, shift data
    ?B.6; DEC n wait for ack reset
  UNTIL n = 0;
  !S.5; !B.7;!~S.5 reset B.7 to input
END Send;

PROCEDURE Receive;
  INT n;
BEGIN d := 0; n := 8; result to global vaiable d
  REPEAT
    ?~B.6; ROR d;     wait for req
    IF B.7 THEN !d.7 ELSE !~d.7 END ; sense data
    !~A.3;           issue ack
    ?B.6;            wait for req reset
    !A.3; DEC n      reset ack
  UNTIL n = 0
END Receive;

Another version of the same procedures also uses three lines. But it is asymmetric: There is a master and a slave. The clock is always delivered by the master on B.6 independent of the direction of the data transmission on A3 and B7.

When sending, the data is applied to A.3, when receiving, the data is on B.7. The advantage of this scheme is that no line ever switches its direction, the disadvantage is its dependence on the relative speeds of the two partners. The clock must be sufficiently slow so that the slave may follow. There is no acknowledgement.

Master                              Slave
PROCEDURE Send(INT x);              PROCEDURE Receive;
  INT n;                              INT n;
BEGIN n := 8;                       BEGIN d := 0; n := 8;  result to global vaiable d
  REPEAT                              REPEAT ?~B.6; !>d;   wait for clock low
    IF x.0 THEN !A.3 ELSE !~A.3 END;    IF B.7 THEN !d.7 ELSE ~d.7 END; sense data
    !~B.6; !>x; !B.6; DEC n             ?B.6; DEC n        wait for clock high
  UNTIL n = 0                         UNTIL n = 0
END Send;                           END Receive;

PROCEDURE Receive;                  PROCEDURE Send(INT x);
  INT n;                              INT n;
BEGIN d := 0; n := 8;               BEGIN n := 8;
  REPEAT !~B.6; ROR d;                REPEAT ?~B.6;        wait for clock low
    IF B.7 THEN !d.7 ELSE ~d.7 END;     IF x.0 THEN !A.3 ELSE !~A.3 END; apply data
    !B.6; DEC n                         ROR x ?B.6; DEC n  wait for clock high
  UNTIL n = 0                         UNTIL n = 0
END Receive;                        END Send;

Conclusions
The motivation behind this experiment in language design and implementation had been thequestion: Are high-level languages truly inappropriate for very small computers? The answer is: Not really, if the language is designed in consideration of the stringent limitations. I justify my answer out of the experience made in using the language for some small sample programs. The corresponding assembler code is rather long, and it is not readily understandable. Convincing oneself of its correctness is rather tedious (and itself error-prone). In the new notation, it is not easy either, but definitely easier due to the structure of the text.
In order to let the regularity of this notation stand out as its main characteristic, completeness was sacrificed, that is, a few of the PIC’s facilities were left out. For example, indirect addressing, or adding multiple-byte values (adding with carry). Corresponding constructs can easily be added.
One might complain that this notation is rather cryptic too, almost like assembler code. However, the command (!) and query (?) facilities are compact and useful, not just cryptic. Programs for computers with 64 bytes of data and 2K of program storage are inherently short; their descriptions should therefore not be longwinded. After my initial doubts, the new notation appears as a definite improvement over conventional assembler code.
The compiler was written in the language Oberon. It consists of a scanner and a parser module of 2 and 4 pages of source code respectively (including the routines for loading and verifying the generated code into the PIC’s ROM). The parser uses the time-honored principle of top-down, recursive descent. Parsing and code generation occur in a single pass.

post

EULER

Euler is a programming language created by Niklaus Wirth and Helmut Weber, conceived as an extension and generalization of ALGOL 60. The designers’ goal was to create a language which was simpler, and yet more flexible, than ALGOL 60 that was a useful programming language processed with reasonable efficiency that can be defined with rigorous formality. Available sources indicate that Euler was operational by 1965.

Euler employs a general type concept. In Euler, arrays, procedures, and switches are not quantities which are declared and named by identifiers: they are not (as opposed to ALGOL) quantities which are on the same level as variables, rather, these quantities are on the level of numeric and boolean constants. Thus, besides the traditional numeric and logical constants, Euler introduces the following additional types:

  • reference
  • label
  • symbol
  • list (array)
  • procedure
  • undefined

All constants can be assigned to variables, which have the same form as in ALGOL, but for which no fixed types are specified: Euler is a dynamically typed programming language. Furthermore, a procedure can produce a value of any type when executed, and this type can vary from one call of the procedure to the next. Similarly, the elements of a list can have values of any type and these can be different from element to element within the list. So, when the list elements are labels, a switch is obtained. If the elements are procedures, a procedure list is obtained (which is not available in ALGOL 60). If the elements are lists themselves, then a general tree structure is obtained. Euler provides general type-test and type-conversion operators.

Sample program

BEGIN NEW FOR; NEW MAKE; NEW T; NEW A;
FOR ~ LQ FORMAL CV; FORMAL LB; FORMAL STEP; FORMAL UB; FORMAL S;
BEGIN
   LABEL L; LABEL K;
   CV ~ LB;
   K:  IF CV { UB THEN S ELSE GOTO L;
   CV ~ CV + STEP;
   GOTO K;
   L: 0
END RQ;

MAKE ~ LQ FORMAL B; FORMAL X;
BEGIN  NEW T; NEW I; NEW F; NEW L;
   L ~ B; T ~ LIST L[1];
   F ~ IF LENGTH L ! 1 THEN MAKE(TAIL L, X) ELSE X;
   FOR (@I, 1, 1, L[1], LQ T[I] ~ F RQ);
   T
END RQ;

   A ~ ();
   FOR (@T, 1, 1, 4, LQ BEGIN A ~ A & (T); OUT MAKE(@A,T) END RQ)
END $
DUMP

Downloads:

EULER Formal Definition, Niklaus Wirth
Source of EULER, 1965
Syntax Processor, Nikluas Wirth, 1964
PDP10 EULER handbook
EULER An Experiment in Language Definiton, Thomas W. Cristopher

See also for an Icon implementation of an Euler compiler/interpreter

Grammar

        PROGRAM
        BLOCK
        BLOKHEAD
        BLOKBODY
        LABDEF
        STAT
        STAT-
        EXPR
        EXPR-
        IFCLAUSE
        TRUEPART
        CATENA
        DISJ
        DISJHEAD
        CONJ
        CONJ-
        CONJHEAD
        NEGATION
        RELATION
        CHOICE
        CHOICE-
        SUM
        SUM-
        TERM
        TERM-
        FACTOR
        FACTOR-
        PRIMARY
        PROCDEF
        PROCHEAD
        LIST*
        LISTHEAD
        REFERENC
        NUMBER
        REAL*
        INTEGER*
        INTEGER-
        DIGIT
        LOGVAL
        VAR
        VAR-
        VARDECL
        FORDECL
        LABDECL
*
        0
        1
        2
        3
        4
        5
        6
        7
        8
        9
        ,
        .
        ;
        :
        @
        NEW
        FORMAL
        LABEL
        IDENT*
        [
        ]
        BEGIN
        END
        (
        )
        LQ
        RQ
        GOTO
        OUT
        ~
        IF
        THEN
        ELSE
        &
        OR
        AND
        NOT
        =
        !
        <
        {
        }
        >
        MIN
        MAX
        +
        -
        |
        /
        %
        MOD
        *
        ABS
        LENGTH
        INTEGER
        REAL
        LOGICAL
        LIST
        TAIL
        IN
        ISB
        ISN
        ISR
        ISL
        ISLI
        ISY
        ISP
        ISU
        SYMBOL*
        UNDEFINE
        TEN
        #
        TRUE
        FALSE
        $
*
 VARDECL           NEW IDENT*                                                001
 FORDECL           FORMAL IDENT*                                             002
 LABDECL           LABEL IDENT*                                              003
 VAR-              IDENT*                                                    004
 VAR-              VAR- [ EXPR ]                                             005
 VAR-              VAR- .                                                    006
 VAR               VAR-                                                      007
 LOGVAL            TRUE                                                      010
 LOGVAL            FALSE                                                     011
 DIGIT             0                                                         012
 DIGIT             1                                                         013
 DIGIT             2                                                         014
 DIGIT             3                                                         015
 DIGIT             4                                                         016
 DIGIT             5                                                         017
 DIGIT             6                                                         020
 DIGIT             7                                                         021
 DIGIT             8                                                         022
 DIGIT             9                                                         023
 INTEGER-          DIGIT                                                     024
 INTEGER-          INTEGER- DIGIT                                            025
 INTEGER*          INTEGER-                                                  026
 REAL*             INTEGER* . INTEGER*                                       027
 REAL*             INTEGER*                                                  030
 NUMBER            REAL*                                                     031
 NUMBER            REAL* TEN INTEGER*                                        032
 NUMBER            REAL* TEN # INTEGER*                                      033
 NUMBER            TEN INTEGER*                                              034
 NUMBER            TEN # INTEGER*                                            035
 REFERENC          @ VAR                                                     036
 LISTHEAD          LISTHEAD EXPR ,                                           037
 LISTHEAD          (                                                         040
 LIST*             LISTHEAD EXPR )                                           041
 LIST*             LISTHEAD )                                                042
 PROCHEAD          PROCHEAD FORDECL ;                                        043
 PROCHEAD          LQ                                                        044
 PROCDEF           PROCHEAD EXPR RQ                                          045
 PRIMARY           VAR                                                       046
 PRIMARY           VAR LIST*                                                 047
 PRIMARY           LOGVAL                                                    050
 PRIMARY           NUMBER                                                    051
 PRIMARY           SYMBOL*                                                   052
 PRIMARY           REFERENC                                                  053
 PRIMARY           LIST*                                                     054
 PRIMARY           TAIL PRIMARY                                              055
 PRIMARY           PROCDEF                                                   056
 PRIMARY           UNDEFINE                                                  057
 PRIMARY           [ EXPR ]                                                  060
 PRIMARY           IN                                                        061
 PRIMARY           ISB VAR                                                   062
 PRIMARY           ISN VAR                                                   063
 PRIMARY           ISR VAR                                                   064
 PRIMARY           ISL VAR                                                   065
 PRIMARY           ISLI VAR                                                  066
 PRIMARY           ISY VAR                                                   067
 PRIMARY           ISP VAR                                                   070
 PRIMARY           ISU VAR                                                   071
 PRIMARY           ABS PRIMARY                                               072
 PRIMARY           LENGTH VAR                                                073
 PRIMARY           INTEGER PRIMARY                                           074
 PRIMARY           REAL PRIMARY                                              075
 PRIMARY           LOGICAL PRIMARY                                           076
 PRIMARY           LIST PRIMARY                                              077
 FACTOR-           PRIMARY                                                   100
 FACTOR-           FACTOR- * PRIMARY                                         101
 FACTOR            FACTOR-                                                   102
 TERM-             FACTOR                                                    103
 TERM-             TERM- | FACTOR                                            104
 TERM-             TERM- / FACTOR                                            105
 TERM-             TERM- % FACTOR                                            106
 TERM-             TERM- MOD FACTOR                                          107
 TERM              TERM-                                                     110
 SUM-              TERM                                                      111
 SUM-              + TERM                                                    112
 SUM-              - TERM                                                    113
 SUM-              SUM- + TERM                                               114
 SUM-              SUM- - TERM                                               115
 SUM               SUM-                                                      116
 CHOICE-           SUM                                                       117
 CHOICE-           CHOICE- MIN SUM                                           120
 CHOICE-           CHOICE- MAX SUM                                           121
 CHOICE            CHOICE-                                                   122
 RELATION          CHOICE                                                    123
 RELATION          CHOICE = CHOICE                                           124
 RELATION          CHOICE ! CHOICE                                           125
 RELATION          CHOICE < CHOICE                                           126
 RELATION          CHOICE { CHOICE                                           127
 RELATION          CHOICE } CHOICE                                           130
 RELATION          CHOICE > CHOICE                                           131
 NEGATION          RELATION                                                  132
 NEGATION          NOT RELATION                                              133
 CONJHEAD          NEGATION AND                                              134
 CONJ-             CONJHEAD CONJ-                                            135
 CONJ-             NEGATION                                                  136
 CONJ              CONJ-                                                     137
 DISJHEAD          CONJ OR                                                   140
 DISJ              DISJHEAD DISJ                                             141
 DISJ              CONJ                                                      142
 CATENA            CATENA & PRIMARY                                          143
 CATENA            DISJ                                                      144
 TRUEPART          EXPR ELSE                                                 145
 IFCLAUSE          IF EXPR THEN                                              146
 EXPR-             BLOCK                                                     147
 EXPR-             IFCLAUSE TRUEPART EXPR-                                   150
 EXPR-             VAR ~ EXPR-                                               151
 EXPR-             GOTO PRIMARY                                              152
 EXPR-             OUT EXPR-                                                 153
 EXPR-             CATENA                                                    154
 EXPR              EXPR-                                                     155
 STAT-             LABDEF STAT-                                              156
 STAT-             EXPR                                                      157
 STAT              STAT-                                                     160
 LABDEF            IDENT* :                                                  161
 BLOKHEAD          BEGIN                                                     162
 BLOKHEAD          BLOKHEAD VARDECL ;                                        163
 BLOKHEAD          BLOKHEAD LABDECL ;                                        164
 BLOKBODY          BLOKHEAD                                                  165
 BLOKBODY          BLOKBODY STAT ;                                           166
 BLOCK             BLOKBODY STAT END                                         167
 PROGRAM           $ BLOCK $                                                 170
*

PL/360

PL360 (or PL/360) is a system programming language designed by Niklaus Wirth and written by Niklaus Wirth, Joseph W. Wells, Jr., and Edwin Satterthwaite, Jr. for the IBM System/360 computer at Stanford University. A description of PL360 was published in early 1968.

Niklaus Wirth in 1966 wanted to have a compiler written for his new Algol W language and the choices of programming language with which to write the compiler were FORTRAN and assembler language Wirth set aside the Algol W project temporarily and developed a programming language which was specifically designed for writing system-level software on an IBM 360 system. This systems programming language, the very first systems programming language other than assembler language, came to be known as PL360 (the name is sometimes written as PL/360 although it seems pretty clear that Wirth called it PL360 – I’m not 100% sure of this so please correct me if I’m wrong).

In practical terms, PL360 isn’t much more than an assembly language dressed up in fancy clothes (strictly speaking, it’s actually called a structured assembly language). Although a reasonable set of operators are defined, expression evaluation is strictly left to right and the programmer is responsible for managing the use of the machine registers and most aspects of memory management. In fact, it really wasn’t possible to write a PL360 program without quite intimate knowledge of the System/360 architecture.

The result is a language which requires considerable care and attention on the part of the programmer. Although friendlier than an actual assembler language, the inattentive programmer is provided with plenty of potential learning opportunities (i.e. pitfalls). For example, consider the following two statements:

R1 := R1 + R2;
R1 := R2 + R1;

Although these may appear to be equivalent, they are actually VERY different. The first statement adds machine register R2 to the contents of register R1 and stores the result in R1 (i.e. it adds R1 and R2 together and stores the result in R1). The second statement is actually equivalent to:
R1 := R2; R1 := R1 + R1;
i.e. it effectively computes 2*R2 and stores the result in R1.
PL360 ends up looking pretty sad if it is considered as a high-level programming language. On the other hand, if viewed as a mid to low-level language (i.e. an assembler language in fancy clothes) then it was actually quite respectable for the era. In fact, since the goal was to create a language which could be used to do systems programming, the necessity to understand the underlying architecture in detail was arguably a language feature rather than a failing.

By 1968, a compiler had been written for the PL360 language and Wirth was able to get on with the task of getting an Algol W compiler written. The ability to write systems programming level software using reasonably conventional looking statements and expressions turned out to be quite useful and PL360 went on to be used for a variety of projects.

PL/360 is a one pass compiler with a syntax similar to Algol that provides facilities for specifying exact machine language instructions and registers similar to assembly language, but also provides features commonly found in high-level languages, such as complex arithmetic expressions and control structures. Wirth used PL360 to create Algol W.

Data types are:

  • Byte or character – a single byte.
  • Short integer – 2 bytes, interpreted as an integer in two’s complement binary notation.
  • Integer or logical – 4 bytes, interpreted as an integer in two’s complement binary notation.
  • Real – 4 bytes, interpreted as a base-16 short floating-point number.
  • Long real – 8 bytes, interpreted as a base-16 long floating-point number.
  • Registers can contain integer, real, or long real.
    • Individual System/360 instructions can be generated inline using the PL360 “function statement” that defined an instruction by format and operation code. Function arguments were assigned sequentially to fields in the instruction.

      From the CS33 Stanford University Report: A Programming Language for the 36O Computers, Niklaus Wirth, Introduction

      This paper is a preliminary definition of a programming language which is specifically designed for use on IBM 360 computers, and is therefore appropriately called PL36O.
      The intention is to present a programming tool which (a) closely reflects the particular structure of the 36O computer, and (b) is a superior notation to present Assembly Codes with respect to presentation and documentation of algorithms. As a consequence of (a), it enables a programmer to design programs mentioning explicitly features of this machine in a degree impossible in “higher level” languages.
      It is also felt that a highly structured language is most appropriate (a) to promote the intelligibility of texts for the human user and (b) to encourage this user to properly structure his algorithms not on paper only, but in his mind as well. The language is therefore a phrase structure language containing many constructions which quite obviously correspond to a single 36O machine instruction (cf, [l]).
      Moreover, it is hoped that through certain conventions (not mentioned in this preliminary paper) concerning the use of general registers as base address registers, programs written in PL36O can be efficiently run under a time-sharing monitor without requiring the presence of additional sophisticated relocation hardware (Model 67)°

      Presently, a compiler for PL36O is available on the B55OO computer
      This compiler is mainly intended to serve as a temporary tool for a bootstrapping process: The compiler is being rewritten in its own language and then becomes automatically available on the 36O computer. Indeed, the primary purpose of this project is to obtain a convenient tool for the development of other compilers (in particular ALGOL X) and monitor systems, where a considerable degree of machine-orientation and -dependence is desirable, but where an adequate standard of program documentation is of no less importance.

      Documents for download:

      A Programming Language for the 360 Computers, Niklaus Wirth, Stanford University CS33, 1965
      STAN-CS-71-215 PL360 Revised A Programming Language For The IBM 360 May71
      A Programming Language for the 360 Computers, M, Malcolm, revised May 1972
      PL360 Reference Manual PDF, text version
      PL360 textbook (HTML)

ALGOL W

During his stay at Stanford University Wirth designed ALGOL W, his first widely distributed structured language. He first implemented PL/360 , the structured assembler for the IBM 360 architecture, to have a development system for ALGOL-W.

ALGOL W is a programming language, based on a proposal for ALGOL X by Niklaus Wirth and Tony Hoare as a successor to ALGOL 60 in the International Federation for Information Processing (IFIP) IFIP Working Group 2.1. When the committee decided that the proposal was not a sufficient advance over ALGOL 60, the proposal was published as A contribution to the development of ALGOL.
After making small modifications to the language Wirth supervised a high quality implementation for the IBM/360 at Stanford University that was widely distributed.

It represented a relatively conservative modification of ALGOL 60, adding string, bitstring, complex number and reference to record datatypes and call-by-result passing of parameters, introducing the while statement, replacing switch with the case statement, and generally tightening up the language. The implementation was written in PL/360, an ALGOL-like assembly language designed by Wirth. The implementation includes influential debugging and profiling abilities.

ALGOL W’s syntax is built on a subset of the EBCDIC character set. In ALGOL 60 reserved words are distinct lexical items, but in ALGOL W they are merely sequences of characters, and do not need to be stropped. Reserved words and identifiers are separated by spaces. In these ways ALGOL W’s syntax resembles that of Pascal and later languages.

The Algol W Language Description (see below)defines Algol W in an affix grammar that resembles BNF. This grammar was a precursor of the Van Wijngaarden grammar.

Much of Algol W’s semantics is defined grammatically: Identifiers are distinguished by their definition within the current scope. For example, a ⟨procedure identifier⟩ is an identifier that has been defined by a procedure declaration, a ⟨label identifier⟩ is an identifier that is being used as a goto label. The types of variables and expressions are represented by affixes. For example ⟨τ function identifier⟩ is the syntactic entity for a function that returns a value of type τ, if an identifier has been declared as an integer function in the current scope then that is expanded to ⟨integer function identifier⟩. Type errors are grammatical errors. For example “⟨integer expression⟩ / ⟨integer expression⟩” and “⟨real expression⟩ / ⟨real expression⟩” are valid but distinct syntactic entities that represent expressions, but “⟨real expression⟩ DIV ⟨integer expression⟩” (i.e. integer division performed on a floating-point value) is an invalid syntactic entity.

The major part of ALGOL W, amounting to approximately 2700 cards (see listing below), was written in Wirth’s PL360. An interface module for the IBM operating system in use (OS, DOS, MTS, ORVYL) was written in IBM assembler, amounting to fewer than 250 cards. In an OS environment on a 360/67 with spooled input and output files, the compiler will recompile itself in about 25 seconds. The compiler is approximately 2700 card images. Thus, when the OS scheduler time is subtracted from the execution time given above, it is seen that the compiler runs at a speed in excess of 100 cards per second (for dense code). In a DOS environment on a 360/30, the compiler is limited only by the speed of the card reader. The compiler has successfully recompiled itself on a 64K 360/30 at a rate of 1200 cards per minute (the speed of the card reader).

Documents for download:

ALGOL W Reference Manual, Niklaus Wirth, June 1972
ALGOL W Reference Manual, February 1972
ALGOL-W Listing November 1969
Algol W Language Description by Henry Bauer Sheldon Becker Susan L. Graham Edwin Satterthwaite Richard L. Sites June 1972
ALGOL W Language description, Henry R. Bauer, Sheldon Becker, Susan L. Graham
MTS ALGOL-W 1980

If you want to work with ALGOL-W, there is a recent implementation AWE for Linux (and Windows via CYGWIN) .

From https://everything2.com/title/Algol+W

In the early 1960s, the IFIP Working Group 2.1 committee was created with the mandate to design a language to replace Algol+60. By the time of the regular committee meeting in the fall of 1966, there were three competing proposals on the table. One of the proposals, by Niklaus Wirth, was for a language which was a relatively modest improvement over Algol 60. One of the other proposals, by Van Wijngaarden, was chosen by the committee and was to evolve into Algol 68. As a result of the decision to pursue Van Wijngaarden’s proposal, a number of the committee members, including Wirth and C.A.R. Hoare, abandoned the committee (it was, apparently, a pretty intense meeting). Wirth developed his proposal into an Algol-style language which, eventually, came to be known as Algol W (like Algol 60 before it, the Algol W language’s gramma was formally described using BNF notation). Although less ambitious than Van Wijngaarden’s proposal, Wirth’s language introduced a number of new concepts including:

  • double precision floating point data type
  • complex data type
  • bit string data type
  • dynamic data structures (i.e. structs and pointers to structs)
  • block expressions

When it came time to actually compiler for the language, a decision was made to first develop a systems programming language called PL360 (the only real alternatives were FORTRAN and Assembler). Once a PL360 compiler had been written, it was used (in about 1968) to implement an Algol W compiler on the OS/360 and MTS (Michigan Terminal system) operating systems.

Algol W was reasonably successful as a teaching language although it was rarely if ever used in commercial contexts. By about 1980, Algol W was being replaced by languages like Pascal.

The Algol W language

The following is a brief description of the language as it was defined in 1972.

Basic syntax

Algol W dates back to the days of punched cards. Consequently, the language is defined strictly in terms of upper case. For example, the following is a valid Algol W program

BEGIN
WRITE("Hello world");
END.

but the following is not

begin
write("Hello world");
end.

Like C, statements are terminated by a semi-colon and whitespace can appear anywhere except within an identifier or reserved word.

The reserved words are
ABS
ALGOL (used when writing separately compiled ‘modules’)
AND
ARRAY
ASSERT
BEGIN
BITS
CASE
COMMENT
complex number COMPLEX
DIV
DO
ELSE
EEND
FALSE
FOR
FORTRAN (used to call a separately compiled FORTRAN routine)
GO TO
GOTO
IF
INTEGER
IS
LOGICAL” LOGICAL
LONG
NULL
OF
OR
PROCEDURE
REAL
RECORD
REFERENCE
REM
RESULT
SHL
SHORT
SHR
STEP
STRING
THEN
TRUE
UNTIL
VALUE
WHILE

Data types

The following is the list of data types supported by the language. Example declarations and constants are provided for each data type.

  • INTEGER (32-bit signed integer)
    INTEGER I, J;
    10
    1232
    
  • REAL (32-bit floating point)
    REAL W, X;
    10.
    10.0
    0.1
    .1
    
  • LONG REAL (64-bit floating point)
    LONG REAL Y, Z;
    10.L
    10.0L
    0.1L
    .1L
    10L
    
  • COMPLEX (32-bit complex – i.e. a pair of 32-bit floating point values)
    COMPLEX A, B;
    10.I
    10.0I
    0.1I
    .1I
    10I
    

    Note that the complex constant only represents the imaginary part of the number. A specification of a complete complex value would involve the addition of a real value with a complex value. e.g. 5.0 + 3I or 7 + 3I (the integer constant 7 would be automatically converted to the real value 7.0 before it was added to the complex constant value 3i).

  • LONG COMPLEX (64-bit complex – i.e. a pair of 64-bit floating point values)
    COMPLEX C, D;
    10.IL 10.0IL 0.1IL .1IL 10IL
    
  • LOGICAL (a boolean value – i.e. either TRUE or FALSE)
    LOGICAL E, F;
    TRUE
    FALSE
    
  • BITS (a 32 element sequence of bits)
    BITS G, H;
    #001248CF
    

    Note that bits constants are represented in hexadecimal. The above constant is equivalent to the binary value 00000000000100100100100011001111.

  • STRING (fixed length string)
    STRING S; STRING(40) T;
    "hello"        a string containing the 5 characters h, e, l, l and o
    """"           a string containing a single "
    

    All strings are fixed length with a minimum length of 1 and a maximum length of 256. If the length isn’t specified in a STRING declaration then it defaults to 16. Also note that there is no backslash convention as is found in many “modern” languages. Use two double quotes in a row if you want to have a single double quote within a string constant.

  • RECORD (essentially a C struct)
    RECORD PERSON( STRING(40) NAME; INTEGER AGE; REAL HEIGHT );
    PERSON( "DANIEL BOULET", 45, 180.3 )
    PERSON
    

    The PERSON( “DANIEL BOULET”, 45, 180.3 ) example defines
    a new PERSON RECORD and initializes all the fields. The second PERSON example creates a new PERSON RECORD with the field
    values uninitialized. Neither of these examples are really constants.

  • REFERENCE (essentially a Java-style pointer – i.e. no pointer-to-pointer or pointer arithmetic operations are supported)
    REFERENCE (PERSON) DANIEL; REFERENCE (PERSON,THING) IT;
    NULL
    
    • a REFERENCE variable can be declared to point at either a single
      RECORD type (e.g. DANIEL above) or a list of alternative record types
      (e.g. IT above).
      If a REFERENCE variable can point at more than one RECORD type then
      the IS operator (see below) can be used to determine which type it
      actually points at.
    • the only REFERENCE constant is the NULL value.

Algol W also supports arrays which can be constructed using any of the other data types. Here are a few example declarations:

INTEGER ARRAY VECTOR(1::10);         COMMENT ten element array of integers;
REAL    ARRAY MATRIX(1::10,1::10);   COMMENT a square 10x10 array of reals;
INTEGER ARRAY RANGE(-10::10);        COMMENT a 21 element array (-10 to +10);
REFERENCE(THING) ARRAY THINGS(1::N); COMMENT an array of references to 
                                             things with a size determined
					     at run-time;

Any of the bounds of an array declaration can be an expression which is evaluated at run-time. If the result is an array in which the lower bound is greater than the upper bound (for any dimension) then the array has no elements – i.e. any attempt to access the array will result in a run-time array bounds error.

Examples for each of the above arrays are:

WRITE( VECTOR(1) );           COMMENT print out first element of VECTOR;
MATRIX(10,1) := MATRIX(1,10); COMMENT copy an element of MATRIX;
RANGE(0) := 0;                COMMENT set the middle element of RANGE to 0;
WRITE(NAME(THINGS(1)));       COMMENT write out the value of the NAME field of the first THING;

Operators and expressions

Algol W supports the usual set of operators although it distinguishes between integer and non-integer division operators.
The operators are:

OR
AND
¬
< <= = ¬= >= > IS
+ -
* / DIV REM
SHL SHR **
LONG SHORT ABS

A few notes are in order:

  • The operators on each line in the above list are of equal precedence (i.e.
    priority) with
    the first line being the lowest precedence and the last line having the
    highest precedence.
  • ¬ is the logical negation operator (equivalent to the C programming language’s ! operator) and ¬= is the inequality comparison operator (equivalent to C’s != operator).
  • the IS operator can be used to determine which RECORD type a REFERENCE variable is pointing at. e.g.
    IF IT IS PERSON THEN
       WRITE("IT is pointing at a PERSON record")
    ELSE
       WRITE("IT is not pointing at a PERSON record");
    
  • DIV and REM are the integer divide and remainder operators (if / is applied to a pair of integer values then the result is a real value).
  • SHL and SHR are the bit-wise shift left and right operators.
  • LONG ‘expands’ REAL and COMPLEX values to LONG REAL and LONG COMPLEX.
    SHORT ‘contracts’ LONG REAL and LONG COMPLEX values to
    REAL and COMPLEX. It’s an error to apply LONG to something which is already LONG or to apply SHORT to something which is not LONG.
  • ABS returns the absolute value of it’s operand.
  • with the exception of the OR and AND operators, the operands of binary operators were evaluated in an unpredictable order. For example, the expression F(X) * G(X) might result in F(X) being called either before or after G(X) gets called. The order would be always the same for a given compilation of a given program but could change if the program was recompiled. Consequently, an operator which combined the result of two function calls which each modified the same global variable could cause unpredictable results.
  • the AND and OR operators are McCarthy operators -i.e. they use what today is often called lazy evaluation: If the left operand of an OR is true then the right operand isn’t evaluated as the result can only be TRUE. If the left operand of an AND is false then the right operand isn’t evaluated as the result can only be FALSE.

Parentheses can, of course, be used to override the operator precedence. Missing from the above list is the unary – and + operators which have higher precendence than any of the binary operators. Missing from this entire writeup is a description of the reasonably large (for the era) set of built-in library routines. Also missing from the above list is a mechanism to access fields of a RECORD. The syntax for this is identical to a function call where the name of the function is the name of the field and the single parameter to the call is the REFERENCE variable. For example,

AGE(DANIEL) := AGE(DANIEL) + 1;

would increment the AGE field of the PERSON record referenced by DANIEL.

An example program

Here’s a very short example program

BEGIN
INTEGER I, J, PRODUCT;
READ(I,J);  COMMENT read two integers from the input device;
PRODUCT := I * J; WRITE("The product is ",PRODUCT);
END.

A few notes are in order

  • The entire program must be enclosed in a BEGIN-END block and the final END must have a period after it.
  • The READ statement is a call to the built-in READ procedure which reads a single input line and assigns successive values to successive parameters (input is free format in this example and additional input lines are read if necessary).
  • Comments are inserted by using the COMMENT reserved word.
  • Everything up to the next semi-colon is ignored

  • Multiple statements can appear on a single line and a statement can span any number of lines.
  • The assignment operator is :=.
  • This allows it to be distinguished from the comparison for equality operator which is =.

  • Lower case letters are allowed within comments and string constants.

Block structured

Like all Algol languages, Algol W is a block structured language. This means that the scope of an identifier is determined by the block within which it is declared. For example, the output of the following program

BEGIN
INTEGER I;
I := 10;
WRITE("I is ",I);
   BEGIN
   INTEGER I;
   I := 20;
   WRITE("this I is ",I);
   END;
WRITE("I is still ",I);
   BEGIN
   I := 30;
   WRITE("I is now ",I);
   END;
WRITE("I's final value is ",I);
END.

would be

I is 10
this I is 20
I is still 10
I is now 30
I's final value is 30

The scope of the I declared on the second line is the entire program except for the first inner block which has a different I declared within it.

Procedures

Algol W has function procedures and proper procedures. A function procedure returns a value and can be used in any context in which an expression can appear. A proper procedure does not return a value. Today, these are generally called functions and procedures respectively. Procedures of either kind can be defined to accept parameters. Here are a pair of examples:

BEGIN
INTEGER P, Q;

PROCEDURE PROC( INTEGER VALUE I, J; INTEGER RESULT PRODUCT );
   BEGIN
   WRITE("call to PROC - I is ",I,", J is ",J,".");
   PRODUCT := I * J;
   END;

INTEGER PROCEDURE FUNC( INTEGER VALUE I, J );
    BEGIN
    WRITE("call to FUNC - I is ",I,", J is ",J,".");
    I * J
    END;

PROC(10, 20, P);
Q := FUNC(10, 20);
END.

The first is a proper procedure called PROC which takes two integer parameters which are initialized based on the first two arguments passed on the call to PROC (i.e. I is initialized to 10 and J is initialized to 20 in this example). It returns a result parameter PRODUCT (i.e. P will be assigned 200 just as the call to PROC returns).
The second is a function procedure called FUNC which takes two integer parameters and returns their product as the value of the procedure (the last thing before the closing END in a function procedure’s body must be an expression which is evaluated to compute the value of the procedure).
Here’s an example of a function procedure that takes no parameters:

BEGIN
INTEGER Q;

REAL PROCEDURE ZERO;
   BEGIN
   0
   END;

Q := ZERO;
END.

This is an expensive (and absurd) way to initialize Q to 0. Short procedures consisting of a single statement can dispense with the BEGIN-END block:

PROCEDURE HELLO;
    WRITE("Hello");

Algol W, like its predecessor Algol 60, also supports the call by name parameter passing mechanism:

BEGIN
INTEGER J;
PROCEDURE BYNAME(INTEGER MAGIC);
   BEGIN
   WRITE("MAGIC is ",MAGIC);
   J := J * 2;
   WRITE("MAGIC is now ",MAGIC);
   END;
J := 10;
BYNAME(J * 3);
END.

A call by name parameter is re-evaluated every time it is used. Consequently, the output of the above program would be:

MAGIC is 30
MAGIC is now 60

The potential for, shall we say, strange program behaviour when using call by name is great enough that the mechanism is rarely used.
A binary operator which combines the value of two function calls, at least one of which modifies a global variable and the other of which relies upon the same global variable, produces unpredictable results. For example, the output of the following program

BEGIN
INTEGER J;
INTEGER PROCEDURE LEFT;
   BEGIN
   J := J + 1;
   J
   END;
INTEGER PROCEDURE RIGHT;
   BEGIN
   J := J * 3;
   J
   END;
J := 2;
WRITE( LEFT * RIGHT );
END.

might be 27 or 42 depending on which of LEFT or RIGHT is called first when the operands of the * operator in the WRITE call are evaluated.
Like all the Algol languages, Algol W supports recursion. Here’s an excellent way to consume vast quantities of CPU time:

INTEGER PROCEDURE ACKERMANN(INTEGER VALUE X, Y);
    IF X = 0 THEN
	Y + 1
    ELSE IF Y = 0 THEN
	ACKERMANN(X - 1, 1)
    ELSE
	ACKERMANN(X - 1, ACKERMANN(X, Y - 1));

If you want to find out if your computer can stay up for a few thousand millennium, call this function with

ACKERMANN(1000,1000)

Block expressions

Although apparently not part of the original language, the 1972 version of Algol W supports block expressions. This is a generalization of how function procedure bodies are written.
It allows the following sort of nonsense to be written:

BEGIN
WRITE("the answer is ",
   BEGIN
   INTEGER X;
   X := 2 * 3;
   X
   END
   * 7
);
END.

In practical terms, block expressions aren’t used very often as they tend to make the program harder to read without adding any real value. Block expressions which modify global variables can also produce unpredictable results:

BEGIN
INTEGER J;
J := 2;
WRITE(
   BEGIN
   J := J + 1;
   J
   END
   *
   BEGIN
   J := J * 3;
   J
   END
);
END.

This program is equivalent to the example given above involving the function procedures LEFT and RIGHT.

Other statements

The IF statement is used to conditionally execute a single statement:

IF I > 10 THEN
   I := I * 2;

An ELSE clause can be included to deal with the alternative case:

IF I > 10 THEN
   I := I * 2
ELSE
   I := I - 3;

Notice that the statement preceding the ELSE isn’t terminated by a semi-colon. The reason is that there is actually only one statement here and it’s terminated by a semi-colon after the 3. If an ELSE clause exists then the statement after the THEN must be a simple statement (e.g. an assignment statement, a call to a proper procedure or a BEGIN-END block). Since an IF statement is not a simple statement, the following is invalid:

IF A < B THEN
    IF X > Y THEN
	X := 2
    ELSE
	Y := 2
ELSE
    Q := 2;

The following is a valid way of expressing what was intended above:

IF A < B THEN
    BEGIN
    IF X > Y THEN
	X := 2
    ELSE
	Y := 2;
    END
ELSE
    Q := 2;

An IF statement without an ELSE clause can have any statement for its body. Consequently, the following is valid:

IF A < B THEN
    IF X > Y THEN
	X := 2
    ELSE
	Y := 2;

as is

IF A < B THEN
    IF X > Y THEN
	X := 2
    ELSE
	IF X < Y THEN
	    X := 3
	ELSE
	    X := 5;

IMPORTANT: don’t let the indentation fool you.
This

IF A < B THEN IF X > Y THEN
X := 2
ELSE
IF X < Y THEN X := 3 ELSE X := 5;

is identical in all respects (except meaningless indentation) to the previous example! Just to be clear, the last two examples are also equivalent to this:

IF A < B THEN
    BEGIN
    IF X > Y THEN
	X := 2
    ELSE
	BEGIN
	IF X < Y THEN
	    X := 3
	ELSE
	    X := 5;
	END;
    END;

If the body of the THEN part or the ELSE part needs to be more than a single statement then a BEGIN-END block is required:

IF I > 10 THEN
   BEGIN
   I := I * 2;
   J := 2;
   END
ELSE
   BEGIN
   I := I - 3;
   J := 5;
   END;

The notion of block expressions is also available in what is called a conditional expression:

J :=
IF I > 10 THEN
   BEGIN
   I := I * 2;
   2
   END
ELSE
   BEGIN
   I := I - 3;
   5
   END;

This is functionally equivalent to the previous IF-THEN-ELSE example.

Here's an IF statement that takes advantage of the fact that the AND and OR operators are McCarthy-style (i.e. lazy evaluation like the C || and && operators):

IF PTR ¬= NULL AND XVAR(PTR) > 10 THEN
   BEGIN
   WRITE("XVAR is too big");
   ASSERT FALSE;
   END;

This also demonstrates the ASSERT statement which can be used to abort the program if an assumption fails. A shorter but more meaningful example of ASSERT would be:

ASSERT NOT ( PTR = NULL OR XVAR(PTR) <= 10 );

The program will terminate with a run-time assertion-failure if the logical (i.e. boolean) expression on the ASSERT statement is false. The first example is, arguably, better as the user gets a better error message prior to termination. The FOR statement is used when the number of iterations required is known prior to the start of the first iteration. For example, the following would print out all the integers from 1 to 10:

FOR I := 1 UNTIL 10 DO
   WRITE(I);

FOR loops can go backwards as well:

FOR I := 10 STEP -1 UNTIL 1 DO
   WRITE(I);

This gives you the integers from 10 down to 1. Once the direction has been determined (i.e. the sign of the STEP), the loop starts at the initial value and iterates until the termination value. If the initial value is after the termination value in an upwards loop or before the termination value in a downwards loop then the loop body is not executed. The initial, step and termination values are computed exactly once (i.e. changing the variables involved in their computation once the loop starts has no effect on how many times the loop goes around or what value is assigned to the iterating variable on each iteration).

The iterating variable, I in the above example, is implicitly declared by the FOR statement as an INTEGER (i.e. it exists only for the duration of the FOR loop) and it may not be assigned to within the body of the loop. There is no exact equivalent to the C language's break or continue statements although the language supports go to statements for the truly foolish (or very brave). There is also nothing equivalent to C's return statement.

The WHILE loop is used when the FOR statement isn't suitable (e.g. number
of iterations not known in advance or irregular step size).
A single example should suffice:

J := 1;
WHILE A(J) < 0 AND J <= 10 DO
   BEGIN
   J := J + 1;
   IF J = 3 THEN
      J := J + 1;
   END;

The body of a FOR or a WHILE statement can be any valid single statement (use a BEGIN-END block if a multi-statement body is required).

The CASE statement is somewhat analogous to the C language's switch statement although it operates rather differently. Here's an example:

CASE I - 1 OF
    BEGIN
    J := 2;
    J := 3;
    BEGIN J := 5; K := 8; END;
    K := J
    END;

The case selector expression (i.e. I - 1 in this example) is used to select a single statement within the body of the BEGIN-END block which is then executed. The value of the expression determines the ordinal number of the statement to execute. i.e. if I - 1 is 1 then the J := 2 statement is executed, if I - 1 is 2 then the J := 3 statement is executed, etc.
Note the use of an inner BEGIN-END block which allows the third statement to actually consists of two statements. It is a fatal run-time error if the value of the case selector expression is less than 1 or greater than the number of statements in the BEGIN-END block.

P2 Pascal Compiler

As the name implies, P2 is the second version of the Portable Pascal compiler. It seems to be the first one widely distributed and also the first one to have surviving sources.

One of the distributions of P2 went to California, UCSD. And that version evolved into the UCSD Pascal system.

Mark Rustad took the P2 source, stripped it (no reals e.g.) and changed the p-code to a compact bytecode in Pascal-M.

 (*********************************************************         
  *                                                       *         
  *                                                       *         
  *     STEP-WISE DEVELOPMENT OF A PASCAL COMPILER        *         
  *     ******************************************        *         
  *                                                       *         
  *                                                       *         
  *     STEP 5:   SYNTAX ANALYSIS INCLUDING ERROR         *         
  *               HANDLING; CHECKS BASED ON DECLARA-      *         
  *     10/7/73   TIONS; ADDRESS AND CODE GENERATION      *         
  *               FOR A HYPOTHETICAL STACK COMPUTER       *         
  *                                                       *         
  *                                                       *         
  *     AUTHOR:   URS AMMANN                              *         
  *               FACHGRUPPE COMPUTERWISSENSCHAFTEN       *         
  *               EIDG. TECHNISCHE HOCHSCHULE             *         
  *               CH-8006 ZUERICH                         *         
  *                                                       *         
  *                                                       *         
  *                                                       *         
  *     MODIFICATION OF STEP 5 OF PASCAL COMPILER         *         
  *     *****************************************         *         
  *                                                       *         
  *     THE COMPILER IS NOW WRITTEN IN A SUBSET OF        *         
  *     STANDARD PASCAL  -  AS DEFINED IN THE NEW         *         
  *     MANUAL BY K. JENSEN AND N. WIRTH  - AND IT        *         
  *     PROCESSES EXACTLY THIS SUBSET.                    *         
  *                                                       *         
  *     AUTHOR OF CHANGES:   KESAV NORI                   *         
  *                          COMPUTER GROUP               *         
  *                          T.I.F.R.                     *         
  *                          HOMI BHABHA ROAD             *         
  *                          BOMBAY - 400005              *         
  *                          INDIA                        *         
  *                                                       *         
  *     THESE CHANGES WERE COMPLETED AT ETH, ZURICH       *         
  *     ON 20/5/74.                                       *         
  *                                                       *         
  *                                                       *         
  *********************************************************)        

Original P2 compiler source
Original P2 interpreter source

Scott Moore’s ISO7185 version of P2

Zürich Pascal compilers

The first Pascal compiler was developed during the years 1969-1971 for Control Data 6000 series hardware at the Institut für Informatik, Eidgenössische Technische Hochschule Zürich. As result of experience with the system and a new implementation begun in July, 1972, resulting in a family of two compilers, Pascal_P and Pascal-6000, having a single overall design.

Pascal-P is a portable compiler that produces code for a hypothetical stack computer, the system is implemented by writing an interpreter for this machine.

Pascal-6000 produces relocatable code for Contrl Data 600 series computers.

Descendants of these two compilers comprised the bulk of the Pascal implementations in existence after 1980.

CDC 6000 Pascal compilers

Pascal Px compilers

Pascal-S compiler

Pascal PL/0 compiler

See the Articles and Books pages for more information!

CDC 6000 Pascal compilers

The CDC 6000 compiler was used as the basis for several other compilers on other machines. When a Pascal implementor needed a compiler, he/she could use either the P4 source as a basis, or the CDC 6000 compiler, or write it from scratch. The reason you might prefer to use the machine specific CDC 6000 compiler as a starting point is that (unlike the P4 compiler) it was a full implementation of Pascal, without any features left off. It also was a full optimizing compiler.

Read this report written by Niklaus Wirth, On “PASCAL” Code generation, and the CDC6000 Computer, Stanford University, 1972

On this page listings from 1972, 1974, 1976 of the Zürich compilers and the surviving (1986) CDC 6000 compiler at Minnesota University.

The 1972 Compiler

The following listing was provided by John Reagan, currently Master Compiler Engineer at VMS Software, formally of Digital Equipment (DEC), Compaq and HP.
Main compiler code in Pascal
The 1972 Compiler was the last version of the original, unrevised Pascal language before Pascal reached the form most folks know as Standard Pascal. It is different in many ways, for example, there was no program header, write/ln and read/ln were considered CDC extentions to the language, dynamic pointers were introduced by a statement, and other differences.
The language of the compiler is described in the 1970 document, see the Articles page.
The method used to create the first Pascal compiler, described by U. Ammann in The Zurich Implementation, was to write the compiler in a subset of unrevised Pascal itself, then hand-translate the code to SCALLOP, a CDC specific language. The compiler was then bootstrapped, or compiled using the Pascal source code and the SCALLOP based compiler, to get a working compiler that was written in Pascal itself. Then, the compiler was extended to accept the full unrevised Pascal language.

The 1974 compiler

The following listings were scanned from listings provided by Bob Felts: CDC 6000 Pascal 3.4 Update 10 compiler.
Main compiler code in Pascal
Cross-reference
Runtime library code in Compass, the CDC 6000 assembly language
The 1974 compiler was the first of the revised compilers. That is, it was rewritten in the “revised Pascal” language that was the Pascal language we recognize today. The “Pascal-P implementation notes” imply that the compiler was Pascal-P ported specifically to the CDC 6000 series computer, and indeed the 1974 CDC Pascal compiler appears to match P2 better than any of the other compilers. As the CDC compiler was modified, it resembled Pascal-P less and less, which is natural.

The 1976 Compiler

The following listings were scanned from listings provided by Mr. John Dykstra.
Main compiler code in Pascal
Runtime library code in Pascal
Runtime library code in Compass, the CDC 6000 assembly language
An error translation routine
The compiler listing is dated 1976. The scans were taken from a listing direct from a CDC 6000 series computer, and bear some unique features to such a listing. The name and line number appears at the right of the listing. Because the listings were wider than a 8 1/2 inch sheet of paper the line numbers to the right have one or more digits cut off. This compiler comes from the revised Pascal that forms the basis of the Pascal User Manual and Report, second edition. The compiler source is not written in standard Pascal, nor would it have been even if the compiler had been written at the time of the standard. It uses several of the CDC 6000 specific extentions, and it has the generation of CDC 6000 machine instructions imbedded in it. It is a one piece compiler, it takes in Pascal on one end, and issues CDC 6000 object code out of the other. The layout of the compiler is similar to the P4 project, which is not an accident. The P4 system was derived from this compiler. The compiler was written in, and compiled for, the revised Pascal language that most of us think of as Standard Pascal. The documents that describe this are described on the Articles page.
U. Ammann described the creation of the revised compiler in The Zürich Implementation, The 1970 compiler (above) was rewritten completely to arrive at the revised Pascal compiler. This was done both because the new Pascal language was different, and also because the experience of writing the old compiler had suggested better code structure for the new compiler. The new compiler was written in unrevised, or 1970 Pascal code. This resulted in a compiler that compiled using the old compiler, but accepted the revised language Pascal. Then, the compiler code itself was hand translated to the new language, and translated by the new compiler that was compiled by the old compiler. This resulted in the new compiler running on itself, and thus a full bootstrap. Of course, at this point you might well wonder what hand translation of the first version of the source on the new compiler from unrevised to revised Pascal might mean, which U. Ammann does not go into. Basically, it is just what you do if the unrevised and revised languages are not quite compatible. Otherwise, if the unrevised compiler was a subset of the revised language, you could just recompile it without changes. This is not nearly as much of a project as translation to SCALLOP, and used in the first compiler. It just means changing to accommodate the differences in the languages, which were substantially similar.

The 1984 Compiler

The CDC compiler continued to evolve past 1976. Most of the changes in what is contained here as the 1984 compiler were made at the University of Minnesota by Dave Bianchi and Jim Miner (who appears as a reviser of the forth edition Pascal User manual and Report). The material contained is marked copyright, but the University of Minnesota has graciously granted permission for it to appear. The University of Minnesota group extended the implementation in a few ways, for example it contains the otherwise statement on case statements. Otherwise, it appears to be a straightforward implementation of the original Zürich compiler, and it continued to be run on the CDC 6000 series computers. The University of Minnesota implementation is important for several reasons:

  • It contains the last known code revision of the CDC compiler.
  • It is well documented.
  • It is exists in machine readable and runnable form.
  • It obeys, with compiler options, the ISO Pascal Standard.

Modification history – History of changes to the source.
Pascal compiler – The main compiler code
Pascal Include Generator – Program to process includes and error information.
Pascal Library – Contains runtime support library routines in Pascal.
Pascal Error Messages – Contains error messages in various languages.
Pascal Runtime Support – Contains Pascal runtime support in Compass, the CDC 6000 assembly language.
Pascal System Support -Contains the run time system in Compass, the CDC 6000 assembly language.
Pascal System Texts – Contains constants and macros used in the compiler, in Compass.

Note that the listings were created by a card listing program (as in punched cards), and have type and sequencing information at the right hand side. This information can be easily removed by clipping everything from column 75 on. It was retained here for historical purposes.
Note also that all of the sources appear in upper case text. The CDC computer native character instruction set only had one case of character.

The documentation files for the compiler:
Pascal-6000 Installation Handbook – Details how to install the release tape.
Pascal-6000 Internal Reference Manual – Overview of program internals.
Pascal-6000 Library Information – Details of the local library.
PASPLOT – a Pascal Plotting Package – Details of an applications package.
SUMMARY OF CHANGES TO PASCAL-6000 – As it says.surveys changes from the last to this release
Pascal-6000 Release 4 Upgrade Guide
Prose Instruction Manual – Manual for Prose, a text formatter.
Pascal-6000 Writeup – The main users manual for the compiler.

Based upon a page and files supplied by by Scott A. Moore

P4 Compiler


Relevant articles about the portable Pascal Px compilers (see also the Articles page for Pascal Reports etc)

Book by Martin Daniels and Steven Pemberton Pascal implementation: The P4 Compiler, online version, local copy
A line by line description of the source.

ETH Pascal Programming Language Technical information:

Portable Compiler project New Edition H.H. Naegeli, 16.02.77
Portable Compiler project Pascal P4 Urs Ammann, Kesav Nori, Christian Jacoby May 76
Pascal P4 interpreter
Lists binary codes P-codes
Cross referencer
P4 Pascal Compiler P-Code listing
Procedural Cross Referencer

Downloads

Pascal P4 adapted to more standard Pascal
The files in this archive are:

  • int.p – P4 code interpreter
  • comp0.p – original compiler as distributed
  • comp1.p – same compiler with bugs fixed up to Pascal Newsletter #12
  • comp2.p – as above but with experimental changes to eliminate the last of the machine dependent code
  • comp.p – lower case, entabbed and stripped version of comp2.p some typos in comp?.p have been fixed
  • compvax.p – essentially the same as comp.p but with changes to allow it to compile under ‘pc’
  • compdiffs – differences between compvax.p and comp.p
  • compvax.errs – warning messages
  • compvax.map – line numbers of procedures and functions

Note that the characters for ^ and ‘ are ‘ and # in the compiler sources.

Pascal P4 adapted to ISO7185 Pascal by Scott Moore

Pascal P4 adapted to more standard Pascal, with examples

Pascal-S Concurrent Pascal-S

Pascal-S is a subset of Pascal, and was originally written by Niklaus Wirth.
Moti Ben-Ari has built on Pascal-S in his Principles of Concurrent Programming, resulting in Concurrent Pascal-S.

Compared to Wirth’s version of Pascal-S, case statement, records and reals are swiped from this edition of Pascal-S. M. Ben-Ari modified Wirth’s original compiler/interpreter in 1980 to include some basic features that were able to simulate concurrent programming.

First, a cobegin s1; …; sn coend block structure was added, allowing concurrent execution of the statements s1 … sn, which were required to be global procedure calls. These cobegin … coend blocks could not be nested within one another.

Second, the use of semaphores was introduced, with a semaphore data type (really synonymous with the integer data type) and the semaphore operations wait(s) and signal(s), corresponding to Dijkstra’s P(s) and V(s), respectively.

Downloads: