LMDZ
exner_milieu_m.F90
Go to the documentation of this file.
2 
3  IMPLICIT NONE
4 
5 contains
6 
7  SUBROUTINE exner_milieu ( 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  !
32  include "dimensions.h"
33  include "paramet.h"
34  include "comconst.h"
35  include "comgeom.h"
36  include "comvert.h"
37  include "serre.h"
38 
39  INTEGER ngrid
40  REAL p(ngrid,llmp1),pk(ngrid,llm)
41  real, optional:: pkf(ngrid,llm)
42  REAL ps(ngrid),pks(ngrid)
43 
44  ! .... variables locales ...
45 
46  INTEGER l, ij
47  REAL dum1
48 
49  logical,save :: firstcall=.true.
50  character(len=*),parameter :: modname="exner_milieu"
51 
52  ! Sanity check
53  if (firstcall) then
54  ! sanity checks for Shallow Water case (1 vertical layer)
55  if (llm.eq.1) then
56  if (kappa.ne.1) then
57  call abort_gcm(modname, &
58  "kappa!=1 , but running in Shallow Water mode!!",42)
59  endif
60  if (cpp.ne.r) then
61  call abort_gcm(modname, &
62  "cpp!=r , but running in Shallow Water mode!!",42)
63  endif
64  endif ! of if (llm.eq.1)
65 
66  firstcall=.false.
67  endif ! of if (firstcall)
68 
69  ! Specific behaviour for Shallow Water (1 vertical layer) case:
70  if (llm.eq.1) then
71 
72  ! Compute pks(:),pk(:),pkf(:)
73 
74  DO ij = 1, ngrid
75  pks(ij) = (cpp/preff) * ps(ij)
76  pk(ij,1) = .5*pks(ij)
77  ENDDO
78 
79  if (present(pkf)) then
80  pkf = pk
81  CALL filtreg ( pkf, jmp1, llm, 2, 1, .true., 1 )
82  end if
83 
84  ! our work is done, exit routine
85  return
86  endif ! of if (llm.eq.1)
87 
88  ! General case:
89 
90  ! -------------
91  ! Calcul de pks
92  ! -------------
93 
94  DO ij = 1, ngrid
95  pks(ij) = cpp * ( ps(ij)/preff ) ** kappa
96  ENDDO
97 
98  ! .... Calcul de pk pour la couche l
99  ! --------------------------------------------
100  !
101  dum1 = cpp * (2*preff)**(-kappa)
102  DO l = 1, llm-1
103  DO ij = 1, ngrid
104  pk(ij,l) = dum1 * (p(ij,l) + p(ij,l+1))**kappa
105  ENDDO
106  ENDDO
107 
108  ! .... Calcul de pk pour la couche l = llm ..
109  ! (on met la meme distance (en log pression) entre Pk(llm)
110  ! et Pk(llm -1) qu'entre Pk(llm-1) et Pk(llm-2)
111 
112  DO ij = 1, ngrid
113  pk(ij,llm) = pk(ij,llm-1)**2 / pk(ij,llm-2)
114  ENDDO
115 
116  if (present(pkf)) then
117  ! calcul de pkf
118  pkf = pk
119  CALL filtreg ( pkf, jmp1, llm, 2, 1, .true., 1 )
120  end if
121 
122  END SUBROUTINE exner_milieu
123 
124 end module exner_milieu_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 exner_milieu(ngrid, ps, p, pks, pk, pkf)
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
!$Id jmp1
Definition: comconst.h:7
subroutine filtreg(champ, nlat, nbniv, ifiltre, iaire, griscal, iter)
Definition: filtreg.F:6