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

Annotation of /trunk/libf/dyn3d/PVtheta.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 71 - (hide annotations)
Mon Jul 8 18:12:18 2013 UTC (10 years, 10 months ago) by guez
File size: 5604 byte(s)
No reason to call inidissip in ce0l.

In inidissip, set random seed to 1 beacuse PGI compiler does not
accept all zeros.

dq was computed needlessly in caladvtrac. Arguments masse and dq of
calfis not used.

Replaced real*8 by double precision.

Pass arrays with inverted order of vertical levels to conflx instead
of creating local variables for this inside conflx.

1 guez 3 SUBROUTINE PVtheta(ilon,ilev,pucov,pvcov,pteta,
2     & ztfi,zplay,zplev,
3     & nbteta,theta,PVteta)
4     use dimens_m
5     use paramet_m
6     use comconst
7 guez 66 use disvert_m
8 guez 3 use comgeom
9     IMPLICIT none
10    
11     c=======================================================================
12     c
13     c Auteur: I. Musat
14     c -------
15     c
16     c Objet:
17     c ------
18     c
19     c *******************************************************************
20     c Calcul de la vorticite potentielle PVteta sur des iso-theta selon
21     c la methodologie du NCEP/NCAR :
22     c 1) on calcule la stabilite statique N**2=g/T*(dT/dz+g/cp) sur les
23     c niveaux du modele => N2
24     c 2) on interpole les vents, la temperature et le N**2 sur des isentropes
25     c (en fait sur des iso-theta) lineairement en log(theta) =>
26     c ucovteta, vcovteta, N2teta
27     c 3) on calcule la vorticite absolue sur des iso-theta => vorateta
28     c 4) on calcule la densite rho sur des iso-theta => rhoteta
29     c
30     c rhoteta = (T/theta)**(cp/R)*p0/(R*T)
31     c
32     c 5) on calcule la vorticite potentielle sur des iso-theta => PVteta
33     c
34     c PVteta = (vorateta * N2 * theta)/(g * rhoteta) ! en PVU
35     c
36     c NB: 1PVU=10**(-6) K*m**2/(s * kg)
37     c
38     c PVteta = vorateta * N2/(g**2 * rhoteta) ! en 1/(Pa*s)
39     c
40     c
41     c *******************************************************************
42     c
43     c
44     c Variables d'entree : ilon,ilev,pucov,pvcov,pteta,ztfi,zplay,zplev,nbteta,theta
45     c -> sur la grille dynamique
46     c Variable de sortie : PVteta
47     c -> sur la grille physique
48     c=======================================================================
49    
50     c
51     c variables Input
52     c
53     INTEGER ilon
54     integer, intent(in):: ilev
55 guez 71 REAL, intent(in):: pvcov(iip1,jjm,ilev)
56 guez 70 REAL, intent(in):: pucov(iip1,jjp1,ilev)
57 guez 44 REAL, intent(in):: pteta(iip1,jjp1,ilev)
58 guez 3 REAL ztfi(ilon,ilev)
59 guez 10 REAL, intent(in):: zplay(ilon,ilev), zplev(ilon,ilev+1)
60 guez 3 INTEGER nbteta
61     REAL theta(nbteta)
62     c
63     c variable Output
64     c
65     REAL PVteta(ilon,nbteta)
66     c
67     c variables locales
68     c
69     INTEGER i, j, l, ig0
70     REAL SSUM
71     REAL teta(ilon, ilev)
72     REAL ptetau(ip1jmp1, ilev), ptetav(ip1jm, ilev)
73     REAL ucovteta(ip1jmp1,ilev), vcovteta(ip1jm,ilev)
74     REAL N2(ilon,ilev-1), N2teta(ilon,nbteta)
75     REAL ztfiteta(ilon,nbteta)
76     REAL rhoteta(ilon,nbteta)
77     REAL vorateta(iip1,jjm,nbteta)
78     REAL voratetafi(ilon,nbteta), vorpol(iim)
79     c
80     c
81     c projection teta sur la grille physique
82     c
83     DO l=1,llm
84     teta(1,l) = pteta(1,1,l)
85     ig0 = 2
86     DO j = 2, jjm
87     DO i = 1, iim
88     teta(ig0,l) = pteta(i,j,l)
89     ig0 = ig0 + 1
90     ENDDO
91     ENDDO
92     teta(ig0,l) = pteta(1,jjp1,l)
93     ENDDO
94     c
95     c calcul pteta sur les grilles U et V
96     c
97     DO l=1, llm
98     DO j=1, jjp1
99     DO i=1, iip1
100     ig0=i+(j-1)*iip1
101     ptetau(ig0,l)=pteta(i,j,l)
102     ENDDO !i
103     ENDDO !j
104     DO j=1, jjm
105     DO i=1, iip1
106     ig0=i+(j-1)*iip1
107     ptetav(ig0,l)=0.5*(pteta(i,j,l)+pteta(i,j+1,l))
108     ENDDO !i
109     ENDDO !j
110     ENDDO !l
111     c
112     c projection pucov, pvcov sur une surface de theta constante
113     c
114     DO l=1, nbteta
115     cIM 1rout CALL tetaleveli1j1(ip1jmp1,llm,.true.,ptetau,theta(l),
116     CALL tetalevel(ip1jmp1,llm,.true.,ptetau,theta(l),
117     . pucov,ucovteta(:,l))
118     cIM 1rout CALL tetaleveli1j(ip1jm,llm,.true.,ptetav,theta(l),
119     CALL tetalevel(ip1jm,llm,.true.,ptetav,theta(l),
120     . pvcov,vcovteta(:,l))
121     ENDDO !l
122     c
123     c calcul vorticite absolue sur une iso-theta : vorateta
124     c
125     CALL tourabs(nbteta,vcovteta,ucovteta,vorateta)
126     c
127     c projection vorateta sur la grille physique => voratetafi
128     c
129     DO l=1,nbteta
130     DO j=2,jjm
131     ig0=1+(j-2)*iim
132     DO i=1,iim
133     voratetafi(ig0+i+1,l)
134     & = vorateta( i ,j-1,l) * alpha4_2d(i+1,j) +
135     & vorateta(i+1,j-1,l) * alpha1_2d(i+1,j) +
136     & vorateta(i ,j ,l) * alpha3_2d(i+1,j) +
137     & vorateta(i+1,j ,l) * alpha2_2d(i+1,j)
138     ENDDO
139     voratetafi(ig0 +1,l) = voratetafi(ig0 +1+ iim,l)
140     ENDDO
141     ENDDO
142     c
143     DO l=1,nbteta
144     DO i=1,iim
145     vorpol(i) = vorateta(i,1,l)*aire_2d(i,1)
146     ENDDO
147     voratetafi(1,l)= SSUM(iim,vorpol,1)/apoln
148     ENDDO
149     c
150     DO l=1,nbteta
151     DO i=1,iim
152     vorpol(i) = vorateta(i,jjm,l)* aire_2d(i,jjm +1)
153     ENDDO
154     voratetafi(ilon,l)= SSUM(iim,vorpol,1)/apols
155     ENDDO
156     c
157     c calcul N**2 sur la grille physique => N2
158     c
159     DO l=1, llm-1
160     DO i=1, ilon
161     N2(i,l) = (g**2 * zplay(i,l) *
162     & (ztfi(i,l+1)-ztfi(i,l)) )/
163     & (R*ztfi(i,l)*ztfi(i,l)*
164     & (zplev(i,l)-zplev(i,l+1)) )+
165     & (g**2)/(ztfi(i,l)*CPP)
166     ENDDO !i
167     ENDDO !l
168     c
169     c calcul N2 sur une iso-theta => N2teta
170     c
171     DO l=1, nbteta
172     CALL tetalevel(ilon,llm-1,.true.,teta,theta(l),
173     & N2,N2teta(:,l))
174     CALL tetalevel(ilon,llm,.true.,teta,theta(l),
175     & ztfi,ztfiteta(:,l))
176     ENDDO !l=1, nbteta
177     c
178     c calcul rho et PV sur une iso-theta : rhoteta, PVteta
179     c
180     DO l=1, nbteta
181     DO i=1, ilon
182     rhoteta(i,l)=(ztfiteta(i,l)/theta(l))**(CPP/R)*
183     & (preff/(R*ztfiteta(i,l)))
184     c
185     c PVteta en PVU
186     c
187     PVteta(i,l)=(theta(l)*g*voratetafi(i,l)*N2teta(i,l))/
188     & (g**2*rhoteta(i,l))
189     c
190     c PVteta en 1/(Pa*s)
191     c
192     PVteta(i,l)=(voratetafi(i,l)*N2teta(i,l))/
193     & (g**2*rhoteta(i,l))
194     ENDDO !i
195     ENDDO !l
196     c
197     RETURN
198     END

  ViewVC Help
Powered by ViewVC 1.1.21