Changeset 2333 for LMDZ5/trunk/libf/phylmd
- Timestamp:
- Jul 22, 2015, 4:14:51 PM (9 years ago)
- Location:
- LMDZ5/trunk/libf/phylmd
- Files:
-
- 1 added
- 10 edited
Legend:
- Unmodified
- Added
- Removed
-
LMDZ5/trunk/libf/phylmd/flott_gwd_rando_m.F90
r2072 r2333 6 6 7 7 SUBROUTINE FLOTT_GWD_rando(DTIME, pp, tt, uu, vv, prec, zustr, zvstr, d_u, & 8 d_v )8 d_v,east_gwstress,west_gwstress) 9 9 10 10 ! Parametrization of the momentum flux deposition due to a discrete … … 15 15 ! Reference: Lott (JGR, vol 118, page 8897, 2013) 16 16 17 use dimphy, only: klon, klev 18 use assert_m, only: assert 19 20 include "YOMCST.h" 21 include "clesphys.h" 17 !ONLINE: 18 use dimphy, only: klon, klev 19 use assert_m, only: assert 20 include "YOMCST.h" 21 include "clesphys.h" 22 ! OFFLINE: 23 ! include "dimensions.h" 24 ! include "dimphy.h" 25 ! END OF DIFFERENCE ONLINE-OFFLINE 22 26 include "YOEGWD.h" 23 27 … … 36 40 37 41 REAL, intent(inout):: d_u(:, :), d_v(:, :) 42 REAL, intent(inout):: east_gwstress(:, :) ! Profile of eastward stress 43 REAL, intent(inout):: west_gwstress(:, :) ! Profile of westward stress 44 38 45 ! (KLON, KLEV) tendencies on winds 39 46 40 47 ! O.3 INTERNAL ARRAYS 41 48 REAL BVLOW(klon) 42 43 INTEGER II, LL 49 REAL DZ ! Characteristic depth of the Source 50 51 INTEGER II, JJ, LL 44 52 45 53 ! 0.3.0 TIME SCALE OF THE LIFE CYCLE OF THE WAVES PARAMETERIZED … … 51 59 INTEGER, PARAMETER:: NK = 2, NP = 2, NO = 2, NW = NK * NP * NO 52 60 INTEGER JK, JP, JO, JW 61 INTEGER, PARAMETER:: NA = 5 !number of realizations to get the phase speed 53 62 REAL KMIN, KMAX ! Min and Max horizontal wavenumbers 54 REAL CMIN, CMAX ! Min and Max absolute ph. vel. 63 REAL CMAX ! standard deviation of the phase speed distribution 64 REAL RUWMAX,SAT ! ONLINE SPECIFIED IN run.def 55 65 REAL CPHA ! absolute PHASE VELOCITY frequency 56 66 REAL ZK(NW, KLON) ! Horizontal wavenumber amplitude … … 86 96 87 97 REAL H0 ! Characteristic Height of the atmosphere 88 REAL DZ ! Characteristic depth of the source!89 98 REAL PR, TR ! Reference Pressure and Temperature 90 99 … … 110 119 ! 1.2 Tuning parameters of V14 111 120 112 RDISS = 1. ! Diffusion parameter 121 122 RDISS = 1. ! Diffusion parameter 123 ! ONLINE 124 RUWMAX=GWD_RANDO_RUWMAX 125 SAT=gwd_rando_sat 126 !END ONLINE 127 ! OFFLINE 128 ! RUWMAX= 1.75 ! Launched flux 129 ! SAT=0.25 ! Saturation parameter 130 ! END OFFLINE 113 131 114 132 PRMAX = 20. / 24. /3600. 115 133 ! maximum of rain for which our theory applies (in kg/m^2/s) 116 134 117 DZ = 1000. ! Characteristic depth of the source 135 ! Characteristic depth of the source 136 DZ = 1000. 118 137 XLAUNCH=0.5 ! Parameter that control launching altitude 119 138 XTROP=0.2 ! Parameter that control tropopause altitude 120 139 DELTAT=24.*3600. ! Time scale of the waves (first introduced in 9b) 140 ! OFFLINE 141 ! DELTAT=DTIME 142 ! END OFFLINE 121 143 122 144 KMIN = 2.E-5 … … 124 146 125 147 KMAX = 1.E-3 ! Max horizontal wavenumber 126 CMIN = 1. ! Min phase velocity 127 CMAX = 50. ! Max phase speed velocity 148 CMAX = 30. ! Max phase speed velocity 128 149 129 150 TR = 240. ! Reference Temperature … … 135 156 ZOISEC = 1.E-6 ! Security FOR 0 INTRINSIC FREQ 136 157 137 call assert(klon == (/size(pp, 1), size(tt, 1), size(uu, 1), & 138 size(vv, 1), size(prec), size(zustr), size(zvstr), size(d_u, 1), & 139 size(d_v, 1)/), "FLOTT_GWD_RANDO klon") 140 call assert(klev == (/size(pp, 2), size(tt, 2), size(uu, 2), & 141 size(vv, 2), size(d_u, 2), size(d_v, 2)/), "FLOTT_GWD_RANDO klev") 158 !ONLINE 159 call assert(klon == (/size(pp, 1), size(tt, 1), size(uu, 1), & 160 size(vv, 1), size(zustr), size(zvstr), size(d_u, 1), & 161 size(d_v, 1), & 162 size(east_gwstress, 1), size(west_gwstress, 1) /), & 163 "FLOTT_GWD_RANDO klon") 164 call assert(klev == (/size(pp, 2), size(tt, 2), size(uu, 2), & 165 size(vv, 2), size(d_u, 2), size(d_v, 2), & 166 size(east_gwstress,2), size(west_gwstress,2) /), & 167 "FLOTT_GWD_RANDO klev") 168 !END ONLINE 142 169 143 170 IF(DELTAT < DTIME)THEN … … 186 213 - TT(:, LL - 1)) / (ZH(:, LL) - ZH(:, LL - 1)) * RD / H0 187 214 end DO 188 BVLOW = 0.5 * (TT(:, LTROP )+ TT(:, LAUNCH)) &215 BVLOW(:) = 0.5 * (TT(:, LTROP )+ TT(:, LAUNCH)) & 189 216 * RD**2 / RCPD / H0**2 + (TT(:, LTROP ) & 190 217 - TT(:, LAUNCH))/(ZH(:, LTROP )- ZH(:, LAUNCH)) * RD / H0 … … 201 228 BV=MAX(SQRT(MAX(BV, 0.)), BVSEC) 202 229 BVLOW=MAX(SQRT(MAX(BVLOW, 0.)), BVSEC) 230 203 231 204 232 ! WINDS … … 230 258 ZK(JW, II) = KMIN + (KMAX - KMIN) * MOD(TT(II, JW) * 100., 1.) 231 259 ! Horizontal phase speed 232 CPHA = CMIN + (CMAX - CMIN) * MOD(TT(II, JW)**2, 1.) 260 CPHA = 0. 261 DO JJ = 1, NA 262 CPHA = CPHA + & 263 CMAX*2.*(MOD(TT(II, JW+3*JJ)**2, 1.)-0.5)*SQRT(3.)/SQRT(NA*1.) 264 END DO 265 IF (CPHA.LT.0.) THEN 266 CPHA = -1.*CPHA 267 ZP(JW,II) = ZP(JW,II) + RPI 268 ENDIF 233 269 ! Absolute frequency is imposed 234 270 ZO(JW, II) = CPHA * ZK(JW, II) … … 238 274 + ZK(JW, II) * SIN(ZP(JW, II)) * VH(II, LAUNCH) 239 275 ! Momentum flux at launch lev 240 RUW0(JW, II) = GWD_RANDO_RUWMAX276 RUW0(JW, II) = RUWMAX 241 277 ENDDO 242 278 end DO … … 264 300 ! tanh limitation to values above prmax: 265 301 WWP(JW, :) = RUW0(JW, :) & 266 * (RD / RCPD / H0 * RLVTT * PRMAX * TANH(PREC / PRMAX))**2302 * (RD / RCPD / H0 * RLVTT * PRMAX * TANH(PREC(:) / PRMAX))**2 267 303 268 304 ! Factor related to the characteristics of the waves: 269 WWP(JW, :) = WWP(JW, :) * ZK(JW, :)**3 / KMIN / BVLOW &305 WWP(JW, :) = WWP(JW, :) * ZK(JW, :)**3 / KMIN / BVLOW(:) & 270 306 / MAX(ABS(ZOP(JW, :)), ZOISEC)**3 271 307 272 308 ! Moderation by the depth of the source (dz here): 273 309 WWP(JW, :) = WWP(JW, :) & 274 * EXP(- BVLOW **2 / MAX(ABS(ZOP(JW, :)), ZOISEC)**2 * ZK(JW, :)**2 &310 * EXP(- BVLOW(:)**2 / MAX(ABS(ZOP(JW, :)), ZOISEC)**2 * ZK(JW, :)**2 & 275 311 * DZ**2) 276 312 … … 281 317 * BV(:, LAUNCH) * SIN(ZP(JW, :)) * WWP(JW, :)**2 282 318 end DO 319 283 320 284 321 ! 4.2 Uniform values below the launching altitude … … 318 355 WWP(JW, :) = min(WWP(JW, :), MAX(0., & 319 356 SIGN(1., ZOP(JW, :) * ZOM(JW, :))) * ABS(ZOP(JW, :))**3 & 320 / BV(:, LL + 1) * EXP(- ZH(:, LL + 1) / H0) * GWD_RANDO_SAT**2&321 * KMIN**2 / ZK(JW, :)**4)357 / BV(:, LL + 1) * EXP(- ZH(:, LL + 1) / H0) * KMIN**2 & 358 * SAT**2 / ZK(JW, :)**4) 322 359 end DO 323 360 … … 336 373 RUW(:, LL + 1) = RUW(:, LL + 1) + RUWP(JW, :) 337 374 RVW(:, LL + 1) = RVW(:, LL + 1) + RVWP(JW, :) 375 EAST_GWSTRESS(:, LL)=EAST_GWSTRESS(:, LL)+MAX(0.,RUWP(JW,:))/FLOAT(NW) 376 WEST_GWSTRESS(:, LL)=WEST_GWSTRESS(:, LL)+MIN(0.,RUWP(JW,:))/FLOAT(NW) 338 377 end DO 339 378 end DO 379 ! OFFLINE ONLY 380 ! PRINT *,'SAT PROFILE:' 381 ! DO LL=1,KLEV 382 ! PRINT *,ZH(KLON/2,LL)/1000.,SAT*(2.+TANH(ZH(KLON/2,LL)/H0-8.)) 383 ! ENDDO 340 384 341 385 ! 5 CALCUL DES TENDANCES: … … 350 394 RUW(:, LL) = RUW(:, LAUNCH+1) 351 395 RVW(:, LL) = RVW(:, LAUNCH+1) 396 EAST_GWSTRESS(:, LL) = EAST_GWSTRESS(:, LAUNCH) 397 WEST_GWSTRESS(:, LL) = WEST_GWSTRESS(:, LAUNCH) 352 398 end DO 353 399 … … 357 403 RG * (RUW(:, LL + 1) - RUW(:, LL)) & 358 404 / (PH(:, LL + 1) - PH(:, LL)) * DTIME 359 D_V(:, LL) = (1.-DTIME/DELTAT) * D_V(:, LL) + DTIME/DELTAT/REAL(NW) * & 405 ! NO AR-1 FOR MERIDIONAL TENDENCIES 406 D_V(:, LL) = 1./REAL(NW) * & 360 407 RG * (RVW(:, LL + 1) - RVW(:, LL)) & 361 408 / (PH(:, LL + 1) - PH(:, LL)) * DTIME -
LMDZ5/trunk/libf/phylmd/orografi_strato.F90
r2311 r2333 1847 1847 1848 1848 zpr = 100000. 1849 ztop = 0.0011849 ZTOP=0.00005 1850 1850 zsigt = 0.94 1851 1851 ! old ZPR=80000. -
LMDZ5/trunk/libf/phylmd/phyetat0.F90
r2320 r2333 11 11 USE phys_state_var_mod, ONLY : ancien_ok, clwcon, detr_therm, dtime, & 12 12 qsol, fevap, z0m, z0h, agesno, & 13 du_gwd_rando, d v_gwd_rando, entr_therm, f0, fm_therm, &13 du_gwd_rando, du_gwd_front, entr_therm, f0, fm_therm, & 14 14 falb_dir, falb_dif, & 15 15 ftsol, pbl_tke, pctsrf, q_ancien, radpas, radsol, rain_fall, ratqs, & … … 369 369 370 370 ! ondes de gravite non orographiques 371 if (ok_gwd_rando) then372 found=phyetat0_get(klev,du_gwd_rando,"du_gwd_rando","du_gwd_rando",0.)373 found=phyetat0_get(klev,dv_gwd_rando,"dv_gwd_rando","dv_gwd_rando",0.)374 end if371 if (ok_gwd_rando) found = & 372 phyetat0_get(klev,du_gwd_rando,"du_gwd_rando","du_gwd_rando",0.) 373 IF (.not. ok_hines .and. ok_gwd_rando) found & 374 = phyetat0_get(klev,du_gwd_front,"du_gwd_front","du_gwd_front",0.) 375 375 376 376 ! prise en compte du relief sous-maille -
LMDZ5/trunk/libf/phylmd/phyredem.F90
r2320 r2333 282 282 END IF 283 283 284 if (ok_gwd_rando) then 285 call put_field("du_gwd_rando", & 286 "tendency on zonal wind due to gravity waves", & 287 du_gwd_rando) 288 call put_field("dv_gwd_rando", & 289 "tendency on meriodional wind due to gravity waves", & 290 dv_gwd_rando) 291 end if 284 if (ok_gwd_rando) call put_field("du_gwd_rando", & 285 "tendency on zonal wind due to flott gravity waves", du_gwd_rando) 286 287 IF (.not. ok_hines .and. ok_gwd_rando) call put_field("du_gwd_front", & 288 "tendency on zonal wind due to acama gravity waves", du_gwd_front) 292 289 293 290 CALL close_restartphy -
LMDZ5/trunk/libf/phylmd/phys_local_var_mod.F90
r2320 r2333 81 81 !$OMP THREADPRIVATE(d_u_lif, d_v_lif) 82 82 ! Tendances Ondes de G non oro (runs strato). 83 REAL, SAVE, ALLOCATABLE :: d_u_hin(:,:) 84 !$OMP THREADPRIVATE(d_u_hin) 85 REAL, SAVE, ALLOCATABLE :: d_v_hin(:,:) 86 !$OMP THREADPRIVATE(d_v_hin) 83 REAL, SAVE, ALLOCATABLE :: du_gwd_hines(:,:) 84 !$OMP THREADPRIVATE(du_gwd_hines) 85 REAL, SAVE, ALLOCATABLE :: dv_gwd_hines(:,:) 86 !$OMP THREADPRIVATE(dv_gwd_hines) 87 REAL, SAVE, ALLOCATABLE :: dv_gwd_rando(:,:) 88 !$OMP THREADPRIVATE(dv_gwd_rando) 89 REAL, SAVE, ALLOCATABLE :: dv_gwd_front(:,:) 90 !$OMP THREADPRIVATE(dv_gwd_front) 91 REAL, SAVE, ALLOCATABLE :: east_gwstress(:,:) 92 !$OMP THREADPRIVATE(east_gwstress) 93 REAL, SAVE, ALLOCATABLE :: west_gwstress(:,:) 94 !$OMP THREADPRIVATE(west_gwstress) 87 95 REAL, SAVE, ALLOCATABLE :: d_t_hin(:,:) 88 96 !$OMP THREADPRIVATE(d_t_hin) … … 434 442 allocate(topsw0_aero(klon,naero_grp), solsw0_aero(klon,naero_grp)) 435 443 allocate(topswcf_aero(klon,3), solswcf_aero(klon,3)) 436 allocate(d_u_hin(klon,klev),d_v_hin(klon,klev),d_t_hin(klon,klev)) 444 allocate(du_gwd_hines(klon,klev),dv_gwd_hines(klon,klev)) 445 allocate(dv_gwd_rando(klon,klev),dv_gwd_front(klon,klev)) 446 allocate(east_gwstress(klon,klev),west_gwstress(klon,klev)) 447 allocate(d_t_hin(klon,klev)) 437 448 allocate(d_q_ch4(klon,klev)) 438 449 ! allocate(tausum_aero(klon,nwave,naero_spc)) … … 679 690 deallocate(load_tmp6) 680 691 deallocate(load_tmp7) 681 deallocate(d _u_hin,d_v_hin,d_t_hin)692 deallocate(du_gwd_hines,dv_gwd_hines,d_t_hin) 682 693 deallocate(d_q_ch4) 694 deallocate(dv_gwd_rando,dv_gwd_front) 695 deallocate(east_gwstress,west_gwstress) 683 696 684 697 !IM ajout variables CFMIP2/CMIP5 -
LMDZ5/trunk/libf/phylmd/phys_output_ctrlout_mod.F90
r2327 r2333 1190 1190 TYPE(ctrl_out), SAVE :: o_dvlif = ctrl_out((/ 4, 10, 10, 10, 10, 10, 11, 11, 11 /), & 1191 1191 'dvlif', 'Orography dV', 'm/s2', (/ ('', i=1, 9) /)) 1192 TYPE(ctrl_out), SAVE :: o_duhin = ctrl_out((/ 4, 10, 10, 10, 10, 10, 11, 11, 11 /), & 1193 'duhin', 'Hines GWD dU', 'm/s2', (/ ('', i=1, 9) /)) 1194 TYPE(ctrl_out), SAVE :: o_dvhin = ctrl_out((/ 4, 10, 10, 10, 10, 10, 11, 11, 11 /), & 1195 'dvhin', 'Hines GWD dV', 'm/s2', (/ ('', i=1, 9) /)) 1192 TYPE(ctrl_out), SAVE :: o_du_gwd_hines = ctrl_out((/ 4, 10, 10, 10, 10, 10, 11, 11, 11 /), & 1193 'du_gwd_hines', 'Hines GWD dU', 'm/s2', (/ ('', i=1, 9) /)) 1194 TYPE(ctrl_out), SAVE :: o_dv_gwd_hines = ctrl_out((/ 4, 10, 10, 10, 10, 10, 11, 11, 11 /), & 1195 'dv_gwd_hines', 'Hines GWD dV', 'm/s2', (/ ('', i=1, 9) /)) 1196 TYPE(ctrl_out), SAVE :: o_du_gwd_front = ctrl_out((/ 4, 10, 10, 10, 10, 10, 11, 11, 11 /), & 1197 'du_gwd_front', 'Fronts GWD dU', 'm/s2', (/ ('', i=1, 9) /)) 1198 TYPE(ctrl_out), SAVE :: o_dv_gwd_front = ctrl_out((/ 4, 10, 10, 10, 10, 10, 11, 11, 11 /), & 1199 'dv_gwd_front', 'Fronts GWD dV', 'm/s2', (/ ('', i=1, 9) /)) 1200 TYPE(ctrl_out), SAVE :: o_east_gwstress = ctrl_out((/ 4, 10, 10, 10, 10, 10, 11, 11, 11 /), & 1201 'east_gwstress', 'Eastward GW Stress', 'Pa', (/ ('', i=1, 9) /)) 1202 TYPE(ctrl_out), SAVE :: o_west_gwstress = ctrl_out((/ 4, 10, 10, 10, 10, 10, 11, 11, 11 /), & 1203 'west_gwstress', 'Westward GW Stress', 'Pa', (/ ('', i=1, 9) /)) 1196 1204 TYPE(ctrl_out), SAVE :: o_dtoro = ctrl_out((/ 4, 10, 10, 10, 10, 10, 11, 11, 11 /), & 1197 1205 'dtoro', 'Orography dT', 'K/s', (/ ('', i=1, 9) /)) … … 1209 1217 = ctrl_out((/ 4, 10, 10, 10, 10, 10, 11, 11, 11 /), 'dv_gwd_rando', & 1210 1218 "Random gravity waves dV/dt", "m/s2", (/ ('', i=1, 9) /)) 1219 type(ctrl_out), save:: o_ustr_gwd_hines & 1220 = ctrl_out((/ 4, 10, 10, 10, 10, 10, 11, 11, 11 /), 'ustr_gwd_hines', & 1221 "zonal wind stress Hines gravity waves", "Pa", (/ ('', i=1, 9) /)) 1222 type(ctrl_out), save:: o_vstr_gwd_hines & 1223 = ctrl_out((/ 4, 10, 10, 10, 10, 10, 11, 11, 11 /), 'vstr_gwd_hines', & 1224 "meridional wind stress Hines gravity waves", "Pa", (/ ('', i=1, 9) /)) 1225 type(ctrl_out), save:: o_ustr_gwd_front & 1226 = ctrl_out((/ 4, 10, 10, 10, 10, 10, 11, 11, 11 /), 'ustr_gwd_front', & 1227 "zonal wind stress fronts gravity waves", "Pa", (/ ('', i=1, 9) /)) 1228 type(ctrl_out), save:: o_vstr_gwd_front & 1229 = ctrl_out((/ 4, 10, 10, 10, 10, 10, 11, 11, 11 /), 'vstr_gwd_front', & 1230 "meridional wind stress fronts gravity waves", "Pa", (/ ('', i=1, 9) /)) 1231 type(ctrl_out), save:: o_ustr_gwd_rando & 1232 = ctrl_out((/ 4, 10, 10, 10, 10, 10, 11, 11, 11 /), 'ustr_gwd_rando', & 1233 "zonal wind stress random gravity waves", "Pa", (/ ('', i=1, 9) /)) 1211 1234 type(ctrl_out), save:: o_vstr_gwd_rando & 1212 1235 = ctrl_out((/ 4, 10, 10, 10, 10, 10, 11, 11, 11 /), 'vstr_gwd_rando', & -
LMDZ5/trunk/libf/phylmd/phys_output_var_mod.F90
r2042 r2333 59 59 LOGICAL, SAVE :: vars_defined = .FALSE. ! ug PAS THREADPRIVATE ET C'EST NORMAL 60 60 61 REAL, allocatable:: zustr_gwd_hines(:), zvstr_gwd_hines(:) ! (klon) 62 REAL, allocatable:: zustr_gwd_front(:), zvstr_gwd_front(:) ! (klon) 61 63 REAL, allocatable:: zustr_gwd_rando(:), zvstr_gwd_rando(:) ! (klon) 62 64 !$OMP THREADPRIVATE(zustr_gwd_rando, zvstr_gwd_rando) … … 86 88 allocate (bils_ec(klon),bils_ech(klon),bils_tke(klon),bils_diss(klon),bils_kinetic(klon),bils_enthalp(klon),bils_latent(klon)) 87 89 90 IF (ok_hines) allocate(zustr_gwd_hines(klon), zvstr_gwd_hines(klon)) 91 IF (.not.ok_hines.and.ok_gwd_rando) & 92 allocate(zustr_gwd_front(klon), zvstr_gwd_front(klon)) 88 93 IF (ok_gwd_rando) allocate(zustr_gwd_rando(klon), zvstr_gwd_rando(klon)) 89 94 -
LMDZ5/trunk/libf/phylmd/phys_output_write_mod.F90
r2320 r2333 1 1 ! 2 ! $ Id$2 ! $Header$ 3 3 ! 4 4 MODULE phys_output_write_mod … … 132 132 o_duvdf, o_dvvdf, o_duoro, o_dvoro, & 133 133 o_dtoro, o_dulif, o_dvlif, o_dtlif, & 134 o_duhin, o_dvhin, o_dthin, o_dqch4, o_rsu, & 134 o_du_gwd_hines, o_dv_gwd_hines, o_dthin, o_dqch4, o_rsu, & 135 o_du_gwd_front, o_dv_gwd_front, & 136 o_east_gwstress, o_west_gwstress, & 135 137 o_rsd, o_rlu, o_rld, o_rsucs, o_rsdcs, & 136 138 o_rlucs, o_rldcs, o_tnt, o_tntr, & … … 151 153 o_dtr_ls, o_dtr_trsp, o_dtr_sscav, & 152 154 o_dtr_sat, o_dtr_uscav, o_trac_cum, o_du_gwd_rando, o_dv_gwd_rando, & 153 o_vstr_gwd_rando 155 o_ustr_gwd_hines,o_vstr_gwd_hines,o_ustr_gwd_rando,o_vstr_gwd_rando, & 156 o_ustr_gwd_front,o_vstr_gwd_front 154 157 155 158 USE phys_state_var_mod, only: pctsrf, paire_ter, rain_fall, snow_fall, & … … 174 177 vqsumSTD, vTsumSTD, O3daysumSTD, wqsumSTD, & 175 178 vphisumSTD, wTsumSTD, u2sumSTD, v2sumSTD, & 176 T2sumSTD, nlevSTD, du_gwd_rando, d v_gwd_rando, &179 T2sumSTD, nlevSTD, du_gwd_rando, du_gwd_front, & 177 180 ulevSTD, vlevSTD, wlevSTD, philevSTD, qlevSTD, tlevSTD, & 178 181 rhlevSTD, O3STD, O3daySTD, uvSTD, vqSTD, vTSTD, wqSTD, & … … 230 233 zw2, fraca, zmax_th, d_q_ajsb, d_t_ec, d_u_vdf, & 231 234 d_v_vdf, d_u_oro, d_v_oro, d_t_oro, d_u_lif, & 232 d_v_lif, d_t_lif, d_u_hin, d_v_hin, d_t_hin, & 235 d_v_lif, d_t_lif, du_gwd_hines, dv_gwd_hines, d_t_hin, & 236 dv_gwd_rando, dv_gwd_front, & 237 east_gwstress, west_gwstress, & 233 238 d_q_ch4, pmfd, pmfu, ref_liq, ref_ice, rhwriteSTD 234 239 235 240 USE phys_output_var_mod, only: vars_defined, snow_o, zfra_o, bils_diss, & 236 241 bils_ec,bils_ech, bils_tke, bils_kinetic, bils_latent, bils_enthalp, & 237 itau_con, nfiles, clef_files, nid_files, zvstr_gwd_rando 242 itau_con, nfiles, clef_files, nid_files, & 243 zustr_gwd_hines, zvstr_gwd_hines,zustr_gwd_rando, zvstr_gwd_rando, & 244 zustr_gwd_front, zvstr_gwd_front 238 245 USE ocean_slab_mod, only: tslab, slab_bils, slab_bilg, tice, seaice 239 246 USE pbl_surface_mod, only: snow … … 1217 1224 1218 1225 IF (ok_hines) THEN 1219 IF(vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_u_hin(1:klon,1:klev)/pdtphys 1220 CALL histwrite_phy(o_duhin, zx_tmp_fi3d) 1221 IF(vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_v_hin(1:klon,1:klev)/pdtphys 1222 CALL histwrite_phy(o_dvhin, zx_tmp_fi3d) 1226 CALL histwrite_phy(o_du_gwd_hines, du_gwd_hines/pdtphys) 1227 CALL histwrite_phy(o_dv_gwd_hines, dv_gwd_hines/pdtphys) 1223 1228 IF(vars_defined) zx_tmp_fi3d(1:klon,1:klev)=d_t_hin(1:klon,1:klev)/pdtphys 1224 1229 CALL histwrite_phy(o_dthin, zx_tmp_fi3d) 1230 CALL histwrite_phy(o_ustr_gwd_hines, zustr_gwd_hines) 1231 CALL histwrite_phy(o_vstr_gwd_hines, zvstr_gwd_hines) 1232 end IF 1233 1234 if (.not. ok_hines .and. ok_gwd_rando) then 1235 CALL histwrite_phy(o_du_gwd_front, du_gwd_front / pdtphys) 1236 CALL histwrite_phy(o_dv_gwd_front, dv_gwd_front / pdtphys) 1237 CALL histwrite_phy(o_ustr_gwd_front, zustr_gwd_front) 1238 CALL histwrite_phy(o_vstr_gwd_front, zvstr_gwd_front) 1225 1239 ENDIF 1226 1240 … … 1228 1242 CALL histwrite_phy(o_du_gwd_rando, du_gwd_rando / pdtphys) 1229 1243 CALL histwrite_phy(o_dv_gwd_rando, dv_gwd_rando / pdtphys) 1244 CALL histwrite_phy(o_ustr_gwd_rando, zustr_gwd_rando) 1230 1245 CALL histwrite_phy(o_vstr_gwd_rando, zvstr_gwd_rando) 1246 CALL histwrite_phy(o_east_gwstress, east_gwstress ) 1247 CALL histwrite_phy(o_west_gwstress, west_gwstress ) 1231 1248 end IF 1232 1249 -
LMDZ5/trunk/libf/phylmd/phys_state_var_mod.F90
r2320 r2333 395 395 !!! fin nrlmd le 10/04/2012 396 396 397 REAL, ALLOCATABLE, SAVE:: du_gwd_rando(:, :), d v_gwd_rando(:, :)398 !$OMP THREADPRIVATE(du_gwd_rando, d v_gwd_rando)397 REAL, ALLOCATABLE, SAVE:: du_gwd_rando(:, :), du_gwd_front(:, :) 398 !$OMP THREADPRIVATE(du_gwd_rando, du_gwd_front) 399 399 ! tendencies on wind due to gravity waves 400 400 … … 581 581 ALLOCATE(ale_bl_trig(klon)) 582 582 !!! fin nrlmd le 10/04/2012 583 if (ok_gwd_rando) allocate(du_gwd_rando(klon, klev) , &584 dv_gwd_rando(klon, klev))583 if (ok_gwd_rando) allocate(du_gwd_rando(klon, klev)) 584 if (.not. ok_hines .and. ok_gwd_rando) allocate(du_gwd_front(klon, klev)) 585 585 586 586 END SUBROUTINE phys_state_var_init … … 705 705 deallocate(tau_aero_lw_rrtm,piz_aero_lw_rrtm,cg_aero_lw_rrtm) 706 706 deallocate(ccm) 707 if (ok_gwd_rando) deallocate(du_gwd_rando, dv_gwd_rando) 707 if (ok_gwd_rando) deallocate(du_gwd_rando) 708 if (.not. ok_hines .and. ok_gwd_rando) deallocate(du_gwd_front) 708 709 709 710 !!! nrlmd le 10/04/2012 -
LMDZ5/trunk/libf/phylmd/physiq.F90
r2328 r2333 5 5 debut,lafin,jD_cur, jH_cur,pdtphys, & 6 6 paprs,pplay,pphi,pphis,presnivs, & 7 u,v, t,qx, &7 u,v,rot,t,qx, & 8 8 flxmass_w, & 9 9 d_u, d_v, d_t, d_qx, d_ps & … … 66 66 USE CFMIP_point_locations 67 67 use FLOTT_GWD_rando_m, only: FLOTT_GWD_rando 68 use ACAMA_GWD_rando_m, only: ACAMA_GWD_rando 68 69 69 70 IMPLICIT none … … 230 231 REAL u(klon,klev) 231 232 REAL v(klon,klev) 233 234 REAL, intent(in):: rot(klon, klev) 235 ! relative vorticity, in s-1, needed for frontal waves 236 232 237 REAL t(klon,klev),thetal(klon,klev) 233 238 ! thetal: ligne suivante a decommenter si vous avez les fichiers MPL 20130625 … … 696 701 REAL zustrli(klon), zvstrli(klon) 697 702 REAL zustrph(klon), zvstrph(klon) 698 REAL zustrhi(klon), zvstrhi(klon)699 703 REAL aam, torsfc 700 704 !IM 141004 END … … 3835 3839 d_t_lif, d_u_lif, d_v_lif) 3836 3840 ENDIF 3837 ! 3838 !----------------------------------------------------------------------------------------- 3841 3839 3842 ! ajout des tendances de la portance de l'orographie 3840 CALL add_phys_tend(d_u_lif,d_v_lif,d_t_lif,dq0,dql0,dqi0,paprs,'lif',abortphy) 3841 !----------------------------------------------------------------------------------------- 3842 ! 3843 CALL add_phys_tend(d_u_lif, d_v_lif, d_t_lif, dq0, dql0, dqi0, paprs, & 3844 'lif', abortphy) 3843 3845 ENDIF ! fin de test sur ok_orolf 3844 ! HINES GWD PARAMETRIZATION3845 3846 3846 3847 IF (ok_hines) then 3847 3848 CALL hines_gwd(klon,klev,dtime,paprs,pplay, & 3849 rlat,t_seri,u_seri,v_seri, & 3850 zustrhi,zvstrhi, & 3851 d_t_hin, d_u_hin, d_v_hin) 3852 ! 3853 ! ajout des tendances 3854 CALL add_phys_tend(d_u_hin,d_v_hin,d_t_hin,dq0,dql0,dqi0,paprs,'hin',abortphy) 3855 3848 ! HINES GWD PARAMETRIZATION 3849 east_gwstress=0. 3850 west_gwstress=0. 3851 du_gwd_hines=0. 3852 dv_gwd_hines=0. 3853 CALL hines_gwd(klon, klev, dtime, paprs, pplay, rlat, t_seri, u_seri, & 3854 v_seri, zustr_gwd_hines, zvstr_gwd_hines, d_t_hin, du_gwd_hines, & 3855 dv_gwd_hines) 3856 zustr_gwd_hines=0. 3857 zvstr_gwd_hines=0. 3858 DO k = 1, klev 3859 zustr_gwd_hines(:)=zustr_gwd_hines(:)+ du_gwd_hines(:, k)/dtime & 3860 * (paprs(:, k)-paprs(:, k+1))/rg 3861 zvstr_gwd_hines(:)=zvstr_gwd_hines(:)+ dv_gwd_hines(:, k)/dtime & 3862 * (paprs(:, k)-paprs(:, k+1))/rg 3863 ENDDO 3864 3865 d_t_hin(:, :)=0. 3866 CALL add_phys_tend(du_gwd_hines, dv_gwd_hines, d_t_hin, dq0, dql0, dqi0, & 3867 paprs, 'hin', abortphy) 3868 ENDIF 3869 3870 IF (.not. ok_hines .and. ok_gwd_rando) then 3871 CALL acama_GWD_rando(DTIME, pplay, rlat, t_seri, u_seri, v_seri, rot, & 3872 zustr_gwd_front, zvstr_gwd_front, du_gwd_front, dv_gwd_front, & 3873 east_gwstress, west_gwstress) 3874 zustr_gwd_front=0. 3875 zvstr_gwd_front=0. 3876 DO k = 1, klev 3877 zustr_gwd_front(:)=zustr_gwd_front(:)+ du_gwd_front(:, k)/dtime & 3878 * (paprs(:, k)-paprs(:, k+1))/rg 3879 zvstr_gwd_front(:)=zvstr_gwd_front(:)+ dv_gwd_front(:, k)/dtime & 3880 * (paprs(:, k)-paprs(:, k+1))/rg 3881 ENDDO 3882 3883 CALL add_phys_tend(du_gwd_front, dv_gwd_front, dt0, dq0, dql0, dqi0, & 3884 paprs, 'front_gwd_rando', abortphy) 3885 3886 ! LIGNE TEMPORAIRE POUR TESTER ROT (ECRITE AUSSI AU DESSOUS!!!): 3887 east_gwstress=rot 3856 3888 ENDIF 3857 3889 … … 3859 3891 call FLOTT_GWD_rando(DTIME, pplay, t_seri, u_seri, v_seri, & 3860 3892 rain_fall + snow_fall, zustr_gwd_rando, zvstr_gwd_rando, & 3861 du_gwd_rando, dv_gwd_rando) 3862 CALL add_phys_tend(du_gwd_rando, dv_gwd_rando, dt0, dq0, dql0,dqi0,paprs, & 3863 'flott_gwd_rando',abortphy) 3893 du_gwd_rando, dv_gwd_rando, east_gwstress, west_gwstress) 3894 CALL add_phys_tend(du_gwd_rando, dv_gwd_rando, dt0, dq0, dql0, dqi0, & 3895 paprs, 'flott_gwd_rando', abortphy) 3896 zustr_gwd_rando=0. 3897 zvstr_gwd_rando=0. 3898 DO k = 1, klev 3899 zustr_gwd_rando(:)=zustr_gwd_rando(:)+ du_gwd_rando(:, k)/dtime & 3900 * (paprs(:, k)-paprs(:, k+1))/rg 3901 zvstr_gwd_rando(:)=zvstr_gwd_rando(:)+ dv_gwd_rando(:, k)/dtime & 3902 * (paprs(:, k)-paprs(:, k+1))/rg 3903 ENDDO 3904 3905 ! LIGNE TEMPORAIRE POUR TESTER ROT (ECRITE AUSSI AU DESSUS!!!): 3906 east_gwstress=rot 3864 3907 end if 3865 3908 … … 3915 3958 CALL METHOX(1,klon,klon,klev,q_seri,d_q_ch4,pplay) 3916 3959 ! ajout de la tendance d'humidite due au methane 3917 CALL add_phys_tend(du0,dv0,dt0,d_q_ch4*dtime,dql0,'q_ch4',abortphy) 3960 CALL add_phys_tend(du0, dv0, dt0, d_q_ch4*dtime, dql0, dqi0, paprs, & 3961 'q_ch4', abortphy) 3918 3962 END IF 3919 3963 !
Note: See TracChangeset
for help on using the changeset viewer.