*DECK DINTDY
SUBROUTINE DINTDY (T, K, YH, NYH, DKY, IFLAG)
C***BEGIN PROLOGUE DINTDY
C***SUBSIDIARY
C***PURPOSE Interpolate solution derivatives.
C***TYPE DOUBLE PRECISION (SINTDY-S, DINTDY-D)
C***AUTHOR Hindmarsh, Alan C., (LLNL)
C***DESCRIPTION
C
C DINTDY computes interpolated values of the K-th derivative of the
C dependent variable vector y, and stores it in DKY. This routine
C is called within the package with K = 0 and T = TOUT, but may
C also be called by the user for any K up to the current order.
C (See detailed instructions in the usage documentation.)
C
C The computed values in DKY are gotten by interpolation using the
C Nordsieck history array YH. This array corresponds uniquely to a
C vector-valued polynomial of degree NQCUR or less, and DKY is set
C to the K-th derivative of this polynomial at T.
C The formula for DKY is:
C q
C DKY(i) = sum c(j,K) * (T - tn)**(j-K) * h**(-j) * YH(i,j+1)
C j=K
C where c(j,K) = j*(j-1)*...*(j-K+1), q = NQCUR, tn = TCUR, h = HCUR.
C The quantities nq = NQCUR, l = nq+1, N = NEQ, tn, and h are
C communicated by COMMON. The above sum is done in reverse order.
C IFLAG is returned negative if either K or T is out of bounds.
C
C***SEE ALSO DLSODE
C***ROUTINES CALLED XERRWD
C***COMMON BLOCKS DLS001
C***REVISION HISTORY (YYMMDD)
C 791129 DATE WRITTEN
C 890501 Modified prologue to SLATEC/LDOC format. (FNF)
C 890503 Minor cosmetic changes. (FNF)
C 930809 Renamed to allow single/double precision versions. (ACH)
C 010418 Reduced size of Common block /DLS001/. (ACH)
C 031105 Restored 'own' variables to Common block /DLS001/, to
C enable interrupt/restart feature. (ACH)
C 050427 Corrected roundoff decrement in TP. (ACH)
C***END PROLOGUE DINTDY
C**End
INTEGER K, NYH, IFLAG
DOUBLE PRECISION T, YH, DKY
DIMENSION YH(NYH,*), DKY(*)
INTEGER IOWND, IOWNS,
1 ICF, IERPJ, IERSL, JCUR, JSTART, KFLAG, L,
2 LYH, LEWT, LACOR, LSAVF, LWM, LIWM, METH, MITER,
3 MAXORD, MAXCOR, MSBP, MXNCF, N, NQ, NST, NFE, NJE, NQU
DOUBLE PRECISION ROWNS,
1 CCMAX, EL0, H, HMIN, HMXI, HU, RC, TN, UROUND
COMMON /DLS001/ ROWNS(209),
1 CCMAX, EL0, H, HMIN, HMXI, HU, RC, TN, UROUND,
2 IOWND(6), IOWNS(6),
3 ICF, IERPJ, IERSL, JCUR, JSTART, KFLAG, L,
4 LYH, LEWT, LACOR, LSAVF, LWM, LIWM, METH, MITER,
5 MAXORD, MAXCOR, MSBP, MXNCF, N, NQ, NST, NFE, NJE, NQU
INTEGER I, IC, J, JB, JB2, JJ, JJ1, JP1
DOUBLE PRECISION C, R, S, TP
CHARACTER*80 MSG
C
C***FIRST EXECUTABLE STATEMENT DINTDY
IFLAG = 0
IF (K .LT. 0 .OR. K .GT. NQ) GO TO 80
TP = TN - HU - 100.0D0*UROUND*SIGN(ABS(TN) + ABS(HU), HU)
IF ((T-TP)*(T-TN) .GT. 0.0D0) GO TO 90
C
S = (T - TN)/H
IC = 1
IF (K .EQ. 0) GO TO 15
JJ1 = L - K
DO 10 JJ = JJ1,NQ
10 IC = IC*JJ
15 C = IC
DO 20 I = 1,N
20 DKY(I) = C*YH(I,L)
IF (K .EQ. NQ) GO TO 55
JB2 = NQ - K
DO 50 JB = 1,JB2
J = NQ - JB
JP1 = J + 1
IC = 1
IF (K .EQ. 0) GO TO 35
JJ1 = JP1 - K
DO 30 JJ = JJ1,J
30 IC = IC*JJ
35 C = IC
DO 40 I = 1,N
40 DKY(I) = C*YH(I,JP1) + S*DKY(I)
50 CONTINUE
IF (K .EQ. 0) RETURN
55 R = H**(-K)
DO 60 I = 1,N
60 DKY(I) = R*DKY(I)
RETURN
C
80 MSG = 'DINTDY- K (=I1) illegal '
CALL XERRWD (MSG, 30, 51, 0, 1, K, 0, 0, 0.0D0, 0.0D0)
IFLAG = -1
RETURN
90 MSG = 'DINTDY- T (=R1) illegal '
CALL XERRWD (MSG, 30, 52, 0, 0, 0, 0, 1, T, 0.0D0)
MSG=' T not in interval TCUR - HU (= R1) to TCUR (=R2) '
CALL XERRWD (MSG, 60, 52, 0, 0, 0, 0, 2, TP, TN)
IFLAG = -2
RETURN
C----------------------- END OF SUBROUTINE DINTDY ----------------------
END