LMDZ
exner_hyb_loc_m.F90
Go to the documentation of this file.
2 
3  IMPLICIT NONE
4 
5 contains
6 
7  SUBROUTINE exner_hyb_loc(ngrid, ps, p, pks,pk,pkf)
8 
9  ! Auteurs : P.Le Van , Fr. Hourdin .
10  ! ..........
11  !
12  ! .... ngrid, ps,p sont des argum.d'entree au sous-prog ...
13  ! .... pks,pk,pkf sont des argum.de sortie au sous-prog ...
14  !
15  ! ************************************************************************
16  ! Calcule la fonction d'Exner pk = Cp * (p/preff) ** kappa , aux milieux des
17  ! couches . Pk(l) sera calcule aux milieux des couches l ,entre les
18  ! pressions p(l) et p(l+1) ,definis aux interfaces des llm couches .
19  ! ************************************************************************
20  ! .. N.B : Au sommet de l'atmosphere, p(llm+1) = 0. , et ps et pks sont
21  ! la pression et la fonction d'Exner au sol .
22  !
23  ! -------- z
24  ! A partir des relations ( 1 ) p*dz(pk) = kappa *pk*dz(p) et
25  ! ( 2 ) pk(l) = alpha(l)+ beta(l)*pk(l-1)
26  ! ( voir note de Fr.Hourdin ) ,
27  !
28  ! on determine successivement , du haut vers le bas des couches, les
29  ! coef. alpha(llm),beta(llm) .,.,alpha(l),beta(l),,,alpha(2),beta(2),
30  ! puis pk(ij,1). Ensuite ,on calcule,du bas vers le haut des couches,
31  ! pk(ij,l) donne par la relation (2), pour l = 2 a l = llm .
32  !
33  !
34  USE parallel_lmdz
35  USE mod_filtreg_p
36  USE write_field_loc
37  !
38  include "dimensions.h"
39  include "paramet.h"
40  include "comconst.h"
41  include "comgeom.h"
42  include "comvert.h"
43  include "serre.h"
44 
45  INTEGER ngrid
46  REAL p(ijb_u:ije_u,llmp1),pk(ijb_u:ije_u,llm)
47  REAL, optional:: pkf(ijb_u:ije_u,llm)
48  REAL ps(ijb_u:ije_u),pks(ijb_u:ije_u)
49  REAL alpha(ijb_u:ije_u,llm),beta(ijb_u:ije_u,llm)
50 
51  ! .... variables locales ...
52 
53  INTEGER l, ij
54  REAL unpl2k,dellta
55 
56  INTEGER ije,ijb,jje,jjb
57  logical,save :: firstcall=.true.
58  !$OMP THREADPRIVATE(firstcall)
59  character(len=*),parameter :: modname="exner_hyb_loc"
60  !
61  !$OMP BARRIER
62 
63  ! Sanity check
64  if (firstcall) then
65  ! sanity checks for Shallow Water case (1 vertical layer)
66  if (llm.eq.1) then
67  if (kappa.ne.1) then
68  call abort_gcm(modname, &
69  "kappa!=1 , but running in Shallow Water mode!!",42)
70  endif
71  if (cpp.ne.r) then
72  call abort_gcm(modname, &
73  "cpp!=r , but running in Shallow Water mode!!",42)
74  endif
75  endif ! of if (llm.eq.1)
76 
77  firstcall=.false.
78  endif ! of if (firstcall)
79 
80  !$OMP BARRIER
81 
82  ! Specific behaviour for Shallow Water (1 vertical layer) case:
83  if (llm.eq.1) then
84 
85  ! Compute pks(:),pk(:),pkf(:)
86  ijb=ij_begin
87  ije=ij_end
88  !$OMP DO SCHEDULE(STATIC)
89  DO ij=ijb, ije
90  pks(ij) = (cpp/preff) * ps(ij)
91  pk(ij,1) = .5*pks(ij)
92  if (present(pkf)) pkf(ij,1)=pk(ij,1)
93  ENDDO
94  !$OMP ENDDO
95 
96  !$OMP BARRIER
97  if (present(pkf)) then
98  jjb=jj_begin
99  jje=jj_end
100  CALL filtreg_p ( pkf,jjb_u,jje_u,jjb,jje, jmp1, llm, &
101  2, 1, .true., 1 )
102  end if
103 
104  ! our work is done, exit routine
105  return
106  endif ! of if (llm.eq.1)
107 
108  ! General case:
109 
110  unpl2k = 1.+ 2.* kappa
111 
112  ! -------------
113  ! Calcul de pks
114  ! -------------
115 
116  ijb=ij_begin
117  ije=ij_end
118 
119  !$OMP DO SCHEDULE(STATIC)
120  DO ij = ijb, ije
121  pks(ij) = cpp * ( ps(ij)/preff ) ** kappa
122  ENDDO
123  !$OMP ENDDO
124  ! Synchro OPENMP ici
125 
126  !$OMP BARRIER
127  !
128  !
129  ! .... Calcul des coeff. alpha et beta pour la couche l = llm ..
130  !
131  !$OMP DO SCHEDULE(STATIC)
132  DO ij = ijb,ije
133  alpha(ij,llm) = 0.
134  beta(ij,llm) = 1./ unpl2k
135  ENDDO
136  !$OMP ENDDO NOWAIT
137  !
138  ! ... Calcul des coeff. alpha et beta pour l = llm-1 a l = 2 ...
139  !
140  DO l = llm -1 , 2 , -1
141  !
142  !$OMP DO SCHEDULE(STATIC)
143  DO ij = ijb, ije
144  dellta = p(ij,l)* unpl2k + p(ij,l+1)* ( beta(ij,l+1)-unpl2k )
145  alpha(ij,l) = - p(ij,l+1) / dellta * alpha(ij,l+1)
146  beta(ij,l) = p(ij,l ) / dellta
147  ENDDO
148  !$OMP ENDDO NOWAIT
149  ENDDO
150 
151  ! ***********************************************************************
152  ! ..... Calcul de pk pour la couche 1 , pres du sol ....
153  !
154  !$OMP DO SCHEDULE(STATIC)
155  DO ij = ijb, ije
156  pk(ij,1) = ( p(ij,1)*pks(ij) - 0.5*alpha(ij,2)*p(ij,2) ) / &
157  ( p(ij,1)* (1.+kappa) + 0.5*( beta(ij,2)-unpl2k )* p(ij,2) )
158  ENDDO
159  !$OMP ENDDO NOWAIT
160  !
161  ! ..... Calcul de pk(ij,l) , pour l = 2 a l = llm ........
162  !
163  DO l = 2, llm
164  !$OMP DO SCHEDULE(STATIC)
165  DO ij = ijb, ije
166  pk(ij,l) = alpha(ij,l) + beta(ij,l) * pk(ij,l-1)
167  ENDDO
168  !$OMP ENDDO NOWAIT
169  ENDDO
170 
171  if (present(pkf)) then
172  ! calcul de pkf
173 
174  DO l = 1, llm
175  !$OMP DO SCHEDULE(STATIC)
176  DO ij = ijb, ije
177  pkf(ij,l)=pk(ij,l)
178  ENDDO
179  !$OMP ENDDO NOWAIT
180  ENDDO
181 
182  !$OMP BARRIER
183 
184  jjb=jj_begin
185  jje=jj_end
186 #ifdef DEBUG_IO
187  call writefield_u('pkf',pkf)
188 #endif
189  CALL filtreg_p ( pkf,jjb_u,jje_u,jjb,jje, jmp1, llm, &
190  2, 1, .true., 1 )
191 #ifdef DEBUG_IO
192  call writefield_u('pkf',pkf)
193 #endif
194  end if
195 
196  END SUBROUTINE exner_hyb_loc
197 
198 end module exner_hyb_loc_m
integer, save jjb_u
!$Id mode_top_bound COMMON comconstr r
Definition: comconst.h:7
!$Id preff
Definition: comvert.h:8
!$Header llmp1
Definition: paramet.h:14
!$Id mode_top_bound COMMON comconstr kappa
Definition: comconst.h:7
subroutine filtreg_p(champ, ibeg, iend, nlat, nbniv, ifiltre, iaire, griscal, iter)
Definition: filtreg_p.F:5
integer, save jj_end
integer, save jj_begin
integer, save ij_end
subroutine abort_gcm(modname, message, ierr)
Definition: abort_gcm.F:7
!$Id Turb_fcg_gcssold get_uvd hqturb_gcssold endif!large scale llm day day1 day day1 *dt_toga endif!time annee_ref dt_toga u_toga vq_toga w_prof vq_prof llm day day1 day day1 *dt_dice endif!time annee_ref dt_dice swup_dice vg_dice omega_dice tg_prof vg_profd w_profd omega_profd!do llm!print llm l llm
subroutine exner_hyb_loc(ngrid, ps, p, pks, pk, pkf)
!$Id itapm1 ENDIF!IM on interpole les champs sur les niveaux STD de pression!IM a chaque pas de temps de la physique c!positionnement de l argument logique a false c!pour ne pas recalculer deux fois la meme chose!c!a cet effet un appel a plevel_new a ete deplace c!a la fin de la serie d appels c!la boucle DO nlevSTD a ete internalisee c!dans d ou la creation de cette routine c c!CALL false
Definition: calcul_STDlev.h:26
!$Id mode_top_bound COMMON comconstr cpp
Definition: comconst.h:7
integer, save jje_u
!$Id itapm1 ENDIF!IM on interpole les champs sur les niveaux STD de pression!IM a chaque pas de temps de la physique c!positionnement de l argument logique a false c!pour ne pas recalculer deux fois la meme chose!c!a cet effet un appel a plevel_new a ete deplace c!a la fin de la serie d appels c!la boucle DO nlevSTD a ete internalisee c!dans d ou la creation de cette routine c c!CALL ulevSTD CALL &zphi philevSTD CALL &zx_rh rhlevSTD!DO klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon du jour ou toutes les read_climoz CALL true
integer, save ij_begin
!$Id jmp1
Definition: comconst.h:7
integer, save ije_u
integer, save ijb_u