PageRenderTime 48ms CodeModel.GetById 14ms RepoModel.GetById 0ms app.codeStats 0ms

/wrfv2_fire/dyn_em/module_initialize_b_wave.F

http://github.com/jbeezley/wrf-fire
FORTRAN Legacy | 941 lines | 563 code | 225 blank | 153 comment | 10 complexity | 48ad8f3b15bdc2118fba03eee6298cc3 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
  7. USE module_io_domain
  8. USE module_state_description
  9. USE module_model_constants
  10. USE module_bc
  11. USE module_timing
  12. USE module_configure
  13. USE module_init_utilities
  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. ! Local data
  57. INTEGER, PARAMETER :: nl_max = 1000
  58. REAL, DIMENSION(nl_max) :: zk, p_in, theta, rho, u, v, qv, pd_in
  59. INTEGER :: nl_in
  60. INTEGER :: icm,jcm, ii, im1, jj, jm1, loop, error, fid, nxc, nyc
  61. REAL :: u_mean,v_mean, f0, p_surf, p_level, qvf, z_at_v, z_at_u
  62. REAL :: z_scale, xrad, yrad, zrad, rad, delt, cof1, cof2
  63. ! REAL, EXTERNAL :: interp_0
  64. REAL :: hm
  65. REAL :: pi
  66. ! stuff from original initialization that has been dropped from the Registry
  67. REAL :: vnu, xnu, xnus, dinit0, cbh, p0_temp, t0_temp, zd, zt
  68. REAL :: qvf1, qvf2, pd_surf
  69. INTEGER :: it
  70. LOGICAL :: moisture_init
  71. LOGICAL :: stretch_grid, dry_sounding, debug
  72. ! kludge space for initial jet
  73. INTEGER, parameter :: nz_jet=64, ny_jet=80
  74. REAL, DIMENSION(nz_jet, ny_jet) :: u_jet, rho_jet, th_jet, z_jet
  75. ! perturbation parameters
  76. REAL, PARAMETER :: htbub=8000., radbub=2000000., radz=8000., tpbub=1.0
  77. REAL :: piov2, tp
  78. INTEGER :: icen, jcen
  79. real :: thtmp, ptmp, temp(3)
  80. SELECT CASE ( model_data_order )
  81. CASE ( DATA_ORDER_ZXY )
  82. kds = grid%sd31 ; kde = grid%ed31 ;
  83. ids = grid%sd32 ; ide = grid%ed32 ;
  84. jds = grid%sd33 ; jde = grid%ed33 ;
  85. kms = grid%sm31 ; kme = grid%em31 ;
  86. ims = grid%sm32 ; ime = grid%em32 ;
  87. jms = grid%sm33 ; jme = grid%em33 ;
  88. kts = grid%sp31 ; kte = grid%ep31 ; ! note that tile is entire patch
  89. its = grid%sp32 ; ite = grid%ep32 ; ! note that tile is entire patch
  90. jts = grid%sp33 ; jte = grid%ep33 ; ! note that tile is entire patch
  91. CASE ( DATA_ORDER_XYZ )
  92. ids = grid%sd31 ; ide = grid%ed31 ;
  93. jds = grid%sd32 ; jde = grid%ed32 ;
  94. kds = grid%sd33 ; kde = grid%ed33 ;
  95. ims = grid%sm31 ; ime = grid%em31 ;
  96. jms = grid%sm32 ; jme = grid%em32 ;
  97. kms = grid%sm33 ; kme = grid%em33 ;
  98. its = grid%sp31 ; ite = grid%ep31 ; ! note that tile is entire patch
  99. jts = grid%sp32 ; jte = grid%ep32 ; ! note that tile is entire patch
  100. kts = grid%sp33 ; kte = grid%ep33 ; ! note that tile is entire patch
  101. CASE ( DATA_ORDER_XZY )
  102. ids = grid%sd31 ; ide = grid%ed31 ;
  103. kds = grid%sd32 ; kde = grid%ed32 ;
  104. jds = grid%sd33 ; jde = grid%ed33 ;
  105. ims = grid%sm31 ; ime = grid%em31 ;
  106. kms = grid%sm32 ; kme = grid%em32 ;
  107. jms = grid%sm33 ; jme = grid%em33 ;
  108. its = grid%sp31 ; ite = grid%ep31 ; ! note that tile is entire patch
  109. kts = grid%sp32 ; kte = grid%ep32 ; ! note that tile is entire patch
  110. jts = grid%sp33 ; jte = grid%ep33 ; ! note that tile is entire patch
  111. END SELECT
  112. piov2 = 2.*atan(1.0)
  113. icen = ide/4
  114. jcen = jde/2
  115. stretch_grid = .true.
  116. delt = 0.
  117. z_scale = .50
  118. pi = 2.*asin(1.0)
  119. write(6,*) ' pi is ',pi
  120. nxc = (ide-ids)/4
  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%ht(i,j) = 0.
  147. grid%msftx(i,j) = 1.
  148. grid%msfty(i,j) = 1.
  149. grid%msfux(i,j) = 1.
  150. grid%msfuy(i,j) = 1.
  151. grid%msfvx(i,j) = 1.
  152. grid%msfvx_inv(i,j)= 1.
  153. grid%msfvy(i,j) = 1.
  154. grid%sina(i,j) = 0.
  155. grid%cosa(i,j) = 1.
  156. grid%e(i,j) = 0.
  157. grid%f(i,j) = 1.e-04
  158. END DO
  159. END DO
  160. DO j = jts, jte
  161. DO k = kts, kte
  162. DO i = its, ite
  163. grid%ww(i,k,j) = 0.
  164. END DO
  165. END DO
  166. END DO
  167. grid%step_number = 0
  168. ! set up the grid
  169. IF (stretch_grid) THEN ! exponential stretch for eta (nearly constant dz)
  170. DO k=1, kde
  171. grid%znw(k) = (exp(-(k-1)/float(kde-1)/z_scale) - exp(-1./z_scale))/ &
  172. (1.-exp(-1./z_scale))
  173. ENDDO
  174. ELSE
  175. DO k=1, kde
  176. grid%znw(k) = 1. - float(k-1)/float(kde-1)
  177. ENDDO
  178. ENDIF
  179. DO k=1, kde-1
  180. grid%dnw(k) = grid%znw(k+1) - grid%znw(k)
  181. grid%rdnw(k) = 1./grid%dnw(k)
  182. grid%znu(k) = 0.5*(grid%znw(k+1)+grid%znw(k))
  183. ENDDO
  184. DO k=2, kde-1
  185. grid%dn(k) = 0.5*(grid%dnw(k)+grid%dnw(k-1))
  186. grid%rdn(k) = 1./grid%dn(k)
  187. grid%fnp(k) = .5* grid%dnw(k )/grid%dn(k)
  188. grid%fnm(k) = .5* grid%dnw(k-1)/grid%dn(k)
  189. ENDDO
  190. cof1 = (2.*grid%dn(2)+grid%dn(3))/(grid%dn(2)+grid%dn(3))*grid%dnw(1)/grid%dn(2)
  191. cof2 = grid%dn(2) /(grid%dn(2)+grid%dn(3))*grid%dnw(1)/grid%dn(3)
  192. grid%cf1 = grid%fnp(2) + cof1
  193. grid%cf2 = grid%fnm(2) - cof1 - cof2
  194. grid%cf3 = cof2
  195. grid%cfn = (.5*grid%dnw(kde-1)+grid%dn(kde-1))/grid%dn(kde-1)
  196. grid%cfn1 = -.5*grid%dnw(kde-1)/grid%dn(kde-1)
  197. grid%rdx = 1./config_flags%dx
  198. grid%rdy = 1./config_flags%dy
  199. ! get the sounding from the ascii sounding file, first get dry sounding and
  200. ! calculate base state
  201. write(6,*) ' reading input jet sounding '
  202. call read_input_jet( u_jet, rho_jet, th_jet, z_jet, nz_jet, ny_jet )
  203. write(6,*) ' getting dry sounding for base state '
  204. write(6,*) ' using middle column in jet sounding, j = ',ny_jet/2
  205. dry_sounding = .true.
  206. dry_sounding = .true.
  207. debug = .true. ! this will produce print of the sounding
  208. CALL get_sounding( zk, p_in, pd_in, theta, rho, u, v, qv, dry_sounding, &
  209. nl_max, nl_in, u_jet, rho_jet, th_jet, z_jet, &
  210. nz_jet, ny_jet, ny_jet/2, debug )
  211. write(6,*) ' returned from reading sounding, nl_in is ',nl_in
  212. ! find ptop for the desired ztop (ztop is input from the namelist),
  213. ! and find surface pressure
  214. ! For the jet, using the middle column for the base state means that
  215. ! we will be extrapolating above the highest height data to the south
  216. ! of the centerline.
  217. grid%p_top = interp_0( p_in, zk, config_flags%ztop, nl_in )
  218. DO j=jts,jte
  219. DO i=its,ite ! flat surface
  220. grid%phb(i,1,j) = 0.
  221. grid%php(i,1,j) = 0.
  222. grid%ph0(i,1,j) = 0.
  223. grid%ht(i,j) = 0.
  224. ENDDO
  225. ENDDO
  226. DO J = jts, jte
  227. DO I = its, ite
  228. p_surf = interp_0( p_in, zk, grid%phb(i,1,j)/g, nl_in )
  229. grid%mub(i,j) = p_surf-grid%p_top
  230. ! this is dry hydrostatic sounding (base state), so given grid%p (coordinate),
  231. ! interp theta (from interp) and compute 1/rho from eqn. of state
  232. DO K = 1, kte-1
  233. p_level = grid%znu(k)*(p_surf - grid%p_top) + grid%p_top
  234. grid%pb(i,k,j) = p_level
  235. grid%t_init(i,k,j) = interp_0( theta, p_in, p_level, nl_in ) - 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. ENDDO
  238. ! calc hydrostatic balance (alternatively we could interp the geopotential from the
  239. ! sounding, but this assures that the base state is in exact hydrostatic balance with
  240. ! respect to the model eqns.
  241. DO k = 2,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. write(6,*) ' ptop is ',grid%p_top
  247. write(6,*) ' base state grid%mub(1,1), p_surf is ',grid%mub(1,1),grid%mub(1,1)+grid%p_top
  248. ! calculate full state for each column - this includes moisture.
  249. write(6,*) ' getting grid%moist sounding for full state '
  250. dry_sounding = .true.
  251. IF (config_flags%mp_physics /= 0) dry_sounding = .false.
  252. DO J = jts, min(jde-1,jte)
  253. ! get sounding for this point
  254. debug = .false. ! this will turn off print of the sounding
  255. CALL get_sounding( zk, p_in, pd_in, theta, rho, u, v, qv, dry_sounding, &
  256. nl_max, nl_in, u_jet, rho_jet, th_jet, z_jet, &
  257. nz_jet, ny_jet, j, debug )
  258. DO I = its, min(ide-1,ite)
  259. ! we could just do the first point in "i" and copy from there, but we'll
  260. ! be lazy and do all the points as if they are all, independent
  261. ! At this point grid%p_top is already set. find the DRY mass in the column
  262. ! by interpolating the DRY pressure.
  263. pd_surf = interp_0( pd_in, zk, grid%phb(i,1,j)/g, nl_in )
  264. ! compute the perturbation mass and the full mass
  265. grid%mu_1(i,j) = pd_surf-grid%p_top - grid%mub(i,j)
  266. grid%mu_2(i,j) = grid%mu_1(i,j)
  267. grid%mu0(i,j) = grid%mu_1(i,j) + grid%mub(i,j)
  268. ! given the dry pressure and coordinate system, interp the potential
  269. ! temperature and qv
  270. do k=1,kde-1
  271. p_level = grid%znu(k)*(pd_surf - grid%p_top) + grid%p_top
  272. grid%moist(i,k,j,P_QV) = interp_0( qv, pd_in, p_level, nl_in )
  273. grid%t_1(i,k,j) = interp_0( theta, pd_in, p_level, nl_in ) - t0
  274. grid%t_2(i,k,j) = grid%t_1(i,k,j)
  275. enddo
  276. ! integrate the hydrostatic equation (from the RHS of the bigstep
  277. ! vertical momentum equation) down from the top to get grid%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,1,-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, grid%al (inverse density)
  302. ! is computed from the geopotential.
  303. grid%ph_1(i,1,j) = 0.
  304. DO k = 2,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. ! interp u
  312. DO K = 1, kte
  313. p_level = grid%znu(k)*(p_surf - grid%p_top) + grid%p_top
  314. grid%u_1(i,k,j) = interp_0( u, p_in, p_level, nl_in )
  315. grid%u_2(i,k,j) = grid%u_1(i,k,j)
  316. ENDDO
  317. ENDDO
  318. ENDDO
  319. ! thermal perturbation to kick off convection
  320. write(6,*) ' nxc, nyc for perturbation ',nxc,nyc
  321. write(6,*) ' delt for perturbation ',tpbub
  322. DO J = jts, min(jde-1,jte)
  323. yrad = config_flags%dy*float(j-jde/2-1)/radbub
  324. DO I = its, min(ide-1,ite)
  325. xrad = float(i-1)/float(ide-ids)
  326. DO K = 1, kte-1
  327. ! put in preturbation theta (bubble) and recalc density. note,
  328. ! the mass in the column is not changing, so when theta changes,
  329. ! we recompute density and geopotential
  330. zrad = 0.5*(grid%ph_1(i,k,j)+grid%ph_1(i,k+1,j) &
  331. +grid%phb(i,k,j)+grid%phb(i,k+1,j))/g
  332. zrad = (zrad-htbub)/radz
  333. RAD=SQRT(yrad*yrad+zrad*zrad)
  334. IF(RAD <= 1.) THEN
  335. tp = tpbub*cos(rad*piov2)*cos(rad*piov2)*cos(xrad*2*pi+pi)
  336. grid%t_1(i,k,j)=grid%t_1(i,k,j)+tp
  337. grid%t_2(i,k,j)=grid%t_1(i,k,j)
  338. qvf = 1. + rvovrd*grid%moist(i,k,j,P_QV)
  339. grid%alt(i,k,j) = (r_d/p1000mb)*(grid%t_1(i,k,j)+t0)*qvf* &
  340. (((grid%p(i,k,j)+grid%pb(i,k,j))/p1000mb)**cvpm)
  341. grid%al(i,k,j) = grid%alt(i,k,j) - grid%alb(i,k,j)
  342. ENDIF
  343. ENDDO
  344. ! rebalance hydrostatically
  345. DO k = 2,kte
  346. grid%ph_1(i,k,j) = grid%ph_1(i,k-1,j) - (1./grid%rdnw(k-1))*( &
  347. (grid%mub(i,j)+grid%mu_1(i,j))*grid%al(i,k-1,j)+ &
  348. grid%mu_1(i,j)*grid%alb(i,k-1,j) )
  349. grid%ph_2(i,k,j) = grid%ph_1(i,k,j)
  350. grid%ph0(i,k,j) = grid%ph_1(i,k,j) + grid%phb(i,k,j)
  351. ENDDO
  352. ENDDO
  353. ENDDO
  354. !#endif
  355. write(6,*) ' grid%mu_1 from comp ', grid%mu_1(1,1)
  356. write(6,*) ' pert state sounding from comp, grid%ph_1, pp, grid%al, grid%t_1, qv '
  357. do k=1,kde-1
  358. write(6,'(i3,1x,5(1x,1pe10.3))') k, grid%ph_1(1,k,1),grid%p(1,k,1), grid%al(1,k,1), &
  359. grid%t_1(1,k,1), grid%moist(1,k,1,P_QV)
  360. enddo
  361. write(6,*) ' grid%mu_1 from comp ', grid%mu_1(1,1)
  362. write(6,*) ' full state sounding from comp, ph, grid%p, grid%al, grid%t_1, qv '
  363. write(6,*) ' at j = 1 '
  364. do k=1,kde-1
  365. write(6,'(i3,1x,5(1x,1pe10.3))') k, grid%ph_1(1,k,1)+grid%phb(1,k,1), &
  366. grid%p(1,k,1)+grid%pb(1,k,1), grid%al(1,k,1)+grid%alb(1,k,1), &
  367. grid%t_1(1,k,1)+t0, grid%moist(1,k,1,P_QV)
  368. enddo
  369. write(6,*) ' full state sounding from comp, ph, grid%p, grid%al, grid%t_1, qv '
  370. write(6,*) ' at j = jde/2 '
  371. do k=1,kde-1
  372. write(6,'(i3,1x,5(1x,1pe10.3))') k, grid%ph_1(1,k,jde/2)+grid%phb(1,k,jde/2), &
  373. grid%p(1,k,jde/2)+grid%pb(1,k,jde/2), grid%al(1,k,jde/2)+grid%alb(1,k,jde/2), &
  374. grid%t_1(1,k,jde/2)+t0, grid%moist(1,k,jde/2,P_QV)
  375. enddo
  376. write(6,*) ' full state sounding from comp, ph, grid%p, grid%al, grid%t_1, qv '
  377. write(6,*) ' at j = jde-1 '
  378. do k=1,kde-1
  379. write(6,'(i3,1x,5(1x,1pe10.3))') k, grid%ph_1(1,k,jde-1)+grid%phb(1,k,jde-1), &
  380. grid%p(1,k,jde-1)+grid%pb(1,k,jde-1), grid%al(1,k,jde-1)+grid%alb(1,k,jde-1), &
  381. grid%t_1(1,k,jde-1)+t0, grid%moist(1,k,jde-1,P_QV)
  382. enddo
  383. ! set v
  384. DO J = jts, jte
  385. DO I = its, min(ide-1,ite)
  386. DO K = 1, kte
  387. grid%v_1(i,k,j) = 0.
  388. grid%v_2(i,k,j) = grid%v_1(i,k,j)
  389. ENDDO
  390. ENDDO
  391. ENDDO
  392. ! fill out last i row for u
  393. DO J = jts, min(jde-1,jte)
  394. DO I = ite, ite
  395. DO K = 1, kte
  396. grid%u_1(i,k,j) = grid%u_1(its,k,j)
  397. grid%u_2(i,k,j) = grid%u_2(its,k,j)
  398. ENDDO
  399. ENDDO
  400. ENDDO
  401. ! set w
  402. DO J = jts, min(jde-1,jte)
  403. DO K = kts, kte
  404. DO I = its, min(ide-1,ite)
  405. grid%w_1(i,k,j) = 0.
  406. grid%w_2(i,k,j) = 0.
  407. ENDDO
  408. ENDDO
  409. ENDDO
  410. ! set a few more things
  411. DO J = jts, min(jde-1,jte)
  412. DO K = kts, kte-1
  413. DO I = its, min(ide-1,ite)
  414. grid%h_diabatic(i,k,j) = 0.
  415. ENDDO
  416. ENDDO
  417. ENDDO
  418. DO k=1,kte-1
  419. grid%t_base(k) = grid%t_1(1,k,1)
  420. grid%qv_base(k) = grid%moist(1,k,1,P_QV)
  421. grid%u_base(k) = grid%u_1(1,k,1)
  422. grid%v_base(k) = grid%v_1(1,k,1)
  423. ENDDO
  424. DO J = jts, min(jde-1,jte)
  425. DO I = its, min(ide-1,ite)
  426. thtmp = grid%t_2(i,1,j)+t0
  427. ptmp = grid%p(i,1,j)+grid%pb(i,1,j)
  428. temp(1) = thtmp * (ptmp/p1000mb)**rcp
  429. thtmp = grid%t_2(i,2,j)+t0
  430. ptmp = grid%p(i,2,j)+grid%pb(i,2,j)
  431. temp(2) = thtmp * (ptmp/p1000mb)**rcp
  432. thtmp = grid%t_2(i,3,j)+t0
  433. ptmp = grid%p(i,3,j)+grid%pb(i,3,j)
  434. temp(3) = thtmp * (ptmp/p1000mb)**rcp
  435. grid%tsk(I,J)=grid%cf1*temp(1)+grid%cf2*temp(2)+grid%cf3*temp(3)
  436. if (i .eq. 1) print*,'sfctem',j,temp(1),temp(2),temp(3),grid%tsk(I,J)
  437. grid%tmn(I,J)=grid%tsk(I,J)-0.5
  438. ENDDO
  439. ENDDO
  440. RETURN
  441. END SUBROUTINE init_domain_rk
  442. !---------------------------------------------------------------------
  443. SUBROUTINE init_module_initialize
  444. END SUBROUTINE init_module_initialize
  445. !---------------------------------------------------------------------
  446. #if 0
  447. ! TEST DRIVER FOR "read_input_jet" and "get_sounding"
  448. implicit none
  449. integer, parameter :: nz_jet=64, ny_jet=80
  450. real, dimension(nz_jet,ny_jet) :: u_jet, rho_jet, &
  451. th_jet, z_jet
  452. real, dimension(nz_jet,ny_jet) :: zk,p,p_dry,theta,rho,u,v,qv
  453. logical :: dry, debug
  454. integer :: j, nl
  455. call read_input_jet( u_jet, rho_jet, th_jet, z_jet, nz_jet, ny_jet )
  456. call opngks
  457. call parray( u_jet, nz_jet, ny_jet)
  458. call parray( rho_jet, nz_jet, ny_jet)
  459. call parray( th_jet, nz_jet, ny_jet)
  460. ! call clsgks
  461. ! set up initial jet
  462. debug = .true.
  463. dry = .true.
  464. do j=1,ny_jet
  465. call get_sounding( zk(:,j),p(:,j),p_dry(:,j),theta(:,j), &
  466. rho(:,j),u(:,j), v(:,j), qv(:,j), &
  467. dry, nz_jet, nl, u_jet, rho_jet, th_jet, &
  468. z_jet, nz_jet, ny_jet, j, debug )
  469. debug = .false.
  470. enddo
  471. write(6,*) ' lowest level p, th, and rho, highest level p '
  472. do j=1,ny_jet
  473. write(6,*) j, p(1,j),theta(1,j),rho(1,j), p(nz_jet,j)
  474. ! write(6,*) j, p(1,j),theta(1,j)-th_jet(1,j),rho(1,j)-rho_jet(1,j)
  475. enddo
  476. call parray( p, nz_jet, ny_jet)
  477. call parray( p_dry, nz_jet, ny_jet)
  478. call parray( theta, nz_jet, ny_jet)
  479. call clsgks
  480. end
  481. !---------------------------------
  482. subroutine parray(a,m,n)
  483. dimension a(m,n)
  484. dimension b(n,m)
  485. do i=1,m
  486. do j=1,n
  487. b(j,i) = a(i,j)
  488. enddo
  489. enddo
  490. write(6,'('' dimensions m,n '',2i6)')m,n
  491. call set(.05,.95,.05,.95,0.,1.,0.,1.,1)
  492. call perim(4,5,4,5)
  493. call setusv('LW',2000)
  494. ! CALL CONREC(a,m,m,n,cmax,cmin,cinc,-1,-638,-922)
  495. CALL CONREC(b,n,n,m,0.,0.,0.,-1,-638,-922)
  496. call frame
  497. return
  498. end
  499. ! END TEST DRIVER FOR "read_input_jet" and "get_sounding"
  500. #endif
  501. !------------------------------------------------------------------
  502. subroutine get_sounding( zk, p, p_dry, theta, rho, &
  503. u, v, qv, dry, nl_max, nl_in, &
  504. u_jet, rho_jet, th_jet, z_jet, &
  505. nz_jet, ny_jet, j_point, debug )
  506. implicit none
  507. integer nl_max, nl_in
  508. real zk(nl_max), p(nl_max), theta(nl_max), rho(nl_max), &
  509. u(nl_max), v(nl_max), qv(nl_max), p_dry(nl_max)
  510. logical dry
  511. integer nz_jet, ny_jet, j_point
  512. real, dimension(nz_jet, ny_jet) :: u_jet, rho_jet, th_jet, z_jet
  513. integer n
  514. parameter(n=1000)
  515. logical debug
  516. ! input sounding data
  517. real p_surf, th_surf, qv_surf
  518. real pi_surf, pi(n)
  519. real h_input(n), th_input(n), qv_input(n), u_input(n), v_input(n)
  520. ! diagnostics
  521. real rho_surf, p_input(n), rho_input(n)
  522. real pm_input(n) ! this are for full moist sounding
  523. ! local data
  524. real r
  525. parameter (r = r_d)
  526. integer k, it, nl
  527. real qvf, qvf1, dz
  528. ! first, read the sounding
  529. ! call read_sounding( p_surf, th_surf, qv_surf, &
  530. ! h_input, th_input, qv_input, u_input, v_input,n, nl, debug )
  531. call calc_jet_sounding( p_surf, th_surf, qv_surf, &
  532. h_input, th_input, qv_input, u_input, v_input, &
  533. n, nl, debug, u_jet, rho_jet, th_jet, z_jet, j_point, &
  534. nz_jet, ny_jet, dry )
  535. nl = nz_jet
  536. if(dry) then
  537. do k=1,nl
  538. qv_input(k) = 0.
  539. enddo
  540. endif
  541. if(debug) write(6,*) ' number of input levels = ',nl
  542. nl_in = nl
  543. if(nl_in .gt. nl_max ) then
  544. write(6,*) ' too many levels for input arrays ',nl_in,nl_max
  545. call wrf_error_fatal ( ' too many levels for input arrays ' )
  546. end if
  547. ! compute diagnostics,
  548. ! first, convert qv(g/kg) to qv(g/g)
  549. !
  550. ! do k=1,nl
  551. ! qv_input(k) = 0.001*qv_input(k)
  552. ! enddo
  553. ! p_surf = 100.*p_surf ! convert to pascals
  554. qvf = 1. + rvovrd*qv_input(1)
  555. rho_surf = 1./((r/p1000mb)*th_surf*qvf*((p_surf/p1000mb)**cvpm))
  556. pi_surf = (p_surf/p1000mb)**(r/cp)
  557. if(debug) then
  558. write(6,*) ' surface density is ',rho_surf
  559. write(6,*) ' surface pi is ',pi_surf
  560. end if
  561. ! integrate moist sounding hydrostatically, starting from the
  562. ! specified surface pressure
  563. ! -> first, integrate from surface to lowest level
  564. qvf = 1. + rvovrd*qv_input(1)
  565. qvf1 = 1. + qv_input(1)
  566. rho_input(1) = rho_surf
  567. dz = h_input(1)
  568. do it=1,10
  569. pm_input(1) = p_surf &
  570. - 0.5*dz*(rho_surf+rho_input(1))*g*qvf1
  571. rho_input(1) = 1./((r/p1000mb)*th_input(1)*qvf*((pm_input(1)/p1000mb)**cvpm))
  572. enddo
  573. ! integrate up the column
  574. do k=2,nl
  575. rho_input(k) = rho_input(k-1)
  576. dz = h_input(k)-h_input(k-1)
  577. qvf1 = 0.5*(2.+(qv_input(k-1)+qv_input(k)))
  578. qvf = 1. + rvovrd*qv_input(k) ! qv is in g/kg here
  579. do it=1,10
  580. pm_input(k) = pm_input(k-1) &
  581. - 0.5*dz*(rho_input(k)+rho_input(k-1))*g*qvf1
  582. rho_input(k) = 1./((r/p1000mb)*th_input(k)*qvf*((pm_input(k)/p1000mb)**cvpm))
  583. enddo
  584. enddo
  585. ! we have the moist sounding
  586. ! next, compute the dry sounding using p at the highest level from the
  587. ! moist sounding and integrating down.
  588. p_input(nl) = pm_input(nl)
  589. do k=nl-1,1,-1
  590. dz = h_input(k+1)-h_input(k)
  591. p_input(k) = p_input(k+1) + 0.5*dz*(rho_input(k)+rho_input(k+1))*g
  592. enddo
  593. do k=1,nl
  594. zk(k) = h_input(k)
  595. p(k) = pm_input(k)
  596. p_dry(k) = p_input(k)
  597. theta(k) = th_input(k)
  598. rho(k) = rho_input(k)
  599. u(k) = u_input(k)
  600. v(k) = v_input(k)
  601. qv(k) = qv_input(k)
  602. enddo
  603. if(debug) then
  604. write(6,*) ' sounding '
  605. write(6,*) ' k height(m) press (Pa) pd(Pa) theta (K) den(kg/m^3) u(m/s) v(m/s) qv(g/g) '
  606. do k=1,nl
  607. 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)
  608. enddo
  609. end if
  610. end subroutine get_sounding
  611. !------------------------------------------------------------------
  612. subroutine calc_jet_sounding( p_surf, th_surf, qv_surf, &
  613. h, th, qv, u, v, n, nl, debug, &
  614. u_jet, rho_jet, th_jet, z_jet, &
  615. jp, nz_jet, ny_jet, dry )
  616. implicit none
  617. integer :: n, nl, jp, nz_jet, ny_jet
  618. real, dimension(nz_jet, ny_jet) :: u_jet, rho_jet, th_jet, z_jet
  619. real, dimension(n) :: h,th,qv,u,v
  620. real :: p_surf, th_surf, qv_surf
  621. logical :: debug, dry
  622. real, dimension(1:nz_jet) :: rho, rel_hum, p
  623. integer :: k
  624. ! some local stuff
  625. real :: tmppi, es, qvs, temperature
  626. ! get sounding from column jp
  627. do k=1,nz_jet
  628. h(k) = z_jet(k,jp)
  629. th(k) = th_jet(k,jp)
  630. qv(k) = 0.
  631. rho(k) = rho_jet(k,jp)
  632. u(k) = u_jet(k,jp)
  633. v(k) = 0.
  634. enddo
  635. if (.not.dry) then
  636. DO k=1,nz_jet
  637. if(h(k) .gt. 8000.) then
  638. rel_hum(k)=0.1
  639. else
  640. rel_hum(k)=(1.-0.90*(h(k)/8000.)**1.25)
  641. end if
  642. rel_hum(k) = min(0.7,rel_hum(k))
  643. ENDDO
  644. else
  645. do k=1,nz_jet
  646. rel_hum(k) = 0.
  647. enddo
  648. endif
  649. ! next, compute pressure
  650. do k=1,nz_jet
  651. p(k) = p1000mb*(R_d*rho(k)*th(k)/p1000mb)**cpovcv
  652. enddo
  653. ! here we adjust for fixed moisture profile
  654. IF (.not.dry) THEN
  655. ! here we assume the input theta is th_v, so we reset theta accordingly
  656. DO k=1,nz_jet
  657. tmppi=(p(k)/p1000mb)**rcp
  658. temperature = tmppi*th(k)
  659. if (temperature .gt. svpt0) then
  660. es = 1000.*svp1*exp(svp2*(temperature-svpt0)/(temperature-svp3))
  661. qvs = ep_2*es/(p(k)-es)
  662. else
  663. es = 1000.*svp1*exp( 21.8745584*(temperature-273.16)/(temperature-7.66) )
  664. qvs = ep_2*es/(p(k)-es)
  665. endif
  666. qv(k) = rel_hum(k)*qvs
  667. th(k) = th(k)/(1.+.61*qv(k))
  668. ENDDO
  669. ENDIF
  670. ! finally, set the surface data. We'll just do a simple extrapolation
  671. p_surf = 1.5*p(1) - 0.5*p(2)
  672. th_surf = 1.5*th(1) - 0.5*th(2)
  673. qv_surf = 1.5*qv(1) - 0.5*qv(2)
  674. end subroutine calc_jet_sounding
  675. !---------------------------------------------------------------------
  676. SUBROUTINE read_input_jet( u, r, t, zk, nz, ny )
  677. implicit none
  678. integer, intent(in) :: nz,ny
  679. real, dimension(nz,ny), intent(out) :: u,r,t,zk
  680. integer :: ny_in, nz_in, j,k
  681. real, dimension(ny,nz) :: field_in
  682. ! this code assumes it is called on processor 0 only
  683. OPEN(unit=10, file='input_jet', form='unformatted', status='old' )
  684. REWIND(10)
  685. read(10) ny_in,nz_in
  686. if((ny_in /= ny ) .or. (nz_in /= nz)) then
  687. write(0,*) ' error in input jet dimensions '
  688. write(0,*) ' ny, ny_input, nz, nz_input ', ny, ny_in, nz,nz_in
  689. write(0,*) ' error exit '
  690. call wrf_error_fatal ( ' error in input jet dimensions ' )
  691. end if
  692. read(10) field_in
  693. do j=1,ny
  694. do k=1,nz
  695. u(k,j) = field_in(j,k)
  696. enddo
  697. enddo
  698. read(10) field_in
  699. do j=1,ny
  700. do k=1,nz
  701. t(k,j) = field_in(j,k)
  702. enddo
  703. enddo
  704. read(10) field_in
  705. do j=1,ny
  706. do k=1,nz
  707. r(k,j) = field_in(j,k)
  708. enddo
  709. enddo
  710. do j=1,ny
  711. do k=1,nz
  712. zk(k,j) = 125. + 250.*float(k-1)
  713. enddo
  714. enddo
  715. end subroutine read_input_jet
  716. END MODULE module_initialize_ideal