source: LMDZ6/branches/Amaury_dev/libf/dyn3d_common/divgrad2.f90 @ 5134

Last change on this file since 5134 was 5134, checked in by abarral, 8 weeks ago

Replace academic.h, alpale.h, comdissip.h, comdissipn.h, comdissnew.h by modules
Remove unused clesph0.h

  • 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: 2.0 KB
Line 
1! $Header$
2
3SUBROUTINE divgrad2(klevel, h, deltapres, lh, divgra)
4  !
5  ! P. Le Van
6  !
7  !   ***************************************************************
8  !
9  ! .....   calcul de  (div( grad ))   de (  pext * h ) .....
10  !   ****************************************************************
11  !   h ,klevel,lh et pext  sont des arguments  d'entree pour le s-prg
12  !     divgra     est  un argument  de sortie pour le s-prg
13  !
14  USE lmdz_ssum_scopy, ONLY: scopy
15  USE lmdz_comdissipn, ONLY: tetaudiv, tetaurot, tetah, cdivu, crot, cdivh
16
17  IMPLICIT NONE
18  !
19  INCLUDE "dimensions.h"
20  INCLUDE "paramet.h"
21  INCLUDE "comgeom2.h"
22
23  !    .......    variables en arguments   .......
24  !
25  INTEGER :: klevel
26  REAL :: h(ip1jmp1, klevel), deltapres(ip1jmp1, klevel)
27  REAL :: divgra(ip1jmp1, klevel)
28  !
29  !    .......    variables  locales    ..........
30  !
31  REAL :: signe, nudivgrs, sqrtps(ip1jmp1, llm)
32  INTEGER :: l, ij, iter, lh
33  !    ...................................................................
34
35  !
36  signe = (-1.)**lh
37  nudivgrs = signe * cdivh
38
39  CALL SCOPY (ip1jmp1 * klevel, h, 1, divgra, 1)
40
41  !
42  CALL laplacien(klevel, divgra, divgra)
43
44  DO l = 1, klevel
45    DO ij = 1, ip1jmp1
46      sqrtps(ij, l) = SQRT(deltapres(ij, l))
47    ENDDO
48  ENDDO
49  !
50  DO l = 1, klevel
51    DO ij = 1, ip1jmp1
52      divgra(ij, l) = divgra(ij, l) * sqrtps(ij, l)
53    ENDDO
54  ENDDO
55
56  !    ........    Iteration de l'operateur  laplacien_gam    ........
57  !
58  DO  iter = 1, lh - 2
59    CALL laplacien_gam (klevel, cuvscvgam2, cvuscugam2, unsair_gam2, &
60            unsapolnga2, unsapolsga2, divgra, divgra)
61  ENDDO
62  !
63  !    ...............................................................
64
65  DO l = 1, klevel
66    DO ij = 1, ip1jmp1
67      divgra(ij, l) = divgra(ij, l) * sqrtps(ij, l)
68    ENDDO
69  ENDDO
70  !
71  CALL laplacien (klevel, divgra, divgra)
72  !
73  DO l = 1, klevel
74    DO ij = 1, ip1jmp1
75      divgra(ij, l) = nudivgrs * divgra(ij, l) / deltapres(ij, l)
76    ENDDO
77  ENDDO
78
79  RETURN
80END SUBROUTINE divgrad2
Note: See TracBrowser for help on using the repository browser.