source: LMDZ6/trunk/libf/dyn3d_common/gradiv2.f90 @ 5272

Last change on this file since 5272 was 5272, checked in by abarral, 23 hours ago

Turn paramet.h into a module

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