 
      FOREST was a preprocessor for FORTRAN that allowed FORTRAN programs to be defined as though written in a structured programming language.
At Atlas, the preprocessor was redefined in a translator writing system called META II.
FOREST, a structured FORTRAN preprocessor, is available to users and is described in a later document. The complete FOREST program is written in FORTRAN and contains a number of facilities not available in the system defined in META. The main purpose of the META implementation is to illustrate the use of the system as a preprocessor.
The standard FORTRAN language is enhanced by the following constructs:
  .IF <(condition)> .THEN
    <statements> 
  .ENDIF
  .IF <(condition)> .THEN
  <statements> 
  .ELSE 
  <statements> 
  .ENDIF
  .WHILE <(condition)> 
  <statements> 
  .ENDWH
  .SWITCH(I,3) 
  .CASE(l) 
  <statements> 
  .CASE(2) 
  <statements> 
  .CASE(3) 
  <statements> 
  .ENDSW
 .LOOP 
 <statements> 
 .EXITIF <(condition)> 
 <statements> 
 .EXITIF
 <(condition)>
 .ENDLP
 .CYCLE 1=1,10 
 <statements> 
 .ENDCY
 .CYCLE I=1,10 
 <statements>
 .EXITIF <(condition)> 
 <statements> 
 .ENDCY
 .CYCLE 1=1,10 
 <statements> 
 .EXITIF <(condition)> 
 <statements> 
 .REPEAT 
 <statements> 
 .ENDCY
 .WRITE(l, [215]) I,J
         Most of these constructs are self=evident. The EXITIF construct may appear several times in a LOOP or CYCLE. The .REPEAT facility in the .CYCLE construct allows a set of statements to be defined which are obeyed assuming the cycle is completed without jumping out by an EXITIF command. The EXITIF always jumps to the statement following the ENDCY command.
Each FOREST routine finishes with a .END statement and the set of FOREST routines is terminated by a .FINISH command. An example of a FOREST program and the preprocessed FORTRAN code is given below:
      SUBROUTINE FRED
C
C  IF
      .IF(A .GT. B) .THEN 
      C=D 
      .ENDIF
C IF THEN ELSE C
      .IF(E .GT. F) .THEN
      X=l 
      .ELSE 
      Y=l 
      .ENDIF
C WHILE
 
      .WHILE(A .GT. B) 
      A=A-B 
      .ENDWH
C SWITCH 
      .SWITCH(I,3) 
      .CASE (1) 
      A=B 
      .CASE(2) 
      A=C 
      .CASE(3) 
      A=D 
      .ENDSW
       
C LOOP 
      .LOOP 
      A=B 
      .EXITIF(G .GT. H) 
      G=G+B 
      .ENDLP
      
C CYCLE 
      .CYCLE 1=1,7,2 
      A=A+I 
      .EXITIF(H .GT 9.0) 
      .REPEAT 
      H=0.0 
      .ENDCY 
C WRITE 
      .WRITE(l, [215]) I,J C 
C END 
      .END 
      .FINISH  
         The preprocessed code for the above program is:
      SUBROUTINE FRED
C IF
      IF(.NOT. (A .GT. B) )GOTO 2001 
      C=D 
 2001 CONTINUE
 
C IF THEN ELSE 
      IF ( .NOT (A .GT. B ))GOTO 2002
      X=1
      GOTO 3001
 2002 CONTINUE
      Y=1
 3001 CONTINUE
C WHILE
 2003 CONTINUE
      IF(.NOT. (A .GT. B) GOTO 3002
      A=A-B
      GOTO 2003
 3002 CONTINUE
C SWITCH
      GOTO(2004,2005,2006),I
 2004 CONTINUE
      A=B
      GOTO 3003
 2005 CONTINUE
      A=C
      GOTO 3003
 2006 CONTINUE
      A=D
      GOTO 3003
 3003 CONTINUE
C LOOP
 2007 CONTINUE
      A=B
      IF(G .GT. H)GOTO 3004
      G=G+B
      GOTO 2007
 3004 CONTINUE
C CYCLE
      DO 2008 I=1,7,2
      A=A+I
      IF(H .GT. 9.0)GOTO 3005
 2008 CONTINUE
      H=0.0
 3005 CONTINUE
C WRITE
      WRITE(1,2009) I,J
 2009 FORMAT(2I5)
C END
      END
         The FOREST preprocessor is defined by the META program stored in FRSTDF:
.INIT ' 2 3' TABSET=6 CRIN=187 .INITEND
.SYNTAX FOREST
FOREST= $ (.NOT ' .FINISH' .BUT ROUTINE) ;
ROUTINE= $ (.NOT '.END' .BUT STMT) ';' [*T ' END' % ] ;
STMT = .COMNST [*B % ] / .CONTST [*B % ] / 
       .LABEL ( 
       '.IF('    [ ' ' * ] IFST    /
       '.SWITCH('[ ' ' * ] SWST /
       '.WHILE(' [ ' ' * *T 'CONTINUE' % ] WHST /
       '.LOOP'   [ ' ' * *T 'CONTINUE' % ] LPST /
       '.WRITE(' [ ' ' * ] WRST /
       '.READ('  [ ' ' * ] RDST /
       '.CYCLE'  [ ' ' * ] CYST /
       'FORMAT'  [ ' ' * ] FMST /
       'CONTINUE' ';' [' ' * *T 'CONTINUE' % ] /
       ['  ' *] . ID FOST )  /
       ( '.IF'       IFST    /
         '.SWITCH('  SWST    /
         '.WHILE('   WHST    /
         '.LOOP'     LPST    /
         '.WRITE('   WRST    /
         '.READ('    RDST    /
         '.CYCLE'    CYST    /
         .ID FOST       ) ;
IFST =  ..'.THEN' ';' [*T 'IF(.NOT.(' * ')GOTO ' *1 %]
        $STMT
        ( '.ENDIF' ';' [ ' ' *1 *T 'CONTINUE' % ] /
        '.ELSE' ';' [*T 'GOTO ' *2 %] [ ' ' *1 *T 'CONTINUE' % ]
        $STMT '.ENDIF' ';' [' ' *2 *T 'CONTINUE' % ] ) ;
        
SWST =  .ID [*->1] ',' .NUMBER ')' ';'
        [*T 'GOTO(' *1 .. '),' *<-1 * % ]
        $ ( '.CASE(' .NUMBER ')' ';' [ ' ' *1+ *T 'CONTINUE' %]
        $ STMT [ *T 'GOTO ' *2 % ])
        '.ENDSW' ';' [ ' ' *2 *T 'CONTINUE' %];
        
WHST =  ..';' [ ' ' *1 *T 'CONTINUE' % *T 'IF(.NOT.(' *B
        ')GOTO ' *2 % ]
        $ STMT
        '.ENDWH' ';' [*T  'GOTO ' *1 %  ] [ ' ' *2 *T 'CONTINUE' % ] ;
LPST =  ';' [ ' ' *1 *T 'CONTINUE' % ] 
        $ ( '.EXITIF(' ..';' [*T 'IF(' *B 'GOTO ' *2 %] /STMT)
        '.ENDLP' ';' [*T 'GOTO ' *1 % ' '  *2 *T 'CONTINUE' % ] ;
WRST = (.ID/.NUMBER) [*T 'WRITE(' * ',' *1 ] ','
        '[' .. ']' [*->2] ..';' [*B %]
        [*1 *T 'FORMAT(' *<-2 * ')' % ] ;
RDST = (.ID/.NUMBER) [*T 'READ(' * ',' *1 ] ','
        '[' .. ']' [*->2] .. ';' [*B %]
        [*1 *T 'FORMAT(' *<-2 * ')' % ] ;
CYST = ..';' [*T 'DO' ' ' *1 *B 5 ]
       $( '.EXITIF(' ..';' [*T 'IF(' *B 'GOTO ' *2 %] / STMT)
       ('.REPEAT' ';' [  ' ' *1 *T 'CONTINUE' % ] $ STMT
       '.ENDCY' ';' [ ' ' *2 *T 'CONTINUE' % ] /
       '.ENDCY' ';'  [' ' *1 *T 'CONTINUE' % ' ' *2 *T 'CONTINUE' % ] ) ;
FOST = [*T *]..';' [ *B % ] ;
FMST = [*T 'FORMAT'] ..';' [*B %] ;
.END
         A macro called FOREST is available to preprocess and compile FOREST programs. For example, to compile the FOREST program FRED requires:
$FOREST FRED OK,SEG #METF GO COMMAND: BININ FRSTBN COMMAND: EXECTE FRED COMMAND: FREDFL FINISH ****STOP OK,FTN FREDFL GO FREDFL OK, DELETE FREDFL GO OK, CO TTY OK,
The user just types the first line $FOREST FRED. The system can be used as an alternative to FOREST. It runs about three times faster and does not pollute the file store with numerous files. Its main drawback is that error handling is less comprehensive than FOREST. Note also the notational difference in the way the EXITIF construct is written. The equivalent FOREST command is:
.IF (<condition>) .EXIT