/[lmdze]/trunk/dyn3d/nxgrad_gam.f90
ViewVC logotype

Annotation of /trunk/dyn3d/nxgrad_gam.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 76 - (hide annotations)
Fri Nov 15 18:45:49 2013 UTC (10 years, 6 months ago) by guez
Original Path: trunk/dyn3d/nxgrad_gam.f
File size: 1282 byte(s)
Moved everything out of libf.
1 guez 3 !
2     ! $Header: /home/cvsroot/LMDZ4/libf/dyn3d/nxgrad_gam.F,v 1.1.1.1 2004/05/19 12:53:06 lmdzadmin Exp $
3     !
4     SUBROUTINE nxgrad_gam( klevel, rot, x, y )
5     c
6     c P. Le Van
7     c
8     c ********************************************************************
9     c calcul du gradient tourne de pi/2 du rotationnel du vect.v
10     c ********************************************************************
11     c rot est un argument d'entree pour le s-prog
12     c x et y sont des arguments de sortie pour le s-prog
13     c
14     use dimens_m
15     use paramet_m
16     use comgeom
17     IMPLICIT NONE
18     c
19 guez 65 INTEGER, intent(in):: klevel
20 guez 3 REAL rot( ip1jm,klevel ),x( ip1jmp1,klevel ),y(ip1jm,klevel )
21     INTEGER l,ij
22     c
23     DO 10 l = 1,klevel
24     c
25     DO 1 ij = 2, ip1jm
26     y( ij,l ) = (rot( ij,l ) - rot( ij-1,l )) * cvscuvgam( ij )
27     1 CONTINUE
28     c
29     c ..... correction pour y ( 1,j,l ) ......
30     c
31     c .... y(1,j,l)= y(iip1,j,l) ....
32     CDIR$ IVDEP
33     DO 2 ij = 1, ip1jm, iip1
34     y( ij,l ) = y( ij +iim,l )
35     2 CONTINUE
36     c
37     DO 4 ij = iip2,ip1jm
38     x( ij,l ) = (rot( ij,l ) - rot( ij -iip1,l )) * cuscvugam( ij )
39     4 CONTINUE
40     DO 6 ij = 1,iip1
41     x( ij ,l ) = 0.
42     x( ij +ip1jm,l ) = 0.
43     6 CONTINUE
44     c
45     10 CONTINUE
46     RETURN
47     END

  ViewVC Help
Powered by ViewVC 1.1.21