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

Last change on this file since 5204 was 5119, checked in by abarral, 2 months ago

enforce PRIVATE by default in several modules, expose PUBLIC as needed
move eigen.f90 to obsolete/
(lint) aslong the way

  • 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
RevLine 
[5114]1module lmdz_coefpoly
[524]2
[5116]3  IMPLICIT NONE; PRIVATE
4  PUBLIC coefpoly
[524]5
[5119]6CONTAINS
[524]7
[2218]8  SUBROUTINE coefpoly(xf1, xf2, xprim1, xprim2, xtild1, xtild2, a0, a1, a2, a3)
[524]9
[2218]10    ! From LMDZ4/libf/dyn3d/coefpoly.F, version 1.1.1.1 2004/05/19 12:53:05
[524]11
[2218]12    ! Author: P. Le Van
[524]13
[2218]14    ! Calcul des coefficients a0, a1, a2, a3 du polynôme de degré 3 qui
15    ! satisfait aux 4 équations suivantes :
[524]16
[2218]17    ! a0 + a1 * xtild1 + a2 * xtild1**2 + a3 * xtild1**3 = Xf1
18    ! a0 + a1 * xtild2 + a2 * xtild2**2 + a3 * xtild2**3 = Xf2
19    ! a1 + 2. * a2 * xtild1 + 3. * a3 * xtild1**2 = Xprim1
20    ! a1 + 2. * a2 * xtild2 + 3. * a3 * xtild2**2 = Xprim2
[524]21
[2218]22    ! (passe par les points (Xf(it), xtild(it)) et (Xf(it + 1),
23    ! xtild(it + 1))
[524]24
[2218]25    ! On en revient à resoudre un système de 4 équations à 4 inconnues
26    ! a0, a1, a2, a3.
27
[5117]28    USE lmdz_physical_constants, ONLY: k8
[2218]29
[5117]30    REAL(K8), INTENT(IN) :: xf1, xf2, xprim1, xprim2, xtild1, xtild2
31    REAL(K8), INTENT(OUT) :: a0, a1, a2, a3
[2228]32
[2218]33    ! Local:
[2228]34    REAL(K8) xtil1car, xtil2car, derr, x1x2car
[2218]35
36    !------------------------------------------------------------
37
38    xtil1car = xtild1 * xtild1
39    xtil2car = xtild2 * xtild2
40
[5114]41    derr = 2. * (xf2 - xf1) / (xtild1 - xtild2)
[2218]42
[5114]43    x1x2car = (xtild1 - xtild2) * (xtild1 - xtild2)
[2218]44
[5114]45    a3 = (derr + xprim1 + xprim2) / x1x2car
46    a2 = (xprim1 - xprim2 + 3. * a3 * (xtil2car - xtil1car)) / (2. * (xtild1 - xtild2))
[2218]47
48    a1 = xprim1 - 3. * a3 * xtil1car - 2. * a2 * xtild1
49    a0 = xf1 - a3 * xtild1 * xtil1car - a2 * xtil1car - a1 * xtild1
50
51  END SUBROUTINE coefpoly
52
[5119]53END MODULE lmdz_coefpoly
Note: See TracBrowser for help on using the repository browser.