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

Annotation of /trunk/dyn3d/rotat_nfil.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/rotat_nfil.f
File size: 1338 byte(s)
Moved everything out of libf.
1 guez 3 !
2     ! $Header: /home/cvsroot/LMDZ4/libf/dyn3d/rotat_nfil.F,v 1.1.1.1 2004/05/19 12:53:05 lmdzadmin Exp $
3     !
4     SUBROUTINE rotat_nfil (klevel, x, y, rot )
5     c
6     c Auteur : P.Le Van
7     c**************************************************************
8     c. Calcule le rotationnel non filtre ,
9     c a tous les niveaux d'1 vecteur de comp. x et y ..
10     c x et y etant des composantes covariantes ...
11     c********************************************************************
12     c klevel, x et y sont des arguments d'entree pour le s-prog
13     c rot est un argument de sortie pour le s-prog
14     c
15     use dimens_m
16     use paramet_m
17     use comgeom
18     IMPLICIT NONE
19     c
20     c
21     c ..... variables en arguments ......
22     c
23 guez 65 INTEGER, intent(in):: klevel
24 guez 3 REAL rot( ip1jm,klevel )
25     REAL x( ip1jmp1,klevel ), y( ip1jm,klevel )
26     c
27     c ... variables locales ...
28     c
29     INTEGER l, ij
30     c
31     c
32     DO 10 l = 1,klevel
33     c
34     DO ij = 1, ip1jm - 1
35     rot( ij,l ) = y( ij+1 , l ) - y( ij,l ) +
36     * x(ij +iip1, l ) - x( ij,l )
37     ENDDO
38     c
39     c .... correction pour rot( iip1,j,l) ....
40     c .... rot(iip1,j,l)= rot(1,j,l) ...
41     CDIR$ IVDEP
42     DO ij = iip1, ip1jm, iip1
43     rot( ij,l ) = rot( ij -iim,l )
44     ENDDO
45     c
46     10 CONTINUE
47    
48     RETURN
49     END

  ViewVC Help
Powered by ViewVC 1.1.21