source: LMDZ6/branches/Amaury_dev/libf/dyn3d_common/nxgraro2.f90 @ 5105

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

Replace 1DUTILS.h by module lmdz_1dutils.f90
Replace 1DConv.h by module lmdz_old_1dconv.f90 (it's only used by old_* files)
Convert *.F to *.f90
Fix gradsdef.h formatting
Remove unnecessary "RETURN" at the end of functions/subroutines

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