LMDZ
exner_hyb_p_m.F90
Go to the documentation of this file.
2 
3  IMPLICIT NONE
4 
5 contains
6 
7  SUBROUTINE exner_hyb_p ( 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  !
36  include "dimensions.h"
37  include "paramet.h"
38  include "comconst.h"
39  include "comgeom.h"
40  include "comvert.h"
41  include "serre.h"
42 
43  INTEGER ngrid
44  REAL p(ngrid,llmp1),pk(ngrid,llm)
45  REAL, optional:: pkf(ngrid,llm)
46  REAL ps(ngrid),pks(ngrid)
47  REAL alpha(ngrid,llm),beta(ngrid,llm)
48 
49  ! .... variables locales ...
50 
51  INTEGER l, ij
52  REAL unpl2k,dellta
53 
54  INTEGER ije,ijb,jje,jjb
55  logical,save :: firstcall=.true.
56  !$OMP THREADPRIVATE(firstcall)
57  character(len=*),parameter :: modname="exner_hyb_p"
58 
59  ! Sanity check
60  if (firstcall) then
61  ! sanity checks for Shallow Water case (1 vertical layer)
62  if (llm.eq.1) then
63  if (kappa.ne.1) then
64  call abort_gcm(modname, &
65  "kappa!=1 , but running in Shallow Water mode!!",42)
66  endif
67  if (cpp.ne.r) then
68  call abort_gcm(modname, &
69  "cpp!=r , but running in Shallow Water mode!!",42)
70  endif
71  endif ! of if (llm.eq.1)
72 
73  firstcall=.false.
74  endif ! of if (firstcall)
75 
76  !$OMP BARRIER
77 
78  ! Specific behaviour for Shallow Water (1 vertical layer) case:
79  if (llm.eq.1) then
80 
81  ! Compute pks(:),pk(:),pkf(:)
82  ijb=ij_begin
83  ije=ij_end
84  !$OMP DO SCHEDULE(STATIC)
85  DO ij=ijb, ije
86  pks(ij) = (cpp/preff) * ps(ij)
87  pk(ij,1) = .5*pks(ij)
88  if (present(pkf)) pkf(ij,1)=pk(ij,1)
89  ENDDO
90  !$OMP ENDDO
91 
92  !$OMP BARRIER
93  if (present(pkf)) then
94  jjb=jj_begin
95  jje=jj_end
96  CALL filtreg_p ( pkf,jjb,jje, jmp1, llm, 2, 1, .true., 1 )
97  end if
98 
99  ! our work is done, exit routine
100  return
101  endif ! of if (llm.eq.1)
102 
103  ! General case:
104 
105  unpl2k = 1.+ 2.* kappa
106 
107  ! -------------
108  ! Calcul de pks
109  ! -------------
110 
111  ijb=ij_begin
112  ije=ij_end
113 
114  !$OMP DO SCHEDULE(STATIC)
115  DO ij = ijb, ije
116  pks(ij) = cpp * ( ps(ij)/preff ) ** kappa
117  ENDDO
118  !$OMP ENDDO
119  ! Synchro OPENMP ici
120 
121  !$OMP BARRIER
122  !
123  !
124  ! .... Calcul des coeff. alpha et beta pour la couche l = llm ..
125  !
126  !$OMP DO SCHEDULE(STATIC)
127  DO ij = ijb,ije
128  alpha(ij,llm) = 0.
129  beta(ij,llm) = 1./ unpl2k
130  ENDDO
131  !$OMP ENDDO NOWAIT
132  !
133  ! ... Calcul des coeff. alpha et beta pour l = llm-1 a l = 2 ...
134  !
135  DO l = llm -1 , 2 , -1
136  !
137  !$OMP DO SCHEDULE(STATIC)
138  DO ij = ijb, ije
139  dellta = p(ij,l)* unpl2k + p(ij,l+1)* ( beta(ij,l+1)-unpl2k )
140  alpha(ij,l) = - p(ij,l+1) / dellta * alpha(ij,l+1)
141  beta(ij,l) = p(ij,l ) / dellta
142  ENDDO
143  !$OMP ENDDO NOWAIT
144  ENDDO
145 
146  ! ***********************************************************************
147  ! ..... Calcul de pk pour la couche 1 , pres du sol ....
148  !
149  !$OMP DO SCHEDULE(STATIC)
150  DO ij = ijb, ije
151  pk(ij,1) = ( p(ij,1)*pks(ij) - 0.5*alpha(ij,2)*p(ij,2) ) / &
152  ( p(ij,1)* (1.+kappa) + 0.5*( beta(ij,2)-unpl2k )* p(ij,2) )
153  ENDDO
154  !$OMP ENDDO NOWAIT
155  !
156  ! ..... Calcul de pk(ij,l) , pour l = 2 a l = llm ........
157  !
158  DO l = 2, llm
159  !$OMP DO SCHEDULE(STATIC)
160  DO ij = ijb, ije
161  pk(ij,l) = alpha(ij,l) + beta(ij,l) * pk(ij,l-1)
162  ENDDO
163  !$OMP ENDDO NOWAIT
164  ENDDO
165 
166  if (present(pkf)) then
167  ! calcul de pkf
168 
169  DO l = 1, llm
170  !$OMP DO SCHEDULE(STATIC)
171  DO ij = ijb, ije
172  pkf(ij,l)=pk(ij,l)
173  ENDDO
174  !$OMP ENDDO NOWAIT
175  ENDDO
176 
177  !$OMP BARRIER
178 
179  jjb=jj_begin
180  jje=jj_end
181  CALL filtreg_p ( pkf,jjb,jje, jmp1, llm, 2, 1, .true., 1 )
182  end if
183 
184  END SUBROUTINE exner_hyb_p
185 
186 end module exner_hyb_p_m
!$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
!$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
!$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
subroutine exner_hyb_p(ngrid, ps, p, pks, pk, pkf)
integer, save ij_begin
!$Id jmp1
Definition: comconst.h:7