massn.f 17 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580
  1. PROGRAM MASS
  2. C This program computes optimum mass entries in the bathtub model
  3. C
  4. C The main program and subroutine are in this file. Routines from
  5. C reading dat input and displaying output are in put in file
  6. C "auxiliary.f".
  7. C
  8. C The main program call a first subroutines to read data input and then
  9. C calls the subroutine that computes the optimum entry rates.
  10. C
  11. C A SUMMARY OF THE SUBROUTINES
  12. C
  13. C UTIL : computes the objective function
  14. C D_UTIL : computes the gradient of the objective function
  15. C CONS : computes the value of the constraint. This version
  16. C has one constraint (the sum of the entry rates is equal to
  17. C one
  18. C D_CONS : computes the gradient of the constraint
  19. C SPLITLINE : for input, it takes the current approximation line with
  20. C respect variable m and breaks and evenly subdivides the largest
  21. C intervals into two intervals. Bu doing so we intend to get
  22. C a smoother approximation of the solution
  23. C
  24. C For the optimization step we use the fortran version IPOPT (the large-scale
  25. C optimization package):
  26. C
  27. C https://www.coin-or.org/Ipopt/ipopt-fortran.html
  28. C
  29. C TO RUN THIS PROGRAM
  30. C - install IPOPT (it requires LAPACK and BLAS)
  31. C - compile through a command like
  32. C gfortran -o massn massn.f auxiliary.f -llapack -lblas -lipopt
  33. C by providing the correct path to the libraries
  34. C - set data in file "params.dat"
  35. C - run the program
  36. C ./massn
  37. C
  38. C The process is little tedious, in particular for IPOPT.
  39. C
  40. C
  41. C KNOWN ISSUES AND POSSIBLE IMPROVEMENTS
  42. C
  43. C 1. This version does not explicitly set constraint on :
  44. C - last arrival time should be smaller than TMAX
  45. C - traffic density should be smaller than road jam capacity
  46. C and relies on the optimization to carry on implicitly these
  47. C constraints. This does not occur in all cases and fine tuning of
  48. C parameter M0, MBAR and ITMAX is frequently required for convergence.
  49. C
  50. C 2. M0 and MBAR are fixed. It is suggested to provide a large window in
  51. C the start. The solution will entail a first phase where without
  52. C entries. Similarly it will entail a last phase where entries are
  53. C equal to zero. A new of the computation can then be considered by
  54. C zooming a new window with higher M0 and smaller MBAR. This process
  55. C can be repeated until satisfactory values are obtained.
  56. C
  57. C 3. The Hessian is not provided to the optimizer. It uses finite
  58. C difference to approximate it (IQUASI = 6, in the options passed to
  59. C IPOPT).
  60. C
  61. C 4. The program does not produce any graphical output. For instance,
  62. C output table can be exported to a text file (redirect the output
  63. C using the unix standard "./massn > outfile") and then use gnuplot
  64. C or another program to make the plots (after deleting useless
  65. C lines).
  66. C
  67. C These issues will be addressed in the updates
  68. C
  69. C
  70. C NOTATION THROUGH AN EXAMPLE
  71. C - number of entry (and exit) points: N = 10
  72. C - number of entry points before within a cycle: NL = 2
  73. C - total number of breakpoints: N + NL = 12
  74. C
  75. C (0) t1 t2 t3 t4 t5 t6 t7 t8 t9 t10 t11
  76. C (1) P----S-------P----S-------P----S-------P-----S-------P----S-----P--------S---
  77. C
  78. C (2) 0 Mb-4L L Mb-3L 2L Mb-2L 3L Mb-L 4L Mb (4+1)L Mb+L
  79. C
  80. C (3) 1 2 3 4 5 6 7 8 9 10 11 12
  81. C
  82. C (4) e1 e2 e3 e4 e5 e6 e7 e8 e9 e10
  83. C
  84. C (5) e1 e2 e3 e4 e5 e6 e7 e8 e9 e10
  85. C
  86. C (6) T1 T2 T3 T4 T5 T6 T7 T8 T9 T10 T11 T12
  87. C
  88. C
  89. C (0) t_i clock-time from m_i to m_(i+1)
  90. C (1) Primary (P) and secondary (S) breakpoints
  91. C (3) indices for variable m
  92. C (4) entries at each breakpoint m_i (at each breakpoint)
  93. C (5) exits at each breakpoint m_i (at each breakpoint)
  94. C (6) T_i clock-time at mile m_i
  95. IMPLICIT NONE
  96. DOUBLE PRECISION UT
  97. DOUBLE PRECISION R0, R1, S0, S1, VF, K, L, P, TMAX
  98. DOUBLE PRECISION M0, MBAR
  99. INTEGER ITMAX
  100. COMMON /MODELPARAM/ R0, R1, S0, S1, VF, K, L, P, TMAX
  101. COMMON /OTHERPARAM/ M0, MBAR, ITMAX
  102. C Read parameters from file "params.dat"
  103. CALL READPARAM("params.dat")
  104. PRINT '(11F9.2)', R0,R1,S0,S1,VF,K,L,P,TMAX,M0,MBAR
  105. C Call subroutine UTILOPT to compute the optimum entry rates
  106. CALL UTILOPT ( M0, MBAR , UT, ITMAX)
  107. C Print the value of the objective function
  108. PRINT*, UT
  109. END
  110. SUBROUTINE UTILOPT (M0,MBAR,F,ITMAX)
  111. C Computes entry masses at points m_i that maximize aggregate
  112. C utility given that M0 and MBAR are fixed
  113. IMPLICIT NONE
  114. DOUBLE PRECISION M0, MBAR
  115. INTEGER I, NCYC, NL, NMAX, IT, ITMAX
  116. PARAMETER (NMAX=10000)
  117. DOUBLE PRECISION U
  118. C Parameters of the problem
  119. DOUBLE PRECISION R0, R1, S0, S1, VF, K, L, P, TMAX
  120. C Variable definition for IPOPT
  121. INTEGER LRW, LIW
  122. PARAMETER ( LRW = 10000, LIW = 10000)
  123. INTEGER IW(LIW)
  124. DOUBLE PRECISION RW(LRW)
  125. DOUBLE PRECISION IPOPT
  126. INTEGER N, M
  127. DOUBLE PRECISION LAM(NMAX)
  128. DOUBLE PRECISION C(NMAX)
  129. DOUBLE PRECISION G(NMAX)
  130. DOUBLE PRECISION E(NMAX)
  131. INTEGER NLB, NUB
  132. INTEGER ILB(NMAX), IUB(NMAX)
  133. DOUBLE PRECISION BNDSL(NMAX), BNDSU(NMAX)
  134. DOUBLE PRECISION V_L(NMAX), V_U(NMAX)
  135. DOUBLE PRECISION DAT (NMAX)
  136. INTEGER IDAT (NMAX)
  137. INTEGER NARGS
  138. DOUBLE PRECISION ARGS (50)
  139. CHARACTER*20 CARGS(50)
  140. INTEGER IERR, ITER
  141. DOUBLE PRECISION F
  142. EXTERNAL UTIL, CONS, D_UTIL, D_CONS
  143. EXTERNAL EV_H_DUMMY,EV_HLV_DUMMY, EV_HOV_DUMMY, EV_HCV_DUMMY
  144. C End of definition of IPOPT variables
  145. COMMON /MODELPARAM/ R0, R1, S0, S1, VF, K, L, P, TMAX
  146. NCYC= FLOOR ( (MBAR-M0) / L )
  147. N = 2 * ( NCYC+ 1 )
  148. IF(MBAR.GT.L) THEN
  149. NL = 2
  150. ELSE
  151. NL =1
  152. ENDIF
  153. IDAT(1) = NCYC
  154. IDAT(2) = NL
  155. C Compute the breakpoints. This is the first approximation that will be
  156. C used.
  157. DO 10, I = 1, NCYC+ NL
  158. C Primary breakpoints
  159. DAT(2*I-1) = M0 + DBLE( I - 1 ) * L
  160. C Secondary breakpoints. Notice that :
  161. C MBAR + L - NCYCL + (I-1) * L = MBAR - (NCYC-I) * L
  162. DAT(2*I) = MBAR - DBLE ( NCYC- I + 1 ) * L
  163. 10 CONTINUE
  164. C Compute a simple initial solution
  165. DO 20, I = 1, N
  166. E(I) = ( DAT(I+1) - DAT(I) ) / ( ( NCYC + 1 ) * L )
  167. 20 CONTINUE
  168. C Set algorithmic parameters (for IPOPT)
  169. NARGS = 1
  170. ARGS(1) = 1.D-8
  171. CARGS = 'dtol'
  172. C MAIN LOOP
  173. C It starts by optimizing over the initial breakpoints, then
  174. C uses the obtained solution to increase the number of approximation
  175. C points. Variable ITMAX indicates the number of iterations (how many
  176. C time the approximation line) is subdivided.
  177. IT = 1
  178. 100 CONTINUE
  179. C Number of variable with lower bounds
  180. NLB = N
  181. C Indices of variables with lower bounds
  182. DO 1, I = 1, N
  183. ILB(I) = I
  184. 1 CONTINUE
  185. C Values of lower bounds
  186. DO 2, I = 1, N
  187. BNDSL(I) = 1.0D-6
  188. 2 CONTINUE
  189. C Number of variables with upper bounds
  190. NUB = 0
  191. C i.e. no uppers bounds on the entry rates
  192. C There is only one constraint on the problem (the sum of all entry
  193. C rates is one)
  194. M = 1
  195. PRINT* , N, NL, IT
  196. C Call IPOPT (the optimizer)
  197. F = - IPOPT(N, E, M, NLB, ILB, BNDSL, NUB, IUB, BNDSU, V_L, V_U,
  198. 1 LAM, C, LRW, RW, LIW, IW, ITER, IERR, UTIL, CONS, D_UTIL,
  199. 1 D_CONS, EV_H_DUMMY, EV_HLV_DUMMY, EV_HOV_DUMMY, EV_HCV_DUMMY,
  200. 1 DAT, IDAT, NARGS, ARGS, CARGS)
  201. PRINT '(A20,F9.3)' , 'Value of objective function : ', F
  202. PRINT '(F9.5)', SUM(E)
  203. IT = IT + 1
  204. IF(IT.LE.ITMAX) THEN
  205. CALL SPLITLINE(N, DAT,NL,E,0.80D0)
  206. IDAT(2) = NL
  207. GOTO 100
  208. ENDIF
  209. C Print the last solution obtained
  210. CALL STATDES(N, E, DAT, IDAT)
  211. RETURN
  212. END
  213. C ======================================
  214. C Computation of the objective function
  215. C (aggregate utility)
  216. C ======================================
  217. SUBROUTINE UTIL(N, E, U, DAT, IDAT)
  218. IMPLICIT NONE
  219. INTEGER I, N, NL, NMAX
  220. PARAMETER (NMAX=10000)
  221. DOUBLE PRECISION U, E(N)
  222. DOUBLE PRECISION DAT(NMAX)
  223. INTEGER IDAT(NMAX)
  224. C Variables used for intermediate computations
  225. DOUBLE PRECISION V(N+IDAT(2)-1), T(N+IDAT(2)-1), TT(N+IDAT(2))
  226. DOUBLE PRECISION UE, UX
  227. DOUBLE PRECISION SUME
  228. C Parameters of the problem
  229. DOUBLE PRECISION R0, R1, S0, S1, VF, K, L, P, TMAX
  230. COMMON /MODELPARAM/ R0, R1, S0, S1, VF, K, L, P, TMAX
  231. NL = IDAT(2)
  232. C Compute travel speed, travel time and clock-time on each interval
  233. I=1
  234. TT(I) = DAT(I) / VF
  235. SUME=E(I)
  236. V(I) = VF * ( 1.0D0 - P * SUME / K )
  237. T(I) = ( DAT(I+1) - DAT(I) ) / V(I)
  238. C PRINT*, V(I), VF, P, K, SUME,T(I),TT(I),DAT(2)- DAT(1)
  239. TT(I+1) = TT(I) + T(I)
  240. DO 1, I = 2, N + NL - 1
  241. IF(I.LE.NL) THEN
  242. SUME = SUME + E(I)
  243. ELSEIF (I.LE.N) THEN
  244. SUME = SUME + E(I) - E(I-NL)
  245. ELSE
  246. SUME = SUME - E(I-NL)
  247. ENDIF
  248. V(I) = MAX(0.D0,VF * ( 1.0D0 - P * SUME / K ))
  249. T(I) = ( DAT(I+1) - DAT(I) ) / V(I)
  250. TT(I+1) = TT(I) + T(I)
  251. C PRINT '(I5,5F9.3)', I,DAT(I),V(I), T(I), TT(I+1), SUME
  252. 1 CONTINUE
  253. C Compute entry and exit sub-utilities
  254. UE = 0.0D0
  255. UX = 0.0D0
  256. DO 20, I = 1, N
  257. UE = UE + R0 * DLOG( R1 * TT(I ) ) * E(I) * P
  258. UX = UX + S0 * DLOG( S1 * ( TMAX - TT(I + NL))) * E(I) * P
  259. C PRINT '(2I5,4F9.3)', I, NL,TMAX,TT(I+NL),UE, UX
  260. 20 CONTINUE
  261. C AGREGATE UTILITY
  262. C Notice that we consider the opposite of the utility since we set the
  263. C problem as a minimization program
  264. U = - ( UE + UX )
  265. RETURN
  266. END
  267. C =====================================================
  268. C Computation of the gradient of the objective function
  269. C =====================================================
  270. SUBROUTINE D_UTIL( N, E, G, DAT, IDAT)
  271. IMPLICIT NONE
  272. INTEGER N, NL, NMAX
  273. PARAMETER (NMAX=10000)
  274. DOUBLE PRECISION G(N), E(N)
  275. DOUBLE PRECISION DAT(NMAX)
  276. INTEGER IDAT(NMAX)
  277. DOUBLE PRECISION D_T(N+IDAT(2)-1), D_TT(N+IDAT(2),N)
  278. DOUBLE PRECISION D_UE(N,N), D_UX(N,N)
  279. DOUBLE PRECISION V(N+IDAT(2)-1), T(N+IDAT(2)-1), TT(N+IDAT(2))
  280. DOUBLE PRECISION SUME
  281. INTEGER I, J, II
  282. C Parameters of the problem
  283. DOUBLE PRECISION R0, R1, S0, S1, VF, K, L, P, TMAX
  284. COMMON /MODELPARAM/ R0, R1, S0, S1, VF, K, L, P, TMAX
  285. NL = IDAT(2)
  286. C Compute travel speed on each interval
  287. C This step is replicated from UTIL subroutine.
  288. I = 1
  289. TT(I) = DAT(I) / VF
  290. SUME = E(I)
  291. V(I) = MAX(0.0D0,VF * ( 1.D0 - P * SUME / K ))
  292. T(I) = ( DAT(I+1) - DAT(I) ) / V(I)
  293. TT(I+1) = TT(I) + T(I)
  294. C PRINT*, V(I), VF, P, K, SUME,T(I),TT(I),DAT(2)- DAT(1)
  295. DO 1, I = 2, N + NL - 1
  296. IF(I.LE.NL) THEN
  297. SUME = SUME + E(I)
  298. ELSEIF (I.LE.N) THEN
  299. SUME = SUME + E(I) - E(I-NL)
  300. ELSE
  301. SUME = SUME - E(I-NL)
  302. ENDIF
  303. V(I) = VF * ( 1.D0 - P * SUME / K )
  304. T(I) = ( DAT(I+1) - DAT(I) ) / V(I)
  305. TT(I+1) = TT(I) + T(I)
  306. C PRINT*, V(I), VF, P, K, SUME,T(I),TT(I),DAT(I+1), DAT(I)
  307. 1 CONTINUE
  308. C Compute the derivative
  309. C
  310. C d t_i m_(i+1) - m_i vf * P
  311. C ----- = ------------- * ------
  312. C d e_i v_i^2 K
  313. C
  314. DO 10, I = 1, N + NL - 1
  315. D_T(I) = (DAT(I+1) - DAT(I))/V(I)**2 * VF*P/K
  316. 10 CONTINUE
  317. C Compute the derivative
  318. C
  319. C /
  320. C | 0 if j <= i
  321. C |
  322. C |
  323. C d T_j | d t_i d t_(j-1)
  324. C ----- = / ----- + ... + --------- if i < j <=i+NL
  325. C d e_i \ d e_i d e_(j-1)
  326. C |
  327. C |
  328. C | d T_(i+NL)
  329. C | ---------- if j > i + NL
  330. C | d e_i
  331. C \
  332. C
  333. D_TT = 0.0D0
  334. DO 20, I = 1, N
  335. DO 20, J = I+1, N+NL
  336. IF (J.LE.I) THEN
  337. D_TT(J,I) = 0.0D0
  338. ELSEIF (J.LE.I+NL) THEN
  339. DO 22, II = I, J-1
  340. D_TT(J,I) = D_TT(J,I) + D_T(II)
  341. 22 CONTINUE
  342. ELSE
  343. D_TT(J,I) = D_TT(I+NL,I)
  344. ENDIF
  345. 20 CONTINUE
  346. C IMPACTS ON ENTRY SUBUTILITIES
  347. C An increase of the entry rate at T_i increases the size of the group
  348. C itself and delays the entry time for all groups that enter at T_j with
  349. C j > i.
  350. C Users who enter at T_N do not delay the entry of any other group. The
  351. C structure of the loop automatically takes into account this case since.
  352. C Indeed, for I=N, J varies varies from N+1 to N and, then, the loop is
  353. C not executed.
  354. D_UE = 0.0D0
  355. DO 30, I = 1, N
  356. D_UE(I, I) = R0 * DLOG( R1 * TT(I) ) * P
  357. DO 30, J = I+1, N
  358. D_UE(J, I) = R0 * D_TT(J,I) / TT(J) * E(J) * P
  359. 30 CONTINUE
  360. C IMPACTS ON EXIT SUBUTILITIES
  361. C An increase of the size of the group of users entering at T_i
  362. C has two impacts: (1) it delays the arrival of all groups entering at
  363. C T_{max(1,i-(NL-1))}, including the group itself, and (2) it increases
  364. C the size of the group of those entering at T_i.
  365. D_UX = 0.0D0
  366. DO 40, I = 1, N
  367. DO 40, J = MAX(I-(NL-1), 1), N
  368. D_UX(J, I) = - S0 * D_TT(J+NL,I) / (TMAX - TT(J+NL)) * E(J) * P
  369. 40 CONTINUE
  370. DO 45, I = 1, N
  371. D_UX(I, I) = D_UX(I, I) + S0 * DLOG( S1 * (TMAX - TT(I+NL)) ) * P
  372. 45 CONTINUE
  373. C TOTAL IMPACTS (the gradient)
  374. C Notice that we compute the gradient of - UTIL since we set
  375. C the problem as a minimization program.
  376. G = 0.0D0
  377. DO 50, I = 1, N
  378. DO 50, J = 1, N
  379. G(I) = G(I) - D_UE(J,I) - D_UX(J,I)
  380. C PRINT '(7F9.3)', G(I), E(1:6)
  381. 50 CONTINUE
  382. RETURN
  383. END
  384. C =========================================
  385. C Computation of the equality constraints
  386. C In this problem, there is only one constraint
  387. C stating that the sum of all entry rates
  388. C is equal to one :
  389. C
  390. C e_1 + e_2 + .. + e_n = 1
  391. C
  392. C =========================================
  393. SUBROUTINE CONS(N, E, M, C, DAT, IDAT)
  394. IMPLICIT NONE
  395. INTEGER N, M, NMAX
  396. PARAMETER (NMAX=10000)
  397. DOUBLE PRECISION C(M), E(N)
  398. DOUBLE PRECISION DAT(NMAX)
  399. INTEGER IDAT(NMAX)
  400. DOUBLE PRECISION SUME
  401. INTEGER I
  402. SUME = 0.D0
  403. DO 10, I = 1, N
  404. SUME = SUME + E(I)
  405. 10 CONTINUE
  406. C(1) = SUME - 1.D0
  407. RETURN
  408. END
  409. C =============================================
  410. C Computation of the Jacobian of the constraint
  411. C =============================================
  412. SUBROUTINE D_CONS(TASK, N, E, NZ, A, ACON, AVAR, DAT, IDAT)
  413. IMPLICIT NONE
  414. INTEGER TASK, N, NZ
  415. INTEGER NMAX, I
  416. PARAMETER (NMAX=10000)
  417. DOUBLE PRECISION E(N), A(NZ)
  418. INTEGER ACON(NZ), AVAR(NZ)
  419. DOUBLE PRECISION DAT(NMAX)
  420. INTEGER IDAT(NMAX)
  421. IF(TASK.EQ.0) THEN
  422. NZ = N
  423. ELSE
  424. DO 10, I = 1, N
  425. AVAR(I) = I
  426. ACON(I) = 1
  427. 10 CONTINUE
  428. DO 20, I = 1, N
  429. A(I) = 1.D0
  430. 20 CONTINUE
  431. ENDIF
  432. RETURN
  433. END
  434. C =============================================
  435. C Split interval
  436. C =============================================
  437. SUBROUTINE SPLITLINE(N, M, NL, E, THR)
  438. IMPLICIT NONE
  439. C Increases the number of approximation points by breaking the largest
  440. C intervals.
  441. C N the number of entry rates, or mile-points where entry occurs
  442. C M table containing the approximation points
  443. C NL index the last element between0 and L: we have M(NL+1) = L
  444. C THR intervals with length larger than THR * X are swplit into two
  445. C intervals, where X is the the length of the largest interval
  446. INTEGER NL, N, I, J, NMAX
  447. PARAMETER (NMAX=10000)
  448. DOUBLE PRECISION M(NMAX), E(NMAX)
  449. DOUBLE PRECISION THR
  450. DOUBLE PRECISION M2(NMAX), E2(NMAX)
  451. INTEGER N2,NPTS,NL2,NTOT
  452. DOUBLE PRECISION Y(NMAX), YMAX
  453. IF(N.LT.2) THEN
  454. PRINT*, "A table of legth 2 at least is expected"
  455. STOP
  456. ENDIF
  457. IF(THR.LE.0.0D0.OR.THR.GE.1.0D0) THEN
  458. PRINT*, "THR should be between 1/2 and 1."
  459. STOP
  460. ENDIF
  461. C Compute the length of the largest interval
  462. YMAX = M(2) - M(1)
  463. DO 10, I = 1, NL
  464. Y(I) = M(I+1) - M(I)
  465. IF(Y(I).GT.YMAX) YMAX = Y(I)
  466. 10 CONTINUE
  467. C Store some values
  468. N2 = N
  469. NL2 = NL
  470. NTOT = N + NL
  471. E2 = 0.0D0
  472. C Split intervals with length higher than
  473. C THR * YMAX and update indexes
  474. J = 0
  475. DO 20, I = 1, N+NL-1
  476. IF((M(I+1)-M(I)).GT.(THR*YMAX)) THEN
  477. M2(I+J ) = M(I)
  478. M2(I+J+1) = M(I) + (M(I+1) - M(I)) / 2.0D0
  479. J = J + 1
  480. IF(I.LE.NL) THEN
  481. E2(I+J ) = E(I)
  482. E2(I+J-1) = 0.0D0
  483. NL2 = NL2 + 1
  484. N2 = N2 + 1
  485. NTOT = NTOT + 1
  486. ELSEIF(I.LT.N) THEN
  487. E2(I+J ) = E(I)
  488. E2(I+J-1) = 0.0D0
  489. N2 = N2 + 1
  490. NTOT = NTOT + 1
  491. ELSE
  492. NTOT = NTOT + 1
  493. ENDIF
  494. ELSE
  495. M2(I+J) = M(I)
  496. E2(I+J) = E(I)
  497. ENDIF
  498. 20 CONTINUE
  499. E2(N2 ) = E(N)
  500. M2(NTOT) = M(N+NL)
  501. C Set valriables to new values
  502. M = M2
  503. E = E2
  504. N = N2
  505. NL = NL2
  506. RETURN
  507. END