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

Last change on this file since 5272 was 5272, checked in by abarral, 25 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: 1.8 KB
Line 
1!
2! $Header$
3!
4 SUBROUTINE nxgraro2 (klevel,xcov, ycov, lr, grx, gry )
5  !
6  !  P.Le Van .
7  !   ***********************************************************
8  !                             lr
9  !  calcul de  ( nxgrad (rot) )   du vect. v  ....
10  !
11  !   xcov et ycov  etant les compos. covariantes de  v
12  !   ***********************************************************
13  ! xcov , ycov et lr  sont des arguments  d'entree pour le s-prog
14  !  grx   et  gry     sont des arguments de sortie pour le s-prog
15  !
16  !
17  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
18USE paramet_mod_h, ONLY: iip1, iip2, iip3, jjp1, llmp1, llmp2, llmm1, kftd, ip1jm, ip1jmp1, &
19          ip1jmi1, ijp1llm, ijmllm, mvar, jcfil, jcfllm
20IMPLICIT NONE
21  !
22
23
24  INCLUDE "comdissipn.h"
25  !
26  !    ......  variables en arguments  .......
27  !
28  INTEGER :: klevel
29  REAL :: xcov( ip1jmp1,klevel ), ycov( ip1jm,klevel )
30  REAL :: grx( ip1jmp1,klevel ),  gry( ip1jm,klevel )
31  !
32  !    ......   variables locales     ........
33  !
34  REAL :: rot(ip1jm,llm) , signe, nugradrs
35  INTEGER :: l,ij,iter,lr
36  !    ........................................................
37  !
38  !
39  !
40  signe    = (-1.)**lr
41  nugradrs = signe * crot
42  !
43  CALL SCOPY ( ip1jmp1* klevel, xcov, 1, grx, 1 )
44  CALL SCOPY (  ip1jm * klevel, ycov, 1, gry, 1 )
45  !
46  CALL     rotatf     ( klevel, grx, gry, rot )
47  !
48  CALL laplacien_rot ( klevel, rot, rot,grx,gry      )
49
50  !
51  !    .....   Iteration de l'operateur laplacien_rotgam  .....
52  !
53  DO  iter = 1, lr -2
54    CALL laplacien_rotgam ( klevel, rot, rot )
55  ENDDO
56  !
57  !
58  CALL filtreg( rot, jjm, klevel, 2,1, .FALSE.,1)
59  CALL nxgrad ( klevel, rot, grx, gry )
60  !
61  DO    l = 1, klevel
62     DO  ij = 1, ip1jm
63      gry( ij,l ) = gry( ij,l ) * nugradrs
64     ENDDO
65     DO  ij = 1, ip1jmp1
66      grx( ij,l ) = grx( ij,l ) * nugradrs
67     ENDDO
68  ENDDO
69  !
70  RETURN
71END SUBROUTINE nxgraro2
Note: See TracBrowser for help on using the repository browser.