GNU Octave 10.1.0
A high-level interpreted language, primarily intended for numerical computations, mostly compatible with Matlab
 
Loading...
Searching...
No Matches
dintdy.f
Go to the documentation of this file.
1 SUBROUTINE dintdy (T, K, YH, NYH, DKY, IFLAG)
2C***BEGIN PROLOGUE DINTDY
3C***SUBSIDIARY
4C***PURPOSE Interpolate solution derivatives.
5C***TYPE DOUBLE PRECISION (SINTDY-S, DINTDY-D)
6C***AUTHOR Hindmarsh, Alan C., (LLNL)
7C***DESCRIPTION
8C
9C DINTDY computes interpolated values of the K-th derivative of the
10C dependent variable vector y, and stores it in DKY. This routine
11C is called within the package with K = 0 and T = TOUT, but may
12C also be called by the user for any K up to the current order.
13C (See detailed instructions in the usage documentation.)
14C
15C The computed values in DKY are gotten by interpolation using the
16C Nordsieck history array YH. This array corresponds uniquely to a
17C vector-valued polynomial of degree NQCUR or less, and DKY is set
18C to the K-th derivative of this polynomial at T.
19C The formula for DKY is:
20C q
21C DKY(i) = sum c(j,K) * (T - tn)**(j-K) * h**(-j) * YH(i,j+1)
22C j=K
23C where c(j,K) = j*(j-1)*...*(j-K+1), q = NQCUR, tn = TCUR, h = HCUR.
24C The quantities nq = NQCUR, l = nq+1, N = NEQ, tn, and h are
25C communicated by COMMON. The above sum is done in reverse order.
26C IFLAG is returned negative if either K or T is out of bounds.
27C
28C***SEE ALSO DLSODE
29C***ROUTINES CALLED XERRWD
30C***COMMON BLOCKS DLS001
31C***REVISION HISTORY (YYMMDD)
32C 791129 DATE WRITTEN
33C 890501 Modified prologue to SLATEC/LDOC format. (FNF)
34C 890503 Minor cosmetic changes. (FNF)
35C 930809 Renamed to allow single/double precision versions. (ACH)
36C 010418 Reduced size of Common block /DLS001/. (ACH)
37C 031105 Restored 'own' variables to Common block /DLS001/, to
38C enable interrupt/restart feature. (ACH)
39C 050427 Corrected roundoff decrement in TP. (ACH)
40C***END PROLOGUE DINTDY
41C**End
42 INTEGER K, NYH, IFLAG
43 DOUBLE PRECISION T, YH, DKY
44 dimension yh(nyh,*), dky(*)
45 INTEGER ILLIN, INIT, LYH, LEWT, LACOR, LSAVF, LWM, LIWM,
46 1 MXSTEP, MXHNIL, NHNIL, NTREP, NSLAST, CNYH,
47 2 IALTH, IPUP, LMAX, MEO, NQNYH, NSLP
48 INTEGER ICF, IERPJ, IERSL, JCUR, JSTART, KFLAG, L, METH, MITER,
49 2 MAXORD, MAXCOR, MSBP, MXNCF, N, NQ, NST, NFE, NJE, NQU
50 DOUBLE PRECISION CONIT, CRATE, EL, ELCO, HOLD, RMAX, TESCO,
51 1 CCMAX, EL0, H, HMIN, HMXI, HU, RC, TN, UROUND
52 COMMON /dls001/ conit, crate, el(13), elco(13,12),
53 1 hold, rmax, tesco(3,12),
54 2 ccmax, el0, h, hmin, hmxi, hu, rc, tn, uround,
55 2 illin, init, lyh, lewt, lacor, lsavf, lwm, liwm,
56 3 mxstep, mxhnil, nhnil, ntrep, nslast, cnyh,
57 3 ialth, ipup, lmax, meo, nqnyh, nslp,
58 4 icf, ierpj, iersl, jcur, jstart, kflag, l, meth, miter,
59 5 maxord, maxcor, msbp, mxncf, n, nq, nst, nfe, nje, nqu
60 INTEGER I, IC, J, JB, JB2, JJ, JJ1, JP1
61 DOUBLE PRECISION C, R, S, TP
62 CHARACTER*80 MSG
63C
64C***FIRST EXECUTABLE STATEMENT DINTDY
65 iflag = 0
66 IF (k .LT. 0 .OR. k .GT. nq) GO TO 80
67 tp = tn - hu - 100.0d0*uround*sign(abs(tn) + abs(hu), hu)
68 IF ((t-tp)*(t-tn) .GT. 0.0d0) GO TO 90
69C
70 s = (t - tn)/h
71 ic = 1
72 IF (k .EQ. 0) GO TO 15
73 jj1 = l - k
74 DO 10 jj = jj1,nq
75 10 ic = ic*jj
76 15 c = ic
77 DO 20 i = 1,n
78 20 dky(i) = c*yh(i,l)
79 IF (k .EQ. nq) GO TO 55
80 jb2 = nq - k
81 DO 50 jb = 1,jb2
82 j = nq - jb
83 jp1 = j + 1
84 ic = 1
85 IF (k .EQ. 0) GO TO 35
86 jj1 = jp1 - k
87 DO 30 jj = jj1,j
88 30 ic = ic*jj
89 35 c = ic
90 DO 40 i = 1,n
91 40 dky(i) = c*yh(i,jp1) + s*dky(i)
92 50 CONTINUE
93 IF (k .EQ. 0) RETURN
94 55 r = h**(-k)
95 DO 60 i = 1,n
96 60 dky(i) = r*dky(i)
97 RETURN
98C
99 80 msg = 'DINTDY- K (=I1) illegal '
100 CALL xerrwd (msg, 30, 51, 0, 1, k, 0, 0, 0.0d0, 0.0d0)
101 iflag = -1
102 RETURN
103 90 msg = 'DINTDY- T (=R1) illegal '
104 CALL xerrwd (msg, 30, 52, 0, 0, 0, 0, 1, t, 0.0d0)
105 msg=' T not in interval TCUR - HU (= R1) to TCUR (=R2) '
106 CALL xerrwd (msg, 60, 52, 0, 0, 0, 0, 2, tp, tn)
107 iflag = -2
108 RETURN
109C----------------------- END OF SUBROUTINE DINTDY ----------------------
110 END
subroutine dintdy(t, k, yh, nyh, dky, iflag)
Definition dintdy.f:2
subroutine xerrwd(msg, nmes, nerr, level, ni, i1, i2, nr, r1, r2)
Definition xerrwd.f:4