source: dynamico_lmdz/aquaplanet/LMDZ5/libf/phylmd/ener_conserv.F90 @ 3814

Last change on this file since 3814 was 3814, checked in by ymipsl, 10 years ago

remove all dynamic dependency in LMDZ physics except for the include "dimensions.h"

YM

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