*DRAFT*  *DRAFT*  *DRAFT*  *DRAFT*  *DRAFT*  *DRAFT*  *DRAFT*  *DRAFT*  *DRAFT*  

      
                        USERS GUIDE TO A PDP_16 DESIGN AID
                               COMPUTER SCIENCE IV
                                GROUP PROJECT 1974

                                
                                   A. ANDERSON
                                   M.A.C. CURRIE
                                   L.F. MARSHALL
                                   P.S. ROBERTSON
                                   B.C. WILKIE

                                
             This document describes a suite of programs which forms  an
          aid  for  designing  and  building  computer  systems from DEC
          PDP-16 modules.
             The design is formulated using a special purpose language.
             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.
             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.
             This  list  can  also be used to produce flowcharts for the
          complete design.
             The programs mentioned in this guide are available on EMAS.
             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:

                                APPENDLIB (CSDEPT.PDP16LIB)


                                
                                       CONTENTS                     PAGE
                             The ARTHUR Language                      1
                                       Declarations                   4
                                       Delimiters                    16
                                       Conditional Statements        20
                                       Unconditional Statements      26
                                       Compiling ARTHUR Programs     36
                                       ARTHUR Fault Messages         38
                             Simulation of ARTHUR Programs           47
                                       Command Language              49
                                       Setting breakpoints           57
                                       Examining Registers and Flags 63
                                       Altering Registers and Flags  67
                                       Other commands                69
                                       Error Messages                73
                             WOMBLE: The Wiring Program              76
                                       Output format                 77
                                       Special Points to Note        80
                             FLO: The Flowchart Program              81
                             Appendices:
                                       1. Phrase Structure of ARTHUR 82
                                       2. Sample Program             87
                                       3. Wiring Schedule            88
                                       4. Definition of SAM          90


                                       
                               THE ARTHUR LANGUAGE

             The ARTHUR  language  is  a  method  of  expressing  PDP-16
          designs  in  a  clear  form  which  is  amenable  to  computer
          processing.
             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).
             With  the  exception  of  the  case  above,  spaces  may be
          inserted freely throughout the program to improve clarity.
             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.
             The maximum  length  of  any  statement  is  currently  300
          characters.
             An ARTHUR program consists of a sequence of statements, one
          per source line, terminated by the statement:
                               
                                    %ENDOFFILE

             Blank lines are accepted as null statements.
             Appendix  two  gives  the  compiler  listing  of the ARTHUR
          version of the example given on page 30 of the PDP-16 COMPUTER
          DESIGNERS HANDBOOK.

                               POINTS TO NOTE
                               
              1)   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.

                               
              ARTHUR statements can be divided into four groups:
                               
               1/   DECLARATIONS

                      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.
                      The following list gives all the  valid  forms  of
                   declarations divided into classes by the general form
                   of the declarative statement used.
                               
                   a)   (MODULE NAME) (NAMELIST)
                        where (MODULE NAME) defines one of the following
                        types of modules:
                        %GPA      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).
                        %FLAG     General   purpose  flip-flops  (flags)
                                  (KFL16)
                        %GPINT    General Purpose Interface (DB16-A)
                        %OUTINT   Output Interface (DB 16-B)
                        %INTINT   Input Interface (DB16-C)
                        %SINT     Serial Interface (DC16-A)

                        Examples of this type of declaration are:
                        %GPA COUNT1,COUNT2
                                  which  defines  two  general   purpose
                                  arithmetic  units  called  COUNT 1 and
                                  COUNT 2
                        %SINT LINK
                                  which  defines  a   serial   interface
                                  called LINK

                   b)   %SPM [NAME] (REGISTER DEFINITION)
                        This  declaration  defines  a  scratchpad memory
                        module (MS16-C)
                        (REGISTER  DEFINITION)  is  either  missing,  or
                        defines   names  to  be  given  to  the  sixteen
                        registers comprising the memory.
                        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.
                            %SPM REGS= RO, R1, NEWREG, ? (12), LAST
                           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.
                        No  names  are  given to any of the registers if
                        the definition is missing . e.g.
                                          %SPM SCRATCH

                   c)   (MEMORY TYPE) [NAME] (SIZE)
                        where (MODULE TYPE) is one of:
                        %MEMORY   which  defines  a  scratchpad   memory
                                  (MS16-D or MS16-E)
                        %ROM      which   defines   a  read-only  memory
                                  (MR16-B)
                        (SIZE) defines the size of the  memory  required
                        and is of the form
                                  '(' [CONSTANT] (UNITS) ')'
                        where  (UNITS)  is  K ( for Kilobytes) or B (for
                        Bytes) e.g.
                                  %ROM DATA (1K)
                                  %MEMORY STORE (1024B)

                   d) (T/B REG) (FORMAT)
                        where (T/B REG) is one of:
                        %TREG     which  defines  a  Transfer   Register
                                  (MS16-A).
                        %BREG     which    defines   a   Byte   Register
                                  (MS16-B).
                        (FORMAT) is a description of the  way  in  which
                        the input and output pins of the register are to
                        be connected.
                        The basic form of the format is
                                  '(' (PIN LIST) ')'
                        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.
                        %TREG REV(0,1,2,3,4,5,6,7,8,9,10,11,12,13,14,15)

                        declares a Transfer register which will  reverse
                        the   order   of   the  input  bits  on  output.
                        (Throughout this guide the bits of  a  word  are
                        numbered with the most significant bit being bit
                        0)
                           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.
                           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.
                        This is done using a %REGFORMAT statement e.g.
                   %REGFORMAT RFM(8,9,10,11,12,13,14,15,0,1,2,3,4,5,6,7)
                           Thereafter a %TREG or a %BREG can be declared
                        replacing the pin list in the format by the name
                        of the %REGFORMAT e.g.
                                  %BREG BYTE (RFM)


                               
                   REFERENCE TO DECLARED NAMES
                               
                      Some of the modules described above contain two or
                   more internal registers or flags which can be used by
                   the designer.
                   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.
                   i    %GPA      This has two registers: A and B.   The
                                  qualifiers to reference these are
                                  _A and _B
                                  For example, if X has been declared as
                                  a %GPA the A and B registers of X  are
                                  referred to as:
                                        X_A and X_B
                   ii   %GPINT    Access  to the output register and the
                                  input  data  lines  is   achieved   by
                                  specifying _OUT and _IN respectively.
                                  e.g.  GP_OUT and GP_IN
                   iii  %SINT     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.
                                       SS_KF SS_PF SS_OVERUN
                   iv   %SPM      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.
                                  For  example,  if  SCRATCH  has   been
                                  declared as an %SPM:
                                  SCRATCH#0      - gives register zero
                                  SCRATCH#12     - gives register twelve
                   v    %TREG, %BREG
                                  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.
                                  If TR and BR  are  transfer  and  byte
                                  registers  the valid field extractions
                                  are:
                                  TR<8:15>, TR<0:7>, TR<0:15>
                                  BR<0:3>, BR<0:7>, BR<0:11>, BR<0:15>
                                  If no qualifier is specified <0:15> is
                                  assumed.
                                  Tregs  can  also  be  loaded  in   the
                                  combinations.
                   vi   Bit extraction
                                  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.
                                  e.g.
                                  X_A<7>, X_B<15>


                   
                                  %DEFINE
                   
                      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.
                   The form of the statement is
                                  %DEFINE (ITEM LIST)
                   where  (ITEM  LIST  ) is a list of items separated by
                   commas.
                      Each item consists of the new name followed by  an
                   equals  sign,  followed  by  the  compound name being
                   given a new name.
                   A  compound  name  is  any  declared  name,  possibly
                   followed by qualifiers. e.g.
                                  %DEFINE SIGN=X_A<15>, PARITY= X_B<0>
                      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.
                      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).
                               %DEFINE LEFT= X_A, RIGHT= X_B

                   assigns the names LEFT and  RIGHT  to  the  A  and  B
                   registers of the %GPA X
                         %DEFINE LOWER= TR<0:7>, MINUS= RIGHT <15>
                   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).


              2/        DELIMITERS

                   This group of statements is used to  delimit  certain
                   text strings and blocks of statements.
                   a)   %ROUTINE [NAME]
                        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.
                        These routines are not procedures in  the  ALGOL
                        sense and the following points should be noted:
                        i         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.
                        ii        Routine definitions may not be  nested
                                  within one another.

                        iii       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)   %END
                        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.
                   c)   %ENDOFFILE
                        This marks the end of the program and causes the
                        compiler to stop the compilation.
                   d)   (LABEL)':'
                        A label is a prefix which can be placed in front
                        of  any  executable  statement to identify it as
                        the destination of a jump.
                        More than one label may be given to a statement.
                        (LABEL) has two forms:
                        i         [NAME]
                                  This is a simple label and is referred
                                  to by a jump  statement  (see  later).
                                  e.g.
                                       TOP:
                        ii        [NAME] '(' (CONSTANT) ')'
                                  This  label  is  the  destination of a
                                  %BRANCH  statement  (see  later)   The
                                  constant  must be in the range zero to
                                  seven inclusive. e.g.
                                       SWLAB (5):
                                  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.
                   e)   Comments
                        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.
                        Comments  are  introduces  by a dollar sign ($).
                        This symbol and the  remainder  of  the  current
                        line are ignored. e.g.
                                  FRED <-BERT + 1 $ update FRED


              3/   CONDITIONAL STATEMENTS

                   Statements  in this class direct the execution of the
                   program by making data - dependent decisions.
                   a)   (CONTROL OP) (IF/UNLESS) (FLAG NAME)
                        where (CONTROL OP) has three forms:
                        -> LABEL  a jump to a simple label.
                        %RETURN   The statement to exit from a routine.
                        %STOP     causes program to be stopped.
                        (FLAG NAME) is any  data  object  which  can  be
                        tested  on a true/false, clear/set basis.   This
                        includes:
                        Flags     defined using %FLAG
                        Implict Flags
                                  These are flags  in  the  bus  control
                                  module which provide information about
                                  the  state of the bus register.   They
                                  are:
                                  DN   SET if the data  on  the  bus  is
                                       negative.
                                  DZ   SET  if  the  data  on the bus is
                                       zero.
                                  DP   SET if the data  on  the  bus  is
                                       positive.
                                  These flags have more explict aliases:
                                  DN   -    NEGATIVE
                                  DZ   -    ZERO
                                  DP   -    POSITIVE
                        Module flags.
                                  _KF,_PF,etc.
                        Register bits
                                  X_A<15> etc.

                        (IF/UNLESS) has two forms:
                        %IF       the  control op. is obeyed if the flag
                                  is set or has the value 1.
                        %UNLESS   the control op. is obeyed if the  flag
                                  is CLEAR or has the value 0.
                        e.g.
                                  ->LAB %IF F         $ jump if F is SET
                                  ->TOP %UNLESS X_A<4>$ jump if bit 4
                                                      $ of A is zero
                                  ->PAST %IF ZERO  $ jump if bus is zero
                   b)   %WAIT (WHILE/UNTIL) (FLAG NAME)
                        This  statement  is used to cause the program to
                        loop whilst waiting for some event.

                        (WHILE/UNTIL) has two forms:
                        %WHILE    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).
                        %UNTIL    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).
                        e.g.
                                  %WAIT %UNTIL FREE
                                  %WAIT %WHILE X_A<0>
                        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.

                   c)   %BRANCH [NAME]'('(LEVEL)','(LEVEL)','(LEVEL)')'
                        where (LEVEL) can be:
                        i         any flag or bit
                        ii        %HIGH - a flag which is always SET
                        iii       %LOW - a flag which is always CLEAR
                        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.
                                  %BRANCH SW (F1, X_A<0>, SS_KF)
                                  %BRANCH BR(%HIGH, %HIGH, %LOW)
                                  $ (will always jump to BR (6):)

                   d)   %BREAKPOINT [NAME]
                        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.


              4/ UNCONDITIONAL STATEMENTS
 
                   This  group  comprises  the   transfers   (data   and
                   control),    arithmetic    operations,   input/output
                   operations, and other data operations.
                   a)   Control Transfers
                        ->LABEL   the next instruction to be  obeyed  is
                                  the one prefixed with the label LABEL
                        Routine Calls
                                  A routine that has been defined in the
                                  program  is called by giving its name.
                                  e.g.
                                       SQUARE
                                  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.

                        %RETURN   This  marks  the  dynamic  end  of   a
                                  routine,  and  so  it is only valid in
                                  the context of a %ROUTINE.
                        %STOP     execution of this statement causes the
                                  program to stop.
                   b)   Data Transfers
                        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.
                                  X_A <-Y_B
                                  SPREG#4 <-TR<0:7>
                        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.

                        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.
                                  X_A <-100
                        The  default  base  to  which  the constants are
                        calculated is ten, but there  are  two  ways  of
                        changing this.
                        i         by  specifying the base along with the
                                  number,  separated  by  an   underline
                                  character.e.g.
                                       X-A <- 8_7747
                        ii        by changing the default base using the
                                  statement:
                                       %RADIX n
                                  which  has  the  effect of causing all
                                  subsequent constants to be  calculated
                                  to base 'n'. e.g. for hex numbers:
                                       %RADIX 16

                                  However,  note that specifying a radix
                                  of  greater   than   ten   may   cause
                                  ambiguities between constants and some
                                  names.
                                  e.g.
                                       %GPA X
                                       %DEFINE A = X_A
                                       %RADIX 16 $ HEX
                                       X_B <- A
                                       $ Either X_A or 10 decimal
                                       $ Compiled as the former.
                           Data  transfers  to and from %MEMORY and %ROM
                        modules need two instructions:
                        i         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.
                                       M <- X_A
                                  (Note that there is no way of  reading
                                  from  the  memory address register, so
                                  X_A<-M is illegal)

                        ii        Second the required memory location is
                                  referenced  by  enclosing  the  memory
                                  module name in square brackets. e.g.
                                       [M] <- X_B $ update contents
                                       X_A <- [M] $ read contents
                   c)   Arithmetic Operations
                        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.
                                  Y_A <-X_A + X_B
                                  Y_B <- -X_A
                                  Y_B <- X_A + 1 etc.
                        Note   that   the   operators  for  the  logical
                        operations AND, OR and EXCLUSIVE-OR  are  &,  !,
                        and !! respectively. e.g.
                                  Y_A <- X_A !!  X_B

                           The full list of operations is:-
                             A+B, A-B, A+1, A-1, \A, \B, A*2,
                             A&B, A!B, A!!B, (...)/2
                           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.
                                  X_A <- (X_A&X_B)/2
                        Note:  that  in  all  arithmetic expressions the
                        component  registers  must  be  the  A   and   B
                        registers of the same %GPA.

                           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).
                        An equivalence to some value or  bit,  similarly
                        to  branch  definitions,  is set up in a %DEFINE
                        statement e.g.
                             %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
                   d)   Input/Output operations
                        Input/Output is achieved using b) and c)  above,
                        where  the  source  of  destination operands are
                        names of interface registers. e.g.
                                  GPI_OUT <- X_A      $ output
                                  X_B <- GPI_IN       $ input
                                  X_A <- ININT        $ input
                                  OUTINT <- X_A_1     $ output
                                  SI <- TR<0:7>       $ output
                   e)   Bus Operations
                        i         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.
                                       BUS <- X_A     $ load bus reg.
                                       Y_B <- BUS     $ store bus reg
                                       -> ODD %IF BUS <0> $ test bit
                        ii        There is a special instruction to load
                                  zero  into the bus register and to set
                                  the bus flags accordingly.  This is
                                       %CLEAR %BUS
                   f)   Flag Operations
                        Flags may be manipulated using:
                        i         %CLEAR F            $ set F to Zero
                        ii        %SET F              $ set F to one
                        iii       %COMPLEMENT F       $ invert F
                        Note: that these operations are  only  valid  on
                        flags  declared using a %FLAG declaration ( or a
                        %DEFINE   statement   referring   to   a   %FLAG
                        declaration).
                   g)   %ENABLE [NAME]
                        This  is an extra instruction provided to enable
                        Serial Interfaces being used with  old  standard
                        teletype paper-tape readers.e.g.
                                  %ENABLE SI2
                   h)   %NOP
                        This  statements  causes  a  NO-OP  module to be
                        evoked to cause a delay, it also clears the bus.


                              COMPILING ARTHUR PROGRAMS

                 Once an ARTHUR program  has  been  written  it  can  be
              compiled using the command:
                        ARTHUR (SOURCE FILE/OBJECT FILE, LISTING FILE)
              If  any  of the file specifications are null the following
              defaults are chosen:
                   SOURCE         -    .TT
                   OBJECT         -    SS#ARTH
                   LISTING        -    SS#LIST
                 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.
                 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.
                 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.


                                ARTHUR FAULT MESSAGES

                 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.

              SYNTAX                   The   statement   violates    the
                                       syntactic rules of the language.
              NAME                     A  name  has  been  used  without
                                       having been declared in some way.
              DUPLICATE                A name has been declared twice.
              DUPLICATE BRANCH         A branch label has  been  defined
                                       twice.
              LABEL ERROR              The  destination of a jump is not
                                       a label.
              CONTEXT                  The given  statement  is  out  of
                                       context.  e.g. %RETURN not inside
                                       a %ROUTINE
              INVALID BIT              The extraction of a  non-existent
                                       bit has been attempted. e.g.  BUS
                                       <18>
              ILLEGAL SUBNAME          A  meaningless  subname  has been
                                       given after a module name.
              ILLEGAL INDEX            A reference has been  made  to  a
                                       scratchpad  register element that
                                       does not exist . e.g.
                                       SP#18
              ILLEGAL EXTRACTION       An  invalid  field  specification
                                       has  been  made  for a %TREG or a
                                       %BREG.
              SPURIOUS END             An %END has been given for  which
                                       there    is    no   corresponding
                                       %ROUTINE statement.
              INCOMPATIBLE REGISTERS   Arithmetic  has  been   attempted
                                       upon  two registers which are not
                                       A and B  registers  in  the  same
                                       %GPA.
              NOT AN 'A' REGISTER      An  arithmetic  operand  which is
                                       not an register has been used  in
                                       a  context  where  an  A register
                                       must be specified.
              NOT A 'B' REGISTER       Similar to the above fault.
              NOT A REGISTER           A name which is  not  a  register
                                       name   has   been  used  where  a
                                       register name is neeeded.
                                       Usually caused by using  a  label
                                       as a register.
              NOT AN ADDRESS           An  assignment has been made to a
                                       named  entity  which  is  not   a
                                       location.
              NOT A FLAG               A  name  which is not a flag name
                                       has been used  in  a  conditional
                                       instruction.
              RECURSIVE CALL ON NAME   A  call  has  been  made  on  the
                                       routine    NAME    inside     the
                                       definition of NAME.
              END MISSING              %ENDOFFILE  has been found inside
                                       a %ROUTINE definition.
              INVALID /2               A  division  by  two   has   been
                                       specified when the quantity to be
                                       assigned has not came from a %GPA
                                       register.
              LABEL MISSING NAME       The named label has been used but
                                       not defined.
              INVALID FLAG OPERATION   An   attempt  has  been  made  to
                                       operate upon a flag which has not
                                       been  declared  using   a   %FLAG
                                       statement. e.g.
                                       %COMPLEMENT POSITIVE
              DECLARATION MISPLACED    An   attempt  has  been  made  to
                                       define    a    %ROUTINE     after
                                       executable  statements  have been
                                       given that were not  enclosed  in
                                       %ROUTINE / %END.
              TOO MANY SCRATCH PADS NAMES
                                       More than sixteen names have been
                                       given in the definition list of a
                                       %SPR declaration.
              NOT ENOUGH PINS          The pin list for a %TREG or %BREG
                                       declaration   does   not  contain
                                       sixteen pin numbers.
              TOO MANY PINS            A pin definition (as  above)  has
                                       over sixteen pin numbers.
              NOT A REG PIN            A  pin  number  in a pin list (as
                                       above) is out of range.
              NOT A REGFORMAT          A name which is not the name of a
                                       %REGFORMAT has been given instead
                                       of a pin list.

                 The following errors are  catastrophic  and  cause  the
              compiler to terminate the compilation.
              TOO MANY BRANCHES/REGFORMATS
              TOO MANY CONSTANTS
              TOO MANY INSTRUCTIONS
              TOO MANY LARGE NAMES     The dictionary has been filled.
              TOO MANY NAMES           The name table has been filled.
              TOO MANY SYMBOLS ON LINE
                                       The  source  line  is too long to
                                       fit   into   the   input   buffer
                                       (currently 300 characters long).
              TOO MANY CONJUNCTS IN STATEMENT
                                       The  statement  is too long to be
                                       analysed  (usually  contains  too
                                       many %AND components).
              TOO MANY STATEMENTS : OBJECT FILE FULL

                 The  following  messages are not considered faults, but
              may serve to indicate logical errors in the program.
              ACCESS                   The current statement  can  never
                                       be executed.  This can indicate a
                                       misplaced     label    or    jump
                                       statement.
              WARNING NOP INSERTED     The same routine has been  called
                                       twice  in  succession  without an
                                       evoke  between  the  calls.   The
                                       compiler   has  inserted  a  %NOP
                                       statement.
              WARNING EVOKE INSERTED   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.
              OVERFLOW MEANINGLESS WITH TWO GPAS ON BUS
                                       The combined output of  two  GPAs
                                       on   the   same  Bus  drives  the
                                       Overflow  flag  in  a   permanent
                                       state of SET.
                                       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.


                               COMPILER ERROR MESSAGES

                 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:
              CANNOT CREATE OBJECT FILE
                                       The  named  object file cannot be
                                       created  for  some  reason.   The
                                       usual reasons are:
                                       FILE INDEX FULL
                                       INVALID FILE NAME
                                       NO PERMISSION


                            SIMULATION OF ARTHUR PROGRAMS

                 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 .
                 The  program  takes  as  its  simulation data any valid
              ARTHUR object file, and accepts  debugging  commands  from
              the user's console.
              The simulator is called by the command:
                          SAM (OBJECT FILE NAME/ INPUT DATA)
                 If  the  object  file  name is omitted the default file
              SS#ARTH is assumed, input is from the teletype.
              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).
                 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.
                 The  simulation  is terminated and the user returned to
              EMAS command level by the statement:
                                  %ENDOFSIM
              The message.
                                  #CLOSE
              is output to indicate the termination of the program run.



                               COMMAND LANGUAGE



          STARTING THE SIMULATION

              %GO  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.
                      The process of simulation will proceed  until  one
                   of the following events take place:
                        a)  The simulator encouters a 'stop' instruction
                        generated by the ARTHUR  statement  %STOP.   The
                        simulation will be halted, and the message:
                        STOPPED AT LINE nn
                        will  be  printed,  where  nn  is  the statement
                        number on the ARTHUR program listing,  at  which
                        the %STOP statement occurred.
                        N.B.   The %ENDOFFILE statement also generates a
                        'stop'.
                        The simulator then prompts  the  user  for  more
                        commands and simulation can only be restarted by
                        use of the %GO command.
                        b)  The simulator hits a breakpoint.   There are
                        three types of  breakpoint  that  can  halt  the
                        simulator (also see below):
                                  1) A programmed breakpoint, set by the
                                  ARTHUR statement %BREAKPOINT e.g.
                                       %BREAKPOINT XANADU
                                  When   the   simulator  executes  this
                                  statement,  it  will  halt  with   the
                                  message:
                                       BREAKPOINT XANADU
                                  2)  A  'statement'  breakpoint, set by
                                  using the %BREAK command (see  below),
                                  the message typed is:
                                       BREAKPOINT LINE (N)
                                  where  (N)  is the statement number at
                                  which the breakpoint had been set.
                                  3) A conditional breakpoint,set by the
                                  '?' command (see below) The  simulator
                                  will output a message of the form:
                                  (NAME-1) (CONDITION SATISFIED)
                                     ...       ..............
                                     ...       ..............
                                  (NAME-n) (CONDITION SATISFIED)
                                  BREAKPOINT LINE nn
                                  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.
                           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).
                        c) The simulator finds a  design  error.   There
                        are two errors that can be found:
                                  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.
                                  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.
                        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.
                        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.
              %CONTINUE (REPEAT COUNT)
                        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.
                           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.

                           Alternative form to %CONTINUE is

                                  : (REPEAT COUNT)


          SETTING AND REMOVING BREAKPOINTS

                 As mentioned above there are three types of  breakpoint
              available  to  a  user,  and there are commands to set and
              remove all three types:
                   a)   PROGRAM BREAKPOINTS
                        These are  breakpoints  set  up  in  the  user's
                        program  with  the  ARTHUR statement %BREAKPOINT
                        e.g.
                                  %BREAKPOINT ERROR1
                        and are, therefore, an  intrinsic  part  of  the
                        simulated  program, until removed by editing and
                        recompiling the source.   However the  execution
                        of the command:
                                  %IGNORE (NAME LIST)
                        will  cause  the  simulator  to  pass  over  the
                        breakpoints named in the list e.g.
                                  %IGNORE FRED, ERROR 1, XANADU
                        If a name given in the list is not a  breakpoint
                        name the message:
                             NOT A BREAKPOINT [NAME]
                        will be output.
                           If  the  list of names is omitted altogether,
                        every programmed  breakpoint  will  be  ignored,
                        thus:
                                  %IGNORE
                        The  command  %REPLACE  (NAME LIST) reverses the
                        effect of %IGNORE:
                                  %REPLACE FRED, ERROR1, XANADU
                        If  the  name  list  is  omitted,  all   program
                        breakpoints will be reinstated.
                   b) STATEMENT BREAKPOINTS
                           These are set using the command:
                                  %BREAK (LINE NUMBER LIST)
                        e.g.
                                  %BREAK 6,9,1
                        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.
                           To remove these breakpoints the command %FREE
                        is used which has the same format as %BREAK e.g.
                                  %FREE 6,9,1
                                  %FREE
                   c) CONDITIONAL BREAKPOINTS
                           These are set using a command of the form:
                                  ? (CONDITION LIST)
                        where (CONDITION LIST) is a list  of  statements
                        in one of the following formats:
                                  [NAME]
                                       a  register  or  flag name alone,
                                       which will cause the simulator to
                                       trap  when  the  named   location
                                       changes  from  its  present value
                                       e.g.
                                       ?X_A
                                       ?FLAG1
                                  [NAME] (OPERATOR) (CONSTANT)
                                       The simulator will halt when  the
                                       relationship,   defined   by  the
                                       comparator,  between  the   given
                                       constant  and  the named location
                                       becomes true.
                                       Valid comparators are:
                                       =  equality 
                                       \= inequality 
                                       >  greater than 
                                       >= greater than or equal to 
                                       <  less than 
                                       <= less than or equal to 
                                  e.g. ?X_A < 78, X_B >= 345
                                     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.
                                  N.B.  The '#' symbol is not used since
                                  it creates ambiguities with the use of
                                  scratchpad memory names.
                           The  %CANCEL  command  is  provided  for  the
                        removal  of  conditional  breakpoints,  and  its
                        format has two forms:
                                  %CANCEL (NAME LIST)
                                       remove  conditional breaks set on
                                       the locations named e.g.
                                       %CANCEL X_A,LINK_PF,F,X_B
                                  %CANCEL
                                       remove all conditional traps
                           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).
                           The command %TRAPS is provided to  print  out
                        status    information    about   statement   and
                        conditional  breaks  currently  set  up  in  the
                        system.


          EXAMINING THE CONTENTS OF REGISTERS AND FLAGS

                      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) #(NAME LIST)
                        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.
                           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').
                           Special facilities exist  for  examining  the
                        contents  of  '%MEMORY'  or '%ROM' modules, as a
                        large number of locations are involved.
                           The facilities are:
                                  1) Specifying the name of the  module,
                                  e.g.   M,  will  print the contents of
                                  the module's memory address register.
                                  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.
                                  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).
                                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.
                                The following examples of the use of the
                             '#'   command  assume  that  the  following
                             declarations have been given in the  ARTHUR
                             program:
                                  %GPA X
                                  %MEMORY M(1K)
                                  %SINT LINK
                                  #X_A,X_B
                                  This  will print out the values of the
                                  'A' and 'B' registers of  the  General
                                  Purpose   Arithmetic   Unit   'X',  on
                                  seperate lines, thus:
                                  X_A 89
                                  X_B 67
                                  #X,M, [M], LINK_PF , [M:567]
                                  This will print out the following text
                                  (for example):
                                  X    89 67
                                  M    34
                                  M    34[1236]
                                  LINK_PF   SET
                                  M    567 [6379]
                        b) %DUMP (DESTINATION)
                           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.
                                       %DUMP FRED
                                       %DUMP .LP
                                       %DUMP
                           The   printout  can  be  terminated  with  an
                        interrupt and string 'ENOUGH'.


          ALTERING REGISTER AND FLAGS

                      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.
                   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.
                                  X_A <-23
                                  Y_OUT <- 16_FA32
                      A special command is provided to zero the bus  and
                   set the DZ flag:
                                  %CLEARBUS
                      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:
                                  %SET F1
                                  %CLEAR F1,F2
                                  %COMPLEMENT F1,F2
                      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.


          OTHER COMMANDS

                   %RADIX nn
                        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.
                        e.g.
                                  %RADIX 16
                        changes the base from 10 to 16 (or from 8 to 14,
                        if the base had been previously set to 8).
                        N.B.
                                  1) Values of the base greater than ten
                                  may invalidate some of the names  that
                                  a user has available!
                                  2) Note that when the base is changed,
                                  ALL constant transactions have changed
                                  base.  Therefore after the command:
                                       %RADIX 16
                                  to return to base 10 the command:
                                       %RADIX A
                                  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:
                                       %RADIX 16
                                       Y_B<-A_67
                                       will give the decimal value 67 to
                                       Y_B.
                           Special  words  can  be given after %RADIX to
                        specify Hexadecimal, Decimal, Octal and Binary -
                        %HEX, %DEC, %OCT, %BIN
                   %TRACEON (destination)
                        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:
                                  %TRACEOFF
                   %FULL/%QUIET
                        When the system executes  a  %WAIT  statement  a
                        message of the form:
                                  WAITING UNTIL FRED
                        or        WAITING WHILE P
                        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.
                        The printing of these messages may be  inhibited
                        by the use of the command:
                                  %QUIET
                        and may be reinstated by the command:
                                  %FULL
                   %INPUT (SOURCE)
                        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.
                   %TIME
                        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.


          ERROR MESSAGES

                      Apart from the error  messages  mentioned  in  the
                   various  sections  above, the system produces several
                   other messages:-

                        a) A command error indication - A question  mark
                        is  output  following  a  command that cannot be
                        understood, or that is invalid:

                                  :%GRUNGE
                                  ?
                                  :

                        However the system will  also  fault  undeclared
                        names, thus:

                                  :#X,Y,P
                                  ?  NAME #X,Y,P
                                             !
                                  :

                        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.

                        b) Runtime errors - these are nine in number:
                             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.
                             2) OVERFLOW , this  occurs  when  a  number
                             greater  than 32767 or less than - 32768 is
                             generated by an arithmetic operation.
                             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.
                             4) LABEL NOT SET, normally a  branch  label
                             for which the calculated value has no label
                             with that index.
                             5)  REFERENCING  UNUSED  NAME, treated as a
                             syntax fault the simulator effectively does
                             not recognise that name.
                             6) OUTPUT USED AS INPUT,the buffer for some
                             I/O modules is being misused.
                             7) INPUT USED AS OUTPUT, same as 6.
                             8) SPURIOUS BUFFER, same as 6 and 7.
                             9) SPURIOUS DESTINATION, unknown  error  in
                             an  arithmetic expression most likely cause
                             is coruption of the object file.

                      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.


                              WOMBLE: THE WIRING PROGRAM

                 WOMBLE takes the output from  ARTHUR  and  outputs  the
              information needed to build the PDP-16 hardware.
              The program is run using the command:
                                  WOMBLE(OBJECTFILE/ LISTING FILE)
              If a null file name is given the default files chosen are:
                   OBJECT         SS#ARTH
                   LISTING        .TT
                 See Appendix 3 for a sample output corresponding to the
              ARTHUR program given in Appendix 2.


                                    OUTPUT FORMAT

                 The output produced by WOMBLE is in three main parts:

              i)   DECLARED MODULES
                   A listing of the control and data modules declared in
                   the ARTHUR program with their associated positions on
                   the control and data buses.

              ii   CONTROL MODULES
                   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.

              iii  WIRING LISTS
                   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.
                   A pin is specified by a four character code, with the
                   characters having the meanings:
                   1    The lateral position as a hexadecimal constant.
                   2    The  vertical  rack  number  as  a letter in the
                        range A-D.
                   3    The pin position in that slot as a letter in the
                        range A-V .
                   4    The side of the slot required: 1 or 2
                   For example: Pin 4AV2 is the V2  pin  of  the  fourth
                   slot in the top rack.
                   The  positions  of  the modules described in i and ii
                   above confirm to 1 and 2 above e.g.
                        NOP 5C
                   specifies a NO-OPERATION card in the  fifth  slot  of
                   the third rack.

                 The  control  bus  must be mapped across from rack B to
              rack C (and rack D if used) , by connecting pins:
              8BA1, 8BB1, 8BC1, 8BD1, 8BE1   TO
              8CA1, 8CB1, 8CC1, 8CD1, 8CE1   (AND
              8DA1, 8DB1, 8DC1, 8DD1, 8DE1)

              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.

                 The  Bus  Sense  module is normally assigned to slot OB
              and will require the following wiring:

                   AUTO/MANUAL SWITCH  connected to OBE2
                   START PULSER        connected to OBJ1
                   SINGLE STEP PULSER  connected to OBH1

              A RESET pulser should be connected to the B1  pin  of  the
              control bus.
              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.


                                SPECIAL POINTS TO NOTE

              1    Transfer registers must be grounded on pins -BN1  and
                   -BP1.

              2    Flags must be grounded on pins --D2, --E2, and --S1

              NOTE:  that  at the time of writing there is no ground pin
              provided on the Departmental patchboards.


                              FLO: THE FLOWCHART PROGRAM

                 FLO takes as input the lists  produced  by  WOMBLE  and
              converts  them  into flowcharts which give an overall view
              of the system being designed.

              FLO may be called using the command:

                                  FLO(INPUT FILE/ OUTPUT FILE)

              The default assumptions are:-
                   INPUT          .TT
                   OUTPUT         .TT