My Project
 All Classes Files Functions Variables Macros
exner_milieu_p.F
Go to the documentation of this file.
1 !
2 ! $Id $
3 !
4  SUBROUTINE exner_milieu_p ( ngrid, ps, p,beta, pks, pk, pkf )
5 c
6 c Auteurs : F. Forget , Y. Wanherdrick
7 c P.Le Van , Fr. Hourdin .
8 c ..........
9 c
10 c .... ngrid, ps,p sont des argum.d'entree au sous-prog ...
11 c .... beta, pks,pk,pkf sont des argum.de sortie au sous-prog ...
12 c
13 c ************************************************************************
14 c Calcule la fonction d'Exner pk = Cp * (p/preff) ** kappa , aux milieux des
15 c couches . Pk(l) sera calcule aux milieux des couches l ,entre les
16 c pressions p(l) et p(l+1) ,definis aux interfaces des llm couches .
17 c ************************************************************************
18 c .. N.B : Au sommet de l'atmosphere, p(llm+1) = 0. , et ps et pks sont
19 c la pression et la fonction d'Exner au sol .
20 c
21 c WARNING : CECI est une version speciale de exner_hyb originale
22 c Utilise dans la version martienne pour pouvoir
23 c tourner avec des coordonnees verticales complexe
24 c => Il ne verifie PAS la condition la proportionalite en
25 c energie totale/ interne / potentielle (F.Forget 2001)
26 c ( voir note de Fr.Hourdin ) ,
27 c
28  USE parallel
29  IMPLICIT NONE
30 c
31 #include "dimensions.h"
32 #include "paramet.h"
33 #include "comconst.h"
34 #include "comgeom.h"
35 #include "comvert.h"
36 #include "serre.h"
37 
38  INTEGER ngrid
39  REAL p(ngrid,llmp1),pk(ngrid,llm),pkf(ngrid,llm)
40  REAL ps(ngrid),pks(ngrid), beta(ngrid,llm)
41 
42 c .... variables locales ...
43 
44  INTEGER l, ij
45  REAL dum1
46 
47  REAL ppn(iim),pps(iim)
48  REAL xpn, xps
49  REAL ssum
50  EXTERNAL ssum
51  INTEGER ije,ijb,jje,jjb
52  logical,save :: firstcall=.true.
53 !$OMP THREADPRIVATE(firstcall)
54  character(len=*),parameter :: modname="exner_milieu_p"
55 
56  ! Sanity check
57  if (firstcall) then
58  ! sanity checks for Shallow Water case (1 vertical layer)
59  if (llm.eq.1) then
60  if (kappa.ne.1) then
61  call abort_gcm(modname,
62  & "kappa!=1 , but running in Shallow Water mode!!",42)
63  endif
64  if (cpp.ne.r) then
65  call abort_gcm(modname,
66  & "cpp!=r , but running in Shallow Water mode!!",42)
67  endif
68  endif ! of if (llm.eq.1)
69 
70  firstcall=.false.
71  endif ! of if (firstcall)
72 
73 c$OMP BARRIER
74 
75 ! Specific behaviour for Shallow Water (1 vertical layer) case
76  if (llm.eq.1) then
77 
78  ! Compute pks(:),pk(:),pkf(:)
79  ijb=ij_begin
80  ije=ij_end
81 !$OMP DO SCHEDULE(STATIC)
82  DO ij=ijb, ije
83  pks(ij)=(cpp/preff)*ps(ij)
84  pk(ij,1) = .5*pks(ij)
85  pkf(ij,1)=pk(ij,1)
86  ENDDO
87 !$OMP ENDDO
88 
89 !$OMP MASTER
90  if (pole_nord) then
91  DO ij = 1, iim
92  ppn(ij) = aire( ij ) * pks( ij )
93  ENDDO
94  xpn = ssum(iim,ppn,1) /apoln
95 
96  DO ij = 1, iip1
97  pks( ij ) = xpn
98  pk(ij,1) = .5*pks(ij)
99  pkf(ij,1)=pk(ij,1)
100  ENDDO
101  endif
102 
103  if (pole_sud) then
104  DO ij = 1, iim
105  pps(ij) = aire(ij+ip1jm) * pks(ij+ip1jm )
106  ENDDO
107  xps = ssum(iim,pps,1) /apols
108 
109  DO ij = 1, iip1
110  pks( ij+ip1jm ) = xps
111  pk(ij+ip1jm,1)=.5*pks(ij+ip1jm)
112  pkf(ij+ip1jm,1)=pk(ij+ip1jm,1)
113  ENDDO
114  endif
115 !$OMP END MASTER
116 !$OMP BARRIER
117  jjb=jj_begin
118  jje=jj_end
119  CALL filtreg_p( pkf,jjb,jje, jmp1, llm, 2, 1, .true., 1 )
120 
121  ! our work is done, exit routine
122  return
123  endif ! of if (llm.eq.1)
124 
125 !!!! General case:
126 
127 c -------------
128 c Calcul de pks
129 c -------------
130 
131  ijb=ij_begin
132  ije=ij_end
133 
134 c$OMP DO SCHEDULE(STATIC)
135  DO ij = ijb, ije
136  pks(ij) = cpp * ( ps(ij)/preff ) ** kappa
137  ENDDO
138 c$OMP ENDDO
139 c Synchro OPENMP ici
140 
141 c$OMP MASTER
142  if (pole_nord) then
143  DO ij = 1, iim
144  ppn(ij) = aire( ij ) * pks( ij )
145  ENDDO
146  xpn = ssum(iim,ppn,1) /apoln
147 
148  DO ij = 1, iip1
149  pks( ij ) = xpn
150  ENDDO
151  endif
152 
153  if (pole_sud) then
154  DO ij = 1, iim
155  pps(ij) = aire(ij+ip1jm) * pks(ij+ip1jm )
156  ENDDO
157  xps = ssum(iim,pps,1) /apols
158 
159  DO ij = 1, iip1
160  pks( ij+ip1jm ) = xps
161  ENDDO
162  endif
163 c$OMP END MASTER
164 c$OMP BARRIER
165 c
166 c
167 c .... Calcul de pk pour la couche l
168 c --------------------------------------------
169 c
170  dum1 = cpp * (2*preff)**(-kappa)
171  DO l = 1, llm-1
172 c$OMP DO SCHEDULE(STATIC)
173  DO ij = ijb, ije
174  pk(ij,l) = dum1 * (p(ij,l) + p(ij,l+1))**kappa
175  ENDDO
176 c$OMP ENDDO NOWAIT
177  ENDDO
178 
179 c .... Calcul de pk pour la couche l = llm ..
180 c (on met la meme distance (en log pression) entre Pk(llm)
181 c et Pk(llm -1) qu'entre Pk(llm-1) et Pk(llm-2)
182 
183 c$OMP DO SCHEDULE(STATIC)
184  DO ij = ijb, ije
185  pk(ij,llm) = pk(ij,llm-1)**2 / pk(ij,llm-2)
186  ENDDO
187 c$OMP ENDDO NOWAIT
188 
189 
190 c calcul de pkf
191 c -------------
192 c CALL SCOPY ( ngrid * llm, pk, 1, pkf, 1 )
193  DO l = 1, llm
194 c$OMP DO SCHEDULE(STATIC)
195  DO ij = ijb, ije
196  pkf(ij,l)=pk(ij,l)
197  ENDDO
198 c$OMP ENDDO NOWAIT
199  ENDDO
200 
201 c$OMP BARRIER
202 
203  jjb=jj_begin
204  jje=jj_end
205  CALL filtreg_p( pkf,jjb,jje, jmp1, llm, 2, 1, .true., 1 )
206 
207 c EST-CE UTILE ?? : calcul de beta
208 c --------------------------------
209  DO l = 2, llm
210 c$OMP DO SCHEDULE(STATIC)
211  DO ij = ijb, ije
212  beta(ij,l) = pk(ij,l) / pk(ij,l-1)
213  ENDDO
214 c$OMP ENDDO NOWAIT
215  ENDDO
216 
217  RETURN
218  END