1 SUBROUTINE dlsode (F, NEQ, Y, T, TOUT, ITOL, RTOL, ATOL, ITASK,
2 1 ISTATE, IOPT, RWORK, LRW, IWORK, LIW, JAC, MF)
4 INTEGER NEQ, ITOL, ITASK, ISTATE, IOPT, LRW, IWORK, LIW, MF
5 DOUBLE PRECISION Y, T, TOUT, RTOL, ATOL, RWORK
6 dimension neq(*), y(*), rtol(*), atol(*), rwork(lrw), iwork(liw)
1206 DOUBLE PRECISION D1MACH, DVNORM
1209 INTEGER ILLIN, INIT, LYH, LEWT, LACOR, LSAVF, LWM, LIWM,
1210 1 mxstep, mxhnil, nhnil, ntrep, nslast, nyh,
1211 2 ialth, ipup, lmax, meo, nqnyh, nslp
1212 INTEGER ICF, IERPJ, IERSL, JCUR, JSTART, KFLAG, L, METH, MITER,
1213 1 maxord, maxcor, msbp, mxncf, n, nq, nst, nfe, nje, nqu
1214 INTEGER I, I1, I2, IFLAG, IMXER, KGO, LF0,
1215 1 leniw, lenrw, lenwm, ml, mord, mu, mxhnl0, mxstp0
1216 DOUBLE PRECISION CONIT, CRATE, EL, ELCO, HOLD, RMAX, TESCO,
1217 1 ccmax, el0, h, hmin, hmxi, hu, rc, tn, uround
1218 DOUBLE PRECISION ATOLI, AYI, BIG, EWTI, H0, HMAX, HMX, RH, RTOLI,
1219 1 tcrit, tdist, tnext, tol, tolsf, tp,
SIZE, sum, w0
1223 SAVE mord, mxstp0, mxhnl0
1234 COMMON /dls001/ conit, crate, el(13), elco(13,12),
1235 1 hold, rmax, tesco(3,12),
1236 1 ccmax, el0, h, hmin, hmxi, hu, rc, tn, uround,
1237 2 illin, init, lyh, lewt, lacor, lsavf, lwm, liwm,
1238 3 mxstep, mxhnil, nhnil, ntrep, nslast, nyh,
1239 3 ialth, ipup, lmax, meo, nqnyh, nslp,
1240 4 icf, ierpj, iersl, jcur, jstart, kflag, l, meth, miter,
1241 5 maxord, maxcor, msbp, mxncf, n, nq, nst, nfe, nje, nqu
1243 DATA mord(1),mord(2)/12,5/, mxstp0/500/, mxhnl0/10/
1254 IF (istate .LT. 1 .OR. istate .GT. 3)
GO TO 601
1255 IF (itask .LT. 1 .OR. itask .GT. 5)
GO TO 602
1256 IF (istate .EQ. 1)
GO TO 10
1257 IF (init .EQ. 0)
GO TO 603
1258 IF (istate .EQ. 2)
GO TO 200
1261 IF (tout .EQ. t)
RETURN
1271 20
IF (neq(1) .LE. 0)
GO TO 604
1272 IF (istate .EQ. 1)
GO TO 25
1273 IF (neq(1) .GT. n)
GO TO 605
1275 IF (itol .LT. 1 .OR. itol .GT. 4)
GO TO 606
1276 IF (iopt .LT. 0 .OR. iopt .GT. 1)
GO TO 607
1278 miter = mf - 10*meth
1279 IF (meth .LT. 1 .OR. meth .GT. 2)
GO TO 608
1280 IF (miter .LT. 0 .OR. miter .GT. 5)
GO TO 608
1281 IF (miter .LE. 3)
GO TO 30
1284 IF (ml .LT. 0 .OR. ml .GE. n)
GO TO 609
1285 IF (mu .LT. 0 .OR. mu .GE. n)
GO TO 610
1288 IF (iopt .EQ. 1)
GO TO 40
1292 IF (istate .EQ. 1) h0 = 0.0d0
1296 40 maxord = iwork(5)
1297 IF (maxord .LT. 0)
GO TO 611
1298 IF (maxord .EQ. 0) maxord = 100
1299 maxord =
min(maxord,mord(meth))
1301 IF (mxstep .LT. 0)
GO TO 612
1302 IF (mxstep .EQ. 0) mxstep = mxstp0
1304 IF (mxhnil .LT. 0)
GO TO 613
1305 IF (mxhnil .EQ. 0) mxhnil = mxhnl0
1306 IF (istate .NE. 1)
GO TO 50
1308 IF ((tout - t)*h0 .LT. 0.0d0)
GO TO 614
1310 IF (hmax .LT. 0.0d0)
GO TO 615
1312 IF (hmax .GT. 0.0d0) hmxi = 1.0d0/hmax
1314 IF (hmin .LT. 0.0d0)
GO TO 616
1322 IF (istate .EQ. 1) nyh = n
1323 lwm = lyh + (maxord + 1)*nyh
1324 IF (miter .EQ. 0) lenwm = 0
1325 IF (miter .EQ. 1 .OR. miter .EQ. 2) lenwm = n*n + 2
1326 IF (miter .EQ. 3) lenwm = n + 2
1327 IF (miter .GE. 4) lenwm = (2*ml + mu + 1)*n + 2
1331 lenrw = lacor + n - 1
1335 IF (miter .EQ. 0 .OR. miter .EQ. 3) leniw = 20
1337 IF (lenrw .GT. lrw)
GO TO 617
1338 IF (leniw .GT. liw)
GO TO 618
1343 IF (itol .GE. 3) rtoli = rtol(i)
1344 IF (itol .EQ. 2 .OR. itol .EQ. 4) atoli = atol(i)
1345 IF (rtoli .LT. 0.0d0)
GO TO 619
1346 IF (atoli .LT. 0.0d0)
GO TO 620
1348 IF (istate .EQ. 1)
GO TO 100
1351 IF (nq .LE. maxord)
GO TO 90
1354 80 rwork(i+lsavf-1) = rwork(i+lwm-1)
1356 90
IF (miter .GT. 0) rwork(lwm) = sqrt(uround)
1357 IF (n .EQ. nyh)
GO TO 200
1360 i2 = lyh + (maxord + 1)*nyh - 1
1361 IF (i1 .GT. i2)
GO TO 200
1372 100 uround = d1mach(4)
1374 IF (itask .NE. 4 .AND. itask .NE. 5)
GO TO 110
1376 IF ((tcrit - tout)*(tout - t) .LT. 0.0d0)
GO TO 625
1377 IF (h0 .NE. 0.0d0 .AND. (t + h0 - tcrit)*h0 .GT. 0.0d0)
1380 IF (miter .GT. 0) rwork(lwm) = sqrt(uround)
1393 CALL f (neq, t, y, rwork(lf0))
1397 115 rwork(i+lyh-1) = y(i)
1401 CALL dewset (n, itol, rtol, atol, rwork(lyh), rwork(lewt))
1403 IF (rwork(i+lewt-1) .LE. 0.0d0)
GO TO 621
1404 120 rwork(i+lewt-1) = 1.0d0/rwork(i+lewt-1)
1421 IF (h0 .NE. 0.0d0)
GO TO 180
1422 tdist = abs(tout - t)
1423 w0 =
max(abs(t),abs(tout))
1424 IF (tdist .LT. 2.0d0*uround*w0)
GO TO 622
1426 IF (itol .LE. 2)
GO TO 140
1428 130 tol =
max(tol,rtol(i))
1429 140
IF (tol .GT. 0.0d0)
GO TO 160
1432 IF (itol .EQ. 2 .OR. itol .EQ. 4) atoli = atol(i)
1434 IF (ayi .NE. 0.0d0) tol =
max(tol,atoli/ayi)
1436 160 tol =
max(tol,100.0d0*uround)
1437 tol =
min(tol,0.001d0)
1438 sum = dvnorm(n, rwork(lf0), rwork(lewt))
1439 sum = 1.0d0/(tol*w0*w0) + tol*sum**2
1440 h0 = 1.0d0/sqrt(sum)
1442 h0 = sign(h0,tout-t)
1444 180 rh = abs(h0)*hmxi
1445 IF (rh .GT. 1.0d0) h0 = h0/rh
1449 190 rwork(i+lf0-1) = h0*rwork(i+lf0-1)
1457 GO TO (210, 250, 220, 230, 240), itask
1458 210
IF ((tn - tout)*h .LT. 0.0d0)
GO TO 250
1459 CALL dintdy (tout, 0, rwork(lyh), nyh, y, iflag)
1460 IF (iflag .NE. 0)
GO TO 627
1463 220 tp = tn - hu*(1.0d0 + 100.0d0*uround)
1464 IF ((tp - tout)*h .GT. 0.0d0)
GO TO 623
1465 IF ((tn - tout)*h .LT. 0.0d0)
GO TO 250
1467 230 tcrit = rwork(1)
1468 IF ((tn - tcrit)*h .GT. 0.0d0)
GO TO 624
1469 IF ((tcrit - tout)*h .LT. 0.0d0)
GO TO 625
1470 IF ((tn - tout)*h .LT. 0.0d0)
GO TO 245
1471 CALL dintdy (tout, 0, rwork(lyh), nyh, y, iflag)
1472 IF (iflag .NE. 0)
GO TO 627
1475 240 tcrit = rwork(1)
1476 IF ((tn - tcrit)*h .GT. 0.0d0)
GO TO 624
1477 245 hmx = abs(tn) + abs(h)
1478 ihit = abs(tn - tcrit) .LE. 100.0d0*uround*hmx
1480 tnext = tn + h*(1.0d0 + 4.0d0*uround)
1481 IF ((tnext - tcrit)*h .LE. 0.0d0)
GO TO 250
1482 h = (tcrit - tn)*(1.0d0 - 4.0d0*uround)
1483 IF (istate .EQ. 2) jstart = -2
1496 IF ((nst-nslast) .GE. mxstep)
GO TO 500
1497 CALL dewset (n, itol, rtol, atol, rwork(lyh), rwork(lewt))
1499 IF (rwork(i+lewt-1) .LE. 0.0d0)
GO TO 510
1500 260 rwork(i+lewt-1) = 1.0d0/rwork(i+lewt-1)
1501 270 tolsf = uround*dvnorm(n, rwork(lyh), rwork(lewt))
1502 IF (tolsf .LE. 1.0d0)
GO TO 280
1504 IF (nst .EQ. 0)
GO TO 626
1506 280
IF ((tn + h) .NE. tn)
GO TO 290
1508 IF (nhnil .GT. mxhnil)
GO TO 290
1509 msg =
'DLSODE- Warning..internal T (=R1) and H (=R2) are'
1510 CALL xerrwd (msg, 50, 101, 0, 0, 0, 0, 0, 0.0d0, 0.0d0)
1511 msg=
' such that in the machine, T + H = T on the next step '
1512 CALL xerrwd (msg, 60, 101, 0, 0, 0, 0, 0, 0.0d0, 0.0d0)
1513 msg =
' (H = step size). Solver will continue anyway'
1514 CALL xerrwd (msg, 50, 101, 0, 0, 0, 0, 2, tn, h)
1515 IF (nhnil .LT. mxhnil)
GO TO 290
1516 msg =
'DLSODE- Above warning has been issued I1 times. '
1517 CALL xerrwd (msg, 50, 102, 0, 0, 0, 0, 0, 0.0d0, 0.0d0)
1518 msg =
' It will not be issued again for this problem'
1519 CALL xerrwd (msg, 50, 102, 0, 1, mxhnil, 0, 0, 0.0d0, 0.0d0)
1524 CALL dstode (neq, y, rwork(lyh), nyh, rwork(lyh), rwork(lewt),
1525 1 rwork(lsavf), rwork(lacor), rwork(lwm), iwork(liwm),
1528 GO TO (300, 530, 540), kgo
1535 GO TO (310, 400, 330, 340, 350), itask
1537 310
IF ((tn - tout)*h .LT. 0.0d0)
GO TO 250
1538 CALL dintdy (tout, 0, rwork(lyh), nyh, y, iflag)
1542 330
IF ((tn - tout)*h .GE. 0.0d0)
GO TO 400
1545 340
IF ((tn - tout)*h .LT. 0.0d0)
GO TO 345
1546 CALL dintdy (tout, 0, rwork(lyh), nyh, y, iflag)
1549 345 hmx = abs(tn) + abs(h)
1550 ihit = abs(tn - tcrit) .LE. 100.0d0*uround*hmx
1552 tnext = tn + h*(1.0d0 + 4.0d0*uround)
1553 IF ((tnext - tcrit)*h .LE. 0.0d0)
GO TO 250
1554 h = (tcrit - tn)*(1.0d0 - 4.0d0*uround)
1558 350 hmx = abs(tn) + abs(h)
1559 ihit = abs(tn - tcrit) .LE. 100.0d0*uround*hmx
1568 410 y(i) = rwork(i+lyh-1)
1570 IF (itask .NE. 4 .AND. itask .NE. 5)
GO TO 420
1591 500 msg =
'DLSODE- At current T (=R1), MXSTEP (=I1) steps '
1592 CALL xerrwd (msg, 50, 201, 0, 0, 0, 0, 0, 0.0d0, 0.0d0)
1593 msg =
' taken on this call before reaching TOUT '
1594 CALL xerrwd (msg, 50, 201, 0, 1, mxstep, 0, 1, tn, 0.0d0)
1598 510 ewti = rwork(lewt+i-1)
1599 msg = .LE.
'DLSODE- At T (=R1), EWT(I1) has become R2 0.'
1600 CALL xerrwd (msg, 50, 202, 0, 1, i, 0, 2, tn, ewti)
1604 520 msg =
'DLSODE- At T (=R1), too much accuracy requested '
1605 CALL xerrwd (msg, 50, 203, 0, 0, 0, 0, 0, 0.0d0, 0.0d0)
1606 msg =
' for precision of machine.. see TOLSF (=R2) '
1607 CALL xerrwd (msg, 50, 203, 0, 0, 0, 0, 2, tn, tolsf)
1612 530 msg =
'DLSODE- At T(=R1) and step size H(=R2), the error'
1613 CALL xerrwd (msg, 50, 204, 0, 0, 0, 0, 0, 0.0d0, 0.0d0)
1614 msg =
' test failed repeatedly or with ABS(H) = HMIN'
1615 CALL xerrwd (msg, 50, 204, 0, 0, 0, 0, 2, tn, h)
1619 540 msg =
'DLSODE- At T (=R1) and step size H (=R2), the '
1620 CALL xerrwd (msg, 50, 205, 0, 0, 0, 0, 0, 0.0d0, 0.0d0)
1621 msg =
' corrector convergence failed repeatedly '
1622 CALL xerrwd (msg, 50, 205, 0, 0, 0, 0, 0, 0.0d0, 0.0d0)
1623 msg =
' or with ABS(H) = HMIN '
1624 CALL xerrwd (msg, 30, 205, 0, 0, 0, 0, 2, tn, h)
1630 SIZE = abs(rwork(i+lacor-1)*rwork(i+lewt-1))
1631 IF (big .GE. size)
GO TO 570
1638 590 y(i) = rwork(i+lyh-1)
1656 601 msg =
'DLSODE- ISTATE (=I1) illegal '
1657 CALL xerrwd (msg, 30, 1, 0, 1, istate, 0, 0, 0.0d0, 0.0d0)
1658 IF (istate .LT. 0)
GO TO 800
1660 602 msg =
'DLSODE- ITASK (=I1) illegal '
1661 CALL xerrwd (msg, 30, 2, 0, 1, itask, 0, 0, 0.0d0, 0.0d0)
1663 603 msg = .GT.
'DLSODE- ISTATE 1 but DLSODE not initialized '
1664 CALL xerrwd (msg, 50, 3, 0, 0, 0, 0, 0, 0.0d0, 0.0d0)
1666 604 msg = .LT.
'DLSODE- NEQ (=I1) 1 '
1667 CALL xerrwd (msg, 30, 4, 0, 1, neq(1), 0, 0, 0.0d0, 0.0d0)
1669 605 msg =
'DLSODE- ISTATE = 3 and NEQ increased (I1 to I2) '
1670 CALL xerrwd (msg, 50, 5, 0, 2, n, neq(1), 0, 0.0d0, 0.0d0)
1672 606 msg =
'DLSODE- ITOL (=I1) illegal '
1673 CALL xerrwd (msg, 30, 6, 0, 1, itol, 0, 0, 0.0d0, 0.0d0)
1675 607 msg =
'DLSODE- IOPT (=I1) illegal '
1676 CALL xerrwd (msg, 30, 7, 0, 1, iopt, 0, 0, 0.0d0, 0.0d0)
1678 608 msg =
'DLSODE- MF (=I1) illegal '
1679 CALL xerrwd (msg, 30, 8, 0, 1, mf, 0, 0, 0.0d0, 0.0d0)
1681 609 msg = .LT..GE.
'DLSODE- ML (=I1) illegal.. 0 or NEQ (=I2)'
1682 CALL xerrwd (msg, 50, 9, 0, 2, ml, neq(1), 0, 0.0d0, 0.0d0)
1684 610 msg = .LT..GE.
'DLSODE- MU (=I1) illegal.. 0 or NEQ (=I2)'
1685 CALL xerrwd (msg, 50, 10, 0, 2, mu, neq(1), 0, 0.0d0, 0.0d0)
1687 611 msg = .LT.
'DLSODE- MAXORD (=I1) 0 '
1688 CALL xerrwd (msg, 30, 11, 0, 1, maxord, 0, 0, 0.0d0, 0.0d0)
1690 612 msg = .LT.
'DLSODE- MXSTEP (=I1) 0 '
1691 CALL xerrwd (msg, 30, 12, 0, 1, mxstep, 0, 0, 0.0d0, 0.0d0)
1693 613 msg = .LT.
'DLSODE- MXHNIL (=I1) 0 '
1694 CALL xerrwd (msg, 30, 13, 0, 1, mxhnil, 0, 0, 0.0d0, 0.0d0)
1696 614 msg =
'DLSODE- TOUT (=R1) behind T (=R2) '
1697 CALL xerrwd (msg, 40, 14, 0, 0, 0, 0, 2, tout, t)
1698 msg =
' Integration direction is given by H0 (=R1) '
1699 CALL xerrwd (msg, 50, 14, 0, 0, 0, 0, 1, h0, 0.0d0)
1701 615 msg = .LT.
'DLSODE- HMAX (=R1) 0.0 '
1702 CALL xerrwd (msg, 30, 15, 0, 0, 0, 0, 1, hmax, 0.0d0)
1704 616 msg = .LT.
'DLSODE- HMIN (=R1) 0.0 '
1705 CALL xerrwd (msg, 30, 16, 0, 0, 0, 0, 1, hmin, 0.0d0)
1708 msg=
'DLSODE- RWORK length needed, LENRW (=I1), exceeds LRW (=I2)'
1709 CALL xerrwd (msg, 60, 17, 0, 2, lenrw, lrw, 0, 0.0d0, 0.0d0)
1712 msg=
'DLSODE- IWORK length needed, LENIW (=I1), exceeds LIW (=I2)'
1713 CALL xerrwd (msg, 60, 18, 0, 2, leniw, liw, 0, 0.0d0, 0.0d0)
1715 619 msg = .LT.
'DLSODE- RTOL(I1) is R1 0.0 '
1716 CALL xerrwd (msg, 40, 19, 0, 1, i, 0, 1, rtoli, 0.0d0)
1718 620 msg = .LT.
'DLSODE- ATOL(I1) is R1 0.0 '
1719 CALL xerrwd (msg, 40, 20, 0, 1, i, 0, 1, atoli, 0.0d0)
1721 621 ewti = rwork(lewt+i-1)
1722 msg = .LE.
'DLSODE- EWT(I1) is R1 0.0 '
1723 CALL xerrwd (msg, 40, 21, 0, 1, i, 0, 1, ewti, 0.0d0)
1726 msg=
'DLSODE- TOUT (=R1) too close to T(=R2) to start integration'
1727 CALL xerrwd (msg, 60, 22, 0, 0, 0, 0, 2, tout, t)
1730 msg=
'DLSODE- ITASK = I1 and TOUT (=R1) behind TCUR - HU (= R2) '
1731 CALL xerrwd (msg, 60, 23, 0, 1, itask, 0, 2, tout, tp)
1734 msg=
'DLSODE- ITASK = 4 OR 5 and TCRIT (=R1) behind TCUR (=R2) '
1735 CALL xerrwd (msg, 60, 24, 0, 0, 0, 0, 2, tcrit, tn)
1738 msg=
'DLSODE- ITASK = 4 or 5 and TCRIT (=R1) behind TOUT (=R2) '
1739 CALL xerrwd (msg, 60, 25, 0, 0, 0, 0, 2, tcrit, tout)
1741 626 msg =
'DLSODE- At start of problem, too much accuracy '
1742 CALL xerrwd (msg, 50, 26, 0, 0, 0, 0, 0, 0.0d0, 0.0d0)
1743 msg=
' requested for precision of machine.. See TOLSF (=R1) '
1744 CALL xerrwd (msg, 60, 26, 0, 0, 0, 0, 1, tolsf, 0.0d0)
1747 627 msg =
'DLSODE- Trouble in DINTDY. ITASK = I1, TOUT = R1'
1748 CALL xerrwd (msg, 50, 27, 0, 1, itask, 0, 1, tout, 0.0d0)
1753 800 msg =
'DLSODE- Run aborted.. apparent infinite loop '
1754 CALL xerrwd (msg, 50, 303, 2, 0, 0, 0, 0, 0.0d0, 0.0d0)
charNDArray max(char d, const charNDArray &m)
charNDArray min(char d, const charNDArray &m)
subroutine dewset(N, ITOL, RTOL, ATOL, YCUR, EWT)
subroutine dintdy(T, K, YH, NYH, DKY, IFLAG)
subroutine dlsode(F, NEQ, Y, T, TOUT, ITOL, RTOL, ATOL, ITASK, ISTATE, IOPT, RWORK, LRW, IWORK, LIW, JAC, MF)
subroutine dprepj(NEQ, Y, YH, NYH, EWT, FTEM, SAVF, WM, IWM, F, JAC)
subroutine dsolsy(WM, IWM, X, TEM)
subroutine dstode(NEQ, Y, YH, NYH, YH1, EWT, SAVF, ACOR, WM, IWM, F, JAC, PJAC, SLVS)
subroutine xerrwd(MSG, NMES, NERR, LEVEL, NI, I1, I2, NR, R1, R2)