SUBROUTINE ERLTRU C C This module of the ERLANG program calculates the number C of servers (trunks) required to the blocking to be no more C than a given value for a given amount of traffic. C C B. Z. Lederman I.T.T. World Communications C BYTE ANS C 300 WRITE (5, 305) 305 FORMAT ( / '$ Enter Erlangs of traffic, % Blocking: ') READ (5, 310, END=260) A, BLOCK 310 FORMAT(2F10.2) C C Check for impossible data. C IF (BLOCK .GT. 100.) GO TO 810 IF (BLOCK .LE. 0.0 ) GO TO 810 C C Start with one trunk and see if the blocking is acceptable: C If not, increase the number of trunks by one and keep trying C until blocking is acceptable. C BLOCK = 0.01 * BLOCK N = 0 320 N = N + 1 BPER = ERLB(N,A) IF (BPER .LT. BLOCK) GO TO 325 C C Stop if the number of trunks gets out of hand. C IF (N .GE. 2000) GO TO 325 GO TO 320 C 325 BPER = 100. * BPER WRITE (5, 230) A, N, BPER 230 FORMAT ('0 Erlangs = ', F7.2, ', Trunks = ', I4, 1', Blocking = ', F6.2, '%' / 1X / 2'$ Another Trunks Problem [Y/N] ?: ') READ (5, 250, END=260) ANS 250 FORMAT (A1) IF ((ANS .EQ. 'Y') .OR. (ANS .EQ. 'y')) GO TO 300 C 260 RETURN C C Tell the user the data is no good. C 810 WRITE (5, 820) 820 FORMAT (' Impossible situation, please re-enter.') GO TO 300 C END