My Project
 All Classes Files Functions Variables Macros
exner_milieu.F
Go to the documentation of this file.
1 !
2 ! $Id $
3 !
4  SUBROUTINE exner_milieu ( 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  IMPLICIT NONE
29 c
30 #include "dimensions.h"
31 #include "paramet.h"
32 #include "comconst.h"
33 #include "comgeom.h"
34 #include "comvert.h"
35 #include "serre.h"
36 
37  INTEGER ngrid
38  REAL p(ngrid,llmp1),pk(ngrid,llm),pkf(ngrid,llm)
39  REAL ps(ngrid),pks(ngrid), beta(ngrid,llm)
40 
41 c .... variables locales ...
42 
43  INTEGER l, ij
44  REAL dum1
45 
46  REAL ppn(iim),pps(iim)
47  REAL xpn, xps
48  REAL ssum
49  EXTERNAL ssum
50  logical,save :: firstcall=.true.
51  character(len=*),parameter :: modname="exner_milieu"
52 
53  ! Sanity check
54  if (firstcall) then
55  ! sanity checks for Shallow Water case (1 vertical layer)
56  if (llm.eq.1) then
57  if (kappa.ne.1) then
58  call abort_gcm(modname,
59  & "kappa!=1 , but running in Shallow Water mode!!",42)
60  endif
61  if (cpp.ne.r) then
62  call abort_gcm(modname,
63  & "cpp!=r , but running in Shallow Water mode!!",42)
64  endif
65  endif ! of if (llm.eq.1)
66 
67  firstcall=.false.
68  endif ! of if (firstcall)
69 
70 !!!! Specific behaviour for Shallow Water (1 vertical layer) case:
71  if (llm.eq.1) then
72 
73  ! Compute pks(:),pk(:),pkf(:)
74 
75  DO ij = 1, ngrid
76  pks(ij) = (cpp/preff) * ps(ij)
77  pk(ij,1) = .5*pks(ij)
78  ENDDO
79 
80  CALL scopy( ngrid * llm, pk, 1, pkf, 1 )
81  CALL filtreg( pkf, jmp1, llm, 2, 1, .true., 1 )
82 
83  ! our work is done, exit routine
84  return
85 
86  endif ! of if (llm.eq.1)
87 
88 !!!! General case:
89 
90 c -------------
91 c Calcul de pks
92 c -------------
93 
94  DO ij = 1, ngrid
95  pks(ij) = cpp * ( ps(ij)/preff ) ** kappa
96  ENDDO
97 
98  DO ij = 1, iim
99  ppn(ij) = aire( ij ) * pks( ij )
100  pps(ij) = aire(ij+ip1jm) * pks(ij+ip1jm )
101  ENDDO
102  xpn = ssum(iim,ppn,1) /apoln
103  xps = ssum(iim,pps,1) /apols
104 
105  DO ij = 1, iip1
106  pks( ij ) = xpn
107  pks( ij+ip1jm ) = xps
108  ENDDO
109 c
110 c
111 c .... Calcul de pk pour la couche l
112 c --------------------------------------------
113 c
114  dum1 = cpp * (2*preff)**(-kappa)
115  DO l = 1, llm-1
116  DO ij = 1, ngrid
117  pk(ij,l) = dum1 * (p(ij,l) + p(ij,l+1))**kappa
118  ENDDO
119  ENDDO
120 
121 c .... Calcul de pk pour la couche l = llm ..
122 c (on met la meme distance (en log pression) entre Pk(llm)
123 c et Pk(llm -1) qu'entre Pk(llm-1) et Pk(llm-2)
124 
125  DO ij = 1, ngrid
126  pk(ij,llm) = pk(ij,llm-1)**2 / pk(ij,llm-2)
127  ENDDO
128 
129 
130 c calcul de pkf
131 c -------------
132  CALL scopy( ngrid * llm, pk, 1, pkf, 1 )
133  CALL filtreg( pkf, jmp1, llm, 2, 1, .true., 1 )
134 
135 c EST-CE UTILE ?? : calcul de beta
136 c --------------------------------
137  DO l = 2, llm
138  DO ij = 1, ngrid
139  beta(ij,l) = pk(ij,l) / pk(ij,l-1)
140  ENDDO
141  ENDDO
142 
143  RETURN
144  END