source: LMDZ6/branches/Amaury_dev/libf/misc/lmdz_coefpoly.f90 @ 5115

Last change on this file since 5115 was 5114, checked in by abarral, 4 months ago

Rename modules in misc from *_mod > lmdz_*
Turn description.h into lmdz_description.f90

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 1.5 KB
Line 
1module lmdz_coefpoly
2
3  IMPLICIT NONE
4
5contains
6
7  SUBROUTINE coefpoly(xf1, xf2, xprim1, xprim2, xtild1, xtild2, a0, a1, a2, a3)
8
9    ! From LMDZ4/libf/dyn3d/coefpoly.F, version 1.1.1.1 2004/05/19 12:53:05
10
11    ! Author: P. Le Van
12
13    ! Calcul des coefficients a0, a1, a2, a3 du polynôme de degré 3 qui
14    ! satisfait aux 4 équations suivantes :
15
16    ! a0 + a1 * xtild1 + a2 * xtild1**2 + a3 * xtild1**3 = Xf1
17    ! a0 + a1 * xtild2 + a2 * xtild2**2 + a3 * xtild2**3 = Xf2
18    ! a1 + 2. * a2 * xtild1 + 3. * a3 * xtild1**2 = Xprim1
19    ! a1 + 2. * a2 * xtild2 + 3. * a3 * xtild2**2 = Xprim2
20
21    ! (passe par les points (Xf(it), xtild(it)) et (Xf(it + 1),
22    ! xtild(it + 1))
23
24    ! On en revient à resoudre un système de 4 équations à 4 inconnues
25    ! a0, a1, a2, a3.
26
27    use nrtype, only: k8
28
29    REAL(K8), intent(in) :: xf1, xf2, xprim1, xprim2, xtild1, xtild2
30    REAL(K8), intent(out) :: a0, a1, a2, a3
31
32    ! Local:
33    REAL(K8) xtil1car, xtil2car, derr, x1x2car
34
35    !------------------------------------------------------------
36
37    xtil1car = xtild1 * xtild1
38    xtil2car = xtild2 * xtild2
39
40    derr = 2. * (xf2 - xf1) / (xtild1 - xtild2)
41
42    x1x2car = (xtild1 - xtild2) * (xtild1 - xtild2)
43
44    a3 = (derr + xprim1 + xprim2) / x1x2car
45    a2 = (xprim1 - xprim2 + 3. * a3 * (xtil2car - xtil1car)) / (2. * (xtild1 - xtild2))
46
47    a1 = xprim1 - 3. * a3 * xtil1car - 2. * a2 * xtild1
48    a0 = xf1 - a3 * xtild1 * xtil1car - a2 * xtil1car - a1 * xtild1
49
50  END SUBROUTINE coefpoly
51
52end module lmdz_coefpoly
Note: See TracBrowser for help on using the repository browser.