source: LMDZ5/branches/Cold_pool_death/libf/phylmd/ener_conserv.F90 @ 4309

Last change on this file since 4309 was 2886, checked in by Laurent Fairhead, 7 years ago

Merged trunk changes r2865:2885 into testing branch

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