LMDZ
exner_milieu_p_m.F90
Go to the documentation of this file.
2 
3  IMPLICIT NONE
4 
5 contains
6 
7  SUBROUTINE exner_milieu_p ( ngrid, ps, p, pks, pk, pkf )
8  !
9  ! Auteurs : F. Forget , Y. Wanherdrick
10  ! P.Le Van , Fr. Hourdin .
11  ! ..........
12  !
13  ! .... ngrid, ps,p sont des argum.d'entree au sous-prog ...
14  ! .... pks,pk,pkf sont des argum.de sortie au sous-prog ...
15  !
16  ! ************************************************************************
17  ! Calcule la fonction d'Exner pk = Cp * (p/preff) ** kappa , aux milieux des
18  ! couches . Pk(l) sera calcule aux milieux des couches l ,entre les
19  ! pressions p(l) et p(l+1) ,definis aux interfaces des llm couches .
20  ! ************************************************************************
21  ! .. N.B : Au sommet de l'atmosphere, p(llm+1) = 0. , et ps et pks sont
22  ! la pression et la fonction d'Exner au sol .
23  !
24  ! WARNING : CECI est une version speciale de exner_hyb originale
25  ! Utilise dans la version martienne pour pouvoir
26  ! tourner avec des coordonnees verticales complexe
27  ! => Il ne verifie PAS la condition la proportionalite en
28  ! energie totale/ interne / potentielle (F.Forget 2001)
29  ! ( voir note de Fr.Hourdin ) ,
30  !
31  USE parallel_lmdz
32  !
33  include "dimensions.h"
34  include "paramet.h"
35  include "comconst.h"
36  include "comgeom.h"
37  include "comvert.h"
38  include "serre.h"
39 
40  INTEGER ngrid
41  REAL p(ngrid,llmp1),pk(ngrid,llm)
42  REAL, optional:: pkf(ngrid,llm)
43  REAL ps(ngrid),pks(ngrid)
44 
45  ! .... variables locales ...
46 
47  INTEGER l, ij,ijb,ije,jjb,jje
48  REAL dum1
49 
50  logical,save :: firstcall=.true.
51  !$OMP THREADPRIVATE(firstcall)
52  character(len=*),parameter :: modname="exner_milieu_p"
53 
54  ! Sanity check
55  if (firstcall) then
56  ! sanity checks for Shallow Water case (1 vertical layer)
57  if (llm.eq.1) then
58  if (kappa.ne.1) then
59  call abort_gcm(modname, &
60  "kappa!=1 , but running in Shallow Water mode!!",42)
61  endif
62  if (cpp.ne.r) then
63  call abort_gcm(modname, &
64  "cpp!=r , but running in Shallow Water mode!!",42)
65  endif
66  endif ! of if (llm.eq.1)
67 
68  firstcall=.false.
69  endif ! of if (firstcall)
70 
71  !$OMP BARRIER
72 
73  ! Specific behaviour for Shallow Water (1 vertical layer) case:
74  if (llm.eq.1) then
75 
76  ! Compute pks(:),pk(:),pkf(:)
77  ijb=ij_begin
78  ije=ij_end
79  !$OMP DO SCHEDULE(STATIC)
80  DO ij=ijb, ije
81  pks(ij) = (cpp/preff) * ps(ij)
82  pk(ij,1) = .5*pks(ij)
83  if (present(pkf)) pkf(ij,1)=pk(ij,1)
84  ENDDO
85  !$OMP ENDDO
86 
87  !$OMP BARRIER
88  if (present(pkf)) then
89  jjb=jj_begin
90  jje=jj_end
91  CALL filtreg_p ( pkf,jjb,jje, jmp1, llm, 2, 1, .true., 1 )
92  end if
93 
94  ! our work is done, exit routine
95  return
96  endif ! of if (llm.eq.1)
97 
98  ! General case:
99 
100  ! -------------
101  ! Calcul de pks
102  ! -------------
103 
104  ijb=ij_begin
105  ije=ij_end
106 
107  !$OMP DO SCHEDULE(STATIC)
108  DO ij = ijb, ije
109  pks(ij) = cpp * ( ps(ij)/preff ) ** kappa
110  ENDDO
111  !$OMP ENDDO
112  ! Synchro OPENMP ici
113 
114  !$OMP BARRIER
115  !
116  !
117  ! .... Calcul de pk pour la couche l
118  ! --------------------------------------------
119  !
120  dum1 = cpp * (2*preff)**(-kappa)
121  DO l = 1, llm-1
122  !$OMP DO SCHEDULE(STATIC)
123  DO ij = ijb, ije
124  pk(ij,l) = dum1 * (p(ij,l) + p(ij,l+1))**kappa
125  ENDDO
126  !$OMP ENDDO NOWAIT
127  ENDDO
128 
129  ! .... Calcul de pk pour la couche l = llm ..
130  ! (on met la meme distance (en log pression) entre Pk(llm)
131  ! et Pk(llm -1) qu'entre Pk(llm-1) et Pk(llm-2)
132 
133  !$OMP DO SCHEDULE(STATIC)
134  DO ij = ijb, ije
135  pk(ij,llm) = pk(ij,llm-1)**2 / pk(ij,llm-2)
136  ENDDO
137  !$OMP ENDDO NOWAIT
138 
139  if (present(pkf)) then
140  ! calcul de pkf
141 
142  DO l = 1, llm
143  !$OMP DO SCHEDULE(STATIC)
144  DO ij = ijb, ije
145  pkf(ij,l)=pk(ij,l)
146  ENDDO
147  !$OMP ENDDO NOWAIT
148  ENDDO
149 
150  !$OMP BARRIER
151 
152  jjb=jj_begin
153  jje=jj_end
154  CALL filtreg_p ( pkf,jjb,jje, jmp1, llm, 2, 1, .true., 1 )
155  end if
156 
157  END SUBROUTINE exner_milieu_p
158 
159 end module exner_milieu_p_m
subroutine exner_milieu_p(ngrid, ps, p, pks, pk, pkf)
!$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
integer, save ij_begin
!$Id jmp1
Definition: comconst.h:7