PageRenderTime 44ms CodeModel.GetById 10ms RepoModel.GetById 0ms app.codeStats 0ms

/wrfv2_fire/dyn_em/module_initialize_heldsuarez.F

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