[2759] | 1 | !IDEAL:MODEL_LAYER:INITIALIZATION |
---|
| 2 | |
---|
| 3 | ! This MODULE holds the routines which are used to perform various initializations |
---|
| 4 | ! for the individual domains. |
---|
| 5 | |
---|
| 6 | !----------------------------------------------------------------------- |
---|
| 7 | |
---|
| 8 | MODULE module_initialize_ideal |
---|
| 9 | |
---|
| 10 | USE module_domain ! frame/module_domain.F |
---|
| 11 | USE module_io_domain ! share |
---|
| 12 | USE module_state_description ! frame |
---|
| 13 | USE module_model_constants ! share |
---|
| 14 | USE module_bc ! share |
---|
| 15 | USE module_timing ! frame |
---|
| 16 | USE module_configure ! frame |
---|
| 17 | USE module_init_utilities ! dyn_em |
---|
| 18 | #ifdef DM_PARALLEL |
---|
| 19 | USE module_dm |
---|
| 20 | #endif |
---|
| 21 | |
---|
| 22 | |
---|
| 23 | CONTAINS |
---|
| 24 | |
---|
| 25 | |
---|
| 26 | !------------------------------------------------------------------- |
---|
| 27 | ! this is a wrapper for the solver-specific init_domain routines. |
---|
| 28 | ! Also dereferences the grid variables and passes them down as arguments. |
---|
| 29 | ! This is crucial, since the lower level routines may do message passing |
---|
| 30 | ! and this will get fouled up on machines that insist on passing down |
---|
| 31 | ! copies of assumed-shape arrays (by passing down as arguments, the |
---|
| 32 | ! data are treated as assumed-size -- ie. f77 -- arrays and the copying |
---|
| 33 | ! business is avoided). Fie on the F90 designers. Fie and a pox. |
---|
| 34 | |
---|
| 35 | SUBROUTINE init_domain ( grid ) |
---|
| 36 | |
---|
| 37 | IMPLICIT NONE |
---|
| 38 | |
---|
| 39 | ! Input data. |
---|
| 40 | TYPE (domain), POINTER :: grid |
---|
| 41 | ! Local data. |
---|
| 42 | INTEGER :: idum1, idum2 |
---|
| 43 | |
---|
| 44 | CALL set_scalar_indices_from_config ( head_grid%id , idum1, idum2 ) |
---|
| 45 | |
---|
| 46 | CALL init_domain_rk( grid & |
---|
| 47 | ! |
---|
| 48 | #include <actual_new_args.inc> |
---|
| 49 | ! |
---|
| 50 | ) |
---|
| 51 | |
---|
| 52 | END SUBROUTINE init_domain |
---|
| 53 | |
---|
| 54 | !------------------------------------------------------------------- |
---|
| 55 | |
---|
| 56 | SUBROUTINE init_domain_rk ( grid & |
---|
| 57 | ! |
---|
| 58 | # include <dummy_new_args.inc> |
---|
| 59 | ! |
---|
| 60 | ) |
---|
| 61 | IMPLICIT NONE |
---|
| 62 | |
---|
| 63 | ! Input data. |
---|
| 64 | TYPE (domain), POINTER :: grid |
---|
| 65 | |
---|
| 66 | # include <dummy_decl.inc> |
---|
| 67 | |
---|
| 68 | TYPE (grid_config_rec_type) :: config_flags |
---|
| 69 | |
---|
| 70 | ! Local data |
---|
| 71 | INTEGER :: & |
---|
| 72 | ids, ide, jds, jde, kds, kde, & |
---|
| 73 | ims, ime, jms, jme, kms, kme, & |
---|
| 74 | its, ite, jts, jte, kts, kte, & |
---|
| 75 | i, j, k |
---|
| 76 | |
---|
| 77 | INTEGER :: nxx, nyy, ig, jg, im, error |
---|
| 78 | |
---|
| 79 | REAL :: dlam, dphi, vlat, tperturb |
---|
| 80 | REAL :: p_surf, p_level, pd_surf, qvf1, qvf2, qvf |
---|
| 81 | REAL :: thtmp, ptmp, temp(3), cof1, cof2 |
---|
| 82 | |
---|
| 83 | INTEGER :: icm,jcm |
---|
| 84 | |
---|
| 85 | SELECT CASE ( model_data_order ) |
---|
| 86 | CASE ( DATA_ORDER_ZXY ) |
---|
| 87 | kds = grid%sd31 ; kde = grid%ed31 ; |
---|
| 88 | ids = grid%sd32 ; ide = grid%ed32 ; |
---|
| 89 | jds = grid%sd33 ; jde = grid%ed33 ; |
---|
| 90 | |
---|
| 91 | kms = grid%sm31 ; kme = grid%em31 ; |
---|
| 92 | ims = grid%sm32 ; ime = grid%em32 ; |
---|
| 93 | jms = grid%sm33 ; jme = grid%em33 ; |
---|
| 94 | |
---|
| 95 | kts = grid%sp31 ; kte = grid%ep31 ; ! note that tile is entire patch |
---|
| 96 | its = grid%sp32 ; ite = grid%ep32 ; ! note that tile is entire patch |
---|
| 97 | jts = grid%sp33 ; jte = grid%ep33 ; ! note that tile is entire patch |
---|
| 98 | CASE ( DATA_ORDER_XYZ ) |
---|
| 99 | ids = grid%sd31 ; ide = grid%ed31 ; |
---|
| 100 | jds = grid%sd32 ; jde = grid%ed32 ; |
---|
| 101 | kds = grid%sd33 ; kde = grid%ed33 ; |
---|
| 102 | |
---|
| 103 | ims = grid%sm31 ; ime = grid%em31 ; |
---|
| 104 | jms = grid%sm32 ; jme = grid%em32 ; |
---|
| 105 | kms = grid%sm33 ; kme = grid%em33 ; |
---|
| 106 | |
---|
| 107 | its = grid%sp31 ; ite = grid%ep31 ; ! note that tile is entire patch |
---|
| 108 | jts = grid%sp32 ; jte = grid%ep32 ; ! note that tile is entire patch |
---|
| 109 | kts = grid%sp33 ; kte = grid%ep33 ; ! note that tile is entire patch |
---|
| 110 | CASE ( DATA_ORDER_XZY ) |
---|
| 111 | ids = grid%sd31 ; ide = grid%ed31 ; |
---|
| 112 | kds = grid%sd32 ; kde = grid%ed32 ; |
---|
| 113 | jds = grid%sd33 ; jde = grid%ed33 ; |
---|
| 114 | |
---|
| 115 | ims = grid%sm31 ; ime = grid%em31 ; |
---|
| 116 | kms = grid%sm32 ; kme = grid%em32 ; |
---|
| 117 | jms = grid%sm33 ; jme = grid%em33 ; |
---|
| 118 | |
---|
| 119 | its = grid%sp31 ; ite = grid%ep31 ; ! note that tile is entire patch |
---|
| 120 | kts = grid%sp32 ; kte = grid%ep32 ; ! note that tile is entire patch |
---|
| 121 | jts = grid%sp33 ; jte = grid%ep33 ; ! note that tile is entire patch |
---|
| 122 | |
---|
| 123 | END SELECT |
---|
| 124 | |
---|
| 125 | CALL model_to_grid_config_rec ( grid%id , model_config_rec , config_flags ) |
---|
| 126 | |
---|
| 127 | ! here we check to see if the boundary conditions are set properly |
---|
| 128 | |
---|
| 129 | CALL boundary_condition_check( config_flags, bdyzone, error, grid%id ) |
---|
| 130 | |
---|
| 131 | grid%itimestep=0 |
---|
| 132 | grid%step_number = 0 |
---|
| 133 | |
---|
| 134 | |
---|
| 135 | #ifdef DM_PARALLEL |
---|
| 136 | CALL wrf_dm_bcast_bytes( icm , IWORDSIZE ) |
---|
| 137 | CALL wrf_dm_bcast_bytes( jcm , IWORDSIZE ) |
---|
| 138 | #endif |
---|
| 139 | |
---|
| 140 | ! Initialize 2D surface arrays |
---|
| 141 | |
---|
| 142 | nxx = ide-ids ! Don't include u-stagger |
---|
| 143 | nyy = jde-jds ! Don't include v-stagger |
---|
| 144 | dphi = 180./REAL(nyy) |
---|
| 145 | dlam = 360./REAL(nxx) |
---|
| 146 | |
---|
| 147 | DO j = jts, jte |
---|
| 148 | DO i = its, ite |
---|
| 149 | ! ig is the I index in the global (domain) span of the array. |
---|
| 150 | ! jg is the J index in the global (domain) span of the array. |
---|
| 151 | ig = i - ids + 1 ! ids is not necessarily 1 |
---|
| 152 | jg = j - jds + 1 ! jds is not necessarily 1 |
---|
| 153 | |
---|
| 154 | grid%xlat(i,j) = (REAL(jg)-0.5)*dphi-90. |
---|
| 155 | grid%xlong(i,j) = (REAL(ig)-0.5)*dlam-180. |
---|
| 156 | vlat = grid%xlat(i,j) - 0.5*dphi |
---|
| 157 | |
---|
| 158 | grid%clat(i,j) = grid%xlat(i,j) |
---|
| 159 | grid%clong(i,j) = grid%xlong(i,j) |
---|
| 160 | |
---|
| 161 | grid%msftx(i,j) = 1./COS(grid%xlat(i,j)*degrad) |
---|
| 162 | grid%msfty(i,j) = 1. |
---|
| 163 | grid%msfux(i,j) = 1./COS(grid%xlat(i,j)*degrad) |
---|
| 164 | grid%msfuy(i,j) = 1. |
---|
| 165 | grid%e(i,j) = 2*EOMEG*COS(grid%xlat(i,j)*degrad) |
---|
| 166 | grid%f(i,j) = 2*EOMEG*SIN(grid%xlat(i,j)*degrad) |
---|
| 167 | |
---|
| 168 | ! The following two are the cosine and sine of the rotation |
---|
| 169 | ! of projection. Simple cylindrical is *simple* ... no rotation! |
---|
| 170 | grid%sina(i,j) = 0. |
---|
| 171 | grid%cosa(i,j) = 1. |
---|
| 172 | |
---|
| 173 | END DO |
---|
| 174 | END DO |
---|
| 175 | |
---|
| 176 | ! DO j = max(jds+1,jts), min(jde-1,jte) |
---|
| 177 | DO j = jts, jte |
---|
| 178 | DO i = its, ite |
---|
| 179 | vlat = grid%xlat(i,j) - 0.5*dphi |
---|
| 180 | grid%msfvx(i,j) = 1./COS(vlat*degrad) |
---|
| 181 | grid%msfvy(i,j) = 1. |
---|
| 182 | grid%msfvx_inv(i,j) = 1./grid%msfvx(i,j) |
---|
| 183 | END DO |
---|
| 184 | END DO |
---|
| 185 | |
---|
| 186 | IF(jts == jds) THEN |
---|
| 187 | DO i = its, ite |
---|
| 188 | grid%msfvx(i,jts) = 00. |
---|
| 189 | grid%msfvx_inv(i,jts) = 0. |
---|
| 190 | END DO |
---|
| 191 | END IF |
---|
| 192 | |
---|
| 193 | IF(jte == jde) THEN |
---|
| 194 | DO i = its, ite |
---|
| 195 | grid%msfvx(i,jte) = 00. |
---|
| 196 | grid%msfvx_inv(i,jte) = 0. |
---|
| 197 | END DO |
---|
| 198 | END IF |
---|
| 199 | |
---|
| 200 | DO j=jts,jte |
---|
| 201 | vlat = grid%xlat(its,j) - 0.5*dphi |
---|
| 202 | write(6,*) j,vlat,grid%msfvx(its,j),grid%msfvx_inv(its,j) |
---|
| 203 | ENDDO |
---|
| 204 | |
---|
| 205 | DO j=jts,jte |
---|
| 206 | DO i=its,ite |
---|
| 207 | grid%ht(i,j) = 0. |
---|
| 208 | |
---|
| 209 | grid%albedo(i,j) = 0. |
---|
| 210 | grid%thc(i,j) = 1000. |
---|
| 211 | grid%znt(i,j) = 0.01 |
---|
| 212 | grid%emiss(i,j) = 1. |
---|
| 213 | grid%ivgtyp(i,j) = 1 |
---|
| 214 | grid%lu_index(i,j) = REAL(ivgtyp(i,j)) |
---|
| 215 | grid%xland(i,j) = 1. |
---|
| 216 | grid%mavail(i,j) = 0. |
---|
| 217 | END DO |
---|
| 218 | END DO |
---|
| 219 | |
---|
| 220 | grid%dx = dlam*degrad/reradius |
---|
| 221 | grid%dy = dphi*degrad/reradius |
---|
| 222 | grid%rdx = 1./grid%dx |
---|
| 223 | grid%rdy = 1./grid%dy |
---|
| 224 | |
---|
| 225 | !WRITE(*,*) '' |
---|
| 226 | !WRITE(*,'(A,1PG14.6,A,1PG14.6)') ' For the namelist: dx =',grid%dx,', dy =',grid%dy |
---|
| 227 | |
---|
| 228 | CALL nl_set_mminlu(1,' ') |
---|
| 229 | grid%iswater = 0 |
---|
| 230 | grid%cen_lat = 0. |
---|
| 231 | grid%cen_lon = 0. |
---|
| 232 | grid%truelat1 = 0. |
---|
| 233 | grid%truelat2 = 0. |
---|
| 234 | grid%moad_cen_lat = 0. |
---|
| 235 | grid%stand_lon = 0. |
---|
| 236 | ! Apparently, map projection 0 is "none" which actually turns out to be |
---|
| 237 | ! a regular grid of latitudes and longitudes, the simple cylindrical projection |
---|
| 238 | grid%map_proj = 0 |
---|
| 239 | |
---|
| 240 | DO k = kds, kde |
---|
| 241 | grid%znw(k) = 1. - REAL(k-kds)/REAL(kde-kds) |
---|
| 242 | END DO |
---|
| 243 | |
---|
| 244 | DO k=1, kde-1 |
---|
| 245 | grid%dnw(k) = grid%znw(k+1) - grid%znw(k) |
---|
| 246 | grid%rdnw(k) = 1./grid%dnw(k) |
---|
| 247 | grid%znu(k) = 0.5*(grid%znw(k+1)+grid%znw(k)) |
---|
| 248 | ENDDO |
---|
| 249 | DO k=2, kde-1 |
---|
| 250 | grid%dn(k) = 0.5*(grid%dnw(k)+grid%dnw(k-1)) |
---|
| 251 | grid%rdn(k) = 1./grid%dn(k) |
---|
| 252 | grid%fnp(k) = .5* grid%dnw(k )/grid%dn(k) |
---|
| 253 | grid%fnm(k) = .5* grid%dnw(k-1)/grid%dn(k) |
---|
| 254 | ENDDO |
---|
| 255 | |
---|
| 256 | cof1 = (2.*grid%dn(2)+grid%dn(3))/(grid%dn(2)+grid%dn(3))*grid%dnw(1)/grid%dn(2) |
---|
| 257 | cof2 = grid%dn(2) /(grid%dn(2)+grid%dn(3))*grid%dnw(1)/grid%dn(3) |
---|
| 258 | grid%cf1 = grid%fnp(2) + cof1 |
---|
| 259 | grid%cf2 = grid%fnm(2) - cof1 - cof2 |
---|
| 260 | grid%cf3 = cof2 |
---|
| 261 | |
---|
| 262 | grid%cfn = (.5*grid%dnw(kde-1)+grid%dn(kde-1))/grid%dn(kde-1) |
---|
| 263 | grid%cfn1 = -.5*grid%dnw(kde-1)/grid%dn(kde-1) |
---|
| 264 | |
---|
| 265 | |
---|
| 266 | ! Need to add perturbations to initial profile. Set up random number |
---|
| 267 | ! seed here. |
---|
| 268 | CALL random_seed |
---|
| 269 | |
---|
| 270 | ! General assumption from here after is that the initial temperature |
---|
| 271 | ! profile is isothermal at a value of T0, and the initial winds are |
---|
| 272 | ! all 0. |
---|
| 273 | |
---|
| 274 | ! find ptop for the desired ztop (ztop is input from the namelist) |
---|
| 275 | grid%p_top = p0 * EXP(-(g*config_flags%ztop)/(r_d*T0)) |
---|
| 276 | |
---|
| 277 | |
---|
| 278 | ! Values of geopotential (base, perturbation, and at p0) at the surface |
---|
| 279 | DO j = jts, jte |
---|
| 280 | DO i = its, ite |
---|
| 281 | grid%phb(i,1,j) = grid%ht(i,j)*g |
---|
| 282 | grid%php(i,1,j) = 0. ! This is perturbation geopotential |
---|
| 283 | ! Since this is an initial condition, there |
---|
| 284 | ! should be no perturbation! |
---|
| 285 | grid%ph0(i,1,j) = grid%ht(i,j)*g |
---|
| 286 | ENDDO |
---|
| 287 | ENDDO |
---|
| 288 | |
---|
| 289 | |
---|
| 290 | DO J = jts, jte |
---|
| 291 | DO I = its, ite |
---|
| 292 | |
---|
| 293 | p_surf = p0 * EXP(-(g*grid%phb(i,1,j)/g)/(r_d*T0)) |
---|
| 294 | grid%mub(i,j) = p_surf-grid%p_top |
---|
| 295 | |
---|
| 296 | ! given p (coordinate), calculate theta and compute 1/rho from equation |
---|
| 297 | ! of state |
---|
| 298 | |
---|
| 299 | DO K = kts, kte-1 |
---|
| 300 | p_level = grid%znu(k)*(p_surf - grid%p_top) + grid%p_top |
---|
| 301 | grid%pb(i,k,j) = p_level |
---|
| 302 | |
---|
| 303 | grid%t_init(i,k,j) = T0*(p0/p_level)**rcp |
---|
| 304 | grid%t_init(i,k,j) = grid%t_init(i,k,j) - t0 |
---|
| 305 | |
---|
| 306 | grid%alb(i,k,j)=(r_d/p1000mb)*(grid%t_init(i,k,j)+t0)*(grid%pb(i,k,j)/p1000mb)**cvpm |
---|
| 307 | END DO |
---|
| 308 | |
---|
| 309 | ! calculate hydrostatic balance (alternatively we could interpolate |
---|
| 310 | ! the geopotential from the sounding, but this assures that the base |
---|
| 311 | ! state is in exact hydrostatic balance with respect to the model eqns. |
---|
| 312 | |
---|
| 313 | DO k = kts+1, kte |
---|
| 314 | grid%phb(i,k,j) = grid%phb(i,k-1,j) - grid%dnw(k-1)*grid%mub(i,j)*grid%alb(i,k-1,j) |
---|
| 315 | ENDDO |
---|
| 316 | |
---|
| 317 | ENDDO |
---|
| 318 | ENDDO |
---|
| 319 | |
---|
| 320 | DO im = PARAM_FIRST_SCALAR, num_moist |
---|
| 321 | DO J = jts, jte |
---|
| 322 | DO K = kts, kte-1 |
---|
| 323 | DO I = its, ite |
---|
| 324 | grid%moist(i,k,j,im) = 0. |
---|
| 325 | END DO |
---|
| 326 | END DO |
---|
| 327 | END DO |
---|
| 328 | END DO |
---|
| 329 | |
---|
| 330 | ! Now calculate the full (hydrostatically-balanced) state for each column |
---|
| 331 | ! We will include moisture |
---|
| 332 | DO J = jts, jte |
---|
| 333 | DO I = its, ite |
---|
| 334 | |
---|
| 335 | ! At this point p_top is already set. find the DRY mass in the column |
---|
| 336 | pd_surf = p0 * EXP(-(g*grid%phb(i,1,j)/g)/(r_d*T0)) |
---|
| 337 | |
---|
| 338 | ! compute the perturbation mass (mu/mu_1/mu_2) and the full mass |
---|
| 339 | grid%mu_1(i,j) = pd_surf-grid%p_top - grid%mub(i,j) |
---|
| 340 | grid%mu_2(i,j) = grid%mu_1(i,j) |
---|
| 341 | grid%mu0(i,j) = grid%mu_1(i,j) + grid%mub(i,j) |
---|
| 342 | |
---|
| 343 | ! given the dry pressure and coordinate system, calculate the |
---|
| 344 | ! perturbation potential temperature (t/t_1/t_2) |
---|
| 345 | |
---|
| 346 | DO k = kds, kde-1 |
---|
| 347 | p_level = grid%znu(k)*(pd_surf - grid%p_top) + grid%p_top |
---|
| 348 | grid%t_1(i,k,j) = T0*(p0/p_level)**rcp |
---|
| 349 | ! Add a small perturbation to initial isothermal profile |
---|
| 350 | CALL random_number(tperturb) |
---|
| 351 | grid%t_1(i,k,j)=grid%t_1(i,k,j)*(1.0+0.004*(tperturb-0.5)) |
---|
| 352 | grid%t_1(i,k,j) = grid%t_1(i,k,j)-t0 |
---|
| 353 | grid%t_2(i,k,j) = grid%t_1(i,k,j) |
---|
| 354 | END DO |
---|
| 355 | |
---|
| 356 | |
---|
| 357 | ! integrate the hydrostatic equation (from the RHS of the bigstep |
---|
| 358 | ! vertical momentum equation) down from the top to get p. |
---|
| 359 | ! first from the top of the model to the top pressure |
---|
| 360 | |
---|
| 361 | k = kte-1 ! top level |
---|
| 362 | |
---|
| 363 | qvf1 = 0.5*(grid%moist(i,k,j,P_QV)+grid%moist(i,k,j,P_QV)) |
---|
| 364 | qvf2 = 1./(1.+qvf1) |
---|
| 365 | qvf1 = qvf1*qvf2 |
---|
| 366 | |
---|
| 367 | ! grid%p(i,k,j) = - 0.5*grid%mu_1(i,j)/grid%rdnw(k) |
---|
| 368 | grid%p(i,k,j) = - 0.5*(grid%mu_1(i,j)+qvf1*grid%mub(i,j))/grid%rdnw(k)/qvf2 |
---|
| 369 | qvf = 1. + rvovrd*grid%moist(i,k,j,P_QV) |
---|
| 370 | grid%alt(i,k,j) = (r_d/p1000mb)*(grid%t_1(i,k,j)+t0)*qvf* & |
---|
| 371 | (((grid%p(i,k,j)+grid%pb(i,k,j))/p1000mb)**cvpm) |
---|
| 372 | grid%al(i,k,j) = grid%alt(i,k,j) - grid%alb(i,k,j) |
---|
| 373 | |
---|
| 374 | ! down the column |
---|
| 375 | |
---|
| 376 | do k=kte-2,kts,-1 |
---|
| 377 | qvf1 = 0.5*(grid%moist(i,k,j,P_QV)+grid%moist(i,k+1,j,P_QV)) |
---|
| 378 | qvf2 = 1./(1.+qvf1) |
---|
| 379 | qvf1 = qvf1*qvf2 |
---|
| 380 | grid%p(i,k,j) = grid%p(i,k+1,j) - (grid%mu_1(i,j) + qvf1*grid%mub(i,j))/qvf2/grid%rdn(k+1) |
---|
| 381 | qvf = 1. + rvovrd*grid%moist(i,k,j,P_QV) |
---|
| 382 | grid%alt(i,k,j) = (r_d/p1000mb)*(grid%t_1(i,k,j)+t0)*qvf* & |
---|
| 383 | (((grid%p(i,k,j)+grid%pb(i,k,j))/p1000mb)**cvpm) |
---|
| 384 | grid%al(i,k,j) = grid%alt(i,k,j) - grid%alb(i,k,j) |
---|
| 385 | enddo |
---|
| 386 | |
---|
| 387 | ! this is the hydrostatic equation used in the model after the |
---|
| 388 | ! small timesteps. In the model, al (inverse density) |
---|
| 389 | ! is computed from the geopotential. |
---|
| 390 | |
---|
| 391 | grid%ph_1(i,1,j) = 0. |
---|
| 392 | DO k = kts+1,kte |
---|
| 393 | grid%ph_1(i,k,j) = grid%ph_1(i,k-1,j) - (1./grid%rdnw(k-1))*( & |
---|
| 394 | (grid%mub(i,j)+grid%mu_1(i,j))*grid%al(i,k-1,j)+ & |
---|
| 395 | grid%mu_1(i,j)*grid%alb(i,k-1,j) ) |
---|
| 396 | |
---|
| 397 | grid%ph_2(i,k,j) = grid%ph_1(i,k,j) |
---|
| 398 | grid%ph0(i,k,j) = grid%ph_1(i,k,j) + grid%phb(i,k,j) |
---|
| 399 | ENDDO |
---|
| 400 | |
---|
| 401 | END DO |
---|
| 402 | END DO |
---|
| 403 | |
---|
| 404 | |
---|
| 405 | |
---|
| 406 | ! Now set U & V |
---|
| 407 | DO J = jts, jte |
---|
| 408 | DO K = kts, kte-1 |
---|
| 409 | DO I = its, ite |
---|
| 410 | grid%u_1(i,k,j) = 0. |
---|
| 411 | grid%u_2(i,k,j) = 0. |
---|
| 412 | grid%v_1(i,k,j) = 0. |
---|
| 413 | grid%v_2(i,k,j) = 0. |
---|
| 414 | END DO |
---|
| 415 | END DO |
---|
| 416 | END DO |
---|
| 417 | |
---|
| 418 | |
---|
| 419 | DO j=jts, jte |
---|
| 420 | DO k=kds, kde |
---|
| 421 | DO i=its, ite |
---|
| 422 | grid%ww(i,k,j) = 0. |
---|
| 423 | grid%w_1(i,k,j) = 0. |
---|
| 424 | grid%w_2(i,k,j) = 0. |
---|
| 425 | grid%h_diabatic(i,k,j) = 0. |
---|
| 426 | END DO |
---|
| 427 | END DO |
---|
| 428 | END DO |
---|
| 429 | |
---|
| 430 | |
---|
| 431 | DO k=kts,kte |
---|
| 432 | grid%t_base(k) = grid%t_init(its,k,jts) |
---|
| 433 | grid%qv_base(k) = 0. |
---|
| 434 | grid%u_base(k) = 0. |
---|
| 435 | grid%v_base(k) = 0. |
---|
| 436 | END DO |
---|
| 437 | |
---|
| 438 | ! One subsurface layer: infinite slab at constant temperature below |
---|
| 439 | ! the surface. Surface temperature is an infinitely thin "skin" on |
---|
| 440 | ! top of a half-infinite slab. The temperature of both the skin and |
---|
| 441 | ! the slab are determined from the initial nearest-surface-air-layer |
---|
| 442 | ! temperature. |
---|
| 443 | DO J = jts, MIN(jte, jde-1) |
---|
| 444 | DO I = its, MIN(ite, ide-1) |
---|
| 445 | thtmp = grid%t_2(i,1,j)+t0 |
---|
| 446 | ptmp = grid%p(i,1,j)+grid%pb(i,1,j) |
---|
| 447 | temp(1) = thtmp * (ptmp/p1000mb)**rcp |
---|
| 448 | thtmp = grid%t_2(i,2,j)+t0 |
---|
| 449 | ptmp = grid%p(i,2,j)+grid%pb(i,2,j) |
---|
| 450 | temp(2) = thtmp * (ptmp/p1000mb)**rcp |
---|
| 451 | thtmp = grid%t_2(i,3,j)+t0 |
---|
| 452 | ptmp = grid%p(i,3,j)+grid%pb(i,3,j) |
---|
| 453 | temp(3) = thtmp * (ptmp/p1000mb)**rcp |
---|
| 454 | grid%tsk(I,J)=cf1*temp(1)+cf2*temp(2)+cf3*temp(3) |
---|
| 455 | grid%tmn(I,J)=grid%tsk(I,J)-0.5 |
---|
| 456 | END DO |
---|
| 457 | END DO |
---|
| 458 | |
---|
| 459 | RETURN |
---|
| 460 | |
---|
| 461 | END SUBROUTINE init_domain_rk |
---|
| 462 | |
---|
| 463 | !--------------------------------------------------------------------- |
---|
| 464 | |
---|
| 465 | SUBROUTINE init_module_initialize |
---|
| 466 | END SUBROUTINE init_module_initialize |
---|
| 467 | |
---|
| 468 | !--------------------------------------------------------------------- |
---|
| 469 | |
---|
| 470 | END MODULE module_initialize_ideal |
---|