source: trunk/LMDZ.COMMON/libf/dyn3d_common/diagedyn.F @ 3000

Last change on this file since 3000 was 1592, checked in by emillour, 8 years ago

Dynamical core and miscellaneous additions to be fully compatible with LMDZ5 and the Earth physics package phylmd (at this point one can compile phylmd, from LMDZ5 revision 2602, with LMDZ.COMMON).

  • dyn3d and dyn3dpar:
  • removed ce0l.F90
  • dyn3d_common:
  • added conf_dat_m.F90 (for Earth model)
  • modified diagedyn.F: hard coded constants for Earth and error message for other planets
  • misc:
  • added slopes_m.F90 and regr1_conserv_m.F90 used by Earth model

EM

File size: 11.5 KB
Line 
1!
2! $Id: diagedyn.F 1279 2009-12-10 09:02:56Z fairhead $
3!
4
5C======================================================================
6      SUBROUTINE diagedyn(tit,iprt,idiag,idiag2,dtime
7     e  , ucov    , vcov , ps, p ,pk , teta , q, ql)
8C======================================================================
9C
10C Purpose:
11C    Calcul la difference d'enthalpie et de masse d'eau entre 2 appels,
12C    et calcul le flux de chaleur et le flux d'eau necessaire a ces
13C    changements. Ces valeurs sont moyennees sur la surface de tout
14C    le globe et sont exprime en W/2 et kg/s/m2
15C    Outil pour diagnostiquer la conservation de l'energie
16C    et de la masse dans la dynamique.
17C
18C
19c======================================================================
20C Arguments:
21C tit-----imput-A15- Comment added in PRINT (CHARACTER*15)
22C iprt----input-I-  PRINT level ( <=1 : no PRINT)
23C idiag---input-I- indice dans lequel sera range les nouveaux
24C                  bilans d' entalpie et de masse
25C idiag2--input-I-les nouveaux bilans d'entalpie et de masse
26C                 sont compare au bilan de d'enthalpie de masse de
27C                 l'indice numero idiag2
28C                 Cas parriculier : si idiag2=0, pas de comparaison, on
29c                 sort directement les bilans d'enthalpie et de masse
30C dtime----input-R- time step (s)
31C uconv, vconv-input-R- vents covariants (m/s)
32C ps-------input-R- Surface pressure (Pa)
33C p--------input-R- pressure at the interfaces
34C pk-------input-R- pk= (p/Pref)**kappa
35c teta-----input-R- potential temperature (K)
36c q--------input-R- vapeur d'eau (kg/kg)
37c ql-------input-R- liquid watter (kg/kg)
38c aire-----input-R- mesh surafce (m2)
39c
40C the following total value are computed by UNIT of earth surface
41C
42C d_h_vcol--output-R- Heat flux (W/m2) define as the Enthalpy
43c            change (J/m2) during one time step (dtime) for the whole
44C            atmosphere (air, watter vapour, liquid and solid)
45C d_qt------output-R- total water mass flux (kg/m2/s) defined as the
46C           total watter (kg/m2) change during one time step (dtime),
47C d_qw------output-R- same, for the watter vapour only (kg/m2/s)
48C d_ql------output-R- same, for the liquid watter only (kg/m2/s)
49C d_ec------output-R- Cinetic Energy Budget (W/m2) for vertical air column
50C
51C
52C J.L. Dufresne, July 2002
53c======================================================================
54 
55      USE control_mod, ONLY : planet_type
56      USE cpdet_mod, ONLY: cpdet,tpot2t
57
58      IMPLICIT NONE
59C
60#include "dimensions.h"
61#include "paramet.h"
62#include "comgeom.h"
63#include "iniprint.h"
64
65!#ifdef CPP_EARTH
66!#include "../phylmd/YOMCST.h"
67!#include "../phylmd/YOETHF.h"
68!#endif
69! Ehouarn: for now set these parameters to what is in Earth physics...
70!          (cf ../phylmd/suphel.h)
71!          this should be generalized...
72      REAL,PARAMETER :: RCPD=
73     &               3.5*(1000.*(6.0221367E+23*1.380658E-23)/28.9644)
74      REAL,PARAMETER :: RCPV=
75     &               4.*(1000.*(6.0221367E+23*1.380658E-23)/18.0153)
76      REAL,PARAMETER :: RCS=RCPV
77      REAL,PARAMETER :: RCW=RCPV
78      REAL,PARAMETER :: RLSTT=2.8345E+6
79      REAL,PARAMETER :: RLVTT=2.5008E+6
80!
81C
82      INTEGER imjmp1
83      PARAMETER( imjmp1=iim*jjp1)
84c     Input variables
85      CHARACTER*15 tit
86      INTEGER iprt,idiag, idiag2
87      REAL dtime
88      REAL vcov(ip1jm,llm),ucov(ip1jmp1,llm) ! vents covariants
89      REAL ps(ip1jmp1)                       ! pression  au sol
90      REAL p (ip1jmp1,llmp1  )  ! pression aux interfac.des couches
91      REAL pk (ip1jmp1,llm  )  ! = (p/Pref)**kappa
92      REAL teta(ip1jmp1,llm)                 ! temperature potentielle
93      REAL q(ip1jmp1,llm)               ! champs eau vapeur
94      REAL ql(ip1jmp1,llm)               ! champs eau liquide
95
96
97c     Output variables
98      REAL d_h_vcol, d_qt, d_qw, d_ql, d_qs, d_ec
99C
100C     Local variables
101c
102      REAL h_vcol_tot, h_dair_tot, h_qw_tot, h_ql_tot
103     .  , h_qs_tot, qw_tot, ql_tot, qs_tot , ec_tot
104c h_vcol_tot--  total enthalpy of vertical air column
105C            (air with watter vapour, liquid and solid) (J/m2)
106c h_dair_tot-- total enthalpy of dry air (J/m2)
107c h_qw_tot----  total enthalpy of watter vapour (J/m2)
108c h_ql_tot----  total enthalpy of liquid watter (J/m2)
109c h_qs_tot----  total enthalpy of solid watter  (J/m2)
110c qw_tot------  total mass of watter vapour (kg/m2)
111c ql_tot------  total mass of liquid watter (kg/m2)
112c qs_tot------  total mass of solid watter (kg/m2)
113c ec_tot------  total cinetic energy (kg/m2)
114C
115      REAL masse(ip1jmp1,llm)                ! masse d'air
116      REAL vcont(ip1jm,llm),ucont(ip1jmp1,llm)
117      REAL ecin(ip1jmp1,llm)
118
119      REAL zaire(imjmp1)
120      REAL zps(imjmp1)
121      REAL zairm(imjmp1,llm)
122      REAL zecin(imjmp1,llm)
123      REAL zpaprs(imjmp1,llm)
124      REAL zpk(imjmp1,llm)
125      REAL zt(imjmp1,llm)
126      REAL zh(imjmp1,llm)
127      REAL zqw(imjmp1,llm)
128      REAL zql(imjmp1,llm)
129      REAL zqs(imjmp1,llm)
130
131      REAL  zqw_col(imjmp1)
132      REAL  zql_col(imjmp1)
133      REAL  zqs_col(imjmp1)
134      REAL  zec_col(imjmp1)
135      REAL  zh_dair_col(imjmp1)
136      REAL  zh_qw_col(imjmp1), zh_ql_col(imjmp1), zh_qs_col(imjmp1)
137C
138      REAL      d_h_dair, d_h_qw, d_h_ql, d_h_qs
139C
140      REAL airetot, zcpvap, zcwat, zcice
141C
142      INTEGER i, k, jj, ij , l ,ip1jjm1
143C
144      INTEGER ndiag     ! max number of diagnostic in parallel
145      PARAMETER (ndiag=10)
146      integer pas(ndiag)
147      save pas
148      data pas/ndiag*0/
149C     
150      REAL      h_vcol_pre(ndiag), h_dair_pre(ndiag), h_qw_pre(ndiag)
151     $    , h_ql_pre(ndiag), h_qs_pre(ndiag), qw_pre(ndiag)
152     $    , ql_pre(ndiag), qs_pre(ndiag) , ec_pre(ndiag)
153      SAVE      h_vcol_pre, h_dair_pre, h_qw_pre, h_ql_pre
154     $        , h_qs_pre, qw_pre, ql_pre, qs_pre , ec_pre
155
156
157!#ifdef CPP_EARTH
158      IF (planet_type=="earth") THEN
159     
160c======================================================================
161C     Compute Kinetic enrgy
162      CALL covcont  ( llm    , ucov    , vcov , ucont, vcont        )
163      CALL enercin ( vcov   , ucov  , vcont     , ucont  , ecin  )
164      CALL massdair( p, masse )
165c======================================================================
166C
167C
168      print*,'MAIS POURQUOI DONC DIAGEDYN NE MARCHE PAS ?'
169      return
170C     On ne garde les donnees que dans les colonnes i=1,iim
171      DO jj = 1,jjp1
172        ip1jjm1=iip1*(jj-1)
173        DO ij =  1,iim
174          i=iim*(jj-1)+ij
175          zaire(i)=aire(ij+ip1jjm1)
176          zps(i)=ps(ij+ip1jjm1)
177        ENDDO
178      ENDDO
179C 3D arrays
180      DO l  =  1, llm
181        DO jj = 1,jjp1
182          ip1jjm1=iip1*(jj-1)
183          DO ij =  1,iim
184            i=iim*(jj-1)+ij
185            zairm(i,l) = masse(ij+ip1jjm1,l)
186            zecin(i,l) = ecin(ij+ip1jjm1,l)
187            zpaprs(i,l) = p(ij+ip1jjm1,l)
188            zpk(i,l) = pk(ij+ip1jjm1,l)
189            zh(i,l) = teta(ij+ip1jjm1,l)
190            zqw(i,l) = q(ij+ip1jjm1,l)
191            zql(i,l) = ql(ij+ip1jjm1,l)
192            zqs(i,l) = 0.
193          ENDDO
194        ENDDO
195      ENDDO
196C
197C     Reset variables
198      DO i = 1, imjmp1
199        zqw_col(i)=0.
200        zql_col(i)=0.
201        zqs_col(i)=0.
202        zec_col(i) = 0.
203        zh_dair_col(i) = 0.
204        zh_qw_col(i) = 0.
205        zh_ql_col(i) = 0.
206        zh_qs_col(i) = 0.
207      ENDDO
208C
209      zcpvap=RCPV
210      zcwat=RCW
211      zcice=RCS
212C
213C     Compute vertical sum for each atmospheric column
214C     ================================================
215! ADAPTATION GCM POUR CP(T)
216      call tpot2t(imjmp1*llm,zh,zt,zpk)
217      DO k = 1, llm
218        DO i = 1, imjmp1
219C         Watter mass
220          zqw_col(i) = zqw_col(i) + zqw(i,k)*zairm(i,k)
221          zql_col(i) = zql_col(i) + zql(i,k)*zairm(i,k)
222          zqs_col(i) = zqs_col(i) + zqs(i,k)*zairm(i,k)
223C         Cinetic Energy
224          zec_col(i) =  zec_col(i)
225     $        +zecin(i,k)*zairm(i,k)
226C         Air enthalpy
227          zh_dair_col(i) = zh_dair_col(i)
228! ADAPTATION GCM POUR CP(T)
229     $        + cpdet(zt(i,k))*(1.-zqw(i,k)-zql(i,k)-zqs(i,k))
230     $                       *zairm(i,k)*zt(i,k)
231          zh_qw_col(i) = zh_qw_col(i)
232     $        + zcpvap*zqw(i,k)*zairm(i,k)*zt(i,k)
233          zh_ql_col(i) = zh_ql_col(i)
234     $        + zcwat*zql(i,k)*zairm(i,k)*zt(i,k)
235     $        - RLVTT*zql(i,k)*zairm(i,k)
236          zh_qs_col(i) = zh_qs_col(i)
237     $        + zcice*zqs(i,k)*zairm(i,k)*zt(i,k)
238     $        - RLSTT*zqs(i,k)*zairm(i,k)
239
240        END DO
241      ENDDO
242C
243C     Mean over the planete surface
244C     =============================
245      qw_tot = 0.
246      ql_tot = 0.
247      qs_tot = 0.
248      ec_tot = 0.
249      h_vcol_tot = 0.
250      h_dair_tot = 0.
251      h_qw_tot = 0.
252      h_ql_tot = 0.
253      h_qs_tot = 0.
254      airetot=0.
255C
256      do i=1,imjmp1
257        qw_tot = qw_tot + zqw_col(i)
258        ql_tot = ql_tot + zql_col(i)
259        qs_tot = qs_tot + zqs_col(i)
260        ec_tot = ec_tot + zec_col(i)
261        h_dair_tot = h_dair_tot + zh_dair_col(i)
262        h_qw_tot = h_qw_tot + zh_qw_col(i)
263        h_ql_tot = h_ql_tot + zh_ql_col(i)
264        h_qs_tot = h_qs_tot + zh_qs_col(i)
265        airetot=airetot+zaire(i)
266      END DO
267C
268      qw_tot = qw_tot/airetot
269      ql_tot = ql_tot/airetot
270      qs_tot = qs_tot/airetot
271      ec_tot = ec_tot/airetot
272      h_dair_tot = h_dair_tot/airetot
273      h_qw_tot = h_qw_tot/airetot
274      h_ql_tot = h_ql_tot/airetot
275      h_qs_tot = h_qs_tot/airetot
276C
277      h_vcol_tot = h_dair_tot+h_qw_tot+h_ql_tot+h_qs_tot
278C
279C     Compute the change of the atmospheric state compare to the one
280C     stored in "idiag2", and convert it in flux. THis computation
281C     is performed IF idiag2 /= 0 and IF it is not the first CALL
282c     for "idiag"
283C     ===================================
284C
285      IF ( (idiag2.gt.0) .and. (pas(idiag2) .ne. 0) ) THEN
286        d_h_vcol  = (h_vcol_tot - h_vcol_pre(idiag2) )/dtime
287        d_h_dair = (h_dair_tot- h_dair_pre(idiag2))/dtime
288        d_h_qw   = (h_qw_tot  - h_qw_pre(idiag2)  )/dtime
289        d_h_ql   = (h_ql_tot  - h_ql_pre(idiag2)  )/dtime
290        d_h_qs   = (h_qs_tot  - h_qs_pre(idiag2)  )/dtime
291        d_qw     = (qw_tot    - qw_pre(idiag2)    )/dtime
292        d_ql     = (ql_tot    - ql_pre(idiag2)    )/dtime
293        d_qs     = (qs_tot    - qs_pre(idiag2)    )/dtime
294        d_ec     = (ec_tot    - ec_pre(idiag2)    )/dtime
295        d_qt = d_qw + d_ql + d_qs
296      ELSE
297        d_h_vcol = 0.
298        d_h_dair = 0.
299        d_h_qw   = 0.
300        d_h_ql   = 0.
301        d_h_qs   = 0.
302        d_qw     = 0.
303        d_ql     = 0.
304        d_qs     = 0.
305        d_ec     = 0.
306        d_qt     = 0.
307      ENDIF
308C
309      IF (iprt.ge.2) THEN
310        WRITE(6,9000) tit,pas(idiag),d_qt,d_qw,d_ql,d_qs
311 9000   format('Dyn3d. Watter Mass Budget (kg/m2/s)',A15
312     $      ,1i6,10(1pE14.6))
313        WRITE(6,9001) tit,pas(idiag), d_h_vcol
314 9001   format('Dyn3d. Enthalpy Budget (W/m2) ',A15,1i6,10(F8.2))
315        WRITE(6,9002) tit,pas(idiag), d_ec
316 9002   format('Dyn3d. Cinetic Energy Budget (W/m2) ',A15,1i6,10(F8.2))
317C        WRITE(6,9003) tit,pas(idiag), ec_tot
318 9003   format('Dyn3d. Cinetic Energy (W/m2) ',A15,1i6,10(E15.6))
319        WRITE(6,9004) tit,pas(idiag), d_h_vcol+d_ec
320 9004   format('Dyn3d. Total Energy Budget (W/m2) ',A15,1i6,10(F8.2))
321      END IF
322C
323C     Store the new atmospheric state in "idiag"
324C
325      pas(idiag)=pas(idiag)+1
326      h_vcol_pre(idiag)  = h_vcol_tot
327      h_dair_pre(idiag) = h_dair_tot
328      h_qw_pre(idiag)   = h_qw_tot
329      h_ql_pre(idiag)   = h_ql_tot
330      h_qs_pre(idiag)   = h_qs_tot
331      qw_pre(idiag)     = qw_tot
332      ql_pre(idiag)     = ql_tot
333      qs_pre(idiag)     = qs_tot
334      ec_pre (idiag)    = ec_tot
335C
336!#else
337      ELSE
338      write(lunout,*)'diagedyn: set to function with Earth parameters'
339      ENDIF ! of if (planet_type=="earth")
340!#endif
341! #endif of #ifdef CPP_EARTH
342      RETURN
343      END
Note: See TracBrowser for help on using the repository browser.