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

Last change on this file since 5271 was 5271, checked in by abarral, 26 hours ago

Move dimensions.h into a module
Nb: doesn't compile yet

  • 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.7 KB
RevLine 
[524]1!
2! $Header$
3!
[5246]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  !
[5271]17  USE dimensions_mod, ONLY: iim, jjm, llm, ndm
18IMPLICIT NONE
[5246]19  !
[5271]20
[5246]21  INCLUDE "paramet.h"
22  INCLUDE "comdissipn.h"
23  !
24  !    ......  variables en arguments  .......
25  !
26  INTEGER :: klevel
27  REAL :: xcov( ip1jmp1,klevel ), ycov( ip1jm,klevel )
28  REAL :: grx( ip1jmp1,klevel ),  gry( ip1jm,klevel )
29  !
30  !    ......   variables locales     ........
31  !
32  REAL :: rot(ip1jm,llm) , signe, nugradrs
33  INTEGER :: l,ij,iter,lr
34  !    ........................................................
35  !
36  !
37  !
38  signe    = (-1.)**lr
39  nugradrs = signe * crot
40  !
41  CALL SCOPY ( ip1jmp1* klevel, xcov, 1, grx, 1 )
42  CALL SCOPY (  ip1jm * klevel, ycov, 1, gry, 1 )
43  !
44  CALL     rotatf     ( klevel, grx, gry, rot )
45  !
46  CALL laplacien_rot ( klevel, rot, rot,grx,gry      )
[524]47
[5246]48  !
49  !    .....   Iteration de l'operateur laplacien_rotgam  .....
50  !
51  DO  iter = 1, lr -2
52    CALL laplacien_rotgam ( klevel, rot, rot )
53  ENDDO
54  !
55  !
56  CALL filtreg( rot, jjm, klevel, 2,1, .FALSE.,1)
57  CALL nxgrad ( klevel, rot, grx, gry )
58  !
59  DO    l = 1, klevel
60     DO  ij = 1, ip1jm
61      gry( ij,l ) = gry( ij,l ) * nugradrs
62     ENDDO
63     DO  ij = 1, ip1jmp1
64      grx( ij,l ) = grx( ij,l ) * nugradrs
65     ENDDO
66  ENDDO
67  !
68  RETURN
69END SUBROUTINE nxgraro2
Note: See TracBrowser for help on using the repository browser.