source: LMDZ5/trunk/libf/phylmd/ener_conserv.F90 @ 2867

Last change on this file since 2867 was 2850, checked in by jyg, 7 years ago

ener_conserv with q_l and q_s arguments

  • 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
File size: 6.4 KB
Line 
1subroutine ener_conserv(klon,klev,pdtphys, &
2 &                      puo,pvo,pto,pqo,pql0,pqs0, &
3 &                      pun,pvn,ptn,pqn,pqln,pqsn,dtke,masse,exner,d_t_ec)
4
5!=============================================================
6! Energy conservation
7! Based on the TKE equation
8! The M2 and N2 terms at the origin of TKE production are
9! concerted into heating in the d_t_ec term
10! Option 1 is the standard
11!        101 is for M2 term only
12!        101 for N2 term only
13!         -1 is a previours treatment for kinetic energy only
14!  FH (hourdin@lmd.jussieu.fr), 2013/04/25
15!=============================================================
16
17!=============================================================
18! Declarations
19!=============================================================
20
21! From module
22USE phys_local_var_mod, ONLY : d_u_vdf,d_v_vdf,d_t_vdf,d_u_ajs,d_v_ajs,d_t_ajs, &
23 &                             d_u_con,d_v_con,d_t_con,d_t_diss
24USE phys_local_var_mod, ONLY : d_t_eva,d_t_lsc,d_q_eva,d_q_lsc
25USE phys_output_var_mod, ONLY : bils_ec,bils_ech,bils_tke,bils_kinetic,bils_enthalp,bils_latent,bils_diss
26
27IMPLICIT none
28#include "YOMCST.h"
29#include "YOETHF.h"
30#include "clesphys.h"
31#include "compbl.h"
32
33! Arguments
34INTEGER, INTENT(IN) :: klon,klev
35REAL, INTENT(IN) :: pdtphys
36REAL, DIMENSION(klon,klev), INTENT(IN)      :: puo,pvo,pto,pqo,pql0,pqs0
37REAL, DIMENSION(klon,klev), INTENT(IN)      :: pun,pvn,ptn,pqn,pqln,pqsn
38REAL, DIMENSION(klon,klev), INTENT(IN)      :: masse,exner
39REAL, DIMENSION(klon,klev+1), INTENT(IN)    :: dtke
40!
41REAL, DIMENSION(klon,klev), INTENT(OUT)     :: d_t_ec
42
43! Local
44      integer k,i
45REAL, DIMENSION(klon,klev+1) :: fluxu,fluxv,fluxt
46REAL, DIMENSION(klon,klev+1) :: dddu,dddv,dddt
47REAL, DIMENSION(klon,klev) :: d_u,d_v,d_t,zv,zu,d_t_ech
48REAL ZRCPD
49
50character*80 abort_message
51character*20 :: modname
52
53
54modname='ener_conser'
55d_t_ec(:,:)=0.
56
57IF (iflag_ener_conserv==-1) THEN
58!+jld ec_conser
59   DO k = 1, klev
60   DO i = 1, klon
61      ZRCPD = RCPD*(1.0+RVTMP2*(pqn(i,k)+pqln(i,k)+pqsn(i,k)))
62      d_t_ec(i,k)=0.5/ZRCPD &
63 &      *(puo(i,k)**2+pvo(i,k)**2-pun(i,k)**2-pvn(i,k)**2)
64      ENDDO
65      ENDDO
66!-jld ec_conser
67
68
69
70ELSEIF (iflag_ener_conserv>=1) THEN
71
72   IF (iflag_ener_conserv<=2) THEN
73!     print*,'ener_conserv pbl=',iflag_pbl
74      IF (iflag_pbl>=20 .AND. iflag_pbl<=27) THEN !d_t_diss accounts for conserv
75         d_t(:,:)=d_t_ajs(:,:)   ! d_t_ajs = adjust + thermals
76         d_u(:,:)=d_u_ajs(:,:)+d_u_con(:,:)
77         d_v(:,:)=d_v_ajs(:,:)+d_v_con(:,:)
78      ELSE
79         d_t(:,:)=d_t_vdf(:,:)+d_t_ajs(:,:)   ! d_t_ajs = adjust + thermals
80         d_u(:,:)=d_u_vdf(:,:)+d_u_ajs(:,:)+d_u_con(:,:)
81         d_v(:,:)=d_v_vdf(:,:)+d_v_ajs(:,:)+d_v_con(:,:)
82      ENDIF
83   ELSEIF (iflag_ener_conserv==101) THEN
84      d_t(:,:)=0.
85      d_u(:,:)=d_u_vdf(:,:)+d_u_ajs(:,:)+d_u_con(:,:)
86      d_v(:,:)=d_v_vdf(:,:)+d_v_ajs(:,:)+d_v_con(:,:)
87   ELSEIF (iflag_ener_conserv==110) THEN
88      d_t(:,:)=d_t_vdf(:,:)+d_t_ajs(:,:)
89      d_u(:,:)=0.
90      d_v(:,:)=0.
91   ELSE
92      abort_message = 'iflag_ener_conserv non prevu'
93      CALL abort_physic (modname,abort_message,1)
94   ENDIF
95
96!----------------------------------------------------------------------------
97! Two options wether we consider time integration in the energy conservation
98!----------------------------------------------------------------------------
99
100   if (iflag_ener_conserv==2) then
101      zu(:,:)=puo(:,:)
102      zv(:,:)=pvo(:,:)
103   else
104      IF (iflag_pbl>=20 .AND. iflag_pbl<=27) THEN
105         zu(:,:)=puo(:,:)+d_u_vdf(:,:)+0.5*d_u(:,:)
106         zv(:,:)=pvo(:,:)+d_v_vdf(:,:)+0.5*d_v(:,:)
107      ELSE
108         zu(:,:)=puo(:,:)+0.5*d_u(:,:)
109         zv(:,:)=pvo(:,:)+0.5*d_v(:,:)
110      ENDIF
111   endif
112
113   fluxu(:,klev+1)=0.
114   fluxv(:,klev+1)=0.
115   fluxt(:,klev+1)=0.
116
117   do k=klev,1,-1
118      fluxu(:,k)=fluxu(:,k+1)+masse(:,k)*d_u(:,k)
119      fluxv(:,k)=fluxv(:,k+1)+masse(:,k)*d_v(:,k)
120      fluxt(:,k)=fluxt(:,k+1)+masse(:,k)*d_t(:,k)/exner(:,k)
121   enddo
122
123   dddu(:,1)=2*zu(:,1)*fluxu(:,1)
124   dddv(:,1)=2*zv(:,1)*fluxv(:,1)
125   dddt(:,1)=(exner(:,1)-1.)*fluxt(:,1)
126
127   do k=2,klev
128      dddu(:,k)=(zu(:,k)-zu(:,k-1))*fluxu(:,k)
129      dddv(:,k)=(zv(:,k)-zv(:,k-1))*fluxv(:,k)
130      dddt(:,k)=(exner(:,k)-exner(:,k-1))*fluxt(:,k)
131   enddo
132   dddu(:,klev+1)=0.
133   dddv(:,klev+1)=0.
134   dddt(:,klev+1)=0.
135
136   do k=1,klev
137      d_t_ech(:,k)=-(rcpd*(dddt(:,k)+dddt(:,k+1)))/(2.*rcpd*masse(:,k))
138      d_t_ec(:,k)=-(dddu(:,k)+dddu(:,k+1)+dddv(:,k)+dddv(:,k+1))/(2.*rcpd*masse(:,k))+d_t_ech(:,k)
139   enddo
140
141ENDIF
142
143!================================================================
144!  Computation of integrated enthalpie and kinetic energy variation
145!  FH (hourdin@lmd.jussieu.fr), 2013/04/25
146!  bils_ec : energie conservation term
147!  bils_ech : part of this term linked to temperature
148!  bils_tke : change of TKE
149!  bils_diss : dissipation of TKE (when activated)
150!  bils_kinetic : change of kinetic energie of the column
151!  bils_enthalp : change of enthalpie
152!  bils_latent  : change of latent heat. Computed between
153!          after reevaporation (at the beginning of the physics)
154!          and before large scale condensation (fisrtilp)
155!================================================================
156
157      bils_ec(:)=0.
158      bils_ech(:)=0.
159      bils_tke(:)=0.
160      bils_diss(:)=0.
161      bils_kinetic(:)=0.
162      bils_enthalp(:)=0.
163      bils_latent(:)=0.
164      DO k=1,klev
165        bils_ec(:)=bils_ec(:)-d_t_ec(:,k)*masse(:,k)
166        bils_tke(:)=bils_tke(:)+0.5*(dtke(:,k)+dtke(:,k+1))*masse(:,k)
167        bils_diss(:)=bils_diss(:)-d_t_diss(:,k)*masse(:,k)
168        bils_kinetic(:)=bils_kinetic(:)+masse(:,k)* &
169     &           (pun(:,k)*pun(:,k)+pvn(:,k)*pvn(:,k) &
170     &            -puo(:,k)*puo(:,k)-pvo(:,k)*pvo(:,k))
171        bils_enthalp(:)= &
172     &  bils_enthalp(:)+masse(:,k)*(ptn(:,k)-pto(:,k)+d_t_ec(:,k)-d_t_eva(:,k)-d_t_lsc(:,k))
173!    &  bils_enthalp(:)+masse(:,k)*(ptn(:,k)-pto(:,k)+d_t_ec(:,k))
174        bils_latent(:)=bils_latent(:)+masse(:,k)* &
175!    &             (pqn(:,k)-pqo(:,k))
176     &             (pqn(:,k)-pqo(:,k)-d_q_eva(:,k)-d_q_lsc(:,k))
177      ENDDO
178      bils_ec(:)=rcpd*bils_ec(:)/pdtphys
179      bils_tke(:)=bils_tke(:)/pdtphys
180      bils_diss(:)=rcpd*bils_diss(:)/pdtphys
181      bils_kinetic(:)= 0.5*bils_kinetic(:)/pdtphys
182      bils_enthalp(:)=rcpd*bils_enthalp(:)/pdtphys
183      bils_latent(:)=rlvtt*bils_latent(:)/pdtphys
184
185IF (iflag_ener_conserv>=1) THEN
186      bils_ech(:)=0.
187      DO k=1,klev
188        bils_ech(:)=bils_ech(:)-d_t_ech(:,k)*masse(:,k)
189      ENDDO
190      bils_ech(:)=rcpd*bils_ech(:)/pdtphys
191ENDIF
192
193RETURN
194
195END
Note: See TracBrowser for help on using the repository browser.