$A MARK=2;UNDSH='@';UND=0;NLS=2 $A CAP=0;CAPO=0;CAPSH=0;CAPSHO=0;INVERT=0;INVO=0 $A TOP=4;BOTTOM=8;UNDSHO='@';SLINE=72 $A LEFT=10;LINE=62;PAGE=52;JUST=1 $A TAB=6,11,16,21,31,41,26 $B10 $L1MU USERS GUIDE TO A PDP_16 DESIGN AID $B4 $L1UM COMPUTER SCIENCE IV $B $L1MU GROUP PROJECT 1974 $B $L5M A. ANDERSON M.A.C. CURRIE L.F. MARSHALL P.S. ROBERTSON B.C. WILKIE $N $P This document describes a suite of programs which forms an aid for designing and building computer systems from DEC PDP-16 modules. $P The design is formulated using a special purpose language. $P With the design specified in this language the system can be simulated to discover logical errors, and to check the operation of any algorithms involved. $P Once a satisfactory version of the design has been produced a detailed list can be output containing the specific modules and interconnections necessary to build the hardware. $P This list can also be used to produce flowcharts for the complete design. $P The programs mentioned in this guide are available on EMAS. $P Before any of them can be used for the first time it is necessary to make them available to the loader. This is done using the command: $B $T4 APPENDLIB (CSDEPT.PDP16LIB) $N $A LEFT<=29;LINE<=43;INDENT<=2;NLS=1;SGAP=1 $B4 @CONTENTS $T6 $C-1 @PAGE $B3 $T0 The ARTHUR Language $T6 $C+1 1 $B0 Declarations $T6 $C+1 4 $B0 Delimiters $T6 16 $B0 Conditional Statements $T6 20 $B0 Unconditional Statements $T6 26 $B0 Compiling ARTHUR Programs $T6 36 $B0 ARTHUR Fault Messages $T6 38 $B $T0 Simulation of ARTHUR Programs $T6 47 $B0 Command Language $T6 49 $B0 Setting breakpoints $T6 57 $B0 Examining Registers and Flags $T6 63 $B0 Altering Registers and Flags $T6 67 $B0 Other commands $T6 69 $B0 Error Messages $T6 73 $B $T0 WOMBLE: The Wiring Program $T6 76 $B0 Output format $T6 77 $B0 Special Points to Note $T6 80 $B $T0 FLO: The Flowchart Program $T6 81 $B $T0 Appendices: $B0 1. Phrase Structure of ARTHUR $T6 82 $B0 2. Sample Program $T6 87 $B0 3. Wiring Schedule $T6 88 $B0 4. Definition of SAM $T6 90 $N $A PAGENO=1;NLS=2;SGAP=2;LEFT>;LINE>;INDENT> $B4 $L1MU THE ARTHUR LANGUAGE $P The ARTHUR language is a method of expressing PDP-16 designs in a clear form which is amenable to computer processing. $P It comprises statements which are strings of keywords, names, constants and special symbols, arranged to conform to a rigid syntactical definition (Appendix 1 gives the BNF definition of the syntax of ARTHUR). Keywords are reserved names, distinguished from user-defined names by being preceeded by a percent charter and terminated by any non-alphabetic character (including spaces and newlines). $P With the exception of the case above, spaces may be inserted freely throughout the program to improve clarity. $P The special keyword %C may be used at the end of a line to indicate to the compiler that the next line is to be considered a continuation of the current line. The %C and the following newline will be ignored. $P The maximum length of any statement is currently 300 characters. $P An ARTHUR program consists of a sequence of statements, one per source line, terminated by the statement: $L1M %ENDOFFILE $P Blank lines are accepted as null statements. $P Appendix two gives the compiler listing of the ARTHUR version of the example given on page 30 of the PDP-16 COMPUTER DESIGNERS HANDBOOK. $N $L1MU POINTS TO NOTE $A LEFT=14;LINE=58;INDENT=1 $B $T0 1) $T1 In all statements which refer to specific bits of a register, the bits are ordered from 0 to 15 with bit 15 being the most significant (the sign bit) i.e. the Nth bit represents 2**N when set. $A LEFT=10;INDENT=0 $N ARTHUR statements can be divided into four groups: $B $T1 1/ $T2 @DECLARATIONS $A LEFT=19;LINE=53 $P A declaration is a statement which defines the modules to be used in the design, and the names by which they are to be referred. In order to prevent any ambiguity all names used in the program must be unique. $P The following list gives all the valid forms of declarations divided into classes by the general form of the declarative statement used. $B $L a) (MODULE NAME) (NAMELIST) $A LEFT=24;LINE=48 $B where (MODULE NAME) defines one of the following types of modules: $B $A INDENT=2 $T0 %GPA $T2 General Purpose Arithmetic unit. This implies both a general purpose arithmetic unit control module (KAC16) and a general purpose arithmetic unit register module (KAR 16). $N $T0 %FLAG $T2 General purpose flip-flops (flags) (KFL16) $B $T0 %GPINT $T2 General Purpose Interface (DB16-A) $B $T0 %OUTINT $T2 Output Interface (DB 16-B) $B $T0 %INTINT $T2 Input Interface (DB16-C) $B $T0 %SINT $T2 Serial Interface (DC16-A) $B $T0 Examples of this type of declaration are: $B $T0 %GPA COUNT1,COUNT2 $B which defines two general purpose arithmetic units called COUNT 1 and COUNT 2 $B $T0 %SINT LINK $B which defines a serial interface called LINK $N $A LEFT=19;INDENT=0 $L1 b) %SPM [NAME] (REGISTER DEFINITION) $A LEFT=24;LINE=48 $B This declaration defines a scratchpad memory module (MS16-C) $B (REGISTER DEFINITION) is either missing, or defines names to be given to the sixteen registers comprising the memory. $B0 The form of the definition is a list of names and 'don't care' markers separated by commas, the whole definition being preceeded by an equals sign. e.g. $B $L1M %SPM REGS= RO, R1, NEWREG, ? (12), LAST $P This gives the names R1, R2, NEWREG, and LAST to the registers SPO, SP1, SP2, and SP15, (PDP-16 handbook terminology) and leaves the twelve registers SP3 to SP14 un-named. $B0 No names are given to any of the registers if the definition is missing . e.g. $B $L1M %SPM SCRATCH $N $A LEFT=19 c) $T1 (MEMORY TYPE) [NAME] (SIZE) $A LEFT=24 $B where (MODULE TYPE) is one of: $B $A INDENT=2 $T0 %MEMORY $T2 which defines a scratchpad memory (MS16-D or MS16-E) $B $T0 %ROM $T2 which defines a read-only memory (MR16-B) $A INDENT=0 $B (SIZE) defines the size of the memory required and is of the form $B0 $T2 '(' [CONSTANT] (UNITS) ')' $B0 where (UNITS) is K ( for Kilobytes) or B (for Bytes) e.g. $B $T2 %ROM DATA (1K) $B $T2 %MEMORY STORE (1024B) $N $A LEFT=19 d) (T/B REG) (FORMAT) $A LEFT=24 $B where (T/B REG) is one of: $B $A INDENT=2 $T0 %TREG $T2 which defines a Transfer Register (MS16-A). $B $T0 %BREG $T2 which defines a Byte Register (MS16-B). $A INDENT=0 $B (FORMAT) is a description of the way in which the input and output pins of the register are to be connected. $B0 The basic form of the format is $B $T2 '(' (PIN LIST) ')' $B where (PIN LIST ) is a list of pin (bit) numbers in the range zero to fifteen. The first pin specified is the output pin to be connected to the first input pin, the second pin specified is the output pin to be connected to the second input pin, and so on. e.g. $B %TREG REV(0,1,2,3,4,5,6,7,8,9,10,11,12,13,14,15) $B declares a Transfer register which will reverse the order of the input bits on output. $J (Throughout this guide the bits of a word are numbered with the most significant bit being bit 0) $P If the format is missing , the register is assumed to be wired input pin 0 to output pin 0, input pin 1 to output pin 1, etc. $P If many registers are to be defined using the same format for the internal writing, the format definition can be given a name which can be used in place of the more lengthy specification. $B0 This is done using a %REGFORMAT statement e.g. $B $A LEFT<=19;LINE<=53 %REGFORMAT RFM(8,9,10,11,12,13,14,15,0,1,2,3,4,5,6,7) $A LEFT>;LINE> $P Thereafter a %TREG or a %BREG can be declared replacing the pin list in the format by the name of the %REGFORMAT e.g. $B $T2 %BREG BYTE (RFM) $N $A LEFT= 10 $L1MU REFERENCE TO DECLARED NAMES $A LEFT=19;LINE=53 $P Some of the modules described above contain two or more internal registers or flags which can be used by the designer. $B0 These registers can be selected by following the reference to the module name by a qualifier. These qualifiers are defined for specific module types and are given below. $B $A INDENT=3 $T0 i $T1 %GPA $T3 This has two registers: A and B. The qualifiers to reference these are $B _A and _B $B For example, if X has been declared as a %GPA the A and B registers of X are referred to as: $B $L1M X_A and X_B $B $T0 ii $T1 %GPINT $T3 Access to the output register and the input data lines is achieved by specifying _OUT and _IN respectively. $B e.g. GP_OUT and GP_IN $B $T0 iii $T1 %SINT $T3 A serial interface contains three Flags: the keyboard flag, the Punch flag, and the Over-run flag. These are specified by the qualifiers _RF, _PF, and _OVERUN respectively. e.g. $B $T4 SS_KF SS_PF SS_OVERUN $B $T0 iv $T1 %SPM $T3 A scratchpad memory of this form contains sixteen registers. These may be referenced using names defined in the declaration of the %SPM, or by giving the qualifier of a hash character (#) followed by the number of the register required. $B0 For example, if SCRATCH has been declared as an %SPM: $B SCRATCH#0 $T5 - gives register zero $B SCRATCH#12 $T5 - gives register twelve $N $T0 v $T1 %TREG, %BREG $B0 Transfer registers and Byte registers can deliver groups of bits from various fields in the register. This can be specified by giving a qualifier consisting of the lower and upper bits of the field, separated by a colon, and the whole enclosed in angle brackets. e.g. $B0 If TR and BR are transfer and byte registers the valid field extractions are: $B0 TR<8:15>, TR<0:7>, TR<0:15> $B BR<0:3>, BR<0:7>, BR<0:11>, BR<0:15> $B If no qualifier is specified <0:15> is assumed. $B0 Tregs can also be loaded in the combinations. $N $T0 vi $T1 Bit extraction $B0 Several modules allow specific bits of internal registers to be tested as flags. This is indicated by giving a qualifier consisting of the required bit number enclosed in angle brackets. $J e.g. $B0 X_A<7>, X_B<15> $A INDENT=0 $N $L1UM %DEFINE $P Once a name has been declared it is possible to give names to the components of the specified module. This is done using the %DEFINE statement. $B0 The form of the statement is $B0 $T3 %DEFINE (ITEM LIST) $B where (ITEM LIST ) is a list of items separated by commas. $P0 Each item consists of the new name followed by an equals sign, followed by the compound name being given a new name. $B0 A compound name is any declared name, possibly followed by qualifiers. e.g. $B0 $T3 %DEFINE SIGN=X_A<15>, PARITY= X_B<0> $P This statement defines SIGN to be a flag which reflects the value of the sign-bit of the A register of the %GPA X, and similarly for PARITY. $P As there is no convenient way of setting or clearing single bits in a register, these flag must be considered 'read only' flags (i.e. they can only be used in conditions). $Lm %DEFINE LEFT= X_A, RIGHT= X_B $B assigns the names LEFT and RIGHT to the A and B registers of the %GPA X $B $L1M %DEFINE LOWER= TR<0:7>, MINUS= RIGHT <15> $B assigns the name LOWER to the lower half of the %TREG TR and the name MINUS to the sign bit of RIGHT (which itself has been defined to be an alias for X_B, see the previous example). $N $A LEFT=14 2/ $T2 @DELIMITERS $P2 $A LEFT=19;LINE=53 This group of statements is used to delimit certain text strings and blocks of statements. $B a) $T1 %ROUTINE [NAME] $A LEFT=24;LINE=48 $B This introduces a group of statements which are to be executed from different parts of the program; entry and return form this block will be achieved using SUBROUTINE RETURN modules. $B0 These routines are @not procedures in the ALGOL sense and the following points should be noted: $B $A INDENT=2 $T0 i $T2 Routines in ARTHUR have no textual identifiers declared in the routine remain declared for the remainder of the program. Therefore these names must be different from any names declared previouly. $B $T0 ii $T2 Routine definitions may not be nested within one another. $N $T0 iii $T2 Routines are entered by giving the name of the routine (see later) but cannot be entered by 'falling through' from the statement before the %ROUTINE statement. Therefore routines must be defined before the main program entry point has been discovered ( the first executable statement of the program not within a routine). $B $A LEFT=19;INDENT=1;LINE=53 $T0 b) $T1 %END $B This statement marks the end of a %ROUTINE definition, and will cause a %RETURN (see later) to the point from which the routine was called. There must be one %END to correspond to each %ROUTINE definition. $B $T0 c) $T1 %ENDOFFILE $B This marks the end of the program and causes the compiler to stop the compilation. $N $T0 d) $T1 (LABEL)':' $B A label is a prefix which can be placed in front of any executable statement to identify it as the destination of a jump. $B0 More than one label may be given to a statement. $B (LABEL) has two forms: $B $A INDENT=3 $T1 i $T3 [NAME] $B This is a simple label and is referred to by a jump statement (see later). e.g. $B $T4 TOP: $B $T1 ii $T3 [NAME] '(' (CONSTANT) ')' $B This label is the destination of a %BRANCH statement (see later) The constant must be in the range zero to seven inclusive. e.g. $B $T4 SWLAB (5): $B This number corresponds to the three bit index calculated by the %BRANCH statement prior to jumping. A label of this form cannot be used as the destination of a simple jump. $B $T0 e) $T1 Comments $A INDENT=1 $B A commment is a text string which is inserted into the program to explain various points of interest and is completely ignored by the compiler. $B0 Comments are introduces by a dollar sign ($$). This symbol and the remainder of the current line are ignored. e.g. $B $T3 FRED <-BERT + 1 $$ update FRED $N $A LEFT=14;INDENT=0 3/ $T1 @CONDITIONAL @STATEMENTS $B $A LEFT=19;LINE=53 Statements in this class direct the execution of the program by making data - dependent decisions. $B a) $T1 (CONTROL OP) (IF/UNLESS) (FLAG NAME) $B $A LEFT=24;LINE=48 where (CONTROL OP) has three forms: $B -> LABEL $T2 a jump to a simple label. $B %RETURN $T2 The statement to exit from a routine. $B %STOP $T2 causes program to be stopped. $B (FLAG NAME) is any data object which can be tested on a true/false, clear/set basis. This includes: $B Flags $T2 defined using %FLAG $N Implict Flags $A LEFT=34;LINE=38 These are flags in the bus control module which provide information about the state of the bus register. They are: $A INDENT=1 $T0 DN $T1 @SET if the data on the bus is negative. $B $T0 DZ $T1 @SET if the data on the bus is zero. $B $T0 DP $T1 @SET if the data on the bus is positive. $B $A INDENT=0 These flags have more explict aliases: $B0 DN $T1 - $T2 NEGATIVE $B DZ $T1 - $T2 ZERO $B DP $T1 - $T2 POSITIVE $B $A LEFT=24;LINE=48 Module flags. $B0 $T2 _KF,_PF,etc. $B Register bits $B0 $T2 X_A<15> etc. $N (IF/UNLESS) has two forms: $B $A INDENT=2 $T0 %IF $T2 the control op. is obeyed if the flag is set or has the value 1. $B $T0 %UNLESS $T2 the control op. is obeyed if the flag is CLEAR or has the value 0. $B $T0 e.g. $B ->LAB %IF F $T5 $$ jump if F is @SET $B ->TOP %UNLESS X_A<4> $T5 $$ jump if bit 4 $B0 $T5 $$ of A is zero $B $T2 ->PAST %IF ZERO $T5 $C-3 $$ jump if bus is zero $B $A LEFT=19;INDENT=0 b) $T1 %WAIT (WHILE/UNTIL) (FLAG NAME) $A LEFT=24 $B This statement is used to cause the program to loop whilst waiting for some event. $N (WHILE/UNTIL) has two forms: $B $A INDENT=2 $T0 %WHILE $T2 the program will loop as long as the flag is SET (has the value 1). The next statement will be executed when the flag becomes CLEAR ( has the value 0). $B $T0 %UNTIL $T2 The program will loop as long as the flag is CLEAR (has the value 0). The next statement will be executed when the flag becomes SET (has the value 1). $B $T0 e.g. $B %WAIT %UNTIL FREE $B %WAIT %WHILE X_A<0> $A INDENT=0 $B In both cases a 'no-operation' module will be evoked @before the flag is tested, thus causing a delay. Since the nop clears the bus, bus flags can not be used as the flags in this statement. $N $A LEFT=19 $L c) %BRANCH [NAME]'('(LEVEL)','(LEVEL)','(LEVEL)')' $B $A LEFT=24;LINE=48 where (LEVEL) can be: $B i $T2 any flag or bit $B ii $T2 %HIGH - a flag which is always SET $B iii $T2 %LOW - a flag which is always CLEAR $B The three levels are treated as a three-bit binary value (set=1). A jump is made to the label [NAME] qualified by the three bit value in brackets. e.g. $B $T2 %BRANCH SW (F1, X_A<0>, SS_KF) $B $T2 %BRANCH BR(%HIGH, %HIGH, %LOW) $B $T2 $$ (will always jump to BR (6):) $N $A LEFT=19 d) $T1 %BREAKPOINT [NAME] $B $A LEFT=24 This statement is not strictly a conditional statement for the PDP-16 as it is only of importance when the program is being simulated (see SAM) , when, if the breakpoint has not been inhibited, the simulation will be suspended. $N $A LEFT=14 4/ @UNCONDITIONAL @STATEMENTS $A LEFT=19;LINE=53 $B This group comprises the transfers (data and control), arithmetic operations, input/output operations, and other data operations. $B a) $T1 Control Transfers $B $A LEFT=24;LINE=48 $A INDENT=2 $T0 ->LABEL $T2 the next instruction to be obeyed is the one prefixed with the label LABEL $B $T0 Routine Calls $B A routine that has been defined in the program is called by giving its name. e.g. $B0 $T3 SQUARE $B0 Note that PDP-16 hardware requires that the same routine is @not called twice in succession without at least one evoke operation between the calls. If the compiler detects that this has been done a NO-OP is inserted between the calls and a warning message to this effect is output. $B $N $T0 %RETURN $T2 This marks the dynamic end of a routine, and so it is only valid in the context of a %ROUTINE. $B $T0 %STOP $T2 execution of this statement causes the program to stop. $B $A LEFT=19;INDENT=0 b) $T1 Data Transfers $A LEFT=24 $B These statements consist of two registers, the source and estination registers, with the destination on the left and the source on the right with a left arrow (<-) between. e.g. $B $T2 X_A <-Y_B $B $T2 SPREG#4 <-TR<0:7> $B The second example means: put the lower half of the transfer register TR onto the bus, then store the contents of the bus into the register four of the scratchpad memory SPREG. $N Constants may be specified as sources, and this will cause constant generator modules (MR16-A) to be added to the list of modules required for the design.e.g. $B $T2 X_A <-100 $B The default base to which the constants are calculated is ten, but there are two ways of changing this. $B $A INDENT=2 $T0 i $T2 by specifying the base along with the number, separated by an underline character.e.g. $B $T3 X-A <- 8_7747 $B $T0 ii $T2 by changing the default base using the statement: $B0 $T3 %RADIX n $B which has the effect of causing all subsequent constants to be calculated to base 'n'. e.g. for hex numbers: $B $T3 %RADIX 16 $N However, note that specifying a radix of greater than ten may cause ambiguities between constants and some names. $B0 e.g. $B0 $A INDENT=3 %GPA X $B0 %DEFINE A = X_A $B0 %RADIX 16 $$ HEX $B0 X_B <- A $B0 $$ Either X_A or 10 decimal $B0 $$ Compiled as the former. $A INDENT=0 $P Data transfers to and from %MEMORY and %ROM modules need two instructions: $A INDENT=2 $B $T0 i $T2 First the memory address register must be loaded with the address of the memory element required. This is done by assigning the address to the name of the memory module concerned e.g. $B $T3 M <- X_A $B (Note that there is no way of reading from the memory address register, so X_A<-M is illegal) $N $T0 ii $T2 Second the required memory location is referenced by enclosing the memory module name in square brackets. e.g. $B $T3 [M] <- X_B $$ update contents $B $T3 X_A <- [M] $$ read contents $B $A LEFT=19;INDENT=0 c) $T1 Arithmetic Operations $A LEFT=24 $B Instead of giving a register as the source of a transfer, any valid operation upon the two registers in a %GPA may be specified. e.g. $B $T2 Y_A <-X_A + X_B $B $T2 Y_B <- -X_A $B $T2 Y_B <- X_A + 1 etc. $B Note that the operators for the logical operations AND, OR and EXCLUSIVE-OR are &, !, and !! respectively. e.g. $B $T2 Y_A <- X_A !! X_B $N $P The full list of operations is:- $B0 $T1 A+B, A-B, A+1, A-1, \A, \B, A*2, $B0 $T1 A&B, A!B, A!!B, (...)/2 $P The PDP-16 hardware allows the result of any arithmetic operation to be divided by two before being put onto the bus. This can be specified by enclosing the whole expression in parentheses followed by '/2' e.g. $B $T2 X_A <- (X_A&X_B)/2 $B Note: that in all arithmetic expressions the component registers must be the A and B registers of the @same %GPA. $N $P Where a shift is involved - i.e. *2, /2 - the value of the shifted-in bit can be specified. For *2 the Left shift input (LSI) and for /2 the Right shift input (RSI). $B0 An equivalence to some value or bit, similarly to branch definitions, is set up in a %DEFINE statement e.g. $A indent=1 $L5I %DEFINE GPA_LSI=OVERFLOW $$ carry out %DEFINE GPA_RSI=%LOW $$ Logical 0 %DEFINE GPA_LSI=TR<15> $$ most significant $$ bit of %TREG TR %DEFINE GPA1_RSI=FLAG $$ a flag $A LEFT=19;indent=0 $N d) $T1 Input/Output operations $A LEFT=24 $B Input/Output is achieved using b) and c) above, where the source of destination operands are names of interface registers. e.g. $B $T2 GPI_OUT <- X_A $T5 $$ output $B $T2 X_B <- GPI_IN $T5 $$ input $B $T2 X_A <- ININT $T5 $$ input $B $T2 OUTINT <- X_A_1 $T5 $$ output $B $T2 SI <- TR<0:7> $T5 $$ output $N $A LEFT=19 e) $T1 Bus Operations $A LEFT=24;INDENT=2 $B $T0 i $T2 Most of the operations described affect the data bus.Not only can the bus flags DN, DP, and DZ, be examined but the bus register may be used as a data register. The bus is specified using the built-in name BUS e.g. $B $T3 BUS <- X_A $T5 $$ load bus reg. $B $T3 Y_B <- BUS $T5 $$ store bus reg $B $T3 -> ODD %IF BUS <0> $$ test bit $B $T0 ii $T2 There is a special instruction to load zero into the bus register and to set the bus flags accordingly. This is $B $T3 %CLEAR %BUS $N $A LEFT=19;INDENT=0 f) $T1 Flag Operations $A LEFT=24 $B Flags may be manipulated using: $B i $T2 %CLEAR F $T5 $$ set F to Zero $B ii $T2 %SET F $T5 $$ set F to one $B iii $T2 %COMPLEMENT F $T5 $$ invert F $B Note: that these operations are only valid on flags declared using a %FLAG declaration ( or a %DEFINE statement referring to a %FLAG declaration). $B $A LEFT=19 g) $T1 %ENABLE [NAME] $A LEFT=24 This is an extra instruction provided to enable Serial Interfaces being used with old standard teletype paper-tape readers.e.g. $B $T2 %ENABLE SI2 $B $A LEFT=19 h) $T1 %NOP $A LEFT=24 This statements causes a NO-OP module to be evoked to cause a delay, it also clears the bus. $N $A LEFT=14;LINE=58 $L1MU COMPILING ARTHUR PROGRAMS $P3 Once an ARTHUR program has been written it can be compiled using the command: $B $T2 ARTHUR (SOURCE FILE/OBJECT FILE, LISTING FILE) $B If any of the file specifications are null the following defaults are chosen: $B $T1 SOURCE $T4 - $T7 .TT $B $T1 OBJECT $T4 - $T7 SS#ARTH $B $T1 LISTING $T4 - $T7 SS#LIST $P2 During the compliation a line-numbered listing is output to the listing file. Any fault messages produced by the compiler are sent to both the listing file and the user's console. $P At the end of the compilation a count of the number of modules of each type required by the design is output to the listing file. $P In order to prevent an INPUT ENDED error if the %ENDOFFILE statement is omitted from the source file, the compiler will take input from the user's console once the source file is exhausted. The compilation can then be stopped by giving the statement %ENDOFFILE. $N $L1MU ARTHUR FAULT MESSAGES $P The first two faults cause the offending source line to be listed and a marker (!) to be placed under the line at the point at which the error became evident. $B $A INDENT=7 $T0 SYNTAX $T7 The statement violates the syntactic rules of the language. $B $T0 NAME $T7 A name has been used without having been declared in some way. $B $T0 DUPLICATE $T7 A name has been declared twice. $B $T0 DUPLICATE BRANCH $T7 A branch label has been defined twice. $B $T0 LABEL ERROR $T7 The destination of a jump is not a label. $B $T0 CONTEXT $T7 The given statement is out of context. e.g. %RETURN not inside a %ROUTINE $N $T0 INVALID BIT $T7 The extraction of a non-existent bit has been attempted. e.g. BUS <18> $B $T0 ILLEGAL SUBNAME $T7 A meaningless subname has been given after a module name. $B $T0 ILLEGAL INDEX $T7 A reference has been made to a scratchpad register element that does not exist . e.g. $B0 SP#18 $B $T0 ILLEGAL EXTRACTION $T7 An invalid field specification has been made for a %TREG or a %BREG. $B $T0 SPURIOUS END $T7 An %END has been given for which there is no corresponding %ROUTINE statement. $B $T0 INCOMPATIBLE REGISTERS $T7 Arithmetic has been attempted upon two registers which are not A and B registers in the same %GPA. $N $T0 NOT AN 'A' REGISTER $T7 An arithmetic operand which is not an register has been used in a context where an A register must be specified. $B $T0 NOT A 'B' REGISTER $T7 Similar to the above fault. $B $T0 NOT A REGISTER $T7 A name which is not a register name has been used where a register name is neeeded. $B0 Usually caused by using a label as a register. $B $T0 NOT AN ADDRESS $T7 An assignment has been made to a named entity which is not a location. $B $T0 NOT A FLAG $T7 A name which is not a flag name has been used in a conditional instruction. $P $T0 RECURSIVE CALL ON NAME $T7 A call has been made on the routine NAME inside the definition of NAME. $N $T0 END MISSING $T7 %ENDOFFILE has been found inside a %ROUTINE definition. $B $T0 INVALID /2 $T7 A division by two has been specified when the quantity to be assigned has not came from a %GPA register. $B $T0 LABEL MISSING NAME $T7 The named label has been used but not defined. $B $T0 INVALID FLAG OPERATION $T7 An attempt has been made to operate upon a flag which has not been declared using a %FLAG statement. e.g. $B0 %COMPLEMENT POSITIVE $B $T0 DECLARATION MISPLACED $T7 An attempt has been made to define a %ROUTINE after executable statements have been given that were not enclosed in $J %ROUTINE / %END. $N $T0 TOO MANY SCRATCH PADS NAMES $B0 More than sixteen names have been given in the definition list of a %SPR declaration. $B $T0 NOT ENOUGH PINS $T7 The pin list for a %TREG or %BREG declaration does not contain sixteen pin numbers. $B $T0 TOO MANY PINS $T7 A pin definition (as above) has over sixteen pin numbers. $B $T0 NOT A REG PIN $T7 A pin number in a pin list (as above) is out of range. $B $T0 NOT A REGFORMAT $T7 A name which is not the name of a %REGFORMAT has been given instead of a pin list. $N $A INDENT=0 $P The following errors are catastrophic and cause the compiler to terminate the compilation. $B TOO MANY BRANCHES/REGFORMATS $B TOO MANY CONSTANTS $B TOO MANY INSTRUCTIONS $B $A INDENT=7 $T0 TOO MANY LARGE NAMES $T7 The dictionary has been filled. $B $T0 TOO MANY NAMES $T7 The name table has been filled. $B $T0 TOO MANY SYMBOLS ON LINE $B0 The source line is too long to fit into the input buffer (currently 300 characters long). $B $T0 TOO MANY CONJUNCTS IN STATEMENT $B0 The statement is too long to be analysed (usually contains too many %AND components). $B $A INDENT=0 TOO MANY STATEMENTS : OBJECT FILE FULL $N $P The following messages are not considered faults, but may serve to indicate logical errors in the program. $A INDENT=7 $B $T0 ACCESS $T7 The current statement can @never be executed. This can indicate a misplaced label or jump statement. $B $T0 WARNING NOP INSERTED $T7 The same routine has been called twice in succession without an evoke between the calls. The compiler has inserted a %NOP statement. $B $T0 WARNING EVOKE INSERTED $T7 The source and destination registers of a simple transfer statement are Scratchpad Memory registers from the @same Memory module. In order to remove the ambiguity that this produces the statement is split into two evokes: one to load the bus, and another to store the contents of the bus into the destination register. $N $T0 OVERFLOW MEANINGLESS WITH TWO GPAS ON BUS $B0 The combined output of two GPAs on the same Bus drives the Overflow flag in a permanent state of SET. $B0 The warning is output at the end of the compiler listing only if two GPA modules have been declared and the Overflow has also been accessed. $N $A INDENT=0 $L1MU COMPILER ERROR MESSAGES $P2 When attempting to compile a program the compiler can come across various error conditions which make the continuation of the compilation impossible.A message is output to the user's console and the compilation is abandoned. The current messages are: $B CANNOT CREATE OBJECT FILE $A INDENT=7 The named object file cannot be created for some reason. The usual reasons are: $B FILE INDEX FULL $B INVALID FILE NAME $B NO PERMISSION $N $B $L1MU SIMULATION OF ARTHUR PROGRAMS $A INDENT=0 $P3 In order to simplify the task of debugging a PDP-16 design, a simulator has been written which will mimic the operations performed by a real PDP-16 system . $P The program takes as its simulation data any valid ARTHUR object file, and accepts debugging commands from the user's console. $B0 The simulator is called by the command: $B $L1M SAM (OBJECT FILE NAME/ INPUT DATA) $P If the object file name is omitted the default file SS#ARTH is assumed, input is from the teletype. $B0 If the file specified is not an ARTHUR object file the simulator will inform the user and terminate, this will also happen if the file cannot be connected (i.e. if it does not exist, or no access permission has been given to it). $N $P When successfully entered, the program will identify itself on the console and then prompt the user with a colon; the simulator is now ready and waiting for a command to be entered. $P The simulation is terminated and the user returned to EMAS command level by the statement: $B0 $T4 %ENDOFSIM $B0 The message. $B0 $T4 #CLOSE $B0 is output to indicate the termination of the program run. $N $A LEFT=10 $L1MU COMMAND LANGUAGE $B2 $L1U STARTING THE SIMULATION $A LEFT=14;INDENT=1 $B2 $T0 %GO $T1 This command, which may be issued at any time, causes the simulator to clear the @whole system ( i.e. set every register to zero, clear every flag, and set the bus DZ flag ,not memory modules or scratchpads), and commence simulating the input program from the first executable statement of the program (i.e. the first statement that is not a declaration or inside a routine body). If the program requests input at any time, the simulator prompps the user with the name of the input module followed by a colon. Every character that the user types, up to and including the next newline, will be buffered, and the user will only be prompted again when this data has been used by the simulated program. When output is performed by the user's program the name of the output module, and the data it contains ( to the current base, see %RADIX command below) are printed. $N $P The process of simulation will proceed until one of the following events take place: $A LEFT=24;LINE=48;INDENT=0 $B a) The simulator encouters a 'stop' instruction generated by the ARTHUR statement %STOP. The simulation will be halted, and the message: $B STOPPED AT LINE nn $B will be printed, where nn is the statement number on the ARTHUR program listing, at which the %STOP statement occurred. $B0 N.B. The %ENDOFFILE statement also generates a 'stop'. $B0 The simulator then prompts the user for more commands and simulation can only be restarted by use of the %GO command. $N b) The simulator hits a breakpoint. There are three types of breakpoint that can halt the simulator (also see below): $A LEFT=34;LINE=38 $B 1) A programmed breakpoint, set by the ARTHUR statement %BREAKPOINT e.g. $B $T1 %BREAKPOINT XANADU $B When the simulator executes this statement, it will halt with the message: $B $T1 BREAKPOINT XANADU $B 2) A 'statement' breakpoint, set by using the %BREAK command (see below), the message typed is: $B $T1 BREAKPOINT LINE (N) $B where (N) is the statement number at which the breakpoint had been set. $N 3) A conditional breakpoint,set by the '?' command (see below) The simulator will output a message of the form: $B $L4 (NAME-1) (CONDITION SATISFIED) ... .............. ... .............. (NAME-n) (CONDITION SATISFIED) $B BREAKPOINT LINE nn $B where each (NAME-i) is a register or flag indentifier, and the (CONDITIONS SATISFIED) are those conditions specified in the '?' command which have come true (see below for a list of possible conditions). Again nn is the statement at which the break occurred. $N $A LEFT<=24;LINE<=48 $P After any of the above three events have taken place, the simulator returns to command level, and any command may be given. If the user wishes the simulator to resume execution at the statement which caused the break, the %CONTINUE command may be used (see below). $N c) The simulator finds a design error. There are two errors that can be found: $A LEFT>;LINE> $B 1) LABEL NOT DEFINED - this happens when an 8-way branch label corresponding to the value calculated from the three test lines. has not been defined in the user's program. $B 2) RETURN ERROR IN ROUTINE - This means that no Subroutine Module associated with the current routine has been activated. Hence the routine has no return point.If this error occurs it is probable that the user's program contains a jump into a routine body by some means other than the normal subroutine entry mechanism. $N $A LEFT=24;LINE=48 Following these faults the simulator outputs an appropriate message, and gives a routine traceback (if possible). This identifies where the error occurred in the program, and gives an indication of the execution path the program took to reach that point. The simulator then returns to command level, and will accept any valid command, except %CONTINUE. $B2 d) The user interrupts the simulator with the string 'WAIT' (see EMAS Subsystem Reference Manual on INTERRUPTS). This will force a breakpoint at the line currently being simulated. $N $A LEFT=14 %CONTINUE (REPEAT COUNT) $A LEFT<=24;LINE<=48 $B This command causes the simulator to resume execution, after a breakpoint has been encountered. If a repeat count is given (as any valid constant), the simulator will ignore the breakpoint (which caused the current break) that number of times. $P If %CONTINUE is typed after a program error, the execution of a %STOP statement (or %ENDOFFILE) or before a %GO command has been executed, it will be ignored. $P Alternative form to %CONTINUE is $B $T2 : (REPEAT COUNT) $A LEFT=10 $N $L1U SETTING AND REMOVING BREAKPOINTS $A LEFT=14;LINE=58 $P2 As mentioned above there are three types of breakpoint available to a user, and there are commands to set and remove all three types: $B $T1 a) $T2 PROGRAM BREAKPOINTS $B $A LEFT=24;LINE=48 These are breakpoints set up in the user's program with the ARTHUR statement %BREAKPOINT e.g. $B0 $T2 %BREAKPOINT ERROR1 $B0 and are, therefore, an intrinsic part of the simulated program, until removed by editing and recompiling the source. However the execution of the command: $B $T2 %IGNORE (NAME LIST) $B0 will cause the simulator to pass over the breakpoints named in the list e.g. $B $T2 %IGNORE FRED, ERROR 1, XANADU $N If a name given in the list is not a breakpoint name the message: $B $T1 NOT A BREAKPOINT [NAME] $B will be output. $P If the list of names is omitted altogether, every programmed breakpoint will be ignored, thus: $B $T2 %IGNORE $B The command %REPLACE (NAME LIST) reverses the effect of %IGNORE: $B $T2 %REPLACE FRED, ERROR1, XANADU $B If the name list is omitted, all program breakpoints will be reinstated. $B $N $A LEFT<=19 b) STATEMENT BREAKPOINTS $A LEFT=24;LINE=48 $P These are set using the command: $B $T2 %BREAK (LINE NUMBER LIST) $B0 e.g. $B0 $T2 %BREAK 6,9,1 $B0 will cause the simulation to be suspended when it reaches any of the statements numbered 6,9 or 1 in the ARTHUR listing.If no list of numbers is given, the simulator enters SINGLE SHOT MODE, and will halt before the execution of every program statement. $P To remove these breakpoints the command %FREE is used which has the same format as %BREAK e.g. $B $T2 %FREE 6,9,1 $B0 $T2 %FREE $N $A LEFT<=19 c) CONDITIONAL BREAKPOINTS $A LEFT> $P2 These are set using a command of the form: $B0 $T2 ? (CONDITION LIST) $B0 where (CONDITION LIST) is a list of statements in one of the following formats: $B $A LEFT<=34;LINE<=38 [NAME] $A INDENT<=1 a register or flag name alone, which will cause the simulator to trap when the named location changes from its present value $J e.g. $B0 ?X_A $B0 ?FLAG1 $B $T0 [NAME] (OPERATOR) (CONSTANT) $B0 The simulator will halt when the relationship, defined by the comparator, between the given constant and the named location becomes true. $N Valid comparators are: $L6I = equality \= inequality > greater than >= greater than or equal to < less than <= less than or equal to $A INDENT> $B e.g. ?X_A < 78, X_B >= 345 $P Only one breakpoint can be set up on any @declared locations - '%DEFINE'd locations will be set at the original declared module, but the type will be taken into consideration. $B N.B. The '#' symbol is not used since it creates ambiguities with the use of scratchpad memory names. $N $A LEFT>;LINE> $P3 The %CANCEL command is provided for the removal of conditional breakpoints, and its format has two forms: $A LEFT<=34;LINE<=38 $B0 %CANCEL (NAME LIST) $B0 $A INDENT<=1 remove conditional breaks set on the locations named e.g. $B0 %CANCEL X_A,LINK_PF,F,X_B $B $T0 %CANCEL $B0 remove @all conditional traps $A LEFT>;LINE>;INDENT> $P All the above types of breakpoint can be temporarily suspended from operation by specifying a repeat count with the %CONTINUE command used to restart the simulation after they have occured (see above). $P The command %TRAPS is provided to print out status information about statement and conditional breaks currently set up in the system. $N $A LEFT<=10 $L1U EXAMINING THE CONTENTS OF REGISTERS AND FLAGS $A LEFT=19;LINE<=53 $P Two commands are provided for examing the values of registers and flags, the first allows individual locations to be examined, and the secpnd will print out the values of every variable in the system. $A LEFT>;LINE> a) #(NAME LIST) $B0 will cause the simulator to print out the contents of each of the named registers (to the current base, see %RADIX) alongside its name. If a name is given which refers to more than one location (e.g. the name of a General Purpose Arithmetic Unit, SPM name etc.) the contents of all its registers and flags will be printed. $P The reserved name 'BUS' will cause the contents of the data bus and its associated flags to be output, and to examine the bus flags individually the system will accept the names 'DZ' (or 'zero'), 'DP' (or 'POSITIVE'), 'DN' (or 'NEGATIVE') and 'OVF' (or 'OVERFLOW'). $P Special facilities exist for examining the contents of '%MEMORY' or '%ROM' modules, as a large number of locations are involved. $N $P The facilities are: $A INDENT<=2 1) Specifying the name of the module, e.g. M, will print the contents of the module's memory address register. $B0 2) The construct '[M]' will print out the contents of the memory address register, and, enclosed in square brackets, the contents of the addressed location. $B0 3) The construct '[M: CONSTANT)]' will print out the contents of the location in the module M addressed by the value of the given constant ( if it gives a valid address). $A INDENT=1 $P If a name is specified in the list for the # command which, through declared in the source text, is not used in the program, a message to that effect is output. $N $P The following examples of the use of the '#' command assume that the following declarations have been given in the ARTHUR program: $B0 $A INDENT<=2 %GPA X $B0 %MEMORY M(1K) $B0 %SINT LINK $B #X_A,X_B $B0 This will print out the values of the 'A' and 'B' registers of the General Purpose Arithmetic Unit 'X', on seperate lines, thus: $B0 X_A 89 $B0 X_B 67 $B0 #X,M, [M], LINK_PF , [M:567] $B0 This will print out the following text (for example): $B0 X $T3 89 67 $B0 M $T3 34 $B0 M $T3 34[1236] $B0 LINK_PF $T4 SET $B0 M $T3 567 [6379] $A INDENT=0 $N b) %DUMP (DESTINATION) $P This causes the values (to the current base, see %RADIX) of every register and flag known to the system ( with the exception of the contents of large '%MEMORY' modules and '%ROM' modules), to be output to the specified device or file, if no destination is given the user's console is assumed. Any valid EMAS file name or the devices .TT and .LP will be accepted as destinations e.g. $B $T3 %DUMP FRED $B0 $T3 %DUMP .LP $B0 $T3 %DUMP $P The printout can be terminated with an interrupt and string 'ENOUGH'. $N $A LEFT=10 $L1U ALTERING REGISTER AND FLAGS $A LEFT=19;LINE=53 $P2 During the simulation it may happen that errors cause vaiables to become set to the wrong values. To allow the simulation to continue in a meaningful way the values may be corrected. $B0 To change the contents of a register, a limited form of the ARTHUR assignment is provided, which only allows a register to be given a constant value e.g. $B $T3 X_A <-23 $B0 $T3 Y_OUT <- 16_FA32 $P A special command is provided to zero the bus and set the DZ flag: $B $T3 %CLEARBUS $P To alter a flag there are three commands, which correspond to the ARTHUR flag operations. The function that each performs is clear from the command: $B $T3 %SET F1 $B0 $T3 %CLEAR F1,F2 $B0 $T3 %COMPLEMENT F1,F2 $P The command %NAMES will print out all the names (and information about them) currently known by the simulator. This facility may be of assistance to the user who does not have a current program listing. $N $A LEFT=10 $L1U OTHER COMMANDS $A LEFT=19; INDENT=1 $B2 $T0 %RADIX nn $B0 Normally all numeric system input/output is performed to base 16, and a user can specify constants to other bases using the form (BASE) _ (VALUE) e.g. 16_F7F, but the %RADIX command can be used to alter the default base. $J e.g. $B $T3 %RADIX 16 $B changes the base from 10 to 16 (or from 8 to 14, if the base had been previously set to 8). $B0 N.B. $B0 $A INDENT=3 1) Values of the base greater than ten may invalidate some of the names that a user has available! $N 2) Note that when the base is changed, @ALL constant transactions have changed base. Therefore after the command: $B0 $T4 %RADIX 16 $B0 to return to base 10 the command: $B $T4 %RADIX A $B must be given, and for 'base specified' constants, the base given must be given in the current base, for example, if the current is ten: $A INDENT=4 $B0 %RADIX 16 $B0 Y_B<-A_67 $B will give the decimal value 67 to Y_B. $A INDENT=1 $P Special words can be given after %RADIX to specify Hexadecimal, Decimal, Octal and Binary - $B0 $T1 %HEX, %DEC, %OCT, %BIN $N $T0 %TRACEON (destination) $B0 This command allows a user to turn on a program path tracing feature, which prints out the line number of the statement that the simulator is currently executing. The destination of this trace can be any valid EMAS filename, .TT or .LP; if no destination is given .TT is assumed. The trace may be turned off with the command: $B0 $T3 %TRACEOFF $B $T0 %FULL/%QUIET $B When the system executes a %WAIT statement a message of the form: $B0 $T3 WAITING UNTIL FRED $B0 or $T3 WAITING WHILE P $B0 is output to the user's console. The simulation then proceeds with the next statement, having set the flag named to a value appropriate to the satisfaction of the %WAIT condition. $B0 The printing of these messages may be inhibited by the use of the command: $B0 $T3 %QUIET $B0 and may be reinstated by the command: $B $T3 %FULL $B $N $T0 %INPUT (SOURCE) $B Data can automatically be read in from a file. The file can contain any normal statement typed on the console provided it is in the correct order. Default input, assumed for the second parameter also, is the console. When the end of the file is reached the input again comes from the console. $B $T0 %TIME $B Elapsed CPU time between command level and total consumed time in simulation are printed each time before the command prompt when the facility is enabled. This time should not be taken as having any strict relation to execution times in the actual hardware. N.B. it can be disabled by calling it again. $N $A INDENT<=0;LEFT<=10 $L1U ERROR MESSAGES $A LEFT> $P Apart from the error messages mentioned in the various sections above, the system produces several other messages:- $B $A INDENT> a) A command error indication - A question mark is output following a command that cannot be understood, or that is invalid: $B $T3 :%GRUNGE $B0 $T3 ? $B0 $T3 : $B0 However the system will also fault undeclared names, thus: $B0 $T3 :#X,Y,P $B0 $T3 ? NAME #X,Y,P $B0 $T7 $C+1 ! $B0 $T3 : $B Errors in specifying register and flag names are indicated by messages corresponding to those of the ARTHUR compiler, and their meanings may be found in the documentation of that part of the system. $N b) Runtime errors - these are nine in number: $A INDENT=2 1) ADDRESS ERROR, this occurs when an attempt is made to access an element of a %MEMORY or %ROM module, with an address which is outwith the declared size of the module. $B 2) OVERFLOW , this occurs when a number greater than 32767 or less than - 32768 is generated by an arithmetic operation. $B 3) ROUTINE ERROR, normally occurs when the program enters by some other means than a routine call i.e. jumping into a label declared inside the routine from the main program level. $B 4) LABEL NOT SET, normally a branch label for which the calculated value has no label with that index. $B 5) REFERENCING UNUSED NAME, treated as a syntax fault the simulator effectively does not recognise that name. $N 6) OUTPUT USED AS INPUT,the buffer for some I/O modules is being misused. $B 7) INPUT USED AS OUTPUT, same as 6. $B 8) SPURIOUS BUFFER, same as 6 and 7. $B 9) SPURIOUS DESTINATION, unknown error in an arithmetic expression most likely cause is coruption of the object file. $A INDENT=0 $P Apart from 3 and 4 none of these errors causes the simulator to halt, but a message is produced to indicate the occurrence of the error, followed by a program trace. $N $A LEFT=14;LINE=58 $L1MU WOMBLE: THE WIRING PROGRAM $P3 WOMBLE takes the output from ARTHUR and outputs the information needed to build the PDP-16 hardware. $B The program is run using the command: $B $T4 WOMBLE(OBJECTFILE/ LISTING FILE) $B If a null file name is given the default files chosen are: $B $T1 OBJECT $T4 SS#ARTH $B0 $T1 LISTING $T4 .TT $P2 See Appendix 3 for a sample output corresponding to the ARTHUR program given in Appendix 2. $N $L1MU OUTPUT FORMAT $P The output produced by WOMBLE is in three main parts: $B i) $T1 DECLARED MODULES $A INDENT=1 A listing of the control and data modules declared in the ARTHUR program with their associated positions on the control and data buses. $B $T0 ii $T1 CONTROL MODULES $B0 A listing of the control modules and their positions on the control bus. Also included are any MERGE modules implied by the structure of the design. $B $T0 iii $T1 WIRING LISTS $B0 The wiring is specified by a list of 'wires', each of which comprises a chain of pins. Each pin will appear on one wire and one wire only, with a maximum of two other pins being wired to it. $N A pin is specified by a four character code, with the characters having the meanings: $A INDENT=2 $T1 1 $T2 The lateral position as a hexadecimal constant. $B0 $T1 2 $T2 The vertical rack number as a letter in the range A-D. $B0 $T1 3 $T2 The pin position in that slot as a letter in the range A-V . $B0 $T1 4 $T2 The side of the slot required: 1 or 2 $B $A INDENT=1 For example: Pin 4AV2 is the V2 pin of the fourth slot in the top rack. $B The positions of the modules described in i and ii above confirm to 1 and 2 above e.g. $B0 $T2 NOP 5C $B0 specifies a NO-OPERATION card in the fifth slot of the third rack. $N $A INDENT=0 $P The control bus must be mapped across from rack B to rack C (and rack D if used) , by connecting pins: $B0 $L3 8BA1, 8BB1, 8BC1, 8BD1, 8BE1 TO 8CA1, 8CB1, 8CC1, 8CD1, 8CE1 (AND 8DA1, 8DB1, 8DC1, 8DD1, 8DE1) $B0 In the event of the un-bused area (slots OC-3C, OD-3D, CC-FC, and CD-FD ) being required for control modules, the control bus must be mapped to each individual slot. $P The Bus Sense module is normally assigned to slot OB and will require the following wiring: $B $T1 AUTO/MANUAL SWITCH $T7 connected to OBE2 $B0 $T1 START PULSER $T7 connected to OBJ1 $B0 $T1 SINGLE STEP PULSER $T7 connected to OBH1 $B A RESET pulser should be connected to the B1 pin of the control bus. $B Transfer and Byte registers are not cleared by the normal Reset so by connecting a wire from the B1 pin of the control bus to a LOAD ZERO pin on the Bus Sense module (OBR2) and the load pins of the relevant registers (-BL2 and -BJ2 for a TREG, and -BD2 for a BREG), a reset can be effected. $N $L1MU SPECIAL POINTS TO NOTE $A INDENT=1 $B $T0 1 $T1 Transfer registers must be grounded on pins -BN1 and -BP1. $B $T0 2 $T1 Flags must be grounded on pins --D2, --E2, and --S1 $A INDENT=0 $B NOTE: that at the time of writing there is @no ground pin provided on the Departmental patchboards. $N $B2 $L1MU FLO: THE FLOWCHART PROGRAM $P3 FLO takes as input the lists produced by WOMBLE and converts them into flowcharts which give an overall view of the system being designed. $B FLO may be called using the command: $B0 $T4 FLO(INPUT FILE/ OUTPUT FILE) $B0 The default assumptions are:- $B0 $T1 INPUT $T4 .TT $B0 $T1 OUTPUT $T4 .TT $E