Changeset 4819
- Timestamp:
- Feb 14, 2024, 8:55:10 PM (11 months ago)
- Location:
- LMDZ6/trunk/libf
- Files:
-
- 9 edited
Legend:
- Unmodified
- Added
- Removed
-
LMDZ6/trunk/libf/phylmd/lmdz_lscp.F90
r4818 r4819 19 19 Tcontr, qcontr, qcontr2, fcontrN, fcontrP, & 20 20 cloudth_sth,cloudth_senv,cloudth_sigmath,cloudth_sigmaenv, & 21 dqreva,dqssub,dqrauto,dqrcol,dqrmelt,dqrfreez,dqsauto, & 22 dqsagg,dqsrim,dqsmelt,dqsfreez) 21 qrain, qsnow, dqreva, dqssub, dqrauto, dqrcol, & 22 dqrmelt, dqrfreez, dqsauto, dqsagg, dqsrim, & 23 dqsmelt, dqsfreez) 23 24 24 25 !++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ … … 203 204 ! for POPRECIP 204 205 205 REAL, DIMENSION(klon,klev), INTENT(OUT) :: dqreva !-- rain tendendy due to evaporation [kg/kg/s] 206 REAL, DIMENSION(klon,klev), INTENT(OUT) :: dqssub !-- snow tendency due to sublimation [kg/kg/s] 207 REAL, DIMENSION(klon,klev), INTENT(OUT) :: dqrcol !-- rain tendendy due to collection by rain of liquid cloud droplets [kg/kg/s] 208 REAL, DIMENSION(klon,klev), INTENT(OUT) :: dqsagg !-- snow tendency due to collection of lcoud ice by aggregation [kg/kg/s] 209 REAL, DIMENSION(klon,klev), INTENT(OUT) :: dqrauto !-- rain tendency due to autoconversion of cloud liquid [kg/kg/s] 210 REAL, DIMENSION(klon,klev), INTENT(OUT) :: dqsauto !-- snow tendency due to autoconversion of cloud ice [kg/kg/s] 211 REAL, DIMENSION(klon,klev), INTENT(OUT) :: dqsrim !-- snow tendency due to riming [kg/kg/s] 212 REAL, DIMENSION(klon,klev), INTENT(OUT) :: dqsmelt !-- snow tendency due to melting [kg/kg/s] 213 REAL, DIMENSION(klon,klev), INTENT(OUT) :: dqrmelt !-- rain tendency due to melting [kg/kg/s] 214 REAL, DIMENSION(klon,klev), INTENT(OUT) :: dqsfreez !-- snow tendency due to freezing [kg/kg/s] 215 REAL, DIMENSION(klon,klev), INTENT(OUT) :: dqrfreez !-- rain tendency due to freezing [kg/kg/s] 206 REAL, DIMENSION(klon,klev), INTENT(OUT) :: qrain !--specific rain content [kg/kg] 207 REAL, DIMENSION(klon,klev), INTENT(OUT) :: qsnow !--specific snow content [kg/kg] 208 REAL, DIMENSION(klon,klev), INTENT(OUT) :: dqreva !--rain tendendy due to evaporation [kg/kg/s] 209 REAL, DIMENSION(klon,klev), INTENT(OUT) :: dqssub !--snow tendency due to sublimation [kg/kg/s] 210 REAL, DIMENSION(klon,klev), INTENT(OUT) :: dqrcol !--rain tendendy due to collection by rain of liquid cloud droplets [kg/kg/s] 211 REAL, DIMENSION(klon,klev), INTENT(OUT) :: dqsagg !--snow tendency due to collection of lcoud ice by aggregation [kg/kg/s] 212 REAL, DIMENSION(klon,klev), INTENT(OUT) :: dqrauto !--rain tendency due to autoconversion of cloud liquid [kg/kg/s] 213 REAL, DIMENSION(klon,klev), INTENT(OUT) :: dqsauto !--snow tendency due to autoconversion of cloud ice [kg/kg/s] 214 REAL, DIMENSION(klon,klev), INTENT(OUT) :: dqsrim !--snow tendency due to riming [kg/kg/s] 215 REAL, DIMENSION(klon,klev), INTENT(OUT) :: dqsmelt !--snow tendency due to melting [kg/kg/s] 216 REAL, DIMENSION(klon,klev), INTENT(OUT) :: dqrmelt !--rain tendency due to melting [kg/kg/s] 217 REAL, DIMENSION(klon,klev), INTENT(OUT) :: dqsfreez !--snow tendency due to freezing [kg/kg/s] 218 REAL, DIMENSION(klon,klev), INTENT(OUT) :: dqrfreez !--rain tendency due to freezing [kg/kg/s] 216 219 217 220 … … 371 374 temp_cltop(:,:)=0. 372 375 !-- poprecip 373 dqreva(:,:)=0.0 374 dqrauto(:,:)=0.0 375 dqrmelt(:,:)=0.0 376 dqrfreez(:,:)=0.0 377 dqrcol(:,:)=0.0 378 dqssub(:,:)=0.0 379 dqsauto(:,:)=0.0 380 dqsrim(:,:)=0.0 381 dqsagg(:,:)=0.0 382 dqsfreez(:,:)=0.0 383 dqsmelt(:,:)=0.0 376 qrain(:,:) = 0. 377 qsnow(:,:) = 0. 378 dqreva(:,:) = 0. 379 dqrauto(:,:) = 0. 380 dqrmelt(:,:) = 0. 381 dqrfreez(:,:) = 0. 382 dqrcol(:,:) = 0. 383 dqssub(:,:) = 0. 384 dqsauto(:,:) = 0. 385 dqsrim(:,:) = 0. 386 dqsagg(:,:) = 0. 387 dqsfreez(:,:) = 0. 388 dqsmelt(:,:) = 0. 384 389 385 390 … … 992 997 zrfl, zrflclr, zrflcld, & 993 998 zifl, ziflclr, ziflcld, & 994 dqrauto(:,k),dqrcol(:,k),dqrmelt(:,k),dqrfreez(:,k), & 995 dqsauto(:,k),dqsagg(:,k),dqsrim(:,k),dqsmelt(:,k),dqsfreez(:,k) & 999 qrain(:,k), qsnow(:,k), dqrauto(:,k), & 1000 dqrcol(:,k), dqrmelt(:,k), dqrfreez(:,k), & 1001 dqsauto(:,k), dqsagg(:,k), dqsrim(:,k), & 1002 dqsmelt(:,k), dqsfreez(:,k) & 996 1003 ) 997 1004 … … 1003 1010 zfice(i) = 0.0 1004 1011 ENDIF 1005 ! when poprecip activated, radiation does not see any precipitation content 1006 radocond(i,k) = zoliq(i) 1007 radocondl(i,k)= radocond(i,k)*(1.-zfice(i)) 1008 radocondi(i,k)= radocond(i,k)*zfice(i) 1012 1013 ! calculation of specific content of condensates seen by radiative scheme 1014 IF (ok_radocond_snow) THEN 1015 radocond(i,k) = zoliq(i) 1016 radocondl(i,k)= radocond(i,k)*(1.-zfice(i)) 1017 radocondi(i,k)= radocond(i,k)*zfice(i)+qsnow(i,k) 1018 ELSE 1019 radocond(i,k) = zoliq(i) 1020 radocondl(i,k)= radocond(i,k)*(1.-zfice(i)) 1021 radocondi(i,k)= radocond(i,k)*zfice(i) 1022 ENDIF 1009 1023 ENDDO 1010 1024 -
LMDZ6/trunk/libf/phylmd/lmdz_lscp_poprecip.F90
r4818 r4819 61 61 62 62 63 ! integer for interating over klon63 !--Integer for interating over klon 64 64 INTEGER :: i 65 66 ! saturation values 65 !--hum_to_flux: coef to convert a specific quantity to a flux 66 REAL, DIMENSION(klon) :: hum_to_flux 67 68 !--Saturation values 67 69 REAL, DIMENSION(klon) :: qzero, qsat, dqsat, qsatl, dqsatl, qsati, dqsati 68 ! fluxes tendencies because of evaporation69 REAL :: flevapmax, flevapl, flevapi, flevaptot70 ! specific humidity tendencies because of evaporation71 REAL :: dq evapl, dqevapi72 ! specific heat constant70 !--Fluxes tendencies because of evaporation and sublimation 71 REAL :: dprecip_evasub_max, draineva, dsnowsub, dprecip_evasub_tot 72 !--Specific humidity tendencies because of evaporation and sublimation 73 REAL :: dqrevap, dqssubl 74 !--Specific heat constant 73 75 REAL :: cpair, cpw 74 76 75 qzero(:) = 0.0 76 dqreva(:) = 0.0 77 dqssub(:) = 0.0 78 dqevapl=0.0 79 dqevapi=0.0 80 81 ! Calculation of saturation specific humidity 82 ! depending on temperature: 77 !--Initialisation 78 qzero(:) = 0. 79 dqreva(:) = 0. 80 dqssub(:) = 0. 81 dqrevap = 0. 82 dqssubl = 0. 83 84 !-- hum_to_flux = rho * dz/dt = 1 / g * dP/dt 85 hum_to_flux(:) = ( paprsdn(:) - paprsup(:) ) / RG / dtime 86 87 !--Calculation of saturation specific humidity 88 !--depending on temperature: 83 89 CALL calc_qsat_ecmwf(klon,temp(:),qzero(:),pplay(:),RTT,0,.false.,qsat(:),dqsat(:)) 84 ! 90 !--wrt liquid water 85 91 CALL calc_qsat_ecmwf(klon,temp(:),qzero(:),pplay(:),RTT,1,.false.,qsatl(:),dqsatl(:)) 86 ! 92 !--wrt ice 87 93 CALL calc_qsat_ecmwf(klon,temp(:),qzero(:),pplay(:),RTT,2,.false.,qsati(:),dqsati(:)) 88 94 89 95 90 96 91 ! 92 ! 93 ! 94 ! 97 !--First step consists in "thermalizing" the layer: 98 !--as the flux of precip from layer above "advects" some heat (as the precip is at the temperature 99 !--of the overlying layer) we recalculate a mean temperature that both the air and the precip in the 100 !--layer have. 95 101 96 102 IF (iftop) THEN 97 103 98 99 100 104 DO i = 1, klon 105 qprecip(i) = 0. 106 ENDDO 101 107 102 108 ELSE 103 109 104 105 ! no condensed water so cp=cp(vapor+dry air)106 !RVTMP2=rcpv/rcpd-1107 cpair=RCPD*(1.0+RVTMP2*qvap(i))108 cpw=RCPD*RVTMP2109 !qprecip has to be thermalized with110 !layer's air so that precipitation at the ground has the111 !same temperature as the lowermost layer112 !we convert the flux into a specific quantity qprecip113 qprecip(i) = (rain(i)+snow(i))*dtime/((paprsdn(i)-paprsup(i))/RG)114 ! t(i,k+1)+d_t(i,k+1): new temperature of the overlying layer115 temp(i) = ( (tempupnew(i))*qprecip(i)*cpw + cpair*temp(i) ) &116 / (cpair + qprecip(i)*cpw)117 110 DO i = 1, klon 111 !--No condensed water so cp=cp(vapor+dry air) 112 !-- RVTMP2=rcpv/rcpd-1 113 cpair = RCPD * ( 1. + RVTMP2 * qvap(i) ) 114 cpw = RCPD * RVTMP2 115 !--qprecip has to be thermalized with 116 !--layer's air so that precipitation at the ground has the 117 !--same temperature as the lowermost layer 118 !--we convert the flux into a specific quantity qprecip 119 qprecip(i) = ( rain(i) + snow(i) ) / hum_to_flux(i) 120 !-- t(i,k+1) + d_t(i,k+1): new temperature of the overlying layer 121 temp(i) = ( tempupnew(i) * qprecip(i) * cpw + cpair * temp(i) ) & 122 / ( cpair + qprecip(i) * cpw ) 123 ENDDO 118 124 119 125 ENDIF … … 122 128 DO i = 1, klon 123 129 124 ! ifprecipitation from the layer above130 !--If there is precipitation from the layer above 125 131 IF ( ( rain(i) + snow(i) ) .GT. 0. ) THEN 126 132 127 ! 128 ! dP/dz=beta*(1-q/qsat)*(P**expo_eva) (lines 1-2)129 ! multiplying by dz = - dP / g / rho (line 3-4)130 ! formula from Sundqvist 1988, Klemp & Wilhemson 1978131 ! LTP: evaporation only in the clear sky part132 133 flevapl = precipfracclr(i) * coef_eva * (1.0- qvap(i) / qsatl(i)) &134 * ( rainclr(i) / MAX(thresh_precip_frac, precipfracclr(i)) ) ** expo_eva &135 * temp(i) * RD / pplay(i) &136 * ( paprsdn(i) - paprsup(i) ) / RG137 138 ! evaporation is limited by 0 and by the total water amount in139 ! 140 flevapl = MAX(0.0, MIN(flevapl,rainclr(i)))141 142 143 ! sublimation of the solid precipitation coming from above144 ! 145 flevapi = precipfracclr(i) * coef_eva_i * (1.0- qvap(i) / qsati(i)) &146 * ( snowclr(i) / MAX(thresh_precip_frac, precipfracclr(i)) ) ** expo_eva_i &147 * temp(i) * RD / pplay(i) &148 * ( paprsdn(i) - paprsup(i) ) / RG149 150 ! sublimation is limited by 0 and by the total water amount in151 ! 133 !--Evaporation of liquid precipitation coming from above 134 !--in the clear sky only 135 !--dP/dz=beta*(1-q/qsat)*(P**expo_eva) (lines 1-2) 136 !--multiplying by dz = - dP / g / rho (line 3-4) 137 !--formula from Sundqvist 1988, Klemp & Wilhemson 1978 138 139 draineva = - precipfracclr(i) * coef_eva * (1. - qvap(i) / qsatl(i)) & 140 * ( rainclr(i) / MAX(thresh_precip_frac, precipfracclr(i)) ) ** expo_eva & 141 * temp(i) * RD / pplay(i) & 142 * ( paprsdn(i) - paprsup(i) ) / RG 143 144 !--Evaporation is limited by 0 and by the total water amount in 145 !--the precipitation 146 draineva = MIN(0., MAX(draineva, -rainclr(i))) 147 148 149 !--Sublimation of the solid precipitation coming from above 150 !--(same formula as for liquid precip) 151 dsnowsub = - precipfracclr(i) * coef_eva_i * (1. - qvap(i) / qsati(i)) & 152 * ( snowclr(i) / MAX(thresh_precip_frac, precipfracclr(i)) ) ** expo_eva_i & 153 * temp(i) * RD / pplay(i) & 154 * ( paprsdn(i) - paprsup(i) ) / RG 155 156 !--Sublimation is limited by 0 and by the total water amount in 157 !--the precipitation 152 158 ! TODO: change max when we will allow for vapor deposition in supersaturated regions 153 flevapi = MAX(0.0, MIN(flevapi, snowclr(i))) 154 155 ! Evaporation limit: we ensure that the layer's fraction below 156 ! the clear sky does not reach saturation. In this case, we 157 ! redistribute the maximum flux flevapmax conserving the ratio liquid/ice 158 ! Max evaporation is computed not to saturate the clear sky precip fraction 159 ! (i.e., the fraction where evaporation occurs) 160 ! It is expressed as a max flux flevapmax 161 ! 162 flevapmax = MAX(0.0, ( qsat(i) - qvap(i) ) * precipfracclr(i)) & 163 * ( paprsdn(i) - paprsup(i) ) / RG / dtime 164 flevaptot = flevapl + flevapi 165 166 IF ( flevaptot .GT. flevapmax ) THEN 167 flevapl = flevapmax * flevapl / flevaptot 168 flevapi = flevapmax * flevapi / flevaptot 159 dsnowsub = MIN(0., MAX(dsnowsub, -snowclr(i))) 160 161 !--Evaporation limit: we ensure that the layer's fraction below 162 !--the clear sky does not reach saturation. In this case, we 163 !--redistribute the maximum flux dprecip_evasub_max conserving the ratio liquid/ice 164 !--Max evaporation is computed not to saturate the clear sky precip fraction 165 !--(i.e., the fraction where evaporation occurs) 166 !--It is expressed as a max flux dprecip_evasub_max 167 168 dprecip_evasub_max = MIN(0., ( qvap(i) - qsat(i) ) * precipfracclr(i)) & 169 * hum_to_flux(i) 170 dprecip_evasub_tot = draineva + dsnowsub 171 172 !--Barriers 173 !--If activates if the total is LOWER than the max because 174 !--everything is negative 175 IF ( dprecip_evasub_tot .LT. dprecip_evasub_max ) THEN 176 draineva = dprecip_evasub_max * draineva / dprecip_evasub_tot 177 dsnowsub = dprecip_evasub_max * dsnowsub / dprecip_evasub_tot 169 178 ENDIF 170 179 171 180 172 ! 173 dq evapl = flevapl / ( paprsdn(i) - paprsup(i) ) * RG * dtime174 dq evapi = flevapi / ( paprsdn(i) - paprsup(i) ) * RG * dtime175 176 177 ! vapor is updated after evaporation/sublimation (it is increased)178 qvap(i) = qvap(i) + dqevapl + dqevapi179 ! 180 qprecip(i) = qprecip(i) - dqevapl - dqevapi181 ! air and precip temperature (i.e., gridbox temperature)182 ! 181 !--New solid and liquid precipitation fluxes after evap and sublimation 182 dqrevap = draineva / hum_to_flux(i) 183 dqssubl = dsnowsub / hum_to_flux(i) 184 185 186 !--Vapor is updated after evaporation/sublimation (it is increased) 187 qvap(i) = qvap(i) - dqrevap - dqssubl 188 !--qprecip is the total condensed water in the precip flux (it is decreased) 189 qprecip(i) = qprecip(i) + dqrevap + dqssubl 190 !--Air and precip temperature (i.e., gridbox temperature) 191 !--is updated due to latent heat cooling 183 192 temp(i) = temp(i) & 184 - dqevapl* RLVTT / RCPD &185 / ( 1. 0+ RVTMP2 * ( qvap(i) + qprecip(i) ) ) &186 - dqevapi* RLSTT / RCPD &187 / ( 1. 0+ RVTMP2 * ( qvap(i) + qprecip(i) ) )188 189 ! New values of liquid and solid precipitation190 rainclr(i) = rainclr(i) - flevapl191 snowclr(i) = snowclr(i) - flevapi192 193 ! if there is no more precip fluxes, the precipitation fraction in clear194 ! 193 + dqrevap * RLVTT / RCPD & 194 / ( 1. + RVTMP2 * ( qvap(i) + qprecip(i) ) ) & 195 + dqssubl * RLSTT / RCPD & 196 / ( 1. + RVTMP2 * ( qvap(i) + qprecip(i) ) ) 197 198 !--Add tendencies 199 rainclr(i) = rainclr(i) + draineva 200 snowclr(i) = snowclr(i) + dsnowsub 201 202 !--If there is no more precip fluxes, the precipitation fraction in clear 203 !--sky is set to 0 195 204 IF ( ( rainclr(i) + snowclr(i) ) .LE. 0. ) precipfracclr(i) = 0. 196 205 197 ! calculation of the total fluxes206 !--Calculation of the total fluxes 198 207 rain(i) = rainclr(i) + raincld(i) 199 208 snow(i) = snowclr(i) + snowcld(i) 200 209 201 210 ELSE 202 ! if no precip, we reinitialize the cloud fraction used for the precip to 0211 !--If no precip, we reinitialize the cloud fraction used for the precip to 0 203 212 precipfraccld(i) = 0. 204 213 precipfracclr(i) = 0. … … 206 215 ENDIF ! ( ( rain(i) + snow(i) ) .GT. 0. ) 207 216 208 209 210 ! write output tendencies for rain and snow 211 212 dqssub(i) = -dqevapi/dtime 213 dqreva(i) = -dqevapl/dtime 217 !--Diagnostic tendencies 218 dqssub(i) = dqssubl / dtime 219 dqreva(i) = dqrevap / dtime 214 220 215 221 ENDDO ! loop on klon … … 232 238 precipfracclr, precipfraccld, & 233 239 rain, rainclr, raincld, snow, snowclr, snowcld, & 234 dqrauto, dqrcol, dqrmelt, dqrfreez, dqsauto, dqsagg, &235 dqs rim, dqsmelt, dqsfreez)240 qrain, qsnow, dqrauto, dqrcol, dqrmelt, dqrfreez, & 241 dqsauto, dqsagg, dqsrim, dqsmelt, dqsfreez) 236 242 237 243 USE lmdz_lscp_ini, ONLY : prt_level, lunout … … 258 264 REAL, INTENT(IN), DIMENSION(klon) :: pplay !--pressure in the middle of the layer [Pa] 259 265 260 REAL, INTENT(IN), DIMENSION(klon) :: ctot_vol !-- 261 LOGICAL, INTENT(IN), DIMENSION(klon) :: ptconv !-- 266 REAL, INTENT(IN), DIMENSION(klon) :: ctot_vol !--volumic cloud fraction [-] 267 LOGICAL, INTENT(IN), DIMENSION(klon) :: ptconv !--true if we are in a convective point 262 268 263 269 REAL, INTENT(INOUT), DIMENSION(klon) :: temp !--current temperature [K] … … 265 271 REAL, INTENT(INOUT), DIMENSION(klon) :: qliq !--current liquid water specific humidity [kg/kg] 266 272 REAL, INTENT(INOUT), DIMENSION(klon) :: qice !--current ice water specific humidity [kg/kg] 267 REAL, INTENT(IN), DIMENSION(klon) :: icefrac !-- 268 REAL, INTENT(IN), DIMENSION(klon) :: cldfra !-- 273 REAL, INTENT(IN), DIMENSION(klon) :: icefrac !--ice fraction [-] 274 REAL, INTENT(IN), DIMENSION(klon) :: cldfra !--cloud fraction [-] 269 275 270 276 REAL, INTENT(INOUT), DIMENSION(klon) :: precipfracclr !--fraction of precipitation in the clear sky IN THE LAYER ABOVE [-] … … 280 286 REAL, INTENT(INOUT), DIMENSION(klon) :: snowcld !--flux of snow gridbox-mean in cloudy air coming from the layer above [kg/s/m2] 281 287 282 REAL, INTENT(OUT), DIMENSION(klon) :: dqrcol !-- rain tendendy due to collection by rain of liquid cloud droplets [kg/kg/s] 283 REAL, INTENT(OUT), DIMENSION(klon) :: dqsagg !-- snow tendency due to collection of lcoud ice by aggregation [kg/kg/s] 284 REAL, INTENT(OUT), DIMENSION(klon) :: dqrauto !-- rain tendency due to autoconversion of cloud liquid [kg/kg/s] 285 REAL, INTENT(OUT), DIMENSION(klon) :: dqsauto !-- snow tendency due to autoconversion of cloud ice [kg/kg/s] 286 REAL, INTENT(OUT), DIMENSION(klon) :: dqsrim !-- snow tendency due to riming [kg/kg/s] 287 REAL, INTENT(OUT), DIMENSION(klon) :: dqsmelt !-- snow tendency due to melting [kg/kg/s] 288 REAL, INTENT(OUT), DIMENSION(klon) :: dqrmelt !-- rain tendency due to melting [kg/kg/s] 289 REAL, INTENT(OUT), DIMENSION(klon) :: dqsfreez !-- snow tendency due to freezing [kg/kg/s] 290 REAL, INTENT(OUT), DIMENSION(klon) :: dqrfreez !-- rain tendency due to freezing [kg/kg/s] 288 REAL, INTENT(OUT), DIMENSION(klon) :: qrain !--specific rain content [kg/kg] 289 REAL, INTENT(OUT), DIMENSION(klon) :: qsnow !--specific snow content [kg/kg] 290 REAL, INTENT(OUT), DIMENSION(klon) :: dqrcol !--rain tendendy due to collection by rain of liquid cloud droplets [kg/kg/s] 291 REAL, INTENT(OUT), DIMENSION(klon) :: dqsagg !--snow tendency due to collection of lcoud ice by aggregation [kg/kg/s] 292 REAL, INTENT(OUT), DIMENSION(klon) :: dqrauto !--rain tendency due to autoconversion of cloud liquid [kg/kg/s] 293 REAL, INTENT(OUT), DIMENSION(klon) :: dqsauto !--snow tendency due to autoconversion of cloud ice [kg/kg/s] 294 REAL, INTENT(OUT), DIMENSION(klon) :: dqsrim !--snow tendency due to riming [kg/kg/s] 295 REAL, INTENT(OUT), DIMENSION(klon) :: dqsmelt !--snow tendency due to melting [kg/kg/s] 296 REAL, INTENT(OUT), DIMENSION(klon) :: dqrmelt !--rain tendency due to melting [kg/kg/s] 297 REAL, INTENT(OUT), DIMENSION(klon) :: dqsfreez !--snow tendency due to freezing [kg/kg/s] 298 REAL, INTENT(OUT), DIMENSION(klon) :: dqrfreez !--rain tendency due to freezing [kg/kg/s] 291 299 292 300 … … 307 315 ! collection, aggregation and riming 308 316 REAL :: eff_cldfra 309 REAL :: coef_col, coef_agg, coef_rim, coef_tmp, qrain 317 REAL :: coef_col, coef_agg, coef_rim, coef_tmp, qrain_tmp 310 318 REAL :: Eff_rain_liq, Eff_snow_ice, Eff_snow_liq 311 319 REAL :: dqlcol ! loss of liquid cloud content due to collection by rain [kg/kg/s] … … 465 473 !--want to collect/aggregate the newly formed fluxes, which already 466 474 !--"saw" the cloud as they come from it 475 !--The formulas come from Muench and Lohmann 2020 476 467 477 !--gamma_col: tuning coefficient [-] 468 478 !--rho_rain: volumic mass of rain [kg/m3] … … 476 486 coef_col = gamma_col * 3. / 4. / rho_rain / r_rain * Eff_rain_liq 477 487 IF ((raincld(i) .GT. 0.) .AND. (coef_col .GT. 0.)) THEN 478 !--Explicit version 479 !dqlcol = - coef_col * qliq(i) * raincld(i) / precipfraccld(i) *dtime 480 !--Semi-implicit version 481 !dqlcol = qliq(i) * ( 1. / ( 1. + coef_col * raincld(i) / precipfraccld(i)*dtime ) - 1. ) 482 !--Implicit version 483 !qrain = raincld(i) / hum_to_flux(i) 484 !coef_tmp = coef_col * dtime * ( qrain / precipfraccld(i) + qliq(i) / eff_cldfra ) 488 !-- ATTENTION Double implicit version 489 !qrain_tmp = raincld(i) / hum_to_flux(i) 490 !coef_tmp = coef_col * dtime * ( qrain_tmp / precipfraccld(i) + qliq(i) / eff_cldfra ) 485 491 !dqlcol = qliq(i) * ( 1. / ( 1. + 0.5 * ( coef_tmp - 1. + SQRT( & 486 ! ( 1. - coef_tmp )**2. + 4. * coef_col * dtime * qrain / precipfraccld(i) ) &492 ! ( 1. - coef_tmp )**2. + 4. * coef_col * dtime * qrain_tmp / precipfraccld(i) ) & 487 493 ! ) ) - 1. ) 488 494 !--Barriers so that the processes do not consume more liquid/ice than 489 495 !--available. 490 496 !dqlcol = MAX( - qliq(i), dqlcol ) 491 !--Exact version 497 !--Exact version, which does not need a barrier because of 498 !--the exponential decrease 492 499 dqlcol = qliq(i) * ( EXP( - dtime * coef_col * raincld(i) / precipfraccld(i) ) - 1. ) 493 500 … … 496 503 raincld(i) = raincld(i) - dqlcol * hum_to_flux(i) 497 504 498 !-- Outputs505 !--Diagnostic tendencies 499 506 dqrcol(i) = - dqlcol / dtime 500 507 ENDIF 501 508 502 509 !--Same as for aggregation 503 !-- Following Milbrandt and Yau 2005, it s a product of a collection504 !-- efficiency and a sticking efficiency510 !--Eff_snow_liq formula: following Milbrandt and Yau 2005, 511 !--it s a product of a collection efficiency and a sticking efficiency 505 512 Eff_snow_ice = 0.05 * EXP( 0.1 * ( temp(i) - RTT ) ) 506 513 coef_agg = gamma_agg * 3. / 4. / rho_snow / r_snow * Eff_snow_ice 507 514 IF ((snowcld(i) .GT. 0.) .AND. (coef_agg .GT. 0.)) THEN 508 !--Explicit version 509 !dqiagg = - coef_agg & 510 ! * qice(i) * snowcld(i) / precipfraccld(i) * dtime 515 !-- ATTENTION Double implicit version? 511 516 !--Barriers so that the processes do not consume more liquid/ice than 512 517 !--available. 513 518 !dqiagg = MAX( - qice(i), dqiagg ) 514 !--Exact version 519 !--Exact version, which does not need a barrier because of 520 !--the exponential decrease 515 521 dqiagg = qice(i) * ( EXP( - dtime * coef_agg * snowcld(i) / precipfraccld(i) ) - 1. ) 516 522 … … 519 525 snowcld(i) = snowcld(i) - dqiagg * hum_to_flux(i) 520 526 521 !-- Outputs527 !--Diagnostic tendencies 522 528 dqsagg(i) = - dqiagg / dtime 523 529 ENDIF … … 527 533 !-- AUTOCONVERSION 528 534 !--------------------------------------------------------- 529 530 ! TODO 531 IF ( ptconv(i) ) THEN ! if convective point 535 !--Autoconversion converts liquid droplets/ice crystals into 536 !--rain drops/snowflakes. It relies on the formulations by 537 !--Sundqvist 1978. 538 ! TODO what else? 539 540 !--If we are in a convective point, we have different parameters 541 !--for the autoconversion 542 IF ( ptconv(i) ) THEN 543 ! ATTENTION voir les constantes ici qui ne devraient pas etre identiques 532 544 qthresh_auto_rain = cld_lc_con 533 545 qthresh_auto_snow = cld_lc_con 534 546 535 547 tau_auto_rain = cld_tau_con 548 !--tau for snow depends on the ice fraction in mixed-phase clouds 536 549 tau_auto_snow = tau_auto_snow_max & 537 550 + ( tau_auto_snow_min - tau_auto_snow_max ) * ( 1. - icefrac(i) ) … … 540 553 expo_auto_snow = cld_expo_con 541 554 ELSE 555 ! ATTENTION voir les constantes ici qui ne devraient pas etre identiques 542 556 qthresh_auto_rain = cld_lc_lsc 543 557 qthresh_auto_snow = cld_lc_lsc 544 558 545 559 tau_auto_rain = cld_tau_lsc 560 !--tau for snow depends on the ice fraction in mixed-phase clouds 546 561 tau_auto_snow = tau_auto_snow_max & 547 562 + ( tau_auto_snow_min - tau_auto_snow_max ) * ( 1. - icefrac(i) ) … … 553 568 554 569 ! Liquid water quantity to remove according to (Sundqvist, 1978) 555 ! dqliq/dt =-qliq/tau*(1-exp(-qcin/clw)**2)570 ! dqliq/dt = -qliq/tau * ( 1-exp(-(qcin/clw)**2) ) 556 571 !......................................................... 557 572 ! we first treat the second term (with exponential) in an explicit way … … 565 580 566 581 582 !--Barriers so that we don t create more rain/snow 583 !--than there is liquid/ice 567 584 dqlauto = MAX( - qliq(i), dqlauto ) 568 585 dqiauto = MAX( - qice(i), dqiauto ) 569 586 587 !--Add tendencies 570 588 qliq(i) = qliq(i) + dqlauto 571 589 qice(i) = qice(i) + dqiauto 572 573 590 raincld(i) = raincld(i) - dqlauto * hum_to_flux(i) 574 591 snowcld(i) = snowcld(i) - dqiauto * hum_to_flux(i) 575 592 576 !-- Outputs593 !--Diagnostic tendencies 577 594 dqsauto(i) = - dqiauto / dtime 578 595 dqrauto(i) = - dqlauto / dtime 579 596 580 581 ! FOLLOWING PROCESSES IMPLY A PHASE CHANGE SO A TEMPERATURE582 ! ADJUSTMENT583 597 584 598 !--------------------------------------------------------- 585 599 !-- RIMING 586 600 !--------------------------------------------------------- 587 588 !--Following Seifert and Beheng 2006, assuming a cloud droplet diameter 589 !--of 20 microns. 601 !--Process which converts liquid droplets in suspension into 602 !--snow (graupel in fact) because of the collision between 603 !--those and falling snowflakes. 604 !--The formula come from Muench and Lohmann 2020 605 !--NB.: this process needs a temperature adjustment 606 607 !--Eff_snow_liq formula: following Seifert and Beheng 2006, 608 !--assuming a cloud droplet diameter of 20 microns. 590 609 Eff_snow_liq = 0.2 591 610 coef_rim = gamma_rim * 3. / 4. / rho_snow / r_snow * Eff_snow_liq 592 611 IF ((snowcld(i) .GT. 0.) .AND. (coef_rim .GT. 0.)) THEN 593 !--Explicit version 594 !dqlrim = - gamma_rim * 3. / 4. / rho_snow / r_snow * Eff_snow_liq & 595 ! * qliq(i) * snowcld(i) / precipfraccld(i) * dtime 612 !-- ATTENTION Double implicit version? 596 613 !--Barriers so that the processes do not consume more liquid than 597 614 !--available. 598 615 !dqlrim = MAX( - qliq(i), dqlrim ) 599 !--Exact version 616 !--Exact version, which does not need a barrier because of 617 !--the exponential decrease 600 618 dqlrim = qliq(i) * ( EXP( - dtime * coef_col * snowcld(i) / precipfraccld(i) ) - 1. ) 601 619 620 !--Add tendencies 602 621 qliq(i) = qliq(i) + dqlrim 603 622 snowcld(i) = snowcld(i) - dqlrim * hum_to_flux(i) 604 623 605 ! Latent heat of melting with precipitation thermalization 624 !--Temperature adjustment with the release of latent 625 !--heat because of solid condensation 606 626 temp(i) = temp(i) - dqlrim * RLMLT / RCPD & 607 627 / ( 1. + RVTMP2 * qtot(i) ) 608 628 609 !-- Outputs629 !--Diagnostic tendencies 610 630 dqsrim(i) = - dqlrim / dtime 611 631 ENDIF 612 632 613 ENDIF ! rneb .GE. seuil_neb 614 615 ENDDO ! iteration on klon 616 617 618 ! Calculation of saturation specific humidity 619 ! depending on temperature: 633 ! ATTENTION veut on faire un processus similaire et symetrique qui 634 ! convertirait la pluie en surfusion qui tombe sur des cristaux de glace 635 ! en flux de neige ? (si la temperature est negative) 636 637 ENDIF ! cldfra .GE. seuil_neb 638 639 ENDDO ! loop on klon 640 641 642 !--Re-calculation of saturation specific humidity 643 !--because riming changed temperature 620 644 CALL calc_qsat_ecmwf(klon, temp, qzero, pplay, RTT, 0, .FALSE., qsat, dqsat) 621 645 … … 625 649 !-- MELTING 626 650 !--------------------------------------------------------- 651 !--Process through which snow melts into rain. 652 !--The formula is homemade. 653 !--NB.: this process needs a temperature adjustment 654 655 !--dqsmelt_max: maximum snow melting so that temperature 656 !-- stays higher than 273 K [kg/kg] 657 !--capa_snowflake: capacitance of a snowflake, equal to 658 !-- the radius if the snowflake is a sphere [m] 659 !--temp_wetbulb: wet-bulb temperature [K] 660 !--fallice: snow fall velocity (in clear/cloudy sky) [m/s] 661 !--air_thermal_conduct: thermal conductivity of the air [J/m/K/s] 662 !--coef_ventil: ventilation coefficient [-] 663 !--nb_snowflake: number of snowflakes (in clear/cloudy air) [-] 627 664 628 665 IF ( ( snowclr(i) + snowcld(i) ) .GT. 0. ) THEN 666 !--Computed according to 667 !--Cpdry * Delta T * (1 + (Cpvap/Cpdry - 1) * qtot) = Lfusion * Delta q 629 668 dqsmelt_max = MIN(0., ( RTT - temp(i) ) / RLMLT * RCPD & 630 669 * ( 1. + RVTMP2 * qtot(i) )) 631 670 671 !--Initialisation 632 672 dqsclrmelt = 0. 633 673 dqscldmelt = 0. … … 640 680 - 40.637 * ( temp(i) - 275. ) ) 641 681 682 !--In clear air 642 683 IF ( snowclr(i) .GT. 0. ) THEN 643 ! ATTENTION ATTENTION ATTENTION684 ! ATTENTION fallice a definir 644 685 fallice_clr = 1. 686 !--Calculated according to 687 !-- flux = velocity_snowflakes * nb_snowflakes * volume_snowflakes * rho_snow 645 688 nb_snowflake_clr = snowclr(i) / precipfracclr(i) / fallice_clr & 646 689 / ( 4. / 3. * RPI * r_snow**3. * rho_snow ) … … 650 693 ENDIF 651 694 695 !--In cloudy air 652 696 IF ( snowcld(i) .GT. 0. ) THEN 653 ! ATTENTION ATTENTION ATTENTION697 ! ATTENTION fallice a definir 654 698 fallice_cld = 1. 699 !--Calculated according to 700 !-- flux = velocity_snowflakes * nb_snowflakes * volume_snowflakes * rho_snow 655 701 nb_snowflake_cld = snowcld(i) / precipfraccld(i) / fallice_cld & 656 702 / ( 4. / 3. * RPI * r_snow**3. * rho_snow ) … … 660 706 ENDIF 661 707 662 ! barrier 663 ! lower than bec. negative values 708 !--Barriers 709 !--It is activated if the total is LOWER than the max 710 !--because everything is negative 664 711 dqstotmelt = dqsclrmelt + dqscldmelt 665 712 IF ( dqstotmelt .LT. dqsmelt_max ) THEN 713 !--We redistribute the max melted snow keeping 714 !--the clear/cloud partition of the melted snow 666 715 dqsclrmelt = dqsmelt_max * dqsclrmelt / dqstotmelt 667 716 dqscldmelt = dqsmelt_max * dqscldmelt / dqstotmelt … … 669 718 ENDIF 670 719 671 ! update of rainfall and snowfall due to melting720 !--Add tendencies 672 721 rainclr(i) = rainclr(i) - dqsclrmelt * hum_to_flux(i) 673 722 raincld(i) = raincld(i) - dqscldmelt * hum_to_flux(i) … … 675 724 snowcld(i) = snowcld(i) + dqscldmelt * hum_to_flux(i) 676 725 677 ! Latent heat of melting with precipitation thermalization 726 !--Temperature adjustment with the release of latent 727 !--heat because of melting 678 728 temp(i) = temp(i) + dqstotmelt * RLMLT / RCPD & 679 729 / ( 1. + RVTMP2 * qtot(i) ) 680 730 731 !--Diagnostic tendencies 681 732 dqrmelt(i) = - dqstotmelt / dtime 682 733 dqsmelt(i) = dqstotmelt / dtime … … 688 739 !-- FREEZING 689 740 !--------------------------------------------------------- 741 !--Process through which rain freezes into snow. This is 742 !--parameterized as an exponential decrease of the rain 743 !--water content. 744 !--The formula is homemade. 745 !--This is based on a caracteritic time of freezing, which 746 !--exponentially depends on temperature so that it is 747 !--equal to 1 for temp_nowater (see below) and is close to 748 !--0 for RTT (=273.15 K). 749 !--NB.: this process needs a temperature adjustment 750 751 !--dqrfreez_max: maximum rain freezing so that temperature 752 !-- stays lower than 273 K [kg/kg] 753 !--tau_freez: caracteristic time of freezing [s] 754 !--gamma_freez: tuning parameter [s-1] 755 !--alpha_freez: tuning parameter for the shape of the exponential curve [-] 756 !--temp_nowater: temperature below which no liquid water exists [K] (about -40 degC) 690 757 691 758 IF ( ( rainclr(i) + raincld(i) ) .GT. 0. ) THEN 692 759 760 !--Computed according to 761 !--Cpdry * Delta T * (1 + (Cpvap/Cpdry - 1) * qtot) = Lfusion * Delta q 693 762 dqrfreez_max = MIN(0., ( temp(i) - RTT ) / RLMLT * RCPD & 694 763 * ( 1. + RVTMP2 * qtot(i) )) 695 764 696 765 tau_freez = 1. / ( gamma_freez & 697 766 * EXP( - alpha_freez * ( temp(i) - temp_nowater ) / ( RTT - temp_nowater ) ) ) 767 !--Exact solution of dqrain/dt = -qrain/tau_freez 698 768 dqrtotfreez = raincld(i) / hum_to_flux(i) * ( EXP( - dtime / tau_freez ) - 1. ) 699 769 700 ! barrier701 ! max bec. those are negative values770 !--Barrier 771 !--It is a MAX because everything is negative 702 772 dqrtotfreez = MAX(dqrtotfreez, dqrfreez_max) 703 773 704 ! partition between clear and cloudy air705 ! proportionnal to the rain fluxes in clear / cloud774 !--The partition between clear and cloudy air 775 !--is proportionnal to the rain fluxes in clear / cloudy air 706 776 dqrclrfreez = dqrtotfreez * rainclr(i) / ( rainclr(i) + raincld(i) ) 707 777 dqrcldfreez = dqrtotfreez - dqrclrfreez 708 778 709 ! update of rainfall and snowfall due to melting779 !--Add tendencies 710 780 rainclr(i) = rainclr(i) + dqrclrfreez * hum_to_flux(i) 711 781 raincld(i) = raincld(i) + dqrcldfreez * hum_to_flux(i) … … 713 783 snowcld(i) = snowcld(i) - dqrcldfreez * hum_to_flux(i) 714 784 715 ! Latent heat of melting with precipitation thermalization 785 !--Temperature adjustment with the uptake of latent 786 !--heat because of freezing 716 787 temp(i) = temp(i) - dqrtotfreez * RLMLT / RCPD & 717 788 / ( 1. + RVTMP2 * qtot(i) ) 718 789 790 !--Diagnostic tendencies 719 791 dqrfreez(i) = dqrtotfreez / dtime 720 792 dqsfreez(i) = - dqrtotfreez / dtime … … 722 794 ENDIF 723 795 724 725 !! MISE A JOUR DES FRACTIONS PRECIP CLD et CS 726 ! LTP: limit of surface cloud fraction covered by precipitation when the local intensity of the flux is below rain_int_min 727 796 !--If the local flux of rain+snow in clear/cloudy air is lower than rain_int_min, 797 !--we reduce the precipiration fraction in the clear/cloudy air so that the new 798 !--local flux of rain+snow is equal to rain_int_min. 799 !--Here, rain+snow is the gridbox-mean flux of precip. 800 !--Therefore, (rain+snow)/precipfrac is the local flux of precip. 801 !--If the local flux of precip is lower than rain_int_min, i.e., 802 !-- (rain+snow)/precipfrac < rain_int_min , i.e., 803 !-- (rain+snow)/rain_int_min < precipfrac , then we want to reduce 804 !--the precip fraction to the equality, i.e., precipfrac = (rain+snow)/rain_int_min. 805 !--Note that this is physically different than what is proposed in LTP thesis. 728 806 precipfracclr(i) = MIN( precipfracclr(i), ( rainclr(i) + snowclr(i) ) / rain_int_min ) 729 807 precipfraccld(i) = MIN( precipfraccld(i), ( raincld(i) + snowcld(i) ) / rain_int_min ) 730 808 809 !--Calculate outputs 731 810 rain(i) = rainclr(i) + raincld(i) 732 811 snow(i) = snowclr(i) + snowcld(i) 733 812 734 ! write output tendencies for rain and snow 735 736 ENDDO 737 738 813 !--Diagnostics 814 ! ATTENTION A REPRENDRE 815 qrain(i) = rain(i) / hum_to_flux(i) 816 qsnow(i) = snow(i) / hum_to_flux(i) 817 818 ENDDO ! loop on klon 739 819 740 820 END SUBROUTINE poprecip_postcld -
LMDZ6/trunk/libf/phylmd/phys_local_var_mod.F90
r4803 r4819 539 539 540 540 !--POPRECIP variables 541 REAL, SAVE, ALLOCATABLE :: qrain_lsc(:,:) 542 !$OMP THREADPRIVATE(qrain_lsc) 543 REAL, SAVE, ALLOCATABLE :: qsnow_lsc(:,:) 544 !$OMP THREADPRIVATE(qsnow_lsc) 541 545 REAL, SAVE, ALLOCATABLE :: dqreva(:,:) 542 546 !$OMP THREADPRIVATE(dqreva) … … 958 962 959 963 !--POPRECIP variables 960 ALLOCATE(dqreva(klon,klev),dqssub(klon,klev)) 964 ALLOCATE(qrain_lsc(klon,klev), qsnow_lsc(klon,klev)) 965 ALLOCATE(dqreva(klon,klev), dqssub(klon,klev)) 961 966 ALLOCATE(dqrauto(klon,klev), dqrcol(klon,klev), dqrmelt(klon,klev), dqrfreez(klon,klev)) 962 967 ALLOCATE(dqsauto(klon,klev), dqsagg(klon,klev), dqsrim(klon,klev), dqsmelt(klon,klev), dqsfreez(klon,klev)) … … 1273 1278 1274 1279 !--POPRECIP variables 1275 DEALLOCATE(dqreva,dqssub) 1276 DEALLOCATE(dqrauto,dqrcol,dqrmelt,dqrfreez) 1277 DEALLOCATE(dqsauto,dqsagg,dqsrim,dqsmelt,dqsfreez) 1280 DEALLOCATE(qrain_lsc, qsnow_lsc) 1281 DEALLOCATE(dqreva, dqssub) 1282 DEALLOCATE(dqrauto, dqrcol, dqrmelt, dqrfreez) 1283 DEALLOCATE(dqsauto, dqsagg, dqsrim, dqsmelt, dqsfreez) 1278 1284 1279 1285 #ifdef CPP_StratAer -
LMDZ6/trunk/libf/phylmd/phys_output_ctrlout_mod.F90
r4803 r4819 1556 1556 TYPE(ctrl_out), SAVE :: o_pfracld = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 11/), & 1557 1557 'pfracld', 'LS precipitation fraction cloudy part', '-', (/ ('', i=1, 10) /)) 1558 TYPE(ctrl_out), SAVE :: o_qrainlsc = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 11/), & 1559 'qrainlsc', 'LS specific rain content', 'kg/kg', (/ ('', i=1, 10) /)) 1560 TYPE(ctrl_out), SAVE :: o_qsnowlsc = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 11/), & 1561 'qsnowlsc', 'LS specific snow content', 'kg/kg', (/ ('', i=1, 10) /)) 1558 1562 TYPE(ctrl_out), SAVE :: o_dqreva = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 11/), & 1559 'dqreva', 'LS rain tendency due to evaporation', 'kg/ m2/s', (/ ('', i=1, 10) /))1563 'dqreva', 'LS rain tendency due to evaporation', 'kg/kg/s', (/ ('', i=1, 10) /)) 1560 1564 TYPE(ctrl_out), SAVE :: o_dqrauto = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 11/), & 1561 'dqrauto', 'LS rain tendency due to autoconversion', 'kg/ m2/s', (/ ('', i=1, 10) /))1565 'dqrauto', 'LS rain tendency due to autoconversion', 'kg/kg/s', (/ ('', i=1, 10) /)) 1562 1566 TYPE(ctrl_out), SAVE :: o_dqrcol = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 11/), & 1563 'dqrcol', 'LS rain tendency due to collection', 'kg/ m2/s', (/ ('', i=1, 10) /))1567 'dqrcol', 'LS rain tendency due to collection', 'kg/kg/s', (/ ('', i=1, 10) /)) 1564 1568 TYPE(ctrl_out), SAVE :: o_dqrmelt = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 11/), & 1565 'dqrmelt', 'LS rain tendency due to melting', 'kg/ m2/s', (/ ('', i=1, 10) /))1569 'dqrmelt', 'LS rain tendency due to melting', 'kg/kg/s', (/ ('', i=1, 10) /)) 1566 1570 TYPE(ctrl_out), SAVE :: o_dqrfreez = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 11/), & 1567 'dqrfreez', 'LS rain tendency due to freezing', 'kg/ m2/s', (/ ('', i=1, 10) /))1571 'dqrfreez', 'LS rain tendency due to freezing', 'kg/kg/s', (/ ('', i=1, 10) /)) 1568 1572 TYPE(ctrl_out), SAVE :: o_dqssub = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 11/), & 1569 'dqssub', 'LS snow tendency due to sublimation', 'kg/ m2/s', (/ ('', i=1, 10) /))1573 'dqssub', 'LS snow tendency due to sublimation', 'kg/kg/s', (/ ('', i=1, 10) /)) 1570 1574 TYPE(ctrl_out), SAVE :: o_dqsauto = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 11/), & 1571 'dqsauto', 'LS snow tendency due to autoconversion', 'kg/ m2/s', (/ ('', i=1, 10) /))1575 'dqsauto', 'LS snow tendency due to autoconversion', 'kg/kg/s', (/ ('', i=1, 10) /)) 1572 1576 TYPE(ctrl_out), SAVE :: o_dqsagg = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 11/), & 1573 'dqsagg', 'LS snow tendency due to aggr agation', 'kg/m2/s', (/ ('', i=1, 10) /))1577 'dqsagg', 'LS snow tendency due to aggregation', 'kg/kg/s', (/ ('', i=1, 10) /)) 1574 1578 TYPE(ctrl_out), SAVE :: o_dqsrim = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 11/), & 1575 'dqsrim', 'LS snow tendency due to riming', 'kg/ m2/s', (/ ('', i=1, 10) /))1579 'dqsrim', 'LS snow tendency due to riming', 'kg/kg/s', (/ ('', i=1, 10) /)) 1576 1580 TYPE(ctrl_out), SAVE :: o_dqsmelt = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 11/), & 1577 'dqsmelt', 'LS snow tendency due to melting', 'kg/ m2/s', (/ ('', i=1, 10) /))1581 'dqsmelt', 'LS snow tendency due to melting', 'kg/kg/s', (/ ('', i=1, 10) /)) 1578 1582 TYPE(ctrl_out), SAVE :: o_dqsfreez = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 11/), & 1579 'dqsfreez', 'LS snow tendency due to freezing', 'kg/ m2/s', (/ ('', i=1, 10) /))1583 'dqsfreez', 'LS snow tendency due to freezing', 'kg/kg/s', (/ ('', i=1, 10) /)) 1580 1584 TYPE(ctrl_out), SAVE :: o_rhum = ctrl_out((/ 2, 5, 10, 10, 10, 10, 11, 11, 11, 11/), & 1581 1585 'rhum', 'Relative humidity', '-', (/ ('', i=1, 10) /)) -
LMDZ6/trunk/libf/phylmd/phys_output_write_mod.F90
r4811 r4819 141 141 o_rnebls, o_rneblsvol, o_rhum, o_rhl, o_rhi, o_ozone, o_ozone_light, & 142 142 o_pfraclr, o_pfracld, & 143 o_ dqreva, o_dqrauto, o_dqrcol, o_dqrmelt, o_dqrfreez, &143 o_qrainlsc, o_qsnowlsc, o_dqreva, o_dqrauto, o_dqrcol, o_dqrmelt, o_dqrfreez, & 144 144 o_dqssub, o_dqsauto, o_dqsagg, o_dqsrim, o_dqsmelt, o_dqsfreez, & 145 145 o_duphy, o_dtphy, o_dqphy, o_dqphy2d, o_dqlphy, o_dqlphy2d, & … … 363 363 rneb, rnebjn, rneblsvol, zx_rh, zx_rhl, zx_rhi, & 364 364 pfraclr, pfracld, & 365 dqreva, dqssub, &365 qrain_lsc, qsnow_lsc, dqreva, dqssub, & 366 366 dqrauto,dqrcol,dqrmelt,dqrfreez, & 367 367 dqsauto,dqsagg,dqsrim,dqsmelt,dqsfreez, & … … 1985 1985 CALL histwrite_phy(o_pfracld, pfracld) 1986 1986 IF (ok_poprecip) THEN 1987 CALL histwrite_phy(o_qrainlsc, qrain_lsc) 1988 CALL histwrite_phy(o_qsnowlsc, qsnow_lsc) 1987 1989 CALL histwrite_phy(o_dqreva, dqreva) 1988 1990 CALL histwrite_phy(o_dqrauto, dqrauto) -
LMDZ6/trunk/libf/phylmd/physiq_mod.F90
r4818 r4819 196 196 d_q_ch4, & 197 197 ! proprecip 198 qrain_lsc, qsnow_lsc, & 198 199 dqreva, dqssub, & 199 200 dqrauto,dqrcol,dqrmelt,dqrfreez, & … … 3892 3893 Tcontr, qcontr, qcontr2, fcontrN, fcontrP , & 3893 3894 cloudth_sth,cloudth_senv,cloudth_sigmath,cloudth_sigmaenv, & 3894 dqreva,dqssub,dqrauto,dqrcol,dqrmelt,dqrfreez,dqsauto,dqsagg,dqsrim,dqsmelt,dqsfreez) 3895 qrain_lsc, qsnow_lsc, dqreva, dqssub, dqrauto, dqrcol, dqrmelt, & 3896 dqrfreez, dqsauto, dqsagg, dqsrim, dqsmelt, dqsfreez) 3895 3897 3896 3898 -
LMDZ6/trunk/libf/phylmdiso/phys_local_var_mod.F90
r4803 r4819 640 640 641 641 !--POPRECIP variables 642 REAL, SAVE, ALLOCATABLE :: qrain_lsc(:,:) 643 !$OMP THREADPRIVATE(qrain_lsc) 644 REAL, SAVE, ALLOCATABLE :: qsnow_lsc(:,:) 645 !$OMP THREADPRIVATE(qsnow_lsc) 642 646 REAL, SAVE, ALLOCATABLE :: dqreva(:,:) 643 647 !$OMP THREADPRIVATE(dqreva) … … 1116 1120 !--POPRECIP variables 1117 1121 ALLOCATE(dqreva(klon,klev),dqssub(klon,klev)) 1122 ALLOCATE(qrain_lsc(klon,klev), qsnow_lsc(klon,klev)) 1118 1123 ALLOCATE(dqrauto(klon,klev), dqrcol(klon,klev), dqrmelt(klon,klev), dqrfreez(klon,klev)) 1119 1124 ALLOCATE(dqsauto(klon,klev), dqsagg(klon,klev), dqsrim(klon,klev), dqsmelt(klon,klev), dqsfreez(klon,klev)) … … 1478 1483 1479 1484 !--POPRECIP variables 1485 DEALLOCATE(qrain_lsc, qsnow_lsc) 1480 1486 DEALLOCATE(dqreva,dqssub) 1481 1487 DEALLOCATE(dqrauto,dqrcol,dqrmelt,dqrfreez) -
LMDZ6/trunk/libf/phylmdiso/phys_output_ctrlout_mod.F90
r4803 r4819 1477 1477 TYPE(ctrl_out), SAVE :: o_pfracld = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 11/), & 1478 1478 'pfracld', 'LS precipitation fraction cloudy part', '-', (/ ('', i=1, 10) /)) 1479 TYPE(ctrl_out), SAVE :: o_qrainlsc = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 11/), & 1480 'qrainlsc', 'LS specific rain content', 'kg/kg', (/ ('', i=1, 10) /)) 1481 TYPE(ctrl_out), SAVE :: o_qsnowlsc = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 11/), & 1482 'qsnowlsc', 'LS specific snow content', 'kg/kg', (/ ('', i=1, 10) /)) 1479 1483 TYPE(ctrl_out), SAVE :: o_dqreva = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 11/), & 1480 'dqreva', 'LS rain tendency due to evaporation', 'kg/ m2/s', (/ ('', i=1, 10) /))1484 'dqreva', 'LS rain tendency due to evaporation', 'kg/kg/s', (/ ('', i=1, 10) /)) 1481 1485 TYPE(ctrl_out), SAVE :: o_dqrauto = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 11/), & 1482 'dqrauto', 'LS rain tendency due to autoconversion', 'kg/ m2/s', (/ ('', i=1, 10) /))1486 'dqrauto', 'LS rain tendency due to autoconversion', 'kg/kg/s', (/ ('', i=1, 10) /)) 1483 1487 TYPE(ctrl_out), SAVE :: o_dqrcol = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 11/), & 1484 'dqrcol', 'LS rain tendency due to collection', 'kg/ m2/s', (/ ('', i=1, 10) /))1488 'dqrcol', 'LS rain tendency due to collection', 'kg/kg/s', (/ ('', i=1, 10) /)) 1485 1489 TYPE(ctrl_out), SAVE :: o_dqrmelt = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 11/), & 1486 'dqrmelt', 'LS rain tendency due to melting', 'kg/ m2/s', (/ ('', i=1, 10) /))1490 'dqrmelt', 'LS rain tendency due to melting', 'kg/kg/s', (/ ('', i=1, 10) /)) 1487 1491 TYPE(ctrl_out), SAVE :: o_dqrfreez = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 11/), & 1488 'dqrfreez', 'LS rain tendency due to freezing', 'kg/ m2/s', (/ ('', i=1, 10) /))1492 'dqrfreez', 'LS rain tendency due to freezing', 'kg/kg/s', (/ ('', i=1, 10) /)) 1489 1493 TYPE(ctrl_out), SAVE :: o_dqssub = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 11/), & 1490 'dqssub', 'LS snow tendency due to sublimation', 'kg/ m2/s', (/ ('', i=1, 10) /))1494 'dqssub', 'LS snow tendency due to sublimation', 'kg/kg/s', (/ ('', i=1, 10) /)) 1491 1495 TYPE(ctrl_out), SAVE :: o_dqsauto = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 11/), & 1492 'dqsauto', 'LS snow tendency due to autoconversion', 'kg/ m2/s', (/ ('', i=1, 10) /))1496 'dqsauto', 'LS snow tendency due to autoconversion', 'kg/kg/s', (/ ('', i=1, 10) /)) 1493 1497 TYPE(ctrl_out), SAVE :: o_dqsagg = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 11/), & 1494 'dqsagg', 'LS snow tendency due to aggr agation', 'kg/m2/s', (/ ('', i=1, 10) /))1498 'dqsagg', 'LS snow tendency due to aggregation', 'kg/kg/s', (/ ('', i=1, 10) /)) 1495 1499 TYPE(ctrl_out), SAVE :: o_dqsrim = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 11/), & 1496 'dqsrim', 'LS snow tendency due to riming', 'kg/ m2/s', (/ ('', i=1, 10) /))1500 'dqsrim', 'LS snow tendency due to riming', 'kg/kg/s', (/ ('', i=1, 10) /)) 1497 1501 TYPE(ctrl_out), SAVE :: o_dqsmelt = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 11/), & 1498 'dqsmelt', 'LS snow tendency due to melting', 'kg/ m2/s', (/ ('', i=1, 10) /))1502 'dqsmelt', 'LS snow tendency due to melting', 'kg/kg/s', (/ ('', i=1, 10) /)) 1499 1503 TYPE(ctrl_out), SAVE :: o_dqsfreez = ctrl_out((/ 11, 11, 11, 11, 11, 11, 11, 11, 11, 11/), & 1500 'dqsfreez', 'LS snow tendency due to freezing', 'kg/ m2/s', (/ ('', i=1, 10) /))1504 'dqsfreez', 'LS snow tendency due to freezing', 'kg/kg/s', (/ ('', i=1, 10) /)) 1501 1505 TYPE(ctrl_out), SAVE :: o_rhum = ctrl_out((/ 2, 5, 10, 10, 10, 10, 11, 11, 11, 11/), & 1502 1506 'rhum', 'Relative humidity', '-', (/ ('', i=1, 10) /)) -
LMDZ6/trunk/libf/phylmdiso/physiq_mod.F90
r4818 r4819 230 230 d_q_ch4, & 231 231 ! proprecip 232 qrain_lsc, qsnow_lsc, & 232 233 dqreva, dqssub, & 233 234 dqrauto,dqrcol,dqrmelt,dqrfreez, & … … 4890 4891 Tcontr, qcontr, qcontr2, fcontrN, fcontrP , & 4891 4892 cloudth_sth,cloudth_senv,cloudth_sigmath,cloudth_sigmaenv, & 4892 dqreva,dqssub,dqrauto,dqrcol,dqrmelt,dqrfreez,dqsauto,dqsagg,dqsrim,dqsmelt,dqsfreez) 4893 qrain_lsc, qsnow_lsc, dqreva, dqssub, dqrauto, dqrcol, dqrmelt, & 4894 dqrfreez, dqsauto, dqsagg, dqsrim, dqsmelt, dqsfreez) 4893 4895 4894 4896
Note: See TracChangeset
for help on using the changeset viewer.