PROGRAM ERLANG C C This is the root module of the traffic analysis program C ERLANG, which solves a number of blocking, queuing, and C occupancy problems using the Erlang formulas. C C B. Z. Lederman I.T.T. World Communications C C Revised 18-Nov-82 C REAL*8 QUANT LOGICAL*1 ANS C WRITE (5, 10) 10 FORMAT ('0 This program solves problems using the Erlang', 1' blocking formulas' / 1X ) 15 WRITE (5, 20) 20 FORMAT ('0 Enter the factor you want to find:' / 1'$ TRUNKS, INPUT, BLOCKING, TRAFFIC, OVERFLOW, QUEUE or PROB: ') READ (5, 25, END=1800) QUANT 25 FORMAT (A8) C C Look for a match and call the proper section. C IF (QUANT .EQ. 'BLOCKING') CALL ERLBLO IF (QUANT .EQ. 'TRUNKS' ) CALL ERLTRU IF (QUANT .EQ. 'TRAFFIC' ) CALL ERLTRA IF (QUANT .EQ. 'INPUT' ) CALL ERLINP IF (QUANT .EQ. 'QUEUE' ) CALL ERLQUE IF (QUANT .EQ. 'PROB' ) CALL ERLPRO IF (QUANT .EQ. 'OVERFLOW') CALL ERLOVE C C Other factors may be added here. C IF (QUANT .EQ. 'STOP' ) GO TO 1800 IF (QUANT .EQ. 'EXIT' ) GO TO 1800 IF (QUANT .EQ. 'END' ) GO TO 1800 C ANS = 'N' 1700 WRITE (5, 1710) 1710 FORMAT (1X /'$ Another Erlang problem [Y/N] ?: ') READ (5, 1720, END=1800) ANS 1720 FORMAT (A1) IF ((ANS .EQ. 'Y') .OR. (ANS .EQ. 'y')) GO TO 15 C 1800 CALL EXIT C END