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

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

Parent Directory Parent Directory | Revision Log Revision Log


Revision 27 - (show annotations)
Thu Mar 25 14:29:07 2010 UTC (14 years, 2 months ago) by guez
File size: 2490 byte(s)
"dyn3d" and "filtrez" do not contain any included file so make rules
have been updated.

"comdissip.f90" was useless, removed it.

"dynredem0" wrote undefined value in "controle(31)", that was
overwritten by "dynredem1". Now "dynredem0" just writes 0 to
"controle(31)".

Removed arguments of "inidissip". "inidissip" now accesses the
variables by use association.

In program "etat0_lim", "itaufin" is not defined so "dynredem1" wrote
undefined value to "controle(31)". Added argument "itau" of
"dynredem1" to correct that.

"itaufin" does not need to be a module variable (of "temps"), made it
a local variable of "leapfrog".

Removed calls to "diagedyn" from "leapfrog".

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 use filtreg_m, only: filtreg
28
29 IMPLICIT NONE
30 c
31 INTEGER ntetaSTD
32 REAL vcov( ip1jm,ntetaSTD ), ucov( ip1jmp1,ntetaSTD )
33 REAL vorabs( ip1jm,ntetaSTD )
34 c
35 c variables locales
36 INTEGER l, ij, i, j
37 REAL rot( ip1jm,ntetaSTD )
38
39
40
41 c ... vorabs = ( Filtre( d(vcov)/dx - d(ucov)/dy ) + fext ) ..
42
43
44
45 c ........ Calcul du rotationnel du vent V puis filtrage ........
46
47 DO 5 l = 1,ntetaSTD
48
49 DO 2 i = 1, iip1
50 DO 2 j = 1, jjm
51 c
52 ij=i+(j-1)*iip1
53 IF(ij.LE.ip1jm - 1) THEN
54 c
55 IF(cv(ij).EQ.0..OR.cv(ij+1).EQ.0..OR.
56 $ cu(ij).EQ.0..OR.cu(ij+iip1).EQ.0.) THEN
57 rot( ij,l ) = 0.
58 continue
59 ELSE
60 rot( ij,l ) = (vcov(ij+1,l)/cv(ij+1)-vcov(ij,l)/cv(ij))/
61 $ (2.*pi*RAD*cos(rlatv(j)))*float(iim)
62 $ +(ucov(ij+iip1,l)/cu(ij+iip1)-ucov(ij,l)/cu(ij))/
63 $ (pi*RAD)*(float(jjm)-1.)
64 c
65 ENDIF
66 ENDIF !(ij.LE.ip1jm - 1) THEN
67 2 CONTINUE
68
69 c .... correction pour rot( iip1,j,l ) .....
70 c .... rot(iip1,j,l) = rot(1,j,l) .....
71
72 CDIR$ IVDEP
73
74 DO 3 ij = iip1, ip1jm, iip1
75 rot( ij,l ) = rot( ij -iim, l )
76 3 CONTINUE
77
78 5 CONTINUE
79
80
81 CALL filtreg( rot, jjm, ntetaSTD, 2, 1, .FALSE., 1 )
82
83
84 DO 10 l = 1, ntetaSTD
85
86 DO 6 ij = 1, ip1jm - 1
87 vorabs( ij,l ) = ( rot(ij,l) + fext(ij)*unsairez(ij) )
88 6 CONTINUE
89
90 c ..... correction pour vorabs( iip1,j,l) .....
91 c .... vorabs(iip1,j,l)= vorabs(1,j,l) ....
92 CDIR$ IVDEP
93 DO 8 ij = iip1, ip1jm, iip1
94 vorabs( ij,l ) = vorabs( ij -iim,l )
95 8 CONTINUE
96
97 10 CONTINUE
98
99 RETURN
100 END

  ViewVC Help
Powered by ViewVC 1.1.21