source: LMDZ6/trunk/libf/dyn3d_common/diagedyn.f90 @ 5272

Last change on this file since 5272 was 5272, checked in by abarral, 23 hours ago

Turn paramet.h into a module

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