PageRenderTime 54ms CodeModel.GetById 19ms RepoModel.GetById 0ms app.codeStats 1ms

/wrfv2_fire/dyn_em/module_initialize_quarter_ss.F

http://github.com/jbeezley/wrf-fire
FORTRAN Legacy | 818 lines | 490 code | 179 blank | 149 comment | 13 complexity | 3e8a94ebe59e283d49dfccc08b703209 MD5 | raw file
Possible License(s): AGPL-1.0
  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. ! This MODULE CONTAINS the following routines:
  6. ! initialize_field_test - 1. Set different fields to different constant
  7. ! values. This is only a test. If the correct
  8. ! domain is not found (based upon the "id")
  9. ! then a fatal error is issued.
  10. !-----------------------------------------------------------------------
  11. MODULE module_initialize_ideal
  12. USE module_domain
  13. USE module_io_domain
  14. USE module_state_description
  15. USE module_model_constants
  16. USE module_bc
  17. USE module_timing
  18. USE module_configure
  19. USE module_init_utilities
  20. #ifdef DM_PARALLEL
  21. USE module_dm
  22. #endif
  23. CONTAINS
  24. !-------------------------------------------------------------------
  25. ! this is a wrapper for the solver-specific init_domain routines.
  26. ! Also dereferences the grid variables and passes them down as arguments.
  27. ! This is crucial, since the lower level routines may do message passing
  28. ! and this will get fouled up on machines that insist on passing down
  29. ! copies of assumed-shape arrays (by passing down as arguments, the
  30. ! data are treated as assumed-size -- ie. f77 -- arrays and the copying
  31. ! business is avoided). Fie on the F90 designers. Fie and a pox.
  32. SUBROUTINE init_domain ( grid )
  33. IMPLICIT NONE
  34. ! Input data.
  35. TYPE (domain), POINTER :: grid
  36. ! Local data.
  37. INTEGER :: idum1, idum2
  38. CALL set_scalar_indices_from_config ( head_grid%id , idum1, idum2 )
  39. CALL init_domain_rk( grid &
  40. !
  41. #include <actual_new_args.inc>
  42. !
  43. )
  44. END SUBROUTINE init_domain
  45. !-------------------------------------------------------------------
  46. SUBROUTINE init_domain_rk ( grid &
  47. !
  48. # include <dummy_new_args.inc>
  49. !
  50. )
  51. IMPLICIT NONE
  52. ! Input data.
  53. TYPE (domain), POINTER :: grid
  54. # include <dummy_new_decl.inc>
  55. TYPE (grid_config_rec_type) :: config_flags
  56. ! Local data
  57. INTEGER :: &
  58. ids, ide, jds, jde, kds, kde, &
  59. ims, ime, jms, jme, kms, kme, &
  60. its, ite, jts, jte, kts, kte, &
  61. i, j, k
  62. ! Local data
  63. INTEGER, PARAMETER :: nl_max = 1000
  64. REAL, DIMENSION(nl_max) :: zk, p_in, theta, rho, u, v, qv, pd_in
  65. INTEGER :: nl_in
  66. INTEGER :: icm,jcm, ii, im1, jj, jm1, loop, error, fid, nxc, nyc
  67. REAL :: u_mean,v_mean, f0, p_surf, p_level, qvf, z_at_v, z_at_u
  68. REAL :: z_scale, xrad, yrad, zrad, rad, delt, cof1, cof2
  69. ! REAL, EXTERNAL :: interp_0
  70. REAL :: hm
  71. REAL :: pi
  72. ! stuff from original initialization that has been dropped from the Registry
  73. REAL :: vnu, xnu, xnus, dinit0, cbh, p0_temp, t0_temp, zd, zt
  74. REAL :: qvf1, qvf2, pd_surf
  75. INTEGER :: it
  76. real :: thtmp, ptmp, temp(3)
  77. LOGICAL :: moisture_init
  78. LOGICAL :: stretch_grid, dry_sounding
  79. INTEGER :: xs , xe , ys , ye
  80. REAL :: mtn_ht
  81. LOGICAL, EXTERNAL :: wrf_dm_on_monitor
  82. SELECT CASE ( model_data_order )
  83. CASE ( DATA_ORDER_ZXY )
  84. kds = grid%sd31 ; kde = grid%ed31 ;
  85. ids = grid%sd32 ; ide = grid%ed32 ;
  86. jds = grid%sd33 ; jde = grid%ed33 ;
  87. kms = grid%sm31 ; kme = grid%em31 ;
  88. ims = grid%sm32 ; ime = grid%em32 ;
  89. jms = grid%sm33 ; jme = grid%em33 ;
  90. kts = grid%sp31 ; kte = grid%ep31 ; ! note that tile is entire patch
  91. its = grid%sp32 ; ite = grid%ep32 ; ! note that tile is entire patch
  92. jts = grid%sp33 ; jte = grid%ep33 ; ! note that tile is entire patch
  93. CASE ( DATA_ORDER_XYZ )
  94. ids = grid%sd31 ; ide = grid%ed31 ;
  95. jds = grid%sd32 ; jde = grid%ed32 ;
  96. kds = grid%sd33 ; kde = grid%ed33 ;
  97. ims = grid%sm31 ; ime = grid%em31 ;
  98. jms = grid%sm32 ; jme = grid%em32 ;
  99. kms = grid%sm33 ; kme = grid%em33 ;
  100. its = grid%sp31 ; ite = grid%ep31 ; ! note that tile is entire patch
  101. jts = grid%sp32 ; jte = grid%ep32 ; ! note that tile is entire patch
  102. kts = grid%sp33 ; kte = grid%ep33 ; ! note that tile is entire patch
  103. CASE ( DATA_ORDER_XZY )
  104. ids = grid%sd31 ; ide = grid%ed31 ;
  105. kds = grid%sd32 ; kde = grid%ed32 ;
  106. jds = grid%sd33 ; jde = grid%ed33 ;
  107. ims = grid%sm31 ; ime = grid%em31 ;
  108. kms = grid%sm32 ; kme = grid%em32 ;
  109. jms = grid%sm33 ; jme = grid%em33 ;
  110. its = grid%sp31 ; ite = grid%ep31 ; ! note that tile is entire patch
  111. kts = grid%sp32 ; kte = grid%ep32 ; ! note that tile is entire patch
  112. jts = grid%sp33 ; jte = grid%ep33 ; ! note that tile is entire patch
  113. END SELECT
  114. stretch_grid = .true.
  115. delt = 3.
  116. ! z_scale = .50
  117. z_scale = .40
  118. pi = 2.*asin(1.0)
  119. write(6,*) ' pi is ',pi
  120. nxc = (ide-ids)/2
  121. nyc = (jde-jds)/2
  122. CALL model_to_grid_config_rec ( grid%id , model_config_rec , config_flags )
  123. ! here we check to see if the boundary conditions are set properly
  124. CALL boundary_condition_check( config_flags, bdyzone, error, grid%id )
  125. moisture_init = .true.
  126. grid%itimestep=0
  127. #ifdef DM_PARALLEL
  128. CALL wrf_dm_bcast_bytes( icm , IWORDSIZE )
  129. CALL wrf_dm_bcast_bytes( jcm , IWORDSIZE )
  130. #endif
  131. CALL nl_set_mminlu(1, ' ')
  132. CALL nl_set_iswater(1,0)
  133. CALL nl_set_cen_lat(1,40.)
  134. CALL nl_set_cen_lon(1,-105.)
  135. CALL nl_set_truelat1(1,0.)
  136. CALL nl_set_truelat2(1,0.)
  137. CALL nl_set_moad_cen_lat (1,0.)
  138. CALL nl_set_stand_lon (1,0.)
  139. CALL nl_set_pole_lon (1,0.)
  140. CALL nl_set_pole_lat (1,90.)
  141. CALL nl_set_map_proj(1,0)
  142. ! here we initialize data we currently is not initialized
  143. ! in the input data
  144. DO j = jts, jte
  145. DO i = its, ite
  146. grid%msftx(i,j) = 1.
  147. grid%msfty(i,j) = 1.
  148. grid%msfux(i,j) = 1.
  149. grid%msfuy(i,j) = 1.
  150. grid%msfvx(i,j) = 1.
  151. grid%msfvx_inv(i,j)= 1.
  152. grid%msfvy(i,j) = 1.
  153. grid%sina(i,j) = 0.
  154. grid%cosa(i,j) = 1.
  155. grid%e(i,j) = 0.
  156. grid%f(i,j) = 0.
  157. END DO
  158. END DO
  159. DO j = jts, jte
  160. DO k = kts, kte
  161. DO i = its, ite
  162. grid%ww(i,k,j) = 0.
  163. END DO
  164. END DO
  165. END DO
  166. grid%step_number = 0
  167. ! set up the grid
  168. IF (stretch_grid) THEN ! exponential stretch for eta (nearly constant dz)
  169. DO k=1, kde
  170. grid%znw(k) = (exp(-(k-1)/float(kde-1)/z_scale) - exp(-1./z_scale))/ &
  171. (1.-exp(-1./z_scale))
  172. ENDDO
  173. ELSE
  174. DO k=1, kde
  175. grid%znw(k) = 1. - float(k-1)/float(kde-1)
  176. ENDDO
  177. ENDIF
  178. DO k=1, kde-1
  179. grid%dnw(k) = grid%znw(k+1) - grid%znw(k)
  180. grid%rdnw(k) = 1./grid%dnw(k)
  181. grid%znu(k) = 0.5*(grid%znw(k+1)+grid%znw(k))
  182. ENDDO
  183. DO k=2, kde-1
  184. grid%dn(k) = 0.5*(grid%dnw(k)+grid%dnw(k-1))
  185. grid%rdn(k) = 1./grid%dn(k)
  186. grid%fnp(k) = .5* grid%dnw(k )/grid%dn(k)
  187. grid%fnm(k) = .5* grid%dnw(k-1)/grid%dn(k)
  188. ENDDO
  189. cof1 = (2.*grid%dn(2)+grid%dn(3))/(grid%dn(2)+grid%dn(3))*grid%dnw(1)/grid%dn(2)
  190. cof2 = grid%dn(2) /(grid%dn(2)+grid%dn(3))*grid%dnw(1)/grid%dn(3)
  191. grid%cf1 = grid%fnp(2) + cof1
  192. grid%cf2 = grid%fnm(2) - cof1 - cof2
  193. grid%cf3 = cof2
  194. grid%cfn = (.5*grid%dnw(kde-1)+grid%dn(kde-1))/grid%dn(kde-1)
  195. grid%cfn1 = -.5*grid%dnw(kde-1)/grid%dn(kde-1)
  196. grid%rdx = 1./config_flags%dx
  197. grid%rdy = 1./config_flags%dy
  198. ! get the sounding from the ascii sounding file, first get dry sounding and
  199. ! calculate base state
  200. dry_sounding = .true.
  201. IF ( wrf_dm_on_monitor() ) THEN
  202. write(6,*) ' getting dry sounding for base state '
  203. CALL get_sounding( zk, p_in, pd_in, theta, rho, u, v, qv, dry_sounding, nl_max, nl_in )
  204. ENDIF
  205. CALL wrf_dm_bcast_real( zk , nl_max )
  206. CALL wrf_dm_bcast_real( p_in , nl_max )
  207. CALL wrf_dm_bcast_real( pd_in , nl_max )
  208. CALL wrf_dm_bcast_real( theta , nl_max )
  209. CALL wrf_dm_bcast_real( rho , nl_max )
  210. CALL wrf_dm_bcast_real( u , nl_max )
  211. CALL wrf_dm_bcast_real( v , nl_max )
  212. CALL wrf_dm_bcast_real( qv , nl_max )
  213. CALL wrf_dm_bcast_integer ( nl_in , 1 )
  214. write(6,*) ' returned from reading sounding, nl_in is ',nl_in
  215. ! find ptop for the desired ztop (ztop is input from the namelist),
  216. ! and find surface pressure
  217. grid%p_top = interp_0( p_in, zk, config_flags%ztop, nl_in )
  218. DO j=jts,jte
  219. DO i=its,ite
  220. grid%ht(i,j) = 0.
  221. ENDDO
  222. ENDDO
  223. xs=ide/2 -3
  224. xs=ids -3
  225. xe=xs + 6
  226. ys=jde/2 -3
  227. ye=ys + 6
  228. mtn_ht = 500
  229. #ifdef MTN
  230. DO j=max(ys,jds),min(ye,jde-1)
  231. DO i=max(xs,ids),min(xe,ide-1)
  232. grid%ht(i,j) = mtn_ht * 0.25 * &
  233. ( 1. + COS ( 2*pi/(xe-xs) * ( i-xs ) + pi ) ) * &
  234. ( 1. + COS ( 2*pi/(ye-ys) * ( j-ys ) + pi ) )
  235. ENDDO
  236. ENDDO
  237. #endif
  238. #ifdef EW_RIDGE
  239. DO j=max(ys,jds),min(ye,jde-1)
  240. DO i=ids,ide
  241. grid%ht(i,j) = mtn_ht * 0.50 * &
  242. ( 1. + COS ( 2*pi/(ye-ys) * ( j-ys ) + pi ) )
  243. ENDDO
  244. ENDDO
  245. #endif
  246. #ifdef NS_RIDGE
  247. DO j=jds,jde
  248. DO i=max(xs,ids),min(xe,ide-1)
  249. grid%ht(i,j) = mtn_ht * 0.50 * &
  250. ( 1. + COS ( 2*pi/(xe-xs) * ( i-xs ) + pi ) )
  251. ENDDO
  252. ENDDO
  253. #endif
  254. DO j=jts,jte
  255. DO i=its,ite
  256. grid%phb(i,1,j) = g * grid%ht(i,j)
  257. grid%ph0(i,1,j) = g * grid%ht(i,j)
  258. ENDDO
  259. ENDDO
  260. DO J = jts, jte
  261. DO I = its, ite
  262. p_surf = interp_0( p_in, zk, grid%phb(i,1,j)/g, nl_in )
  263. grid%mub(i,j) = p_surf-grid%p_top
  264. ! this is dry hydrostatic sounding (base state), so given grid%p (coordinate),
  265. ! interp theta (from interp) and compute 1/rho from eqn. of state
  266. DO K = 1, kte-1
  267. p_level = grid%znu(k)*(p_surf - grid%p_top) + grid%p_top
  268. grid%pb(i,k,j) = p_level
  269. grid%t_init(i,k,j) = interp_0( theta, p_in, p_level, nl_in ) - t0
  270. grid%alb(i,k,j) = (r_d/p1000mb)*(grid%t_init(i,k,j)+t0)*(grid%pb(i,k,j)/p1000mb)**cvpm
  271. ENDDO
  272. ! calc hydrostatic balance (alternatively we could interp the geopotential from the
  273. ! sounding, but this assures that the base state is in exact hydrostatic balance with
  274. ! respect to the model eqns.
  275. DO k = 2,kte
  276. 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)
  277. ENDDO
  278. ENDDO
  279. ENDDO
  280. IF ( wrf_dm_on_monitor() ) THEN
  281. write(6,*) ' ptop is ',grid%p_top
  282. write(6,*) ' base state grid%mub(1,1), p_surf is ',grid%mub(1,1),grid%mub(1,1)+grid%p_top
  283. ENDIF
  284. ! calculate full state for each column - this includes moisture.
  285. write(6,*) ' getting moist sounding for full state '
  286. dry_sounding = .false.
  287. CALL get_sounding( zk, p_in, pd_in, theta, rho, u, v, qv, dry_sounding, nl_max, nl_in )
  288. DO J = jts, min(jde-1,jte)
  289. DO I = its, min(ide-1,ite)
  290. ! At this point grid%p_top is already set. find the DRY mass in the column
  291. ! by interpolating the DRY pressure.
  292. pd_surf = interp_0( pd_in, zk, grid%phb(i,1,j)/g, nl_in )
  293. ! compute the perturbation mass and the full mass
  294. grid%mu_1(i,j) = pd_surf-grid%p_top - grid%mub(i,j)
  295. grid%mu_2(i,j) = grid%mu_1(i,j)
  296. grid%mu0(i,j) = grid%mu_1(i,j) + grid%mub(i,j)
  297. ! given the dry pressure and coordinate system, interp the potential
  298. ! temperature and qv
  299. do k=1,kde-1
  300. p_level = grid%znu(k)*(pd_surf - grid%p_top) + grid%p_top
  301. moist(i,k,j,P_QV) = interp_0( qv, pd_in, p_level, nl_in )
  302. grid%t_1(i,k,j) = interp_0( theta, pd_in, p_level, nl_in ) - t0
  303. grid%t_2(i,k,j) = grid%t_1(i,k,j)
  304. enddo
  305. ! integrate the hydrostatic equation (from the RHS of the bigstep
  306. ! vertical momentum equation) down from the top to get grid%p.
  307. ! first from the top of the model to the top pressure
  308. k = kte-1 ! top level
  309. qvf1 = 0.5*(moist(i,k,j,P_QV)+moist(i,k,j,P_QV))
  310. qvf2 = 1./(1.+qvf1)
  311. qvf1 = qvf1*qvf2
  312. ! grid%p(i,k,j) = - 0.5*grid%mu_1(i,j)/grid%rdnw(k)
  313. grid%p(i,k,j) = - 0.5*(grid%mu_1(i,j)+qvf1*grid%mub(i,j))/grid%rdnw(k)/qvf2
  314. qvf = 1. + rvovrd*moist(i,k,j,P_QV)
  315. grid%alt(i,k,j) = (r_d/p1000mb)*(grid%t_1(i,k,j)+t0)*qvf* &
  316. (((grid%p(i,k,j)+grid%pb(i,k,j))/p1000mb)**cvpm)
  317. grid%al(i,k,j) = grid%alt(i,k,j) - grid%alb(i,k,j)
  318. ! down the column
  319. do k=kte-2,1,-1
  320. qvf1 = 0.5*(moist(i,k,j,P_QV)+moist(i,k+1,j,P_QV))
  321. qvf2 = 1./(1.+qvf1)
  322. qvf1 = qvf1*qvf2
  323. 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)
  324. qvf = 1. + rvovrd*moist(i,k,j,P_QV)
  325. grid%alt(i,k,j) = (r_d/p1000mb)*(grid%t_1(i,k,j)+t0)*qvf* &
  326. (((grid%p(i,k,j)+grid%pb(i,k,j))/p1000mb)**cvpm)
  327. grid%al(i,k,j) = grid%alt(i,k,j) - grid%alb(i,k,j)
  328. enddo
  329. ! this is the hydrostatic equation used in the model after the
  330. ! small timesteps. In the model, grid%al (inverse density)
  331. ! is computed from the geopotential.
  332. grid%ph_1(i,1,j) = 0.
  333. DO k = 2,kte
  334. grid%ph_1(i,k,j) = grid%ph_1(i,k-1,j) - (1./grid%rdnw(k-1))*( &
  335. (grid%mub(i,j)+grid%mu_1(i,j))*grid%al(i,k-1,j)+ &
  336. grid%mu_1(i,j)*grid%alb(i,k-1,j) )
  337. grid%ph_2(i,k,j) = grid%ph_1(i,k,j)
  338. grid%ph0(i,k,j) = grid%ph_1(i,k,j) + grid%phb(i,k,j)
  339. ENDDO
  340. IF ( wrf_dm_on_monitor() ) THEN
  341. if((i==2) .and. (j==2)) then
  342. write(6,*) ' grid%ph_1 calc ',grid%ph_1(2,1,2),grid%ph_1(2,2,2),&
  343. grid%mu_1(2,2)+grid%mub(2,2),grid%mu_1(2,2), &
  344. grid%alb(2,1,2),grid%al(1,2,1),grid%rdnw(1)
  345. endif
  346. ENDIF
  347. ENDDO
  348. ENDDO
  349. !#if 0
  350. ! thermal perturbation to kick off convection
  351. write(6,*) ' nxc, nyc for perturbation ',nxc,nyc
  352. write(6,*) ' delt for perturbation ',delt
  353. DO J = jts, min(jde-1,jte)
  354. yrad = config_flags%dy*float(j-nyc)/10000.
  355. ! yrad = 0.
  356. DO I = its, min(ide-1,ite)
  357. xrad = config_flags%dx*float(i-nxc)/10000.
  358. ! xrad = 0.
  359. DO K = 1, kte-1
  360. ! put in preturbation theta (bubble) and recalc density. note,
  361. ! the mass in the column is not changing, so when theta changes,
  362. ! we recompute density and geopotential
  363. zrad = 0.5*(grid%ph_1(i,k,j)+grid%ph_1(i,k+1,j) &
  364. +grid%phb(i,k,j)+grid%phb(i,k+1,j))/g
  365. zrad = (zrad-1500.)/1500.
  366. RAD=SQRT(xrad*xrad+yrad*yrad+zrad*zrad)
  367. IF(RAD <= 1.) THEN
  368. grid%t_1(i,k,j)=grid%t_1(i,k,j)+delt*COS(.5*PI*RAD)**2
  369. grid%t_2(i,k,j)=grid%t_1(i,k,j)
  370. qvf = 1. + rvovrd*moist(i,k,j,P_QV)
  371. grid%alt(i,k,j) = (r_d/p1000mb)*(grid%t_1(i,k,j)+t0)*qvf* &
  372. (((grid%p(i,k,j)+grid%pb(i,k,j))/p1000mb)**cvpm)
  373. grid%al(i,k,j) = grid%alt(i,k,j) - grid%alb(i,k,j)
  374. ENDIF
  375. ENDDO
  376. ! rebalance hydrostatically
  377. DO k = 2,kte
  378. grid%ph_1(i,k,j) = grid%ph_1(i,k-1,j) - (1./grid%rdnw(k-1))*( &
  379. (grid%mub(i,j)+grid%mu_1(i,j))*grid%al(i,k-1,j)+ &
  380. grid%mu_1(i,j)*grid%alb(i,k-1,j) )
  381. grid%ph_2(i,k,j) = grid%ph_1(i,k,j)
  382. grid%ph0(i,k,j) = grid%ph_1(i,k,j) + grid%phb(i,k,j)
  383. ENDDO
  384. ENDDO
  385. ENDDO
  386. !#endif
  387. IF ( wrf_dm_on_monitor() ) THEN
  388. write(6,*) ' grid%mu_1 from comp ', grid%mu_1(1,1)
  389. write(6,*) ' full state sounding from comp, ph, grid%p, grid%al, grid%t_1, qv '
  390. do k=1,kde-1
  391. write(6,'(i3,1x,5(1x,1pe10.3))') k, grid%ph_1(1,k,1)+grid%phb(1,k,1), &
  392. grid%p(1,k,1)+grid%pb(1,k,1), grid%alt(1,k,1), &
  393. grid%t_1(1,k,1)+t0, moist(1,k,1,P_QV)
  394. enddo
  395. write(6,*) ' pert state sounding from comp, grid%ph_1, pp, alp, grid%t_1, qv '
  396. do k=1,kde-1
  397. write(6,'(i3,1x,5(1x,1pe10.3))') k, grid%ph_1(1,k,1), &
  398. grid%p(1,k,1), grid%al(1,k,1), &
  399. grid%t_1(1,k,1), moist(1,k,1,P_QV)
  400. enddo
  401. ENDIF
  402. ! interp v
  403. DO J = jts, jte
  404. DO I = its, min(ide-1,ite)
  405. IF (j == jds) THEN
  406. z_at_v = grid%phb(i,1,j)/g
  407. ELSE IF (j == jde) THEN
  408. z_at_v = grid%phb(i,1,j-1)/g
  409. ELSE
  410. z_at_v = 0.5*(grid%phb(i,1,j)+grid%phb(i,1,j-1))/g
  411. END IF
  412. p_surf = interp_0( p_in, zk, z_at_v, nl_in )
  413. DO K = 1, kte-1
  414. p_level = grid%znu(k)*(p_surf - grid%p_top) + grid%p_top
  415. grid%v_1(i,k,j) = interp_0( v, p_in, p_level, nl_in )
  416. grid%v_2(i,k,j) = grid%v_1(i,k,j)
  417. ENDDO
  418. ENDDO
  419. ENDDO
  420. ! interp u
  421. DO J = jts, min(jde-1,jte)
  422. DO I = its, ite
  423. IF (i == ids) THEN
  424. z_at_u = grid%phb(i,1,j)/g
  425. ELSE IF (i == ide) THEN
  426. z_at_u = grid%phb(i-1,1,j)/g
  427. ELSE
  428. z_at_u = 0.5*(grid%phb(i,1,j)+grid%phb(i-1,1,j))/g
  429. END IF
  430. p_surf = interp_0( p_in, zk, z_at_u, nl_in )
  431. DO K = 1, kte-1
  432. p_level = grid%znu(k)*(p_surf - grid%p_top) + grid%p_top
  433. grid%u_1(i,k,j) = interp_0( u, p_in, p_level, nl_in )
  434. grid%u_2(i,k,j) = grid%u_1(i,k,j)
  435. ENDDO
  436. ENDDO
  437. ENDDO
  438. ! set w
  439. DO J = jts, min(jde-1,jte)
  440. DO K = kts, kte
  441. DO I = its, min(ide-1,ite)
  442. grid%w_1(i,k,j) = 0.
  443. grid%w_2(i,k,j) = 0.
  444. ENDDO
  445. ENDDO
  446. ENDDO
  447. ! set a few more things
  448. DO J = jts, min(jde-1,jte)
  449. DO K = kts, kte-1
  450. DO I = its, min(ide-1,ite)
  451. grid%h_diabatic(i,k,j) = 0.
  452. ENDDO
  453. ENDDO
  454. ENDDO
  455. IF ( wrf_dm_on_monitor() ) THEN
  456. DO k=1,kte-1
  457. grid%t_base(k) = grid%t_1(1,k,1)
  458. grid%qv_base(k) = moist(1,k,1,P_QV)
  459. grid%u_base(k) = grid%u_1(1,k,1)
  460. grid%v_base(k) = grid%v_1(1,k,1)
  461. grid%z_base(k) = 0.5*(grid%phb(1,k,1)+grid%phb(1,k+1,1)+grid%ph_1(1,k,1)+grid%ph_1(1,k+1,1))/g
  462. ENDDO
  463. ENDIF
  464. CALL wrf_dm_bcast_real( grid%t_base , kte )
  465. CALL wrf_dm_bcast_real( grid%qv_base , kte )
  466. CALL wrf_dm_bcast_real( grid%u_base , kte )
  467. CALL wrf_dm_bcast_real( grid%v_base , kte )
  468. CALL wrf_dm_bcast_real( grid%z_base , kte )
  469. DO J = jts, min(jde-1,jte)
  470. DO I = its, min(ide-1,ite)
  471. thtmp = grid%t_2(i,1,j)+t0
  472. ptmp = grid%p(i,1,j)+grid%pb(i,1,j)
  473. temp(1) = thtmp * (ptmp/p1000mb)**rcp
  474. thtmp = grid%t_2(i,2,j)+t0
  475. ptmp = grid%p(i,2,j)+grid%pb(i,2,j)
  476. temp(2) = thtmp * (ptmp/p1000mb)**rcp
  477. thtmp = grid%t_2(i,3,j)+t0
  478. ptmp = grid%p(i,3,j)+grid%pb(i,3,j)
  479. temp(3) = thtmp * (ptmp/p1000mb)**rcp
  480. grid%tsk(I,J)=grid%cf1*temp(1)+grid%cf2*temp(2)+grid%cf3*temp(3)
  481. grid%tmn(I,J)=grid%tsk(I,J)-0.5
  482. ENDDO
  483. ENDDO
  484. END SUBROUTINE init_domain_rk
  485. SUBROUTINE init_module_initialize
  486. END SUBROUTINE init_module_initialize
  487. !---------------------------------------------------------------------
  488. ! test driver for get_sounding
  489. !
  490. ! implicit none
  491. ! integer n
  492. ! parameter(n = 1000)
  493. ! real zk(n),p(n),theta(n),rho(n),u(n),v(n),qv(n),pd(n)
  494. ! logical dry
  495. ! integer nl,k
  496. !
  497. ! dry = .false.
  498. ! dry = .true.
  499. ! call get_sounding( zk, p, pd, theta, rho, u, v, qv, dry, n, nl )
  500. ! write(6,*) ' input levels ',nl
  501. ! write(6,*) ' sounding '
  502. ! write(6,*) ' k height(m) press (Pa) pd(Pa) theta (K) den(kg/m^3) u(m/s) v(m/s) qv(g/g) '
  503. ! do k=1,nl
  504. ! write(6,'(1x,i3,8(1x,1pe10.3))') k, zk(k), p(k), pd(k), theta(k), rho(k), u(k), v(k), qv(k)
  505. ! enddo
  506. ! end
  507. !
  508. !---------------------------------------------------------------------------
  509. subroutine get_sounding( zk, p, p_dry, theta, rho, &
  510. u, v, qv, dry, nl_max, nl_in )
  511. implicit none
  512. integer nl_max, nl_in
  513. real zk(nl_max), p(nl_max), theta(nl_max), rho(nl_max), &
  514. u(nl_max), v(nl_max), qv(nl_max), p_dry(nl_max)
  515. logical dry
  516. integer n
  517. parameter(n=1000)
  518. logical debug
  519. parameter( debug = .true.)
  520. ! input sounding data
  521. real p_surf, th_surf, qv_surf
  522. real pi_surf, pi(n)
  523. real h_input(n), th_input(n), qv_input(n), u_input(n), v_input(n)
  524. ! diagnostics
  525. real rho_surf, p_input(n), rho_input(n)
  526. real pm_input(n) ! this are for full moist sounding
  527. ! local data
  528. real r
  529. parameter (r = r_d)
  530. integer k, it, nl
  531. real qvf, qvf1, dz
  532. ! first, read the sounding
  533. call read_sounding( p_surf, th_surf, qv_surf, &
  534. h_input, th_input, qv_input, u_input, v_input,n, nl, debug )
  535. if(dry) then
  536. do k=1,nl
  537. qv_input(k) = 0.
  538. enddo
  539. endif
  540. if(debug) write(6,*) ' number of input levels = ',nl
  541. nl_in = nl
  542. if(nl_in .gt. nl_max ) then
  543. write(6,*) ' too many levels for input arrays ',nl_in,nl_max
  544. call wrf_error_fatal ( ' too many levels for input arrays ' )
  545. end if
  546. ! compute diagnostics,
  547. ! first, convert qv(g/kg) to qv(g/g)
  548. do k=1,nl
  549. qv_input(k) = 0.001*qv_input(k)
  550. enddo
  551. p_surf = 100.*p_surf ! convert to pascals
  552. qvf = 1. + rvovrd*qv_input(1)
  553. rho_surf = 1./((r/p1000mb)*th_surf*qvf*((p_surf/p1000mb)**cvpm))
  554. pi_surf = (p_surf/p1000mb)**(r/cp)
  555. if(debug) then
  556. write(6,*) ' surface density is ',rho_surf
  557. write(6,*) ' surface pi is ',pi_surf
  558. end if
  559. ! integrate moist sounding hydrostatically, starting from the
  560. ! specified surface pressure
  561. ! -> first, integrate from surface to lowest level
  562. qvf = 1. + rvovrd*qv_input(1)
  563. qvf1 = 1. + qv_input(1)
  564. rho_input(1) = rho_surf
  565. dz = h_input(1)
  566. do it=1,10
  567. pm_input(1) = p_surf &
  568. - 0.5*dz*(rho_surf+rho_input(1))*g*qvf1
  569. rho_input(1) = 1./((r/p1000mb)*th_input(1)*qvf*((pm_input(1)/p1000mb)**cvpm))
  570. enddo
  571. ! integrate up the column
  572. do k=2,nl
  573. rho_input(k) = rho_input(k-1)
  574. dz = h_input(k)-h_input(k-1)
  575. qvf1 = 0.5*(2.+(qv_input(k-1)+qv_input(k)))
  576. qvf = 1. + rvovrd*qv_input(k) ! qv is in g/kg here
  577. do it=1,10
  578. pm_input(k) = pm_input(k-1) &
  579. - 0.5*dz*(rho_input(k)+rho_input(k-1))*g*qvf1
  580. rho_input(k) = 1./((r/p1000mb)*th_input(k)*qvf*((pm_input(k)/p1000mb)**cvpm))
  581. enddo
  582. enddo
  583. ! we have the moist sounding
  584. ! next, compute the dry sounding using p at the highest level from the
  585. ! moist sounding and integrating down.
  586. p_input(nl) = pm_input(nl)
  587. do k=nl-1,1,-1
  588. dz = h_input(k+1)-h_input(k)
  589. p_input(k) = p_input(k+1) + 0.5*dz*(rho_input(k)+rho_input(k+1))*g
  590. enddo
  591. do k=1,nl
  592. zk(k) = h_input(k)
  593. p(k) = pm_input(k)
  594. p_dry(k) = p_input(k)
  595. theta(k) = th_input(k)
  596. rho(k) = rho_input(k)
  597. u(k) = u_input(k)
  598. v(k) = v_input(k)
  599. qv(k) = qv_input(k)
  600. enddo
  601. if(debug) then
  602. write(6,*) ' sounding '
  603. write(6,*) ' k height(m) press (Pa) pd(Pa) theta (K) den(kg/m^3) u(m/s) v(m/s) qv(g/g) '
  604. do k=1,nl
  605. write(6,'(1x,i3,8(1x,1pe10.3))') k, zk(k), p(k), p_dry(k), theta(k), rho(k), u(k), v(k), qv(k)
  606. enddo
  607. end if
  608. end subroutine get_sounding
  609. !-------------------------------------------------------
  610. subroutine read_sounding( ps,ts,qvs,h,th,qv,u,v,n,nl,debug )
  611. implicit none
  612. integer n,nl
  613. real ps,ts,qvs,h(n),th(n),qv(n),u(n),v(n)
  614. logical end_of_file
  615. logical debug
  616. integer k
  617. open(unit=10,file='input_sounding',form='formatted',status='old')
  618. rewind(10)
  619. read(10,*) ps, ts, qvs
  620. if(debug) then
  621. write(6,*) ' input sounding surface parameters '
  622. write(6,*) ' surface pressure (mb) ',ps
  623. write(6,*) ' surface pot. temp (K) ',ts
  624. write(6,*) ' surface mixing ratio (g/kg) ',qvs
  625. end if
  626. end_of_file = .false.
  627. k = 0
  628. do while (.not. end_of_file)
  629. read(10,*,end=100) h(k+1), th(k+1), qv(k+1), u(k+1), v(k+1)
  630. k = k+1
  631. if(debug) write(6,'(1x,i3,5(1x,e10.3))') k, h(k), th(k), qv(k), u(k), v(k)
  632. go to 110
  633. 100 end_of_file = .true.
  634. 110 continue
  635. enddo
  636. nl = k
  637. close(unit=10,status = 'keep')
  638. end subroutine read_sounding
  639. END MODULE module_initialize_ideal