massn.f 17 KB

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