source: LMDZ5/trunk/tools/Max_diff_nc_with_lib/Jumble/Numerical/dtridgl.f90 @ 1907

Last change on this file since 1907 was 1907, checked in by lguez, 10 years ago

Added a copyright property to every file of the distribution, except
for the fcm files (which have their own copyright). Use svn propget on
a file to see the copyright. For instance:

$ svn propget copyright libf/phylmd/physiq.F90
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

Also added the files defining the CeCILL version 2 license, in French
and English, at the top of the LMDZ tree.

  • 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
File size: 971 bytes
Line 
1module DTRIDGL_m
2
3  implicit none
4
5contains
6
7  SUBROUTINE DTRIDGL(L,AF,BF,CF,DF,XK)
8
9    ! Double precision version of tridgl. This subroutine solves a
10    ! system of tridiagional matrix equations. The form of the
11    ! equations are:
12    ! A(I)*X(I-1) + B(I)*X(I) + C(I)*X(I+1) = D(I)
13    ! where i=1,l less than 103. Reviewed -CP
14
15    integer, intent(in):: l
16    double precision, intent(in):: AF(L),BF(L),CF(L),DF(L)
17    double precision, intent(out):: XK(L)
18
19    ! Variables local to the procedure:
20
21    integer, PARAMETER:: NMAX=201
22    double precision AS(NMAX),DS(NMAX),  xkb, x
23    integer i
24
25    !----------------------------
26
27    AS(L) = AF(L)/BF(L)
28    DS(L) = DF(L)/BF(L)
29    DO I=2,L
30       X=1./(BF(L+1-I) - CF(L+1-I)*AS(L+2-I))
31       AS(L+1-I)=AF(L+1-I)*X
32       DS(L+1-I)=(DF(L+1-I)-CF(L+1-I)*DS(L+2-I))*X
33    end DO
34    XK(1)=DS(1)
35    DO I=2,L
36       XKB=XK(I-1)
37       XK(I)=DS(I)-AS(I)*XKB
38    end DO
39
40  END SUBROUTINE DTRIDGL
41
42end module DTRIDGL_m
Note: See TracBrowser for help on using the repository browser.