source: LMDZ6/branches/Amaury_dev/libf/dyn3d_common/gradiv2.f90 @ 5136

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

Put comgeom.h, comgeom2.h into modules

  • 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.9 KB
Line 
1! $Header$
2
3SUBROUTINE gradiv2(klevel, xcov, ycov, ld, gdx, gdy)
4  !
5  ! P. Le Van
6  !
7  !   **********************************************************
8  !                            ld
9  !   calcul  de  (grad (div) )   du vect. v ....
10  !
11  ! xcov et ycov etant les composant.covariantes de v
12  !   **********************************************************
13  ! xcont , ycont et ld  sont des arguments  d'entree pour le s-prog
14  !  gdx   et  gdy       sont des arguments de sortie pour le s-prog
15  !
16  !
17  USE lmdz_filtreg, ONLY: filtreg
18  USE lmdz_ssum_scopy, ONLY: scopy
19  USE lmdz_comdissipn, ONLY: tetaudiv, tetaurot, tetah, cdivu, crot, cdivh
20  USE lmdz_comgeom
21
22  IMPLICIT NONE
23  !
24  INCLUDE "dimensions.h"
25  INCLUDE "paramet.h"
26  !
27  ! ........    variables en arguments      ........
28
29  INTEGER :: klevel
30  REAL :: xcov(ip1jmp1, klevel), ycov(ip1jm, klevel)
31  REAL :: gdx(ip1jmp1, klevel), gdy(ip1jm, klevel)
32  !
33  ! ........       variables locales       .........
34  !
35  REAL :: div(ip1jmp1, llm)
36  REAL :: signe, nugrads
37  INTEGER :: l, ij, iter, ld
38
39  !    ........................................................
40  !
41  !
42  CALL SCOPY(ip1jmp1 * klevel, xcov, 1, gdx, 1)
43  CALL SCOPY(ip1jm * klevel, ycov, 1, gdy, 1)
44  !
45  !
46  signe = (-1.)**ld
47  nugrads = signe * cdivu
48  !
49
50  CALL    divergf(klevel, gdx, gdy, div)
51
52  IF(ld>1)   THEN
53
54    CALL laplacien (klevel, div, div)
55
56    !    ......  Iteration de l'operateur laplacien_gam   .......
57
58    DO iter = 1, ld - 2
59      CALL laplacien_gam (klevel, cuvscvgam1, cvuscugam1, unsair_gam1, &
60              unsapolnga1, unsapolsga1, div, div)
61    ENDDO
62
63  ENDIF
64
65  CALL filtreg(div, jjp1, klevel, 2, 1, .TRUE., 1)
66  CALL  grad  (klevel, div, gdx, gdy)
67
68  !
69  DO   l = 1, klevel
70    DO  ij = 1, ip1jmp1
71      gdx(ij, l) = gdx(ij, l) * nugrads
72    ENDDO
73    DO  ij = 1, ip1jm
74      gdy(ij, l) = gdy(ij, l) * nugrads
75    ENDDO
76  ENDDO
77  !
78  RETURN
79END SUBROUTINE gradiv2
Note: See TracBrowser for help on using the repository browser.