/[lmdze]/trunk/misc/coefpoly.f90
ViewVC logotype

Annotation of /trunk/misc/coefpoly.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 276 - (hide annotations)
Thu Jul 12 14:49:20 2018 UTC (5 years, 11 months ago) by guez
Original Path: trunk/misc/coefpoly.f
File size: 1147 byte(s)
Move procedure read_serre from module read_serre_m to module
dynetat0_m, to avoid side effet on variables of module dynetat0_m.

Create procedure set_unit_nml to avoid side effect on variable of
module unit_nml_m.

Downgrade pctsrf from variable of module etat0_m to argument of etat0
and limit to avoid side effect on pctsrf.

Move variable zmasq from module dimphy to module phyetat0_m to avoid
side effect on zmasq.

1 guez 120 module coefpoly_m
2 guez 3
3 guez 81 IMPLICIT NONE
4 guez 3
5 guez 276 DOUBLE PRECISION, protected:: a0, a1, a2, a3
6 guez 149
7 guez 120 contains
8 guez 3
9 guez 149 SUBROUTINE coefpoly(y1, y2, yp1, yp2, x1, x2)
10 guez 3
11 guez 121 ! From LMDZ4/libf/dyn3d/coefpoly.F, version 1.1.1.1 2004/05/19 12:53:05
12 guez 3
13 guez 121 ! Author: P. Le Van
14 guez 3
15 guez 145 ! Calcul des coefficients a0, a1, a2, a3 du polynôme de degré 3
16 guez 146 ! qui passe par les points (x1, Y1) et (x2, Y2) avec les
17     ! dérivées yp1 et yp2. Système linéaire de 4 équations à 4
18 guez 145 ! inconnues :
19 guez 3
20 guez 146 ! a0 + a1 * x1 + a2 * x1**2 + a3 * x1**3 = Y1
21     ! a0 + a1 * x2 + a2 * x2**2 + a3 * x2**3 = Y2
22     ! a1 + 2 * a2 * x1 + 3 * a3 * x1**2 = Yp1
23     ! a1 + 2 * a2 * x2 + 3 * a3 * x2**2 = Yp2
24 guez 3
25 guez 146 DOUBLE PRECISION, intent(in):: y1, y2, yp1, yp2, x1, x2
26 guez 81
27 guez 120 ! Local:
28 guez 146 DOUBLE PRECISION x1car, x2car
29 guez 81
30 guez 120 !------------------------------------------------------------
31 guez 81
32 guez 146 x1car = x1 * x1
33     x2car = x2 * x2
34 guez 81
35 guez 146 a3 = (2d0 * (y2-y1)/(x1-x2)+yp1+yp2)/((x1-x2) * (x1-x2))
36     a2 = (yp1-yp2+3d0 * a3 * (x2car-x1car))/(2d0 * (x1-x2))
37 guez 120
38 guez 146 a1 = yp1 - 3d0 * a3 * x1car - 2d0 * a2 * x1
39     a0 = y1 - a3 * x1 * x1car - a2 * x1car - a1 * x1
40 guez 120
41     END SUBROUTINE coefpoly
42    
43     end module coefpoly_m

  ViewVC Help
Powered by ViewVC 1.1.21