source: CONFIG/publications/ICOLMDZORINCA_CO2_Transport_GMD_2023/INCA/build/ppsrc/INCA_SRC/bl_for_dms.f90 @ 6610

Last change on this file since 6610 was 6610, checked in by acosce, 10 months ago

INCA used for ICOLMDZORINCA_CO2_Transport_GMD_2023

File size: 9.2 KB
Line 
1
2
3
4
5
6
7
8
9
10
11
12!$Id: bl_for_dms.F90 163 2010-02-22 15:41:45Z acosce $
13!! =========================================================================
14!! INCA - INteraction with Chemistry and Aerosols
15!!
16!! Copyright Laboratoire des Sciences du Climat et de l'Environnement (LSCE)
17!!           Unite mixte CEA-CNRS-UVSQ
18!!
19!! Contributors to this INCA subroutine:
20!!
21!! E. Cosme
22!!
23!! Anne Cozic, LSCE, anne.cozic@cea.fr
24!! Yann Meurdesoif, LSCE, yann.meurdesoif@cea.fr
25!!
26!! This software is a computer program whose purpose is to simulate the
27!! atmospheric gas phase and aerosol composition. The model is designed to be
28!! used within a transport model or a general circulation model. This version
29!! of INCA was designed to be coupled to the LMDz GCM. LMDz-INCA accounts
30!! for emissions, transport (resolved and sub-grid scale), photochemical
31!! transformations, and scavenging (dry deposition and washout) of chemical
32!! species and aerosols interactively in the GCM. Several versions of the INCA
33!! model are currently used depending on the envisaged applications with the
34!! chemistry-climate model.
35!!
36!! This software is governed by the CeCILL  license under French law and
37!! abiding by the rules of distribution of free software.  You can  use,
38!! modify and/ or redistribute the software under the terms of the CeCILL
39!! license as circulated by CEA, CNRS and INRIA at the following URL
40!! "http://www.cecill.info".
41!!
42!! As a counterpart to the access to the source code and  rights to copy,
43!! modify and redistribute granted by the license, users are provided only
44!! with a limited warranty  and the software's author,  the holder of the
45!! economic rights,  and the successive licensors  have only  limited
46!! liability.
47!!
48!! In this respect, the user's attention is drawn to the risks associated
49!! with loading,  using,  modifying and/or developing or reproducing the
50!! software by the user in light of its specific status of free software,
51!! that may mean  that it is complicated to manipulate,  and  that  also
52!! therefore means  that it is reserved for developers  and  experienced
53!! professionals having in-depth computer knowledge. Users are therefore
54!! encouraged to load and test the software's suitability as regards their
55!! requirements in conditions enabling the security of their systems and/or
56!! data to be ensured and,  more generally, to use and operate it in the
57!! same conditions as regards security.
58!!
59!! The fact that you are presently reading this means that you have had
60!! knowledge of the CeCILL license and that you accept its terms.
61!! =========================================================================
62
63
64SUBROUTINE bl_for_dms(u,v,paprs,pplay,cdragh,cdragm &
65     ,t,q,tsol,ustar,obklen)
66
67  USE INCA_DIM
68  USE PRINT_INCA
69  IMPLICIT NONE
70
71  !===================================================================
72  ! Auteur : E. Cosme
73  ! Calcul de la vitesse de friction (ustar) et de la longueur de
74  ! Monin-Obukhov (obklen), necessaires pour calculer les flux de DMS
75  ! par la methode de Nightingale.
76  ! Cette subroutine est plus que fortement inspiree de la subroutine
77  ! 'nonlocal' dans clmain.F .
78  ! reference :  Holtslag, A.A.M., and B.A. Boville, 1993:
79  ! Local versus nonlocal boundary-layer diffusion in a global climate
80  ! model. J. of Climate, vol. 6, 1825-1842. (a confirmer)
81  ! 31 08 01
82  !===================================================================
83  !
84!
85! $Header$
86!
87!  ATTENTION!!!!: ce fichier include est compatible format fixe/format libre
88!                 veillez à n'utiliser que des ! pour les commentaires
89!                 et à bien positionner les & des lignes de continuation
90!                 (les placer en colonne 6 et en colonne 73)
91!
92!
93! A1.0 Fundamental constants
94      REAL RPI,RCLUM,RHPLA,RKBOL,RNAVO
95! A1.1 Astronomical constants
96      REAL RDAY,REA,REPSM,RSIYEA,RSIDAY,ROMEGA
97! A1.1.bis Constantes concernant l'orbite de la Terre:
98      REAL R_ecc, R_peri, R_incl
99! A1.2 Geoide
100      REAL RA,RG,R1SA
101! A1.3 Radiation
102!     REAL RSIGMA,RI0
103      REAL RSIGMA
104! A1.4 Thermodynamic gas phase
105      REAL R,RMD,RMO3,RMV,RD,RV,RCPD,RCPV,RCVD,RCVV
106      REAL RKAPPA,RETV
107! A1.5,6 Thermodynamic liquid,solid phases
108      REAL RCW,RCS
109! A1.7 Thermodynamic transition of phase
110      REAL RLVTT,RLSTT,RLMLT,RTT,RATM
111! A1.8 Curve of saturation
112      REAL RESTT,RALPW,RBETW,RGAMW,RALPS,RBETS,RGAMS
113      REAL RALPD,RBETD,RGAMD
114!
115      COMMON/YOMCST_I/RPI   ,RCLUM ,RHPLA ,RKBOL ,RNAVO                   &
116     &      ,RDAY  ,REA   ,REPSM ,RSIYEA,RSIDAY,ROMEGA                  &
117     &      ,R_ecc, R_peri, R_incl                                      &
118     &      ,RA    ,RG    ,R1SA                                         &
119     &      ,RSIGMA                                                     &
120     &      ,R     ,RMD   ,RMO3  ,RMV   ,RD    ,RV    ,RCPD             &
121     &      ,RCPV  ,RCVD  ,RCVV  ,RKAPPA,RETV                           &
122     &      ,RCW   ,RCS                                                 &
123     &      ,RLVTT ,RLSTT ,RLMLT ,RTT   ,RATM                           &
124     &      ,RESTT ,RALPW ,RBETW ,RGAMW ,RALPS ,RBETS ,RGAMS            &
125     &      ,RALPD ,RBETD ,RGAMD
126!    ------------------------------------------------------------------
127!$OMP THREADPRIVATE(/YOMCST_I/)
128!
129! $Header$
130!
131!  ATTENTION!!!!: ce fichier include est compatible format fixe/format libre
132!                 veillez  n'utiliser que des ! pour les commentaires
133!                 et  bien positionner les & des lignes de continuation
134!                 (les placer en colonne 6 et en colonne 73)
135!
136!*    COMMON *YOETHF* DERIVED CONSTANTS SPECIFIC TO ECMWF THERMODYNAMICS
137!
138!     *R__ES*   *CONSTANTS USED FOR COMPUTATION OF SATURATION
139!                MIXING RATIO OVER LIQUID WATER(*R_LES*) OR
140!                ICE(*R_IES*).
141!     *RVTMP2*  *RVTMP2=RCPV/RCPD-1.
142!     *RHOH2O*  *DENSITY OF LIQUID WATER.   (RATM/100.)
143!
144      REAL R2ES, R3LES, R3IES, R4LES, R4IES, R5LES, R5IES
145      REAL RVTMP2, RHOH2O
146      COMMON /YOETHF_I/R2ES, R3LES, R3IES, R4LES, R4IES, R5LES, R5IES,    &
147     &               RVTMP2, RHOH2O
148!$OMP THREADPRIVATE(/YOETHF_I/)
149!
150! $Header$
151!
152!
153!  ATTENTION!!!!: ce fichier include est compatible format fixe/format libre
154!                 veillez  n'utiliser que des ! pour les commentaires
155!                 et  bien positionner les & des lignes de continuation
156!                 (les placer en colonne 6 et en colonne 73)
157!
158!     ------------------------------------------------------------------
159!     This COMDECK includes the Thermodynamical functions for the cy39
160!       ECMWF Physics package.
161!       Consistent with YOMCST Basic physics constants, assuming the
162!       partial pressure of water vapour is given by a first order
163!       Taylor expansion of Qs(T) w.r.t. to Temperature, using constants
164!       in YOETHF
165!     ------------------------------------------------------------------
166      REAL PTARG, PDELARG
167      REAL FOEEW
168!
169      FOEEW ( PTARG,PDELARG ) = EXP (                                   &
170     &          (R3LES*(1.-PDELARG)+R3IES*PDELARG) * (PTARG-RTT)        &
171     & / (PTARG-(R4LES*(1.-PDELARG)+R4IES*PDELARG)) )
172!
173
174
175  ! Arguments :
176  REAL u(PLON,PLEV)          ! vent zonal
177  REAL v(PLON,PLEV)          ! vent meridien
178  REAL paprs(PLON,PLEV+1)    ! niveaux de pression aux intercouches (Pa)
179  REAL pplay(PLON,PLEV)      ! niveaux de pression aux milieux... (Pa)
180  REAL cdragh(PLON)          ! coefficient de trainee pour la chaleur
181  REAL cdragm(PLON)          ! coefficient de trainee pour le vent
182  REAL t(PLON,PLEV)          ! temperature
183  REAL q(PLON,PLEV)          ! humidite kg/kg
184  REAL tsol(PLON)            ! temperature du sol
185  REAL ustar(PLON)           ! vitesse de friction
186  REAL obklen(PLON)          ! longueur de Monin-Obukhov
187
188  ! Locales :
189  REAL vk
190  PARAMETER (vk=0.35)
191  REAL beta  ! coefficient d'evaporation reelle (/evapotranspiration)
192  ! entre 0 et 1, mais 1 au-dessus de la mer
193  PARAMETER (beta=1.)
194  INTEGER i,k
195  REAL zxt, zxu, zxv, zxq, zxqs, zxmod, taux, tauy
196  REAL zcor, zdelta, zcvm5
197  REAL z(PLON,1)
198  REAL khfs(PLON)       ! surface kinematic heat flux [mK/s]
199  REAL kqfs(PLON)       ! sfc kinematic constituent flux [m/s]
200  REAL heatv(PLON)      ! surface virtual heat flux
201  !
202  !======================================================================
203  !
204  ! Calculer les hauteurs de chaque couche
205  !
206  DO i = 1, PLON
207     z(i,1) = RD * t(i,1) / (0.5*(paprs(i,1)+pplay(i,1))) &
208          * (paprs(i,1)-pplay(i,1)) / RG
209  ENDDO
210
211
212  DO i = 1, PLON
213     !
214     zdelta=MAX(0.,SIGN(1.,RTT-tsol(i)))
215     zcvm5 = R5LES*RLVTT*(1.-zdelta) + R5IES*RLSTT*zdelta
216     zcvm5 = zcvm5 / RCPD / (1.0+RVTMP2*q(i,1))
217     zxqs= R2ES * FOEEW(tsol(i),zdelta)/paprs(i,1)
218     zxqs=MIN(0.5,zxqs)
219     zcor=1./(1.-RETV*zxqs)
220     zxqs=zxqs*zcor
221
222     zxt = (t(i,1)+z(i,1)*RG/RCPD/(1.+RVTMP2*q(i,1))) &
223          *(1.+RETV*q(i,1))
224
225     zxu = u(i,1)
226     zxv = v(i,1)
227     zxq = q(i,1)
228     zxmod = 1.0+SQRT(zxu**2+zxv**2)
229     khfs(i) = (tsol(i)*(1.+RETV*q(i,1))-zxt) *zxmod*cdragh(i)
230     kqfs(i) = (zxqs-zxq) *zxmod*cdragh(i) * beta
231     heatv(i) = khfs(i) + 0.61*zxt*kqfs(i)
232     taux = zxu *zxmod*cdragm(i)
233     tauy = zxv *zxmod*cdragm(i)
234
235     ustar(i) = SQRT(taux**2+tauy**2)
236     ustar(i) = MAX(SQRT(ustar(i)),0.01)
237
238  ENDDO
239
240  DO i = 1, PLON
241     obklen(i) = -t(i,1)*ustar(i)**3/(RG*vk*heatv(i))
242  ENDDO
243
244END SUBROUTINE bl_for_dms
245
246
247
248
249
250
Note: See TracBrowser for help on using the repository browser.