source: LMDZ6/trunk/libf/phylmd/tend_to_tke.f90 @ 5319

Last change on this file since 5319 was 5285, checked in by abarral, 10 days ago

As discussed internally, remove generic ONLY: ... for new _mod_h modules

File size: 5.0 KB
Line 
1!***************************************************************************************
2! tend_to_tke.F90
3!*************
4!
5! Subroutine that adds a tendency on the TKE created by the
6! fluxes of momentum retrieved from the wind speed tendencies
7! of the physics.
8!
9! The basic concept is the following:
10! the TKE equation writes  de/dt = -u'w' du/dz -v'w' dv/dz +g/theta dtheta/dz +......
11!
12!
13! We expect contributions to the term u'w' and v'w' that do not come from the Yamada
14! scheme, for instance: gravity waves, drag from high vegetation..... These contributions
15! need to be accounted for.
16! we explicitely calculate the fluxes, integrating the wind speed
17!                        tendency from the top of the atmospher
18!
19!
20!
21! contacts: Frederic Hourdin, Etienne Vignon
22!
23! History:
24!---------
25! - 1st redaction, Etienne, 15/10/2016
26! Ajout des 4 sous surfaces pour la tke
27! on sort l'ajout des tendances du if sur les deux cas, pour ne pas
28! dupliuqer les lignes
29! on enleve le pas de temps qui disprait dans les calculs
30!
31!
32!**************************************************************************************
33
34 SUBROUTINE tend_to_tke(dt,plev,exner,temp,windu,windv,dt_a,du_a,dv_a,pctsrf,tke)
35
36 USE dimphy, ONLY: klon, klev
37 USE indice_sol_mod, ONLY: nbsrf
38
39USE yomcst_mod_h
40IMPLICIT NONE
41
42
43! Declarations
44!==============
45
46
47! Inputs
48!-------
49  REAL dt                   ! Time step [s]
50  REAL plev(klon,klev+1)    ! inter-layer pressure [Pa]
51  REAL temp(klon,klev)      ! temperature [K], grid-cell average or for a one subsurface
52  REAL windu(klon,klev)     ! zonal wind [m/s], grid-cell average or for a one subsurface
53  REAL windv(klon,klev)     ! meridonal wind [m/s], grid-cell average or for a one subsurface
54  REAL exner(klon,klev)     ! Fonction d'Exner = T/theta
55  REAL dt_a(klon,klev)      ! Temperature tendency [K], grid-cell average or for a one subsurface
56  REAL du_a(klon,klev)      ! Zonal wind speed tendency [m/s], grid-cell average or for a one subsurface
57  REAL dv_a(klon,klev)      ! Meridional wind speed tendency [m/s], grid-cell average or for a one subsurface
58  REAL pctsrf(klon,nbsrf+1)       ! Turbulent Kinetic energy [m2/s2], grid-cell average or for a subsurface
59
60! Inputs/Outputs
61!---------------
62  REAL tke(klon,klev+1,nbsrf+1)       ! Turbulent Kinetic energy [m2/s2], grid-cell average or for a subsurface
63
64
65! Local
66!-------
67
68
69  INTEGER i,k,isrf                 ! indices
70  REAL    masse(klon,klev)          ! mass in the layers [kg/m2]
71  REAL    unsmasse(klon,klev+1)     ! linear mass in the layers [kg/m2]
72  REAL    flux_rhotw(klon,klev+1)   ! flux massique de tempe. pot. rho*u'*theta'
73  REAL    flux_rhouw(klon,klev+1)   ! flux massique de quantit?? de mouvement rho*u'*w' [kg/m/s2]
74  REAL    flux_rhovw(klon,klev+1)   ! flux massique de quantit?? de mouvement rho*v'*w' [kg/m/s2]
75  REAL    tendt(klon,klev)        ! new temperature tke tendency [m2/s2/s]
76  REAL    tendu(klon,klev)        ! new zonal tke tendency [m2/s2/s]
77  REAL    tendv(klon,klev)        ! new meridonal tke tendency [m2/s2/s]
78 
79
80
81
82! First calculations:
83!=====================
84
85      unsmasse(:,:)=0.
86      DO k=1,klev
87         masse(:,k)=(plev(:,k)-plev(:,k+1))/RG
88         unsmasse(:,k)=unsmasse(:,k)+0.5/masse(:,k)
89         unsmasse(:,k+1)=unsmasse(:,k+1)+0.5/masse(:,k)
90      END DO
91
92      tendu(:,:)=0.0
93      tendv(:,:)=0.0
94
95! Method 1: Calculation of fluxes using a downward integration
96!============================================================
97
98
99 
100! Flux calculation
101
102 flux_rhotw(:,klev+1)=0.
103 flux_rhouw(:,klev+1)=0.
104 flux_rhovw(:,klev+1)=0.
105
106   DO k=klev,1,-1
107      flux_rhotw(:,k)=flux_rhotw(:,k+1)+masse(:,k)*dt_a(:,k)/exner(:,k)
108      flux_rhouw(:,k)=flux_rhouw(:,k+1)+masse(:,k)*du_a(:,k)
109      flux_rhovw(:,k)=flux_rhovw(:,k+1)+masse(:,k)*dv_a(:,k)
110   ENDDO
111
112
113! TKE update:
114
115   DO k=2,klev
116      tendt(:,k)=-flux_rhotw(:,k)*(exner(:,k)-exner(:,k-1))*unsmasse(:,k)*RCPD
117      tendu(:,k)=-flux_rhouw(:,k)*(windu(:,k)-windu(:,k-1))*unsmasse(:,k)
118      tendv(:,k)=-flux_rhovw(:,k)*(windv(:,k)-windv(:,k-1))*unsmasse(:,k)
119   ENDDO
120   tendt(:,1)=-flux_rhotw(:,1)*(exner(:,1)-1.)*unsmasse(:,1)*RCPD
121   tendu(:,1)=-1.*flux_rhouw(:,1)*windu(:,1)*unsmasse(:,1)
122   tendv(:,1)=-1.*flux_rhovw(:,1)*windv(:,1)*unsmasse(:,1)
123
124
125 DO isrf=1,nbsrf
126    DO k=1,klev
127       DO i=1,klon
128          IF (pctsrf(i,isrf)>0.) THEN
129            tke(i,k,isrf)= tke(i,k,isrf)+tendu(i,k)+tendv(i,k)+tendt(i,k)
130            tke(i,k,isrf)= max(tke(i,k,isrf),1.e-10)
131          ENDIF
132       ENDDO
133    ENDDO
134 ENDDO
135
136
137!  IF (klon==1) THEN
138!  CALL iophys_ecrit('u',klev,'u','',windu)
139!  CALL iophys_ecrit('v',klev,'v','',windu)
140!  CALL iophys_ecrit('t',klev,'t','',temp)
141!  CALL iophys_ecrit('tke1',klev,'tke1','',tke(:,1:klev,1))
142!  CALL iophys_ecrit('tke2',klev,'tke2','',tke(:,1:klev,2))
143!  CALL iophys_ecrit('tke3',klev,'tke3','',tke(:,1:klev,3))
144!  CALL iophys_ecrit('tke4',klev,'tke4','',tke(:,1:klev,4))
145!  CALL iophys_ecrit('theta',klev,'theta','',temp/exner)
146!  CALL iophys_ecrit('Duv',klev,'Duv','',tendu(:,1:klev)+tendv(:,1:klev))
147!  CALL iophys_ecrit('Dt',klev,'Dt','',tendt(:,1:klev))
148!  ENDIF
149
150 END SUBROUTINE tend_to_tke
Note: See TracBrowser for help on using the repository browser.