SUBROUTINE ERLOVE C C This module of the ERLANG program calculates the amount C of traffic which overflows from one group of trunks to C a second (overflow) group when the traffic presented C and either the number of trunks or the blocking of the C first group is known C C B. Z. Lederman I.T.T. World Communications C BYTE ANS C 10 WRITE (5, 20) 20 FORMAT (1X / '$ Known factors are Erlangs of traffic, and', 1' Blocking or Trunks [B/T] : ') READ (5, 30, END=900) ANS 30 FORMAT (A1) IF (ANS .EQ. 'B' .OR. ANS .EQ. 'b') GOTO 200 IF (ANS .EQ. 'T' .OR. ANS .EQ. 't') GOTO 100 WRITE (5, 35) 35 FORMAT (' Answer incorrect, please re-enter.') GOTO 10 100 WRITE (5, 40) 40 FORMAT ('$ Enter Erlangs of traffic, Number of trunks: ') READ (5, 50, END=900) A, N 50 FORMAT (F10.2, I4) BPER = ERLB(N,A) GOTO 300 C 200 WRITE (5, 210) 210 FORMAT ('$ Enter Erlangs of traffic, Blocking (%): ') READ (5, 220, END=900) A, BPER 220 FORMAT (2F10.2) BPER = 0.01 * BPER C 300 R = A * BPER ANON = A - R D = ((A / ((N + 1) - A + R)) - R) BPER = 100. * BPER C WRITE (5, 310) A, BPER, ANON, R, D 310 FORMAT ('0 Traffic = ', F6.2, ' Erlangs, Blocking = ', F6.2, 1'%, Non-Blocked = ', F6.2, ' Erlangs' / 1'0 Overflow = ', F6.2, ' Erlangs, Variance = ', F6.2 / 1X / 1'$ Another Overflow Problem [Y/N] ? ') READ (5, 30, END=900) ANS IF (ANS .EQ. 'Y' .OR. ANS .EQ. 'y') GOTO 10 C 900 RETURN C END