/[lmdze]/trunk/libf/dyn3d/tourabs.f
ViewVC logotype

Contents of /trunk/libf/dyn3d/tourabs.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 3 - (show annotations)
Wed Feb 27 13:16:39 2008 UTC (16 years, 2 months ago) by guez
File size: 2454 byte(s)
Initial import
1 SUBROUTINE tourabs ( ntetaSTD,vcov, ucov, vorabs )
2
3 c=======================================================================
4 c
5 c Modif: I. Musat (28/10/04)
6 c -------
7 c adaptation du code tourpot.F pour le calcul de la vorticite absolue
8 c cf. P. Le Van
9 c
10 c Objet:
11 c ------
12 c
13 c *******************************************************************
14 c ............. calcul de la vorticite absolue .................
15 c *******************************************************************
16 c
17 c ntetaSTD, vcov,ucov sont des argum. d'entree pour le s-pg .
18 c vorabs est un argum.de sortie pour le s-pg .
19 c
20 c=======================================================================
21
22 use dimens_m
23 use paramet_m
24 use comconst
25 use logic
26 use comgeom
27 IMPLICIT NONE
28 c
29 INTEGER ntetaSTD
30 REAL vcov( ip1jm,ntetaSTD ), ucov( ip1jmp1,ntetaSTD )
31 REAL vorabs( ip1jm,ntetaSTD )
32 c
33 c variables locales
34 INTEGER l, ij, i, j
35 REAL rot( ip1jm,ntetaSTD )
36
37
38
39 c ... vorabs = ( Filtre( d(vcov)/dx - d(ucov)/dy ) + fext ) ..
40
41
42
43 c ........ Calcul du rotationnel du vent V puis filtrage ........
44
45 DO 5 l = 1,ntetaSTD
46
47 DO 2 i = 1, iip1
48 DO 2 j = 1, jjm
49 c
50 ij=i+(j-1)*iip1
51 IF(ij.LE.ip1jm - 1) THEN
52 c
53 IF(cv(ij).EQ.0..OR.cv(ij+1).EQ.0..OR.
54 $ cu(ij).EQ.0..OR.cu(ij+iip1).EQ.0.) THEN
55 rot( ij,l ) = 0.
56 continue
57 ELSE
58 rot( ij,l ) = (vcov(ij+1,l)/cv(ij+1)-vcov(ij,l)/cv(ij))/
59 $ (2.*pi*RAD*cos(rlatv(j)))*float(iim)
60 $ +(ucov(ij+iip1,l)/cu(ij+iip1)-ucov(ij,l)/cu(ij))/
61 $ (pi*RAD)*(float(jjm)-1.)
62 c
63 ENDIF
64 ENDIF !(ij.LE.ip1jm - 1) THEN
65 2 CONTINUE
66
67 c .... correction pour rot( iip1,j,l ) .....
68 c .... rot(iip1,j,l) = rot(1,j,l) .....
69
70 CDIR$ IVDEP
71
72 DO 3 ij = iip1, ip1jm, iip1
73 rot( ij,l ) = rot( ij -iim, l )
74 3 CONTINUE
75
76 5 CONTINUE
77
78
79 CALL filtreg( rot, jjm, ntetaSTD, 2, 1, .FALSE., 1 )
80
81
82 DO 10 l = 1, ntetaSTD
83
84 DO 6 ij = 1, ip1jm - 1
85 vorabs( ij,l ) = ( rot(ij,l) + fext(ij)*unsairez(ij) )
86 6 CONTINUE
87
88 c ..... correction pour vorabs( iip1,j,l) .....
89 c .... vorabs(iip1,j,l)= vorabs(1,j,l) ....
90 CDIR$ IVDEP
91 DO 8 ij = iip1, ip1jm, iip1
92 vorabs( ij,l ) = vorabs( ij -iim,l )
93 8 CONTINUE
94
95 10 CONTINUE
96
97 RETURN
98 END

  ViewVC Help
Powered by ViewVC 1.1.21