source: LMDZ6/branches/Amaury_dev/libf/dyn3dmem/nxgrad_loc.f90 @ 5153

Last change on this file since 5153 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
File size: 1.5 KB
Line 
1SUBROUTINE nxgrad_loc(klevel, rot, x, y )
2  !
3  ! P. Le Van
4  !
5  !   ********************************************************************
6  !  calcul du gradient tourne de pi/2 du rotationnel du vect.v
7  !   ********************************************************************
8  !   rot          est un argument  d'entree pour le s-prog
9  !   x  et y    sont des arguments de sortie pour le s-prog
10  !
11  USE parallel_lmdz
12  USE lmdz_comgeom
13
14  IMPLICIT NONE
15  !
16  INCLUDE "dimensions.h"
17  INCLUDE "paramet.h"
18  INTEGER :: klevel
19  REAL :: rot( ijb_v:ije_v,klevel ),x( ijb_u:ije_u,klevel )
20  REAL :: y(ijb_v:ije_v,klevel )
21  INTEGER :: l,ij
22  INTEGER :: ijb,ije
23  !
24  !
25!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
26  DO l = 1,klevel
27  !
28  ijb=ij_begin
29  ije=ij_end
30  IF (pole_sud)  ije=ij_end-iip1
31
32  DO ij = ijb+1, ije
33  y( ij,l ) = (  rot( ij,l ) - rot( ij-1,l )  ) * cvsurcuv( ij )
34  END DO
35  !
36  !    ..... correction pour  y ( 1,j,l )  ......
37  !
38  !    ....    y(1,j,l)= y(iip1,j,l) ....
39  !DIR$ IVDEP
40  DO ij = ijb, ije, iip1
41  y( ij,l ) = y( ij +iim,l )
42  END DO
43  !
44  ijb=ij_begin
45  ije=ij_end+iip1
46
47  IF (pole_nord)  ijb=ij_begin+iip1
48  IF (pole_sud)  ije=ij_end-iip1
49
50  DO ij = ijb,ije
51  x( ij,l ) = (  rot( ij,l ) - rot( ij -iip1,l )  ) * cusurcvu( ij )
52  END DO
53
54  IF (pole_nord) THEN
55    DO ij = 1,iip1
56      x(    ij    ,l ) = 0.
57    ENDDO
58  ENDIF
59
60  IF (pole_sud) THEN
61    DO ij = 1,iip1
62      x( ij +ip1jm,l ) = 0.
63    ENDDO
64  ENDIF
65  !
66  END DO
67!$OMP END DO NOWAIT
68
69END SUBROUTINE nxgrad_loc
Note: See TracBrowser for help on using the repository browser.